{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeSynonymInstances #-} {-| Description: Stuff for finding paths in a git directory. -} module Data.Git.Paths where import Control.Monad.State import qualified Data.ByteString as B import System.Posix.FilePath import Data.Git.Hash import Data.Git.Internal.Types (GitConf (..), GitT (..)) -- | Types that are associated with a particular path in the @.git@ directory. class InRepo a where -- | The portion of the path under the git directory---thus, @inRepo HEAD == "HEAD"@, not -- @".git/HEAD"@. inRepo :: a -> RawFilePath -- | 'RawFilePath's are themselves (@inRepo = id@) in a @.git@ directory. instance InRepo RawFilePath where inRepo = id -- | The path of an object in the git directory repoPath :: (MonadIO m, InRepo a) => a -> GitT m RawFilePath repoPath a = gets gitDir >>= \dir -> return $ dir inRepo a -- | Location of the @packed-refs@ file. packedRefsPath :: RawFilePath packedRefsPath = "packed-refs" -- | Path for a loose object 'Sha1'. looseObjectPath :: Sha1 -> RawFilePath looseObjectPath s | validSha1 s = "objects" B.take 2 sh B.drop 2 sh | otherwise = error $ "malformed sha1: " ++ show (getSha1 s) where sh = getSha1Hex . toHex $ s -- | Location of packfiles. packDir :: RawFilePath packDir = "objects" "pack"