module B9.RepositoryIO (repoSearch
,pushToRepo
,pullFromRepo
,pullGlob
,Repository(..)
,toRemoteRepository
,FilePathGlob(..)) where
import B9.Repository
import B9.B9Monad
import B9.ConfigUtils
import Control.Applicative
import Data.List
import Control.Monad.IO.Class
import System.Directory
import System.FilePath
import Text.Printf (printf)
data Repository = Cache | Remote String
deriving (Eq, Ord, Read, Show)
toRemoteRepository :: RemoteRepo -> Repository
toRemoteRepository = Remote . remoteRepoRepoId
repoSearch :: FilePath -> FilePathGlob -> B9 [(Repository, [FilePath])]
repoSearch subDir glob = (:) <$> localMatches <*> remoteRepoMatches
where remoteRepoMatches = do
remoteRepos <- getRemoteRepos
mapM remoteRepoSearch remoteRepos
localMatches :: B9 (Repository, [FilePath])
localMatches = do
cache <- getRepoCache
let dir = localRepoDir cache </> subDir
files <- findGlob dir
return (Cache, files)
remoteRepoSearch :: RemoteRepo -> B9 (Repository, [FilePath])
remoteRepoSearch repo = do
cache <- getRepoCache
let dir = remoteRepoCacheDir cache repoId </> subDir
(RemoteRepo repoId _ _ _ _) = repo
files <- findGlob dir
return (Remote repoId, files)
findGlob :: FilePath -> B9 [FilePath]
findGlob dir = do
traceL (printf "reading contents of directory '%s'" dir)
ensureDir (dir ++ "/")
files <- liftIO (getDirectoryContents dir)
return ((dir </>) <$> filter (matchGlob glob) files)
pushToRepo :: RemoteRepo -> FilePath -> FilePath -> B9 ()
pushToRepo repo@(RemoteRepo repoId _ _ _ _) src dest = do
dbgL (printf "PUSHING '%s' TO REPO '%s'" (takeFileName src) repoId)
cmd (repoEnsureDirCmd repo dest)
cmd (pushCmd repo src dest)
pullFromRepo :: RemoteRepo -> FilePath -> FilePath -> B9 ()
pullFromRepo repo@(RemoteRepo repoId
rootDir
_key
(SshRemoteHost (host, _port))
(SshRemoteUser user)) src dest = do
dbgL (printf "PULLING '%s' FROM REPO '%s'" (takeFileName src) repoId)
cmd (printf "rsync -rtv -e 'ssh %s' '%s@%s:%s' '%s'"
(sshOpts repo)
user
host
(rootDir </> src)
dest)
pullGlob :: FilePath -> FilePathGlob -> RemoteRepo -> B9 ()
pullGlob subDir glob repo@(RemoteRepo repoId rootDir _key (SshRemoteHost (host,_port)) (SshRemoteUser user)) = do
cache <- getRepoCache
infoL (printf "SYNCING REPO METADATA '%s'" repoId)
let c =
printf
"rsync -rtv --include '%s' --exclude '*.*' -e 'ssh %s' '%s@%s:%s/' '%s/'"
(globToPattern glob)
(sshOpts repo)
user
host
(rootDir </> subDir)
destDir
destDir = repoCacheDir </> subDir
repoCacheDir = remoteRepoCacheDir cache repoId
ensureDir destDir
cmd c
data FilePathGlob = FileExtension String
globToPattern :: FilePathGlob -> String
globToPattern (FileExtension ext) = "*." ++ ext
matchGlob :: FilePathGlob -> FilePath -> Bool
matchGlob (FileExtension ext) = isSuffixOf ("." ++ ext)
pushCmd :: RemoteRepo -> FilePath -> FilePath -> String
pushCmd repo@(RemoteRepo _repoId
rootDir
_key
(SshRemoteHost (host, _port))
(SshRemoteUser user)) src dest =
printf "rsync -rtv --inplace --ignore-existing -e 'ssh %s' '%s' '%s'"
(sshOpts repo) src sshDest
where sshDest = printf "%s@%s:%s/%s" user host rootDir dest :: String
repoEnsureDirCmd :: RemoteRepo -> FilePath -> String
repoEnsureDirCmd repo@(RemoteRepo _repoId
rootDir
_key
(SshRemoteHost (host, _port))
(SshRemoteUser user)) dest =
printf "ssh %s %s@%s mkdir -p '%s'"
(sshOpts repo)
user
host
(rootDir </> takeDirectory dest)
sshOpts :: RemoteRepo -> String
sshOpts (RemoteRepo _repoId
_rootDir
(SshPrivKey key)
(SshRemoteHost (_host, port))
_user) =
unwords ["-o","StrictHostKeyChecking=no"
,"-o","UserKnownHostsFile=/dev/null"
,"-o",printf "Port=%i" port
,"-o","IdentityFile=" ++ key]