{-# Language FlexibleContexts, FlexibleInstances, NoFieldSelectors, OverloadedStrings,
Rank2Types, RecordWildCards, ScopedTypeVariables,
TemplateHaskell, TupleSections, TypeOperators, TypeSynonymInstances #-}
module Language.Haskell.Grammar (Parser,
HaskellGrammar(..), ModuleLevelGrammar(..), DeclarationGrammar(..),
grammar, grammar2010,
keyword, delimiter, terminator, moduleLexeme, moduleId, nameQualifier, nameToken,
constructorSymbolLexeme, variableSymbolLexeme,
whiteSpace, comment,
reservedWords,
isLineChar, isNameTailChar, isSymbol,
blockOf, blockWith, blockTerminatorKeyword, oneExtendedLine, verifyStatements,
OutlineMonoid(currentColumn), inputColumn,
NodeWrap, storeToken, wrap, rewrap, unwrap,
expressionToStatement, startSepEndBy) where
import Control.Applicative
import Control.Monad (void)
import qualified Data.Char as Char
import Data.Either (lefts, isLeft, partitionEithers)
import Data.Foldable (toList)
import Data.Functor.Compose (Compose(Compose))
import Data.Functor.Identity (Identity)
import Data.List.NonEmpty (NonEmpty((:|)))
import Data.Ord (Down)
import qualified Data.Monoid.Factorial as Factorial
import qualified Data.Monoid.Textual as Textual
import Data.Monoid.Null (null)
import Data.Monoid.Textual (TextualMonoid, characterPrefix, toString)
import Data.Monoid.Instances.Positioned (LinePositioned, column)
import Data.Monoid.Instances.PrefixMemory (Shadowed (content, prefix))
import qualified Data.Set as Set
import qualified Data.Text as Text
import Data.Text (Text)
import Numeric (readOct, readDec, readHex, readFloat)
import Witherable (filter, mapMaybe)
import qualified Text.Grampa
import Text.Grampa hiding (keyword)
import Text.Grampa.Combinators (moptional, someNonEmpty)
import Text.Grampa.ContextFree.SortedMemoizing.Transformer.LeftRecursive (ParserT, autochain, lift, tmap)
import qualified Text.Parser.Char
import Text.Parser.Combinators (eof, sepBy, sepBy1, sepByNonEmpty, sepEndBy, try)
import Text.Parser.Token (braces, brackets, comma, parens)
import qualified Rank2
import qualified Rank2.TH
import qualified Transformation.Deep as Deep
import qualified Transformation.Rank2
import qualified Language.Haskell.Abstract as Abstract
import qualified Language.Haskell.Reserializer as Reserializer
import Language.Haskell.Reserializer (ParsedLexemes(..), Lexeme(..), Serialization, TokenType(..), lexemes)
import Prelude hiding (exponent, filter, null)
type Parser g s = ParserT ((,) [[Lexeme s]]) g s
data HaskellGrammar l t f p = HaskellGrammar {
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (f (Module l l f f))
haskellModule :: p (f (Abstract.Module l l f f)),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> ModuleLevelGrammar l f p
moduleLevel :: ModuleLevelGrammar l f p,
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> DeclarationGrammar l f p
declarationLevel :: DeclarationGrammar l f p,
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p
-> p ([f (Import l l f f)], [f (Declaration l l f f)])
body :: p ([f (Abstract.Import l l f f)], [f (Abstract.Declaration l l f f)]),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Type l l f f)
typeTerm, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Type l l f f)
bType, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Type l l f f)
aType :: p (Abstract.Type l l f f),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Type l l f f)
generalTypeConstructor :: p (Abstract.Type l l f f),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (EquationRHS l l f f)
rhs :: p (Abstract.EquationRHS l l f f),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (NonEmpty (f (Statement l l f f)))
guards, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (NonEmpty (f (Statement l l f f)))
qualifiers :: p (NonEmpty (f (Abstract.Statement l l f f))),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Statement l l f f)
guard, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Statement l l f f)
qualifier :: p (Abstract.Statement l l f f),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (f (Expression l l f f))
expression, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (f (Expression l l f f))
infixExpression, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (f (Expression l l f f))
leftInfixExpression :: p (f (Abstract.Expression l l f f)),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (f (Expression l l f f))
lExpression, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (f (Expression l l f f))
dExpression, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (f (Expression l l f f))
fExpression, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (f (Expression l l f f))
aExpression :: p (f (Abstract.Expression l l f f)),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Expression l l f f)
bareExpression, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Expression l l f f)
openBlockExpression, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Expression l l f f)
closedBlockExpression :: p (Abstract.Expression l l f f),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Expression l l f f)
prefixNegation :: p (Abstract.Expression l l f f),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p [f (CaseAlternative l l f f)]
alternatives :: p [f (Abstract.CaseAlternative l l f f)],
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (CaseAlternative l l f f)
alternative :: p (Abstract.CaseAlternative l l f f),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (GuardedExpression l l f f)
statements :: p (Abstract.GuardedExpression l l f f),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p
-> p (f (Sum (Statement l l) (Expression l l) f f))
statement :: p (f (Deep.Sum (Abstract.Statement l l) (Abstract.Expression l l) f f)),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (FieldBinding l l f f)
fieldBinding :: p (Abstract.FieldBinding l l f f),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Pattern l l f f)
pattern, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Pattern l l f f)
lPattern, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Pattern l l f f)
aPattern, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Pattern l l f f)
pPattern :: p (Abstract.Pattern l l f f),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (FieldPattern l l f f)
fieldPattern :: p (Abstract.FieldPattern l l f f),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Constructor l l f f)
generalConstructor :: p (Abstract.Constructor l l f f),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
variable, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
constructor, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
variableOperator, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
constructorOperator, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
operator :: p (Abstract.Name l),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedVariable, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedConstructor :: p (Abstract.QualifiedName l),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedVariableOperator, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedConstructorOperator, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedOperator :: p (Abstract.QualifiedName l),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedConstructorIdentifier, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedConstructorSymbol, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedTypeConstructor,
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedVariableIdentifier, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedVariableSymbol :: p (Abstract.QualifiedName l),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
constructorIdentifier, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
constructorSymbol,
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
typeConstructor, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
typeVar, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
variableIdentifier, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
variableSymbol :: p (Abstract.Name l),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Value l l f f)
literal, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Value l l f f)
literalLexeme :: p (Abstract.Value l l f f),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p ()
doubleColon, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p ()
rightDoubleArrow, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p ()
rightArrow, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p ()
leftArrow :: p (),
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p Integer
integer, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p Integer
integerLexeme :: p Integer,
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p Rational
float, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p Rational
floatLexeme :: p Rational,
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p t
decimal, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p t
octal, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p t
hexadecimal, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p t
exponent :: p t,
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p Char
charLiteral, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p Char
charLexeme, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p Char
escape :: p Char,
forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p Text
stringLiteral, forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p Text
stringLexeme :: p Text
}
data ModuleLevelGrammar l f p = ModuleLevelGrammar {
forall l (f :: * -> *) (p :: * -> *).
ModuleLevelGrammar l f p -> p [f (Export l l f f)]
exports :: p [f (Abstract.Export l l f f)],
forall l (f :: * -> *) (p :: * -> *).
ModuleLevelGrammar l f p -> p (Export l l f f)
export :: p (Abstract.Export l l f f),
forall l (f :: * -> *) (p :: * -> *).
ModuleLevelGrammar l f p -> p (Import l l f f)
importDeclaration :: p (Abstract.Import l l f f),
forall l (f :: * -> *) (p :: * -> *).
ModuleLevelGrammar l f p -> p (ImportSpecification l l f f)
importSpecification :: p (Abstract.ImportSpecification l l f f),
forall l (f :: * -> *) (p :: * -> *).
ModuleLevelGrammar l f p -> p (ImportItem l l f f)
importItem :: p (Abstract.ImportItem l l f f),
forall l (f :: * -> *) (p :: * -> *).
ModuleLevelGrammar l f p -> p (Members l)
members :: p (Abstract.Members l),
forall l (f :: * -> *) (p :: * -> *).
ModuleLevelGrammar l f p -> p (Name l)
cname :: p (Abstract.Name l)
}
data DeclarationGrammar l f p = DeclarationGrammar {
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Declaration l l f f)
topLevelDeclaration :: p (Abstract.Declaration l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p [f (Declaration l l f f)]
declarations :: p [f (Abstract.Declaration l l f f)],
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Declaration l l f f)
declaration :: p (Abstract.Declaration l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Declaration l l f f)
inClassDeclaration :: p (Abstract.Declaration l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Declaration l l f f)
inInstanceDeclaration :: p (Abstract.Declaration l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Declaration l l f f)
equationDeclaration :: p (Abstract.Declaration l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Declaration l l f f)
generalDeclaration :: p (Abstract.Declaration l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p [f (Declaration l l f f)]
whereClauses :: p [f (Abstract.Declaration l l f f)],
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (NonEmpty (Name l))
variables :: p (NonEmpty (Abstract.Name l)),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Associativity l)
fixity :: p (Abstract.Associativity l),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p [f (DataConstructor l l f f)]
declaredConstructors :: p [f (Abstract.DataConstructor l l f f)],
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (DataConstructor l l f f)
declaredConstructor :: p (Abstract.DataConstructor l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Type l l f f)
infixConstructorArgType :: p (Abstract.Type l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Type l l f f)
strictType :: p (Abstract.Type l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (DataConstructor l l f f)
newConstructor :: p (Abstract.DataConstructor l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (FieldDeclaration l l f f)
fieldDeclaration :: p (Abstract.FieldDeclaration l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Context l l f f)
optionalContext, forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Context l l f f)
optionalTypeSignatureContext, forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Context l l f f)
context, forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Context l l f f)
constraint :: p (Abstract.Context l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Type l l f f)
typeApplications :: p (Abstract.Type l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (TypeLHS l l f f)
simpleType :: p (Abstract.TypeLHS l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (TypeLHS l l f f)
classLHS :: p (Abstract.TypeLHS l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p [f (DerivingClause l l f f)]
derivingClause :: p [f (Abstract.DerivingClause l l f f)],
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (ClassInstanceLHS l l f f)
instanceDesignator :: p (Abstract.ClassInstanceLHS l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Type l l f f)
instanceTypeDesignator :: p (Abstract.Type l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Type l l f f)
typeVarApplications :: p (Abstract.Type l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (NonEmpty (f (Type l l f f)))
typeVarTuple :: p (NonEmpty (f (Abstract.Type l l f f))),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Declaration l l f f)
foreignDeclaration :: p (Abstract.Declaration l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (CallingConvention l)
callingConvention :: p (Abstract.CallingConvention l),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (CallSafety l)
safety :: p (Abstract.CallSafety l),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Type l l f f)
foreignType :: p (Abstract.Type l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Type l l f f)
foreignReturnType :: p (Abstract.Type l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Type l l f f)
foreignArgType :: p (Abstract.Type l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (EquationLHS l l f f)
functionLHS :: p (Abstract.EquationLHS l l f f),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (QualifiedName l)
qualifiedTypeClass :: p (Abstract.QualifiedName l),
forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Name l)
typeClass :: p (Abstract.Name l)
}
$(Rank2.TH.deriveAll ''HaskellGrammar)
$(Rank2.TH.deriveAll ''ModuleLevelGrammar)
$(Rank2.TH.deriveAll ''DeclarationGrammar)
grammar2010 :: (Abstract.Haskell l,
Ord t, Show t, OutlineMonoid t,
Deep.Foldable (Serialization (Down Int) t) (Abstract.CaseAlternative l l),
Deep.Foldable (Serialization (Down Int) t) (Abstract.Declaration l l),
Deep.Foldable (Serialization (Down Int) t) (Abstract.Expression l l),
Deep.Foldable (Serialization (Down Int) t) (Abstract.Import l l),
Deep.Foldable (Serialization (Down Int) t) (Abstract.Statement l l))
=> Grammar (HaskellGrammar l t (NodeWrap t)) (ParserT ((,) [[Lexeme t]])) t
grammar2010 :: forall l t.
(Haskell l, Ord t, Show t, OutlineMonoid t,
Foldable (Serialization (Down Int) t) (CaseAlternative l l),
Foldable (Serialization (Down Int) t) (Declaration l l),
Foldable (Serialization (Down Int) t) (Expression l l),
Foldable (Serialization (Down Int) t) (Import l l),
Foldable (Serialization (Down Int) t) (Statement l l)) =>
Grammar
(HaskellGrammar l t (NodeWrap t)) (ParserT ((,) [[Lexeme t]])) t
grammar2010 = HaskellGrammar
l
t
(NodeWrap t)
(Fixed
(ParserT ((,) [[Lexeme t]])) (HaskellGrammar l t (NodeWrap t)) t)
-> HaskellGrammar
l
t
(NodeWrap t)
(Fixed
(ParserT ((,) [[Lexeme t]])) (HaskellGrammar l t (NodeWrap t)) t)
forall (p :: ((* -> *) -> *) -> * -> * -> *) (g :: (* -> *) -> *) s
(f :: * -> *) (rl :: * -> * -> *) (cb :: * -> *).
(cb ~ Const (g (Const Bool)), f ~ GrammarFunctor (p g s), f ~ rl s,
LeftRecParsing p g s rl, DeterministicParsing (p g s), Apply g,
Traversable g, Distributive g, Logistic g) =>
g (Fixed p g s) -> g (Fixed p g s)
autochain (HaskellGrammar
l
t
(NodeWrap t)
(Fixed
(ParserT ((,) [[Lexeme t]])) (HaskellGrammar l t (NodeWrap t)) t)
-> HaskellGrammar
l
t
(NodeWrap t)
(Fixed
(ParserT ((,) [[Lexeme t]])) (HaskellGrammar l t (NodeWrap t)) t))
-> HaskellGrammar
l
t
(NodeWrap t)
(Fixed
(ParserT ((,) [[Lexeme t]])) (HaskellGrammar l t (NodeWrap t)) t)
-> HaskellGrammar
l
t
(NodeWrap t)
(Fixed
(ParserT ((,) [[Lexeme t]])) (HaskellGrammar l t (NodeWrap t)) t)
forall a b. (a -> b) -> a -> b
$ (HaskellGrammar
l
t
(NodeWrap t)
(Fixed
(ParserT ((,) [[Lexeme t]])) (HaskellGrammar l t (NodeWrap t)) t)
-> HaskellGrammar
l
t
(NodeWrap t)
(Fixed
(ParserT ((,) [[Lexeme t]])) (HaskellGrammar l t (NodeWrap t)) t))
-> HaskellGrammar
l
t
(NodeWrap t)
(Fixed
(ParserT ((,) [[Lexeme t]])) (HaskellGrammar l t (NodeWrap t)) t)
forall (m :: * -> *) (g :: (* -> *) -> *).
(GrammarParsing m, g ~ ParserGrammar m, GrammarConstraint m g,
Distributive g) =>
(g m -> g m) -> g m
forall (g :: (* -> *) -> *).
(g
~ ParserGrammar
(Fixed
(ParserT ((,) [[Lexeme t]])) (HaskellGrammar l t (NodeWrap t)) t),
GrammarConstraint
(Fixed
(ParserT ((,) [[Lexeme t]])) (HaskellGrammar l t (NodeWrap t)) t)
g,
Distributive g) =>
(g (Fixed
(ParserT ((,) [[Lexeme t]])) (HaskellGrammar l t (NodeWrap t)) t)
-> g (Fixed
(ParserT ((,) [[Lexeme t]])) (HaskellGrammar l t (NodeWrap t)) t))
-> g (Fixed
(ParserT ((,) [[Lexeme t]])) (HaskellGrammar l t (NodeWrap t)) t)
fixGrammar HaskellGrammar
l
t
(NodeWrap t)
(Fixed
(ParserT ((,) [[Lexeme t]])) (HaskellGrammar l t (NodeWrap t)) t)
-> HaskellGrammar
l
t
(NodeWrap t)
(Fixed
(ParserT ((,) [[Lexeme t]])) (HaskellGrammar l t (NodeWrap t)) t)
forall l (g :: (* -> *) -> *) t.
(Apply g, Haskell l, Ord t, Show t, OutlineMonoid t,
Foldable (Serialization (Down Int) t) (CaseAlternative l l),
Foldable (Serialization (Down Int) t) (Declaration l l),
Foldable (Serialization (Down Int) t) (Expression l l),
Foldable (Serialization (Down Int) t) (Import l l),
Foldable (Serialization (Down Int) t) (Statement l l)) =>
GrammarBuilder
(HaskellGrammar l t (NodeWrap t)) g (ParserT ((,) [[Lexeme t]])) t
grammar
grammar :: forall l g t. (Rank2.Apply g, Abstract.Haskell l, Ord t, Show t, OutlineMonoid t,
Deep.Foldable (Serialization (Down Int) t) (Abstract.CaseAlternative l l),
Deep.Foldable (Serialization (Down Int) t) (Abstract.Declaration l l),
Deep.Foldable (Serialization (Down Int) t) (Abstract.Expression l l),
Deep.Foldable (Serialization (Down Int) t) (Abstract.Import l l),
Deep.Foldable (Serialization (Down Int) t) (Abstract.Statement l l))
=> GrammarBuilder (HaskellGrammar l t (NodeWrap t)) g (ParserT ((,) [[Lexeme t]])) t
grammar :: forall l (g :: (* -> *) -> *) t.
(Apply g, Haskell l, Ord t, Show t, OutlineMonoid t,
Foldable (Serialization (Down Int) t) (CaseAlternative l l),
Foldable (Serialization (Down Int) t) (Declaration l l),
Foldable (Serialization (Down Int) t) (Expression l l),
Foldable (Serialization (Down Int) t) (Import l l),
Foldable (Serialization (Down Int) t) (Statement l l)) =>
GrammarBuilder
(HaskellGrammar l t (NodeWrap t)) g (ParserT ((,) [[Lexeme t]])) t
grammar HaskellGrammar{moduleLevel :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> ModuleLevelGrammar l f p
moduleLevel= ModuleLevelGrammar{ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
ParserT
((,) [[Lexeme t]])
g
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT ((,) [[Lexeme t]]) g t (Members l)
ParserT ((,) [[Lexeme t]]) g t (Name l)
exports :: forall l (f :: * -> *) (p :: * -> *).
ModuleLevelGrammar l f p -> p [f (Export l l f f)]
export :: forall l (f :: * -> *) (p :: * -> *).
ModuleLevelGrammar l f p -> p (Export l l f f)
importDeclaration :: forall l (f :: * -> *) (p :: * -> *).
ModuleLevelGrammar l f p -> p (Import l l f f)
importSpecification :: forall l (f :: * -> *) (p :: * -> *).
ModuleLevelGrammar l f p -> p (ImportSpecification l l f f)
importItem :: forall l (f :: * -> *) (p :: * -> *).
ModuleLevelGrammar l f p -> p (ImportItem l l f f)
members :: forall l (f :: * -> *) (p :: * -> *).
ModuleLevelGrammar l f p -> p (Members l)
cname :: forall l (f :: * -> *) (p :: * -> *).
ModuleLevelGrammar l f p -> p (Name l)
exports :: ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
export :: ParserT
((,) [[Lexeme t]])
g
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
importDeclaration :: ParserT
((,) [[Lexeme t]])
g
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
importSpecification :: ParserT
((,) [[Lexeme t]])
g
t
(ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
importItem :: ParserT
((,) [[Lexeme t]])
g
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
members :: ParserT ((,) [[Lexeme t]]) g t (Members l)
cname :: ParserT ((,) [[Lexeme t]]) g t (Name l)
..},
declarationLevel :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> DeclarationGrammar l f p
declarationLevel= DeclarationGrammar{ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
ParserT ((,) [[Lexeme t]]) g t (NonEmpty (Name l))
ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(ClassInstanceLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
ParserT ((,) [[Lexeme t]]) g t (CallSafety l)
ParserT ((,) [[Lexeme t]]) g t (Associativity l)
ParserT ((,) [[Lexeme t]]) g t (Name l)
ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
topLevelDeclaration :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Declaration l l f f)
declarations :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p [f (Declaration l l f f)]
declaration :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Declaration l l f f)
inClassDeclaration :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Declaration l l f f)
inInstanceDeclaration :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Declaration l l f f)
equationDeclaration :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Declaration l l f f)
generalDeclaration :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Declaration l l f f)
whereClauses :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p [f (Declaration l l f f)]
variables :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (NonEmpty (Name l))
fixity :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Associativity l)
declaredConstructors :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p [f (DataConstructor l l f f)]
declaredConstructor :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (DataConstructor l l f f)
infixConstructorArgType :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Type l l f f)
strictType :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Type l l f f)
newConstructor :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (DataConstructor l l f f)
fieldDeclaration :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (FieldDeclaration l l f f)
optionalContext :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Context l l f f)
optionalTypeSignatureContext :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Context l l f f)
context :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Context l l f f)
constraint :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Context l l f f)
typeApplications :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Type l l f f)
simpleType :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (TypeLHS l l f f)
classLHS :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (TypeLHS l l f f)
derivingClause :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p [f (DerivingClause l l f f)]
instanceDesignator :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (ClassInstanceLHS l l f f)
instanceTypeDesignator :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Type l l f f)
typeVarApplications :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Type l l f f)
typeVarTuple :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (NonEmpty (f (Type l l f f)))
foreignDeclaration :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Declaration l l f f)
callingConvention :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (CallingConvention l)
safety :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (CallSafety l)
foreignType :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Type l l f f)
foreignReturnType :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Type l l f f)
foreignArgType :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Type l l f f)
functionLHS :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (EquationLHS l l f f)
qualifiedTypeClass :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (QualifiedName l)
typeClass :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Name l)
topLevelDeclaration :: ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
declarations :: ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
declaration :: ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
inClassDeclaration :: ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
inInstanceDeclaration :: ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
equationDeclaration :: ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
generalDeclaration :: ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
whereClauses :: ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
variables :: ParserT ((,) [[Lexeme t]]) g t (NonEmpty (Name l))
fixity :: ParserT ((,) [[Lexeme t]]) g t (Associativity l)
declaredConstructors :: ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
declaredConstructor :: ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
infixConstructorArgType :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
strictType :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
newConstructor :: ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
fieldDeclaration :: ParserT
((,) [[Lexeme t]])
g
t
(FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
optionalContext :: ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
optionalTypeSignatureContext :: ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
context :: ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
constraint :: ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeApplications :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
simpleType :: ParserT
((,) [[Lexeme t]])
g
t
(TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
classLHS :: ParserT
((,) [[Lexeme t]])
g
t
(TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
derivingClause :: ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
instanceDesignator :: ParserT
((,) [[Lexeme t]])
g
t
(ClassInstanceLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
instanceTypeDesignator :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeVarApplications :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeVarTuple :: ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
foreignDeclaration :: ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
callingConvention :: ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
safety :: ParserT ((,) [[Lexeme t]]) g t (CallSafety l)
foreignType :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
foreignReturnType :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
foreignArgType :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
functionLHS :: ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
qualifiedTypeClass :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
typeClass :: ParserT ((,) [[Lexeme t]]) g t (Name l)
..},
Fixed (ParserT ((,) [[Lexeme t]])) g t t
ParserT ((,) [[Lexeme t]]) g t Char
ParserT ((,) [[Lexeme t]]) g t Integer
ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
ParserT ((,) [[Lexeme t]]) g t Rational
ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
ParserT ((,) [[Lexeme t]]) g t ()
ParserT
((,) [[Lexeme t]])
g
t
([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))],
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
ParserT ((,) [[Lexeme t]]) g t Text
ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
ParserT ((,) [[Lexeme t]]) g t (Name l)
ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
haskellModule :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (f (Module l l f f))
body :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p
-> p ([f (Import l l f f)], [f (Declaration l l f f)])
typeTerm :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Type l l f f)
bType :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Type l l f f)
aType :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Type l l f f)
generalTypeConstructor :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Type l l f f)
rhs :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (EquationRHS l l f f)
guards :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (NonEmpty (f (Statement l l f f)))
qualifiers :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (NonEmpty (f (Statement l l f f)))
guard :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Statement l l f f)
qualifier :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Statement l l f f)
expression :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (f (Expression l l f f))
infixExpression :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (f (Expression l l f f))
leftInfixExpression :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (f (Expression l l f f))
lExpression :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (f (Expression l l f f))
dExpression :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (f (Expression l l f f))
fExpression :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (f (Expression l l f f))
aExpression :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (f (Expression l l f f))
bareExpression :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Expression l l f f)
openBlockExpression :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Expression l l f f)
closedBlockExpression :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Expression l l f f)
prefixNegation :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Expression l l f f)
alternatives :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p [f (CaseAlternative l l f f)]
alternative :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (CaseAlternative l l f f)
statements :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (GuardedExpression l l f f)
statement :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p
-> p (f (Sum (Statement l l) (Expression l l) f f))
fieldBinding :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (FieldBinding l l f f)
pattern :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Pattern l l f f)
lPattern :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Pattern l l f f)
aPattern :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Pattern l l f f)
pPattern :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Pattern l l f f)
fieldPattern :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (FieldPattern l l f f)
generalConstructor :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Constructor l l f f)
variable :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
constructor :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
variableOperator :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
constructorOperator :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
operator :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
qualifiedVariable :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedConstructor :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedVariableOperator :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedConstructorOperator :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedOperator :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedConstructorIdentifier :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedConstructorSymbol :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedTypeConstructor :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedVariableIdentifier :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
qualifiedVariableSymbol :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (QualifiedName l)
constructorIdentifier :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
constructorSymbol :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
typeConstructor :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
typeVar :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
variableIdentifier :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
variableSymbol :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Name l)
literal :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Value l l f f)
literalLexeme :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (Value l l f f)
doubleColon :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p ()
rightDoubleArrow :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p ()
rightArrow :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p ()
leftArrow :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p ()
integer :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p Integer
integerLexeme :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p Integer
float :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p Rational
floatLexeme :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p Rational
decimal :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p t
octal :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p t
hexadecimal :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p t
exponent :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p t
charLiteral :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p Char
charLexeme :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p Char
escape :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p Char
stringLiteral :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p Text
stringLexeme :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p Text
haskellModule :: ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
body :: ParserT
((,) [[Lexeme t]])
g
t
([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))],
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
typeTerm :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
bType :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
aType :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
generalTypeConstructor :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
rhs :: ParserT
((,) [[Lexeme t]])
g
t
(EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
guards :: ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
qualifiers :: ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
guard :: ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
qualifier :: ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
expression :: ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
infixExpression :: ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
leftInfixExpression :: ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
lExpression :: ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
dExpression :: ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
fExpression :: ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
aExpression :: ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
bareExpression :: ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
openBlockExpression :: ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
closedBlockExpression :: ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
prefixNegation :: ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
alternatives :: ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
alternative :: ParserT
((,) [[Lexeme t]])
g
t
(CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
statements :: ParserT
((,) [[Lexeme t]])
g
t
(GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
statement :: ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
fieldBinding :: ParserT
((,) [[Lexeme t]])
g
t
(FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
pattern :: ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
lPattern :: ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
aPattern :: ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
pPattern :: ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
fieldPattern :: ParserT
((,) [[Lexeme t]])
g
t
(FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
generalConstructor :: ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
variable :: ParserT ((,) [[Lexeme t]]) g t (Name l)
constructor :: ParserT ((,) [[Lexeme t]]) g t (Name l)
variableOperator :: ParserT ((,) [[Lexeme t]]) g t (Name l)
constructorOperator :: ParserT ((,) [[Lexeme t]]) g t (Name l)
operator :: ParserT ((,) [[Lexeme t]]) g t (Name l)
qualifiedVariable :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructor :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedVariableOperator :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructorOperator :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedOperator :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructorIdentifier :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructorSymbol :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedTypeConstructor :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedVariableIdentifier :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedVariableSymbol :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
constructorIdentifier :: ParserT ((,) [[Lexeme t]]) g t (Name l)
constructorSymbol :: ParserT ((,) [[Lexeme t]]) g t (Name l)
typeConstructor :: ParserT ((,) [[Lexeme t]]) g t (Name l)
typeVar :: ParserT ((,) [[Lexeme t]]) g t (Name l)
variableIdentifier :: ParserT ((,) [[Lexeme t]]) g t (Name l)
variableSymbol :: ParserT ((,) [[Lexeme t]]) g t (Name l)
literal :: ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
literalLexeme :: ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
doubleColon :: ParserT ((,) [[Lexeme t]]) g t ()
rightDoubleArrow :: ParserT ((,) [[Lexeme t]]) g t ()
rightArrow :: ParserT ((,) [[Lexeme t]]) g t ()
leftArrow :: ParserT ((,) [[Lexeme t]]) g t ()
integer :: ParserT ((,) [[Lexeme t]]) g t Integer
integerLexeme :: ParserT ((,) [[Lexeme t]]) g t Integer
float :: ParserT ((,) [[Lexeme t]]) g t Rational
floatLexeme :: ParserT ((,) [[Lexeme t]]) g t Rational
decimal :: Fixed (ParserT ((,) [[Lexeme t]])) g t t
octal :: Fixed (ParserT ((,) [[Lexeme t]])) g t t
hexadecimal :: Fixed (ParserT ((,) [[Lexeme t]])) g t t
exponent :: Fixed (ParserT ((,) [[Lexeme t]])) g t t
charLiteral :: ParserT ((,) [[Lexeme t]]) g t Char
charLexeme :: ParserT ((,) [[Lexeme t]]) g t Char
escape :: ParserT ((,) [[Lexeme t]]) g t Char
stringLiteral :: ParserT ((,) [[Lexeme t]]) g t Text
stringLexeme :: ParserT ((,) [[Lexeme t]]) g t Text
..} = HaskellGrammar{
haskellModule :: ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
haskellModule = Parser
g
t
(Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe Char)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Char -> ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
utf8bom) Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe Char)
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t ()
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t ()
whiteSpace
ParserT ((,) [[Lexeme t]]) g t ()
-> Parser
g
t
(Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
(Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))],
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))],
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))],
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ModuleName l
-> Maybe
[NodeWrap
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
ModuleName λ
-> Maybe [s (Export l l d d)]
-> [s (Import l l d d)]
-> [s (Declaration l l d d)]
-> Module λ l d s
forall (s :: * -> *) l (d :: * -> *).
ModuleName l
-> Maybe [s (Export l l d d)]
-> [s (Import l l d d)]
-> [s (Declaration l l d d)]
-> Module l l d s
Abstract.namedModule (ModuleName l
-> Maybe
[NodeWrap
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ModuleName l
-> Maybe
[NodeWrap
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"module" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ModuleName l
-> Maybe
[NodeWrap
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe
[NodeWrap
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
forall (g :: (* -> *) -> *) l t.
(Apply g, Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t (ModuleName l)
moduleId
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe
[NodeWrap
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe
[NodeWrap
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe
[NodeWrap
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
exports Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"where"
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
[s (Import l l d d)] -> [s (Declaration l l d d)] -> Module λ l d s
forall (s :: * -> *) l (d :: * -> *).
[s (Import l l d d)] -> [s (Declaration l l d d)] -> Module l l d s
Abstract.anonymousModule)
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))],
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
-> Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))],
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
-> Parser
g
t
(Module
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))],
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
body)),
body :: ParserT
((,) [[Lexeme t]])
g
t
([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))],
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
body = let ordered :: [(a, Sum g h d s)] -> Maybe ([(a, g d s)], [(a, h d s)])
ordered [(a, Sum g h d s)]
impdecs
| [(a, g d s)] -> Bool
forall m. MonoidNull m => m -> Bool
null [(a, g d s)]
rightImports = ([(a, g d s)], [(a, h d s)]) -> Maybe ([(a, g d s)], [(a, h d s)])
forall a. a -> Maybe a
Just ([(a, g d s)]
leftImports, [(a, h d s)]
rightDeclarations)
| Bool
otherwise = Maybe ([(a, g d s)], [(a, h d s)])
forall a. Maybe a
Nothing
where ([Either (a, g d s) (a, h d s)]
prefix, [Either (a, g d s) (a, h d s)]
rest) = (Either (a, g d s) (a, h d s) -> Bool)
-> [Either (a, g d s) (a, h d s)]
-> ([Either (a, g d s) (a, h d s)], [Either (a, g d s) (a, h d s)])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span Either (a, g d s) (a, h d s) -> Bool
forall a b. Either a b -> Bool
isLeft ((a, Sum g h d s) -> Either (a, g d s) (a, h d s)
forall {a} {g :: (* -> *) -> (* -> *) -> *}
{h :: (* -> *) -> (* -> *) -> *} {d :: * -> *} {s :: * -> *}.
(a, Sum g h d s) -> Either (a, g d s) (a, h d s)
expose ((a, Sum g h d s) -> Either (a, g d s) (a, h d s))
-> [(a, Sum g h d s)] -> [Either (a, g d s) (a, h d s)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(a, Sum g h d s)]
impdecs)
leftImports :: [(a, g d s)]
leftImports = [Either (a, g d s) (a, h d s)] -> [(a, g d s)]
forall a b. [Either a b] -> [a]
lefts [Either (a, g d s) (a, h d s)]
prefix
([(a, g d s)]
rightImports, [(a, h d s)]
rightDeclarations) = [Either (a, g d s) (a, h d s)] -> ([(a, g d s)], [(a, h d s)])
forall a b. [Either a b] -> ([a], [b])
partitionEithers [Either (a, g d s) (a, h d s)]
rest
expose :: (a, Sum g h d s) -> Either (a, g d s) (a, h d s)
expose (a
w, Deep.InL g d s
imp) = (a, g d s) -> Either (a, g d s) (a, h d s)
forall a b. a -> Either a b
Left (a
w, g d s
imp)
expose (a
w, Deep.InR h d s
dec) = (a, h d s) -> Either (a, g d s) (a, h d s)
forall a b. b -> Either a b
Right (a
w, h d s
dec)
in ([((Down Int, ParsedLexemes t, Down Int),
Sum
(Import l l)
(Declaration l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Maybe
([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))],
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Sum
(Import l l)
(Declaration l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))],
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
forall a b.
(a -> Maybe b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe [((Down Int, ParsedLexemes t, Down Int),
Sum
(Import l l)
(Declaration l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Maybe
([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))],
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
forall {a} {g :: (* -> *) -> (* -> *) -> *}
{h :: (* -> *) -> (* -> *) -> *} {d :: * -> *} {s :: * -> *}.
[(a, Sum g h d s)] -> Maybe ([(a, g d s)], [(a, h d s)])
ordered (Parser
g
t
((Down Int, ParsedLexemes t, Down Int),
Sum
(Import l l)
(Declaration l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Sum
(Import l l)
(Declaration l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (g :: (* -> *) -> *) t (node :: (* -> *) -> (* -> *) -> *).
(Apply g, Ord t, Show t, OutlineMonoid t,
Foldable (Serialization (Down Int) t) node) =>
Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Parser g t [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
blockOf (Parser
g
t
(Sum
(Import l l)
(Declaration l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
((Down Int, ParsedLexemes t, Down Int),
Sum
(Import l l)
(Declaration l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> Sum
(Import l l)
(Declaration l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall (g :: (* -> *) -> (* -> *) -> *)
(h :: (* -> *) -> (* -> *) -> *) (d :: * -> *) (s :: * -> *).
g d s -> Sum g h d s
Deep.InL (Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> Sum
(Import l l)
(Declaration l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
(Sum
(Import l l)
(Declaration l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
importDeclaration Parser
g
t
(Sum
(Import l l)
(Declaration l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
(Sum
(Import l l)
(Declaration l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
(Sum
(Import l l)
(Declaration l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> Sum
(Import l l)
(Declaration l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall (g :: (* -> *) -> (* -> *) -> *)
(h :: (* -> *) -> (* -> *) -> *) (d :: * -> *) (s :: * -> *).
h d s -> Sum g h d s
Deep.InR (Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> Sum
(Import l l)
(Declaration l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
(Sum
(Import l l)
(Declaration l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
topLevelDeclaration)))
ParserT
((,) [[Lexeme t]])
g
t
([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))],
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
-> [Char]
-> ParserT
((,) [[Lexeme t]])
g
t
([NodeWrap
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))],
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> [Char] -> m a
<?> [Char]
"imports followed by declarations",
moduleLevel :: ModuleLevelGrammar
l
((,) (Down Int, ParsedLexemes t, Down Int))
(Fixed (ParserT ((,) [[Lexeme t]])) g t)
moduleLevel= ModuleLevelGrammar{
exports :: ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
exports = ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens (ParserT
((,) [[Lexeme t]])
g
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
(NodeWrap
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
export Parser
g
t
(NodeWrap
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
`sepEndBy` ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma),
export :: ParserT
((,) [[Lexeme t]])
g
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
export = QualifiedName l
-> Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
QualifiedName λ -> Export λ l d s
forall l (d :: * -> *) (s :: * -> *).
QualifiedName l -> Export l l d s
Abstract.exportVar (QualifiedName l
-> Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedVariable
ParserT
((,) [[Lexeme t]])
g
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> QualifiedName l
-> Maybe (Members l)
-> Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
QualifiedName λ -> Maybe (Members λ) -> Export λ l d s
forall l (d :: * -> *) (s :: * -> *).
QualifiedName l -> Maybe (Members l) -> Export l l d s
Abstract.exportClassOrType (QualifiedName l
-> Maybe (Members l)
-> Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe (Members l)
-> Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedTypeConstructor Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe (Members l)
-> Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe (Members l))
-> ParserT
((,) [[Lexeme t]])
g
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t (Members l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe (Members l))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParserT ((,) [[Lexeme t]]) g t (Members l)
members
ParserT
((,) [[Lexeme t]])
g
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ModuleName l
-> Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
ModuleName λ -> Export λ l d s
forall l (d :: * -> *) (s :: * -> *).
ModuleName l -> Export l l d s
Abstract.reExportModule (ModuleName l
-> Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ModuleName l
-> Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"module" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ModuleName l
-> Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Export
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
forall (g :: (* -> *) -> *) l t.
(Apply g, Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t (ModuleName l)
moduleId,
importDeclaration :: ParserT
((,) [[Lexeme t]])
g
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
importDeclaration = Bool
-> ModuleName l
-> Maybe (ModuleName l)
-> Maybe
((Down Int, ParsedLexemes t, Down Int),
ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
Bool
-> ModuleName λ
-> Maybe (ModuleName λ)
-> Maybe (s (ImportSpecification l l d d))
-> Import λ l d s
forall (s :: * -> *) l (d :: * -> *).
Bool
-> ModuleName l
-> Maybe (ModuleName l)
-> Maybe (s (ImportSpecification l l d d))
-> Import l l d s
Abstract.importDeclaration (Bool
-> ModuleName l
-> Maybe (ModuleName l)
-> Maybe
((Down Int, ParsedLexemes t, Down Int),
ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Bool
-> ModuleName l
-> Maybe (ModuleName l)
-> Maybe
((Down Int, ParsedLexemes t, Down Int),
ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"import"
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Bool
-> ModuleName l
-> Maybe (ModuleName l)
-> Maybe
((Down Int, ParsedLexemes t, Down Int),
ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Bool
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ModuleName l
-> Maybe (ModuleName l)
-> Maybe
((Down Int, ParsedLexemes t, Down Int),
ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Bool
True Bool
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Bool
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"qualified" Fixed (ParserT ((,) [[Lexeme t]])) g t Bool
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Bool
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Bool
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bool -> Fixed (ParserT ((,) [[Lexeme t]])) g t Bool
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False) Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ModuleName l
-> Maybe (ModuleName l)
-> Maybe
((Down Int, ParsedLexemes t, Down Int),
ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe (ModuleName l)
-> Maybe
((Down Int, ParsedLexemes t, Down Int),
ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
forall (g :: (* -> *) -> *) l t.
(Apply g, Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t (ModuleName l)
moduleId
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe (ModuleName l)
-> Maybe
((Down Int, ParsedLexemes t, Down Int),
ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe (ModuleName l))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe
((Down Int, ParsedLexemes t, Down Int),
ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe (ModuleName l))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"as" ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
forall (g :: (* -> *) -> *) l t.
(Apply g, Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t (ModuleName l)
moduleId) Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe
((Down Int, ParsedLexemes t, Down Int),
ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe
((Down Int, ParsedLexemes t, Down Int),
ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Import
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe
((Down Int, ParsedLexemes t, Down Int),
ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParserT
((,) [[Lexeme t]])
g
t
(ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
importSpecification),
importSpecification :: ParserT
((,) [[Lexeme t]])
g
t
(ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
importSpecification = (([NodeWrap
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [NodeWrap
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
[s (ImportItem l l d d)] -> ImportSpecification λ l d s
forall (s :: * -> *) l (d :: * -> *).
[s (ImportItem l l d d)] -> ImportSpecification l l d s
Abstract.includedImports Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [NodeWrap
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
[s (ImportItem l l d d)] -> ImportSpecification λ l d s
forall (s :: * -> *) l (d :: * -> *).
[s (ImportItem l l d d)] -> ImportSpecification l l d s
Abstract.excludedImports ([NodeWrap
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"hiding")
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(ImportSpecification
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens (ParserT
((,) [[Lexeme t]])
g
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
(NodeWrap
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
importItem Parser
g
t
(NodeWrap
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
`sepEndBy` ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma),
importItem :: ParserT
((,) [[Lexeme t]])
g
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
importItem = Name l
-> ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Name λ -> ImportItem λ l d s
forall l (d :: * -> *) (s :: * -> *). Name l -> ImportItem l l d s
Abstract.importVar (Name l
-> ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT
((,) [[Lexeme t]])
g
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
variable
ParserT
((,) [[Lexeme t]])
g
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Name l
-> Maybe (Members l)
-> ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Name λ -> Maybe (Members λ) -> ImportItem λ l d s
forall l (d :: * -> *) (s :: * -> *).
Name l -> Maybe (Members l) -> ImportItem l l d s
Abstract.importClassOrType (Name l
-> Maybe (Members l)
-> ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe (Members l)
-> ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
typeConstructor Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe (Members l)
-> ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe (Members l))
-> ParserT
((,) [[Lexeme t]])
g
t
(ImportItem
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t (Members l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe (Members l))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParserT ((,) [[Lexeme t]]) g t (Members l)
members,
members :: ParserT ((,) [[Lexeme t]]) g t (Members l)
members = ParserT ((,) [[Lexeme t]]) g t (Members l)
-> ParserT ((,) [[Lexeme t]]) g t (Members l)
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens (Members l
forall λ. Haskell λ => Members λ
Abstract.allMembers Members l
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (Members l)
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
".."
ParserT ((,) [[Lexeme t]]) g t (Members l)
-> ParserT ((,) [[Lexeme t]]) g t (Members l)
-> ParserT ((,) [[Lexeme t]]) g t (Members l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [Name l] -> Members l
forall λ. Haskell λ => [Name λ] -> Members λ
Abstract.memberList ([Name l] -> Members l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [Name l]
-> ParserT ((,) [[Lexeme t]]) g t (Members l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
cname ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [Name l]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
`sepEndBy` ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma),
cname :: ParserT ((,) [[Lexeme t]]) g t (Name l)
cname = ParserT ((,) [[Lexeme t]]) g t (Name l)
variable ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT ((,) [[Lexeme t]]) g t (Name l)
constructor},
declarationLevel :: DeclarationGrammar
l
((,) (Down Int, ParsedLexemes t, Down Int))
(Fixed (ParserT ((,) [[Lexeme t]])) g t)
declarationLevel= DeclarationGrammar{
topLevelDeclaration :: ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
topLevelDeclaration =
((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (TypeLHS l l d d) -> s (Type l l d d) -> Declaration λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (TypeLHS l l d d) -> s (Type l l d d) -> Declaration l l d s
Abstract.typeSynonymDeclaration (((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"type" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
simpleType Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"=" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeTerm
ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Context l l d d)
-> s (TypeLHS l l d d)
-> [s (DataConstructor l l d d)]
-> [s (DerivingClause l l d d)]
-> Declaration λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Context l l d d)
-> s (TypeLHS l l d d)
-> [s (DataConstructor l l d d)]
-> [s (DerivingClause l l d d)]
-> Declaration l l d s
Abstract.dataDeclaration (((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"data"
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
optionalContext
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
simpleType Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"=" ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
declaredConstructors ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []) Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (p :: * -> *) a. (Alternative p, Monoid a) => p a -> p a
moptional ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
derivingClause
ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Context l l d d)
-> s (TypeLHS l l d d)
-> s (DataConstructor l l d d)
-> [s (DerivingClause l l d d)]
-> Declaration λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Context l l d d)
-> s (TypeLHS l l d d)
-> s (DataConstructor l l d d)
-> [s (DerivingClause l l d d)]
-> Declaration l l d s
Abstract.newtypeDeclaration (((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"newtype"
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
optionalContext
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
simpleType Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"=" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
newConstructor Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (p :: * -> *) a. (Alternative p, Monoid a) => p a -> p a
moptional ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
derivingClause
ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Context l l d d)
-> s (TypeLHS l l d d)
-> [s (Declaration l l d d)]
-> Declaration λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Context l l d d)
-> s (TypeLHS l l d d)
-> [s (Declaration l l d d)]
-> Declaration l l d s
Abstract.classDeclaration (((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"class"
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
optionalContext
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
classLHS
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"where" ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser
g
t
(NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (g :: (* -> *) -> *) t (node :: (* -> *) -> (* -> *) -> *).
(Apply g, Ord t, Show t, OutlineMonoid t,
Foldable (Serialization (Down Int) t) node) =>
Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Parser g t [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
blockOf (ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
(NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
inClassDeclaration) ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [])
ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
ClassInstanceLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Context l l d d)
-> s (ClassInstanceLHS l l d d)
-> [s (Declaration l l d d)]
-> Declaration λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Context l l d d)
-> s (ClassInstanceLHS l l d d)
-> [s (Declaration l l d d)]
-> Declaration l l d s
Abstract.instanceDeclaration (((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
ClassInstanceLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
ClassInstanceLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"instance"
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
ClassInstanceLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
ClassInstanceLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
optionalContext
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
ClassInstanceLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
ClassInstanceLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(ClassInstanceLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
ClassInstanceLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(ClassInstanceLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
instanceDesignator
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"where" ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser
g
t
(NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (g :: (* -> *) -> *) t (node :: (* -> *) -> (* -> *) -> *).
(Apply g, Ord t, Show t, OutlineMonoid t,
Foldable (Serialization (Down Int) t) node) =>
Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Parser g t [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
blockOf (ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
(NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
inInstanceDeclaration) ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [])
ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
[s (Type l l d d)] -> Declaration λ l d s
forall (s :: * -> *) l (d :: * -> *).
[s (Type l l d d)] -> Declaration l l d s
Abstract.defaultDeclaration ([NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"default" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens (ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeTerm Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
`sepBy` ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma)
ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"foreign" ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
foreignDeclaration
ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
declaration,
declarations :: ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
declarations = Parser
g
t
(NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (g :: (* -> *) -> *) t (node :: (* -> *) -> (* -> *) -> *).
(Apply g, Ord t, Show t, OutlineMonoid t,
Foldable (Serialization (Down Int) t) node) =>
Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Parser g t [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
blockOf (ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
(NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
declaration),
declaration :: ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
declaration = ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
generalDeclaration
ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Down Int, ParsedLexemes t, Down Int),
EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (EquationLHS l l d d)
-> s (EquationRHS l l d d)
-> [s (Declaration l l d d)]
-> Declaration λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (EquationLHS l l d d)
-> s (EquationRHS l l d d)
-> [s (Declaration l l d d)]
-> Declaration l l d s
Abstract.equationDeclaration (((Down Int, ParsedLexemes t, Down Int),
EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
functionLHS ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Pattern l l d d) -> EquationLHS λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Pattern l l d d) -> EquationLHS l l d s
Abstract.patternLHS (((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
pattern)
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
rhs Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
whereClauses,
classLHS :: ParserT
((,) [[Lexeme t]])
g
t
(TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
classLHS = Name l
-> [Name l]
-> TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Name λ -> [Name λ] -> TypeLHS λ l d s
forall l (d :: * -> *) (s :: * -> *).
Name l -> [Name l] -> TypeLHS l l d s
Abstract.simpleTypeLHS (Name l
-> [Name l]
-> TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([Name l]
-> TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
typeClass Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([Name l]
-> TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [Name l]
-> ParserT
((,) [[Lexeme t]])
g
t
(TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Name l -> [Name l] -> [Name l]
forall a. a -> [a] -> [a]
:[]) (Name l -> [Name l])
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [Name l]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
typeVar),
inClassDeclaration :: ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
inClassDeclaration = ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
generalDeclaration ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
equationDeclaration,
inInstanceDeclaration :: ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
inInstanceDeclaration = ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
equationDeclaration,
equationDeclaration :: ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
equationDeclaration = ((Down Int, ParsedLexemes t, Down Int),
EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (EquationLHS l l d d)
-> s (EquationRHS l l d d)
-> [s (Declaration l l d d)]
-> Declaration λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (EquationLHS l l d d)
-> s (EquationRHS l l d d)
-> [s (Declaration l l d d)]
-> Declaration l l d s
Abstract.equationDeclaration (((Down Int, ParsedLexemes t, Down Int),
EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
functionLHS ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Name l
-> EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Name λ -> EquationLHS λ l d s
forall l (d :: * -> *) (s :: * -> *). Name l -> EquationLHS l l d s
Abstract.variableLHS (Name l
-> EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
variable)
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
rhs Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
whereClauses,
generalDeclaration :: ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
generalDeclaration =
NonEmpty (Name l)
-> ((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
NonEmpty (Name λ)
-> s (Context l l d d) -> s (Type l l d d) -> Declaration λ l d s
forall (s :: * -> *) l (d :: * -> *).
NonEmpty (Name l)
-> s (Context l l d d) -> s (Type l l d d) -> Declaration l l d s
Abstract.typeSignature (NonEmpty (Name l)
-> ((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (NonEmpty (Name l))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (NonEmpty (Name l))
variables Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT ((,) [[Lexeme t]]) g t ()
doubleColon Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
optionalTypeSignatureContext Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeTerm
ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Associativity l
-> Maybe Int
-> NonEmpty (Name l)
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Associativity λ
-> Maybe Int -> NonEmpty (Name λ) -> Declaration λ l d s
forall l (d :: * -> *) (s :: * -> *).
Associativity l
-> Maybe Int -> NonEmpty (Name l) -> Declaration l l d s
Abstract.fixityDeclaration (Associativity l
-> Maybe Int
-> NonEmpty (Name l)
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Associativity l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe Int
-> NonEmpty (Name l)
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Associativity l)
fixity Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe Int
-> NonEmpty (Name l)
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe Int)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty (Name l)
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed (ParserT ((,) [[Lexeme t]])) g t Int
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int)
-> ParserT ((,) [[Lexeme t]]) g t Integer
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t Integer
integer)
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty (Name l)
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (NonEmpty (Name l))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (ParserT ((,) [[Lexeme t]]) g t (Name l)
operator ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t (NonEmpty (Name l))
forall (m :: * -> *) a sep.
Alternative m =>
m a -> m sep -> m (NonEmpty a)
`sepByNonEmpty` ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma),
optionalTypeSignatureContext :: ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
optionalTypeSignatureContext = ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
optionalContext,
whereClauses :: ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
whereClauses = t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"where" ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
declarations ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [],
variables :: ParserT ((,) [[Lexeme t]]) g t (NonEmpty (Name l))
variables = ParserT ((,) [[Lexeme t]]) g t (Name l)
variable ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t (NonEmpty (Name l))
forall (m :: * -> *) a sep.
Alternative m =>
m a -> m sep -> m (NonEmpty a)
`sepByNonEmpty` ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma,
fixity :: ParserT ((,) [[Lexeme t]]) g t (Associativity l)
fixity = Associativity l
forall λ. Haskell λ => Associativity λ
Abstract.leftAssociative Associativity l
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (Associativity l)
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"infixl"
ParserT ((,) [[Lexeme t]]) g t (Associativity l)
-> ParserT ((,) [[Lexeme t]]) g t (Associativity l)
-> ParserT ((,) [[Lexeme t]]) g t (Associativity l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Associativity l
forall λ. Haskell λ => Associativity λ
Abstract.rightAssociative Associativity l
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (Associativity l)
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"infixr"
ParserT ((,) [[Lexeme t]]) g t (Associativity l)
-> ParserT ((,) [[Lexeme t]]) g t (Associativity l)
-> ParserT ((,) [[Lexeme t]]) g t (Associativity l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Associativity l
forall λ. Haskell λ => Associativity λ
Abstract.nonAssociative Associativity l
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (Associativity l)
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"infix",
declaredConstructors :: ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
declaredConstructors = ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
declaredConstructor Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
`sepBy1` t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"|",
declaredConstructor :: ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
declaredConstructor = Name l
-> [NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
Name λ -> [s (Type l l d d)] -> DataConstructor λ l d s
forall (s :: * -> *) l (d :: * -> *).
Name l -> [s (Type l l d d)] -> DataConstructor l l d s
Abstract.constructor (Name l
-> [NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
constructor
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall a b. (a -> b) -> a -> b
$ ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
aType ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
strictType)
ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
infixConstructorArgType
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> (ParserT ((,) [[Lexeme t]]) g t (Name l)
constructorOperator
ParserT ((,) [[Lexeme t]]) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> (ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
infixConstructorArgType
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> ((NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> (NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b. (a -> b) -> a -> b
$ \NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
right Name l
op NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
left-> Name l
-> [NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
Name λ -> [s (Type l l d d)] -> DataConstructor λ l d s
forall (s :: * -> *) l (d :: * -> *).
Name l -> [s (Type l l d d)] -> DataConstructor l l d s
Abstract.constructor Name l
op [NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
left, NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
right])))
ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Name l
-> [((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
Name λ -> [s (FieldDeclaration l l d d)] -> DataConstructor λ l d s
forall (s :: * -> *) l (d :: * -> *).
Name l -> [s (FieldDeclaration l l d d)] -> DataConstructor l l d s
Abstract.recordConstructor (Name l
-> [((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
constructor
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a. TokenParsing m => m a -> m a
braces (ParserT
((,) [[Lexeme t]])
g
t
(FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
fieldDeclaration Parser
g
t
((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
`sepBy` ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma),
infixConstructorArgType :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
infixConstructorArgType = ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
bType ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
strictType,
newConstructor :: ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
newConstructor = Name l
-> [NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
Name λ -> [s (Type l l d d)] -> DataConstructor λ l d s
forall (s :: * -> *) l (d :: * -> *).
Name l -> [s (Type l l d d)] -> DataConstructor l l d s
Abstract.constructor (Name l
-> [NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
constructor Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a. a -> [a] -> [a]
:[]) (NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
aType)
ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Name l
-> [((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
Name λ -> [s (FieldDeclaration l l d d)] -> DataConstructor λ l d s
forall (s :: * -> *) l (d :: * -> *).
Name l -> [s (FieldDeclaration l l d d)] -> DataConstructor l l d s
Abstract.recordConstructor (Name l
-> [((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
constructor
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(DataConstructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a. TokenParsing m => m a -> m a
braces ((((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a. a -> [a] -> [a]
:[]) (((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
-> Parser
g
t
((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
((Down Int, ParsedLexemes t, Down Int),
FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (NonEmpty (Name l)
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
NonEmpty (Name λ) -> s (Type l l d d) -> FieldDeclaration λ l d s
forall (s :: * -> *) l (d :: * -> *).
NonEmpty (Name l) -> s (Type l l d d) -> FieldDeclaration l l d s
Abstract.constructorFields (NonEmpty (Name l)
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (NonEmpty (Name l))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Name l -> [Name l] -> NonEmpty (Name l)
forall a. a -> [a] -> NonEmpty a
:|[]) (Name l -> NonEmpty (Name l))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (NonEmpty (Name l))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
variable)
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT ((,) [[Lexeme t]]) g t ()
doubleColon Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeTerm)),
fieldDeclaration :: ParserT
((,) [[Lexeme t]])
g
t
(FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
fieldDeclaration = NonEmpty (Name l)
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
NonEmpty (Name λ) -> s (Type l l d d) -> FieldDeclaration λ l d s
forall (s :: * -> *) l (d :: * -> *).
NonEmpty (Name l) -> s (Type l l d d) -> FieldDeclaration l l d s
Abstract.constructorFields (NonEmpty (Name l)
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (NonEmpty (Name l))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (NonEmpty (Name l))
variables Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT ((,) [[Lexeme t]]) g t ()
doubleColon Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(FieldDeclaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeTerm ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
strictType),
strictType :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
strictType = NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Type l l d d) -> Type λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Type l l d d) -> Type l l d s
Abstract.strictType (NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"!" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
aType,
optionalContext :: ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
optionalContext = ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
context ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT ((,) [[Lexeme t]]) g t ()
rightDoubleArrow ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Context λ l d s
forall l (d :: * -> *) (s :: * -> *). Context l l d s
Abstract.noContext,
context :: ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
context = ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
constraint ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
[s (Context l l d d)] -> Context λ l d s
forall (s :: * -> *) l (d :: * -> *).
[s (Context l l d d)] -> Context l l d s
Abstract.constraints ([((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens (ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
constraint Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
`sepBy` ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma),
constraint :: ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
constraint = QualifiedName l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
QualifiedName λ -> s (Type l l d d) -> Context λ l d s
forall (s :: * -> *) l (d :: * -> *).
QualifiedName l -> s (Type l l d d) -> Context l l d s
Abstract.classConstraint (QualifiedName l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedTypeClass
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Context
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (Name l
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Name λ -> Type λ l d s
forall l (d :: * -> *) (s :: * -> *). Name l -> Type l l d s
Abstract.typeVariable (Name l
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
typeVar ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeApplications),
typeApplications :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeApplications = NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Type l l d d) -> s (Type l l d d) -> Type λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Type l l d d) -> s (Type l l d d) -> Type l l d s
Abstract.typeApplication (NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (Name l
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Name λ -> Type λ l d s
forall l (d :: * -> *) (s :: * -> *). Name l -> Type l l d s
Abstract.typeVariable (Name l
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
typeVar ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeApplications)
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
aType,
simpleType :: ParserT
((,) [[Lexeme t]])
g
t
(TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
simpleType = Name l
-> [Name l]
-> TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Name λ -> [Name λ] -> TypeLHS λ l d s
forall l (d :: * -> *) (s :: * -> *).
Name l -> [Name l] -> TypeLHS l l d s
Abstract.simpleTypeLHS (Name l
-> [Name l]
-> TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([Name l]
-> TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
typeConstructor Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([Name l]
-> TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [Name l]
-> ParserT
((,) [[Lexeme t]])
g
t
(TypeLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [Name l]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many ParserT ((,) [[Lexeme t]]) g t (Name l)
typeVar,
derivingClause :: ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
derivingClause = t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"deriving"
ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser
g
t
(DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (QualifiedName l
-> DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
QualifiedName λ -> DerivingClause λ l d s
forall l (d :: * -> *) (s :: * -> *).
QualifiedName l -> DerivingClause l l d s
Abstract.simpleDerive (QualifiedName l
-> DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> Parser
g
t
(DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedTypeClass)
ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens (Parser
g
t
(DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (QualifiedName l
-> DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
QualifiedName λ -> DerivingClause λ l d s
forall l (d :: * -> *) (s :: * -> *).
QualifiedName l -> DerivingClause l l d s
Abstract.simpleDerive (QualifiedName l
-> DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> Parser
g
t
(DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedTypeClass) Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
`sepBy` ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma)),
instanceDesignator :: ParserT
((,) [[Lexeme t]])
g
t
(ClassInstanceLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
instanceDesignator = QualifiedName l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ClassInstanceLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
QualifiedName λ -> s (Type l l d d) -> ClassInstanceLHS λ l d s
forall (s :: * -> *) l (d :: * -> *).
QualifiedName l -> s (Type l l d d) -> ClassInstanceLHS l l d s
Abstract.typeClassInstanceLHS (QualifiedName l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ClassInstanceLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ClassInstanceLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedTypeClass Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ClassInstanceLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(ClassInstanceLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
instanceTypeDesignator,
instanceTypeDesignator :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
instanceTypeDesignator =
ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
generalTypeConstructor
ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Type l l d d) -> Type λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Type l l d d) -> Type l l d s
Abstract.listType (NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (m :: * -> *) a. TokenParsing m => m a -> m a
brackets (ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall a b. (a -> b) -> a -> b
$ Name l
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Name λ -> Type λ l d s
forall l (d :: * -> *) (s :: * -> *). Name l -> Type l l d s
Abstract.typeVariable (Name l
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
typeVar)
ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens (ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeVarApplications
ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
NonEmpty (s (Type l l d d)) -> Type λ l d s
forall (s :: * -> *) l (d :: * -> *).
NonEmpty (s (Type l l d d)) -> Type l l d s
Abstract.tupleType (NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
typeVarTuple
ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Type l l d d) -> s (Type l l d d) -> Type λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Type l l d d) -> s (Type l l d d) -> Type l l d s
Abstract.functionType (NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (Name l
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Name λ -> Type λ l d s
forall l (d :: * -> *) (s :: * -> *). Name l -> Type l l d s
Abstract.typeVariable (Name l
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
typeVar) Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT ((,) [[Lexeme t]]) g t ()
rightArrow
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (Name l
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Name λ -> Type λ l d s
forall l (d :: * -> *) (s :: * -> *). Name l -> Type l l d s
Abstract.typeVariable (Name l
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
typeVar)),
typeVarApplications :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeVarApplications = ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
generalTypeConstructor
ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Type l l d d) -> s (Type l l d d) -> Type λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Type l l d d) -> s (Type l l d d) -> Type l l d s
Abstract.typeApplication (NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeVarApplications
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (Name l
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Name λ -> Type λ l d s
forall l (d :: * -> *) (s :: * -> *). Name l -> Type l l d s
Abstract.typeVariable (Name l
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
typeVar),
typeVarTuple :: ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
typeVarTuple = NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall a. a -> [a] -> NonEmpty a
(:|) (NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (Name l
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Name λ -> Type λ l d s
forall l (d :: * -> *) (s :: * -> *). Name l -> Type l l d s
Abstract.typeVariable (Name l
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
typeVar)
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
some (ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (Name l
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Name λ -> Type λ l d s
forall l (d :: * -> *) (s :: * -> *). Name l -> Type l l d s
Abstract.typeVariable (Name l
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
typeVar)),
foreignDeclaration :: ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
foreignDeclaration = CallingConvention l
-> Maybe (CallSafety l)
-> Maybe Text
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
CallingConvention λ
-> Maybe (CallSafety λ)
-> Maybe Text
-> Name λ
-> s (Type l l d d)
-> Declaration λ l d s
forall (s :: * -> *) l (d :: * -> *).
CallingConvention l
-> Maybe (CallSafety l)
-> Maybe Text
-> Name l
-> s (Type l l d d)
-> Declaration l l d s
Abstract.foreignImport (CallingConvention l
-> Maybe (CallSafety l)
-> Maybe Text
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(CallingConvention l
-> Maybe (CallSafety l)
-> Maybe Text
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"import" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(CallingConvention l
-> Maybe (CallSafety l)
-> Maybe Text
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe (CallSafety l)
-> Maybe Text
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
callingConvention Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe (CallSafety l)
-> Maybe Text
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe (CallSafety l))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe Text
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t (CallSafety l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe (CallSafety l))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParserT ((,) [[Lexeme t]]) g t (CallSafety l)
safety
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe Text
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe Text)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t Text
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParserT ((,) [[Lexeme t]]) g t Text
stringLiteral Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t (Name l)
variable Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT ((,) [[Lexeme t]]) g t ()
doubleColon
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
foreignType
ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> CallingConvention l
-> Maybe Text
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
CallingConvention λ
-> Maybe Text -> Name λ -> s (Type l l d d) -> Declaration λ l d s
forall (s :: * -> *) l (d :: * -> *).
CallingConvention l
-> Maybe Text -> Name l -> s (Type l l d d) -> Declaration l l d s
Abstract.foreignExport (CallingConvention l
-> Maybe Text
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(CallingConvention l
-> Maybe Text
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"export" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(CallingConvention l
-> Maybe Text
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe Text
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
callingConvention
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe Text
-> Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe Text)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t Text
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParserT ((,) [[Lexeme t]]) g t Text
stringLiteral Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Name l
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t (Name l)
variable Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT ((,) [[Lexeme t]]) g t ()
doubleColon
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
foreignType,
callingConvention :: ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
callingConvention = CallingConvention l
forall λ. Haskell λ => CallingConvention λ
Abstract.cCall CallingConvention l
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"ccall" ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
-> ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
-> ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> CallingConvention l
forall λ. Haskell λ => CallingConvention λ
Abstract.stdCall CallingConvention l
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"stdcall"
ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
-> ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
-> ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> CallingConvention l
forall λ. Haskell λ => CallingConvention λ
Abstract.cppCall CallingConvention l
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"cplusplus" ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
-> ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
-> ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> CallingConvention l
forall λ. Haskell λ => CallingConvention λ
Abstract.jvmCall CallingConvention l
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"jvm"
ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
-> ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
-> ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> CallingConvention l
forall λ. Haskell λ => CallingConvention λ
Abstract.dotNetCall CallingConvention l
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (CallingConvention l)
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"dotnet",
safety :: ParserT ((,) [[Lexeme t]]) g t (CallSafety l)
safety = CallSafety l
forall λ. Haskell λ => CallSafety λ
Abstract.safeCall CallSafety l
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (CallSafety l)
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"safe" ParserT ((,) [[Lexeme t]]) g t (CallSafety l)
-> ParserT ((,) [[Lexeme t]]) g t (CallSafety l)
-> ParserT ((,) [[Lexeme t]]) g t (CallSafety l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> CallSafety l
forall λ. Haskell λ => CallSafety λ
Abstract.unsafeCall CallSafety l
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (CallSafety l)
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"unsafe",
foreignType :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
foreignType = NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Type l l d d) -> s (Type l l d d) -> Type λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Type l l d d) -> s (Type l l d d) -> Type l l d s
Abstract.functionType (NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
foreignArgType Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT ((,) [[Lexeme t]]) g t ()
rightArrow Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
foreignType
ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
foreignReturnType,
foreignReturnType :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
foreignReturnType = ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
foreignArgType
ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Constructor l l d d) -> Type λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Constructor l l d d) -> Type l l d s
Abstract.constructorType (((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Constructor λ l d s
forall l (d :: * -> *) (s :: * -> *). Constructor l l d s
Abstract.unitConstructor
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
terminator t
"(" ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
terminator t
")"),
foreignArgType :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
foreignArgType = ((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Constructor l l d d) -> Type λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Constructor l l d d) -> Type l l d s
Abstract.constructorType (((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (QualifiedName l
-> Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
QualifiedName λ -> Constructor λ l d s
forall l (d :: * -> *) (s :: * -> *).
QualifiedName l -> Constructor l l d s
Abstract.constructorReference (QualifiedName l
-> Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedTypeConstructor)
ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Type l l d d) -> s (Type l l d d) -> Type λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Type l l d d) -> s (Type l l d d) -> Type l l d s
Abstract.typeApplication
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
foreignArgType
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Type l l d d) -> Type λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Type l l d d) -> Type l l d s
Abstract.strictType (NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
aType),
functionLHS :: ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
functionLHS = ((Down Int, ParsedLexemes t, Down Int),
EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NonEmpty
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (EquationLHS l l d d)
-> NonEmpty (s (Pattern l l d d)) -> EquationLHS λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (EquationLHS l l d d)
-> NonEmpty (s (Pattern l l d d)) -> EquationLHS l l d s
Abstract.prefixLHS (((Down Int, ParsedLexemes t, Down Int),
EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NonEmpty
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (Name l
-> EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Name λ -> EquationLHS λ l d s
forall l (d :: * -> *) (s :: * -> *). Name l -> EquationLHS l l d s
Abstract.variableLHS (Name l
-> EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
variable ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
functionLHS)
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (p :: * -> *) a. Alternative p => p a -> p (NonEmpty a)
someNonEmpty (ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
aPattern)
ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Name l
-> ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Pattern l l d d)
-> Name λ -> s (Pattern l l d d) -> EquationLHS λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Pattern l l d d)
-> Name l -> s (Pattern l l d d) -> EquationLHS l l d s
Abstract.infixLHS (((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Name l
-> ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Name l
-> ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
pattern Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Name l
-> ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t (Name l)
variableOperator Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationLHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
pattern,
qualifiedTypeClass :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedTypeClass = ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructorIdentifier,
typeClass :: ParserT ((,) [[Lexeme t]]) g t (Name l)
typeClass = ParserT ((,) [[Lexeme t]]) g t (Name l)
constructorIdentifier
},
typeTerm :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeTerm = NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Type l l d d) -> s (Type l l d d) -> Type λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Type l l d d) -> s (Type l l d d) -> Type l l d s
Abstract.functionType (NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
bType Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT ((,) [[Lexeme t]]) g t ()
rightArrow Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeTerm ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
bType,
bType :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
bType = NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Type l l d d) -> s (Type l l d d) -> Type λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Type l l d d) -> s (Type l l d d) -> Type l l d s
Abstract.typeApplication (NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
bType Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
aType ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
aType,
aType :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
aType = ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
generalTypeConstructor
ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Name l
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Name λ -> Type λ l d s
forall l (d :: * -> *) (s :: * -> *). Name l -> Type l l d s
Abstract.typeVariable (Name l
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
typeVar
ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
NonEmpty (s (Type l l d d)) -> Type λ l d s
forall (s :: * -> *) l (d :: * -> *).
NonEmpty (s (Type l l d d)) -> Type l l d s
Abstract.tupleType (NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens (NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall a. a -> [a] -> NonEmpty a
(:|) (NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeTerm Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
some (ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeTerm))
ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Type l l d d) -> Type λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Type l l d d) -> Type l l d s
Abstract.listType (NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (m :: * -> *) a. TokenParsing m => m a -> m a
brackets (ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeTerm)
ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeTerm,
generalTypeConstructor :: ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
generalTypeConstructor = ((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Constructor l l d d) -> Type λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Constructor l l d d) -> Type l l d s
Abstract.constructorType (((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
generalConstructor
ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *). Haskell λ => Type λ l d s
forall l (d :: * -> *) (s :: * -> *). Type l l d s
Abstract.functionConstructorType Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t ()
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens ParserT ((,) [[Lexeme t]]) g t ()
rightArrow,
rhs :: ParserT
((,) [[Lexeme t]])
g
t
(EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
rhs = NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Expression l l d d) -> EquationRHS λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Expression l l d d) -> EquationRHS l l d s
Abstract.normalRHS (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"=" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression
ParserT
((,) [[Lexeme t]])
g
t
(EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NonEmpty
((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
NonEmpty (s (GuardedExpression l l d d)) -> EquationRHS λ l d s
forall (s :: * -> *) l (d :: * -> *).
NonEmpty (s (GuardedExpression l l d d)) -> EquationRHS l l d s
Abstract.guardedRHS
(NonEmpty
((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty
((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty
((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (p :: * -> *) a. Alternative p => p a -> p (NonEmpty a)
someNonEmpty (ParserT
((,) [[Lexeme t]])
g
t
(GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (ParserT
((,) [[Lexeme t]])
g
t
(GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b. (a -> b) -> a -> b
$ [NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
[s (Statement l l d d)]
-> s (Expression l l d d) -> GuardedExpression λ l d s
forall (s :: * -> *) l (d :: * -> *).
[s (Statement l l d d)]
-> s (Expression l l d d) -> GuardedExpression l l d s
Abstract.guardedExpression ([NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> (NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> [NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
-> NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> [NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
guards Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"=" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression),
guards :: ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
guards = t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"|" ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
guard Parser
g
t
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
forall (m :: * -> *) a sep.
Alternative m =>
m a -> m sep -> m (NonEmpty a)
`sepByNonEmpty` ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma,
guard :: ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
guard = ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Pattern l l d d) -> s (Expression l l d d) -> Statement λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Pattern l l d d) -> s (Expression l l d d) -> Statement l l d s
Abstract.bindStatement (((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
pattern Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT ((,) [[Lexeme t]]) g t ()
leftArrow Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
infixExpression
ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
[s (Declaration l l d d)] -> Statement λ l d s
forall (s :: * -> *) l (d :: * -> *).
[s (Declaration l l d d)] -> Statement l l d s
Abstract.letStatement ([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"let" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
declarations
ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Expression l l d d) -> Statement λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Expression l l d d) -> Statement l l d s
Abstract.expressionStatement (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
infixExpression,
expression :: ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression = ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Expression l l d d) -> s (Type l l d d) -> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Expression l l d d) -> s (Type l l d d) -> Expression l l d s
Abstract.typedExpression (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
leftInfixExpression Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT ((,) [[Lexeme t]]) g t ()
doubleColon Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Type
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
typeTerm)
ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
infixExpression,
infixExpression :: ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
infixExpression = ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Expression l l d d)
-> s (Expression l l d d)
-> s (Expression l l d d)
-> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Expression l l d d)
-> s (Expression l l d d)
-> s (Expression l l d d)
-> Expression l l d s
Abstract.infixExpression
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
dExpression
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (QualifiedName l
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *).
Haskell λ =>
QualifiedName λ -> Expression λ l d d
forall l (d :: * -> *). QualifiedName l -> Expression l l d d
Abstract.referenceExpression (QualifiedName l
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedOperator)
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
infixExpression
ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Expression l l d d)
-> s (Expression l l d d) -> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Expression l l d d)
-> s (Expression l l d d) -> Expression l l d s
Abstract.applyExpression (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
prefixNegation Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
lExpression)
ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
lExpression,
leftInfixExpression :: ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
leftInfixExpression = ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Expression l l d d)
-> s (Expression l l d d)
-> s (Expression l l d d)
-> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Expression l l d d)
-> s (Expression l l d d)
-> s (Expression l l d d)
-> Expression l l d s
Abstract.infixExpression
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
dExpression
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (QualifiedName l
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *).
Haskell λ =>
QualifiedName λ -> Expression λ l d d
forall l (d :: * -> *). QualifiedName l -> Expression l l d d
Abstract.referenceExpression (QualifiedName l
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedOperator)
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
leftInfixExpression
ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Expression l l d d)
-> s (Expression l l d d) -> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Expression l l d d)
-> s (Expression l l d d) -> Expression l l d s
Abstract.applyExpression (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
prefixNegation Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
dExpression)
ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
dExpression,
prefixNegation :: ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
prefixNegation = Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Expression λ l d s
forall l (d :: * -> *) (s :: * -> *). Expression l l d s
Abstract.negate Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"-",
lExpression :: ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
lExpression = ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
openBlockExpression ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
dExpression,
openBlockExpression :: ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
openBlockExpression = [((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
[s (Pattern l l d d)]
-> s (Expression l l d d) -> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
[s (Pattern l l d d)]
-> s (Expression l l d d) -> Expression l l d s
Abstract.lambdaExpression ([((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"\\" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
some (ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
aPattern) Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT ((,) [[Lexeme t]]) g t ()
rightArrow
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression
ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
[s (Declaration l l d d)]
-> s (Expression l l d d) -> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
[s (Declaration l l d d)]
-> s (Expression l l d d) -> Expression l l d s
Abstract.letExpression ([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"let" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
declarations Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"in" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression
ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Expression l l d d)
-> s (Expression l l d d)
-> s (Expression l l d d)
-> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Expression l l d d)
-> s (Expression l l d d)
-> s (Expression l l d d)
-> Expression l l d s
Abstract.conditionalExpression (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"if" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe Char)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe Char)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
semi
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"then" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe Char)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe Char)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
semi
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"else" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression,
dExpression :: ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
dExpression = ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
closedBlockExpression ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
fExpression,
closedBlockExpression :: ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
closedBlockExpression = NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Expression l l d d)
-> [s (CaseAlternative l l d d)] -> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Expression l l d d)
-> [s (CaseAlternative l l d d)] -> Expression l l d s
Abstract.caseExpression (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"case" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"of" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
alternatives
ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (GuardedExpression l l d d) -> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (GuardedExpression l l d d) -> Expression l l d s
Abstract.doExpression (((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"do" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
statements,
fExpression :: ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
fExpression = ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Expression l l d d)
-> s (Expression l l d d) -> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Expression l l d d)
-> s (Expression l l d d) -> Expression l l d s
Abstract.applyExpression (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
fExpression Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
aExpression) ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
aExpression,
aExpression :: ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
aExpression = ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
bareExpression ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Wrapped
(Down Int)
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall pos s a.
(Position pos, Factorial s) =>
Wrapped pos s (Wrapped pos s a) -> Wrapped pos s a
Reserializer.joinWrapped (Wrapped
(Down Int)
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Wrapped
(Down Int)
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Wrapped
(Down Int)
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression),
bareExpression :: ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
bareExpression = QualifiedName l
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *).
Haskell λ =>
QualifiedName λ -> Expression λ l d d
forall l (d :: * -> *). QualifiedName l -> Expression l l d d
Abstract.referenceExpression (QualifiedName l
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedVariable
ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Constructor l l d d) -> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Constructor l l d d) -> Expression l l d s
Abstract.constructorExpression (((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
generalConstructor
ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Down Int, ParsedLexemes t, Down Int),
Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Value l l d d) -> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Value l l d d) -> Expression l l d s
Abstract.literalExpression (((Down Int, ParsedLexemes t, Down Int),
Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
literal
ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NonEmpty
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
NonEmpty (s (Expression l l d d)) -> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
NonEmpty (s (Expression l l d d)) -> Expression l l d s
Abstract.tupleExpression (NonEmpty
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NonEmpty
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall a. a -> [a] -> NonEmpty a
(:|) (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NonEmpty
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NonEmpty
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NonEmpty
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
some (ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression))
ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (m :: * -> *) a. TokenParsing m => m a -> m a
brackets ([NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
[s (Expression l l d d)] -> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
[s (Expression l l d d)] -> Expression l l d s
Abstract.listExpression ([NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
`sepBy1` ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma)
ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Maybe
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Maybe
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Expression l l d d)
-> Maybe (s (Expression l l d d))
-> Maybe (s (Expression l l d d))
-> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Expression l l d d)
-> Maybe (s (Expression l l d d))
-> Maybe (s (Expression l l d d))
-> Expression l l d s
Abstract.sequenceExpression (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Maybe
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Maybe
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Maybe
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Maybe
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression)
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
".." Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression
ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Expression l l d d)
-> NonEmpty (s (Statement l l d d)) -> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Expression l l d d)
-> NonEmpty (s (Statement l l d d)) -> Expression l l d s
Abstract.listComprehension (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
qualifiers)
ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> QualifiedName l
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Expression l l d d) -> QualifiedName λ -> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Expression l l d d) -> QualifiedName l -> Expression l l d s
Abstract.leftSectionExpression (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> QualifiedName l
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(QualifiedName l
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
infixExpression Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(QualifiedName l
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedOperator
ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> QualifiedName l
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
QualifiedName λ -> s (Expression l l d d) -> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
QualifiedName l -> s (Expression l l d d) -> Expression l l d s
Abstract.rightSectionExpression
(QualifiedName l
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> ParserT ((,) [[Lexeme t]]) g t ()
forall a.
Show a =>
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> ParserT ((,) [[Lexeme t]]) g t ()
forall (m :: * -> *) a. (Parsing m, Show a) => m a -> m ()
notFollowedBy (ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"-" Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (Char -> Bool) -> ParserT ((,) [[Lexeme t]]) g t ()
forall (m :: * -> *). InputCharParsing m => (Char -> Bool) -> m ()
notSatisfyChar Char -> Bool
isSymbol) ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedOperator)
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
infixExpression)
ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Expression l l d d)
-> [s (FieldBinding l l d d)] -> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Expression l l d d)
-> [s (FieldBinding l l d d)] -> Expression l l d s
Abstract.recordExpression
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Constructor l l d d) -> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Constructor l l d d) -> Expression l l d s
Abstract.constructorExpression
(((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (QualifiedName l
-> Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
QualifiedName λ -> Constructor λ l d s
forall l (d :: * -> *) (s :: * -> *).
QualifiedName l -> Constructor l l d s
Abstract.constructorReference (QualifiedName l
-> Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructor))
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a. TokenParsing m => m a -> m a
braces ([((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [])
ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Expression l l d d)
-> [s (FieldBinding l l d d)] -> Expression λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Expression l l d d)
-> [s (FieldBinding l l d d)] -> Expression l l d s
Abstract.recordExpression (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
aExpression Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a. TokenParsing m => m a -> m a
braces (ParserT
((,) [[Lexeme t]])
g
t
(FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
fieldBinding Parser
g
t
((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
`sepBy1` ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma),
qualifiers :: ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
qualifiers = t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"|" ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
qualifier Parser
g
t
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
forall (m :: * -> *) a sep.
Alternative m =>
m a -> m sep -> m (NonEmpty a)
`sepByNonEmpty` ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma,
qualifier :: ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
qualifier = ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Pattern l l d d) -> s (Expression l l d d) -> Statement λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Pattern l l d d) -> s (Expression l l d d) -> Statement l l d s
Abstract.bindStatement (((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
pattern Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT ((,) [[Lexeme t]]) g t ()
leftArrow Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression
ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
[s (Declaration l l d d)] -> Statement λ l d s
forall (s :: * -> *) l (d :: * -> *).
[s (Declaration l l d d)] -> Statement l l d s
Abstract.letStatement ([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"let" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
declarations
ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Expression l l d d) -> Statement λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Expression l l d d) -> Statement l l d s
Abstract.expressionStatement (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression,
alternatives :: ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
alternatives = let blockOfAlternatives :: ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
blockOfAlternatives = (Int
-> t
-> ((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Bool)
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Parser
g
t
((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (g :: (* -> *) -> *) t (node :: (* -> *) -> (* -> *) -> *).
(Apply g, Ord t, Show t, OutlineMonoid t,
Foldable (Serialization (Down Int) t) node) =>
(Int -> t -> NodeWrap t (node (NodeWrap t) (NodeWrap t)) -> Bool)
-> Parser g t ()
-> Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Parser g t [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
blockWith Int
-> t
-> ((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Bool
forall t (node :: (* -> *) -> (* -> *) -> *).
(Ord t, Show t, OutlineMonoid t,
Foldable (Serialization (Down Int) t) node) =>
Int -> t -> NodeWrap t (node (NodeWrap t) (NodeWrap t)) -> Bool
oneExtendedLine ParserT ((,) [[Lexeme t]]) g t ()
alternativeTerminatorKeyword (ParserT
((,) [[Lexeme t]])
g
t
(CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
alternative)
alternativeTerminatorKeyword :: ParserT ((,) [[Lexeme t]]) g t ()
alternativeTerminatorKeyword = (ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"else" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"in" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"of")
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t ()
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Char -> Bool) -> ParserT ((,) [[Lexeme t]]) g t ()
forall (m :: * -> *). InputCharParsing m => (Char -> Bool) -> m ()
notSatisfyChar Char -> Bool
isNameTailChar
in ([((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Bool)
-> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a.
(a -> Bool)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter (Bool -> Bool
not (Bool -> Bool)
-> ([((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Bool)
-> [((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Bool
forall m. MonoidNull m => m -> Bool
null) ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
blockOfAlternatives
ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [Char]
-> ParserT
((,) [[Lexeme t]])
g
t
[((Down Int, ParsedLexemes t, Down Int),
CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> [Char] -> m a
<?> [Char]
"non-empty case alternatives",
alternative :: ParserT
((,) [[Lexeme t]])
g
t
(CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
alternative = ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Pattern l l d d)
-> s (EquationRHS l l d d)
-> [s (Declaration l l d d)]
-> CaseAlternative λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Pattern l l d d)
-> s (EquationRHS l l d d)
-> [s (Declaration l l d d)]
-> CaseAlternative l l d s
Abstract.caseAlternative (((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
pattern
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Expression l l d d) -> EquationRHS λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Expression l l d d) -> EquationRHS l l d s
Abstract.normalRHS (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserT ((,) [[Lexeme t]]) g t ()
rightArrow Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression
ParserT
((,) [[Lexeme t]])
g
t
(EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NonEmpty
((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
NonEmpty (s (GuardedExpression l l d d)) -> EquationRHS λ l d s
forall (s :: * -> *) l (d :: * -> *).
NonEmpty (s (GuardedExpression l l d d)) -> EquationRHS l l d s
Abstract.guardedRHS
(NonEmpty
((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty
((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(EquationRHS
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty
((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (p :: * -> *) a. Alternative p => p a -> p (NonEmpty a)
someNonEmpty (ParserT
((,) [[Lexeme t]])
g
t
(GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (ParserT
((,) [[Lexeme t]])
g
t
(GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b. (a -> b) -> a -> b
$ [NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
[s (Statement l l d d)]
-> s (Expression l l d d) -> GuardedExpression λ l d s
forall (s :: * -> *) l (d :: * -> *).
[s (Statement l l d d)]
-> s (Expression l l d d) -> GuardedExpression l l d s
Abstract.guardedExpression ([NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> (NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> [NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))])
-> NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> [NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(NonEmpty
(NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))))
guards Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT ((,) [[Lexeme t]]) g t ()
rightArrow
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression))
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(CaseAlternative
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
whereClauses,
statements :: ParserT
((,) [[Lexeme t]])
g
t
(GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
statements = ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Parser
g
t
[NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (g :: (* -> *) -> *) t (node :: (* -> *) -> (* -> *) -> *).
(Apply g, Ord t, Show t, OutlineMonoid t,
Foldable (Serialization (Down Int) t) node) =>
Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Parser g t [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
blockOf ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
statement Parser
g
t
[NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ([NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> (a -> Fixed (ParserT ((,) [[Lexeme t]])) g t b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall l (g :: (* -> *) -> *) t.
(Haskell l, Apply g, Ord t) =>
[NodeWrap
t (Sum (Statement l l) (Expression l l) (NodeWrap t) (NodeWrap t))]
-> Parser g t (GuardedExpression l l (NodeWrap t) (NodeWrap t))
verifyStatements,
statement :: ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
statement = Parser
g
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall (g :: (* -> *) -> (* -> *) -> *)
(h :: (* -> *) -> (* -> *) -> *) (d :: * -> *) (s :: * -> *).
g d s -> Sum g h d s
Deep.InL (Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Pattern l l d d) -> s (Expression l l d d) -> Statement λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Pattern l l d d) -> s (Expression l l d d) -> Statement l l d s
Abstract.bindStatement (((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
pattern Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT ((,) [[Lexeme t]]) g t ()
leftArrow Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression
ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
[s (Declaration l l d d)] -> Statement λ l d s
forall (s :: * -> *) l (d :: * -> *).
[s (Declaration l l d d)] -> Statement l l d s
Abstract.letStatement ([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"let" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
[NodeWrap
t
(Declaration
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
declarations))
ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
(a -> b)
-> ((Down Int, ParsedLexemes t, Down Int), a)
-> ((Down Int, ParsedLexemes t, Down Int), b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall (g :: (* -> *) -> (* -> *) -> *)
(h :: (* -> *) -> (* -> *) -> *) (d :: * -> *) (s :: * -> *).
h d s -> Sum g h d s
Deep.InR (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression,
fieldBinding :: ParserT
((,) [[Lexeme t]])
g
t
(FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
fieldBinding = QualifiedName l
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
QualifiedName λ -> s (Expression l l d d) -> FieldBinding λ l d s
forall (s :: * -> *) l (d :: * -> *).
QualifiedName l -> s (Expression l l d d) -> FieldBinding l l d s
Abstract.fieldBinding (QualifiedName l
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedVariable Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"=" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(FieldBinding
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
expression,
pattern :: ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
pattern = ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> QualifiedName l
-> ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Pattern l l d d)
-> QualifiedName λ -> s (Pattern l l d d) -> Pattern λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Pattern l l d d)
-> QualifiedName l -> s (Pattern l l d d) -> Pattern l l d s
Abstract.infixPattern (((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> QualifiedName l
-> ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(QualifiedName l
-> ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
lPattern Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(QualifiedName l
-> ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructorOperator Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
pattern ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
lPattern,
lPattern :: ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
lPattern = ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
aPattern
ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Down Int, ParsedLexemes t, Down Int),
Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Value l l d d) -> Pattern λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Value l l d d) -> Pattern l l d s
Abstract.literalPattern (((Down Int, ParsedLexemes t, Down Int),
Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ((Integer
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Integer -> Value λ l d s
forall l (d :: * -> *) (s :: * -> *). Integer -> Value l l d s
Abstract.integerLiteral (Integer
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> (Integer -> Integer)
-> Integer
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Integer
forall a. Num a => a -> a
negate) (Integer
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Integer
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"-" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Integer
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t Integer
-> ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t Integer
integer)
ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Down Int, ParsedLexemes t, Down Int),
Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Value l l d d) -> Pattern λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Value l l d d) -> Pattern l l d s
Abstract.literalPattern (((Down Int, ParsedLexemes t, Down Int),
Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ((Rational
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Rational -> Value λ l d s
forall l (d :: * -> *) (s :: * -> *). Rational -> Value l l d s
Abstract.floatingLiteral (Rational
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> (Rational -> Rational)
-> Rational
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> Rational
forall a. Num a => a -> a
negate) (Rational
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Rational
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"-" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Rational
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t Rational
-> ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t Rational
float)
ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Constructor l l d d) -> [s (Pattern l l d d)] -> Pattern λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Constructor l l d d) -> [s (Pattern l l d d)] -> Pattern l l d s
Abstract.constructorPattern (((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
generalConstructor Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
some (ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
aPattern),
aPattern :: ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
aPattern = Name l
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Name λ -> Pattern λ l d s
forall l (d :: * -> *) (s :: * -> *). Name l -> Pattern l l d s
Abstract.variablePattern (Name l
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
variable
ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Name l
-> ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
Name λ -> s (Pattern l l d d) -> Pattern λ l d s
forall (s :: * -> *) l (d :: * -> *).
Name l -> s (Pattern l l d d) -> Pattern l l d s
Abstract.asPattern (Name l
-> ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (Name l)
variable Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"@" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
aPattern
ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Constructor l l d d) -> [s (Pattern l l d d)] -> Pattern λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Constructor l l d d) -> [s (Pattern l l d d)] -> Pattern l l d s
Abstract.constructorPattern (((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
generalConstructor Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> QualifiedName l
-> [((Down Int, ParsedLexemes t, Down Int),
FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
QualifiedName λ -> [s (FieldPattern l l d d)] -> Pattern λ l d s
forall (s :: * -> *) l (d :: * -> *).
QualifiedName l -> [s (FieldPattern l l d d)] -> Pattern l l d s
Abstract.recordPattern (QualifiedName l
-> [((Down Int, ParsedLexemes t, Down Int),
FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructor Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a. TokenParsing m => m a -> m a
braces (ParserT
((,) [[Lexeme t]])
g
t
(FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Parser
g
t
((Down Int, ParsedLexemes t, Down Int),
FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
fieldPattern Parser
g
t
((Down Int, ParsedLexemes t, Down Int),
FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
`sepBy` ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma)
ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Down Int, ParsedLexemes t, Down Int),
Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Value l l d d) -> Pattern λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Value l l d d) -> Pattern l l d s
Abstract.literalPattern (((Down Int, ParsedLexemes t, Down Int),
Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
literal
ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Pattern λ l d s
forall l (d :: * -> *) (s :: * -> *). Pattern l l d s
Abstract.wildcardPattern Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword t
"_"
ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens (ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
pPattern
ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NonEmpty
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
NonEmpty (s (Pattern l l d d)) -> Pattern λ l d s
forall (s :: * -> *) l (d :: * -> *).
NonEmpty (s (Pattern l l d d)) -> Pattern l l d s
Abstract.tuplePattern
(NonEmpty
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NonEmpty
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a. a -> [a] -> NonEmpty a
(:|) (((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> [((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NonEmpty
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NonEmpty
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
pPattern Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NonEmpty
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
some (t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
terminator t
"," ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
pPattern)))
ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
[s (Pattern l l d d)] -> Pattern λ l d s
forall (s :: * -> *) l (d :: * -> *).
[s (Pattern l l d d)] -> Pattern l l d s
Abstract.listPattern ([((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a. TokenParsing m => m a -> m a
brackets (ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
pPattern Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
`sepBy1` ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma)
ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Pattern l l d d) -> Pattern λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Pattern l l d d) -> Pattern l l d s
Abstract.irrefutablePattern (((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"~" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
aPattern,
fieldPattern :: ParserT
((,) [[Lexeme t]])
g
t
(FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
fieldPattern = QualifiedName l
-> ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
QualifiedName λ -> s (Pattern l l d d) -> FieldPattern λ l d s
forall (s :: * -> *) l (d :: * -> *).
QualifiedName l -> s (Pattern l l d d) -> FieldPattern l l d s
Abstract.fieldPattern (QualifiedName l
-> ((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedVariable Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"=" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(FieldPattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
pPattern,
pPattern :: ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
pPattern = ParserT
((,) [[Lexeme t]])
g
t
(Pattern
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
pattern,
generalConstructor :: ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
generalConstructor = QualifiedName l
-> Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
QualifiedName λ -> Constructor λ l d s
forall l (d :: * -> *) (s :: * -> *).
QualifiedName l -> Constructor l l d s
Abstract.constructorReference (QualifiedName l
-> Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructor
ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Constructor λ l d s
forall l (d :: * -> *) (s :: * -> *). Constructor l l d s
Abstract.unitConstructor Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
terminator t
"(" ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
terminator t
")"
ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Constructor λ l d s
forall l (d :: * -> *) (s :: * -> *). Constructor l l d s
Abstract.emptyListConstructor Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
terminator t
"[" ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
terminator t
"]"
ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Int
-> Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Int -> Constructor λ l d s
forall l (d :: * -> *) (s :: * -> *). Int -> Constructor l l d s
Abstract.tupleConstructor (Int
-> Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ([Char] -> Int)
-> [Char]
-> Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int
forall a. Enum a => a -> a
succ (Int -> Int) -> ([Char] -> Int) -> [Char] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Char]
-> Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [Char]
-> ParserT
((,) [[Lexeme t]])
g
t
(Constructor
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed (ParserT ((,) [[Lexeme t]])) g t [Char]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [Char]
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens (ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [Char]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
some ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma),
variable :: ParserT ((,) [[Lexeme t]]) g t (Name l)
variable = ParserT ((,) [[Lexeme t]]) g t (Name l)
variableIdentifier ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens ParserT ((,) [[Lexeme t]]) g t (Name l)
variableSymbol,
qualifiedVariable :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedVariable = ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedVariableIdentifier ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedVariableSymbol,
constructor :: ParserT ((,) [[Lexeme t]]) g t (Name l)
constructor = ParserT ((,) [[Lexeme t]]) g t (Name l)
constructorIdentifier ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens ParserT ((,) [[Lexeme t]]) g t (Name l)
constructorSymbol,
qualifiedConstructor :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructor = ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructorIdentifier ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructorSymbol,
variableOperator :: ParserT ((,) [[Lexeme t]]) g t (Name l)
variableOperator = ParserT ((,) [[Lexeme t]]) g t (Name l)
variableSymbol ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
terminator t
"`" ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT ((,) [[Lexeme t]]) g t (Name l)
variableIdentifier ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
terminator t
"`",
qualifiedVariableOperator :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedVariableOperator = ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedVariableSymbol
ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
terminator t
"`" ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedVariableIdentifier ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
terminator t
"`",
constructorOperator :: ParserT ((,) [[Lexeme t]]) g t (Name l)
constructorOperator = ParserT ((,) [[Lexeme t]]) g t (Name l)
constructorSymbol ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
terminator t
"`" ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT ((,) [[Lexeme t]]) g t (Name l)
constructorIdentifier ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
terminator t
"`",
qualifiedConstructorOperator :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructorOperator = ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructorSymbol
ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
terminator t
"`" ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructorIdentifier ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
terminator t
"`",
operator :: ParserT ((,) [[Lexeme t]]) g t (Name l)
operator = ParserT ((,) [[Lexeme t]]) g t (Name l)
variableOperator ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT ((,) [[Lexeme t]]) g t (Name l)
constructorOperator,
qualifiedOperator :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedOperator = ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedVariableOperator ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructorOperator ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> [Char] -> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> [Char] -> m a
<?> [Char]
"qualified operator",
qualifiedVariableIdentifier :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedVariableIdentifier = ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. TokenParsing m => m a -> m a
token (Parser g t (Name l -> QualifiedName l)
forall (g :: (* -> *) -> *) l t.
(Apply g, Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t (Name l -> QualifiedName l)
nameQualifier Parser g t (Name l -> QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t (Name l)
variableIdentifier),
qualifiedConstructorIdentifier :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructorIdentifier = ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. TokenParsing m => m a -> m a
token (Parser g t (Name l -> QualifiedName l)
forall (g :: (* -> *) -> *) l t.
(Apply g, Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t (Name l -> QualifiedName l)
nameQualifier Parser g t (Name l -> QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t (Name l)
constructorIdentifier),
qualifiedTypeConstructor :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedTypeConstructor = ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructorIdentifier,
qualifiedVariableSymbol :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedVariableSymbol = ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. TokenParsing m => m a -> m a
token (Parser g t (Name l -> QualifiedName l)
forall (g :: (* -> *) -> *) l t.
(Apply g, Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t (Name l -> QualifiedName l)
nameQualifier Parser g t (Name l -> QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t (Name l)
variableSymbol),
qualifiedConstructorSymbol :: ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
qualifiedConstructorSymbol = ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. TokenParsing m => m a -> m a
token (Parser g t (Name l -> QualifiedName l)
forall (g :: (* -> *) -> *) l t.
(Apply g, Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t (Name l -> QualifiedName l)
nameQualifier Parser g t (Name l -> QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t (a -> b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT ((,) [[Lexeme t]]) g t (Name l)
constructorSymbol
ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe (ModuleName l) -> Name l -> QualifiedName l
forall λ.
Haskell λ =>
Maybe (ModuleName λ) -> Name λ -> QualifiedName λ
Abstract.qualifiedName Maybe (ModuleName l)
forall a. Maybe a
Nothing (Name l -> QualifiedName l)
-> (t -> Name l) -> t -> QualifiedName l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Name l
forall λ. Haskell λ => Text -> Name λ
Abstract.name (Text -> Name l) -> (t -> Text) -> t -> Name l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
Text.pack ([Char] -> Text) -> (t -> [Char]) -> t -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (t -> [Char]) -> t -> [Char]
forall t. TextualMonoid t => (t -> [Char]) -> t -> [Char]
toString t -> [Char]
forall a. Monoid a => a
mempty
(t -> QualifiedName l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
":" ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
-> ParserT ((,) [[Lexeme t]]) g t ()
-> ParserT ((,) [[Lexeme t]]) g t (QualifiedName l)
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (Char -> Bool) -> ParserT ((,) [[Lexeme t]]) g t ()
forall (m :: * -> *). InputCharParsing m => (Char -> Bool) -> m ()
notSatisfyChar Char -> Bool
isSymbol),
typeVar :: ParserT ((,) [[Lexeme t]]) g t (Name l)
typeVar = ParserT ((,) [[Lexeme t]]) g t (Name l)
variableIdentifier,
typeConstructor :: ParserT ((,) [[Lexeme t]]) g t (Name l)
typeConstructor = ParserT ((,) [[Lexeme t]]) g t (Name l)
constructorIdentifier,
variableIdentifier :: ParserT ((,) [[Lexeme t]]) g t (Name l)
variableIdentifier = Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
forall (g :: (* -> *) -> *) l t.
(Apply g, Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t t -> Parser g t (Name l)
nameToken Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t t
variableLexeme,
constructorIdentifier :: ParserT ((,) [[Lexeme t]]) g t (Name l)
constructorIdentifier = Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
forall (g :: (* -> *) -> *) l t.
(Apply g, Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t t -> Parser g t (Name l)
nameToken Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t t
constructorLexeme,
variableSymbol :: ParserT ((,) [[Lexeme t]]) g t (Name l)
variableSymbol = Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
forall (g :: (* -> *) -> *) l t.
(Apply g, Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t t -> Parser g t (Name l)
nameToken Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t t
variableSymbolLexeme,
constructorSymbol :: ParserT ((,) [[Lexeme t]]) g t (Name l)
constructorSymbol = Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> ParserT ((,) [[Lexeme t]]) g t (Name l)
forall (g :: (* -> *) -> *) l t.
(Apply g, Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t t -> Parser g t (Name l)
nameToken Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t t
constructorSymbolLexeme,
literal :: ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
literal = ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. TokenParsing m => m a -> m a
token ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
literalLexeme,
literalLexeme :: ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
literalLexeme = Integer
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Integer -> Value λ l d s
forall l (d :: * -> *) (s :: * -> *). Integer -> Value l l d s
Abstract.integerLiteral (Integer
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t Integer
-> ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t Integer
integerLexeme ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Rational
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Rational -> Value λ l d s
forall l (d :: * -> *) (s :: * -> *). Rational -> Value l l d s
Abstract.floatingLiteral (Rational
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t Rational
-> ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t Rational
floatLexeme
ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Char
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Char -> Value λ l d s
forall l (d :: * -> *) (s :: * -> *). Char -> Value l l d s
Abstract.charLiteral (Char
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t Char
charLexeme ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Text -> Value λ l d s
forall l (d :: * -> *) (s :: * -> *). Text -> Value l l d s
Abstract.stringLiteral (Text
-> Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ParserT ((,) [[Lexeme t]]) g t Text
-> ParserT
((,) [[Lexeme t]])
g
t
(Value
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t Text
stringLexeme,
doubleColon :: ParserT ((,) [[Lexeme t]]) g t ()
doubleColon = t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"::",
rightDoubleArrow :: ParserT ((,) [[Lexeme t]]) g t ()
rightDoubleArrow = t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"=>",
rightArrow :: ParserT ((,) [[Lexeme t]]) g t ()
rightArrow = t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"->",
leftArrow :: ParserT ((,) [[Lexeme t]]) g t ()
leftArrow = t -> ParserT ((,) [[Lexeme t]]) g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
"<-",
integer :: ParserT ((,) [[Lexeme t]]) g t Integer
integer = ParserT ((,) [[Lexeme t]]) g t Integer
-> ParserT ((,) [[Lexeme t]]) g t Integer
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. TokenParsing m => m a -> m a
token ParserT ((,) [[Lexeme t]]) g t Integer
integerLexeme,
float :: ParserT ((,) [[Lexeme t]]) g t Rational
float = ParserT ((,) [[Lexeme t]]) g t Rational
-> ParserT ((,) [[Lexeme t]]) g t Rational
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. TokenParsing m => m a -> m a
token ParserT ((,) [[Lexeme t]]) g t Rational
floatLexeme,
integerLexeme :: ParserT ((,) [[Lexeme t]]) g t Integer
integerLexeme = (Integer, [Char]) -> Integer
forall a b. (a, b) -> a
fst ((Integer, [Char]) -> Integer)
-> ([(Integer, [Char])] -> (Integer, [Char]))
-> [(Integer, [Char])]
-> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Integer, [Char])] -> (Integer, [Char])
forall a. HasCallStack => [a] -> a
head
([(Integer, [Char])] -> Integer)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Integer, [Char])]
-> ParserT ((,) [[Lexeme t]]) g t Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"0o" Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"0O") Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Integer, [Char])]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Integer, [Char])]
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (ReadS Integer
forall a. (Eq a, Num a) => ReadS a
Numeric.readOct ReadS Integer -> (t -> [Char]) -> t -> [(Integer, [Char])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (t -> [Char]) -> t -> [Char]
forall t. TextualMonoid t => (t -> [Char]) -> t -> [Char]
toString t -> [Char]
forall a. Monoid a => a
mempty (t -> [(Integer, [Char])])
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Integer, [Char])]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed (ParserT ((,) [[Lexeme t]])) g t t
octal)
Fixed (ParserT ((,) [[Lexeme t]])) g t [(Integer, [Char])]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Integer, [Char])]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Integer, [Char])]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> (ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"0x" Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"0X") Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Integer, [Char])]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Integer, [Char])]
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (ReadS Integer
forall a. (Eq a, Num a) => ReadS a
Numeric.readHex ReadS Integer -> (t -> [Char]) -> t -> [(Integer, [Char])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (t -> [Char]) -> t -> [Char]
forall t. TextualMonoid t => (t -> [Char]) -> t -> [Char]
toString t -> [Char]
forall a. Monoid a => a
mempty (t -> [(Integer, [Char])])
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Integer, [Char])]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed (ParserT ((,) [[Lexeme t]])) g t t
hexadecimal)
Fixed (ParserT ((,) [[Lexeme t]])) g t [(Integer, [Char])]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Integer, [Char])]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Integer, [Char])]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> ReadS Integer
forall a. (Eq a, Num a) => ReadS a
Numeric.readDec ReadS Integer -> (t -> [Char]) -> t -> [(Integer, [Char])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (t -> [Char]) -> t -> [Char]
forall t. TextualMonoid t => (t -> [Char]) -> t -> [Char]
toString t -> [Char]
forall a. Monoid a => a
mempty (t -> [(Integer, [Char])])
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Integer, [Char])]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed (ParserT ((,) [[Lexeme t]])) g t t
decimal
Fixed (ParserT ((,) [[Lexeme t]])) g t [(Integer, [Char])]
-> ParserT ((,) [[Lexeme t]]) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Integer, [Char])]
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> ParserT ((,) [[Lexeme t]]) g t ()
forall a.
Show a =>
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> ParserT ((,) [[Lexeme t]]) g t ()
forall (m :: * -> *) a. (Parsing m, Show a) => m a -> m ()
notFollowedBy (ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"." Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Fixed (ParserT ((,) [[Lexeme t]])) g t t
decimal Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Fixed (ParserT ((,) [[Lexeme t]])) g t t
exponent)),
floatLexeme :: ParserT ((,) [[Lexeme t]]) g t Rational
floatLexeme = (Rational, [Char]) -> Rational
forall a b. (a, b) -> a
fst ((Rational, [Char]) -> Rational)
-> (t -> (Rational, [Char])) -> t -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Rational, [Char])] -> (Rational, [Char])
forall a. HasCallStack => [a] -> a
head ([(Rational, [Char])] -> (Rational, [Char]))
-> (t -> [(Rational, [Char])]) -> t -> (Rational, [Char])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadS Rational
forall a. RealFrac a => ReadS a
Numeric.readFloat ReadS Rational -> (t -> [Char]) -> t -> [(Rational, [Char])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (t -> [Char]) -> t -> [Char]
forall t. TextualMonoid t => (t -> [Char]) -> t -> [Char]
toString t -> [Char]
forall a. Monoid a => a
mempty
(t -> Rational)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> ParserT ((,) [[Lexeme t]]) g t Rational
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Fixed (ParserT ((,) [[Lexeme t]])) g t t
decimal Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a. Semigroup a => a -> a -> a
<> ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"." Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a. Semigroup a => a -> a -> a
<> Fixed (ParserT ((,) [[Lexeme t]])) g t t
decimal Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a. Semigroup a => a -> a -> a
<> (Fixed (ParserT ((,) [[Lexeme t]])) g t t
exponent Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a. Monoid a => a
mempty)
Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Fixed (ParserT ((,) [[Lexeme t]])) g t t
decimal Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a. Semigroup a => a -> a -> a
<> Fixed (ParserT ((,) [[Lexeme t]])) g t t
exponent),
decimal :: Fixed (ParserT ((,) [[Lexeme t]])) g t t
decimal = (Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile1 Char -> Bool
Char.isDigit Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> [Char] -> m a
<?> [Char]
"decimal number",
octal :: Fixed (ParserT ((,) [[Lexeme t]])) g t t
octal = (Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile1 Char -> Bool
Char.isOctDigit Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> [Char] -> m a
<?> [Char]
"octal number",
hexadecimal :: Fixed (ParserT ((,) [[Lexeme t]])) g t t
hexadecimal = (Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile1 Char -> Bool
Char.isHexDigit Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> [Char] -> m a
<?> [Char]
"hexadecimal number",
exponent :: Fixed (ParserT ((,) [[Lexeme t]])) g t t
exponent = (ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"e" Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"E") Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a. Semigroup a => a -> a -> a
<> (ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"+" Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"-" Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a. Monoid a => a
mempty) Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a. Semigroup a => a -> a -> a
<> Fixed (ParserT ((,) [[Lexeme t]])) g t t
decimal,
charLiteral :: ParserT ((,) [[Lexeme t]]) g t Char
charLiteral = ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. TokenParsing m => m a -> m a
token ParserT ((,) [[Lexeme t]]) g t Char
charLexeme,
charLexeme :: ParserT ((,) [[Lexeme t]]) g t Char
charLexeme = Char -> ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'\''
ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t Char
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ((Char -> Bool) -> ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
Text.Parser.Char.satisfy (\Char
c-> Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' ' Bool -> Bool -> Bool
|| Bool -> Bool
not (Char -> Bool
Char.isSpace Char
c) Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\'' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\\')
ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT ((,) [[Lexeme t]]) g t Char
escape)
ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t Char
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'\'',
stringLiteral :: ParserT ((,) [[Lexeme t]]) g t Text
stringLiteral = ParserT ((,) [[Lexeme t]]) g t Text
-> ParserT ((,) [[Lexeme t]]) g t Text
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. TokenParsing m => m a -> m a
token ParserT ((,) [[Lexeme t]]) g t Text
stringLexeme ParserT ((,) [[Lexeme t]]) g t Text
-> [Char] -> ParserT ((,) [[Lexeme t]]) g t Text
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> [Char] -> m a
<?> [Char]
"string literal",
stringLexeme :: ParserT ((,) [[Lexeme t]]) g t Text
stringLexeme = [Char] -> Text
Text.pack ([Char] -> Text) -> (t -> [Char]) -> t -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (t -> [Char]) -> t -> [Char]
forall t. TextualMonoid t => (t -> [Char]) -> t -> [Char]
toString t -> [Char]
forall a. Monoid a => a
mempty (t -> Text)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> ParserT ((,) [[Lexeme t]]) g t Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(Char -> ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'"'
ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall (p :: * -> *) a. (Alternative p, Monoid a) => p a -> p a
concatMany ((Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile1 (\Char
c-> Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' ' Bool -> Bool -> Bool
|| Bool -> Bool
not (Char -> Bool
Char.isSpace Char
c) Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'"' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\\')
Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Char -> t
forall t. TextualMonoid t => Char -> t
Textual.singleton (Char -> t)
-> ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT ((,) [[Lexeme t]]) g t Char
escape
Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Char -> ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'\\'
ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t Char
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Char -> ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'&' ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile1 Char -> Bool
Char.isSpace Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t Char
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'\\')
ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> t -> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure t
"")
Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> ParserT ((,) [[Lexeme t]]) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParserT ((,) [[Lexeme t]]) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'"'),
escape :: ParserT ((,) [[Lexeme t]]) g t Char
escape = ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"\\" Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t Char
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (ParserT ((,) [[Lexeme t]]) g t Char
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t Char
charEscape ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserT ((,) [[Lexeme t]]) g t Char
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t Char
asciiEscape
ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t Char
-> ParserT ((,) [[Lexeme t]]) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Int -> Char
Char.chr (Int -> Char)
-> ([(Int, [Char])] -> Int) -> [(Int, [Char])] -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, [Char]) -> Int
forall a b. (a, b) -> a
fst ((Int, [Char]) -> Int)
-> ([(Int, [Char])] -> (Int, [Char])) -> [(Int, [Char])] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Int, [Char])] -> (Int, [Char])
forall a. HasCallStack => [a] -> a
head ([(Int, [Char])] -> Char)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Int, [Char])]
-> ParserT ((,) [[Lexeme t]]) g t Char
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ReadS Int
forall a. (Eq a, Num a) => ReadS a
Numeric.readDec ReadS Int -> (t -> [Char]) -> t -> [(Int, [Char])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (t -> [Char]) -> t -> [Char]
forall t. TextualMonoid t => (t -> [Char]) -> t -> [Char]
toString t -> [Char]
forall a. Monoid a => a
mempty (t -> [(Int, [Char])])
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Int, [Char])]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed (ParserT ((,) [[Lexeme t]])) g t t
decimal
Fixed (ParserT ((,) [[Lexeme t]])) g t [(Int, [Char])]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Int, [Char])]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Int, [Char])]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"o" Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Int, [Char])]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Int, [Char])]
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (ReadS Int
forall a. (Eq a, Num a) => ReadS a
Numeric.readOct ReadS Int -> (t -> [Char]) -> t -> [(Int, [Char])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (t -> [Char]) -> t -> [Char]
forall t. TextualMonoid t => (t -> [Char]) -> t -> [Char]
toString t -> [Char]
forall a. Monoid a => a
mempty (t -> [(Int, [Char])])
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Int, [Char])]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed (ParserT ((,) [[Lexeme t]])) g t t
octal)
Fixed (ParserT ((,) [[Lexeme t]])) g t [(Int, [Char])]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Int, [Char])]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Int, [Char])]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"x"
Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Int, [Char])]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Int, [Char])]
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (ReadS Int
forall a. (Eq a, Num a) => ReadS a
Numeric.readHex ReadS Int -> (t -> [Char]) -> t -> [(Int, [Char])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (t -> [Char]) -> t -> [Char]
forall t. TextualMonoid t => (t -> [Char]) -> t -> [Char]
toString t -> [Char]
forall a. Monoid a => a
mempty (t -> [(Int, [Char])])
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [(Int, [Char])]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed (ParserT ((,) [[Lexeme t]])) g t t
hexadecimal)))
}
variableLexeme, constructorLexeme, variableSymbolLexeme, constructorSymbolLexeme,
identifierTail :: (Rank2.Apply g, Ord t, Show t, TextualMonoid t) => Parser g t t
variableLexeme :: forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t t
variableLexeme = (t -> Bool)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
(a -> Bool)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter (t -> Set t -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.notMember` Set t
forall t. (Ord t, TextualMonoid t) => Set t
reservedWords) ((Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
satisfyCharInput Char -> Bool
varStart Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a. Semigroup a => a -> a -> a
<> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t t
identifierTail) Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> [Char] -> m a
<?> [Char]
"variable"
where varStart :: Char -> Bool
varStart Char
c = Char -> Bool
Char.isLower Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_'
constructorLexeme :: forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t t
constructorLexeme = (Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
satisfyCharInput Char -> Bool
Char.isUpper Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a. Semigroup a => a -> a -> a
<> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t t
identifierTail Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> [Char] -> m a
<?> [Char]
"constructor"
variableSymbolLexeme :: forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t t
variableSymbolLexeme = (t -> Bool)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
(a -> Bool)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter t -> Bool
forall {a}. (TextualMonoid a, Ord a) => a -> Bool
validSymbol ((Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile1 Char -> Bool
isSymbol) Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> [Char] -> m a
<?> [Char]
"variable symbol"
where validSymbol :: a -> Bool
validSymbol a
tok = a -> Maybe Char
forall t. TextualMonoid t => t -> Maybe Char
Textual.characterPrefix a
tok Maybe Char -> Maybe Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char -> Maybe Char
forall a. a -> Maybe a
Just Char
':' Bool -> Bool -> Bool
&& a
tok a -> Set a -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.notMember` Set a
forall t. (Ord t, TextualMonoid t) => Set t
reservedOperators
constructorSymbolLexeme :: forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t t
constructorSymbolLexeme = (t -> Bool)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
(a -> Bool)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter (t -> Set t -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.notMember` Set t
forall t. (Ord t, TextualMonoid t) => Set t
reservedOperators) (ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
":" Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a. Semigroup a => a -> a -> a
<> (Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile Char -> Bool
isSymbol)
identifierTail :: forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t t
identifierTail = (Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile Char -> Bool
isNameTailChar
reservedWords, reservedOperators :: (Ord t, TextualMonoid t) => Set.Set t
reservedWords :: forall t. (Ord t, TextualMonoid t) => Set t
reservedWords = [t] -> Set t
forall a. Ord a => [a] -> Set a
Set.fromList [t
"case", t
"class", t
"data", t
"default", t
"deriving", t
"do", t
"else",
t
"foreign", t
"if", t
"import", t
"in", t
"infix", t
"infixl",
t
"infixr", t
"instance", t
"let", t
"module", t
"newtype", t
"of",
t
"then", t
"type", t
"where", t
"_"]
reservedOperators :: forall t. (Ord t, TextualMonoid t) => Set t
reservedOperators = [t] -> Set t
forall a. Ord a => [a] -> Set a
Set.fromList [t
"--", t
"..", t
":", t
"::", t
"=", t
"\\", t
"|", t
"<-", t
"->", t
"@", t
"~", t
"=>"]
asciiSymbols :: Set.Set Char
asciiSymbols :: Set Char
asciiSymbols = [Char] -> Set Char
forall a. Ord a => [a] -> Set a
Set.fromList [Char]
"!#$%&*+./<=>?@\\^|-~:"
moduleId :: (Rank2.Apply g, Abstract.Haskell l, Ord t, Show t, TextualMonoid t) => Parser g t (Abstract.ModuleName l)
moduleId :: forall (g :: (* -> *) -> *) l t.
(Apply g, Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t (ModuleName l)
moduleId = NonEmpty (Name l) -> ModuleName l
forall λ. Haskell λ => NonEmpty (Name λ) -> ModuleName λ
Abstract.moduleName (NonEmpty (Name l) -> ModuleName l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (NonEmpty (Name l))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed (ParserT ((,) [[Lexeme t]])) g t (NonEmpty (Name l))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (NonEmpty (Name l))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. TokenParsing m => m a -> m a
token Fixed (ParserT ((,) [[Lexeme t]])) g t (NonEmpty (Name l))
forall (g :: (* -> *) -> *) l t.
(Apply g, Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t (NonEmpty (Name l))
moduleLexeme
moduleLexeme :: (Rank2.Apply g, Abstract.Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t (NonEmpty (Abstract.Name l))
moduleLexeme :: forall (g :: (* -> *) -> *) l t.
(Apply g, Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t (NonEmpty (Name l))
moduleLexeme = (Text -> Name l
forall λ. Haskell λ => Text -> Name λ
Abstract.name (Text -> Name l) -> (t -> Text) -> t -> Name l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
Text.pack ([Char] -> Text) -> (t -> [Char]) -> t -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (t -> [Char]) -> t -> [Char]
forall t. TextualMonoid t => (t -> [Char]) -> t -> [Char]
toString t -> [Char]
forall a. Monoid a => a
mempty (t -> Name l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t t
constructorLexeme Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> [Char] -> m a
<?> [Char]
"module name")
Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (NonEmpty (Name l))
forall (m :: * -> *) a sep.
Alternative m =>
m a -> m sep -> m (NonEmpty a)
`sepByNonEmpty` ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"."
nameQualifier :: (Rank2.Apply g, Abstract.Haskell l, Ord t, Show t, TextualMonoid t)
=> Parser g t (Abstract.Name l -> Abstract.QualifiedName l)
nameQualifier :: forall (g :: (* -> *) -> *) l t.
(Apply g, Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t (Name l -> QualifiedName l)
nameQualifier =
Maybe (ModuleName l) -> Name l -> QualifiedName l
forall λ.
Haskell λ =>
Maybe (ModuleName λ) -> Name λ -> QualifiedName λ
Abstract.qualifiedName
(Maybe (ModuleName l) -> Name l -> QualifiedName l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe (ModuleName l))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (Name l -> QualifiedName l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe (ModuleName l))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe a)
forall (m :: * -> *) a.
DeterministicParsing m =>
m a -> m (Maybe a)
takeOptional (Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t a
storeToken (NonEmpty (Name l) -> ModuleName l
forall λ. Haskell λ => NonEmpty (Name λ) -> ModuleName λ
Abstract.moduleName (NonEmpty (Name l) -> ModuleName l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (NonEmpty (Name l))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed (ParserT ((,) [[Lexeme t]])) g t (NonEmpty (Name l))
forall (g :: (* -> *) -> *) l t.
(Apply g, Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t (NonEmpty (Name l))
moduleLexeme Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
".")
Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (ModuleName l)
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall a.
Show a =>
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (m :: * -> *) a. (Parsing m, Show a) => m a -> m ()
notFollowedBy (Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t t
constructorLexeme Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"."
Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (t -> Bool)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
(a -> Bool)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter (t -> Set t -> Bool
forall a. Eq a => a -> Set a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Set t
forall t. (Ord t, TextualMonoid t) => Set t
reservedWords) ((Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile1 Char -> Bool
Char.isLower)))
asciiEscape, charEscape, controlEscape :: (Rank2.Apply g, Ord t, Show t, TextualMonoid t) => Parser g t Char
charEscape :: forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t Char
charEscape = Char
'\a' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'a'
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Char
'\b' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'b'
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Char
'\f' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'f'
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Char
'\n' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'n'
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Char
'\r' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'r'
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Char
'\t' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
't'
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Char
'\v' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'v'
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Char -> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'\\'
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Char -> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'"'
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Char -> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'\''
asciiEscape :: forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t Char
asciiEscape = Char -> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'^' Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t Char
controlEscape
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\NUL' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"NUL"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\SOH' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"SOH"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\STX' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"STX"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\ETX' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"ETX"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\EOT' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"EOT"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\ENQ' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"ENQ"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\ACK' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"ACK"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\BEL' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"BEL"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\BS' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"BS"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\HT' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"HT"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\LF' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"LF"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\VT' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"VT"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\FF' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"FF"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\CR' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"CR"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\SO' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"SO"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\SI' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"SI"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\DLE' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"DLE"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\DC1' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"DC1"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\DC2' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"DC2"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\DC3' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"DC3"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\DC4' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"DC4"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\NAK' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"NAK"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\SYN' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"SYN"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\ETB' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"ETB"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\CAN' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"CAN"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\EM' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"EM"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\SUB' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"SUB"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\ESC' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"ESC"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\FS' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"FS"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\GS' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"GS"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\RS' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"RS"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\US' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"US"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\SP' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"SP"
Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Char
'\DEL' Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall a b.
a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"DEL"
controlEscape :: forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t Char
controlEscape = Int -> Char
Char.chr (Int -> Char) -> (Char -> Int) -> Char -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (-Int
64 Int -> Int -> Int
forall a. Num a => a -> a -> a
+) (Int -> Int) -> (Char -> Int) -> Char -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
Char.ord (Char -> Char)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Bool) -> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
Text.Parser.Char.satisfy (\Char
c-> Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'@' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'_')
type NodeWrap s = Reserializer.Wrapped (Down Int) s
wrap :: (Rank2.Apply g, Ord t, TextualMonoid t) => Parser g t a -> Parser g t (NodeWrap t a)
wrap :: forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap = (\Fixed (ParserT ((,) [[Lexeme t]])) g t (ParsedLexemes t, a)
p-> (Down Int -> (ParsedLexemes t, a) -> Down Int -> NodeWrap t a)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Down Int)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (ParsedLexemes t, a)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Down Int)
-> Parser g t (NodeWrap t a)
forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 Down Int -> (ParsedLexemes t, a) -> Down Int -> NodeWrap t a
forall {a} {b} {b} {c}. a -> (b, b) -> c -> ((a, b, c), b)
surround Fixed (ParserT ((,) [[Lexeme t]])) g t (Down Int)
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserPosition (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *). InputParsing m => m (ParserPosition m)
getSourcePos Fixed (ParserT ((,) [[Lexeme t]])) g t (ParsedLexemes t, a)
p Fixed (ParserT ((,) [[Lexeme t]])) g t (Down Int)
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserPosition (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *). InputParsing m => m (ParserPosition m)
getSourcePos)
(Fixed (ParserT ((,) [[Lexeme t]])) g t (ParsedLexemes t, a)
-> Parser g t (NodeWrap t a))
-> (Parser g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (ParsedLexemes t, a))
-> Parser g t a
-> Parser g t (NodeWrap t a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([[Lexeme t]], (ParsedLexemes (ZonkAny 0), a))
-> ([[Lexeme t]], (ParsedLexemes t, a)))
-> ParserT ((,) [[Lexeme t]]) g t (ParsedLexemes (ZonkAny 0), a)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (ParsedLexemes t, a)
forall b (m :: * -> *) a (g :: (* -> *) -> *) s.
AmbiguityDecidable b =>
(m a -> m b) -> ParserT m g s a -> ParserT m g s b
tmap ([[Lexeme t]], (ParsedLexemes (ZonkAny 0), a))
-> ([[Lexeme t]], (ParsedLexemes t, a))
forall {a} {t :: * -> *} {s} {s} {b}.
(Monoid a, Foldable t) =>
(t [Lexeme s], (ParsedLexemes s, b)) -> (a, (ParsedLexemes s, b))
store (ParserT ((,) [[Lexeme t]]) g t (ParsedLexemes (ZonkAny 0), a)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (ParsedLexemes t, a))
-> (Parser g t a
-> ParserT ((,) [[Lexeme t]]) g t (ParsedLexemes (ZonkAny 0), a))
-> Parser g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (ParsedLexemes t, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((,) ([Lexeme (ZonkAny 0)] -> ParsedLexemes (ZonkAny 0)
forall s. [Lexeme s] -> ParsedLexemes s
Trailing []) (a -> (ParsedLexemes (ZonkAny 0), a))
-> Parser g t a
-> ParserT ((,) [[Lexeme t]]) g t (ParsedLexemes (ZonkAny 0), a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>)
where store :: (t [Lexeme s], (ParsedLexemes s, b)) -> (a, (ParsedLexemes s, b))
store (t [Lexeme s]
wss, (Trailing [], b
a)) = (a
forall a. Monoid a => a
mempty, ([Lexeme s] -> ParsedLexemes s
forall s. [Lexeme s] -> ParsedLexemes s
Trailing (t [Lexeme s] -> [Lexeme s]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat t [Lexeme s]
wss), b
a))
surround :: a -> (b, b) -> c -> ((a, b, c), b)
surround a
start (b
ls, b
val) c
end = ((a
start, b
ls, c
end), b
val)
rewrap :: (NodeWrap t a -> b) -> NodeWrap t a -> NodeWrap t b
rewrap :: forall t a b. (NodeWrap t a -> b) -> NodeWrap t a -> NodeWrap t b
rewrap NodeWrap t a -> b
f node :: NodeWrap t a
node@((Down Int
start, ParsedLexemes t
_, Down Int
end), a
_) = ((Down Int
start, ParsedLexemes t
forall a. Monoid a => a
mempty, Down Int
end), NodeWrap t a -> b
f NodeWrap t a
node)
unwrap :: NodeWrap t a -> a
unwrap :: forall t a. NodeWrap t a -> a
unwrap ((Down Int, ParsedLexemes t, Down Int)
_, a
x) = a
x
instance (Rank2.Apply g, Ord t, Show t, TextualMonoid t) => TokenParsing (Parser g t) where
someSpace :: Parser g t ()
someSpace = Parser g t ()
forall (m :: * -> *). LexicalParsing m => m ()
someLexicalSpace
token :: forall a. Parser g t a -> Parser g t a
token = Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall a. Parser g t a -> Parser g t a
forall (m :: * -> *) a. LexicalParsing m => m a -> m a
lexicalToken
instance (Rank2.Apply g, Ord t, Show t, TextualMonoid t) => LexicalParsing (Parser g t) where
lexicalComment :: Parser g t ()
lexicalComment = Parser g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t ()
comment
lexicalWhiteSpace :: Parser g t ()
lexicalWhiteSpace = Parser g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t ()
whiteSpace
isIdentifierStartChar :: Char -> Bool
isIdentifierStartChar = Char -> Bool
Char.isLetter
isIdentifierFollowChar :: Char -> Bool
isIdentifierFollowChar = Char -> Bool
isNameTailChar
identifierToken :: Parser g t (ParserInput (Parser g t))
-> Parser g t (ParserInput (Parser g t))
identifierToken Parser g t (ParserInput (Parser g t))
word = Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a. Parser g t a -> Parser g t a
forall (m :: * -> *) a. LexicalParsing m => m a -> m a
lexicalToken ((t -> Bool)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
(a -> Bool)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter (t -> Set t -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` Set t
forall t. (Ord t, TextualMonoid t) => Set t
reservedWords) Fixed (ParserT ((,) [[Lexeme t]])) g t t
Parser g t (ParserInput (Parser g t))
word)
lexicalToken :: forall a. Parser g t a -> Parser g t a
lexicalToken Parser g t a
p = Parser g t a -> Parser g t a
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t a
storeToken Parser g t a
p Parser g t a -> Parser g t () -> Parser g t a
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser g t ()
forall (m :: * -> *). LexicalParsing m => m ()
lexicalWhiteSpace
keyword :: ParserInput (Parser g t) -> Parser g t ()
keyword = t -> Parser g t ()
ParserInput (Parser g t) -> Parser g t ()
forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword
keyword :: (Rank2.Apply g, Ord s, Show s, TextualMonoid s) => s -> Parser g s ()
keyword :: forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
keyword s
s = Fixed (ParserT ((,) [[Lexeme s]])) g s ()
-> Fixed (ParserT ((,) [[Lexeme s]])) g s ()
forall a.
Fixed (ParserT ((,) [[Lexeme s]])) g s a
-> Fixed (ParserT ((,) [[Lexeme s]])) g s a
forall (m :: * -> *) a. LexicalParsing m => m a -> m a
lexicalToken (ParserInput (Fixed (ParserT ((,) [[Lexeme s]])) g s)
-> Fixed
(ParserT ((,) [[Lexeme s]]))
g
s
(ParserInput (Fixed (ParserT ((,) [[Lexeme s]])) g s))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string s
ParserInput (Fixed (ParserT ((,) [[Lexeme s]])) g s)
s
Fixed (ParserT ((,) [[Lexeme s]])) g s s
-> Fixed (ParserT ((,) [[Lexeme s]])) g s ()
-> Fixed (ParserT ((,) [[Lexeme s]])) g s ()
forall a b.
Fixed (ParserT ((,) [[Lexeme s]])) g s a
-> Fixed (ParserT ((,) [[Lexeme s]])) g s b
-> Fixed (ParserT ((,) [[Lexeme s]])) g s b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Char -> Bool) -> Fixed (ParserT ((,) [[Lexeme s]])) g s ()
forall (m :: * -> *). InputCharParsing m => (Char -> Bool) -> m ()
notSatisfyChar Char -> Bool
isNameTailChar
Fixed (ParserT ((,) [[Lexeme s]])) g s ()
-> Fixed (ParserT ((,) [[Lexeme s]])) g s ()
-> Fixed (ParserT ((,) [[Lexeme s]])) g s ()
forall a b.
Fixed (ParserT ((,) [[Lexeme s]])) g s a
-> Fixed (ParserT ((,) [[Lexeme s]])) g s b
-> Fixed (ParserT ((,) [[Lexeme s]])) g s a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ([[Lexeme s]], ()) -> Fixed (ParserT ((,) [[Lexeme s]])) g s ()
forall (m :: * -> *) s a (g :: (* -> *) -> *).
(Applicative m, Ord s) =>
m a -> ParserT m g s a
lift ([[TokenType -> s -> Lexeme s
forall s. TokenType -> s -> Lexeme s
Token TokenType
Keyword s
s]], ()))
Fixed (ParserT ((,) [[Lexeme s]])) g s ()
-> [Char] -> Fixed (ParserT ((,) [[Lexeme s]])) g s ()
forall a.
Fixed (ParserT ((,) [[Lexeme s]])) g s a
-> [Char] -> Fixed (ParserT ((,) [[Lexeme s]])) g s a
forall (m :: * -> *) a. Parsing m => m a -> [Char] -> m a
<?> ([Char]
"keyword " [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> s -> [Char]
forall a. Show a => a -> [Char]
show s
s)
storeToken :: (Rank2.Apply g, Ord t, TextualMonoid t) => Parser g t a -> Parser g t a
storeToken :: forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t a
storeToken Parser g t a
p = (t, a) -> a
forall a b. (a, b) -> b
snd ((t, a) -> a)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (t, a) -> Parser g t a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (([[Lexeme t]], (t, a)) -> ([[Lexeme t]], (t, a)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (t, a)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (t, a)
forall b (m :: * -> *) a (g :: (* -> *) -> *) s.
AmbiguityDecidable b =>
(m a -> m b) -> ParserT m g s a -> ParserT m g s b
tmap ([[Lexeme t]], (t, a)) -> ([[Lexeme t]], (t, a))
forall {a} {b}. ([[Lexeme a]], (a, b)) -> ([[Lexeme a]], (a, b))
addOtherToken (Parser g t a
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t), a)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t), a)
forall (m :: * -> *) a.
ConsumedInputParsing m =>
m a -> m (ParserInput m, a)
match Parser g t a
p)
where addOtherToken :: ([[Lexeme a]], (a, b)) -> ([[Lexeme a]], (a, b))
addOtherToken ([], (a
i, b
x)) = ([[TokenType -> a -> Lexeme a
forall s. TokenType -> s -> Lexeme s
Token TokenType
Other a
i]], (a
i, b
x))
addOtherToken ([[Lexeme a]]
t, (a
i, b
x)) = ([[Lexeme a]]
t, (a
i, b
x))
isLineChar, isNameTailChar, isSymbol :: Char -> Bool
isLineChar :: Char -> Bool
isLineChar Char
c = Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\n' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\r' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\f'
isNameTailChar :: Char -> Bool
isNameTailChar Char
c = Char -> Bool
Char.isAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\''
isSymbol :: Char -> Bool
isSymbol Char
c = if Char -> Bool
Char.isAscii Char
c then Char
c Char -> Set Char -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set Char
asciiSymbols else Char -> Bool
Char.isSymbol Char
c Bool -> Bool -> Bool
|| Char -> Bool
Char.isPunctuation Char
c
delimiter, terminator :: (Rank2.Apply g, Ord t, Show t, TextualMonoid t) => t -> Parser g t ()
delimiter :: forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
delimiter t
s = Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. LexicalParsing m => m a -> m a
lexicalToken (Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a b. (a -> b) -> a -> b
$
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
s
Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (Char -> Bool) -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (m :: * -> *). InputCharParsing m => (Char -> Bool) -> m ()
notSatisfyChar Char -> Bool
isSymbol
Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ([[Lexeme t]], ()) -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (m :: * -> *) s a (g :: (* -> *) -> *).
(Applicative m, Ord s) =>
m a -> ParserT m g s a
lift ([[TokenType -> t -> Lexeme t
forall s. TokenType -> s -> Lexeme s
Token TokenType
Delimiter t
s]], ()))
Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> [Char] -> m a
<?> ([Char]
"delimiter " [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> t -> [Char]
forall a. Show a => a -> [Char]
show t
s)
terminator :: forall (g :: (* -> *) -> *) s.
(Apply g, Ord s, Show s, TextualMonoid s) =>
s -> Parser g s ()
terminator t
s = Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. LexicalParsing m => m a -> m a
lexicalToken (Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a b. (a -> b) -> a -> b
$ ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
s Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ([[Lexeme t]], ()) -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (m :: * -> *) s a (g :: (* -> *) -> *).
(Applicative m, Ord s) =>
m a -> ParserT m g s a
lift ([[TokenType -> t -> Lexeme t
forall s. TokenType -> s -> Lexeme s
Token TokenType
Delimiter t
s]], ()))
Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> [Char] -> m a
<?> ([Char]
"terminating delimiter " [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> t -> [Char]
forall a. Show a => a -> [Char]
show t
s)
nameToken :: (Rank2.Apply g, Abstract.Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t t -> Parser g t (Abstract.Name l)
nameToken :: forall (g :: (* -> *) -> *) l t.
(Apply g, Haskell l, Ord t, Show t, TextualMonoid t) =>
Parser g t t -> Parser g t (Name l)
nameToken Parser g t t
p = Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. TokenParsing m => m a -> m a
token (Text -> Name l
forall λ. Haskell λ => Text -> Name λ
Abstract.name (Text -> Name l) -> (t -> Text) -> t -> Name l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
Text.pack ([Char] -> Text) -> (t -> [Char]) -> t -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (t -> [Char]) -> t -> [Char]
forall t. TextualMonoid t => (t -> [Char]) -> t -> [Char]
toString t -> [Char]
forall a. Monoid a => a
mempty (t -> Name l)
-> Parser g t t -> Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser g t t
p)
whiteSpace :: (Rank2.Apply g, Ord t, Show t, TextualMonoid t) => Parser g t ()
whiteSpace :: forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t ()
whiteSpace = Fixed (ParserT ((,) [[Lexeme t]])) g t ()
spaceChars Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (m :: * -> *) a. DeterministicParsing m => m a -> m ()
skipAll (Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (m :: * -> *). LexicalParsing m => m ()
lexicalComment Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
spaceChars) Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> [Char] -> m a
<?> [Char]
"whitespace"
where spaceChars :: Fixed (ParserT ((,) [[Lexeme t]])) g t ()
spaceChars = (((Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile1 Char -> Bool
Char.isSpace
Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> (t -> Fixed (ParserT ((,) [[Lexeme t]])) g t ())
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> (a -> Fixed (ParserT ((,) [[Lexeme t]])) g t b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \t
ws-> ([[Lexeme t]], ()) -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (m :: * -> *) s a (g :: (* -> *) -> *).
(Applicative m, Ord s) =>
m a -> ParserT m g s a
lift ([[t -> Lexeme t
forall s. s -> Lexeme s
WhiteSpace t
ws]], ())) Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> [Char] -> m a
<?> [Char]
"whitespace")
Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> () -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
comment :: (Rank2.Apply g, Ord t, Show t, TextualMonoid t) => Parser g t ()
= do c <- Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> m a
try (Fixed (ParserT ((,) [[Lexeme t]])) g t t
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
blockComment
Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"--" Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a. Semigroup a => a -> a -> a
<> (Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-') Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (Char -> Bool) -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (m :: * -> *). InputCharParsing m => (Char -> Bool) -> m ()
notSatisfyChar Char -> Bool
isSymbol)
Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a. Semigroup a => a -> a -> a
<> (Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile Char -> Bool
isLineChar) Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> [Char] -> m a
<?> [Char]
"comment"
lift ([[Comment c]], ())
where isCommentChar :: Char -> Bool
isCommentChar Char
c = Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'-' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'{'
blockComment :: Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
blockComment =
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"{-"
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall a. Semigroup a => a -> a -> a
<> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (p :: * -> *) a. (Alternative p, Monoid a) => p a -> p a
concatMany (Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
blockComment Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> (Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall a.
Show a =>
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (m :: * -> *) a. (Parsing m, Show a) => m a -> m ()
notFollowedBy (ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"-}") Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *). InputParsing m => m (ParserInput m)
anyToken) Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall a. Semigroup a => a -> a -> a
<> (Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile Char -> Bool
isCommentChar)
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall a. Semigroup a => a -> a -> a
<> ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"-}"
verifyStatements :: (Abstract.Haskell l, Rank2.Apply g, Ord t) =>
[NodeWrap t (Deep.Sum (Abstract.Statement l l) (Abstract.Expression l l) (NodeWrap t) (NodeWrap t))]
-> Parser g t (Abstract.GuardedExpression l l (NodeWrap t) (NodeWrap t))
verifyStatements :: forall l (g :: (* -> *) -> *) t.
(Haskell l, Apply g, Ord t) =>
[NodeWrap
t (Sum (Statement l l) (Expression l l) (NodeWrap t) (NodeWrap t))]
-> Parser g t (GuardedExpression l l (NodeWrap t) (NodeWrap t))
verifyStatements [] = [Char]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a. [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"empty do block"
verifyStatements [NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
stats =
[((Down Int, ParsedLexemes t, Down Int),
Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> ((Down Int, ParsedLexemes t, Down Int),
Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
[s (Statement l l d d)]
-> s (Expression l l d d) -> GuardedExpression λ l d s
forall (s :: * -> *) l (d :: * -> *).
[s (Statement l l d d)]
-> s (Expression l l d d) -> GuardedExpression l l d s
Abstract.guardedExpression (NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall l t.
Haskell l =>
NodeWrap
t (Sum (Statement l l) (Expression l l) (NodeWrap t) (NodeWrap t))
-> NodeWrap t (Statement l l (NodeWrap t) (NodeWrap t))
expressionToStatement (NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> [NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [((Down Int, ParsedLexemes t, Down Int),
Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> [NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
forall a. HasCallStack => [a] -> [a]
init [NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
stats)
(((Down Int, ParsedLexemes t, Down Int),
Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(GuardedExpression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Either
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ((Down Int, ParsedLexemes t, Down Int),
Either
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> ((Down Int, ParsedLexemes t, Down Int), a)
-> f ((Down Int, ParsedLexemes t, Down Int), b)
traverse ((Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> (Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Either
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b. a -> b -> a
const (Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b. (a -> b) -> a -> b
$ [Char]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a. [Char] -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"do block must end with an expression") Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure)
(((Down Int, ParsedLexemes t, Down Int),
Either
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> ((Down Int, ParsedLexemes t, Down Int),
Either
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b. (a -> b) -> a -> b
$ Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> Either
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall (g :: (* -> *) -> (* -> *) -> *)
(h :: (* -> *) -> (* -> *) -> *) (d :: * -> *) (s :: * -> *).
Sum g h d s -> Either (g d s) (h d s)
Deep.eitherFromSum (Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> Either
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
-> NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> ((Down Int, ParsedLexemes t, Down Int),
Either
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
-> NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a. HasCallStack => [a] -> a
last [NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))]
stats)
expressionToStatement
:: Abstract.Haskell l
=> NodeWrap t (Deep.Sum (Abstract.Statement l l) (Abstract.Expression l l) (NodeWrap t) (NodeWrap t))
-> NodeWrap t (Abstract.Statement l l (NodeWrap t) (NodeWrap t))
expressionToStatement :: forall l t.
Haskell l =>
NodeWrap
t (Sum (Statement l l) (Expression l l) (NodeWrap t) (NodeWrap t))
-> NodeWrap t (Statement l l (NodeWrap t) (NodeWrap t))
expressionToStatement NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
se = case NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall t a. NodeWrap t a -> a
unwrap NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
se of
Deep.InL Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
s -> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
s Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> ((Down Int, ParsedLexemes t, Down Int), b)
-> ((Down Int, ParsedLexemes t, Down Int), a)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
se
Deep.InR Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
e -> (NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall t a b. (NodeWrap t a -> b) -> NodeWrap t a -> NodeWrap t b
rewrap NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> Statement
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
s (Expression l l d d) -> Statement λ l d s
forall (s :: * -> *) l (d :: * -> *).
s (Expression l l d d) -> Statement l l d s
Abstract.expressionStatement (Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
e Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int))
-> NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
-> NodeWrap
t
(Expression
l
l
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
forall a b.
a
-> ((Down Int, ParsedLexemes t, Down Int), b)
-> ((Down Int, ParsedLexemes t, Down Int), a)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ NodeWrap
t
(Sum
(Statement l l)
(Expression l l)
((,) (Down Int, ParsedLexemes t, Down Int))
((,) (Down Int, ParsedLexemes t, Down Int)))
se)
blockOf :: (Rank2.Apply g, Ord t, Show t, OutlineMonoid t, Deep.Foldable (Serialization (Down Int) t) node)
=> Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Parser g t [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
blockOf :: forall (g :: (* -> *) -> *) t (node :: (* -> *) -> (* -> *) -> *).
(Apply g, Ord t, Show t, OutlineMonoid t,
Foldable (Serialization (Down Int) t) node) =>
Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Parser g t [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
blockOf = (Int -> t -> NodeWrap t (node (NodeWrap t) (NodeWrap t)) -> Bool)
-> Parser g t ()
-> Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Parser g t [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
forall (g :: (* -> *) -> *) t (node :: (* -> *) -> (* -> *) -> *).
(Apply g, Ord t, Show t, OutlineMonoid t,
Foldable (Serialization (Down Int) t) node) =>
(Int -> t -> NodeWrap t (node (NodeWrap t) (NodeWrap t)) -> Bool)
-> Parser g t ()
-> Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Parser g t [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
blockWith Int -> t -> NodeWrap t (node (NodeWrap t) (NodeWrap t)) -> Bool
forall t (node :: (* -> *) -> (* -> *) -> *).
(Ord t, Show t, OutlineMonoid t,
Foldable (Serialization (Down Int) t) node) =>
Int -> t -> NodeWrap t (node (NodeWrap t) (NodeWrap t)) -> Bool
oneExtendedLine Parser g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, OutlineMonoid t, Show t) =>
Parser g t ()
blockTerminatorKeyword
blockWith :: (Rank2.Apply g, Ord t, Show t, OutlineMonoid t, Deep.Foldable (Serialization (Down Int) t) node)
=> (Int -> t -> NodeWrap t (node (NodeWrap t) (NodeWrap t)) -> Bool)
-> Parser g t ()
-> Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Parser g t [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
blockWith :: forall (g :: (* -> *) -> *) t (node :: (* -> *) -> (* -> *) -> *).
(Apply g, Ord t, Show t, OutlineMonoid t,
Foldable (Serialization (Down Int) t) node) =>
(Int -> t -> NodeWrap t (node (NodeWrap t) (NodeWrap t)) -> Bool)
-> Parser g t ()
-> Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Parser g t [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
blockWith Int -> t -> NodeWrap t (node (NodeWrap t) (NodeWrap t)) -> Bool
lineFilter Parser g t ()
terminatorKeyword Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
p =
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap t (node (NodeWrap t) (NodeWrap t))]
forall (m :: * -> *) a. TokenParsing m => m a -> m a
braces (Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
p Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap t (node (NodeWrap t) (NodeWrap t))]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
`startSepEndBy` Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall (m :: * -> *). TokenParsing m => m Char
semi) Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap t (node (NodeWrap t) (NodeWrap t))]
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser g t Int
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, OutlineMonoid t) =>
Parser g t Int
inputColumn Parser g t Int
-> (Int
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap t (node (NodeWrap t) (NodeWrap t))])
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap t (node (NodeWrap t) (NodeWrap t))]
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> (a -> Fixed (ParserT ((,) [[Lexeme t]])) g t b)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe (NodeWrap t (node (NodeWrap t) (NodeWrap t)))))
-> ([NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap t (node (NodeWrap t) (NodeWrap t))])
-> Int
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap t (node (NodeWrap t) (NodeWrap t))]
forall {b}.
(Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe (NodeWrap t (node (NodeWrap t) (NodeWrap t)))))
-> ([NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b)
-> Int
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
alignedBlock Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe (NodeWrap t (node (NodeWrap t) (NodeWrap t))))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap t (node (NodeWrap t) (NodeWrap t))]
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure)
where alignedBlock :: (Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe (NodeWrap t (node (NodeWrap t) (NodeWrap t)))))
-> ([NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b)
-> Int
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
alignedBlock Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe (NodeWrap t (node (NodeWrap t) (NodeWrap t))))
opt [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
cont Int
indent =
do rest <- Fixed (ParserT ((,) [[Lexeme t]])) g t t
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *). InputParsing m => m (ParserInput m)
getInput
maybeItem <- opt (filter (lineFilter indent rest) p)
case maybeItem of
Maybe (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
Nothing -> [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
cont []
Just NodeWrap t (node (NodeWrap t) (NodeWrap t))
item -> do
Parser g t Int -> Parser g t ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ((Int -> Bool) -> Parser g t Int -> Parser g t Int
forall a.
(a -> Bool)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter (Int
indent Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=) Parser g t Int
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, OutlineMonoid t) =>
Parser g t Int
inputColumn)
Parser g t () -> Parser g t () -> Parser g t ()
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> Parser g t () -> Parser g t ()
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. LookAheadParsing m => m a -> m a
lookAhead (Fixed (ParserT ((,) [[Lexeme t]])) g t Char -> Parser g t ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ((Char -> Bool) -> Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
Text.Parser.Char.satisfy (Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char]
terminators))
Parser g t () -> Parser g t () -> Parser g t ()
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser g t ()
terminatorKeyword
Parser g t () -> Parser g t () -> Parser g t ()
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser g t ()
forall (m :: * -> *). Parsing m => m ()
eof)
indent' <- Parser g t Int
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, OutlineMonoid t) =>
Parser g t Int
inputColumn
let cont' = [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
cont ([NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b)
-> ([NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> [NodeWrap t (node (NodeWrap t) (NodeWrap t))])
-> [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NodeWrap t (node (NodeWrap t) (NodeWrap t))
item NodeWrap t (node (NodeWrap t) (NodeWrap t))
-> [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
forall a. a -> [a] -> [a]
:)
restOfBlock = (Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe (NodeWrap t (node (NodeWrap t) (NodeWrap t)))))
-> ([NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b)
-> Int
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
alignedBlock Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Maybe (NodeWrap t (node (NodeWrap t) (NodeWrap t))))
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Maybe a)
forall (m :: * -> *) a.
DeterministicParsing m =>
m a -> m (Maybe a)
takeOptional [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
cont' Int
indent
if indent == indent'
then many semi *> restOfBlock
else if indent < indent'
then some semi *> restOfBlock <<|> cont' []
else cont' []
terminators :: [Char]
terminators :: [Char]
terminators = [Char]
",;)]}"
startSepEndBy :: Alternative m => m a -> m sep -> m [a]
startSepEndBy :: forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
startSepEndBy m a
p m sep
sep = (:) (a -> [a] -> [a]) -> m a -> m ([a] -> [a])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m a
p m ([a] -> [a]) -> m [a] -> m [a]
forall a b. m (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f 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 -> m sep -> m [a]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
startSepEndBy m a
p m sep
sep m [a] -> m [a] -> m [a]
forall a. m a -> m a -> m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [a] -> m [a]
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [])
m [a] -> m [a] -> m [a]
forall a. m a -> m a -> m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> 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 -> m sep -> m [a]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
startSepEndBy m a
p m sep
sep
m [a] -> m [a] -> m [a]
forall a. m a -> m a -> m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [a] -> m [a]
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
class TextualMonoid t => OutlineMonoid t where
currentColumn :: t -> Int
instance OutlineMonoid (LinePositioned Text) where
currentColumn :: LinePositioned Text -> Int
currentColumn = LinePositioned Text -> Int
forall m. LinePositioned m -> Int
column
instance OutlineMonoid (Shadowed Text) where
currentColumn :: Shadowed Text -> Int
currentColumn Shadowed Text
t
| Int
column Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 Bool -> Bool -> Bool
&& HasCallStack => Text -> Char
Text -> Char
Text.head Text
line Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
utf8bom = Int
column Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
| Bool
otherwise = Int
column
where line :: Text
line = (Char -> Bool) -> Text -> Text
Text.takeWhileEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\n') (Shadowed Text -> Text
forall m. Shadowed m -> m
prefix Shadowed Text
t)
column :: Int
column = Text -> Int
Text.length Text
line
utf8bom :: Char
utf8bom :: Char
utf8bom = Char
'\xfeff'
inputColumn :: (Rank2.Apply g, Ord t, OutlineMonoid t) => Parser g t Int
inputColumn :: forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, OutlineMonoid t) =>
Parser g t Int
inputColumn = t -> Int
forall t. OutlineMonoid t => t -> Int
currentColumn (t -> Int)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed (ParserT ((,) [[Lexeme t]])) g t t
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *). InputParsing m => m (ParserInput m)
getInput
blockTerminatorKeyword :: (Rank2.Apply g, Ord t, OutlineMonoid t, Show t) => Parser g t ()
blockTerminatorKeyword :: forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, OutlineMonoid t, Show t) =>
Parser g t ()
blockTerminatorKeyword = (ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"else" Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"in" Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"of" Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Fixed (ParserT ((,) [[Lexeme t]])) g t)
"where")
Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall a b.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Char -> Bool) -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (m :: * -> *). InputCharParsing m => (Char -> Bool) -> m ()
notSatisfyChar Char -> Bool
isNameTailChar
oneExtendedLine :: (Ord t, Show t, OutlineMonoid t,
Deep.Foldable (Serialization (Down Int) t) node)
=> Int -> t -> NodeWrap t (node (NodeWrap t) (NodeWrap t)) -> Bool
oneExtendedLine :: forall t (node :: (* -> *) -> (* -> *) -> *).
(Ord t, Show t, OutlineMonoid t,
Foldable (Serialization (Down Int) t) node) =>
Int -> t -> NodeWrap t (node (NodeWrap t) (NodeWrap t)) -> Bool
oneExtendedLine Int
indent t
_input NodeWrap t (node (NodeWrap t) (NodeWrap t))
node =
Integer -> [Lexeme t] -> Bool
forall {a}. (Enum a, Ord a, Num a) => a -> [Lexeme t] -> Bool
allIndented Integer
0 (NodeWrap t (node (NodeWrap t) (NodeWrap t)) -> [Lexeme t]
forall s pos (g :: (* -> *) -> (* -> *) -> *).
(Factorial s, Position pos, Foldable (Serialization pos s) g) =>
Wrapped pos s (g (Wrapped pos s) (Wrapped pos s)) -> [Lexeme s]
lexemes NodeWrap t (node (NodeWrap t) (NodeWrap t))
node)
where allIndented :: a -> [Lexeme t] -> Bool
allIndented a
nesting (WhiteSpace t
_ : Token TokenType
Delimiter t
tok : [Lexeme t]
rest) = a -> [Lexeme t] -> Bool
allIndented a
nesting [Lexeme t]
rest
allIndented a
nesting (WhiteSpace t
ws : Token TokenType
_ t
tok : [Lexeme t]
rest)
| (Char -> Bool) -> t -> Bool
forall t. TextualMonoid t => (Char -> Bool) -> t -> Bool
Textual.all Char -> Bool
isLineChar t
ws = a -> [Lexeme t] -> Bool
allIndented (t -> a -> a
forall {a} {a}. (Eq a, IsString a, Enum a) => a -> a -> a
nest t
tok a
nesting) [Lexeme t]
rest
| Int
tokenIndent Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
indent = Bool
False
| Int
tokenIndent Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
indent Bool -> Bool -> Bool
&& a
nesting a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
0 Bool -> Bool -> Bool
&& t
tok t -> [t] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [t]
terminators = Bool
False
where tokenIndent :: Int
tokenIndent = t -> Int
forall t. OutlineMonoid t => t -> Int
currentColumn ((t -> Bool) -> t -> t
forall m. FactorialMonoid m => (m -> Bool) -> m -> m
Factorial.dropWhile (Bool -> t -> Bool
forall a b. a -> b -> a
const Bool
True) t
ws)
allIndented a
nesting (Token TokenType
_ t
tok : [Lexeme t]
rest) = a -> [Lexeme t] -> Bool
allIndented (t -> a -> a
forall {a} {a}. (Eq a, IsString a, Enum a) => a -> a -> a
nest t
tok a
nesting) [Lexeme t]
rest
allIndented a
nesting (Lexeme t
_ : [Lexeme t]
rest) = a -> [Lexeme t] -> Bool
allIndented a
nesting [Lexeme t]
rest
allIndented a
_ [] = Bool
True
terminators :: [t]
terminators = [t
"{", t
",", t
";", t
")", t
"]", t
"}", t
"else", t
"in", t
"of", t
"then"]
nest :: a -> a -> a
nest a
"{" = a -> a
forall a. Enum a => a -> a
succ
nest a
"}" = a -> a
forall a. Enum a => a -> a
pred
nest a
_ = a -> a
forall a. a -> a
id