{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Language.Symantic.Type.Map where import Data.Map.Strict as Map import Data.Proxy import Data.Type.Equality ((:~:)(Refl)) import Language.Symantic.Type.Root import Language.Symantic.Type.Type0 import Language.Symantic.Type.Type1 import Language.Symantic.Type.Type2 -- * Type 'Type_Map' -- | The 'Map' type. type Type_Map = Type_Type2 (Proxy Map) pattern Type_Map :: root k -> root a -> Type_Type2 (Proxy Map) root (Map k a) pattern Type_Map k a = Type_Type2 Proxy k a instance Unlift_Type1 Type_Map where unlift_type1 (Type_Type2 px a b) k = k ( Type_Type1 (Proxy::Proxy (Map a)) b , Lift_Type1 (\(Type_Type1 _ b') -> Type_Type2 px a b') ) instance Constraint_Type Eq root => Constraint_Type Eq (Type_Map root) where constraint_type c (Type_Type2 _ k a) | Just Dict <- constraint_type c k , Just Dict <- constraint_type c a = Just Dict constraint_type _c _ = Nothing instance Constraint_Type Ord root => Constraint_Type Ord (Type_Map root) where constraint_type c (Type_Type2 _ k a) | Just Dict <- constraint_type c k , Just Dict <- constraint_type c a = Just Dict constraint_type _c _ = Nothing instance Constraint_Type Ord root => Constraint_Type Monoid (Type_Map root) where constraint_type _c (Type_Type2 _ k _a) | Just Dict <- constraint_type (Proxy::Proxy Ord) k = Just Dict constraint_type _c _ = Nothing instance Constraint_Type Num (Type_Map root) instance Constraint_Type Integral (Type_Map root) instance Constraint_Type1 Functor (Type_Map root) where constraint_type1 _c Type_Type2{} = Just Dict instance Constraint_Type1 Traversable (Type_Map root) where constraint_type1 _c Type_Type2{} = Just Dict instance Constraint_Type1 Foldable (Type_Map root) where constraint_type1 _c Type_Type2{} = Just Dict instance -- Eq_Type Eq_Type root => Eq_Type (Type_Map root) where eq_type (Type_Type2 _px1 k1 a1) (Type_Type2 _px2 k2 a2) | Just Refl <- k1 `eq_type` k2 , Just Refl <- a1 `eq_type` a2 = Just Refl eq_type _ _ = Nothing instance -- Eq_Type1 Eq_Type root => Eq_Type1 (Type_Map root) where eq_type1 (Type_Type2 _px1 k1 _a1) (Type_Type2 _px2 k2 _a2) | Just Refl <- k1 `eq_type` k2 = Just Refl eq_type1 _ _ = Nothing instance -- String_from_Type String_from_Type root => String_from_Type (Type_Map root) where string_from_type (Type_Type2 _ k a) = "Map (" ++ string_from_type k ++ ")" ++ " (" ++ string_from_type a ++ ")" -- | Inject 'Type_Map' within a root type. type_map :: forall root h_k h_a. (Lift_Type_Root Type_Map root) => root h_k -> root h_a -> root (Map h_k h_a) type_map k a = lift_type_root (Type_Type2 Proxy k a ::Type_Map root (Map h_k h_a))