]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Expr/Bool.hs
Eq, Ord
[haskell/symantic.git] / Language / Symantic / Expr / Bool.hs
1 {-# LANGUAGE DefaultSignatures #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE OverloadedStrings #-}
4 {-# LANGUAGE ScopedTypeVariables #-}
5 {-# LANGUAGE TypeFamilies #-}
6 {-# LANGUAGE TypeOperators #-}
7 -- | Expression for 'Bool'.
8 module Language.Symantic.Expr.Bool where
9
10 import Control.Monad
11 import qualified Data.Bool as Bool
12 import Data.Monoid
13 import qualified Data.Text as Text
14 import Prelude hiding ((&&), not, (||))
15
16 import Language.Symantic.Type
17 import Language.Symantic.Repr
18 import Language.Symantic.Expr.Root
19 import Language.Symantic.Expr.Error
20 import Language.Symantic.Expr.From
21 import Language.Symantic.Trans.Common
22
23 -- * Class 'Sym_Bool'
24 -- | Symantic.
25 class Sym_Bool repr where
26 bool :: Bool -> repr Bool
27 not :: repr Bool -> repr Bool
28 (&&) :: repr Bool -> repr Bool -> repr Bool
29 (||) :: repr Bool -> repr Bool -> repr Bool
30 xor :: repr Bool -> repr Bool -> repr Bool
31 xor x y = (x || y) && not (x && y)
32
33 default bool :: Trans t repr => Bool -> t repr Bool
34 default not :: Trans t repr => t repr Bool -> t repr Bool
35 default (&&) :: Trans t repr => t repr Bool -> t repr Bool -> t repr Bool
36 default (||) :: Trans t repr => t repr Bool -> t repr Bool -> t repr Bool
37
38 bool = trans_lift . bool
39 not = trans_map1 not
40 (&&) = trans_map2 (&&)
41 (||) = trans_map2 (||)
42
43 infixr 2 ||
44 infixr 2 `xor`
45 infixr 3 &&
46
47 instance Sym_Bool Repr_Host where
48 bool = Repr_Host
49 not = liftM Bool.not
50 (&&) = liftM2 (Bool.&&)
51 (||) = liftM2 (Bool.||)
52 instance Sym_Bool Repr_Text where
53 bool a = Repr_Text $ \_p _v ->
54 Text.pack (show a)
55 not (Repr_Text x) =
56 Repr_Text $ \p v ->
57 let p' = Precedence 9 in
58 paren p p' $ "not " <> x p' v
59 (&&) = repr_text_infix "&&" (Precedence 6)
60 (||) = repr_text_infix "||" (Precedence 5)
61 xor = repr_text_infix "`xor`" (Precedence 5)
62 instance
63 ( Sym_Bool r1
64 , Sym_Bool r2
65 ) => Sym_Bool (Dup r1 r2) where
66 bool x = bool x `Dup` bool x
67 not (x1 `Dup` x2) = not x1 `Dup` not x2
68 (&&) (x1 `Dup` x2) (y1 `Dup` y2) = (&&) x1 y1 `Dup` (&&) x2 y2
69 (||) (x1 `Dup` x2) (y1 `Dup` y2) = (||) x1 y1 `Dup` (||) x2 y2
70 xor (x1 `Dup` x2) (y1 `Dup` y2) = xor x1 y1 `Dup` xor x2 y2
71
72 -- * Type 'Expr_Bool'
73 -- | Expression.
74 data Expr_Bool (root:: *)
75 type instance Root_of_Expr (Expr_Bool root) = root
76 type instance Type_of_Expr (Expr_Bool root) = Type_Bool
77 type instance Sym_of_Expr (Expr_Bool root) repr = Sym_Bool repr
78 type instance Error_of_Expr ast (Expr_Bool root) = No_Error_Expr