github-workflow-commands-0.0.1.0: GitHub Actions workflow commands
Safe HaskellSafe-Inferred
LanguageGHC2021

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

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 to stdout.
  • For custom monads that support MonadIO, you may derive MonadCommand via PrintCommands to get the same behavior that IO 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 the GITHUB_ACTIONS environment variable is present, and otherwise takes some other more context-appropriate action.

Methods

executeCommand :: ToCommand a => a -> m () Source #

Instances

Instances details
MonadCommand IO Source # 
Instance details

Defined in GitHub.Workflow.Command.Execution

Methods

executeCommand :: ToCommand a => a -> IO () Source #

MonadIO m => MonadCommand (PrintCommands m) Source # 
Instance details

Defined in GitHub.Workflow.Command.Execution

Methods

executeCommand :: ToCommand a => a -> PrintCommands m () Source #

newtype PrintCommands m a Source #

Constructors

PrintCommands (m a) 

Instances

Instances details
MonadIO m => MonadIO (PrintCommands m) Source # 
Instance details

Defined in GitHub.Workflow.Command.Execution

Methods

liftIO :: IO a -> PrintCommands m a #

Applicative m => Applicative (PrintCommands m) Source # 
Instance details

Defined in GitHub.Workflow.Command.Execution

Methods

pure :: a -> PrintCommands m a #

(<*>) :: PrintCommands m (a -> b) -> PrintCommands m a -> PrintCommands m b #

liftA2 :: (a -> b -> c) -> PrintCommands m a -> PrintCommands m b -> PrintCommands m c #

(*>) :: PrintCommands m a -> PrintCommands m b -> PrintCommands m b #

(<*) :: PrintCommands m a -> PrintCommands m b -> PrintCommands m a #

Functor m => Functor (PrintCommands m) Source # 
Instance details

Defined in GitHub.Workflow.Command.Execution

Methods

fmap :: (a -> b) -> PrintCommands m a -> PrintCommands m b #

(<$) :: a -> PrintCommands m b -> PrintCommands m a #

Monad m => Monad (PrintCommands m) Source # 
Instance details

Defined in GitHub.Workflow.Command.Execution

Methods

(>>=) :: PrintCommands m a -> (a -> PrintCommands m b) -> PrintCommands m b #

(>>) :: PrintCommands m a -> PrintCommands m b -> PrintCommands m b #

return :: a -> PrintCommands m a #

MonadIO m => MonadCommand (PrintCommands m) Source # 
Instance details

Defined in GitHub.Workflow.Command.Execution

Methods

executeCommand :: ToCommand a => a -> PrintCommands m () Source #

Commands

class ToCommand a where Source #

Methods

addToCommand :: a -> Command -> Command Source #

Instances

Instances details
ToCommand Debug Source # 
Instance details

Defined in GitHub.Workflow.Command.Annotation.Commands.Debug

ToCommand Error Source # 
Instance details

Defined in GitHub.Workflow.Command.Annotation.Commands.Error

ToCommand Notice Source # 
Instance details

Defined in GitHub.Workflow.Command.Annotation.Commands.Notice

ToCommand Warning Source # 
Instance details

Defined in GitHub.Workflow.Command.Annotation.Commands.Warning

ToCommand GroupEnd Source # 
Instance details

Defined in GitHub.Workflow.Command.Grouping

ToCommand GroupStart Source # 
Instance details

Defined in GitHub.Workflow.Command.Grouping

ToCommand AddMask Source # 
Instance details

Defined in GitHub.Workflow.Command.Masking

ToCommand ResumeCommands Source # 
Instance details

Defined in GitHub.Workflow.Command.Stopping

ToCommand StopCommands Source # 
Instance details

Defined in GitHub.Workflow.Command.Stopping

(IsAnnotationType a, HasMessage a, GetProperties a) => ToCommand (GenericAnnotation a) Source # 
Instance details

Defined in GitHub.Workflow.Command.Annotation.Commands.Generic

Setting a debug message

Setting a notice message

data Notice Source #

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 

Setting a warning message

data Warning Source #

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 

Setting an error message

data Error Source #

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 

Grouping log lines

group Source #

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 

Fields

Instances

Instances details
ToCommand GroupStart Source # 
Instance details

Defined in GitHub.Workflow.Command.Grouping

data GroupEnd Source #

Ends a group

Constructors

GroupEnd 

Instances

Instances details
ToCommand GroupEnd Source # 
Instance details

Defined in GitHub.Workflow.Command.Grouping

Masking a value in a log

newtype AddMask Source #

Prevents a string or variable from being printed in the log

GitHub documentation: Masking a value in a log

Constructors

AddMask 

Fields

  • value :: Text

    An environment variable or string

Instances

Instances details
ToCommand AddMask Source # 
Instance details

Defined in GitHub.Workflow.Command.Masking

Stopping and starting workflow commands

suspendCommands Source #

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

Location

data Location Source #

Constructors

Location 

Fields

File

newtype File Source #

Constructors

File 

Fields

Instances

Instances details
IsString File Source # 
Instance details

Defined in GitHub.Workflow.Command.Annotation.File

Methods

fromString :: String -> File #

Show File Source # 
Instance details

Defined in GitHub.Workflow.Command.Annotation.File

Methods

showsPrec :: Int -> File -> ShowS #

show :: File -> String #

showList :: [File] -> ShowS #

Eq File Source # 
Instance details

Defined in GitHub.Workflow.Command.Annotation.File

Methods

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

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

Ord File Source # 
Instance details

Defined in GitHub.Workflow.Command.Annotation.File

Methods

compare :: File -> File -> Ordering #

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

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

(>) :: File -> File -> Bool #

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

max :: File -> File -> File #

min :: File -> File -> File #

Position

data Position Source #

Where an annotation is marked within a file

Constructors

Position 

Fields

data Extent Source #

Extra positional data, as a modification to the start Line

Constructors

WithinLine Columns 
ToLine Line 

data Columns Source #

Constructors

Columns 

Fields

newtype Line Source #

Constructors

Line 

Fields

Instances

Instances details
Num Line Source # 
Instance details

Defined in GitHub.Workflow.Command.Annotation.Position.Line

Methods

(+) :: Line -> Line -> Line #

(-) :: Line -> Line -> Line #

(*) :: Line -> Line -> Line #

negate :: Line -> Line #

abs :: Line -> Line #

signum :: Line -> Line #

fromInteger :: Integer -> Line #

Show Line Source # 
Instance details

Defined in GitHub.Workflow.Command.Annotation.Position.Line

Methods

showsPrec :: Int -> Line -> ShowS #

show :: Line -> String #

showList :: [Line] -> ShowS #

Eq Line Source # 
Instance details

Defined in GitHub.Workflow.Command.Annotation.Position.Line

Methods

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

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

Ord Line Source # 
Instance details

Defined in GitHub.Workflow.Command.Annotation.Position.Line

Methods

compare :: Line -> Line -> Ordering #

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

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

(>) :: Line -> Line -> Bool #

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

max :: Line -> Line -> Line #

min :: Line -> Line -> Line #

Anatomy of a command

data Command Source #

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

Instances details
IsString Command Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Command

Methods

fromString :: String -> Command #

Show Command Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Command

Eq Command Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Command

Methods

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

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

Ord Command Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Command

HasMessage Command Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Command

HasName Command Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Command

HasProperties Command Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Command

ToByteString Command Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Command

Name

newtype Name Source #

Constructors

Name 

Fields

Instances

Instances details
IsString Name Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Name

Methods

fromString :: String -> Name #

Show Name Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Name

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Eq Name Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Name

Methods

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

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

Ord Name Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Name

Methods

compare :: Name -> Name -> Ordering #

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

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

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

HasName Name Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Name

ToByteString Name Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Name

class HasName a where Source #

Methods

name :: Lens' a Name Source #

Instances

Instances details
HasName Command Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Command

HasName Name Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Name

Message

Properties

newtype Key Source #

Constructors

Key 

Fields

Instances

Instances details
IsString Key Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Key

Methods

fromString :: String -> Key #

Show Key Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Key

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Eq Key Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Key

Methods

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

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

Ord Key Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Key

Methods

compare :: Key -> Key -> Ordering #

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

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

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

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

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

ToByteString Key Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Key

newtype Value Source #

Constructors

Value 

Fields

Instances

Instances details
IsString Value Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Value

Methods

fromString :: String -> Value #

Show Value Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Value

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Eq Value Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Value

Methods

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

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

Ord Value Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Value

Methods

compare :: Value -> Value -> Ordering #

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

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

(>) :: Value -> Value -> Bool #

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

max :: Value -> Value -> Value #

min :: Value -> Value -> Value #

ToByteString Value Source # 
Instance details

Defined in GitHub.Workflow.Command.Syntax.Value