{-# LANGUAGE
AllowAmbiguousTypes,
ConstraintKinds,
DataKinds,
PolyKinds,
RankNTypes,
TypeFamilies,
TypeInType,
TypeOperators,
UndecidableInstances #-}
module Fcf.Utils
( Error
, TError
, Constraints
, TyEq
, Stuck
, IsBool(_If)
, Case
, Match()
, type (-->)
, Is
, Any
, Else
, If
) where
import Data.Kind (Constraint)
import Data.Type.Bool (If)
import GHC.TypeLits (Symbol, TypeError, ErrorMessage(..))
import Fcf.Core
import Fcf.Combinators (Pure)
data Error :: Symbol -> Exp a
type instance Eval (Error msg) = TypeError ('Text msg)
data TError :: ErrorMessage -> Exp a
type instance Eval (TError msg) = TypeError msg
data Constraints :: [Constraint] -> Exp Constraint
type instance Eval (Constraints '[]) = (() :: Constraint)
type instance Eval (Constraints (a ': as)) = (a, Eval (Constraints as))
data TyEq :: a -> b -> Exp Bool
type instance Eval (TyEq a b) = TyEqImpl a b
type family TyEqImpl (a :: k) (b :: l) :: Bool where
TyEqImpl a a = 'True
TyEqImpl a b = 'False
type family Stuck :: a
class IsBool (b :: Bool) where
_If :: ((b ~ 'True) => r) -> ((b ~ 'False) => r) -> r
instance IsBool 'True where _If a _ = a
instance IsBool 'False where _If _ b = b
infix 0 -->
data Match j k
= Match_ j k
| Is_ (j -> Exp Bool) k
| Any_ k
| Else_ (j -> Exp k)
data Case :: [Match j k] -> j -> Exp k
type instance Eval (Case ms a) = Case_ ms a
type family Case_ (ms :: [Match j k]) (a :: j) :: k where
Case_ ('Match_ a' b : ms) a = Eval (If (TyEqImpl a' a) (Pure b) (Case ms a))
Case_ ('Is_ p b : ms) a = Case_ [ 'True --> b
, 'False --> Case_ ms a
] (p @@ a)
Case_ ('Any_ b : _ ) _ = b
Case_ ('Else_ f : _ ) a = f @@ a
type (-->) = ('Match_ :: j -> k -> Match j k)
type Is = ('Is_ :: (j -> Exp Bool) -> k -> Match j k)
type Any = ('Any_ :: k -> Match j k)
type Else = ('Else_ :: (j -> Exp k) -> Match j k)