{-# LANGUAGE OverloadedStrings #-}
module Data.JSONPath.Parser
(jsonPathElement, jsonPath)
where
import Control.Applicative ((<|>))
import Data.Attoparsec.Text as A
import Data.Functor
import Data.JSONPath.Types
jsonPath :: Parser [JSONPathElement]
jsonPath :: Parser [JSONPathElement]
jsonPath = do
()
_ <- (Char -> Bool) -> Parser ()
skip (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'$') Parser () -> Parser () -> Parser ()
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> () -> Parser ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Parser Text JSONPathElement -> Parser [JSONPathElement]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many1 Parser Text JSONPathElement
jsonPathElement
jsonPathElement :: Parser JSONPathElement
jsonPathElement :: Parser Text JSONPathElement
jsonPathElement = do
(Parser Text JSONPathElement
keyChildDot Parser Text JSONPathElement
-> String -> Parser Text JSONPathElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"keyChildDot")
Parser Text JSONPathElement
-> Parser Text JSONPathElement -> Parser Text JSONPathElement
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser Text JSONPathElement
keyChildBracket Parser Text JSONPathElement
-> String -> Parser Text JSONPathElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"keyChildBracket")
Parser Text JSONPathElement
-> Parser Text JSONPathElement -> Parser Text JSONPathElement
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser Text JSONPathElement
keyChildren Parser Text JSONPathElement
-> String -> Parser Text JSONPathElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"keyChildren")
Parser Text JSONPathElement
-> Parser Text JSONPathElement -> Parser Text JSONPathElement
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser Text JSONPathElement
anyChild Parser Text JSONPathElement
-> String -> Parser Text JSONPathElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"anyChild")
Parser Text JSONPathElement
-> Parser Text JSONPathElement -> Parser Text JSONPathElement
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser Text JSONPathElement
slice Parser Text JSONPathElement
-> String -> Parser Text JSONPathElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"slice")
Parser Text JSONPathElement
-> Parser Text JSONPathElement -> Parser Text JSONPathElement
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser Text JSONPathElement
sliceUnion Parser Text JSONPathElement
-> String -> Parser Text JSONPathElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"sliceUnion")
Parser Text JSONPathElement
-> Parser Text JSONPathElement -> Parser Text JSONPathElement
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser Text JSONPathElement
filterParser Parser Text JSONPathElement
-> String -> Parser Text JSONPathElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"filterParser")
Parser Text JSONPathElement
-> Parser Text JSONPathElement -> Parser Text JSONPathElement
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser Text JSONPathElement
search Parser Text JSONPathElement
-> String -> Parser Text JSONPathElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"search")
Parser Text JSONPathElement
-> Parser Text JSONPathElement -> Parser Text JSONPathElement
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser Text JSONPathElement
searchBeginningWithSlice Parser Text JSONPathElement
-> String -> Parser Text JSONPathElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"searchBeginningWithSlice")
slice :: Parser JSONPathElement
slice :: Parser Text JSONPathElement
slice = SliceElement -> JSONPathElement
Slice (SliceElement -> JSONPathElement)
-> Parser Text SliceElement -> Parser Text JSONPathElement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text SliceElement -> Parser Text SliceElement
forall a. Parser a -> Parser a
ignoreSurroundingSqBr Parser Text SliceElement
sliceWithoutBrackets
sliceWithoutBrackets :: Parser Text SliceElement
sliceWithoutBrackets = (Parser Text SliceElement
sliceWithStep Parser Text SliceElement -> String -> Parser Text SliceElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"sliceWithStep")
Parser Text SliceElement
-> Parser Text SliceElement -> Parser Text SliceElement
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser Text SliceElement
simpleSlice Parser Text SliceElement -> String -> Parser Text SliceElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"simpleSlice")
Parser Text SliceElement
-> Parser Text SliceElement -> Parser Text SliceElement
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser Text SliceElement
sliceFromWithStep Parser Text SliceElement -> String -> Parser Text SliceElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"sliceFromWithStep")
Parser Text SliceElement
-> Parser Text SliceElement -> Parser Text SliceElement
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser Text SliceElement
sliceFrom Parser Text SliceElement -> String -> Parser Text SliceElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"sliceFrom")
Parser Text SliceElement
-> Parser Text SliceElement -> Parser Text SliceElement
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser Text SliceElement
singleIndex Parser Text SliceElement -> String -> Parser Text SliceElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"singleIndex")
Parser Text SliceElement
-> Parser Text SliceElement -> Parser Text SliceElement
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser Text SliceElement
sliceToWithStep Parser Text SliceElement -> String -> Parser Text SliceElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"sliceToWithStep")
Parser Text SliceElement
-> Parser Text SliceElement -> Parser Text SliceElement
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser Text SliceElement
sliceTo Parser Text SliceElement -> String -> Parser Text SliceElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"sliceTo")
Parser Text SliceElement
-> Parser Text SliceElement -> Parser Text SliceElement
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser Text SliceElement
sliceWithOnlyStep Parser Text SliceElement -> String -> Parser Text SliceElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"sliceWithOnlyStep")
singleIndex :: Parser SliceElement
singleIndex :: Parser Text SliceElement
singleIndex = Int -> SliceElement
SingleIndex (Int -> SliceElement)
-> Parser Text Int -> Parser Text SliceElement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text Int -> Parser Text Int
forall a. Num a => Parser a -> Parser a
signed Parser Text Int
forall a. Integral a => Parser a
decimal
keyChildBracket :: Parser JSONPathElement
keyChildBracket :: Parser Text JSONPathElement
keyChildBracket = Text -> JSONPathElement
KeyChild
(Text -> JSONPathElement)
-> Parser Text Text -> Parser Text JSONPathElement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text -> Parser Text Text
string Text
"['" Parser Text Text -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Char -> Bool) -> Parser Text Text
takeWhile1 (String -> Char -> Bool
inClass String
"a-zA-Z0-9_-") Parser Text Text -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Text -> Parser Text Text
string Text
"']")
keyChildDot :: Parser JSONPathElement
keyChildDot :: Parser Text JSONPathElement
keyChildDot = Text -> JSONPathElement
KeyChild
(Text -> JSONPathElement)
-> Parser Text Text -> Parser Text JSONPathElement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Parser Char
char Char
'.' Parser Char -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Char -> Bool) -> Parser Text Text
takeWhile1 (String -> Char -> Bool
inClass String
"a-zA-Z0-9_-"))
keyChildren :: Parser JSONPathElement
keyChildren :: Parser Text JSONPathElement
keyChildren = do
Text
_ <- Text -> Parser Text Text
string Text
"['"
Text
firstKey <- (Char -> Bool) -> Parser Text Text
takeWhile1 (String -> Char -> Bool
inClass String
"a-zA-Z0-9_-")
[Text]
restKeys <- Parser Text Text -> Parser Text [Text]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many' (Parser Text Text -> Parser Text [Text])
-> Parser Text Text -> Parser Text [Text]
forall a b. (a -> b) -> a -> b
$ Char -> Parser Char
char Char
'.' Parser Char -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Char -> Bool) -> Parser Text Text
takeWhile1 (String -> Char -> Bool
inClass String
"a-zA-Z0-9_-")
Text
_ <- Text -> Parser Text Text
string Text
"']"
JSONPathElement -> Parser Text JSONPathElement
forall (m :: * -> *) a. Monad m => a -> m a
return (JSONPathElement -> Parser Text JSONPathElement)
-> JSONPathElement -> Parser Text JSONPathElement
forall a b. (a -> b) -> a -> b
$ [Text] -> JSONPathElement
KeyChildren (Text
firstKeyText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
restKeys)
anyChild :: Parser JSONPathElement
anyChild :: Parser Text JSONPathElement
anyChild = JSONPathElement
AnyChild JSONPathElement -> Parser Text Text -> Parser Text JSONPathElement
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Text -> Parser Text Text
string Text
".*" Parser Text Text -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> Parser Text Text
string Text
"[*]")
simpleSlice :: Parser SliceElement
simpleSlice :: Parser Text SliceElement
simpleSlice = do
Int
start <- Parser Text Int -> Parser Text Int
forall a. Num a => Parser a -> Parser a
signed Parser Text Int
forall a. Integral a => Parser a
decimal
Char
_ <- Char -> Parser Char
char Char
':'
Int
end <- Parser Text Int -> Parser Text Int
forall a. Num a => Parser a -> Parser a
signed Parser Text Int
forall a. Integral a => Parser a
decimal
SliceElement -> Parser Text SliceElement
forall (m :: * -> *) a. Monad m => a -> m a
return (SliceElement -> Parser Text SliceElement)
-> SliceElement -> Parser Text SliceElement
forall a b. (a -> b) -> a -> b
$ Int -> Int -> SliceElement
SimpleSlice Int
start Int
end
sliceWithStep :: Parser SliceElement
sliceWithStep :: Parser Text SliceElement
sliceWithStep = do
Int
start <- Parser Text Int -> Parser Text Int
forall a. Num a => Parser a -> Parser a
signed Parser Text Int
forall a. Integral a => Parser a
decimal
Char
_ <- Char -> Parser Char
char Char
':'
Int
end <- Parser Text Int -> Parser Text Int
forall a. Num a => Parser a -> Parser a
signed Parser Text Int
forall a. Integral a => Parser a
decimal
Char
_ <- Char -> Parser Char
char Char
':'
Int
step <- Parser Text Int -> Parser Text Int
forall a. Num a => Parser a -> Parser a
signed Parser Text Int
forall a. Integral a => Parser a
decimal
SliceElement -> Parser Text SliceElement
forall (m :: * -> *) a. Monad m => a -> m a
return (SliceElement -> Parser Text SliceElement)
-> SliceElement -> Parser Text SliceElement
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> SliceElement
SliceWithStep Int
start Int
end Int
step
sliceFrom :: Parser SliceElement
sliceFrom :: Parser Text SliceElement
sliceFrom = do
Int
start <- Parser Text Int -> Parser Text Int
forall a. Num a => Parser a -> Parser a
signed Parser Text Int
forall a. Integral a => Parser a
decimal
Char
_ <- Char -> Parser Char
char Char
':'
SliceElement -> Parser Text SliceElement
forall (m :: * -> *) a. Monad m => a -> m a
return (SliceElement -> Parser Text SliceElement)
-> SliceElement -> Parser Text SliceElement
forall a b. (a -> b) -> a -> b
$ Int -> SliceElement
SliceFrom Int
start
sliceFromWithStep :: Parser SliceElement
sliceFromWithStep :: Parser Text SliceElement
sliceFromWithStep = do
Int
start <- Parser Text Int -> Parser Text Int
forall a. Num a => Parser a -> Parser a
signed Parser Text Int
forall a. Integral a => Parser a
decimal
Text
_ <- Text -> Parser Text Text
string Text
"::"
Int
step <- Parser Text Int -> Parser Text Int
forall a. Num a => Parser a -> Parser a
signed Parser Text Int
forall a. Integral a => Parser a
decimal
SliceElement -> Parser Text SliceElement
forall (m :: * -> *) a. Monad m => a -> m a
return (SliceElement -> Parser Text SliceElement)
-> SliceElement -> Parser Text SliceElement
forall a b. (a -> b) -> a -> b
$ Int -> Int -> SliceElement
SliceFromWithStep Int
start Int
step
sliceTo :: Parser SliceElement
sliceTo :: Parser Text SliceElement
sliceTo = do
Char
_ <- Char -> Parser Char
char Char
':'
Int
end <- Parser Text Int -> Parser Text Int
forall a. Num a => Parser a -> Parser a
signed Parser Text Int
forall a. Integral a => Parser a
decimal
SliceElement -> Parser Text SliceElement
forall (m :: * -> *) a. Monad m => a -> m a
return (SliceElement -> Parser Text SliceElement)
-> SliceElement -> Parser Text SliceElement
forall a b. (a -> b) -> a -> b
$ Int -> SliceElement
SliceTo Int
end
sliceToWithStep :: Parser SliceElement
sliceToWithStep :: Parser Text SliceElement
sliceToWithStep = do
Char
_ <- Char -> Parser Char
char Char
':'
Int
end <- Parser Text Int -> Parser Text Int
forall a. Num a => Parser a -> Parser a
signed Parser Text Int
forall a. Integral a => Parser a
decimal
Char
_ <- Char -> Parser Char
char Char
':'
Int
step <- Parser Text Int -> Parser Text Int
forall a. Num a => Parser a -> Parser a
signed Parser Text Int
forall a. Integral a => Parser a
decimal
SliceElement -> Parser Text SliceElement
forall (m :: * -> *) a. Monad m => a -> m a
return (SliceElement -> Parser Text SliceElement)
-> SliceElement -> Parser Text SliceElement
forall a b. (a -> b) -> a -> b
$ Int -> Int -> SliceElement
SliceToWithStep Int
end Int
step
sliceWithOnlyStep :: Parser SliceElement
sliceWithOnlyStep :: Parser Text SliceElement
sliceWithOnlyStep = do
Text
_ <- Text -> Parser Text Text
string Text
"::"
Int
step <- Parser Text Int -> Parser Text Int
forall a. Num a => Parser a -> Parser a
signed Parser Text Int
forall a. Integral a => Parser a
decimal
SliceElement -> Parser Text SliceElement
forall (m :: * -> *) a. Monad m => a -> m a
return (SliceElement -> Parser Text SliceElement)
-> SliceElement -> Parser Text SliceElement
forall a b. (a -> b) -> a -> b
$ Int -> SliceElement
SliceWithOnlyStep Int
step
sliceUnion :: Parser JSONPathElement
sliceUnion :: Parser Text JSONPathElement
sliceUnion = Parser Text JSONPathElement -> Parser Text JSONPathElement
forall a. Parser a -> Parser a
ignoreSurroundingSqBr (Parser Text JSONPathElement -> Parser Text JSONPathElement)
-> Parser Text JSONPathElement -> Parser Text JSONPathElement
forall a b. (a -> b) -> a -> b
$ do
SliceElement
firstElement <- Parser Text SliceElement
sliceWithoutBrackets Parser Text SliceElement -> String -> Parser Text SliceElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"firstElement"
Char
_ <- Char -> Parser Char
char Char
','
SliceElement
secondElement <- Parser Text SliceElement
sliceWithoutBrackets Parser Text SliceElement -> String -> Parser Text SliceElement
forall i a. Parser i a -> String -> Parser i a
<?> String
"secondElement"
JSONPathElement -> Parser Text JSONPathElement
forall (m :: * -> *) a. Monad m => a -> m a
return (JSONPathElement -> Parser Text JSONPathElement)
-> JSONPathElement -> Parser Text JSONPathElement
forall a b. (a -> b) -> a -> b
$ SliceElement -> SliceElement -> JSONPathElement
SliceUnion SliceElement
firstElement SliceElement
secondElement
filterParser :: Parser JSONPathElement
filterParser :: Parser Text JSONPathElement
filterParser = do
Text
_ <- Text -> Parser Text Text
string Text
"[?(" Parser Text Text -> String -> Parser Text Text
forall i a. Parser i a -> String -> Parser i a
<?> String
"[?("
BeginningPoint
b <- Parser BeginningPoint
beginningPoint Parser BeginningPoint -> String -> Parser BeginningPoint
forall i a. Parser i a -> String -> Parser i a
<?> String
"beginning point"
[JSONPathElement]
js <- Parser [JSONPathElement]
jsonPath Parser [JSONPathElement] -> String -> Parser [JSONPathElement]
forall i a. Parser i a -> String -> Parser i a
<?> String
"jsonPathElements"
Condition
c <- Parser Condition
condition Parser Condition -> String -> Parser Condition
forall i a. Parser i a -> String -> Parser i a
<?> String
"condition"
Literal
l <- Parser Literal
literal Parser Literal -> String -> Parser Literal
forall i a. Parser i a -> String -> Parser i a
<?> String
"literal"
Text
_ <- Text -> Parser Text Text
string Text
")]" Parser Text Text -> String -> Parser Text Text
forall i a. Parser i a -> String -> Parser i a
<?> String
")]"
JSONPathElement -> Parser Text JSONPathElement
forall (m :: * -> *) a. Monad m => a -> m a
return (JSONPathElement -> Parser Text JSONPathElement)
-> JSONPathElement -> Parser Text JSONPathElement
forall a b. (a -> b) -> a -> b
$ BeginningPoint
-> [JSONPathElement] -> Condition -> Literal -> JSONPathElement
Filter BeginningPoint
b [JSONPathElement]
js Condition
c Literal
l
search :: Parser JSONPathElement
search :: Parser Text JSONPathElement
search = do
Char
_ <- Char -> Parser Char
char Char
'.'
Bool
isDot <- (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.') (Char -> Bool) -> Parser Char -> Parser Text Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Char
peekChar'
if Bool
isDot
then [JSONPathElement] -> JSONPathElement
Search ([JSONPathElement] -> JSONPathElement)
-> Parser [JSONPathElement] -> Parser Text JSONPathElement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text JSONPathElement -> Parser [JSONPathElement]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many1 Parser Text JSONPathElement
jsonPathElement
else String -> Parser Text JSONPathElement
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"not a search element"
searchBeginningWithSlice :: Parser JSONPathElement
searchBeginningWithSlice :: Parser Text JSONPathElement
searchBeginningWithSlice = do
Text
_ <- Text -> Parser Text Text
string Text
".."
Bool
isBracket <- (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'[') (Char -> Bool) -> Parser Char -> Parser Text Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Char
peekChar'
if Bool
isBracket
then [JSONPathElement] -> JSONPathElement
Search ([JSONPathElement] -> JSONPathElement)
-> Parser [JSONPathElement] -> Parser Text JSONPathElement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text JSONPathElement -> Parser [JSONPathElement]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many1 Parser Text JSONPathElement
jsonPathElement
else String -> Parser Text JSONPathElement
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"not a search element"
beginningPoint :: Parser BeginningPoint
beginningPoint :: Parser BeginningPoint
beginningPoint = do
((Char -> Parser Char
char Char
'$' Parser Char -> BeginningPoint -> Parser BeginningPoint
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> BeginningPoint
Root) Parser BeginningPoint
-> Parser BeginningPoint -> Parser BeginningPoint
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Char -> Parser Char
char Char
'@' Parser Char -> BeginningPoint -> Parser BeginningPoint
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> BeginningPoint
CurrentObject))
condition :: Parser Condition
condition :: Parser Condition
condition = Parser Condition -> Parser Condition
forall a. Parser a -> Parser a
ignoreSurroundingSpace
(Parser Condition -> Parser Condition)
-> Parser Condition -> Parser Condition
forall a b. (a -> b) -> a -> b
$ Text -> Parser Text Text
string Text
"==" Parser Text Text -> Condition -> Parser Condition
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Condition
Equal
Parser Condition -> Parser Condition -> Parser Condition
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> Parser Text Text
string Text
"!=" Parser Text Text -> Condition -> Parser Condition
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Condition
NotEqual
Parser Condition -> Parser Condition -> Parser Condition
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> Parser Text Text
string Text
">" Parser Text Text -> Condition -> Parser Condition
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Condition
GreaterThan
Parser Condition -> Parser Condition -> Parser Condition
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> Parser Text Text
string Text
"<" Parser Text Text -> Condition -> Parser Condition
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Condition
SmallerThan
literal :: Parser Literal
literal :: Parser Literal
literal = do
(Int -> Literal
LitNumber (Int -> Literal) -> Parser Text Int -> Parser Literal
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text Int -> Parser Text Int
forall a. Num a => Parser a -> Parser a
signed Parser Text Int
forall a. Integral a => Parser a
decimal)
Parser Literal -> Parser Literal -> Parser Literal
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> Literal
LitString (Text -> Literal) -> Parser Text Text -> Parser Literal
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Parser Char
char Char
'"' Parser Char -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Char -> Bool) -> Parser Text Text
A.takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'"') Parser Text Text -> Parser Char -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> Parser Char
char Char
'"')
ignoreSurroundingSpace :: Parser a -> Parser a
ignoreSurroundingSpace :: Parser a -> Parser a
ignoreSurroundingSpace Parser a
p = Parser Char -> Parser Text String
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many' Parser Char
space Parser Text String -> Parser a -> Parser a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser a
p Parser a -> Parser Text String -> Parser a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser Char -> Parser Text String
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many' Parser Char
space
ignoreSurroundingSqBr :: Parser a -> Parser a
ignoreSurroundingSqBr :: Parser a -> Parser a
ignoreSurroundingSqBr Parser a
p = Char -> Parser Char
char Char
'[' Parser Char -> Parser a -> Parser a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser a
p Parser a -> Parser Char -> Parser a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> Parser Char
char Char
']'