{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Codec.CBOR.Cuddle.Parser where
import Codec.CBOR.Cuddle.CDDL
import Codec.CBOR.Cuddle.CDDL.CtlOp (CtlOp)
import Codec.CBOR.Cuddle.CDDL.CtlOp qualified as COp
import Codec.CBOR.Cuddle.Comments (Comment, WithComment (..), withComment, (!*>), (//-), (<*!))
import Codec.CBOR.Cuddle.Parser.Lexer (
Parser,
charInRange,
pCommentBlock,
space,
)
import Control.Applicative.Combinators.NonEmpty qualified as NE
import Data.Foldable (Foldable (..))
import Data.Functor (void, ($>))
import Data.List.NonEmpty (NonEmpty)
import Data.List.NonEmpty qualified as NE
import Data.Maybe (isJust)
import Data.Text (Text)
import Data.Text qualified as T
import Data.Text.Encoding (encodeUtf8)
import GHC.Word (Word64, Word8)
import Text.Megaparsec
import Text.Megaparsec.Char hiding (space)
import Text.Megaparsec.Char qualified as C
import Text.Megaparsec.Char.Lexer qualified as L
pCDDL :: Parser CDDL
pCDDL :: Parser CDDL
pCDDL = do
[Comment]
initialComments <- ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity [Comment]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many (ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Comment
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Comment)
-> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Comment
forall a b. (a -> b) -> a -> b
$ ParsecT Void Text Identity ()
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m ()
C.space ParsecT Void Text Identity ()
-> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Comment
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Comment
pCommentBlock ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity ()
-> ParsecT Void Text Identity Comment
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Rule -> ParsecT Void Text Identity ()
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy ParsecT Void Text Identity Rule
pRule)
Maybe Comment
initialRuleComment <- ParsecT Void Text Identity ()
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m ()
C.space ParsecT Void Text Identity ()
-> ParsecT Void Text Identity (Maybe Comment)
-> ParsecT Void Text Identity (Maybe Comment)
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity (Maybe Comment)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT Void Text Identity Comment
pCommentBlock
Rule
initialRule <- ParsecT Void Text Identity Rule
pRule
[TopLevel]
cddlTail <- ParsecT Void Text Identity TopLevel
-> ParsecT Void Text Identity [TopLevel]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many (ParsecT Void Text Identity TopLevel
-> ParsecT Void Text Identity [TopLevel])
-> ParsecT Void Text Identity TopLevel
-> ParsecT Void Text Identity [TopLevel]
forall a b. (a -> b) -> a -> b
$ ParsecT Void Text Identity TopLevel
pTopLevel ParsecT Void Text Identity TopLevel
-> ParsecT Void Text Identity ()
-> ParsecT Void Text Identity TopLevel
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity ()
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m ()
C.space
ParsecT Void Text Identity ()
forall e s (m :: * -> *). MonadParsec e s m => m ()
eof ParsecT Void Text Identity () -> CDDL -> Parser CDDL
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> [Comment] -> Rule -> [TopLevel] -> CDDL
CDDL [Comment]
initialComments (Rule
initialRule Rule -> Comment -> Rule
forall a. HasComment a => a -> Comment -> a
//- Maybe Comment -> Comment
forall m. Monoid m => Maybe m -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold Maybe Comment
initialRuleComment) [TopLevel]
cddlTail
pTopLevel :: Parser TopLevel
pTopLevel :: ParsecT Void Text Identity TopLevel
pTopLevel = ParsecT Void Text Identity TopLevel
-> ParsecT Void Text Identity TopLevel
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT Void Text Identity TopLevel
tlRule ParsecT Void Text Identity TopLevel
-> ParsecT Void Text Identity TopLevel
-> ParsecT Void Text Identity TopLevel
forall a.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT Void Text Identity TopLevel
tlComment
where
tlRule :: ParsecT Void Text Identity TopLevel
tlRule = do
Maybe Comment
mCmt <- ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity (Maybe Comment)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT Void Text Identity Comment
pCommentBlock
Rule
rule <- ParsecT Void Text Identity Rule
pRule
TopLevel -> ParsecT Void Text Identity TopLevel
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TopLevel -> ParsecT Void Text Identity TopLevel)
-> (Rule -> TopLevel)
-> Rule
-> ParsecT Void Text Identity TopLevel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rule -> TopLevel
TopLevelRule (Rule -> ParsecT Void Text Identity TopLevel)
-> Rule -> ParsecT Void Text Identity TopLevel
forall a b. (a -> b) -> a -> b
$ Rule
rule Rule -> Comment -> Rule
forall a. HasComment a => a -> Comment -> a
//- Maybe Comment -> Comment
forall m. Monoid m => Maybe m -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold Maybe Comment
mCmt
tlComment :: ParsecT Void Text Identity TopLevel
tlComment = Comment -> TopLevel
TopLevelComment (Comment -> TopLevel)
-> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity TopLevel
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Comment
pCommentBlock
pRule :: Parser Rule
pRule :: ParsecT Void Text Identity Rule
pRule = do
Name
name <- Parser Name
pName
Maybe GenericParam
genericParam <- ParsecT Void Text Identity GenericParam
-> ParsecT Void Text Identity (Maybe GenericParam)
forall e s (f :: * -> *) a. MonadParsec e s f => f a -> f (Maybe a)
optcomp ParsecT Void Text Identity GenericParam
pGenericParam
Comment
cmt <- ParsecT Void Text Identity Comment
space
(Assign
assign, TypeOrGroup
typeOrGrp) <-
[ParsecT Void Text Identity (Assign, TypeOrGroup)]
-> ParsecT Void Text Identity (Assign, TypeOrGroup)
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
[ ParsecT Void Text Identity (Assign, TypeOrGroup)
-> ParsecT Void Text Identity (Assign, TypeOrGroup)
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT Void Text Identity (Assign, TypeOrGroup)
-> ParsecT Void Text Identity (Assign, TypeOrGroup))
-> ParsecT Void Text Identity (Assign, TypeOrGroup)
-> ParsecT Void Text Identity (Assign, TypeOrGroup)
forall a b. (a -> b) -> a -> b
$
(,)
(Assign -> TypeOrGroup -> (Assign, TypeOrGroup))
-> ParsecT Void Text Identity Assign
-> ParsecT
Void Text Identity (TypeOrGroup -> (Assign, TypeOrGroup))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Assign
pAssignT
ParsecT Void Text Identity (TypeOrGroup -> (Assign, TypeOrGroup))
-> ParsecT Void Text Identity Comment
-> ParsecT
Void Text Identity (TypeOrGroup -> (Assign, TypeOrGroup))
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Comment
space
ParsecT Void Text Identity (TypeOrGroup -> (Assign, TypeOrGroup))
-> ParsecT Void Text Identity TypeOrGroup
-> ParsecT Void Text Identity (Assign, TypeOrGroup)
forall a b.
ParsecT Void Text Identity (a -> b)
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Type0 -> TypeOrGroup
TOGType (Type0 -> TypeOrGroup)
-> ParsecT Void Text Identity Type0
-> ParsecT Void Text Identity TypeOrGroup
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Type0
pType0 ParsecT Void Text Identity TypeOrGroup
-> ParsecT Void Text Identity ()
-> ParsecT Void Text Identity TypeOrGroup
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Text -> ParsecT Void Text Identity ()
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy (ParsecT Void Text Identity Comment
space ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (ParsecT Void Text Identity Text
":" ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
forall a.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT Void Text Identity Text
"=>")))
, (,) (Assign -> TypeOrGroup -> (Assign, TypeOrGroup))
-> ParsecT Void Text Identity Assign
-> ParsecT
Void Text Identity (TypeOrGroup -> (Assign, TypeOrGroup))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Assign
pAssignG ParsecT Void Text Identity (TypeOrGroup -> (Assign, TypeOrGroup))
-> ParsecT Void Text Identity Comment
-> ParsecT
Void Text Identity (TypeOrGroup -> (Assign, TypeOrGroup))
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Comment
space ParsecT Void Text Identity (TypeOrGroup -> (Assign, TypeOrGroup))
-> ParsecT Void Text Identity TypeOrGroup
-> ParsecT Void Text Identity (Assign, TypeOrGroup)
forall a b.
ParsecT Void Text Identity (a -> b)
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GroupEntry -> TypeOrGroup
TOGGroup (GroupEntry -> TypeOrGroup)
-> ParsecT Void Text Identity GroupEntry
-> ParsecT Void Text Identity TypeOrGroup
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity GroupEntry
pGrpEntry)
]
Rule -> ParsecT Void Text Identity Rule
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Rule -> ParsecT Void Text Identity Rule)
-> Rule -> ParsecT Void Text Identity Rule
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe GenericParam -> Assign -> TypeOrGroup -> Comment -> Rule
Rule Name
name Maybe GenericParam
genericParam Assign
assign TypeOrGroup
typeOrGrp Comment
cmt
pName :: Parser Name
pName :: Parser Name
pName = String -> Parser Name -> Parser Name
forall a.
String
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"name" (Parser Name -> Parser Name) -> Parser Name -> Parser Name
forall a b. (a -> b) -> a -> b
$ do
Char
fc <- ParsecT Void Text Identity Char
firstChar
String
rest <- ParsecT Void Text Identity Char
-> ParsecT Void Text Identity String
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many ParsecT Void Text Identity Char
midChar
Name -> Parser Name
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Name -> Parser Name) -> Name -> Parser Name
forall a b. (a -> b) -> a -> b
$ (Text -> Comment -> Name
`Name` Comment
forall a. Monoid a => a
mempty) (Text -> Name) -> (String -> Text) -> String -> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack (String -> Name) -> String -> Name
forall a b. (a -> b) -> a -> b
$ (Char
fc Char -> String -> String
forall a. a -> [a] -> [a]
: String
rest)
where
firstChar :: ParsecT Void Text Identity Char
firstChar = ParsecT Void Text Identity Char
ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
letterChar ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
forall a.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'@' ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
forall a.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'_' ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
forall a.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'$'
midChar :: ParsecT Void Text Identity Char
midChar =
ParsecT Void Text Identity Char
ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
alphaNumChar
ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
forall a.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'@'
ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
forall a.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'_'
ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
forall a.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'$'
ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
forall a.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'.' ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
forall a.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'-') ParsecT Void Text Identity Char
-> ParsecT Void Text Identity () -> ParsecT Void Text Identity Char
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity () -> ParsecT Void Text Identity ()
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy (ParsecT Void Text Identity ()
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m ()
space1 ParsecT Void Text Identity ()
-> ParsecT Void Text Identity () -> ParsecT Void Text Identity ()
forall a.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT Void Text Identity ()
forall e s (m :: * -> *). MonadParsec e s m => m ()
eof ParsecT Void Text Identity ()
-> ParsecT Void Text Identity () -> ParsecT Void Text Identity ()
forall a.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT Void Text Identity (Tokens Text)
-> ParsecT Void Text Identity ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Tokens s)
eol))
pAssignT :: Parser Assign
pAssignT :: ParsecT Void Text Identity Assign
pAssignT =
[ParsecT Void Text Identity Assign]
-> ParsecT Void Text Identity Assign
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
[ Assign
AssignEq Assign
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Assign
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Void Text Identity Text
"="
, Assign
AssignExt Assign
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Assign
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Void Text Identity Text
"/="
]
pAssignG :: Parser Assign
pAssignG :: ParsecT Void Text Identity Assign
pAssignG =
[ParsecT Void Text Identity Assign]
-> ParsecT Void Text Identity Assign
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
[ Assign
AssignEq Assign
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Assign
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Void Text Identity Text
"="
, Assign
AssignExt Assign
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Assign
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Void Text Identity Text
"//="
]
pGenericParam :: Parser GenericParam
pGenericParam :: ParsecT Void Text Identity GenericParam
pGenericParam =
NonEmpty Name -> GenericParam
GenericParam
(NonEmpty Name -> GenericParam)
-> ParsecT Void Text Identity (NonEmpty Name)
-> ParsecT Void Text Identity GenericParam
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity (NonEmpty Name)
-> ParsecT Void Text Identity (NonEmpty Name)
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between ParsecT Void Text Identity Text
"<" ParsecT Void Text Identity Text
">" (Parser Name
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity (NonEmpty Name)
forall (m :: * -> *) a sep.
Alternative m =>
m a -> m sep -> m (NonEmpty a)
NE.sepBy1 (ParsecT Void Text Identity Comment
space ParsecT Void Text Identity Comment -> Parser Name -> Parser Name
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m Comment -> m a -> m a
!*> Parser Name
pName Parser Name -> ParsecT Void Text Identity Comment -> Parser Name
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m a -> m Comment -> m a
<*! ParsecT Void Text Identity Comment
space) ParsecT Void Text Identity Text
",")
pGenericArg :: Parser GenericArg
pGenericArg :: Parser GenericArg
pGenericArg =
NonEmpty Type1 -> GenericArg
GenericArg
(NonEmpty Type1 -> GenericArg)
-> ParsecT Void Text Identity (NonEmpty Type1) -> Parser GenericArg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity (NonEmpty Type1)
-> ParsecT Void Text Identity (NonEmpty Type1)
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between ParsecT Void Text Identity Text
"<" ParsecT Void Text Identity Text
">" (ParsecT Void Text Identity Type1
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity (NonEmpty Type1)
forall (m :: * -> *) a sep.
Alternative m =>
m a -> m sep -> m (NonEmpty a)
NE.sepBy1 (ParsecT Void Text Identity Comment
space ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Type1
-> ParsecT Void Text Identity Type1
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m Comment -> m a -> m a
!*> ParsecT Void Text Identity Type1
pType1 ParsecT Void Text Identity Type1
-> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Type1
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m a -> m Comment -> m a
<*! ParsecT Void Text Identity Comment
space) ParsecT Void Text Identity Text
",")
pType0 :: Parser Type0
pType0 :: ParsecT Void Text Identity Type0
pType0 = NonEmpty Type1 -> Type0
Type0 (NonEmpty Type1 -> Type0)
-> ParsecT Void Text Identity (NonEmpty Type1)
-> ParsecT Void Text Identity Type0
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Type1
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity (NonEmpty Type1)
forall e s (m :: * -> *) a sep.
MonadParsec e s m =>
m a -> m sep -> m (NonEmpty a)
sepBy1' (ParsecT Void Text Identity Comment
space ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Type1
-> ParsecT Void Text Identity Type1
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m Comment -> m a -> m a
!*> ParsecT Void Text Identity Type1
pType1 ParsecT Void Text Identity Type1
-> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Type1
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m a -> m Comment -> m a
<*! ParsecT Void Text Identity Comment
space) (ParsecT Void Text Identity Text -> ParsecT Void Text Identity Text
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT Void Text Identity Text
"/")
pType1 :: Parser Type1
pType1 :: ParsecT Void Text Identity Type1
pType1 = do
Type2
v <- Parser Type2
pType2
Maybe (Comment, TyOp, Comment, Type2)
rest <- ParsecT Void Text Identity (Comment, TyOp, Comment, Type2)
-> ParsecT
Void Text Identity (Maybe (Comment, TyOp, Comment, Type2))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT Void Text Identity (Comment, TyOp, Comment, Type2)
-> ParsecT
Void Text Identity (Maybe (Comment, TyOp, Comment, Type2)))
-> ParsecT Void Text Identity (Comment, TyOp, Comment, Type2)
-> ParsecT
Void Text Identity (Maybe (Comment, TyOp, Comment, Type2))
forall a b. (a -> b) -> a -> b
$ do
(Comment
cmtFst, TyOp
tyOp) <- ParsecT Void Text Identity (Comment, TyOp)
-> ParsecT Void Text Identity (Comment, TyOp)
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT Void Text Identity (Comment, TyOp)
-> ParsecT Void Text Identity (Comment, TyOp))
-> ParsecT Void Text Identity (Comment, TyOp)
-> ParsecT Void Text Identity (Comment, TyOp)
forall a b. (a -> b) -> a -> b
$ do
Comment
cmt <- ParsecT Void Text Identity Comment
space
TyOp
tyOp <- Parser TyOp
pTyOp
(Comment, TyOp) -> ParsecT Void Text Identity (Comment, TyOp)
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Comment
cmt, TyOp
tyOp)
Comment
cmtSnd <- ParsecT Void Text Identity Comment
space
Type2
w <- Parser Type2
pType2
(Comment, TyOp, Comment, Type2)
-> ParsecT Void Text Identity (Comment, TyOp, Comment, Type2)
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Comment
cmtFst, TyOp
tyOp, Comment
cmtSnd, Type2
w)
case Maybe (Comment, TyOp, Comment, Type2)
rest of
Just (Comment
cmtFst, TyOp
tyOp, Comment
cmtSnd, Type2
w) ->
Type1 -> ParsecT Void Text Identity Type1
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Type1 -> ParsecT Void Text Identity Type1)
-> Type1 -> ParsecT Void Text Identity Type1
forall a b. (a -> b) -> a -> b
$ Type2 -> Maybe (TyOp, Type2) -> Comment -> Type1
Type1 Type2
v ((TyOp, Type2) -> Maybe (TyOp, Type2)
forall a. a -> Maybe a
Just (TyOp
tyOp, Type2
w)) (Comment -> Type1) -> Comment -> Type1
forall a b. (a -> b) -> a -> b
$ Comment
cmtFst Comment -> Comment -> Comment
forall a. Semigroup a => a -> a -> a
<> Comment
cmtSnd
Maybe (Comment, TyOp, Comment, Type2)
Nothing -> Type1 -> ParsecT Void Text Identity Type1
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Type1 -> ParsecT Void Text Identity Type1)
-> Type1 -> ParsecT Void Text Identity Type1
forall a b. (a -> b) -> a -> b
$ Type2 -> Maybe (TyOp, Type2) -> Comment -> Type1
Type1 Type2
v Maybe (TyOp, Type2)
forall a. Maybe a
Nothing Comment
forall a. Monoid a => a
mempty
pType2 :: Parser Type2
pType2 :: Parser Type2
pType2 =
[Parser Type2] -> Parser Type2
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
[ Value -> Type2
T2Value (Value -> Type2)
-> ParsecT Void Text Identity Value -> Parser Type2
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Value
pValue
, Name -> Maybe GenericArg -> Type2
T2Name (Name -> Maybe GenericArg -> Type2)
-> Parser Name
-> ParsecT Void Text Identity (Maybe GenericArg -> Type2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Name
pName ParsecT Void Text Identity (Maybe GenericArg -> Type2)
-> ParsecT Void Text Identity (Maybe GenericArg) -> Parser Type2
forall a b.
ParsecT Void Text Identity (a -> b)
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser GenericArg -> ParsecT Void Text Identity (Maybe GenericArg)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser GenericArg
pGenericArg
, Type0 -> Type2
T2Group (Type0 -> Type2)
-> ParsecT Void Text Identity Type0 -> Parser Type2
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String
-> ParsecT Void Text Identity Type0
-> ParsecT Void Text Identity Type0
forall a.
String
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"group" (ParsecT Void Text Identity Text
"(" ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Type0
-> ParsecT Void Text Identity Type0
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Comment
space ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Type0
-> ParsecT Void Text Identity Type0
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m Comment -> m a -> m a
!*> ParsecT Void Text Identity Type0
pType0 ParsecT Void Text Identity Type0
-> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Type0
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m a -> m Comment -> m a
<*! ParsecT Void Text Identity Comment
space ParsecT Void Text Identity Type0
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Type0
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Text
")")
, Group -> Type2
T2Map (Group -> Type2)
-> ParsecT Void Text Identity Group -> Parser Type2
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String
-> ParsecT Void Text Identity Group
-> ParsecT Void Text Identity Group
forall a.
String
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"map" (ParsecT Void Text Identity Text
"{" ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Group
-> ParsecT Void Text Identity Group
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Group
pGroup ParsecT Void Text Identity Group
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Group
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Text
"}")
, Group -> Type2
T2Array (Group -> Type2)
-> ParsecT Void Text Identity Group -> Parser Type2
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String
-> ParsecT Void Text Identity Group
-> ParsecT Void Text Identity Group
forall a.
String
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"array" (ParsecT Void Text Identity Text
"[" ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Group
-> ParsecT Void Text Identity Group
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Comment
space ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Group
-> ParsecT Void Text Identity Group
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m Comment -> m a -> m a
!*> ParsecT Void Text Identity Group
pGroup ParsecT Void Text Identity Group
-> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Group
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m a -> m Comment -> m a
<*! ParsecT Void Text Identity Comment
space ParsecT Void Text Identity Group
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Group
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Text
"]")
, Name -> Maybe GenericArg -> Type2
T2Unwrapped (Name -> Maybe GenericArg -> Type2)
-> Parser Name
-> ParsecT Void Text Identity (Maybe GenericArg -> Type2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Void Text Identity Text
"~" ParsecT Void Text Identity Text -> Parser Name -> Parser Name
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Comment
space ParsecT Void Text Identity Comment -> Parser Name -> Parser Name
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m Comment -> m a -> m a
!*> Parser Name
pName) ParsecT Void Text Identity (Maybe GenericArg -> Type2)
-> ParsecT Void Text Identity (Maybe GenericArg) -> Parser Type2
forall a b.
ParsecT Void Text Identity (a -> b)
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser GenericArg -> ParsecT Void Text Identity (Maybe GenericArg)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser GenericArg
pGenericArg
, do
Text
_ <- ParsecT Void Text Identity Text
"&"
Comment
cmt <- ParsecT Void Text Identity Comment
space
[Parser Type2] -> Parser Type2
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
[ Group -> Type2
T2Enum (Group -> Type2)
-> ParsecT Void Text Identity Group -> Parser Type2
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Void Text Identity Text
"(" ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Group
-> ParsecT Void Text Identity Group
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Comment
space ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Group
-> ParsecT Void Text Identity Group
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m Comment -> m a -> m a
!*> ParsecT Void Text Identity Group
pGroup ParsecT Void Text Identity Group
-> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Group
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m a -> m Comment -> m a
<*! Comment -> ParsecT Void Text Identity Comment
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Comment
cmt ParsecT Void Text Identity Group
-> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Group
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m a -> m Comment -> m a
<*! ParsecT Void Text Identity Comment
space ParsecT Void Text Identity Group
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Group
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Text
")")
, Name -> Maybe GenericArg -> Type2
T2EnumRef (Name -> Maybe GenericArg -> Type2)
-> Parser Name
-> ParsecT Void Text Identity (Maybe GenericArg -> Type2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Name
pName ParsecT Void Text Identity (Maybe GenericArg -> Type2)
-> ParsecT Void Text Identity (Maybe GenericArg) -> Parser Type2
forall a b.
ParsecT Void Text Identity (a -> b)
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser GenericArg -> ParsecT Void Text Identity (Maybe GenericArg)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser GenericArg
pGenericArg
]
, ParsecT Void Text Identity Text
"#" ParsecT Void Text Identity Text -> Parser Type2 -> Parser Type2
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> do
Maybe Word8
mmajor :: Maybe Word8 <- ParsecT Void Text Identity Word8
-> ParsecT Void Text Identity (Maybe Word8)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT Void Text Identity Word8
forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
L.decimal
case Maybe Word8
mmajor of
Just Word8
major -> do
Maybe Word64
mminor <- ParsecT Void Text Identity Word64
-> ParsecT Void Text Identity (Maybe Word64)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT Void Text Identity Text
"." ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Word64
-> ParsecT Void Text Identity Word64
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Word64
forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
L.decimal)
let
pTag :: Parser Type2
pTag
| Word8
major Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
6 = Maybe Word64 -> Type0 -> Type2
T2Tag Maybe Word64
mminor (Type0 -> Type2)
-> ParsecT Void Text Identity Type0 -> Parser Type2
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Void Text Identity Text
"(" ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Type0
-> ParsecT Void Text Identity Type0
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Comment
space ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Type0
-> ParsecT Void Text Identity Type0
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m Comment -> m a -> m a
!*> ParsecT Void Text Identity Type0
pType0 ParsecT Void Text Identity Type0
-> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Type0
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m a -> m Comment -> m a
<*! ParsecT Void Text Identity Comment
space ParsecT Void Text Identity Type0
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Type0
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Text
")")
| Bool
otherwise = Parser Type2
forall a. ParsecT Void Text Identity a
forall (f :: * -> *) a. Alternative f => f a
empty
Parser Type2
pTag Parser Type2 -> Parser Type2 -> Parser Type2
forall a.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Type2 -> Parser Type2
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word8 -> Maybe Word64 -> Type2
T2DataItem Word8
major Maybe Word64
mminor)
Maybe Word8
Nothing -> Type2 -> Parser Type2
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Type2
T2Any
]
pHeadNumber :: Parser Word64
pHeadNumber :: ParsecT Void Text Identity Word64
pHeadNumber = ParsecT Void Text Identity Word64
forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
L.decimal
pRangeOp :: Parser RangeBound
pRangeOp :: Parser RangeBound
pRangeOp = String -> Parser RangeBound -> Parser RangeBound
forall a.
String
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"range operator" (Parser RangeBound -> Parser RangeBound)
-> Parser RangeBound -> Parser RangeBound
forall a b. (a -> b) -> a -> b
$ Parser RangeBound -> Parser RangeBound
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT Void Text Identity Text
"..." ParsecT Void Text Identity Text -> RangeBound -> Parser RangeBound
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> RangeBound
ClOpen) Parser RangeBound -> Parser RangeBound -> Parser RangeBound
forall a.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (ParsecT Void Text Identity Text
".." ParsecT Void Text Identity Text -> RangeBound -> Parser RangeBound
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> RangeBound
Closed)
pCtlOp :: Parser CtlOp
pCtlOp :: Parser CtlOp
pCtlOp =
String -> Parser CtlOp -> Parser CtlOp
forall a.
String
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"control operator" (Parser CtlOp -> Parser CtlOp) -> Parser CtlOp -> Parser CtlOp
forall a b. (a -> b) -> a -> b
$
ParsecT Void Text Identity Text
"."
ParsecT Void Text Identity Text -> Parser CtlOp -> Parser CtlOp
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [Parser CtlOp] -> Parser CtlOp
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
( Parser CtlOp -> Parser CtlOp
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try
(Parser CtlOp -> Parser CtlOp) -> [Parser CtlOp] -> [Parser CtlOp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ ParsecT Void Text Identity Text
"cborseq" ParsecT Void Text Identity Text -> CtlOp -> Parser CtlOp
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> CtlOp
COp.Cborseq
, ParsecT Void Text Identity Text
"cbor" ParsecT Void Text Identity Text -> CtlOp -> Parser CtlOp
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> CtlOp
COp.Cbor
, ParsecT Void Text Identity Text
"size" ParsecT Void Text Identity Text -> CtlOp -> Parser CtlOp
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> CtlOp
COp.Size
, ParsecT Void Text Identity Text
"bits" ParsecT Void Text Identity Text -> CtlOp -> Parser CtlOp
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> CtlOp
COp.Bits
, ParsecT Void Text Identity Text
"within" ParsecT Void Text Identity Text -> CtlOp -> Parser CtlOp
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> CtlOp
COp.Within
, ParsecT Void Text Identity Text
"and" ParsecT Void Text Identity Text -> CtlOp -> Parser CtlOp
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> CtlOp
COp.And
, ParsecT Void Text Identity Text
"lt" ParsecT Void Text Identity Text -> CtlOp -> Parser CtlOp
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> CtlOp
COp.Lt
, ParsecT Void Text Identity Text
"le" ParsecT Void Text Identity Text -> CtlOp -> Parser CtlOp
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> CtlOp
COp.Le
, ParsecT Void Text Identity Text
"gt" ParsecT Void Text Identity Text -> CtlOp -> Parser CtlOp
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> CtlOp
COp.Gt
, ParsecT Void Text Identity Text
"ge" ParsecT Void Text Identity Text -> CtlOp -> Parser CtlOp
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> CtlOp
COp.Ge
, ParsecT Void Text Identity Text
"eq" ParsecT Void Text Identity Text -> CtlOp -> Parser CtlOp
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> CtlOp
COp.Eq
, ParsecT Void Text Identity Text
"ne" ParsecT Void Text Identity Text -> CtlOp -> Parser CtlOp
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> CtlOp
COp.Ne
, ParsecT Void Text Identity Text
"default" ParsecT Void Text Identity Text -> CtlOp -> Parser CtlOp
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> CtlOp
COp.Default
, ParsecT Void Text Identity Text
"regexp" ParsecT Void Text Identity Text -> CtlOp -> Parser CtlOp
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> CtlOp
COp.Regexp
]
)
pGroup :: Parser Group
pGroup :: ParsecT Void Text Identity Group
pGroup = NonEmpty GrpChoice -> Group
Group (NonEmpty GrpChoice -> Group)
-> ParsecT Void Text Identity (NonEmpty GrpChoice)
-> ParsecT Void Text Identity Group
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity GrpChoice
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity (NonEmpty GrpChoice)
forall (m :: * -> *) a sep.
Alternative m =>
m a -> m sep -> m (NonEmpty a)
NE.sepBy1 (ParsecT Void Text Identity Comment
space ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity GrpChoice
-> ParsecT Void Text Identity GrpChoice
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m Comment -> m a -> m a
!*> ParsecT Void Text Identity GrpChoice
pGrpChoice) ParsecT Void Text Identity Text
"//"
pGrpChoice :: Parser GrpChoice
pGrpChoice :: ParsecT Void Text Identity GrpChoice
pGrpChoice = [GroupEntry] -> Comment -> GrpChoice
GrpChoice ([GroupEntry] -> Comment -> GrpChoice)
-> ParsecT Void Text Identity [GroupEntry]
-> ParsecT Void Text Identity (Comment -> GrpChoice)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity GroupEntry
-> ParsecT Void Text Identity [GroupEntry]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many (ParsecT Void Text Identity Comment
space ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity GroupEntry
-> ParsecT Void Text Identity GroupEntry
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m Comment -> m a -> m a
!*> ParsecT Void Text Identity GroupEntry
pGrpEntry ParsecT Void Text Identity GroupEntry
-> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity GroupEntry
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m a -> m Comment -> m a
<*! ParsecT Void Text Identity Comment
pOptCom) ParsecT Void Text Identity (Comment -> GrpChoice)
-> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity GrpChoice
forall a b.
ParsecT Void Text Identity (a -> b)
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Void Text Identity Comment
forall a. Monoid a => a
mempty
pGrpEntry :: Parser GroupEntry
pGrpEntry :: ParsecT Void Text Identity GroupEntry
pGrpEntry = do
Maybe OccurrenceIndicator
occur <- ParsecT Void Text Identity OccurrenceIndicator
-> ParsecT Void Text Identity (Maybe OccurrenceIndicator)
forall e s (f :: * -> *) a. MonadParsec e s f => f a -> f (Maybe a)
optcomp ParsecT Void Text Identity OccurrenceIndicator
pOccur
Comment
cmt <- ParsecT Void Text Identity Comment
space
WithComment Comment
cmt' GroupEntryVariant
variant <-
[ParsecT Void Text Identity (WithComment GroupEntryVariant)]
-> ParsecT Void Text Identity (WithComment GroupEntryVariant)
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
[ ParsecT Void Text Identity (WithComment GroupEntryVariant)
-> ParsecT Void Text Identity (WithComment GroupEntryVariant)
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT Void Text Identity (WithComment GroupEntryVariant)
-> ParsecT Void Text Identity (WithComment GroupEntryVariant))
-> ParsecT Void Text Identity (WithComment GroupEntryVariant)
-> ParsecT Void Text Identity (WithComment GroupEntryVariant)
forall a b. (a -> b) -> a -> b
$ do
Maybe (WithComment MemberKey)
mKey <- ParsecT Void Text Identity (WithComment MemberKey)
-> ParsecT Void Text Identity (Maybe (WithComment MemberKey))
forall e s (f :: * -> *) a. MonadParsec e s f => f a -> f (Maybe a)
optcomp (ParsecT Void Text Identity (WithComment MemberKey)
-> ParsecT Void Text Identity (Maybe (WithComment MemberKey)))
-> ParsecT Void Text Identity (WithComment MemberKey)
-> ParsecT Void Text Identity (Maybe (WithComment MemberKey))
forall a b. (a -> b) -> a -> b
$ ParsecT Void Text Identity (WithComment MemberKey)
pMemberKey ParsecT Void Text Identity (WithComment MemberKey)
-> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity (WithComment MemberKey)
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m a -> m Comment -> m a
<*! ParsecT Void Text Identity Comment
space
Type0
t0 <- ParsecT Void Text Identity Type0
pType0
WithComment GroupEntryVariant
-> ParsecT Void Text Identity (WithComment GroupEntryVariant)
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WithComment GroupEntryVariant
-> ParsecT Void Text Identity (WithComment GroupEntryVariant))
-> WithComment GroupEntryVariant
-> ParsecT Void Text Identity (WithComment GroupEntryVariant)
forall a b. (a -> b) -> a -> b
$ Maybe MemberKey -> Type0 -> GroupEntryVariant
GEType (Maybe MemberKey -> Type0 -> GroupEntryVariant)
-> WithComment (Maybe MemberKey)
-> WithComment (Type0 -> GroupEntryVariant)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (WithComment MemberKey) -> WithComment (Maybe MemberKey)
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => Maybe (m a) -> m (Maybe a)
sequence Maybe (WithComment MemberKey)
mKey WithComment (Type0 -> GroupEntryVariant)
-> WithComment Type0 -> WithComment GroupEntryVariant
forall a b. WithComment (a -> b) -> WithComment a -> WithComment b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Type0 -> WithComment Type0
forall a. a -> WithComment a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Type0
t0
, ParsecT Void Text Identity (WithComment GroupEntryVariant)
-> ParsecT Void Text Identity (WithComment GroupEntryVariant)
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT Void Text Identity (WithComment GroupEntryVariant)
-> ParsecT Void Text Identity (WithComment GroupEntryVariant))
-> ParsecT Void Text Identity (WithComment GroupEntryVariant)
-> ParsecT Void Text Identity (WithComment GroupEntryVariant)
forall a b. (a -> b) -> a -> b
$ GroupEntryVariant -> WithComment GroupEntryVariant
forall a. a -> WithComment a
withComment (GroupEntryVariant -> WithComment GroupEntryVariant)
-> ParsecT Void Text Identity GroupEntryVariant
-> ParsecT Void Text Identity (WithComment GroupEntryVariant)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Name -> Maybe GenericArg -> GroupEntryVariant
GERef (Name -> Maybe GenericArg -> GroupEntryVariant)
-> Parser Name
-> ParsecT
Void Text Identity (Maybe GenericArg -> GroupEntryVariant)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Name
pName ParsecT Void Text Identity (Maybe GenericArg -> GroupEntryVariant)
-> ParsecT Void Text Identity (Maybe GenericArg)
-> ParsecT Void Text Identity GroupEntryVariant
forall a b.
ParsecT Void Text Identity (a -> b)
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser GenericArg -> ParsecT Void Text Identity (Maybe GenericArg)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser GenericArg
pGenericArg)
, GroupEntryVariant -> WithComment GroupEntryVariant
forall a. a -> WithComment a
withComment (GroupEntryVariant -> WithComment GroupEntryVariant)
-> (Group -> GroupEntryVariant)
-> Group
-> WithComment GroupEntryVariant
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Group -> GroupEntryVariant
GEGroup (Group -> WithComment GroupEntryVariant)
-> ParsecT Void Text Identity Group
-> ParsecT Void Text Identity (WithComment GroupEntryVariant)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Void Text Identity Text
"(" ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Group
-> ParsecT Void Text Identity Group
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Comment
space ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Group
-> ParsecT Void Text Identity Group
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m Comment -> m a -> m a
!*> ParsecT Void Text Identity Group
pGroup ParsecT Void Text Identity Group
-> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Group
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m a -> m Comment -> m a
<*! ParsecT Void Text Identity Comment
space ParsecT Void Text Identity Group
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Group
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Text
")")
]
GroupEntry -> ParsecT Void Text Identity GroupEntry
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GroupEntry -> ParsecT Void Text Identity GroupEntry)
-> GroupEntry -> ParsecT Void Text Identity GroupEntry
forall a b. (a -> b) -> a -> b
$ Maybe OccurrenceIndicator
-> Comment -> GroupEntryVariant -> GroupEntry
GroupEntry Maybe OccurrenceIndicator
occur (Comment
cmt Comment -> Comment -> Comment
forall a. Semigroup a => a -> a -> a
<> Comment
cmt') GroupEntryVariant
variant
pMemberKey :: Parser (WithComment MemberKey)
pMemberKey :: ParsecT Void Text Identity (WithComment MemberKey)
pMemberKey =
[ParsecT Void Text Identity (WithComment MemberKey)]
-> ParsecT Void Text Identity (WithComment MemberKey)
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
[ ParsecT Void Text Identity (WithComment MemberKey)
-> ParsecT Void Text Identity (WithComment MemberKey)
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT Void Text Identity (WithComment MemberKey)
-> ParsecT Void Text Identity (WithComment MemberKey))
-> ParsecT Void Text Identity (WithComment MemberKey)
-> ParsecT Void Text Identity (WithComment MemberKey)
forall a b. (a -> b) -> a -> b
$ do
Type1
t1 <- ParsecT Void Text Identity Type1
pType1
Comment
cmt0 <- ParsecT Void Text Identity Comment
space
Comment
cmt1 <- Maybe Comment -> Comment
forall m. Monoid m => Maybe m -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold (Maybe Comment -> Comment)
-> ParsecT Void Text Identity (Maybe Comment)
-> ParsecT Void Text Identity Comment
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity (Maybe Comment)
forall e s (f :: * -> *) a. MonadParsec e s f => f a -> f (Maybe a)
optcomp (ParsecT Void Text Identity Text
"^" ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Comment
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Comment
space) ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Comment
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Text
"=>"
WithComment MemberKey
-> ParsecT Void Text Identity (WithComment MemberKey)
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WithComment MemberKey
-> ParsecT Void Text Identity (WithComment MemberKey))
-> WithComment MemberKey
-> ParsecT Void Text Identity (WithComment MemberKey)
forall a b. (a -> b) -> a -> b
$ Comment -> MemberKey -> WithComment MemberKey
forall a. Comment -> a -> WithComment a
WithComment (Comment
cmt0 Comment -> Comment -> Comment
forall a. Semigroup a => a -> a -> a
<> Comment
cmt1) (Type1 -> MemberKey
MKType Type1
t1)
, ParsecT Void Text Identity (WithComment MemberKey)
-> ParsecT Void Text Identity (WithComment MemberKey)
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT Void Text Identity (WithComment MemberKey)
-> ParsecT Void Text Identity (WithComment MemberKey))
-> ParsecT Void Text Identity (WithComment MemberKey)
-> ParsecT Void Text Identity (WithComment MemberKey)
forall a b. (a -> b) -> a -> b
$ do
Name
name <- Parser Name
pName
Comment
cmt <- ParsecT Void Text Identity Comment
space
Text
_ <- ParsecT Void Text Identity Text
":"
WithComment MemberKey
-> ParsecT Void Text Identity (WithComment MemberKey)
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WithComment MemberKey
-> ParsecT Void Text Identity (WithComment MemberKey))
-> (MemberKey -> WithComment MemberKey)
-> MemberKey
-> ParsecT Void Text Identity (WithComment MemberKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Comment -> MemberKey -> WithComment MemberKey
forall a. Comment -> a -> WithComment a
WithComment Comment
cmt (MemberKey -> ParsecT Void Text Identity (WithComment MemberKey))
-> MemberKey -> ParsecT Void Text Identity (WithComment MemberKey)
forall a b. (a -> b) -> a -> b
$ Name -> MemberKey
MKBareword Name
name
, do
Value
val <- ParsecT Void Text Identity Value
pValue
Comment
cmt <- ParsecT Void Text Identity Comment
space
Text
_ <- ParsecT Void Text Identity Text
":"
WithComment MemberKey
-> ParsecT Void Text Identity (WithComment MemberKey)
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WithComment MemberKey
-> ParsecT Void Text Identity (WithComment MemberKey))
-> (MemberKey -> WithComment MemberKey)
-> MemberKey
-> ParsecT Void Text Identity (WithComment MemberKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Comment -> MemberKey -> WithComment MemberKey
forall a. Comment -> a -> WithComment a
WithComment Comment
cmt (MemberKey -> ParsecT Void Text Identity (WithComment MemberKey))
-> MemberKey -> ParsecT Void Text Identity (WithComment MemberKey)
forall a b. (a -> b) -> a -> b
$ Value -> MemberKey
MKValue Value
val
]
pOptCom :: Parser Comment
pOptCom :: ParsecT Void Text Identity Comment
pOptCom = ParsecT Void Text Identity Comment
space ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Comment
forall a (m :: * -> *).
(HasComment a, Applicative m) =>
m a -> m Comment -> m a
<*! (Maybe Comment -> Comment
forall m. Monoid m => Maybe m -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold (Maybe Comment -> Comment)
-> ParsecT Void Text Identity (Maybe Comment)
-> ParsecT Void Text Identity Comment
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity (Maybe Comment)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT Void Text Identity Text
"," ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Comment
-> ParsecT Void Text Identity Comment
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Void Text Identity Comment
space))
pOccur :: Parser OccurrenceIndicator
pOccur :: ParsecT Void Text Identity OccurrenceIndicator
pOccur =
String
-> ParsecT Void Text Identity OccurrenceIndicator
-> ParsecT Void Text Identity OccurrenceIndicator
forall a.
String
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"occurrence indicator" (ParsecT Void Text Identity OccurrenceIndicator
-> ParsecT Void Text Identity OccurrenceIndicator)
-> ParsecT Void Text Identity OccurrenceIndicator
-> ParsecT Void Text Identity OccurrenceIndicator
forall a b. (a -> b) -> a -> b
$
[ParsecT Void Text Identity OccurrenceIndicator]
-> ParsecT Void Text Identity OccurrenceIndicator
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
[ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'+' ParsecT Void Text Identity Char
-> OccurrenceIndicator
-> ParsecT Void Text Identity OccurrenceIndicator
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> OccurrenceIndicator
OIOneOrMore
, Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'?' ParsecT Void Text Identity Char
-> OccurrenceIndicator
-> ParsecT Void Text Identity OccurrenceIndicator
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> OccurrenceIndicator
OIOptional
, ParsecT Void Text Identity OccurrenceIndicator
pBounded
]
pValue :: Parser Value
pValue :: ParsecT Void Text Identity Value
pValue =
String
-> ParsecT Void Text Identity Value
-> ParsecT Void Text Identity Value
forall a.
String
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"value" (ParsecT Void Text Identity Value
-> ParsecT Void Text Identity Value)
-> ParsecT Void Text Identity Value
-> ParsecT Void Text Identity Value
forall a b. (a -> b) -> a -> b
$
(ValueVariant -> Comment -> Value
`Value` Comment
forall a. Monoid a => a
mempty)
(ValueVariant -> Value)
-> ParsecT Void Text Identity ValueVariant
-> ParsecT Void Text Identity Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ParsecT Void Text Identity ValueVariant]
-> ParsecT Void Text Identity ValueVariant
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
[ ParsecT Void Text Identity ValueVariant
-> ParsecT Void Text Identity ValueVariant
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT Void Text Identity ValueVariant
pFloat
, ParsecT Void Text Identity ValueVariant
-> ParsecT Void Text Identity ValueVariant
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT Void Text Identity ValueVariant
pInt
, ParsecT Void Text Identity ValueVariant
-> ParsecT Void Text Identity ValueVariant
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT Void Text Identity ValueVariant
pBytes
, ParsecT Void Text Identity ValueVariant
pText
]
where
pSignedNum :: Num a => Parser a -> Parser (Bool, a)
pSignedNum :: forall a. Num a => Parser a -> Parser (Bool, a)
pSignedNum Parser a
valParser = do
Maybe Text
sign <- ParsecT Void Text Identity Text
-> ParsecT Void Text Identity (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT Void Text Identity Text
"-"
a
val <- Parser a
valParser Parser a -> ParsecT Void Text Identity () -> Parser a
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Text -> ParsecT Void Text Identity ()
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy ParsecT Void Text Identity Text
"*"
(Bool, a) -> Parser (Bool, a)
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe Text -> Bool
forall a. Maybe a -> Bool
isJust Maybe Text
sign, a
val)
pInt :: ParsecT Void Text Identity ValueVariant
pInt =
ParsecT Void Text Identity Word64 -> Parser (Bool, Word64)
forall a. Num a => Parser a -> Parser (Bool, a)
pSignedNum ParsecT Void Text Identity Word64
forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
L.decimal Parser (Bool, Word64)
-> ((Bool, Word64) -> ParsecT Void Text Identity ValueVariant)
-> ParsecT Void Text Identity ValueVariant
forall a b.
ParsecT Void Text Identity a
-> (a -> ParsecT Void Text Identity b)
-> ParsecT Void Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
(Bool
False, Word64
val) -> ValueVariant -> ParsecT Void Text Identity ValueVariant
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ValueVariant -> ParsecT Void Text Identity ValueVariant)
-> ValueVariant -> ParsecT Void Text Identity ValueVariant
forall a b. (a -> b) -> a -> b
$ Word64 -> ValueVariant
VUInt Word64
val
(Bool
True, Word64
val) -> ValueVariant -> ParsecT Void Text Identity ValueVariant
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ValueVariant -> ParsecT Void Text Identity ValueVariant)
-> ValueVariant -> ParsecT Void Text Identity ValueVariant
forall a b. (a -> b) -> a -> b
$ Word64 -> ValueVariant
VNInt Word64
val
pFloat :: ParsecT Void Text Identity ValueVariant
pFloat =
Parser Double -> Parser (Bool, Double)
forall a. Num a => Parser a -> Parser (Bool, a)
pSignedNum Parser Double
forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, RealFloat a) =>
m a
L.float Parser (Bool, Double)
-> ((Bool, Double) -> ParsecT Void Text Identity ValueVariant)
-> ParsecT Void Text Identity ValueVariant
forall a b.
ParsecT Void Text Identity a
-> (a -> ParsecT Void Text Identity b)
-> ParsecT Void Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
(Bool
False, Double
val) -> ValueVariant -> ParsecT Void Text Identity ValueVariant
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ValueVariant -> ParsecT Void Text Identity ValueVariant)
-> ValueVariant -> ParsecT Void Text Identity ValueVariant
forall a b. (a -> b) -> a -> b
$ Double -> ValueVariant
VFloat64 Double
val
(Bool
True, Double
val) -> ValueVariant -> ParsecT Void Text Identity ValueVariant
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ValueVariant -> ParsecT Void Text Identity ValueVariant)
-> (Double -> ValueVariant)
-> Double
-> ParsecT Void Text Identity ValueVariant
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> ValueVariant
VFloat64 (Double -> ParsecT Void Text Identity ValueVariant)
-> Double -> ParsecT Void Text Identity ValueVariant
forall a b. (a -> b) -> a -> b
$ Double -> Double
forall a. Num a => a -> a
negate Double
val
pSChar :: Parser Text
pSChar :: ParsecT Void Text Identity Text
pSChar = Maybe String
-> (Token Text -> Bool) -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhileP (String -> Maybe String
forall a. a -> Maybe a
Just String
"character") ((Token Text -> Bool) -> ParsecT Void Text Identity (Tokens Text))
-> (Token Text -> Bool) -> ParsecT Void Text Identity (Tokens Text)
forall a b. (a -> b) -> a -> b
$ \Token Text
x ->
[Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
or ([Bool] -> Bool) -> [Bool] -> Bool
forall a b. (a -> b) -> a -> b
$
[ Char -> Char -> Char -> Bool
charInRange Char
'\x20' Char
'\x21'
, Char -> Char -> Char -> Bool
charInRange Char
'\x23' Char
'\x5b'
, Char -> Char -> Char -> Bool
charInRange Char
'\x5d' Char
'\x7e'
, Char -> Char -> Char -> Bool
charInRange Char
'\x80' Char
'\x10fffd'
]
[Char -> Bool] -> String -> [Bool]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Char -> String
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure Char
Token Text
x
pText :: ParsecT Void Text Identity ValueVariant
pText = Text -> ValueVariant
VText (Text -> ValueVariant)
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity ValueVariant
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Void Text Identity Text
"\"" ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Text
pSChar ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Text
"\"")
pSByte :: ParsecT Void Text Identity (Tokens Text)
pSByte = Maybe String
-> (Token Text -> Bool) -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhileP (String -> Maybe String
forall a. a -> Maybe a
Just String
"byte character") ((Token Text -> Bool) -> ParsecT Void Text Identity (Tokens Text))
-> (Token Text -> Bool) -> ParsecT Void Text Identity (Tokens Text)
forall a b. (a -> b) -> a -> b
$ \Token Text
x ->
[Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
or ([Bool] -> Bool) -> [Bool] -> Bool
forall a b. (a -> b) -> a -> b
$
[ Char -> Char -> Char -> Bool
charInRange Char
'\x20' Char
'\x26'
, Char -> Char -> Char -> Bool
charInRange Char
'\x28' Char
'\x5b'
, Char -> Char -> Char -> Bool
charInRange Char
'\x5d' Char
'\x10fffd'
]
[Char -> Bool] -> String -> [Bool]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Char -> String
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure Char
Token Text
x
pBytes :: ParsecT Void Text Identity ValueVariant
pBytes = do
Maybe Text
_qualifier <- ParsecT Void Text Identity Text
-> ParsecT Void Text Identity (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT Void Text Identity Text
"h" ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
forall a.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT Void Text Identity Text
"b64")
ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity ValueVariant
-> ParsecT Void Text Identity ValueVariant
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between ParsecT Void Text Identity Text
"'" ParsecT Void Text Identity Text
"'" (ParsecT Void Text Identity ValueVariant
-> ParsecT Void Text Identity ValueVariant)
-> ParsecT Void Text Identity ValueVariant
-> ParsecT Void Text Identity ValueVariant
forall a b. (a -> b) -> a -> b
$ ByteString -> ValueVariant
VBytes (ByteString -> ValueVariant)
-> (Text -> ByteString) -> Text -> ValueVariant
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8 (Text -> ValueVariant)
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity ValueVariant
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Text
ParsecT Void Text Identity (Tokens Text)
pSByte
pTyOp :: Parser TyOp
pTyOp :: Parser TyOp
pTyOp =
[Parser TyOp] -> Parser TyOp
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
[ Parser TyOp -> Parser TyOp
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser TyOp -> Parser TyOp) -> Parser TyOp -> Parser TyOp
forall a b. (a -> b) -> a -> b
$ RangeBound -> TyOp
RangeOp (RangeBound -> TyOp) -> Parser RangeBound -> Parser TyOp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser RangeBound
pRangeOp
, CtlOp -> TyOp
CtrlOp (CtlOp -> TyOp) -> Parser CtlOp -> Parser TyOp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser CtlOp
pCtlOp
]
pBounded :: Parser OccurrenceIndicator
pBounded :: ParsecT Void Text Identity OccurrenceIndicator
pBounded = do
Maybe Word64
lo <- ParsecT Void Text Identity Word64
-> ParsecT Void Text Identity (Maybe Word64)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT Void Text Identity Word64
forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
L.decimal
Char
_ <- Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'*'
Maybe Word64
hi <- ParsecT Void Text Identity Word64
-> ParsecT Void Text Identity (Maybe Word64)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT Void Text Identity Word64
forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
L.decimal
OccurrenceIndicator
-> ParsecT Void Text Identity OccurrenceIndicator
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (OccurrenceIndicator
-> ParsecT Void Text Identity OccurrenceIndicator)
-> OccurrenceIndicator
-> ParsecT Void Text Identity OccurrenceIndicator
forall a b. (a -> b) -> a -> b
$ case (Maybe Word64
lo, Maybe Word64
hi) of
(Maybe Word64
Nothing, Maybe Word64
Nothing) -> OccurrenceIndicator
OIZeroOrMore
(Maybe Word64
x, Maybe Word64
y) -> Maybe Word64 -> Maybe Word64 -> OccurrenceIndicator
OIBounded Maybe Word64
x Maybe Word64
y
optcomp :: MonadParsec e s f => f a -> f (Maybe a)
optcomp :: forall e s (f :: * -> *) a. MonadParsec e s f => f a -> f (Maybe a)
optcomp = f a -> f (Maybe a)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (f a -> f (Maybe a)) -> (f a -> f a) -> f a -> f (Maybe a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f a -> f a
forall a. f a -> f a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try
sepBy1' :: MonadParsec e s m => m a -> m sep -> m (NonEmpty a)
sepBy1' :: forall e s (m :: * -> *) a sep.
MonadParsec e s m =>
m a -> m sep -> m (NonEmpty a)
sepBy1' m a
p m sep
sep = [a] -> NonEmpty a
forall a. HasCallStack => [a] -> NonEmpty a
NE.fromList ([a] -> NonEmpty a) -> m [a] -> m (NonEmpty a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m [a]
go
where
go :: m [a]
go = (a -> [a] -> [a]) -> m a -> m [a] -> m [a]
forall a b c. (a -> b -> c) -> m a -> m b -> m c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (:) m a
p (m a -> m [a]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many (m a -> m a
forall a. m a -> m a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (m a -> m a) -> m a -> m a
forall a b. (a -> b) -> a -> b
$ m sep
sep m sep -> m a -> m a
forall a b. m a -> m b -> m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> m a
p))