Haskell Guru's,
Am I right in assuming that Haskell will correctly derive instances of
'readsPrec' for user defined types, if they include the 'deriving (Text)'
keywords in the type declaration, and if all elements of that user defined
type have a 'Text' instance defined somewhere.
I am investigating I/O in Haskell with a user defined 'Set' type as follows.
> data (Ord a) => Set a = MkSet [a] deriving (Eq,Ord,Text)
I can get the Haskell generated 'showsPrec' function to work Ok with a
Set of Int's and I can also override it with my own version of 'showsPrec' etc.
But, on trying to read back a Set of Int's from a file I am getting the
following error.
Fail: No default method for "PreludeCore.Text.readsPrec"
Can anyone shed any light on my problem. The offending script is shown below.
Note 's1' is a set of integers and is exported from the set module.
> module Main where
> import Set
>main =
> writeFile "out" (show s1) exit $
> readFile "out" (\e ->appendChan stdout
> "No Such file!" exit done) $
> \c -> appendChan stdout (show (read c::Set Int)) exit done
Also, while I'm on the subject of I/O I notice in the standard prelude
a member function of the Text class called 'showList' of type
> showList :; Text a => [a] -> ShowS
If I try to use this function when displaying my Set type as follows
> instance (Text a) => Text (Set a) where
> showsPrec d (MkSet [a]) = showString "Set " . showList [a]
the program compiles but aborts with following runtime error when executed.
'incomplete pattern(s) to match in function "showsPrec"'
I have implemented the function as follows and all works as expected but I am
curious as to why the first example does not work.
> instance (Text a) => Text (Set a) where
> showsPrec d (MkSet []) = showString "Set []"
> showsPrec d (MkSet (x:xs)) =
> showString "MkSet [" . shows x . srest xs
> where
> srest [] = showChar ']'
> srest (x':xs') = showChar ',' .shows x' . srest xs'
Aiden McCaughey
University of Ulster
[EMAIL PROTECTED]