source: sizechecking/branches/macs/Size.hs

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

cleanup

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
21instance SContext s => Size (S s) where
22    unsized = S $ \_ -> showChar 'U'
23    bottom = S $ \_ -> showChar '┮'
24    list size sexp = S $ \ctx ->
25        let (s1, s2) = S.split2 (getL supply ctx)
26            p = getL prec ctx
27        in showParen (p>0) $
28            showString "List " .
29            unS size (updateCtx s1 9 ctx) .
30            showChar ' ' .
31            unS sexp (updateCtx s2 9 ctx)
32    slam f = S $ \ctx ->
33        let (s1, s2, s3) = S.split3 (getL supply ctx)
34            v1           = S.supplyValue s1
35            showV1       = S $ \_ -> showVar v1
36            v2           = S.supplyValue s2
37            showV2       = S $ \_ -> showVar v2
38            p = getL prec ctx
39        in showParen (p>0) $
40            showChar 'Λ' .
41            showVar v1 .
42            showChar ',' .
43            showVar v2 .
44            showChar '.' .
45            unS (f showV1 showV2) (updateCtx s3 0 ctx)
46    shift e1 ss e2 = S $ \ctx ->
47        let (s1, s2, s3) = S.split3 (getL supply ctx)
48            p = getL prec ctx
49        in showParen (p>0)
50        $ showString "Shift "
51        . unS e1 (updateCtx s1 2 ctx)
52        . showChar ' '
53        . unS ss (updateCtx s2 2 ctx)
54        . showChar ' '
55        . unS e2 (updateCtx s3 2 ctx)
56
Note: See TracBrowser for help on using the repository browser.