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

Safe HaskellNone
LanguageHaskell2010

B9.B9Config.Repository

Synopsis

Documentation

data RemoteRepo Source #

Instances
Eq RemoteRepo Source # 
Instance details

Defined in B9.B9Config.Repository

Data RemoteRepo Source # 
Instance details

Defined in B9.B9Config.Repository

Methods

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

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

toConstr :: RemoteRepo -> Constr #

dataTypeOf :: RemoteRepo -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RemoteRepo Source # 
Instance details

Defined in B9.B9Config.Repository

Show RemoteRepo Source # 
Instance details

Defined in B9.B9Config.Repository

newtype RepoCache Source #

Constructors

RepoCache FilePath 
Instances
Data RepoCache Source # 
Instance details

Defined in B9.B9Config.Repository

Methods

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

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

toConstr :: RepoCache -> Constr #

dataTypeOf :: RepoCache -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RepoCache Source # 
Instance details

Defined in B9.B9Config.Repository

Show RepoCache Source # 
Instance details

Defined in B9.B9Config.Repository

newtype SshPrivKey Source #

Constructors

SshPrivKey FilePath 
Instances
Eq SshPrivKey Source # 
Instance details

Defined in B9.B9Config.Repository

Data SshPrivKey Source # 
Instance details

Defined in B9.B9Config.Repository

Methods

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

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

toConstr :: SshPrivKey -> Constr #

dataTypeOf :: SshPrivKey -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SshPrivKey Source # 
Instance details

Defined in B9.B9Config.Repository

Show SshPrivKey Source # 
Instance details

Defined in B9.B9Config.Repository

newtype SshRemoteHost Source #

Constructors

SshRemoteHost (String, Int) 
Instances
Eq SshRemoteHost Source # 
Instance details

Defined in B9.B9Config.Repository

Data SshRemoteHost Source # 
Instance details

Defined in B9.B9Config.Repository

Methods

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

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

toConstr :: SshRemoteHost -> Constr #

dataTypeOf :: SshRemoteHost -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SshRemoteHost Source # 
Instance details

Defined in B9.B9Config.Repository

Show SshRemoteHost Source # 
Instance details

Defined in B9.B9Config.Repository

newtype SshRemoteUser Source #

Constructors

SshRemoteUser String 
Instances
Eq SshRemoteUser Source # 
Instance details

Defined in B9.B9Config.Repository

Data SshRemoteUser Source # 
Instance details

Defined in B9.B9Config.Repository

Methods

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

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

toConstr :: SshRemoteUser -> Constr #

dataTypeOf :: SshRemoteUser -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SshRemoteUser Source # 
Instance details

Defined in B9.B9Config.Repository

Show SshRemoteUser Source # 
Instance details

Defined in B9.B9Config.Repository

remoteRepoToCPDocument :: RemoteRepo -> CPDocument -> Either CPError CPDocument Source #

Persist a repo to a configuration file.

parseRemoteRepos :: CPDocument -> Either CPError [RemoteRepo] Source #

Load a repository from a configuration file that has been written by writeRepositoryToB9Config.