-- Copyright (C) 2002-2004,2007-2008 David Roundy -- Copyright (C) 2005 Juliusz Chroboczek -- -- This program is free software; you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation; either version 2, or (at your option) -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program; see the file COPYING. If not, write to -- the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, -- Boston, MA 02110-1301, USA. {-# OPTIONS_GHC -cpp -fglasgow-exts #-} {-# LANGUAGE CPP #-} #include "gadts.h" module Darcs.Repository.LowLevel ( read_pending, read_pendingfile, pendingName, readPrims ) where import Darcs.Repository.InternalTypes ( RepoType(..), Repository(..) ) import Darcs.Patch ( readPatch, Prim, Patch, RepoPatch, effect ) import Darcs.Global ( darcsdir ) import Darcs.Witnesses.Sealed ( Sealed(Sealed) ) import Darcs.Witnesses.Ordered ( FL(..) ) import Darcs.Utils ( catchall, withCurrentDirectory ) import ByteStringUtils ( gzReadFilePS ) import qualified Data.ByteString as BS ( ByteString, empty ) pendingName :: RepoType p -> String pendingName (DarcsRepository _ _) = darcsdir++"/patches/pending" read_pending :: RepoPatch p => Repository p C(r u t) -> IO (Sealed (FL Prim C(r))) read_pending (Repo r _ _ tp) = withCurrentDirectory r (read_pendingfile (pendingName tp)) read_pendingfile :: String -> IO (Sealed (FL Prim C(x))) read_pendingfile name = do pend <- gzReadFilePS name `catchall` return BS.empty return $ readPrims pend readPrims :: BS.ByteString -> Sealed (FL Prim C(x)) readPrims s = case readPatch s :: Maybe (Sealed (Patch C(x )), BS.ByteString) of Nothing -> Sealed NilFL Just (Sealed p,_) -> Sealed (effect p)