Re: [Haskell-beginners] help with types and composition

Ah silly me I think I sorta get it. after looking up currying this somewhat makes sense (it isn't really mentioned in YAHT and not till later in most other books.) So, basically any function's type will always be in curryfied form, and the only time there's a tuple involved is if the function's argument is itself a tuple? I'll have to ponder a bit how nesting functions are equivalent to a function with multiple arguments. Sorry about the messed up Unicode. That question doesn't really make sense knowing this. On 6 Jul 2009, Daniel Fischer wrote:
Am Montag 06 Juli 2009 13:53:01 schrieb Dan Douglas:
Hello everyone! first post here. I'm working through YAHT and Real World Haskell sort of in parallel. I have a somewhat related question.
Assume we have a binary operator which is not a higher order function. The "greater than" relation for example:
Prelude List> :t (>) (>) :: forall a. (Ord a) => a -> a -> Bool
Type classes and variables make sense - I assume since we have quantifiers, the type classes must be essentially predicates, and the type variables are bound to them as expected. Also I assume whenever we see (a -> b) this means roughly f:(<domain> -> <codomain>)
Correct.
a -> a -> Bool could therefore mean either: "a function whose domain is
an
'a' and whose codomain is a function from a to bool";
Yes, that's it.
or "a function which takes a function from type 'a' to 'a' and returns a bool.
That would be the type (a -> a) -> Bool.
According to YAHT:
"NOTE The parentheses are not necessary; in function types, if you have a -> b -> y it is assume that b -> y is grouped. If you want the other way, with a -> b grouped, you need to put parentheses around them."
In short: (->) is right associative,
a -> b -> c -> d === a -> (b -> (c -> d))
I'm confused by this. A function which takes multiple arguments should be equivalent to a predicate bound to some n-tuple. Or in this case of a binary infix operator, equivalent to a prefix operator which takes a
tuple.
Correct.
But, (a, a) is not equivalent to (a -> a),
Indeed it isn't, the two sets don't even have the same cardinality (except a contains only one element). But (a -> a) -> Bool is *not* equivalent to a -> (a -> Bool).
and (a -> Bool) just doesn't make sense as a range.
But it does. (a -> Bool) is a perfectly reasonable set/Haskell type. Functions whose result is a function are very common in functional programming.
It should be something like:
(>) :: forall a. (Ord a) => (a, a) -> Bool
Note that, (ignoring _|_ and partial functions), the types ((a,b) -> c) and
(a -> (b -> c)) are isomorphic. The isomorphism is given by
curry :: ((a,b) -> c) -> (a -> (b -> c)) curry f = \x y -> f (x,y)
and
uncurry :: (a -> (b -> c)) -> ((a,b) -> c) uncurry g = \(x,y) -> g x y
Someone on freenode told me that if you had:
foo :: a -> b bar :: b -> c baz :: c -> d
and:
bork = (baz . bar . foo)
then:
bork :: a -> d
Yup.
Which, if correct means Haskell should always chain types for first-order functions. And since (>) is transitive, it should satisfy ∀x∀y∀z(((x,y) ∈ R & (y,z) ∈ R) -> (x,z) ∈ R) and omit the case for (y,z).
???
How it is possible to express a function which takes multiple arguments
(or
any first-order function at all) with more than one arrow/map symbol? How does this even make sense?
It gets even worse with more complicated examples:
Prelude List> :t foldl foldl :: forall a b. (a -> b -> a) -> a -> [b] -> a
Prelude List> :t (>>=) (>>=)
:: forall (m :: * -> *) a b. (Monad m) => m a -> (a -> m b) -> m b
How do the non-existent associativity rules make complex function types seemingly without enough parentheses have unique meaning?
The associativity rules exist:
(->) associates to the right.
Hence, fully parenthesised:
foldl :: (a -> (b -> a)) -> (a -> ([b] -> a))
Due to the right associativity, you can omit three pairs of parentheses.
Nearly every example in every tutorial on types I can find has this unexplained phenomenon, or I'm really not reading carefully.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Excerpts from Dan Douglas's message of Mon Jul 06 09:30:46 -0400 2009:
So, basically any function's type will always be in curryfied form, and the only time there's a tuple involved is if the function's argument is itself a tuple? I'll have to ponder a bit how nesting functions are equivalent to a function with multiple arguments.
The easiest way to think about this is to add parentheses around the type declaration. Int -> Int -> Int becomes: Int -> (Int -> Int) Cheers, Edward

On 6 Jul 2009, at 16:30, Edward Z. Yang wrote:
Excerpts from Dan Douglas's message of Mon Jul 06 09:30:46 -0400 2009:
So, basically any function's type will always be in curryfied form, and the only time there's a tuple involved is if the function's argument is itself a tuple? I'll have to ponder a bit how nesting functions are equivalent to a function with multiple arguments.
The easiest way to think about this is to add parentheses around the type declaration.
Int -> Int -> Int
becomes:
Int -> (Int -> Int)
The other part of the story being the definition of functions. First lets rewrite some syntactic sugar: f x y = x + y -- Rewrite to use lambda abstraction instead of the definition syntax f = \x y -> x + y -- Rewrite to remove multiple argument lambas f = \x -> \y -> x + y -- Add in the parentheses to show the currying going on f = \x -> (\y -> x + y) Bob
participants (3)
-
Dan Douglas
-
Edward Z. Yang
-
Thomas Davie