{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Language.Symantic.Type.Fun where import Data.Proxy import Data.Type.Equality ((:~:)(Refl)) import qualified Data.MonoTraversable as MT import Language.Symantic.Type.Root import Language.Symantic.Type.Error 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_Fun' -- | The @->@ type. type Type_Fun = Type2 (Proxy (->)) pattern Type_Fun :: root arg -> root res -> Type_Fun root ((->) arg res) pattern Type_Fun arg res = Type2 Proxy arg res instance Type1_Unlift Type_Fun where type1_unlift (Type2 px a b) k = k ( Type1 (Proxy::Proxy ((->) a)) b , Type1_Lift (\(Type1 _ b') -> Type2 px a b') ) instance Type0_Eq root => Type1_Eq (Type_Fun root) where type1_eq (Type2 _ a1 _b1) (Type2 _ a2 _b2) | Just Refl <- type0_eq a1 a2 = Just Refl type1_eq _ _ = Nothing instance Type0_Constraint Eq (Type_Fun root) instance Type0_Constraint Ord (Type_Fun root) instance Type0_Constraint Monoid root => Type0_Constraint Monoid (Type_Fun root) where type0_constraint c (Type2 _ _arg res) | Just Dict <- type0_constraint c res = Just Dict type0_constraint _c _ = Nothing instance Type0_Constraint Num (Type_Fun root) instance Type0_Constraint Integral (Type_Fun root) instance Type0_Constraint MT.MonoFunctor (Type_Fun root) where type0_constraint _c Type2{} = Just Dict instance Type1_Constraint Functor (Type_Fun root) where type1_constraint _c Type2{} = Just Dict instance Type1_Constraint Applicative (Type_Fun root) where type1_constraint _c Type2{} = Just Dict instance Type1_Constraint Foldable (Type_Fun root) instance Type1_Constraint Traversable (Type_Fun root) instance Type1_Constraint Monad (Type_Fun root) where type1_constraint _c Type2{} = Just Dict instance Type0_Family Type_Family_MonoElement (Type_Fun root) where type0_family _at (Type2 _px _r a) = Just a instance -- Type0_Eq Type0_Eq root => Type0_Eq (Type_Fun root) where type0_eq (Type2 _ arg1 res1) (Type2 _ arg2 res2) | Just Refl <- arg1 `type0_eq` arg2 , Just Refl <- res1 `type0_eq` res2 = Just Refl type0_eq _ _ = Nothing instance -- String_from_Type String_from_Type root => String_from_Type (Type_Fun root) where string_from_type (Type2 _ arg res) = "(" ++ string_from_type arg ++ " -> " ++ string_from_type res ++ ")" -- | Convenient alias to include a 'Type_Fun' within a type. type_fun :: Type_Root_Lift Type_Fun root => root h_arg -> root h_res -> root ((->) h_arg h_res) type_fun = type2 -- | Parse 'Type_Fun'. type_fun_from :: forall (root :: * -> *) ast ret. ( Type_Root_Lift Type_Fun root , Type0_From ast root , Root_of_Type root ~ root ) => Proxy (Type_Fun root) -> ast -> ast -> (forall h. root h -> Either (Error_of_Type ast root) ret) -> Either (Error_of_Type ast root) ret type_fun_from _ty ast_arg ast_res k = type0_from (Proxy::Proxy root) ast_arg $ \(ty_arg::root h_arg) -> type0_from (Proxy::Proxy root) ast_res $ \(ty_res::root h_res) -> k (ty_arg `type_fun` ty_res :: root ((->) h_arg h_res))