]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Expr/If.hs
revamp Repr/*
[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_If in
34 paren p p' $
35 "if " <> cond p' v <>
36 " then " <> ok p' v <>
37 " else " <> ko p' v
38 instance
39 ( Sym_If r1
40 , Sym_If r2
41 ) => Sym_If (Dup r1 r2) where
42 if_ (c1 `Dup` c2) (ok1 `Dup` ok2) (ko1 `Dup` ko2) =
43 if_ c1 ok1 ko1 `Dup` if_ c2 ok2 ko2
44
45 -- * Class 'Sym_When'
46 -- | Symantic.
47 class Sym_When repr where
48 when :: repr Bool -> repr () -> repr ()
49 default when :: Trans t repr => t repr Bool -> t repr () -> t repr ()
50 when = trans_map2 when
51 instance Sym_When Repr_Host where
52 when (Repr_Host b) = Monad.when b
53 instance Sym_When Repr_Text where
54 when (Repr_Text cond) (Repr_Text ok) =
55 Repr_Text $ \p v ->
56 let p' = precedence_If in
57 paren p p' $
58 "when " <> cond p' v <>
59 " " <> ok p' v
60 instance
61 ( Sym_When r1
62 , Sym_When r2
63 ) => Sym_When (Dup r1 r2) where
64 when (c1 `Dup` c2) (ok1 `Dup` ok2) =
65 when c1 ok1 `Dup` when c2 ok2
66
67 -- * Type 'Expr_If'
68 -- | Expression.
69 data Expr_If (root:: *)
70 type instance Root_of_Expr (Expr_If root) = root
71 type instance Type_of_Expr (Expr_If root) = No_Type
72 type instance Sym_of_Expr (Expr_If root) repr = (Sym_If repr)
73 type instance Error_of_Expr ast (Expr_If root) = No_Error_Expr
74
75 if_from
76 :: forall root ty ast hs ret.
77 ( ty ~ Type_Root_of_Expr (Expr_If root)
78 , Eq_Type ty
79 , Lift_Type Type_Bool (Type_of_Expr root)
80 , Expr_from ast root
81 , Lift_Error_Expr (Error_Expr (Error_of_Type ast ty) ty ast)
82 (Error_of_Expr ast root)
83 , Root_of_Expr root ~ root
84 ) => ast -> ast -> ast
85 -> Expr_From ast (Expr_If root) hs ret
86 if_from ast_cond ast_ok ast_ko ex ast ctx k =
87 expr_from (Proxy::Proxy root) ast_cond ctx $
88 \(ty_cond::ty h_n) (Forall_Repr_with_Context cond) ->
89 expr_from (Proxy::Proxy root) ast_ok ctx $
90 \(ty_ok::ty h_ok) (Forall_Repr_with_Context ok) ->
91 expr_from (Proxy::Proxy root) ast_ko ctx $
92 \(ty_ko::ty h_ko) (Forall_Repr_with_Context ko) ->
93 check_eq_type ex ast type_bool ty_cond $ \Refl ->
94 check_eq_type ex ast ty_ok ty_ko $ \Refl ->
95 k ty_ok $ Forall_Repr_with_Context $
96 \c -> if_ (cond c) (ok c) (ko c)
97
98 -- * Type 'Expr_When'
99 -- | Expression.
100 data Expr_When (root:: *)
101 type instance Root_of_Expr (Expr_When root) = root
102 type instance Type_of_Expr (Expr_When root) = No_Type
103 type instance Sym_of_Expr (Expr_When root) repr = (Sym_When repr)
104 type instance Error_of_Expr ast (Expr_When root) = No_Error_Expr
105
106 when_from
107 :: forall root ty ast hs ret.
108 ( ty ~ Type_Root_of_Expr (Expr_When root)
109 , Eq_Type ty
110 , Lift_Type Type_Bool (Type_of_Expr root)
111 , Lift_Type Type_Unit (Type_of_Expr root)
112 , Expr_from ast root
113 , Lift_Error_Expr (Error_Expr (Error_of_Type ast ty) ty ast)
114 (Error_of_Expr ast root)
115 , Root_of_Expr root ~ root
116 ) => ast -> ast
117 -> Expr_From ast (Expr_When root) hs ret
118 when_from ast_cond ast_ok ex ast ctx k =
119 expr_from (Proxy::Proxy root) ast_cond ctx $
120 \(ty_cond::ty h_n) (Forall_Repr_with_Context cond) ->
121 expr_from (Proxy::Proxy root) ast_ok ctx $
122 \(ty_ok::ty h_ok) (Forall_Repr_with_Context ok) ->
123 check_eq_type ex ast type_bool ty_cond $ \Refl ->
124 check_eq_type ex ast type_unit ty_ok $ \Refl ->
125 k ty_ok $ Forall_Repr_with_Context $
126 \c -> when (cond c) (ok c)