mirror of
https://github.com/github/semantic.git
synced 2024-12-22 14:21:31 +03:00
🔥 the MonadDead module.
This commit is contained in:
parent
ab9e129778
commit
e1a45b9997
@ -38,7 +38,6 @@ library
|
|||||||
, Control.Effect
|
, Control.Effect
|
||||||
-- Effects used for program analysis
|
-- Effects used for program analysis
|
||||||
-- , Control.Monad.Effect.Cache
|
-- , Control.Monad.Effect.Cache
|
||||||
-- , Control.Monad.Effect.Dead
|
|
||||||
, Control.Monad.Effect.Fresh
|
, Control.Monad.Effect.Fresh
|
||||||
-- , Control.Monad.Effect.GC
|
-- , Control.Monad.Effect.GC
|
||||||
-- , Control.Monad.Effect.NonDet
|
-- , Control.Monad.Effect.NonDet
|
||||||
|
@ -1,23 +0,0 @@
|
|||||||
{-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses, TypeOperators, UndecidableInstances #-}
|
|
||||||
module Control.Monad.Effect.Dead where
|
|
||||||
|
|
||||||
import Prologue
|
|
||||||
import Data.Set (delete)
|
|
||||||
import Control.Monad.Effect
|
|
||||||
import Control.Monad.Effect.State
|
|
||||||
|
|
||||||
-- | A set of “dead” (unreachable) terms.
|
|
||||||
newtype Dead a = Dead { unDead :: Set a }
|
|
||||||
deriving (Eq, Foldable, Semigroup, Monoid, Ord, Show)
|
|
||||||
|
|
||||||
-- | 'Monad's offering a readable & writable set of 'Dead' terms.
|
|
||||||
class Monad m => MonadDead t m where
|
|
||||||
-- | Update the current 'Dead' set.
|
|
||||||
killAll :: Dead t -> m ()
|
|
||||||
|
|
||||||
-- | Revive a single term, removing it from the current 'Dead' set.
|
|
||||||
revive :: Ord t => t -> m ()
|
|
||||||
|
|
||||||
instance (State (Dead t) :< fs) => MonadDead t (Eff fs) where
|
|
||||||
killAll = put
|
|
||||||
revive t = modify (Dead . delete t . unDead)
|
|
Loading…
Reference in New Issue
Block a user