hledger/hledger-lib/Hledger/Utils/Parse.hs

134 lines
3.8 KiB
Haskell
Raw Normal View History

2018-09-30 04:32:08 +03:00
{-# LANGUAGE FlexibleContexts #-}
2018-07-31 11:30:08 +03:00
{-# LANGUAGE TypeFamilies #-}
module Hledger.Utils.Parse (
SimpleStringParser,
SimpleTextParser,
TextParser,
JournalParser,
ErroringJournalParser,
choice',
choiceInState,
surroundedBy,
parsewith,
parsewithString,
parseWithState,
parseWithState',
fromparse,
parseerror,
showDateParseError,
nonspace,
isNonNewlineSpace,
spacenonewline,
restofline,
eolof,
-- * re-exports
CustomErr
)
where
2015-08-19 23:47:26 +03:00
import Control.Monad.Except (ExceptT)
import Control.Monad.State.Strict (StateT, evalStateT)
2015-08-19 23:47:26 +03:00
import Data.Char
import Data.Functor.Identity (Identity(..))
2015-08-19 23:47:26 +03:00
import Data.List
import Data.Text (Text)
import Text.Megaparsec
import Text.Megaparsec.Char
import Text.Megaparsec.Custom
2015-08-19 23:47:26 +03:00
import Text.Printf
import Hledger.Data.Types
2015-08-19 23:47:26 +03:00
import Hledger.Utils.UTF8IOCompat (error')
-- | A parser of string to some type.
type SimpleStringParser a = Parsec CustomErr String a
-- | A parser of strict text to some type.
type SimpleTextParser = Parsec CustomErr Text -- XXX an "a" argument breaks the CsvRulesParser declaration somehow
-- | A parser of text that runs in some monad.
type TextParser m a = ParsecT CustomErr Text m a
-- | A parser of text that runs in some monad, keeping a Journal as state.
type JournalParser m a = StateT Journal (ParsecT CustomErr Text m) a
-- | A parser of text that runs in some monad, keeping a Journal as
-- state, that can throw an exception to end parsing, preventing
-- further parser backtracking.
type ErroringJournalParser m a =
StateT Journal (ParsecT CustomErr Text (ExceptT FinalParseError m)) a
2015-08-19 23:47:26 +03:00
-- | Backtracking choice, use this when alternatives share a prefix.
-- Consumes no input if all choices fail.
choice' :: [TextParser m a] -> TextParser m a
choice' = choice . map try
2015-08-19 23:47:26 +03:00
-- | Backtracking choice, use this when alternatives share a prefix.
-- Consumes no input if all choices fail.
choiceInState :: [StateT s (ParsecT CustomErr Text m) a] -> StateT s (ParsecT CustomErr Text m) a
choiceInState = choice . map try
surroundedBy :: Applicative m => m openclose -> m a -> m a
surroundedBy p = between p p
2018-09-30 04:32:08 +03:00
parsewith :: Parsec e Text a -> Text -> Either (ParseErrorBundle Text e) a
parsewith p = runParser p ""
2018-09-30 04:32:08 +03:00
parsewithString
:: Parsec e String a -> String -> Either (ParseErrorBundle String e) a
parsewithString p = runParser p ""
2015-08-19 23:47:26 +03:00
2018-08-04 18:11:32 +03:00
-- | Run a stateful parser with some initial state on a text.
-- See also: runTextParser, runJournalParser.
2018-09-30 04:32:08 +03:00
parseWithState
:: Monad m
=> st
-> StateT st (ParsecT CustomErr Text m) a
-> Text
-> m (Either (ParseErrorBundle Text CustomErr) a)
parseWithState ctx p s = runParserT (evalStateT p ctx) "" s
2015-08-19 23:47:26 +03:00
parseWithState'
:: (Stream s)
=> st
-> StateT st (ParsecT e s Identity) a
-> s
2018-09-30 04:32:08 +03:00
-> (Either (ParseErrorBundle s e) a)
parseWithState' ctx p s = runParser (evalStateT p ctx) "" s
2018-09-30 04:32:08 +03:00
fromparse
:: (Show t, Show (Token t), Show e) => Either (ParseErrorBundle t e) a -> a
2015-08-19 23:47:26 +03:00
fromparse = either parseerror id
2018-09-30 04:32:08 +03:00
parseerror :: (Show t, Show (Token t), Show e) => ParseErrorBundle t e -> a
2015-08-19 23:47:26 +03:00
parseerror e = error' $ showParseError e
2018-09-30 04:32:08 +03:00
showParseError
:: (Show t, Show (Token t), Show e)
=> ParseErrorBundle t e -> String
2015-08-19 23:47:26 +03:00
showParseError e = "parse error at " ++ show e
2018-09-30 04:32:08 +03:00
showDateParseError
:: (Show t, Show (Token t), Show e) => ParseErrorBundle t e -> String
2015-08-19 23:47:26 +03:00
showDateParseError e = printf "date parse error (%s)" (intercalate ", " $ tail $ lines $ show e)
nonspace :: TextParser m Char
2015-08-19 23:47:26 +03:00
nonspace = satisfy (not . isSpace)
2018-05-22 04:09:47 +03:00
isNonNewlineSpace :: Char -> Bool
isNonNewlineSpace c = c /= '\n' && isSpace c
-- XXX support \r\n ?
-- isNonNewlineSpace c = c /= '\n' && c /= '\r' && isSpace c
2018-05-22 04:09:47 +03:00
spacenonewline :: (Stream s, Char ~ Token s) => ParsecT CustomErr s m Char
2018-05-22 04:09:47 +03:00
spacenonewline = satisfy isNonNewlineSpace
2015-08-19 23:47:26 +03:00
restofline :: TextParser m String
restofline = anySingle `manyTill` eolof
2015-08-19 23:47:26 +03:00
eolof :: TextParser m ()
2015-08-19 23:47:26 +03:00
eolof = (newline >> return ()) <|> eof