module Stratosphere.Output
( Output(..)
, OutputExport(..)
, Outputs(..)
, mkOutput
)
where
import GHC.Exts (IsList(..))
import Stratosphere.NamedItem
import Stratosphere.Prelude
import Stratosphere.Property
import Stratosphere.Value
import qualified Data.Aeson as JSON
data OutputExport
= OutputExport { OutputExport -> Value Text
outputExportName :: Value Text }
deriving stock (Int -> OutputExport -> ShowS
[OutputExport] -> ShowS
OutputExport -> String
(Int -> OutputExport -> ShowS)
-> (OutputExport -> String)
-> ([OutputExport] -> ShowS)
-> Show OutputExport
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OutputExport -> ShowS
showsPrec :: Int -> OutputExport -> ShowS
$cshow :: OutputExport -> String
show :: OutputExport -> String
$cshowList :: [OutputExport] -> ShowS
showList :: [OutputExport] -> ShowS
Show, OutputExport -> OutputExport -> Bool
(OutputExport -> OutputExport -> Bool)
-> (OutputExport -> OutputExport -> Bool) -> Eq OutputExport
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OutputExport -> OutputExport -> Bool
== :: OutputExport -> OutputExport -> Bool
$c/= :: OutputExport -> OutputExport -> Bool
/= :: OutputExport -> OutputExport -> Bool
Eq)
instance JSON.ToJSON OutputExport where
toJSON :: OutputExport -> Value
toJSON OutputExport{Value Text
outputExportName :: OutputExport -> Value Text
outputExportName :: Value Text
..}
= [Pair] -> Value
JSON.object
[ Key
"Name" Key -> Value Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Value Text
outputExportName
]
data Output = Output
{ Output -> Text
name :: Text
, Output -> Maybe Text
condition :: Maybe Text
, Output -> Maybe Text
description :: Maybe Text
, Output -> Value Text
value :: Value Text
, Output -> Maybe OutputExport
export :: Maybe OutputExport
} deriving (Int -> Output -> ShowS
[Output] -> ShowS
Output -> String
(Int -> Output -> ShowS)
-> (Output -> String) -> ([Output] -> ShowS) -> Show Output
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Output -> ShowS
showsPrec :: Int -> Output -> ShowS
$cshow :: Output -> String
show :: Output -> String
$cshowList :: [Output] -> ShowS
showList :: [Output] -> ShowS
Show, Output -> Output -> Bool
(Output -> Output -> Bool)
-> (Output -> Output -> Bool) -> Eq Output
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Output -> Output -> Bool
== :: Output -> Output -> Bool
$c/= :: Output -> Output -> Bool
/= :: Output -> Output -> Bool
Eq)
instance ToRef Output b where
toRef :: Output -> Value b
toRef Output{Maybe Text
Maybe OutputExport
Text
Value Text
name :: Output -> Text
condition :: Output -> Maybe Text
description :: Output -> Maybe Text
value :: Output -> Value Text
export :: Output -> Maybe OutputExport
name :: Text
condition :: Maybe Text
description :: Maybe Text
value :: Value Text
export :: Maybe OutputExport
..} = Text -> Value b
forall a. Text -> Value a
Ref Text
name
instance Property "Name" Output where
type PropertyType "Name" Output = Text
set :: PropertyType "Name" Output -> Output -> Output
set PropertyType "Name" Output
newValue Output{Maybe Text
Maybe OutputExport
Text
Value Text
name :: Output -> Text
condition :: Output -> Maybe Text
description :: Output -> Maybe Text
value :: Output -> Value Text
export :: Output -> Maybe OutputExport
name :: Text
condition :: Maybe Text
description :: Maybe Text
value :: Value Text
export :: Maybe OutputExport
..} = Output{name :: Text
name = Text
PropertyType "Name" Output
newValue, Maybe Text
Maybe OutputExport
Value Text
condition :: Maybe Text
description :: Maybe Text
value :: Value Text
export :: Maybe OutputExport
condition :: Maybe Text
description :: Maybe Text
value :: Value Text
export :: Maybe OutputExport
..}
instance Property "Condition" Output where
type PropertyType "Condition" Output = Text
set :: PropertyType "Condition" Output -> Output -> Output
set PropertyType "Condition" Output
newValue Output{Maybe Text
Maybe OutputExport
Text
Value Text
name :: Output -> Text
condition :: Output -> Maybe Text
description :: Output -> Maybe Text
value :: Output -> Value Text
export :: Output -> Maybe OutputExport
name :: Text
condition :: Maybe Text
description :: Maybe Text
value :: Value Text
export :: Maybe OutputExport
..} = Output{condition :: Maybe Text
condition = Text -> Maybe Text
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
PropertyType "Condition" Output
newValue, Maybe Text
Maybe OutputExport
Text
Value Text
name :: Text
description :: Maybe Text
value :: Value Text
export :: Maybe OutputExport
name :: Text
description :: Maybe Text
value :: Value Text
export :: Maybe OutputExport
..}
instance Property "Description" Output where
type PropertyType "Description" Output = Text
set :: PropertyType "Description" Output -> Output -> Output
set PropertyType "Description" Output
newValue Output{Maybe Text
Maybe OutputExport
Text
Value Text
name :: Output -> Text
condition :: Output -> Maybe Text
description :: Output -> Maybe Text
value :: Output -> Value Text
export :: Output -> Maybe OutputExport
name :: Text
condition :: Maybe Text
description :: Maybe Text
value :: Value Text
export :: Maybe OutputExport
..} = Output{description :: Maybe Text
description = Text -> Maybe Text
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
PropertyType "Description" Output
newValue, Maybe Text
Maybe OutputExport
Text
Value Text
name :: Text
condition :: Maybe Text
value :: Value Text
export :: Maybe OutputExport
name :: Text
condition :: Maybe Text
value :: Value Text
export :: Maybe OutputExport
..}
instance Property "Value" Output where
type PropertyType "Value" Output = Value Text
set :: PropertyType "Value" Output -> Output -> Output
set PropertyType "Value" Output
newValue Output{Maybe Text
Maybe OutputExport
Text
Value Text
name :: Output -> Text
condition :: Output -> Maybe Text
description :: Output -> Maybe Text
value :: Output -> Value Text
export :: Output -> Maybe OutputExport
name :: Text
condition :: Maybe Text
description :: Maybe Text
value :: Value Text
export :: Maybe OutputExport
..} = Output{value :: Value Text
value = PropertyType "Value" Output
Value Text
newValue, Maybe Text
Maybe OutputExport
Text
name :: Text
condition :: Maybe Text
description :: Maybe Text
export :: Maybe OutputExport
name :: Text
condition :: Maybe Text
description :: Maybe Text
export :: Maybe OutputExport
..}
instance Property "Export" Output where
type PropertyType "Export" Output = OutputExport
set :: PropertyType "Export" Output -> Output -> Output
set PropertyType "Export" Output
newValue Output{Maybe Text
Maybe OutputExport
Text
Value Text
name :: Output -> Text
condition :: Output -> Maybe Text
description :: Output -> Maybe Text
value :: Output -> Value Text
export :: Output -> Maybe OutputExport
name :: Text
condition :: Maybe Text
description :: Maybe Text
value :: Value Text
export :: Maybe OutputExport
..} = Output{export :: Maybe OutputExport
export = OutputExport -> Maybe OutputExport
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure PropertyType "Export" Output
OutputExport
newValue, Maybe Text
Text
Value Text
name :: Text
condition :: Maybe Text
description :: Maybe Text
value :: Value Text
name :: Text
condition :: Maybe Text
description :: Maybe Text
value :: Value Text
..}
mkOutput
:: Text
-> Value Text
-> Output
mkOutput :: Text -> Value Text -> Output
mkOutput Text
name Value Text
value =
Output
{ condition :: Maybe Text
condition = Maybe Text
forall a. Maybe a
Nothing
, description :: Maybe Text
description = Maybe Text
forall a. Maybe a
Nothing
, export :: Maybe OutputExport
export = Maybe OutputExport
forall a. Maybe a
Nothing
, Text
Value Text
name :: Text
value :: Value Text
name :: Text
value :: Value Text
..
}
outputToJSON :: Output -> JSON.Value
outputToJSON :: Output -> Value
outputToJSON Output{Maybe Text
Maybe OutputExport
Text
Value Text
name :: Output -> Text
condition :: Output -> Maybe Text
description :: Output -> Maybe Text
value :: Output -> Value Text
export :: Output -> Maybe OutputExport
name :: Text
condition :: Maybe Text
description :: Maybe Text
value :: Value Text
export :: Maybe OutputExport
..}
= [Pair] -> Value
JSON.object
([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
catMaybes
[ Pair -> Maybe Pair
forall a. a -> Maybe a
Just (Key
"Value" Key -> Value Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Value Text
value)
, Key -> Maybe Text -> Maybe Pair
forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
maybeField Key
"Condition" Maybe Text
condition
, Key -> Maybe Text -> Maybe Pair
forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
maybeField Key
"Description" Maybe Text
description
, Key -> Maybe OutputExport -> Maybe Pair
forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
maybeField Key
"Export" Maybe OutputExport
export
]
newtype Outputs = Outputs { Outputs -> [Output]
outputs :: [Output] }
deriving stock (Int -> Outputs -> ShowS
[Outputs] -> ShowS
Outputs -> String
(Int -> Outputs -> ShowS)
-> (Outputs -> String) -> ([Outputs] -> ShowS) -> Show Outputs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Outputs -> ShowS
showsPrec :: Int -> Outputs -> ShowS
$cshow :: Outputs -> String
show :: Outputs -> String
$cshowList :: [Outputs] -> ShowS
showList :: [Outputs] -> ShowS
Show, Outputs -> Outputs -> Bool
(Outputs -> Outputs -> Bool)
-> (Outputs -> Outputs -> Bool) -> Eq Outputs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Outputs -> Outputs -> Bool
== :: Outputs -> Outputs -> Bool
$c/= :: Outputs -> Outputs -> Bool
/= :: Outputs -> Outputs -> Bool
Eq)
deriving newtype (Semigroup Outputs
Outputs
Semigroup Outputs =>
Outputs
-> (Outputs -> Outputs -> Outputs)
-> ([Outputs] -> Outputs)
-> Monoid Outputs
[Outputs] -> Outputs
Outputs -> Outputs -> Outputs
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: Outputs
mempty :: Outputs
$cmappend :: Outputs -> Outputs -> Outputs
mappend :: Outputs -> Outputs -> Outputs
$cmconcat :: [Outputs] -> Outputs
mconcat :: [Outputs] -> Outputs
Monoid, (Element Outputs -> Element Outputs) -> Outputs -> Outputs
((Element Outputs -> Element Outputs) -> Outputs -> Outputs)
-> MonoFunctor Outputs
forall mono.
((Element mono -> Element mono) -> mono -> mono)
-> MonoFunctor mono
$comap :: (Element Outputs -> Element Outputs) -> Outputs -> Outputs
omap :: (Element Outputs -> Element Outputs) -> Outputs -> Outputs
MonoFunctor, NonEmpty Outputs -> Outputs
Outputs -> Outputs -> Outputs
(Outputs -> Outputs -> Outputs)
-> (NonEmpty Outputs -> Outputs)
-> (forall b. Integral b => b -> Outputs -> Outputs)
-> Semigroup Outputs
forall b. Integral b => b -> Outputs -> Outputs
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: Outputs -> Outputs -> Outputs
<> :: Outputs -> Outputs -> Outputs
$csconcat :: NonEmpty Outputs -> Outputs
sconcat :: NonEmpty Outputs -> Outputs
$cstimes :: forall b. Integral b => b -> Outputs -> Outputs
stimes :: forall b. Integral b => b -> Outputs -> Outputs
Semigroup)
type instance Element Outputs = Output
instance IsList Outputs where
type Item Outputs = Output
fromList :: [Item Outputs] -> Outputs
fromList = [Item Outputs] -> Outputs
[Output] -> Outputs
Outputs
toList :: Outputs -> [Item Outputs]
toList = (.outputs)
instance NamedItem Output where
itemName :: Output -> Text
itemName = (.name)
nameToJSON :: Output -> Value
nameToJSON = Output -> Value
outputToJSON
instance JSON.ToJSON Outputs where
toJSON :: Outputs -> Value
toJSON = [Output] -> Value
forall a. NamedItem a => [a] -> Value
namedItemToJSON ([Output] -> Value) -> (Outputs -> [Output]) -> Outputs -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (.outputs)