
I'm trying to learn Haskell and translating some Lisp functions as exercises. How would I write a Haskell function named ALWAYS that behaves like this: one = always 1 bozo = always "clown"
map one [2,3,4,5,6] [1,1,1,1,1]
one 62 1
map bozo [2,3,4,5,6] ["clown","clown" ,"clown", "clown"," clown"]
bozo 62 "clown"
i.e. ALWAYS returns a function with a single parameter that is ignored, returning instead the value given to ALWAYS when the function was created. This is what I've been trying: always :: (a -> a) -> a -> a always x = (\y -> x) one = always 1 Michael __________________________________________________ Do You Yahoo!? Tired of spam? Yahoo! Mail has the best spam protection around http://mail.yahoo.com

I'm trying to learn Haskell and translating some Lisp functions as exercises.
How would I write a Haskell function named ALWAYS that behaves like this:
one = always 1 bozo = always "clown"
map one [2,3,4,5,6] [1,1,1,1,1]
one 62 1
map bozo [2,3,4,5,6] ["clown","clown" ,"clown", "clown"," clown"]
bozo 62 "clown"
i.e. ALWAYS returns a function with a single parameter that is ignored, returning instead the value given to ALWAYS when the function was created.
This is what I've been trying:
always :: (a -> a) -> a -> a always x = (\y -> x)
one = always 1
Michael
First, you want 'one' to take an integer and return 1. So,
one :: Integer -> Integer
since one = always 1, then
always 1 :: Integer -> Integer
So, 'always' takes an Integer and returns an Integer -> Integer
always :: Integer -> (Integer -> Integer)
But that's the same as
always :: Integer -> Integer -> Integer
You actually have the implementation correct, you just didn't have the right type signature.
always first = (\second -> first)
Of course, neither of these implementations need to be tied to Integers; they can be polymorphic. So, we end up with: always :: a -> b -> a -- no reason the second parameter has to be the same type as the first, so use 'b' instead of 'a'. always first = (\_ -> first) -- replace 'second' with '_', because we don't need to bind anything to the second parameter. Does that makes sense? Bryan Burgers

Thanks Brian. I think these signatures are starting to
make sense. And I didn't know "_" (don't care) could
be used like that. I'm liking Haskell more and more.
Michael
--- Bryan Burgers
I'm trying to learn Haskell and translating some Lisp functions as exercises.
How would I write a Haskell function named ALWAYS that behaves like this:
one = always 1 bozo = always "clown"
map one [2,3,4,5,6] [1,1,1,1,1]
one 62 1
map bozo [2,3,4,5,6] ["clown","clown" ,"clown", "clown"," clown"]
bozo 62 "clown"
i.e. ALWAYS returns a function with a single parameter that is ignored, returning instead the value given to ALWAYS when the function was created.
This is what I've been trying:
always :: (a -> a) -> a -> a always x = (\y -> x)
one = always 1
Michael
First, you want 'one' to take an integer and return 1. So,
one :: Integer -> Integer
since one = always 1, then
always 1 :: Integer -> Integer
So, 'always' takes an Integer and returns an Integer -> Integer
always :: Integer -> (Integer -> Integer)
But that's the same as
always :: Integer -> Integer -> Integer
You actually have the implementation correct, you just didn't have the right type signature.
always first = (\second -> first)
Of course, neither of these implementations need to be tied to Integers; they can be polymorphic. So, we end up with:
always :: a -> b -> a -- no reason the second parameter has to be the same type as the first, so use 'b' instead of 'a'. always first = (\_ -> first) -- replace 'second' with '_', because we don't need to bind anything to the second parameter.
Does that makes sense?
Bryan Burgers
__________________________________________________ Do You Yahoo!? Tired of spam? Yahoo! Mail has the best spam protection around http://mail.yahoo.com

This is what I've been trying:
always :: (a -> a) -> a -> a always x = (\y -> x)
Your function implementation is correct, but the type is wrong. Try this: always :: a -> b -> a Or, just use the function "const", from the Prelude. :-) The type system can be very handy when learning Haskell. If you think you have the correct implementation but can't work out the type, just start up an interpreter and ask it for the inferred type. For example: Prelude> let always x _ = x Prelude> :t always always :: t -> t1 -> t Once you have the type, ask Hoogle if the function already exists: http://haskell.org/hoogle/?q=t+-%3E+t1+-%3E+t And there is "const" at the top of the results. :-)

Thanks! I figured I was close. Didn't even know const was available. I put together a compliment functions earlier complement :: (a -> Bool) -> a -> Bool complement p x = not (p x) By the signature, the first argument is a function (predicate) which when given a value returns a Bool? And the second argument is just a value? And the function returns a Bool?
map (complement odd) [1,2,3,4,5,6] [False,True,False,True,False,True]
By similar reasoning the always function would seem to
have a signature
a -> (b -> a)
where the first argument is just a value and the
return value is a function that when given a possibly
different value just returns the value originally
given to always?
Is that reasoning OK? Are
a -> (b -> a) and a -> b -> a the same signature?
So the inferred type is usually pretty accurate? These
signatures are a bit confusing. Is there a good
tutorial?
I'm using Hugs/Win XP just to scope out the language
right now. I tried what you suggested and got
Hugs> let always x _ = x
ERROR - Syntax error in expression (unexpected end of
input)
Hugs>
Isn't Hugs an interpreter?
Thanks again. Really interesting language Haskell.
Michael
--- Matthew Brecknell
This is what I've been trying:
always :: (a -> a) -> a -> a always x = (\y -> x)
Your function implementation is correct, but the type is wrong. Try this:
always :: a -> b -> a
Or, just use the function "const", from the Prelude. :-)
The type system can be very handy when learning Haskell. If you think you have the correct implementation but can't work out the type, just start up an interpreter and ask it for the inferred type. For example:
Prelude> let always x _ = x Prelude> :t always always :: t -> t1 -> t
Once you have the type, ask Hoogle if the function already exists:
http://haskell.org/hoogle/?q=t+-%3E+t1+-%3E+t
And there is "const" at the top of the results. :-)
__________________________________________________ Do You Yahoo!? Tired of spam? Yahoo! Mail has the best spam protection around http://mail.yahoo.com

nowgate:
Thanks! I figured I was close.
Didn't even know const was available.
I put together a compliment functions earlier
complement :: (a -> Bool) -> a -> Bool complement p x = not (p x)
By the signature, the first argument is a function (predicate) which when given a value returns a Bool? And the second argument is just a value? And the function returns a Bool?
map (complement odd) [1,2,3,4,5,6] [False,True,False,True,False,True]
By similar reasoning the always function would seem to have a signature
a -> (b -> a)
where the first argument is just a value and the return value is a function that when given a possibly different value just returns the value originally given to always?
Yep. Which may be written as: const :: a -> b -> a
Is that reasoning OK? Are
a -> (b -> a) and a -> b -> a the same signature?
Yep.
So the inferred type is usually pretty accurate? These
Yes :-)
I'm using Hugs/Win XP just to scope out the language right now. I tried what you suggested and got
Hugs> let always x _ = x ERROR - Syntax error in expression (unexpected end of input) Hugs>
let-bindings aren't supported in Hugs at the prompt, the solution is to load the source from a file, with :reload, as you change it. You can define them in GHC/GHCi however. Also, you can use them locally as: let always x _ = x in always 1 "foo" -- Don

On Dec 27, 2006, at 22:55 , michael rice wrote:
By similar reasoning the always function would seem to have a signature
a -> (b -> a)
where the first argument is just a value and the return value is a function that when given a possibly different value just returns the value originally given to always?
Is that reasoning OK? Are
a -> (b -> a) and a -> b -> a the same signature?
This is a point that has been glossed over a bit: Haskell has the notion of partial application. If you want to start with a function that takes two values, and return a function that takes one value and uses the one previously passed in, you just invoke the function with one parameter; Haskell will produce a function which takes a single argument to complete the expression. Using (*) (prefix version of multiplication) as an example: Prelude> :t ((*) 2) ((*) 2) :: (Num t) => t -> t Prelude> let x2 = ((*) 2) in x2 5 10 This shows the equivalence of the type signatures (a -> a -> a) and (a -> (a -> a)), and is one of the strengths of Haskell: you can pass a section (a "partially expanded" function") wherever a function is expected. Prelude> map ((*) 2) [1..5] [2,4,6,8,10] This doesn't only work for prefix functions, by the way; the above example is more naturally written as (2*): Prelude> :t (2*) (2*) :: (Num t) => t -> t Prelude> map (2*) [1..5] [2,4,6,8,10] You can also say (*2), which provides the right-hand argument; this is useful for non-commutative functions like (/). But don't try it with (-), because you'll trip over an unfortunate parsing hack for negative numbers: Prelude> :t (-2) -- whoops, it's a number, not a function! (-2) :: (Num a) => a The Prelude provides a workaround for this, though: Prelude> :t (subtract 2) (subtract 2) :: (Num t) => t -> t -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

complement :: (a -> Bool) -> a -> Bool complement p x = not (p x)
By the signature, the first argument is a function (predicate) which when given a value returns a Bool? And the second argument is just a value? And the function returns a Bool?
Indeed. In the type expression, the lower-case identifiers are type variables, while the upper-case identifiers are types. Thus, "a" could be instantiated to any type, with the constraint that both appearances of "a" are the same type.
map (complement odd) [1,2,3,4,5,6]
Typically, you would use function composition here: map (not.odd) [1..6] If you really want a seperate complement function, you could define it using a section: complement = (not.)
By similar reasoning the always function would seem to have a signature
a -> (b -> a)
where the first argument is just a value and the return value is a function that when given a possibly different value just returns the value originally given to always?
Is that reasoning OK? Are
a -> (b -> a) and a -> b -> a the same signature?
Yes. Function application (->) is right-associative in a type expression. What about a value expression? f a b === (f a) b Looks like an inconsistency? Not if you think about it. :-) Of course, this is what curried functions and partial application are all about.
So the inferred type is usually pretty accurate? These signatures are a bit confusing. Is there a good tutorial?
http://haskell.org/tutorial, particularly chapter 2.

G'day all.
Quoting Matthew Brecknell
Yes. Function application (->) is right-associative in a type expression. What about a value expression?
f a b === (f a) b
Looks like an inconsistency? Not if you think about it. :-)
And if you don't want to think about it, this should make everything clear: f :: A -> (B -> (C -> D)) f a :: B -> (C -> D) (f a) b :: C -> D ((f a) b) c :: d Cheers, Andrew Bromage

On Fri, Dec 29, 2006 at 03:36:45AM -0500, ajb@spamcop.net wrote:
And if you don't want to think about it, this should make everything clear:
f :: A -> (B -> (C -> D)) f a :: B -> (C -> D) (f a) b :: C -> D ((f a) b) c :: d
Nice illustration. It's as if the letters jumped over the colons from the type world to the value world. Now if you can't sleep, you can count jumping types instead of sheep ;-) Best regards Tomasz

On 29/12/06, ajb@spamcop.net
And if you don't want to think about it, this should make everything clear:
My additions displayed below: f :: A -> B -> C -> D
f :: A -> (B -> (C -> D))
By right-associativity of f.
f a :: B -> (C -> D) (f a) b :: C -> D ((f a) b) c :: d
s/d/D/ -- -David House, dmhouse@gmail.com

nowgate:
I'm trying to learn Haskell and translating some Lisp functions as exercises.
How would I write a Haskell function named ALWAYS that behaves like this:
one = always 1 bozo = always "clown"
map one [2,3,4,5,6] [1,1,1,1,1]
one 62 1
map bozo [2,3,4,5,6] ["clown","clown" ,"clown", "clown"," clown"]
bozo 62 "clown"
i.e. ALWAYS returns a function with a single parameter that is ignored, returning instead the value given to ALWAYS when the function was created.
This is what I've been trying:
always :: (a -> a) -> a -> a always x = (\y -> x)
one = always 1
So there are two cases you want to handle: * return a list, if the argument is a list * return a single value, if the argument is a single value. We can write thes functions separately: alwayList :: a -> [b] -> [a] alwayList n xs = map (const n) xs *Main> let one = always 1 *Main> one "foo" [1,1,1] *Main> let bozo = always "clown" *Main> bozo "haskell" ["clown","clown","clown","clown","clown","clown","clown"] Now handle the non-list case: alwaysAtom :: a -> b -> a alwaysAtom a b = a *Main> let one = alwaysAtom 1 *Main> one 'x' 1 Unifying these two under a common type class is left as an exercise ;) I guess the type signature for such a class would be something like: class Const a b a' | b -> a', a' -> a where Something like that. -- Don

Hi Donald, I think you misunderstood what I was asking. There's not two cases. Maybe I'm not saying it sufficiently well but the function ALWAYS just returns a function that always returns the original argument to ALWAYS no matter what else you give the resulting function. when one is define as follows one = always 1 then
one 4 1 one "abc" 1 one (2,3) 1 one [0,4,8,2] 1 map one ["one","two","three"] [1,1,1]
The mapping example is just an alternative way of
illustrating the functionality. No matter what the
defined function is given it always gives back the
original value give to ALWAYS.
Michael
--- Donald Bruce Stewart
I'm trying to learn Haskell and translating some Lisp functions as exercises.
How would I write a Haskell function named ALWAYS
behaves like this:
one = always 1 bozo = always "clown"
map one [2,3,4,5,6] [1,1,1,1,1]
one 62 1
map bozo [2,3,4,5,6] ["clown","clown" ,"clown", "clown"," clown"]
bozo 62 "clown"
i.e. ALWAYS returns a function with a single
nowgate: that parameter
that is ignored, returning instead the value given to ALWAYS when the function was created.
This is what I've been trying:
always :: (a -> a) -> a -> a always x = (\y -> x)
one = always 1
So there are two cases you want to handle: * return a list, if the argument is a list * return a single value, if the argument is a single value. We can write thes functions separately:
alwayList :: a -> [b] -> [a] alwayList n xs = map (const n) xs
*Main> let one = always 1 *Main> one "foo" [1,1,1]
*Main> let bozo = always "clown" *Main> bozo "haskell"
["clown","clown","clown","clown","clown","clown","clown"]
Now handle the non-list case:
alwaysAtom :: a -> b -> a alwaysAtom a b = a
*Main> let one = alwaysAtom 1 *Main> one 'x' 1
Unifying these two under a common type class is left as an exercise ;)
I guess the type signature for such a class would be something like:
class Const a b a' | b -> a', a' -> a where
Something like that.
-- Don
__________________________________________________ Do You Yahoo!? Tired of spam? Yahoo! Mail has the best spam protection around http://mail.yahoo.com

nowgate:
Hi Donald,
I think you misunderstood what I was asking. There's not two cases. Maybe I'm not saying it sufficiently well but the function ALWAYS just returns a function that always returns the original argument to ALWAYS no matter what else you give the resulting function.
when one is define as follows
one = always 1
then
one 4 1 one "abc" 1 one (2,3) 1 one [0,4,8,2] 1 map one ["one","two","three"] [1,1,1]
The mapping example is just an alternative way of illustrating the functionality. No matter what the defined function is given it always gives back the original value give to ALWAYS.
Ah yes, I must have missed the 'map one' in the original post. Hence I thought you were looking for different behaviour for lists. My mistake. Prelude.const is your friend :-) -- Don
participants (8)
-
ajb@spamcop.net
-
Brandon S. Allbery KF8NH
-
Bryan Burgers
-
David House
-
dons@cse.unsw.edu.au
-
Matthew Brecknell
-
michael rice
-
Tomasz Zielonka