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