Polymorphic lists...

MR K P SCHUPKE k.schupke at imperial.ac.uk
Tue Mar 9 10:01:08 EST 2004


I did not know about Oleg's posting, as I originally said, I based my implementation on
a paper by Conor McBride. Oleg is addressing the question of type safe casting, rather
than generic storage, so his code is a bit different. Infact his class:

> class TypeSeq t s where
>     type_index:: t -> s -> Int
>     fetch:: t -> s -> t
>     alter:: t -> s -> s
>    
> instance (PList Cons t r) => TypeSeq t (Cons t r) where
>     type_index _ _ = 0
>     fetch _ (Cons v _) = v
>     alter newv (Cons v r)  = Cons newv r
>    
> instance (PList Cons t' r', TypeSeq t r') => TypeSeq t (Cons t' r') where
>     type_index v s = 1 + (type_index v $ cdr s)
>     fetch v s = fetch v $ cdr s
>     alter newv (Cons v' r') = Cons v' $ alter newv r'

This stores unique types in a list that can be indexed by their types. Actually last 
night (before I read this code) I came up with something similar:

data MNil = MNil deriving (Show,Data,Typeable)
data MCons l a r = MCons l a r deriving (Show,Data,Typeable)

class MLookup l r a | l r -> a where
   mLookup :: r -> l -> a
instance MLookup l (MCons l a r) a where
   mLookup (MCons _ x _) _ = x
instance MLookup l r b => MLookup l (MCons m a r) b where
   mLookup (MCons _ _ xs) l = mLookup xs l


This is indexed by a unique type, but stores a second independant
type. The allows a kind of static finite map, which is pretty cool!
Here's an example:

data TmId = TmId
data TmVal = TmVal
data TmFloat = TmFloat
data TmName = TmName

testMap :: MCons TmId Int
	(MCons TmVal String
	(MCons TmFloat Float
	(MCons TmName String
	MNil)))

testMap = MCons TmId 1
	$ MCons TmVal "Hello"
	$ MCons TmFloat 1.2
	$ MCons TmName "World"
	MNil

main :: IO ()
main = do
	putStrLn $ show $ testMap `mLookup` TmId
	putStrLn $ show $ testMap `mLookup` TmVal
	putStrLn $ show $ testMap `mLookup` TmFloat
	putStrLn $ show $ testMap `mLookup` TmName

Index types don't need to be unique, the first match from the
head of the list will be returned. No match will result in a 
compile time error.

Regards,
	Keean Schupke.


More information about the Glasgow-haskell-users mailing list