Safe Haskell | None |
---|---|
Language | Haskell2010 |
B9.B9Config.Repository
Synopsis
- data RemoteRepo = RemoteRepo String FilePath SshPrivKey SshRemoteHost SshRemoteUser
- remoteRepoRepoId :: RemoteRepo -> String
- newtype RepoCache = RepoCache FilePath
- newtype SshPrivKey = SshPrivKey FilePath
- newtype SshRemoteHost = SshRemoteHost (String, Int)
- newtype SshRemoteUser = SshRemoteUser String
- remoteRepoToCPDocument :: RemoteRepo -> CPDocument -> Either CPError CPDocument
- parseRemoteRepos :: CPDocument -> Either CPError [RemoteRepo]
Documentation
data RemoteRepo Source #
Constructors
RemoteRepo String FilePath SshPrivKey SshRemoteHost SshRemoteUser |
Instances
Eq RemoteRepo Source # | |
Defined in B9.B9Config.Repository | |
Data RemoteRepo Source # | |
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 # | |
Defined in B9.B9Config.Repository Methods readsPrec :: Int -> ReadS RemoteRepo # readList :: ReadS [RemoteRepo] # readPrec :: ReadPrec RemoteRepo # readListPrec :: ReadPrec [RemoteRepo] # | |
Show RemoteRepo Source # | |
Defined in B9.B9Config.Repository Methods showsPrec :: Int -> RemoteRepo -> ShowS # show :: RemoteRepo -> String # showList :: [RemoteRepo] -> ShowS # |
remoteRepoRepoId :: RemoteRepo -> String Source #
Instances
Data RepoCache Source # | |
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 # | |
Show RepoCache Source # | |
newtype SshPrivKey Source #
Constructors
SshPrivKey FilePath |
Instances
Eq SshPrivKey Source # | |
Defined in B9.B9Config.Repository | |
Data SshPrivKey Source # | |
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 # | |
Defined in B9.B9Config.Repository Methods readsPrec :: Int -> ReadS SshPrivKey # readList :: ReadS [SshPrivKey] # readPrec :: ReadPrec SshPrivKey # readListPrec :: ReadPrec [SshPrivKey] # | |
Show SshPrivKey Source # | |
Defined in B9.B9Config.Repository Methods showsPrec :: Int -> SshPrivKey -> ShowS # show :: SshPrivKey -> String # showList :: [SshPrivKey] -> ShowS # |
newtype SshRemoteHost Source #
Constructors
SshRemoteHost (String, Int) |
Instances
newtype SshRemoteUser Source #
Constructors
SshRemoteUser String |
Instances
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
.