{-# LANGUAGE OverloadedStrings #-}
module B9.Artifact.Content.CloudConfigYaml
( CloudConfigYaml (..),
cloudConfigFileHeader,
)
where
import B9.Artifact.Content.AST
import B9.Artifact.Content.YamlObject
import B9.Text
import Control.Parallel.Strategies (NFData)
import Data.Data
( Data,
Typeable,
)
import Data.Hashable (Hashable)
import Data.Text as Text
import GHC.Generics (Generic)
import Test.QuickCheck (Arbitrary)
newtype CloudConfigYaml
= MkCloudConfigYaml
{ CloudConfigYaml -> YamlObject
fromCloudConfigYaml :: YamlObject
}
deriving (Int -> CloudConfigYaml -> Int
CloudConfigYaml -> Int
(Int -> CloudConfigYaml -> Int)
-> (CloudConfigYaml -> Int) -> Hashable CloudConfigYaml
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: CloudConfigYaml -> Int
$chash :: CloudConfigYaml -> Int
hashWithSalt :: Int -> CloudConfigYaml -> Int
$chashWithSalt :: Int -> CloudConfigYaml -> Int
Hashable, CloudConfigYaml -> ()
(CloudConfigYaml -> ()) -> NFData CloudConfigYaml
forall a. (a -> ()) -> NFData a
rnf :: CloudConfigYaml -> ()
$crnf :: CloudConfigYaml -> ()
NFData, CloudConfigYaml -> CloudConfigYaml -> Bool
(CloudConfigYaml -> CloudConfigYaml -> Bool)
-> (CloudConfigYaml -> CloudConfigYaml -> Bool)
-> Eq CloudConfigYaml
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CloudConfigYaml -> CloudConfigYaml -> Bool
$c/= :: CloudConfigYaml -> CloudConfigYaml -> Bool
== :: CloudConfigYaml -> CloudConfigYaml -> Bool
$c== :: CloudConfigYaml -> CloudConfigYaml -> Bool
Eq, Typeable CloudConfigYaml
DataType
Constr
Typeable CloudConfigYaml
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CloudConfigYaml -> c CloudConfigYaml)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CloudConfigYaml)
-> (CloudConfigYaml -> Constr)
-> (CloudConfigYaml -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CloudConfigYaml))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CloudConfigYaml))
-> ((forall b. Data b => b -> b)
-> CloudConfigYaml -> CloudConfigYaml)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CloudConfigYaml -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CloudConfigYaml -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CloudConfigYaml -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CloudConfigYaml -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CloudConfigYaml -> m CloudConfigYaml)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CloudConfigYaml -> m CloudConfigYaml)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CloudConfigYaml -> m CloudConfigYaml)
-> Data CloudConfigYaml
CloudConfigYaml -> DataType
CloudConfigYaml -> Constr
(forall b. Data b => b -> b) -> CloudConfigYaml -> CloudConfigYaml
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CloudConfigYaml -> c CloudConfigYaml
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CloudConfigYaml
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CloudConfigYaml -> u
forall u. (forall d. Data d => d -> u) -> CloudConfigYaml -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CloudConfigYaml -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CloudConfigYaml -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CloudConfigYaml -> m CloudConfigYaml
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CloudConfigYaml -> m CloudConfigYaml
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CloudConfigYaml
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CloudConfigYaml -> c CloudConfigYaml
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CloudConfigYaml)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CloudConfigYaml)
$cMkCloudConfigYaml :: Constr
$tCloudConfigYaml :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> CloudConfigYaml -> m CloudConfigYaml
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CloudConfigYaml -> m CloudConfigYaml
gmapMp :: (forall d. Data d => d -> m d)
-> CloudConfigYaml -> m CloudConfigYaml
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CloudConfigYaml -> m CloudConfigYaml
gmapM :: (forall d. Data d => d -> m d)
-> CloudConfigYaml -> m CloudConfigYaml
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CloudConfigYaml -> m CloudConfigYaml
gmapQi :: Int -> (forall d. Data d => d -> u) -> CloudConfigYaml -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CloudConfigYaml -> u
gmapQ :: (forall d. Data d => d -> u) -> CloudConfigYaml -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> CloudConfigYaml -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CloudConfigYaml -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CloudConfigYaml -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CloudConfigYaml -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CloudConfigYaml -> r
gmapT :: (forall b. Data b => b -> b) -> CloudConfigYaml -> CloudConfigYaml
$cgmapT :: (forall b. Data b => b -> b) -> CloudConfigYaml -> CloudConfigYaml
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CloudConfigYaml)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CloudConfigYaml)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c CloudConfigYaml)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CloudConfigYaml)
dataTypeOf :: CloudConfigYaml -> DataType
$cdataTypeOf :: CloudConfigYaml -> DataType
toConstr :: CloudConfigYaml -> Constr
$ctoConstr :: CloudConfigYaml -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CloudConfigYaml
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CloudConfigYaml
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CloudConfigYaml -> c CloudConfigYaml
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CloudConfigYaml -> c CloudConfigYaml
$cp1Data :: Typeable CloudConfigYaml
Data, Typeable, (forall x. CloudConfigYaml -> Rep CloudConfigYaml x)
-> (forall x. Rep CloudConfigYaml x -> CloudConfigYaml)
-> Generic CloudConfigYaml
forall x. Rep CloudConfigYaml x -> CloudConfigYaml
forall x. CloudConfigYaml -> Rep CloudConfigYaml x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CloudConfigYaml x -> CloudConfigYaml
$cfrom :: forall x. CloudConfigYaml -> Rep CloudConfigYaml x
Generic, Gen CloudConfigYaml
Gen CloudConfigYaml
-> (CloudConfigYaml -> [CloudConfigYaml])
-> Arbitrary CloudConfigYaml
CloudConfigYaml -> [CloudConfigYaml]
forall a. Gen a -> (a -> [a]) -> Arbitrary a
shrink :: CloudConfigYaml -> [CloudConfigYaml]
$cshrink :: CloudConfigYaml -> [CloudConfigYaml]
arbitrary :: Gen CloudConfigYaml
$carbitrary :: Gen CloudConfigYaml
Arbitrary, ReadPrec [CloudConfigYaml]
ReadPrec CloudConfigYaml
Int -> ReadS CloudConfigYaml
ReadS [CloudConfigYaml]
(Int -> ReadS CloudConfigYaml)
-> ReadS [CloudConfigYaml]
-> ReadPrec CloudConfigYaml
-> ReadPrec [CloudConfigYaml]
-> Read CloudConfigYaml
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CloudConfigYaml]
$creadListPrec :: ReadPrec [CloudConfigYaml]
readPrec :: ReadPrec CloudConfigYaml
$creadPrec :: ReadPrec CloudConfigYaml
readList :: ReadS [CloudConfigYaml]
$creadList :: ReadS [CloudConfigYaml]
readsPrec :: Int -> ReadS CloudConfigYaml
$creadsPrec :: Int -> ReadS CloudConfigYaml
Read, Int -> CloudConfigYaml -> ShowS
[CloudConfigYaml] -> ShowS
CloudConfigYaml -> String
(Int -> CloudConfigYaml -> ShowS)
-> (CloudConfigYaml -> String)
-> ([CloudConfigYaml] -> ShowS)
-> Show CloudConfigYaml
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CloudConfigYaml] -> ShowS
$cshowList :: [CloudConfigYaml] -> ShowS
show :: CloudConfigYaml -> String
$cshow :: CloudConfigYaml -> String
showsPrec :: Int -> CloudConfigYaml -> ShowS
$cshowsPrec :: Int -> CloudConfigYaml -> ShowS
Show, b -> CloudConfigYaml -> CloudConfigYaml
NonEmpty CloudConfigYaml -> CloudConfigYaml
CloudConfigYaml -> CloudConfigYaml -> CloudConfigYaml
(CloudConfigYaml -> CloudConfigYaml -> CloudConfigYaml)
-> (NonEmpty CloudConfigYaml -> CloudConfigYaml)
-> (forall b.
Integral b =>
b -> CloudConfigYaml -> CloudConfigYaml)
-> Semigroup CloudConfigYaml
forall b. Integral b => b -> CloudConfigYaml -> CloudConfigYaml
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: b -> CloudConfigYaml -> CloudConfigYaml
$cstimes :: forall b. Integral b => b -> CloudConfigYaml -> CloudConfigYaml
sconcat :: NonEmpty CloudConfigYaml -> CloudConfigYaml
$csconcat :: NonEmpty CloudConfigYaml -> CloudConfigYaml
<> :: CloudConfigYaml -> CloudConfigYaml -> CloudConfigYaml
$c<> :: CloudConfigYaml -> CloudConfigYaml -> CloudConfigYaml
Semigroup)
cloudConfigFileHeader :: Text
= Text
"#cloud-config\n"
instance FromAST CloudConfigYaml where
fromAST :: AST c CloudConfigYaml -> Eff e CloudConfigYaml
fromAST AST c CloudConfigYaml
ast = YamlObject -> CloudConfigYaml
MkCloudConfigYaml (YamlObject -> CloudConfigYaml)
-> Eff e YamlObject -> Eff e CloudConfigYaml
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AST c YamlObject -> Eff e YamlObject
forall a (e :: [* -> *]) c.
(FromAST a, IsB9 e, ToContentGenerator c) =>
AST c a -> Eff e a
fromAST (CloudConfigYaml -> YamlObject
fromCloudConfigYaml (CloudConfigYaml -> YamlObject)
-> AST c CloudConfigYaml -> AST c YamlObject
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AST c CloudConfigYaml
ast)
instance Textual CloudConfigYaml where
parseFromText :: Text -> Either String CloudConfigYaml
parseFromText Text
txt = do
let header :: Text
header = Int -> Text -> Text
Text.take (Text -> Int
Text.length Text
cloudConfigFileHeader) Text
txt
txt' :: Text
txt' =
if Text
header Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
cloudConfigFileHeader
then Int -> Text -> Text
Text.drop (Text -> Int
Text.length Text
cloudConfigFileHeader) Text
txt
else Text
txt
YamlObject
y <- Text -> Either String YamlObject
forall a. (Textual a, HasCallStack) => Text -> Either String a
parseFromText Text
txt'
CloudConfigYaml -> Either String CloudConfigYaml
forall (m :: * -> *) a. Monad m => a -> m a
return (YamlObject -> CloudConfigYaml
MkCloudConfigYaml YamlObject
y)
renderToText :: CloudConfigYaml -> Either String Text
renderToText (MkCloudConfigYaml YamlObject
y) = do
Text
txt <- YamlObject -> Either String Text
forall a. (Textual a, HasCallStack) => a -> Either String Text
renderToText YamlObject
y
Text -> Either String Text
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text] -> Text
Text.unlines [Text
cloudConfigFileHeader, Text
txt])