| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Development.IDE.Graph.Internal.Types
Synopsis
- unwrapDynamic :: forall a. Typeable a => Dynamic -> a
- type TheRules = HashMap TypeRep Dynamic
- newtype Rules a = Rules (ReaderT SRules IO a)
- data SRules = SRules {
- rulesExtra :: !Dynamic
- rulesActions :: !(IORef [Action ()])
- rulesMap :: !(IORef TheRules)
- newtype Action a = Action {
- fromAction :: ReaderT SAction IO a
- data SAction = SAction {
- actionDatabase :: !Database
- actionDeps :: !(IORef ResultDeps)
- getDatabase :: Action Database
- newtype Step = Step Int
- data Key = forall a.(Typeable a, Eq a, Hashable a, Show a) => Key a
- newtype Value = Value Dynamic
- data Database = Database {
- databaseExtra :: Dynamic
- databaseRules :: TheRules
- databaseStep :: !(IORef Step)
- databaseLock :: !Lock
- databaseIds :: !(IORef (Intern Key))
- databaseValues :: !(Ids (Key, Status))
- databaseReverseDeps :: !(Ids IntSet)
- databaseReverseDepsLock :: !Lock
- data Status
- getResult :: Status -> Maybe Result
- data Result = Result {
- resultValue :: !Value
- resultBuilt :: !Step
- resultChanged :: !Step
- resultVisited :: !Step
- resultDeps :: !ResultDeps
- resultExecution :: !Seconds
- resultData :: ByteString
- data ResultDeps
- = UnknownDeps
- | AlwaysRerunDeps ![Id]
- | ResultDeps ![Id]
- getResultDepsDefault :: [Id] -> ResultDeps -> [Id]
- mapResultDeps :: ([Id] -> [Id]) -> ResultDeps -> ResultDeps
- data RunMode
- data RunChanged
- data RunResult value = RunResult {
- runChanged :: RunChanged
- runStore :: ByteString
- runValue :: value
Documentation
unwrapDynamic :: forall a. Typeable a => Dynamic -> a Source #
Instances
Constructors
| SRules | |
Fields
| |
Constructors
| Action | |
Fields
| |
Instances
| Monad Action Source # | |
| Functor Action Source # | |
| MonadFail Action Source # | |
Defined in Development.IDE.Graph.Internal.Types | |
| Applicative Action Source # | |
| MonadIO Action Source # | |
Defined in Development.IDE.Graph.Internal.Types | |
| MonadThrow Action Source # | |
Defined in Development.IDE.Graph.Internal.Types | |
| MonadCatch Action Source # | |
| MonadMask Action Source # | |
Defined in Development.IDE.Graph.Internal.Types | |
Constructors
| SAction | |
Fields
| |
Constructors
| Database | |
Fields
| |
Constructors
| Result | |
Fields
| |
data ResultDeps Source #
Constructors
| UnknownDeps | |
| AlwaysRerunDeps ![Id] | |
| ResultDeps ![Id] |
Instances
| Semigroup ResultDeps Source # | |
Defined in Development.IDE.Graph.Internal.Types Methods (<>) :: ResultDeps -> ResultDeps -> ResultDeps # sconcat :: NonEmpty ResultDeps -> ResultDeps # stimes :: Integral b => b -> ResultDeps -> ResultDeps # | |
| Monoid ResultDeps Source # | |
Defined in Development.IDE.Graph.Internal.Types Methods mempty :: ResultDeps # mappend :: ResultDeps -> ResultDeps -> ResultDeps # mconcat :: [ResultDeps] -> ResultDeps # | |
getResultDepsDefault :: [Id] -> ResultDeps -> [Id] Source #
mapResultDeps :: ([Id] -> [Id]) -> ResultDeps -> ResultDeps Source #
What mode a rule is running in, passed as an argument to BuiltinRun.
Constructors
| RunDependenciesSame | My dependencies have not changed. |
| RunDependenciesChanged | At least one of my dependencies from last time have changed, or I have no recorded dependencies. |
data RunChanged Source #
How the output of a rule has changed.
Constructors
| ChangedNothing | Nothing has changed. |
| ChangedStore | The stored value has changed, but in a way that should be considered identical (used rarely). |
| ChangedRecomputeSame | I recomputed the value and it was the same. |
| ChangedRecomputeDiff | I recomputed the value and it was different. |
Instances
The result of BuiltinRun.
Constructors
| RunResult | |
Fields
| |