]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Typing/Type.hs
Add Parsing.Token.
[haskell/symantic.git] / Language / Symantic / Typing / Type.hs
1 {-# LANGUAGE GADTs #-}
2 {-# LANGUAGE TypeInType #-}
3 {-# LANGUAGE UndecidableInstances #-}
4 {-# LANGUAGE ViewPatterns #-}
5 {-# OPTIONS_GHC -fno-warn-orphans #-}
6 module Language.Symantic.Typing.Type where
7
8 import Data.Monoid ((<>))
9 import Data.Proxy
10 import Data.Maybe (fromMaybe, isJust)
11 import Data.Text (Text)
12 import Data.Type.Equality
13 import qualified Data.Kind as K
14
15 import Language.Symantic.Typing.Kind
16 import Language.Symantic.Typing.Constant
17 import Language.Symantic.Parsing.Token
18
19 -- * Type 'Type'
20
21 -- | /Type of terms/.
22 --
23 -- * @cs@: /type constants/, fixed at compile time.
24 -- * @h@: indexed Haskell type.
25 --
26 -- * 'TyConst': /type constant/, selected amongst @cs@.
27 -- * @(:$)@: /type application/.
28 data Type (cs::[K.Type]) (h::k) where
29 TyConst
30 :: Const cs c
31 -> Type cs c
32 (:$)
33 :: Type cs f
34 -> Type cs x
35 -> Type cs (f x)
36 {-
37 TyVar
38 :: SKind k
39 -> Type cs (v::k)
40 -}
41 infixl 9 :$
42
43 -- | 'Type' constructor to be used
44 -- with @TypeApplications@
45 -- and @NoMonomorphismRestriction@.
46 ty :: forall c cs. Inj_Const cs c => Type cs c
47 ty = TyConst inj_const
48
49 instance TestEquality (Type cs) where
50 testEquality = eq_type
51 instance Eq (Type cs h) where
52 _x == _y = True
53 instance Show_Const cs => Show (Type cs h) where
54 show = show_type
55 -- deriving instance Show_Const cs => Show (Type cs h)
56
57 kind_of :: Type cs (h::k) -> SKind k
58 kind_of t =
59 case t of
60 TyConst c -> kind_of_const c
61 f :$ _x ->
62 case kind_of f of
63 _kx `SKiArrow` kf -> kf
64
65 eq_type
66 :: Type cs (x::k) -> Type cs (y::k) -> Maybe (x:~:y)
67 eq_type (TyConst x) (TyConst y)
68 | Just Refl <- testEquality x y
69 = Just Refl
70 eq_type (xf :$ xx) (yf :$ yx)
71 | Just Refl <- eq_skind (kind_of xf) (kind_of yf)
72 , Just Refl <- eq_type xf yf
73 , Just Refl <- eq_type xx yx
74 = Just Refl
75 eq_type _ _ = Nothing
76
77 eq_kind_type
78 :: Type cs (x::kx) -> Type cs (y::ky) -> Maybe (kx:~:ky)
79 eq_kind_type (TyConst x) (TyConst y)
80 | Just Refl <- eq_kind_const x y
81 = Just Refl
82 eq_kind_type (xf :$ xx) (yf :$ yx)
83 | Just Refl <- eq_kind_type xf yf
84 , Just Refl <- eq_kind_type xx yx
85 = Just Refl
86 eq_kind_type _x _y = Nothing
87
88 show_type :: Show_Const cs => Type cs h -> String
89 show_type (TyConst c) = show c
90 show_type ((:$) f@(:$){} a@(:$){}) = "(" <> show_type f <> ") (" <> show_type a <> ")"
91 show_type ((:$) f@(:$){} a) = "(" <> show_type f <> ") " <> show_type a
92 show_type ((:$) f a@(:$){}) = show_type f <> " (" <> show_type a <> ")"
93 show_type ((:$) f a) = show_type f <> " " <> show_type a
94 -- show_type (TyVar v) = "t" <> show (integral_from_peano v::Integer)
95
96 -- * Type 'EType'
97 -- | Existential for 'Type'.
98 data EType cs = forall h. EType (Type cs h)
99
100 instance Eq (EType cs) where
101 EType x == EType y
102 | Just Refl <- eq_kind_type x y
103 = isJust $ eq_type x y
104 _x == _y = False
105 instance Show_Const cs => Show (EType cs) where
106 show (EType t) = show t
107
108 -- * Type 'KType'
109 -- | Existential for 'Type' of a known 'Kind'.
110 data KType cs k = forall (h::k). KType (Type cs h)
111
112 instance Eq (KType cs ki) where
113 KType x == KType y = isJust $ eq_type x y
114 instance Show_Const cs => Show (KType cs ki) where
115 show (KType t) = show_type t
116
117 -- * Type 'Token_Type'
118 type Token_Type = Type '[] ()
119
120 data instance TokenT meta ts (Proxy Token_Type)
121 = Token_Type Text [EToken meta ts]
122 deriving instance Eq_Token meta ts => Eq (TokenT meta ts (Proxy Token_Type))
123 deriving instance Show_Token meta ts => Show (TokenT meta ts (Proxy Token_Type))
124
125 instance Const_from Text cs => Const_from Text (Proxy Token_Type ': cs) where
126 const_from "Type" k = k (ConstZ kind)
127 const_from s k = const_from s $ k . ConstS
128 instance Show_Const cs => Show_Const (Proxy Token_Type ': cs) where
129 show_const ConstZ{} = "Type"
130 show_const (ConstS c) = show_const c
131
132 -- * Class 'Type_from'
133 -- | Try to build a 'Type' from raw data.
134 class Type_from ts cs where
135 type_from
136 :: ( MonoLift (Error_Type meta ts) err
137 , MonoLift (Constraint_Kind meta ts) err )
138 => EToken meta ts
139 -> (forall k h. Type cs (h::k) -> Either err ret)
140 -> Either err ret
141
142 -- ** Type 'Constraint_Kind'
143 data Constraint_Kind meta ts
144 = Constraint_Kind_Eq (At meta ts EKind) (At meta ts EKind)
145 | Constraint_Kind_Arrow (At meta ts EKind)
146 deriving instance (Eq_TokenR meta ts ts) => Eq (Constraint_Kind meta ts)
147 deriving instance (Show_TokenR meta ts ts) => Show (Constraint_Kind meta ts)
148
149 check_kind
150 :: MonoLift (Constraint_Kind meta ts) err
151 => At meta ts (SKind x)
152 -> At meta ts (SKind y)
153 -> ((x :~: y) -> Either err ret) -> Either err ret
154 check_kind x y k =
155 case unAt x `eq_skind` unAt y of
156 Just Refl -> k Refl
157 Nothing -> Left $ olift $
158 Constraint_Kind_Eq (EKind <$> x) (EKind <$> y)
159
160 check_kind_arrow
161 :: MonoLift (Constraint_Kind meta ts) err
162 => At meta ts (SKind x)
163 -> (forall a b. (x :~: (a -> b)) -> SKind a -> SKind b -> Either err ret)
164 -> Either err ret
165 check_kind_arrow x k =
166 case unAt x of
167 a `SKiArrow` b -> k Refl a b
168 _ -> Left $ olift $
169 Constraint_Kind_Arrow (EKind <$> x)
170
171 -- ** Type 'Error_Type'
172 data Error_Type meta ts
173 = Error_Type_Token_invalid (EToken meta ts)
174 | Error_Type_Constant_unknown (At meta ts Text)
175 | Error_Type_Constraint_Kind (Constraint_Kind meta ts)
176 deriving instance (Eq_TokenR meta ts ts) => Eq (Error_Type meta ts)
177 deriving instance (Show_TokenR meta ts ts) => Show (Error_Type meta ts)
178
179 instance
180 ( Const_from Text cs
181 , Proj_Token ts Token_Type
182 ) => Type_from ts cs where
183 type_from
184 :: forall meta err ret.
185 ( MonoLift (Error_Type meta ts) err
186 , MonoLift (Constraint_Kind meta ts) err
187 ) => EToken meta ts
188 -> (forall k h. Type cs (h::k) -> Either err ret)
189 -> Either err ret
190 type_from tok@(proj_etoken -> Just (Token_Type cst args)) kk =
191 fromMaybe (Left $ olift $ Error_Type_Constant_unknown $ At (Just tok) cst) $
192 const_from cst $ \c -> Just $
193 go args (TyConst c) kk
194 where
195 go :: [EToken meta ts]
196 -> Type cs h
197 -> (forall k' h'. Type cs (h'::k') -> Either err ret)
198 -> Either err ret
199 go [] typ k = k typ
200 go (tok_x:tok_xs) ty_f k =
201 type_from tok_x $ \(ty_x::Type cs (h'::k')) ->
202 check_kind_arrow
203 (At (Just tok) $ kind_of ty_f) $ \Refl ki_f_a _ki_f_b ->
204 check_kind
205 (At (Just tok) ki_f_a)
206 (At (Just tok_x) $ kind_of ty_x) $ \Refl ->
207 go tok_xs (ty_f :$ ty_x) k
208 type_from tok _k = Left $ olift $ Error_Type_Token_invalid tok
209
210 -- * Type 'Types'
211 data Types cs (hs::[K.Type]) where
212 TypesZ :: Types cs '[]
213 TypesS :: Type cs h
214 -> Types cs hs
215 -> Types cs (Proxy h ': hs)
216 infixr 5 `TypesS`
217
218 etypes :: Types cs hs -> [EType cs]
219 etypes TypesZ = []
220 etypes (TypesS t ts) = EType t : etypes ts
221
222 -- | Build the left spine of a 'Type'.
223 spine_of_type
224 :: Type cs h
225 -> (forall kc (c::kc) hs. Const cs c -> Types cs hs -> ret) -> ret
226 spine_of_type (TyConst c) k = k c TypesZ
227 spine_of_type (f :$ a) k = spine_of_type f $ \c as -> k c (a `TypesS` as)
228
229 -- * Type 'UnProxy'
230 type family UnProxy (x::K.Type) :: k where
231 UnProxy (Proxy x) = x
232
233 -- * Class 'MonoLift'
234 class MonoLift a b where
235 olift :: a -> b
236 instance MonoLift
237 (Error_Type meta ts)
238 (Error_Type meta ts) where
239 olift = id
240 instance
241 MonoLift (Constraint_Kind meta ts) (Error_Type meta ts) where
242 olift = olift . Error_Type_Constraint_Kind