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

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

new files

File size: 1.8 KB
RevLine 
[22]1module Exp where
2
[23]3import Lambda
4import Ops
5import Data.Supply as S
[27]6import Data.Lens.Light
[22]7
[23]8class LOps l => Exp l where
[22]9    nil :: l [a]
10    cons :: l a -> l [a] -> l [a]
[23]11    cons = infixopr ":" 5 (:)
12    match :: l [a] -> l b -> (l a -> l [a] -> l b) -> l b
13    cond :: l Bool -> l a -> l a -> l a
14    undefined :: l a
15
16instance Exp Q where
17    nil = Q []
18    cons x xs = Q ( unQ x : unQ xs )
19    match l nbranch cbranch = case unQ l of
20        [] -> nbranch
21        (x:xs) -> cbranch (Q x) (Q xs)
22    cond c tbranch fbranch = if unQ c then tbranch else fbranch
23    undefined = Prelude.undefined
[27]24
25instance SContext s => Exp (S s) where
26    nil = S $ \_ -> showString "[]"
27    undefined = S $ \_ -> showString "undefined"
28    match list nbranch cbranch = S $ \ctx ->
29        let (s1, s2, ss) = S.split3 (getL supply ctx)
[23]30            (s3, s4, s5) = S.split3 ss
31            v1           = S.supplyValue s4
[27]32            showV1       = S $ \_ -> showVar v1
[23]33            v2           = S.supplyValue s5
[27]34            showV2       = S $ \_ -> showVar v2
35            p = getL prec ctx
[23]36        in showParen (p>0) $ 
37            showString "case ".
[27]38            unS list (updateCtx s1 0 ctx) .
[23]39            showString " of [] => ".
[27]40            unS nbranch (updateCtx s2 0 ctx) .
[23]41            showString "; (" .  showVar v1 . showChar ':' . showVar v2 . showString ") => " .
[27]42            unS (cbranch showV1 showV2) (updateCtx s3 0 ctx)
43    cond c tbranch fbranch = S $ \ctx ->
44        let (s1, s2, s3) = S.split3 (getL supply ctx)
45            p = getL prec ctx
[24]46        in showParen (p>0) $ 
47            showString "if ".
[27]48            unS c (updateCtx s1 0 ctx).
[24]49            showString " then " .
[27]50            unS tbranch (updateCtx s2 0 ctx).
[24]51            showString " else " .
[27]52            unS fbranch (updateCtx s3 0 ctx)
Note: See TracBrowser for help on using the repository browser.