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

Safe HaskellNone
LanguageHaskell2010

B9.Artifact.Readable.Interpreter

Description

Mostly effectful functions to assemble artifacts.

Synopsis

Documentation

buildArtifacts :: ArtifactGenerator -> B9 String Source #

Execute an ArtifactGenerator and return a B9Invocation that returns the build id obtained by getBuildId.

getArtifactOutputFiles :: ArtifactGenerator -> Either String [FilePath] Source #

Return a list of relative paths for the local files to be generated by the ArtifactGenerator. This excludes Shared and Transient image targets.

assemble :: ArtifactGenerator -> B9 [AssembledArtifact] Source #

Run an artifact generator to produce the artifacts.

evalArtifactGenerator :: String -> String -> Environment -> ArtifactGenerator -> Either String [InstanceGenerator [SourceGenerator]] Source #

Evaluate an ArtifactGenerator into a list of low-level build instructions that can be built with createAssembledArtifacts.

parseArtifactGenerator :: ArtifactGenerator -> CGParser () Source #

Parse an artifacto generator inside a CGParser monad.

withArtifactSources :: [ArtifactSource] -> CGParser () -> CGParser () Source #

Execute a CGParser action in an environment that contains a list of ArtifactSources.

newtype CGParser a Source #

Monad for creating Instance generators.

Instances
Monad CGParser Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

Methods

(>>=) :: CGParser a -> (a -> CGParser b) -> CGParser b #

(>>) :: CGParser a -> CGParser b -> CGParser b #

return :: a -> CGParser a #

fail :: String -> CGParser a #

Functor CGParser Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

Methods

fmap :: (a -> b) -> CGParser a -> CGParser b #

(<$) :: a -> CGParser b -> CGParser a #

Applicative CGParser Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

Methods

pure :: a -> CGParser a #

(<*>) :: CGParser (a -> b) -> CGParser a -> CGParser b #

liftA2 :: (a -> b -> c) -> CGParser a -> CGParser b -> CGParser c #

(*>) :: CGParser a -> CGParser b -> CGParser b #

(<*) :: CGParser a -> CGParser b -> CGParser a #

MonadThrow CGParser Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

Methods

throwM :: Exception e => e -> CGParser a #

MonadReader CGEnv CGParser Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

Methods

ask :: CGParser CGEnv #

local :: (CGEnv -> CGEnv) -> CGParser a -> CGParser a #

reader :: (CGEnv -> a) -> CGParser a #

MonadWriter [InstanceGenerator CGEnv] CGParser Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

data InstanceGenerator e Source #

Instances
Eq e => Eq (InstanceGenerator e) Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

Data e => Data (InstanceGenerator e) Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

Methods

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

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

toConstr :: InstanceGenerator e -> Constr #

dataTypeOf :: InstanceGenerator e -> DataType #

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

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

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

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

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

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

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

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

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

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

Read e => Read (InstanceGenerator e) Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

Show e => Show (InstanceGenerator e) Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

MonadWriter [InstanceGenerator CGEnv] CGParser Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

newtype CGError Source #

Constructors

CGError String 
Instances
Eq CGError Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

Methods

(==) :: CGError -> CGError -> Bool #

(/=) :: CGError -> CGError -> Bool #

Data CGError Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

Methods

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

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

toConstr :: CGError -> Constr #

dataTypeOf :: CGError -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CGError Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

Show CGError Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

Exception CGError Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

data SourceGenerator Source #

Internal data type simplifying the rather complex source generation by bioling down ArtifactSources to a flat list of uniform SourceGenerators.

sourceGeneratorOutputFile :: SourceGenerator -> FilePath Source #

Return the (internal-)output file of the source file that is generated.

data SGPerm Source #

Constructors

SGSetPerm (Int, Int, Int) 
KeepPerm 
Instances
Eq SGPerm Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

Methods

(==) :: SGPerm -> SGPerm -> Bool #

(/=) :: SGPerm -> SGPerm -> Bool #

Data SGPerm Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

Methods

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

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

toConstr :: SGPerm -> Constr #

dataTypeOf :: SGPerm -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SGPerm Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

Show SGPerm Source # 
Instance details

Defined in B9.Artifact.Readable.Interpreter

createTarget :: InstanceId -> FilePath -> ArtifactAssembly -> B9 [ArtifactTarget] Source #

Create the actual target, either just a mountpoint, or an ISO or VFAT image.