[Haskell-beginners] Type families with kind * -> *

Daniel Fischer daniel.is.fischer at web.de
Thu Apr 23 13:32:15 EDT 2009


Am Donnerstag 23 April 2009 19:15:05 schrieb Marco Túlio Gontijo e Silva:
> Hello,
>
> I read the type families example at
> http://haskell.org/haskellwiki/GHC/Indexed_types and I wanted to do
> something similar to the Collects example, but using a type of kind * ->
>
> *:
> > class StateFunctor sf where
> >   type SFMonad sf
> >   type SFValue sf
> >   sfmap :: (SFValue sf -> SFValue sf) -> sf -> SFMonad sf ()
>
> I wrote the instance as:
> > instance StateFunctor (ListStore a) where
> >   type SFMonad (ListStore a) = IO
> >   type SFValue (ListStore a) = a
> >   sfmap function listStore
> >     = listStoreGetSize listStore >>= listStoreSfmap function listStore
> >
> > listStoreSfmap :: (a -> a) -> ListStore a -> Int -> IO ()
> > listStoreSfmap _function _listStore 0 = []
> > listStoreSfmap function listStore size
> >   = listStoreGetValue listStore index
> >
> >     >>= listStoreSetValue listStore index . function
> >   >>
> >   >> listStoreSfmap function listStore index
> >
> >   where
> >     index :: Int
> >     index = pred size
>
> I'm getting:
>
> DistroCreator/GUI/List.hs:51:47:
>     Kind error: `SFMonad' is applied to too many type arguments
>     In the type `SFMonad sf ()'
>     In the type `sf -> SFMonad sf ()'
>     In the type `(SFValue sf -> SFValue sf) -> sf -> SFMonad sf ()'
> Failed, modules loaded: none.
>
> How can I use type families with types * -> *?

For example:
-----------------------------------
{-# LANGUAGE TypeFamilies, KindSignatures #-}
module TypeF where

data ListStore a = Dummy

listStoreGetSize = undefined
listStoreSfmap = undefined

class StateFunctor sf where
   type SFMonad sf :: (* -> *)
   type SFValue sf
   sfmap :: (SFValue sf -> SFValue sf) -> sf -> SFMonad sf ()

instance StateFunctor (ListStore a) where
   type SFMonad (ListStore a) = IO
   type SFValue (ListStore a) = a
   sfmap function listStore
     = listStoreGetSize listStore >>= listStoreSfmap function listStore

-------------------------------------
Prelude> :l TypeF
[1 of 1] Compiling TypeF            ( TypeF.hs, interpreted )
Ok, modules loaded: TypeF.


>
> Greetings.



More information about the Beginners mailing list