hls-graph-2.7.0.0: Haskell Language Server internal graph API
Safe HaskellSafe-Inferred
LanguageGHC2021

Development.IDE.Graph

Synopsis

Documentation

data Rules a Source #

A computation that defines all the rules that form part of the computation graph.

Rules has access to IO through MonadIO. Use of IO is at your own risk: if you write Rules that throw exceptions, then you need to make sure to handle them yourself when you run the resulting Rules.

Instances

Instances details
MonadIO Rules Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

liftIO :: IO a -> Rules a #

Applicative Rules Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

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 #

Functor Rules Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

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

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

Monad Rules Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

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

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

return :: a -> Rules a #

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

Defined in Development.IDE.Graph.Internal.Types

Methods

mempty :: Rules a #

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

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

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

Defined in Development.IDE.Graph.Internal.Types

Methods

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

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

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

data Action a Source #

An action representing something that can be run as part of a Rule.

Actions can be pure functions but also have access to IO via MonadIO and 'MonadUnliftIO. It should be assumed that actions throw exceptions, these can be caught with actionCatch. In particular, it is permissible to use the MonadFail instance, which will lead to an IOException.

Instances

Instances details
MonadFail Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

fail :: String -> Action a #

MonadIO Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

liftIO :: IO a -> Action a #

Applicative Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

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 #

Functor Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

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

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

Monad Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

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

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

return :: a -> Action a #

MonadCatch Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

catch :: (HasCallStack, Exception e) => Action a -> (e -> Action a) -> Action a #

MonadMask Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

mask :: HasCallStack => ((forall a. Action a -> Action a) -> Action b) -> Action b #

uninterruptibleMask :: HasCallStack => ((forall a. Action a -> Action a) -> Action b) -> Action b #

generalBracket :: HasCallStack => Action a -> (a -> ExitCase b -> Action c) -> (a -> Action b) -> Action (b, c) #

MonadThrow Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

throwM :: (HasCallStack, Exception e) => e -> Action a #

MonadUnliftIO Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

withRunInIO :: ((forall a. Action a -> IO a) -> IO b) -> Action b #

pattern Key :: () => (Typeable a, Hashable a, Show a) => a -> Key Source #

newKey :: (Typeable a, Hashable a, Show a) => a -> Key Source #

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

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

actionFork :: Action a -> (Async a -> Action b) -> Action b Source #

Configuration

Explicit parallelism

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

Oracle rules

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

type family RuleResult key Source #

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

Special rules

alwaysRerun :: Action () Source #

Always rerun this rule when dirty, regardless of the dependencies.

Batching

Actions for inspecting the keys in the database

getDirtySet :: Action [(Key, Int)] Source #

Returns the set of dirty keys annotated with their age (in # of builds)