module Stratosphere.Outputs
( Output (..)
, output
, Outputs (..)
, name
, description
, value
) where
import Control.Lens hiding ((.=))
import Data.Aeson
import Data.Aeson.Types (Parser)
import Data.Maybe (catMaybes)
import qualified Data.Text as T
import GHC.Exts (IsList(..))
import Stratosphere.Helpers
import Stratosphere.Parameters
import Stratosphere.Values
data Output =
Output
{ outputName :: T.Text
, outputDescription :: Maybe T.Text
, outputValue :: Val T.Text
} deriving (Show)
$(makeFields ''Output)
instance ToRef Output b where
toRef o = Ref (outputName o)
output
:: T.Text
-> Val T.Text
-> Output
output oname oval =
Output
{ outputName = oname
, outputDescription = Nothing
, outputValue = oval
}
outputToJSON :: Output -> Value
outputToJSON Output {..} =
object $ catMaybes
[ Just ("Value" .= outputValue)
, maybeField "Description" outputDescription
]
outputFromJSON :: T.Text -> Object -> Parser Output
outputFromJSON n o =
Output n
<$> o .:? "Description"
<*> o .: "Value"
newtype Outputs = Outputs { unOutputs :: [Output] }
deriving (Show, Monoid)
instance IsList Outputs where
type Item Outputs = Output
fromList = Outputs
toList = unOutputs
instance NamedItem Output where
itemName = outputName
nameToJSON = outputToJSON
nameParseJSON = outputFromJSON
instance ToJSON Outputs where
toJSON = namedItemToJSON . unOutputs
instance FromJSON Outputs where
parseJSON v = Outputs <$> namedItemFromJSON v