Why does `flip` cause function type so different ?

let f x xs = [x:xs,xs] :t f f :: a -> [a] -> [[a]]
:t (>>=) .f (>>=) .f :: a -> ([[a]] -> [a] -> b) -> [a] -> b
:t (flip (>>=) .f) (flip (>>=) .f) :: a -> [[a]] -> [[a]]
Why is the type of `(>>=) .f` and `flip (>>=) .f` so different ? Sincerely! ----- fac n = let { f = foldr (*) 1 [1..n] } in f -- View this message in context: http://old.nabble.com/Why-does-%60flip%60-cause-function-type-so-different--... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Hint: look at the type of flip...
Also, there's a haskell-beginners mailing list. You may wish to post
there rather than asking us every question you get whilst learning
Haskell.
On 19 March 2010 14:34, zaxis
let f x xs = [x:xs,xs] :t f f :: a -> [a] -> [[a]]
:t (>>=) .f (>>=) .f :: a -> ([[a]] -> [a] -> b) -> [a] -> b
:t (flip (>>=) .f) (flip (>>=) .f) :: a -> [[a]] -> [[a]]
Why is the type of `(>>=) .f` and `flip (>>=) .f` so different ?
Sincerely!
----- fac n = let { f = foldr (*) 1 [1..n] } in f -- View this message in context: http://old.nabble.com/Why-does-%60flip%60-cause-function-type-so-different--... 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
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Ivan Miljenovic wrote:
Hint: look at the type of flip...
Also, there's a haskell-beginners mailing list. You may wish to post there rather than asking us every question you get whilst learning Haskell.
Every question is welcome on haskell-cafe . The goal of haskell-beginners is to encourage answers that are tailored to beginners, i.e. no scary existential multi-parameter category theory type class monads there. :) Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Every question is welcome on haskell-cafe . The goal of haskell-beginners is to encourage answers that are tailored to beginners, i.e. no scary existential multi-parameter category theory type class monads there. :)
Do you get warm fuzzy existential multi-parameter category theory type class things there? Matthias.

Heinrich Apfelmus
Ivan Miljenovic wrote:
Also, there's a haskell-beginners mailing list. You may wish to post there rather than asking us every question you get whilst learning Haskell.
Every question is welcome on haskell-cafe . The goal of haskell-beginners is to encourage answers that are tailored to beginners, i.e. no scary existential multi-parameter category theory type class monads there. :)
Well, yes; except that recently zaxis has been asking quite a few of these "beginner-level" questions to the list, and I figured that haskell-beginners was catering more for the type of questions he had. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Fri, Mar 19, 2010 at 5:10 PM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
Heinrich Apfelmus
writes: Ivan Miljenovic wrote:
Also, there's a haskell-beginners mailing list. You may wish to post there rather than asking us every question you get whilst learning Haskell.
Every question is welcome on haskell-cafe . The goal of haskell-beginners is to encourage answers that are tailored to beginners, i.e. no scary existential multi-parameter category theory type class monads there. :)
Well, yes; except that recently zaxis has been asking quite a few of these "beginner-level" questions to the list, and I figured that haskell-beginners was catering more for the type of questions he had.
The IRC channels for haskell on freenode, such as #haskell and #haskell-in-depth, might also be good places to ask. You tend to get a quick turn around on simply stated questions. Jason

yes, i am a haskell-beginners. However, i still feel haskell-cafe is a good place for me to learn haskell ! If the question is too simple for you to answer, then you can just ignore it . I believe somebody else can still supply help even if without you. Ivan Lazar Miljenovic wrote:
Heinrich Apfelmus
writes: Ivan Miljenovic wrote:
Also, there's a haskell-beginners mailing list. You may wish to post there rather than asking us every question you get whilst learning Haskell.
Every question is welcome on haskell-cafe . The goal of haskell-beginners is to encourage answers that are tailored to beginners, i.e. no scary existential multi-parameter category theory type class monads there. :)
Well, yes; except that recently zaxis has been asking quite a few of these "beginner-level" questions to the list, and I figured that haskell-beginners was catering more for the type of questions he had.
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
----- fac n = let { f = foldr (*) 1 [1..n] } in f -- View this message in context: http://old.nabble.com/Why-does-%60flip%60-cause-function-type-so-different--... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Thu, 2010-03-18 at 20:34 -0700, zaxis wrote:
let f x xs = [x:xs,xs] :t f f :: a -> [a] -> [[a]]
:t (>>=) .f (>>=) .f :: a -> ([[a]] -> [a] -> b) -> [a] -> b
Hmm. You seems to have defined Monad ((->) a). (>>=) . f == \x -> (>>=) (f x) == \x -> (f x >>=) 1. x :: ∀ a. a from type of f 2. f :: ∀ a. a -> [a] -> [[a]] 3. (>>=) :: ∀ m a b. m a -> (a -> m b) -> m b From which follows: 4. (>>=) :: ∀ m b c. Monad m => m b -> (b -> m c) -> m c (from 3) 5. f x :: ∀ a. [a] -> [[a]] (from 1 and 2) 6. (>>=) :: ∀ a c. ([a] -> [[a]]) -> ([[a]] -> [a] -> c) -> ([a] -> c) If it works for all m b c (4) it works for m := [a] -> b := [[a]] 7. (f x >>=) :: ∀ a c. ([[a]] -> [a] -> c) -> ([a] -> c) From 6. Simply substituting first argument 8. \x -> (f x >>=) :: ∀ a. a -> ([[a]] -> [a] -> c) -> ([a] -> c) If you know first-order logic I guess you can see the pattern.
:t (flip (>>=) .f) (flip (>>=) .f) :: a -> [[a]] -> [[a]]
Note that list ([] a == [a]) is monad. :t flip (>>=) flip (>>=) :: (Monad m) => (a -> m b) -> m a -> m b (flip (>>=) .f) == \x -> flip (>>=) (f x) == \x y -> y >>= f x 1. x :: ∀ a. a from type of f 2. f :: ∀ a. a -> [a] -> [[a]] 3. (>>=) :: ∀ m a b. m a -> (a -> m b) -> m b From which follows 4. (>>=) :: ∀ m b c. Monad m => m b -> (b -> m c) -> m c (from 3) 5. f x :: ∀ a. [a] -> [[a]] (from 1 and 2) 6. (>>=) :: ∀ a. [[a]] -> ([a] -> [[a]]) -> [[a]] From 4 for m := [] b := [a] c := [a] 7. (>>= f x) :: ∀ a. [[a]] -> [[a]] From 6 (inserting second argument) 8. y :: ∀ a. [[a]] (forced by 7) 9. y >>= f x :: ∀ a. [[a]] (7 and 8) 10. \x y -> y >>= f x :: ∀ a. a -> [[a]] -> [[a]] (1, 8 and 9) While far from rigours proof I hope it gives some gasp of what's going on. I hope it was helpful Regards

Am Freitag 19 März 2010 04:34:53 schrieb zaxis:
let f x xs = [x:xs,xs]
:t f
f :: a -> [a] -> [[a]]
:t (>>=) .f
(>>=) .f :: a -> ([[a]] -> [a] -> b) -> [a] -> b
:t (flip (>>=) .f)
(flip (>>=) .f) :: a -> [[a]] -> [[a]]
Why is the type of `(>>=) .f` and `flip (>>=) .f` so different ?
Because the types of (>>=) and flip (>>=) are different. (>>=) :: Monad m => m a -> (a -> m b) -> m b flip (>>=) :: Monad m => (a -> m b) -> m a -> m b Now, for whatever f, for ((>>=) . f) to be well-typed, f must have the type f :: s -> m t for some Monad m. (It must be a function because it's an argument of composition (.), and since ((>>=) . f) x === (>>=) (f x) === (f x >>=), f's return type must be monadic.) Then (f x >>=) takes a function g :: t -> mu, so that (f x >>= g) is a value of type m u. The given f has type a -> [a] -> [[a]] === a -> ([a] -> [[a]]), so m t === [a] -> [[a]] === ((->) [a]) [[a]], i.e. m === ((->) a) and t === [[a]] (f x >>=) then takes a function g of type (t -> m b), expanded ([[a]] -> ([a] -> b)), and then f x >>= g is a value of type m b, expanded [a] -> b. This works because for any type w, ((->) w) is indeed a Monad, the Reader Monad, to be specific. On the other hand, for (flip (>>=) . f) to be well typed, f must be a function returning something of type (t -> m u) for some Monad m, so f's type must be s -> (t -> m u). The given f has type a -> [a] -> [[a]], so s === a, t === [a], m === [] and u === [a] === t. Then (flip (>>=) . f) x, which is (>>= f x), takes a further argument of type m t === [[a]] and then returns a value of type m u === m t === [[a]]

As a beginner, i cannot understand completely what both Maciej Piechotka and Daniel Fischer-4 said. However, i think it will be a big step for me to study haskell once i understand it. thanks ! zaxis wrote:
let f x xs = [x:xs,xs] :t f f :: a -> [a] -> [[a]]
:t (>>=) .f (>>=) .f :: a -> ([[a]] -> [a] -> b) -> [a] -> b
:t (flip (>>=) .f) (flip (>>=) .f) :: a -> [[a]] -> [[a]]
Why is the type of `(>>=) .f` and `flip (>>=) .f` so different ?
BTW, Would you mind explaining the following result ?
let fff x y z = x + y +z ((>>=) . fff) 2 (\f x -> f x) 3 8
Sincerely!
----- fac n = let { f = foldr (*) 1 [1..n] } in f -- View this message in context: http://old.nabble.com/Why-does-%60flip%60-cause-function-type-so-different--... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
participants (8)
-
Daniel Fischer
-
Heinrich Apfelmus
-
Ivan Lazar Miljenovic
-
Ivan Miljenovic
-
Jason Dagit
-
Maciej Piechotka
-
Matthias Görgens
-
zaxis