hls-graph-1.4.0.0: Haskell Language Server internal graph API
Safe HaskellNone
LanguageHaskell2010

Development.IDE.Graph

Synopsis

Documentation

data Rules a Source #

Instances

Instances details
Monad Rules Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Rules

Methods

(>>=) :: Rules a -> (a -> Rules b) -> Rules b #

(>>) :: Rules a -> Rules b -> Rules b #

return :: a -> Rules a #

Functor Rules Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Rules

Methods

fmap :: (a -> b) -> Rules a -> Rules b #

(<$) :: a -> Rules b -> Rules a #

MonadFail Rules Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Rules

Methods

fail :: String -> Rules a #

Applicative Rules Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Rules

Methods

pure :: a -> Rules a #

(<*>) :: Rules (a -> b) -> Rules a -> Rules b #

liftA2 :: (a -> b -> c) -> Rules a -> Rules b -> Rules c #

(*>) :: Rules a -> Rules b -> Rules b #

(<*) :: Rules a -> Rules b -> Rules a #

MonadIO Rules Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Rules

Methods

liftIO :: IO a -> Rules a #

Semigroup a => Semigroup (Rules a) Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Rules

Methods

(<>) :: Rules a -> Rules a -> Rules a #

sconcat :: NonEmpty (Rules a) -> Rules a #

stimes :: Integral b => b -> Rules a -> Rules a #

Monoid a => Monoid (Rules a) Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Rules

Methods

mempty :: Rules a #

mappend :: Rules a -> Rules a -> Rules a #

mconcat :: [Rules a] -> Rules a #

data Action a Source #

Instances

Instances details
Monad Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Action

Methods

(>>=) :: Action a -> (a -> Action b) -> Action b #

(>>) :: Action a -> Action b -> Action b #

return :: a -> Action a #

Functor Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Action

Methods

fmap :: (a -> b) -> Action a -> Action b #

(<$) :: a -> Action b -> Action a #

MonadFail Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Action

Methods

fail :: String -> Action a #

Applicative Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Action

Methods

pure :: a -> Action a #

(<*>) :: Action (a -> b) -> Action a -> Action b #

liftA2 :: (a -> b -> c) -> Action a -> Action b -> Action c #

(*>) :: Action a -> Action b -> Action b #

(<*) :: Action a -> Action b -> Action a #

MonadIO Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Action

Methods

liftIO :: IO a -> Action a #

actionBracket :: IO a -> (a -> IO b) -> (a -> Action c) -> Action c Source #

actionCatch :: Exception e => Action a -> (e -> Action a) -> Action a Source #

data ShakeException #

Error representing all expected exceptions thrown by Shake. Problems when executing rules will be raising using this exception type.

Constructors

ShakeException 

Fields

Configuration

Explicit parallelism

parallel :: [Action a] -> Action [a] Source #

Oracle rules

type ShakeValue a = (Show a, Typeable a, Eq a, Hashable a, Binary a, NFData a) #

Define an alias for the six type classes required for things involved in Shake rules. Using this alias requires the ConstraintKinds extension.

To define your own values meeting the necessary constraints it is convenient to use the extensions GeneralizedNewtypeDeriving and DeriveDataTypeable to write:

newtype MyType = MyType (String, Bool) deriving (Show, Typeable, Eq, Hashable, Binary, NFData)

Shake needs these instances on keys and values. They are used for:

  • Show is used to print out keys in errors, profiling, progress messages and diagnostics.
  • Typeable is used because Shake indexes its database by the type of the key and value involved in the rule (overlap is not allowed for type classes and not allowed in Shake either).
  • Eq and Hashable are used on keys in order to build hash maps from keys to values. Eq is used on values to test if the value has changed or not (this is used to support unchanging rebuilds, where Shake can avoid rerunning rules if it runs a dependency, but it turns out that no changes occurred.) The Hashable instances are only use at runtime (never serialised to disk), so they do not have to be stable across runs. Hashable on values is not used, and only required for a consistent interface.
  • Binary is used to serialize keys and values into Shake's build database; this lets Shake cache values across runs and implement unchanging rebuilds.
  • NFData is used to avoid space and thunk leaks, especially when Shake is parallelized.

type family RuleResult key #

The type mapping between the key or a rule and the resulting value. See addBuiltinRule and apply.

Instances

Instances details
type RuleResult AlwaysRerunQ 
Instance details

Defined in Development.Shake.Internal.Rules.Rerun

type RuleResult AlwaysRerunQ = ()

Special rules

Batching