]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Expr/Root.hs
init
[haskell/symantic.git] / Language / Symantic / Expr / Root.hs
1 {-# LANGUAGE ConstraintKinds #-}
2 {-# LANGUAGE DataKinds #-}
3 {-# LANGUAGE FlexibleContexts #-}
4 {-# LANGUAGE FlexibleInstances #-}
5 {-# LANGUAGE GADTs #-}
6 {-# LANGUAGE KindSignatures #-}
7 {-# LANGUAGE MultiParamTypeClasses #-}
8 {-# LANGUAGE Rank2Types #-}
9 {-# LANGUAGE ScopedTypeVariables #-}
10 {-# LANGUAGE TypeFamilies #-}
11 {-# LANGUAGE TypeOperators #-}
12 {-# LANGUAGE UndecidableInstances #-}
13 module Language.Symantic.Expr.Root where
14
15 import Language.Symantic.Type
16
17 -- ** Type family 'Root_of_Expr'
18 -- | The root expression of an expression.
19 type family Root_of_Expr (ex:: *) :: *
20
21 -- ** Type family 'Type_of_Expr'
22 -- | The type of an expression, parameterized by a root type.
23 type family Type_of_Expr (ex:: *) :: {-root-}(* -> *) -> {-h-}* -> *
24
25 -- ** Type 'Type_Root_of_Expr'
26 -- | Convenient alias.
27 --
28 -- NOTE: include 'Type_Var' only to use it
29 -- within 'Error_Expr_Type_mismatch' so far.
30 type Type_Root_of_Expr (ex:: *)
31 = Type_Root (Type_Var0 :|: Type_Var1 :|: Type_of_Expr (Root_of_Expr ex))
32
33 -- * Type 'Expr_Root'
34 -- | The root expression, passing itself as parameter to the given expression.
35 newtype Expr_Root (ex:: * -> *)
36 = Expr_Root (ex (Expr_Root ex))
37 type instance Root_of_Expr (Expr_Root ex) = Expr_Root ex
38 type instance Type_of_Expr (Expr_Root ex)
39 = Type_of_Expr (ex (Expr_Root ex))