{-# LANGUAGE Safe #-}
{-|
Module      : Text.Gigaparsec.Combinator
Description : This module contains a huge number of pre-made combinators that are
              very useful for a variety of purposes.
License     : BSD-3-Clause
Maintainer  : Jamie Willis, Gigaparsec Maintainers
Stability   : stable

This module contains a huge number of pre-made combinators that are very useful for a variety of purposes.

In particular, it contains combinators for: performing a parser iteratively, collecting all the results;
querying whether or not any input is left; optionally performing parsers; parsing delimited constructions;
handling multiple possible alternatives or parsers to sequence; handling more complex conditional execution;
and more.

@since 0.1.0.0
-}
module Text.Gigaparsec.Combinator (
  -- * Iterative Combinators
  -- | These combinators all execute a given parser an unbounded number of times, until either it fails, or another
  -- parser succeeds, depending on the combinator. Depending on the combinator, all of the results produced by the
  -- repeated execution of the parser may be returned in a @[]@. These are almost essential for any practical parsing
  -- task.
    manyN, skipMany, skipSome, skipManyN, count, count1, manyTill, someTill, skipManyTill, skipSomeTill,

  -- * Optional Parsing Combinators
  -- | These combinators allow for the /possible/ parsing of some parser. If the parser succeeds, that is ok
  -- so long as it __did not consume input__. Be aware that the result of the success may be replaced with
  -- these combinators, with the exception of "option", which still preserves the result.
    option, optional, optionalAs, decide, fromMaybeS,

  -- * Separated Values Combinators
  -- | These combinators are concerned with delimited parsing, where one parser is repeated but delimited by another one.
  -- In each of these cases @p@ is the parser of interest and @sep@ is the delimeter. These combinators mainly differ
  -- in either the number of @p@s they require, or exactly where the delimeters are allowed (only between, always
  -- trailing, or either). In all cases, they return the list of results generated by the repeated parses of @p@.
    sepBy, sepBy1, sepEndBy, sepEndBy1, endBy, endBy1,

  -- * Multiple Branching/Sequencing Combinators
  -- | These combinators allow for testing or sequencing a large number of parsers in one go.
    choice, sequence, traverse, skip,

  -- * Range Combinators
  -- | These combinators allow for the parsing of a specific parser either a specific number of times, or between a certain
  -- amount of times.
    exactly, range, range_, countRange,

  -- * Selective Combinators
  -- | These combinators allow for the conditional extraction of a result, or the execution of a parser
  -- based on another. They are derived from 'Text.Gigaparsec.branch'.
    ifS, whenS, guardS, whileS,
  ) where

import Text.Gigaparsec (Parsec, many, some, (<|>), ($>), (<:>), select,
                        branch, empty, unit, manyl, somel, notFollowedBy, liftA2, void)
import Data.Foldable (asum, sequenceA_)

{-|
This combinator tries to parse each of the parsers @ps@ in order, until one of them succeeds.

Finds the first parser in @ps@ which succeeds, returning its result. If Nothing of the parsers
succeed, then this combinator fails. If a parser fails having consumed input, this combinator
fails __immediately__.

==== __Examples__
>>> let p = choice [string "abc", string "ab", string "bc", string "d"]
>>> parse @String p "abc"
Success "abc"
>>> parse @String p "ab"
Failure ..
>>> parse @String p "bc"
Success "bc"
>>> parse @String p "x"
Failure ..

@since 0.1.0.0
-}
choice :: [Parsec a] -- ^ the parsers, @ps@ to try, in order.
       -> Parsec a   -- ^ a parser that tries to parse one of @ps@.
choice :: forall a. [Parsec a] -> Parsec a
choice = [Parsec a] -> Parsec a
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum

{-|
This combinator will parse each of @ps@ in order, discarding the results.

Given the parsers @ps@, consisting of @p1@ through @pn@, parses
each in order. If they all succeed, this combinator succeeds. If any of
the parsers fail, then the whole combinator fails.

==== __Examples__
>>> let p = skip [char'a', item, char 'c']
>>> parse @String p "abc"
Success ()
>>> parse @String p "ab"
Failure ..

@since 0.1.0.0
-}
skip :: [Parsec a] -- ^ parsers @ps@ to be sequenced.
     -> Parsec ()  -- ^ a parser that parses each of @ps@, returning @()@.
skip :: forall a. [Parsec a] -> Parsec ()
skip = [Parsec a] -> Parsec ()
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Applicative f) =>
t (f a) -> f ()
sequenceA_

{-|
This combinator tries to parse @p@, wrapping its result in a @Just@ if it succeeds, or returns @Nothing@ if it fails.

Tries to parse @p@. If @p@ succeeded, producing @x@, then @Just x@ is returned. Otherwise, if @p@ failed
__without consuming input__, then @Nothing@ is returned instead.

==== __Examples__
>>> let p = option (string "abc")
>>> parse @String p ""
Success Nothing
>>> parse @String p "abc"
Success (Just "abc")
>>> parse @String p "ab"
Failure ..

@since 0.1.0.0
-}
option :: Parsec a         -- ^ the parser @p@ to try to parse
       -> Parsec (Maybe a)
option :: forall a. Parsec a -> Parsec (Maybe a)
option Parsec a
p = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> Parsec a -> Parsec (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parsec a
p Parsec (Maybe a) -> Parsec (Maybe a) -> Parsec (Maybe a)
forall a. Parsec a -> Parsec a -> Parsec a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe a -> Parsec (Maybe a)
forall a. a -> Parsec a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing

{-|
This combinator will parse @p@ if possible, otherwise will do nothing.

Tries to parse @p@. If @p@ succeeds, or fails __without consuming input__ then this combinator is successful. Otherwise, if @p@ failed
having consumed input, this combinator fails.

==== __Examples__
>>> let p = optional (string "abc")
>>> parse @String p ""
Success ()
>>> parse @String p "abc"
Success ()
>>> parse @String p "ab"
Failure ..

@since 0.1.0.0
-}
optional :: Parsec a -- ^ the parser @p@ to try to parse.
         -> Parsec ()
optional :: forall a. Parsec a -> Parsec ()
optional = () -> Parsec a -> Parsec ()
forall b a. b -> Parsec a -> Parsec b
optionalAs ()

{-|
This combinator will parse @p@ if possible, otherwise will do nothing.

Tries to parse @p@. If @p@ succeeds, or fails __without consuming input__ then this combinator is successful and returns @x@. Otherwise,
if @p@ failed having consumed input, this combinator fails.

==== __Examples__
>>> let p = optionalAs 7 (string "abc")
>>> parse @String p ""
Success 7
>>> parse @String p "abc"
Success 7
>>> parse @String p "ab"
Failure ..

@since 0.1.0.0
-}
optionalAs :: b        -- ^ the value @x@ to return regardless of how @p@ performs.
           -> Parsec a -- ^ the parser @p@ to try to parse.
           -> Parsec b -- ^ a parser that tries to parse @p@, returning @x@ regardless of success or failure.
optionalAs :: forall b a. b -> Parsec a -> Parsec b
optionalAs b
x Parsec a
p = Parsec a
p Parsec a -> b -> Parsec b
forall a b. Parsec a -> b -> Parsec b
$> b
x Parsec b -> Parsec b -> Parsec b
forall a. Parsec a -> Parsec a -> Parsec a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> b -> Parsec b
forall a. a -> Parsec a
forall (f :: * -> *) a. Applicative f => a -> f a
pure b
x

-- TODO: collect
{-|
This combinator can eliminate an @Maybe@ from the result of the parser @p@.

First parse @p@, if it succeeds returning @Just x@, then return @x@. However,
if @p@ fails, or returned @Nothing@, then this combinator fails.

==== __Examples__
@decide (option p) = p@
-}
decide :: Parsec (Maybe a) -- ^ the parser @p@ to parse and extract the result from.
       -> Parsec a         -- ^ a parser that tries to extract the result from @p@.
decide :: forall a. Parsec (Maybe a) -> Parsec a
decide Parsec (Maybe a)
p = Parsec (Maybe a)
p Parsec (Maybe a) -> (Maybe a -> Parsec a) -> Parsec a
forall a b. Parsec a -> (a -> Parsec b) -> Parsec b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Parsec a -> (a -> Parsec a) -> Maybe a -> Parsec a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Parsec a
forall a. Parsec a
forall (f :: * -> *) a. Alternative f => f a
empty a -> Parsec a
forall a. a -> Parsec a
forall (f :: * -> *) a. Applicative f => a -> f a
pure

-- this is decide overload
{-|
This combinator parses @q@ depending only if @p@ returns a @Nothing@.

First parses @p@. If @p@ returned @Just x@, then @x@ is returned.
Otherwise, if @p@ returned @Nothing@ then @q@ is parsed, producing @y@,
and @y@ is returned. If @p@ or @q@ fails, the combinator fails.

==== __Examples__
fromMaybe q (option p) = p <|> q

@since 0.1.0.0
-}
fromMaybeS :: Parsec a         -- ^ a parser to execute when @p@ returns @Nothing@, to provide a value of type @a@.
           -> Parsec (Maybe a) -- ^ the first parser @p@, which returns an @Maybe@ to eliminate.
           -> Parsec a         -- ^ a parser that either just parses @p@ or both @p@ and @q@ in order to return an @a@.
fromMaybeS :: forall a. Parsec a -> Parsec (Maybe a) -> Parsec a
fromMaybeS Parsec a
q Parsec (Maybe a)
p = Parsec (Either () a) -> Parsec (() -> a) -> Parsec a
forall a b. Parsec (Either a b) -> Parsec (a -> b) -> Parsec b
forall (f :: * -> *) a b.
Selective f =>
f (Either a b) -> f (a -> b) -> f b
select (Either () a -> (a -> Either () a) -> Maybe a -> Either () a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> Either () a
forall a b. a -> Either a b
Left ()) a -> Either () a
forall a b. b -> Either a b
Right (Maybe a -> Either () a)
-> Parsec (Maybe a) -> Parsec (Either () a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parsec (Maybe a)
p) (a -> () -> a
forall a b. a -> b -> a
const (a -> () -> a) -> Parsec a -> Parsec (() -> a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parsec a
q)

{-|
This combinator repeatedly parses a given parser __@n@__ or more times, collecting the results into a list.

Parses a given parser, @p@, repeatedly until it fails. If @p@ failed having consumed input,
this combinator fails. Otherwise when @p@ fails __without consuming input__, this combinator
will return all of the results, @x1@ through @xm@ (with @m >= n@), in a list: @[x1, .., xm]@.
If @p@ was not successful at least @n@ times, this combinator fails.

==== __Examples__
>>> let p = manyN 2 (string "ab")
>>> parse @String p ""
Failure ..
>>> parse @String p "ab"
Failure ..
>>> parse @String p "abababab"
Success ["ab", "ab", "ab", "ab"]
>>> parse @String p "aba"
Failure ..

==== Notes
* @many p == many 0 p@ and @some p == many 1 p@.

@since 0.1.0.0
-}
manyN :: Int        -- ^ the minimum number of @p@s required, @n@.
      -> Parsec a   -- ^ the parser @p@ to execute multiple times.
      -> Parsec [a] -- ^ a parser that parses @p@ until it fails, returning the list of all the successful results.
manyN :: forall a. Int -> Parsec a -> Parsec [a]
manyN Int
0 Parsec a
p = Parsec a -> Parsec [a]
forall a. Parsec a -> Parsec [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many Parsec a
p
manyN Int
1 Parsec a
p = Parsec a -> Parsec [a]
forall a. Parsec a -> Parsec [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
some Parsec a
p
manyN Int
n Parsec a
p = Parsec a
p Parsec a -> Parsec [a] -> Parsec [a]
forall a. Parsec a -> Parsec [a] -> Parsec [a]
<:> Int -> Parsec a -> Parsec [a]
forall a. Int -> Parsec a -> Parsec [a]
manyN (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Parsec a
p

{-|
This combinator repeatedly parses a given parser __zero__ or more times, ignoring the results.

Parses a given parser, @p@, repeatedly until it fails. If @p@ failed having consumed input,
this combinator fails. Otherwise when @p@ fails __without consuming input__, this combinator
will succeed.

==== __Examples__
>>> let p = skipMany (string "ab")
>>> parse @String p ""
Success ()
>>> parse @String p "ab"
Success ()
>>> parse @String p "abababab"
Success ()
>>> parse @String p "aba"
Failure ..

@since 0.1.0.0
-}
skipMany :: Parsec a  -- ^ the parser @p@ to execute multiple times.
         -> Parsec () -- ^ a parser that parses @p@ until it fails, returning unit.
skipMany :: forall a. Parsec a -> Parsec ()
skipMany Parsec a
p = let go :: Parsec ()
go = Parsec a
p Parsec a -> Parsec () -> Parsec ()
forall a b. Parsec a -> Parsec b -> Parsec b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec ()
go Parsec () -> Parsec () -> Parsec ()
forall a. Parsec a -> Parsec a -> Parsec a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parsec ()
unit in Parsec ()
go

{-|
This combinator repeatedly parses a given parser __one__ or more times, ignoring the results.

Parses a given parser, @p@, repeatedly until it fails. If @p@ failed having consumed input,
this combinator fails. Otherwise when @p@ fails __without consuming input__, this combinator
will succeed. The parser @p@ must succeed at least once.

==== __Examples__
>>> let p = skipSome (string "ab")
>>> parse @String p ""
Failure ..
>>> parse @String p "ab"
Success ()
>>> parse @String p "abababab"
Success ()
>>> parse @String p "aba"
Failure ..

@since 0.1.0.0
-}
skipSome :: Parsec a  -- ^ @p@, the parser to execute multiple times.
         -> Parsec () -- ^ a parser that parses @p@ until it fails, returning unit.
skipSome :: forall a. Parsec a -> Parsec ()
skipSome Parsec a
p = Parsec a
p Parsec a -> Parsec () -> Parsec ()
forall a b. Parsec a -> Parsec b -> Parsec b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec a -> Parsec ()
forall a. Parsec a -> Parsec ()
skipMany Parsec a
p

{-|
This combinator repeatedly parses a given parser __@n@__ or more times, ignoring the results.

Parses a given parser, @p@, repeatedly until it fails. If @p@ failed having consumed input,
this combinator fails. Otherwise when @p@ fails __without consuming input__, this combinator
will succeed. The parser @p@ must succeed at least @n@ times.

==== __Examples__
>>> let p = skipManyN 2 (string "ab")
>>> parse @String p ""
Failure ..
>>> parse @String p "ab"
Failure ..
>>> parse @String p "abababab"
Success ()
>>> parse @String p "aba"
Failure ..

@since 0.1.0.0
-}
skipManyN :: Int       -- ^ @n@, the minimum number of times to execute.
          -> Parsec a  -- ^ @p@, the parser to execute multiple times.
          -> Parsec () -- ^ a parser that parses @p@ until it fails, returning unit.
skipManyN :: forall a. Int -> Parsec a -> Parsec ()
skipManyN Int
0 Parsec a
p = Parsec a -> Parsec ()
forall a. Parsec a -> Parsec ()
skipMany Parsec a
p
skipManyN Int
1 Parsec a
p = Parsec a -> Parsec ()
forall a. Parsec a -> Parsec ()
skipSome Parsec a
p
skipManyN Int
n Parsec a
p = Parsec a
p Parsec a -> Parsec () -> Parsec ()
forall a b. Parsec a -> Parsec b -> Parsec b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Int -> Parsec a -> Parsec ()
forall a. Int -> Parsec a -> Parsec ()
skipManyN (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Parsec a
p

{-|
This combinator repeatedly parses a given parser __zero__ or more times, returning how many times it succeeded.

Parses a given parser, @p@, repeatedly until it fails. If @p@ failed having consumed input,
this combinator fails. Otherwise when @p@ fails __without consuming input__, this combinator
will succeed. The number of times @p@ succeeded is returned as the result.

==== __Examples__
>>> let p = count (string "ab")
>>> parse @String p ""
Success 0
>>> parse @String p "ab"
Success 1
>>> parse @String p "abababab"
Success 4
>>> parse @String p "aba"
Failure ..

@since 0.1.0.0
-}
count :: Parsec a   -- ^ @p@, the parser to execute multiple times.
      -> Parsec Int -- ^ the number of times @p@ successfully parses
count :: forall a. Parsec a -> Parsec Int
count = (Int -> a -> Int) -> Int -> Parsec a -> Parsec Int
forall b a. (b -> a -> b) -> b -> Parsec a -> Parsec b
manyl ((a -> Int -> Int) -> Int -> a -> Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((Int -> Int) -> a -> Int -> Int
forall a b. a -> b -> a
const (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1))) Int
0

{-|
This combinator repeatedly parses a given parser __one__ or more times, returning how many times it succeeded.

Parses a given parser, @p@, repeatedly until it fails. If @p@ failed having consumed input,
this combinator fails. Otherwise when @p@ fails __without consuming input__, this combinator
will succeed. The parser @p@ must succeed at least once. The number of times @p@ succeeded is returned as the result.

==== __Examples__
>>> let p = count1 (string "ab")
>>> parse @String p ""
Failure ..
>>> parse @String p "ab"
Success 1
>>> parse @String p "abababab"
Success 4
>>> parse @String p "aba"
Failure ..

@since 0.1.0.0
-}
count1 :: Parsec a   -- ^ @p@, the parser to execute multiple times.
       -> Parsec Int -- ^ the number of times @p@ successfully parses
count1 :: forall a. Parsec a -> Parsec Int
count1 = (Int -> a -> Int) -> Int -> Parsec a -> Parsec Int
forall b a. (b -> a -> b) -> b -> Parsec a -> Parsec b
somel ((a -> Int -> Int) -> Int -> a -> Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((Int -> Int) -> a -> Int -> Int
forall a b. a -> b -> a
const (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1))) Int
0

{-|
This combinator parses __zero__ or more occurrences of @p@, separated by @sep@.

Behaves just like @sepBy1@, except does not require an initial @p@, returning the empty list instead.

==== __Examples__
>>> ...
>>> let args = sepBy int (string ", ")
>>> parse @String args "7, 3, 2"
Success [7, 3, 2]
>>> parse @String args ""
Success []
>>> parse @String args "1"
Success [1]
>>> parse @String args "1, 2, "
Failure ..

@since 0.1.0.0
-}
sepBy :: Parsec a   -- ^ @p@, the parser whose results are collected into a list.
      -> Parsec sep -- ^ @sep@, the delimiter that must be parsed between every @p@.
      -> Parsec [a] -- ^ a parser that parses @p@ delimited by @sep@, returning the list of @p@'s results.
sepBy :: forall a sep. Parsec a -> Parsec sep -> Parsec [a]
sepBy Parsec a
p Parsec sep
sep = Parsec a -> Parsec sep -> Parsec [a]
forall a sep. Parsec a -> Parsec sep -> Parsec [a]
sepBy1 Parsec a
p Parsec sep
sep Parsec [a] -> Parsec [a] -> Parsec [a]
forall a. Parsec a -> Parsec a -> Parsec a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [a] -> Parsec [a]
forall a. a -> Parsec a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []

{-|
This combinator parses __one__ or more occurrences of @p@, separated by @sep@.

First parses a @p@. Then parses @sep@ followed by @p@ until there are no more @sep@s.
The results of the @p@'s, @x1@ through @xn@, are returned as @[x1, .., xn]@.
If @p@ or @sep@ fails having consumed input, the whole parser fails. Requires at least
one @p@ to have been parsed.

==== __Examples__
>>> ...
>>> let args = sepBy1 int (string ", ")
>>> parse @String args "7, 3, 2"
Success [7, 3, 2]
>>> parse @String args ""
Failure ..
>>> parse @String args "1"
Success [1]
>>> parse @String args "1, 2, "
Failure ..

@since 0.1.0.0
-}
sepBy1 :: Parsec a   -- ^ @p@, the parser whose results are collected into a list.
       -> Parsec sep -- ^ @sep@, the delimiter that must be parsed between every @p@.
       -> Parsec [a] -- ^ a parser that parses @p@ delimited by @sep@, returning the list of @p@'s results.
sepBy1 :: forall a sep. Parsec a -> Parsec sep -> Parsec [a]
sepBy1 Parsec a
p Parsec sep
sep = Parsec a
p Parsec a -> Parsec [a] -> Parsec [a]
forall a. Parsec a -> Parsec [a] -> Parsec [a]
<:> Parsec a -> Parsec [a]
forall a. Parsec a -> Parsec [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (Parsec sep
sep Parsec sep -> Parsec a -> Parsec a
forall a b. Parsec a -> Parsec b -> Parsec b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec a
p)

{-|
This combinator parses __zero__ or more occurrences of @p@, separated and optionally ended by @sep@.

Behaves just like @sepEndBy1@, except does not require an initial @p@, returning the empty list instead.

==== __Examples__
>>> ...
>>> let args = sepEndBy int (string ";\n")
>>> parse @String args "7;\n3;\n2"
Success [7, 3, 2]
>>> parse @String args ""
Success Nil
>>> parse @String args "1"
Success [1]
>>> parse @String args "1;\n2;\n"
Success [1, 2]

@since 0.1.0.0
-}
sepEndBy :: Parsec a   -- ^ @p@, the parser whose results are collected into a list.
         -> Parsec sep -- ^ @sep@, the delimiter that must be parsed between every @p@.
         -> Parsec [a] -- ^ a parser that parses @p@ delimited by @sep@, returning the list of @p@'s results.
sepEndBy :: forall a sep. Parsec a -> Parsec sep -> Parsec [a]
sepEndBy Parsec a
p Parsec sep
sep = Parsec a -> Parsec sep -> Parsec [a]
forall a sep. Parsec a -> Parsec sep -> Parsec [a]
sepEndBy1 Parsec a
p Parsec sep
sep Parsec [a] -> Parsec [a] -> Parsec [a]
forall a. Parsec a -> Parsec a -> Parsec a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [a] -> Parsec [a]
forall a. a -> Parsec a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []

{-|
This combinator parses __one__ or more occurrences of @p@, separated and optionally ended by @sep@.

First parses a @p@. Then parses @sep@ followed by @p@ until there are no more: if a final @sep@ exists, this is parsed.
The results of the @p@'s, @x1@ through @xn@, are returned as @[x1, .., xn]@.
If @p@ or @sep@ fails having consumed input, the whole parser fails. Requires at least
one @p@ to have been parsed.

==== __Examples__
>>> ...
>>> let args = sepEndBy1 int (string ";\n")
>>> parse @String args "7;\n3;\n2"
Success [7, 3, 2]
>>> parse @String args ""
Failure ..
>>> parse @String args "1"
Success [1]
>>> parse @String args "1;\n2;\n"
Success [1, 2]

@since 0.1.0.0
-}
sepEndBy1 :: Parsec a   -- ^ @p@, the parser whose results are collected into a list.
          -> Parsec sep -- ^ @sep@, the delimiter that must be parsed between every @p@.
          -> Parsec [a] -- ^ a parser that parses @p@ delimited by @sep@, returning the list of @p@'s results.
sepEndBy1 :: forall a sep. Parsec a -> Parsec sep -> Parsec [a]
sepEndBy1 Parsec a
p Parsec sep
sep = let seb1 :: Parsec [a]
seb1 = Parsec a
p Parsec a -> Parsec [a] -> Parsec [a]
forall a. Parsec a -> Parsec [a] -> Parsec [a]
<:> (Parsec sep
sep Parsec sep -> Parsec [a] -> Parsec [a]
forall a b. Parsec a -> Parsec b -> Parsec b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Parsec [a]
seb1 Parsec [a] -> Parsec [a] -> Parsec [a]
forall a. Parsec a -> Parsec a -> Parsec a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [a] -> Parsec [a]
forall a. a -> Parsec a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []) Parsec [a] -> Parsec [a] -> Parsec [a]
forall a. Parsec a -> Parsec a -> Parsec a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [a] -> Parsec [a]
forall a. a -> Parsec a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []) in Parsec [a]
seb1

{-|
This combinator parses __zero__ or more occurrences of @p@, separated and ended by @sep@.

Behaves just like @endBy1@, except does not require an initial @p@ and @sep@, returning the empty list instead.

==== __Examples__
>>> ...
>>> let args = endBy int (string ";\n")
>>> parse @String args "7;\n3;\n2"
Failure ..
>>> parse @String args ""
Success Nil
>>> parse @String args "1;\n"
Success [1]
>>> parse @String args "1;\n2;\n"
Success [1, 2]

@since 0.1.0.0
-}
endBy :: Parsec a   -- ^ @p@, the parser whose results are collected into a list.
      -> Parsec sep -- ^ @sep@, the delimiter that must be parsed between every @p@.
      -> Parsec [a] -- ^ a parser that parses @p@ delimited by @sep@, returning the list of @p@'s results.
endBy :: forall a sep. Parsec a -> Parsec sep -> Parsec [a]
endBy Parsec a
p Parsec sep
sep = Parsec a -> Parsec sep -> Parsec [a]
forall a sep. Parsec a -> Parsec sep -> Parsec [a]
endBy1 Parsec a
p Parsec sep
sep Parsec [a] -> Parsec [a] -> Parsec [a]
forall a. Parsec a -> Parsec a -> Parsec a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [a] -> Parsec [a]
forall a. a -> Parsec a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []

{-|
This combinator parses __one__ or more occurrences of @p@, separated and ended by @sep@.

Parses @p@ followed by @sep@ one or more times.
The results of the @p@'s, @x1@ through @xn@, are returned as @[x1, .., xn]@.
If @p@ or @sep@ fails having consumed input, the whole parser fails.

==== __Examples__
>>> ...
>>> let args = endBy1 int (string ";\n")
>>> parse @String args "7;\n3;\n2"
Failure ..
>>> parse @String args ""
Failure ..
>>> parse @String args "1;\n"
Success [1]
>>> parse @String args "1;\n2;\n"
Success [1, 2]

@since 0.1.0.0
-}
endBy1 :: Parsec a   -- ^ @p@, the parser whose results are collected into a list.
       -> Parsec sep -- ^ @sep@, the delimiter that must be parsed between every @p@.
       -> Parsec [a] -- ^ a parser that parses @p@ delimited by @sep@, returning the list of @p@'s results.
endBy1 :: forall a sep. Parsec a -> Parsec sep -> Parsec [a]
endBy1 Parsec a
p Parsec sep
sep = Parsec a -> Parsec [a]
forall a. Parsec a -> Parsec [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
some (Parsec a
p Parsec a -> Parsec sep -> Parsec a
forall a b. Parsec a -> Parsec b -> Parsec a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parsec sep
sep)

{-|
This combinator repeatedly parses a given parser __zero__ or more times, until the @end@ parser succeeds, collecting the results into a list.

First tries to parse @end@, if it fails __without consuming input__, then parses @p@, which must succeed. This repeats until @end@ succeeds.
When @end@ does succeed, this combinator will return all of the results generated by @p@, @x1@ through @xn@ (with @n >= 0@), in a
list: @[x1, .., xn]@. If @end@ could be parsed immediately, the empty list is returned.

==== __Examples__
This can be useful for scanning comments:

>>> let comment = string "--" *> manyUntil item endOfLine
>>> parse @String p "--hello world"
Failure ..
>>> parse @String p "--hello world\n"
Success ['h', 'e', 'l', 'l', 'o', ' ', 'w', 'o', 'r', 'l', 'd']
>>> parse @String p "--\n"
Success Nil

@since 0.1.0.0
-}
manyTill :: Parsec a   -- ^ @p@, the parser to execute multiple times.
         -> Parsec end -- ^ @end@, the parser that stops the parsing of @p@.
         -> Parsec [a] -- ^ a parser that parses @p@ until @end@ succeeds, returning the list of all the successful results.
manyTill :: forall a sep. Parsec a -> Parsec sep -> Parsec [a]
manyTill Parsec a
p Parsec end
end = let go :: Parsec [a]
go = Parsec end
end Parsec end -> [a] -> Parsec [a]
forall a b. Parsec a -> b -> Parsec b
$> [] Parsec [a] -> Parsec [a] -> Parsec [a]
forall a. Parsec a -> Parsec a -> Parsec a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parsec a
p Parsec a -> Parsec [a] -> Parsec [a]
forall a. Parsec a -> Parsec [a] -> Parsec [a]
<:> Parsec [a]
go in Parsec [a]
go

{-|
This combinator repeatedly parses a given parser __one__ or more times, until the @end@ parser succeeds, collecting the results into a list.

First ensures that trying to parse @end@ fails, then tries to parse @p@. If it succeed then it will repeatedly: try to parse @end@, if it fails
__without consuming input__, then parses @p@, which must succeed. When @end@ does succeed, this combinator will return all of the results
generated by @p@, @x1@ through @xn@ (with @n >= 1@), in a list: @[x1, .., xn]@. The parser @p@ must succeed at least once
before @end@ succeeds.

==== __Examples__
This can be useful for scanning comments:

>>> let comment = string "--" *> someUntil item endOfLine
>>> parse @String p "--hello world"
Failure ..
>>> parse @String p "--hello world\n"
Success ['h', 'e', 'l', 'l', 'o', ' ', 'w', 'o', 'r', 'l', 'd']
>>> parse @String p "--\n"
Failure ..
>>> parse @String p "--a\n"
Success ['a']

@since 0.1.0.0
-}
someTill :: Parsec a   -- ^ @p@, the parser to execute multiple times.
         -> Parsec end -- ^ @end@, the parser that stops the parsing of @p@.
         -> Parsec [a] -- ^ a parser that parses @p@ until @end@ succeeds, returning the list of all the successful results.
someTill :: forall a sep. Parsec a -> Parsec sep -> Parsec [a]
someTill Parsec a
p Parsec end
end = Parsec end -> Parsec ()
forall a. Parsec a -> Parsec ()
notFollowedBy Parsec end
end Parsec () -> Parsec [a] -> Parsec [a]
forall a b. Parsec a -> Parsec b -> Parsec b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Parsec a
p Parsec a -> Parsec [a] -> Parsec [a]
forall a. Parsec a -> Parsec [a] -> Parsec [a]
<:> Parsec a -> Parsec end -> Parsec [a]
forall a sep. Parsec a -> Parsec sep -> Parsec [a]
manyTill Parsec a
p Parsec end
end)

skipManyTill :: Parsec a -> Parsec end -> Parsec ()
skipManyTill :: forall a end. Parsec a -> Parsec end -> Parsec ()
skipManyTill Parsec a
p Parsec end
end = Parsec [a] -> Parsec ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Parsec a -> Parsec end -> Parsec [a]
forall a sep. Parsec a -> Parsec sep -> Parsec [a]
manyTill Parsec a
p Parsec end
end)

skipSomeTill :: Parsec a -> Parsec end -> Parsec ()
skipSomeTill :: forall a end. Parsec a -> Parsec end -> Parsec ()
skipSomeTill Parsec a
p Parsec end
end = Parsec [a] -> Parsec ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Parsec a -> Parsec end -> Parsec [a]
forall a sep. Parsec a -> Parsec sep -> Parsec [a]
someTill Parsec a
p Parsec end
end)

-- this is ifP
{-|
This combinator parses one of @thenP@ or @elseP@ depending on the result of parsing @condP@.

This is a lifted @if@-statement. First, parse @condP@: if it is successful and returns
@True@, then parse @thenP@; else, if it returned @False@, parse @elseP@; or, if @condP@ failed
then fail. If either of @thenP@ or @elseP@ fail, then this combinator also fails.

Most useful in conjunction with /Registers/, as this allows for decisions to be made
based on state.

==== __Examples__
>>> ifP (pure True) p _ == p
>>> ifP (pure False) _ p == p

@since 0.1.0.0
-}
ifS :: Parsec Bool -- ^ @condP@, the parser that yields the condition value.
    -> Parsec a    -- ^ @thenP@, the parser to execute if the condition is @True@.
    -> Parsec a    -- ^ @elseP@, the parser to execute if the condition is @False@.
    -> Parsec a    -- ^ a parser that conditionally parses @thenP@ or @elseP@ after @condP@.
ifS :: forall a. Parsec Bool -> Parsec a -> Parsec a -> Parsec a
ifS Parsec Bool
cond Parsec a
t Parsec a
e = Parsec (Either () ())
-> Parsec (() -> a) -> Parsec (() -> a) -> Parsec a
forall (f :: * -> *) a b c.
Selective f =>
f (Either a b) -> f (a -> c) -> f (b -> c) -> f c
branch (Bool -> Either () ()
bool (Bool -> Either () ()) -> Parsec Bool -> Parsec (Either () ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parsec Bool
cond) (a -> () -> a
forall a b. a -> b -> a
const (a -> () -> a) -> Parsec a -> Parsec (() -> a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parsec a
e) (a -> () -> a
forall a b. a -> b -> a
const (a -> () -> a) -> Parsec a -> Parsec (() -> a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parsec a
t)
  where bool :: Bool -> Either () ()
bool Bool
True = () -> Either () ()
forall a b. b -> Either a b
Right ()
        bool Bool
False = () -> Either () ()
forall a b. a -> Either a b
Left ()

-- this is when
{-|
This combinator conditionally parses @thenP@ depending on the result of parsing @condP@.

This is a lifted @if@-statement. First, parse @condP@: if it is successful and returns
@True@, then parse @thenP@; else, if it returned @False@ do nothing; or, if @condP@ failed
then fail. If @thenP@ fails, then this combinator also fails.

Most useful in conjunction with /Registers/, as this allows for decisions to be made
based on state.

==== __Examples__
>>> when (pure True) p == p
>>> when (pure False) _ == unit

@since 0.1.0.0
-}
whenS :: Parsec Bool -- ^ @condP@, the parser that yields the condition value.
      -> Parsec ()   -- ^ @thenP@, the parser to execute if the condition is @True@.
      -> Parsec ()   -- ^ a parser that conditionally parses @thenP@ after @condP@.
whenS :: Parsec Bool -> Parsec () -> Parsec ()
whenS Parsec Bool
cond Parsec ()
p = Parsec Bool -> Parsec () -> Parsec () -> Parsec ()
forall a. Parsec Bool -> Parsec a -> Parsec a -> Parsec a
ifS Parsec Bool
cond Parsec ()
p Parsec ()
unit

-- this is guard
{-|
This combinator verfies that the given parser returns @True@, or else fails.

First, parse @p@; if it succeeds then, so long at returns @True@, this @guard p@ succeeds. Otherwise,
if @p@ either fails, or returns @False@, @guard p@ will fail.

==== __Examples__
>>> guard (pure True) == unit
>>> guard (pure False) == empty
>>> when (not <$> p) empty == guard p

@since 0.1.0.0
-}
guardS :: Parsec Bool -- ^ @p@, the parser that yields the condition value.
       -> Parsec ()
guardS :: Parsec Bool -> Parsec ()
guardS Parsec Bool
cond = Parsec Bool -> Parsec () -> Parsec () -> Parsec ()
forall a. Parsec Bool -> Parsec a -> Parsec a -> Parsec a
ifS Parsec Bool
cond Parsec ()
unit Parsec ()
forall a. Parsec a
forall (f :: * -> *) a. Alternative f => f a
empty

-- this is whileP
{-|
This combinator repeatedly parses @p@ so long as it returns @True@.

This is a lifted @while@-loop. First, parse @p@: if it is successful and
returns @True@, then repeat; else if it returned @False@ stop; or, if it
failed then this combinator fails.

Most useful in conjunction with /Registers/, as this allows for decisions to be made
based on state. In particular, this can be used to define the @forP@ combinator.

@since 0.1.0.0
-}
whileS :: Parsec Bool -- ^ @p@, the parser to repeatedly parse.
       -> Parsec ()   -- ^ a parser that continues to parse @p@ until it returns @False@.
whileS :: Parsec Bool -> Parsec ()
whileS Parsec Bool
c = let go :: Parsec ()
go = Parsec Bool -> Parsec () -> Parsec ()
whenS Parsec Bool
c Parsec ()
go in Parsec ()
go

{-|
This combinator parses exactly @n@ occurrences of @p@, returning these @n@ results in a list.

Parses @p@ repeatedly up to @n@ times. If @p@ fails before @n@ is reached, then this combinator
fails. It is not required for @p@ to fail after the @n@th parse. The results produced by
@p@, @x1@ through @xn@, are returned as @[x1, .., xn]@.

==== __Examples__
>>> let p = exactly 3 item
>>> parse @String p "ab"
Failure ..
>>> parse @String p "abc"
Success ['a', 'b', 'c']
>>> parse @String p "abcd"
Success ['a', 'b', 'c']

@since 0.1.0.0
-}
exactly :: Int        -- ^ @n@, the number of times to repeat @p@.
        -> Parsec a   -- ^ @p@, the parser to repeat.
        -> Parsec [a] -- ^ a parser that parses @p@ exactly @n@ times, returning a list of the results.
exactly :: forall a. Int -> Parsec a -> Parsec [a]
exactly Int
n = Int -> Int -> Parsec a -> Parsec [a]
forall a. Int -> Int -> Parsec a -> Parsec [a]
range Int
n Int
n

{-|
This combinator parses between @min@ and @max@ occurrences of @p@, returning these @n@ results in a list.

Parses @p@ repeatedly a minimum of @min@ times and up to @max@ times both inclusive. If @p@ fails before
@min@ is reached, then this combinator fails. It is not required for @p@ to fail after the @max@^th^ parse.
The results produced by @p@, @xmin@ through @xmax@, are returned as @[xmin, .., xmax]@.

==== __Examples__
>>> let p = range 3 5 item
>>> parse @String p "ab"
Failure ..
>>> parse @String p "abc"
Success ['a', 'b', 'c']
>>> parse @String p "abcd"
Success ['a', 'b', 'c', 'd']
>>> parse @String p "abcde"
Success ['a', 'b', 'c', 'd', 'e']
>>> parse @String p "abcdef"
Success ['a', 'b', 'c', 'd', 'e']

@since 0.1.0.0
-}
range :: Int        -- ^ @min@, the minimum number of times to repeat @p@, inclusive.
      -> Int        -- ^ @max@, the maximum number of times to repeat @p@, inclusive.
      -> Parsec a   -- ^ @p@, the parser to repeat.
      -> Parsec [a] -- ^ the results of the successful parses of @p@.
range :: forall a. Int -> Int -> Parsec a -> Parsec [a]
range Int
mn Int
mx Parsec a
p
  | Int
mn Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
|| Int
mx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
mn = [a] -> Parsec [a]
forall a. a -> Parsec a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
  | Bool
otherwise = Int -> Int -> Parsec [a]
forall {t} {t}. (Eq t, Eq t, Num t, Num t) => t -> t -> Parsec [a]
go Int
mn Int
mx
  where
    go :: t -> t -> Parsec [a]
go t
0 t
0 = [a] -> Parsec [a]
forall a. a -> Parsec a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
    go t
0 t
n = Parsec a
p Parsec a -> Parsec [a] -> Parsec [a]
forall a. Parsec a -> Parsec [a] -> Parsec [a]
<:> t -> t -> Parsec [a]
go t
0 (t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
1) Parsec [a] -> Parsec [a] -> Parsec [a]
forall a. Parsec a -> Parsec a -> Parsec a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [a] -> Parsec [a]
forall a. a -> Parsec a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
    go t
m t
n = Parsec a
p Parsec a -> Parsec [a] -> Parsec [a]
forall a. Parsec a -> Parsec [a] -> Parsec [a]
<:> t -> t -> Parsec [a]
go (t
m t -> t -> t
forall a. Num a => a -> a -> a
- t
1) (t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
1)

{-|
This combinator parses between @min@ and @max@ occurrences of @p@ but ignoring the results.

Parses @p@ repeatedly a minimum of @min@ times and up to @max@ times both inclusive. If @p@ fails before
@min@ is reached, then this combinator fails. It is not required for @p@ to fail after the @max@th parse.
The results are discarded and @()@ is returned instead.

==== __Examples__
>>> let p = range_ 3 5 item
>>> parse @String p "ab"
Failure ..
>>> parse @String p "abc"
Success ()
>>> parse @String p "abcd"
Success ()
>>> parse @String p "abcde"
Success ()
>>> parse @String p "abcdef"
Success ()

@since 0.1.0.0
-}
range_ :: Int       -- ^ @min@, the minimum number of times to repeat @p@, inclusive.
       -> Int       -- ^ @max@, the maximum number of times to repeat @p@, inclusive.
       -> Parsec a  -- ^ @p@, the parser to repeat.
       -> Parsec ()
range_ :: forall a. Int -> Int -> Parsec a -> Parsec ()
range_ Int
mn Int
mx Parsec a
p
  | Int
mn Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
|| Int
mx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
mn = Parsec ()
unit
  | Bool
otherwise = Int -> Int -> Parsec ()
forall {t} {t}. (Eq t, Eq t, Num t, Num t) => t -> t -> Parsec ()
go Int
mn Int
mx
  where
    go :: t -> t -> Parsec ()
go t
0 t
0 = Parsec ()
unit
    go t
0 t
n = Parsec () -> Parsec ()
forall a. Parsec a -> Parsec ()
optional (Parsec a
p Parsec a -> Parsec () -> Parsec ()
forall a b. Parsec a -> Parsec b -> Parsec b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> t -> t -> Parsec ()
go t
0 (t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
1))
    go t
m t
n = Parsec a
p Parsec a -> Parsec () -> Parsec ()
forall a b. Parsec a -> Parsec b -> Parsec b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> t -> t -> Parsec ()
go (t
m t -> t -> t
forall a. Num a => a -> a -> a
- t
1) (t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
1)

-- this is count overloading
{-|
This combinator parses between @min@ and @max@ occurrences of @p@, returning the number of successes.

Parses @p@ repeatedly a minimum of @min@ times and up to @max@ times both inclusive. If @p@ fails before
@min@ is reached, then this combinator fails. It is not required for @p@ to fail after the @max@th parse.
The results are discarded and the number of successful parses of @p@, @n@, is returned instead, such that
@min <= n <= max@.

==== __Examples__
>>> let p = count 3 5 item
>>> parse @String p "ab"
Failure ..
>>> parse @String p "abc"
Success 3
>>> parse @String p "abcd"
Success 4
>>> parse @String p "abcde"
Success 5
>>> parse @String p "abcdef"
Success 5

@since 0.1.0.0
-}
countRange :: Int        -- ^ @min@, the minimum number of times to repeat @p@, inclusive.
           -> Int        -- ^ @max@, the maximum number of times to repeat @p@, inclusive.
           -> Parsec a   -- ^ @p@, the parser to repeat.
           -> Parsec Int -- ^ the number of times @p@ parsed successfully.
countRange :: forall a. Int -> Int -> Parsec a -> Parsec Int
countRange Int
mn Int
mx Parsec a
p
  | Int
mn Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
|| Int
mx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
mn = Int -> Parsec Int
forall a. a -> Parsec a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
0
  | Bool
otherwise = Int -> Int -> Parsec Int
forall {t} {t} {a}.
(Eq t, Eq t, Num t, Num t, Num a) =>
t -> t -> Parsec a
go Int
mn Int
mx
  where
    go :: t -> t -> Parsec a
go t
0 t
0 = a -> Parsec a
forall a. a -> Parsec a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
0
    go t
0 t
n = (a -> a -> a) -> Parsec a -> Parsec a -> Parsec a
forall a b c. (a -> b -> c) -> Parsec a -> Parsec b -> Parsec c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 ((a -> a) -> a -> a -> a
forall a b. a -> b -> a
const (a -> a -> a
forall a. Num a => a -> a -> a
+ a
1)) Parsec a
p (t -> t -> Parsec a
go t
0 (t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
1)) Parsec a -> Parsec a -> Parsec a
forall a. Parsec a -> Parsec a -> Parsec a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> a -> Parsec a
forall a. a -> Parsec a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
0
    go t
m t
n = (a -> a -> a) -> Parsec a -> Parsec a -> Parsec a
forall a b c. (a -> b -> c) -> Parsec a -> Parsec b -> Parsec c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 ((a -> a) -> a -> a -> a
forall a b. a -> b -> a
const (a -> a -> a
forall a. Num a => a -> a -> a
+ a
1)) Parsec a
p (t -> t -> Parsec a
go (t
m t -> t -> t
forall a. Num a => a -> a -> a
- t
1) (t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
1))