| Safe Haskell | Safe-Inferred | 
|---|---|
| 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)
- actionStack :: !Stack
 
- getDatabase :: Action Database
- data ShakeDatabase = ShakeDatabase !Int [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 KeyDetails = KeyDetails {- keyStatus :: !Status
- keyReverseDeps :: !(HashSet Key)
 
- onKeyReverseDeps :: (HashSet Key -> HashSet Key) -> KeyDetails -> KeyDetails
- data Database = Database {- databaseExtra :: Dynamic
- databaseRules :: TheRules
- databaseStep :: !(TVar Step)
- databaseValues :: !(Map Key KeyDetails)
 
- getDatabaseValues :: Database -> IO [(Key, Status)]
- data Status- = Clean !Result
- | Dirty (Maybe Result)
- | Running { - runningStep :: !Step
- runningWait :: !(IO ())
- runningResult :: Result
- runningPrev :: !(Maybe Result)
 
 
- viewDirty :: Step -> Status -> 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 ![Key]
- | ResultDeps ![Key]
 
- getResultDepsDefault :: [Key] -> ResultDeps -> [Key]
- mapResultDeps :: ([Key] -> [Key]) -> ResultDeps -> ResultDeps
- data RunMode
- data RunChanged
- data RunResult value = RunResult {- runChanged :: RunChanged
- runStore :: ByteString
- runValue :: value
 
- data GraphException = forall e.Exception e => GraphException {}
- fromGraphException :: Typeable b => SomeException -> Maybe b
- data Stack = Stack [Key] !(HashSet Key)
- newtype StackException = StackException Stack
- addStack :: Key -> Stack -> Either StackException Stack
- memberStack :: Key -> Stack -> Bool
- emptyStack :: Stack
Documentation
unwrapDynamic :: forall a. Typeable a => Dynamic -> a Source #
Instances
Constructors
| SRules | |
| Fields 
 | |
Constructors
| Action | |
| Fields 
 | |
Instances
| MonadFail Action Source # | |
| Defined in Development.IDE.Graph.Internal.Types | |
| MonadIO Action Source # | |
| Defined in Development.IDE.Graph.Internal.Types | |
| Applicative Action Source # | |
| Functor Action Source # | |
| Monad Action Source # | |
| MonadCatch Action Source # | |
| MonadMask Action Source # | |
| Defined in Development.IDE.Graph.Internal.Types | |
| MonadThrow Action Source # | |
| Defined in Development.IDE.Graph.Internal.Types | |
| MonadUnliftIO Action Source # | |
| Defined in Development.IDE.Graph.Internal.Types | |
Constructors
| SAction | |
| Fields 
 | |
data ShakeDatabase Source #
Constructors
| ShakeDatabase !Int [Action ()] Database | 
data KeyDetails Source #
Constructors
| KeyDetails | |
| Fields 
 | |
onKeyReverseDeps :: (HashSet Key -> HashSet Key) -> KeyDetails -> KeyDetails Source #
Constructors
| Database | |
| Fields 
 | |
Constructors
| Clean !Result | |
| Dirty (Maybe Result) | |
| Running | |
| Fields 
 | |
Constructors
| Result | |
| Fields 
 | |
data ResultDeps Source #
Constructors
| UnknownDeps | |
| AlwaysRerunDeps ![Key] | |
| ResultDeps ![Key] | 
Instances
| Monoid ResultDeps Source # | |
| Defined in Development.IDE.Graph.Internal.Types Methods mempty :: ResultDeps # mappend :: ResultDeps -> ResultDeps -> ResultDeps # mconcat :: [ResultDeps] -> ResultDeps # | |
| Semigroup ResultDeps Source # | |
| Defined in Development.IDE.Graph.Internal.Types Methods (<>) :: ResultDeps -> ResultDeps -> ResultDeps # sconcat :: NonEmpty ResultDeps -> ResultDeps # stimes :: Integral b => b -> ResultDeps -> ResultDeps # | |
| Show ResultDeps Source # | |
| Defined in Development.IDE.Graph.Internal.Types Methods showsPrec :: Int -> ResultDeps -> ShowS # show :: ResultDeps -> String # showList :: [ResultDeps] -> ShowS # | |
| Eq ResultDeps Source # | |
| Defined in Development.IDE.Graph.Internal.Types | |
getResultDepsDefault :: [Key] -> ResultDeps -> [Key] Source #
mapResultDeps :: ([Key] -> [Key]) -> 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 
 | |
data GraphException Source #
Constructors
| forall e.Exception e => GraphException | |
Instances
| Exception GraphException Source # | |
| Defined in Development.IDE.Graph.Internal.Types Methods toException :: GraphException -> SomeException # | |
| Show GraphException Source # | |
| Defined in Development.IDE.Graph.Internal.Types Methods showsPrec :: Int -> GraphException -> ShowS # show :: GraphException -> String # showList :: [GraphException] -> ShowS # | |
fromGraphException :: Typeable b => SomeException -> Maybe b Source #
newtype StackException Source #
Constructors
| StackException Stack | 
Instances
| Exception StackException Source # | |
| Defined in Development.IDE.Graph.Internal.Types Methods toException :: StackException -> SomeException # | |
| Show StackException Source # | |
| Defined in Development.IDE.Graph.Internal.Types Methods showsPrec :: Int -> StackException -> ShowS # show :: StackException -> String # showList :: [StackException] -> ShowS # | |
emptyStack :: Stack Source #