module Data.FileStore.Types
( RevisionId
, Resource(..)
, Author(..)
, Change(..)
, Description
, Revision(..)
, Contents(..)
, TimeRange(..)
, MergeInfo(..)
, FileStoreError(..)
, SearchMatch(..)
, SearchQuery(..)
, defaultSearchQuery
, UTCTime
, FileStore (..) )
where
import Data.ByteString.Lazy (ByteString)
import Data.Typeable
import Data.ByteString.Lazy.UTF8 (toString, fromString)
import Data.Time (UTCTime)
import Control.Exception (Exception)
type RevisionId = String
data Resource = FSFile FilePath
| FSDirectory FilePath
deriving (Show, Read, Eq, Typeable, Ord)
data Author =
Author {
authorName :: String
, authorEmail :: String
} deriving (Show, Read, Eq, Typeable)
data Change =
Added FilePath
| Deleted FilePath
| Modified FilePath
deriving (Show, Read, Eq, Typeable)
type Description = String
data Revision =
Revision {
revId :: RevisionId
, revDateTime :: UTCTime
, revAuthor :: Author
, revDescription :: Description
, revChanges :: [Change]
} deriving (Show, Read, Eq, Typeable)
class Contents a where
fromByteString :: ByteString -> a
toByteString :: a -> ByteString
instance Contents ByteString where
toByteString = id
fromByteString = id
instance Contents String where
toByteString = fromString
fromByteString = toString
data TimeRange =
TimeRange {
timeFrom :: Maybe UTCTime
, timeTo :: Maybe UTCTime
} deriving (Show, Read, Eq, Typeable)
data MergeInfo =
MergeInfo {
mergeRevision :: Revision
, mergeConflicts :: Bool
, mergeText :: String
} deriving (Show, Read, Eq, Typeable)
data FileStoreError =
RepositoryExists
| ResourceExists
| NotFound
| IllegalResourceName
| Unchanged
| UnsupportedOperation
| NoMaxCount
| UnknownError String
deriving (Read, Eq, Typeable)
instance Show FileStoreError where
show RepositoryExists = "RepositoryExists"
show ResourceExists = "ResourceExists"
show NotFound = "NotFound"
show IllegalResourceName = "IllegalResourceName"
show Unchanged = "Unchanged"
show UnsupportedOperation = "UnsupportedOperation"
show NoMaxCount = "NoMaxCount:\n"
++ "filestore was compiled with the maxcount flag, but your version of\n"
++ "darcs does not support the --max-count option. You should either\n"
++ "upgrade to darcs >= 2.3.0 (recommended) or compile filestore without\n"
++ "the maxcount flag (cabal install filestore -f-maxcount)."
show (UnknownError s) = "UnknownError: " ++ s
instance Exception FileStoreError
data SearchQuery =
SearchQuery {
queryPatterns :: [String]
, queryWholeWords :: Bool
, queryMatchAll :: Bool
, queryIgnoreCase :: Bool
} deriving (Show, Read, Eq, Typeable)
defaultSearchQuery :: SearchQuery
defaultSearchQuery = SearchQuery {
queryPatterns = []
, queryWholeWords = True
, queryMatchAll = True
, queryIgnoreCase = True
}
data SearchMatch =
SearchMatch {
matchResourceName :: FilePath
, matchLineNumber :: Integer
, matchLine :: String
} deriving (Show, Read, Eq, Typeable)
data FileStore = FileStore {
initialize :: IO ()
, save :: Contents a
=> FilePath
-> Author
-> Description
-> a
-> IO ()
, retrieve :: Contents a
=> FilePath
-> Maybe RevisionId
-> IO a
, delete :: FilePath
-> Author
-> Description
-> IO ()
, rename :: FilePath
-> FilePath
-> Author
-> Description
-> IO ()
, history :: [FilePath]
-> TimeRange
-> Maybe Int
-> IO [Revision]
, latest :: FilePath
-> IO RevisionId
, revision :: RevisionId
-> IO Revision
, index :: IO [FilePath]
, directory :: FilePath
-> IO [Resource]
, idsMatch :: RevisionId
-> RevisionId
-> Bool
, search :: SearchQuery
-> IO [SearchMatch]
}