{-# LANGUAGE CPP #-}
{-
	Copyright (C) 2018 Dr. Alistair Ward

	This file is part of BishBosh.

	BishBosh is free software: you can redistribute it and/or modify
	it under the terms of the GNU General Public License as published by
	the Free Software Foundation, either version 3 of the License, or
	(at your option) any later version.

	BishBosh is distributed in the hope that it will be useful,
	but WITHOUT ANY WARRANTY; without even the implied warranty of
	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
	GNU General Public License for more details.

	You should have received a copy of the GNU General Public License
	along with BishBosh.  If not, see <http://www.gnu.org/licenses/>.
-}
{- |
 [@AUTHOR@]	Dr. Alistair Ward

 [@DESCRIPTION@]	Exports functions to enhance the package /polyparse/.
-}

module BishBosh.Text.Poly(
-- * Types
-- ** Type-synonyms
	TextParser,
-- * Functions
	char,
	string,
	spaces,
	unsignedDecimal,
) where

import qualified	BishBosh.Data.Integral			as Data.Integral
import qualified	Data.Char

#if USE_POLYPARSE == 'L'
import qualified	Text.ParserCombinators.Poly.Lazy	as Poly
#elif USE_POLYPARSE == 'P'
import qualified	Text.ParserCombinators.Poly.Plain	as Poly
#else
#	error "USE_POLYPARSE invalid"
#endif

-- | Self-documentation.
type TextParser	= Poly.Parser Char

-- | Matches the specified char.
char :: Char -> TextParser ()
char :: Char -> TextParser ()
char Char
c	= do
	Char
_	<- (Char -> Bool) -> String -> Parser Char Char
forall t. Show t => (t -> Bool) -> String -> Parser t t
Poly.satisfyMsg (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c) [Char
c]

	() -> TextParser ()
forall (m :: * -> *) a. Monad m => a -> m a
return {-to Parser-monad-} ()

{- |
	* Matches the specified string.

	* N.B. this differs from /Text.Parse.word/ in that there's no requirement for the string to be a single Haskell lexical token.
-}
string :: String -> TextParser ()
string :: String -> TextParser ()
string	= (Char -> TextParser ()) -> String -> TextParser ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Char -> TextParser ()
char

{- |
	* Matches any number (including zero) of consecutive spaces.

	* CAVEAT: performance-hotspot.
-}
spaces :: TextParser ()
-- spaces	= Control.Monad.void . Poly.many $ Poly.satisfy Data.Char.isSpace	-- CAVEAT: poor performance ?!
spaces :: TextParser ()
spaces	= do
	String
_	<- Parser Char Char -> Parser Char String
forall (f :: * -> *) a. Alternative f => f a -> f [a]
Poly.many (Parser Char Char -> Parser Char String)
-> Parser Char Char -> Parser Char String
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Parser Char Char
forall t. (t -> Bool) -> Parser t t
Poly.satisfy Char -> Bool
Data.Char.isSpace

	() -> TextParser ()
forall (m :: * -> *) a. Monad m => a -> m a
return {-to Parser-monad-} ()

-- | Parses an unsigned base-10 integer.
unsignedDecimal :: Num i => TextParser i
unsignedDecimal :: TextParser i
unsignedDecimal	= TextParser ()
spaces TextParser () -> TextParser i -> TextParser i
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> i
forall i. Num i => String -> i
Data.Integral.stringToUnsignedDecimal (String -> i) -> Parser Char String -> TextParser i
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Parser Char Char -> Parser Char String
forall (p :: * -> *) a. PolyParse p => p a -> p [a]
Poly.many1 ((Char -> Bool) -> String -> Parser Char Char
forall t. Show t => (t -> Bool) -> String -> Parser t t
Poly.satisfyMsg Char -> Bool
Data.Char.isDigit String
"<digit>")