[Haskell-cafe] reading existential types
Andrea Rossato
mailing_list at istitutocolli.org
Mon Jul 9 10:22:23 EDT 2007
Hi,
I have a problem I cannot solve. I have a data type that I need to be
readable, and the read instance derivable.
I need it readable because it is going to be a data type for
configuring at run time an application, and I want the application to
read it when booting up.
On the other side, I also need an existential type to be used within
this data type: it is a list that must be polymorphic somehow.
Since instances for existentially qualified types cannot be derived I
thought to create a type that could be easily read. But I'm not able to
write the parser, and I'm not sure if this is my fault or just a
limitation I'm trying to futilely overcome.
Below there's a piece of code that shows the problem.
I'd like to be able to use MT to build a list like:
[MT (T1a,1), MT (T1b,3)]
And I'd like to read str with:
read $ show str
No way, and the code below compiles.
Substituting return (m) with return (MT m) leads to error messages
like: Ambiguous type variable `e' in the constraints
What am I getting wrong? Is just the parser or there's something
deeper?
Thanks for your kind attention.
All the best
Andrea
the code:
----------------------------------------------------------------
{-# OPTIONS -fglasgow-exts #-}
module Test where
import Text.Read
import Text.ParserCombinators.ReadPrec
data MyData =
MD { rec1 :: String
, rec2 :: String
, rec3 :: [MyType]
} deriving (Read,Show)
data MyType = forall e . (MyClass e, Show e, Read e) => MT (e,Int)
instance Show MyType where
show (MT a) = "MT " ++ show a
class MyClass c where
myShow :: c -> String
data TipoA = T1a
| T2a
| T3a
deriving(Show,Read,Eq)
instance MyClass TipoA where
myShow T1a = "t1a"
myShow T2a = "t2a"
myShow T3a = "t3a"
data TipoB = T1b
| T2b
| T3b
deriving(Show,Read,Eq)
instance MyClass TipoB where
myShow T1b = "t1b"
myShow T2b = "t2b"
myShow T3b = "t3b"
str :: MyData
str = MD {rec1 = "Ciao", rec2 = "Ciao Ciao", rec3 = [MT (T1a,1), MT (T1b,3)] }
instance Read MyType where
readPrec = readMT
readMT :: ReadPrec MyType
readMT = prec 10 $ do
Ident "MT" <- lexP
parens $ do m <- readPrec
return (m)
More information about the Haskell-Cafe
mailing list