{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}

-- |
-- Module      :  Text.Megaparsec.Char.Lexer
-- Copyright   :  © 2015–present Megaparsec contributors
--                © 2007 Paolo Martini
--                © 1999–2001 Daan Leijen
-- License     :  FreeBSD
--
-- Maintainer  :  Mark Karpov <markkarpov92@gmail.com>
-- Stability   :  experimental
-- Portability :  non-portable
--
-- High-level parsers to help you write your lexer. The module doesn't
-- impose how you should write your parser, but certain approaches may be
-- more elegant than others.
--
-- Parsing of white space is an important part of any parser. We propose a
-- convention where __every lexeme parser assumes no spaces before the__
-- __lexeme and consumes all spaces after the lexeme__; this is what the
-- 'lexeme' combinator does, and so it's enough to wrap every lexeme parser
-- with 'lexeme' to achieve this. Note that you'll need to call 'space'
-- manually to consume any white space before the first lexeme (i.e. at the
-- beginning of the file).
--
-- This module is intended to be imported qualified:
--
-- > import qualified Text.Megaparsec.Char.Lexer as L
--
-- To do lexing of byte streams, see "Text.Megaparsec.Byte.Lexer".
module Text.Megaparsec.Char.Lexer
  ( -- * White space
    space,
    lexeme,
    symbol,
    symbol',
    skipLineComment,
    skipBlockComment,
    skipBlockCommentNested,

    -- * Indentation
    indentLevel,
    incorrectIndent,
    indentGuard,
    nonIndented,
    IndentOpt (..),
    indentBlock,
    lineFold,

    -- * Character and string literals
    charLiteral,

    -- * Numbers
    decimal,
    binary,
    octal,
    hexadecimal,
    scientific,
    float,
    signed,
  )
where

import Control.Applicative
import Control.Monad (void)
import qualified Data.Char as Char
import Data.List (foldl')
import Data.List.NonEmpty (NonEmpty (..))
import Data.Maybe (fromMaybe, isJust, listToMaybe)
import Data.Proxy
import Data.Scientific (Scientific)
import qualified Data.Scientific as Sci
import qualified Data.Set as E
import Text.Megaparsec
import qualified Text.Megaparsec.Char as C
import Text.Megaparsec.Lexer

----------------------------------------------------------------------------
-- White space

-- | Given a comment prefix this function returns a parser that skips line
-- comments. Note that it stops just before the newline character but
-- doesn't consume the newline. Newline is either supposed to be consumed by
-- 'space' parser or picked up manually.
skipLineComment ::
  (MonadParsec e s m, Token s ~ Char) =>
  -- | Line comment prefix
  Tokens s ->
  m ()
skipLineComment :: forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Tokens s -> m ()
skipLineComment Tokens s
prefix =
  forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
C.string Tokens s
prefix forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall (f :: * -> *) a. Functor f => f a -> f ()
void (forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhileP (forall a. a -> Maybe a
Just String
"character") (forall a. Eq a => a -> a -> Bool
/= Char
'\n'))
{-# INLINEABLE skipLineComment #-}

-- | @'skipBlockComment' start end@ skips non-nested block comment starting
-- with @start@ and ending with @end@.
skipBlockComment ::
  (MonadParsec e s m, Token s ~ Char) =>
  -- | Start of block comment
  Tokens s ->
  -- | End of block comment
  Tokens s ->
  m ()
skipBlockComment :: forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Tokens s -> Tokens s -> m ()
skipBlockComment Tokens s
start Tokens s
end = m (Tokens s)
p forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (f :: * -> *) a. Functor f => f a -> f ()
void (forall (m :: * -> *) a end. MonadPlus m => m a -> m end -> m [a]
manyTill forall e s (m :: * -> *). MonadParsec e s m => m (Token s)
anySingle m (Tokens s)
n)
  where
    p :: m (Tokens s)
p = forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
C.string Tokens s
start
    n :: m (Tokens s)
n = forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
C.string Tokens s
end
{-# INLINEABLE skipBlockComment #-}

-- | @'skipBlockCommentNested' start end@ skips possibly nested block
-- comment starting with @start@ and ending with @end@.
--
-- @since 5.0.0
skipBlockCommentNested ::
  (MonadParsec e s m, Token s ~ Char) =>
  -- | Start of block comment
  Tokens s ->
  -- | End of block comment
  Tokens s ->
  m ()
skipBlockCommentNested :: forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Tokens s -> Tokens s -> m ()
skipBlockCommentNested Tokens s
start Tokens s
end = m (Tokens s)
p forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (f :: * -> *) a. Functor f => f a -> f ()
void (forall (m :: * -> *) a end. MonadPlus m => m a -> m end -> m [a]
manyTill m ()
e m (Tokens s)
n)
  where
    e :: m ()
e = forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Tokens s -> Tokens s -> m ()
skipBlockCommentNested Tokens s
start Tokens s
end forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (f :: * -> *) a. Functor f => f a -> f ()
void forall e s (m :: * -> *). MonadParsec e s m => m (Token s)
anySingle
    p :: m (Tokens s)
p = forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
C.string Tokens s
start
    n :: m (Tokens s)
n = forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
C.string Tokens s
end
{-# INLINEABLE skipBlockCommentNested #-}

----------------------------------------------------------------------------
-- Indentation

-- | Return the current indentation level.
--
-- The function is a simple shortcut defined as:
--
-- > indentLevel = sourceColumn <$> getPosition
--
-- @since 4.3.0
indentLevel :: (TraversableStream s, MonadParsec e s m) => m Pos
indentLevel :: forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m Pos
indentLevel = SourcePos -> Pos
sourceColumn forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m SourcePos
getSourcePos
{-# INLINE indentLevel #-}

-- | Fail reporting incorrect indentation error. The error has attached
-- information:
--
--     * Desired ordering between reference level and actual level
--     * Reference indentation level
--     * Actual indentation level
--
-- @since 5.0.0
incorrectIndent ::
  MonadParsec e s m =>
  -- | Desired ordering between reference level and actual level
  Ordering ->
  -- | Reference indentation level
  Pos ->
  -- | Actual indentation level
  Pos ->
  m a
incorrectIndent :: forall e s (m :: * -> *) a.
MonadParsec e s m =>
Ordering -> Pos -> Pos -> m a
incorrectIndent Ordering
ord Pos
ref Pos
actual =
  forall e s (m :: * -> *) a.
MonadParsec e s m =>
Set (ErrorFancy e) -> m a
fancyFailure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Set a
E.singleton forall a b. (a -> b) -> a -> b
$
    forall e. Ordering -> Pos -> Pos -> ErrorFancy e
ErrorIndentation Ordering
ord Pos
ref Pos
actual
{-# INLINEABLE incorrectIndent #-}

-- | @'indentGuard' spaceConsumer ord ref@ first consumes all white space
-- (indentation) with @spaceConsumer@ parser, then it checks the column
-- position. Ordering between current indentation level and the reference
-- indentation level @ref@ should be @ord@, otherwise the parser fails. On
-- success the current column position is returned.
--
-- When you want to parse a block of indentation, first run this parser with
-- arguments like @'indentGuard' spaceConsumer 'GT' 'pos1'@—this will make
-- sure you have some indentation. Use returned value to check indentation
-- on every subsequent line according to syntax of your language.
indentGuard ::
  (TraversableStream s, MonadParsec e s m) =>
  -- | How to consume indentation (white space)
  m () ->
  -- | Desired ordering between reference level and actual level
  Ordering ->
  -- | Reference indentation level
  Pos ->
  -- | Current column (indentation level)
  m Pos
indentGuard :: forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m () -> Ordering -> Pos -> m Pos
indentGuard m ()
sc Ordering
ord Pos
ref = do
  m ()
sc
  Pos
actual <- forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m Pos
indentLevel
  if forall a. Ord a => a -> a -> Ordering
compare Pos
actual Pos
ref forall a. Eq a => a -> a -> Bool
== Ordering
ord
    then forall (m :: * -> *) a. Monad m => a -> m a
return Pos
actual
    else forall e s (m :: * -> *) a.
MonadParsec e s m =>
Ordering -> Pos -> Pos -> m a
incorrectIndent Ordering
ord Pos
ref Pos
actual
{-# INLINEABLE indentGuard #-}

-- | Parse a non-indented construction. This ensures that there is no
-- indentation before actual data. Useful, for example, as a wrapper for
-- top-level function definitions.
--
-- @since 4.3.0
nonIndented ::
  (TraversableStream s, MonadParsec e s m) =>
  -- | How to consume indentation (white space)
  m () ->
  -- | How to parse actual data
  m a ->
  m a
nonIndented :: forall s e (m :: * -> *) a.
(TraversableStream s, MonadParsec e s m) =>
m () -> m a -> m a
nonIndented m ()
sc m a
p = forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m () -> Ordering -> Pos -> m Pos
indentGuard m ()
sc Ordering
EQ Pos
pos1 forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> m a
p
{-# INLINEABLE nonIndented #-}

-- | Behaviors for parsing of indented tokens. This is used in
-- 'indentBlock', which see.
--
-- @since 4.3.0
data IndentOpt m a b
  = -- | Parse no indented tokens, just return the value
    IndentNone a
  | -- | Parse many indented tokens (possibly zero), use given indentation
    -- level (if 'Nothing', use level of the first indented token); the
    -- second argument tells how to get the final result, and the third
    -- argument describes how to parse an indented token
    IndentMany (Maybe Pos) ([b] -> m a) (m b)
  | -- | Just like 'IndentMany', but requires at least one indented token to
    -- be present
    IndentSome (Maybe Pos) ([b] -> m a) (m b)

-- | Parse a “reference” token and a number of other tokens that have a
-- greater (but the same for all of them) level of indentation than that of
-- the “reference” token. The reference token can influence parsing, see
-- 'IndentOpt' for more information.
--
-- __Note__: the first argument of this function /must/ consume newlines
-- among other white space characters.
--
-- @since 4.3.0
indentBlock ::
  (TraversableStream s, MonadParsec e s m, Token s ~ Char) =>
  -- | How to consume indentation (white space)
  m () ->
  -- | How to parse “reference” token
  m (IndentOpt m a b) ->
  m a
indentBlock :: forall s e (m :: * -> *) a b.
(TraversableStream s, MonadParsec e s m, Token s ~ Char) =>
m () -> m (IndentOpt m a b) -> m a
indentBlock m ()
sc m (IndentOpt m a b)
r = do
  m ()
sc
  Pos
ref <- forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m Pos
indentLevel
  IndentOpt m a b
a <- m (IndentOpt m a b)
r
  case IndentOpt m a b
a of
    IndentNone a
x -> a
x forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ m ()
sc
    IndentMany Maybe Pos
indent [b] -> m a
f m b
p -> do
      Maybe Pos
mlvl <- (forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try) (forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Tokens s)
C.eol forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m () -> Ordering -> Pos -> m Pos
indentGuard m ()
sc Ordering
GT Pos
ref)
      Bool
done <- forall a. Maybe a -> Bool
isJust forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional forall e s (m :: * -> *). MonadParsec e s m => m ()
eof
      case (Maybe Pos
mlvl, Bool
done) of
        (Just Pos
lvl, Bool
False) ->
          forall s e (m :: * -> *) b.
(TraversableStream s, MonadParsec e s m) =>
Pos -> Pos -> m () -> m b -> m [b]
indentedItems Pos
ref (forall a. a -> Maybe a -> a
fromMaybe Pos
lvl Maybe Pos
indent) m ()
sc m b
p forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [b] -> m a
f
        (Maybe Pos, Bool)
_ -> m ()
sc forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [b] -> m a
f []
    IndentSome Maybe Pos
indent [b] -> m a
f m b
p -> do
      Pos
pos <- forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Tokens s)
C.eol forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m () -> Ordering -> Pos -> m Pos
indentGuard m ()
sc Ordering
GT Pos
ref
      let lvl :: Pos
lvl = forall a. a -> Maybe a -> a
fromMaybe Pos
pos Maybe Pos
indent
      b
x <-
        if
            | Pos
pos forall a. Ord a => a -> a -> Bool
<= Pos
ref -> forall e s (m :: * -> *) a.
MonadParsec e s m =>
Ordering -> Pos -> Pos -> m a
incorrectIndent Ordering
GT Pos
ref Pos
pos
            | Pos
pos forall a. Eq a => a -> a -> Bool
== Pos
lvl -> m b
p
            | Bool
otherwise -> forall e s (m :: * -> *) a.
MonadParsec e s m =>
Ordering -> Pos -> Pos -> m a
incorrectIndent Ordering
EQ Pos
lvl Pos
pos
      [b]
xs <- forall s e (m :: * -> *) b.
(TraversableStream s, MonadParsec e s m) =>
Pos -> Pos -> m () -> m b -> m [b]
indentedItems Pos
ref Pos
lvl m ()
sc m b
p
      [b] -> m a
f (b
x forall a. a -> [a] -> [a]
: [b]
xs)
{-# INLINEABLE indentBlock #-}

-- | Grab indented items. This is a helper for 'indentBlock', it's not a
-- part of the public API.
indentedItems ::
  (TraversableStream s, MonadParsec e s m) =>
  -- | Reference indentation level
  Pos ->
  -- | Level of the first indented item ('lookAhead'ed)
  Pos ->
  -- | How to consume indentation (white space)
  m () ->
  -- | How to parse indented tokens
  m b ->
  m [b]
indentedItems :: forall s e (m :: * -> *) b.
(TraversableStream s, MonadParsec e s m) =>
Pos -> Pos -> m () -> m b -> m [b]
indentedItems Pos
ref Pos
lvl m ()
sc m b
p = m [b]
go
  where
    go :: m [b]
go = do
      m ()
sc
      Pos
pos <- forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m Pos
indentLevel
      Bool
done <- forall a. Maybe a -> Bool
isJust forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional forall e s (m :: * -> *). MonadParsec e s m => m ()
eof
      if Bool
done
        then forall (m :: * -> *) a. Monad m => a -> m a
return []
        else
          if
              | Pos
pos forall a. Ord a => a -> a -> Bool
<= Pos
ref -> forall (m :: * -> *) a. Monad m => a -> m a
return []
              | Pos
pos forall a. Eq a => a -> a -> Bool
== Pos
lvl -> (:) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m b
p forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> m [b]
go
              | Bool
otherwise -> forall e s (m :: * -> *) a.
MonadParsec e s m =>
Ordering -> Pos -> Pos -> m a
incorrectIndent Ordering
EQ Pos
lvl Pos
pos

-- | Create a parser that supports line-folding. The first argument is used
-- to consume white space between components of line fold, thus it /must/
-- consume newlines in order to work properly. The second argument is a
-- callback that receives a custom space-consuming parser as an argument.
-- This parser should be used after separate components of line fold that
-- can be put on different lines.
--
-- An example should clarify the usage pattern:
--
-- > sc = L.space (void spaceChar) empty empty
-- >
-- > myFold = L.lineFold sc $ \sc' -> do
-- >   L.symbol sc' "foo"
-- >   L.symbol sc' "bar"
-- >   L.symbol sc  "baz" -- for the last symbol we use normal space consumer
--
-- @since 5.0.0
lineFold ::
  (TraversableStream s, MonadParsec e s m) =>
  -- | How to consume indentation (white space)
  m () ->
  -- | Callback that uses provided space-consumer
  (m () -> m a) ->
  m a
lineFold :: forall s e (m :: * -> *) a.
(TraversableStream s, MonadParsec e s m) =>
m () -> (m () -> m a) -> m a
lineFold m ()
sc m () -> m a
action =
  m ()
sc forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m Pos
indentLevel forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= m () -> m a
action forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Functor f => f a -> f ()
void forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m () -> Ordering -> Pos -> m Pos
indentGuard m ()
sc Ordering
GT
{-# INLINEABLE lineFold #-}

----------------------------------------------------------------------------
-- Character and string literals

-- | The lexeme parser parses a single literal character without quotes. The
-- purpose of this parser is to help with parsing of conventional escape
-- sequences. It's your responsibility to take care of character literal
-- syntax in your language (by surrounding it with single quotes or
-- similar).
--
-- The literal character is parsed according to the grammar rules defined in
-- the Haskell report.
--
-- Note that you can use this parser as a building block to parse various
-- string literals:
--
-- > stringLiteral = char '"' >> manyTill L.charLiteral (char '"')
--
-- __Performance note__: the parser is not particularly efficient at the
-- moment.
charLiteral :: (MonadParsec e s m, Token s ~ Char) => m Char
charLiteral :: forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m Char
charLiteral = forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"literal character" forall a b. (a -> b) -> a -> b
$ do
  -- The @~@ is needed to avoid requiring a MonadFail constraint,
  -- and we do know that r will be non-empty if count' succeeds.
  String
r <- forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
lookAhead (forall (m :: * -> *) a. MonadPlus m => Int -> Int -> m a -> m [a]
count' Int
1 Int
10 forall e s (m :: * -> *). MonadParsec e s m => m (Token s)
anySingle)
  case forall a. [a] -> Maybe a
listToMaybe (ReadS Char
Char.readLitChar String
r) of
    Just (Char
c, String
r') -> Char
c forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (m :: * -> *) a. Monad m => Int -> m a -> m ()
skipCount (forall (t :: * -> *) a. Foldable t => t a -> Int
length String
r forall a. Num a => a -> a -> a
- forall (t :: * -> *) a. Foldable t => t a -> Int
length String
r') forall e s (m :: * -> *). MonadParsec e s m => m (Token s)
anySingle
    Maybe (Char, String)
Nothing -> forall e s (m :: * -> *) a.
MonadParsec e s m =>
ErrorItem (Token s) -> m a
unexpected (forall t. NonEmpty t -> ErrorItem t
Tokens (forall a. [a] -> a
head String
r forall a. a -> [a] -> NonEmpty a
:| []))
{-# INLINEABLE charLiteral #-}

----------------------------------------------------------------------------
-- Numbers

-- | Parse an integer in the decimal representation according to the format
-- of integer literals described in the Haskell report.
--
-- If you need to parse signed integers, see the 'signed' combinator.
--
-- __Note__: before the version /6.0.0/ the function returned 'Integer',
-- i.e. it wasn't polymorphic in its return type.
--
-- __Warning__: this function does not perform range checks.
decimal :: (MonadParsec e s m, Token s ~ Char, Num a) => m a
decimal :: forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
decimal = forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
decimal_ forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> String
"integer"
{-# INLINEABLE decimal #-}

-- | A non-public helper to parse decimal integers.
decimal_ ::
  forall e s m a.
  (MonadParsec e s m, Token s ~ Char, Num a) =>
  m a
decimal_ :: forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
decimal_ = Tokens s -> a
mkNum forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhile1P (forall a. a -> Maybe a
Just String
"digit") Char -> Bool
Char.isDigit
  where
    mkNum :: Tokens s -> a
mkNum = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' forall {a}. Num a => a -> Char -> a
step a
0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. Stream s => Proxy s -> Tokens s -> [Token s]
chunkToTokens (forall {k} (t :: k). Proxy t
Proxy :: Proxy s)
    step :: a -> Char -> a
step a
a Char
c = a
a forall a. Num a => a -> a -> a
* a
10 forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
Char.digitToInt Char
c)
{-# INLINE decimal_ #-}

-- | Parse an integer in binary representation. The binary number is
-- expected to be a non-empty sequence of zeroes “0” and ones “1”.
--
-- You could of course parse some prefix before the actual number:
--
-- > binary = char '0' >> char' 'b' >> L.binary
--
-- __Warning__: this function does not perform range checks.
--
-- @since 7.0.0
binary ::
  forall e s m a.
  (MonadParsec e s m, Token s ~ Char, Num a) =>
  m a
binary :: forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
binary =
  Tokens s -> a
mkNum
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhile1P forall a. Maybe a
Nothing Char -> Bool
isBinDigit
    forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> String
"binary integer"
  where
    mkNum :: Tokens s -> a
mkNum = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' forall {a}. Num a => a -> Char -> a
step a
0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. Stream s => Proxy s -> Tokens s -> [Token s]
chunkToTokens (forall {k} (t :: k). Proxy t
Proxy :: Proxy s)
    step :: a -> Char -> a
step a
a Char
c = a
a forall a. Num a => a -> a -> a
* a
2 forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
Char.digitToInt Char
c)
    isBinDigit :: Char -> Bool
isBinDigit Char
x = Char
x forall a. Eq a => a -> a -> Bool
== Char
'0' Bool -> Bool -> Bool
|| Char
x forall a. Eq a => a -> a -> Bool
== Char
'1'
{-# INLINEABLE binary #-}

-- | Parse an integer in the octal representation. The format of the octal
-- number is expected to be according to the Haskell report except for the
-- fact that this parser doesn't parse “0o” or “0O” prefix. It is a
-- responsibility of the programmer to parse correct prefix before parsing
-- the number itself.
--
-- For example you can make it conform to the Haskell report like this:
--
-- > octal = char '0' >> char' 'o' >> L.octal
--
-- __Note__: before version /6.0.0/ the function returned 'Integer', i.e. it
-- wasn't polymorphic in its return type.
--
-- __Warning__: this function does not perform range checks.
octal ::
  forall e s m a.
  (MonadParsec e s m, Token s ~ Char, Num a) =>
  m a
octal :: forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
octal =
  Tokens s -> a
mkNum
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhile1P forall a. Maybe a
Nothing Char -> Bool
Char.isOctDigit
    forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> String
"octal integer"
  where
    mkNum :: Tokens s -> a
mkNum = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' forall {a}. Num a => a -> Char -> a
step a
0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. Stream s => Proxy s -> Tokens s -> [Token s]
chunkToTokens (forall {k} (t :: k). Proxy t
Proxy :: Proxy s)
    step :: a -> Char -> a
step a
a Char
c = a
a forall a. Num a => a -> a -> a
* a
8 forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
Char.digitToInt Char
c)
{-# INLINEABLE octal #-}

-- | Parse an integer in the hexadecimal representation. The format of the
-- hexadecimal number is expected to be according to the Haskell report
-- except for the fact that this parser doesn't parse “0x” or “0X” prefix.
-- It is a responsibility of the programmer to parse correct prefix before
-- parsing the number itself.
--
-- For example you can make it conform to the Haskell report like this:
--
-- > hexadecimal = char '0' >> char' 'x' >> L.hexadecimal
--
-- __Note__: before version /6.0.0/ the function returned 'Integer', i.e. it
-- wasn't polymorphic in its return type.
--
-- __Warning__: this function does not perform range checks.
hexadecimal ::
  forall e s m a.
  (MonadParsec e s m, Token s ~ Char, Num a) =>
  m a
hexadecimal :: forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
hexadecimal =
  Tokens s -> a
mkNum
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhile1P forall a. Maybe a
Nothing Char -> Bool
Char.isHexDigit
    forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> String
"hexadecimal integer"
  where
    mkNum :: Tokens s -> a
mkNum = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' forall {a}. Num a => a -> Char -> a
step a
0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. Stream s => Proxy s -> Tokens s -> [Token s]
chunkToTokens (forall {k} (t :: k). Proxy t
Proxy :: Proxy s)
    step :: a -> Char -> a
step a
a Char
c = a
a forall a. Num a => a -> a -> a
* a
16 forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
Char.digitToInt Char
c)
{-# INLINEABLE hexadecimal #-}

-- | Parse a floating point value as a 'Scientific' number. 'Scientific' is
-- great for parsing of arbitrary precision numbers coming from an untrusted
-- source. See documentation in "Data.Scientific" for more information.
--
-- The parser can be used to parse integers or floating point values. Use
-- functions like 'Data.Scientific.floatingOrInteger' from "Data.Scientific"
-- to test and extract integer or real values.
--
-- This function does not parse sign, if you need to parse signed numbers,
-- see 'signed'.
--
-- @since 5.0.0
scientific ::
  forall e s m.
  (MonadParsec e s m, Token s ~ Char) =>
  m Scientific
scientific :: forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m Scientific
scientific = do
  Integer
c' <- forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
decimal_
  SP Integer
c Int
e' <- forall (m :: * -> *) a. Alternative m => a -> m a -> m a
option (Integer -> Int -> SP
SP Integer
c' Int
0) (forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try forall a b. (a -> b) -> a -> b
$ forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Proxy s -> Integer -> m SP
dotDecimal_ (forall {k} (t :: k). Proxy t
Proxy :: Proxy s) Integer
c')
  Int
e <- forall (m :: * -> *) a. Alternative m => a -> m a -> m a
option Int
e' (forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try forall a b. (a -> b) -> a -> b
$ forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Int -> m Int
exponent_ Int
e')
  forall (m :: * -> *) a. Monad m => a -> m a
return (Integer -> Int -> Scientific
Sci.scientific Integer
c Int
e)
{-# INLINEABLE scientific #-}

data SP = SP !Integer {-# UNPACK #-} !Int

-- | Parse a floating point number according to the syntax for floating
-- point literals described in the Haskell report.
--
-- This function does not parse sign, if you need to parse signed numbers,
-- see 'signed'.
--
-- __Note__: before version /6.0.0/ the function returned 'Double', i.e. it
-- wasn't polymorphic in its return type.
--
-- __Note__: in versions /6.0.0/–/6.1.1/ this function accepted plain
-- integers.
float :: (MonadParsec e s m, Token s ~ Char, RealFloat a) => m a
float :: forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, RealFloat a) =>
m a
float = do
  Integer
c' <- forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
decimal_
  forall a. RealFloat a => Scientific -> a
Sci.toRealFloat
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ( ( do
              SP Integer
c Int
e' <- forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Proxy s -> Integer -> m SP
dotDecimal_ (forall {k} (t :: k). Proxy t
Proxy :: Proxy s) Integer
c'
              Int
e <- forall (m :: * -> *) a. Alternative m => a -> m a -> m a
option Int
e' (forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try forall a b. (a -> b) -> a -> b
$ forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Int -> m Int
exponent_ Int
e')
              forall (m :: * -> *) a. Monad m => a -> m a
return (Integer -> Int -> Scientific
Sci.scientific Integer
c Int
e)
          )
            forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Integer -> Int -> Scientific
Sci.scientific Integer
c' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Int -> m Int
exponent_ Int
0)
        )
{-# INLINEABLE float #-}

dotDecimal_ ::
  (MonadParsec e s m, Token s ~ Char) =>
  Proxy s ->
  Integer ->
  m SP
dotDecimal_ :: forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Proxy s -> Integer -> m SP
dotDecimal_ Proxy s
pxy Integer
c' = do
  forall (f :: * -> *) a. Functor f => f a -> f ()
void (forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
C.char Char
'.')
  let mkNum :: Tokens s -> SP
mkNum = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' SP -> Char -> SP
step (Integer -> Int -> SP
SP Integer
c' Int
0) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. Stream s => Proxy s -> Tokens s -> [Token s]
chunkToTokens Proxy s
pxy
      step :: SP -> Char -> SP
step (SP Integer
a Int
e') Char
c =
        Integer -> Int -> SP
SP
          (Integer
a forall a. Num a => a -> a -> a
* Integer
10 forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
Char.digitToInt Char
c))
          (Int
e' forall a. Num a => a -> a -> a
- Int
1)
  Tokens s -> SP
mkNum forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhile1P (forall a. a -> Maybe a
Just String
"digit") Char -> Bool
Char.isDigit
{-# INLINE dotDecimal_ #-}

exponent_ ::
  (MonadParsec e s m, Token s ~ Char) =>
  Int ->
  m Int
exponent_ :: forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Int -> m Int
exponent_ Int
e' = do
  forall (f :: * -> *) a. Functor f => f a -> f ()
void (forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
C.char' Char
'e')
  (forall a. Num a => a -> a -> a
+ Int
e') forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m () -> m a -> m a
signed (forall (m :: * -> *) a. Monad m => a -> m a
return ()) forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
decimal_
{-# INLINE exponent_ #-}

-- | @'signed' space p@ parses an optional sign character (“+” or “-”), then
-- if there is a sign it consumes optional white space (using the @space@
-- parser), then it runs the parser @p@ which should return a number. Sign
-- of the number is changed according to the previously parsed sign
-- character.
--
-- For example, to parse signed integer you can write:
--
-- > lexeme        = L.lexeme spaceConsumer
-- > integer       = lexeme L.decimal
-- > signedInteger = L.signed spaceConsumer integer
signed ::
  (MonadParsec e s m, Token s ~ Char, Num a) =>
  -- | How to consume white space after the sign
  m () ->
  -- | How to parse the number itself
  m a ->
  -- | Parser for signed numbers
  m a
signed :: forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m () -> m a -> m a
signed m ()
spc m a
p = forall (m :: * -> *) a. Alternative m => a -> m a -> m a
option forall a. a -> a
id (forall e s (m :: * -> *) a. MonadParsec e s m => m () -> m a -> m a
lexeme m ()
spc m (a -> a)
sign) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> m a
p
  where
    sign :: m (a -> a)
sign = (forall a. a -> a
id forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
C.char Char
'+') forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (forall a. Num a => a -> a
negate forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
C.char Char
'-')
{-# INLINEABLE signed #-}