b9-0.5.46: A tool and library for building virtual machine images.

Safe HaskellNone
LanguageHaskell2010

B9.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.

Imagine you would want to create a cloud-init 'user-data' file from a set of 'user-data' snippets which each are valid 'user-data' files in yaml syntax and e.g. a write_files section. Now the goal is, for b9 to be able to merge these snippets into one, such that all writefiles sections are combined into a single writefile section. Another example is OTP/Erlang sys.config files. This type class is the greatest commonon denominator of types describing a syntax that can be parsed, concatenated e.g. like in the above example and rendered. The actual concatenation operation is the append from Monoid, i.e. like monoid but without the need for an empty element.

Synopsis

Documentation

class Semigroup a => ConcatableSyntax a where Source #

Types of values that can be parsedrendered fromto ByteStrings. This class is used as basis for the ASTish class.

Minimal complete definition

decodeSyntax, encodeSyntax

Methods

decodeSyntax Source #

Arguments

:: FilePath

An arbitrary string for error messages that

-> ByteString

The raw input to parse

-> Either String a 

encodeSyntax :: a -> ByteString Source #

class ConcatableSyntax a => ASTish a where Source #

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

Minimal complete definition

fromAST

Methods

fromAST :: CanRender c => AST c a -> ReaderT Environment B9 a 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 embeded, e.g. B9.Content.Generator.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 
ASTParse SourceFile 
AST a 

Instances

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

Methods

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

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

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

Methods

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

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

toConstr :: AST c a -> Constr #

dataTypeOf :: AST c a -> DataType #

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

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (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 :: (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 a, Read c) => Read (AST c a) Source # 

Methods

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

readList :: ReadS [AST c a] #

readPrec :: ReadPrec (AST c a) #

readListPrec :: ReadPrec [AST c a] #

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

Methods

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

show :: AST c a -> String #

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

Generic (AST c a) Source # 

Associated Types

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

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 # 

Methods

arbitrary :: Gen (AST c a) #

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

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

Methods

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

hash :: AST c a -> Int #

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

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 # 

Methods

rnf :: AST c a -> () #

type Rep (AST c a) Source # 

class CanRender c where Source #

Types of values that can be rendered into a ByteString

Minimal complete definition

render