1 | {-# LANGUAGE TypeFamilies, MultiParamTypeClasses, FlexibleInstances, |
---|
2 | IncoherentInstances, RankNTypes, ScopedTypeVariables, |
---|
3 | FlexibleContexts,UndecidableInstances #-} |
---|
4 | |
---|
5 | module SizedExp where |
---|
6 | -- ( |
---|
7 | -- SizedExp(..), ($), unQ, prove |
---|
8 | -- ) where |
---|
9 | |
---|
10 | import Lambda as L |
---|
11 | import Constraints |
---|
12 | import Data.Supply |
---|
13 | |
---|
14 | |
---|
15 | class TS b => (Unify se a b) where |
---|
16 | unify :: (forall a b c. (TS c, Unify se a b) => c -> (Size se c -> a) -> (Size se (c -> b), d)) -> |
---|
17 | (b -> Size se b -> (Size se b, d)) -> |
---|
18 | a -> (Size se b, d) |
---|
19 | |
---|
20 | instance (SizedExp se, Unify se a b, se~se1, c1~c2, TS c2) => Unify se (Size se1 c1->a) (c2->b) where |
---|
21 | unify f g x = f undefined x |
---|
22 | |
---|
23 | instance (SizedExp se, se~se1, c1~c2, TS c2) => Unify se (Size se1 c1) c2 where |
---|
24 | unify f g x = g undefined x |
---|
25 | |
---|
26 | class SizedExp (se :: * -> *) where |
---|
27 | data Size se :: * -> * |
---|
28 | true :: Size se x |
---|
29 | known :: L -> Size se x |
---|
30 | match :: Size se [l] -> Size se r -> (Size se l -> Size se [l] -> Size se r) -> Size se r |
---|
31 | bind :: (Unify se a b) => L.L -> a -> Size se b |
---|
32 | app :: Size se (a->b) -> Size se a -> Size se b |
---|
33 | iff :: Bool -> Size se a -> Size se a -> Size se a |
---|
34 | num :: Integer -> Size se Int |
---|
35 | |
---|
36 | instance Show (Size se a) where |
---|
37 | show (==) = error "no show on Size!" |
---|
38 | instance Eq (Size se a) where |
---|
39 | (==) = undefined |
---|
40 | instance (SizedExp se) => Num (Size se Int) where |
---|
41 | fromInteger = num |
---|
42 | x + y = num 0 |
---|
43 | x * y = num 0 |
---|
44 | abs = undefined |
---|
45 | signum = undefined |
---|
46 | instance (SizedExp se) => Ord(Size se Int) where |
---|
47 | |
---|
48 | {- |
---|
49 | - Implementation of constraints |
---|
50 | -} |
---|
51 | sizeof :: Size Q a -> IO [SExp] |
---|
52 | sizeof (QSynt s) = s |
---|
53 | sizeof (QProvable l _) = return [([], l)] |
---|
54 | |
---|
55 | fresh :: TypeKind -> Supply Int -> L |
---|
56 | fresh sig var = fresh' sig [] var |
---|
57 | where |
---|
58 | fresh' U _ _ = Unsized |
---|
59 | fresh' V l var = appall (supplyValue var) l |
---|
60 | fresh' (F _ b) l var = Abs i $ fresh' b (Var i:l) v2 |
---|
61 | where |
---|
62 | (v1,v2) = split2 var |
---|
63 | i = supplyValue v1 |
---|
64 | fresh' (L a) l var = List (appall i l) (Abs j $ fresh' a (Var j:l) v3) |
---|
65 | where |
---|
66 | (v1,v2,v3) = split3 var |
---|
67 | i = supplyValue v1 |
---|
68 | j = supplyValue v2 |
---|
69 | |
---|
70 | |
---|
71 | freshvars2 :: (TS b, Unify Q (Size Q a) a) => Supply Int -> b -> Size Q a -> (Size Q a, L -> L) |
---|
72 | freshvars2 supply q exp = (exp , id) |
---|
73 | |
---|
74 | freshvars :: (TS c, Unify Q a b) => Supply Int -> c -> (Size Q c -> a) -> (Size Q (c -> b), L -> L) |
---|
75 | freshvars supply q = freshvars' (unify (freshvars s1) (freshvars2 s2)) |
---|
76 | where |
---|
77 | (s1, s2, s3) = split3 supply |
---|
78 | freshvars' :: (Unify Q a b) => (a -> (Size Q b, L -> L)) -> (Size Q c -> a) -> (Size Q (c -> b), L -> L) |
---|
79 | freshvars' u exp = (QSynt $ sizeof $ x, \l -> f $ App l fv) |
---|
80 | where |
---|
81 | (x, f) = u $ exp $ QSynt $ do |
---|
82 | putStrLn $ "[Bind] var="++(show fv)++" of type "++(show $ tk q) |
---|
83 | return [([], fv)] |
---|
84 | fv = fresh (tk q) s3 |
---|
85 | |
---|
86 | addConstraint :: Constraint -> [SExp] -> [SExp] |
---|
87 | addConstraint nc = map (\(c,l) -> (nc:c, l)) |
---|
88 | |
---|
89 | concatMapM :: (a -> IO [b]) -> [a] -> IO [b] |
---|
90 | concatMapM f l = mapM f l >>= return.concat |
---|
91 | |
---|
92 | type SExp = ([Constraint], L) |
---|
93 | newtype Q a = Q { unQ :: () } |
---|
94 | instance SizedExp Q where |
---|
95 | data Size Q a = QSynt (IO [SExp]) | QProvable L (Supply Int -> IO [Condition]) |
---|
96 | known l = QSynt $return [([], l)] |
---|
97 | true = QSynt $ return [] |
---|
98 | match l nil cons = let |
---|
99 | match1 (cond, ltype) = do |
---|
100 | x <- sizeof l |
---|
101 | putStrLn $ "ORIGINAL is " ++ (show x) |
---|
102 | putStrLn $ "[MATCH] ==> " ++ (show $ ltype) |
---|
103 | let lt = rall$ App (AAbs 18 5 $ Var 18) ltype |
---|
104 | putStrLn $ " --- NIL ---" ++ (show lt) |
---|
105 | nils <- sizeof nil |
---|
106 | putStrLn $ show nils |
---|
107 | let nilc = foldr addConstraint nils $ Zero lt:cond |
---|
108 | let tx = rall $ App (AAbs 18 5 $ App (Var 5) (Op (Var 18) '-' (Num 1))) ltype |
---|
109 | let txs = rall $App (AAbs 18 5 $ List (Op (Var 18) '-' (Num 1)) (Var 5)) ltype |
---|
110 | putStrLn $ " --- CONS --- "++(show tx)++" <-> "++(show txs) |
---|
111 | conss <- sizeof $ cons (QSynt$return [([], tx)]) (QSynt$return [([], txs)]) |
---|
112 | print conss |
---|
113 | let consc = foldr addConstraint conss $ lt `GEC` Num 1:cond |
---|
114 | print "END MATCH" |
---|
115 | print $ nilc ++ consc |
---|
116 | return $ nilc ++ consc |
---|
117 | in QSynt $ sizeof l >>= concatMapM match1 |
---|
118 | |
---|
119 | iff _ l1 l2 = QSynt $ do |
---|
120 | ll1 <- sizeof l1 |
---|
121 | ll2 <- sizeof l2 |
---|
122 | return $ ll1 ++ ll2 |
---|
123 | |
---|
124 | app l1 l2 = QSynt $ do |
---|
125 | ll1 <- sizeof l1 |
---|
126 | ll2 <- sizeof l2 |
---|
127 | return [ (c1 ++ c2, App e1 e2) | (c1,e1) <- ll1, (c2,e2) <- ll2] |
---|
128 | |
---|
129 | bind l exp = z $ \supply -> let (s1,s2) = split2 supply in unify (freshvars s1) (freshvars2 s2) exp |
---|
130 | where |
---|
131 | z :: (Supply Int -> (Size Q c, L -> L)) -> Size Q c |
---|
132 | z x = QProvable l $ \supply -> let |
---|
133 | (sexp, f) = x supply |
---|
134 | ll = rall $ f l |
---|
135 | rr (Zero a) = Zero $ rall a |
---|
136 | rr (GEC a b) = rall a `GEC` rall b |
---|
137 | rr (LTC a b) = rall a `LTC` rall b |
---|
138 | in do |
---|
139 | l3 <- sizeof sexp |
---|
140 | print l |
---|
141 | print ll |
---|
142 | return $ map (\(c,l2) -> Condition (map rr c) ll (rall l2)) l3 |
---|
143 | |
---|
144 | num n = QSynt $return [([], Unsized)] |
---|
145 | |
---|
146 | instance Num (Size Q Int) where |
---|
147 | (+) = undefined |
---|
148 | (*) = undefined |
---|
149 | abs = undefined |
---|
150 | signum = undefined |
---|
151 | fromInteger = num |
---|
152 | |
---|
153 | prove :: Size Q b -> IO (Bool) |
---|
154 | prove (QProvable l x) = do |
---|
155 | (s1,s2,s3) <- newSupply 30 (+1) >>= return.split3 |
---|
156 | c <- x s1 |
---|
157 | putStrLn "" |
---|
158 | putStrLn "------------" |
---|
159 | putStrLn "Conditions: " |
---|
160 | print c |
---|
161 | putStrLn "" |
---|
162 | putStrLn "------------" |
---|
163 | putStrLn "Equations: " |
---|
164 | x <- checkCond s2 c |
---|
165 | print x |
---|
166 | putStrLn "" |
---|
167 | putStrLn "------------" |
---|
168 | putStrLn "Solving: " |
---|
169 | y <- solve x s3 |
---|
170 | putStrLn "" |
---|
171 | if null y then do |
---|
172 | putStrLn "QED" |
---|
173 | return True |
---|
174 | else do |
---|
175 | putStrLn "------------" |
---|
176 | putStrLn "Cannot prove: " |
---|
177 | print y |
---|
178 | return False |
---|
179 | |
---|