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

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

monad for observable sharing

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