{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -fno-warn-missing-methods #-} module Language.Symantic.Type.Fun where import Data.Proxy import Language.Symantic.Type.Common -- * Type 'Type_Fun' -- | The @->@ type. type Type_Fun lam = Type_Type2 (Lambda lam) pattern Type_Fun arg res = Type_Type2 Proxy arg res instance -- String_from_Type String_from_Type root => String_from_Type (Type_Fun lam root) where string_from_type (Type_Type2 _ arg res) = "(" ++ string_from_type arg ++ " -> " ++ string_from_type res ++ ")" -- | Convenient alias to include a 'Type_Fun' within a type. type_fun :: Lift_Type_Root (Type_Fun lam) root => root h_arg -> root h_res -> root (Lambda lam h_arg h_res) type_fun arg res = lift_type_root (Type_Type2 Proxy arg res) type_fun_from :: forall (lam :: * -> *) (root :: * -> *) ast ret. ( Lift_Type_Root (Type_Fun lam) root , Type_from ast root , Root_of_Type root ~ root ) => Proxy (Type_Fun lam 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 = type_from (Proxy::Proxy root) ast_arg $ \(ty_arg::root h_arg) -> type_from (Proxy::Proxy root) ast_res $ \(ty_res::root h_res) -> k (ty_arg `type_fun` ty_res :: root (Lambda lam h_arg h_res)) -- ** Type 'Lambda' -- | A newtype for the host-type function (->), -- wrapping argument and result within a type constructor @lam@, -- which is used in the 'Repr_Host' instance of 'Sym_Lambda' -- to implement 'val' and 'lazy'. -- -- NOTE: a newtype is used instead of a type synonym -- in order to be able to use it as a type constructor: @Lambda lam arg@, -- which for instance has instances: 'Functor', 'Applicative', and 'Monad'. newtype Lambda lam arg res = Lambda { unLambda :: (->) (lam arg) (lam res) } {- data Type_Fun lam root h where Type_Fun :: root h_arg -> root h_res -> Type_Fun lam root (Lambda lam h_arg h_res) type instance Root_of_Type (Type_Fun lam root) = root type instance Error_of_Type ast (Type_Fun lam root) = () instance -- Eq_Type Eq_Type root => Eq_Type (Type_Fun lam root) where eq_type (arg1 `Type_Fun` res1) (arg2 `Type_Fun` res2) | Just Refl <- arg1 `eq_type` arg2 , Just Refl <- res1 `eq_type` res2 = Just Refl eq_type _ _ = Nothing instance -- Eq Eq_Type root => Eq (Type_Fun lam root h) where x == y = isJust $ x `eq_type` y instance -- Show String_from_Type root => Show (Type_Fun lam root h) where show = string_from_type instance Constraint_Type Eq (Type_Fun lam root) instance Constraint_Type Ord (Type_Fun lam root) instance Unlift_Type1 (Type_Fun lam) instance Eq_Type1 (Type_Fun lam root) -}