Skip to content

Instantly share code, notes, and snippets.

@jan-matejka
Created July 10, 2015 01:35
Show Gist options
  • Select an option

  • Save jan-matejka/f4575eb93c5d9baf27c1 to your computer and use it in GitHub Desktop.

Select an option

Save jan-matejka/f4575eb93c5d9baf27c1 to your computer and use it in GitHub Desktop.
{-# LANGUAGE OverloadedStrings #-}
module YGit.Forking
( headCommit
, Repo (..)
) where
import Git
import qualified Git.Libgit2 as Lg
import Control.Monad.Reader
import Control.Monad.Logger
data Repo = Local FilePath
deriving (Show)
headCommit :: Repo -> IO (Maybe Lg.OidPtr)
headCommit (Local path) = withRepository Lg.lgFactory path act
where
act = resolveReference "HEAD"
{-# LANGUAGE OverloadedStrings #-}
module YGit.ForkingSpec (spec) where
import Test.Hspec
import YGit.Forking
import Turtle
import System.IO.Temp
import qualified Git.Libgit2 as Lg
import qualified Filesystem.Path.CurrentOS as F
spec :: Spec
spec = do
describe "tests skeleton" $ do
it "calling unit tests works" $ do
True `shouldBe` True
describe "getHeadCommit (local repo path)" $ do
it "works" $ do
c <- withSystemTempDirectory "ygit-tests.XXXX" setup
(show c) `shouldBe` ("Just 2ec919241be9fa53382e5b9c903630c8221643bf")
setup :: Prelude.FilePath -> IO (Maybe Lg.OidPtr)
setup tmpd = do
sh $ do
cd (F.decodeString tmpd)
_sh "git init ./"
_sh "git config user.name Foo"
_sh "git config user.email [email protected]"
_sh "echo a > ./a"
_sh "git add a"
_sh "GIT_COMMITTER_DATE=2005-04-07T22:13:13 git commit --date 2005-04-07T22:13:13 -m a"
_sh "cp -a ./ /tmp/foo"
return ()
headCommit $ Local tmpd
where
_sh c = do
liftIO $ print c
view $ shell c empty
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment