[Haskell-cafe] Intermediate type variables

Giuseppe Maggiore giuseppemag at gmail.com
Fri Mar 19 07:51:38 EDT 2010


Hi! How can I specify intermediate type variables to help the compiler do
its job?

The following, simple, code does not compile because the compiler cannot
infer that the type variable a' is CInt; this makes sense, because finding
that out would be quite hard. How can I tell the compiler that a' is CInt?

 {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
FlexibleInstances,
  UndecidableInstances, FlexibleContexts, EmptyDataDecls,
ScopedTypeVariables,
  TypeOperators, TypeSynonymInstances #-}
class C a a'  where convert :: a -> a'
class F a b   where apply :: a -> b
class S s a   where select :: s -> a
data CInt = CInt Int
instance S (Int,String) Int where select (i,_) = i
instance C Int CInt where convert = CInt
instance F CInt Int where apply (CInt i) = i + 1
f :: forall s a a' b . (S s a, C a a', F a' b) => s -> b
f s =
  let v = select s :: a
      v' = convert v :: a'
      y = apply v' :: b
  in y

x :: Int
x = f (10,"foo")


Thanks
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100319/e17ca6a3/attachment.html


More information about the Haskell-Cafe mailing list