Ingo Sander wrote:
I have a question concerning the Read and Show classes.

I have read the Haskell 98 report (section 6.3.3 The Read and Show
Classes), but I still do not figure out how to make instances.

I have a simple data type:

data TVal a =  Abst
             | Prst a

I managed to define the function show, so that I can use it with the data
type TVal

instance (Show a) => Show (TVal a) where
         show Abst     = "_"
         show (Prst x) = show x

Signals> [Prst 1, Abst, Prst 2]
[1,_,2] :: [TVal Integer]

which is what I want to have.

But how do I make a Read instance?

I still do not understand the meaning of 'readsPrec' and
'readList' (and not of 'showPrec' and 'showList') either.

Can somebody explain to me or give me a good reference so that I can make
TVal an instance of the classes Read and Show.

Thanks in advance for your help!

Ingo Sander

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


I might do it this way:

> data TVal a = Abst | Prst a
 
> instance (Show a) => Show (TVal a) where
>     showsPrec p Abst = ('_' :)
>     showsPrec p (Prst x) = showsPrec p x

> instance (Read a) => Read (TVal a) where
>     readsPrec p s = case s' of ('_':t) -> (Abst,t) : readsA
>                                _ -> readsA
>       where s' = dropWhile isSpace s
>             readsA = map (\(a,t)-> (Prst a,t)) (readsPrec p s')

See section D.4 of the Haskell report for information on 'readsPrec', 'readList', 'showPrec', and 'showList'.

Dean Herington