Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
GitHub.Workflow.Command
Description
Programs run by GitHub Actions can use workflow commands to communicate with the runner.
GitHub documentation: Workflow commands for GitHub Actions
Synopsis
- class Monad m => MonadCommand m where
- executeCommand :: ToCommand a => a -> m ()
- newtype PrintCommands m a = PrintCommands (m a)
- class ToCommand a where
- addToCommand :: a -> Command -> Command
- newtype Debug = Debug {}
- debug :: Message -> Debug
- data Notice = Notice {}
- notice :: Message -> Notice
- data Warning = Warning {}
- warning :: Message -> Warning
- data Error = Error {}
- error :: Message -> Error
- group :: MonadCommand m => Text -> m a -> m a
- newtype GroupStart = GroupStart {}
- data GroupEnd = GroupEnd
- newtype AddMask = AddMask {}
- suspendCommands :: (MonadCommand m, MonadRandom m) => m a -> m a
- stopCommands :: (MonadCommand m, MonadRandom m) => m SuspendToken
- resumeCommands :: MonadCommand m => SuspendToken -> m ()
- data SuspendToken
- data Location = Location {}
- class HasLocationMaybe a where
- newtype File = File {}
- inFile :: File -> Location
- file :: Lens' Location File
- data Position = Position {}
- position :: Lens' Location (Maybe Position)
- data Extent
- extent :: Lens' Position (Maybe Extent)
- data Columns = Columns {}
- line :: Lens' Position Line
- startColumn :: Lens' Columns Column
- endColumn :: Lens' Columns (Maybe Column)
- newtype Line = Line {}
- atLine :: Line -> Position
- newtype Column = Column {}
- atColumn :: Column -> Columns
- data Command
- newtype Name = Name {}
- class HasName a where
- newtype Message = Message {}
- class HasMessage a where
- data Properties
- class HasProperties a where
- properties :: Lens' a Properties
- newtype Key = Key {}
- newtype Value = Value {}
Executing commands
class Monad m => MonadCommand m where Source #
Monadic context in which GitHub workflow commands may be executed
- For the most basic uses, use the
IO
instance, which prints commands tostdout
. - For custom monads that support
MonadIO
, you may deriveMonadCommand
viaPrintCommands
to get the same behavior thatIO
exhibits. - A program that wishes to accommodate running in both GitHub and non-GitHub contexts
may wish to define a more sophisicated
MonadCommand
instance that prints GitHub workflow commands only when theGITHUB_ACTIONS
environment variable is present, and otherwise takes some other more context-appropriate action.
Methods
executeCommand :: ToCommand a => a -> m () Source #
Instances
MonadCommand IO Source # | |
Defined in GitHub.Workflow.Command.Execution Methods executeCommand :: ToCommand a => a -> IO () Source # | |
MonadIO m => MonadCommand (PrintCommands m) Source # | |
Defined in GitHub.Workflow.Command.Execution Methods executeCommand :: ToCommand a => a -> PrintCommands m () Source # |
newtype PrintCommands m a Source #
Constructors
PrintCommands (m a) |
Instances
Commands
class ToCommand a where Source #
Methods
addToCommand :: a -> Command -> Command Source #
Instances
ToCommand Debug Source # | |
ToCommand Error Source # | |
ToCommand Notice Source # | |
ToCommand Warning Source # | |
ToCommand GroupEnd Source # | |
Defined in GitHub.Workflow.Command.Grouping | |
ToCommand GroupStart Source # | |
Defined in GitHub.Workflow.Command.Grouping Methods addToCommand :: GroupStart -> Command -> Command Source # | |
ToCommand AddMask Source # | |
Defined in GitHub.Workflow.Command.Masking | |
ToCommand ResumeCommands Source # | |
Defined in GitHub.Workflow.Command.Stopping Methods addToCommand :: ResumeCommands -> Command -> Command Source # | |
ToCommand StopCommands Source # | |
Defined in GitHub.Workflow.Command.Stopping Methods addToCommand :: StopCommands -> Command -> Command Source # | |
(IsAnnotationType a, HasMessage a, GetProperties a) => ToCommand (GenericAnnotation a) Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Generic Methods addToCommand :: GenericAnnotation a -> Command -> Command Source # |
Setting a debug message
Prints a debug message to the log
GitHub documentation: Setting a debug message
Instances
GetProperties Debug Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Debug Methods getProperties :: Debug -> Properties Source # | |
ToCommand Debug Source # | |
FromMessage Debug Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Debug Methods fromMessage :: Message -> Debug Source # | |
HasMessage Debug Source # | |
ToByteString Debug Source # | |
IsAnnotationType Debug Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Debug Methods |
Setting a notice message
Creates a notice message and prints the message to the log
The message can be associated with a particular file in your repository,
and optionally also a position within the file. See HasLocationMaybe
.
GitHub documentation: Setting a notice message
Constructors
Notice | |
Fields
|
Instances
HasLocationMaybe Notice Source # | |
GetProperties Notice Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Notice Methods getProperties :: Notice -> Properties Source # | |
HasProperties Notice Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Notice Methods | |
ToCommand Notice Source # | |
FromMessage Notice Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Notice Methods fromMessage :: Message -> Notice Source # | |
HasMessage Notice Source # | |
ToByteString Notice Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Notice Methods toByteStringBuilder :: Notice -> Builder Source # toByteString :: Notice -> ByteString Source # | |
IsAnnotationType Notice Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Notice Methods |
Setting a warning message
Creates a warning message and prints the message to the log
The message can be associated with a particular file in your repository,
and optionally also a position within the file. See HasLocationMaybe
.
GitHub documentation: Setting a warning message
Constructors
Warning | |
Fields
|
Instances
HasLocationMaybe Warning Source # | |
GetProperties Warning Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Warning Methods getProperties :: Warning -> Properties Source # | |
HasProperties Warning Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Warning Methods | |
ToCommand Warning Source # | |
FromMessage Warning Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Warning Methods fromMessage :: Message -> Warning Source # | |
HasMessage Warning Source # | |
ToByteString Warning Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Warning Methods toByteStringBuilder :: Warning -> Builder Source # toByteString :: Warning -> ByteString Source # | |
IsAnnotationType Warning Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Warning Methods |
Setting an error message
Creates an error message and prints the message to the log
The message can be associated with a particular file in your repository,
and optionally also a position within the file. See HasLocationMaybe
.
GitHub documentation: Setting an error message
Constructors
Error | |
Fields
|
Instances
HasLocationMaybe Error Source # | |
GetProperties Error Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Error Methods getProperties :: Error -> Properties Source # | |
HasProperties Error Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Error Methods | |
ToCommand Error Source # | |
FromMessage Error Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Error Methods fromMessage :: Message -> Error Source # | |
HasMessage Error Source # | |
ToByteString Error Source # | |
IsAnnotationType Error Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Error Methods |
Grouping log lines
Arguments
:: MonadCommand m | |
=> Text | Group title |
-> m a | Anything printed within this action will be nested inside an expandable entry in the log |
-> m a |
Creates an expandable group in the log
GitHub documentation: Grouping log lines
newtype GroupStart Source #
Starts a group
Constructors
GroupStart | |
Instances
ToCommand GroupStart Source # | |
Defined in GitHub.Workflow.Command.Grouping Methods addToCommand :: GroupStart -> Command -> Command Source # |
Masking a value in a log
Prevents a string or variable from being printed in the log
GitHub documentation: Masking a value in a log
Stopping and starting workflow commands
Arguments
:: (MonadCommand m, MonadRandom m) | |
=> m a | Commands issued by this action will have no effect |
-> m a |
Run an action with processing of workflow commands suspended
GitHub documentation: Stopping and starting workflow commands
stopCommands :: (MonadCommand m, MonadRandom m) => m SuspendToken Source #
Stops processing any workflow commands
This special command allows you to log anything without accidentally running a workflow command.
resumeCommands :: MonadCommand m => SuspendToken -> m () Source #
Resume processing workflow commands
data SuspendToken Source #
Location
Constructors
Location | |
Instances
IsString Location Source # | |
Defined in GitHub.Workflow.Command.Annotation.Location Methods fromString :: String -> Location # | |
AddToProperties Location Source # | |
Defined in GitHub.Workflow.Command.Annotation.Location Methods addToProperties :: Location -> Properties -> Properties Source # | |
HasLocationMaybe (Maybe Location) Source # | |
class HasLocationMaybe a where Source #
Instances
File
Position
Where an annotation is marked within a file
Instances
AddToProperties Position Source # | |
Defined in GitHub.Workflow.Command.Annotation.Position Methods addToProperties :: Position -> Properties -> Properties Source # |
Extra positional data, as a modification to the start Line
Constructors
WithinLine Columns | |
ToLine Line |
Instances
AddToProperties Extent Source # | |
Defined in GitHub.Workflow.Command.Annotation.Position.Extent Methods addToProperties :: Extent -> Properties -> Properties Source # |
Instances
AddToProperties Columns Source # | |
Defined in GitHub.Workflow.Command.Annotation.Position.Columns Methods addToProperties :: Columns -> Properties -> Properties Source # |
Anatomy of a command
A GitHub workflow command
A Command
consists of:
Of these, only Name
is always required. Some particular types of command require
a message or have restrictions on what properties they support or require.
Instances
IsString Command Source # | |
Defined in GitHub.Workflow.Command.Syntax.Command Methods fromString :: String -> Command # | |
Show Command Source # | |
Eq Command Source # | |
Ord Command Source # | |
Defined in GitHub.Workflow.Command.Syntax.Command | |
HasMessage Command Source # | |
HasName Command Source # | |
HasProperties Command Source # | |
Defined in GitHub.Workflow.Command.Syntax.Command Methods | |
ToByteString Command Source # | |
Defined in GitHub.Workflow.Command.Syntax.Command Methods toByteStringBuilder :: Command -> Builder Source # toByteString :: Command -> ByteString Source # |
Name
Message
Instances
IsString Message Source # | |
Defined in GitHub.Workflow.Command.Syntax.Message Methods fromString :: String -> Message # | |
Show Message Source # | |
Eq Message Source # | |
Ord Message Source # | |
Defined in GitHub.Workflow.Command.Syntax.Message | |
FromMessage Message Source # | |
Defined in GitHub.Workflow.Command.Syntax.Message Methods fromMessage :: Message -> Message Source # | |
HasMessage Message Source # | |
ToByteString Message Source # | |
Defined in GitHub.Workflow.Command.Syntax.Message Methods toByteStringBuilder :: Message -> Builder Source # toByteString :: Message -> ByteString Source # |
class HasMessage a where Source #
Properties
data Properties Source #
Instances
Show Properties Source # | |
Defined in GitHub.Workflow.Command.Syntax.Properties Methods showsPrec :: Int -> Properties -> ShowS # show :: Properties -> String # showList :: [Properties] -> ShowS # | |
Eq Properties Source # | |
Defined in GitHub.Workflow.Command.Syntax.Properties | |
Ord Properties Source # | |
Defined in GitHub.Workflow.Command.Syntax.Properties Methods compare :: Properties -> Properties -> Ordering # (<) :: Properties -> Properties -> Bool # (<=) :: Properties -> Properties -> Bool # (>) :: Properties -> Properties -> Bool # (>=) :: Properties -> Properties -> Bool # max :: Properties -> Properties -> Properties # min :: Properties -> Properties -> Properties # | |
HasProperties Properties Source # | |
Defined in GitHub.Workflow.Command.Syntax.Properties Methods | |
ToByteString Properties Source # | |
Defined in GitHub.Workflow.Command.Syntax.Properties Methods toByteStringBuilder :: Properties -> Builder Source # toByteString :: Properties -> ByteString Source # |
class HasProperties a where Source #
Methods
properties :: Lens' a Properties Source #
Instances
HasProperties Command Source # | |
Defined in GitHub.Workflow.Command.Syntax.Command Methods | |
HasProperties Properties Source # | |
Defined in GitHub.Workflow.Command.Syntax.Properties Methods |