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

Safe HaskellNone
LanguageHaskell2010

B9.ArtifactGenerator

Description

Top-Level data types for B9 build artifacts.

Synopsis

Documentation

data ArtifactGenerator Source #

Artifacts represent the things B9 can build. A generator specifies howto generate parameterized, multiple artifacts. The general structure is:

   Let [ ... bindings ... ]
       [ Sources
           [ ... list all input files ... ]
           [ Artifact ...
           , Artifact ...
           , Let [ ... ] [ ... ]
           ]
       ]

The reasons why Sources takes a list of ArtifactGenerators is that

  1. this makes the value easier to read/write for humans
  2. the sources are static files used in all children (e.g. company logo image)
  3. the sources are parameterized by variables that bound to different values for each artifact, e.g. a template network config file which contains the host IP address.

To bind such variables use Let, Each, LetX or EachT.

String subtitution of these variables is done by B9.Content.StringTemplate. These variables can be used as value in nested Lets, in most file names/paths and in source files added with SourceFile

Constructors

Sources [ArtifactSource] [ArtifactGenerator]

Add sources available to ArtifactAssemblys in nested artifact generators.

Let [(String, String)] [ArtifactGenerator]

Bind variables, variables are avaible in nested generators.

LetX [(String, [String])] [ArtifactGenerator]

A Let where each variable is assigned to each value; the nested generator is executed for each permutation.

    LetX [("x", ["1","2","3"]), ("y", ["a","b"])] [..]

Is equal to:

    Let [] [
      Let [("x", "1"), ("y", "a")] [..]
      Let [("x", "1"), ("y", "b")] [..]
      Let [("x", "2"), ("y", "a")] [..]
      Let [("x", "2"), ("y", "b")] [..]
      Let [("x", "3"), ("y", "a")] [..]
      Let [("x", "3"), ("y", "b")] [..]
    ]
Each [(String, [String])] [ArtifactGenerator]

Bind each variable to their first value, then each variable to the second value, etc ... and execute the nested generator in every step. LetX represents a product of all variables, whereas Each represents a sum of variable bindings - Each is more like a zip whereas LetX is more like a list comprehension.

EachT [String] [[String]] [ArtifactGenerator]

The transposed verison of Each: Bind the variables in the first list to each a set of values from the second argument; execute the nested generators for each binding

Artifact InstanceId ArtifactAssembly

Generate an artifact defined by an ArtifactAssembly; the assembly can access the files created from the Sources and variables bound by Letish elements. An artifact has an instance id, that is a unique, human readable string describing the artifact to assemble.

EmptyArtifact 
Instances
Eq ArtifactGenerator Source # 
Instance details

Defined in B9.ArtifactGenerator

Data ArtifactGenerator Source # 
Instance details

Defined in B9.ArtifactGenerator

Methods

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

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

toConstr :: ArtifactGenerator -> Constr #

dataTypeOf :: ArtifactGenerator -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> ArtifactGenerator -> ArtifactGenerator #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArtifactGenerator -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArtifactGenerator -> r #

gmapQ :: (forall d. Data d => d -> u) -> ArtifactGenerator -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArtifactGenerator -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArtifactGenerator -> m ArtifactGenerator #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArtifactGenerator -> m ArtifactGenerator #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArtifactGenerator -> m ArtifactGenerator #

Read ArtifactGenerator Source # 
Instance details

Defined in B9.ArtifactGenerator

Show ArtifactGenerator Source # 
Instance details

Defined in B9.ArtifactGenerator

Generic ArtifactGenerator Source # 
Instance details

Defined in B9.ArtifactGenerator

Associated Types

type Rep ArtifactGenerator :: Type -> Type #

Semigroup ArtifactGenerator Source # 
Instance details

Defined in B9.ArtifactGenerator

Monoid ArtifactGenerator Source # 
Instance details

Defined in B9.ArtifactGenerator

Arbitrary ArtifactGenerator Source # 
Instance details

Defined in B9.ArtifactGenerator

Hashable ArtifactGenerator Source # 
Instance details

Defined in B9.ArtifactGenerator

Binary ArtifactGenerator Source # 
Instance details

Defined in B9.ArtifactGenerator

NFData ArtifactGenerator Source # 
Instance details

Defined in B9.ArtifactGenerator

Methods

rnf :: ArtifactGenerator -> () #

type Rep ArtifactGenerator Source # 
Instance details

Defined in B9.ArtifactGenerator

type Rep ArtifactGenerator = D1 (MetaData "ArtifactGenerator" "B9.ArtifactGenerator" "b9-0.5.60-KHsq2VPutWSEzRAbTAGn9c" False) ((C1 (MetaCons "Sources" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ArtifactSource]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ArtifactGenerator])) :+: (C1 (MetaCons "Let" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, String)]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ArtifactGenerator])) :+: C1 (MetaCons "LetX" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, [String])]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ArtifactGenerator])))) :+: ((C1 (MetaCons "Each" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, [String])]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ArtifactGenerator])) :+: C1 (MetaCons "EachT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [[String]]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ArtifactGenerator])))) :+: (C1 (MetaCons "Artifact" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 InstanceId) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ArtifactAssembly)) :+: C1 (MetaCons "EmptyArtifact" PrefixI False) (U1 :: Type -> Type))))

data ArtifactSource Source #

Describe how input files for artifacts to build are obtained. The general structure of each constructor is FromXXX destination source

Constructors

FromFile FilePath SourceFile

Copy a SourceFile potentially replacing variabled defined in Let-like parent elements.

FromContent FilePath Content

Create a file from some Content

SetPermissions Int Int Int [ArtifactSource]

Set the unix file permissions to all files generated by the nested list of ArtifactSources.

FromDirectory FilePath [ArtifactSource]

Assume a local directory as starting point for all relative source files in the nested ArtifactSources.

IntoDirectory FilePath [ArtifactSource]

Specify an output directory for all the files generated by the nested ArtifactSources

Concatenation FilePath [ArtifactSource]

Deprecated Concatenate the files generated by the nested ArtifactSources. The nested, generated files are not written when they are concatenated.

Instances
Eq ArtifactSource Source # 
Instance details

Defined in B9.ArtifactGenerator

Data ArtifactSource Source # 
Instance details

Defined in B9.ArtifactGenerator

Methods

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

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

toConstr :: ArtifactSource -> Constr #

dataTypeOf :: ArtifactSource -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> ArtifactSource -> ArtifactSource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArtifactSource -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArtifactSource -> r #

gmapQ :: (forall d. Data d => d -> u) -> ArtifactSource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArtifactSource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArtifactSource -> m ArtifactSource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArtifactSource -> m ArtifactSource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArtifactSource -> m ArtifactSource #

Read ArtifactSource Source # 
Instance details

Defined in B9.ArtifactGenerator

Show ArtifactSource Source # 
Instance details

Defined in B9.ArtifactGenerator

Generic ArtifactSource Source # 
Instance details

Defined in B9.ArtifactGenerator

Associated Types

type Rep ArtifactSource :: Type -> Type #

Arbitrary ArtifactSource Source # 
Instance details

Defined in B9.ArtifactGenerator

Hashable ArtifactSource Source # 
Instance details

Defined in B9.ArtifactGenerator

Binary ArtifactSource Source # 
Instance details

Defined in B9.ArtifactGenerator

NFData ArtifactSource Source # 
Instance details

Defined in B9.ArtifactGenerator

Methods

rnf :: ArtifactSource -> () #

type Rep ArtifactSource Source # 
Instance details

Defined in B9.ArtifactGenerator

type Rep ArtifactSource = D1 (MetaData "ArtifactSource" "B9.ArtifactGenerator" "b9-0.5.60-KHsq2VPutWSEzRAbTAGn9c" False) ((C1 (MetaCons "FromFile" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceFile)) :+: (C1 (MetaCons "FromContent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Content)) :+: C1 (MetaCons "SetPermissions" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ArtifactSource]))))) :+: (C1 (MetaCons "FromDirectory" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ArtifactSource])) :+: (C1 (MetaCons "IntoDirectory" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ArtifactSource])) :+: C1 (MetaCons "Concatenation" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ArtifactSource])))))

newtype InstanceId Source #

Identify an artifact. Deprecated TODO: B9 does not check if all instances IDs are unique.

Constructors

IID String 
Instances
Eq InstanceId Source # 
Instance details

Defined in B9.ArtifactGenerator

Data InstanceId Source # 
Instance details

Defined in B9.ArtifactGenerator

Methods

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

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

toConstr :: InstanceId -> Constr #

dataTypeOf :: InstanceId -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> InstanceId -> InstanceId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstanceId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstanceId -> r #

gmapQ :: (forall d. Data d => d -> u) -> InstanceId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstanceId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstanceId -> m InstanceId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceId -> m InstanceId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceId -> m InstanceId #

Read InstanceId Source # 
Instance details

Defined in B9.ArtifactGenerator

Show InstanceId Source # 
Instance details

Defined in B9.ArtifactGenerator

Arbitrary InstanceId Source # 
Instance details

Defined in B9.ArtifactGenerator

Hashable InstanceId Source # 
Instance details

Defined in B9.ArtifactGenerator

Binary InstanceId Source # 
Instance details

Defined in B9.ArtifactGenerator

NFData InstanceId Source # 
Instance details

Defined in B9.ArtifactGenerator

Methods

rnf :: InstanceId -> () #

data ArtifactTarget Source #

Instances
Eq ArtifactTarget Source # 
Instance details

Defined in B9.ArtifactGenerator

Data ArtifactTarget Source # 
Instance details

Defined in B9.ArtifactGenerator

Methods

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

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

toConstr :: ArtifactTarget -> Constr #

dataTypeOf :: ArtifactTarget -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> ArtifactTarget -> ArtifactTarget #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArtifactTarget -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArtifactTarget -> r #

gmapQ :: (forall d. Data d => d -> u) -> ArtifactTarget -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArtifactTarget -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArtifactTarget -> m ArtifactTarget #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArtifactTarget -> m ArtifactTarget #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArtifactTarget -> m ArtifactTarget #

Read ArtifactTarget Source # 
Instance details

Defined in B9.ArtifactGenerator

Show ArtifactTarget Source # 
Instance details

Defined in B9.ArtifactGenerator

Generic ArtifactTarget Source # 
Instance details

Defined in B9.ArtifactGenerator

Associated Types

type Rep ArtifactTarget :: Type -> Type #

Hashable ArtifactTarget Source # 
Instance details

Defined in B9.ArtifactGenerator

Binary ArtifactTarget Source # 
Instance details

Defined in B9.ArtifactGenerator

NFData ArtifactTarget Source # 
Instance details

Defined in B9.ArtifactGenerator

Methods

rnf :: ArtifactTarget -> () #

type Rep ArtifactTarget Source # 
Instance details

Defined in B9.ArtifactGenerator

type Rep ArtifactTarget = D1 (MetaData "ArtifactTarget" "B9.ArtifactGenerator" "b9-0.5.60-KHsq2VPutWSEzRAbTAGn9c" False) (C1 (MetaCons "CloudInitTarget" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CloudInitType) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)) :+: C1 (MetaCons "VmImagesTarget" PrefixI False) (U1 :: Type -> Type))

data CloudInitType Source #

Constructors

CI_ISO 
CI_VFAT 
CI_DIR 
Instances
Eq CloudInitType Source # 
Instance details

Defined in B9.ArtifactGenerator

Data CloudInitType Source # 
Instance details

Defined in B9.ArtifactGenerator

Methods

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

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

toConstr :: CloudInitType -> Constr #

dataTypeOf :: CloudInitType -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> CloudInitType -> CloudInitType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CloudInitType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CloudInitType -> r #

gmapQ :: (forall d. Data d => d -> u) -> CloudInitType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CloudInitType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CloudInitType -> m CloudInitType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CloudInitType -> m CloudInitType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CloudInitType -> m CloudInitType #

Read CloudInitType Source # 
Instance details

Defined in B9.ArtifactGenerator

Show CloudInitType Source # 
Instance details

Defined in B9.ArtifactGenerator

Generic CloudInitType Source # 
Instance details

Defined in B9.ArtifactGenerator

Associated Types

type Rep CloudInitType :: Type -> Type #

Arbitrary CloudInitType Source # 
Instance details

Defined in B9.ArtifactGenerator

Hashable CloudInitType Source # 
Instance details

Defined in B9.ArtifactGenerator

Binary CloudInitType Source # 
Instance details

Defined in B9.ArtifactGenerator

NFData CloudInitType Source # 
Instance details

Defined in B9.ArtifactGenerator

Methods

rnf :: CloudInitType -> () #

type Rep CloudInitType Source # 
Instance details

Defined in B9.ArtifactGenerator

type Rep CloudInitType = D1 (MetaData "CloudInitType" "B9.ArtifactGenerator" "b9-0.5.60-KHsq2VPutWSEzRAbTAGn9c" False) (C1 (MetaCons "CI_ISO" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CI_VFAT" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CI_DIR" PrefixI False) (U1 :: Type -> Type)))

data ArtifactAssembly Source #

Define an output of a build. Assemblies are nested into ArtifactGenerators. They contain all the files defined by the Sources they are nested into.

Constructors

CloudInit [CloudInitType] FilePath

Generate a cloud-init compatible directory, ISO- or VFAT image, as specified by the list of CloudInitTypes. Every item will use the second argument to create an appropriate file name, e.g. for the CI_ISO type the output is second_param.iso.

VmImages [ImageTarget] VmScript

a set of VM-images that were created by executing a build script on them.

Instances
Eq ArtifactAssembly Source # 
Instance details

Defined in B9.ArtifactGenerator

Data ArtifactAssembly Source # 
Instance details

Defined in B9.ArtifactGenerator

Methods

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

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

toConstr :: ArtifactAssembly -> Constr #

dataTypeOf :: ArtifactAssembly -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> ArtifactAssembly -> ArtifactAssembly #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArtifactAssembly -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArtifactAssembly -> r #

gmapQ :: (forall d. Data d => d -> u) -> ArtifactAssembly -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArtifactAssembly -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArtifactAssembly -> m ArtifactAssembly #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArtifactAssembly -> m ArtifactAssembly #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArtifactAssembly -> m ArtifactAssembly #

Read ArtifactAssembly Source # 
Instance details

Defined in B9.ArtifactGenerator

Show ArtifactAssembly Source # 
Instance details

Defined in B9.ArtifactGenerator

Generic ArtifactAssembly Source # 
Instance details

Defined in B9.ArtifactGenerator

Associated Types

type Rep ArtifactAssembly :: Type -> Type #

Arbitrary ArtifactAssembly Source # 
Instance details

Defined in B9.ArtifactGenerator

Hashable ArtifactAssembly Source # 
Instance details

Defined in B9.ArtifactGenerator

Binary ArtifactAssembly Source # 
Instance details

Defined in B9.ArtifactGenerator

NFData ArtifactAssembly Source # 
Instance details

Defined in B9.ArtifactGenerator

Methods

rnf :: ArtifactAssembly -> () #

type Rep ArtifactAssembly Source # 
Instance details

Defined in B9.ArtifactGenerator

data AssembledArtifact Source #

A type representing the targets assembled by assemble from an ArtifactAssembly. There is a list of ArtifactTargets because e.g. a single CloudInit can produce upto three output files, a directory, an ISO image and a VFAT image.

Instances
Eq AssembledArtifact Source # 
Instance details

Defined in B9.ArtifactGenerator

Data AssembledArtifact Source # 
Instance details

Defined in B9.ArtifactGenerator

Methods

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

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

toConstr :: AssembledArtifact -> Constr #

dataTypeOf :: AssembledArtifact -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> AssembledArtifact -> AssembledArtifact #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AssembledArtifact -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AssembledArtifact -> r #

gmapQ :: (forall d. Data d => d -> u) -> AssembledArtifact -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AssembledArtifact -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AssembledArtifact -> m AssembledArtifact #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AssembledArtifact -> m AssembledArtifact #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AssembledArtifact -> m AssembledArtifact #

Read AssembledArtifact Source # 
Instance details

Defined in B9.ArtifactGenerator

Show AssembledArtifact Source # 
Instance details

Defined in B9.ArtifactGenerator

Generic AssembledArtifact Source # 
Instance details

Defined in B9.ArtifactGenerator

Associated Types

type Rep AssembledArtifact :: Type -> Type #

Hashable AssembledArtifact Source # 
Instance details

Defined in B9.ArtifactGenerator

Binary AssembledArtifact Source # 
Instance details

Defined in B9.ArtifactGenerator

NFData AssembledArtifact Source # 
Instance details

Defined in B9.ArtifactGenerator

Methods

rnf :: AssembledArtifact -> () #

type Rep AssembledArtifact Source # 
Instance details

Defined in B9.ArtifactGenerator

data AssemblyOutput Source #

The output of an ArtifactAssembly is either a set of generated files, or it might be a directory that contains the artifacts sources.

Instances
Eq AssemblyOutput Source # 
Instance details

Defined in B9.ArtifactGenerator

Data AssemblyOutput Source # 
Instance details

Defined in B9.ArtifactGenerator

Methods

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

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

toConstr :: AssemblyOutput -> Constr #

dataTypeOf :: AssemblyOutput -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> AssemblyOutput -> AssemblyOutput #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AssemblyOutput -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AssemblyOutput -> r #

gmapQ :: (forall d. Data d => d -> u) -> AssemblyOutput -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AssemblyOutput -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AssemblyOutput -> m AssemblyOutput #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AssemblyOutput -> m AssemblyOutput #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AssemblyOutput -> m AssemblyOutput #

Read AssemblyOutput Source # 
Instance details

Defined in B9.ArtifactGenerator

Show AssemblyOutput Source # 
Instance details

Defined in B9.ArtifactGenerator

Generic AssemblyOutput Source # 
Instance details

Defined in B9.ArtifactGenerator

Associated Types

type Rep AssemblyOutput :: Type -> Type #

type Rep AssemblyOutput Source # 
Instance details

Defined in B9.ArtifactGenerator

type Rep AssemblyOutput = D1 (MetaData "AssemblyOutput" "B9.ArtifactGenerator" "b9-0.5.60-KHsq2VPutWSEzRAbTAGn9c" False) (C1 (MetaCons "AssemblyGeneratesOutputFiles" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath])) :+: C1 (MetaCons "AssemblyCopiesSourcesToDirectory" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)))

instanceIdKey :: String Source #

The variable containing the instance id. Deprecated

buildIdKey :: String Source #

The variable containing the buildId that identifies each execution of B9. For more info about variable substitution in source files see StringTemplate

buildDateKey :: String Source #

The variable containing the date and time a build was started. For more info about variable substitution in source files see StringTemplate

getAssemblyOutput :: ArtifactAssembly -> [AssemblyOutput] Source #

Return the files that the artifact assembly consist of.

getArtifactSourceFiles :: ArtifactSource -> [FilePath] Source #

Return all source files generated by an ArtifactSource.