| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | GHC2021 | 
Development.IDE.Types.Shake
Synopsis
- newtype Q k = Q (k, NormalizedFilePath)
- newtype A v = A (Value v)
- data Value v- = Succeeded (Maybe FileVersion) v
- | Stale (Maybe PositionDelta) (Maybe FileVersion) v
- | Failed Bool
 
- data ValueWithDiagnostics = ValueWithDiagnostics !(Value Dynamic) !(Vector FileDiagnostic)
- type Values = Map Key ValueWithDiagnostics
- data Key
- 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
- toKey :: ShakeValue k => k -> NormalizedFilePath -> Key
- toNoFileKey :: (Show k, Typeable k, Eq k, Hashable k) => k -> Key
- fromKey :: Typeable k => Key -> Maybe (k, NormalizedFilePath)
- fromKeyType :: Key -> Maybe (SomeTypeRep, NormalizedFilePath)
- type WithHieDb = forall a. (HieDb -> IO a) -> IO a
Documentation
Constructors
| Q (k, NormalizedFilePath) | 
Invariant: the v must be in normal form (fully evaluated).
   Otherwise we keep repeatedly rnfing values taken from the Shake database
Constructors
| Succeeded (Maybe FileVersion) v | |
| Stale (Maybe PositionDelta) (Maybe FileVersion) v | |
| Failed Bool | 
Instances
data ValueWithDiagnostics Source #
Constructors
| ValueWithDiagnostics !(Value Dynamic) !(Vector FileDiagnostic) | 
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
Constructors
| BadDependency String | 
Instances
| Exception BadDependency Source # | |
| Defined in Development.IDE.Types.Shake Methods toException :: BadDependency -> SomeException # fromException :: SomeException -> Maybe BadDependency # displayException :: BadDependency -> String # | |
| Show BadDependency Source # | |
| Defined in Development.IDE.Types.Shake Methods showsPrec :: Int -> BadDependency -> ShowS # show :: BadDependency -> String # showList :: [BadDependency] -> ShowS # | |
data ShakeValue Source #
Constructors
| ShakeNoCutoff | This is what we use when we get Nothing from a rule. | 
| ShakeResult !ByteString | |
| ShakeStale !ByteString | 
Instances
| Generic ShakeValue Source # | |
| Defined in Development.IDE.Types.Shake Associated Types type Rep ShakeValue :: Type -> Type # | |
| Show ShakeValue Source # | |
| Defined in Development.IDE.Types.Shake Methods showsPrec :: Int -> ShakeValue -> ShowS # show :: ShakeValue -> String # showList :: [ShakeValue] -> ShowS # | |
| NFData ShakeValue Source # | |
| Defined in Development.IDE.Types.Shake Methods rnf :: ShakeValue -> () # | |
| type Rep ShakeValue Source # | |
| Defined in Development.IDE.Types.Shake type Rep ShakeValue = D1 ('MetaData "ShakeValue" "Development.IDE.Types.Shake" "ghcide-2.7.0.0-5yfM0XizHZdJVqoEnQAFOL" 'False) (C1 ('MetaCons "ShakeNoCutoff" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ShakeResult" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString)) :+: C1 ('MetaCons "ShakeStale" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString)))) | |
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 #
toKey :: ShakeValue k => k -> NormalizedFilePath -> Key Source #
fromKeyType :: Key -> Maybe (SomeTypeRep, NormalizedFilePath) Source #
fromKeyType (Q (k,f)) = (typeOf k, f)