1 {-# LANGUAGE ConstraintKinds #-}
 
   2 {-# LANGUAGE DataKinds #-}
 
   3 {-# LANGUAGE FlexibleContexts #-}
 
   4 {-# LANGUAGE FlexibleInstances #-}
 
   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
 
  15 import Language.Symantic.Type
 
  18 -- | The root expression, passing itself as parameter to the given expression.
 
  19 newtype Expr_Root (ex:: * -> *)
 
  20  =      Expr_Root (ex (Expr_Root ex))
 
  21 type instance Root_of_Expr (Expr_Root ex) = Expr_Root ex
 
  22 type instance Type_of_Expr (Expr_Root ex)
 
  23  =            Type_of_Expr (ex (Expr_Root ex))
 
  25 -- * Type family 'Root_of_Expr'
 
  26 -- | The root expression of an expression.
 
  27 type family Root_of_Expr (ex:: *) :: *
 
  29 -- * Type family 'Type_of_Expr'
 
  30 -- | The type of an expression, parameterized by a root type.
 
  31 type family Type_of_Expr (ex:: *) :: {-root-}(* -> *) -> {-h-}* -> *
 
  33 -- ** Type 'Type_Root_of_Expr'
 
  34 -- | Convenient alias.
 
  36 -- NOTE: include 'Type_Var' only to use it
 
  37 -- within 'Error_Expr_Type_mismatch' so far.
 
  38 type Type_Root_of_Expr (ex:: *)
 
  39  =   Type_Root (Type_Var0 :|: Type_Var1 :|: Type_of_Expr (Root_of_Expr ex))