source: sizechecking/branches/macs/Ops.hs @ 23

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

expression

File size: 1.7 KB
Line 
1{-# LANGUAGE FlexibleInstances #-}
2
3module Ops where
4
5import qualified Data.Supply as S
6import Prelude (String, Int, ($), (.))
7import qualified Prelude
8import Lambda
9
10class (Lambda l) => LOps l where
11    infixop :: String -> Int -> (a -> b -> c) -> l a -> l b -> l c
12    infixopr :: String -> Int -> (a -> b -> c) -> l a -> l b -> l c
13    infixopl :: String -> Int -> (a -> b -> c) -> l a -> l b -> l c
14    fun :: String -> a -> l a
15
16    (+) :: l Int -> l Int -> l Int
17    (+) = infixopl "+" 6 (Prelude.+)
18
19    (-) :: l Int -> l Int -> l Int
20    (-) = infixopl "-" 6 (Prelude.-)
21
22    (*) :: l Int -> l Int -> l Int
23    (*) = infixopl "*" 7 (Prelude.*)
24
25
26instance LOps Q where
27    infixopl _ _ f lhs rhs = Q (eval lhs `f` eval rhs)
28    infixop  _ _ f lhs rhs = Q (eval lhs `f` eval rhs)
29    infixopr _ _ f lhs rhs = Q (eval lhs `f` eval rhs)
30    fun _ = Q
31
32instance LOps S where
33    fun name _ = S (\_ p -> Prelude.showsPrec p name)
34
35    infixopl name prec _ lhs rhs = S(\s p ->
36        let (s1, s2) = S.split2 s
37        in Prelude.showParen (p Prelude.> prec) $
38            unS lhs s1 prec .
39            Prelude.showString name .
40            unS rhs s2 (Prelude.succ prec)
41        )
42    infixop name prec _ lhs rhs = S(\s p ->
43        let (s1, s2) = S.split2 s
44        in Prelude.showParen (p Prelude.> prec) $
45            unS lhs s1 (Prelude.succ prec) .
46            Prelude.showString name .
47            unS rhs s2 (Prelude.succ prec)
48        )
49    infixopr name prec _ lhs rhs = S(\s p ->
50        let (s1, s2) = S.split2 s
51        in Prelude.showParen (p Prelude.> prec) $
52            unS lhs s1 (Prelude.succ prec) .
53            Prelude.showString name .
54            unS rhs s2 prec
55        )
Note: See TracBrowser for help on using the repository browser.