{-# LANGUAGE CPP #-}
module Data.TPTP.Parse.Text (
  
  parseUnit,
  parseUnitOnly,
  parseUnitWith,
  
  parseTPTP,
  parseTPTPOnly,
  parseTPTPWith
) where
#if !MIN_VERSION_base(4, 8, 0)
import Control.Applicative ((*>), (<*))
#endif
import Data.Attoparsec.Text (Result, parse, parseOnly, parseWith, endOfInput)
import Data.Text (Text)
import Data.TPTP (Unit, TPTP)
import Data.TPTP.Parse.Combinators (whitespace, unit, tptp)
parseUnit :: Text -> Result Unit
parseUnit = parse (whitespace *> unit <* endOfInput)
parseUnitOnly :: Text -> Either String Unit
parseUnitOnly = parseOnly (whitespace *> unit <* endOfInput)
parseUnitWith :: Monad m => m Text -> Text -> m (Result Unit)
parseUnitWith m = parseWith m (whitespace *> unit <* endOfInput)
parseTPTP :: Text -> Result TPTP
parseTPTP = parse (whitespace *> tptp <* endOfInput)
parseTPTPOnly :: Text -> Either String TPTP
parseTPTPOnly = parseOnly (whitespace *> tptp <* endOfInput)
parseTPTPWith :: Monad m => m Text -> Text -> m (Result TPTP)
parseTPTPWith m = parseWith m (whitespace *> tptp <* endOfInput)