| Safe Haskell | Safe-Inferred |
|---|---|
| Language | GHC2021 |
GitHub.Workflow.Command.Annotation
Synopsis
- debug :: Message -> Debug
- newtype Debug = Debug {}
- error :: Message -> Error
- data Error = Error {}
- warning :: Message -> Warning
- data Warning = Warning {}
- notice :: Message -> Notice
- data Notice = Notice {}
- newtype Message = Message {}
- class FromMessage a where
- fromMessage :: Message -> a
- data Properties = Properties {}
- 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
- class Monad m => MonadCommand m where
- executeCommand :: ToCommand a => a -> m ()
- class ToCommand a where
- addToCommand :: a -> Command -> Command
- toCommand :: ToCommand a => a -> Command
- class ToByteString a where
- toByteStringBuilder :: a -> Builder
- toByteString :: a -> ByteString
- printByteStringLn :: (ToByteString a, MonadIO m) => a -> m ()
Annotations
Debug
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 | |
Error
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 | |
Warning
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 | |
Notice
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 | |
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 FromMessage a where Source #
Methods
fromMessage :: Message -> a Source #
Instances
| FromMessage Debug Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Debug Methods fromMessage :: Message -> Debug Source # | |
| FromMessage Error Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Error Methods fromMessage :: Message -> Error Source # | |
| FromMessage Notice Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Notice Methods fromMessage :: Message -> Notice Source # | |
| FromMessage Warning Source # | |
Defined in GitHub.Workflow.Command.Annotation.Commands.Warning Methods fromMessage :: Message -> Warning Source # | |
| FromMessage Message Source # | |
Defined in GitHub.Workflow.Command.Syntax.Message Methods fromMessage :: Message -> Message Source # | |
Properties
data Properties Source #
Constructors
| Properties | |
Instances
| HasLocationMaybe Properties Source # | |
| GetProperties Properties Source # | |
Defined in GitHub.Workflow.Command.Annotation.Properties Methods getProperties :: Properties -> Properties Source # | |
| HasProperties Properties Source # | |
Defined in GitHub.Workflow.Command.Annotation.Properties Methods annotationProperties :: Lens' Properties Properties Source # | |
| AddToProperties Properties Source # | |
Defined in GitHub.Workflow.Command.Annotation.Properties Methods addToProperties :: Properties -> Properties0 -> Properties0 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 # | |
Output
class Monad m => MonadCommand m where Source #
Monadic context in which GitHub workflow commands may be executed
- For the most basic uses, use the
IOinstance, which prints commands tostdout. - For custom monads that support
MonadIO, you may deriveMonadCommandviaPrintCommandsto get the same behavior thatIOexhibits. - A program that wishes to accommodate running in both GitHub and non-GitHub contexts
may wish to define a more sophisicated
MonadCommandinstance that prints GitHub workflow commands only when theGITHUB_ACTIONSenvironment 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 # | |
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 # | |
class ToByteString a where Source #
Minimal complete definition
Instances
printByteStringLn :: (ToByteString a, MonadIO m) => a -> m () Source #