{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-} -- Imports internal modules
#endif

{-# OPTIONS_GHC -fno-warn-warnings-deprecations #-}
-- |
-- Module      :  Data.Attoparsec.Text.Lazy
-- Copyright   :  Bryan O'Sullivan 2007-2015
-- License     :  BSD3
--
-- Maintainer  :  bos@serpentine.com
-- Stability   :  experimental
-- Portability :  unknown
--
-- Simple, efficient combinator parsing that can consume lazy 'Text'
-- strings, loosely based on the Parsec library.
--
-- This is essentially the same code as in the 'Data.Attoparsec.Text'
-- module, only with a 'parse' function that can consume a lazy
-- 'Text' incrementally, and a 'Result' type that does not allow
-- more input to be fed in.  Think of this as suitable for use with a
-- lazily read file, e.g. via 'L.readFile' or 'L.hGetContents'.
--
-- /Note:/ The various parser functions and combinators such as
-- 'string' still expect /strict/ 'T.Text' parameters, and return
-- strict 'T.Text' results.  Behind the scenes, strict 'T.Text' values
-- are still used internally to store parser input and manipulate it
-- efficiently.

module Data.Attoparsec.Text.Lazy
    (
      Result(..)
    , module Data.Attoparsec.Text
    -- * Running parsers
    , parse
    , parseOnly
    , parseTest
    -- ** Result conversion
    , maybeResult
    , eitherResult
    ) where

import Control.DeepSeq (NFData(rnf))
import Data.List (intercalate)
import Data.Text.Lazy.Internal (Text(..), chunk)
import qualified Data.Attoparsec.Internal.Types as T
import qualified Data.Attoparsec.Text as A
import qualified Data.Text as T
import Data.Attoparsec.Text hiding (IResult(..), Result, eitherResult,
                                    maybeResult, parse, parseOnly, parseWith, parseTest)

-- | The result of a parse.
data Result r = Fail Text [String] String
              -- ^ The parse failed.  The 'Text' is the input
              -- that had not yet been consumed when the failure
              -- occurred.  The @[@'String'@]@ is a list of contexts
              -- in which the error occurred.  The 'String' is the
              -- message describing the error, if any.
              | Done Text r
              -- ^ The parse succeeded.  The 'Text' is the
              -- input that had not yet been consumed (if any) when
              -- the parse succeeded.
    deriving (Int -> Result r -> ShowS
[Result r] -> ShowS
Result r -> String
(Int -> Result r -> ShowS)
-> (Result r -> String) -> ([Result r] -> ShowS) -> Show (Result r)
forall r. Show r => Int -> Result r -> ShowS
forall r. Show r => [Result r] -> ShowS
forall r. Show r => Result r -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Result r] -> ShowS
$cshowList :: forall r. Show r => [Result r] -> ShowS
show :: Result r -> String
$cshow :: forall r. Show r => Result r -> String
showsPrec :: Int -> Result r -> ShowS
$cshowsPrec :: forall r. Show r => Int -> Result r -> ShowS
Show)

instance NFData r => NFData (Result r) where
    rnf :: Result r -> ()
rnf (Fail Text
bs [String]
ctxs String
msg) = Text -> ()
forall a. NFData a => a -> ()
rnf Text
bs () -> () -> ()
`seq` [String] -> ()
forall a. NFData a => a -> ()
rnf [String]
ctxs () -> () -> ()
`seq` String -> ()
forall a. NFData a => a -> ()
rnf String
msg
    rnf (Done Text
bs r
r)        = Text -> ()
forall a. NFData a => a -> ()
rnf Text
bs () -> () -> ()
`seq` r -> ()
forall a. NFData a => a -> ()
rnf r
r
    {-# INLINE rnf #-}

fmapR :: (a -> b) -> Result a -> Result b
fmapR :: (a -> b) -> Result a -> Result b
fmapR a -> b
_ (Fail Text
st [String]
stk String
msg) = Text -> [String] -> String -> Result b
forall r. Text -> [String] -> String -> Result r
Fail Text
st [String]
stk String
msg
fmapR a -> b
f (Done Text
bs a
r)       = Text -> b -> Result b
forall r. Text -> r -> Result r
Done Text
bs (a -> b
f a
r)

instance Functor Result where
    fmap :: (a -> b) -> Result a -> Result b
fmap = (a -> b) -> Result a -> Result b
forall a b. (a -> b) -> Result a -> Result b
fmapR

-- | Run a parser and return its result.
parse :: A.Parser a -> Text -> Result a
parse :: Parser a -> Text -> Result a
parse Parser a
p Text
s = case Text
s of
              Chunk Text
x Text
xs -> IResult Text a -> Text -> Result a
forall r. IResult Text r -> Text -> Result r
go (Parser a -> Text -> IResult Text a
forall a. Parser a -> Text -> Result a
A.parse Parser a
p Text
x) Text
xs
              Text
empty      -> IResult Text a -> Text -> Result a
forall r. IResult Text r -> Text -> Result r
go (Parser a -> Text -> IResult Text a
forall a. Parser a -> Text -> Result a
A.parse Parser a
p Text
T.empty) Text
empty
  where
    go :: IResult Text r -> Text -> Result r
go (T.Fail Text
x [String]
stk String
msg) Text
ys      = Text -> [String] -> String -> Result r
forall r. Text -> [String] -> String -> Result r
Fail (Text -> Text -> Text
chunk Text
x Text
ys) [String]
stk String
msg
    go (T.Done Text
x r
r) Text
ys            = Text -> r -> Result r
forall r. Text -> r -> Result r
Done (Text -> Text -> Text
chunk Text
x Text
ys) r
r
    go (T.Partial Text -> IResult Text r
k) (Chunk Text
y Text
ys) = IResult Text r -> Text -> Result r
go (Text -> IResult Text r
k Text
y) Text
ys
    go (T.Partial Text -> IResult Text r
k) Text
empty        = IResult Text r -> Text -> Result r
go (Text -> IResult Text r
k Text
T.empty) Text
empty

-- | Run a parser and print its result to standard output.
parseTest :: (Show a) => A.Parser a -> Text -> IO ()
parseTest :: Parser a -> Text -> IO ()
parseTest Parser a
p Text
s = Result a -> IO ()
forall a. Show a => a -> IO ()
print (Parser a -> Text -> Result a
forall a. Parser a -> Text -> Result a
parse Parser a
p Text
s)

-- | Convert a 'Result' value to a 'Maybe' value.
maybeResult :: Result r -> Maybe r
maybeResult :: Result r -> Maybe r
maybeResult (Done Text
_ r
r) = r -> Maybe r
forall a. a -> Maybe a
Just r
r
maybeResult Result r
_          = Maybe r
forall a. Maybe a
Nothing

-- | Convert a 'Result' value to an 'Either' value.
eitherResult :: Result r -> Either String r
eitherResult :: Result r -> Either String r
eitherResult (Done Text
_ r
r)        = r -> Either String r
forall a b. b -> Either a b
Right r
r
eitherResult (Fail Text
_ [] String
msg)   = String -> Either String r
forall a b. a -> Either a b
Left String
msg
eitherResult (Fail Text
_ [String]
ctxs String
msg) = String -> Either String r
forall a b. a -> Either a b
Left (String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
" > " [String]
ctxs String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
": " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg)

-- | Run a parser that cannot be resupplied via a 'T.Partial' result.
--
-- This function does not force a parser to consume all of its input.
-- Instead, any residual input will be discarded.  To force a parser
-- to consume all of its input, use something like this:
--
-- @
--'parseOnly' (myParser 'Control.Applicative.<*' 'endOfInput')
-- @
parseOnly :: A.Parser a -> Text -> Either String a
parseOnly :: Parser a -> Text -> Either String a
parseOnly Parser a
p = Result a -> Either String a
forall r. Result r -> Either String r
eitherResult (Result a -> Either String a)
-> (Text -> Result a) -> Text -> Either String a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser a -> Text -> Result a
forall a. Parser a -> Text -> Result a
parse Parser a
p
{-# INLINE parseOnly #-}