{-# LANGUAGE DerivingStrategies         #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs               #-}
{-# LANGUAGE ScopedTypeVariables        #-}
{-# LANGUAGE TypeApplications           #-}
{-# LANGUAGE TypeFamilies               #-}
{-# LANGUAGE TypeOperators              #-}
--------------------------------------------------------------------
-- |
-- Module      : XMonad.Util.Parser
-- Description : A parser combinator library for xmonad
-- Copyright   : (c) 2021  Tony Zorman
-- License     : BSD3
-- Maintainer  : Tony Zorman <soliditsallgood@mailbox.org>
-- Stability   : experimental
-- Portability : non-portable
--
-- A small wrapper around the 'ReadP' parser combinator in @base@,
-- providing a more intuitive behaviour.  While it's theoretically nice
-- that 'ReadP' is actually commutative, this makes a lot of parsing
-- operations rather awkward—more often than not, one only wants the
-- argument that's parsed "first".
--
-- Due to the left-biased nature of the chosen semigroup implementation,
-- using functions like 'many' or 'optional' from "Control.Applicative"
-- now yields more consistent behaviour with other parser combinator
-- libraries.
--
--------------------------------------------------------------------
module XMonad.Util.Parser (
  -- * Usage
  -- $usage

  -- * Running
  Parser,
  runParser,

  -- * Primitive Parsers
  pfail,
  eof,
  num,
  char,
  string,
  skipSpaces,
  get,
  look,
  gather,

  -- * Combining Parsers
  satisfy,
  choice,
  count,
  between,
  option,
  optionally,
  skipMany,
  skipMany1,
  many1,
  sepBy,
  sepBy1,
  endBy,
  endBy1,
  munch,
  munch1,
  chainr,
  chainr1,
  chainl,
  chainl1,
  manyTill,
) where

import XMonad.Prelude

import qualified Text.ParserCombinators.ReadP as ReadP

import Data.Coerce (coerce)
import Data.String (IsString (fromString))
import Text.ParserCombinators.ReadP (ReadP, (<++))

{- $usage

NOTE: This module is mostly intended for developing of other modules.
If you are a users, you probably won't find much use here—you have been
warned.

The high-level API tries to stay as close to 'ReadP' as possible.  If
you are familiar with that then no functions here should surprise you.

One notable usability difference when forcing left-biasedness is /when/
one wants to disambiguate a parse.  For normal 'ReadP' usage this
happens after the actual parsing stage by going through the list of
successful parses.  For 'Parser' it does when constructing the relevant
combinators, leading to only one successful parse.  As an example,
consider the 'ReadP'-based parser

> pLangle = ReadP.string "<"
> pLongerSequence = ReadP.char '<' *> ReadP.string "f" <* ReadP.char '>'
> pCombination = pLangle ReadP.+++ pLongerSequence

Parsing the string @"\<f\>"@ will return

>>> ReadP.readP_to_S pCombination "<f>"
[("<","f>"),("f","")]

One would now need to, for example, filter for the second (leftover)
string being empty and take the head of the resulting list (which may
still have more than one element).

With 'Parser', the same situation would look like the following

> pLangle' = string "<"
> pLongerSequence' = char '<' *> string "f" <* char '>'
> pCombination' = pLongerSequence' <> pLangle'

Notice how @pLangle'@ and @pLongerSequence'@ have traded places—since we
are not forcing @pLangle'@ to consume the entire string and @(<>)@ is
left-biased, @pLongerSequence'@ parses a superset of @pLangle'@!
Running @runParser pCombination'@ now yields the expected result:

>>> runParser pCombination' "<f>"
Just "f"

One might also define @pLangle'@ as @string "<" <* eof@, which would
enable a definition of @pCombination' = pLangle' <> pLongerSequence'@.

For example uses, see "XMonad.Util.EZConfig" or "XMonad.Prompt.OrgMode".
-}

-- Parser :: Type -> Type
newtype Parser a = Parser (ReadP a)
  deriving newtype (forall a b. a -> Parser b -> Parser a
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Parser b -> Parser a
$c<$ :: forall a b. a -> Parser b -> Parser a
fmap :: forall a b. (a -> b) -> Parser a -> Parser b
$cfmap :: forall a b. (a -> b) -> Parser a -> Parser b
Functor, Functor Parser
forall a. a -> Parser a
forall a b. Parser a -> Parser b -> Parser a
forall a b. Parser a -> Parser b -> Parser b
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall a b c. (a -> b -> c) -> Parser a -> Parser b -> Parser c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b. Parser a -> Parser b -> Parser a
$c<* :: forall a b. Parser a -> Parser b -> Parser a
*> :: forall a b. Parser a -> Parser b -> Parser b
$c*> :: forall a b. Parser a -> Parser b -> Parser b
liftA2 :: forall a b c. (a -> b -> c) -> Parser a -> Parser b -> Parser c
$cliftA2 :: forall a b c. (a -> b -> c) -> Parser a -> Parser b -> Parser c
<*> :: forall a b. Parser (a -> b) -> Parser a -> Parser b
$c<*> :: forall a b. Parser (a -> b) -> Parser a -> Parser b
pure :: forall a. a -> Parser a
$cpure :: forall a. a -> Parser a
Applicative, Applicative Parser
forall a. a -> Parser a
forall a b. Parser a -> Parser b -> Parser b
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> Parser a
$creturn :: forall a. a -> Parser a
>> :: forall a b. Parser a -> Parser b -> Parser b
$c>> :: forall a b. Parser a -> Parser b -> Parser b
>>= :: forall a b. Parser a -> (a -> Parser b) -> Parser b
$c>>= :: forall a b. Parser a -> (a -> Parser b) -> Parser b
Monad)

instance Semigroup (Parser a) where
  -- | Local, exclusive, left-biased choice: If left parser locally
  -- produces any result at all, then right parser is not used.
  (<>) :: Parser a -> Parser a -> Parser a
  <> :: Parser a -> Parser a -> Parser a
(<>) = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ReadP a -> ReadP a -> ReadP a
(<++) @a)
  {-# INLINE (<>) #-}

instance Monoid (Parser a) where
  -- | A parser that always fails.
  mempty :: Parser a
  mempty :: Parser a
mempty = forall a. ReadP a -> Parser a
Parser forall (f :: * -> *) a. Alternative f => f a
empty
  {-# INLINE mempty #-}

instance Alternative Parser where
  empty :: Parser a
  empty :: forall a. Parser a
empty = forall a. Monoid a => a
mempty
  {-# INLINE empty #-}

  (<|>) :: Parser a -> Parser a -> Parser a
  <|> :: forall a. Parser a -> Parser a -> Parser a
(<|>) = forall a. Semigroup a => a -> a -> a
(<>)
  {-# INLINE (<|>) #-}

-- | When @-XOverloadedStrings@ is on, treat a string @s@ as the parser
-- @'string' s@, when appropriate.  This allows one to write things like
-- @"a" *> otherParser@ instead of @'string' "a" *> otherParser@.
instance a ~ String => IsString (Parser a) where
  fromString :: String -> Parser a
  fromString :: String -> Parser a
fromString = String -> Parser String
string
  {-# INLINE fromString #-}

-- | Run a parser on a given string.
runParser :: Parser a -> String -> Maybe a
runParser :: forall a. Parser a -> String -> Maybe a
runParser (Parser ReadP a
p) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Maybe a
listToMaybe forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ReadP a -> ReadS a
ReadP.readP_to_S ReadP a
p
{-# INLINE runParser #-}

-- | Always fails
pfail :: Parser a
pfail :: forall a. Parser a
pfail = forall (f :: * -> *) a. Alternative f => f a
empty
{-# INLINE pfail #-}

-- | Consume and return the next character.  Fails if there is no input
-- left.
get :: Parser Char
get :: Parser Char
get = coerce :: forall a b. Coercible a b => a -> b
coerce ReadP Char
ReadP.get
{-# INLINE get #-}

-- | Look-ahead: return the part of the input that is left, without
-- consuming it.
look :: Parser String
look :: Parser String
look = coerce :: forall a b. Coercible a b => a -> b
coerce ReadP String
ReadP.look
{-# INLINE look #-}

-- | Transform a parser into one that does the same, but in addition
-- returns the exact characters read.
--
-- >>> runParser (         string "* " $> True) "* hi"
-- Just True
-- >>> runParser (gather $ string "* " $> True) "* hi"
-- Just ("* ",True)
gather :: forall a. Parser a -> Parser (String, a)
gather :: forall a. Parser a -> Parser (String, a)
gather = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ReadP a -> ReadP (String, a)
ReadP.gather @a)
{-# INLINE gather #-}

-- | Succeeds if and only if we are at the end of input.
eof :: Parser ()
eof :: Parser ()
eof = coerce :: forall a b. Coercible a b => a -> b
coerce ReadP ()
ReadP.eof
{-# INLINE eof #-}

-- | Parse an integral number.
num :: (Read a, Integral a) => Parser a
num :: forall a. (Read a, Integral a) => Parser a
num = forall a. Read a => String -> a
read forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Bool) -> Parser String
munch1 Char -> Bool
isDigit
{-# INLINE num #-}

-- | Parse and return the specified character.
char :: Char -> Parser Char
char :: Char -> Parser Char
char = coerce :: forall a b. Coercible a b => a -> b
coerce Char -> ReadP Char
ReadP.char
{-# INLINE char #-}

-- | Parse and return the specified string.
string :: String -> Parser String
string :: String -> Parser String
string = coerce :: forall a b. Coercible a b => a -> b
coerce String -> ReadP String
ReadP.string
{-# INLINE string #-}

-- | Skip all whitespace.
skipSpaces :: Parser ()
skipSpaces :: Parser ()
skipSpaces = coerce :: forall a b. Coercible a b => a -> b
coerce ReadP ()
ReadP.skipSpaces
{-# INLINE skipSpaces #-}

-- | Consume and return the next character if it satisfies the specified
-- predicate.
satisfy :: (Char -> Bool) -> Parser Char
satisfy :: (Char -> Bool) -> Parser Char
satisfy = coerce :: forall a b. Coercible a b => a -> b
coerce (Char -> Bool) -> ReadP Char
ReadP.satisfy
{-# INLINE satisfy #-}

-- | Combine all parsers in the given list in a left-biased way.
choice :: [Parser a] -> Parser a
choice :: forall a. [Parser a] -> Parser a
choice = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' forall a. Semigroup a => a -> a -> a
(<>) forall a. Monoid a => a
mempty
{-# INLINE choice #-}

-- | @count n p@ parses @n@ occurrences of @p@ in sequence and returns a
-- list of results.
count :: Int -> Parser a -> Parser [a]
count :: forall a. Int -> Parser a -> Parser [a]
count = forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM
{-# INLINE count #-}

-- | @between open close p@ parses @open@, followed by @p@ and finally
-- @close@.  Only the value of @p@ is returned.
between :: Parser open -> Parser close -> Parser a -> Parser a
between :: forall open close a.
Parser open -> Parser close -> Parser a -> Parser a
between Parser open
open Parser close
close Parser a
p = Parser open
open forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser a
p forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser close
close
{-# INLINE between #-}

-- | @option def p@ will try to parse @p@ and, if it fails, simply
-- return @def@ without consuming any input.
option :: a -> Parser a -> Parser a
option :: forall a. a -> Parser a -> Parser a
option a
def Parser a
p = Parser a
p forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (f :: * -> *) a. Applicative f => a -> f a
pure a
def
{-# INLINE option #-}

-- | @optionally p@ optionally parses @p@ and always returns @()@.
optionally :: Parser a -> Parser ()
optionally :: forall a. Parser a -> Parser ()
optionally Parser a
p = forall (f :: * -> *) a. Functor f => f a -> f ()
void Parser a
p forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
{-# INLINE optionally #-}

-- | Like 'many', but discard the result.
skipMany :: Parser a -> Parser ()
skipMany :: forall a. Parser a -> Parser ()
skipMany = forall (f :: * -> *) a. Functor f => f a -> f ()
void forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Alternative f => f a -> f [a]
many
{-# INLINE skipMany #-}

-- | Like 'many1', but discard the result.
skipMany1 :: Parser a -> Parser ()
skipMany1 :: forall a. Parser a -> Parser ()
skipMany1 Parser a
p = Parser a
p forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall a. Parser a -> Parser ()
skipMany Parser a
p
{-# INLINE skipMany1 #-}

-- | Parse the first zero or more characters satisfying the predicate.
-- Always succeeds; returns an empty string if the predicate returns
-- @False@ on the first character of input.
munch :: (Char -> Bool) -> Parser String
munch :: (Char -> Bool) -> Parser String
munch = coerce :: forall a b. Coercible a b => a -> b
coerce (Char -> Bool) -> ReadP String
ReadP.munch
{-# INLINE munch #-}

-- | Parse the first one or more characters satisfying the predicate.
-- Fails if none, else succeeds exactly once having consumed all the
-- characters.
munch1 :: (Char -> Bool) -> Parser String
munch1 :: (Char -> Bool) -> Parser String
munch1 = coerce :: forall a b. Coercible a b => a -> b
coerce (Char -> Bool) -> ReadP String
ReadP.munch1
{-# INLINE munch1 #-}

-- | @endBy p sep@ parses zero or more occurrences of @p@, separated and
-- ended by @sep@.
endBy :: Parser a -> Parser sep -> Parser [a]
endBy :: forall a sep. Parser a -> Parser sep -> Parser [a]
endBy Parser a
p Parser sep
sep = forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (Parser a
p forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser sep
sep)
{-# INLINE endBy #-}

-- | @endBy p sep@ parses one or more occurrences of @p@, separated and
-- ended by @sep@.
endBy1 :: Parser a -> Parser sep -> Parser [a]
endBy1 :: forall a sep. Parser a -> Parser sep -> Parser [a]
endBy1 Parser a
p Parser sep
sep = forall a. Parser a -> Parser [a]
many1 (Parser a
p forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser sep
sep)
{-# INLINE endBy1 #-}

-- | Parse one or more occurrences of the given parser.
many1 :: Parser a -> Parser [a]
many1 :: forall a. Parser a -> Parser [a]
many1 = forall (f :: * -> *) a. Alternative f => f a -> f [a]
some
{-# INLINE many1 #-}

-- | @sepBy p sep@ parses zero or more occurrences of @p@, separated by
-- @sep@.  Returns a list of values returned by @p@.
sepBy :: Parser a -> Parser sep -> Parser [a]
sepBy :: forall a sep. Parser a -> Parser sep -> Parser [a]
sepBy Parser a
p Parser sep
sep = forall a sep. Parser a -> Parser sep -> Parser [a]
sepBy1 Parser a
p Parser sep
sep forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. Applicative f => a -> f a
pure []
{-# INLINE sepBy #-}

-- | @sepBy1 p sep@ parses one or more occurrences of @p@, separated by
-- @sep@.  Returns a list of values returned by @p@.
sepBy1 :: Parser a -> Parser sep -> Parser [a]
sepBy1 :: forall a sep. Parser a -> Parser sep -> Parser [a]
sepBy1 Parser a
p Parser sep
sep = forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (:) Parser a
p (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (Parser sep
sep forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser a
p))
{-# INLINE sepBy1 #-}

-- | @chainr p op x@ parses zero or more occurrences of @p@, separated
-- by @op@.  Returns a value produced by a /right/ associative
-- application of all functions returned by @op@.  If there are no
-- occurrences of @p@, @x@ is returned.
chainr :: Parser a -> Parser (a -> a -> a) -> a -> Parser a
chainr :: forall a. Parser a -> Parser (a -> a -> a) -> a -> Parser a
chainr Parser a
p Parser (a -> a -> a)
op a
x = forall a. a -> Parser a -> Parser a
option a
x (forall a. Parser a -> Parser (a -> a -> a) -> Parser a
chainr1 Parser a
p Parser (a -> a -> a)
op)
{-# INLINE chainr #-}

-- | Like 'chainr', but parses one or more occurrences of @p@.
chainr1 :: forall a. Parser a -> Parser (a -> a -> a) -> Parser a
chainr1 :: forall a. Parser a -> Parser (a -> a -> a) -> Parser a
chainr1 Parser a
p Parser (a -> a -> a)
op = Parser a
scan
 where
  scan :: Parser a
  scan :: Parser a
scan = Parser a
p forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> Parser a
rest

  rest :: a -> Parser a
  rest :: a -> Parser a
rest a
x = forall a. a -> Parser a -> Parser a
option a
x forall a b. (a -> b) -> a -> b
$ do a -> a -> a
f <- Parser (a -> a -> a)
op
                         a -> a -> a
f a
x forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser a
scan
{-# INLINE chainr1 #-}

-- | @chainl p op x@ parses zero or more occurrences of @p@, separated
-- by @op@.  Returns a value produced by a /left/ associative
-- application of all functions returned by @op@.  If there are no
-- occurrences of @p@, @x@ is returned.
chainl :: Parser a -> Parser (a -> a -> a) -> a -> Parser a
chainl :: forall a. Parser a -> Parser (a -> a -> a) -> a -> Parser a
chainl Parser a
p Parser (a -> a -> a)
op a
x = forall a. a -> Parser a -> Parser a
option a
x (forall a. Parser a -> Parser (a -> a -> a) -> Parser a
chainl1 Parser a
p Parser (a -> a -> a)
op)
{-# INLINE chainl #-}

-- | Like 'chainl', but parses one or more occurrences of @p@.
chainl1 :: forall a. Parser a -> Parser (a -> a -> a) -> Parser a
chainl1 :: forall a. Parser a -> Parser (a -> a -> a) -> Parser a
chainl1 Parser a
p Parser (a -> a -> a)
op = Parser a
scan
 where
  scan :: Parser a
  scan :: Parser a
scan = Parser a
p forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> Parser a
rest

  rest :: a -> Parser a
  rest :: a -> Parser a
rest a
x = forall a. a -> Parser a -> Parser a
option a
x forall a b. (a -> b) -> a -> b
$ do a -> a -> a
f <- Parser (a -> a -> a)
op
                         a
y <- Parser a
p
                         a -> Parser a
rest (a -> a -> a
f a
x a
y)
{-# INLINE chainl1 #-}

-- | @manyTill p end@ parses zero or more occurrences of @p@, until
-- @end@ succeeds.  Returns a list of values returned by @p@.
manyTill :: forall a end. Parser a -> Parser end -> Parser [a]
manyTill :: forall a sep. Parser a -> Parser sep -> Parser [a]
manyTill Parser a
p Parser end
end = Parser [a]
scan
 where
  scan :: Parser [a]
  scan :: Parser [a]
scan = Parser end
end forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> [] forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (:) Parser a
p Parser [a]
scan
{-# INLINE manyTill #-}