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