Re: [Haskell-cafe] On to applicative

2010-09-04 Thread michael rice
, 9/4/10, David Menendez wrote: From: David Menendez Subject: Re: [Haskell-cafe] On to applicative To: "michael rice" Cc: haskell-cafe@haskell.org Date: Saturday, September 4, 2010, 2:23 PM On Sat, Sep 4, 2010 at 2:06 PM, michael rice wrote: The two myAction functions below seem to be equiv

Re: [Haskell-cafe] On to applicative

2010-09-04 Thread David Menendez
On Sat, Sep 4, 2010 at 2:06 PM, michael rice wrote: > The two myAction functions below seem to be equivalent and, for this small > case, show an interesting economy of code, but being far from a Haskell > expert, I have to ask, is the first function as small (code wise) as it > could be? > > Mich

[Haskell-cafe] On to applicative

2010-09-04 Thread michael rice
The two myAction functions below seem to be equivalent and, for this small case, show an interesting economy of code, but being far from a Haskell expert, I have to ask, is the first function as small (code wise) as it could be? Michael import Control.Applicative data Color     = Red     | Bl

Re: [Haskell-cafe] On to applicative

2010-09-02 Thread michael rice
Cool, I'll go looking for it. I couldn't find anything on Hoogle. Thanks, Michael --- On Thu, 9/2/10, David Menendez wrote: From: David Menendez Subject: Re: [Haskell-cafe] On to applicative To: "michael rice" Cc: haskell-cafe@haskell.org Date: Thursday, September 2, 2

Re: [Haskell-cafe] On to applicative

2010-09-02 Thread David Menendez
On Thu, Sep 2, 2010 at 9:16 PM, michael rice wrote: > This may be a dumb question, but here goes. > > Types Maybe, Either, List, are types and also instances of Functor (and > Monad). > > Assuming (->) is also a type, where can I find its type definition? > (->) is a built-in type. You could say

[Haskell-cafe] On to applicative

2010-09-02 Thread michael rice
This may be a dumb question, but here goes. Types Maybe, Either, List, are types and also instances of Functor (and Monad). Assuming (->) is also a type, where can I find its type definition? Michael ___ Haskell-Cafe mailing list Haskell-Cafe

Re: [Haskell-cafe] On to applicative

2010-09-02 Thread michael rice
xander Solla wrote: From: Alexander Solla Subject: Re: [Haskell-cafe] On to applicative To: Cc: "haskell-cafe Cafe" Date: Thursday, September 2, 2010, 2:46 PM On Sep 2, 2010, at 11:30 AM, michael rice wrote: In each case, what does the notation show:: ... and undefined:: ... ac

Re: [Haskell-cafe] On to applicative

2010-09-02 Thread Alexander Solla
On Sep 2, 2010, at 11:30 AM, michael rice wrote: In each case, what does the notation show:: ... and undefined:: ... accomplish? They're type annotations. show is a function in "many" types: Prelude> :t show show :: (Show a) => a -> String If you want to see the type of a "specific" sh

Re: [Haskell-cafe] On to applicative

2010-09-02 Thread michael rice
nt -> String Michael --- On Tue, 8/31/10, Ryan Ingram wrote: From: Ryan Ingram Subject: Re: [Haskell-cafe] On to applicative To: "michael rice" Cc: "Vo Minh Thu" , haskell-cafe@haskell.org Date: Tuesday, August 31, 2010, 4:17 PM FmapFunc is just a test module I c

Re: [Haskell-cafe] On to applicative

2010-09-02 Thread David Menendez
On Thu, Sep 2, 2010 at 10:45 AM, michael rice wrote: > > Can you think of a situation for > > \x -> f x > or > \x y z -> x + ord y - head z > > that would require x (y z) to have their type(s) declared (ala Pascal), or > is it always > inferred by what appears to the right of "->"? > I think H

Re: [Haskell-cafe] On to applicative

2010-09-02 Thread michael rice
0, Tillmann Rendel wrote: From: Tillmann Rendel Subject: Re: [Haskell-cafe] On to applicative To: "michael rice" Cc: haskell-cafe@haskell.org Date: Wednesday, September 1, 2010, 5:28 PM michael rice wrote: > Prelude Data.Either> let m = Just 7 > Prelude Data.Either> :t

Re: [Haskell-cafe] On to applicative

2010-09-01 Thread michael rice
t Can you think of a situation for  \x -> f x that would require x to have a declared type, or is it always inferred by the type of f? Michael --- On Wed, 9/1/10, Tillmann Rendel wrote: From: Tillmann Rendel Subject: Re: [Haskell-cafe] On to applicative To: "michael rice&qu

Re: [Haskell-cafe] On to applicative

2010-09-01 Thread Tillmann Rendel
michael rice wrote: Prelude Data.Either> let m = Just 7 Prelude Data.Either> :t m m :: Maybe Integer So to create a value of type (Maybe ...), you can use Just. Prelude Data.Either> let l = 2:[] Prelude Data.Either> :t l l :: [Integer] So to create a value of type [...], you can use (:) and

Re: [Haskell-cafe] On to applicative

2010-08-31 Thread michael rice
Thanks, Brandon, but Ryan gave me what I was looking for. Michael --- On Tue, 8/31/10, Brandon S Allbery KF8NH wrote: From: Brandon S Allbery KF8NH Subject: Re: [Haskell-cafe] On to applicative To: haskell-cafe@haskell.org Date: Tuesday, August 31, 2010, 4:35 PM -BEGIN PGP SIGNED MESSAGE

Re: [Haskell-cafe] On to applicative

2010-08-31 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 On 8/31/10 13:27 , michael rice wrote: > So it's a type constructor, not a type? Could you please provide a simple > example of its usage? Assuming you don't mean the trivial use in defining functions, see Control.Monad.Instances: > instance Functor

Re: [Haskell-cafe] On to applicative

2010-08-31 Thread Ryan Ingram
> *Main> :t (->) Int Char > > :1:1: parse error on input `->' > > What got loaded with FmapFunc? I Hoogled it and got back nothing. > > Michael > > --- On *Tue, 8/31/10, Ryan Ingram * wrote: > > > From: Ryan Ingram > > Subject: Re: [Haskell-caf

Re: [Haskell-cafe] On to applicative

2010-08-31 Thread Vo Minh Thu
hael > > > --- On Tue, 8/31/10, Vo Minh Thu wrote: > > From: Vo Minh Thu > Subject: Re: [Haskell-cafe] On to applicative > To: "michael rice" > Cc: "Ryan Ingram" , haskell-cafe@haskell.org > Date: Tuesday, August 31, 2010, 3:23 PM > > 2010/8/3

Re: [Haskell-cafe] On to applicative

2010-08-31 Thread michael rice
om: Vo Minh Thu Subject: Re: [Haskell-cafe] On to applicative To: "michael rice" Cc: "Ryan Ingram" , haskell-cafe@haskell.org Date: Tuesday, August 31, 2010, 3:23 PM 2010/8/31 michael rice > > Hi Vo, > > Pardon, I grabbed the wrong lines. > > *Main>

Re: [Haskell-cafe] On to applicative

2010-08-31 Thread Alexander Solla
On Aug 31, 2010, at 12:03 PM, michael rice wrote: I tried creating an instance earlier but *Main> :t (->) Int Char :1:1: parse error on input `->' Try: Prelude> :info (->) data (->) a b-- Defined in GHC.Prim If you want type-information about values, use :t. If you want informa

Re: [Haskell-cafe] On to applicative

2010-08-31 Thread Vo Minh Thu
> Michael > > --- On Tue, 8/31/10, Vo Minh Thu wrote: > > From: Vo Minh Thu > Subject: Re: [Haskell-cafe] On to applicative > To: "michael rice" > Cc: "Ryan Ingram" , haskell-cafe@haskell.org > Date: Tuesday, August 31, 2010, 3:07 PM > > 201

Re: [Haskell-cafe] On to applicative

2010-08-31 Thread michael rice
Hi Vo, Pardon, I grabbed the wrong lines. *Main> :t (->) 3 "abc" :1:1: parse error on input `->' Michael --- On Tue, 8/31/10, Vo Minh Thu wrote: From: Vo Minh Thu Subject: Re: [Haskell-cafe] On to applicative To: "michael rice" Cc: "Ryan Ingram&qu

Re: [Haskell-cafe] On to applicative

2010-08-31 Thread Vo Minh Thu
:t undefined :: Int is ok, just like :t undefined :: (->) Int Int > What got loaded with FmapFunc? I Hoogled it and got back nothing. > > Michael > > --- On Tue, 8/31/10, Ryan Ingram wrote: > > From: Ryan Ingram > Subject: Re: [Haskell-cafe] On to applicative > To: &quo

Re: [Haskell-cafe] On to applicative

2010-08-31 Thread michael rice
wrote: From: Ryan Ingram Subject: Re: [Haskell-cafe] On to applicative To: "michael rice" Cc: "Vo Minh Thu" , haskell-cafe@haskell.org Date: Tuesday, August 31, 2010, 2:36 PM Prelude FmapFunc> let s = show :: ((->) Int) String Prelude FmapFunc> :t s s :: Int ->

Re: [Haskell-cafe] On to applicative

2010-08-31 Thread Vo Minh Thu
nstance Functor Maybe where ... Note how the type argument of Maybe is not given. But above, when you create a value, it has type Maybe Int, not only Maybe. So for the ((->) r) case, you still want to "complete" it. E.g. m :: Maybe Int -- not just Maybe (+) :: (->) Int Int -

Re: [Haskell-cafe] On to applicative

2010-08-31 Thread Ryan Ingram
; :t e > e :: Either a [Char] > > All these instances are functors, each with its own version of fmap that > can be applied to it. > > How can I similarly create an instance of (->) so I can apply (->)'s > version of fmap > > instance Functor ((->) r) whe

Re: [Haskell-cafe] On to applicative

2010-08-31 Thread michael rice
be applied to it. How can I similarly create an instance of (->) so I can apply (->)'s version of fmap instance Functor ((->) r) where      fmap f g = (\x -> f (g x)) to it? Michael --- On Tue, 8/31/10, Vo Minh Thu wrote: From: Vo Minh Thu Subject: Re: [Haskell-cafe] On to

Re: [Haskell-cafe] On to applicative

2010-08-31 Thread Vo Minh Thu
> From: Vo Minh Thu > Subject: Re: [Haskell-cafe] On to applicative > To: "michael rice" > Cc: haskell-cafe@haskell.org > Date: Tuesday, August 31, 2010, 1:17 PM > > 2010/8/31 michael rice > > > > "Learn You a Haskell ..."  says that (->

Re[2]: [Haskell-cafe] On to applicative

2010-08-31 Thread Bulat Ziganshin
h Thu wrote: > From: Vo Minh Thu > Subject: Re: [Haskell-cafe] On to applicative > To: "michael rice" > Cc: haskell-cafe@haskell.org > Date: Tuesday, August 31, 2010, 1:17 PM > 2010/8/31 michael rice >> >> "Learn You a Haskell ..."  says tha

Re: [Haskell-cafe] On to applicative

2010-08-31 Thread michael rice
So it's a type constructor, not a type? Could you please provide a simple example of its usage? Michael --- On Tue, 8/31/10, Vo Minh Thu wrote: From: Vo Minh Thu Subject: Re: [Haskell-cafe] On to applicative To: "michael rice" Cc: haskell-cafe@haskell.org Date: Tuesday, Aug

Re: [Haskell-cafe] On to applicative

2010-08-31 Thread Vo Minh Thu
2010/8/31 michael rice > > "Learn You a Haskell ..."  says that (->) is a type just like Either. Where > can I find its type definition? You can't define it *in* Haskell as user code. It is a built-in infix type constructor (Either or Maybe are type constructors too, not just types). In fact, if

[Haskell-cafe] On to applicative

2010-08-31 Thread michael rice
"Learn You a Haskell ..."  says that (->) is a type just like Either. Where can I find its type definition? Michael ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] On to applicative

2010-08-29 Thread Ivan Lazar Miljenovic
On 30 August 2010 14:50, michael rice wrote: > > Hi Ivan, > > I already looked there and didn't find anything, but went back and noticed > the "Source Code" at the top right of the page and found it there. Why are > there two source codes, the one at the top and the ones down the right margin >

Re: [Haskell-cafe] On to applicative

2010-08-29 Thread michael rice
ael --- On Mon, 8/30/10, Ivan Lazar Miljenovic wrote: From: Ivan Lazar Miljenovic Subject: Re: [Haskell-cafe] On to applicative To: "michael rice" Cc: haskell-cafe@haskell.org, "Brandon S Allbery KF8NH" Date: Monday, August 30, 2010, 12:36 AM On 30 August 2010 14:25, mich

Re: [Haskell-cafe] On to applicative

2010-08-29 Thread Ivan Lazar Miljenovic
On 30 August 2010 14:25, michael rice wrote: > > Looks like the fmap definition for the Either functor matches what's given in > Learn You A Haskell ... > > instance Functor (Either a) where >    fmap f (Right x) = Right (f x) >    fmap f (Left x) = Left x > > but Hoogle couldn't find Control.Mon

Re: [Haskell-cafe] On to applicative

2010-08-29 Thread michael rice
Control.Monad.Instances Data.Either> fmap length r Right 4 --- On Sat, 8/28/10, Brandon S Allbery KF8NH wrote: From: Brandon S Allbery KF8NH Subject: Re: [Haskell-cafe] On to applicative To: haskell-cafe@haskell.org Date: Saturday, August 28, 2010, 9:06 PM -BEGIN PGP SIGNED MESSAGE-

Re: [Haskell-cafe] On to applicative

2010-08-29 Thread Stephen Tetley
On 29 August 2010 07:58, Ivan Lazar Miljenovic wrote: > One might also say that that's because there is no BiFunctor in the > report, standard library, etc. Yep - that's where the historical accident comes in. ___ Haskell-Cafe mailing list Haskell-Cafe

Re: [Haskell-cafe] On to applicative

2010-08-28 Thread Ivan Lazar Miljenovic
On 29 August 2010 16:51, Stephen Tetley wrote: > One might also say its a historical accident that Either isn't an > instance of Bifunctor - "Equal rights for Lefts!", but that's another > story... One might also say that that's because there is no BiFunctor in the report, standard library, etc.

Re: [Haskell-cafe] On to applicative

2010-08-28 Thread Stephen Tetley
On 29 August 2010 02:06, Brandon S Allbery KF8NH wrote: > -BEGIN PGP SIGNED MESSAGE- > Hash: SHA1 > > On 8/28/10 20:43 , michael rice wrote: > Historical accident, to wit:  Haskell 98 minimally defined Either in the > Prelude, so in practice we get the basic definitions (Either itself and

Re: [Haskell-cafe] On to applicative

2010-08-28 Thread michael rice
Thanks, Brandon. Michael --- On Sat, 8/28/10, Brandon S Allbery KF8NH wrote: From: Brandon S Allbery KF8NH Subject: Re: [Haskell-cafe] On to applicative To: "michael rice" Cc: haskell-cafe@haskell.org Date: Saturday, August 28, 2010, 10:43 PM -BEGIN PGP SIGNED MESSAGE-

Re: [Haskell-cafe] On to applicative

2010-08-28 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 On 8/28/10 22:15 , michael rice wrote: > Prelude> fmap (*2) l > > :1:0: > No instance for (Functor (Either Integer)) > arising from a use of `fmap' at :1:0-10 > Possible fix: > add an instance declaration for (Functor (Either Integ

Re: [Haskell-cafe] On to applicative

2010-08-28 Thread michael rice
KF8NH wrote: From: Brandon S Allbery KF8NH Subject: Re: [Haskell-cafe] On to applicative To: haskell-cafe@haskell.org Date: Saturday, August 28, 2010, 9:06 PM -BEGIN PGP SIGNED MESSAGE- Hash: SHA1 On 8/28/10 20:43 , michael rice wrote: > I'm looking at a discussion of Either (as f

Re: [Haskell-cafe] On to applicative

2010-08-28 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 On 8/28/10 20:43 , michael rice wrote: > I'm looking at a discussion of Either (as functor) here: > > http://learnyouahaskell.com/making-our-own-types-and-typeclasses#the-functor-typeclass > > instance Functor (Either a) where > fmap f (Right x

[Haskell-cafe] On to applicative

2010-08-28 Thread michael rice
I'm looking at a discussion of Either (as functor) here: http://learnyouahaskell.com/making-our-own-types-and-typeclasses#the-functor-typeclass instance Functor (Either a) where       fmap f (Right x) = Right (f x)       fmap f (Left x) = Left x And this line in Data.Either Functor (Either a)

Re: [Haskell-cafe] On to applicative

2010-08-27 Thread michael rice
A "map" can be a function (applied to a (single) value). Got it. Thanks, Michael --- On Fri, 8/27/10, Ivan Lazar Miljenovic wrote: From: Ivan Lazar Miljenovic Subject: Re: [Haskell-cafe] On to applicative To: "michael rice" Cc: haskell-cafe@haskell.org Date: Friday, A

Re: [Haskell-cafe] On to applicative

2010-08-27 Thread Ivan Lazar Miljenovic
On 28 August 2010 10:38, michael rice wrote: > > fmap seems oddly named because no "mapping" takes place, except in the fourth > example, where the map is "passed in." Just sayin'. *ahem* http://en.wikipedia.org/wiki/Map_%28mathematics%29 > Prelude Control.Monad Control.Applicative Data.Char> f

[Haskell-cafe] On to applicative

2010-08-27 Thread michael rice
fmap seems oddly named because no "mapping" takes place, except in the fourth example, where the map is "passed in." Just sayin'. Michael 1) Prelude Control.Monad Control.Applicative> fmap (++ "abc") getLine xyz "xyzabc" 2) Prelude Control.Monad Control.Applicative Data.Char Data.String> fmap (

Re: [Haskell-cafe] On to applicative

2010-08-26 Thread michael rice
some time there but will no doubt be back before long with another question. Thanks all, Michael --- On Thu, 8/26/10, Alexander Solla wrote: From: Alexander Solla Subject: Re: [Haskell-cafe] On to applicative To: Cc: "haskell-cafe Cafe" Date: Thursday, August 26, 2010, 2:15 PM O

Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Alexander Solla
On Aug 26, 2010, at 9:27 AM, michael rice wrote: Some functions just happen to map to other functions. <$> is flip fmap. f <$> functor = fmap f functor Brent Yorgey's post noted. "map to"? Take as arguments? "maps to" as in "outputs". pure f <*> functor = f <$> functor

Re: [Haskell-cafe] On to applicative

2010-08-26 Thread michael rice
Hi Alexander, Didn't get to sleep till 4 AM and it took me a while to go though your post. So far... --- On Thu, 8/26/10, Alexander Solla wrote: From: Alexander Solla Subject: Re: [Haskell-cafe] On to applicative To: Cc: "haskell-cafe Cafe" Date: Thursday, August 26, 2010, 4

Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Brent Yorgey
On Thu, Aug 26, 2010 at 01:29:16AM -0700, Alexander Solla wrote: > > > <$> is flip fmap. f <$> functor = fmap f functor > Just a quick correction: <$> is fmap, not flip fmap. -Brent ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.h

Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Alexander Solla
On Aug 26, 2010, at 1:29 AM, Alexander Solla wrote: The other function is pure :: (a -> b) -> f (a -> b). It takes a function and lifts it into the functor, without applying it to anything. In other words, given an f :: a -> b, My mistake, though if you got the rest of it, it should come

Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Alexander Solla
On Aug 26, 2010, at 12:34 AM, michael rice wrote: A lot of stuff to get one's head around. Was aware of liftM2, liftM3, etc., but not liftA2, liftA3, etc. liftM and liftA are essentially equivalent (and are both essentially equivalent to fmap) Same for the liftAn = liftMn functions (whe

Re: [Haskell-cafe] On to applicative

2010-08-26 Thread michael rice
e the patience. Michael --- On Thu, 8/26/10, Thomas Davie wrote: From: Thomas Davie Subject: Re: [Haskell-cafe] On to applicative To: "michael rice" Cc: "Ivan Lazar Miljenovic" , haskell-cafe@haskell.org Date: Thursday, August 26, 2010, 3:10 AM On 26 Aug 2010, at 08:01

Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Thomas Davie
On 26 Aug 2010, at 08:01, michael rice wrote: > Hmm... it was my understanding that the example was showing how to *avoid* > having to create a lot of functions that do the same thing but have > different numbers of arguments. > > From the Wiki page: > > "Anytime you feel the need to define

Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Vo Minh Thu
t; Michael > > > > --- On Thu, 8/26/10, Ivan Lazar Miljenovic wrote: > > From: Ivan Lazar Miljenovic > Subject: Re: [Haskell-cafe] On to applicative > To: "michael rice" > Cc: haskell-cafe@haskell.org > Date: Thursday, August 26, 2010, 2:50 AM > >

Re: [Haskell-cafe] On to applicative

2010-08-26 Thread michael rice
date for function-arguments with a different number of arguments, think about how defining a proper instance of Applicative can make your life easier." Not so? Michael --- On Thu, 8/26/10, Ivan Lazar Miljenovic wrote: From: Ivan Lazar Miljenovic Subject: Re: [Haskell-cafe] On to applicative

Re: [Haskell-cafe] On to applicative

2010-08-25 Thread Vo Minh Thu
-> b' against inferred type `Int' >     In the first argument of `fmap3', namely `sumsqr' >     In the expression: fmap3 sumsqr (Just 3) (Just 4) (Just 5) >     In the definition of `it': >     it = fmap3 sumsqr (Just 3) (Just 4) (Just 5) > *Main> &g

Re: [Haskell-cafe] On to applicative

2010-08-25 Thread Ivan Lazar Miljenovic
(Just 5) >     In the definition of `it': >     it = fmap3 sumsqr (Just 3) (Just 4) (Just 5) > *Main> sumsqr takes three arguments; fmap3 has type: fmap3 :: (a -> b -> c -> d) -> Maybe a -> Maybe b -> Maybe c -> Maybe d i.e. the function you pass it needs

Re: [Haskell-cafe] On to applicative

2010-08-25 Thread michael rice
`fmap3', namely `sumsqr'     In the expression: fmap3 sumsqr (Just 3) (Just 4) (Just 5)     In the definition of `it':     it = fmap3 sumsqr (Just 3) (Just 4) (Just 5) *Main> --- On Thu, 8/26/10, Ivan Lazar Miljenovic wrote: From: Ivan Lazar Miljenovic Subject: Re:

Re: [Haskell-cafe] On to applicative

2010-08-25 Thread Ivan Lazar Miljenovic
On 26 August 2010 16:29, michael rice wrote: > > Can you recommend an example that works? An example of what? The definitions of fmap2, etc. on that page look like they're correct. -- Ivan Lazar Miljenovic ivan.miljeno...@gmail.com IvanMiljenovic.wordpress.com __

Re: [Haskell-cafe] On to applicative

2010-08-25 Thread michael rice
Can you recommend an example that works? Michael --- On Thu, 8/26/10, Ivan Lazar Miljenovic wrote: From: Ivan Lazar Miljenovic Subject: Re: [Haskell-cafe] On to applicative To: "michael rice" Cc: haskell-cafe@haskell.org Date: Thursday, August 26, 2010, 2:13 AM On 26 August

Re: [Haskell-cafe] On to applicative

2010-08-25 Thread Ivan Lazar Miljenovic
On 26 August 2010 16:09, michael rice wrote: > > Yeah, I figured as much, but the code is copied right off the referenced page. Because as Vo Minh Thu says, it was there as a demonstration; in this instance they were doing "algebraic" manipulation of the code and corresponding type signatures. A

Re: [Haskell-cafe] On to applicative

2010-08-25 Thread michael rice
Yeah, I figured as much, but the code is copied right off the referenced page. Michael --- On Thu, 8/26/10, Ivan Lazar Miljenovic wrote: From: Ivan Lazar Miljenovic Subject: Re: [Haskell-cafe] On to applicative To: "michael rice" Cc: haskell-cafe@haskell.org Date: Thursday, Augus

Re: [Haskell-cafe] On to applicative

2010-08-25 Thread Vo Minh Thu
2010/8/26 michael rice > > From: http://en.wikibooks.org/wiki/Haskell/Applicative_Functors > > = > import Control.Applicative > > f :: (a -> b -> c) > fmap :: Functor f => (d -> e) -> f d -> f e > fmap f :: Functor f => f a -> f (b -> c)    -- Identify d with a, and e w

Re: [Haskell-cafe] On to applicative

2010-08-25 Thread Ivan Lazar Miljenovic
On 26 August 2010 15:56, michael rice wrote: > > From: http://en.wikibooks.org/wiki/Haskell/Applicative_Functors > > = > import Control.Applicative > > f :: (a -> b -> c) > fmap :: Functor f => (d -> e) -> f d -> f e > fmap f :: Functor f => f a -> f (b -> c)    -- Iden

[Haskell-cafe] On to applicative

2010-08-25 Thread michael rice
From: http://en.wikibooks.org/wiki/Haskell/Applicative_Functors = import Control.Applicative f :: (a -> b -> c) fmap :: Functor f => (d -> e) -> f d -> f e fmap f :: Functor f => f a -> f (b -> c)    -- Identify d with a, and e with (b -> c) sumsqr :: Int -> Int -> I