source: sizechecking/branches/macs/Lambda.hs @ 21

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

lint and cleanup

File size: 1.4 KB
Line 
1{-# LANGUAGE FlexibleContexts,FlexibleInstances #-}
2module Lambda where
3
4import qualified Data.Supply as S
5import qualified Data.Char as C
6
7{-
8 - Lambda calculus beagyazas
9 -}
10class Lambda l where
11    lam   :: (l a -> l b) -> l (a -> b)
12    app   :: l (a -> b) -> l a -> l b
13    const :: Int -> l Int
14
15
16{-
17 - eval interpreter
18 -}
19newtype Q a = Q { unQ :: a }
20instance Lambda Q where
21    const = Q
22    lam a = Q (unQ.a.Q)
23    app a b = Q $ unQ a (unQ b)
24
25eval :: Q a -> a
26eval = unQ
27
28{-
29 - show interpreter
30 -}
31showVar :: Int -> String -> String
32showVar x = if x>28 
33    then showVar (x `div` 29) . showChar (C.chr $ C.ord 'a' + (x `mod` 29))
34    else showChar $ C.chr $ C.ord 'a' + x
35
36-- unS :: Value supply -> Precedence -> ShowS
37newtype S a = S { unS :: S.Supply Int -> Int -> ShowS }
38
39instance Lambda S where
40    const a = S (\_ p -> showsPrec p a)
41    app (S fun) (S arg) = S (\s p -> 
42        let (s1, s2) = S.split2 s
43        in showParen (p>6) $ fun s1 6 . showChar ' ' . arg s2 7)
44    lam fun = S (\s p -> 
45        let (s1, s2) = S.split2 s
46            v        = S.supplyValue s1
47            showV = S $ \_ _ -> showVar v
48        in showParen (p>0) $ showChar 'λ' . showVar v . showChar '.' . unS (fun showV) s2 0)
49
50ast :: S a -> IO ShowS
51ast a = do
52    s <- S.newSupply 0 (+1)
53    return $ unS a s 0
54
55printAst :: S a -> IO ()
56printAst l = ast l >>= (\s -> putStrLn $ s "")
Note: See TracBrowser for help on using the repository browser.