stack-1.4.0: The Haskell Tool Stack

Safe HaskellNone
LanguageHaskell2010

Stack.Types.StackT

Description

The monad used for the command-line executable stack.

Synopsis

Documentation

data StackT config m a Source #

The monad used for the executable stack.

Instances

MonadBaseControl b m => MonadBaseControl b (StackT config m) Source # 

Associated Types

type StM (StackT config m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (StackT config m) b -> b a) -> StackT config m a #

restoreM :: StM (StackT config m) a -> StackT config m a #

MonadBase b m => MonadBase b (StackT config m) Source # 

Methods

liftBase :: b α -> StackT config m α #

MonadTrans (StackT config) Source # 

Methods

lift :: Monad m => m a -> StackT config m a #

MonadTransControl (StackT config) Source # 

Associated Types

type StT (StackT config :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (StackT config) -> m a) -> StackT config m a #

restoreT :: Monad m => m (StT (StackT config) a) -> StackT config m a #

Monad m => MonadReader (Env config) (StackT config m) Source # 

Methods

ask :: StackT config m (Env config) #

local :: (Env config -> Env config) -> StackT config m a -> StackT config m a #

reader :: (Env config -> a) -> StackT config m a #

Monad m => Monad (StackT config m) Source # 

Methods

(>>=) :: StackT config m a -> (a -> StackT config m b) -> StackT config m b #

(>>) :: StackT config m a -> StackT config m b -> StackT config m b #

return :: a -> StackT config m a #

fail :: String -> StackT config m a #

Functor m => Functor (StackT config m) Source # 

Methods

fmap :: (a -> b) -> StackT config m a -> StackT config m b #

(<$) :: a -> StackT config m b -> StackT config m a #

Applicative m => Applicative (StackT config m) Source # 

Methods

pure :: a -> StackT config m a #

(<*>) :: StackT config m (a -> b) -> StackT config m a -> StackT config m b #

(*>) :: StackT config m a -> StackT config m b -> StackT config m b #

(<*) :: StackT config m a -> StackT config m b -> StackT config m a #

MonadIO m => MonadIO (StackT config m) Source # 

Methods

liftIO :: IO a -> StackT config m a #

MonadThrow m => MonadThrow (StackT config m) Source # 

Methods

throwM :: Exception e => e -> StackT config m a #

MonadCatch m => MonadCatch (StackT config m) Source # 

Methods

catch :: Exception e => StackT config m a -> (e -> StackT config m a) -> StackT config m a #

MonadMask m => MonadMask (StackT config m) Source # 

Methods

mask :: ((forall a. StackT config m a -> StackT config m a) -> StackT config m b) -> StackT config m b #

uninterruptibleMask :: ((forall a. StackT config m a -> StackT config m a) -> StackT config m b) -> StackT config m b #

MonadIO m => MonadLogger (StackT config m) Source #

Takes the configured log level into account.

Methods

monadLoggerLog :: ToLogStr msg => Loc -> LogSource -> LogLevel -> msg -> StackT config m () #

MonadIO m => MonadLoggerIO (StackT config m) Source # 

Methods

askLoggerIO :: StackT config m (Loc -> LogSource -> LogLevel -> LogStr -> IO ()) #

type StT (StackT config) a Source # 
type StT (StackT config) a = StT (ReaderT * (Env config)) a
type StM (StackT config m) a Source # 
type StM (StackT config m) a = ComposeSt (StackT config) m a

type HasEnv r = (HasLogOptions r, HasTerminal r, HasReExec r, HasSticky r) Source #

Constraint synonym for all of the common environment instances

type StackM r m = (MonadReader r m, MonadIO m, MonadBaseControl IO m, MonadLoggerIO m, MonadMask m, HasEnv r) Source #

Constraint synonym for constraints commonly satisifed by monads used in stack.

runStackT :: MonadIO m => config -> LogLevel -> Bool -> Bool -> ColorWhen -> Bool -> StackT config m a -> m a Source #

runStackTGlobal :: MonadIO m => config -> GlobalOpts -> StackT config m a -> m a Source #

Run a Stack action, using global options.

runInnerStackT :: (HasEnv r, MonadReader r m, MonadIO m) => config -> StackT config IO a -> m a Source #

logSticky :: Q Exp Source #

Write a "sticky" line to the terminal. Any subsequent lines will overwrite this one, and that same line will be repeated below again. In other words, the line sticks at the bottom of the output forever. Running this function again will replace the sticky line with a new sticky line. When you want to get rid of the sticky line, run logStickyDone.

logStickyDone :: Q Exp Source #

This will print out the given message with a newline and disable any further stickiness of the line until a new call to logSticky happens.

It might be better at some point to have a runSticky function that encompasses the logSticky->logStickyDone pairing.