module GitHub.Workflow.Command.Annotation.Commands.Warning
( warning
, Warning (..)
) where
import Control.Category
import Control.Lens.TH
import GitHub.Workflow.Command.Annotation.Commands.Generic
import GitHub.Workflow.Command.Annotation.Location
import GitHub.Workflow.Command.Annotation.Properties
import GitHub.Workflow.Command.Annotation.Properties qualified as Properties
import GitHub.Workflow.Command.Syntax
( FromMessage
, HasMessage
, Message
, ToByteString
, ToCommand
)
import GitHub.Workflow.Command.Syntax qualified as Syntax
data Warning = Warning
{ Warning -> Message
message :: Message
, Warning -> Properties
properties :: Properties
}
makeLensesFor
[ ("message", "warningMessage")
, ("properties", "warningProperties")
]
''Warning
deriving via GenericAnnotation Warning instance ToCommand Warning
deriving via GenericAnnotation Warning instance ToByteString Warning
instance IsAnnotationType Warning where
annotationTypeName :: Name
annotationTypeName = Name
"warning"
instance HasMessage Warning where
message :: Lens' Warning Message
message = (Message -> f Message) -> Warning -> f Warning
Lens' Warning Message
warningMessage
instance HasProperties Warning where
annotationProperties :: Lens' Warning Properties
annotationProperties = (Properties -> f Properties) -> Warning -> f Warning
Lens' Warning Properties
warningProperties
instance HasLocationMaybe Warning where
location :: Lens' Warning (Maybe Location)
location = (Properties -> f Properties) -> Warning -> f Warning
forall a. HasProperties a => Lens' a Properties
Lens' Warning Properties
annotationProperties ((Properties -> f Properties) -> Warning -> f Warning)
-> ((Maybe Location -> f (Maybe Location))
-> Properties -> f Properties)
-> (Maybe Location -> f (Maybe Location))
-> Warning
-> f Warning
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Maybe Location -> f (Maybe Location))
-> Properties -> f Properties
forall a. HasLocationMaybe a => Lens' a (Maybe Location)
Lens' Properties (Maybe Location)
location
instance FromMessage Warning where
fromMessage :: Message -> Warning
fromMessage = Message -> Warning
warning
instance GetProperties Warning where
getProperties :: Warning -> Properties
getProperties = (.properties)
warning :: Message -> Warning
warning :: Message -> Warning
warning Message
x = Warning {$sel:message:Warning :: Message
message = Message
x, $sel:properties:Warning :: Properties
properties = Properties
Properties.empty}