module Arion.ExtendedInfo where
import Arion.Aeson
import Control.Lens
import Data.Aeson as Aeson
import Data.Aeson.Lens
import Protolude
import Prelude ()
data Image = Image
{
Image -> Maybe Text
image :: Maybe Text,
Image -> Maybe Text
imageExe :: Maybe Text,
Image -> Text
imageName :: Text,
Image -> Text
imageTag :: Text
}
deriving stock (Image -> Image -> Bool
(Image -> Image -> Bool) -> (Image -> Image -> Bool) -> Eq Image
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Image -> Image -> Bool
== :: Image -> Image -> Bool
$c/= :: Image -> Image -> Bool
/= :: Image -> Image -> Bool
Eq, Int -> Image -> ShowS
[Image] -> ShowS
Image -> String
(Int -> Image -> ShowS)
-> (Image -> String) -> ([Image] -> ShowS) -> Show Image
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Image -> ShowS
showsPrec :: Int -> Image -> ShowS
$cshow :: Image -> String
show :: Image -> String
$cshowList :: [Image] -> ShowS
showList :: [Image] -> ShowS
Show, (forall x. Image -> Rep Image x)
-> (forall x. Rep Image x -> Image) -> Generic Image
forall x. Rep Image x -> Image
forall x. Image -> Rep Image x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Image -> Rep Image x
from :: forall x. Image -> Rep Image x
$cto :: forall x. Rep Image x -> Image
to :: forall x. Rep Image x -> Image
Generic)
deriving anyclass ([Image] -> Value
[Image] -> Encoding
Image -> Value
Image -> Encoding
(Image -> Value)
-> (Image -> Encoding)
-> ([Image] -> Value)
-> ([Image] -> Encoding)
-> ToJSON Image
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: Image -> Value
toJSON :: Image -> Value
$ctoEncoding :: Image -> Encoding
toEncoding :: Image -> Encoding
$ctoJSONList :: [Image] -> Value
toJSONList :: [Image] -> Value
$ctoEncodingList :: [Image] -> Encoding
toEncodingList :: [Image] -> Encoding
Aeson.ToJSON, Value -> Parser [Image]
Value -> Parser Image
(Value -> Parser Image)
-> (Value -> Parser [Image]) -> FromJSON Image
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser Image
parseJSON :: Value -> Parser Image
$cparseJSONList :: Value -> Parser [Image]
parseJSONList :: Value -> Parser [Image]
Aeson.FromJSON)
data ExtendedInfo = ExtendedInfo
{ ExtendedInfo -> Maybe Text
projectName :: Maybe Text,
ExtendedInfo -> [Image]
images :: [Image]
}
deriving stock (ExtendedInfo -> ExtendedInfo -> Bool
(ExtendedInfo -> ExtendedInfo -> Bool)
-> (ExtendedInfo -> ExtendedInfo -> Bool) -> Eq ExtendedInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExtendedInfo -> ExtendedInfo -> Bool
== :: ExtendedInfo -> ExtendedInfo -> Bool
$c/= :: ExtendedInfo -> ExtendedInfo -> Bool
/= :: ExtendedInfo -> ExtendedInfo -> Bool
Eq, Int -> ExtendedInfo -> ShowS
[ExtendedInfo] -> ShowS
ExtendedInfo -> String
(Int -> ExtendedInfo -> ShowS)
-> (ExtendedInfo -> String)
-> ([ExtendedInfo] -> ShowS)
-> Show ExtendedInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExtendedInfo -> ShowS
showsPrec :: Int -> ExtendedInfo -> ShowS
$cshow :: ExtendedInfo -> String
show :: ExtendedInfo -> String
$cshowList :: [ExtendedInfo] -> ShowS
showList :: [ExtendedInfo] -> ShowS
Show)
loadExtendedInfoFromPath :: FilePath -> IO ExtendedInfo
loadExtendedInfoFromPath :: String -> IO ExtendedInfo
loadExtendedInfoFromPath String
fp = do
Value
v <- String -> IO Value
forall a. FromJSON a => String -> IO a
decodeFile String
fp
ExtendedInfo -> IO ExtendedInfo
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
ExtendedInfo
{
$sel:projectName:ExtendedInfo :: Maybe Text
projectName = Value
v Value -> Getting (First Text) Value Text -> Maybe Text
forall s a. s -> Getting (First a) s a -> Maybe a
^? Key -> Traversal' Value Value
forall t. AsValue t => Key -> Traversal' t Value
key Key
"x-arion" ((Value -> Const (First Text) Value)
-> Value -> Const (First Text) Value)
-> Getting (First Text) Value Text
-> Getting (First Text) Value Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> Traversal' Value Value
forall t. AsValue t => Key -> Traversal' t Value
key Key
"project" ((Value -> Const (First Text) Value)
-> Value -> Const (First Text) Value)
-> Getting (First Text) Value Text
-> Getting (First Text) Value Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> Traversal' Value Value
forall t. AsValue t => Key -> Traversal' t Value
key Key
"name" ((Value -> Const (First Text) Value)
-> Value -> Const (First Text) Value)
-> Getting (First Text) Value Text
-> Getting (First Text) Value Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting (First Text) Value Text
forall t. AsValue t => Prism' t Text
Prism' Value Text
_String,
$sel:images:ExtendedInfo :: [Image]
images = (Value
v :: Aeson.Value) Value -> Getting (Endo [Image]) Value Image -> [Image]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. Key -> Traversal' Value Value
forall t. AsValue t => Key -> Traversal' t Value
key Key
"x-arion" ((Value -> Const (Endo [Image]) Value)
-> Value -> Const (Endo [Image]) Value)
-> Getting (Endo [Image]) Value Image
-> Getting (Endo [Image]) Value Image
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> Traversal' Value Value
forall t. AsValue t => Key -> Traversal' t Value
key Key
"images" ((Value -> Const (Endo [Image]) Value)
-> Value -> Const (Endo [Image]) Value)
-> Getting (Endo [Image]) Value Image
-> Getting (Endo [Image]) Value Image
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector Value -> Const (Endo [Image]) (Vector Value))
-> Value -> Const (Endo [Image]) Value
forall t. AsValue t => Prism' t (Vector Value)
Prism' Value (Vector Value)
_Array ((Vector Value -> Const (Endo [Image]) (Vector Value))
-> Value -> Const (Endo [Image]) Value)
-> ((Image -> Const (Endo [Image]) Image)
-> Vector Value -> Const (Endo [Image]) (Vector Value))
-> Getting (Endo [Image]) Value Image
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Value -> Const (Endo [Image]) Value)
-> Vector Value -> Const (Endo [Image]) (Vector Value)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Vector a -> f (Vector b)
traverse ((Value -> Const (Endo [Image]) Value)
-> Vector Value -> Const (Endo [Image]) (Vector Value))
-> Getting (Endo [Image]) Value Image
-> (Image -> Const (Endo [Image]) Image)
-> Vector Value
-> Const (Endo [Image]) (Vector Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting (Endo [Image]) Value Image
forall t a b. (AsJSON t, FromJSON a, ToJSON b) => Prism t t a b
forall a b. (FromJSON a, ToJSON b) => Prism Value Value a b
Prism Value Value Image Image
_JSON
}