[Haskell-cafe] On to applicative

Vo Minh Thu noteed at gmail.com
Tue Aug 31 16:00:13 EDT 2010


2010/8/31 michael rice <nowgate at yahoo.com>
>
> You most certainly meant
>
> Prelude Data.Either> :t undefined :: (->) Int String
> undefined :: (->) Int String :: Int -> String
>
> though it is confusing. Constructors usually take values, but here the values (->) takes are types.

Either and (->) are *type* constructors.
Just is a (value) constructor.

This makes sense:

Just 7 is a value, so Just surely constructs a value. Nothing doesn't
take an argument but is called a constructor too.
Maybe Int is a type, so Maybe surely constructs a type.

> Michael
>
>
> --- On Tue, 8/31/10, Vo Minh Thu <noteed at gmail.com> wrote:
>
> From: Vo Minh Thu <noteed at gmail.com>
> Subject: Re: [Haskell-cafe] On to applicative
> To: "michael rice" <nowgate at yahoo.com>
> Cc: "Ryan Ingram" <ryani.spam at gmail.com>, haskell-cafe at haskell.org
> Date: Tuesday, August 31, 2010, 3:23 PM
>
> 2010/8/31 michael rice <nowgate at yahoo.com>
> >
> > Hi Vo,
> >
> > Pardon, I grabbed the wrong lines.
> >
> > *Main> :t (->) 3 "abc"
> >
> > <interactive>:1:1: parse error on input `->'
>
> Try
>
> *Main> :t undefined :: (->) 3 "abc"
>
> You can't write
>   :t <some type>
> You have to write
>   :t <some value>
>
> > Michael
> >
> > --- On Tue, 8/31/10, Vo Minh Thu <noteed at gmail.com> wrote:
> >
> > From: Vo Minh Thu <noteed at gmail.com>
> > Subject: Re: [Haskell-cafe] On to applicative
> > To: "michael rice" <nowgate at yahoo.com>
> > Cc: "Ryan Ingram" <ryani.spam at gmail.com>, haskell-cafe at haskell.org
> > Date: Tuesday, August 31, 2010, 3:07 PM
> >
> > 2010/8/31 michael rice <nowgate at yahoo.com>
> > >
> > > Hi, Ryan and all,
> > >
> > > Bingo! I guess my question was all right after all.
> > >
> > > I tried creating an instance earlier but
> > >
> > > *Main> :t (->) Int Char
> > >
> > > <interactive>:1:1: parse error on input `->'
> >
> >   :t Int
> > does not make sense but
> >   :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 <ryani.spam at gmail.com> wrote:
> > >
> > > From: Ryan Ingram <ryani.spam at gmail.com>
> > > Subject: Re: [Haskell-cafe] On to applicative
> > > To: "michael rice" <nowgate at yahoo.com>
> > > Cc: "Vo Minh Thu" <noteed at gmail.com>, haskell-cafe at haskell.org
> > > Date: Tuesday, August 31, 2010, 2:36 PM
> > >
> > > Prelude FmapFunc> let s = show :: ((->) Int) String
> > > Prelude FmapFunc> :t s
> > > s :: Int -> String
> > > Prelude FmapFunc> let v = fmap ("hello " ++) s
> > > Prelude FmapFunc> :t v
> > > v :: Int -> String
> > > Prelude FmapFunc> v 1
> > > "hello 1"
> > >
> > >   -- ryan
> > >
> > > On Tue, Aug 31, 2010 at 11:28 AM, michael rice <nowgate at yahoo.com> wrote:
> > >
> > > I'm not sure if my terminology is correct or even if my question makes sense, but I can create "instances" of Maybe, List, IO, and Either.
> > >
> > > Prelude Data.Either> let m = Just 7
> > > Prelude Data.Either> :t m
> > > m :: Maybe Integer
> > >
> > > Prelude Data.Either> let l = 2:[]
> > > Prelude Data.Either> :t l
> > > l :: [Integer]
> > >
> > > Prelude Data.Either> let g = getLine
> > > Prelude Data.Either> :t g
> > > g :: IO String
> > >
> > > Prelude Data.Either> let e = Right "abc"
> > > Prelude Data.Either> :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) where
> > >     fmap f g = (\x -> f (g x))
> > >
> > > to it?
> > >
> > > Michael
> > >
> > > --- On Tue, 8/31/10, Vo Minh Thu <noteed at gmail.com> wrote:
> > >
> > > From: Vo Minh Thu <noteed at gmail.com>
> > > Subject: Re: [Haskell-cafe] On to applicative
> > > To: "michael rice" <nowgate at yahoo.com>
> > > Cc: haskell-cafe at haskell.org
> > > Date: Tuesday, August 31, 2010, 1:50 PM
> > >
> > > 2010/8/31 michael rice <nowgate at yahoo.com>
> > > >
> > > > So it's a type constructor, not a type? Could you please provide a simple example of its usage?
> > >
> > > Sure, although I'm sure you've come by some already.
> > >
> > > -- the identity function
> > > id :: a -> a
> > > -- often, we write it like this:
> > > -- id x = x
> > > -- but here we see the relationship between the ananymous function
> > > syntax and the function type:
> > > id = \x -> x
> > >
> > > In fact, if you write in prefix form, it is quite familiar:
> > > f :: (->) Int Bool
> > > e = Either String Float
> > >
> > > Cheers,
> > > Thu
> > >
> > > > Michael
> > > >
> > > > --- On Tue, 8/31/10, Vo Minh Thu <noteed at gmail.com> wrote:
> > > >
> > > > From: Vo Minh Thu <noteed at gmail.com>
> > > > Subject: Re: [Haskell-cafe] On to applicative
> > > > To: "michael rice" <nowgate at yahoo.com>
> > > > Cc: haskell-cafe at haskell.org
> > > > Date: Tuesday, August 31, 2010, 1:17 PM
> > > >
> > > > 2010/8/31 michael rice <nowgate at yahoo.com>
> > > > >
> > > > > "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 you want to implement a simple, typed functional
> > > > language, you'll find it is the only built-in type constructor you
> > > > have to implement (as the implementor of the language).
> > > >
> > > > Also,
> > > >   Show a => a
> > > > is a type too, but you won't find a definition for 'a' or for '=>'.
> > > > All those things are defined by the language.
> > > >
> > > > Cheers,
> > > > Thu
> > > >
> > >
> > >
> > > _______________________________________________
> > > Haskell-Cafe mailing list
> > > Haskell-Cafe at haskell.org
> > > http://www.haskell.org/mailman/listinfo/haskell-cafe
> > >
> > >
> > >
> >
>


More information about the Haskell-Cafe mailing list