{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeSynonymInstances #-}
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 (..))
class InRepo a where
inRepo :: a -> RawFilePath
instance InRepo RawFilePath where
inRepo = id
repoPath :: (MonadIO m, InRepo a) => a -> GitT m RawFilePath
repoPath a = gets gitDir >>= \dir -> return $ dir </> inRepo a
packedRefsPath :: RawFilePath
packedRefsPath = "packed-refs"
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
packDir :: RawFilePath
packDir = "objects" </> "pack"