[10] | 1 | {-# Language GADTs, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses, FunctionalDependencies, ScopedTypeVariables, TypeFamilies, NoMonomorphismRestriction, OverlappingInstances #-} |
---|
| 2 | module L where |
---|
[7] | 3 | |
---|
| 4 | import Data.Char(ord, chr) |
---|
| 5 | import Control.Monad.State |
---|
[8] | 6 | --import Data.Supply |
---|
[7] | 7 | |
---|
| 8 | data OpName = PLUS | MINUS | MUL |
---|
| 9 | data Bottom = Bottom |
---|
| 10 | deriving Show |
---|
| 11 | |
---|
| 12 | {- Lambda calculus without free variables -} |
---|
[8] | 13 | type Arr repr a b = repr a -> repr b |
---|
| 14 | |
---|
[7] | 15 | class Lambda l where |
---|
[8] | 16 | labs :: (l a -> l b) -> l (Arr l a b) |
---|
| 17 | app :: l (Arr l a b) -> l a -> l b |
---|
[7] | 18 | lit :: Int -> l Int |
---|
| 19 | op :: l Int -> OpName -> l Int -> l Int |
---|
| 20 | |
---|
| 21 | class SizeExp l where |
---|
| 22 | type List l :: * -> * |
---|
[8] | 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) |
---|
[7] | 26 | undef :: l Bottom |
---|
| 27 | unsized :: l () |
---|
| 28 | |
---|
[10] | 29 | instance Lambda l => Show (l a) where |
---|
| 30 | showsPrec _ e = error "Error: no show" |
---|
| 31 | |
---|
| 32 | instance Lambda l => Eq (l a) where |
---|
| 33 | (==) _ _ = error "Error: no eq" |
---|
| 34 | |
---|
[7] | 35 | instance 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 -} |
---|
[8] | 44 | newtype LPrint a = LPrint { unPrint :: Int -> Int -> ShowS } |
---|
[7] | 45 | |
---|
| 46 | instance Lambda LPrint where |
---|
[8] | 47 | lit x = LPrint $ \_ -> return $ shows x |
---|
[7] | 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 |
---|
[8] | 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 |
---|
[7] | 61 | |
---|
| 62 | instance SizeExp LPrint where |
---|
| 63 | type List LPrint = [] |
---|
[8] | 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 |
---|
[7] | 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 | |
---|
[8] | 82 | view :: LPrint a -> LPrint a |
---|
| 83 | view = id |
---|
| 84 | instance Show (LPrint a) where |
---|
| 85 | showsPrec _ e = unPrint e 0 0 |
---|
[7] | 86 | |
---|
| 87 | showVar 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 | |
---|
| 91 | getPrec :: OpName -> (Int,Int,Int,Char) |
---|
| 92 | getPrec PLUS = (4,4,5,'+') |
---|
| 93 | getPrec MINUS = (4,4,5,'-') |
---|
| 94 | getPrec MUL = (5,5,6,'*') |
---|
| 95 | |
---|
| 96 | getVar :: State Int Int |
---|
| 97 | getVar = do { x <- get; put (x+1); return x } |
---|
| 98 | |
---|
| 99 | x = aabs (\s _ -> s) `app` list (lit 0) (labs $ \_ -> undef) |
---|
| 100 | y = list 0 $ labs $ \_ -> undef |
---|
| 101 | z = (labs $ \s -> s+1) `app` (lit 1+2) |
---|
| 102 | conss = labs $ \x -> aabs $ \ys yf -> list (ys + 1) $ shift yf ys (labs $ \_ -> x) |
---|
| 103 | concats = aabs $ \xs xf -> (aabs $ \ys yf -> list (xs+ys) $ shift xf xs yf) |
---|
| 104 | maps = labs $ \x -> aabs $ \ys yf -> list ys ( x `app` yf ) |
---|
| 105 | l0 = list (lit 0) (labs $ \_ -> unsized) |
---|
| 106 | l1 = list (lit 1) (labs $ \_ -> unsized) |
---|
| 107 | l2 = list (lit 2) (labs $ \_ -> unsized) |
---|
| 108 | l00 = list (lit 0) (labs $ \_ -> list (lit 0) (labs $ \_ -> unsized)) |
---|
| 109 | l10 = list (lit 1) (labs $ \_ -> list (lit 0) (labs $ \_ -> unsized)) |
---|
| 110 | l01 = list (lit 0) (labs $ \_ -> list (lit 1) (labs $ \_ -> unsized)) |
---|
| 111 | l11 = list (lit 1) (labs $ \_ -> list (lit 1) (labs $ \_ -> unsized)) |
---|
| 112 | l12 = list (lit 1) (labs $ \_ -> list (lit 2) (labs $ \_ -> unsized)) |
---|
| 113 | |
---|
| 114 | {- Evaluating -} |
---|
| 115 | newtype R a = R { unR :: a } |
---|
| 116 | instance Lambda R where |
---|
[8] | 117 | labs f = R $ f |
---|
| 118 | app e1 e2 = (unR e1) e2 |
---|
[7] | 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 | |
---|
| 126 | newtype RList a = RList { unList :: (Int, Int -> a) } |
---|
[9] | 127 | instance (Show a) => Show (RList a) where |
---|
| 128 | show (RList (s,f)) = show (map f [0..s-1]) |
---|
[7] | 129 | |
---|
| 130 | instance SizeExp R where |
---|
| 131 | type List R = RList |
---|
| 132 | undef = R $ Bottom |
---|
| 133 | unsized = R $ () |
---|
[8] | 134 | list s f = R $ RList (unR s, unR . (unR f) . R ) |
---|
[9] | 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 |
---|
[7] | 137 | |
---|
[8] | 138 | -- Type level int to count arity |
---|
| 139 | data Zero |
---|
| 140 | data Succ a |
---|
[7] | 141 | |
---|
[8] | 142 | data 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 |
---|
[7] | 147 | |
---|
[8] | 148 | instance 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 |
---|
[7] | 156 | |
---|
[8] | 157 | type IntExp = Exp Zero |
---|
| 158 | data Condition = Eq IntExp IntExp | Gt IntExp IntExp | Lt IntExp IntExp |
---|
[9] | 159 | type SExp a = ([Condition], IntExp) |
---|
| 160 | newtype Compile a = Compile { unCompile :: SExp a } |
---|
[7] | 161 | |
---|
[8] | 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) |
---|