1 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE MultiParamTypeClasses #-}
4 {-# LANGUAGE Rank2Types #-}
5 {-# LANGUAGE OverloadedStrings #-}
6 {-# LANGUAGE ScopedTypeVariables #-}
7 {-# LANGUAGE TypeFamilies #-}
8 module Language.Symantic.Type.Fun where
10 import Data.Maybe (isJust)
12 import Data.Type.Equality ((:~:)(Refl))
14 import Language.Symantic.Type.Common
17 -- | The function type.
18 data Type_Fun lam root h where
19 Type_Fun :: root h_arg
21 -> Type_Fun lam root (Lambda lam h_arg h_res)
23 type instance Root_of_Type (Type_Fun lam root) = root
24 type instance Error_of_Type ast (Type_Fun lam root) = ()
28 Eq_Type (Type_Fun lam root) where
30 (arg1 `Type_Fun` res1)
31 (arg2 `Type_Fun` res2)
32 | Just Refl <- arg1 `eq_type` arg2
33 , Just Refl <- res1 `eq_type` res2
38 Eq (Type_Fun lam root h) where
39 x == y = isJust $ x `eq_type` y
40 instance -- String_from_Type
41 String_from_Type root =>
42 String_from_Type (Type_Fun lam root) where
43 string_from_type (arg `Type_Fun` res) =
44 "(" ++ string_from_type arg ++ " -> "
45 ++ string_from_type res ++ ")"
47 String_from_Type root =>
48 Show (Type_Fun lam root h) where
49 show = string_from_type
50 instance Constraint_Type Eq (Type_Fun lam root)
51 instance Constraint_Type Ord (Type_Fun lam root)
54 :: forall (lam :: * -> *) (root :: * -> *) ast ret.
55 ( Type_Root_Lift (Type_Fun lam) root
57 , Root_of_Type root ~ root
58 ) => Proxy (Type_Fun lam root)
60 -> (forall h. root h -> Either (Error_of_Type ast root) ret)
61 -> Either (Error_of_Type ast root) ret
62 type_fun_from _ty ast_arg ast_res k =
63 type_from (Proxy::Proxy root) ast_arg $ \(ty_arg::root h_arg) ->
64 type_from (Proxy::Proxy root) ast_res $ \(ty_res::root h_res) ->
65 k (ty_arg `type_fun` ty_res
66 :: root (Lambda lam h_arg h_res))
68 -- | Convenient alias to include a 'Type_Fun' within a type.
70 :: Type_Root_Lift (Type_Fun lam) root
71 => root h_arg -> root h_res
72 -> root (Lambda lam h_arg h_res)
73 type_fun arg res = type_root_lift (Type_Fun arg res)
76 -- | A type synonym for the host-type function,
77 -- wrapping argument and result within a type constructor @lam@,
78 -- which is used in the 'Repr_Host' instance of 'Sym_Lambda'
79 -- to implement 'val' and 'lazy'.
80 type Lambda lam arg res = lam arg -> lam res