Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Q k = Q (k, NormalizedFilePath)
- newtype A v = A (Value v)
- data Value v
- data ValueWithDiagnostics = ValueWithDiagnostics !(Value Dynamic) !(Vector FileDiagnostic)
- type Values = HashMap (NormalizedFilePath, Key) ValueWithDiagnostics
- data Key = forall k.(Typeable k, Hashable k, Eq k, Show k) => Key k
- newtype BadDependency = BadDependency String
- data ShakeValue
- currentValue :: Value v -> Maybe v
- isBadDependency :: SomeException -> Bool
- toShakeValue :: (ByteString -> ShakeValue) -> Maybe ByteString -> ShakeValue
- encodeShakeValue :: ShakeValue -> ByteString
- decodeShakeValue :: ByteString -> ShakeValue
Documentation
Q (k, NormalizedFilePath) |
Instances
Eq k => Eq (Q k) Source # | |
Show k => Show (Q k) Source # | |
Hashable k => Hashable (Q k) Source # | |
Defined in Development.IDE.Types.Shake | |
Binary k => Binary (Q k) Source # | |
NFData k => NFData (Q k) Source # | |
Defined in Development.IDE.Types.Shake | |
type RuleResult (Q k) Source # | |
Defined in Development.IDE.Types.Shake |
Invariant: the v
must be in normal form (fully evaluated).
Otherwise we keep repeatedly rnf
ing values taken from the Shake database
Instances
Functor Value Source # | |
Show v => Show (Value v) Source # | |
Generic (Value v) Source # | |
NFData v => NFData (Value v) Source # | |
Defined in Development.IDE.Types.Shake | |
type Rep (Value v) Source # | |
Defined in Development.IDE.Types.Shake type Rep (Value v) = D1 ('MetaData "Value" "Development.IDE.Types.Shake" "ghcide-0.7.3.0-7Jt80mSDLDuL0bAoNcQUR5" 'False) (C1 ('MetaCons "Succeeded" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TextDocumentVersion) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 v)) :+: (C1 ('MetaCons "Stale" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TextDocumentVersion) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 v)) :+: C1 ('MetaCons "Failed" 'PrefixI 'False) (U1 :: Type -> Type))) |
type Values = HashMap (NormalizedFilePath, Key) ValueWithDiagnostics Source #
The state of the all values and diagnostics
Key type
newtype BadDependency Source #
When we depend on something that reported an error, and we fail as a direct result, throw BadDependency which short-circuits the rest of the action
Instances
Show BadDependency Source # | |
Defined in Development.IDE.Types.Shake showsPrec :: Int -> BadDependency -> ShowS # show :: BadDependency -> String # showList :: [BadDependency] -> ShowS # | |
Exception BadDependency Source # | |
Defined in Development.IDE.Types.Shake |
data ShakeValue Source #
ShakeNoCutoff | This is what we use when we get Nothing from a rule. |
ShakeResult !ByteString | |
ShakeStale !ByteString |
Instances
currentValue :: Value v -> Maybe v Source #
Convert a Value to a Maybe. This will only return Just
for
up2date results not for stale values.
isBadDependency :: SomeException -> Bool Source #
toShakeValue :: (ByteString -> ShakeValue) -> Maybe ByteString -> ShakeValue Source #