1 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE MultiParamTypeClasses #-}
4 {-# LANGUAGE OverloadedStrings #-}
5 {-# LANGUAGE ScopedTypeVariables #-}
6 {-# LANGUAGE TypeFamilies #-}
7 module Language.Symantic.Type.Map where
9 import Data.Map.Strict as Map
10 import Data.Maybe (isJust)
11 import Data.Type.Equality ((:~:)(Refl))
13 import Language.Symantic.Type.Common
14 import Language.Symantic.Type.Fun
15 import Language.Symantic.Type.Bool
16 import Language.Symantic.Type.Var
20 data Type_Map root h where
24 -> Type_Map root (Map h_k h_a)
26 type instance Root_of_Type (Type_Map root) = root
27 type instance Error_of_Type ast (Type_Map root) = No_Error_Type
31 Type_Eq (Type_Map root) where
32 type_eq (Type_Map k1 a1) (Type_Map k2 a2)
33 | Just Refl <- k1 `type_eq` k2
34 , Just Refl <- a1 `type_eq` a2
39 Eq (Type_Map root h) where
40 x == y = isJust $ type_eq x y
41 instance -- String_from_Type
42 String_from_Type root =>
43 String_from_Type (Type_Map root) where
44 string_from_type (Type_Map k a) =
45 "Map (" ++ string_from_type k ++ ")"
46 ++ " (" ++ string_from_type a ++ ")"
48 String_from_Type root =>
49 Show (Type_Map root h) where
50 show = string_from_type
52 -- | Convenient alias to include a 'Type_Map' within a type.
54 :: (Type_Root_Lift Type_Map root, Ord h_k)
58 type_map k a = type_root_lift (Type_Map k a)
60 -- * Type 'Type_Fun_Bool_Map'
61 -- | Convenient alias.
62 type Type_Fun_Bool_Map lam
63 = Type_Root (Type_Alt Type_Var
64 (Type_Alt (Type_Fun lam)