source: sizechecking/branches/macs/SizedFun.hs

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

move to separate file

File size: 1.6 KB
Line 
1{-# LANGUAGE TypeFamilies,TemplateHaskell,MultiParamTypeClasses,FlexibleContexts,FlexibleInstances,OverlappingInstances,IncoherentInstances #-}
2{-# LANGUAGE GADTs #-}
3
4module SizedFun where
5
6import Lambda
7import Size
8import Exp
9import Ops
10
11import qualified Data.Supply as S
12import Data.Lens.Light
13import Control.Monad.IO.Class
14
15
16class Infer a b where
17instance (Infer a b, Infer p q) => Infer (a->p) (b->q)
18instance Infer a b => Infer [a] [b]
19instance a~b => Infer a b
20instance Infer Unsized Int
21
22class (Exp e, Size (SizeExp e)) => SizedFun e where
23  type SizeExp e :: * -> *
24  bind :: Infer a b => String -> SizeExp e a -> e b -> e b
25
26class SContext s => SBContext s where
27    bound :: Lens s Bool
28
29instance SBContext s => SizedFun (S s) where
30  type SizeExp (S s) = S s
31  bind name size exp = S $ \ctxo -> if getL bound ctxo then
32      showString name
33      else let (s1, s2) = S.split2 (getL supply ctxo)
34               ctx = setL bound True ctxo
35      in showString name . showString " :: " . unS size (updateCtx s1 0 ctx) . showChar '\n'.
36         showString name . showString " = "  . unS exp (updateCtx s2 0 ctx) 
37
38data SBData = SBData { _getSBDataSupply :: S.Supply Int, _getSBDataPrec :: Int, _getSBDataBound :: Bool }
39$(makeLens ''SBData)
40
41instance SContext SBData where
42    supply = getSBDataSupply
43    prec = getSBDataPrec
44
45instance SBContext SBData where
46    bound = getSBDataBound
47
48astf :: S SBData a -> IO ShowS
49astf a = do
50    s <- S.newSupply 0 (Prelude.+1)
51    return $ unS a $ SBData s 0 False
52
53printFun :: S SBData a -> IO ()
54printFun l = astf l >>= (\s -> putStrLn $ s "")
55
56instance SizedFun Q where
57    type SizeExp Q = S SData
58    bind name size exp = exp
Note: See TracBrowser for help on using the repository browser.