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

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

new files

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