module Darcs.Patch.Read
( ReadPatch(..)
, readPatch
, readPatchPartial
, bracketedFL
, peekfor
, readFileName
) where
import Darcs.Prelude
import Control.Applicative ( (<|>) )
import Control.Monad ( mzero )
import qualified Data.ByteString as B ( ByteString, null )
import qualified Data.ByteString.Char8 as BC ( ByteString, pack, stripPrefix )
import Darcs.Patch.Bracketed ( Bracketed(..), unBracketedFL )
import Darcs.Patch.Format
( FileNameFormat(..)
, ListFormat(..)
, PatchListFormat(..)
)
import Darcs.Util.Parser
( Parser
, checkConsumes
, choice
, lexChar
, lexString
, lexWord
, parse
)
import Darcs.Patch.Witnesses.Ordered ( FL(..), RL, reverseFL )
import Darcs.Patch.Witnesses.Sealed ( Sealed(..), mapSeal )
import Darcs.Util.ByteString ( decodeLocale, dropSpace, unpackPSFromUTF8 )
import Darcs.Util.Path ( AnchoredPath, decodeWhite, floatPath )
class ReadPatch p where
readPatch' :: Parser (Sealed (p wX))
readPatchPartial :: ReadPatch p => B.ByteString -> Either String (Sealed (p wX), B.ByteString)
readPatchPartial = parse readPatch'
readPatch :: ReadPatch p => B.ByteString -> Either String (Sealed (p wX))
readPatch ps =
case parse readPatch' ps of
Left e -> Left e
Right (p, leftover)
| B.null (dropSpace leftover) -> Right p
| otherwise -> Left $ unlines ["leftover:",show leftover]
instance ReadPatch p => ReadPatch (Bracketed p) where
readPatch' = mapSeal Braced <$> bracketedFL readPatch' '{' '}'
<|>
mapSeal Parens <$> bracketedFL readPatch' '(' ')'
<|>
mapSeal Singleton <$> readPatch'
instance (ReadPatch p, PatchListFormat p) => ReadPatch (FL p) where
readPatch'
| ListFormatV1 <- patchListFormat :: ListFormat p
= mapSeal unBracketedFL <$> readPatch'
| ListFormatV2 <- patchListFormat :: ListFormat p
= mapSeal unBracketedFL <$> readPatch'
| otherwise
= read_patches
where read_patches :: Parser (Sealed (FL p wX))
read_patches = do
mp <- (Just <$> checkConsumes readPatch') <|> return Nothing
case mp of
Just (Sealed p) -> do
Sealed ps <- read_patches
return $ Sealed (p:>:ps)
Nothing -> return $ Sealed NilFL
instance (ReadPatch p, PatchListFormat p) => ReadPatch (RL p) where
readPatch' = mapSeal reverseFL <$> readPatch'
{-# INLINE bracketedFL #-}
bracketedFL :: forall p wX .
(forall wY . Parser (Sealed (p wY))) -> Char -> Char -> Parser (Sealed (FL p wX))
bracketedFL parser pre post =
peekforc pre bfl mzero
where bfl :: forall wZ . Parser (Sealed (FL p wZ))
bfl = peekforc post (return $ Sealed NilFL)
(do Sealed p <- parser
Sealed ps <- bfl
return $ Sealed (p:>:ps))
{-# INLINE peekforc #-}
peekforc :: Char -> Parser a -> Parser a -> Parser a
peekforc c ifstr ifnot = choice [ lexChar c >> ifstr
, ifnot ]
peekfor :: BC.ByteString -> Parser a -> Parser a -> Parser a
peekfor ps ifstr ifnot = choice [ do lexString ps
ifstr
, ifnot ]
{-# INLINE peekfor #-}
readFileName :: FileNameFormat -> Parser AnchoredPath
readFileName fmt = do
raw <- lexWord
case BC.stripPrefix (BC.pack "./") raw of
Nothing -> fail $ "invalid file path"
Just raw' -> return $ convert fmt raw'
where
convert FileNameFormatV1 =
floatPath . decodeWhite . decodeLocale . BC.pack . unpackPSFromUTF8
convert FileNameFormatV2 =
floatPath . decodeWhite . decodeLocale
convert FileNameFormatDisplay = error "readFileName called with FileNameFormatDisplay"