module Darcs.Patch.ReadMonads (ParserM, work, maybe_work, alter_input, parse_strictly, parse_lazily, peek_input, lex_char, lex_string, lex_strings, lex_eof, my_lex) where import FastPackedString ( PackedString, dropWhitePS, breakWhitePS, nullPS, unpackPS, nilPS ) lex_char :: ParserM m => Char -> m () lex_char c = lex_string [c] lex_string :: ParserM m => String -> m () lex_string str = work $ \s -> case my_lex s of Just (xs, ys) | unpackPS xs == str -> Just ((), ys) _ -> Nothing lex_eof :: ParserM m => m () lex_eof = work $ \s -> if nullPS (dropWhitePS s) then (Just ((), nilPS)) else Nothing lex_strings :: ParserM m => [String] -> m String lex_strings str = work $ \s -> case my_lex s of Just (xs, ys) | xs' `elem` str -> Just (xs', ys) where xs' = unpackPS xs _ -> Nothing my_lex :: PackedString -> Maybe (PackedString, PackedString) my_lex s = let s' = dropWhitePS s in if nullPS s' then Nothing else Just $ breakWhitePS s' alter_input :: ParserM m => (PackedString -> PackedString) -> m () alter_input f = work (\s -> Just ((), f s)) class Monad m => ParserM m where work :: (PackedString -> Maybe (a, PackedString)) -> m a maybe_work :: (PackedString -> Maybe (a, PackedString)) -> m (Maybe a) peek_input :: m PackedString ----- Strict Monad ----- parse_strictly :: SM a -> PackedString -> Maybe (a, PackedString) parse_strictly (SM f) s = f s newtype SM a = SM (PackedString -> Maybe (a, PackedString)) instance Monad SM where SM m >>= k = SM $ \s -> case m s of Nothing -> Nothing Just (x, s') -> case k x of SM y -> y s' return x = SM (\s -> Just (x,s)) fail _ = SM (\_ -> Nothing) instance ParserM SM where work f = SM f maybe_work f = SM $ \s -> case f s of Just (x, s') -> Just (Just x, s') Nothing -> Just (Nothing, s) peek_input = SM $ \s -> Just (s, s) ----- Lazy Monad ----- parse_lazily :: LM a -> PackedString -> (a, PackedString) parse_lazily (LM f) s = f s newtype LM a = LM (PackedString -> (a, PackedString)) instance Monad LM where LM m >>= k = LM $ \s -> let (x, s') = m s LM y = k x in y s' return x = LM (\s -> (x,s)) fail s = error s instance ParserM LM where work f = LM $ \s -> case f s of Nothing -> error "parser error" Just x -> x maybe_work f = LM $ \s -> case f s of Nothing -> (Nothing, s) Just (x, s') -> (Just x, s') peek_input = LM $ \s -> (s, s)