]> 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 FlexibleInstances #-}
3 {-# LANGUAGE GADTs #-}
4 {-# LANGUAGE MultiParamTypeClasses #-}
5 {-# LANGUAGE OverloadedStrings #-}
6 {-# LANGUAGE PatternSynonyms #-}
7 {-# LANGUAGE ScopedTypeVariables #-}
8 {-# LANGUAGE TypeFamilies #-}
9 module Language.Symantic.Type.Map where
10
11 import Data.Proxy
12 import Data.Map.Strict as Map
13
14 import Language.Symantic.Type.Common
15
16 -- * Type 'Type_Map'
17 -- | The 'Map' type.
18 type Type_Map
19 = Type_Type2 Constraint2_Map Map
20 pattern Type_Map arg res
21 = Type_Type2 Proxy Proxy arg res
22
23 -- ** Class 'Constraint2_Map'
24 class Constraint2_Map k a
25 instance Ord k => Constraint2_Map k a
26
27 instance -- String_from_Type
28 String_from_Type root =>
29 String_from_Type (Type_Map root) where
30 string_from_type (Type_Type2 _ _ k a) =
31 "Map (" ++ string_from_type k ++ ")"
32 ++ " (" ++ string_from_type a ++ ")"
33
34 -- | Convenient alias to include a 'Type_Map' within a type.
35 type_map
36 :: forall root h_k h_a.
37 (Lift_Type_Root Type_Map root, Ord h_k)
38 => root h_k -> root h_a
39 -> root (Map h_k h_a)
40 type_map k a = lift_type_root (Type_Map k a
41 ::Type_Map root (Map h_k h_a))