{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} module Language.Symantic.Type.List where import Data.Maybe (isJust) import Data.Type.Equality ((:~:)(Refl)) import Language.Symantic.Type.Common import Language.Symantic.Type.Fun import Language.Symantic.Type.Bool import Language.Symantic.Type.Var -- * Type 'Type_List' -- | The 'List' type. data Type_List root h where Type_List :: root h_a -> Type_List root [h_a] type instance Root_of_Type (Type_List root) = root type instance Error_of_Type ast (Type_List root) = No_Error_Type instance -- Type_Eq Type_Eq root => Type_Eq (Type_List root) where type_eq (Type_List a1) (Type_List a2) | Just Refl <- a1 `type_eq` a2 = Just Refl type_eq _ _ = Nothing instance -- Eq Type_Eq root => Eq (Type_List root h) where x == y = isJust $ type_eq x y instance -- String_from_Type String_from_Type root => String_from_Type (Type_List root) where string_from_type (Type_List a) = "List (" ++ string_from_type a ++ ")" instance -- Show String_from_Type root => Show (Type_List root h) where show = string_from_type -- | Convenient alias to include a 'Type_List' within a type. type_list :: Type_Root_Lift Type_List root => root h_a -> root [h_a] type_list a = type_root_lift (Type_List a) -- * Type 'Type_Fun_Bool_List' -- | Convenient alias. type Type_Fun_Bool_List lam = Type_Root (Type_Alt Type_Var (Type_Alt (Type_Fun lam) (Type_Alt Type_Bool Type_List)))