{-# 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 qualified Data.MonoTraversable as MT 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 import Language.Symantic.Type.Constraint import Language.Symantic.Type.Family -- * Type 'Type_Map' -- | The 'Map' type. type Type_Map = Type2 (Proxy Map) pattern Type_Map :: root k -> root a -> Type2 (Proxy Map) root (Map k a) pattern Type_Map k a = Type2 Proxy k a instance Type1_Unlift Type_Map where type1_unlift (Type2 px a b) k = k ( Type1 (Proxy::Proxy (Map a)) b , Type1_Lift (\(Type1 _ b') -> Type2 px a b') ) instance Type0_Constraint Eq root => Type0_Constraint Eq (Type_Map root) where type0_constraint c (Type2 _ k a) | Just Dict <- type0_constraint c k , Just Dict <- type0_constraint c a = Just Dict type0_constraint _c _ = Nothing instance Type0_Constraint Ord root => Type0_Constraint Ord (Type_Map root) where type0_constraint c (Type2 _ k a) | Just Dict <- type0_constraint c k , Just Dict <- type0_constraint c a = Just Dict type0_constraint _c _ = Nothing instance Type0_Constraint Ord root => Type0_Constraint Monoid (Type_Map root) where type0_constraint _c (Type2 _ k _a) | Just Dict <- type0_constraint (Proxy::Proxy Ord) k = Just Dict type0_constraint _c _ = Nothing instance Type0_Constraint Num (Type_Map root) instance Type0_Constraint Integral (Type_Map root) instance Type0_Constraint MT.MonoFunctor (Type_Map root) where type0_constraint _c Type2{} = Just Dict instance Type1_Constraint Functor (Type_Map root) where type1_constraint _c Type2{} = Just Dict instance Type1_Constraint Traversable (Type_Map root) where type1_constraint _c Type2{} = Just Dict instance Type1_Constraint Foldable (Type_Map root) where type1_constraint _c Type2{} = Just Dict instance Type0_Family Type_Family_MonoElement (Type_Map root) where type0_family _at (Type2 _px _k a) = Just a instance -- Type0_Eq Type0_Eq root => Type0_Eq (Type_Map root) where type0_eq (Type2 _px1 k1 a1) (Type2 _px2 k2 a2) | Just Refl <- k1 `type0_eq` k2 , Just Refl <- a1 `type0_eq` a2 = Just Refl type0_eq _ _ = Nothing instance -- Type1_Eq Type0_Eq root => Type1_Eq (Type_Map root) where type1_eq (Type2 _px1 k1 _a1) (Type2 _px2 k2 _a2) | Just Refl <- k1 `type0_eq` k2 = Just Refl type1_eq _ _ = Nothing instance -- String_from_Type String_from_Type root => String_from_Type (Type_Map root) where string_from_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. (Type_Root_Lift Type_Map root) => root h_k -> root h_a -> root (Map h_k h_a) type_map = type2