b9-3.2.3: A tool and library for building virtual machine images.
Safe HaskellNone
LanguageHaskell2010

B9.Artifact.Content.AST

Description

B9 produces not only VM-Images but also text documents such as configuration files required by virtual machines. This module is about creating and merging files containing parsable syntactic structures, such as most configuration files do.

B9 can be used to create configuration files by assembling structured documents, for example Yaml, JSON, Erlang Terms.

One example is creating a single cloud-init 'user-data' file from a set of 'user-data' snippets - all of which using yaml syntax to declare the same object (e.g "user-data").

The goal is, that b9 is able to merge these snippets into one, intelligently merging fields as one would expect, e.g. when merging multiple snippets with writefiles fields, the output object's writefiles field contains all the write_file objects.

Another example is the OTPErlang sys.config for configuring OTPErlang releases.

Synopsis

Documentation

class FromAST a where Source #

Types of values that describe content, that can be created from an AST.

Methods

fromAST :: (IsB9 e, ToContentGenerator c) => AST c a -> Eff e a Source #

Instances

Instances details
FromAST YamlObject Source # 
Instance details

Defined in B9.Artifact.Content.YamlObject

Methods

fromAST :: forall (e :: [Type -> Type]) c. (IsB9 e, ToContentGenerator c) => AST c YamlObject -> Eff e YamlObject Source #

FromAST ErlangPropList Source # 
Instance details

Defined in B9.Artifact.Content.ErlangPropList

Methods

fromAST :: forall (e :: [Type -> Type]) c. (IsB9 e, ToContentGenerator c) => AST c ErlangPropList -> Eff e ErlangPropList Source #

FromAST CloudConfigYaml Source # 
Instance details

Defined in B9.Artifact.Content.CloudConfigYaml

Methods

fromAST :: forall (e :: [Type -> Type]) c. (IsB9 e, ToContentGenerator c) => AST c CloudConfigYaml -> Eff e CloudConfigYaml Source #

data AST c a Source #

Describe how to create structured content that has a tree-like syntactic structure, e.g. yaml, JSON and erlang-proplists. The first parameter defines a context into which the AST is embedded, e.g. B9.Artifact.Content'. The second parameter defines a specifix syntax, e.g ErlangPropList that the AST value generates.

Constructors

ASTObj [(String, AST c a)]

Create an object similar to a Json object.

ASTArr [AST c a]

An array.

ASTMerge [AST c a]

Merge the nested elements, this is a very powerful tool that allows to combine

ASTEmbed c 
ASTString String 
ASTInt Int 
ASTParse SourceFile 
AST a 

Instances

Instances details
Functor (AST c) Source # 
Instance details

Defined in B9.Artifact.Content.AST

Methods

fmap :: (a -> b) -> AST c a -> AST c b #

(<$) :: a -> AST c b -> AST c a #

(Eq c, Eq a) => Eq (AST c a) Source # 
Instance details

Defined in B9.Artifact.Content.AST

Methods

(==) :: AST c a -> AST c a -> Bool #

(/=) :: AST c a -> AST c a -> Bool #

(Data c, Data a) => Data (AST c a) Source # 
Instance details

Defined in B9.Artifact.Content.AST

Methods

gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> AST c a -> c0 (AST c a) #

gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (AST c a) #

toConstr :: AST c a -> Constr #

dataTypeOf :: AST c a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (AST c a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (AST c a)) #

gmapT :: (forall b. Data b => b -> b) -> AST c a -> AST c a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AST c a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AST c a -> r #

gmapQ :: (forall d. Data d => d -> u) -> AST c a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AST c a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AST c a -> m (AST c a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AST c a -> m (AST c a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AST c a -> m (AST c a) #

(Read c, Read a) => Read (AST c a) Source # 
Instance details

Defined in B9.Artifact.Content.AST

Methods

readsPrec :: Int -> ReadS (AST c a) #

readList :: ReadS [AST c a] #

readPrec :: ReadPrec (AST c a) #

readListPrec :: ReadPrec [AST c a] #

(Show c, Show a) => Show (AST c a) Source # 
Instance details

Defined in B9.Artifact.Content.AST

Methods

showsPrec :: Int -> AST c a -> ShowS #

show :: AST c a -> String #

showList :: [AST c a] -> ShowS #

Generic (AST c a) Source # 
Instance details

Defined in B9.Artifact.Content.AST

Associated Types

type Rep (AST c a) :: Type -> Type #

Methods

from :: AST c a -> Rep (AST c a) x #

to :: Rep (AST c a) x -> AST c a #

(Arbitrary c, Arbitrary a) => Arbitrary (AST c a) Source # 
Instance details

Defined in B9.Artifact.Content.AST

Methods

arbitrary :: Gen (AST c a) #

shrink :: AST c a -> [AST c a] #

(Hashable c, Hashable a) => Hashable (AST c a) Source # 
Instance details

Defined in B9.Artifact.Content.AST

Methods

hashWithSalt :: Int -> AST c a -> Int #

hash :: AST c a -> Int #

(Binary c, Binary a) => Binary (AST c a) Source # 
Instance details

Defined in B9.Artifact.Content.AST

Methods

put :: AST c a -> Put #

get :: Get (AST c a) #

putList :: [AST c a] -> Put #

(NFData c, NFData a) => NFData (AST c a) Source # 
Instance details

Defined in B9.Artifact.Content.AST

Methods

rnf :: AST c a -> () #

type Rep (AST c a) Source # 
Instance details

Defined in B9.Artifact.Content.AST

parseFromTextWithErrorMessage Source #

Arguments

:: (HasCallStack, Textual a) 
=> String

An arbitrary string for error messages

-> Text 
-> Either String a 

Parse the given Text. -- Return Left errorMessage or Right a.