Re: [Haskell-cafe] do

2007-10-13 Thread Luke Palmer
On 10/13/07, PR Stanley [EMAIL PROTECTED] wrote:
 Hi
 do, what's its role?
 I know a few uses for it but can't quite understand the semantics -
 e.g. do putStrLn bla bla
 So, what does do, do?

In this example, do doesn't do anything.  do doesn't do anything to a
single expression (well, I think it enforces that its return value is
a monad...).  It's only when you give it multiple expressions that it
rewrites them into more formal notation.  For example:

do putStrLn bla
   putStrLn blah

Will be rewritten into:

putStrLn bla  putStrLn blah

It introduces a block of sequential actions (in a monad), to do each
action one after another.  Both of these (since they're equivalent)
mean print bla *and then* print blah.

do also allows a more imperative-feeling variable binding:

do line - getLine
   putStr You said: 
   putStrLn line

Will be rewritten into:

getLine = (\line - putStr You said:   putStrLn line)

Looking at the do notation again: execute getLine and bind the return
value to the (newly introduced) variable 'line', then print You said:
, then print the value in the variable line.

You can think of the last line in the block as the return value of the
block.  So you can do something like:

do line - do putStr Say something: 
  getLine
   putStr You said: 
   putStrLn line

In this example it's kind of silly, but there are cases where this is useful.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] do

2007-10-13 Thread Luke Palmer
Disclaimer:  I'm explaining all of this in terms of actions, which
are only one way of looking at monads, and the view only works for
certain ones (IO, State, ...).  Without futher ado...

An action does two things:  it has a side-effect and then it has a
return value.  The type IO Int is an I/O action which does something
then returns an Int.

() :: m a - m b - m b

x  y  first does x, *discards* its return value, then does y.  You
can see that the return value of x is discarded by the absence of the
type variable a in the return value of ().  So if you said:

getLine  putStrLn Hello

This is an action which gets a line from the user and then throws it
away, never to be retrieved again, only to print Hello.

(=) :: m a - (a - m b) - m b

But what if you want to do something with the return value?  That's
what (=) is for.  (=) takes an action on its left side and a
function which returns an action on its right, and then pipes one
into the other.

getLine = (\x - putStrLn x)

This gets a line from the user and then executes the function on the
right given the return value from getLine as an argument; i.e. x is
bound to the return value of getLine.  The above can also be written
as:

getLine = putStrLn

Because of currying.  This action echoes one line.

Using this you can do more complex actions, like, for instance, adding
two numbers:

readLine = (\x - readLine = (\y - print (x + y)))

Take a moment to grok that...

Which you might like to write:

do x - readLine
   y - readLine
   print (x + y)

The parser sequencing thing is probably from the List monad (unless
you're using Parsec or something).  List was the first monad I really
understood (before IO even), thanks to this great tutorial:

http://www.haskell.org/haskellwiki/Monads_as_containers

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Pixel plotter

2007-10-14 Thread Luke Palmer
YEEESSS!!   W00t11   I've been looking for that for a long time.  I
get so sick of glut...  Thanks.

Luke

On 10/14/07, Roel van Dijk [EMAIL PROTECTED] wrote:
  I say someone binds SDL[1]. (If it hasn't been done already.)

 Ask and you shall receive:

 http://darcs.haskell.org/~lemmih/hsSDL/

 I use those SDL bindings to plot pixels with OpenGL and play with 3D
 stuff in Haskell.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] haskell-curry, classical logic, excluded middle

2007-10-14 Thread Luke Palmer
On 10/14/07, Tim Newsham [EMAIL PROTECTED] wrote:
 I've been struggling with this for the last day and a half.  I'm
 trying to get some exercise with the type system and with logic by
 playing with the curry-howard correspondence.  I got stuck on
 the excluded-middle, and I think now I got it almost all the way
 there, but its still not quite right.  Is this error I'm getting
 (inline at the end) easily fixed, and what exactly is going on?

I'll admit this is a cursory response, but (to my understanding)
excluded middle doesn't hold in the Curry-Howard correspondence.  It
is an isomorphism between *constructive* logic and types; excluded
middle is a nonconstructive axiom.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange subtract operator behavior - and lazy naturals

2007-10-20 Thread Luke Palmer
On 10/19/07, Yitzchak Gale [EMAIL PROTECTED] wrote:
 So why not make the laziness available
 also for cases where 1 - 2 == 0 does _not_ do
 the right thing?

 data LazyInteger = IntZero | IntSum Bool Integer LazyInteger

 or

 data LazyInteger = LazyInteger Bool Nat

I think

data LazyInteger = IntDiff Nat Nat

would admit implementation of most of the nice properties of this
implementation.  Comparison operators could short circuit when one of
the two naturals is zero.  The only  value which would diverge when
compared to a constant would be infinity - infinity.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type vs TypeClass duality

2007-10-23 Thread Luke Palmer
On 10/23/07, TJ [EMAIL PROTECTED] wrote:
 What I find strange is, if we can have functions with hidden
 parameters, why can't we have the same for, say, elements of a list?

 Suppose that I have a list of type Show a = [a], I imagine that it
 would not be particularly difficult to have GHC insert a hidden item
 along with each value I cons onto the list, in effect making the
 concrete type of the list [(Dictionary Show, a)]. I'm assuming that it
 will not be particularly difficult because GHC will know the types of
 the values I cons onto it, so it will most definitely be able to find
 the Show dictionary implemented by that type, or report a type
 mismatch error. No dynamic type information is necessary.

Which is exactly what happens with:

data Showable = forall a. Show a = Showable a
stuff = [Showable 42, Showable hello, Showable 'w']

 I am not an OO programming zealot, but I'd like to note here that this
 is also how (class based) OO languages would allow the programmer to
 mix types. e.g. I can have a ListShow where the elements can be
 instances of Show, or instances of subclasses of Show.


 Why does this second rate treatment of type classes exist in Haskell?

I think partially the reason is that such polymorphic data structures
are somewhat less useful in Haskell than they are in OO languages.
This may be in part due to the fact that there's no down-casting.  And
certain wrappers, eg. Gtk, emulate up- and down-casting using various
typeclass tricks.

I was in a similar dilemma shortly after I started learning Haskell,
coming from a C++ and Perl background.  I think #perl6 has some logs
of me whining about Haskell's lack of OO features.  How are you
supposed to design your programs modularly if you can't have a
type-agnostic list?

But it doesn't bug me anymore.  I can't really say why.  The natural
solution space in Haskell is so different than that of OO languages,
that you don't really need such existentially polymorphic (just made
up that term) objects[1].  There is still plenty of modularity in
Haskell programs--I would even call it OO, I think--it just looks
different, and took a lot of getting used to.  I had to remap what I
considered an object in my brain.

Anyway, enough preachy.  Typeclasses definitely aren't perfect; global
instance exportation has gotten me in trouble several times.  But,
other than

 [exists a. Show a = a]

What would be a first-rate treatment of type classes to you?  What
kind of features do you want that they don't have?

[1] I hardly ever use them.  When I do use existential types, they are
usually without context, i.e. they fill the role of 'something which I
know nothing about'.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Disjunctive Normal Form

2007-11-01 Thread Luke Palmer
A good way to approach this is data-structure-driven programming.  You
want a data structure which represents, and can _only_ represent,
propositions in DNF.  So:

data Term = Pos Var | Neg Var
type Conj = [Term]
type DNF  = [Conj]

Then write:

dnf :: LS - DNF

The inductive definition of dnf is straightforward given this output type...

Luke

On 11/1/07, Jim Burton [EMAIL PROTECTED] wrote:

 I am trying to rewrite sentences in a logical language into DNF, and wonder
 if someone would point out where I'm going wrong. My dim understanding of it
 is that I need to move And and Not inwards and Or out, but the function
 below fails, for example:

  dnf (Or (And A B) (Or (And C D) E))
 And (Or A (And (Or C E) (Or D E))) (Or B (And (Or C E) (Or D E)))


 data LS = Var | Not LS | And LS LS | Or LS LS
 --convert sentences to DNF
 dnf :: LS - LS
 dnf (And (Or s1 s2) s3) = Or (And (dnf s1) (dnf s3)) (And (dnf s2) (dnf s3))
 dnf (And s1 (Or s2 s3)) = Or (And (dnf s1) (dnf s2)) (And (dnf s1) (dnf s3))
 dnf (And s1 s2) = And (dnf s1) (dnf s2)
 dnf (Or s1 s2)  = Or (dnf s1) (dnf s2)
 dnf (Not (Not d))   = dnf d
 dnf (Not (And s1 s2))   = Or (Not (dnf s1)) (Not (dnf s2))
 dnf (Not (Or s1 s2))= And (Not (dnf s1)) (Not (dnf s2))
 dnf s   = s

 Thanks,

 Jim

 --
 View this message in context: 
 http://www.nabble.com/Disjunctive-Normal-Form-tf4733248.html#a13534567
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Disjunctive Normal Form

2007-11-01 Thread Luke Palmer
On 11/2/07, Luke Palmer [EMAIL PROTECTED] wrote:
 On 11/1/07, Arnar Birgisson [EMAIL PROTECTED] wrote:
  dnf :: LS - DNF
  dnf (Var s) = [[Pos s]]
  dnf (Or l1 l2) = (dnf l1) ++ (dnf l2)
  dnf (And l1 l2) = [t1 ++ t2 | t1 - dnf l1, t2 - dnf l2]
  dnf (Not (Not d)) = dnf d
  dnf (Not (And l1 l2)) = (dnf $ Not l1) ++ (dnf $ Not l2)
  dnf (Not (Or l1 l2)) = [t1 ++ t2 | t1 - dnf $ Not l1, t2 - dnf $ Not l2]

 These two are doing a little extra work:

 dnf (Not (And l1 l2)) = dnf (Or (Not l1) (Not l2))
 dnf (Not (Or l1 l2))  = dnf (And (Not l1) (Not l2))

I should clarify.  I meant that *you* were doing a little extra work,
by re-implementing that logic for the not cases.  I'm a fan of only
implementing each unit of logic in one place, whatever that means.

But to appease the pedantic, my versions are actually doing more
computational work: they are doing one extra pattern match when these
patterns are encountered.  Whoopty-doo.  :-)

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Disjunctive Normal Form

2007-11-01 Thread Luke Palmer
On 11/1/07, Arnar Birgisson [EMAIL PROTECTED] wrote:
 I'm learning too and found this an interesting problem. Luke, is this
 similar to what you meant?

Heh, your program is almost identical to the one I wrote to make sure
I wasn't on crack.  :-)

 data LS = Var String | Not LS | And LS LS | Or LS LS deriving Show

 data Term = Pos String | Neg String deriving Show
 type Conj = [Term]
 type DNF = [Conj]

 dnf :: LS - DNF
 dnf (Var s) = [[Pos s]]
 dnf (Or l1 l2) = (dnf l1) ++ (dnf l2)
 dnf (And l1 l2) = [t1 ++ t2 | t1 - dnf l1, t2 - dnf l2]
 dnf (Not (Not d)) = dnf d
 dnf (Not (And l1 l2)) = (dnf $ Not l1) ++ (dnf $ Not l2)
 dnf (Not (Or l1 l2)) = [t1 ++ t2 | t1 - dnf $ Not l1, t2 - dnf $ Not l2]

These two are doing a little extra work:

dnf (Not (And l1 l2)) = dnf (Or (Not l1) (Not l2))
dnf (Not (Or l1 l2))  = dnf (And (Not l1) (Not l2))

 dnf (Not (Var s)) = [[Neg s]]

 -- test cases
 x = (Or (And (Var A) (Var B)) (Or (And (Not $ Var C) (Var D))
 (Var E)))
 y = (Not (And (Var A) (Var B)))
 z = (Not (And (Not y) y))

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-02 Thread Luke Palmer
On 11/2/07, Isaac Gouy [EMAIL PROTECTED] wrote:
 Ketil Malde wrote:

  [LOC vs gz as a program complexity metric]

 Do either of those make sense as a program /complexity/ metric?

You're right!  We should be using Kolmogorov complexity instead!

I'll go write a program to calculate it for the shootout.  Oh wait...

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Please help from a newby

2007-11-02 Thread Luke Palmer
On 11/2/07, karle [EMAIL PROTECTED] wrote:
 type Address = Int
 data Port = C | D deriving(Eq,Show)
 data Payload = UP[Char] | RTDP(Address,Port) deriving(Eq,Show)
 data Pkgtype = RTD | U deriving(Eq,Show)
 type Pkg = (Pkgtype,Address,Payload)
 type Table = [(Address,Port)]
^^
  Two elements

 update_table1::Table - Pkg - Table
 update_table1 [] (t,d,y)  = [(t,d,y)]
   ^^^
Three elements

So there's the error.You probably want to return something like
[(a,p)] where a is an address and p is a port.  I'm trying to figure
out where you would get that information though.  If your payload (the
y parameter in your implementation) is RTDP then you have _two_
addresses (the d parameter and the one in the payload), so I
wouldn't know which one to use, and if your payload is a UP then I
don't know where you would get a port.

On the other hand, I haven't the slightest clue what you're trying to
implement, I was just trying to figure it out based on the types :-)

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monte Carlo Pi calculation (newbie learnings)

2007-11-05 Thread Luke Palmer
On Nov 5, 2007 1:30 PM, Jonathan Cast [EMAIL PROTECTED] wrote:
  main = do

 Get two standard generators (one per dimension)

g0 - newStdGen
g1 - newStdGen

 Get an infinite list of pairs

let pairs = [ (x, y) | x - randoms (-1, 1) g0,
   y - randoms (-1, 1) g1 ]

This will return a list like [(a,b),(a,c),(a,d),(a,e),...].  This
needs to be a parallel comprehension:

let pairs = [ (x,y) | x - randoms (-1,1) g0 | y - randoms (-1,1) g1 ]

(Did I remember that syntax right?)

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange Type Inference

2007-11-05 Thread Luke Palmer
On Nov 5, 2007 2:37 PM, C.M.Brown [EMAIL PROTECTED] wrote:
 Hi,

 I was given a quandary this evening, suppose I have the following code:

 module Test1 where

 import qualified Data.Map as Map

 testFunction :: Ord a = Map.Map a b - Map.Map a b - a - (Maybe b,
 Maybe b)
 testFunction m0 m1 k = (lookup0 k, lookup1 k)
 where
   lookup0 x  = Map.lookup x m0

   lookup1 x  = Map.lookup x m1

 This compiles and type checks fine. However, the only way I could add type
 signatures to lookup0 and lookup1 was to do something along the lines
 of this:

 testFunction :: Ord a = Map.Map a b - Map.Map a b - a - (Maybe b,
 Maybe b)
 testFunction m0 m1 k = (lookup0 k m0, lookup1 k m1)
 where
   lookup0 :: (Monad m, Ord a) = a - Map.Map a b
 - m b
   lookup0 x m0 = Map.lookup x m0

   lookup1 :: (Monad m, Ord a) = a - Map.Map a b
 - m b
   lookup1 x m1 = Map.lookup x m1

 Is there a way to give lookup0 and lookup1 explicit type signatures
 without passing in m0 and m1 as parameters? (So their definitions are the
 same as in the first example) If ghc can infer the type, surely it must
 be possible?

Yes, using a ghc extension of scoped type variables.  In the signature
of testFunction, if you explicitly quantify all your variables with
forall, then they are visible in the where clause (and elsewhere in
the function).

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type/class question: toString

2007-11-06 Thread Luke Palmer
 I'm assuming you're not fond of the way the print function handles
 Strings?

 With GHC you can do this:

  {-# OPTIONS -fallow-overlapping-instances #-}
  {-# OPTIONS -fallow-undecidable-instances #-}
 
  class Show a = MyShow a where show_ :: a - String
  instance MyShow String where show_ s = s
  instance (Show a) = MyShow a where show_ s = show s

I'm curious why this works.  How does GHC know to pick the MyShow String
instance instead of the one coming from Show String?

I expect there's no way to do this without undecidable instances, is there?
I try to stay away from that flag nowadays, since I've seen some strange
unpredictable behavior from it in the past  (the unpredictability of the
behavior may come from the fact that I don't know how the inference algorithm
works).

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monte Carlo Pi calculation (newbie learnings)

2007-11-06 Thread Luke Palmer
On Nov 5, 2007 8:11 PM, Alex Young [EMAIL PROTECTED] wrote:
 {--}
 module Main where

 import Random
 import System.Environment
 import List
 import Monad

 randMax = 32767
 unitRadius = randMax * randMax

 rand :: IO Int
 rand = getStdRandom (randomR (0, randMax))

 randListTail accum 0 = accum
 randListTail accum n = randListTail (rand : accum) (n - 1)

I can't believe that nobody has pointed this out yet.  I think we were
all focused on your weird usage of the IO monad...

Anyway, you do not want to use tail recursion in this case.  Here you
have to evaluate everything before you can return the first element,
because we don't know that you're going to return accum when you get
down to zero... you might return 1:accum or something.  When you're
returning a list, it's best not to use tail recursion because we can
get the initial elements of the list lazily.

randList 0 = []
randList n = rand : randList (n-1)

Is a much better implementation in Haskell.

But that's usually just spelled replicate n rand.  :-)

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FW: please help... small problem

2007-11-09 Thread Luke Palmer
I'm not sure what you mean by not use auxillary functions.  This code
is about as compact as it is going to get if you don't want to use
library functions.

wordToInt is not necessary at all, of course; you could just replace
wordToInt everywhere with read, and type inference will figure out
the types for you.

There is a (very common) library function which does exactly what
method does, but its types are polymorphic.  But you don't want to
use library functions?  That same function will accomplish what test
does very easily.  parseResults is your work horse; really that's the
only function that needs to be there; all the others are just simple
compositions of functions.

I don't see any opportunities to factor any of this logic _into_
pattern matching though.

Luke

On Nov 9, 2007 9:57 PM, Ryan Bloor [EMAIL PROTECTED] wrote:


 sorry heres the code

  I always do that.




  
  From: [EMAIL PROTECTED]
 To: Subject: please help... small problem
 Date: Fri, 9 Nov 2007 21:44:35 +


  hi

 Is there anyway to cut down this code and to not use auxillary functons, but
 instead use pattern matching?

 The code basically splits up a list 'rslis' into a list of lists - but so
 each word is split up and the integers have been parsed. so [hi ryan
 1,hi jeff 2] becomes [[hi,ryan 1], [hi,jeff, 2]].
 The code is far too long. I don't wanna use premade functions too much...
 pattern matching is required.

 Ryan

  
  The next generation of MSN Hotmail has arrived - Windows Live Hotmail
 
 Are you the Quizmaster? Play BrainBattle with a friend now!
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] can someone explain monad transformers to me, or how do you combine maybe and IO?

2007-11-12 Thread Luke Palmer
On Nov 12, 2007 11:59 PM, Anatoly Yakovenko [EMAIL PROTECTED] wrote:
 works just like I want it to.  But isn't this something that a monad
 transformer should be able to do?

Yes.  And I have rewritten MaybeT several times for use in my own projects.

We want MaybeT!

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problems with do notation

2007-11-22 Thread Luke Palmer
On Nov 22, 2007 8:19 AM, Peter Verswyvelen [EMAIL PROTECTED] wrote:
  worksFine =
if True
then putStrLn True
else putStrLn False

This is just an expression, the indentation is inconsequential.

  worksNOT = do
if True
then putStrLn True
else putStrLn False

The first line, if True, sets the indentation level of the
statements in the do to two spaces.  So this is interpreted as

  worksNOT = do {
if True ;
then putStrLn True ;
else putStrLn False
  }

Which is of course illegal.

  worksAgain = do
if True
  then putStrLn True
  else putStrLn False

Here, the indentation level of the do is still two spaces, but then
then and else are at a higher indent than that, so they are
interpreted as part of the preceding expression.  The rules are
actually very simple.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Composing monads

2007-11-23 Thread Luke Palmer
On Nov 23, 2007 6:24 PM, Jules Bean [EMAIL PROTECTED] wrote:
 ...i.e. I wouldn't be afraid of a lambda in a case like that. IME it's
 moderately common to have to do:

 mapM_ (\a - some stuff  something_with a  some stuff) ll

This has terrible endweight.  In this imperativesque case, I'd write:

forM_ li $ \a - do
  some stuff
  something with a
  some stuff

Where forM_ is from Data.Foldable  (but is easily written as flip mapM_).

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] been scouring through the Haskell prelude to no avail ...

2007-11-24 Thread Luke Palmer
Word16 from the Data.Word module.

Luke

On Nov 24, 2007 11:47 PM, Galchin Vasili [EMAIL PROTECTED] wrote:
 Hello,

 Is there any predefined datatype that can be used to represent a two
 byte value?

 Kind regards, Vasili

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about GADTs on ghci

2007-11-27 Thread Luke Palmer
On Nov 27, 2007 12:57 PM, Yu-Teh Shen [EMAIL PROTECTED] wrote:
 i have seen the documents in
 http://www.haskell.org/haskellwiki/Generalised_algebraic_datatype
 but i can not run the following code on ghci

 ex:

 data Term x where
 K :: Term (a - b - a)
 S :: Term ((a - b - c)  - (a - b) - a - c)
 Const :: a - Term a
 (:@) :: Term (a - b) - (Term a) - Term b
 infixl 6 :@

 could any tell me how to run the code?

Put it in a file (eg ski.hs), and run:

  % ghci -fglasgow-exts ski.hs

You cannot enter it directly into ghci; you can't define new data
types interactively.

You can also put the line

{-# OPTIONS_GHC -fglasgow-exts #-}

At the top, to turn on glasgow extensions whenever GHC compiles this file.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] St. Petersburg Game

2007-11-27 Thread Luke Palmer
On Nov 27, 2007 1:27 PM,  [EMAIL PROTECTED] wrote:
 Hello,

 I'm trying to program an implementation of the St. Petersburg game in
 Haskell. There is a coin toss implied, and the random-number generation is
 driving me quite mad. So far, I've tried this:

Yeah, random number generation is one of those things in Haskell that
can be tricky.  But it looks like you're struggling more with the idea
of monadic programming.  That is expected :-)

 import Random

 increment :: Int - Int
 increment b = b + 1

This is unnecessary; it can just be written (+1).  (I.e. wherever you
said increment you could write (+1) instead)

 main =  do  let b = 0
 let c = randomRIO (1,2)
 until (c == 1)  increment b
 return b

You can think of this block as four statements, one after the other.
 the do-until thing doesn't delimit anything, i.e. doesn't work the
way you think it does.   Let me rewrite this so it's clearer what's
going on:


main = do { let b = 0;
let c = randomRIO (1,2);
until (c == 1) increment b;
return b;
  }

In particular, until is a function, and you've given it three
arguments: c == 1 (which is False), increment, and b.

To solve this problem you'll probably want to use recursion, since it
is a loop.  There are higher-order ways to loop, but they all boil
down to recursion in the end.

So let's write a function which does this, call it count:

count :: Int - IO Int

That is the type.  It takes an integer representing the current count,
does some IO and returns an integer.  Specifically, it should take the
current count and flip a coin.  If the coin comes up tails, it should
just return the current count.  It it comes up heads, it should call
itself again with 1 + the current count as an argument.  I'll get you
started

count currentCount = do
coin - randomRIO (1,2)
...

We use - to run an action and get its result; we use let .. = to
define the meaning of a symbol (but nothing is run).  Using let just
gives a shorter name for an expression.

Why don't you try to write the rest?  main will look like:

main = do
flips - count 0
print flips

I also recommend going through a tutorial which others will doubtless
recommend to you until you get to monads (or skip ahead to monads and
see if you understand).

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hit a wall with the type system

2007-11-28 Thread Luke Palmer
On Nov 29, 2007 4:02 AM, Chris Smith [EMAIL PROTECTED] wrote:
 I was talking to a few people about this on #haskell, and it was
 suggested I ask here.  I should say that I'm playing around here; don't
 mistake this for an urgent request or a serious problem.

 Suppose I wanted to implement automatic differentiation of simple
 functions on real numbers; then I'd take the operations from Num,
 Fractional, and Floating, and define how to perform them on pairs of
 values and their differentials, and then I'd write a differentiate
 function... but finding an appropriate type for that function seems to
 be a challenge.

 We have:

 1. Differentiating a function of the most general type (Num a = a - a)
 should produce a result of type (Num a = a - a).

I don't see why this should be true.  Int - Int is an instance of this type,
but derivatives require limits, which integers don't have.  Do you intend to
output the difference sequence of the function in this case?

But then Double - Double is also an instance of this type.  Do you intend
to approximate the real derivative when it's specialized to this?

Instead of worrying about the types, first tell us what semantics you want.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hit a wall with the type system

2007-11-28 Thread Luke Palmer
On Nov 29, 2007 4:31 AM, Luke Palmer [EMAIL PROTECTED] wrote:
 On Nov 29, 2007 4:02 AM, Chris Smith [EMAIL PROTECTED] wrote:
  I was talking to a few people about this on #haskell, and it was
  suggested I ask here.  I should say that I'm playing around here; don't
  mistake this for an urgent request or a serious problem.
 
  Suppose I wanted to implement automatic differentiation of simple
  functions on real numbers; then I'd take the operations from Num,
  Fractional, and Floating, and define how to perform them on pairs of
  values and their differentials, and then I'd write a differentiate
  function... but finding an appropriate type for that function seems to
  be a challenge.

Oh, I think I totally missed the point.  I missed the word simple.

I think the problem is that a function of type Num a = a - a can be any
function whatsoever, it does not have to be a simple combination of operators
(it could, for example, use show, do a string transformation, and then read
the result). So while you can do your AD type, I think a function which
differentiates (Num a = a - a) is not possible using this approach.  You
must resort to numerical methods...

Luke

  We have:
 
  1. Differentiating a function of the most general type (Num a = a - a)
  should produce a result of type (Num a = a - a).

 I don't see why this should be true.  Int - Int is an instance of this type,
 but derivatives require limits, which integers don't have.  Do you intend to
 output the difference sequence of the function in this case?

 But then Double - Double is also an instance of this type.  Do you intend
 to approximate the real derivative when it's specialized to this?

 Instead of worrying about the types, first tell us what semantics you want.

 Luke

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What is the role of $!?

2007-11-28 Thread Luke Palmer
On Nov 29, 2007 4:23 AM, PR Stanley [EMAIL PROTECTED] wrote:
 PRS: You would also get different results - e.g.
 let a = 3, b = 7, c = 2
 therefore 20 = strict ( ( (a+(b*c)) )
 therefore 17 = non-strict ( (a+(b*c)) )

 or am I misunderstanding the concept?

Yes.  If the strict program does not error, then the strict program
and the lazy program will have the same results.

Numerics are not the best way to illustrate the difference, because
they are essentially strict in their semantics.

How about a list function:

head [] = error empty list
head (x:xs)  = x

map f [] = []
map f (x:xs) = f x:map f xs

head (map (+1) [1,2,3])  -- rewrite as...
head (map (+1) (1:2:3:[]))

Strictly would go like this:

head (map (+1) (1:2:3:[]))   -- evaluate map (+1) (1:2:3:[])
head ((1+1) : map (+1) (2:3:[])) -- evaluate 1+1
head (2 : map (+1) (2:3:[])) -- evaluate map (+1) (2:3:[])
head (2 : (2+1) : map (+1) (3:[]))   -- evaluate 2+1
head (2 : 3 : map (+1) (3:[]))   -- evaluate map (+1) (3:[])
head (2 : 3 : (3+1) : [])-- evaluate 3+1
head (2 : 3 : 4 : [])-- evaluate [] (nothing to do)
head (2 : 3 : 4 : [])-- evaluate head
2

Lazily would go like this:

head (map (+1) (1:2:3:[]))   -- evaluate head
 -- try to match map (+1) (1:2:3:[])
 -- against x:xs, need to evaluate map
head ((1+1) : map (+1) (2:3:[]))
 -- evaluate head
 -- match (1+1):map (+1) (2:3:[]) against
 -- x:xs succeeds, with x = (1+1)
(1+1)
 -- evaluate (1+1)
2

Here I'm describing lazy evaluation rather than non-strict semantics,
but they're pretty closely related.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Optimizing cellular automata evaluation (round 2)

2007-11-30 Thread Luke Palmer
On Nov 30, 2007 6:03 PM, Justin Bailey [EMAIL PROTECTED] wrote:
 On Nov 29, 2007 9:11 PM, Jon Harrop [EMAIL PROTECTED] wrote:
  Mathematica uses a single arbitrary-precision integer to represent each
  generation of a 1D automaton. The rules to derive the next generation are
  compiled into arithmetic operations on the integer. The offloads all such
  work onto your big number library and, with GMP, will be as fast in Haskell
  as most other languages.

 Does GHC already use the GMP library for Integer? It looks that way
 but I'm not positive. That'd be ironic, if the higher-level Integer
 representation is faster than a low-level bitwise one ... Still, I
 suspect accessing individual bits might kill me if I'm not able to
 move most of the calculation into a call to the library.

 Do you mind elaborating on how rules are compiled into 'arithmetic'
 operations or providing a link?

Integer is an instance of Bits, so you can just use bitshifts and
bitops to do any 1-D rule.  There might be a more efficient way.

For rule 110:

 111 110 101 100 011 010 001 000
  0   1   1   0   1   1   1   0

Algebraically, that's not (a  b  c || a  not b  not c || not a
 not b  not c)

So just translate that to:

rule z =
 complement ((a .. b .. c) .|. (a .. b' .. c') .|. (a' .. b' .. c'))
  where
  a = z `shift` (-1)
  b = z
  c = z `shift` 1
  a' = complement a
  b' = complement b
  c' = complement c

Modulo some algebra to make it even better, but this should be pretty
darn fast...

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Design of a Physics Interface

2007-11-30 Thread Luke Palmer
I'm currently working on idioms for game programming using FRP.  After
going through several representations of physics as arrows[1] I
decided that physics objects must not be implemented as arrows,
because introducing new arrows in the middle of a computation[2] leads
to ugly pain.

So far the best approach I have is to represent the physics world as a
single object World, with a function

 integrate :: TimeStep - World - World

But I can't figure out a good way to represent bodies in this world.
I considered:

 newBody :: (Position,Velocity) - World - (Body,World)

Where Body is an ADT with an internal representation of an Integer or
something.  The problem with this is that (1) there is no way to
guarantee that a Body actually exists in a World (which is a minor but
still annoying issue), and (2) that there's a possibility that you
could make a Body in one world and use it in another and there would
be no way to detect the error.

(2) could be solved using an internal representation of Data.Unique,
but (1) still remains a problem.  And as long as the function

 deleteBody :: Body - World - World

exists, it will always remain a problem.  Are there any clever idioms
I can use for this interface or implementation?  Is there a way to
store the data for bodies along with the Body object instead of with
the world in a way that the relationships between them respect
different generations of the World (through integrate)?  Any other
ideas?

Thanks,
Luke

[1]  Once as SF () (Position,Velocity), and again as SF PhysIn PhysOut
where PhysIn = (Impulse,Momentum) and PhysOut = (Position,Velocity).

[2] Using the arrow joinSF :: SF (Event (SF [a] a)) [a], and other
similar style functions taking streams of SF events...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Rigid type-var unification failure in existentials used with parametrically polymorphic functions

2007-11-30 Thread Luke Palmer
On Nov 30, 2007 12:20 PM, Pablo Nogueira [EMAIL PROTECTED] wrote:
 A question about existential quantification:

 Given the existential type:

   data Box = forall a. B a

[...]

 I cannot type-check the function:

 mapBox :: forall a b. (a - b) - Box - Box
 --:: forall a b. (a - b) - (exists a.a) - (exists a.a)
 mapBox f (B x) = B (f x)

 However, at first sight |f| is polymorphic so it could be applied to
 any value, included the value hidden in  |Box|.

f is not polymorphic here; mapBox is.

 Of course, this works:

 mapBox :: (forall a b. a - b) - Box - Box
 mapBox f (B x) = B (f x)

Here f is polymorphic.

 Because it's a tautology: given a proof of a - b for any a or b I can
 prove Box - Box. However the only value of type forall a b. a - b is
 bottom.

Yes, but that is only because your Box type is trivial.  It can contain
any value, so you can never extract any information from it.

Let's detrivialize your box and see where that leads us:

data Box = forall a. (Num a) = B a

Then:

mapBox :: (forall a b. (Num a) = a - a) - Box - Box

Should work fine, and there are functions which you can give to mapBox
which are not bottom.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Design of a Physics Interface

2007-11-30 Thread Luke Palmer
On Nov 30, 2007 7:26 PM, Dan Weston [EMAIL PROTECTED] wrote:
 There seems to be three salient benefits of using arrows, as I read the
 Abstract and Introduction of Benjamin Lerner, Arrow Laws and Efficiency
 in Yampa, 2003,
 http://zoo.cs.yale.edu/classes/cs490/03-04a/benjamin.lerner/

 1) The discipline of using arrows assists in avoiding space-leaks
 The reasons underlying this...primarily stemmed from the
  availability of signals as first-class values.
 [the ugly pain you experience up front saves you
  chronic pain later. Self-discipline is the key to a happy life.]

I experienced the chronic pain in my initial comonadic implementation
of FRP.  It was
pretty, but ran in quaadratic time :-(.

To be clear, I am not abandoning arrows in FRP.  I am abandoning using
an arrow to
represent *each* object in favor of moving objects into the value level rather
than the signal level.

i.e. the following dies:

ball :: Position - Velocity - SF PhysIn PhysOut
...

In favor of

game = proc () - do
rec world - integrate initWorld - trajectory world
...

I have an idea for an external solution though that I'm going to play
with now.  I'll
report on how it goes :-)

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: do

2007-12-04 Thread Luke Palmer
On Dec 4, 2007 11:39 AM, Jules Bean [EMAIL PROTECTED] wrote:
 Ben Franksen wrote:
  I don't buy this. As has been noted by others before, IO is a very special
  case, in that it can't be defined in Haskell itself, and there is no
  evaluation function runIO :: IO a - a.

 This is a straw man. Most monads will not have such a function:

When I first learned monads, I heard that once you get into IO, you
can never get out.
The point here was that that doesn't generalize, so a student might
start thinking that
a monad is like a taint flag or something.  Not to say that statement
that it's a complete
falsity when generalized to other monads -- it's reflective of the
algebra of monads --
you just have to define never a little differently. :-)

In any case, I don't think that's a big issue.  While it is important
to eliminate things
that monads aren't from students' possible models, it's better just to
build a good model
in the first place.

FWIW, the list monad was how I made the leap from monads do IO to
monads do nifty stuff.

Luke

 There is no function (State s a) - a.

 There is no function (r - a) - a.

 There is no function (Random a) - a. [assuming some random monad, often
 discussed]

 There is no function (Supply s a) - a. [Another useful monad although
 not one of the standard ones]

 There are no (total) functions Maybe a - a, [a] - a, Either e a - a.



 As to the topic of the thread: I agree IO is an unusual monad. I'm not
 sure if I agree that it shouldn't be used as a teaching basis. I think
 there are all kinds of ways to teach haskell; I'd be inclined to want to
 start with some IO, without explaining the plumbing in detail, and then
 come back to it later with better perspective when discussing general
 monads.

 Jules

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why is this strict in its arguments?

2007-12-05 Thread Luke Palmer
On Dec 5, 2007 12:16 AM, Aaron Denney [EMAIL PROTECTED] wrote:
  we (the FPSIG group) defined:
  data BTree a = Leaf a
   | Branch (BTree a) a (BTree a)

 Totally avoiding your question, but I'm curious as to why you
 deliberately exclude empty trees.

 Come to think of it, how can you represent a tree with two elements?

Indeed, this tree is only capable of representing odd numbers of
elements, which can be shown by straightforward induction.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Luke Palmer
On Dec 5, 2007 11:56 AM, Andrew Coppin [EMAIL PROTECTED] wrote:
 I was merely noting that questions of the form is X decidable? are
 usually undecidable. (It's as if God himself wants to tease us...)

I take issue with your definition of usually then.

Whenever X is decidable is undecidable, 'X is decidable' is decidable' is
decidable, namely false.  So there are at least as many decidable sentences
of the form X is decidable as there are undecidable ones.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Luke Palmer
On Dec 5, 2007 12:30 PM, Andrew Coppin [EMAIL PROTECTED] wrote:

 Luke Palmer wrote:
  On Dec 5, 2007 11:56 AM, Andrew Coppin [EMAIL PROTECTED] wrote:
 
  I was merely noting that questions of the form is X decidable? are
  usually undecidable. (It's as if God himself wants to tease us...)
 
 
  I take issue with your definition of usually then.
 
  Whenever X is decidable is undecidable, 'X is decidable' is decidable' is
  decidable, namely false.  So there are at least as many decidable sentences
  of the form X is decidable as there are undecidable ones.
 

 Ouch... my head hurts.

 OK, well how about I rephrase it as most 'interesting' questions about
 decidability tend to be undecidable and we call it quits? ;-)

Nah, I was just performing a slight-of-hand on you.  Basically by
saying X is decidable
is undecidable, you were implying you could prove it.   Which you
usually can't.  Well,
rather, which you usually don't know if you can...

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] matching

2007-12-05 Thread Luke Palmer
Just remove that if.  What comes after | is already a conditional.

Luke

On Dec 6, 2007 7:03 AM, Ryan Bloor [EMAIL PROTECTED] wrote:

 hi

  I have a matching problem... I am wanting to identify whether or not a
 string is an opening substring of another (ignoring leading spaces). I have
 this:
  word is a single word and str is a string.

  match :: String - String - (Bool, String)
 match word str
   | if removeSpace str `elem` (removeSpace word) ++ rest =
 (True, rest)
   | otherwise == (False,str)
   where rest = str

  Any help?

  Ryan




 
 Can you guess the film? Search Charades!
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] matching

2007-12-05 Thread Luke Palmer
Oops, not quite.  otherwise == should be otherwise =.  Looks like
you already go this from the first one, but guard syntax looks like:

defn
  | cond1 = ...
  | cond2 = ...
  | ...
  | otherwise = ...

(otherwise is not actually necessary; it is just a synonym for True)

Luke

On Dec 6, 2007 7:09 AM, Luke Palmer [EMAIL PROTECTED] wrote:
 Just remove that if.  What comes after | is already a conditional.

 Luke


 On Dec 6, 2007 7:03 AM, Ryan Bloor [EMAIL PROTECTED] wrote:
 
  hi
 
   I have a matching problem... I am wanting to identify whether or not a
  string is an opening substring of another (ignoring leading spaces). I have
  this:
   word is a single word and str is a string.
 
   match :: String - String - (Bool, String)
  match word str
| if removeSpace str `elem` (removeSpace word) ++ rest =
  (True, rest)
| otherwise == (False,str)
where rest = str
 
   Any help?
 
   Ryan
 
 
 
 
  
  Can you guess the film? Search Charades!
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-06 Thread Luke Palmer
On Dec 6, 2007 9:30 AM, Alistair Bayley [EMAIL PROTECTED] wrote:
  Use of isNothing and fromJust and a cascade of ifs is generally a poor
  sign, much better to use case:
 
  findAllPath pred (Branch lf r rt)
   | pred r =
   case (findAllPath pred lf,findAllPath pred rt) of
 (Nothing,Nothing)   - Nothing
 (Nothing,Just rtpaths)  - Just (map (r:) rtpaths)
 (Just lfpaths,Nothing)  - Just (map (r:) lfpaths)
 (Just lfpaths,Just rtpaths) - Just (map (r:) $ rtpaths ++
  lfpaths)
   | otherwise = Nothing
 
  the general pattern is : replace isNothing with a case match on Nothing,
  replace fromJust with a case match on Just, don't be afraid to case two
  expressions at once.

I have actually seen this pattern a lot recently.  Recently I have
started using a function:

mergeMaybes :: (a - a - a) - Maybe a - Maybe a - Maybe a
mergeMaybes f Nothing y = y
mergeMaybes f x Nothing = x
mergeMaybes f (Just x) (Just y) = Just (f x y)

With which findAllPath could be written:

finaAllPath pred (Branch lf r rt)
| pred r= fmap (map (r:)) $ mergeMaybes (++) (findAllPath lf)
(findAllPath rt)
| otherwise = Nothing

Or this more search-like feel:

findAllPath pred (Branch lf r rt) = do
guard (pred r)
subpaths - mergeMaybes (++) (findAllPath lf) (findAllPath rt)
return $ map (r:) subpaths

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Luke Palmer
On Dec 7, 2007 6:27 AM, Victor Nazarov [EMAIL PROTECTED] wrote:
 Cool solution and not so complicated and ad-hoc. But I'd like to ask
 isn't the following definition is more natural and simple?

 nary 0 x [] = x
 nary n f (x:xs) | n  0 = nary (n-1) (f $ read x) xs

Sometimes it helps to write type signatures for functions.  As in this
case, where you'll find you won't be able to...  :-)

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Luke Palmer
On Dec 7, 2007 6:21 PM, Dan Weston [EMAIL PROTECTED] wrote:
 This is great! Two questions:

 1) I want to make sure the function arity matches the list length (as a
 runtime check). I think I can do this with an arity function using
 Data.Typeable. I came up with:

 arity f = a (typeOf f) where
a tr | typeRepTyCon tr /= mkTyCon - = 0
 | otherwise = 1 + (a . fromJust . funResultTy tr . head
  . typeRepArgs $ tr)

 This looks awful. Is there a better way to get the function arity?

 2) Once I have say arity (+) == 2 at runtime, how can I get it reified
 into Succ (Succ Zero)) at compile time to be able to use it as the first
 argument in your nary function? Can/should I use Template Haskell for this?

You can project the compile time numbers into runtime ones:

 class ProjectN n where
 projectN :: n - Int

 instance ProjectN Zero where
 projectN _ = 0

 instance (ProjectN n) = ProjectN (Succ n) where
 projectN _ = 1 + projectN (undefined :: n)

And then make sure the length matches the projected number of
arguments.  Other disagreements will be resolved at compile time.

Luke

 Dan

 Victor Nazarov wrote:
 
  {-# OPTIONS -fglasgow-exts #-}
  {-# OPTIONS -fallow-undecidable-instances #-}
 
  data Zero
  data Succ a
 
  class Nary n x y | n x - y where
nary :: n - x - [String] - y
 
  instance Nary Zero x x where
nary _ x [] = x
 
  instance (Nary n y z, Read x) = Nary (Succ n) (x-y) z where
nary _ f (x:xs) = nary (undefined::n) (f $ read x) xs
 



 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Re: type class question

2007-12-07 Thread Luke Palmer
On Dec 7, 2007 5:57 PM, Peter Padawitz [EMAIL PROTECTED] wrote:
 type Block   = [Command]
 data Command = Skip | Assign String IntE | Cond BoolE Block Block | Loop
 BoolE Block
 data IntE= IntE Int | Var String | Sub IntE IntE | Sum [IntE] | Prod
 [IntE]
 data BoolE   = BoolE Bool | Greater IntE IntE | Not BoolE

 class Java block command intE boolE
where block_ :: [command] - block
  skip :: command
  assign :: String - intE - command
  cond :: boolE - block - block - command
  loop :: boolE - block - command
  intE_ :: Int - intE
  var :: String - intE
  sub :: intE - intE - intE
  sum_ :: [intE] - intE
  prod :: [intE] - intE
  boolE_ :: Bool - boolE
  greater :: intE - intE - boolE
  not_ :: boolE - boolE

  compBlock :: Block - block
  compBlock = block_ . map compCommand

  compCommand :: Command - command
  compCommand Skip   = skip
  compCommand (Assign x e)   = assign x (compIntE e)
  compCommand (Cond be cs cs') = cond (compBoolE be) (compBlock
 cs) (compBlock cs')
  compCommand (Loop be cs)= loop (compBoolE be) (compBlock cs)

  compIntE :: IntE - intE
  compIntE (IntE i)   = intE_ i
  compIntE (Var x)= var x
  compIntE (Sub e e') = sub (compIntE e) (compIntE e')
  compIntE (Sum es)   = sum_ (map compIntE es)
  compIntE (Prod es)  = prod (map kcompIntE es)

  compBoolE :: BoolE - boolE
  compBoolE (BoolE b)  = boolE_ b
  compBoolE (Greater e e') = greater (compIntE e) (compIntE e')
  compBoolE (Not be)   = not_ (compBoolE be)

I'm not sure what this is worth, since you seem to have your mind set
on using this strange four-parameter type class.

You can keep most of the design advantages of using this type at the
cost of being more explicit if you factor it into a data type
yourself:

 data Java block command intE boolE
   = Java { block_ :: [command] - block
  , skip   :: command
  , assign :: String - intE - command
  , ...
  , compBlock :: Block - block
  , ...
  }

For your default implementations:

 defCompBlock :: Java block command intE boolE - Block - block
 defCompBlock self = block_ self . map (compCommand self)

 .. etc

Then to define an example instance:

 javaAST :: Java Block Command IntE BoolE
 javaAST
   = Java { block_ = Block
  , ...
  , compBlock = defCompBlock javaAST
  , ...
  }

Your type errors will be resolved because you are saying explicitly
which instance to use by passing the instance data structure you want
explicitly.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Luke Palmer
On Dec 7, 2007 8:39 PM, Dan Weston [EMAIL PROTECTED] wrote:
  compose f g = f . g
 
  compose' f g x = f (g x)
 
  Are you saying that these two exactly equivalent functions should have
  different arity?   If not, then is the arity 2 or 3?

 Prelude :t let compose f g = f . g in compose
 let compose f g = f . g in compose :: (b - c) - (a - b) - a - c
 Prelude :t let compose' f g x = f (g x) in compose'
 let compose' f g x = f (g x) in compose' :: (t - t1) - (t2 - t) - t2
 - t1

 The arity is the number of top-level -

 Both are arity 3.


Hmm, this still seems ill-defined to me.

compose :: (Int - Int - Int) - (Int - Int) - Int - Int - Int

Is a valid expression given that definition (with a,b = Int and c = Int - Int),
but now the arity is 4.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Luke Palmer
On Dec 7, 2007 7:57 PM, Luke Palmer [EMAIL PROTECTED] wrote:
 On Dec 7, 2007 7:41 PM, Dan Weston [EMAIL PROTECTED] wrote:
  Luke Palmer wrote:
   You can project the compile time numbers into runtime ones:
 
  Yes, that works well if I know a priori what the arity of the function
  is. But I want to be able to have the compiler deduce the arity of the
  function (e.g. by applying undefined until it is no longer a function),
  precisely so I don't have to supply it myself.
 
  Function arity is (I think) something already known to GHC, so I don't
  know why we can't get at it too.

 No, it is not.  Consider:

 compose f g x = f (g x)

 What is the arity of f?

Oh, you're saying at run-time, given an object.

Still no, by some definition.

compose f g = f . g

compose' f g x = f (g x)

Are you saying that these two exactly equivalent functions should have
different arity?   If not, then is the arity 2 or 3?

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Luke Palmer
On Dec 7, 2007 7:41 PM, Dan Weston [EMAIL PROTECTED] wrote:
 Luke Palmer wrote:
  You can project the compile time numbers into runtime ones:

 Yes, that works well if I know a priori what the arity of the function
 is. But I want to be able to have the compiler deduce the arity of the
 function (e.g. by applying undefined until it is no longer a function),
 precisely so I don't have to supply it myself.

 Function arity is (I think) something already known to GHC, so I don't
 know why we can't get at it too.

No, it is not.  Consider:

compose f g x = f (g x)

What is the arity of f?

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] general

2007-12-08 Thread Luke Palmer
On Dec 8, 2007 7:41 PM, Ryan Bloor [EMAIL PROTECTED] wrote:

 hi

  I have a problem.

  Function A is a function that passes its input into B
  Function B is a function that does something once.

What do you mean by that?  B does something once.

More details!  (Type signatures at least will give us a good idea what
is going on)

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread Luke Palmer
On Dec 10, 2007 7:09 PM, Wolfgang Jeltsch [EMAIL PROTECTED] wrote:
  there's the fear that laziness can impact performance,

 Hmm, tell them that performance isn't all and that laziness helps you to write
 more modular programs.

Nah, in this case I've found it's better to realistically compare the
performance of
Haskell to Perl/Python, because it usually blows them out of the water, despite
laziness :-)

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] class default method proposal

2007-12-12 Thread Luke Palmer
On Dec 11, 2007 3:19 PM, David Menendez [EMAIL PROTECTED] wrote:
 On Dec 11, 2007 9:20 AM, Duncan Coutts [EMAIL PROTECTED] wrote:

  So my suggestion is that we let classes declare default implementations
  of methods from super-classes.
 snip.

  Does this proposal have any unintended consequences? I'm not sure.
  Please discuss :-)

 It creates ambiguity if two classes declare defaults for a common
 superclass.

 My standard example involves Functor, Monad, and Comonad. Both Monad and
 Comonad could provide a default implementation for fmap. But let's say I
 have a type which is both a Monad and a Comonad: which default
 implementation gets used?

Isn't a type which is both a Monad and a Comonad just Identity?

(I'm actually not sure, I'm just conjecting)

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing a MUD server in haskell

2007-12-16 Thread Luke Palmer
On Dec 16, 2007 1:45 PM, Jules Bean [EMAIL PROTECTED] wrote:
  This needs to stand up to concurrent modification of a shared world
  structure, but I think I'll set up the concurrency controls after I get
  my head around this.t
 The simplest way to do this is to bundle all your big shared mutable
 world into a single MVar. What this amounts to is perfect brute force
 serialisation of the actual modification part: i.e. all world
 modifications share a global lock. This is easy to implement and easy to
 reason about.

 If that turns out to be too restrictive, then you split up the MVars
 into smaller pieces, but then you have to think a bit harder to convince
 yourself it is safe.

STM! Why use Haskell concurrently and not use STM?  STM is beautiful.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: OOP'er with (hopefully) trivial questions.....

2007-12-17 Thread Luke Palmer
There was a thread about this recently.

In any case, if you load the code interpreted (which happens if there
is no .o or .hi file of the module lying around), then you can
look inside all you want.  But if it loads compiled, then you only
have access to the exported symbols.  The reason is because of
inlining optimizations; you know about the encapsulation of the module
when you compile it, and you can optimize the memory and
code usage based on compiling functions that are not exported
differently.  That's my weak understanding, at least.

Luke

On Dec 17, 2007 5:52 PM, Peter Hercek [EMAIL PROTECTED] wrote:
 Thomas Davie wrote:
  Take a look at the Typable class.  Although, pretty much any code that
  you can compile can be loaded into ghci without modification, and that's
  by far the easier way of finding the types of things.

 Is there a way to make ghci to know also the symbols which are not exported?
 My problem is that :t unexportedSymbolName reports undefined. Is there a
 way to make :t working without first exporting unexportedSymbolName and
 then reloading the module in ghci and asking with :t again?

 Peter.


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Luke Palmer
On Dec 18, 2007 7:31 AM, Cristian Baboi [EMAIL PROTECTED] wrote:
 Here is some strange example:

 module Hugs where

 aa::Int
 aa=7

 cc:: (Int-Int)-(Int-Int-Int)-Int-(Int-Int)
 cc a op b  =  \x- case x of  {   _ | x==aa - x+1 ;  _- a x `op` b }

 f::Int-Int
 f(1)=1
 f(2)=2
 f(_)=3

 g::Int-Int
 g(1)=13
 g(2)=23
 g(_)=33

 h::[Int-Int] - Int -Int
 h  []  x   = x
 h  [rr]  x=  let { u=Hugs.f ; v=Hugs.g } in  case rr of  {  u  -
 Hugs.g(x)+aa ; v - Hugs.f(x)+aa ; _ -rr (x) + aa }
 h  (rr:ll)  x =  h [rr] x + h (ll) x


 What I don't understand is why I'm forced to use guards like x==aa in cc,
 when aa is clearly bounded (is 7) and why in function h, the bounded u and
 v become free variables in the case expression.

It's a simple issue of scoping.   The left side of case expressions are
*patterns*, which bind new names, and don't look outside their scope for
names.  This is a good thing.  Say you have:

case Left 0 of
  Left  x - x
  Right y - show y

(The values are instances of the Either type, specifically Either Int)

This will match the value Left 0 against an expression which either looks
like Left x or Right y, for any x or y, and act accordingly.  If you decided
to add

x :: Int
x = 42

To the top level of your program, you wouldn't want the first case only to
match Left 42 when it previously matched any value starting with Left,
would you?

It is the same as scoping in C (or whatever language your background is, they
all support it); you don't want names in a larger scope to interfere with
names in a smaller scope.  Each case in a case expression introduces a scope,
and the left side of the arrow binds new names.

I hope this helps,

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Knowledge

2007-12-19 Thread Luke Palmer
On Dec 19, 2007 7:26 PM, jlw501 [EMAIL PROTECTED] wrote:

 I'm new to functional programming and Haskell and I love its expressive
 ability! I've been trying to formalize the following function for time.
 Given people and a piece of information, can all people know the same thing?
 Anyway, this is just a bit of fun... but can anyone help me reduce it or
 talk about strictness and junk as I'd like to make a blog on it?

This looks like an encoding of some philosophical problem or something.  I
don't really follow.  I'll comment anyway.

 contains :: Eq a = [a]-a-Bool
 contains [] e = False
 contains (x:xs) e = if x==e then True else contains xs e

contains = flip elem

 perfectcomm :: Bool
 perfectcomm = undefined
 knowself :: Bool
 knowself = undefined

Why are these undefined?

 allKnow :: Eq a = [a]-String-Bool
 allKnow _  = True
 allKnow [] k = False
 allKnow (x:[]) k = knowself
 allKnow (x:xs) k =
comm x xs k  allKnow xs k
where
   comm p [] k = False

This case will never be reached, because you match against (x:[]) first.

   comm p ps k = if contains ps p then knowself
else perfectcomm

And I don't understand the logic here. :-p

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New to Haskell

2007-12-19 Thread Luke Palmer
On Dec 20, 2007 1:23 AM, Jake McArthur [EMAIL PROTECTED] wrote:
 On Dec 19, 2007, at 6:25 PM, John Meacham wrote:

  On Tue, Dec 18, 2007 at 01:58:00PM +0300, Miguel Mitrofanov wrote:
  I just want the sistem to be able to print one of these
  expressions !
  Its this too much to ask ?
  Yes, 'cause it means you want to embed almost all source code
  into the
  compiled program.
  So ?
  So, I don't know any compiler of any language which does it.
 
  Actually, it is a pretty fundamental feature of the lisp-derived
  languages that they can self modify their own source, and hence keep
  their own source representation all the way through runtime.

 I'm not really a Lisp programmer, but don't you mean AST instead of
 source?

It's Lisp, they're basically the same thing!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type trickery

2007-12-20 Thread Luke Palmer
On Dec 20, 2007 9:34 AM, Adrian Neumann [EMAIL PROTECTED] wrote:
 Hello haskell-cafe!

 After making data Number = Zero | Succ Number an instance of
 Integral, I wondered how I could do the same with galois fields. So
 starting with Z mod p, I figured I'd need something like this

 data GF = GF Integer Integer

 so that each element of the finite field would remember p. However I
 can't think of a way to use the typesystem to ensure that p is always
 the same. I think that would need an infinite number of different
 types, but the type hackers here probably know something better.

Yes, you can have some fun by taking your Number definition to the type level:

data Zero-- phantom type, no implementation
data Succ a  -- same

class Runtimify a where
runtimify :: a - Integer

instance Runtimify Zero where
runtimify _ = 0

instance (Runtimify a) = Runtimify (Succ a) where
runtimify _ = 1 + runtimify (undefined :: a)

data GF p = GF Integer

instance (Runtimify p) = Num (GF p) where
-- you fill in the rest :-)

Note that p is encoded in only a type variable, so you'll
have to use runtimify (sorry for the silly name) to get
it out.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Smart Constructor Puzzle

2007-12-20 Thread Luke Palmer
On Dec 21, 2007 4:39 AM, Ronald Guida [EMAIL PROTECTED] wrote:
 Finally, I tried to define vecLength, but I am getting an error.

   vecLength :: (Peano s) = Vec s t - Int
   vecLength _ = pToInt (pGetValue :: s)

The s in (pGetValue :: s) is different from the s in (Peano s).  Use
the scoped type variables extension:

  vecLength :: forall s. (Peano s) = Vec s t - Int
  vecLength _ = pToInt (pGetValue :: s)

The forall introduces a scope for s, which type signatures usually do not.

Luke

  Could not deduce (Peano s1) from the context ()
arising from a use of `pGetValue'
  Possible fix:
add (Peano s1) to the context of the polymorphic type `forall s. s'
  In the first argument of `pToInt', namely `(pGetValue :: s)'
  In the expression: pToInt (pGetValue :: s)
  In the definition of `vecLength':
  vecLength _ = pToInt (pGetValue :: s)

 Any suggestions?
 -- Ron

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does this blow the stack?

2007-12-22 Thread Luke Palmer
On Dec 22, 2007 12:06 AM, Stefan O'Rear [EMAIL PROTECTED]   The
explicit loop you're talking about is:
  enumDeltaInteger :: Integer - Integer - [Integer]
  enumDeltaInteger x d = x : enumDeltaInteger (x+d) d
  That code isn't very complicated, and I would hope to be able to write
  code like that in my own programs without having to worry about
  strictness.  Given that the compiler even has an explicit signature,
  why can't it transform that code to
  enumDeltaInteger x d = let s = x + d in x : (seq s $ enumDeltaInteger s 
  d)
  since it knows that (Integer+Integer) is strict?  Of course, improving
  the strictness analysis is harder, but it pays off more, too.

 Because they simply aren't the same.

 Try applying your functions to undefined undefined.

This took a little work for me to see.  Here it is for the interested:

Prelude let edi :: Integer - Integer - [Integer]; edi x d = x : edi (x+d) d
Prelude let edi' :: Integer - Integer - [Integer]; edi' x d = let s
= x + d in x : (seq s $ edi s d)
Prelude _:_:_ - return $ edi undefined undefined
Prelude _:_:_ - return $ edi' undefined undefined
*** Exception: Prelude.undefined

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Wikipedia on first-class object

2007-12-28 Thread Luke Palmer
On Dec 28, 2007 5:58 AM, Cristian Baboi [EMAIL PROTECTED] wrote:
 Here is how I want print to be in Haskell

 print :: (a-b) - (a-b)

 with print = id, but the following side effect:

 - I want to call the print function today, and get the value tomorrow.

You might be interested in the standard module Debug.Trace, which
defines a function:

   trace :: String - b - b

Which allows you to print something avoiding the IO monad as you seem
to want.  Then to get
your print function, all you would need is a Show instance for a - b:

   print f = trace (show f) f

Then the Show instance:

   instance Show (a - b) where
   show f = function

And there you have it.  It's not very useful, since it just prints
function for every function, but there you go.  I suspect you want
to print some serialization of the function such that it can be read
in again and executed later.  You're not gonna get that any time soon.

But I also suspect that there is another legitimate solution to your
problem.  Unless the problem has to do with transferring *arbitrary*
functions (that is, your program knows nothing at all about what is
transferred) between processes (not to be confused with threads, which
Haskell is very good at).

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] what does @ mean?.....

2007-12-28 Thread Luke Palmer
On Dec 28, 2007 9:35 AM, Jules Bean [EMAIL PROTECTED] wrote:
 In particular, adding sharing can stop something being GCed, which can
 convert an algorithm which runs in linear time and constant space to one
 which runs in linear space (and therefore, perhaps, quadratic time).

I've heard of this before, but can you give an example?

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Doing some things right

2007-12-28 Thread Luke Palmer
On Dec 28, 2007 2:55 PM, Miguel Mitrofanov [EMAIL PROTECTED] wrote:
  I thought Lisp and Erlang were both infinitely more
  popular and better known.
 
  Certainly not infinitely.  Lisp isn't entirely functional, and while
  Erlang is an industrial success story, I think Haskell is seeing a
  wider range of application.

 Well, it seems for me that Erlang is much less functional than Lisp.
 It's totally OO, in fact.

OO is orthogonal to functional.  Erlang is pure functional, Lisp is a
bastard child...

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Doing some things right

2007-12-29 Thread Luke Palmer
On Dec 29, 2007 10:32 AM, Andrew Coppin [EMAIL PROTECTED] wrote:
 Luke Palmer wrote:
  OO is orthogonal to functional.  Erlang is pure functional, Lisp is a
  bastard child...
 

 1. Wasn't Lisp here first? (I mean, from what I've read, Lisp is so old
 it almost predates electricity...)

Before the concepts of OO, functional, and imperative?  Well, certainly before
OO -- the other two... perhaps.

 2. I'm curios as to how you can have a functional OO language. The two
 seem fundamentally incompatible:

See O'Caml, O'Haskell.  I'd call those OO functional languages.  You may
reject state from OO and still have something which is quite close to OO.
But it's a matter of minor semantics now I think...

 3. I know very little about Erlang, but the Haskell wiki claims it is
 not pure functional. (This agrees with the small amount of Erlang I do
 know.)

I don't know any erlang.  Someone in freenode.net#erlang things erlang is
pure functional :-)

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Sending bottom to his room

2007-12-29 Thread Luke Palmer
On Dec 29, 2007 11:14 AM, Cristian Baboi [EMAIL PROTECTED] wrote:
 In The Implementation of Functional Programming Languages by S.P. Jones,
 section 2.5.3, page 32 it is written:


 Eval [[*]] a b = a x b
 Eval [[*]] _|_ b = _|_
 Eval [[*]] a _|_ = _|_

 but in section 2.5.2 it is said that _|_ is an element of the value domain.
 What business does it have on the left side of the '=' ?

I don't know the book you're talking about, but I suspect that this is not
a definition of a function in a language, but rather the denotational semantics
for a function.  Just as mathematics is allowed to categorize all
turing machines
into two categories (those that halt and those that do not), even
though to actually
do this is impossible, so too can mathematics talk about what a function returns
when given _|_, even though it is impossible in general to know when
you actually
do have _|_ or you're just waiting for a value.

However, if you saw something like this:

  Eval [[*]] a b   = a x b
  Eval [[*]] _|_ b = b
  Eval [[*]] a _|_ = a

Then you would have cause for alarm, since this is not a monotone
function (am I using
that term correctly?).

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] More newbie typeclass confusion...

2007-12-29 Thread Luke Palmer
On Dec 30, 2007 3:43 AM, Jonathan Cast [EMAIL PROTECTED] wrote:
 On 29 Dec 2007, at 9:31 PM, alex wrote:

  Hi there.
 
  If someone can tell me why I am getting type ambiguity
  in the following code:
 
  class (Ord s, Num s) = Scalar s where
  zero :: s
 
  class Metric m where
  delta   :: Scalar s = m - m - s

Just to clear up common confusion: the caller chooses s here, not the
delta function.  So
delta has to work for any choice of s the caller chooses (as long as
it is an instance of
Scalar).

  (=~):: m - m - Bool
  (/~):: m - m - Bool
 
  (=~) a b= (delta a b) = zero

What instance of Scalar do you want delta to return here?  There's no
way for the compiler
to deduce that information.

What you probably want is a fundep or associated type, associating a
single choice of scalar
for each metric:

class (Scalar (Field m)) = Metric m where
type Field m :: *
delta :: m - m - Field m
...

instance Metric Double where
type Field Double = Double
delta = (-)
...

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Web server (Was: Basic question concerning data constructors)

2007-12-31 Thread Luke Palmer
On Dec 30, 2007 6:24 PM, Joost Behrends [EMAIL PROTECTED] wrote:
 I've already browsed through the docomentation of all that. Sorry, but i will
 not use WASH. I like things to be direct, to write  p { ... } or similar
 things instead of p ... /p is worsening things for me.

Haskell is not a good quick and dirty templating language.  See perl
for 500 templating approaches.

So, now that we're past that.  One of the beautiful things I have
noticed about Haskell is that there
has been essentially nothing I have not been able to factor out.  If I
have any common repeated logic
anywhere in my program, I have always been able to naturally factor it
out so it appears in only
one place.

So how, prey tell, do you factor out an expression which includes
p.../p?  It is not Haskell,
Haskell has no power there.  What the libraries you are looking at do
is precisely to encode
HTML/SQL into Haskell, so it may be manipulated by Haskell functions
without resorting
to string mangling.  Haskell however does not look anything like HTML
or like SQL, so there
is a mapping you must learn.  But that mapping is a refined version of
what you might come
up with if you were starting from scratch and diligently refactoring
as much as possible.  Surely
learning that mapping is easier than building your own (which will
doubtlessly be worse (no
offense, that's the first law of library use)).

And since you are a Haskell beginner, learning a library will teach
you not only the library, but
loads about common idioms and Haskell programming in general.  As an
example, it was only
after using the Parsec library that I finally came to terms with
monads; for whatever reason, I
was incapable of grokking them studying only the standard built-ins.

I dunno, it just seems odd to me to avoid extra learning when you're
trying to learn the
language in the first place.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Basic question concerning data constructors

2008-01-01 Thread Luke Palmer
On Jan 1, 2008 3:43 PM, Yitzchak Gale [EMAIL PROTECTED] wrote:
 The classical definition of general recursive function
 refers to functions in Integer - Integer to begin
 with, so there can only be countably many values by
 construction.

Except that there are uncountably many (2^Aleph_0) functions in
Integer - Integer.  That doesn't change the fact that there are
countably many computable functions, as you guys have been saying.
But I think you need to refer to the LC or Turing machine definition
to get countability.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] confusion about 'instance'....

2008-01-10 Thread Luke Palmer
On Jan 10, 2008 1:03 PM, Nicholls, Mark [EMAIL PROTECTED] wrote:
 Should be straight forwardsimplest example is...

 class A a

 data D = D1

 instance A D

 fine.D is declared to be a member of type class A

 what about.

 class A a

 type T = (forall x.Num x=x)

 instance A T

 error!...

  Illegal polymorphic or qualified type: forall x. (Num x) = x
 In the instance declaration for `A T'

 I am simply trying to state that all members of typeclass Num are of
 typeclass A

Ahh, you want:

  instance Num a = A a

Sorry to lead you on, but that actually is not legal (and
-fallow-undecidable-instances
will make it legal, but you don't want that, because instances of this
particular form
are very likely to lead to an infinite loop).

Adding supertypes like this is not possible in Haskell.  I really want
it to be, but alas...

Luke

 Doesn't like it.

 Does this mean that instance only operates on 'atomic' (for want of a
 better word) types?


 -Original Message-
 From: Peter Verswyvelen [mailto:[EMAIL PROTECTED] On Behalf Of
 Peter Verswyvelen
 Sent: 03 January 2008 12:02
 To: Nicholls, Mark
 Cc: haskell-cafe@haskell.org
 Subject: RE: [Haskell-cafe] Is there anyone out there who can translate
 C# generics into Haskell?

 Hi Mark,

  foo1 :: Int - obj - String
  Yep...I think that's what I'd dothough I would have done...
  foo1 :: obj - Int - String
  Does that matter?

 Well, it's a good habit in Haskell to move the most important
 parameter to
 the end of the argument list. See e.g.
 http://www.haskell.org/haskellwiki/Parameter_order.

  OK but I was going to go onto
  Interface IXA where A : IXA {}
  and
  Interface IXA,B where A : B {}

 No, I would not know how to that in Haskell using type classes. It seems
 Haskell does not allow cycles in type class definitions. But as I'm new,
 this does not mean it's not possible. It's more important to know *what*
 you
 are trying to do, than to give a solution in a different language, since
 OO
 and FP are kind of orthogonal languages.

  Where I cannot see a way to do the above in Haskell at allas
  interfaces effectively operator on type classes not typeswhich
 seems
  inherently more powerful

 Yeah, kind of makes sense. I liked interfaces in C# a lot, but when I
 started doing everything with interfaces, I found the lack of support
 for
 mixins or default implementations problematic. This ended up in a
 lot of
 copy/paste or encapsulating the implementations into a static class with
 plain functions, a mess.

  But if these could be done in Haskell the see what could be made of
  stuff likewhich is obviously problematic in C# it obviously
 doesn't
  workbut potentially does make 'sense'.
  Interface IXA : A {}

 Ah! That's one of the bigger restrictions in C# yes! C++ can do that;
 ATL
 uses it a lot, and I also like that approach. You can emulate mixins
 with
 that, and still stay in the single inheritance paradigm. In Haskell you
 don't do that at all of course, since you avoid thinking about objects
 and
 inheritance in the first place.

 OO is strange. They offer you the nice concept of inheritance, and then
 the
 guidelines tell you: don't use too many levels of inheritance...
 Although
 I've build huge projects using OO, it always felt a bit like unsafe
 hacking.
 I don't really have that feeling with Haskell, but that could also be
 because I'm too new to the language ;-)

  I'm looking at Haskell because of the formality of it's type
  systembut I'm actually not convinced it is as powerful as an OO
  onei.e. OO ones operatate principally (in Haskell speak) on type
  classes not types

 Maybe you are right, I don't know, my theoritical skills are not high
 enough
 to answer that. Haskell just feels better to me, although the lack of
 a
 friendly productive IDE and large standard framework remains a bit of a
 burden.

 Good luck,
 Peter

 -Original Message-
 From: [EMAIL PROTECTED]
 [mailto:[EMAIL PROTECTED] On Behalf Of Nicholls, Mark
 Sent: Wednesday, January 02, 2008 5:41 PM
 To: haskell-cafe@haskell.org
 Subject: [Haskell-cafe] Is there anyone out there who can translate C#
 generics into Haskell?

 I'm trying to translate some standard C# constucts into Haskell... some
 of this seems easy

 Specifically

 1)

 Interface IX
 {
 }

 2)

 Interface IXA
 {
 }

 3)

 Interface IXA
 Where A : IY
 {
 }

 4)

 Interface IXA : IZ
 Where A : IY
 {
 }


 I can take a punt at the first 2but then it all falls apart
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] confusion about 'instance'....

2008-01-10 Thread Luke Palmer
On Jan 10, 2008 1:25 PM, Nicholls, Mark [EMAIL PROTECTED] wrote:
 Thanks for your response, I think you helped me on one of my previous
 abberations.

 Hmmmthis all slightly does my head inon one hand we have
 typesthen type classes (which appear to be a relation defined on
 types)then existential types...which now appear not to be treated
 quite in the same way as 'normal' typesand in this instance the
 syntax even seems to changedoes

 instance Num a = A a

 Mean the same thing as

 instance A (forall a.Num a=a)

Uh... that second one is pretty much nonsensical to me.  I could imagine it
meaning the type (forall a.Num a = a) itself is an instance of A, but not
specializations of it (like Int).  But without an identity in the type system,
the meaning of that would be convoluted.  It's kind of off topic, but just
for the interested, here are two similar, legal constructions:

Existential:
newtype Numeric  = forall a. Num a = Numeric a

Universal:
newtype Numeric' = Numeric' (forall a. Num a = a)

Both of which are easily declared to be instances of Num.  They're not what
you want though, because Haskell doesn't support what you want :-(.  Anyway,
if you have a value of type Numeric, you know it contains some value of a
Num type, but you don't know what type exactly (and you can never find out).
If you have a value of type Numeric', then you can produce a value of any Num
type you please (i.e. the value is built out of only operations in the Num
class, nothing more specific).

But that was a digression; ignore at your leisure (now that you've already
read it :-).

 and secondly in what way can this construct lead to undecidable
 instances

Okay, read:

instance A a = B b

(where a and be might be more complex expressions) not as b is an instance of
B whenever a is an instance of A, but rather as b is an instance of B, and
using it as such adds a constraint of A a.  Let's look at a slightly more
complex (and contrived) example:

class Foo a where
foo :: a - a

instance (Foo [a]) = Foo a where
foo x = head $ foo [x]

Then when checking the type of the expression foo (0::Int), we'd have to
check if Foo Int, Foo [Int], Foo [[Int]], Foo [[[Int]]], ad infinitum.

 What are the instances, and what about them is undecidableseems
 pretty decidable to me?

 What is the ramifications of turning this option on?

Theoretically, compile time fails to guarantee to ever finish.  Practically,
ghc will give you a very-difficult-to-reason-about message when constraint
checking stack overflows.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] confusion about 'instance'....

2008-01-10 Thread Luke Palmer
On Jan 10, 2008 2:04 PM, Nicholls, Mark [EMAIL PROTECTED] wrote:
 I can translate OO into mathematical logic pretty easily, I was trying
 to do the same thing (informally of course) with Haskellbut things
 are not quite what they appearnot because of some OO hang up (which
 I probably have many)...but because of what type class actually means.

But you can think of a type class as a set of types!  The problem is that
if we allow certain kinds of instances (such as the Foo instance I gave
earlier) then the set is allowed to be non-recursive (only recursively
enumerable), so determining whether a particular type is a member of it
would be undecidable.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] confusion about 'instance'....

2008-01-10 Thread Luke Palmer
On Jan 10, 2008 1:36 PM, Bulat Ziganshin [EMAIL PROTECTED] wrote:
 Hello Mark,

 Thursday, January 10, 2008, 4:25:20 PM, you wrote:

 instance Num a = A a

  Mean the same thing as

  instance A (forall a.Num a=a)

 programmers going from OOP world always forget that classes in Haskell
 doesn't the same as classes in C++. *implementation* of this instance
 require to pass dictionary of Num class along with type. now imagine
 the following code:

 f :: A a = a - a

 f cannot use your instance because it doesn't receive Num dictionary
 of type `a`. it is unlike OOP situation where every object carries the
 generic VMT which includes methods for every class/interface that
 object supports

I'm not sure that's a good argument.  It doesn't need a Num dictionary,
it only needs an A dictionary.  That's what it says.  You only need a Num
dictionary in order to construct an A dictionary, which seems perfectly
reasonable.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] \_ - not equivalent to const $

2008-01-10 Thread Luke Palmer
In attempting to devise a variant of cycle which did not keep its
argument alive (for the purpose of cycle [1::Int..]), I came across
this peculiar behavior:

import Debug.Trace

cycle' :: (a - [b]) - [b]
cycle' xs = xs undefined ++ cycle' xs


 take 20 $ cycle' (const $ 1:2:3:4:trace x 5:[])
[1,2,3,4,x
5,1,2,3,4,5,1,2,3,4,5,1,2,3,4,5]

Nuts.  Oh, but wait:

 take 20 $ cycle' (\_ - 1:2:3:4:trace x 5:[])
[1,2,3,4,x
5,1,2,3,4,x
5,1,2,3,4,x
5,1,2,3,4,x
5]

Hey, it worked!

Can someone explain what the heck is going on here?

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] \_ - not equivalent to const $

2008-01-10 Thread Luke Palmer
On Jan 10, 2008 11:11 PM, Felipe Lessa [EMAIL PROTECTED] wrote:
 On Jan 10, 2008 8:54 PM, Luke Palmer [EMAIL PROTECTED] wrote:
  Can someone explain what the heck is going on here?

 AFAICT, nothing is wrong. You see, both returned the very same values.
 What you saw was in fact the problem with unsafePerformIO and friends,
 as they may be executed lots of times *or not*. The compiler is free
 to behave in those two ways for the code with const or with the
 lambda. But referential transparency wasn't broken at all =).

Of course.  I'm trying to write a variant of cycle that will be efficient
with memory for my purposes, so the Haskell 98 standard, which says nothing
about memory usage, doesn't really interest me.  I'm more interested in
what is going on in ghc (6.8.1) in this case, if it has a simple explanation.
And of course am interested if there are any better ways to write such a
function.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] \_ - not equivalent to const $

2008-01-10 Thread Luke Palmer
On Jan 10, 2008 11:15 PM, Victor Nazarov [EMAIL PROTECTED] wrote:
 On Jan 11, 2008 2:11 AM, Felipe Lessa [EMAIL PROTECTED] wrote:
  On Jan 10, 2008 8:54 PM, Luke Palmer [EMAIL PROTECTED] wrote:
   Can someone explain what the heck is going on here?
 
  AFAICT, nothing is wrong. You see, both returned the very same values.
 [snip]
  But referential transparency wasn't broken at all =).
 
 Referential transparency wasn't broken, but I wonder what was the
 compiler, and what were it's options.

Ahh, it was ghc 6.8.1, without any optimization.  If I turn on optimization,
the behavior goes away, and they both behave like the const version.

Darn.

Luke

 --
 vir
 http://vir.comtv.ru/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why purely in haskell?

2008-01-10 Thread Luke Palmer
On Jan 11, 2008 12:09 AM,  [EMAIL PROTECTED] wrote:

 1. Indirect black holes that are not expressible in a strict
 language.  You generally have to be doing something bizarre for this
 to occur, and it doesn't take too long before you can accurately
 predict when they constitute a likely risk.

What do you mean by black hole here?

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why purely in haskell?

2008-01-11 Thread Luke Palmer
On Jan 11, 2008 9:27 AM, Wolfgang Jeltsch [EMAIL PROTECTED] wrote:
 However, the fact that (0 / 0) == (0 / 0) yields False is quite shocking.  It
 doesn't adhere to any meaningful axiom set for Eq.  So I think that this
 behavior should be changed.  Think of a set implementation which uses (==) to
 compare set elements for equality.  The NaN behavior would break this
 implementation since it would allow for sets which contain NaN multiple
 times.

Here's another thing that makes me want to throw up.

Prelude let nan :: Double = 0/0
Prelude compare nan nan
GT
Prelude nan  nan
False

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type questions again....

2008-01-11 Thread Luke Palmer
2008/1/11 Nicholls, Mark [EMAIL PROTECTED]:
 Can someone explain (in simple terms) what is meant by existential and
 universal types.

 Preferably illustrating it in terms of logic rather than lambda calculus.

Well, I don't know about logic.  While they are certainly related to
existential and universal types in logic, I don't really see a way to
explain them in terms of that.

Universal types are easy, you use them every day in Haskell.  Take for
example id:

 id :: a - a

Or better illustrated (using ghc extension):

 id :: forall a. a - a

That means that for any type a I pick, I can get a value of type a -
a from id.  If you wrap an existential type up in a constructor, not
much changes:

 newtype ID = ID (forall a. a - a)

ID can hold any value of type forall a. a - a; i.e. it can hold any
value which exhibits the property that it can give me a value of type
a - a for any type a I choose.  In this case the only things ID can
hold are id and _|_, because id is the only function that has that
type.   Here's how I might use it:

 applyID :: ID - (Int,String) - (Int,String)
 applyID (ID f) (i,s) = (f i, f s)

Note how I can use f, which is a universal type, on both an Int and a
String in the same place.

You can also put typeclass constraints on universals.  Take the
universal type forall a. Num a = a - a.  Among functions that have
this type are:

 add1 :: forall a. Num a = a - a
 add1 x = x + 1

 id' :: forall a. Num a = a - a
 id' = id  -- it doesn't have to use the constraint if it doesn't want to

Wrapping this up in a constructor:

 newtype NUM = NUM (forall a. Num a = a - a)

We can create values:

 NUM add1 :: NUM
 NUM id   :: NUM

And use them:

 applyNUM :: NUM - (Int, Double) - (Int, Double)
 applyNUM (NUM f) (i,d) = (f i, f d)



Existential types are dual, but you need to use constructors to use
them.  I'll write them using GADTs, because I think they're a lot
clearer that way:

data NUM' where
NUM' :: Num a = a - NUM'

Look at the type of the constructor NUM'.  It has a universal type,
meaning whatever type a you pick (as long as it is a Num), you can
create a NUM' value with it.  So the type contained inside the NUM'
constructor is called existential (note that NUM' itself is just a
regular ADT; NUM' is not existential).

So when you have:

 negNUM' :: NUM' - NUM'
 negNUM' (NUM' n) = NUM' (negate n)

Here the argument could have been constructed using any numeric type
n, so we know very little about it.  The only thing we know is that it
is of some type a, and that type has a Num instance.  So we can
perform operations to it which work for any Num type, such as negate,
but not things that only work for particular Num types, such as div.

 doubleNUM' :: NUM' - NUM'
 doubleNUM' (NUM' n) = NUleM' (n + n)

We can add it to itself, but note:

 addNUM' :: NUM' - NUM' - NUM'
 addNUM' (NUM' a) (NUM' b) = NUM (a + b)  -- Illegal!

We can't add them to each other, because the first argument could have
been constructed with, say, a Double and the other with a Rational.

But do you see why we're allowed to add it to itself?

How about this:

 data Variant where
Variant :: a - Variant

This is a type that can be constructed with any value whatsoever.
Looks pretty powerful... but it isn't.  Why not?

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type questions again....

2008-01-11 Thread Luke Palmer
On Jan 11, 2008 5:47 PM, Nicholls, Mark [EMAIL PROTECTED] wrote:
  If you wrap an existential type up in a constructor, not
  much changes:

 If you wrap a what?should this read existential or universal?

Whoops, right, universal.

   newtype ID = ID (forall a. a - a)
 
  ID can hold any value of type forall a. a - a; i.e. it can hold any
  value which exhibits the property that it can give me a value of type
  a - a for any type a I choose.  In this case the only things ID can
  hold are id and _|_, because id is the only function that has that
  type.   Here's how I might use it:

 It's the only function you've defined the type of

 Id2 :: forall a. a - a

 Now it can hold id2?

Well, that's not what I meant, but yes it can hold id2.

What I meant was that, in this case, id2 = _|_ or id2 = id, there are no
other possibilities.


   id' :: forall a. Num a = a - a
   id' = id  -- it doesn't have to use the constraint if it doesn't
 want to

 it doesn't have to use the constraint if it doesn't want to ?

 If id was of type..

 Id::forall a. Ord a = a - a

 Then I assume it would complain?

Yes.

  but you need to use constructors to use
  them.  I'll write them using GADTs, because I think they're a lot
  clearer that way:
 
  data NUM' where
  NUM' :: Num a = a - NUM'
 
  Look at the type of the constructor NUM'.  It has a universal type,
  meaning whatever type a you pick (as long as it is a Num), you can
  create a NUM' value with it.

 yes

 and then it goes wrong...

  So the type contained inside the NUM'
  constructor

 ?

  is called existential (note that NUM' itself is just a
  regular ADT; NUM' is not existential).
 

 Why existentialsee below...I have a guess

Okay, I was being handwavy here.  Explaining this will allow me to
clear this up.

If you take the non-GADT usage of an existential type:

data Foo
= forall a. Num a = Foo a

That is isomorphic to a type:

data Foo
= Foo (exists a. Num a = a)

Except GHC doesn't support a keyword 'exists', and if it did, it would only be
able to be used inside constructors like this (in order for inference
to be decidable),
so why bother?  That's what I meant by the type inside the constructor, Foo is
not existential, (exists a. Num a = a) is.

  So when you have:
 
   negNUM' :: NUM' - NUM'
   negNUM' (NUM' n) = NUM' (negate n)

Here n has an existential type, specifically (exists a. Num a = a).

  Here the argument could have been constructed using any numeric type
  n, so we know very little about it.  The only thing we know is that it
  is of some type a, and that type has a Num instance.

 I think one of the harrowing things about Haskell is the practice of
 overloading data constructors with type namesit confuses the hell
 out of me

Yeah that took a little getting used to for me too.  But how am I supposed
to come up with enough names if I want to name them differently!?  That
would require too much creativity...  :-)

 OK so this declaration says that forall x constructed using NUM'
 n...there *exists* a type T s.t. T is a member of type class NUM...

(you probably meant type class Num here)

 which in term implies that that there exists the function negate...

 yes?

Huh, I had never thought of it like that, but yes.

I just realized that I think of programming in a way quite different
than I think of logic.  Maybe I should try to have my brain unify them.

   doubleNUM' :: NUM' - NUM'
   doubleNUM' (NUM' n) = NUleM' (n + n)
 
  We can add it to itself, but note:
 
   addNUM' :: NUM' - NUM' - NUM'
   addNUM' (NUM' a) (NUM' b) = NUM (a + b)  -- Illegal!
 
  We can't add them to each other, because the first argument could have
  been constructed with, say, a Double and the other with a Rational.
 
  But do you see why we're allowed to add it to itself?

 We can add it to itself because + is of type a-a-a...

Yep, so whatever type a n happens to have, it matches both arguments.

  How about this:
 
   data Variant where
  Variant :: a - Variant
 
  This is a type that can be constructed with any value whatsoever.
  Looks pretty powerful... but it isn't.  Why not?
 

 Eeek.

 Because a could be of any type whatsover?...so how I actually do
 anything with it?

Right.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Not to load Prelude

2008-01-11 Thread Luke Palmer
On Jan 11, 2008 8:13 PM, Jeremy Shaw [EMAIL PROTECTED] wrote:
 At Thu, 10 Jan 2008 22:16:27 -0200,
 Maurí­cio wrote:

  I tried google and ghc homepage, but could
  not find elsewhere :) Can you give me a
  link or somewhere to start from?

 No. What I meant to say was, I'm not really sure myself, I just know
 there is a difference and -fno-implicit-prelude is more aggressive. I
 you do find a clear explaination, I would love to see it.

So, when you write the number 3 in Haskell, GHC converts this to
essentially (Prelude.fromInteger (3::Integer)) in its internal format.
 So it doesn't matter if you import Prelude (), Prelude's version of
fromInteger still gets called.  If you give -fno-implicit-prelude,
then this is converted to simply (fromInteger (3::Integer)), without
the hard-coded prelude reference.  That means you could write your own
version of fromInteger that does something different.  A common usage
for -fno-implicit-prelude (insofar as it is used at all, which is
seldom) is to replace the standard Num hierarchy with a saner one,
with numeric literals resolving to that one instead.

There are a few other hard-coded references to Prelude in the internal
format, but I don't remember what they are offhand.
-fno-implicit-prelude gets rid of those, too.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Solving a geometry problem with Haskell

2008-01-12 Thread Luke Palmer
On Jan 12, 2008 9:19 PM, Rafael Almeida [EMAIL PROTECTED] wrote:
 After some profiling I found out that about 94% of the execution time is
 spent in the ``isPerfectSquare'' function.

That function is quite inefficient for large numbers.  You might try
something like this:

isPerfectSquare n = searchSquare 0 n
where
searchSquare lo hi
  | lo == hi = False
  | otherwise =
  let mid = (lo + hi) `div` 2 in
  case mid^2 `compare` n of
  EQ - True
  LT - searchSquare mid hi
  GT - searchSquare lo mid

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Solving a geometry problem with Haskell

2008-01-12 Thread Luke Palmer
You can do better than this, too, actually.  It looks like you're
using isPerfectSquare inside a filter, which is given a monotone
sequence.  That means we can do:

  -- finds the intersection of two monotone sequences
  intersectMonotone :: (Ord a) = [a] - [a] - [a]
  intersectMonotone (x:xs) (y:ys) =
  case x `compare` y of
  EQ - x : intersectMonotone x y
  LT - intersectMonotone xs (y:ys)
  GT - intersectMonotone (x:xs) ys
  intersectMonotone _ _ = []

Then you can change (filter isPerfectSquare) to (intersectMonotone
perfectSquares) and you should get a big speed boost.

Luke

On Jan 12, 2008 9:48 PM, Luke Palmer [EMAIL PROTECTED] wrote:
 On Jan 12, 2008 9:19 PM, Rafael Almeida [EMAIL PROTECTED] wrote:
  After some profiling I found out that about 94% of the execution time is
  spent in the ``isPerfectSquare'' function.

 That function is quite inefficient for large numbers.  You might try
 something like this:

 isPerfectSquare n = searchSquare 0 n
 where
 searchSquare lo hi
   | lo == hi = False
   | otherwise =
   let mid = (lo + hi) `div` 2 in
   case mid^2 `compare` n of
   EQ - True
   LT - searchSquare mid hi
   GT - searchSquare lo mid

 Luke

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [newbie question] Memoization automatic in Haskell?

2008-01-12 Thread Luke Palmer
On Jan 12, 2008 11:30 PM, David Benbennick [EMAIL PROTECTED] wrote:
 On 1/12/08, Henning Thielemann [EMAIL PROTECTED] wrote:
   Caching is not the default, but you can easily code this by yourself:
  Define an array and initialize it with all function values. Because of
  lazy evaluation the function values are computed only when they are
  requested and then they persist in the array.

 But how can I implement memoization for a more complicated function?
 For example, perhaps I want to memoize

 f :: String - Int - Double - String - Bool

 In Python, it's pretty easy to memoize this.  How can I do it in
 Haskell?  I suspect the only way would involve changing the function
 signature to use IO or ST.

No, that is one way to do it, and probably the easiest to think about.
 Because its
conceptually pure, I wouldn't be opposed to wrapping it in unsafePerformIO (but
that can be, well, unsafe if you do it wrong :-)

But there is a way to do it if you demand to be a purist, but only if you can
code a data structure representing all values of a type.  Doing this for a
particular type is one of my favorite ways to spend a half hour when
I'm bored :-)

For an obvious case, but to illustrate the point, I'll do Bool.

  data BoolCache a = BC a a

  bools :: BoolCache Bool
  bools = BC True False

  lookupBool :: BoolCache a - Bool - a
  lookupBool (BC t f) True  = t
  lookupBool (BC t f) False = f

  memoBool :: (Bool - a) - (Bool - a)
  memoBool f = lookupBool (fmap f bools)

The pattern is the same for any type.  You can do it for types with infinitely
many members, like Integer, but it's trickier (but it's the same pattern, just
a trickier data structure).  The Integer case is scattered here and
there online.
I haven't found any other cases online, but I've implemented a few.

 It would be nice if I could just tell the compiler I command you to
 memoize this function, and have it produce the required code
 automatically.

Tru dat!

But it's not clear what the best way for the compiler writer to do
that is.  For
example, if I know the access patterns of the function, I can design the
aforementioned data structure to favor those.   Also, not every type admits
memoization, for example functions.  But I can certainly envisage a
library providing:

  class Memo a where
memo :: (a - b) - (a - b)

For a bunch of different types.

Hmm, one probably already exists, actually...

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] the trivial monad- thoughts and a question

2008-01-12 Thread Luke Palmer
On Jan 13, 2008 12:47 AM, Brian Hurt [EMAIL PROTECTED] wrote:
 So, I've been playing around with what I call the trivial monad:

 module TrivialMonad where

 data TrivialMonad a = M a

Better to use newtype here; then it really is operationally equivalent
to using just a, except that it's possible to implement a monad
instance for it (see below).

 The first question I have is it is possible to implement this guy without
 wrapping the value in a constructor?  What I'd like to do is replace the:
 data TrivialMonad a = M a
 with something like:
 type TrivialMonad a = a
 and then be able to junk the recover function.

Nope.  That would mean that every type is a monad, which would cause endless
troubles for type inference.  For example, what monad is (putStrLn x) a
member of:  IO () or TrivialMonad (IO ())  (or even TrivialMonad
(TrivialMonad (IO(?

 The second question I have is: is there any hope of getting something like
 this into the standard library?

Control.Monad.Identity, perhaps?

http://www.haskell.org/ghc/docs/latest/html/libraries/mtl/Control-Monad-Identity.html

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comments and suggestions on code

2008-01-12 Thread Luke Palmer
On Jan 13, 2008 12:42 AM, Andre Nathan [EMAIL PROTECTED] wrote:
 On Sat, 2008-01-12 at 16:00 -0800, Jonathan Cast wrote:
  Wait, the last entry?  If you're just printing out the values, then
  no --- those should have been garbage collected already.

 Won't they be garbage collected only after the last entry is used,
 though? Since getDirectoryEntries returns a list, won't its elements
 have to be kept until the list is not used anymore, i.e., after the last
 entry is processed?

Well, if you're using the list like this:

   map (\i - f (list !! i)) [0..1]

Then yes (it will not be garbage collected), but if you're using the list
like this:

   map f list

Then no (depending on the surroundings, of course).

Recall what a list is:

data List a = Empty | Cons a (List a)

So once you process the first element and move to its tail, if there are no
references to the original list, only its tail, then the first element
will be garbage collected.  Which is why you can do things like:

filter isPowerOfTwo [1..]

And get a list back without running out of memory when you get as high as 2^32.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec monad transformer with IO?

2010-03-18 Thread Luke Palmer
On Thu, Mar 18, 2010 at 10:37 AM, Stefan Klinger
all-li...@stefan-klinger.de wrote:
 Hello!

 Nice, Parsec 3 comes with a monad transformer [1]. So I thought I could
 use IO as inner monad, and perform IO operations during parsing.

 But I failed. Monad transformers still bend my mind. My problem: I
 don't see a function to actually lift the IO operation into the
 ParsecT. It should be something like

  lift :: IO a - ParsecT s u IO a

That operation, with that name, and (a generalization of) that type,
is *the* method of the MonadTrans class.  Essentially the presence of
that operation is the definition of what it means to be a monad
transformer.

 The following is a toy example, I just could not make something
 smaller: Let's parse command line arguments (tokens are Strings), and
 execute them while parsing.

 import Text.Parsec.Prim
 import Text.Parsec.Pos
 import Text.Parsec
 import System.Environment ( getArgs )


 Command line interface parser (Clip) type: Inner monad IO, user state
 u, tokens are Strings, returns something typed a.

 type Clip u a = ParsecT [String] u IO a


 Source code position for command line arguments: The line is always 1,
 column n represents the n-th command line argument.

 nextPos p _ _ = incSourceColumn p 1


 Two primitive parsers, one for flags (with a dash) and one for other
 arguments:

 clipFlag x accepts the command line flag -x, and returns x.

 clipFlag :: String - Clip u String
 clipFlag x
     = tokenPrim
       id
       nextPos
       (\y - if '-':x == y then Just x else Nothing)


 clipValue accepts any command line argument that does not tart with a
 dash '-'.

 clipValue :: Clip u String
 clipValue
     = tokenPrim id nextPos test
     where
     test ('-':_) = Nothing
     test other = Just other



 Now the test program:

 Load files given on the command line, and sum up their word count,
 until -p is given. -p prints the current word count and sets the
 counter to zero. Further files may be processed then. At the end, show
 the sum of all word counts.

 Example: foo has 12 words, bar has 34 words:

  main foo -p bar -p foo bar -p
  Counted 12 words, reset counter.
  Counted 34 words, reset counter.
  Counted 46 words, reset counter.
  Grand total: 92


 type CurrentCount = Int -- the user state used with Clip/ParsecT.


 root implements the command line grammar (filename+ -p)* and
 returns the sum of all word counts.

 root :: Clip CurrentCount Int
 root
     = do ns - many (many1 loadFile  printSize)
          eof
          return $ sum ns


 Interprets each non-flag on the command line as filename, loads it,
 counts its words, and adds the count to the state.

 loadFile :: Clip CurrentCount ()
 loadFile
     = do -- expect a filename
          filename - clipValue

          -- load the file: IO
          content - lift $ readFile filename

          -- add wordcount to state
          modifyState ((+) (length $ words content))


 If -p shows up on the command line, print accumulated count, reset
 counter to cero and return count for grand-total calculation.

 printSize :: Clip CurrentCount Int
 printSize
     = do -- expect flag -p
          clipFlag p

          -- print current word count: IO
          n - getState
          lift . putStrLn $ Counted ++show n++ words, reset counter.

          -- reset user state to zero, return word count for grand total
          putState 0
          return n


 main just runs the root parser on the command line arguments and
 checks the result.

 main
     = do result - getArgs = runParserT root 0 command line
          case result of
            Left err - error $ show err
            Right n - putStrLn $ Grand total: ++show n


 So where is the lift function? Does it exist? Here, I need your help.

 lift :: IO a - ParsecT s u IO a
 lift = undefined


 Any comments are appreciated.

 Thank you!
 Stefan

 
 [1] 
 http://hackage.haskell.org/packages/archive/parsec/3.0.0/doc/html/Text-Parsec-Prim.html#t:ParsecT


 --
 Stefan Klinger                                      o/klettern
                                                    /\/  bis zum
 send plaintext only - max size 32kB - no spam         \   Abfallen
 http://stefan-klinger.de
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Abstraction in data types

2010-03-18 Thread Luke Palmer
On Thu, Mar 18, 2010 at 12:17 PM, John Meacham j...@repetae.net wrote:
 On Wed, Mar 17, 2010 at 09:20:49PM -0700, Darrin Chandler wrote:
 data Point    = Cartesian (Cartesian_coord, Cartesian_coord)
               | Spherical (Latitude, Longitude)

 Just a quick unrelated note, though you are probably aware of this,
 doing

 data Foo = Foo (X,Y)
 means something subtly different than
 data Foo = Foo X Y
 and can be less efficient.

On the other hand, the latter is equivalent to:

newtype Foo = Foo (X,Y)

 A quick way to see they are different is to count the bottoms,

 in the first case (where _ is bottom and X is some value)
 you have the cases
 Foo _
 Foo (_,_)
 Foo (X,_)
 Foo (_,X)
 Foo (X,X)
 and in the other case you have
 Foo _ _
 Foo X _
 Foo _ X
 Foo X X

 so one has 5 distinct values, and the other has 4, hence they are not
 isomorphic. All things being equal, this means the second case will be
 more efficient as there is one less case it needs to distinguish (every
 potential bottom implys an 'eval' somewhere). Depending on your code,
 all things may not be equal and there are rare times when the tupled
 version is more efficient however.

        John


 --
 John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Are there any female Haskellers?

2010-03-27 Thread Luke Palmer
On Sat, Mar 27, 2010 at 2:22 PM, Peter Verswyvelen bugf...@gmail.com wrote:
 So the first computer nerd was a women??!!! ;-) ;-) ;-)

Yeah, and she was so attractive that the entire male gender spent the
next 50 years trying to impress her.

Luke

 On Sat, Mar 27, 2010 at 9:06 PM, John Van Enk vane...@gmail.com wrote:
 http://en.wikipedia.org/wiki/Grace_Hopper
 A heck of a lady.

 On Sat, Mar 27, 2010 at 12:51 PM, Andrew Coppin
 andrewcop...@btinternet.com wrote:

 Ozgur Akgun wrote:

 Nevertheless, I guess you're right. There are very few females in most of
 the CS topics, and haskell is no different.

 This is my experience too. Although note that apparently the world's very
 first computer programmer was apparently a woman...

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Are there any female Haskellers?

2010-03-28 Thread Luke Palmer
2010/3/28 Pekka Enberg penb...@cs.helsinki.fi:
 2010/3/28 Günther Schmidt gue.schm...@web.de:
 This is definately a point where we will continue to disagree. I found
 myself assuming that there are no female haskellers and wanted to verify it
 by asking for data.

 So what exactly is off-topic for this list?  Is unsubscribing from the
 list the only option to get rid of this kind of utter nonsense posts
 that contain absolutely zero valuable discussion on _Haskell_?

It sounds like you are complaining because people are not talking
about what you want them to be talking about.  This will happen in
large groups.

Use a decent mail reader so that such nonsense posts are only one
keypress away from the garbage.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Announce: hothasktags

2010-04-01 Thread Luke Palmer
Hi,

I'd like to draw attention to a little script I wrote.  I tend to use
qualified imports and short names like new and filter.  This makes
hasktags pretty much useless, since it basically just guesses which
one to go to.  hothasktags is a reimplementation of hasktags that uses
haskell-src-exts to analyze the import structure to generate (scoped)
tags pointing to the right definition.  I'm pretty addicted to it,
since it provides the only functionality I miss from visual studio
:-).

VIm only for now, since I don't know if emacs tags format supports
scoped tags.  I am aware that it is not perfect -- patches and bug
reports welcome.

http://hackage.haskell.org/package/hothasktags

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Hackage accounts and real names

2010-04-05 Thread Luke Palmer
On Mon, Apr 5, 2010 at 9:18 PM, Ertugrul Soeylemez e...@ertes.de wrote:
 David House dmho...@gmail.com wrote:

 * Reputation. Using a RealName is the most credible way to build a
 combined online and RealLife identity. (Some people don't want this,
 for whatever reasons.)

 I agree that the restriction should be lifted.  A lot of very smart
 people do not want their real names connected to certain projects or be
 found on the internet at all.

 And I don't agree that why not? can be a valid argument, but even if
 it is, the above is a valid answer to it.  So all in all there is no
 convincing argument for the restriction, but at least two convincing
 arguments against.

When you say convincing, you are talking about yourself being
convinced, right?  So this paragraph means The arguments against my
position haven't convinced me, but the arguments for my position
have.

 Human identity is much more than just a file descriptor or a map key,
 and people from academia often don't get this, because they don't have
 to fear using their real names.  Particularly in economically illiberal
 countries being known as the author of a certain Haskell package can get
 you into trouble either at work or even with the government.  It can
 also prevent you from getting a job.

 Nobody should be forced to use their real name anywhere on the internet,
 because unlike a bulletin board in a university, lab or school, the
 internet can be searched by employers easily.


 Greets
 Ertugrul


 --
 nightmare = unsafePerformIO (getWrongWife = sex)
 http://blog.ertes.de/


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announce: hothasktags

2010-04-07 Thread Luke Palmer
On Wed, Apr 7, 2010 at 1:23 AM, Evan Laforge qdun...@gmail.com wrote:
 On Thu, Apr 1, 2010 at 1:46 PM, Luke Palmer lrpal...@gmail.com wrote:
 Hi,

 I'd like to draw attention to a little script I wrote.  I tend to use
 qualified imports and short names like new and filter.  This makes
 hasktags pretty much useless, since it basically just guesses which
 one to go to.  hothasktags is a reimplementation of hasktags that uses
 haskell-src-exts to analyze the import structure to generate (scoped)
 tags pointing to the right definition.  I'm pretty addicted to it,
 since it provides the only functionality I miss from visual studio
 :-).

 VIm only for now, since I don't know if emacs tags format supports
 scoped tags.  I am aware that it is not perfect -- patches and bug
 reports welcome.

 Hi, thanks for this, I've been wanting something like this for a long
 time!  I have a suggestion and a question though:

 If you prepend the tags file with !_TAG_FILE_SORTED\t1\t ~\n then I
 think vim should be able to do a binary search on the file.

Thanks!

 This program generates a tag for each reference to a symbol:

Almost.  It generates a tag for each file/symbol pair such that the
symbol is accessible from the file.


 Derive.PitchDeriver     Derive/Derive.hs        98;    file:Cmd/Cmd.hs
 Derive.PitchDeriver     Derive/Derive.hs        98;    file:Cmd/Play.hs
 Derive.PitchDeriver     Derive/Derive.hs        98;
 file:Cmd/ResponderSync.hs
 ... [ 20 more ] ...

 The vim tag documentation says these are static tags, and implies
 they are meant to apply to symbols only valid within the same file,
 but this is clearly not the case.  Actually, the vim doc implies that
 only file: is defined, and doesn't talk about scoped tags so I'm
 not sure what is going on.  Anyway, whenever I go to a tag I have to
 first step through a message that says 1 of 25 or so.  There's one
 for each reference in the tags file, even though those are references
 in other files.

Hmm odd, I don't get that behavior.  Is that with the sorted
annotation?  What version of vim?

 What's going on?  I even checked the current docs at vim.org and they
 don't mention a file:xyz form either.

I think I saw it documented *somewhere*, but now that I look again I
can't find it anywhere.  Maybe it was in a dream.  I hope a newer
version of vim didn't remove the support or something...

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Luke Palmer
On Wed, Apr 14, 2010 at 4:41 AM,  rocon...@theorem.ca wrote:
 As ski noted on #haskell we probably want to extend this to work on Compact
 types and not just Finite types

 instance (Compact a, Eq b) = Eq (a - b) where ...

 For example (Int - Bool) is a perfectly fine Compact set that isn't finite
 and (Int - Bool) - Int has a decidable equality in Haskell (which Oleg
 claims that everyone knows ;).

 I don't know off the top of my head what the class member for Compact should
 be.  I'd guess it should have a member search :: (a - Bool) - a with the
 specificaiton that p (search p) = True iff p is True from some a. But I'm
 not sure if this is correct or not.  Maybe someone know knows more than I do
 can claify what the member of the Compact class should be.

 http://math.andrej.com/2007/09/28/seemingly-impossible-functional-programs/

Here is a summary of my prelude for topology-extras, which never got
cool enough to publish.

-- The sierpinski space.  Two values: T and _|_ (top and bottom); aka.
halting and not-halting.
-- With a reliable unamb we could implement this as data Sigma = Sigma.
-- Note that negation is not a computable function, so we for example
split up equality and
-- inequality below.
data Sigma

(\/) :: Sigma - Sigma - Sigma   -- unamb
(/\) :: Sigma - Sigma - Sigma   -- seq

class Discrete a where  -- equality is observable
(===) :: a - a - Sigma

class Hausdorff a where  -- inequality is observable
(=/=) :: a - a - Sigma

class Compact a where  -- universal quantifiers are computable
forevery :: (a - Sigma) - Sigma

class Overt a where   -- existential quantifiers are computable
forsome :: (a - Sigma) - Sigma

instance (Compact a, Discrete b) = Discrete (a - b) where
f === g = forevery $ \x - f x === g x

instance (Overt a, Hausdorff b) = Hausdorff (a - b) where
f =/= g = forsome $ \x - f x =/= g x

By Tychonoff's theorem we should have:

instance (Compact b) = Compact (a - b) where
forevert p = ???

But I am not sure whether this is computable, whether (-) counts as a
product topology, how it generalizes to ASD-land [1] (in which I am
still a noob -- not that I am not a topology noob), etc.

Luke

[1] Abstract Stone Duality -- a formalization of computable topology.
http://www.paultaylor.eu/ASD/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread Luke Palmer
On Wed, Apr 14, 2010 at 5:13 AM, Luke Palmer lrpal...@gmail.com wrote:
 On Wed, Apr 14, 2010 at 4:41 AM,  rocon...@theorem.ca wrote:
 As ski noted on #haskell we probably want to extend this to work on Compact
 types and not just Finite types

 instance (Compact a, Eq b) = Eq (a - b) where ...

 For example (Int - Bool) is a perfectly fine Compact set that isn't finite
 and (Int - Bool) - Int has a decidable equality in Haskell (which Oleg
 claims that everyone knows ;).

 I don't know off the top of my head what the class member for Compact should
 be.  I'd guess it should have a member search :: (a - Bool) - a with the
 specificaiton that p (search p) = True iff p is True from some a. But I'm
 not sure if this is correct or not.  Maybe someone know knows more than I do
 can claify what the member of the Compact class should be.

 http://math.andrej.com/2007/09/28/seemingly-impossible-functional-programs/

 Here is a summary of my prelude for topology-extras, which never got
 cool enough to publish.

 -- The sierpinski space.  Two values: T and _|_ (top and bottom); aka.
 halting and not-halting.
 -- With a reliable unamb we could implement this as data Sigma = Sigma.
 -- Note that negation is not a computable function, so we for example
 split up equality and
 -- inequality below.
 data Sigma

 (\/) :: Sigma - Sigma - Sigma   -- unamb
 (/\) :: Sigma - Sigma - Sigma   -- seq

 class Discrete a where  -- equality is observable
    (===) :: a - a - Sigma

 class Hausdorff a where  -- inequality is observable
    (=/=) :: a - a - Sigma

 class Compact a where  -- universal quantifiers are computable
    forevery :: (a - Sigma) - Sigma

 class Overt a where   -- existential quantifiers are computable
    forsome :: (a - Sigma) - Sigma

 instance (Compact a, Discrete b) = Discrete (a - b) where
    f === g = forevery $ \x - f x === g x

 instance (Overt a, Hausdorff b) = Hausdorff (a - b) where
    f =/= g = forsome $ \x - f x =/= g x

Elaborating a little, for Eq we need Discrete and Hausdorff, together
with some new primitive:

-- Takes x and y such that x \/ y = T and x /\ y = _|_, and returns
False if x = T and True if y = T.
decide :: Sigma - Sigma - Bool

Escardo's searchable monad[1][2] from an Abstract Stone Duality
perspective actually encodes compact *and* overt. (a - Bool) - a
seems a good basis, even though it has a weird spec (it gives you an a
for which the predicate returns true, but it's allowed to lie if there
is no such a).  (a - Bool) - Maybe a  seems more appropriate, but it
does not compose well.

I am not sure how I feel about adding an instance of Eq (a - b).  All
this topology stuff gets a lot more interesting and enlightening when
you talk about Sigma instead of Bool, so I think any sort of Compact
constraint on Eq would be a bit ad-hoc.  The issues with bottom are
subtle and wishywashy enough that, if I were writing the prelude, I
would be wary of providing any general mechanism for comparing
functions, leaving those decisions to be tailored to the specific
problem at hand.  On the other hand, with a good unamb
(pleez?) and Sigma, I think all these definitions make perfect
sense.  I think the reason I feel that way is that in Sigma's very
essence lies the concept of bottom, whereas with Bool sometimes we
like to pretend there is no bottom and sometimes we don't.

[1] On hackage: http://hackage.haskell.org/package/infinite-search
[2] Article: 
http://math.andrej.com/2008/11/21/a-haskell-monad-for-infinite-search-in-finite-time/

 By Tychonoff's theorem we should have:

 instance (Compact b) = Compact (a - b) where
    forevert p = ???

 But I am not sure whether this is computable, whether (-) counts as a
 product topology, how it generalizes to ASD-land [1] (in which I am
 still a noob -- not that I am not a topology noob), etc.

 Luke

 [1] Abstract Stone Duality -- a formalization of computable topology.
 http://www.paultaylor.eu/ASD/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FRP for game programming / artifical life simulation

2010-04-21 Thread Luke Palmer
On Wed, Apr 21, 2010 at 4:47 PM, Ben Christy ben.chri...@gmail.com wrote:
 I have an interest in both game programming and artificial life. I have
 recently stumbled on Haskell and would like to take a stab at programming a
 simple game using FRP such as YAMPA or Reactive but I am stuck. I am not
 certain which one I should choose. It seems that Reactive is more active but
 is it suitable for game programming. Also has anyone attempted to implement
 neural networks using FRP if so again which of these two approaches to FRP
 would you suggest?

I am in the process of writing a game using FRP.  I haven't followed
reactive in a while, but last I checked it had some rather annoying
issues, such as joinE (monad join on events) not working and an open
space leak.  So we are using a Yampa-like approach, but not
specifically Yampa.  However most of the game logic is *not* in AFRP
(arrowized FRP) style, it is just there to give a nice foundation
and top level game loop, playing much the same role as IO does in many
Haskell programs (but it is implemented purely!).

The workhorse of our game has so far been generalized differentials.
 While not entirely rigorous, they have provided a very nice framework
in which to express our thoughts and designs, and are very good at
highly dynamic situations which appear in games.  For example, with
arrows it is painful to maintain a list of moving actors such that can
be added and removed.  With differentials this is quite natural.

I haven't published the differential library yet, I am waiting until
we have used them enough to discover essential techniques and find a
nice bases for primitives.  But I will give a sketch here.  Let the
types be your guide, as I am implementing from memory without a
compiler :-P

 import qualified Data.Accessor.Basic as Acc
 import Data.VectorSpace
 import Control.Comonad

A differential is implemented as a function that takes a timestep and
returns an update function.  Don't expose the D constructor; step is
okay to expose, it's kind of a generalized linear approximation.

 newtype D a = D { step :: Double - a - a }

 instance Monoid (D a) where
 mempty = D (const id)
 mappend da db = D (\dt - step da dt . step db dt)

Given a differential for a component of a value, we can construct a
differential for that value.

 accessor :: Acc.T s a - D a - D s
 accessor acc da = D (Acc.modify acc . step da)

Given a differential for each component of a tuple, we can find the
differential for the tuple.

 product :: D a - D b - D (a, b)
 product da db = D (\dt (x,y) - (step da dt x, step db dt y))

A differential can depend on the current value.

 dependent :: (a - D a) - D a
 dependent f = D (\dt x - step (f x) dt x)

Vectors can be treated directly as differentials over themselves.

 vector :: (VectorSpace v, Scalar v ~ Double) = v - D v
 vector v = D (\dt x - x ^+^ dt *^ v)

Impulses allow non-continuous burst changes, such as adding/removing
an element from a list of actors. This is the only function that bugs
me.  Incorrectly using it you can determine the framerate, which is
supposed be hidden.  But if used correctly; i.e. only trigger them on
passing conditions, they can be quite handy.  But my eyes and ears are
open for alternatives.

 impulse :: (a - a) - D a
 impulse f = D (const f)

If we can can find the differential for an element of some comonad
given its context, we can find the differential for the whole
structure.  (Our game world is a comonad, that's why this is in
here)

 comonad :: (Comonad w) = (w a - D a) - D (w a)
 comonad f = D (\dt - let h w = step (f w) dt (extract w) in extend h)

I add new primitives at the drop of a hat. I would like to find a nice
combinator basis, but as yet, one hasn't jumped out at me. It might
require some tweaking of the concept.

The arrow we are using is implemented in terms of differentials:

 data Continuous a b = forall s. Continuous s (s - a - (b, D s))

 instance Category Continuous where
 id = Continuous () (\() x - (x, mempty))
 Continuous sg0 g . Continuous sf0 f = MkC (sg0,sf0) $ \(sg,sf) x -
 let !(y, df) = f sf x -- mind the strict patterns
 !(z, dg) = g sg y in
 (z, product dg df)

Exercise: implement the Arrow and ArrowLoop instances.

And here is where it comes together.  Integration over generalized
differentials is a continuous arrow:

 integral :: Continuous (D a) a
 integral a0 = Continuous a0 (,)

So our game loop looks something like:

 dGameState :: Input - D GameState
 dGameState = ... -- built out of simpler Ds of its components

 mainGame = proc input - do
 gameState - integral initialGameState - dGameState input
 returnA - drawGameState gameState

This is my first experience with functional game programming, and so
far I love it!  It makes so much more sense than the imperative
alternative.  But the techniques are quite new and different as well,
and sometimes it takes a lot of thinking to figure out how to do
something that 

Re: [Haskell-cafe] I need help getting started

2010-04-24 Thread Luke Palmer
On Sat, Apr 24, 2010 at 10:34 PM,  mitch...@kaplan2.com wrote:
 Hi,



 I’m just starting to learn, or trying to learn Haskell.  I want to write a
 function to tell me if a number’s prime.  This is what I’ve got:



 f x n y = if n=y

   then True

   else

   if gcd x n == 1

   then f x (n+1) y

   else False





 primeQ x = f x 2 y

   where y = floor(sqrt(x))

Pretty good so far.  The only trouble is that the type of x is
inconsistent. In f it is an integer, but in primeQ it is a floating
point (because you are taking its square root).  Getting past this
just involves understanding Haskell's type system peculiarities.
Change that last line to:

where y = floor (sqrt (fromIntegral x))

And you should be fine.  (Untested)

In the future, post the error that you are getting addition to the
code that is causing it.  That helps us find it faster.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] singleton types

2010-04-25 Thread Luke Palmer
2010/4/25 Günther Schmidt gue.schm...@web.de:
 Hello,

 HaskellDB makes extensive use of Singleton Types, both in its original
 version and the more recent one where it's using HList instead of the legacy
 implementation.

 I wonder if it is possible, not considering feasibility for the moment, to
 implement HaskellDB *without* using Singleton Types.

Would you please define singleton type?

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Learning about Programming Languages (specifically Haskell)

2010-05-03 Thread Luke Palmer
On Mon, May 3, 2010 at 9:17 AM, Kyle Murphy orc...@gmail.com wrote:
 Reasons to learn Haskell include:
 Lazy evaluation can make some kinds of algorithms possible to implement that
 aren't possible to implement in other languages (without modification to the
 algorithm).

One could say the reverse as well.

I would say that laziness allows many more *compositions* of
algorithms.  Many more objects can be described from simple building
blocks (combinators).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strict type system allows for a maximum number of programming errors to be caught at compile time.

2010-05-03 Thread Luke Palmer
On Mon, May 3, 2010 at 9:34 AM, Casey Hawthorne cas...@istar.ca wrote:
Strict type system allows for a maximum number of programming errors to be 
caught at compile time.

 I keep hearing this statement but others would argue that programming
 errors caught at compile time only form a minor subset of all errors
 caught.

 So, in functional programming languages with a strict type system,
 e.g. Haskell, do typing errors from a larger subset of all programming
 errors.

Absolutely!  Haskell developers trade debugging time for time arguing
with the compiler about the correctness of their code.

I'll give this meaningless anecdotal statistic:

Compiler says my code is right = My code is actually right   -- 60%
Compiler says my code is wrong = My code is actually wrong -- 95%

Haskell has a particular reputation for the former.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strict type system allows for a maximum number of programming errors to be caught at compile time.

2010-05-03 Thread Luke Palmer
On Mon, May 3, 2010 at 11:07 AM, Kyle Murphy orc...@gmail.com wrote:
 The problem with dynamic typing is that it has a much higher chance of
 having a subtle error creep into your code that can go undetected for a long
 period of time. A strong type system forces the code to fail early where
 it's easier to track down and fix the problem, rather than trying to perform
 debugging on the fly in a production system. This has an added advantage for
 compiled languages in that for many non-trivial applications the time to
 build and deploy a new instance of the program, even in the development
 environment is often substantial, and the more trivial errors are discovered
 at compile time, the less time is wasted on builds.

 For small code bases the time spent tracking down a error at runtime might
 be less than the time spent making your code conform to strict type
 requirements, but for larger code bases the amount of time necessary to
 track down such errors greatly out weighs the amount of time needed to make
 your code well typed.

 To look at the flip side of your statistics:
 Compiler says my code is right = My code is actually wrong -- 40%
 Compiler says my code is wrong = My code is actually right -- 5%

 I'd argue this is provably wrong, as correct code by definition would compile.

Here is a contrived example of what I am referring to:

prefac f 0 = 1
prefac f n = n * f (n-1)

fac = (\x - x x) (\x - prefac (x x))

If this code were allowed to compile (say by inserting unsafeCoerce
anywhere you like), it would correctly implement a factorial function.

It is precisely these cases behind the dynamically typed languages'
advocacy: my code is right but I can't (or it is too much work to)
convince the compiler of that fact.  It is a pretty bold statement to
say that these do not occur.

 The fact that it doesn't is proof enough that there's a problem
 with it even if that problem is simply that the types you're using aren't
 exactly correct. Further, I'd argue that in the first instance with a
 non-strict type system, the instance of wrong code that compiles would be
 higher. The only argument to support non-strict typing would be if you could
 show that it takes less time to track down runtime bugs than it does to fix
 compile time type errors, and any such claim I'd be highly skeptical of.

Clearly.  But many people believe in this methodology, and use test
suites and code coverage instead of types.  Indeed, such practices are
essentially empirical type checking, and they afford the advantage
that their verification is much more expressive (however less
reliable) than our static type system, because they may use arbitrary
code to express their predicates.

What I seem to be getting at is this plane of type systems:

Constrained - Expressive
Unreliable
|   (C)
|(test suites)
|   (C++).
|.
|   (Java/C#)(Scala) .
|.
|.
|   (Haskell).
|
| (Agda)
Reliable


Where by Constrained/Expressive I mean the ability for the system to
express properties *about the code* (so C++'s type system being turing
complete is irrelevant).  By Unreliable/Reliable I mean, given popular
engineering practice in that language, the chance that if it passes
the checks then it works as intended.  For all the languages, I mean
their compilers.  Test suites extend down the right-hand side,
depending on how rigorous you are about testing, but they never get as
far down as Agda.  :-)

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strict type system allows for a maximum number of programming errors to be caught at compile time.

2010-05-03 Thread Luke Palmer
On Mon, May 3, 2010 at 10:13 PM, Ivan Miljenovic
ivan.miljeno...@gmail.com wrote:
 On 4 May 2010 13:30, Luke Palmer lrpal...@gmail.com wrote:
 Here is a contrived example of what I am referring to:

 prefac f 0 = 1
 prefac f n = n * f (n-1)

 fac = (\x - x x) (\x - prefac (x x))

 I can't work out how this works (or should work rather); is it meant
 to be using church numerals or something (assuming that they have been
 made an instance of Num so that - and * work)?

No they're just integers.  fac is a beta expansion of fix prefac.
Obseve the magic:

   (\x - x x) (\x - prefac (x x)) 2
   (\x - prefac (x x)) (\x - prefac (x x)) 2
   prefac ((\x - prefac (x x)) (\x - prefac (x x))) 2
   2 * ((\x - prefac (x x)) (\x - prefac (x x)) (2-1)
   2 * prefac ((\x - prefac (x x)) (\x - prefac (x x))) (2-1)
  2 * prefac ((\x - prefac (x x)) (\x - prefac (x x))) 1
   2 * (1 * ((\x - prefac (x x)) (\x - prefac (x x))) (1-1))
   2 * (1 * prefac ((\x - prefac (x x)) (\x - prefac (x x))) (1-1))
   2 * (1 * prefac ((\x - prefac (x x)) (\x - prefac (x x))) 0)
   2 * (1 * 1)
   2

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: has-0.4 Entity based records

2010-05-04 Thread Luke Palmer
On Tue, May 4, 2010 at 10:18 AM, HASHIMOTO, Yusaku nonow...@gmail.com wrote:
 Hello,

 I'm pleased to announce the release of my new library, named has,
 written to aim to ease pain at inconvinience of Haskell's build-in
 records.

Hmm, nice work, looks interesting.

 With the has, You can reuse accessors over records to write generic
 function, combine records with another.

 Repository is at GitHub: http://github.com/nonowarn/has
 Uploaded on Hackage: http://hackage.haskell.org/package/has

 So you can install this by cabal install has

 You can use the has in three steps (without counting installation).

 1. Write {-# OPTIONS_GHC -fglasgow-exts #-} top of your code,

This is going out of style.  It would be nice to know specifically
what LANGUAGE extensions are necessary.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proof question -- (==) over Bool

2010-05-21 Thread Luke Palmer
2010/5/21 R J rj248...@hotmail.com:
 I'm trying to prove that (==) is reflexive, symmetric, and transitive over
 the Bools, given this definition:
 (==)                       :: Bool - Bool - Bool
 x == y                     =  (x  y) || (not x  not y)
 My question is:  are the proofs below for reflexivity and symmetricity
 rigorous, and what is the proof of transitivity, which eludes me?  Thanks.

 Theorem (reflexivity):  For all x `elem` Bool, x == x.
 Proof:
       x == x
   =    {definition of ==}
       (x  x) || (not x  not x)
   =    {logic (law of the excluded middle)}
       True

This one depends on what you mean by rigorous.  But you would have to
have lemmas showing that  and || correspond to the predicate logic
notions.  I would do this by cases:

x = True:
  (True  True) || (not True  not True)
  ...
  True || False
  True
x = False
  (False  False) || (not False  not False)
  ...
  False || True
  True



 Theorem (symmetricity):  For all x, y `elem` Bool, if x == y, then y == x.
 Proof:
       x == y
   =    {definition of ==}
       (x  y) || (not x  not y)
   =    {lemma:  () is commutative}
       (y  x) || (not x  not y)
   =    {lemma:  () is commutative}
       (y  x) || (not y  not x)
   =    {definition of ==}
       y == x

Yes, given the lemmas about  and ||, this is rigorous.  You can
prove those lemmas by case analysis.

 Theorem (transitivity):  For all x, y, z `elem` Bool, if x == y, and y == z,
 then x == z.
 Proof: ?

My first hunch here is to try the following lemma:

  Lemma: if (x == y) = True if and only if x = y.

where == is the version you defined, and = is regular equality from
logic, if you are allowed to rely on that.  I would prove this by
cases.

At this point, you can convert transitivity of == to transitivity of
=, which is assumed by the axioms.  You could do the same for the
other proofs you asked about instead of brute-forcing them.

If you aren't allowed such magic, then I guess you could do all 8
cases of x, y, and z (i.e. proof by truth table).  Somebody else might
have a cleverer idea.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to Show an Operation?

2010-06-09 Thread Luke Palmer
On Wed, Jun 9, 2010 at 12:33 PM, Martin Drautzburg
martin.drautzb...@web.de wrote:
 So far so good. However my Named things are all functions and I don't see I
 ever want to map over any of them. But what I'd like to do is use them like
 ordinary functions as in:

 f::Named (Int-Int)
 f x

 Is there a way to do this, other than writing

 apply::Named Int -Int
 apply n x = (val_of n) x

What's wrong with that?  (Other than the type signature, but I get
what you mean).  The proper type signature is apply :: Named (Int -
Int) - Int - Int.

You don't need the parentheses:

apply n x = val_of n x

Or just:

apply = val_of

I frequently suggest the following to new Haskellers: don't worry so
much about notation.  Sometimes programmers get a picture in their
heads about how the code *should* look, and then they go through all
manner of ugly contortions to make the notation right.

I suggest that you will encounter much less pain if you accept
Haskell's straightforward notation, and focus on the meaning rather
than the syntax of your program.

So, to summarize:  if you have something that isn't a function and you
want to use it like a function, convert it to a function (using
another function :-P).  That's all.  No syntax magic, just say what
you're doing.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Thread scheduling

2010-06-10 Thread Luke Palmer
On Thu, Jun 10, 2010 at 11:50 AM, Andrew Coppin
andrewcop...@btinternet.com wrote:
 Control.Concurrent provides the threadDelay function, which allows you to
 make the current thread sleep until T=now+X. However, I can't find any way
 of making the current thread sleep until T=X. In other words, I want to
 specify an absolute wakeup time, not a relative one.

Modulo a small epsilon between the two actions, can't you just get the
current time and subtract it from the target time?  threadDelay is
allowed to delay for too long anyway, so doing it this way does not
lose you any correctness.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Thread scheduling

2010-06-10 Thread Luke Palmer
Say, using System.Time.getClockTime.

Luke

On Thu, Jun 10, 2010 at 11:31 PM, Luke Palmer lrpal...@gmail.com wrote:
 On Thu, Jun 10, 2010 at 11:50 AM, Andrew Coppin
 andrewcop...@btinternet.com wrote:
 Control.Concurrent provides the threadDelay function, which allows you to
 make the current thread sleep until T=now+X. However, I can't find any way
 of making the current thread sleep until T=X. In other words, I want to
 specify an absolute wakeup time, not a relative one.

 Modulo a small epsilon between the two actions, can't you just get the
 current time and subtract it from the target time?  threadDelay is
 allowed to delay for too long anyway, so doing it this way does not
 lose you any correctness.

 Luke

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: How to Show an Operation?

2010-06-10 Thread Luke Palmer
On Thu, Jun 10, 2010 at 10:43 PM, Brandon S. Allbery KF8NH
allb...@ece.cmu.edu wrote:
 On Jun 10, 2010, at 17:38 , Martin Drautzburg wrote:

 instance Applicative Named where
   pure x = Named  x
   (Named s f) * (Named t v) = Named (s ++ ( ++ t ++ )) (f v)

 Applicative. Need to study that

 The above is just the Functor, rephrased in Applicative style.  * is
 exactly fmap.  Likewise, Monad has a function liftM which is exactly fmap.
  (For historical reasons, these are not related the way they should be:  all
 Monads should be Applicatives, all Applicatives should be Functors, and all
 Functors should be instances of an even more primitive class Pointed.)

(*) :: Applicative f = f (a - b) - f a - f b
($) :: Functor f = (a - b) - f a - f b

($) is fmap, not (*).  (*) is available for monads as Control.Monad.ap.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


  1   2   3   4   5   6   7   >