summaryrefslogtreecommitdiff
path: root/Git/Types.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Git/Types.hs')
-rw-r--r--Git/Types.hs62
1 files changed, 49 insertions, 13 deletions
diff --git a/Git/Types.hs b/Git/Types.hs
index 9c2754a..ce1818e 100644
--- a/Git/Types.hs
+++ b/Git/Types.hs
@@ -1,12 +1,11 @@
{- git data types
-
- - Copyright 2010-2019 Joey Hess <id@joeyh.name>
+ - Copyright 2010-2020 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
-{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE OverloadedStrings, TypeSynonymInstances, FlexibleInstances #-}
module Git.Types where
@@ -18,6 +17,8 @@ import qualified Data.ByteString as S
import System.Posix.Types
import Utility.SafeCommand
import Utility.FileSystemEncoding
+import qualified Data.Semigroup as Sem
+import Prelude
{- Support repositories on local disk, and repositories accessed via an URL.
-
@@ -33,6 +34,7 @@ data RepoLocation
= Local { gitdir :: RawFilePath, worktree :: Maybe RawFilePath }
| LocalUnknown RawFilePath
| Url URI
+ | UnparseableUrl String
| Unknown
deriving (Show, Eq, Ord)
@@ -49,43 +51,67 @@ data Repo = Repo
, gitEnvOverridesGitDir :: Bool
-- global options to pass to git when running git commands
, gitGlobalOpts :: [CommandParam]
+ -- True only when --git-dir or GIT_DIR was used
+ , gitDirSpecifiedExplicitly :: Bool
} deriving (Show, Eq, Ord)
newtype ConfigKey = ConfigKey S.ByteString
deriving (Ord, Eq)
-newtype ConfigValue = ConfigValue S.ByteString
- deriving (Ord, Eq, Semigroup, Monoid)
+data ConfigValue
+ = ConfigValue S.ByteString
+ | NoConfigValue
+ -- ^ git treats a setting with no value as different than a setting
+ -- with an empty value
+ deriving (Ord, Eq)
+
+instance Sem.Semigroup ConfigValue where
+ ConfigValue a <> ConfigValue b = ConfigValue (a <> b)
+ a <> NoConfigValue = a
+ NoConfigValue <> b = b
+
+instance Monoid ConfigValue where
+ mempty = ConfigValue mempty
instance Default ConfigValue where
def = ConfigValue mempty
fromConfigKey :: ConfigKey -> String
-fromConfigKey (ConfigKey s) = decodeBS' s
+fromConfigKey (ConfigKey s) = decodeBS s
instance Show ConfigKey where
show = fromConfigKey
-fromConfigValue :: ConfigValue -> String
-fromConfigValue (ConfigValue s) = decodeBS' s
+class FromConfigValue a where
+ fromConfigValue :: ConfigValue -> a
+
+instance FromConfigValue S.ByteString where
+ fromConfigValue (ConfigValue s) = s
+ fromConfigValue NoConfigValue = mempty
+
+instance FromConfigValue String where
+ fromConfigValue = decodeBS . fromConfigValue
instance Show ConfigValue where
show = fromConfigValue
instance IsString ConfigKey where
- fromString = ConfigKey . encodeBS'
+ fromString = ConfigKey . encodeBS
instance IsString ConfigValue where
- fromString = ConfigValue . encodeBS'
+ fromString = ConfigValue . encodeBS
type RemoteName = String
{- A git ref. Can be a sha1, or a branch or tag name. -}
-newtype Ref = Ref String
+newtype Ref = Ref S.ByteString
deriving (Eq, Ord, Read, Show)
fromRef :: Ref -> String
-fromRef (Ref s) = s
+fromRef = decodeBS . fromRef'
+
+fromRef' :: Ref -> S.ByteString
+fromRef' (Ref s) = s
{- Aliases for Ref. -}
type Branch = Ref
@@ -98,6 +124,7 @@ newtype RefDate = RefDate String
{- Types of objects that can be stored in git. -}
data ObjectType = BlobObject | CommitObject | TreeObject
+ deriving (Show)
readObjectType :: S.ByteString -> Maybe ObjectType
readObjectType "blob" = Just BlobObject
@@ -111,7 +138,12 @@ fmtObjectType CommitObject = "commit"
fmtObjectType TreeObject = "tree"
{- Types of items in a tree. -}
-data TreeItemType = TreeFile | TreeExecutable | TreeSymlink | TreeSubmodule
+data TreeItemType
+ = TreeFile
+ | TreeExecutable
+ | TreeSymlink
+ | TreeSubmodule
+ | TreeSubtree
deriving (Eq, Show)
{- Git uses magic numbers to denote the type of a tree item. -}
@@ -120,6 +152,7 @@ readTreeItemType "100644" = Just TreeFile
readTreeItemType "100755" = Just TreeExecutable
readTreeItemType "120000" = Just TreeSymlink
readTreeItemType "160000" = Just TreeSubmodule
+readTreeItemType "040000" = Just TreeSubtree
readTreeItemType _ = Nothing
fmtTreeItemType :: TreeItemType -> S.ByteString
@@ -127,12 +160,14 @@ fmtTreeItemType TreeFile = "100644"
fmtTreeItemType TreeExecutable = "100755"
fmtTreeItemType TreeSymlink = "120000"
fmtTreeItemType TreeSubmodule = "160000"
+fmtTreeItemType TreeSubtree = "040000"
toTreeItemType :: FileMode -> Maybe TreeItemType
toTreeItemType 0o100644 = Just TreeFile
toTreeItemType 0o100755 = Just TreeExecutable
toTreeItemType 0o120000 = Just TreeSymlink
toTreeItemType 0o160000 = Just TreeSubmodule
+toTreeItemType 0o040000 = Just TreeSubtree
toTreeItemType _ = Nothing
fromTreeItemType :: TreeItemType -> FileMode
@@ -140,6 +175,7 @@ fromTreeItemType TreeFile = 0o100644
fromTreeItemType TreeExecutable = 0o100755
fromTreeItemType TreeSymlink = 0o120000
fromTreeItemType TreeSubmodule = 0o160000
+fromTreeItemType TreeSubtree = 0o040000
data Commit = Commit
{ commitTree :: Sha