]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Expr/List.hs
init
[haskell/symantic.git] / Language / Symantic / Expr / List.hs
1 {-# LANGUAGE DefaultSignatures #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE FlexibleInstances #-}
4 {-# LANGUAGE MultiParamTypeClasses #-}
5 {-# LANGUAGE ScopedTypeVariables #-}
6 {-# LANGUAGE TypeFamilies #-}
7 {-# LANGUAGE TypeOperators #-}
8 {-# OPTIONS_GHC -fno-warn-orphans #-}
9 -- | Expression for 'List'.
10 module Language.Symantic.Expr.List where
11
12 import Data.Proxy (Proxy(..))
13 import Data.Type.Equality ((:~:)(Refl))
14
15 import Language.Symantic.Type
16 import Language.Symantic.Repr.Dup
17 import Language.Symantic.Trans.Common
18 import Language.Symantic.Expr.Common
19 import Language.Symantic.Expr.Lambda
20 import Language.Symantic.Expr.Functor
21
22 -- * Class 'Sym_List_Lam'
23 -- | Symantic.
24 class Sym_List repr where
25 list_empty :: repr [a]
26 list_cons :: repr a -> repr [a] -> repr [a]
27 list :: [repr a] -> repr [a]
28
29 default list_empty :: Trans t repr => t repr [a]
30 default list_cons :: Trans t repr => t repr a -> t repr [a] -> t repr [a]
31 default list :: Trans t repr => [t repr a] -> t repr [a]
32 list_empty = trans_lift list_empty
33 list_cons = trans_map2 list_cons
34 list l = trans_lift $ list (trans_apply <$> l)
35 -- | Symantic requiring a 'Lambda'.
36 class Sym_List_Lam lam repr where
37 list_filter
38 :: repr (Lambda lam a Bool)
39 -> repr [a]
40 -> repr [a]
41
42 default list_filter
43 :: Trans t repr
44 => t repr (Lambda lam a Bool)
45 -> t repr [a]
46 -> t repr [a]
47 list_filter = trans_map2 list_filter
48
49 instance -- Sym_List Dup
50 ( Sym_List r1
51 , Sym_List r2
52 ) => Sym_List (Dup r1 r2) where
53 list_empty = list_empty `Dup` list_empty
54 list_cons (a1 `Dup` a2) (l1 `Dup` l2) = list_cons a1 l1 `Dup` list_cons a2 l2
55 list l =
56 let (l1, l2) =
57 foldr (\(x1 `Dup` x2) (xs1, xs2) ->
58 (x1:xs1, x2:xs2)) ([], []) l in
59 list l1 `Dup` list l2
60 instance -- Sym_List_Lam Dup
61 ( Sym_List_Lam lam r1
62 , Sym_List_Lam lam r2
63 ) => Sym_List_Lam lam (Dup r1 r2) where
64 list_filter (f1 `Dup` f2) (l1 `Dup` l2) =
65 list_filter f1 l1 `Dup` list_filter f2 l2
66
67 -- * Type 'Expr_List'
68 -- | Expression.
69 data Expr_List (lam:: * -> *) (root:: *)
70 type instance Root_of_Expr (Expr_List lam root) = root
71 type instance Type_of_Expr (Expr_List lam root) = Type_List
72 type instance Sym_of_Expr (Expr_List lam root) repr = (Sym_List repr, Sym_List_Lam lam repr)
73 type instance Error_of_Expr ast (Expr_List lam root) = No_Error_Expr
74
75 instance Constraint1_Type Functor_with_Lambda (Type_Type1 [] root) where
76 constraint1_type _c (Type_Type1 _ _) = Just Dict
77
78 -- | Parsing utility to check that the given type is a 'Type_List'
79 -- or raise 'Error_Expr_Type_mismatch'.
80 check_type_list
81 :: forall ast ex root ty h ret.
82 ( root ~ Root_of_Expr ex
83 , ty ~ Type_Root_of_Expr ex
84 , Type_Lift Type_List (Type_of_Expr root)
85 , Type_Unlift Type_List (Type_of_Expr root)
86 , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast)
87 (Error_of_Expr ast root)
88 )
89 => Proxy ex -> ast -> ty h
90 -> (Type_List ty h -> Either (Error_of_Expr ast root) ret)
91 -> Either (Error_of_Expr ast root) ret
92 check_type_list ex ast ty k =
93 case type_unlift $ unType_Root ty of
94 Just ty_l -> k ty_l
95 Nothing -> Left $
96 error_expr ex $
97 Error_Expr_Type_mismatch ast
98 (Exists_Type (type_list $ type_var SZero
99 :: Type_Root_of_Expr ex [Zero]))
100 (Exists_Type ty)
101
102 -- | Parse 'list_empty'.
103 list_empty_from
104 :: forall root lam ty ty_root ast hs ret.
105 ( ty ~ Type_Root_of_Expr (Expr_List lam root)
106 , ty_root ~ Type_Root_of_Expr root
107 , Type_from ast ty_root
108 , Type_Root_Lift Type_List ty_root
109 , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast)
110 (Error_of_Expr ast root)
111 , Root_of_Expr root ~ root
112 ) => ast
113 -> Expr_From ast (Expr_List lam root) hs ret
114 list_empty_from ast_ty_a ex ast _ctx k =
115 case type_from (Proxy::Proxy ty_root)
116 ast_ty_a (Right . Exists_Type) of
117 Left err -> Left $ error_expr ex $ Error_Expr_Type err ast
118 Right (Exists_Type ty_a) ->
119 k (type_list ty_a) $ Forall_Repr_with_Context $
120 const list_empty
121
122 -- | Parse 'list_cons'.
123 list_cons_from
124 :: forall root lam ty ast hs ret.
125 ( ty ~ Type_Root_of_Expr (Expr_List lam root)
126 , Eq_Type (Type_Root_of_Expr root)
127 , Expr_from ast root
128 , Type_Lift Type_List (Type_of_Expr root)
129 , Type_Unlift Type_List (Type_of_Expr root)
130 , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast)
131 (Error_of_Expr ast root)
132 , Root_of_Expr root ~ root
133 ) => ast -> ast
134 -> Expr_From ast (Expr_List lam root) hs ret
135 list_cons_from ast_a ast_l ex ast ctx k =
136 expr_from (Proxy::Proxy root) ast_a ctx $
137 \(ty_a::Type_Root_of_Expr root h_a) (Forall_Repr_with_Context a) ->
138 expr_from (Proxy::Proxy root) ast_l ctx $
139 \(ty_l::Type_Root_of_Expr root h_l) (Forall_Repr_with_Context l) ->
140 check_type_list ex ast ty_l $ \(Type_Type1 _ ty_l_a) ->
141 check_eq_type ex ast ty_a ty_l_a $ \Refl ->
142 k (type_list ty_a) $ Forall_Repr_with_Context $
143 \c -> list_cons (a c) (l c)
144
145 -- | Parse 'list'.
146 list_from
147 :: forall root lam ex ty ty_root ast hs ret.
148 ( ty ~ Type_Root_of_Expr (Expr_List lam root)
149 , ty_root ~ Type_Root_of_Expr root
150 , ex ~ Expr_List lam root
151 , Eq_Type (Type_Root_of_Expr root)
152 , Type_from ast ty_root
153 , Expr_from ast root
154 , Type_Lift Type_List (Type_of_Expr root)
155 , Type_Unlift Type_List (Type_of_Expr root)
156 , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast)
157 (Error_of_Expr ast root)
158 , Root_of_Expr root ~ root
159 , Root_of_Type ty_root ~ ty_root
160 ) => ast -> [ast]
161 -> Expr_From ast ex hs ret
162 list_from ast_ty_a ast_as =
163 case type_from (Proxy::Proxy ty_root)
164 ast_ty_a (Right . Exists_Type) of
165 Left err -> \ex ast _ctx _k -> Left $ error_expr ex $ Error_Expr_Type err ast
166 Right (Exists_Type ty_a) -> go ty_a [] ast_as
167 where
168 go :: Type_Root_of_Expr root ty_a
169 -> [Forall_Repr_with_Context root hs ty_a]
170 -> [ast]
171 -> Expr_From ast (Expr_List lam root) hs ret
172 go ty_a as [] _ex _ast _ctx k =
173 k (type_list ty_a) $ Forall_Repr_with_Context $
174 \c -> list ((\(Forall_Repr_with_Context a) -> a c) <$> reverse as)
175 go ty_a as (ast_x:ast_xs) ex ast ctx k =
176 expr_from (Proxy::Proxy root) ast_x ctx $
177 \(ty_x::Type_Root_of_Expr root h_x) x ->
178 check_eq_type ex ast ty_a ty_x $ \Refl ->
179 go ty_a (x:as) ast_xs ex ast ctx k
180
181 -- | Parse 'list_filter'.
182 list_filter_from
183 :: forall root lam ty ty_root ast hs ret.
184 ( ty ~ Type_Root_of_Expr (Expr_List lam root)
185 , ty_root ~ Type_of_Expr root
186 , Eq_Type (Type_Root_of_Expr root)
187 , Expr_from ast root
188 , Type_Lift Type_Bool ty_root
189 , Type_Lift (Type_Fun lam) ty_root
190 , Type_Unlift (Type_Fun lam) ty_root
191 , Type_Lift Type_List ty_root
192 , Type_Unlift Type_List ty_root
193 , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast)
194 (Error_of_Expr ast root)
195 , Root_of_Expr root ~ root
196 ) => ast -> ast
197 -> Expr_From ast (Expr_List lam root) hs ret
198 list_filter_from ast_f ast_l ex ast ctx k =
199 expr_from (Proxy::Proxy root) ast_f ctx $
200 \(ty_f::Type_Root_of_Expr root h_f) (Forall_Repr_with_Context f) ->
201 expr_from (Proxy::Proxy root) ast_l ctx $
202 \(ty_l::Type_Root_of_Expr root h_l) (Forall_Repr_with_Context l) ->
203 check_type_fun ex ast ty_f $ \(ty_f_a `Type_Fun` ty_f_b
204 :: Type_Fun lam (Type_Root_of_Expr root) h_f) ->
205 check_eq_type ex ast type_bool ty_f_b $ \Refl ->
206 check_type_list ex ast ty_l $ \(Type_Type1 _ ty_l_a) ->
207 check_eq_type ex ast ty_f_a ty_l_a $ \Refl ->
208 k ty_l $ Forall_Repr_with_Context $
209 \c -> list_filter (f c) (l c)