
Didn't know If I should post it straight away... its quite long and I dont do attachments (well not If I can help it. I am aware Dynamic can model heterogenious lists (thanks for correct terminology) - but I need static typing. Thats the clever thing about this code - the list is heterogenious but statically typed. So... for your perusal - and If its not up to being included in the libraries I would value any comments/code review for my own edification. The module is called "Relation" as I am modelling Relational Algebra... but if anyone can think of a better name... First some examples: putStrLn $ show (rIndex two rel1) -- show the third item in rel1 putStrLn $ show (rHead r) putStrLn $ show (rTail r) putStrLn $ show (rLast r) putStrLn $ show (rInit r) putStrLn $ show (r `rEnqueue` "TEST3") -- insert the string into the last (not head) position putStrLn $ show ((3 :: Int) `RCons` r) -- insert the Int into the head of the list r = toTuple (( 1.1 :: Double) `RCons` (fromTuple ("hello",1,"World"))) And the code: {-# OPTIONS -fglasgow-exts #-} {-# OPTIONS -fallow-undecidable-instances #-} {-# OPTIONS -fallow-overlapping-instances #-} module Lib.DBC.Relation where ------------------------------------------------------------------------------ -- (c) 2004 Keean Schupke, All Rights Reserved. ------------------------------------------------------------------------------ data Zero = Zero deriving Show data Suc n = Suc n deriving Show class Nat n instance Nat Zero instance Nat n => Nat (Suc n) zero :: Zero zero = Zero one :: Suc Zero one = Suc zero two :: Suc (Suc Zero) two = Suc one three :: Suc (Suc (Suc Zero)) three = Suc two four :: Suc (Suc (Suc (Suc Zero))) four = Suc three five :: Suc (Suc (Suc (Suc (Suc Zero)))) five = Suc four ------------------------------------------------------------------------------ infixr 1 `RCons` data RNil = RNil deriving Show data RCons a r = a `RCons` r deriving Show ------------------------------------------------------------------------------ class Relation r where rHead :: a `RCons` r -> a rTail :: a `RCons` r -> r rIsEmpty :: r -> Bool instance Relation RNil where rHead (x `RCons` _) = x rTail (_ `RCons` _) = RNil rIsEmpty RNil = True instance Relation r => Relation (a `RCons` r) where rHead (x `RCons` _) = x rTail (_ `RCons` xs) = xs rIsEmpty (_ `RCons` _) = False class RLast r a | r -> a where rLast :: r -> a instance RLast (a `RCons` RNil) a where rLast (x `RCons` RNil) = x instance RLast r b => RLast (a `RCons` r) b where rLast (_ `RCons` xs) = rLast xs class RInit r1 r2 | r1 -> r2 where rInit :: r1 -> r2 instance RInit (a `RCons` RNil) RNil where rInit (_ `RCons` RNil) = RNil instance RInit (b `RCons` r1) r2 => RInit (a `RCons` b `RCons` r1) (a `RCons` r2) where rInit (x `RCons` xs) = x `RCons` rInit xs class REnqueue r1 r2 a | r1 a -> r2 where rEnqueue :: r1 -> a -> r2 instance REnqueue RNil (a `RCons` RNil) a where rEnqueue RNil y = y `RCons` RNil instance REnqueue r1 r2 b => REnqueue (a `RCons` r1) (a `RCons` r2) b where rEnqueue (x `RCons` xs) y = x `RCons` rEnqueue xs y class (Nat n,Relation r) => RIndex n r a | n r -> a where rIndex :: n -> r -> a instance Relation r => RIndex Zero (a `RCons` r) a where rIndex Zero (x `RCons` _) = x instance RIndex n r b => RIndex (Suc n) (a `RCons` r) b where rIndex (Suc n) (_ `RCons` xs) = rIndex n xs infixl 2 `rProduct` class (Relation r1,Relation r2,Relation r3) => RProduct r1 r2 r3 | r1 r2 -> r3 where rProduct :: r1 -> r2 -> r3 instance RProduct RNil RNil RNil where rProduct RNil RNil = RNil instance Relation r => RProduct RNil r r where rProduct RNil r = r instance RProduct r1 r2 r3 => RProduct (a `RCons` r1) r2 (a `RCons` r3) where rProduct (x `RCons` xs) y = x `RCons` (xs `rProduct` y) ------------------------------------------------------------------------------ class Relation r => RTuple t r | t -> r , r -> t where fromTuple :: t -> r toTuple :: r -> t instance RTuple (a,b) (a `RCons` b `RCons` RNil) where fromTuple (a,b) = a `RCons` b `RCons` RNil toTuple (a `RCons` b `RCons` RNil) = (a,b) instance RTuple (a,b,c) (a `RCons` b `RCons` c `RCons` RNil) where fromTuple (a,b,c) = a `RCons` b `RCons` c `RCons` RNil toTuple (a `RCons` b `RCons` c `RCons` RNil) = (a,b,c) instance RTuple (a,b,c,d) (a `RCons` b `RCons` c `RCons` d `RCons` RNil) where fromTuple (a,b,c,d) = a `RCons` b `RCons` c `RCons` d `RCons` RNil toTuple (a `RCons` b `RCons` c `RCons` d `RCons` RNil) = (a,b,c,d) instance RTuple (a,b,c,d,e) (a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` RNil) where fromTuple (a,b,c,d,e) = a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` RNil toTuple (a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` RNil) = (a,b,c,d,e) instance RTuple (a,b,c,d,e,f) (a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` f `RCons` RNil) where fromTuple (a,b,c,d,e,f) = a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` f `RCons` RNil toTuple (a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` f `RCons` RNil) = (a,b,c,d,e,f) ------------------------------------------------------------------------------

Hi Kean, looks cool. I get your point about static typing. I guess that adding a fold operator would make your implementation more complete. Oleg has also encountered some of your operations (as you probably know): http://www.haskell.org/pipermail/haskell/2003-August/012355.html (Oleg also prefers the term polymorphic lists --- sigh, and he considers indexing by types rather than naturals. In fact, he mentions that values can be retrieved by either type or index, while only the former is discussed in detail, if I am right. To me it seems, he would also need to end up using dependant-type encoding of naturals, say data Zero ... and data Succ ..., for look-up. If I am still right, then his operator type_index is underspecified because it returns a plain Int, but Int could be replaced by dependant-type Naturals. Really just guessing. Oleg?) Minor point: the code I posted combines existential types and type-safe cast. It does *not* employ the type Dynamic. (You might say that dynamics and this combination are somewhat equivalent.) Ralf MR K P SCHUPKE wrote:
Didn't know If I should post it straight away... its quite long and I dont do attachments (well not If I can help it. I am aware Dynamic can model heterogenious lists (thanks for correct terminology) - but I need static typing. Thats the clever thing about this code - the list is heterogenious but statically typed.
So... for your perusal - and If its not up to being included in the libraries I would value any comments/code review for my own edification.
The module is called "Relation" as I am modelling Relational Algebra... but if anyone can think of a better name...
First some examples:
putStrLn $ show (rIndex two rel1) -- show the third item in rel1 putStrLn $ show (rHead r) putStrLn $ show (rTail r) putStrLn $ show (rLast r) putStrLn $ show (rInit r) putStrLn $ show (r `rEnqueue` "TEST3") -- insert the string into the last (not head) position putStrLn $ show ((3 :: Int) `RCons` r) -- insert the Int into the head of the list r = toTuple (( 1.1 :: Double) `RCons` (fromTuple ("hello",1,"World")))
And the code:
{-# OPTIONS -fglasgow-exts #-} {-# OPTIONS -fallow-undecidable-instances #-} {-# OPTIONS -fallow-overlapping-instances #-}
module Lib.DBC.Relation where
------------------------------------------------------------------------------ -- (c) 2004 Keean Schupke, All Rights Reserved. ------------------------------------------------------------------------------
data Zero = Zero deriving Show data Suc n = Suc n deriving Show
class Nat n instance Nat Zero instance Nat n => Nat (Suc n)
zero :: Zero zero = Zero
one :: Suc Zero one = Suc zero
two :: Suc (Suc Zero) two = Suc one
three :: Suc (Suc (Suc Zero)) three = Suc two
four :: Suc (Suc (Suc (Suc Zero))) four = Suc three
five :: Suc (Suc (Suc (Suc (Suc Zero)))) five = Suc four
------------------------------------------------------------------------------
infixr 1 `RCons` data RNil = RNil deriving Show data RCons a r = a `RCons` r deriving Show
------------------------------------------------------------------------------
class Relation r where rHead :: a `RCons` r -> a rTail :: a `RCons` r -> r rIsEmpty :: r -> Bool instance Relation RNil where rHead (x `RCons` _) = x rTail (_ `RCons` _) = RNil rIsEmpty RNil = True instance Relation r => Relation (a `RCons` r) where rHead (x `RCons` _) = x rTail (_ `RCons` xs) = xs rIsEmpty (_ `RCons` _) = False
class RLast r a | r -> a where rLast :: r -> a instance RLast (a `RCons` RNil) a where rLast (x `RCons` RNil) = x instance RLast r b => RLast (a `RCons` r) b where rLast (_ `RCons` xs) = rLast xs
class RInit r1 r2 | r1 -> r2 where rInit :: r1 -> r2 instance RInit (a `RCons` RNil) RNil where rInit (_ `RCons` RNil) = RNil instance RInit (b `RCons` r1) r2 => RInit (a `RCons` b `RCons` r1) (a `RCons` r2) where rInit (x `RCons` xs) = x `RCons` rInit xs
class REnqueue r1 r2 a | r1 a -> r2 where rEnqueue :: r1 -> a -> r2 instance REnqueue RNil (a `RCons` RNil) a where rEnqueue RNil y = y `RCons` RNil instance REnqueue r1 r2 b => REnqueue (a `RCons` r1) (a `RCons` r2) b where rEnqueue (x `RCons` xs) y = x `RCons` rEnqueue xs y
class (Nat n,Relation r) => RIndex n r a | n r -> a where rIndex :: n -> r -> a instance Relation r => RIndex Zero (a `RCons` r) a where rIndex Zero (x `RCons` _) = x instance RIndex n r b => RIndex (Suc n) (a `RCons` r) b where rIndex (Suc n) (_ `RCons` xs) = rIndex n xs
infixl 2 `rProduct` class (Relation r1,Relation r2,Relation r3) => RProduct r1 r2 r3 | r1 r2 -> r3 where rProduct :: r1 -> r2 -> r3 instance RProduct RNil RNil RNil where rProduct RNil RNil = RNil instance Relation r => RProduct RNil r r where rProduct RNil r = r instance RProduct r1 r2 r3 => RProduct (a `RCons` r1) r2 (a `RCons` r3) where rProduct (x `RCons` xs) y = x `RCons` (xs `rProduct` y)
------------------------------------------------------------------------------
class Relation r => RTuple t r | t -> r , r -> t where fromTuple :: t -> r toTuple :: r -> t
instance RTuple (a,b) (a `RCons` b `RCons` RNil) where fromTuple (a,b) = a `RCons` b `RCons` RNil toTuple (a `RCons` b `RCons` RNil) = (a,b)
instance RTuple (a,b,c) (a `RCons` b `RCons` c `RCons` RNil) where fromTuple (a,b,c) = a `RCons` b `RCons` c `RCons` RNil toTuple (a `RCons` b `RCons` c `RCons` RNil) = (a,b,c)
instance RTuple (a,b,c,d) (a `RCons` b `RCons` c `RCons` d `RCons` RNil) where fromTuple (a,b,c,d) = a `RCons` b `RCons` c `RCons` d `RCons` RNil toTuple (a `RCons` b `RCons` c `RCons` d `RCons` RNil) = (a,b,c,d)
instance RTuple (a,b,c,d,e) (a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` RNil) where fromTuple (a,b,c,d,e) = a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` RNil toTuple (a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` RNil) = (a,b,c,d,e)
instance RTuple (a,b,c,d,e,f) (a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` f `RCons` RNil) where fromTuple (a,b,c,d,e,f) = a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` f `RCons` RNil toTuple (a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` f `RCons` RNil) = (a,b,c,d,e,f)
------------------------------------------------------------------------------

Hello, Ralf!
In fact, he mentions that values can be retrieved by either type or index, while only the former is discussed in detail, if I am right. To me it seems, he would also need to end up using dependant-type encoding of naturals, say data Zero ... and data Succ ..., for look-up. If I am still right, then his operator type_index is underspecified because it returns a plain Int, but Int could be replaced by dependant-type Naturals.
Indexing of types by regular integers was discussed in http://www.mail-archive.com/haskell@haskell.org/msg13163.html which was a response to your comments. I hope you saw them. The topic was encoding and storing of values of _polymorphic_ datatypes. However, the following is a more succinct realization of a polymorphic list. Retrieval is done by ordinary _integers_. The list behaves roughly as a regular list. Although we use the type of a value to obtain the integral index, and we use the integral index to fetch the value.
{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances -fallow-overlapping-instances #-}
module Foo where
class (Show a) => TH a b where idx:: a -> b -> Int alter:: a -> b -> b tke:: a -> b -> (forall u v. TH u v => u -> v -> w) -> w
instance (Show a) => TH a (a,x) where idx x y = 0 alter x (_,y) = (x,y)
instance (TH a c) => TH a (b,c) where idx x y = 1 + idx x (undefined::c) alter x (h,t) = (h,alter x t)
data W = W Int deriving Show
instance (TH a (a,b), TH W b) => TH W (a,b) where tke (W 0) th@(h,t) f = f h th tke (W n) (h,t) f = tke (W$ n-1) t f
instance TH W () where tke _ _ _ = error "Not found"
That's it. Class Show is for expository purposes, so we can print what we've got. The following is to enable us to store functional values
instance Show (a->b) where show _ = "<fn>"
Here's the initial heap
infixr 5 &+
a &+ b = (a,b)
th1 = (1::Int) &+ 'x' &+ (Just True) &+ () &+ [1.0::Float] &+ (\(c::Char) -> True) &+ () -- just to mark the end of it
Now the fun begins: *Foo> idx 'a' th1 1 *Foo> idx [2.0::Float] th1 4 *Foo> idx (=='c') th1 5 We can use a functional type as an index. We can fetch things too: *Foo> tke (W 0) th1 (const.show) "1" *Foo> tke (W 1) th1 (const.show) "'x'" *Foo> tke (W 4) th1 (const.show) "[1.0]" *Foo> tke (W 5) th1 (const.show) "<fn>" We can store and retrieve things *Foo> tke (W 4) (alter [1.0::Float, 2.0::Float] th1) (const.show) "[1.0,2.0]" Right fold can be done along the lines of tke. Only a type like W will hold our accumulator.
participants (3)
-
MR K P SCHUPKE
-
oleg@pobox.com
-
Ralf Laemmel