source: sizechecking/Examples.hs @ 17

Last change on this file since 17 was 17, checked in by gobi, 12 years ago

copyu

File size: 10.4 KB
Line 
1--
2-- Copyright (C) 2012 Attila Gobi - http://kp.elte.hu/sizechecking
3--
4
5{-# LANGUAGE ScopedTypeVariables, ExistentialQuantification, Rank2Types #-}
6module Examples where
7
8import Lambda
9import SizedExp
10import Constraints()
11import Prelude ( ($), (+), (-), Int, (==), (*), (<), (>), (<=), (>=), (/=) )
12import qualified Prelude as P
13import qualified Control.Monad as M
14import qualified Data.List as List
15
16head :: (SizedExp se ) => Size se ([l] -> l)
17head = bind headc body
18    where 
19    body l = match l true P.const
20
21tail :: (SizedExp se ) => Size se ([l] -> [l])
22tail = bind tailc body
23    where body l = match l true (\_ xs -> xs)
24
25cons :: (SizedExp se) => Size se (x -> [x] -> [x])
26cons = bind conss true
27
28t3 :: (SizedExp se) => Size se ( (a -> a) -> a -> a )
29t3 = bind t3s body
30    where body f x = f `app` (f `app` (f `app` x))
31
32nil :: (SizedExp se) => Size se [x]
33nil  = bind nils true
34
35map :: (SizedExp se)  => Size se ( (a->b) -> [a] -> [b] )
36map = bind smap body
37    where body f l = match l nil
38            ( \x xs ->  cons `app` (f `app` x) `app` (map `app` f `app` xs ))
39
40heads :: (SizedExp se) => Size se ( [[a]] -> [a] )
41heads = bind sheads $ \l ->  map `app` head `app` l
42
43tails :: (SizedExp se) => Size se ( [[a]] -> [[a]] )
44tails = bind stails $ \l ->  map `app` tail `app` l
45
46append :: (SizedExp se) => Size se ([a] -> [a] -> [a])
47append = bind appends body
48    where body l1 l2 = match l1 l2
49            (\x xs -> cons `app` x `app` (append `app` xs `app` l2))
50
51t27 :: (SizedExp se) => Size se ((a -> a) -> a -> a)
52t27 = bind (App t3s t3s) $ t3 `app` t3
53
54t27_ :: (SizedExp se) => Size se ((a -> a) -> a -> a)
55t27_ = bind (App t3s t3s) $ 
56        \f ->  t3 `app` t3 `app` f
57
58t27__ :: (SizedExp se) => Size se ((a -> a) -> a -> a)
59t27__ = bind (App t3s t3s) $ \f x ->
60            t3 `app` t3 `app` f `app` x
61
62pam :: (SizedExp se) => Size se ([a -> b] -> a -> [b])
63pam = bind (AAbs 1 2 $ Abs 3 $ List (Var 1) (Abs 4 $ App (App (Var 2) (Var 4)) (Var 3))) $ \fl x -> match fl nil
64    (\f fs -> cons `app` (f `app` x) `app` (pam `app` fs `app` x))
65
66reverse :: (SizedExp se) => Size se([a] -> [a])
67reverse = bind reverses $ \l -> match l
68                nil
69            (
70                \x xs -> append `app` (reverse `app` xs) `app` (cons `app` x `app` nil)
71            )
72
73addone :: (SizedExp se) => Size se ([P.Int] -> [P.Int])
74addone = bind addones $ \l -> cons `app` 1 `app` l
75
76add3 :: (SizedExp se) => Size se ([P.Int] -> [P.Int])
77add3 = bind (AAbs 0 1 $ List (Op (Var 0) '+' (Num 3)) (Var 1)) $
78        \l -> t3 `app` addone `app` l
79
80add3_ :: (SizedExp se) => Size se ([P.Int] -> [P.Int])
81add3_ = bind (AAbs 0 1 $ List (Op (Var 0) '+' (Num 3)) (Var 1)) $
82        t3 `app` addone
83
84t9_ :: (SizedExp se) => Size se ((a -> a) -> a -> a)
85t9_ = bind ( Abs 0 $ App t3s (App t3s (Var 0))) $
86        \f -> t3 `app` (t3 `app` f)
87
88t9 :: (SizedExp se) => Size se ((a -> a) -> a -> a)
89t9 = bind ( Abs 0 $ App t3s (App t3s (Var 0))) $
90        \f x -> t3 `app` (t3 `app` f) `app` x
91
92add27s :: L
93add27s = AAbs 0 1 $ List (Op (Var 0) '+' (Num 27)) (Abs 2 Unsized)
94add27 :: (SizedExp se) => Size se ([P.Int] -> [P.Int])
95add27 = bind add27s $ \x ->  t27 `app` addone `app` x
96
97
98zipWiths :: L
99zipWiths = let q = App (Var 4) $ Op (Op (Var 5) '+' (Var 3)) '-' (Var 1)  in
100    (Abs 0 $ AAbs 1 2 $ AAbs 3 4 $ List (Var 1) (Abs 5 $ App (App (Var 0) (App (Var 2) (Var 5))) q ))
101zipWith :: (SizedExp se) => Size se ((a2 -> a1 -> a) -> [a2] -> [a1] -> [a])
102zipWith = bind zipWiths $ \f l1 l2 ->
103        match l1
104            nil
105        (
106            \x xs -> match l2
107                true
108            (
109                \y ys -> cons `app` (f `app` x `app` y) `app` (zipWith `app` f `app` xs `app` ys)
110            )
111        )
112appAll :: (SizedExp se) => Size se ( [a -> b] -> a -> [b] )
113appAll = bind (AAbs 0 1 $ Abs 2 $ List (Var 0) (Abs 3 $ Var 1 `App` Var 3 `App` Var 2 ) ) $ \fl x -> match fl
114            nil
115        (
116            \f fs -> cons `app` (f `app` x) `app` (appAll `app` fs `app` x)
117        )
118
119conspack :: (SizedExp se) => Size se (P.Int -> [P.Int] -> [P.Int])
120conspack = bind (Abs 0 $ AAbs 1 2 $ List (Op (Var 1) '+' (Num 1)) (Abs 3 Unsized)) $ \x l ->
121    match l (cons `app` x `app` l) 
122    (\hd tl -> iff (x == hd) (
123            cons `app` x `app` l
124        ) (
125            cons `app` hd `app` (conspack `app` x `app` tl)
126        )
127    )
128
129cprod :: (SizedExp se) => Size se ([P.Int] -> [P.Int] -> [[P.Int]])
130cprod = known  (AAbs 0 1 $ AAbs 2 3 $ List (Op (Var 0) '*' (Var 2)) $ Abs 4 $ List (Num 2) $ Abs 5 Unsized) 
131
132sqdiff :: SizedExp se => Size se ([Int] -> [Int] -> [[Int]])
133sqdiff = bind (let sq l = Op l '*' l in AAbs 0 1 $ AAbs 2 3 $ List (sq $ Op (Var 0) '-' (Var 2)) $ Abs 4 $ List (Num 2) $ Abs 5 Unsized) $
134    \l1 l2 -> match l1 (cprod `app` l2 `app` l2)
135        (\_ tl1 -> match l2 (cprod `app` l1 `app` l1)
136            (\_ tl2 -> sqdiff `app` tl1 `app` tl2))
137
138replace :: SizedExp se => Size se (Int -> [Int] -> [Int])
139replace = bind (Abs 0 $ AAbs 1 2 $ List (Var 1) (Abs 3 Unsized)) $
140    \x l -> match l nil (\hd tl -> cons `app` (x+hd) `app` tl)
141
142scalarProd :: (SizedExp se0) =>  Size se0 ([Int] -> [Int] -> [Int])
143scalarProd = bind (AAbs 0 1 $ AAbs 2 3 $ List (Num 1) (Abs 4  Unsized)) $ 
144    \l1 l2 -> match l1 (
145        match l2 ( cons `app` 0 `app` nil ) 
146            (\_ _ -> true)
147    ) ( \hd1 tl1 ->
148        match l2 true
149            ( \hd2 tl2 -> replace `app` (hd1 * hd2) `app` (scalarProd `app` tl1 `app` tl2) )
150    )
151
152mlist :: SizedExp se => Size se (a -> [a -> x] -> [x])
153mlist = bind (Abs 0 $ AAbs 1 2 $ List (Var 1) (Abs 3 $ Var 2 `App` Var 3 `App` Var 0)) 
154    $ \x l -> match l nil (\f fs -> cons `app` (f `app` x) `app` (mlist `app` x `app` fs))
155
156strange :: (SizedExp se) => Size se ([Int] -> [Int])
157strange = bind (AAbs 0 1 $ List (Num 2) (Abs 2 Unsized)) $ \l1 ->
158    let b = match l1 nil (\x1 l2 -> match l2 nil (\x2 l3 ->  cons `app` x2 `app` (cons `app` x1 `app` nil)))
159    in match b (cons `app` 0 `app` (cons `app` 0 `app` nil)) (\x xs -> b)
160
161
162take4 :: SizedExp se => Size se (([a] -> [a]) -> [[a]])
163take4 = bind (Abs 0 $ List (Num 1) (Abs 2 (Var 0 `App` (Var 0 `App` List (Num 0) (Abs 1 Bottom))))) $
164    \f ->cons `app` (f `app` (f `app` nil) ) `app` nil
165
166
167merge :: SizedExp se => Size se ([Int] -> [Int] -> [Int])
168merge = bind (AAbs 0 1 $ AAbs 2 3 $ List (Op (Var 0) '+' (Var 2)) (Abs 4 Unsized))$
169    \l1 l2 -> match l1 l2 (
170        \x xs -> match l2 l1 (
171                \y ys -> iff (x>y) (cons `app` x `app` (merge `app` xs `app` l2))
172                                  (cons `app` y `app` (merge `app` l1 `app` ys))
173            )
174        )
175
176split1 :: SizedExp se => Size se ([Int] -> [Int])
177split1 = bind (AAbs 0 1 $ List (Op (Op (Var 0) '+' (Num 1))'/' (Num 2)) (Abs 2 Unsized))  $
178    \z -> match z nil (\y ys -> cons `app` y `app` (split2 `app` ys))
179
180split2 :: SizedExp se => Size se ([Int] -> [Int])
181split2 = bind (AAbs 0 1 $ List (Op (Var 0) '/' (Num 2)) (Abs 2 Unsized)) $
182    \z -> match z nil (\y ys -> split1 `app` ys)
183
184ms = AAbs 0 1 $ List (Var 0) (Abs 4 Unsized)
185mergesort :: SizedExp se => Size se ([Int] -> [Int])
186mergesort = bind ms $
187    \l -> match l nil (\x xs ->
188        merge `app` (mergesort `app` (split1 `app` l)) `app` (mergesort `app` (split2 `app` l))
189    )
190
191last :: SizedExp se => Size se ([a] -> a)
192last = bind (AAbs 0 1 $ App (Var 1) (Num 0)) $
193    \l -> match l true (\x xs -> match xs x (\_ _ -> last `app` xs))
194
195charm :: SizedExp se => Size se (([a] -> [a]) -> a)
196charm = bind (Abs 0 $ App (AAbs 2 3 $ App (Var 3) (Num 0)) (App (Var 0) (List (Num 0) $ Abs 1 Bottom))) $
197    \ f -> last `app` (f `app` nil)
198
199fix :: SizedExp se => Size se ((a -> a) -> a)
200fix = bind (Abs 2 $ App yComb (Var 2)) $ 
201    \f -> f `app` (fix `app` f)
202
203transpose :: SizedExp se => Size se ([[a]] -> [[a]])
204transpose = bind transposec $ \l -> match l true $
205    \l1 xss -> match l1 true $
206        \x xs -> cons `app` (cons `app` x `app` (heads `app` xss))
207            `app` (transpose `app` (cons `app` xs `app` (tails `app` xss)))
208transposec = AAbs 18 5 $ List len fun
209    where
210    len = AAbs 19 6 (Var 19) `App` (Var 5 `App` Num 0)
211    fun = Abs 8 $ List (Var 18) (Abs 9 $ AAbs 19 6 (Var 6 `App` Var 8) `App` (Var 5 `App` Var 9))
212
213comps = Abs 2 $ Abs 3 $ Abs 4 $ App (Var 2) (App (Var 3) (Var 4))
214comp :: (SizedExp se)  => Size se ( (b->c) -> (a->b) -> a->c )
215comp = bind comps $ \f g x -> f `app` (g `app` x)
216
217test1s = Abs 2 $ AAbs 19 6 $ Var 2 `App` List (Var 19) (Var 6)
218test1 :: (SizedExp se)  => Size se (([a] -> [b]) -> [a] -> [b])
219test1 = bind test1s $ \f l -> match (f `app` l) nil (\x xs -> f `app` l)
220
221
222test2s = Abs 2 $ AAbs 18 5  $ appends `App` (Var 2 `App` List (Var 18) (Var 5)) `App`
223  (appends `App` (Var 2 `App` List (Var 18) (Var 5)) `App` List (Var 18) (Var 5))
224test2 :: (SizedExp se)  => Size se (([a] -> [a]) -> [a] -> [a])
225test2 = bind test2s $ \f l -> append `app` (f `app` l) `app` (append `app` (f `app` l) `app` l)
226
227data TestCase = forall a . TestCase P.String (forall se. SizedExp se => Size se a)
228
229tests :: [TestCase]
230tests = [
231          TestCase "append" append
232        , TestCase "reverse" reverse
233        , TestCase "heads" heads
234        , TestCase "map" map
235        , TestCase "pam" pam
236        , TestCase "head" head
237        , TestCase "tail" tail
238        , TestCase "t3" t3
239        , TestCase "t9" t9
240--        , TestCase "t9_" t9_  -- too few arguments in definition
241--        , TestCase "t27" t27
242--        , TestCase "t27_" t27_
243        , TestCase "t27__" t27__
244        , TestCase "addone" addone
245        , TestCase "add3" add3
246--        , TestCase "add3_" add3_ -- too few arguments in definition
247        , TestCase "add27" add27
248        , TestCase "zipWith" zipWith
249        , TestCase "appAll" appAll
250        , TestCase "conspack" conspack
251        , TestCase "scalarProd" scalarProd
252        , TestCase "sqdiff" sqdiff
253        , TestCase "mlist" mlist
254        , TestCase "strange" strange
255        , TestCase "take4" take4
256        , TestCase "charm" charm
257        , TestCase "comp" comp
258        , TestCase "merge" merge
259        , TestCase "split1" split1
260        , TestCase "split2" split2
261        , TestCase "mergesort" mergesort
262    ]
263
264runTests = do
265    failed <- M.forM tests $ \(TestCase name test) -> do
266        P.print " +++++++++++++++++++++++++++++++"
267        P.print $ " +  Proving " P.++ name
268        P.print " +++++++++++++++++++++++++++++++"
269
270        s <- prove test
271        M.return [name | P.not s]
272
273    let f = P.concat failed
274    if List.null f then 
275        P.putStrLn "All ok."
276      else do
277        P.putStr "\n\nFailed test cases: "
278        P.putStrLn $ List.intercalate ", " f
279
Note: See TracBrowser for help on using the repository browser.