source: sizechecking/branches/macs/Size.hs @ 27

Last change on this file since 27 was 27, checked in by gobi, 11 years ago

new files

File size: 1.7 KB
Line 
1{-# LANGUAGE TypeFamilies #-}
2{-# LANGUAGE MultiParamTypeClasses #-}
3{-# LANGUAGE FlexibleInstances #-}
4
5module Size where
6
7import Lambda
8import Ops
9import Data.Supply as S
10import Data.Lens.Light
11
12data Unsized
13
14class (LOps l) => Size l where
15    list :: l Int -> l (Int -> a) -> l [a]
16    slam :: (l Int -> l (Int -> a) -> l b) -> l ([a] -> b)
17    shift :: l (Int -> a) -> l Int -> l (Int -> a) -> l (Int -> a)
18    unsized :: l Unsized
19    bottom :: l a
20
21
22instance SContext s => Size (S s) where
23    unsized = S $ \_ -> showChar 'U'
24    bottom = S $ \_ -> showChar '┮'
25    list size sexp = S $ \ctx ->
26        let (s1, s2) = S.split2 (getL supply ctx)
27            p = getL prec ctx
28        in showParen (p>0) $
29            showString "List " .
30            unS size (updateCtx s1 9 ctx) .
31            showChar ' ' .
32            unS sexp (updateCtx s2 9 ctx)
33    slam f = S $ \ctx ->
34        let (s1, s2, s3) = S.split3 (getL supply ctx)
35            v1           = S.supplyValue s1
36            showV1       = S $ \_ -> showVar v1
37            v2           = S.supplyValue s2
38            showV2       = S $ \_ -> showVar v2
39            p = getL prec ctx
40        in showParen (p>0) $
41            showChar 'Λ' .
42            showVar v1 .
43            showChar ',' .
44            showVar v2 .
45            showChar '.' .
46            unS (f showV1 showV2) (updateCtx s3 0 ctx)
47    shift e1 ss e2 = S $ \ctx ->
48        let (s1, s2, s3) = S.split3 (getL supply ctx)
49            p = getL prec ctx
50        in showParen (p>0)
51        $ showString "Shift "
52        . unS e1 (updateCtx s1 2 ctx)
53        . showChar ' '
54        . unS ss (updateCtx s2 2 ctx)
55        . showChar ' '
56        . unS e2 (updateCtx s3 2 ctx)
57
Note: See TracBrowser for help on using the repository browser.