]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Type/Map.hs
init
[haskell/symantic.git] / Language / Symantic / Type / Map.hs
1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE GADTs #-}
3 {-# LANGUAGE MultiParamTypeClasses #-}
4 {-# LANGUAGE OverloadedStrings #-}
5 {-# LANGUAGE ScopedTypeVariables #-}
6 {-# LANGUAGE TypeFamilies #-}
7 module Language.Symantic.Type.Map where
8
9 import Data.Map.Strict as Map
10 import Data.Maybe (isJust)
11 import Data.Type.Equality ((:~:)(Refl))
12
13 import Language.Symantic.Type.Common
14
15 -- * Type 'Type_Map'
16 -- | The 'Map' type.
17 data Type_Map root h where
18 Type_Map :: Ord h_k
19 => root h_k
20 -> root h_a
21 -> Type_Map root (Map h_k h_a)
22
23 type instance Root_of_Type (Type_Map root) = root
24 type instance Error_of_Type ast (Type_Map root) = No_Error_Type
25
26 instance -- Type_Eq
27 Type_Eq root =>
28 Type_Eq (Type_Map root) where
29 type_eq (Type_Map k1 a1) (Type_Map k2 a2)
30 | Just Refl <- k1 `type_eq` k2
31 , Just Refl <- a1 `type_eq` a2
32 = Just Refl
33 type_eq _ _ = Nothing
34 instance -- Eq
35 Type_Eq root =>
36 Eq (Type_Map root h) where
37 x == y = isJust $ type_eq x y
38 instance -- String_from_Type
39 String_from_Type root =>
40 String_from_Type (Type_Map root) where
41 string_from_type (Type_Map k a) =
42 "Map (" ++ string_from_type k ++ ")"
43 ++ " (" ++ string_from_type a ++ ")"
44 instance -- Show
45 String_from_Type root =>
46 Show (Type_Map root h) where
47 show = string_from_type
48
49 -- | Convenient alias to include a 'Type_Map' within a type.
50 type_map
51 :: (Type_Root_Lift Type_Map root, Ord h_k)
52 => root h_k
53 -> root h_a
54 -> root (Map h_k h_a)
55 type_map k a = type_root_lift (Type_Map k a)