{-# OPTIONS_GHC -Wno-orphans #-}
{-# LANGUAGE MultiParamTypeClasses, CPP #-}
module Parsley (
runParser, parseFromFile,
module Core,
module Primitives,
module Applicative,
module Alternative,
module Selective,
module Combinator,
module Fold,
module THUtils,
) where
import Prelude hiding (readFile)
import Data.Text.IO (readFile)
import Parsley.InputExtras (Text16(..))
import Parsley.Internal (Input, Trace(trace))
import Parsley.Alternative as Alternative
import Parsley.Applicative as Applicative
import Parsley.Combinator as Combinator (item, char, string, satisfy, notFollowedBy, lookAhead, try)
import Parsley.Fold as Fold (many, some)
import Parsley.Internal as Core (Parser)
import Parsley.ParserOps as Core (ParserOps)
import Parsley.Internal as THUtils (Quapplicative(..), WQ, Code)
import Parsley.Debug as Primitives (debug)
import Parsley.Selective as Selective
#if MIN_VERSION_parsley_core(1,7,1)
import qualified Parsley.Internal as Internal (parse)
#else
import qualified Parsley.Internal as Internal (eval, compile, codeGen)
#endif
runParser :: (Trace, Input input)
=> Parser a
-> Code (input -> Maybe a)
#if MIN_VERSION_parsley_core(1,7,1)
runParser :: Parser a -> Code (input -> Maybe a)
runParser = Parser a -> Code (input -> Maybe a)
forall input a.
(Trace, Input input) =>
Parser a -> Code (input -> Maybe a)
Internal.parse
#else
runParser p = [||\input -> $$(Internal.eval [||input||] (Internal.compile (try p) Internal.codeGen))||]
#endif
parseFromFile :: Trace
=> Parser a
-> Code (FilePath -> IO (Maybe a))
parseFromFile :: Parser a -> Code (FilePath -> IO (Maybe a))
parseFromFile Parser a
p = [||\filename -> do input <- readFile filename; return ($$(runParser p) (Text16 input))||]
instance {-# INCOHERENT #-} (forall a. FilePath -> a -> a) -> Trace
forall a. FilePath -> a -> a
Trace where
trace :: FilePath -> a -> a
trace = (a -> FilePath -> a) -> FilePath -> a -> a
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> FilePath -> a
forall a b. a -> b -> a
const