{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternSynonyms #-} -- | Utility module that should probably disappear. module Data.Git.Types ( Date , utcTimeToDate , Mode(..) , pattern BlobMode, pattern ExecMode, pattern TreeMode, pattern LinkMode, pattern SubmMode , Contact(..) , makeContact , makeContact' , GitT() , Git() ) where import qualified Data.ByteString as B import Data.Git.Formats import Data.Git.Internal.Types import Data.Time import Data.Time.Clock.POSIX import Data.Word -- | Git dates are seconds-since-the-epoch and a timezone string. type Date = (Int, B.ByteString) -- | Turn a 'UTCTime' into something git can understand. utcTimeToDate :: UTCTime -> Date utcTimeToDate t = (truncate $ utcTimeToPOSIXSeconds t, "+0000") -- | Author and Committer data in commit messages. data Contact = Contact { contactName, contactEmail :: SafeString } deriving (Eq, Ord, Show) -- | Try to make a 'Contact'. Gives 'Nothing' when 'safeString' fails on either argument. makeContact' :: B.ByteString -> B.ByteString -> Maybe Contact makeContact' name email = Contact <$> safeString name <*> safeString email -- | Make a 'Contact' or explode trying. makeContact :: B.ByteString -> B.ByteString -> Contact makeContact name email = maybe (error "illegal contact string") id $ makeContact' name email -- | File modes from git trees. newtype Mode = BareMode Word32 deriving (Eq, Ord, Show) -- Seperate lines because 8.0 can't handle , with patterns. pattern BlobMode :: Mode pattern ExecMode :: Mode pattern TreeMode :: Mode pattern SubmMode :: Mode pattern LinkMode :: Mode -- | The mode of a non-executable file in git. pattern BlobMode = BareMode 0o100644 -- | The mode of an executable file in git. pattern ExecMode = BareMode 0o100755 -- | The mode of a directory in git. pattern TreeMode = BareMode 0o040000 -- | The mode that represents a submodule in git. pattern SubmMode = BareMode 0o160000 -- | The mode of a symbolic link in git. pattern LinkMode = BareMode 0o120000 -- | A convenient version of 'GitT'. type Git a = GitT IO a