[Haskell-beginners] am I wording this right?

Peter Verswyvelen bugfact at gmail.com
Tue Aug 4 20:15:44 EDT 2009


That sound okay to me.

Usually when we have type constructor "T a" and an "instance Functor T
where..." we just say that "T is a functor"

Note that the signature of a type constructor is called the "kind" of
the type constructor.

For example, the following code

data NotSoKind = X
instance Functor NotSoKind where

would give the error:

Kind mis-match
    Expected kind `* -> *', but `NotSoKind' has kind `*'
    In the instance declaration for `Functor NotSoKind'

and

instance Functor (,) where

gives the error

(,)' is not applied to enough type arguments
    Expected kind `* -> *', but `(,)' has kind `* -> * -> *'
    In the instance declaration for `Functor (,)'


Note however that the following is correct:

instance Functor ((,) a) where
    fmap f (x,y) = (x, f y)

and even:

instance Functor ((->) a) where
    fmap f g = f . g


You can ask GHCi to show the kind of a type constructor:

:kind (,)
(,) :: * -> * -> *

:kind ((,) 1)
((,) 1) :: * -> *

:kind Char
*











On Wed, Aug 5, 2009 at 1:07 AM, Michael P Mossey <mpm at alumni.caltech.edu> wrote:
>
> Is this the right way of saying what I'm trying to say?
>
> "Functor is a typeclass of type constructors which take one argument."
>
> Thanks,
> Mike
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners


More information about the Beginners mailing list