source: sizechecking_branches/L.hs @ 11

Last change on this file since 11 was 10, checked in by gobi, 13 years ago

adding a new implementation of Lambda

File size: 6.6 KB
Line 
1{-# Language GADTs, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses, FunctionalDependencies, ScopedTypeVariables, TypeFamilies, NoMonomorphismRestriction, OverlappingInstances #-}
2module L where
3
4import Data.Char(ord, chr)
5import Control.Monad.State
6--import Data.Supply
7
8data OpName = PLUS | MINUS | MUL
9data Bottom = Bottom
10  deriving Show
11
12{- Lambda calculus without free variables -}
13type Arr repr a b = repr a -> repr b
14
15class Lambda l where
16    labs    :: (l a -> l b) -> l (Arr l a b)
17    app     :: l (Arr l a b) -> l a -> l b
18    lit     :: Int -> l Int
19    op      :: l Int -> OpName -> l Int -> l Int
20
21class SizeExp l where
22    type List l :: * -> *
23    list    :: l Int -> l (Arr l Int b) -> l (List l b)
24    aabs    :: (l Int -> l (Arr l Int a) -> l b) -> l (Arr l (List l a) b)
25    shift   :: l (Arr l Int a) -> l Int -> l (Arr l Int a) -> l (Arr l Int a)
26    undef   :: l Bottom
27    unsized :: l ()
28
29instance Lambda l => Show (l a) where
30    showsPrec _ e = error "Error: no show"
31
32instance Lambda l => Eq (l a) where
33    (==) _ _ = error "Error: no eq"
34
35instance Lambda l => Num (l Int) where
36    fromInteger = lit . fromIntegral
37    lhs + rhs   = op lhs PLUS rhs
38    lhs - rhs   = op lhs MINUS rhs
39    lhs * rhs   = op lhs MUL rhs
40    abs = error "abs is not implemented"
41    signum = error "signum is not implemented"
42
43{- Printing -}
44newtype LPrint a = LPrint { unPrint :: Int -> Int -> ShowS }
45
46instance Lambda LPrint where
47  lit x      = LPrint $ \_ -> return $ shows x
48  op m opc n = LPrint $ \p -> do
49    let (prec, lprec, rprec, c) = getPrec opc
50    l1 <- (unPrint m lprec)
51    l2 <- (unPrint n rprec)
52    return $ showParen (p>prec) $  l1 . showChar c . l2
53  app f v    = LPrint $ \p -> do
54    l1 <- unPrint f 6
55    l2 <- unPrint v 7
56    return $ showParen (p>6) $ l1 . showChar ' ' . l2
57  labs e      = LPrint $ \p v -> let
58    var = LPrint $ \_ -> return $ showVar v
59    l = unPrint (e var) 0 $ succ v
60    in showParen (p>0) $ showChar 'λ' . showVar v . showChar '.' . l
61
62instance SizeExp LPrint where
63  type List LPrint = []
64  aabs f   = LPrint $ \p v -> let 
65    v2 = succ v
66    var1 = LPrint $ \_ _ -> showVar v
67    var2 = LPrint $ \_ _ -> showVar v2
68    l = unPrint (f var1 var2) 0 (v+2)
69    in showParen (p>0) $ showChar 'Λ' . showVar v . showChar ',' . showVar v2 . showChar '.' . l
70  list s f = LPrint $ \p -> do
71    l1 <- unPrint s 9
72    l2 <- unPrint f 9
73    return $ showParen (p>0) $ showString "List " . l1 . showChar ' ' . l2
74  shift e1 s e2 = LPrint $ \p -> do
75    l1 <- unPrint e1 2
76    l2 <- unPrint s 2
77    l3 <- unPrint e2 2
78    return $ showParen (p>0) $ showString "Shift " . l1 .  showChar ' ' . l2 . showChar ' ' . l3
79  undef = LPrint $ \_ -> return $ showChar '┮'
80  unsized = LPrint $ \_ -> return $ showChar 'U'
81
82view :: LPrint a -> LPrint a
83view = id
84instance Show (LPrint a) where
85    showsPrec _ e = unPrint e 0 0
86
87showVar x = if x>28 
88    then showVar (x `div` 29) . showChar (chr $ ord 'a' + (x `mod` 29))
89    else showChar $ chr $ ord 'a' + x
90
91getPrec :: OpName -> (Int,Int,Int,Char)
92getPrec PLUS = (4,4,5,'+')
93getPrec MINUS = (4,4,5,'-')
94getPrec MUL = (5,5,6,'*')
95
96getVar :: State Int Int
97getVar = do { x <- get; put (x+1); return x }
98
99x = aabs (\s _ -> s) `app` list (lit 0) (labs $ \_ -> undef)
100y = list 0 $ labs $ \_ -> undef
101z = (labs $ \s -> s+1) `app` (lit 1+2)
102conss = labs $ \x -> aabs $ \ys yf -> list (ys + 1) $ shift yf ys (labs $ \_ -> x)
103concats = aabs $ \xs xf -> (aabs $ \ys yf -> list (xs+ys) $ shift xf xs yf)
104maps = labs $ \x -> aabs $ \ys yf -> list ys ( x `app` yf )
105l0 = list (lit 0) (labs $ \_ -> unsized)
106l1 = list (lit 1) (labs $ \_ -> unsized)
107l2 = list (lit 2) (labs $ \_ -> unsized)
108l00 = list (lit 0) (labs $ \_ -> list (lit 0) (labs $ \_ -> unsized))
109l10 = list (lit 1) (labs $ \_ -> list (lit 0) (labs $ \_ -> unsized))
110l01 = list (lit 0) (labs $ \_ -> list (lit 1) (labs $ \_ -> unsized))
111l11 = list (lit 1) (labs $ \_ -> list (lit 1) (labs $ \_ -> unsized))
112l12 = list (lit 1) (labs $ \_ -> list (lit 2) (labs $ \_ -> unsized))
113
114{- Evaluating -}
115newtype R a = R { unR :: a }
116instance Lambda R where
117  labs f      = R $ f
118  app e1 e2   = (unR e1) e2
119  lit i       = R i
120  op e1 op e2 = let opm = case op of
121                                  PLUS  -> (+)
122                                  MINUS -> (-)
123                                  MUL   -> (*)
124                in R $ opm (unR e1) (unR e2)
125
126newtype RList a = RList { unList :: (Int, Int -> a)  }
127instance (Show a) => Show (RList a) where
128  show (RList (s,f)) = show (map f [0..s-1])
129
130instance SizeExp R where
131  type List R = RList
132  undef       = R $ Bottom
133  unsized     = R $ ()
134  list s f    = R $ RList (unR s, unR . (unR f) . R )
135  aabs e = R $ ( \(RList (s,f)) -> (e (R s) (R (R . f . unR))) ) . unR
136  shift a s c = R $ \i -> if (unR i)<(unR s) then unR a i else unR c i
137
138-- Type level int to count arity
139data Zero
140data Succ a
141
142data Exp a where
143    Lit :: Int -> Exp Zero
144    Op  :: Exp Zero -> OpName -> Exp Zero -> Exp Zero
145    App :: Exp (Succ a) -> Exp Zero -> Exp a
146    Var :: Int -> Exp a
147
148instance Show (Exp a) where
149    showsPrec _ (Lit a)         = shows a
150    showsPrec p (Op lhs op rhs) =
151        let (prec, lprec, rprec, c) = getPrec op
152        in showParen (p>prec) $  showsPrec lprec lhs . showChar c . showsPrec rprec rhs
153    showsPrec p (App lhs rhs)   =
154        showParen (p>6) $ showsPrec 6 lhs . showChar ' ' . showsPrec 7 rhs
155    showsPrec _ (Var i)         = showVar i
156
157type IntExp = Exp Zero
158data Condition = Eq IntExp IntExp | Gt IntExp IntExp | Lt IntExp IntExp
159type SExp a = ([Condition], IntExp)
160newtype Compile a = Compile { unCompile :: SExp a }
161
162--instance Lambda Compile where
163--  labs :: (l a -> l b) -> l (a -> b)
164--    labs f = Compile $ f
165
166
167--{- Create a restricted deep embedding to work with the expression -}
168--{- sized [a] to prove -}
169--
170--class Restricted a where
171--    kind :: a -> Int
172--
173--instance Restricted Int where
174--    kind _ = 0
175--
176--instance Restricted a => Restricted (Int -> a) where
177--    kind _ = succ $ kind $ (undefined :: a)
178--
179--class Var l where
180--    var :: Restricted a => Int -> l a
181--
182--showVar2 x = showChar '_' . showVar x
183--
184--newtype Count a = C { count :: Int }
185--cnv :: Restricted a => Count a -> a
186--cnv = undefined
187--
188--ckind :: (Restricted a) => Count a -> Int
189--ckind = kind . cnv
190--
191--instance Var Count where
192--    var _ = undefined
193--
194--instance Var LPrint where
195--    var x = LPrint $ \_ -> return $ showVar2 x
196--
197--class MGS a where
198--  mgs :: Supply Int -> a -> a
199--  mgs = mgs' []
200--  mgs' :: [Int] -> Supply Int -> a -> a
201--
202--instance MGS () where
203--  mgs' _ _ _ = ()
204--
205--instance MGS a => MGS (RList a) where
206--  mgs' bound supp  _ = RList (listsize, undefined)
207--    where
208--    (s1, s2, s3) = split3 supp
209--    listsize = mgs' bound supp (undefined :: a)
Note: See TracBrowser for help on using the repository browser.