[Haskell-cafe] Code that doesn't compile - but should :)

Giuseppe Maggiore giuseppemag at gmail.com
Tue Mar 16 05:22:46 EDT 2010


Hi! Can anyone tell me why this code does not work? I cannot seem to
figure why it is broken...



{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances,
  UndecidableInstances, FlexibleContexts, EmptyDataDecls, ScopedTypeVariables,
  TypeOperators, TypeSynonymInstances #-}

data Data k = Pair Integer (() -> k)
data RecData = RecData (Data RecData)
mk_data x = RecData(Pair x (\() -> mk_data (x+1)))

class Converter a f where convert :: a -> f a

instance Converter RecData Data where
  convert (RecData r) = r

class Selector s a where select :: s -> a

f :: (Selector s (a->f a), Converter a f) => s -> (a->a)
f s =
  let method = select s
  in (\x ->
        let res = method x
        in convert res)

--
Giuseppe Maggiore
Ph.D. Student (Languages and Games)
Microsoft Student Partner
Mobile: +393319040031
Office: +390412348444


More information about the Haskell-Cafe mailing list