{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}

-- |
-- Module      :  Text.Megaparsec.State
-- Copyright   :  © 2015–present Megaparsec contributors
--                © 2007 Paolo Martini
--                © 1999–2001 Daan Leijen
-- License     :  FreeBSD
--
-- Maintainer  :  Mark Karpov <markkarpov92@gmail.com>
-- Stability   :  experimental
-- Portability :  portable
--
-- Definition of Megaparsec's 'State'.
--
-- @since 6.5.0
module Text.Megaparsec.State
  ( State (..),
    PosState (..),
  )
where

import Control.DeepSeq (NFData)
import Data.Data (Data)
import Data.Typeable (Typeable)
import GHC.Generics
import {-# SOURCE #-} Text.Megaparsec.Error (ParseError)
import Text.Megaparsec.Pos

-- | This is the Megaparsec's state parametrized over stream type @s@ and
-- custom error component type @e@.
data State s e = State
  { -- | The rest of input to process
    forall s e. State s e -> s
stateInput :: s,
    -- | Number of processed tokens so far
    --
    -- @since 7.0.0
    forall s e. State s e -> Int
stateOffset :: {-# UNPACK #-} !Int,
    -- | State that is used for line\/column calculation
    --
    -- @since 7.0.0
    forall s e. State s e -> PosState s
statePosState :: PosState s,
    -- | Collection of “delayed” 'ParseError's in reverse order. This means
    -- that the last registered error is the first element of the list.
    --
    -- @since 8.0.0
    forall s e. State s e -> [ParseError s e]
stateParseErrors :: [ParseError s e]
  }
  deriving (Typeable, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall s e x. Rep (State s e) x -> State s e
forall s e x. State s e -> Rep (State s e) x
$cto :: forall s e x. Rep (State s e) x -> State s e
$cfrom :: forall s e x. State s e -> Rep (State s e) x
Generic)

deriving instance
  ( Show (ParseError s e),
    Show s
  ) =>
  Show (State s e)

deriving instance
  ( Eq (ParseError s e),
    Eq s
  ) =>
  Eq (State s e)

deriving instance
  ( Data e,
    Data (ParseError s e),
    Data s
  ) =>
  Data (State s e)

instance (NFData s, NFData (ParseError s e)) => NFData (State s e)

-- | A special kind of state that is used to calculate line\/column
-- positions on demand.
--
-- @since 7.0.0
data PosState s = PosState
  { -- | The rest of input to process
    forall s. PosState s -> s
pstateInput :: s,
    -- | Offset corresponding to beginning of 'pstateInput'
    forall s. PosState s -> Int
pstateOffset :: !Int,
    -- | Source position corresponding to beginning of 'pstateInput'
    forall s. PosState s -> SourcePos
pstateSourcePos :: !SourcePos,
    -- | Tab width to use for column calculation
    forall s. PosState s -> Pos
pstateTabWidth :: Pos,
    -- | Prefix to prepend to offending line
    forall s. PosState s -> String
pstateLinePrefix :: String
  }
  deriving (Int -> PosState s -> ShowS
forall s. Show s => Int -> PosState s -> ShowS
forall s. Show s => [PosState s] -> ShowS
forall s. Show s => PosState s -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PosState s] -> ShowS
$cshowList :: forall s. Show s => [PosState s] -> ShowS
show :: PosState s -> String
$cshow :: forall s. Show s => PosState s -> String
showsPrec :: Int -> PosState s -> ShowS
$cshowsPrec :: forall s. Show s => Int -> PosState s -> ShowS
Show, PosState s -> PosState s -> Bool
forall s. Eq s => PosState s -> PosState s -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PosState s -> PosState s -> Bool
$c/= :: forall s. Eq s => PosState s -> PosState s -> Bool
== :: PosState s -> PosState s -> Bool
$c== :: forall s. Eq s => PosState s -> PosState s -> Bool
Eq, PosState s -> DataType
PosState s -> Constr
forall {s}. Data s => Typeable (PosState s)
forall s. Data s => PosState s -> DataType
forall s. Data s => PosState s -> Constr
forall s.
Data s =>
(forall b. Data b => b -> b) -> PosState s -> PosState s
forall s u.
Data s =>
Int -> (forall d. Data d => d -> u) -> PosState s -> u
forall s u.
Data s =>
(forall d. Data d => d -> u) -> PosState s -> [u]
forall s r r'.
Data s =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PosState s -> r
forall s r r'.
Data s =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PosState s -> r
forall s (m :: * -> *).
(Data s, Monad m) =>
(forall d. Data d => d -> m d) -> PosState s -> m (PosState s)
forall s (m :: * -> *).
(Data s, MonadPlus m) =>
(forall d. Data d => d -> m d) -> PosState s -> m (PosState s)
forall s (c :: * -> *).
Data s =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PosState s)
forall s (c :: * -> *).
Data s =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PosState s -> c (PosState s)
forall s (t :: * -> *) (c :: * -> *).
(Data s, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (PosState s))
forall s (t :: * -> * -> *) (c :: * -> *).
(Data s, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (PosState s))
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PosState s)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PosState s -> c (PosState s)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (PosState s))
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PosState s -> m (PosState s)
$cgmapMo :: forall s (m :: * -> *).
(Data s, MonadPlus m) =>
(forall d. Data d => d -> m d) -> PosState s -> m (PosState s)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PosState s -> m (PosState s)
$cgmapMp :: forall s (m :: * -> *).
(Data s, MonadPlus m) =>
(forall d. Data d => d -> m d) -> PosState s -> m (PosState s)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PosState s -> m (PosState s)
$cgmapM :: forall s (m :: * -> *).
(Data s, Monad m) =>
(forall d. Data d => d -> m d) -> PosState s -> m (PosState s)
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PosState s -> u
$cgmapQi :: forall s u.
Data s =>
Int -> (forall d. Data d => d -> u) -> PosState s -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> PosState s -> [u]
$cgmapQ :: forall s u.
Data s =>
(forall d. Data d => d -> u) -> PosState s -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PosState s -> r
$cgmapQr :: forall s r r'.
Data s =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PosState s -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PosState s -> r
$cgmapQl :: forall s r r'.
Data s =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PosState s -> r
gmapT :: (forall b. Data b => b -> b) -> PosState s -> PosState s
$cgmapT :: forall s.
Data s =>
(forall b. Data b => b -> b) -> PosState s -> PosState s
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (PosState s))
$cdataCast2 :: forall s (t :: * -> * -> *) (c :: * -> *).
(Data s, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (PosState s))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (PosState s))
$cdataCast1 :: forall s (t :: * -> *) (c :: * -> *).
(Data s, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (PosState s))
dataTypeOf :: PosState s -> DataType
$cdataTypeOf :: forall s. Data s => PosState s -> DataType
toConstr :: PosState s -> Constr
$ctoConstr :: forall s. Data s => PosState s -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PosState s)
$cgunfold :: forall s (c :: * -> *).
Data s =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PosState s)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PosState s -> c (PosState s)
$cgfoldl :: forall s (c :: * -> *).
Data s =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PosState s -> c (PosState s)
Data, Typeable, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall s x. Rep (PosState s) x -> PosState s
forall s x. PosState s -> Rep (PosState s) x
$cto :: forall s x. Rep (PosState s) x -> PosState s
$cfrom :: forall s x. PosState s -> Rep (PosState s) x
Generic)

instance NFData s => NFData (PosState s)