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

Development.IDE.Graph.Internal.Types

Synopsis

Documentation

unwrapDynamic :: forall a. Typeable a => Dynamic -> a Source #

newtype Rules a Source #

Constructors

Rules (ReaderT SRules IO a) 

Instances

Instances details
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 #

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 #

MonadFail Rules Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

fail :: String -> 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 #

MonadIO Rules Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

liftIO :: IO 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 #

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 #

data SRules Source #

Constructors

SRules 

newtype Action a Source #

Constructors

Action 

Instances

Instances details
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 #

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 #

MonadFail Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

fail :: String -> 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 #

MonadIO Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

liftIO :: IO a -> Action a #

MonadThrow Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

throwM :: Exception e => e -> Action a #

MonadCatch Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

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

MonadMask Action Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

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

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

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

newtype Step Source #

Constructors

Step Int 

Instances

Instances details
Eq Step Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

(==) :: Step -> Step -> Bool #

(/=) :: Step -> Step -> Bool #

Ord Step Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

compare :: Step -> Step -> Ordering #

(<) :: Step -> Step -> Bool #

(<=) :: Step -> Step -> Bool #

(>) :: Step -> Step -> Bool #

(>=) :: Step -> Step -> Bool #

max :: Step -> Step -> Step #

min :: Step -> Step -> Step #

Hashable Step Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

hashWithSalt :: Int -> Step -> Int #

hash :: Step -> Int #

data Key Source #

Constructors

forall a.(Typeable a, Eq a, Hashable a, Show a) => Key a 

Instances

Instances details
Eq Key Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

(==) :: Key -> Key -> Bool #

(/=) :: Key -> Key -> Bool #

Show Key Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Hashable Key Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

hashWithSalt :: Int -> Key -> Int #

hash :: Key -> Int #

newtype Value Source #

Constructors

Value Dynamic 

data Result Source #

Constructors

Result 

Fields

data RunMode 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.

Instances

Instances details
Eq RunMode Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

(==) :: RunMode -> RunMode -> Bool #

(/=) :: RunMode -> RunMode -> Bool #

Show RunMode Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

NFData RunMode Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

rnf :: RunMode -> () #

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

Instances details
Eq RunChanged Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Show RunChanged Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Generic RunChanged Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Associated Types

type Rep RunChanged :: Type -> Type #

ToJSON RunChanged Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

FromJSON RunChanged Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

NFData RunChanged Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

rnf :: RunChanged -> () #

type Rep RunChanged Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

type Rep RunChanged = D1 ('MetaData "RunChanged" "Development.IDE.Graph.Internal.Types" "hls-graph-1.5.1.1-JDgU6oKhpPB2rEOyg68txM" 'False) ((C1 ('MetaCons "ChangedNothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ChangedStore" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ChangedRecomputeSame" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ChangedRecomputeDiff" 'PrefixI 'False) (U1 :: Type -> Type)))

data RunResult value Source #

The result of BuiltinRun.

Constructors

RunResult 

Fields

Instances

Instances details
Functor RunResult Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

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

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

NFData value => NFData (RunResult value) Source # 
Instance details

Defined in Development.IDE.Graph.Internal.Types

Methods

rnf :: RunResult value -> () #