module Ivory.Language.Effects
( Effects(..)
, AllocEffects
, ProcEffects
, NoEffects
, ReturnEff(..)
, GetReturn()
, ClearReturn()
, BreakEff(..)
, GetBreaks()
, AllowBreak()
, ClearBreak()
, AllocEff(..)
, GetAlloc()
, ClearAlloc()
) where
data Effects = Effects ReturnEff BreakEff AllocEff
data ReturnEff = forall t. Returns t | NoReturn
data BreakEff = Break | NoBreak
data AllocEff = forall s. Scope s | NoAlloc
type family GetReturn (effs :: Effects) :: ReturnEff
type instance GetReturn ('Effects r b a) = r
type family ClearReturn (effs :: Effects) :: Effects
type instance ClearReturn ('Effects r b a) = 'Effects 'NoReturn b a
type family GetBreaks (effs :: Effects) :: BreakEff
type instance GetBreaks ('Effects r b a) = b
type family AllowBreak (effs :: Effects) :: Effects
type instance AllowBreak ('Effects r b a) = 'Effects r 'Break a
type family ClearBreak (effs :: Effects) :: Effects
type instance ClearBreak ('Effects r b a) = 'Effects r 'NoBreak a
type family GetAlloc (effs :: Effects) :: AllocEff
type instance GetAlloc ('Effects r b a) = a
type family ClearAlloc (effs :: Effects) :: Effects
type instance ClearAlloc ('Effects r b a) = 'Effects r b 'NoAlloc
type AllocEffects s = 'Effects 'NoReturn 'NoBreak (Scope s)
type ProcEffects s t = 'Effects (Returns t) 'NoBreak (Scope s)
type NoEffects = 'Effects 'NoReturn 'NoBreak 'NoAlloc