source: sizechecking/L.hs @ 9

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

finishing arrow type

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