Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Where is hugs (or other) version of gofer
      modular-interpreter code? (Larry Evans)
   2.  curry in a hurry (prad)
   3. Re:  Where is hugs (or other) version of gofer
      modular-interpreter code? (Stephen Tetley)
   4. Re:  curry in a hurry (MAN)
   5. Re:  curry in a hurry (Daniel Fischer)
   6. Re:  curry in a hurry (Brandon S Allbery KF8NH)
   7. Re:  curry in a hurry (Daniel Fischer)


----------------------------------------------------------------------

Message: 1
Date: Sat, 03 Jul 2010 16:13:18 -0500
From: Larry Evans <cppljev...@suddenlink.net>
Subject: [Haskell-beginners] Where is hugs (or other) version of gofer
        modular-interpreter code?
To: beginners@haskell.org
Message-ID: <4c2fa7ee.5070...@suddenlink.net>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Page 2 of:

http://www.cs.yale.edu/~liang-sheng/popl95.ps.gz

says the source code is at:

  nebula.cs.yale.edu/pub/yale-fp/modular-interpreter

However, that's no longer present.

Since Hugs is the successor to gofer, I was wondering
if anyone could tell me how to get a copy of the
corresponding hugs code.

TIA.

-Larry


------------------------------

Message: 2
Date: Sat, 3 Jul 2010 15:19:24 -0700
From: prad <p...@towardsfreedom.com>
Subject: [Haskell-beginners] curry in a hurry
To: haskellbeginners <beginners@haskell.org>
Message-ID: <20100703151924.14f6e...@gom>
Content-Type: text/plain; charset=US-ASCII

today i'm trying to understand curry and uncurry (in 3 parts with
specific questions labelled as subsections of the parts).


part 1

if we have 

f (x,y) = x + y
this is a function working on a single argument (x,y) albeit composed
of 2 parameters. however, since all functions are curried in haskell
(read that here: http://www.haskell.org/haskellwiki/Currying), what is
really happening is 

(f x) y
or specific to this case (+ x) y since f ends up being (+) as defined.

now if we write
g = curry f
we are naming a function whose purpose is to (f x) whatever comes its
way allowing us to do neat things like:

map (g 3) [4,5,6]
[7,8,9]

which we can't do by map (f 3) [4,5,6] because 
f :: (Num t) => (t, t) -> t
meaning f 
- is a function ... the (Num t)
- applies itself ... the =>
- to a Pair of (Num t)s 
- gives back a Num t

1.1 am i reading the type statement correctly?

while 
g :: Integer -> Integer -> Integer
means g takes an Integer, applies itself and that Integer to another
Integer and computes another Integer.

1.2 how come these are Integer suddenly and not Num t?

this is a problem because while i can do
f (2.3,9.3)
i get an error when i try
(g 2.3) 9.3
ghci wants an instance declaration for (Fractional Integer) which
puzzles me because g came about through currying f which is fine with
fractions.


part 2

now the next discovery is really strange to me.

if i name 

f x y = x + y
we see f :: (Num a) => a -> a -> a
which looks like the curried form of f (x,y)
in fact that's what it exactly is and i can do
map (f 3) [4,5,6]
[7,8,9]
just as i did with g before!!

which is what the wiki statement says too:

f :: a -> b -> c
is the curried form of
g :: (a, b) -> c

however, it starts by stating:

"Currying is the process of transforming a function that takes multiple
arguments into a function that takes just a single argument and returns
another function if any arguments are still needed."
http://www.haskell.org/haskellwiki/Currying

2.1 so does all this mean that

f (x,y) is the function that takes multiple arguments and not a single
argument as i initially thought 

and 

f x y is the function that actually takes a single argument twice?




part 3

some of the above seems to be confirmed by looking at these types

c x y = x + y
c :: (Num a) => a -> a -> a
so that's curried

u (x,y) = x + y
u :: (Num t) => (t,t) -> t
so that's uncurried

:t uncurry c
uncurry c :: (Num a) => (a, a) -> a

:t curry u
curry u :: (Num a) => a -> a -> a


but


:t uncurry u
uncurry u :: (Num (b -> c)) => ((b -> c, b -> c), b) -> c
we're trying to uncurry something that is already uncurried

and

:t curry c
curry c :: (Num (a, b)) => a -> b -> (a, b) -> (a, b)
we're trying to curry something that is already curried

3.1 just what are these strange looking things and how should their
types be interpreted?


-- 
In friendship,
prad

                                      ... with you on your journey
Towards Freedom
http://www.towardsfreedom.com (website)
Information, Inspiration, Imagination - truly a site for soaring I's


------------------------------

Message: 3
Date: Sat, 3 Jul 2010 23:22:25 +0100
From: Stephen Tetley <stephen.tet...@gmail.com>
Subject: Re: [Haskell-beginners] Where is hugs (or other) version of
        gofer   modular-interpreter code?
To: Larry Evans <cppljev...@suddenlink.net>
Cc: beginners@haskell.org
Message-ID:
        <aanlktikebnfzu8trcnvbcygwhles3odkokjp7s778...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hello

You might want to look at Wolfram Kahl's update of the modular
interpreter code to Haskell 98:

http://www.cas.mcmaster.ca/~kahl/FP/2003/
http://www.cas.mcmaster.ca/~kahl/FP/2003/Interpreter.pdf
http://www.cas.mcmaster.ca/~kahl/FP/2003/Interpreter.lhs

Best wishes

Stephen


------------------------------

Message: 4
Date: Sat, 03 Jul 2010 20:18:24 -0300
From: MAN <elviotoccal...@gmail.com>
Subject: Re: [Haskell-beginners] curry in a hurry
To: prad <p...@towardsfreedom.com>
Cc: haskellbeginners <beginners@haskell.org>
Message-ID: <1278199105.3104.1.ca...@dy-book>
Content-Type: text/plain; charset="UTF-8"

I'm sure a more thorough answer would come from a more experienced
Haskell user, but I'm gonna go and through my two cents just in case it
helps:

part 1:
'f' takes one argument (albeit one which is not concrete), 'g' takes two
arguments. The Integer/Num discrepancy you experience is due to ghci
pushing the types a bit... put your code in a file for better results.

part 2:
'f x y' has this type: 
f :: (Num t) => t -> t -> t

which you could read as...
f :: (Num t) => t -> (t -> t)
... to make the curry'ing more evident.

You'd see that 'f' takes a single argument, a 't' which belongs to
type-class Num, and returns some unknown function with type 't ->
t' (where the type constrain for 't' still holds). However, to keep it
simple, just say that 'f' takes two arguments ;)

part 3:
I refuse to put myself through that twisted experiment of yours :P
Seriously, though, I have no sufficient knowledge to answer with
confidence.

El sáb, 03-07-2010 a las 15:19 -0700, prad escribió:
> today i'm trying to understand curry and uncurry (in 3 parts with
> specific questions labelled as subsections of the parts).
> 
> 
> part 1
> 
> if we have 
> 
> f (x,y) = x + y
> this is a function working on a single argument (x,y) albeit composed
> of 2 parameters. however, since all functions are curried in haskell
> (read that here: http://www.haskell.org/haskellwiki/Currying), what is
> really happening is 
> 
> (f x) y
> or specific to this case (+ x) y since f ends up being (+) as defined.
> 
> now if we write
> g = curry f
> we are naming a function whose purpose is to (f x) whatever comes its
> way allowing us to do neat things like:
> 
> map (g 3) [4,5,6]
> [7,8,9]
> 
> which we can't do by map (f 3) [4,5,6] because 
> f :: (Num t) => (t, t) -> t
> meaning f 
> - is a function ... the (Num t)
> - applies itself ... the =>
> - to a Pair of (Num t)s 
> - gives back a Num t
> 
> 1.1 am i reading the type statement correctly?
> 
> while 
> g :: Integer -> Integer -> Integer
> means g takes an Integer, applies itself and that Integer to another
> Integer and computes another Integer.
> 
> 1.2 how come these are Integer suddenly and not Num t?
> 
> this is a problem because while i can do
> f (2.3,9.3)
> i get an error when i try
> (g 2.3) 9.3
> ghci wants an instance declaration for (Fractional Integer) which
> puzzles me because g came about through currying f which is fine with
> fractions.
> 
> 
> part 2
> 
> now the next discovery is really strange to me.
> 
> if i name 
> 
> f x y = x + y
> we see f :: (Num a) => a -> a -> a
> which looks like the curried form of f (x,y)
> in fact that's what it exactly is and i can do
> map (f 3) [4,5,6]
> [7,8,9]
> just as i did with g before!!
> 
> which is what the wiki statement says too:
> 
> f :: a -> b -> c
> is the curried form of
> g :: (a, b) -> c
> 
> however, it starts by stating:
> 
> "Currying is the process of transforming a function that takes multiple
> arguments into a function that takes just a single argument and returns
> another function if any arguments are still needed."
> http://www.haskell.org/haskellwiki/Currying
> 
> 2.1 so does all this mean that
> 
> f (x,y) is the function that takes multiple arguments and not a single
> argument as i initially thought 
> 
> and 
> 
> f x y is the function that actually takes a single argument twice?
> 
> 
> 
> 
> part 3
> 
> some of the above seems to be confirmed by looking at these types
> 
> c x y = x + y
> c :: (Num a) => a -> a -> a
> so that's curried
> 
> u (x,y) = x + y
> u :: (Num t) => (t,t) -> t
> so that's uncurried
> 
> :t uncurry c
> uncurry c :: (Num a) => (a, a) -> a
> 
> :t curry u
> curry u :: (Num a) => a -> a -> a
> 
> 
> but
> 
> 
> :t uncurry u
> uncurry u :: (Num (b -> c)) => ((b -> c, b -> c), b) -> c
> we're trying to uncurry something that is already uncurried
> 
> and
> 
> :t curry c
> curry c :: (Num (a, b)) => a -> b -> (a, b) -> (a, b)
> we're trying to curry something that is already curried
> 
> 3.1 just what are these strange looking things and how should their
> types be interpreted?
> 
> 




------------------------------

Message: 5
Date: Sun, 4 Jul 2010 01:17:45 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] curry in a hurry
To: beginners@haskell.org
Cc: prad <p...@towardsfreedom.com>
Message-ID: <201007040117.45812.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

On Sunday 04 July 2010 00:19:24, prad wrote:
> today i'm trying to understand curry and uncurry (in 3 parts with
> specific questions labelled as subsections of the parts).
>
>
> part 1
>
> if we have
>
> f (x,y) = x + y
> this is a function working on a single argument (x,y) albeit composed
> of 2 parameters. however, since all functions are curried in haskell
> (read that here: http://www.haskell.org/haskellwiki/Currying), what is
> really happening is
>
> (f x) y

Not really, f takes a tuple as argument.

> or specific to this case (+ x) y since f ends up being (+) as defined.

It would be ((+) x), which is the same as (x +) rather than (+ x)

>
> now if we write
> g = curry f
> we are naming a function whose purpose is to (f x) whatever comes its
> way allowing us to do neat things like:
>
> map (g 3) [4,5,6]
> [7,8,9]
>
> which we can't do by map (f 3) [4,5,6] because

You'd have to use 

map (f . (,) 3) [4,5,6]

generally,

curry fun x

is tha same as

fun . (,) x

the function composed with the partially applied tuple constructor.

> f :: (Num t) => (t, t) -> t
> meaning f
> - is a function ... the (Num t)
> - applies itself ... the =>
> - to a Pair of (Num t)s
> - gives back a Num t
>
> 1.1 am i reading the type statement correctly?

No, correctly, it would read

f is a function taking a pair of t's and returning a t, provided t is a 
member of the Num class

or

for all members t of Num, f is a function from (t,t) to t

>
> while
> g :: Integer -> Integer -> Integer
> means g takes an Integer, applies itself and that Integer to another
> Integer and computes another Integer.
>
> 1.2 how come these are Integer suddenly and not Num t?

It's the monomorphism restriction.
By the monomorphism restriction, a name boud by a binding of the form

val = rhs

without a type signature must have a monomorphic type. Thus the natural 
polymorphic type of g is made monomorphic by instantiating the type 
variable t to Integer.

You can avoid that by
- giving a type signature for g
- binding g by a function binding, i.e. with at least one argument to the 
left of '='
or
- turning off the monomorphism restriction.

Since the monomorphism restriction bites mostly in ghci sessions, it is 
generally a good idea to put the line

:set -XNoMonomorphismRestriction

in your .ghci file

(you can turn it off in source files with 
{-# LANGUAGE NoMonomorphismRestriction #-}
or on the command line with -XNoMonomorphismRestriction
)

>
> this is a problem because while i can do
> f (2.3,9.3)
> i get an error when i try
> (g 2.3) 9.3
> ghci wants an instance declaration for (Fractional Integer) which
> puzzles me because g came about through currying f which is fine with
> fractions.

Since g's type was monomorphised to Integer -> Integer -> Integer, ghci 
tries to interpret 2.3 and 9.3 as Integers.
But numeric literals of that form have type
Fractional a => a
(and are interpreted as 
fromRational 2.3)
so ghci wants to have an instance of the Fractional calss for Integer to 
know how to interpret 2.3 and 9.3 as Integers.

>
>
> part 2
>
> now the next discovery is really strange to me.
>
> if i name
>
> f x y = x + y
> we see f :: (Num a) => a -> a -> a

Yes, f is defined with arguments to the left of '=', so it isn't subjected 
to the monomorphism restriction.
If you'd defined

f = \x y -> x + y

the MR would kick in again.

> which looks like the curried form of f (x,y)

not only looks it like that, it is that

> in fact that's what it exactly is and i can do
> map (f 3) [4,5,6]
> [7,8,9]
> just as i did with g before!!
>
> which is what the wiki statement says too:
>
> f :: a -> b -> c
> is the curried form of
> g :: (a, b) -> c
>
> however, it starts by stating:
>
> "Currying is the process of transforming a function that takes multiple
> arguments into a function that takes just a single argument and returns
> another function if any arguments are still needed."
> http://www.haskell.org/haskellwiki/Currying

Which is somewhat incorrect. Every function takes exactly one argument, 
curried or not. (It is however, much more convenient to speak of functions 
taking four arguments of types a1 a2 a3 a4 and returning a value of type b 
than of functions taking an argument of type a1 returning a function taking 
anargument of type a2 returning a function taking an argument of type a3 
..., so we do that usually).

Some functions, however, take a tuple as argument.
And there's a natural correspondence between

(a,b) -> c

and

a -> b -> c

that correspondence in one direction is curry, in the other direction, 
uncurry

>
> 2.1 so does all this mean that
>
> f (x,y) is the function that takes multiple arguments and not a single
> argument as i initially thought

No, your initial thought is correct, f takes a single argument, which is a 
pair. (Well, since tuples are composed of several components, it is also a 
common way of speech to say that functions taking a tuple argument take 
several arguments. In that sense, f takes two arguments. But in Haskell-
speak, it's more common to say a function
fun :: a -> b -> c
takes two arguments - of course, if c is a function type, we can also say 
that f takes three [or more] arguments.)

>
> and
>
> f x y is the function that actually takes a single argument twice?
>

That is more correct.

>
>
>
> part 3
>
> some of the above seems to be confirmed by looking at these types
>
> c x y = x + y
> c :: (Num a) => a -> a -> a
> so that's curried

Yes.

>
> u (x,y) = x + y
> u :: (Num t) => (t,t) -> t
> so that's uncurried

Yes.

>
> :t uncurry c
>
> uncurry c :: (Num a) => (a, a) -> a
>
> :t curry u
>
> curry u :: (Num a) => a -> a -> a
>
>
> but
>
> :t uncurry u
>
> uncurry u :: (Num (b -> c)) => ((b -> c, b -> c), b) -> c
> we're trying to uncurry something that is already uncurried

Yes. To apply uncurry, u must have a type a -> b -> c
u has the type (t,t) -> t [we ignore the Num constraint here, as it's not 
important]

to match (t,t) -> t with a -> b -> c [or, with parentheses, a -> (b -> c)]

we must match the types before the '->', i.e.

a ~ (t,t)

and the types after the '->', i.e.

(b -> c) ~ t

So, with these matchings, the type of u must be

u :: (b -> c, b -> c) -> b -> c

with a Num constraint on (b -> c) ~ t.
(there's no standard Num instance for any function type, but you can write 
such instances [more or less sensible if the result type is a Num 
instance].

>
> and
>
> :t curry c
>
> curry c :: (Num (a, b)) => a -> b -> (a, b) -> (a, b)
> we're trying to curry something that is already curried

Yes, we have

c :: Num n => n -> n -> n
curry :: ((a,b) -> d) -> a -> b -> d

So to figure out curry c, we must match c's type to the type of curry's 
argument, i.e. we must match n -> n -> n to (a,b) -> d [again ignoring the 
Num constraint for the moment].

We must match the types before the '->', i.e.

n ~ (a,b)

and the types after, i.e.

n -> n ~ d

so

c :: Num (a,b) => (a,b) -> (a,b) -> (a,b)

and 

curry c :: Num (a,b) => a -> b -> (a,b) -> (a,b)

>
> 3.1 just what are these strange looking things and how should their
> types be interpreted?

HTH,
Daniel



------------------------------

Message: 6
Date: Sat, 03 Jul 2010 19:37:48 -0400
From: Brandon S Allbery KF8NH <allb...@ece.cmu.edu>
Subject: Re: [Haskell-beginners] curry in a hurry
To: beginners@haskell.org
Message-ID: <4c2fc9cc.7050...@ece.cmu.edu>
Content-Type: text/plain; charset=UTF-8

-----BEGIN PGP SIGNED MESSAGE-----
Hash: SHA1

El sáb, 03-07-2010 a las 15:19 -0700, prad escribió:
>> :t uncurry u
>> uncurry u :: (Num (b -> c)) => ((b -> c, b -> c), b) -> c
>> we're trying to uncurry something that is already uncurried
>>
>> and
>>
>> :t curry c
>> curry c :: (Num (a, b)) => a -> b -> (a, b) -> (a, b)
>> we're trying to curry something that is already curried
>>
>> 3.1 just what are these strange looking things and how should their
>> types be interpreted?

(uncurry u):  "given a function from b to c which is an instance of Num,
transform the pair of pairs ( (b -> c) , (b -> c) , b) to c.  This is easier
to see if you replace (b -> c) with a temporary name `f':  ((f, f), b) -> c.
 Remember that GHC doesn't know what "Num" means, so it is free to invent
apparently nonsensical typeclass members.  (That said, they might actually
be meaningful in some contexts; look up Church numerals.)

(curry c):  you can see this one by re-parenthesizing.  (a -> b) -> ((a,b)
- -> (a,b)), given that (a,b) is an instance of Num.  (Raise a function from a
to b, to a function from a pair (a,b) to another pair (a,b).)  This too
looks odd; but consider Gaussian integers, which are slightly less general,
being ((Num a) => (a,a)).  You could also think of it as a Num with a "tag"
of arbitrary type, ((Num a) => (a,b)).

- -- 
brandon s. allbery     [linux,solaris,freebsd,perl]      allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university      KF8NH
-----BEGIN PGP SIGNATURE-----
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkwvycwACgkQIn7hlCsL25W7jgCeLdu+iCANQneCHAmGOk4+7QHN
2UAAoJXHCBWP4WaAj9K3Io+pv0h8L1GR
=ti56
-----END PGP SIGNATURE-----


------------------------------

Message: 7
Date: Sun, 4 Jul 2010 01:41:29 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] curry in a hurry
To: beginners@haskell.org
Cc: prad <p...@towardsfreedom.com>
Message-ID: <201007040141.29839.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="utf-8"

On Sunday 04 July 2010 01:18:24, MAN wrote:
> The Integer/Num discrepancy you experience is due to ghci
> pushing the types a bit... put your code in a file for better results.
>
That depends. If you put the definition

g = curry f

at the top level of the module *and g is exported from the module*, the 
monomorphism restriction still applies. If g is not exported from the 
module (be it by not putting it in the module's explicit export list or 
because it's a local definition and not a top level definition), the MR 
does not apply and g has its fully polymorphic type.

Yes, MR is fun, fun, fun.

But generally, MR problems occur far more seldomly in source files than 
ghci sessions.
>
> part 3:
> I refuse to put myself through that twisted experiment of yours :P

It's not so bad actually. It looks daunting at first, but if it's broken 
down a bit, it's understandable, I think.



------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 25, Issue 10
*****************************************

Reply via email to