]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Expr/If.hs
polish names
[haskell/symantic.git] / Language / Symantic / Expr / If.hs
1 {-# LANGUAGE DefaultSignatures #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE OverloadedStrings #-}
4 {-# LANGUAGE ScopedTypeVariables #-}
5 {-# LANGUAGE TypeFamilies #-}
6 {-# LANGUAGE TypeOperators #-}
7 -- | Expression for @if@.
8 module Language.Symantic.Expr.If where
9
10 import qualified Control.Monad as Monad
11 import Data.Monoid
12 import Data.Proxy (Proxy(..))
13 import Data.Type.Equality ((:~:)(Refl))
14
15 import Language.Symantic.Type
16 import Language.Symantic.Repr
17 import Language.Symantic.Expr.Root
18 import Language.Symantic.Expr.Error
19 import Language.Symantic.Expr.From
20 import Language.Symantic.Trans.Common
21
22 -- * Class 'Sym_If'
23 -- | Symantic.
24 class Sym_If repr where
25 if_ :: repr Bool -> repr a -> repr a -> repr a
26 default if_ :: Trans t repr => t repr Bool -> t repr a -> t repr a -> t repr a
27 if_ = trans_map3 if_
28 instance Sym_If Repr_Host where
29 if_ (Repr_Host b) ok ko = if b then ok else ko
30 instance Sym_If Repr_Text where
31 if_ (Repr_Text cond) (Repr_Text ok) (Repr_Text ko) =
32 Repr_Text $ \p v ->
33 let p' = Precedence 2 in
34 paren p p' $
35 "if " <> cond p' v <>
36 " then " <> ok p' v <>
37 " else " <> ko p' v
38
39 instance (Sym_If r1, Sym_If r2) => Sym_If (Repr_Dup r1 r2) where
40 if_ (c1 `Repr_Dup` c2) (ok1 `Repr_Dup` ok2) (ko1 `Repr_Dup` ko2) =
41 if_ c1 ok1 ko1 `Repr_Dup` if_ c2 ok2 ko2
42
43 -- * Class 'Sym_When'
44 -- | Symantic.
45 class Sym_When repr where
46 when :: repr Bool -> repr () -> repr ()
47 default when :: Trans t repr => t repr Bool -> t repr () -> t repr ()
48 when = trans_map2 when
49 instance Sym_When Repr_Host where
50 when (Repr_Host b) = Monad.when b
51 instance Sym_When Repr_Text where
52 when (Repr_Text cond) (Repr_Text ok) =
53 Repr_Text $ \p v ->
54 let p' = Precedence 2 in
55 paren p p' $
56 "when " <> cond p' v <>
57 " " <> ok p' v
58 instance (Sym_When r1, Sym_When r2) => Sym_When (Repr_Dup r1 r2) where
59 when (c1 `Repr_Dup` c2) (ok1 `Repr_Dup` ok2) =
60 when c1 ok1 `Repr_Dup` when c2 ok2
61
62 -- * Type 'Expr_If'
63 -- | Expression.
64 data Expr_If (root:: *)
65 type instance Root_of_Expr (Expr_If root) = root
66 type instance Type_of_Expr (Expr_If root) = No_Type
67 type instance Sym_of_Expr (Expr_If root) repr = (Sym_If repr)
68 type instance Error_of_Expr ast (Expr_If root) = No_Error_Expr
69
70 if_from
71 :: forall root ty ast hs ret.
72 ( ty ~ Type_Root_of_Expr (Expr_If root)
73 , Type0_Eq ty
74 , Type0_Lift Type_Bool (Type_of_Expr root)
75 , Expr_From ast root
76 , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast)
77 (Error_of_Expr ast root)
78 , Root_of_Expr root ~ root
79 ) => ast -> ast -> ast
80 -> ExprFrom ast (Expr_If root) hs ret
81 if_from ast_cond ast_ok ast_ko ex ast ctx k =
82 expr_from (Proxy::Proxy root) ast_cond ctx $
83 \(ty_cond::ty h_n) (Forall_Repr_with_Context cond) ->
84 expr_from (Proxy::Proxy root) ast_ok ctx $
85 \(ty_ok::ty h_ok) (Forall_Repr_with_Context ok) ->
86 expr_from (Proxy::Proxy root) ast_ko ctx $
87 \(ty_ko::ty h_ko) (Forall_Repr_with_Context ko) ->
88 check_type0_eq ex ast type_bool ty_cond $ \Refl ->
89 check_type0_eq ex ast ty_ok ty_ko $ \Refl ->
90 k ty_ok $ Forall_Repr_with_Context $
91 \c -> if_ (cond c) (ok c) (ko c)
92
93 -- * Type 'Expr_When'
94 -- | Expression.
95 data Expr_When (root:: *)
96 type instance Root_of_Expr (Expr_When root) = root
97 type instance Type_of_Expr (Expr_When root) = No_Type
98 type instance Sym_of_Expr (Expr_When root) repr = (Sym_When repr)
99 type instance Error_of_Expr ast (Expr_When root) = No_Error_Expr
100
101 when_from
102 :: forall root ty ast hs ret.
103 ( ty ~ Type_Root_of_Expr (Expr_When root)
104 , Type0_Eq ty
105 , Type0_Lift Type_Bool (Type_of_Expr root)
106 , Type0_Lift Type_Unit (Type_of_Expr root)
107 , Expr_From ast root
108 , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast)
109 (Error_of_Expr ast root)
110 , Root_of_Expr root ~ root
111 ) => ast -> ast
112 -> ExprFrom ast (Expr_When root) hs ret
113 when_from ast_cond ast_ok ex ast ctx k =
114 expr_from (Proxy::Proxy root) ast_cond ctx $
115 \(ty_cond::ty h_n) (Forall_Repr_with_Context cond) ->
116 expr_from (Proxy::Proxy root) ast_ok ctx $
117 \(ty_ok::ty h_ok) (Forall_Repr_with_Context ok) ->
118 check_type0_eq ex ast type_bool ty_cond $ \Refl ->
119 check_type0_eq ex ast type_unit ty_ok $ \Refl ->
120 k ty_ok $ Forall_Repr_with_Context $
121 \c -> when (cond c) (ok c)