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

B9.Artifact.Content.Readable

Description

Content defined in text files (.b9 files), read with the Read instances.

Synopsis

Documentation

data Content Source #

This is content that can be read via the generated Read instance.

Constructors

RenderErlang (AST Content ErlangPropList) 
RenderYamlObject (AST Content YamlObject) 
RenderCloudConfig (AST Content CloudConfigYaml) 
FromByteString ByteString

This data will be passed through unaltered. This is used during the transition phase from having B9 stuff read from files via Read instances towards programatic use or the use of HOCON.

Since: 0.5.62

FromString String

Embed a literal string

FromTextFile SourceFile

Embed the contents of the SourceFile with template parameter substitution.

RenderBase64BinaryFile FilePath

The data in the given file will be base64 encoded.

RenderBase64Binary ByteString

This data will be base64 encoded.

FromURL String

Download the contents of the URL

Instances

Instances details
Eq Content Source # 
Instance details

Defined in B9.Artifact.Content.Readable

Methods

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

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

Data Content Source # 
Instance details

Defined in B9.Artifact.Content.Readable

Methods

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

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

toConstr :: Content -> Constr #

dataTypeOf :: Content -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Content Source # 
Instance details

Defined in B9.Artifact.Content.Readable

Show Content Source # 
Instance details

Defined in B9.Artifact.Content.Readable

Generic Content Source # 
Instance details

Defined in B9.Artifact.Content.Readable

Associated Types

type Rep Content :: Type -> Type #

Methods

from :: Content -> Rep Content x #

to :: Rep Content x -> Content #

Arbitrary Content Source # 
Instance details

Defined in B9.Artifact.Content.Readable

NFData Content Source # 
Instance details

Defined in B9.Artifact.Content.Readable

Methods

rnf :: Content -> () #

ToContentGenerator Content Source # 
Instance details

Defined in B9.Artifact.Content.Readable

Methods

toContentGenerator :: forall (e :: [Type -> Type]). (HasCallStack, IsB9 e) => Content -> Eff e Text Source #

type Rep Content Source # 
Instance details

Defined in B9.Artifact.Content.Readable

type Rep Content = D1 ('MetaData "Content" "B9.Artifact.Content.Readable" "b9-3.2.3-3sZk3wiMlOE9ANxPzA3rTw" 'False) (((C1 ('MetaCons "RenderErlang" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AST Content ErlangPropList))) :+: C1 ('MetaCons "RenderYamlObject" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AST Content YamlObject)))) :+: (C1 ('MetaCons "RenderCloudConfig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AST Content CloudConfigYaml))) :+: C1 ('MetaCons "FromByteString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))) :+: ((C1 ('MetaCons "FromString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "FromTextFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourceFile))) :+: (C1 ('MetaCons "RenderBase64BinaryFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: (C1 ('MetaCons "RenderBase64Binary" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)) :+: C1 ('MetaCons "FromURL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))

Convenient Aliases