]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Expr/Map.hs
fix (->) by removing inline/val/lazy
[haskell/symantic.git] / Language / Symantic / Expr / Map.hs
1 {-# LANGUAGE DefaultSignatures #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE FlexibleInstances #-}
4 {-# LANGUAGE MultiParamTypeClasses #-}
5 {-# LANGUAGE ScopedTypeVariables #-}
6 {-# LANGUAGE TypeFamilies #-}
7 {-# OPTIONS_GHC -fno-warn-orphans #-}
8 -- | Expression for 'Map'.
9 module Language.Symantic.Expr.Map where
10
11 import Data.Map.Strict (Map)
12 import Data.Proxy (Proxy(..))
13 import Data.Type.Equality ((:~:)(Refl))
14
15 import Language.Symantic.Type
16 import Language.Symantic.Trans.Common
17 import Language.Symantic.Expr.Root
18 import Language.Symantic.Expr.Error
19 import Language.Symantic.Expr.From
20 import Language.Symantic.Expr.Lambda
21 import Language.Symantic.Expr.List
22 import Language.Symantic.Expr.Tuple
23
24 -- * Class 'Sym_Map_Lam'
25 -- | Symantic.
26 class Sym_Map repr where
27 map_from_list :: Ord k => repr [(k, a)] -> repr (Map k a)
28 mapWithKey
29 :: repr (k -> a -> b)
30 -> repr (Map k a)
31 -> repr (Map k b)
32
33 default map_from_list :: (Trans t repr, Ord k) => t repr [(k, a)] -> t repr (Map k a)
34 default mapWithKey
35 :: Trans t repr
36 => t repr (k -> a -> b)
37 -> t repr (Map k a)
38 -> t repr (Map k b)
39
40 map_from_list = trans_map1 map_from_list
41 mapWithKey = trans_map2 mapWithKey
42
43 -- | Parsing utility to check that the given type is a 'Type_List'
44 -- or raise 'Error_Expr_Type_mismatch'.
45 check_type_map
46 :: forall ast ex root ty h ret.
47 ( root ~ Root_of_Expr ex
48 , ty ~ Type_Root_of_Expr ex
49 , Lift_Type Type_Map (Type_of_Expr root)
50 , Unlift_Type Type_Map (Type_of_Expr root)
51 , Lift_Error_Expr (Error_Expr (Error_of_Type ast ty) ty ast)
52 (Error_of_Expr ast root)
53 )
54 => Proxy ex -> ast -> ty h
55 -> (Type_Map ty h -> Either (Error_of_Expr ast root) ret)
56 -> Either (Error_of_Expr ast root) ret
57 check_type_map ex ast ty k =
58 case unlift_type $ unType_Root ty of
59 Just ty_l -> k ty_l
60 Nothing -> Left $
61 error_expr ex $
62 Error_Expr_Type_mismatch ast
63 (Exists_Type (type_map (type_var0 SZero) (type_var0 $ SSucc SZero)
64 :: ty (Map Var0 Var0)))
65 (Exists_Type ty)
66
67 -- | Parse 'map_from_list'.
68 map_from_list_from
69 :: forall root ty ast hs ret.
70 ( ty ~ Type_Root_of_Expr (Expr_Map root)
71 , Expr_from ast root
72 , Lift_Type Type_List (Type_of_Expr root)
73 , Unlift_Type Type_List (Type_of_Expr root)
74 , Lift_Type Type_Map (Type_of_Expr root)
75 , Lift_Type Type_Tuple2 (Type_of_Expr root)
76 , Unlift_Type Type_Tuple2 (Type_of_Expr root)
77 , Constraint_Type Ord ty
78 , Lift_Error_Expr (Error_Expr (Error_of_Type ast ty) ty ast)
79 (Error_of_Expr ast root)
80 , Root_of_Expr root ~ root
81 ) => ast
82 -> Expr_From ast (Expr_Map root) hs ret
83 map_from_list_from ast_l ex ast ctx k =
84 expr_from (Proxy::Proxy root) ast_l ctx $
85 \(ty_l::ty h_l) (Forall_Repr_with_Context l) ->
86 check_type_list ex ast ty_l $ \(Type_Type1 _ ty_l_t) ->
87 check_type_tuple2 ex ast ty_l_t $ \(Type_Type2 Proxy ty_k ty_a) ->
88 check_constraint_type ex (Proxy::Proxy Ord) ast ty_k $ \Dict ->
89 k (type_map ty_k ty_a) $ Forall_Repr_with_Context $
90 \c -> map_from_list (l c)
91
92 -- | Parse 'mapWithKey'.
93 mapWithKey_from
94 :: forall root ty ast hs ret.
95 ( ty ~ Type_Root_of_Expr (Expr_Map root)
96 , Eq_Type ty
97 , Expr_from ast root
98 , Lift_Type Type_Fun (Type_of_Expr root)
99 , Unlift_Type Type_Fun (Type_of_Expr root)
100 , Lift_Type Type_Map (Type_of_Expr root)
101 , Unlift_Type Type_Map (Type_of_Expr root)
102 , Constraint_Type Ord ty
103 , Lift_Error_Expr (Error_Expr (Error_of_Type ast ty) ty ast)
104 (Error_of_Expr ast root)
105 , Root_of_Expr root ~ root
106 ) => ast -> ast
107 -> Expr_From ast (Expr_Map root) hs ret
108 mapWithKey_from ast_f ast_m ex ast ctx k =
109 expr_from (Proxy::Proxy root) ast_f ctx $
110 \(ty_f::ty h_f) (Forall_Repr_with_Context f) ->
111 expr_from (Proxy::Proxy root) ast_m ctx $
112 \(ty_m::ty h_m) (Forall_Repr_with_Context m) ->
113 check_type_fun ex ast ty_f $ \(Type_Type2 Proxy ty_f_k ty_f_a2b
114 :: Type_Fun ty h_f) ->
115 check_type_fun ex ast ty_f_a2b $ \(Type_Type2 Proxy ty_f_a ty_f_b
116 :: Type_Fun ty h_f_a2b) ->
117 check_type_map ex ast ty_m $ \(Type_Type2 Proxy ty_m_k ty_m_a) ->
118 check_eq_type ex ast ty_f_k ty_m_k $ \Refl ->
119 check_eq_type ex ast ty_f_a ty_m_a $ \Refl ->
120 check_constraint_type ex (Proxy::Proxy Ord) ast ty_m_k $ \Dict ->
121 k (type_map ty_m_k ty_f_b) $ Forall_Repr_with_Context $
122 \c -> mapWithKey (f c) (m c)
123
124 -- * Type 'Expr_Map'
125 -- | Expression.
126 data Expr_Map (root:: *)
127 type instance Root_of_Expr (Expr_Map root) = root
128 type instance Type_of_Expr (Expr_Map root) = Type_Map
129 type instance Sym_of_Expr (Expr_Map root) repr = (Sym_Map repr)
130 type instance Error_of_Expr ast (Expr_Map root) = No_Error_Expr
131
132 instance Constraint_Type1 Functor (Type_Map root) where
133 constraint_type1 _c Type_Type2{} = Just Dict
134 instance Constraint_Type1 Functor (Type_Type1 (Proxy (Map k)) root) where
135 constraint_type1 _c Type_Type1{} = Just Dict
136 instance Constraint_Type1 Applicative (Type_Map root)
137 instance Constraint_Type1 Applicative (Type_Type1 (Proxy (Map k)) root)
138 instance Constraint_Type1 Traversable (Type_Map root) where
139 constraint_type1 _c Type_Type2{} = Just Dict
140 instance Constraint_Type1 Traversable (Type_Type1 (Proxy (Map k)) root) where
141 constraint_type1 _c Type_Type1{} = Just Dict