{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -- | Type Families. module Language.Symantic.Type.Family where import Data.Proxy (Proxy(..)) import qualified Data.MonoTraversable as MT import Language.Symantic.Type.Error import Language.Symantic.Type.Root import Language.Symantic.Type.Alt -- * Type 'Host_of_Type0_Family' type family Host_of_Type0_Family tf h0 :: * -- * Class 'Type0_Family' class Type0_Family (tf:: *) (ty:: * -> *) where type0_family :: forall h0. Proxy tf -> ty h0 -> Maybe (Root_of_Type ty (Host_of_Type0_Family tf h0)) type0_family _tf _ty = Nothing instance -- Type_Root ( Type0_Family tf (ty (Type_Root ty)) , Root_of_Type (ty (Type_Root ty)) ~ Type_Root ty ) => Type0_Family tf (Type_Root ty) where type0_family tf (Type_Root ty) = type0_family tf ty instance -- Type_Alt ( Type0_Family tf (curr root) , Type0_Family tf (next root) , Root_of_Type (curr root) ~ root , Root_of_Type (next root) ~ root ) => Type0_Family tf (Type_Alt curr next root) where type0_family tf (Type_Alt_Curr ty) = type0_family tf ty type0_family tf (Type_Alt_Next ty) = type0_family tf ty -- | Parsing utility to check that the resulting type -- from the application of a given type family to a given type -- is within the type stack, -- or raise 'Error_Type_No_Type0_Family'. check_type_type0_family :: forall ast ty tf h ret. ( Error_Type_Lift (Error_Type ast) (Error_of_Type ast ty) , Type0_Family tf ty , Root_of_Type ty ~ ty ) => Proxy tf -> ast -> ty h -> (ty (Host_of_Type0_Family tf h) -> Either (Error_of_Type ast ty) ret) -> Either (Error_of_Type ast ty) ret check_type_type0_family tf ast ty k = case type0_family tf ty of Just t -> k t Nothing -> Left $ error_type_lift $ Error_Type_No_Type_Family ast -- (Exists_Type0 ty) -- * Type 'Type_Family_MonoElement' -- | Proxy type for 'MT.Element'. data Type_Family_MonoElement type instance Host_of_Type0_Family Type_Family_MonoElement h = MT.Element h