module Data.FileStore.Generic
( modify
, create
, Diff(..)
, diff
, searchRevisions
, smartRetrieve
, richDirectory
)
where
import Data.FileStore.Types
import Control.Exception as E
import Data.FileStore.Utils
import Data.List (isInfixOf)
import Data.Algorithm.Diff (Diff(..), getGroupedDiff)
import System.FilePath ((</>))
handleUnknownError :: E.SomeException -> IO a
handleUnknownError = E.throwIO . UnknownError . show
create :: Contents a
=> FileStore
-> FilePath
-> Author
-> Description
-> a
-> IO ()
create fs name author logMsg contents = E.catch (latest fs name >> E.throwIO ResourceExists)
(\e -> if e == NotFound
then save fs name author logMsg contents
else E.throwIO e)
modify :: Contents a
=> FileStore
-> FilePath
-> RevisionId
-> Author
-> Description
-> a
-> IO (Either MergeInfo ())
modify fs name originalRevId author msg contents = do
latestRevId <- latest fs name
latestRev <- revision fs latestRevId
if idsMatch fs originalRevId latestRevId
then save fs name author msg contents >> return (Right ())
else do
latestContents <- retrieve fs name (Just latestRevId)
originalContents <- retrieve fs name (Just originalRevId)
(conflicts, mergedText) <- E.catch
(mergeContents ("edited", toByteString contents) (originalRevId, originalContents) (latestRevId, latestContents))
handleUnknownError
return $ Left (MergeInfo latestRev conflicts mergedText)
diff :: FileStore
-> FilePath
-> Maybe RevisionId
-> Maybe RevisionId
-> IO [Diff [String]]
diff fs name Nothing id2 = do
contents2 <- retrieve fs name id2
return [Second (lines contents2) ]
diff fs name id1 id2 = do
contents1 <- retrieve fs name id1
contents2 <- retrieve fs name id2
return $ getGroupedDiff (lines contents1) (lines contents2)
searchRevisions :: FileStore
-> Bool
-> FilePath
-> Description
-> IO [Revision]
searchRevisions repo exact name desc = do
let matcher = if exact
then (== desc)
else (desc `isInfixOf`)
revs <- history repo [name] (TimeRange Nothing Nothing) Nothing
return $ Prelude.filter (matcher . revDescription) revs
smartRetrieve
:: Contents a
=> FileStore
-> Bool
-> FilePath
-> Maybe String
-> IO a
smartRetrieve fs exact name mrev = do
edoc <- E.try (retrieve fs name mrev)
case (edoc, mrev) of
(Right doc, _) -> return doc
(Left e, Nothing) -> E.throwIO (e :: FileStoreError)
(Left _, Just rev) -> do
revs <- searchRevisions fs exact name rev
if Prelude.null revs
then E.throwIO NotFound
else retrieve fs name (Just $ revId $ Prelude.head revs)
richDirectory :: FileStore -> FilePath -> IO [(Resource, Either String Revision)]
richDirectory fs fp = directory fs fp >>= mapM f
where f r = E.catch (g r) (\(e :: FileStoreError)-> return ( r, Left . show $ e ) )
g r@(FSDirectory _dir) = return (r,Left "richDirectory, we don't care about revision info for directories")
g res@(FSFile file) = do rev <- revision fs =<< latest fs ( fp </> file )
return (res,Right rev)