1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE FlexibleInstances #-}
4 {-# LANGUAGE MultiParamTypeClasses #-}
5 {-# LANGUAGE OverloadedStrings #-}
6 {-# LANGUAGE PatternSynonyms #-}
7 {-# LANGUAGE Rank2Types #-}
8 {-# LANGUAGE ScopedTypeVariables #-}
9 {-# LANGUAGE TypeFamilies #-}
10 {-# OPTIONS_GHC -fno-warn-missing-methods #-}
11 module Language.Symantic.Type.Fun where
14 import Data.Type.Equality ((:~:)(Refl))
15 import Language.Symantic.Type.Root
16 import Language.Symantic.Type.Error
17 import Language.Symantic.Type.Type0
18 import Language.Symantic.Type.Type1
19 import Language.Symantic.Type.Type2
24 = Type_Type2 (Proxy (Lambda lam))
26 type instance Constraint2_of (Proxy (Lambda lam))
28 instance Unlift_Type1 (Type_Type2 (Proxy (Lambda lam))) where
29 unlift_type1 (Type_Type2 px a b) k =
30 k ( Type_Type1 (Proxy::Proxy (Lambda lam a)) b
31 , Lift_Type1 (\(Type_Type1 _ b') -> Type_Type2 px a b')
33 instance Constraint_Type1 Applicative (Type_Fun lam root)
36 :: root arg -> root res
37 -> Type_Fun lam root ((Lambda lam) arg res)
38 pattern Type_Fun arg res
39 = Type_Type2 Proxy arg res
43 Eq_Type (Type_Type2 (Proxy (Lambda lam)) root) where
45 (Type_Type2 _ arg1 res1)
46 (Type_Type2 _ arg2 res2)
47 | Just Refl <- arg1 `eq_type` arg2
48 , Just Refl <- res1 `eq_type` res2
51 instance -- String_from_Type
52 String_from_Type root =>
53 String_from_Type (Type_Fun lam root) where
54 string_from_type (Type_Type2 _ arg res) =
55 "(" ++ string_from_type arg ++ " -> "
56 ++ string_from_type res ++ ")"
59 -- | A newtype for the host-type function (->),
60 -- wrapping argument and result within a type constructor @lam@,
61 -- which is used in the 'Repr_Host' instance of 'Sym_Lambda'
62 -- to control the calling (see 'val' and 'lazy').
64 -- NOTE: a newtype is used instead of a type synonym
65 -- in order to be able to use it as a type constructor: @Lambda lam arg@,
66 -- which for instance has instances: 'Functor', 'Applicative', and 'Monad'.
67 newtype Lambda lam arg res
68 = Lambda { unLambda :: (->) (lam arg) (lam res) }
70 -- | Convenient alias to include a 'Type_Fun' within a type.
72 :: forall lam root h_arg h_res.
73 Lift_Type_Root (Type_Fun lam) root
74 => root h_arg -> root h_res
75 -> root (Lambda lam h_arg h_res)
76 type_fun arg res = lift_type_root (Type_Fun arg res
77 ::Type_Fun lam root (Lambda lam h_arg h_res))
79 -- | Parse 'Type_Fun'.
81 :: forall (lam :: * -> *) (root :: * -> *) ast ret.
82 ( Lift_Type_Root (Type_Fun lam) root
84 , Root_of_Type root ~ root
85 ) => Proxy (Type_Fun lam root)
87 -> (forall h. root h -> Either (Error_of_Type ast root) ret)
88 -> Either (Error_of_Type ast root) ret
89 type_fun_from _ty ast_arg ast_res k =
90 type_from (Proxy::Proxy root) ast_arg $ \(ty_arg::root h_arg) ->
91 type_from (Proxy::Proxy root) ast_res $ \(ty_res::root h_res) ->
92 k (ty_arg `type_fun` ty_res
93 :: root (Lambda lam h_arg h_res))