| 1 | {-# Language GADTs, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses, FunctionalDependencies, ScopedTypeVariables, TypeFamilies, NoMonomorphismRestriction, OverlappingInstances, IncoherentInstances #-} |
|---|
| 2 | module L where |
|---|
| 3 | |
|---|
| 4 | import qualified Data.SBV as SBV |
|---|
| 5 | import Data.Char(ord, chr) |
|---|
| 6 | import Control.Monad.State |
|---|
| 7 | --import Data.Supply |
|---|
| 8 | |
|---|
| 9 | data OpName = PLUS | MINUS | MUL |
|---|
| 10 | data Bottom = Bottom |
|---|
| 11 | deriving Show |
|---|
| 12 | |
|---|
| 13 | {- Lambda calculus without free variables -} |
|---|
| 14 | type Arr repr a b = repr a -> repr b |
|---|
| 15 | |
|---|
| 16 | class (Num (LInt l)) => Lambda l where |
|---|
| 17 | type LInt l :: * |
|---|
| 18 | labs :: (l a -> l b) -> l (Arr l a b) |
|---|
| 19 | app :: l (Arr l a b) -> l a -> l b |
|---|
| 20 | lit :: (LInt l) -> l (LInt l) |
|---|
| 21 | op :: l (LInt l) -> OpName -> l (LInt l) -> l (LInt l) |
|---|
| 22 | |
|---|
| 23 | class SizeExp l where |
|---|
| 24 | type List l :: * -> * |
|---|
| 25 | list :: l Int -> l (Arr l Int b) -> l (List l b) |
|---|
| 26 | aabs :: (l Int -> l (Arr l Int a) -> l b) -> l (Arr l (List l a) b) |
|---|
| 27 | shift :: l (Arr l Int a) -> l Int -> l (Arr l Int a) -> l (Arr l Int a) |
|---|
| 28 | undef :: l Bottom |
|---|
| 29 | unsized :: l () |
|---|
| 30 | |
|---|
| 31 | instance (Lambda l, LInt l ~ a) => Num (l a) where |
|---|
| 32 | fromInteger = lit . fromIntegral |
|---|
| 33 | lhs + rhs = op lhs PLUS rhs |
|---|
| 34 | lhs - rhs = op lhs MINUS rhs |
|---|
| 35 | lhs * rhs = op lhs MUL rhs |
|---|
| 36 | abs = error "abs is not implemented" |
|---|
| 37 | signum = error "signum is not implemented" |
|---|
| 38 | |
|---|
| 39 | {- Printing -} |
|---|
| 40 | newtype LPrint a = LPrint { unPrint :: Int -> Int -> ShowS } |
|---|
| 41 | |
|---|
| 42 | instance Lambda LPrint where |
|---|
| 43 | type LInt LPrint = Int |
|---|
| 44 | lit x = LPrint $ \_ -> return $ shows x |
|---|
| 45 | op m opc n = LPrint $ \p -> do |
|---|
| 46 | let (prec, lprec, rprec, c) = getPrec opc |
|---|
| 47 | l1 <- (unPrint m lprec) |
|---|
| 48 | l2 <- (unPrint n rprec) |
|---|
| 49 | return $ showParen (p>prec) $ l1 . showChar c . l2 |
|---|
| 50 | app f v = LPrint $ \p -> do |
|---|
| 51 | l1 <- unPrint f 6 |
|---|
| 52 | l2 <- unPrint v 7 |
|---|
| 53 | return $ showParen (p>6) $ l1 . showChar ' ' . l2 |
|---|
| 54 | labs e = LPrint $ \p v -> let |
|---|
| 55 | var = LPrint $ \_ -> return $ showVar v |
|---|
| 56 | l = unPrint (e var) 0 $ succ v |
|---|
| 57 | in showParen (p>0) $ showChar 'λ' . showVar v . showChar '.' . l |
|---|
| 58 | |
|---|
| 59 | instance SizeExp LPrint where |
|---|
| 60 | type List LPrint = [] |
|---|
| 61 | aabs f = LPrint $ \p v -> let |
|---|
| 62 | v2 = succ v |
|---|
| 63 | var1 = LPrint $ \_ _ -> showVar v |
|---|
| 64 | var2 = LPrint $ \_ _ -> showVar v2 |
|---|
| 65 | l = unPrint (f var1 var2) 0 (v+2) |
|---|
| 66 | in showParen (p>0) $ showChar 'Î' . showVar v . showChar ',' . showVar v2 . showChar '.' . l |
|---|
| 67 | list s f = LPrint $ \p -> do |
|---|
| 68 | l1 <- unPrint s 9 |
|---|
| 69 | l2 <- unPrint f 9 |
|---|
| 70 | return $ showParen (p>0) $ showString "List " . l1 . showChar ' ' . l2 |
|---|
| 71 | shift e1 s e2 = LPrint $ \p -> do |
|---|
| 72 | l1 <- unPrint e1 2 |
|---|
| 73 | l2 <- unPrint s 2 |
|---|
| 74 | l3 <- unPrint e2 2 |
|---|
| 75 | return $ showParen (p>0) $ showString "Shift " . l1 . showChar ' ' . l2 . showChar ' ' . l3 |
|---|
| 76 | undef = LPrint $ \_ -> return $ showChar 'âŽ' |
|---|
| 77 | unsized = LPrint $ \_ -> return $ showChar 'U' |
|---|
| 78 | |
|---|
| 79 | view :: LPrint a -> LPrint a |
|---|
| 80 | view = id |
|---|
| 81 | instance Show (LPrint a) where |
|---|
| 82 | showsPrec _ e = unPrint e 0 0 |
|---|
| 83 | |
|---|
| 84 | showVar x = if x>28 |
|---|
| 85 | then showVar (x `div` 29) . showChar (chr $ ord 'a' + (x `mod` 29)) |
|---|
| 86 | else showChar $ chr $ ord 'a' + x |
|---|
| 87 | |
|---|
| 88 | getPrec :: OpName -> (Int,Int,Int,Char) |
|---|
| 89 | getPrec PLUS = (4,4,5,'+') |
|---|
| 90 | getPrec MINUS = (4,4,5,'-') |
|---|
| 91 | getPrec MUL = (5,5,6,'*') |
|---|
| 92 | |
|---|
| 93 | getVar :: State Int Int |
|---|
| 94 | getVar = do { x <- get; put (x+1); return x } |
|---|
| 95 | |
|---|
| 96 | x = aabs (\s _ -> s) `app` list (lit 0) (labs $ \_ -> undef) |
|---|
| 97 | y = list 0 $ labs $ \_ -> undef |
|---|
| 98 | conss = labs $ \x -> aabs $ \ys yf -> list (ys + 1) $ shift yf ys (labs $ \_ -> x) |
|---|
| 99 | concats = aabs $ \xs xf -> (aabs $ \ys yf -> list (xs+ys) $ shift xf xs yf) |
|---|
| 100 | maps = labs $ \x -> aabs $ \ys yf -> list ys ( x `app` yf ) |
|---|
| 101 | l0 = list (lit 0) (labs $ \_ -> unsized) |
|---|
| 102 | l1 = list (lit 1) (labs $ \_ -> unsized) |
|---|
| 103 | l2 = list (lit 2) (labs $ \_ -> unsized) |
|---|
| 104 | l00 = list (lit 0) (labs $ \_ -> list (lit 0) (labs $ \_ -> unsized)) |
|---|
| 105 | l10 = list (lit 1) (labs $ \_ -> list (lit 0) (labs $ \_ -> unsized)) |
|---|
| 106 | l01 = list (lit 0) (labs $ \_ -> list (lit 1) (labs $ \_ -> unsized)) |
|---|
| 107 | l11 = list (lit 1) (labs $ \_ -> list (lit 1) (labs $ \_ -> unsized)) |
|---|
| 108 | l12 = list (lit 1) (labs $ \_ -> list (lit 2) (labs $ \_ -> unsized)) |
|---|
| 109 | |
|---|
| 110 | v = (labs $ \s -> s+1) `app` (lit 1+2) |
|---|
| 111 | w1 = (labs $ \s -> s+ lit 1) |
|---|
| 112 | w2 = (labs $ \s -> s+ lit 2) |
|---|
| 113 | q1 :: (Lambda l, a ~ LInt l, Num (l a)) => l (Arr l b (Arr l a a)) |
|---|
| 114 | q1 = (labs $ \q -> labs $ \s -> s + lit 1) |
|---|
| 115 | q2 :: (Lambda l, a ~ LInt l, Num (l a)) => l (Arr l a (Arr l a a)) |
|---|
| 116 | q2 = (labs $ \q -> labs $ \s -> s + q) |
|---|
| 117 | q3 = (labs $ \q -> labs $ \s -> q + s) |
|---|
| 118 | |
|---|
| 119 | {- Evaluating -} |
|---|
| 120 | eval = unR |
|---|
| 121 | newtype R a = R { unR :: a } |
|---|
| 122 | instance Lambda R where |
|---|
| 123 | type LInt R = Int |
|---|
| 124 | labs f = R $ f |
|---|
| 125 | app e1 e2 = (unR e1) e2 |
|---|
| 126 | lit i = R i |
|---|
| 127 | op e1 op e2 = let opm = case op of |
|---|
| 128 | PLUS -> (+) |
|---|
| 129 | MINUS -> (-) |
|---|
| 130 | MUL -> (*) |
|---|
| 131 | in R $ opm (unR e1) (unR e2) |
|---|
| 132 | |
|---|
| 133 | newtype RList a = RList { unList :: (Int, Int -> a) } |
|---|
| 134 | instance (Show a) => Show (RList a) where |
|---|
| 135 | show (RList (s,f)) = show (map f [0..s-1]) |
|---|
| 136 | |
|---|
| 137 | instance SizeExp R where |
|---|
| 138 | type List R = RList |
|---|
| 139 | undef = R $ Bottom |
|---|
| 140 | unsized = R $ () |
|---|
| 141 | list s f = R $ RList (unR s, unR . (unR f) . R ) |
|---|
| 142 | aabs e = R $ ( \(RList (s,f)) -> (e (R s) (R (R . f . unR))) ) . unR |
|---|
| 143 | shift a s c = R $ \i -> if (unR i)<(unR s) then unR a i else unR c i |
|---|
| 144 | |
|---|
| 145 | newtype E a = E { unE :: a } |
|---|
| 146 | instance Lambda E where |
|---|
| 147 | type LInt E = SBV.SInteger |
|---|
| 148 | labs f = E $ f |
|---|
| 149 | app e1 e2 = (unE e1) e2 |
|---|
| 150 | lit = E |
|---|
| 151 | op e1 op e2 = let opm = case op of |
|---|
| 152 | PLUS -> (+) |
|---|
| 153 | MINUS -> (-) |
|---|
| 154 | MUL -> (*) |
|---|
| 155 | in E $ opm (unE e1) (unE e2) |
|---|
| 156 | |
|---|
| 157 | class Sizeable' a where |
|---|
| 158 | getl' :: E (Arr E a b) -> SBV.Symbolic b |
|---|
| 159 | |
|---|
| 160 | instance Sizeable' (SBV.SInteger) where |
|---|
| 161 | getl' f = do |
|---|
| 162 | x <- SBV.sInteger "x" |
|---|
| 163 | return $ unE $ (unE f) $ E x |
|---|
| 164 | |
|---|
| 165 | {- |
|---|
| 166 | getEq f = SBV.proveWith (SBV.z3 {SBV.verbose=True}) $ do |
|---|
| 167 | x <- getl f |
|---|
| 168 | return $ x SBV..== x |
|---|
| 169 | -} |
|---|
| 170 | data ST = ST |
|---|
| 171 | |
|---|
| 172 | class Instantiateable a r | a -> r where |
|---|
| 173 | instantiate :: a -> SBV.Symbolic r |
|---|
| 174 | |
|---|
| 175 | instance Instantiateable SBV.SInteger SBV.SInteger where |
|---|
| 176 | instantiate _ = do |
|---|
| 177 | liftIO $ putStrLn " INT VARIABLE x" |
|---|
| 178 | SBV.sInteger "x" |
|---|
| 179 | |
|---|
| 180 | instance Instantiateable a ST where |
|---|
| 181 | instantiate _ = do |
|---|
| 182 | liftIO $ putStrLn " ? VARIABLE x" |
|---|
| 183 | return $ undefined -- SBV.uninterpret "f" |
|---|
| 184 | |
|---|
| 185 | class Sizeable a where |
|---|
| 186 | type Ret a :: * |
|---|
| 187 | getl :: a -> a -> SBV.Symbolic (Ret a, Ret a) |
|---|
| 188 | |
|---|
| 189 | instance (Instantiateable a r, Sizeable b) => Sizeable (Arr E a b) where |
|---|
| 190 | type Ret (Arr E a b) = Ret b |
|---|
| 191 | getl f g = do |
|---|
| 192 | liftIO $ putStrLn " -> x" |
|---|
| 193 | x <- instantiate (undefined :: a) |
|---|
| 194 | let f' = unE $ f $ E x |
|---|
| 195 | let g' = unE $ g $ E x |
|---|
| 196 | getl f' g' |
|---|
| 197 | |
|---|
| 198 | instance Sizeable (SBV.SInteger) where |
|---|
| 199 | type Ret SBV.SInteger = SBV.SInteger |
|---|
| 200 | getl f g = return (f,g) |
|---|
| 201 | |
|---|
| 202 | getEq f g = SBV.proveWith (SBV.z3 {SBV.verbose=True}) $ do |
|---|
| 203 | (x,y) <- getl (unE f) (unE g) |
|---|
| 204 | return $ x SBV..== y |
|---|