1 | {-# Language GADTs, |
---|
2 | FlexibleInstances, |
---|
3 | FlexibleContexts, |
---|
4 | ScopedTypeVariables, |
---|
5 | TypeFamilies, |
---|
6 | NoMonomorphismRestriction, |
---|
7 | OverlappingInstances #-} |
---|
8 | |
---|
9 | import Data.Char |
---|
10 | import Control.Monad.Instances() |
---|
11 | |
---|
12 | data OpName = PLUS | MINUS | MUL |
---|
13 | data Bottom = Bottom |
---|
14 | deriving Show |
---|
15 | |
---|
16 | type family Arr (repr :: * -> *) (a :: *) (b :: *) :: * |
---|
17 | |
---|
18 | class Lambda l where |
---|
19 | labs :: (l a -> l b) -> l (Arr l a b) |
---|
20 | app :: l (Arr l a b) -> l a -> l b |
---|
21 | lit :: Int -> l Int |
---|
22 | op :: l Int -> OpName -> l Int -> l Int |
---|
23 | |
---|
24 | -- Required for Num |
---|
25 | instance Lambda l => Show (l a) where |
---|
26 | showsPrec _ _ = error "Error: no show" |
---|
27 | |
---|
28 | -- Required for Num |
---|
29 | instance Lambda l => Eq (l a) where |
---|
30 | (==) _ _ = error "Error: no eq" |
---|
31 | |
---|
32 | instance Lambda l => Num (l Int) where |
---|
33 | fromInteger = lit . fromIntegral |
---|
34 | lhs + rhs = op lhs PLUS rhs |
---|
35 | lhs - rhs = op lhs MINUS rhs |
---|
36 | lhs * rhs = op lhs MUL rhs |
---|
37 | abs = error "abs is not implemented" |
---|
38 | signum = error "signum is not implemented" |
---|
39 | |
---|
40 | {- Printing -} |
---|
41 | showVar x = if x>28 |
---|
42 | then showVar (x `div` 29) . showChar (chr $ ord 'a' + (x `mod` 29)) |
---|
43 | else showChar $ chr $ ord 'a' + x |
---|
44 | |
---|
45 | getPrec :: OpName -> (Int,Int,Int,Char) |
---|
46 | getPrec PLUS = (4,4,5,'+') |
---|
47 | getPrec MINUS = (4,4,5,'-') |
---|
48 | getPrec MUL = (5,5,6,'*') |
---|
49 | |
---|
50 | newtype LPrint a = LPrint { unPrint :: Int -> Int -> ShowS } |
---|
51 | type instance Arr LPrint a b = a -> b |
---|
52 | |
---|
53 | instance Lambda LPrint where |
---|
54 | lit x = LPrint $ \_ -> return $ shows x |
---|
55 | op m opc n = LPrint $ \p -> do |
---|
56 | let (prec, lprec, rprec, c) = getPrec opc |
---|
57 | l1 <- unPrint m lprec |
---|
58 | l2 <- unPrint n rprec |
---|
59 | return $ showParen (p>prec) $ l1 . showChar c . l2 |
---|
60 | app f v = LPrint $ \p -> do |
---|
61 | l1 <- unPrint f 6 |
---|
62 | l2 <- unPrint v 7 |
---|
63 | return $ showParen (p>6) $ l1 . showChar ' ' . l2 |
---|
64 | labs e = LPrint $ \p v -> let |
---|
65 | var = LPrint $ \_ -> return $ showVar v |
---|
66 | l = unPrint (e var) 0 $ succ v |
---|
67 | in showParen (p>0) $ showChar 'λ' . showVar v . showChar '.' . l |
---|
68 | |
---|
69 | instance Show (LPrint a) where |
---|
70 | showsPrec _ e = unPrint e 0 0 |
---|
71 | |
---|
72 | view :: LPrint a -> LPrint a |
---|
73 | view = id |
---|
74 | |
---|
75 | {- Evaluating -} |
---|
76 | newtype R a = R { unR :: a } |
---|
77 | type instance Arr R a b = R a -> R b |
---|
78 | |
---|
79 | instance Lambda R where |
---|
80 | labs = R |
---|
81 | app = unR |
---|
82 | lit = R |
---|
83 | op e1 op e2 = let opm = case op of |
---|
84 | PLUS -> (+) |
---|
85 | MINUS -> (-) |
---|
86 | MUL -> (*) |
---|
87 | in R $ opm (unR e1) (unR e2) |
---|
88 | |
---|
89 | newtype RList a = RList { unList :: (Int, Int -> a) } |
---|
90 | |
---|
91 | instance (Show a) => Show (RList a) where |
---|
92 | show (RList (s,f)) = show (map f [0..s-1]) |
---|
93 | |
---|
94 | eval = unR |
---|
95 | |
---|
96 | z = labs ( \s -> s + 1) `app` ( 1 + lit 2) |
---|