summaryrefslogtreecommitdiff
path: root/Git/Types.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Git/Types.hs')
-rw-r--r--Git/Types.hs132
1 files changed, 95 insertions, 37 deletions
diff --git a/Git/Types.hs b/Git/Types.hs
index bb91a17..9c2754a 100644
--- a/Git/Types.hs
+++ b/Git/Types.hs
@@ -1,17 +1,23 @@
{- git data types
-
- - Copyright 2010-2012 Joey Hess <id@joeyh.name>
+ - Copyright 2010-2019 Joey Hess <id@joeyh.name>
-
- - Licensed under the GNU GPL version 3 or higher.
+ - Licensed under the GNU AGPL version 3 or higher.
-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+
module Git.Types where
import Network.URI
+import Data.String
+import Data.Default
import qualified Data.Map as M
+import qualified Data.ByteString as S
import System.Posix.Types
import Utility.SafeCommand
-import Utility.URI ()
+import Utility.FileSystemEncoding
{- Support repositories on local disk, and repositories accessed via an URL.
-
@@ -24,26 +30,54 @@ import Utility.URI ()
- else known about it.
-}
data RepoLocation
- = Local { gitdir :: FilePath, worktree :: Maybe FilePath }
- | LocalUnknown FilePath
+ = Local { gitdir :: RawFilePath, worktree :: Maybe RawFilePath }
+ | LocalUnknown RawFilePath
| Url URI
| Unknown
deriving (Show, Eq, Ord)
data Repo = Repo
{ location :: RepoLocation
- , config :: M.Map String String
+ , config :: M.Map ConfigKey ConfigValue
-- a given git config key can actually have multiple values
- , fullconfig :: M.Map String [String]
- , remotes :: [Repo]
- -- remoteName holds the name used for this repo in remotes
+ , fullconfig :: M.Map ConfigKey [ConfigValue]
+ -- remoteName holds the name used for this repo in some other
+ -- repo's list of remotes, when this repo is such a remote
, remoteName :: Maybe RemoteName
-- alternate environment to use when running git commands
, gitEnv :: Maybe [(String, String)]
+ , gitEnvOverridesGitDir :: Bool
-- global options to pass to git when running git commands
, gitGlobalOpts :: [CommandParam]
} deriving (Show, Eq, Ord)
+newtype ConfigKey = ConfigKey S.ByteString
+ deriving (Ord, Eq)
+
+newtype ConfigValue = ConfigValue S.ByteString
+ deriving (Ord, Eq, Semigroup, Monoid)
+
+instance Default ConfigValue where
+ def = ConfigValue mempty
+
+fromConfigKey :: ConfigKey -> String
+fromConfigKey (ConfigKey s) = decodeBS' s
+
+instance Show ConfigKey where
+ show = fromConfigKey
+
+fromConfigValue :: ConfigValue -> String
+fromConfigValue (ConfigValue s) = decodeBS' s
+
+instance Show ConfigValue where
+ show = fromConfigValue
+
+instance IsString ConfigKey where
+ fromString = ConfigKey . encodeBS'
+
+instance IsString ConfigValue where
+ fromString = ConfigValue . encodeBS'
+
type RemoteName = String
{- A git ref. Can be a sha1, or a branch or tag name. -}
@@ -64,37 +98,61 @@ newtype RefDate = RefDate String
{- Types of objects that can be stored in git. -}
data ObjectType = BlobObject | CommitObject | TreeObject
- deriving (Eq)
-
-instance Show ObjectType where
- show BlobObject = "blob"
- show CommitObject = "commit"
- show TreeObject = "tree"
-readObjectType :: String -> Maybe ObjectType
+readObjectType :: S.ByteString -> Maybe ObjectType
readObjectType "blob" = Just BlobObject
readObjectType "commit" = Just CommitObject
readObjectType "tree" = Just TreeObject
readObjectType _ = Nothing
-{- Types of blobs. -}
-data BlobType = FileBlob | ExecutableBlob | SymlinkBlob
- deriving (Eq)
-
-{- Git uses magic numbers to denote the type of a blob. -}
-instance Show BlobType where
- show FileBlob = "100644"
- show ExecutableBlob = "100755"
- show SymlinkBlob = "120000"
-
-readBlobType :: String -> Maybe BlobType
-readBlobType "100644" = Just FileBlob
-readBlobType "100755" = Just ExecutableBlob
-readBlobType "120000" = Just SymlinkBlob
-readBlobType _ = Nothing
-
-toBlobType :: FileMode -> Maybe BlobType
-toBlobType 0o100644 = Just FileBlob
-toBlobType 0o100755 = Just ExecutableBlob
-toBlobType 0o120000 = Just SymlinkBlob
-toBlobType _ = Nothing
+fmtObjectType :: ObjectType -> S.ByteString
+fmtObjectType BlobObject = "blob"
+fmtObjectType CommitObject = "commit"
+fmtObjectType TreeObject = "tree"
+
+{- Types of items in a tree. -}
+data TreeItemType = TreeFile | TreeExecutable | TreeSymlink | TreeSubmodule
+ deriving (Eq, Show)
+
+{- Git uses magic numbers to denote the type of a tree item. -}
+readTreeItemType :: S.ByteString -> Maybe TreeItemType
+readTreeItemType "100644" = Just TreeFile
+readTreeItemType "100755" = Just TreeExecutable
+readTreeItemType "120000" = Just TreeSymlink
+readTreeItemType "160000" = Just TreeSubmodule
+readTreeItemType _ = Nothing
+
+fmtTreeItemType :: TreeItemType -> S.ByteString
+fmtTreeItemType TreeFile = "100644"
+fmtTreeItemType TreeExecutable = "100755"
+fmtTreeItemType TreeSymlink = "120000"
+fmtTreeItemType TreeSubmodule = "160000"
+
+toTreeItemType :: FileMode -> Maybe TreeItemType
+toTreeItemType 0o100644 = Just TreeFile
+toTreeItemType 0o100755 = Just TreeExecutable
+toTreeItemType 0o120000 = Just TreeSymlink
+toTreeItemType 0o160000 = Just TreeSubmodule
+toTreeItemType _ = Nothing
+
+fromTreeItemType :: TreeItemType -> FileMode
+fromTreeItemType TreeFile = 0o100644
+fromTreeItemType TreeExecutable = 0o100755
+fromTreeItemType TreeSymlink = 0o120000
+fromTreeItemType TreeSubmodule = 0o160000
+
+data Commit = Commit
+ { commitTree :: Sha
+ , commitParent :: [Sha]
+ , commitAuthorMetaData :: CommitMetaData
+ , commitCommitterMetaData :: CommitMetaData
+ , commitMessage :: String
+ }
+ deriving (Show)
+
+data CommitMetaData = CommitMetaData
+ { commitName :: Maybe String
+ , commitEmail :: Maybe String
+ , commitDate :: Maybe String -- In raw git form, "epoch -tzoffset"
+ }
+ deriving (Show)