{-# Language DataKinds, FlexibleContexts, FlexibleInstances,
NamedFieldPuns, NoFieldSelectors, OverloadedRecordDot, OverloadedStrings,
Rank2Types, RecordWildCards, ScopedTypeVariables,
TemplateHaskell, TupleSections, TypeApplications, TypeFamilies, TypeOperators, TypeSynonymInstances #-}
module Language.Haskell.Extensions.Grammar (ExtendedGrammar(report), extendedGrammar, parseModule, NodeWrap) where
import Control.Applicative
import Control.Monad (void)
import qualified Data.Char as Char
import Data.Foldable (fold, toList)
import Data.Function ((&))
import Data.Functor.Compose (Compose(getCompose))
import qualified Data.List as List
import Data.List.NonEmpty (NonEmpty((:|)))
import Data.Ord (Down)
import Data.Maybe (isJust, isNothing)
import Data.Function.Memoize (memoize)
import Data.Monoid (Endo(..))
import Data.Monoid.Cancellative (RightReductive, isPrefixOf, isSuffixOf)
import Data.Monoid.Instances.Positioned (LinePositioned, column)
import Data.Monoid.Instances.PrefixMemory (Shadowed (content, prefix))
import Data.Monoid.Textual (TextualMonoid, toString)
import qualified Data.Monoid.Factorial as Factorial
import qualified Data.Monoid.Textual as Textual
import qualified Data.Map.Lazy as Map
import qualified Data.Set as Set
import Data.Map (Map)
import Data.Set (Set)
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Numeric
import qualified Rank2
import qualified Rank2.TH
import qualified Text.Parser.Char
import Text.Parser.Combinators (eof, endBy, sepBy, sepBy1, sepByNonEmpty, sepEndBy)
import Text.Parser.Token (braces, brackets, comma, parens)
import Text.Grampa
import Text.Grampa.Combinators (moptional, someNonEmpty, takeSomeNonEmpty)
import Text.Grampa.ContextFree.SortedMemoizing.Transformer.LeftRecursive (autochain, ParserT, lift)
import qualified Transformation.Deep as Deep
import Witherable (filter, mapMaybe)
import Language.Haskell.Extensions (Extension(..), ExtensionSwitch(..),
on, partitionContradictory, switchesByName, withImplications)
import qualified Language.Haskell.Extensions.Abstract as Abstract
import qualified Language.Haskell.Grammar as Report
import Language.Haskell.Grammar (HaskellGrammar(..), ModuleLevelGrammar(..), DeclarationGrammar(..),
Parser, OutlineMonoid, NodeWrap,
blockOf, delimiter, terminator, inputColumn, isSymbol,
moduleId, nameQualifier,
oneExtendedLine, rewrap, startSepEndBy, storeToken, wrap, unwrap, whiteSpace)
import Language.Haskell.Reserializer (Lexeme(..), Serialization, TokenType(..), lexemes)
import Prelude hiding (exponent, filter)
class TextualMonoid t => SpaceMonoid t where
precededByString :: t -> t -> Bool
precededByOpenSpace :: t -> Bool
instance (Eq t, Factorial.StableFactorial t, RightReductive t, TextualMonoid t) => SpaceMonoid (Shadowed t) where
precededByString :: Shadowed t -> Shadowed t -> Bool
precededByString Shadowed t
s Shadowed t
t = Shadowed t -> t
forall m. Shadowed m -> m
content Shadowed t
s t -> t -> Bool
forall m. RightReductive m => m -> m -> Bool
`isSuffixOf` Shadowed t -> t
forall m. Shadowed m -> m
prefix Shadowed t
t
precededByOpenSpace :: Shadowed t -> Bool
precededByOpenSpace Shadowed t
t = (Char -> Bool) -> t -> Bool
forall t. TextualMonoid t => (Char -> Bool) -> t -> Bool
Textual.any Char -> Bool
isOpenOrSpace (t -> t
forall m. Factorial m => m -> m
Factorial.primeSuffix (t -> t) -> t -> t
forall a b. (a -> b) -> a -> b
$ Shadowed t -> t
forall m. Shadowed m -> m
prefix Shadowed t
t) Bool -> Bool -> Bool
|| t
"-}" t -> t -> Bool
forall m. RightReductive m => m -> m -> Bool
`isSuffixOf` Shadowed t -> t
forall m. Shadowed m -> m
prefix Shadowed t
t
where isOpenOrSpace :: Char -> Bool
isOpenOrSpace Char
c = Char -> Bool
Char.isSpace Char
c Bool -> Bool -> Bool
|| Char
c Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (String
"([{,;" :: [Char])
followedByCloseSpace :: TextualMonoid t => t -> Bool
followedByCloseSpace :: forall t. TextualMonoid t => t -> Bool
followedByCloseSpace t
t =
(Char -> Bool) -> Maybe Char -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Char -> Bool
isCloseOrSpace (t -> Maybe Char
forall t. TextualMonoid t => t -> Maybe Char
Textual.characterPrefix t
t) Bool -> Bool -> Bool
|| t
"{-" t -> t -> Bool
forall m. LeftReductive m => m -> m -> Bool
`isPrefixOf` t
t Bool -> Bool -> Bool
|| t
"--" t -> t -> Bool
forall m. LeftReductive m => m -> m -> Bool
`isPrefixOf` t
t
where isCloseOrSpace :: Char -> Bool
isCloseOrSpace Char
c = Char -> Bool
Char.isSpace Char
c Bool -> Bool -> Bool
|| Char
c Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (String
")]},;" :: [Char])
data ExtendedGrammar l t f p = ExtendedGrammar {
forall l t (f :: * -> *) (p :: * -> *).
ExtendedGrammar l t f p -> HaskellGrammar l t f p
report :: HaskellGrammar l t f p,
forall l t (f :: * -> *) (p :: * -> *).
ExtendedGrammar l t f p -> GrammarExtensions l t f p
extensions :: GrammarExtensions l t f p}
data GrammarExtensions l t f p = GrammarExtensions {
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p [f (DerivingClause l l f f)]
singleDerivingClause :: p [f (Abstract.DerivingClause l l f f)],
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p ()
keywordForall :: p (),
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Kind l l f f)
kindSignature :: p (Abstract.Kind l l f f),
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p ()
groundTypeKind :: p (),
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Type l l f f)
cType, forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Type l l f f)
arrowType :: p (Abstract.Type l l f f),
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Type l l f f)
promotedLiteral, forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Type l l f f)
promotedStructure :: p (Abstract.Type l l f f),
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Context l l f f)
equalityConstraint, forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Context l l f f)
implicitParameterConstraint :: p (Abstract.Context l l f f),
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Pattern l l f f)
infixPattern :: p (Abstract.Pattern l l f f),
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (GADTConstructor l l f f)
gadtNewConstructor, forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (GADTConstructor l l f f)
gadtConstructors :: p (Abstract.GADTConstructor l l f f),
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (NonEmpty (Name l))
constructorIDs :: p (NonEmpty (Abstract.Name l)),
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (DerivingStrategy l l f f)
derivingStrategy :: p (Abstract.DerivingStrategy l l f f),
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Declaration l l f f)
inClassOrInstanceTypeFamilyDeclaration :: p (Abstract.Declaration l l f f),
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (ClassInstanceLHS l l f f)
instanceDesignatorApplications, forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (ClassInstanceLHS l l f f)
instanceDesignatorBase :: p (Abstract.ClassInstanceLHS l l f f),
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p [TypeVarBinding l l f f]
optionalForall :: p [Abstract.TypeVarBinding l l f f],
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (TypeVarBinding l l f f)
typeVarBinder :: p (Abstract.TypeVarBinding l l f f),
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Name l)
optionallyParenthesizedTypeVar :: p (Abstract.Name l),
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Type l l f f)
optionallyKindedTypeVar, forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Type l l f f)
optionallyKindedAndParenthesizedTypeVar :: p (Abstract.Type l l f f),
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Pattern l l f f)
conArgPattern :: p (Abstract.Pattern l l f f),
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Type l l f f)
gadtNewBody, forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Type l l f f)
gadtBody, forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Type l l f f)
prefix_gadt_body, forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Type l l f f)
record_gadt_body :: p (Abstract.Type l l f f),
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Type l l f f)
return_type, forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p (Type l l f f)
arg_type :: p (Abstract.Type l l f f),
forall l t (f :: * -> *) (p :: * -> *).
GrammarExtensions l t f p -> p t
binary :: p t}
$(Rank2.TH.deriveAll ''ExtendedGrammar)
$(Rank2.TH.deriveAll ''GrammarExtensions)
type ExtensionOverlay l g t = (Abstract.Haskell l, LexicalParsing (Parser g t), Ord t, Show t, TextualMonoid t,
g ~ ExtendedGrammar l t (NodeWrap t)) => GrammarOverlay g (Parser g t)
extensionMixins :: forall l g t. (Abstract.ExtendedHaskell l,
LexicalParsing (Parser (ExtendedGrammar l t (NodeWrap t)) t),
Ord t, Show t, OutlineMonoid t, SpaceMonoid t,
Abstract.DeeplyFoldable (Serialization (Down Int) t) l,
g ~ ExtendedGrammar l t (NodeWrap t))
=> Map (Set Extension) [(Int, GrammarOverlay g (Parser g t))]
extensionMixins :: forall l (g :: (* -> *) -> *) t.
(ExtendedHaskell l,
LexicalParsing (Parser (ExtendedGrammar l t (NodeWrap t)) t),
Ord t, Show t, OutlineMonoid t, SpaceMonoid t,
DeeplyFoldable (Serialization (Down Int) t) l,
g ~ ExtendedGrammar l t (NodeWrap t)) =>
Map (Set Extension) [(Int, GrammarOverlay g (Parser g t))]
extensionMixins =
[(Set Extension, [(Int, GrammarOverlay g (Parser g t))])]
-> Map (Set Extension) [(Int, GrammarOverlay g (Parser g t))]
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
IdentifierSyntax], [(Int
0, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
identifierSyntaxMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
PackageImports], [(Int
0, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
packageImportsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
SafeImports], [(Int
0, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
safeImportsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
ImportQualifiedPost], [(Int
0, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
importQualifiedPostMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
UnicodeSyntax], [(Int
1, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
unicodeSyntaxMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
BinaryLiterals], [(Int
1, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
binaryLiteralsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
HexFloatLiterals], [(Int
1, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
hexFloatLiteralsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
NumericUnderscores], [(Int
1, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
numericUnderscoresMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
MultiParameterConstraints], [(Int
1, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
multiParameterConstraintsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
BinaryLiterals,
Extension
NumericUnderscores], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
binaryUnderscoresMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
PackageImports,
Extension
SafeImports], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
safePackageImportsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
PackageImports,
Extension
ImportQualifiedPost], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
packageImportsQualifiedPostMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
SafeImports,
Extension
ImportQualifiedPost], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
safeImportsQualifiedPostMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
PackageImports,
Extension
SafeImports,
Extension
ImportQualifiedPost], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
safePackageImportsQualifiedPostMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
NamedDefaults], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'NamedDefaults] l =>
ExtensionOverlay l g t
namedDefaultsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
NegativeLiterals], [(Int
2, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
negativeLiteralsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
LexicalNegation], [(Int
3, GrammarOverlay g (Parser g t)
forall t l (g :: (* -> *) -> *).
SpaceMonoid t =>
ExtensionOverlay l g t
lexicalNegationMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
MagicHash], [(Int
3, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
(SpaceMonoid t, ExtendedHaskell l) =>
ExtensionOverlay l g t
magicHashMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
ParallelListComprehensions], [(Int
3, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
parallelListComprehensionsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
ExtendedLiterals], [(Int
4, GrammarOverlay g (Parser g t)
forall t l (g :: (* -> *) -> *).
(SpaceMonoid t, ExtendedWith '[ 'ExtendedLiterals] l) =>
ExtensionOverlay l g t
extendedLiteralsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
OverloadedLabels], [(Int
4, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
overloadedLabelsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
RecursiveDo], [(Int
4, GrammarOverlay g (Parser g t)
forall t l (g :: (* -> *) -> *).
(OutlineMonoid t, ExtendedWith '[ 'RecursiveDo] l,
DeeplyFoldable (Serialization (Down Int) t) l) =>
ExtensionOverlay l g t
recursiveDoMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
QualifiedDo], [(Int
4, GrammarOverlay g (Parser g t)
forall (g :: (* -> *) -> *) t l.
(OutlineMonoid t, Haskell l, ExtendedWith '[ 'QualifiedDo] l,
DeeplyFoldable (Serialization (Down Int) t) l) =>
ExtensionOverlay l g t
qualifiedDoMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
QualifiedDo, Extension
RecursiveDo], [(Int
4, GrammarOverlay g (Parser g t)
forall (g :: (* -> *) -> *) t l.
(OutlineMonoid t, Haskell l,
ExtendedWith '[ 'QualifiedDo, 'RecursiveDo] l,
DeeplyFoldable (Serialization (Down Int) t) l) =>
ExtensionOverlay l g t
qualifiedRecursiveDoMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
TupleSections], [(Int
5, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
tupleSectionsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
EmptyCase], [(Int
6, GrammarOverlay g (Parser g t)
forall t l (g :: (* -> *) -> *).
(OutlineMonoid t, ExtendedHaskell l,
Foldable (Serialization (Down Int) t) (CaseAlternative l l)) =>
ExtensionOverlay l g t
emptyCaseMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
LambdaCase], [(Int
7, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
(ExtendedWith '[ 'LambdaCase] l, OutlineMonoid t,
Foldable
(Serialization (Down Int) t) (LambdaCasesAlternative l l)) =>
ExtensionOverlay l g t
lambdaCaseMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
GratuitouslyParenthesizedTypes], [(Int
7, GrammarOverlay g (Parser g t)
forall t l (g :: (* -> *) -> *).
(OutlineMonoid t, ExtendedHaskell l,
Foldable (Serialization (Down Int) t) (Declaration l l),
Foldable (Serialization (Down Int) t) (GADTConstructor l l)) =>
ExtensionOverlay l g t
gratuitouslyParenthesizedTypesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
EqualityConstraints], [(Int
7, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
equalityConstraintsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
MultiWayIf], [(Int
8, GrammarOverlay g (Parser g t)
forall t l (g :: (* -> *) -> *).
(OutlineMonoid t, ExtendedHaskell l,
Foldable (Serialization (Down Int) t) (GuardedExpression l l)) =>
ExtensionOverlay l g t
multiWayIfMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
KindSignatures], [(Int
7, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
kindSignaturesBaseMixin), (Int
8, GrammarOverlay g (Parser g t)
forall t l (g :: (* -> *) -> *).
(OutlineMonoid t, ExtendedHaskell l,
Foldable (Serialization (Down Int) t) (Declaration l l)) =>
ExtensionOverlay l g t
kindSignaturesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
ParenthesizedTypeOperators], [(Int
8, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
parenthesizedTypeOperatorsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
TypeOperators], [(Int
8, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
typeOperatorsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
DataKinds], [(Int
8, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
(ExtendedHaskell l, TextualMonoid t) =>
ExtensionOverlay l g t
dataKindsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
DataKinds,
Extension
ListTuplePuns], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
(ExtendedHaskell l, TextualMonoid t) =>
ExtensionOverlay l g t
dataKindsListTuplePunsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
ListTuplePuns], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
listTuplePunsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
ListTuplePuns,
Extension
UnboxedTuples], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'UnboxedTuples] l =>
ExtensionOverlay l g t
unboxedListTuplePunsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
ListTuplePuns,
Extension
UnboxedSums], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'UnboxedSums] l =>
ExtensionOverlay l g t
unboxedSumPunsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
ExplicitNamespaces], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'ExplicitNamespaces] l =>
ExtensionOverlay l g t
explicitNamespacesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
BlockArguments], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
blockArgumentsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
ExistentialQuantification], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
existentialQuantificationMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
ExplicitForAll], [(Int
9, GrammarOverlay g (Parser g t)
forall t l (g :: (* -> *) -> *).
(OutlineMonoid t, ExtendedHaskell l,
Foldable (Serialization (Down Int) t) (Declaration l l)) =>
ExtensionOverlay l g t
explicitForAllMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
ScopedTypeVariables], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
scopedTypeVariablesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
GADTSyntax], [(Int
9, GrammarOverlay g (Parser g t)
forall t l (g :: (* -> *) -> *).
(OutlineMonoid t, ExtendedHaskell l,
Foldable (Serialization (Down Int) t) (GADTConstructor l l)) =>
ExtensionOverlay l g t
gadtSyntaxMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
TypeFamilies], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
(OutlineMonoid t, ExtendedHaskell l,
Foldable (Serialization (Down Int) t) (Declaration l l),
Foldable (Serialization (Down Int) t) (GADTConstructor l l)) =>
ExtensionOverlay l g t
typeFamiliesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
TypeFamilyDependencies], [(Int
9, GrammarOverlay g (Parser g t)
forall t l (g :: (* -> *) -> *).
(OutlineMonoid t, ExtendedHaskell l,
Foldable (Serialization (Down Int) t) (Declaration l l),
Foldable (Serialization (Down Int) t) (GADTConstructor l l)) =>
ExtensionOverlay l g t
typeFamilyDependenciesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
TypeData], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'TypeData] l =>
ExtensionOverlay l g t
typeDataMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
GADTs, Extension
TypeData], [(Int
9, GrammarOverlay g (Parser g t)
forall t l (g :: (* -> *) -> *).
(OutlineMonoid t, ExtendedWith '[ 'GADTs, 'TypeData] l,
DeeplyFoldable (Serialization (Down Int) t) l) =>
ExtensionOverlay l g t
typeDataGADTMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
StandaloneKindSignatures], [(Int
7, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
kindSignaturesBaseMixin),
(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
standaloneKindSignaturesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
StarIsType], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
starIsTypeMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
TypeApplications], [(Int
9, GrammarOverlay g (Parser g t)
forall l t (g :: (* -> *) -> *).
(ExtendedHaskell l, DeeplyFoldable (Serialization (Down Int) t) l,
SpaceMonoid t) =>
ExtensionOverlay l g t
typeApplicationsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
TypeAbstractionsOrApplicationsInConstructorPatterns],
[(Int
9, GrammarOverlay g (Parser g t)
forall l t (g :: (* -> *) -> *).
(ExtendedHaskell l, SpaceMonoid t,
DeeplyFoldable (Serialization (Down Int) t) l) =>
ExtensionOverlay l g t
typeAbstractionsOrApplicationsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
TypeAbstractions], [(Int
9, GrammarOverlay g (Parser g t)
forall l t (g :: (* -> *) -> *).
(ExtendedWith '[ 'TypeAbstractions] l, SpaceMonoid t) =>
ExtensionOverlay l g t
typeAbstractionsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
InferredTypeVariables], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
inferredTypeVariablesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
LinearTypes], [(Int
9, GrammarOverlay g (Parser g t)
forall t l (g :: (* -> *) -> *).
(SpaceMonoid t, ExtendedHaskell l) =>
ExtensionOverlay l g t
linearTypesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
RoleAnnotations], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
roleAnnotationsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
UnboxedTuples], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'UnboxedTuples] l =>
ExtensionOverlay l g t
unboxedTuplesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
TupleSections, Extension
UnboxedTuples], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'UnboxedTuples] l =>
ExtensionOverlay l g t
unboxedTupleSectionsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
UnboxedSums], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'UnboxedSums] l =>
ExtensionOverlay l g t
unboxedSumsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
InterruptibleFFI], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'InterruptibleFFI] l =>
ExtensionOverlay l g t
interruptibleFFIMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
CApiFFI], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'CApiFFI] l =>
ExtensionOverlay l g t
cApiFFIMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
NamedFieldPuns], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
namedFieldPunsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
RecordWildCards], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'RecordWildCards] l =>
ExtensionOverlay l g t
recordWildCardsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
OverloadedRecordDot], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
overloadedRecordDotMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
ImplicitParameters], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'ImplicitParameters] l =>
ExtensionOverlay l g t
implicitParametersMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
StrictData], [(Int
9, GrammarOverlay g (Parser g t)
forall t l (g :: (* -> *) -> *).
(SpaceMonoid t, ExtendedWith '[ 'StrictData] l) =>
ExtensionOverlay l g t
strictDataMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
Strict], [(Int
9, GrammarOverlay g (Parser g t)
forall t l (g :: (* -> *) -> *).
(SpaceMonoid t, ExtendedWith '[ 'Strict] l) =>
ExtensionOverlay l g t
strictMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
BangPatterns], [(Int
9, GrammarOverlay g (Parser g t)
forall t l (g :: (* -> *) -> *).
(SpaceMonoid t, ExtendedWith '[ 'BangPatterns] l) =>
ExtensionOverlay l g t
bangPatternsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
ViewPatterns], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'ViewPatterns] l =>
ExtensionOverlay l g t
viewPatternsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
NPlusKPatterns], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'NPlusKPatterns] l =>
ExtensionOverlay l g t
nPlusKPatternsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
PatternSynonyms], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
(OutlineMonoid t, ExtendedWith '[ 'PatternSynonyms] l,
Foldable (Serialization (Down Int) t) (PatternEquationClause l l),
Foldable (Serialization (Down Int) t) (Declaration l l)) =>
ExtensionOverlay l g t
patternSynonymsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
StandaloneDeriving], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'StandaloneDeriving] l =>
ExtensionOverlay l g t
standaloneDerivingMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
DerivingStrategies], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'DerivingStrategies] l =>
ExtensionOverlay l g t
derivingStrategiesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
DerivingVia], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'DerivingVia] l =>
ExtensionOverlay l g t
derivingViaMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
StandaloneDeriving,
Extension
DerivingStrategies], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
(ExtendedWith '[ 'StandaloneDeriving] l,
ExtendedWith '[ 'DerivingStrategies] l) =>
ExtensionOverlay l g t
standaloneDerivingStrategiesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
StandaloneDeriving,
Extension
DerivingVia], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
(ExtendedWith '[ 'StandaloneDeriving] l,
ExtendedWith '[ 'DerivingStrategies] l,
ExtendedWith '[ 'DerivingVia] l) =>
ExtensionOverlay l g t
standaloneDerivingViaMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
FunctionalDependencies], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
(OutlineMonoid t, ExtendedWith '[ 'FunctionalDependencies] l,
Foldable (Serialization (Down Int) t) (Declaration l l)) =>
ExtensionOverlay l g t
functionalDependenciesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
InstanceSigs], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
instanceSignaturesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
DefaultSignatures], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'DefaultSignatures] l =>
ExtensionOverlay l g t
defaultSignaturesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
NondecreasingIndentation], [(Int
9, GrammarOverlay g (Parser g t)
forall t l (g :: (* -> *) -> *).
(Foldable (Serialization (Down Int) t) (Expression l l),
Foldable (Serialization (Down Int) t) (Statement l l),
OutlineMonoid t) =>
ExtensionOverlay l g t
nondecreasingIndentationMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
LinearTypes, Extension
GADTSyntax], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
gadtLinearTypesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
LinearTypes, Extension
UnicodeSyntax], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
unicodeLinearTypesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
GADTSyntax, Extension
LinearTypes,
Extension
UnicodeSyntax], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
gadtUnicodeLinearTypesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
StarIsType,
Extension
ParenthesizedTypeOperators], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
starIsTypeOperatorsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
StarIsType, Extension
UnicodeSyntax], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
unicodeStarIsTypeMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
GADTSyntax, Extension
TypeOperators], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
gadtSyntaxTypeOperatorsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
DataKinds, Extension
TypeOperators], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
dataKindsTypeOperatorsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
DataKinds, Extension
TypeOperators,
Extension
GADTSyntax], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
dataKindsGadtSyntaxTypeOperatorsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
VisibleDependedentQuantification],
[(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
visibleDependentQuantificationMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
RequiredTypeArguments], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'ExplicitNamespaces] l =>
ExtensionOverlay l g t
requiredTypeArgumentsMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
ConstraintsAreTypes], [(Int
9, GrammarOverlay g (Parser g t)
forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
constraintsAreTypesMixin)]),
([Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList [Extension
SpaceSensitiveOperators], [(Int
9, GrammarOverlay g (Parser g t)
forall t l (g :: (* -> *) -> *).
SpaceMonoid t =>
ExtensionOverlay l g t
spaceSensitiveOperatorsMixin)])]
languagePragmas :: (Rank2.Apply g, Ord t, Show t, TextualMonoid t, LexicalParsing (Parser g t)) =>
Parser g t [ExtensionSwitch]
languagePragmas :: forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t,
LexicalParsing (Parser g t)) =>
Parser g t [ExtensionSwitch]
languagePragmas = Fixed (ParserT ((,) [[Lexeme t]])) g t t
Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
spaceChars
Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [ExtensionSwitch]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [ExtensionSwitch]
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
(CommittedResults (Parser g t) [ExtensionSwitch])
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [ExtensionSwitch]
forall a.
Fixed
(ParserT ((,) [[Lexeme t]])) g t (CommittedResults (Parser g t) a)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a.
CommittedParsing m =>
m (CommittedResults m a) -> m a
admit (ParserInput (Parser g t)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Parser g t)
"{-#" 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
*> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t ()
whiteSpace Fixed (ParserT ((,) [[Lexeme t]])) g 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
*> (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 t. TextualMonoid t => t -> Bool
isLanguagePragma ((Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile Char -> Bool
Char.isAlphaNum)
Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Either (ParseFailure (Down Int) t) [ExtensionSwitch])
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Either (ParseFailure (Down Int) t) [ExtensionSwitch])
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 [ExtensionSwitch]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(CommittedResults (Parser g t) [ExtensionSwitch])
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (CommittedResults (Parser g t) a)
forall (m :: * -> *) a.
CommittedParsing m =>
m a -> m (CommittedResults m a)
commit (Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t ()
whiteSpace
Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [ExtensionSwitch]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [ExtensionSwitch]
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
*> ([ExtensionSwitch] -> [ExtensionSwitch] -> [ExtensionSwitch])
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [ExtensionSwitch]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [ExtensionSwitch]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [ExtensionSwitch]
forall a b c.
(a -> b -> c)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t b
-> Fixed (ParserT ((,) [[Lexeme t]])) g t c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 [ExtensionSwitch] -> [ExtensionSwitch] -> [ExtensionSwitch]
forall a. Semigroup a => a -> a -> a
(<>)
(Fixed (ParserT ((,) [[Lexeme t]])) g t ExtensionSwitch
extension Fixed (ParserT ((,) [[Lexeme t]])) g t ExtensionSwitch
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [ExtensionSwitch]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
`sepBy` (ParserInput (Parser g t)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Parser g t)
"," 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
*> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t ()
whiteSpace) Fixed (ParserT ((,) [[Lexeme t]])) g t [ExtensionSwitch]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [ExtensionSwitch]
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 (Parser g t)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Parser g t)
"#-}")
Fixed (ParserT ((,) [[Lexeme t]])) g t [ExtensionSwitch]
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t,
LexicalParsing (Parser g t)) =>
Parser g t [ExtensionSwitch]
languagePragmas)
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Either (ParseFailure (Down Int) t) [ExtensionSwitch])
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Either (ParseFailure (Down Int) t) [ExtensionSwitch])
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Either (ParseFailure (Down Int) t) [ExtensionSwitch])
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
comment Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Either (ParseFailure (Down Int) t) [ExtensionSwitch])
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Either (ParseFailure (Down Int) t) [ExtensionSwitch])
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 [ExtensionSwitch]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(CommittedResults (Parser g t) [ExtensionSwitch])
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (CommittedResults (Parser g t) a)
forall (m :: * -> *) a.
CommittedParsing m =>
m a -> m (CommittedResults m a)
commit Fixed (ParserT ((,) [[Lexeme t]])) g t [ExtensionSwitch]
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t,
LexicalParsing (Parser g t)) =>
Parser g t [ExtensionSwitch]
languagePragmas
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Either (ParseFailure (Down Int) t) [ExtensionSwitch])
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Either (ParseFailure (Down Int) t) [ExtensionSwitch])
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Either (ParseFailure (Down Int) t) [ExtensionSwitch])
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 [ExtensionSwitch]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(CommittedResults (Parser g t) [ExtensionSwitch])
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (CommittedResults (Parser g t) a)
forall (m :: * -> *) a.
CommittedParsing m =>
m a -> m (CommittedResults m a)
commit ([ExtensionSwitch]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [ExtensionSwitch]
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [ExtensionSwitch]
forall a. Monoid a => a
mempty))
where spaceChars :: Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
spaceChars = (Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile Char -> Bool
Char.isSpace
isLanguagePragma :: t -> Bool
isLanguagePragma t
pragmaName = Text -> Text
Text.toUpper ((t -> Text) -> t -> Text
forall t. TextualMonoid t => (t -> Text) -> t -> Text
Textual.toText t -> Text
forall a. Monoid a => a
mempty t
pragmaName) Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"LANGUAGE"
extension :: Fixed (ParserT ((,) [[Lexeme t]])) g t ExtensionSwitch
extension = do extensionName <- (Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile Char -> Bool
Char.isAlphaNum
void whiteSpace
case Map.lookup extensionName switchesByName of
Just ExtensionSwitch
ext -> ExtensionSwitch
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ExtensionSwitch
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ExtensionSwitch
ext
Maybe ExtensionSwitch
Nothing -> String -> Fixed (ParserT ((,) [[Lexeme t]])) g t ExtensionSwitch
forall a. String -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"Unknown language extension " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> (t -> String) -> t -> String
forall t. TextualMonoid t => (t -> String) -> t -> String
toString t -> String
forall a. Monoid a => a
mempty t
extensionName)
comment :: Fixed (ParserT ((,) [[Lexeme t]])) g t t
comment = ParserInput (Parser g t)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Parser 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 a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile Char -> Bool
Report.isLineChar 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
Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
blockComment
blockComment :: Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
blockComment = ParserInput (Parser g t)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string ParserInput (Parser g t)
"{-"
Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser 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 (ParserInput (Parser 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. Parsing m => m a -> m ()
skipMany (Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
blockComment
Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (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
<|> Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser 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 (Parser g t)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string ParserInput (Parser g t)
"-}") Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser 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 (Parser g t))
forall (m :: * -> *). InputParsing m => m (ParserInput m)
anyToken Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall a. Semigroup a => a -> a -> a
<> (Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser 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 ()
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser 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
*> ParserInput (Parser g t)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string ParserInput (Parser g t)
"-}"
parseModule :: forall l t. (Abstract.ExtendedHaskell l, LexicalParsing (Parser (ExtendedGrammar l t (NodeWrap t)) t),
Ord t, Show t, OutlineMonoid t, SpaceMonoid t,
Abstract.DeeplyFoldable (Serialization (Down Int) t) l)
=> Map Extension Bool -> t
-> ParseResults t [NodeWrap t (Abstract.Module l l (NodeWrap t) (NodeWrap t))]
parseModule :: forall l t.
(ExtendedHaskell l,
LexicalParsing (Parser (ExtendedGrammar l t (NodeWrap t)) t),
Ord t, Show t, OutlineMonoid t, SpaceMonoid t,
DeeplyFoldable (Serialization (Down Int) t) l) =>
Map Extension Bool
-> t
-> ParseResults
t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
parseModule Map Extension Bool
extensions t
source = case Either (ParseFailure (Down Int) t) [[ExtensionSwitch]]
moduleExtensions of
Left ParseFailure (Down Int) t
err -> ParseFailure (Down Int) t
-> ParseResults
t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
forall a b. a -> Either a b
Left ParseFailure (Down Int) t
err
Right [[ExtensionSwitch]
extensions']
| let (Set ExtensionSwitch
contradictions, Map Extension Bool
extensionMap) = Set ExtensionSwitch -> (Set ExtensionSwitch, Map Extension Bool)
partitionContradictory ([ExtensionSwitch] -> Set ExtensionSwitch
forall a. Ord a => [a] -> Set a
Set.fromList [ExtensionSwitch]
extensions') ->
if Set ExtensionSwitch -> Bool
forall a. Set a -> Bool
Set.null Set ExtensionSwitch
contradictions then
(if [ExtensionSwitch] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
List.null [ExtensionSwitch]
extensions' then ParseResults t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
-> ParseResults
t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
forall a. a -> a
id else ([NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
-> [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))])
-> ParseResults
t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
-> ParseResults
t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
forall a b.
(a -> b)
-> Either (ParseFailure (Down Int) t) a
-> Either (ParseFailure (Down Int) t) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (([NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
-> [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))])
-> ParseResults
t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
-> ParseResults
t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))])
-> ([NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
-> [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))])
-> ParseResults
t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
-> ParseResults
t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
forall a b. (a -> b) -> a -> b
$ (NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))
-> NodeWrap t (Module l l (NodeWrap t) (NodeWrap t)))
-> [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
-> [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))
-> NodeWrap t (Module l l (NodeWrap t) (NodeWrap t)))
-> [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
-> [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))])
-> (NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))
-> NodeWrap t (Module l l (NodeWrap t) (NodeWrap t)))
-> [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
-> [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
forall a b. (a -> b) -> a -> b
$ (NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))
-> Module l l (NodeWrap t) (NodeWrap t))
-> NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))
-> NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))
forall t a b. (NodeWrap t a -> b) -> NodeWrap t a -> NodeWrap t b
rewrap ((NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))
-> Module l l (NodeWrap t) (NodeWrap t))
-> NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))
-> NodeWrap t (Module l l (NodeWrap t) (NodeWrap t)))
-> (NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))
-> Module l l (NodeWrap t) (NodeWrap t))
-> NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))
-> NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))
forall a b. (a -> b) -> a -> b
$ [ExtensionSwitch]
-> NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))
-> Module l l (NodeWrap t) (NodeWrap t)
forall λ (s :: * -> *) l (d :: * -> *).
Haskell λ =>
[ExtensionSwitch] -> s (Module l l d d) -> Module λ l d s
forall (s :: * -> *) l (d :: * -> *).
[ExtensionSwitch] -> s (Module l l d d) -> Module l l d s
Abstract.withLanguagePragma [ExtensionSwitch]
extensions')
(ParseResults t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
-> ParseResults
t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))])
-> ParseResults
t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
-> ParseResults
t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
forall a b. (a -> b) -> a -> b
$ Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
(NodeWrap t (Module l l (NodeWrap t) (NodeWrap t)))
-> ParseResults
t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
forall {a} {a}.
Compose (Compose (Either (ParseFailure (Down Int) t)) []) ((,) a) a
-> Either (ParseFailure (Down Int) t) [a]
parseResults (Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
(NodeWrap t (Module l l (NodeWrap t) (NodeWrap t)))
-> ParseResults
t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))])
-> Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
(NodeWrap t (Module l l (NodeWrap t) (NodeWrap t)))
-> ParseResults
t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
forall a b. (a -> b) -> a -> b
$ (.report.haskellModule)
(ExtendedGrammar
l
t
(NodeWrap t)
(Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]]))
-> Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
(NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))))
-> ExtendedGrammar
l
t
(NodeWrap t)
(Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]]))
-> Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
(NodeWrap t (Module l l (NodeWrap t) (NodeWrap t)))
forall a b. (a -> b) -> a -> b
$ ExtendedGrammar
l t (NodeWrap t) (Parser (ExtendedGrammar l t (NodeWrap t)) t)
-> t
-> ExtendedGrammar
l
t
(NodeWrap t)
(ResultFunctor (Parser (ExtendedGrammar l t (NodeWrap t)) t))
forall s (g :: (* -> *) -> *).
(ParserInput (Parser (ExtendedGrammar l t (NodeWrap t)) t) ~ s,
GrammarConstraint (Parser (ExtendedGrammar l t (NodeWrap t)) t) g,
Eq s, FactorialMonoid s) =>
g (Parser (ExtendedGrammar l t (NodeWrap t)) t)
-> s
-> g (ResultFunctor (Parser (ExtendedGrammar l t (NodeWrap t)) t))
forall (m :: * -> *) s (g :: (* -> *) -> *).
(MultiParsing m, ParserInput m ~ s, GrammarConstraint m g, Eq s,
FactorialMonoid s) =>
g m -> s -> g (ResultFunctor m)
parseComplete (Set Extension
-> ExtendedGrammar
l t (NodeWrap t) (Parser (ExtendedGrammar l t (NodeWrap t)) t)
forall l t.
(ExtendedHaskell l,
LexicalParsing (Parser (ExtendedGrammar l t (NodeWrap t)) t),
Ord t, Show t, OutlineMonoid t, SpaceMonoid t,
DeeplyFoldable (Serialization (Down Int) t) l) =>
Set Extension
-> Grammar
(ExtendedGrammar l t (NodeWrap t)) (ParserT ((,) [[Lexeme t]])) t
extendedGrammar (Set Extension
-> ExtendedGrammar
l t (NodeWrap t) (Parser (ExtendedGrammar l t (NodeWrap t)) t))
-> Set Extension
-> ExtendedGrammar
l t (NodeWrap t) (Parser (ExtendedGrammar l t (NodeWrap t)) t)
forall a b. (a -> b) -> a -> b
$ Map Extension Bool -> Set Extension
forall {k}. Map k Bool -> Set k
positiveKeys (Map Extension Bool -> Set Extension)
-> Map Extension Bool -> Set Extension
forall a b. (a -> b) -> a -> b
$ Map Extension Bool -> Map Extension Bool
withImplications (Map Extension Bool -> Map Extension Bool)
-> Map Extension Bool -> Map Extension Bool
forall a b. (a -> b) -> a -> b
$ Map Extension Bool
extensionMap Map Extension Bool -> Map Extension Bool -> Map Extension Bool
forall a. Semigroup a => a -> a -> a
<> Map Extension Bool
extensions) t
source
else ParseFailure (Down Int) t
-> ParseResults
t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
forall a b. a -> Either a b
Left ParseFailure (Down Int) t
forall a. Monoid a => a
mempty{errorAlternatives= ["Contradictory extension switches " <> show (toList contradictions)]}
Right [[ExtensionSwitch]]
extensionses -> String
-> ParseResults
t [NodeWrap t (Module l l (NodeWrap t) (NodeWrap t))]
forall a. HasCallStack => String -> a
error (String
"Ambiguous extensions: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> [[ExtensionSwitch]] -> String
forall a. Show a => a -> String
show [[ExtensionSwitch]]
extensionses)
where moduleExtensions :: Either (ParseFailure (Down Int) t) [[ExtensionSwitch]]
moduleExtensions = Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
[ExtensionSwitch]
-> Either (ParseFailure (Down Int) t) [[ExtensionSwitch]]
forall {a} {a}.
Compose (Compose (Either (ParseFailure (Down Int) t)) []) ((,) a) a
-> Either (ParseFailure (Down Int) t) [a]
parseResults (Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
[ExtensionSwitch]
-> Either (ParseFailure (Down Int) t) [[ExtensionSwitch]])
-> Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
[ExtensionSwitch]
-> Either (ParseFailure (Down Int) t) [[ExtensionSwitch]]
forall a b. (a -> b) -> a -> b
$ ((t, [ExtensionSwitch]) -> [ExtensionSwitch])
-> Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
(t, [ExtensionSwitch])
-> Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
[ExtensionSwitch]
forall a b.
(a -> b)
-> Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
a
-> Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (t, [ExtensionSwitch]) -> [ExtensionSwitch]
forall a b. (a, b) -> b
snd (Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
(t, [ExtensionSwitch])
-> Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
[ExtensionSwitch])
-> Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
(t, [ExtensionSwitch])
-> Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
[ExtensionSwitch]
forall a b. (a -> b) -> a -> b
$ Compose
(Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]]))
((,) t)
[ExtensionSwitch]
-> Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
(t, [ExtensionSwitch])
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose (Compose
(Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]]))
((,) t)
[ExtensionSwitch]
-> Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
(t, [ExtensionSwitch]))
-> Compose
(Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]]))
((,) t)
[ExtensionSwitch]
-> Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]])
(t, [ExtensionSwitch])
forall a b. (a -> b) -> a -> b
$ (Only
[ExtensionSwitch]
(Fixed (ParserT ((,) [[Lexeme t]])) (Only [ExtensionSwitch]) t)
-> t
-> Only
[ExtensionSwitch]
(Compose
(Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]]))
((,) t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
(Only [ExtensionSwitch])
t
[ExtensionSwitch]
-> t
-> Compose
(Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]]))
((,) t)
[ExtensionSwitch]
forall r (p :: ((* -> *) -> *) -> * -> * -> *) s (f :: * -> *).
(Only r (p (Only r) s) -> s -> Only r f)
-> p (Only r) s r -> s -> f r
simply Only
[ExtensionSwitch]
(Fixed (ParserT ((,) [[Lexeme t]])) (Only [ExtensionSwitch]) t)
-> t
-> Only
[ExtensionSwitch]
(Compose
(Compose
(Compose (Either (ParseFailure (Down Int) t)) [])
((,) [[Lexeme t]]))
((,) t))
Only
[ExtensionSwitch]
(Fixed (ParserT ((,) [[Lexeme t]])) (Only [ExtensionSwitch]) t)
-> t
-> Only
[ExtensionSwitch]
(Compose
(ResultFunctor
(Fixed (ParserT ((,) [[Lexeme t]])) (Only [ExtensionSwitch]) t))
((,) t))
forall s (g :: (* -> *) -> *).
(ParserInput
(Fixed (ParserT ((,) [[Lexeme t]])) (Only [ExtensionSwitch]) t)
~ s,
GrammarConstraint
(Fixed (ParserT ((,) [[Lexeme t]])) (Only [ExtensionSwitch]) t) g,
Eq s, FactorialMonoid s) =>
g (Fixed (ParserT ((,) [[Lexeme t]])) (Only [ExtensionSwitch]) t)
-> s
-> g (Compose
(ResultFunctor
(Fixed (ParserT ((,) [[Lexeme t]])) (Only [ExtensionSwitch]) t))
((,) s))
forall (m :: * -> *) s (g :: (* -> *) -> *).
(MultiParsing m, ParserInput m ~ s, GrammarConstraint m g, Eq s,
FactorialMonoid s) =>
g m -> s -> g (Compose (ResultFunctor m) ((,) s))
parsePrefix Fixed
(ParserT ((,) [[Lexeme t]]))
(Only [ExtensionSwitch])
t
[ExtensionSwitch]
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t,
LexicalParsing (Parser g t)) =>
Parser g t [ExtensionSwitch]
languagePragmas t
source
parseResults :: Compose (Compose (Either (ParseFailure (Down Int) t)) []) ((,) a) a
-> Either (ParseFailure (Down Int) t) [a]
parseResults = Compose (Either (ParseFailure (Down Int) t)) [] a
-> Either (ParseFailure (Down Int) t) [a]
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose (Compose (Either (ParseFailure (Down Int) t)) [] a
-> Either (ParseFailure (Down Int) t) [a])
-> (Compose
(Compose (Either (ParseFailure (Down Int) t)) []) ((,) a) a
-> Compose (Either (ParseFailure (Down Int) t)) [] a)
-> Compose
(Compose (Either (ParseFailure (Down Int) t)) []) ((,) a) a
-> Either (ParseFailure (Down Int) t) [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, a) -> a)
-> Compose (Either (ParseFailure (Down Int) t)) [] (a, a)
-> Compose (Either (ParseFailure (Down Int) t)) [] a
forall a b.
(a -> b)
-> Compose (Either (ParseFailure (Down Int) t)) [] a
-> Compose (Either (ParseFailure (Down Int) t)) [] b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a, a) -> a
forall a b. (a, b) -> b
snd (Compose (Either (ParseFailure (Down Int) t)) [] (a, a)
-> Compose (Either (ParseFailure (Down Int) t)) [] a)
-> (Compose
(Compose (Either (ParseFailure (Down Int) t)) []) ((,) a) a
-> Compose (Either (ParseFailure (Down Int) t)) [] (a, a))
-> Compose
(Compose (Either (ParseFailure (Down Int) t)) []) ((,) a) a
-> Compose (Either (ParseFailure (Down Int) t)) [] a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose (Compose (Either (ParseFailure (Down Int) t)) []) ((,) a) a
-> Compose (Either (ParseFailure (Down Int) t)) [] (a, a)
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
positiveKeys :: Map k Bool -> Set k
positiveKeys = Map k Bool -> Set k
forall k a. Map k a -> Set k
Map.keysSet (Map k Bool -> Set k)
-> (Map k Bool -> Map k Bool) -> Map k Bool -> Set k
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Bool) -> Map k Bool -> Map k Bool
forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter Bool -> Bool
forall a. a -> a
id
getSwitch :: ExtensionSwitch -> (Extension, Bool)
getSwitch (ExtensionSwitch (Extension, Bool)
s) = (Extension, Bool)
s
extendedGrammar :: forall l t.
(Abstract.ExtendedHaskell l, LexicalParsing (Parser (ExtendedGrammar l t (NodeWrap t)) t),
Ord t, Show t, OutlineMonoid t, SpaceMonoid t,
Abstract.DeeplyFoldable (Serialization (Down Int) t) l)
=> Set Extension -> Grammar (ExtendedGrammar l t (NodeWrap t)) (ParserT ((,) [[Lexeme t]])) t
extendedGrammar :: forall l t.
(ExtendedHaskell l,
LexicalParsing (Parser (ExtendedGrammar l t (NodeWrap t)) t),
Ord t, Show t, OutlineMonoid t, SpaceMonoid t,
DeeplyFoldable (Serialization (Down Int) t) l) =>
Set Extension
-> Grammar
(ExtendedGrammar l t (NodeWrap t)) (ParserT ((,) [[Lexeme t]])) t
extendedGrammar Set Extension
extensions = ([Set Extension]
-> Grammar
(ExtendedGrammar l t (NodeWrap t)) (ParserT ((,) [[Lexeme t]])) t)
-> [Set Extension]
-> Grammar
(ExtendedGrammar l t (NodeWrap t)) (ParserT ((,) [[Lexeme t]])) t
forall a v. Memoizable a => (a -> v) -> a -> v
forall v. ([Set Extension] -> v) -> [Set Extension] -> v
memoize [Set Extension]
-> Grammar
(ExtendedGrammar l t (NodeWrap t)) (ParserT ((,) [[Lexeme t]])) t
extendWith [Set Extension]
mixinKeys
where mixinKeys :: [Set Extension]
mixinKeys :: [Set Extension]
mixinKeys = (Set Extension -> Bool) -> [Set Extension] -> [Set Extension]
forall a. (a -> Bool) -> [a] -> [a]
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter ((Extension -> Bool) -> Set Extension -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Extension -> Set Extension -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set Extension
extensions)) ([Set Extension] -> [Set Extension])
-> [Set Extension] -> [Set Extension]
forall a b. (a -> b) -> a -> b
$ Set (Set Extension) -> [Set Extension]
forall a. Set a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (Set (Set Extension) -> [Set Extension])
-> Set (Set Extension) -> [Set Extension]
forall a b. (a -> b) -> a -> b
$ Map
(Set Extension)
[(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))]
-> Set (Set Extension)
forall k a. Map k a -> Set k
Map.keysSet (Map
(Set Extension)
[(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))]
-> Set (Set Extension))
-> Map
(Set Extension)
[(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))]
-> Set (Set Extension)
forall a b. (a -> b) -> a -> b
$ forall l (g :: (* -> *) -> *) t.
(ExtendedHaskell l,
LexicalParsing (Parser (ExtendedGrammar l t (NodeWrap t)) t),
Ord t, Show t, OutlineMonoid t, SpaceMonoid t,
DeeplyFoldable (Serialization (Down Int) t) l,
g ~ ExtendedGrammar l t (NodeWrap t)) =>
Map (Set Extension) [(Int, GrammarOverlay g (Parser g t))]
extensionMixins @l @_ @t
extendWith :: [Set Extension] -> Grammar (ExtendedGrammar l t (NodeWrap t)) (ParserT ((,) [[Lexeme t]])) t
extendWith :: [Set Extension]
-> Grammar
(ExtendedGrammar l t (NodeWrap t)) (ParserT ((,) [[Lexeme t]])) t
extendWith = (Grammar
(ExtendedGrammar l t (NodeWrap t)) (ParserT ((,) [[Lexeme t]])) t
-> Grammar
(ExtendedGrammar l t (NodeWrap t)) (ParserT ((,) [[Lexeme t]])) t)
-> [GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)]
-> Grammar
(ExtendedGrammar l t (NodeWrap t)) (ParserT ((,) [[Lexeme t]])) t
forall (m :: * -> *) (g :: (* -> *) -> *) (f :: * -> *).
(GrammarParsing m, g ~ ParserGrammar m, GrammarConstraint m g,
Distributive g, Foldable f) =>
(g m -> g m) -> f (GrammarOverlay g m) -> g m
overlay Grammar
(ExtendedGrammar l t (NodeWrap t)) (ParserT ((,) [[Lexeme t]])) t
-> Grammar
(ExtendedGrammar l t (NodeWrap t)) (ParserT ((,) [[Lexeme t]])) t
forall {t} {l} {g :: (* -> *) -> *}.
(Foldable (Serialization (Down Int) t) (Statement l l),
Foldable (Serialization (Down Int) t) (Import l l),
Foldable (Serialization (Down Int) t) (Expression l l),
Foldable (Serialization (Down Int) t) (Declaration l l),
Foldable (Serialization (Down Int) t) (CaseAlternative l l),
OutlineMonoid t, Show t, Ord t, Haskell l, Apply g,
Foldable (CaseAlternative l l (Wrapped (Down Int) t)),
Foldable (Declaration l l (Wrapped (Down Int) t)),
Foldable (Expression l l (Wrapped (Down Int) t)),
Foldable (Import l l (Wrapped (Down Int) t)),
Foldable (Statement l l (Wrapped (Down Int) t))) =>
ExtendedGrammar
l t (Wrapped (Down Int) t) (ParserT ((,) [[Lexeme t]]) g t)
-> ExtendedGrammar
l t (Wrapped (Down Int) t) (ParserT ((,) [[Lexeme t]]) g t)
extendedReport ([GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)]
-> Grammar
(ExtendedGrammar l t (NodeWrap t)) (ParserT ((,) [[Lexeme t]])) t)
-> ([Set Extension]
-> [GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)])
-> [Set Extension]
-> Grammar
(ExtendedGrammar l t (NodeWrap t)) (ParserT ((,) [[Lexeme t]])) t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)]
-> [GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)]
forall a. [a] -> [a]
reverse
([GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)]
-> [GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)])
-> ([Set Extension]
-> [GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)])
-> [Set Extension]
-> [GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)
forall l (g :: (* -> *) -> *) t.
(ExtendedHaskell l,
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)) =>
ExtensionOverlay l g t
initialOverlay GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)
-> [GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)]
-> [GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)]
forall a. a -> [a] -> [a]
:) ([GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)]
-> [GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)])
-> ([Set Extension]
-> [GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)])
-> [Set Extension]
-> [GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))
-> GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))
-> [(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))]
-> [GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)]
forall a b. (a -> b) -> [a] -> [b]
map (Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))
-> GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)
forall a b. (a, b) -> b
snd ([(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))]
-> [GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)])
-> ([Set Extension]
-> [(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))])
-> [Set Extension]
-> [GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))
-> Int)
-> [(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))]
-> [(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))]
forall b a. Ord b => (a -> b) -> [a] -> [a]
List.sortOn (Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))
-> Int
forall a b. (a, b) -> a
fst ([(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))]
-> [(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))])
-> ([Set Extension]
-> [(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))])
-> [Set Extension]
-> [(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))]]
-> [(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))]
forall m. Monoid m => [m] -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold ([[(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))]]
-> [(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))])
-> ([Set Extension]
-> [[(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))]])
-> [Set Extension]
-> [(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Set Extension
-> [(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))])
-> [Set Extension]
-> [[(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))]]
forall a b. (a -> b) -> [a] -> [b]
map (Map
(Set Extension)
[(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))]
forall l (g :: (* -> *) -> *) t.
(ExtendedHaskell l,
LexicalParsing (Parser (ExtendedGrammar l t (NodeWrap t)) t),
Ord t, Show t, OutlineMonoid t, SpaceMonoid t,
DeeplyFoldable (Serialization (Down Int) t) l,
g ~ ExtendedGrammar l t (NodeWrap t)) =>
Map (Set Extension) [(Int, GrammarOverlay g (Parser g t))]
extensionMixins Map
(Set Extension)
[(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))]
-> Set Extension
-> [(Int,
GrammarOverlay
(ExtendedGrammar l t (NodeWrap t))
(Parser (ExtendedGrammar l t (NodeWrap t)) t))]
forall k a. Ord k => Map k a -> k -> a
Map.!)
extendedReport :: ExtendedGrammar
l t (Wrapped (Down Int) t) (ParserT ((,) [[Lexeme t]]) g t)
-> ExtendedGrammar
l t (Wrapped (Down Int) t) (ParserT ((,) [[Lexeme t]]) g t)
extendedReport ExtendedGrammar
l t (Wrapped (Down Int) t) (ParserT ((,) [[Lexeme t]]) g t)
g = ExtendedGrammar
l t (Wrapped (Down Int) t) (ParserT ((,) [[Lexeme t]]) g t)
g{report = Report.grammar g.report}
initialOverlay :: forall l g t. (Abstract.ExtendedHaskell l,
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))
=> ExtensionOverlay l g t
initialOverlay :: forall l (g :: (* -> *) -> *) t.
(ExtendedHaskell l,
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)) =>
ExtensionOverlay l g t
initialOverlay g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
declarationLevel= super.report.declarationLevel{
classLHS = self.report.declarationLevel.simpleType,
simpleType =
Abstract.simpleTypeLHS <$> self.report.typeConstructor <*> pure []
<|> Abstract.infixTypeLHSApplication
<$> self.extensions.typeVarBinder
<* terminator "`"
<*> self.report.declarationLevel.typeClass
<* terminator "`"
<*> self.extensions.typeVarBinder
<|> Abstract.typeLHSApplication
<$> wrap self.report.declarationLevel.simpleType
<*> self.extensions.typeVarBinder,
optionalTypeSignatureContext = pure Abstract.noContext,
context =
self.report.declarationLevel.constraint
<|> self.extensions.equalityConstraint
<|> Abstract.constraints <$> parens (wrap (self.report.declarationLevel.constraint
<|> self.extensions.equalityConstraint
<|> self.extensions.implicitParameterConstraint) `sepBy` comma),
instanceDesignator = self.extensions.instanceDesignatorApplications,
instanceTypeDesignator = self.report.aType},
pattern = self.extensions.infixPattern,
lPattern = self.report.aPattern
<|> Abstract.literalPattern
<$ delimiter "-"
<*> wrap ((Abstract.integerLiteral . negate) <$> self.report.integer
<|> (Abstract.floatingLiteral . negate) <$> self.report.float)
<|> Abstract.constructorPattern
<$> wrap self.report.generalConstructor
<*> some (wrap self.extensions.conArgPattern),
aPattern = self.extensions.conArgPattern,
aType = self.report.generalTypeConstructor
<|> Abstract.typeVariable <$> self.report.typeVar
<|> parens self.report.typeTerm
<|> Abstract.typeWildcard <$ keyword "_"
<|> Abstract.groundType <$ self.extensions.groundTypeKind,
generalTypeConstructor =
Abstract.constructorType <$> wrap (Abstract.constructorReference <$> self.report.qualifiedConstructor)
<|> Abstract.functionConstructorType <$ parens self.report.rightArrow,
typeTerm = self.extensions.arrowType},
extensions = super.extensions{
keywordForall = empty,
kindSignature = empty,
groundTypeKind = empty,
derivingStrategy = empty,
arrowType = self.extensions.cType
<|> Abstract.functionType <$> wrap self.extensions.cType
<* self.report.rightArrow
<*> wrap self.extensions.arrowType
<|> Abstract.constrainedType <$> wrap self.report.declarationLevel.context
<* self.report.rightDoubleArrow
<*> wrap self.extensions.arrowType,
cType = self.report.bType,
equalityConstraint = empty,
implicitParameterConstraint = empty,
infixPattern = super.report.pattern,
promotedLiteral = empty,
promotedStructure = empty,
inClassOrInstanceTypeFamilyDeclaration = empty,
instanceDesignatorBase =
Abstract.classReferenceInstanceLHS <$> self.report.declarationLevel.qualifiedTypeClass
<|> parens self.report.declarationLevel.instanceDesignator,
instanceDesignatorApplications =
self.extensions.instanceDesignatorBase
<|> Abstract.classInstanceLHSApplication
<$> wrap self.extensions.instanceDesignatorApplications
<*> wrap self.report.declarationLevel.instanceTypeDesignator,
optionalForall = pure [],
optionallyParenthesizedTypeVar = self.report.typeVar,
optionallyKindedAndParenthesizedTypeVar = Abstract.typeVariable <$> self.extensions.optionallyParenthesizedTypeVar,
optionallyKindedTypeVar = empty,
typeVarBinder = Abstract.implicitlyKindedTypeVariable <$> self.report.typeVar,
gadtConstructors =
Abstract.gadtConstructors <$> self.extensions.constructorIDs
<* self.report.doubleColon
<*> self.extensions.optionalForall
<*> wrap self.report.declarationLevel.optionalContext
<*> wrap self.extensions.gadtBody,
gadtNewConstructor =
Abstract.gadtConstructors <$> ((:|[]) <$> self.report.constructor) <* self.report.doubleColon
<*> self.extensions.optionalForall
<*> wrap (pure Abstract.noContext
<|> self.report.declarationLevel.context
*> self.report.rightDoubleArrow
*> fail "No context allowed on GADT newtype")
<*> wrap self.extensions.gadtNewBody,
constructorIDs = self.report.constructor `sepByNonEmpty` comma,
gadtNewBody =
parens self.extensions.gadtNewBody
<|> Abstract.functionType
<$> wrap self.report.bType
<* self.report.rightArrow
<*> wrap (self.extensions.return_type)
<|> Abstract.recordFunctionType
<$> braces ((:[]) <$> wrap self.report.declarationLevel.fieldDeclaration)
<* self.report.rightArrow
<*> wrap (self.extensions.return_type),
gadtBody = (self.extensions.prefix_gadt_body) <|> (self.extensions.record_gadt_body),
prefix_gadt_body =
parens (self.extensions.prefix_gadt_body)
<|> (self.extensions.return_type)
<|> Abstract.functionType
<$> wrap (self.report.bType <|> self.report.declarationLevel.strictType)
<* self.report.rightArrow
<*> wrap (self.extensions.prefix_gadt_body),
record_gadt_body =
parens (self.extensions.record_gadt_body)
<|> Abstract.recordFunctionType
<$> braces (wrap self.report.declarationLevel.fieldDeclaration `sepBy` comma)
<* self.report.rightArrow
<*> wrap (self.extensions.return_type),
return_type = Abstract.typeApplication
<$> wrap ((self.extensions.return_type) <|> parens (self.extensions.return_type))
<*> wrap (self.extensions.arg_type)
<|> self.report.generalTypeConstructor,
conArgPattern = super.report.aPattern,
arg_type = self.report.aType,
binary = empty}}
identifierSyntaxMixin :: ExtensionOverlay l g t
identifierSyntaxMixin :: forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
identifierSyntaxMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
variableIdentifier = token (Abstract.name . Text.pack . toString mempty <$> variableLexeme),
constructorIdentifier = token (Abstract.name . Text.pack . toString mempty <$> constructorLexeme),
variableSymbol = token (Abstract.name . Text.pack . toString mempty <$> Report.variableSymbolLexeme),
constructorSymbol = token (Abstract.name . Text.pack . toString mempty <$> Report.constructorSymbolLexeme)}}
overloadedLabelsMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
overloadedLabelsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
overloadedLabelsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
bareExpression = super.report.bareExpression
<|> Abstract.overloadedLabel . Text.pack . toString mempty
<$> token (string "#" *> variableLexeme),
variableSymbol = notFollowedBy (string "#" *> variableLexeme) *> super.report.variableSymbol}}
unicodeSyntaxMixin :: ExtensionOverlay l g t
unicodeSyntaxMixin :: forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
unicodeSyntaxMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
keywordForall = super.extensions.keywordForall <|> delimiter "∀"},
report= super.report{
doubleColon = super.report.doubleColon <|> delimiter "∷",
rightDoubleArrow = super.report.rightDoubleArrow <|> delimiter "⇒",
rightArrow = super.report.rightArrow <|> delimiter "→",
leftArrow = super.report.leftArrow <|> delimiter "←",
variableSymbol = notSatisfyChar (`elem` ("∀←→⇒∷★" :: [Char])) *> super.report.variableSymbol}}
listTuplePunsMixin :: forall l g t. ExtensionOverlay l g t
listTuplePunsMixin :: forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
listTuplePunsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
aType = super.report.aType
<|> Abstract.tupleType <$> parens ((:|) <$> wrap self.report.typeTerm
<*> some (comma *> wrap self.report.typeTerm))
<|> Abstract.listType <$> brackets (wrap self.report.typeTerm),
generalTypeConstructor = super.report.generalTypeConstructor
<|> Abstract.constructorType
<$> wrap (Abstract.unitConstructor <$ terminator "(" <* terminator ")"
<|> Abstract.emptyListConstructor <$ terminator "[" <* terminator "]"
<|> Abstract.tupleConstructor . succ . length <$> parens (some comma))}}
unboxedTuplesMixin :: forall l g t. Abstract.ExtendedWith '[ 'UnboxedTuples ] l => ExtensionOverlay l g t
unboxedTuplesMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'UnboxedTuples] l =>
ExtensionOverlay l g t
unboxedTuplesMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
conArgPattern = super.extensions.conArgPattern
<|> Abstract.unboxedTuplePattern Abstract.build
<$> hashParens (wrap self.report.pPattern `sepByNonEmpty` comma)},
report= super.report{
generalConstructor = super.report.generalConstructor
<|> Abstract.unboxedTupleConstructor Abstract.build . succ . length
<$> hashParens (many comma),
bareExpression = super.report.bareExpression
<|> Abstract.unboxedTupleExpression Abstract.build
<$> hashParens (self.report.expression `sepByNonEmpty` comma)}}
where hashParens :: Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
hashParens Fixed (ParserT ((,) [[Lexeme t]])) g t a
p = t -> Parser g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
t -> Parser g t ()
delimiter t
"(#" Parser g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) 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 b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Fixed (ParserT ((,) [[Lexeme t]])) g t a
p Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Parser g t () -> Fixed (ParserT ((,) [[Lexeme t]])) 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
<* t -> Parser g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
t -> Parser g t ()
terminator t
"#)"
unboxedListTuplePunsMixin :: forall l g t. Abstract.ExtendedWith '[ 'UnboxedTuples ] l => ExtensionOverlay l g t
unboxedListTuplePunsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'UnboxedTuples] l =>
ExtensionOverlay l g t
unboxedListTuplePunsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
aType = super.report.aType
<|> Abstract.unboxedTupleType Abstract.build
<$> hashParens (wrap self.report.typeTerm `sepByNonEmpty` comma),
generalTypeConstructor = super.report.generalTypeConstructor
<|> Abstract.constructorType
<$> wrap (Abstract.unboxedTupleConstructor Abstract.build . succ . length
<$> hashParens (many comma))}}
where hashParens :: Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
hashParens Fixed (ParserT ((,) [[Lexeme t]])) g t a
p = t -> Parser g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
t -> Parser g t ()
delimiter t
"(#" Parser g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) 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 b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Fixed (ParserT ((,) [[Lexeme t]])) g t a
p Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Parser g t () -> Fixed (ParserT ((,) [[Lexeme t]])) 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
<* t -> Parser g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
t -> Parser g t ()
terminator t
"#)"
unboxedTupleSectionsMixin :: forall l g t. Abstract.ExtendedWith '[ 'UnboxedTuples ] l => ExtensionOverlay l g t
unboxedTupleSectionsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'UnboxedTuples] l =>
ExtensionOverlay l g t
unboxedTupleSectionsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
bareExpression = super.report.bareExpression
<|> Abstract.unboxedTupleSectionExpression Abstract.build
<$> hashParens (filter (\NonEmpty
(Maybe (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t))))
l-> (Maybe (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t)))
-> Bool)
-> NonEmpty
(Maybe (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t))))
-> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Maybe (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t)))
-> Bool
forall a. Maybe a -> Bool
isJust NonEmpty
(Maybe (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t))))
l Bool -> Bool -> Bool
&& (Maybe (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t)))
-> Bool)
-> NonEmpty
(Maybe (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t))))
-> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Maybe (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t)))
-> Bool
forall a. Maybe a -> Bool
isNothing NonEmpty
(Maybe (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t))))
l)
$ optional self.report.expression `sepByNonEmpty` comma)}}
where hashParens :: Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
hashParens Fixed (ParserT ((,) [[Lexeme t]])) g t a
p = t -> Parser g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
t -> Parser g t ()
delimiter t
"(#" Parser g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) 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 b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Fixed (ParserT ((,) [[Lexeme t]])) g t a
p Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Parser g t () -> Fixed (ParserT ((,) [[Lexeme t]])) 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
<* t -> Parser g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
t -> Parser g t ()
terminator t
"#)"
unboxedSumsMixin :: forall l g t. Abstract.ExtendedWith '[ 'UnboxedSums ] l => ExtensionOverlay l g t
unboxedSumsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'UnboxedSums] l =>
ExtensionOverlay l g t
unboxedSumsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
conArgPattern = super.extensions.conArgPattern
<|> hashParens (Abstract.unboxedSumPattern Abstract.build
<$> (length <$> some (delimiter "|"))
<*> wrap self.report.pPattern
<*> (length <$> many (delimiter "|"))
<|> Abstract.unboxedSumPattern Abstract.build 0
<$> wrap self.report.pPattern
<*> (length <$> some (delimiter "|")))},
report= super.report{
generalConstructor = super.report.generalConstructor
<|> Abstract.unboxedSumConstructor Abstract.build . succ . length
<$> hashParens (some $ delimiter "|"),
bareExpression = super.report.bareExpression
<|> hashParens (Abstract.unboxedSumExpression Abstract.build
<$> (length <$> some (delimiter "|"))
<*> self.report.expression
<*> (length <$> many (delimiter "|"))
<|> Abstract.unboxedSumExpression Abstract.build 0
<$> self.report.expression
<*> (length <$> some (delimiter "|")))}}
where hashParens :: Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
hashParens Fixed (ParserT ((,) [[Lexeme t]])) g t a
p = t -> Parser g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
t -> Parser g t ()
delimiter t
"(#" Parser g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) 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 b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Fixed (ParserT ((,) [[Lexeme t]])) g t a
p Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Parser g t () -> Fixed (ParserT ((,) [[Lexeme t]])) 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
<* t -> Parser g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
t -> Parser g t ()
terminator t
"#)"
unboxedSumPunsMixin :: forall l g t. Abstract.ExtendedWith '[ 'UnboxedSums ] l => ExtensionOverlay l g t
unboxedSumPunsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'UnboxedSums] l =>
ExtensionOverlay l g t
unboxedSumPunsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
aType = super.report.aType
<|> Abstract.unboxedSumType Abstract.build
<$> hashParens ((:|) <$> wrap self.report.typeTerm
<*> some (delimiter "|" *> wrap self.report.typeTerm)),
generalTypeConstructor = super.report.generalTypeConstructor
<|> Abstract.constructorType
<$> wrap (Abstract.unboxedSumConstructor Abstract.build . succ . length
<$> hashParens (some $ delimiter "|"))}}
where hashParens :: Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
hashParens Fixed (ParserT ((,) [[Lexeme t]])) g t a
p = t -> Parser g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
t -> Parser g t ()
delimiter t
"(#" Parser g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Fixed (ParserT ((,) [[Lexeme t]])) 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 b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Fixed (ParserT ((,) [[Lexeme t]])) g t a
p Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> Parser g t () -> Fixed (ParserT ((,) [[Lexeme t]])) 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
<* t -> Parser g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
t -> Parser g t ()
terminator t
"#)"
interruptibleFFIMixin :: forall l g t. Abstract.ExtendedWith '[ 'InterruptibleFFI ] l => ExtensionOverlay l g t
interruptibleFFIMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'InterruptibleFFI] l =>
ExtensionOverlay l g t
interruptibleFFIMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
declarationLevel= super.report.declarationLevel{
safety = super.report.declarationLevel.safety
<|> Abstract.interruptibleCall Abstract.build <$ keyword "interruptible"}}}
cApiFFIMixin :: forall l g t. Abstract.ExtendedWith '[ 'CApiFFI ] l => ExtensionOverlay l g t
cApiFFIMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'CApiFFI] l =>
ExtensionOverlay l g t
cApiFFIMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
declarationLevel= super.report.declarationLevel{
callingConvention = super.report.declarationLevel.callingConvention
<|> Abstract.cApiCall Abstract.build <$ keyword "capi"}}}
extendedLiteralsMixin :: (SpaceMonoid t, Abstract.ExtendedWith '[ 'ExtendedLiterals ] l) => ExtensionOverlay l g t
extendedLiteralsMixin :: forall t l (g :: (* -> *) -> *).
(SpaceMonoid t, ExtendedWith '[ 'ExtendedLiterals] l) =>
ExtensionOverlay l g t
extendedLiteralsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
literalLexeme = super.report.literalLexeme
<* notFollowedBy ((filter (precededByString "#") getInput <|> string "#")
*> void (Text.Parser.Char.satisfy Char.isUpper))
<|> Abstract.extendedLiteral Abstract.build
<$> storeToken self.report.integerLexeme
<*> hashType}}
where hashType :: Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
hashType = Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t a
storeToken (ParserInput (Parser g t)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Parser g t)
"#") Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
-> Fixed (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
*> g (Parser g t)
self.report.typeConstructor
magicHashMixin :: forall l g t. (SpaceMonoid t, Abstract.ExtendedHaskell l) => ExtensionOverlay l g t
magicHashMixin :: forall l (g :: (* -> *) -> *) t.
(SpaceMonoid t, ExtendedHaskell l) =>
ExtensionOverlay l g t
magicHashMixin g (Parser g t)
self g (Parser g t)
super =
let prefixMinusFollow :: Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
prefixMinusFollow = (Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile1 Char -> Bool
Char.isDigit Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser 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 (ParserInput (Parser g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
takeCharsWhile Char -> Bool
isNumChar Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser 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
*> ParserInput (Parser g t)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string ParserInput (Parser g t)
"#"
isNumChar :: Char -> Bool
isNumChar Char
c = Char -> Bool
Char.isHexDigit Char
c Bool -> Bool -> Bool
|| Char
c Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (String
"eE.bBoOxX_" :: String)
in g (Parser g t)
super{report= super.report{
variableIdentifier =
token (Abstract.name . Text.pack . toString mempty <$> (variableLexeme <> concatAll (string "#"))),
constructorIdentifier =
token (Abstract.name . Text.pack . toString mempty <$> (constructorLexeme <> concatAll (string "#"))),
literalLexeme = super.report.literalLexeme
<**> (Abstract.hashLiteral . Abstract.hashLiteral <$ string "##"
<<|> Abstract.hashLiteral <$ string "#"
<<|> pure id),
integerLexeme = super.report.integerLexeme
<<|> negate <$ string "-" <*> super.report.integerLexeme <* lookAhead (string "#"),
floatLexeme = super.report.floatLexeme
<<|> negate <$ string "-" <*> super.report.floatLexeme <* lookAhead (string "#")}}
ExtendedGrammar l t (NodeWrap t) (Parser g t)
-> (ExtendedGrammar l t (NodeWrap t) (Parser g t)
-> g (Parser g t))
-> g (Parser g t)
forall a b. a -> (a -> b) -> b
& Fixed (ParserT ((,) [[Lexeme t]])) g t t -> ExtensionOverlay l g t
forall (g :: (* -> *) -> *) t l.
Parser g t t -> ExtensionOverlay l g t
negationConstraintMixin Fixed (ParserT ((,) [[Lexeme t]])) g t t
Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
prefixMinusFollow g (Parser g t)
self
recursiveDoMixin :: (OutlineMonoid t, Abstract.ExtendedWith '[ 'RecursiveDo ] l,
Abstract.DeeplyFoldable (Serialization (Down Int) t) l)
=> ExtensionOverlay l g t
recursiveDoMixin :: forall t l (g :: (* -> *) -> *).
(OutlineMonoid t, ExtendedWith '[ 'RecursiveDo] l,
DeeplyFoldable (Serialization (Down Int) t) l) =>
ExtensionOverlay l g t
recursiveDoMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
closedBlockExpression = super.report.closedBlockExpression
<|> Abstract.mdoExpression' Abstract.build <$ keyword "mdo" <*> wrap self.report.statements,
statement = super.report.statement
<|> wrap (Deep.InL
<$> Abstract.recursiveStatement' Abstract.build
. map Report.expressionToStatement
<$ keyword "rec"
<*> blockOf self.report.statement),
variableIdentifier = notFollowedBy (keyword "mdo" <|> keyword "rec") *> super.report.variableIdentifier}}
qualifiedDoMixin :: forall g t l. (OutlineMonoid t, Abstract.Haskell l, Abstract.ExtendedWith '[ 'QualifiedDo ] l,
Abstract.DeeplyFoldable (Serialization (Down Int) t) l)
=> ExtensionOverlay l g t
qualifiedDoMixin :: forall (g :: (* -> *) -> *) t l.
(OutlineMonoid t, Haskell l, ExtendedWith '[ 'QualifiedDo] l,
DeeplyFoldable (Serialization (Down Int) t) l) =>
ExtensionOverlay l g t
qualifiedDoMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
closedBlockExpression = super.report.closedBlockExpression
<|> Abstract.qualifiedDoExpression Abstract.build
<$> Report.storeToken (Abstract.moduleName <$> Report.moduleLexeme <* string ".")
<* keyword "do"
<*> wrap self.report.statements,
qualifiedVariableSymbol =
notFollowedBy (string "." *> optional (Report.moduleLexeme @g @l *> string ".") *> keyword "do")
*> super.report.qualifiedVariableSymbol}}
qualifiedRecursiveDoMixin :: forall g t l. (OutlineMonoid t, Abstract.Haskell l,
Abstract.ExtendedWith '[ 'QualifiedDo, 'RecursiveDo ] l,
Abstract.DeeplyFoldable (Serialization (Down Int) t) l)
=> ExtensionOverlay l g t
qualifiedRecursiveDoMixin :: forall (g :: (* -> *) -> *) t l.
(OutlineMonoid t, Haskell l,
ExtendedWith '[ 'QualifiedDo, 'RecursiveDo] l,
DeeplyFoldable (Serialization (Down Int) t) l) =>
ExtensionOverlay l g t
qualifiedRecursiveDoMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
closedBlockExpression = super.report.closedBlockExpression
<|> Abstract.mdoQualifiedExpression Abstract.build
<$> Report.storeToken (Abstract.moduleName <$> Report.moduleLexeme <* string ".")
<* keyword "mdo"
<*> wrap self.report.statements,
qualifiedVariableSymbol =
notFollowedBy (string "." *> optional (Report.moduleLexeme @g @l *> string ".") *> keyword "mdo")
*> super.report.qualifiedVariableSymbol}}
parallelListComprehensionsMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
parallelListComprehensionsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
parallelListComprehensionsMixin self :: g (Parser g t)
self@ExtendedGrammar{report :: forall l t (f :: * -> *) (p :: * -> *).
ExtendedGrammar l t f p -> HaskellGrammar l t f p
report= HaskellGrammar{Parser
g
t
(NonEmpty (NodeWrap t (Statement l l (NodeWrap t) (NodeWrap t))))
qualifiers :: Parser
g
t
(NonEmpty (NodeWrap t (Statement l l (NodeWrap t) (NodeWrap t))))
qualifiers :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (NonEmpty (f (Statement l l f f)))
qualifiers, Parser g t (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t)))
expression :: Parser g t (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t)))
expression :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p (f (Expression l l f f))
expression}} g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
bareExpression = super.report.bareExpression
<|> brackets (Abstract.parallelListComprehension
<$> expression <*> qualifiers <*> qualifiers <*> many qualifiers)}}
tupleSectionsMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
tupleSectionsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
tupleSectionsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
bareExpression = super.report.bareExpression
<|> Abstract.tupleSectionExpression
<$> parens (filter (\NonEmpty
(Maybe (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t))))
l-> (Maybe (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t)))
-> Bool)
-> NonEmpty
(Maybe (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t))))
-> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Maybe (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t)))
-> Bool
forall a. Maybe a -> Bool
isJust NonEmpty
(Maybe (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t))))
l Bool -> Bool -> Bool
&& (Maybe (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t)))
-> Bool)
-> NonEmpty
(Maybe (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t))))
-> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Maybe (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t)))
-> Bool
forall a. Maybe a -> Bool
isNothing NonEmpty
(Maybe (NodeWrap t (Expression l l (NodeWrap t) (NodeWrap t))))
l)
$ (:|) <$> optional self.report.expression
<*> some (comma *> optional self.report.expression))}}
lambdaCaseMixin :: forall l g t. (Abstract.ExtendedWith '[ 'LambdaCase ] l, OutlineMonoid t,
Deep.Foldable (Serialization (Down Int) t) (Abstract.LambdaCasesAlternative l l))
=> ExtensionOverlay l g t
lambdaCaseMixin :: forall l (g :: (* -> *) -> *) t.
(ExtendedWith '[ 'LambdaCase] l, OutlineMonoid t,
Foldable
(Serialization (Down Int) t) (LambdaCasesAlternative l l)) =>
ExtensionOverlay l g t
lambdaCaseMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
openBlockExpression = notFollowedBy (delimiter "\\" *> keyword "cases") *> super.report.openBlockExpression,
closedBlockExpression = super.report.closedBlockExpression
<|> Abstract.lambdaCaseExpression Abstract.build <$ (delimiter "\\" *> keyword "case")
<*> self.report.alternatives
<|> Abstract.lambdaCasesExpression Abstract.build <$ (delimiter "\\" *> keyword "cases")
<*> blockOf (wrap $ Abstract.lambdaCasesAlternative @l Abstract.build
<$> many (wrap self.report.aPattern)
<*> wrap (Abstract.normalRHS <$ delimiter "->" <*> self.report.expression
<|> Abstract.guardedRHS
<$> takeSomeNonEmpty (wrap $ Abstract.guardedExpression . toList
<$> self.report.guards
<* delimiter "->"
<*> self.report.expression)))}}
emptyCaseMixin :: (OutlineMonoid t, Abstract.ExtendedHaskell l,
Deep.Foldable (Serialization (Down Int) t) (Abstract.CaseAlternative l l))
=> ExtensionOverlay l g t
emptyCaseMixin :: forall t l (g :: (* -> *) -> *).
(OutlineMonoid t, ExtendedHaskell l,
Foldable (Serialization (Down Int) t) (CaseAlternative l l)) =>
ExtensionOverlay l g t
emptyCaseMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
alternatives = blockOf (wrap super.report.alternative)}}
multiWayIfMixin :: (OutlineMonoid t, Abstract.ExtendedHaskell l,
Deep.Foldable (Serialization (Down Int) t) (Abstract.GuardedExpression l l))
=> ExtensionOverlay l g t
multiWayIfMixin :: forall t l (g :: (* -> *) -> *).
(OutlineMonoid t, ExtendedHaskell l,
Foldable (Serialization (Down Int) t) (GuardedExpression l l)) =>
ExtensionOverlay l g t
multiWayIfMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
closedBlockExpression = super.report.closedBlockExpression
<|> Abstract.multiWayIfExpression <$ keyword "if"
<*> blockOf' (wrap (Abstract.guardedExpression . toList
<$> self.report.guards
<* self.report.rightArrow
<*> self.report.expression))}}
packageImportsMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
packageImportsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
packageImportsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
moduleLevel= super.report.moduleLevel{
importDeclaration = super.report.moduleLevel.importDeclaration
<|> Abstract.packageQualifiedImportDeclaration <$ keyword "import"
<*> (True <$ keyword "qualified" <|> pure False)
<*> self.report.stringLiteral
<*> moduleId
<*> optional (keyword "as" *> moduleId)
<*> optional (wrap self.report.moduleLevel.importSpecification)}}}
safeImportsMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
safeImportsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
safeImportsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
moduleLevel= super.report.moduleLevel{
importDeclaration = super.report.moduleLevel.importDeclaration
<|> Abstract.safeImportDeclaration <$ keyword "import" <* keyword "safe"
<*> (True <$ keyword "qualified" <|> pure False)
<*> moduleId
<*> optional (keyword "as" *> moduleId)
<*> optional (wrap self.report.moduleLevel.importSpecification)}}}
importQualifiedPostMixin :: ExtensionOverlay l g t
importQualifiedPostMixin :: forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
importQualifiedPostMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
moduleLevel= super.report.moduleLevel{
importDeclaration = super.report.moduleLevel.importDeclaration
<|> flip Abstract.importDeclaration <$ keyword "import"
<*> moduleId
<*> (True <$ keyword "qualified")
<*> optional (keyword "as" *> moduleId)
<*> optional (wrap self.report.moduleLevel.importSpecification)}}}
safePackageImportsMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
safePackageImportsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
safePackageImportsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
moduleLevel= super.report.moduleLevel{
importDeclaration = super.report.moduleLevel.importDeclaration
<|> Abstract.safePackageQualifiedImportDeclaration <$ keyword "import" <* keyword "safe"
<*> (True <$ keyword "qualified" <|> pure False)
<*> self.report.stringLiteral
<*> moduleId
<*> optional (keyword "as" *> moduleId)
<*> optional (wrap self.report.moduleLevel.importSpecification)}}}
packageImportsQualifiedPostMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
packageImportsQualifiedPostMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
packageImportsQualifiedPostMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
moduleLevel= super.report.moduleLevel{
importDeclaration = super.report.moduleLevel.importDeclaration
<|> Abstract.packageQualifiedImportDeclaration <$ keyword "import"
<**> pure flip
<*> self.report.stringLiteral
<**> pure flip
<*> moduleId
<*> (True <$ keyword "qualified" <|> pure False)
<*> optional (keyword "as" *> moduleId)
<*> optional (wrap self.report.moduleLevel.importSpecification)}}}
safeImportsQualifiedPostMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
safeImportsQualifiedPostMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
safeImportsQualifiedPostMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
moduleLevel= super.report.moduleLevel{
importDeclaration = super.report.moduleLevel.importDeclaration
<|> flip Abstract.safeImportDeclaration <$ keyword "import" <* keyword "safe"
<*> moduleId
<*> (True <$ keyword "qualified" <|> pure False)
<*> optional (keyword "as" *> moduleId)
<*> optional (wrap self.report.moduleLevel.importSpecification)}}}
safePackageImportsQualifiedPostMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
safePackageImportsQualifiedPostMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
safePackageImportsQualifiedPostMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
moduleLevel= super.report.moduleLevel{
importDeclaration = super.report.moduleLevel.importDeclaration
<|> Abstract.safePackageQualifiedImportDeclaration <$ keyword "import" <* keyword "safe"
<**> pure flip
<*> self.report.stringLiteral
<**> pure flip
<*> moduleId
<*> (True <$ keyword "qualified" <|> pure False)
<*> optional (keyword "as" *> moduleId)
<*> optional (wrap self.report.moduleLevel.importSpecification)}}}
namedDefaultsMixin :: Abstract.ExtendedWith '[ 'NamedDefaults ] l => ExtensionOverlay l g t
namedDefaultsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'NamedDefaults] l =>
ExtensionOverlay l g t
namedDefaultsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
declarationLevel= super.report.declarationLevel{
topLevelDeclaration = super.report.declarationLevel.topLevelDeclaration
<|> Abstract.namedDefaultDeclaration Abstract.build <$ keyword "default"
<*> self.report.qualifiedConstructor
<*> parens (wrap self.report.typeTerm `sepBy` comma)}}}
explicitNamespacesMixin :: Abstract.ExtendedWith '[ 'ExplicitNamespaces ] l => ExtensionOverlay l g t
explicitNamespacesMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'ExplicitNamespaces] l =>
ExtensionOverlay l g t
explicitNamespacesMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
moduleLevel= super.report.moduleLevel{
export = super.report.moduleLevel.export
<|> Abstract.exportClassOrType <$ keyword "type"
<*> parens self.report.qualifiedVariableSymbol
<*> optional self.report.moduleLevel.members,
importItem = super.report.moduleLevel.importItem
<|> Abstract.importClassOrType <$ keyword "type"
<*> parens (self.report.variableSymbol <|> self.report.constructorSymbol)
<*> optional self.report.moduleLevel.members,
members = parens (Abstract.allMembers <$ delimiter ".."
<|> Abstract.explicitlyNamespacedMemberList Abstract.build
<$> (Abstract.defaultMember Abstract.build <$> self.report.moduleLevel.cname
<|> Abstract.typeMember Abstract.build <$ keyword "type"
<*> self.report.moduleLevel.cname)
`sepEndBy` comma)},
declarationLevel = super.report.declarationLevel {
generalDeclaration = super.report.declarationLevel.generalDeclaration
<|> Abstract.explicitTypeFixityDeclaration Abstract.build
<$> self.report.declarationLevel.fixity
<*> optional (fromIntegral <$> self.report.integer)
<* keyword "type"
<*> (self.report.operator `sepByNonEmpty` comma)
<|> Abstract.explicitDataFixityDeclaration Abstract.build
<$> self.report.declarationLevel.fixity
<*> optional (fromIntegral <$> self.report.integer)
<* keyword "data"
<*> (self.report.operator `sepByNonEmpty` comma)},
expression = super.report.expression
<|> wrap (Abstract.explicitTypeExpression Abstract.build <$ keyword "type" <*> wrap self.report.typeTerm),
pPattern = super.report.pPattern
<|> Abstract.explicitTypePattern Abstract.build <$ keyword "type" <*> wrap self.report.typeTerm}}
blockArgumentsMixin :: ExtensionOverlay l g t
blockArgumentsMixin :: forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
blockArgumentsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
lExpression = super.report.lExpression
<|> wrap (Abstract.applyExpression <$> self.report.fExpression
<*> wrap self.report.openBlockExpression),
dExpression = self.report.fExpression,
bareExpression = super.report.bareExpression <|> self.report.closedBlockExpression}}
spaceSensitiveOperatorsMixin :: SpaceMonoid t => ExtensionOverlay l g t
spaceSensitiveOperatorsMixin :: forall t l (g :: (* -> *) -> *).
SpaceMonoid t =>
ExtensionOverlay l g t
spaceSensitiveOperatorsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
conArgPattern = Abstract.variablePattern <$> super.report.variable <* lookAhead unreservedSymbolLexeme
<<|> notFollowedBy unreservedSymbolLexeme *> super.extensions.conArgPattern},
report= super.report{
variableSymbol = super.report.variableSymbol <|> Report.nameToken unreservedSymbolLexeme}}
unreservedSymbolLexeme :: (Rank2.Apply g, Ord t, SpaceMonoid t) => Parser g t t
unreservedSymbolLexeme :: forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, SpaceMonoid t) =>
Parser g t t
unreservedSymbolLexeme =
(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 t. SpaceMonoid t => t -> Bool
precededByOpenSpace 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
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
<|> 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 a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> 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 -> Bool
forall t. TextualMonoid t => t -> Bool
followedByCloseSpace 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
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 (Bool -> Bool
not (Bool -> Bool) -> (t -> Bool) -> t -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> Bool
forall t. SpaceMonoid t => t -> Bool
precededByOpenSpace) 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 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)
"~"
lexicalNegationMixin :: SpaceMonoid t => ExtensionOverlay l g t
lexicalNegationMixin :: forall t l (g :: (* -> *) -> *).
SpaceMonoid t =>
ExtensionOverlay l g t
lexicalNegationMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
qualifiedVariableSymbol = notFollowedBy (filter precededByOpenSpace getInput
*> string "-"
*> satisfyCharInput (\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
'['))
*> token (nameQualifier <*> self.report.variableSymbol),
prefixNegation = empty,
bareExpression = super.report.bareExpression
<|> Abstract.applyExpression <$> wrap (Abstract.negate <$ prefixMinus) <*> self.report.aExpression
<|> parens (Abstract.rightSectionExpression
<$> (notFollowedBy prefixMinus *> self.report.qualifiedOperator)
<*> self.report.infixExpression)}}
where prefixMinus :: Fixed (ParserT ((,) [[Lexeme t]])) g t ()
prefixMinus = Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ((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 t. SpaceMonoid t => t -> Bool
precededByOpenSpace Fixed (ParserT ((,) [[Lexeme t]])) g t t
Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *). InputParsing m => m (ParserInput m)
getInput
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 (Parser g t)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Parser g t)
"-"
Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser 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
<* Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (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 ((Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
satisfyCharInput ((Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t)))
-> (Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall a b. (a -> b) -> a -> b
$ \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
'[')
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
Modifier t
"-"]], ()))
Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> String -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> String -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"prefix -"
negativeLiteralsMixin :: ExtensionOverlay l g t
negativeLiteralsMixin :: forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
negativeLiteralsMixin g (Parser g t)
self g (Parser g t)
super =
g (Parser g t)
super{
report= super.report{
integerLexeme = (negate <$ string "-" <|> pure id) <*> super.report.integerLexeme,
floatLexeme = (negate <$ string "-" <|> pure id) <*> super.report.floatLexeme}}
ExtendedGrammar l t (NodeWrap t) (Parser g t)
-> (ExtendedGrammar l t (NodeWrap t) (Parser g t)
-> g (Parser g t))
-> g (Parser g t)
forall a b. a -> (a -> b) -> b
& Parser g t t -> ExtensionOverlay l g t
forall (g :: (* -> *) -> *) t l.
Parser g t t -> ExtensionOverlay l g t
negationConstraintMixin ((Char -> Bool) -> Parser g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputCharParsing m =>
(Char -> Bool) -> m (ParserInput m)
satisfyCharInput Char -> Bool
Char.isDigit) g (Parser g t)
self
binaryLiteralsMixin :: ExtensionOverlay l g t
binaryLiteralsMixin :: forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
binaryLiteralsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
binary = (string "0b" <|> string "0B") *> (takeCharsWhile1 (\Char
c-> Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'0' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'1') <?> "binary number")},
report = super.report{
integerLexeme = List.foldl' addBinary 0 . toString mempty <$> self.extensions.binary
<<|> super.report.integerLexeme}}
where addBinary :: a -> Char -> a
addBinary a
n Char
'0' = a
2a -> a -> a
forall a. Num a => a -> a -> a
*a
n
addBinary a
n Char
'1' = a
2a -> a -> a
forall a. Num a => a -> a -> a
*a
n a -> a -> a
forall a. Num a => a -> a -> a
+ a
1
addBinary a
_ Char
_ = String -> a
forall a. HasCallStack => String -> a
error String
"non-binary"
hexFloatLiteralsMixin :: ExtensionOverlay l g t
hexFloatLiteralsMixin :: forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
hexFloatLiteralsMixin self :: g (Parser g t)
self@ExtendedGrammar{report :: forall l t (f :: * -> *) (p :: * -> *).
ExtendedGrammar l t f p -> HaskellGrammar l t f p
report= HaskellGrammar{Parser g t t
decimal :: Parser g t t
decimal :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p t
decimal, Parser g t t
hexadecimal :: Parser g t t
hexadecimal :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> p t
hexadecimal}} g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
integerLexeme = notFollowedBy ((string "0x" <|> string "0X")
*> hexadecimal *> satisfyCharInput (`elem` ['.', 'p', 'P']))
*> super.report.integerLexeme,
floatLexeme = (string "0x" <|> string "0X")
*> (readHexFloat <$> hexadecimal <* string "." <*> hexadecimal <*> (hexExponent <<|> pure 0)
<|> readHexFloat <$> hexadecimal <*> pure mempty <*> hexExponent)
<|> super.report.floatLexeme}}
where hexExponent :: Parser g t Int
hexExponent =
(ParserInput (Parser g t) -> Parser g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Parser g t)
"p" Parser g t t -> Parser g t t -> Parser g t t
forall a. Parser g t a -> Parser g t a -> Parser g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParserInput (Parser g t) -> Parser g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Parser g t)
"P")
Parser g t t -> Parser g t (Int -> Int) -> Parser g t (Int -> Int)
forall a b. Parser g t a -> Parser g t b -> Parser g t b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Int -> Int
forall a. a -> a
id (Int -> Int) -> Parser g t t -> Parser g t (Int -> Int)
forall a b. a -> Parser g t b -> Parser g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Parser g t) -> Parser g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Parser g t)
"+" Parser g t (Int -> Int)
-> Parser g t (Int -> Int) -> Parser g t (Int -> Int)
forall a. Parser g t a -> Parser g t a -> Parser g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Int -> Int
forall a. Num a => a -> a
negate (Int -> Int) -> Parser g t t -> Parser g t (Int -> Int)
forall a b. a -> Parser g t b -> Parser g t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserInput (Parser g t) -> Parser g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Parser g t)
"-" Parser g t (Int -> Int)
-> Parser g t (Int -> Int) -> Parser g t (Int -> Int)
forall a. Parser g t a -> Parser g t a -> Parser g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Int -> Int) -> Parser g t (Int -> Int)
forall a. a -> Parser g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int -> Int
forall a. a -> a
id)
Parser g t (Int -> Int) -> Parser g t Int -> Parser g t Int
forall a b. Parser g t (a -> b) -> Parser g t a -> Parser g t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Int, String) -> Int
forall a b. (a, b) -> a
fst ((Int, String) -> Int) -> (t -> (Int, String)) -> t -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Int, String)] -> (Int, String)
forall a. HasCallStack => [a] -> a
head ([(Int, String)] -> (Int, String))
-> (t -> [(Int, String)]) -> t -> (Int, String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadS Int
forall a. (Eq a, Num a) => ReadS a
Numeric.readDec ReadS Int -> (t -> String) -> t -> [(Int, String)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (t -> String) -> t -> String
forall t. TextualMonoid t => (t -> String) -> t -> String
toString t -> String
forall a. Monoid a => a
mempty (t -> Int) -> Parser g t t -> Parser g t Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser g t t
decimal)
readHexFloat :: m -> m -> Int -> a
readHexFloat m
whole m
fraction Int
magnitude =
(a, String) -> a
forall a b. (a, b) -> a
fst ([(a, String)] -> (a, String)
forall a. HasCallStack => [a] -> a
head ([(a, String)] -> (a, String)) -> [(a, String)] -> (a, String)
forall a b. (a -> b) -> a -> b
$ ReadS a
forall a. (Eq a, Num a) => ReadS a
Numeric.readHex ReadS a -> ReadS a
forall a b. (a -> b) -> a -> b
$ (m -> String) -> m -> String
forall t. TextualMonoid t => (t -> String) -> t -> String
toString m -> String
forall a. Monoid a => a
mempty (m -> String) -> m -> String
forall a b. (a -> b) -> a -> b
$ m
whole m -> m -> m
forall a. Semigroup a => a -> a -> a
<> m
fraction)
a -> a -> a
forall a. Num a => a -> a -> a
* a
2 a -> Int -> a
forall a b. (Fractional a, Integral b) => a -> b -> a
^^ (Int
magnitude Int -> Int -> Int
forall a. Num a => a -> a -> a
- m -> Int
forall m. Factorial m => m -> Int
Factorial.length m
fraction)
numericUnderscoresMixin :: ExtensionOverlay l g t
numericUnderscoresMixin :: forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
numericUnderscoresMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
decimal = takeCharsWhile1 Char.isDigit <> concatAll (char '_' *> takeCharsWhile1 Char.isDigit)
<?> "decimal number",
octal = takeCharsWhile1 Char.isOctDigit <> concatAll (char '_' *> takeCharsWhile1 Char.isOctDigit)
<?> "octal number",
hexadecimal = takeCharsWhile1 Char.isHexDigit <> concatAll (char '_' *> takeCharsWhile1 Char.isHexDigit)
<?> "hexadecimal number"}}
binaryUnderscoresMixin :: ExtensionOverlay l g t
binaryUnderscoresMixin :: forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
binaryUnderscoresMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
binary = (string "0b" <|> string "0B") *> (binaryDigits <> concatAll (char '_' *> binaryDigits) <?> "binary number")}}
where binaryDigits :: Parser g t (ParserInput (Parser g t))
binaryDigits = (Char -> Bool) -> Parser g t (ParserInput (Parser 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
'0' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'1')
parenthesizedTypeOperatorsMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
parenthesizedTypeOperatorsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
parenthesizedTypeOperatorsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
moduleLevel= super.report.moduleLevel{
export = Abstract.exportVar <$> self.report.qualifiedVariable
<|> Abstract.exportClassOrType
<$> (self.report.qualifiedConstructorIdentifier
<|> parens self.report.qualifiedConstructorSymbol)
<*> pure Nothing
<|> Abstract.exportClassOrType
<$> self.report.qualifiedTypeConstructor
<*> (Just <$> self.report.moduleLevel.members)
<|> Abstract.reExportModule <$ keyword "module" <*> Report.moduleId},
qualifiedTypeConstructor = self.report.qualifiedConstructorIdentifier <|> parens anyQualifiedOperator,
generalTypeConstructor = super.report.generalTypeConstructor
<|> Abstract.constructorType
<$> wrap (Abstract.constructorReference <$> parens self.report.qualifiedVariableSymbol),
declarationLevel= super.report.declarationLevel{
qualifiedTypeClass =
super.report.declarationLevel.qualifiedTypeClass <|> parens anyQualifiedOperator}}}
where anyQualifiedOperator :: Fixed (ParserT ((,) [[Lexeme t]])) g t (QualifiedName l)
anyQualifiedOperator =
g (Parser g t)
self.report.qualifiedConstructorOperator Fixed (ParserT ((,) [[Lexeme t]])) g t (QualifiedName l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (QualifiedName l)
-> Fixed (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
<|> g (Parser g t)
self.report.qualifiedVariableOperator
typeOperatorsMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
typeOperatorsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
typeOperatorsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
moduleLevel= super.report.moduleLevel{
importItem = Abstract.importVar <$> self.report.variable
<|> Abstract.importClassOrType
<$> (self.report.constructorIdentifier <|> parens self.report.constructorSymbol)
<*> pure Nothing
<|> Abstract.importClassOrType
<$> self.report.typeConstructor
<*> (Just <$> self.report.moduleLevel.members)},
declarationLevel= super.report.declarationLevel{
typeClass = super.report.declarationLevel.typeClass <|> parens anyOperator,
simpleType = super.report.declarationLevel.simpleType
<|> Abstract.infixTypeLHSApplication
<$> self.extensions.typeVarBinder
<*> (notFollowedBy (string "`") *> anyOperator)
<*> self.extensions.typeVarBinder,
instanceDesignator =
super.report.declarationLevel.instanceDesignator
<|> Abstract.infixTypeClassInstanceLHS
<$> wrap self.report.bType
<*> self.report.qualifiedOperator
<*> wrap self.report.bType},
typeConstructor = self.report.constructorIdentifier <|> parens anyOperator},
extensions = super.extensions{
equalityConstraint = empty,
cType = super.extensions.cType
<|> Abstract.infixTypeApplication
<$> wrap self.extensions.cType
<*> self.report.qualifiedOperator
<*> wrap self.report.bType}}
where anyOperator :: Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
anyOperator = g (Parser g t)
self.report.constructorOperator Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
-> 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
-> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> g (Parser g t)
self.report.variableOperator
equalityConstraintsMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
equalityConstraintsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
equalityConstraintsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
equalityConstraint =
Abstract.typeEquality
<$> wrap self.report.bType
<* delimiter "~"
<*> wrap (self.report.bType)}}
multiParameterConstraintsMixin :: forall l g t. Abstract.ExtendedHaskell l => ExtensionOverlay l g t
multiParameterConstraintsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
multiParameterConstraintsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
declarationLevel= super.report.declarationLevel{
derivingClause =
keyword "deriving"
*> (pure <$> wrap (parens (Abstract.strategicDerive Abstract.build
<$> wrap (pure $ Abstract.defaultStrategy @l Abstract.build)
<*> wrap self.report.typeTerm `sepBy` comma)
<<|> Abstract.simpleDerive <$> self.report.declarationLevel.qualifiedTypeClass))}}}
gratuitouslyParenthesizedTypesMixin :: (OutlineMonoid t, Abstract.ExtendedHaskell l,
Deep.Foldable (Serialization (Down Int) t) (Abstract.Declaration l l),
Deep.Foldable (Serialization (Down Int) t) (Abstract.GADTConstructor l l))
=> ExtensionOverlay l g t
gratuitouslyParenthesizedTypesMixin :: forall t l (g :: (* -> *) -> *).
(OutlineMonoid t, ExtendedHaskell l,
Foldable (Serialization (Down Int) t) (Declaration l l),
Foldable (Serialization (Down Int) t) (GADTConstructor l l)) =>
ExtensionOverlay l g t
gratuitouslyParenthesizedTypesMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
declarationLevel = super.report.declarationLevel{
qualifiedTypeClass = super.report.declarationLevel.qualifiedTypeClass <|> parens qtc,
typeVarApplications = self.report.generalTypeConstructor
<|> Abstract.typeApplication
<$> wrap (self.report.declarationLevel.typeVarApplications
<|> parens self.report.declarationLevel.typeVarApplications)
<*> wrap self.extensions.optionallyKindedAndParenthesizedTypeVar,
simpleType = super.report.declarationLevel.simpleType
<|> parens self.report.declarationLevel.simpleType}},
extensions = super.extensions{
gadtConstructors = super.extensions.gadtConstructors
<|> Abstract.gadtConstructors <$> self.extensions.constructorIDs
<* self.report.doubleColon
<**> pure uncurry3
<*> (parens forallAndContextAndBody <|> forallAndParenContextBody),
gadtNewConstructor = super.extensions.gadtNewConstructor
<|> Abstract.gadtConstructors <$> ((:|[]) <$> self.report.constructor)
<* self.report.doubleColon
<**> pure uncurry3
<*> parens forallAndNewBody,
gadtNewBody = super.extensions.gadtNewBody
<|> Abstract.functionType
<$> wrap self.report.bType
<* self.report.rightArrow
<*> wrap paren_return_type
<|> Abstract.recordFunctionType
<$> braces ((:[]) <$> wrap self.report.declarationLevel.fieldDeclaration)
<* self.report.rightArrow
<*> wrap paren_return_type,
record_gadt_body = (super.extensions.record_gadt_body)
<|> Abstract.recordFunctionType
<$> braces (wrap self.report.declarationLevel.fieldDeclaration `sepBy` comma)
<* self.report.rightArrow
<*> wrap paren_return_type,
optionallyParenthesizedTypeVar = self.report.typeVar
<|> parens self.extensions.optionallyParenthesizedTypeVar,
typeVarBinder = Abstract.implicitlyKindedTypeVariable <$> self.extensions.optionallyParenthesizedTypeVar}}
where qtc :: Fixed (ParserT ((,) [[Lexeme t]])) g t (QualifiedName l)
qtc = g (Parser g t)
self.report.declarationLevel.qualifiedTypeClass
paren_return_type :: Parser g t (Type l l (NodeWrap t) (NodeWrap t))
paren_return_type = Parser g t (Type l l (NodeWrap t) (NodeWrap t))
-> Parser g t (Type l l (NodeWrap t) (NodeWrap t))
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens ((g (Parser g t)
self.extensions.return_type) Parser g t (Type l l (NodeWrap t) (NodeWrap t))
-> Parser g t (Type l l (NodeWrap t) (NodeWrap t))
-> Parser g t (Type l l (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 (Type l l (NodeWrap t) (NodeWrap t))
-> Parser g t (Type l l (NodeWrap t) (NodeWrap t))
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens Parser g t (Type l l (NodeWrap t) (NodeWrap t))
paren_return_type)
optionalContextAndGadtBody :: Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
optionalContextAndGadtBody =
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
contextAndGadtBody Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (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
<|> (,) (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Context l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (Context l l (NodeWrap t) (NodeWrap t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Context l l (NodeWrap t) (NodeWrap t))
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Context l l (NodeWrap t) (NodeWrap t)
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Context λ l d s
forall l (d :: * -> *) (s :: * -> *). Context l l d s
Abstract.noContext) Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
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
<*> Parser g t (Type l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap g (Parser g t)
self.extensions.gadtBody
contextAndGadtBody :: Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
contextAndGadtBody =
(,) (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Context l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap g (Parser g t)
self.report.declarationLevel.context
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap 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
<* g (Parser g t)
self.report.rightDoubleArrow
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
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
<*> Parser g t (Type l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap g (Parser g t)
self.extensions.gadtBody
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (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
<|> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
contextAndGadtBody
forallAndContextAndBody :: Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
forallAndContextAndBody =
(,,) ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)]
-> ((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)]
-> ((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
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
<$ g (Parser g t)
self.extensions.keywordForall
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)]
-> ((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[TypeVarBinding l l (NodeWrap t) (NodeWrap t)]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
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
(TypeVarBinding l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[TypeVarBinding l l (NodeWrap t) (NodeWrap t)]
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 g (Parser g t)
self.extensions.typeVarBinder
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap 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
<* t -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
t -> Parser g t ()
delimiter t
"."
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> ((((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
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),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
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),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
optionalContextAndGadtBody
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (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
<|> (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ((,,) []) ((((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
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 (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
contextAndGadtBody
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (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
<|> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
forallAndContextAndBody
forallAndParenContextBody :: Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
forallAndParenContextBody =
(,,) ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)]
-> ((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)]
-> ((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
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
<$ g (Parser g t)
self.extensions.keywordForall
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)]
-> ((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[TypeVarBinding l l (NodeWrap t) (NodeWrap t)]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
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
(TypeVarBinding l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[TypeVarBinding l l (NodeWrap t) (NodeWrap t)]
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 g (Parser g t)
self.extensions.typeVarBinder
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap 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
<* t -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
t -> Parser g t ()
delimiter t
"."
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> ((((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
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),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> (((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
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),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
contextAndGadtBody
forallAndNewBody :: Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
forallAndNewBody =
(,,) ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)]
-> ((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)]
-> ((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
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
<$ g (Parser g t)
self.extensions.keywordForall
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)]
-> ((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[TypeVarBinding l l (NodeWrap t) (NodeWrap t)]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
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
(TypeVarBinding l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[TypeVarBinding l l (NodeWrap t) (NodeWrap t)]
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 g (Parser g t)
self.extensions.typeVarBinder
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap 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
<* t -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
t -> Parser g t ()
delimiter t
"."
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
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
(Context l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap (Context l l (NodeWrap t) (NodeWrap t)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Context l l (NodeWrap t) (NodeWrap t))
forall a. a -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Context l l (NodeWrap t) (NodeWrap t)
forall λ l (d :: * -> *) (s :: * -> *).
Haskell λ =>
Context λ l d s
forall l (d :: * -> *) (s :: * -> *). Context l l d s
Abstract.noContext
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Context l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Context l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Context l l (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
<|> g (Parser g t)
self.report.declarationLevel.context
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Context l l (NodeWrap t) (NodeWrap 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
*> g (Parser g t)
self.report.rightDoubleArrow
Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Context l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Context l l (NodeWrap t) (NodeWrap 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
*> String
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Context l l (NodeWrap t) (NodeWrap t))
forall a. String -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"No context allowed on GADT newtype")
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> ([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
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
<*> Parser g t (Type l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap g (Parser g t)
self.extensions.gadtNewBody
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (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
<|> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([TypeVarBinding l l (NodeWrap t) (NodeWrap t)],
((Down Int, ParsedLexemes t, Down Int),
Context l l (NodeWrap t) (NodeWrap t)),
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t)))
forallAndNewBody
uncurry3 :: (t -> t -> t -> t) -> (t, t, t) -> t
uncurry3 t -> t -> t -> t
f (t
a, t
b, t
c) = t -> t -> t -> t
f t
a t
b t
c
typeFamiliesMixin :: forall l g t. (OutlineMonoid t, Abstract.ExtendedHaskell l,
Deep.Foldable (Serialization (Down Int) t) (Abstract.Declaration l l),
Deep.Foldable (Serialization (Down Int) t) (Abstract.GADTConstructor l l))
=> ExtensionOverlay l g t
typeFamiliesMixin :: forall l (g :: (* -> *) -> *) t.
(OutlineMonoid t, ExtendedHaskell l,
Foldable (Serialization (Down Int) t) (Declaration l l),
Foldable (Serialization (Down Int) t) (GADTConstructor l l)) =>
ExtensionOverlay l g t
typeFamiliesMixin self :: g (Parser g t)
self@ExtendedGrammar{
report :: forall l t (f :: * -> *) (p :: * -> *).
ExtendedGrammar l t f p -> HaskellGrammar l t f p
report= HaskellGrammar{
declarationLevel :: forall l t (f :: * -> *) (p :: * -> *).
HaskellGrammar l t f p -> DeclarationGrammar l f p
declarationLevel= DeclarationGrammar{Parser g t (Context l l (NodeWrap t) (NodeWrap t))
optionalContext :: Parser g t (Context l l (NodeWrap t) (NodeWrap t))
optionalContext :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (Context l l f f)
optionalContext, Parser g t (TypeLHS l l (NodeWrap t) (NodeWrap t))
simpleType :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p (TypeLHS l l f f)
simpleType :: Parser g t (TypeLHS l l (NodeWrap t) (NodeWrap t))
simpleType, Parser
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause l l (NodeWrap t) (NodeWrap t))]
derivingClause :: forall l (f :: * -> *) (p :: * -> *).
DeclarationGrammar l f p -> p [f (DerivingClause l l f f)]
derivingClause :: Parser
g
t
[((Down Int, ParsedLexemes t, Down Int),
DerivingClause l l (NodeWrap t) (NodeWrap t))]
derivingClause}}}
g (Parser g t)
super =
g (Parser g t)
super{
report= super.report{
declarationLevel= super.report.declarationLevel{
topLevelDeclaration = super.report.declarationLevel.topLevelDeclaration
<|> Abstract.dataFamilyDeclaration <$ keyword "data" <* keyword "family"
<*> wrap simpleType <*> optional (wrap self.extensions.kindSignature)
<|> Abstract.openTypeFamilyDeclaration <$ keyword "type" <* keyword "family"
<*> wrap simpleType <*> optional (wrap self.extensions.kindSignature)
<|> Abstract.closedTypeFamilyDeclaration <$ keyword "type" <* keyword "family"
<*> wrap simpleType <*> optional (wrap self.extensions.kindSignature) <* keyword "where"
<*> blockOf (wrap
$ Abstract.typeFamilyInstance
<$> self.extensions.optionalForall
<*> wrap self.report.declarationLevel.instanceDesignator <* delimiter "="
<*> wrap self.report.typeTerm)
<|> Abstract.dataFamilyInstance <$ (keyword "data" *> keyword "instance")
<*> self.extensions.optionalForall
<*> wrap optionalContext
<*> wrap self.report.declarationLevel.instanceDesignator
<*> optional (wrap self.extensions.kindSignature)
<*> moptional (delimiter "=" *> self.report.declarationLevel.declaredConstructors)
<*> moptional derivingClause
<|> Abstract.newtypeFamilyInstance <$ (keyword "newtype" *> keyword "instance")
<*> self.extensions.optionalForall
<*> wrap optionalContext
<*> wrap self.report.declarationLevel.instanceDesignator
<*> optional (wrap self.extensions.kindSignature)
<* delimiter "="
<*> wrap self.report.declarationLevel.newConstructor
<*> moptional derivingClause
<|> Abstract.gadtDataFamilyInstance <$ (keyword "data" *> keyword "instance")
<*> self.extensions.optionalForall
<*> wrap self.report.declarationLevel.instanceDesignator
<*> optional (wrap self.extensions.kindSignature)
<* keyword "where"
<*> blockOf (wrap self.extensions.gadtConstructors)
<*> moptional derivingClause
<|> Abstract.gadtNewtypeFamilyInstance <$ (keyword "newtype" *> keyword "instance")
<*> self.extensions.optionalForall
<*> wrap self.report.declarationLevel.instanceDesignator
<*> optional (wrap self.extensions.kindSignature)
<* keyword "where"
<*> wrap self.extensions.gadtNewConstructor
<*> moptional derivingClause
<|> Abstract.typeFamilyInstance <$ (keyword "type" *> keyword "instance")
<*> self.extensions.optionalForall
<*> wrap self.report.declarationLevel.instanceDesignator
<* delimiter "="
<*> wrap self.report.typeTerm,
inClassDeclaration = super.report.declarationLevel.inClassDeclaration
<|> Abstract.dataFamilyDeclaration <$ keyword "data" <* optional (keyword "family")
<*> wrap simpleType <*> optional (wrap self.extensions.kindSignature)
<|> Abstract.openTypeFamilyDeclaration <$ keyword "type" <* optional (keyword "family")
<*> wrap simpleType <*> optional (wrap self.extensions.kindSignature)
<|> self.extensions.inClassOrInstanceTypeFamilyDeclaration,
inInstanceDeclaration = super.report.declarationLevel.inInstanceDeclaration
<|> Abstract.dataFamilyInstance <$ keyword "data" <* optional (keyword "instance")
<*> self.extensions.optionalForall
<*> wrap optionalContext
<*> wrap self.report.declarationLevel.instanceDesignator
<*> optional (wrap self.extensions.kindSignature)
<*> moptional (delimiter "=" *> self.report.declarationLevel.declaredConstructors)
<*> moptional derivingClause
<|> Abstract.newtypeFamilyInstance <$ keyword "newtype" <* optional (keyword "instance")
<*> self.extensions.optionalForall
<*> wrap optionalContext
<*> wrap self.report.declarationLevel.instanceDesignator
<*> optional (wrap self.extensions.kindSignature)
<* delimiter "="
<*> wrap self.report.declarationLevel.newConstructor
<*> moptional derivingClause
<|> Abstract.gadtDataFamilyInstance <$ (keyword "data" *> optional (keyword "instance"))
<*> self.extensions.optionalForall
<*> wrap self.report.declarationLevel.instanceDesignator
<*> optional (wrap self.extensions.kindSignature)
<* keyword "where"
<*> blockOf (wrap self.extensions.gadtConstructors)
<*> moptional derivingClause
<|> Abstract.gadtNewtypeFamilyInstance <$ (keyword "newtype" *> optional (keyword "instance"))
<*> self.extensions.optionalForall
<*> wrap self.report.declarationLevel.instanceDesignator
<*> optional (wrap self.extensions.kindSignature)
<* keyword "where"
<*> wrap self.extensions.gadtNewConstructor
<*> moptional derivingClause
<|> self.extensions.inClassOrInstanceTypeFamilyDeclaration}},
extensions = super.extensions{
inClassOrInstanceTypeFamilyDeclaration =
Abstract.typeFamilyInstance <$ keyword "type" <* optional (keyword "instance")
<*> self.extensions.optionalForall
<*> wrap self.report.declarationLevel.instanceDesignator
<* delimiter "="
<*> wrap self.report.typeTerm}}
typeFamilyDependenciesMixin :: (OutlineMonoid t, Abstract.ExtendedHaskell l,
Deep.Foldable (Serialization (Down Int) t) (Abstract.Declaration l l),
Deep.Foldable (Serialization (Down Int) t) (Abstract.GADTConstructor l l))
=> ExtensionOverlay l g t
typeFamilyDependenciesMixin :: forall t l (g :: (* -> *) -> *).
(OutlineMonoid t, ExtendedHaskell l,
Foldable (Serialization (Down Int) t) (Declaration l l),
Foldable (Serialization (Down Int) t) (GADTConstructor l l)) =>
ExtensionOverlay l g t
typeFamilyDependenciesMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
declarationLevel= super.report.declarationLevel{
topLevelDeclaration = super.report.declarationLevel.topLevelDeclaration
<|> Abstract.injectiveOpenTypeFamilyDeclaration <$ keyword "type" <* keyword "family"
<*> wrap self.report.declarationLevel.simpleType <* delimiter "="
<*> self.extensions.typeVarBinder
<*> optional dependencies
<|> Abstract.injectiveClosedTypeFamilyDeclaration <$ keyword "type" <* keyword "family"
<*> wrap self.report.declarationLevel.simpleType <* delimiter "="
<*> self.extensions.typeVarBinder
<*> optional dependencies
<* keyword "where"
<*> blockOf (wrap $ Abstract.typeFamilyInstance
<$> self.extensions.optionalForall
<*> wrap self.report.declarationLevel.instanceDesignator <* delimiter "="
<*> wrap self.report.typeTerm),
inClassDeclaration = super.report.declarationLevel.inClassDeclaration
<|> Abstract.injectiveOpenTypeFamilyDeclaration <$ keyword "type" <* optional (keyword "family")
<*> wrap self.report.declarationLevel.simpleType <* delimiter "="
<*> self.extensions.typeVarBinder
<*> (Just <$> dependencies)}}}
where dependencies :: Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l, NonEmpty (Name l))
dependencies = (,) (Name l -> NonEmpty (Name l) -> (Name l, NonEmpty (Name l)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty (Name l) -> (Name l, NonEmpty (Name l)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (t -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
t -> Parser g t ()
delimiter t
"|" Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
-> Fixed (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
*> g (Parser g t)
self.report.typeVar) Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty (Name l) -> (Name l, NonEmpty (Name l)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty (Name l) -> (Name l, NonEmpty (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
<* g (Parser g t)
self.report.rightArrow
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(NonEmpty (Name l) -> (Name l, NonEmpty (Name l)))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (NonEmpty (Name l))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (Name l, NonEmpty (Name 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
<*> Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (NonEmpty (Name l))
forall (p :: * -> *) a. Alternative p => p a -> p (NonEmpty a)
someNonEmpty g (Parser g t)
self.report.typeVar
dataKindsMixin :: forall l g t. (Abstract.ExtendedHaskell l, TextualMonoid t) => ExtensionOverlay l g t
dataKindsMixin :: forall l (g :: (* -> *) -> *) t.
(ExtendedHaskell l, TextualMonoid t) =>
ExtensionOverlay l g t
dataKindsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
aType = super.report.aType
<|> self.extensions.promotedLiteral
<|> self.extensions.promotedStructure,
generalTypeConstructor = super.report.generalTypeConstructor
<|> Abstract.promotedConstructorType
<$ terminator "'"
<*> wrap (Abstract.constructorReference <$> self.report.qualifiedConstructor)},
extensions = super.extensions{
promotedLiteral =
Abstract.promotedIntegerLiteral <$> self.report.integer
<|> Abstract.promotedCharLiteral <$> self.report.charLiteral
<|> Abstract.promotedStringLiteral <$> self.report.stringLiteral,
promotedStructure =
Abstract.promotedTupleType <$> parens (pure []
<|> (:) <$> wrap self.report.typeTerm
<*> some (comma *> wrap self.report.typeTerm))
<|> Abstract.promotedListType <$> brackets (wrap self.report.typeTerm `sepBy` comma)}}
dataKindsListTuplePunsMixin :: forall l g t. (Abstract.ExtendedHaskell l, TextualMonoid t) => ExtensionOverlay l g t
dataKindsListTuplePunsMixin :: forall l (g :: (* -> *) -> *) t.
(ExtendedHaskell l, TextualMonoid t) =>
ExtensionOverlay l g t
dataKindsListTuplePunsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
promotedStructure =
Abstract.promotedTupleType <$ terminator "'" <*> parens (wrap self.report.typeTerm `sepBy` comma)
<|> Abstract.promotedListType <$ terminator "'" <*> brackets (wrap self.report.typeTerm `sepBy` comma)
<|> Abstract.promotedListType <$> brackets ((:) <$> wrap self.report.typeTerm
<*> some (comma *> wrap self.report.typeTerm))}}
dataKindsTypeOperatorsMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
dataKindsTypeOperatorsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
dataKindsTypeOperatorsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
cType = super.extensions.cType
<|> Abstract.promotedInfixTypeApplication
<$> wrap self.extensions.cType
<* terminator "'"
<*> self.report.qualifiedOperator
<*> wrap self.report.bType}}
typeDataMixin :: Abstract.ExtendedWith '[ 'TypeData ] l => ExtensionOverlay l g t
typeDataMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'TypeData] l =>
ExtensionOverlay l g t
typeDataMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
declarationLevel= super.report.declarationLevel{
topLevelDeclaration = super.report.declarationLevel.topLevelDeclaration
<|> Abstract.typeDataDeclaration Abstract.build <$ keyword "type" <* keyword "data"
<*> wrap self.report.declarationLevel.simpleType
<*> optional (wrap self.extensions.kindSignature)
<*> (delimiter "=" *> self.report.declarationLevel.declaredConstructors <|> pure [])}}}
typeDataGADTMixin :: (OutlineMonoid t,
Abstract.ExtendedWith '[ 'GADTs, 'TypeData ] l,
Abstract.DeeplyFoldable (Serialization (Down Int) t) l) => ExtensionOverlay l g t
typeDataGADTMixin :: forall t l (g :: (* -> *) -> *).
(OutlineMonoid t, ExtendedWith '[ 'GADTs, 'TypeData] l,
DeeplyFoldable (Serialization (Down Int) t) l) =>
ExtensionOverlay l g t
typeDataGADTMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
declarationLevel= super.report.declarationLevel{
topLevelDeclaration = super.report.declarationLevel.topLevelDeclaration
<|> Abstract.typeGADTDeclaration Abstract.build <$ keyword "type" <* keyword "data"
<*> wrap self.report.declarationLevel.simpleType
<*> optional (wrap self.extensions.kindSignature) <* keyword "where"
<*> blockOf (wrap self.extensions.gadtConstructors)}}}
visibleDependentQuantificationMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
visibleDependentQuantificationMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
visibleDependentQuantificationMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
arrowType = super.extensions.arrowType
<|> Abstract.visibleDependentType
<$ self.extensions.keywordForall
<*> many self.extensions.typeVarBinder
<* self.report.rightArrow
<*> wrap self.extensions.arrowType}}
requiredTypeArgumentsMixin :: Abstract.ExtendedWith '[ 'ExplicitNamespaces ] l => ExtensionOverlay l g t
requiredTypeArgumentsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'ExplicitNamespaces] l =>
ExtensionOverlay l g t
requiredTypeArgumentsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
aExpression = super.report.aExpression
<<|> wrap (Abstract.explicitTypeExpression Abstract.build <$> wrap self.report.aType)}}
kindSignaturesBaseMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
kindSignaturesBaseMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
kindSignaturesBaseMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
kindSignature = Abstract.typeKind <$ self.report.doubleColon <*> wrap self.report.typeTerm}}
starIsTypeMixin :: ExtensionOverlay l g t
starIsTypeMixin :: forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
starIsTypeMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
groundTypeKind = super.extensions.groundTypeKind <|> delimiter "*"}}
unicodeStarIsTypeMixin :: ExtensionOverlay l g t
unicodeStarIsTypeMixin :: forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
unicodeStarIsTypeMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
groundTypeKind = super.extensions.groundTypeKind <|> delimiter "★"}}
starIsTypeOperatorsMixin :: ExtensionOverlay l g t
starIsTypeOperatorsMixin :: forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
starIsTypeOperatorsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
aType = parens (Abstract.constructorType
<$> wrap (Abstract.constructorReference . Abstract.qualifiedName Nothing
<$> token (Report.nameToken $ string "*")))
<<|> super.report.aType}}
roleAnnotationsMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
roleAnnotationsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
roleAnnotationsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
declarationLevel= super.report.declarationLevel {
topLevelDeclaration = super.report.declarationLevel.topLevelDeclaration
<|> Abstract.typeRoleDeclaration <$ keyword "type" <* keyword "role"
<*> self.report.qualifiedTypeConstructor
<*> some (Abstract.nominalRole <$ keyword "nominal"
<|> Abstract.representationalRole <$ keyword "representational"
<|> Abstract.phantomRole <$ keyword "phantom"
<|> Abstract.inferredRole <$ keyword "_")
}
}
}
inferredTypeVariablesMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
inferredTypeVariablesMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
inferredTypeVariablesMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
typeVarBinder = super.extensions.typeVarBinder
<|> braces (Abstract.inferredTypeVariable <$> self.report.typeVar
<|> Abstract.inferredExplicitlyKindedTypeVariable
<$> self.report.typeVar
<*> wrap self.extensions.kindSignature)}}
typeApplicationsMixin :: (Abstract.ExtendedHaskell l, Abstract.DeeplyFoldable (Serialization (Down Int) t) l,
SpaceMonoid t) => ExtensionOverlay l g t
typeApplicationsMixin :: forall l t (g :: (* -> *) -> *).
(ExtendedHaskell l, DeeplyFoldable (Serialization (Down Int) t) l,
SpaceMonoid t) =>
ExtensionOverlay l g t
typeApplicationsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
bType = super.report.bType
<|> Abstract.visibleKindApplication
<$> filter whiteSpaceTrailing (wrap self.report.bType)
<* typeApplicationDelimiter
<*> wrap (Abstract.typeKind <$> wrap self.report.aType),
bareExpression = super.report.bareExpression
<|> Abstract.visibleTypeApplication
<$> filter whiteSpaceTrailing self.report.aExpression
<* typeApplicationDelimiter
<*> wrap self.report.aType},
extensions = super.extensions{
return_type = (super.extensions.return_type)
<|> Abstract.visibleKindApplication
<$> filter whiteSpaceTrailing (wrap self.extensions.return_type)
<* typeApplicationDelimiter
<*> wrap (Abstract.typeKind <$> wrap self.report.aType)}}
where typeApplicationDelimiter :: Fixed (ParserT ((,) [[Lexeme t]])) g t ()
typeApplicationDelimiter = 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, SpaceMonoid t) =>
Parser g t t
unreservedSymbolLexeme 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
*> t -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
t -> Parser g t ()
delimiter t
"@"
typeAbstractionsOrApplicationsMixin :: (Abstract.ExtendedHaskell l, SpaceMonoid t,
Abstract.DeeplyFoldable (Serialization (Down Int) t) l)
=> ExtensionOverlay l g t
typeAbstractionsOrApplicationsMixin :: forall l t (g :: (* -> *) -> *).
(ExtendedHaskell l, SpaceMonoid t,
DeeplyFoldable (Serialization (Down Int) t) l) =>
ExtensionOverlay l g t
typeAbstractionsOrApplicationsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
lPattern = super.report.lPattern
<|> Abstract.constructorPatternWithTypeApplications
<$> filter whiteSpaceTrailing (wrap self.report.generalConstructor)
<*> some (typeApplicationDelimiter *> wrap self.report.aType)
<*> many (wrap self.extensions.conArgPattern)},
extensions = super.extensions{
instanceDesignatorApplications = super.extensions.instanceDesignatorApplications
<|> Abstract.classInstanceLHSKindApplication
<$> filter whiteSpaceTrailing (wrap self.extensions.instanceDesignatorApplications)
<* typeApplicationDelimiter
<*> wrap (Abstract.typeKind <$> wrap self.report.aType)}}
where typeApplicationDelimiter :: Fixed (ParserT ((,) [[Lexeme t]])) g t ()
typeApplicationDelimiter = 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, SpaceMonoid t) =>
Parser g t t
unreservedSymbolLexeme 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
*> t -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
t -> Parser g t ()
delimiter t
"@"
typeAbstractionsMixin :: (Abstract.ExtendedWith '[ 'TypeAbstractions ] l,
SpaceMonoid t) => ExtensionOverlay l g t
typeAbstractionsMixin :: forall l t (g :: (* -> *) -> *).
(ExtendedWith '[ 'TypeAbstractions] l, SpaceMonoid t) =>
ExtensionOverlay l g t
typeAbstractionsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
declarationLevel = super.report.declarationLevel{
simpleType = super.report.declarationLevel.simpleType
<|> Abstract.typeLHSTypeApplication Abstract.build
<$> wrap self.report.declarationLevel.simpleType
<* delimiter "@"
<*> self.extensions.typeVarBinder},
aPattern =
Abstract.invisibleTypePattern Abstract.build
<$ (filter precededByOpenSpace getInput *> delimiter "@")
<*> wrap self.report.aType
<|> notFollowedBy (self.report.variable *> filter precededByOpenSpace getInput *> delimiter "@")
*> super.report.aPattern}}
linearTypesMixin :: (SpaceMonoid t, Abstract.ExtendedHaskell l) => ExtensionOverlay l g t
linearTypesMixin :: forall t l (g :: (* -> *) -> *).
(SpaceMonoid t, ExtendedHaskell l) =>
ExtensionOverlay l g t
linearTypesMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
variableSymbol = notFollowedBy prefixPercent *> super.report.variableSymbol},
extensions = super.extensions{
arrowType = super.extensions.arrowType
<|> Abstract.linearFunctionType
<$> wrap self.extensions.cType
<* token prefixPercent
<* keyword "1"
<* self.report.rightArrow
<*> wrap self.extensions.arrowType
<|> Abstract.multiplicityFunctionType
<$> wrap self.extensions.cType
<* token prefixPercent
<* notFollowedBy (keyword "1")
<*> wrap self.report.aType
<* self.report.rightArrow
<*> wrap self.extensions.arrowType}}
where prefixPercent :: Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
prefixPercent =
(ParserInput (Parser g t) -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g 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 ParserInput (Parser g t) -> Bool
forall t. SpaceMonoid t => t -> Bool
precededByOpenSpace Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *). InputParsing m => m (ParserInput m)
getInput Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser 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
*> ParserInput (Parser g t)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string ParserInput (Parser g t)
"%" Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser 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 a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (ParserInput (Parser g t) -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g 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 (Bool -> Bool
not (Bool -> Bool)
-> (ParserInput (Parser g t) -> Bool)
-> ParserInput (Parser g t)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParserInput (Parser g t) -> Bool
forall t. TextualMonoid t => t -> Bool
followedByCloseSpace) Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *). InputParsing m => m (ParserInput m)
getInput
gadtLinearTypesMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
gadtLinearTypesMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
gadtLinearTypesMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
prefix_gadt_body = (super.extensions.prefix_gadt_body)
<|> Abstract.linearFunctionType
<$> wrap (self.report.bType <|> self.report.declarationLevel.strictType)
<* delimiter "%"
<* keyword "1"
<* self.report.rightArrow
<*> wrap (self.extensions.prefix_gadt_body)
<|> Abstract.multiplicityFunctionType
<$> wrap (self.report.bType <|> self.report.declarationLevel.strictType)
<* delimiter "%"
<* notFollowedBy (keyword "1")
<*> wrap self.report.aType
<* self.report.rightArrow
<*> wrap (self.extensions.prefix_gadt_body),
gadtNewBody = super.extensions.gadtNewBody
<|> Abstract.linearFunctionType
<$> wrap self.report.bType
<* delimiter "%"
<* keyword "1"
<* self.report.rightArrow
<*> wrap (self.extensions.return_type)
<|> Abstract.multiplicityFunctionType
<$> wrap (self.report.bType <|> self.report.declarationLevel.strictType)
<* delimiter "%"
<* notFollowedBy (keyword "1")
<*> wrap self.report.aType
<* self.report.rightArrow
<*> wrap (self.extensions.return_type)}}
unicodeLinearTypesMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
unicodeLinearTypesMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
unicodeLinearTypesMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
arrowType = super.extensions.arrowType
<|> Abstract.linearFunctionType
<$> wrap self.extensions.cType
<* delimiter "⊸"
<*> wrap self.extensions.arrowType}}
gadtUnicodeLinearTypesMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
gadtUnicodeLinearTypesMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
gadtUnicodeLinearTypesMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
prefix_gadt_body = (super.extensions.prefix_gadt_body)
<|> Abstract.linearFunctionType
<$> wrap (self.report.bType <|> self.report.declarationLevel.strictType)
<* delimiter "⊸"
<*> wrap (self.extensions.prefix_gadt_body),
gadtNewBody = super.extensions.gadtNewBody
<|> Abstract.linearFunctionType
<$> wrap self.report.bType
<* delimiter "⊸"
<*> wrap (self.extensions.return_type)}}
standaloneKindSignaturesMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
standaloneKindSignaturesMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
standaloneKindSignaturesMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
declarationLevel= super.report.declarationLevel{
topLevelDeclaration = super.report.declarationLevel.topLevelDeclaration
<|> Abstract.kindSignature <$ keyword "type"
<*> self.report.typeConstructor
<*> wrap self.extensions.kindSignature}}}
kindSignaturesMixin :: (OutlineMonoid t, Abstract.ExtendedHaskell l,
Deep.Foldable (Serialization (Down Int) t) (Abstract.Declaration l l))
=> ExtensionOverlay l g t
kindSignaturesMixin :: forall t l (g :: (* -> *) -> *).
(OutlineMonoid t, ExtendedHaskell l,
Foldable (Serialization (Down Int) t) (Declaration l l)) =>
ExtensionOverlay l g t
kindSignaturesMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
declarationLevel= super.report.declarationLevel{
topLevelDeclaration = super.report.declarationLevel.topLevelDeclaration
<|> Abstract.kindedDataDeclaration <$ keyword "data"
<*> wrap self.report.declarationLevel.optionalContext
<*> wrap self.report.declarationLevel.simpleType
<*> wrap self.extensions.kindSignature
<*> (delimiter "=" *> self.report.declarationLevel.declaredConstructors <|> pure [])
<*> moptional self.report.declarationLevel.derivingClause
<|> Abstract.kindedNewtypeDeclaration <$ keyword "newtype"
<*> wrap self.report.declarationLevel.optionalContext
<*> wrap self.report.declarationLevel.simpleType
<*> wrap self.extensions.kindSignature
<* delimiter "="
<*> wrap self.report.declarationLevel.newConstructor
<*> moptional self.report.declarationLevel.derivingClause},
typeTerm = super.report.typeTerm <|>
Abstract.kindedType <$> wrap self.report.typeTerm <*> wrap self.extensions.kindSignature},
extensions = super.extensions{
optionallyKindedAndParenthesizedTypeVar =
Abstract.typeVariable <$> self.extensions.optionallyParenthesizedTypeVar
<|> parens (Abstract.kindedType
<$> wrap (Abstract.typeVariable <$> self.extensions.optionallyParenthesizedTypeVar)
<*> wrap self.extensions.kindSignature),
optionallyKindedTypeVar =
Abstract.typeVariable <$> self.report.typeVar
<|> Abstract.kindedType
<$> wrap (Abstract.typeVariable <$> self.report.typeVar)
<*> wrap self.extensions.kindSignature,
typeVarBinder = super.extensions.typeVarBinder
<|> parens (Abstract.explicitlyKindedTypeVariable
<$> self.report.typeVar
<*> wrap self.extensions.kindSignature)}}
existentialQuantificationMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
existentialQuantificationMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
existentialQuantificationMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
declarationLevel= super.report.declarationLevel{
declaredConstructor = super.report.declarationLevel.declaredConstructor
<|> Abstract.existentialConstructor
<$ self.extensions.keywordForall
<*> many self.extensions.typeVarBinder <* delimiter "."
<*> wrap self.report.declarationLevel.optionalContext
<*> wrap super.report.declarationLevel.declaredConstructor
<|> Abstract.existentialConstructor []
<$> wrap self.report.declarationLevel.context
<* self.report.rightDoubleArrow
<*> wrap super.report.declarationLevel.declaredConstructor}}}
scopedTypeVariablesMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
scopedTypeVariablesMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
scopedTypeVariablesMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
pattern = super.report.pattern
<|> Abstract.typedPattern
<$> wrap self.extensions.infixPattern
<* self.report.doubleColon
<*> wrap self.report.typeTerm}}
explicitForAllMixin :: (OutlineMonoid t, Abstract.ExtendedHaskell l,
Deep.Foldable (Serialization (Down Int) t) (Abstract.Declaration l l))
=> ExtensionOverlay l g t
explicitForAllMixin :: forall t l (g :: (* -> *) -> *).
(OutlineMonoid t, ExtendedHaskell l,
Foldable (Serialization (Down Int) t) (Declaration l l)) =>
ExtensionOverlay l g t
explicitForAllMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
declarationLevel= super.report.declarationLevel{
optionalTypeSignatureContext = pure Abstract.noContext,
topLevelDeclaration = super.report.declarationLevel.topLevelDeclaration
<|> Abstract.explicitlyScopedInstanceDeclaration <$ keyword "instance"
<* self.extensions.keywordForall
<*> many self.extensions.typeVarBinder
<* delimiter "."
<*> wrap self.report.declarationLevel.optionalContext
<*> wrap self.report.declarationLevel.instanceDesignator
<*> (keyword "where"
*> blockOf (wrap self.report.declarationLevel.inInstanceDeclaration)
<|> pure [])},
typeVar = notFollowedBy (self.extensions.keywordForall) *> super.report.typeVar},
extensions = super.extensions{
arrowType = super.extensions.arrowType
<|> Abstract.forallType <$ self.extensions.keywordForall
<*> many self.extensions.typeVarBinder <* delimiter "."
<*> wrap self.extensions.arrowType,
keywordForall = super.extensions.keywordForall <|> keyword "forall",
optionalForall = self.extensions.keywordForall *> many self.extensions.typeVarBinder <* delimiter "."
<<|> pure []}}
gadtSyntaxMixin :: (OutlineMonoid t, Abstract.ExtendedHaskell l,
Deep.Foldable (Serialization (Down Int) t) (Abstract.GADTConstructor l l))
=> ExtensionOverlay l g t
gadtSyntaxMixin :: forall t l (g :: (* -> *) -> *).
(OutlineMonoid t, ExtendedHaskell l,
Foldable (Serialization (Down Int) t) (GADTConstructor l l)) =>
ExtensionOverlay l g t
gadtSyntaxMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
declarationLevel= super.report.declarationLevel{
topLevelDeclaration = super.report.declarationLevel.topLevelDeclaration
<|> Abstract.gadtDeclaration <$ keyword "data"
<*> wrap super.report.declarationLevel.simpleType
<*> optional (wrap self.extensions.kindSignature) <* keyword "where"
<*> blockOf (wrap self.extensions.gadtConstructors)
<*> moptional super.report.declarationLevel.derivingClause
<|> Abstract.gadtNewtypeDeclaration <$ keyword "newtype"
<*> wrap super.report.declarationLevel.simpleType
<*> optional (wrap self.extensions.kindSignature) <* keyword "where"
<*> wrap self.extensions.gadtNewConstructor
<*> moptional super.report.declarationLevel.derivingClause}},
extensions = super.extensions{
optionalForall = self.extensions.keywordForall *> many self.extensions.typeVarBinder <* delimiter "."
<<|> pure []}}
gadtSyntaxTypeOperatorsMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
gadtSyntaxTypeOperatorsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
gadtSyntaxTypeOperatorsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
prefix_gadt_body = (super.extensions.prefix_gadt_body)
<|> Abstract.functionType
<$> wrap (Abstract.infixTypeApplication
<$> wrap self.extensions.cType
<*> self.report.qualifiedOperator
<*> wrap self.report.bType)
<* self.report.rightArrow
<*> wrap (self.extensions.prefix_gadt_body),
return_type = (super.extensions.return_type) <|>
Abstract.infixTypeApplication <$> wrap (self.extensions.arg_type)
<*> self.report.qualifiedOperator
<*> wrap (self.extensions.arg_type)}}
dataKindsGadtSyntaxTypeOperatorsMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
dataKindsGadtSyntaxTypeOperatorsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
dataKindsGadtSyntaxTypeOperatorsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
return_type = (super.extensions.return_type) <|>
Abstract.promotedInfixTypeApplication
<$> wrap (self.extensions.arg_type)
<* terminator "'"
<*> self.report.qualifiedOperator
<*> wrap (self.extensions.arg_type)}}
namedFieldPunsMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
namedFieldPunsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
namedFieldPunsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
fieldBinding = super.report.fieldBinding <|>
Abstract.punnedFieldBinding <$> self.report.qualifiedVariable,
fieldPattern = super.report.fieldPattern <|>
Abstract.punnedFieldPattern <$> self.report.qualifiedVariable}}
recordWildCardsMixin :: Abstract.ExtendedWith '[ 'RecordWildCards ] l => ExtensionOverlay l g t
recordWildCardsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'RecordWildCards] l =>
ExtensionOverlay l g t
recordWildCardsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
conArgPattern = super.extensions.conArgPattern
<|> Abstract.wildcardRecordPattern' Abstract.build <$> self.report.qualifiedConstructor
<*> braces (wrap self.report.fieldPattern `endBy` comma <* delimiter "..")},
report = super.report{
bareExpression = super.report.bareExpression
<|> Abstract.wildcardRecordExpression' Abstract.build <$> self.report.qualifiedConstructor
<*> braces (wrap self.report.fieldBinding `endBy` comma <* delimiter "..")}}
overloadedRecordDotMixin :: Abstract.ExtendedHaskell l => ExtensionOverlay l g t
overloadedRecordDotMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
overloadedRecordDotMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
qualifiedVariableSymbol =
notFollowedBy (string "." *> satisfyCharInput varStart) *> super.report.qualifiedVariableSymbol,
bareExpression = super.report.bareExpression <|>
Abstract.getField <$> self.report.aExpression <* prefixDot <*> self.report.variableIdentifier
<|>
Abstract.fieldProjection <$> parens (someNonEmpty $ prefixDot *> self.report.variableIdentifier)}}
where prefixDot :: Fixed (ParserT ((,) [[Lexeme t]])) g t ()
prefixDot = Fixed (ParserT ((,) [[Lexeme t]])) g t t
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParserInput (Parser g t)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Parser 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 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 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 ((Char -> Bool)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser 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 ()
-> 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
Modifier t
"."]], ()))
Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> String -> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> String -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"prefix ."
implicitParametersMixin :: Abstract.ExtendedWith '[ 'ImplicitParameters ] l => ExtensionOverlay l g t
implicitParametersMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'ImplicitParameters] l =>
ExtensionOverlay l g t
implicitParametersMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
implicitParameterConstraint =
Abstract.implicitParameterConstraint Abstract.build
<$ delimiter "?"
<*> self.report.variableIdentifier
<* self.report.doubleColon
<*> wrap self.report.typeTerm},
report = super.report{
declarationLevel = super.report.declarationLevel{
declaration = super.report.declarationLevel.declaration
<|> Abstract.implicitParameterDeclaration Abstract.build
<$ delimiter "?"
<*> self.report.variableIdentifier
<* delimiter "="
<*> self.report.expression},
bareExpression = super.report.bareExpression
<|> Abstract.implicitParameterExpression Abstract.build
<$ delimiter "?" <*> self.report.variableIdentifier,
qualifiedVariableSymbol = notFollowedBy (delimiter "?") *> super.report.qualifiedVariableSymbol}}
strictDataMixin :: (SpaceMonoid t, Abstract.ExtendedWith '[ 'StrictData ] l) => ExtensionOverlay l g t
strictDataMixin :: forall t l (g :: (* -> *) -> *).
(SpaceMonoid t, ExtendedWith '[ 'StrictData] l) =>
ExtensionOverlay l g t
strictDataMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
declarationLevel = super.report.declarationLevel{
strictType = super.report.declarationLevel.strictType
<|> Abstract.lazyType Abstract.build <$ delimiter "~" <*> wrap self.report.aType}}}
strictMixin :: (SpaceMonoid t, Abstract.ExtendedWith '[ 'Strict ] l) => ExtensionOverlay l g t
strictMixin :: forall t l (g :: (* -> *) -> *).
(SpaceMonoid t, ExtendedWith '[ 'Strict] l) =>
ExtensionOverlay l g t
strictMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
aPattern =
Abstract.irrefutablePattern
<$ delimiter "~"
<*> parens (wrap (Abstract.lazyPattern Abstract.build
<$ delimiter "~"
<*> wrap self.report.aPattern))
<<|> Abstract.lazyPattern Abstract.build <$ delimiter "~" <*> wrap self.report.aPattern
<<|> super.report.aPattern}}
bangPatternsMixin :: (SpaceMonoid t, Abstract.ExtendedWith '[ 'BangPatterns ] l) => ExtensionOverlay l g t
bangPatternsMixin :: forall t l (g :: (* -> *) -> *).
(SpaceMonoid t, ExtendedWith '[ 'BangPatterns] l) =>
ExtensionOverlay l g t
bangPatternsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
conArgPattern = super.extensions.conArgPattern
<|> Abstract.bangPattern Abstract.build <$ bang <*> wrap self.extensions.conArgPattern},
report = super.report{
variableOperator = notFollowedBy bang *> super.report.variableOperator}}
where bang :: Fixed (ParserT ((,) [[Lexeme t]])) g t t
bang = (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 t. SpaceMonoid t => t -> Bool
precededByOpenSpace Fixed (ParserT ((,) [[Lexeme t]])) g t t
Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *). InputParsing m => m (ParserInput m)
getInput
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 (Parser g t)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Parser g t)
"!"
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
c-> Char -> Bool
Char.isSpace Char
c Bool -> Bool -> Bool
|| Char -> Bool
isSymbol Char
c)
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
<* 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 Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (g :: (* -> *) -> *) t.
(Apply g, Ord t, Show t, TextualMonoid t) =>
Parser g t ()
Report.comment
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
"!"]], ())
viewPatternsMixin :: Abstract.ExtendedWith '[ 'ViewPatterns ] l => ExtensionOverlay l g t
viewPatternsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'ViewPatterns] l =>
ExtensionOverlay l g t
viewPatternsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
pPattern = super.report.pPattern
<|> Abstract.viewPattern Abstract.build
<$> self.report.expression
<* self.report.rightArrow
<*> wrap self.report.pPattern}}
nPlusKPatternsMixin :: Abstract.ExtendedWith '[ 'NPlusKPatterns ] l => ExtensionOverlay l g t
nPlusKPatternsMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'NPlusKPatterns] l =>
ExtensionOverlay l g t
nPlusKPatternsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
pPattern = super.report.pPattern
<|> Abstract.nPlusKPattern Abstract.build
<$> self.report.variable
<* delimiter "+"
<*> self.report.integer}}
patternSynonymsMixin :: forall l g t. (OutlineMonoid t, Abstract.ExtendedWith '[ 'PatternSynonyms ] l,
Deep.Foldable (Serialization (Down Int) t) (Abstract.PatternEquationClause l l),
Deep.Foldable (Serialization (Down Int) t) (Abstract.Declaration l l))
=> ExtensionOverlay l g t
patternSynonymsMixin :: forall l (g :: (* -> *) -> *) t.
(OutlineMonoid t, ExtendedWith '[ 'PatternSynonyms] l,
Foldable (Serialization (Down Int) t) (PatternEquationClause l l),
Foldable (Serialization (Down Int) t) (Declaration l l)) =>
ExtensionOverlay l g t
patternSynonymsMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
moduleLevel= super.report.moduleLevel{
export = super.report.moduleLevel.export
<|> Abstract.exportPattern Abstract.build <$ keyword "pattern"
<*> self.report.qualifiedConstructor,
importItem = super.report.moduleLevel.importItem
<|> Abstract.importPattern Abstract.build <$ keyword "pattern"
<*> self.report.constructor,
members = super.report.moduleLevel.members
<|> parens (Abstract.allMembersPlus Abstract.build
<$> filter (not . null)
(moptional (self.report.moduleLevel.cname `sepBy` comma <* comma)
<> ([] <$ delimiter "..")
<> moptional (comma *> self.report.moduleLevel.cname `sepEndBy` comma)))},
declarationLevel= super.report.declarationLevel{
topLevelDeclaration = super.report.declarationLevel.topLevelDeclaration
<|> keyword "pattern" *>
(Abstract.implicitPatternSynonym Abstract.build
<$> wrap lhsPattern <* delimiter "=" <*> wrap self.report.pattern
<|> Abstract.unidirectionalPatternSynonym Abstract.build
<$> wrap lhsPattern <* self.report.leftArrow <*> wrap self.report.pattern
<|> Abstract.explicitPatternSynonym Abstract.build
<$> wrap lhsPattern
<* self.report.leftArrow
<*> wrap self.report.pattern
<*> patternClauses
<|> Abstract.patternSynonymSignature Abstract.build
<$> self.report.constructor `sepByNonEmpty` comma
<* self.report.doubleColon
<*> self.extensions.optionalForall
<*> wrap (self.report.declarationLevel.context <* self.report.rightDoubleArrow
<<|> pure Abstract.noContext)
<*> self.extensions.optionalForall
<*> wrap self.report.declarationLevel.optionalContext
<*> many (wrap self.extensions.cType <* self.report.rightArrow)
<*> wrap self.extensions.cType)},
variableIdentifier = notFollowedBy (keyword "pattern") *> super.report.variableIdentifier}}
where lhsPattern :: Parser g t (PatternLHS l l (NodeWrap t) (NodeWrap t))
lhsPattern =
Construct '[ 'PatternSynonyms] l l (NodeWrap t) (NodeWrap t)
-> Name l -> [Name l] -> PatternLHS l l (NodeWrap t) (NodeWrap t)
forall λ l (d :: * -> *) (s :: * -> *).
Construct '[ 'PatternSynonyms] λ l d s
-> Name λ -> [Name λ] -> PatternLHS λ l d s
Abstract.prefixPatternLHS Construct '[ 'PatternSynonyms] l l (NodeWrap t) (NodeWrap t)
forall (es :: [Extension]) λ l (d :: * -> *) (s :: * -> *).
ExtendedWith es λ =>
Construct es λ l d s
forall l (d :: * -> *) (s :: * -> *).
Construct '[ 'PatternSynonyms] l l d s
Abstract.build
(Name l -> [Name l] -> PatternLHS l l (NodeWrap t) (NodeWrap t))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([Name l] -> PatternLHS l l (NodeWrap t) (NodeWrap t))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> g (Parser g t)
self.report.constructor
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([Name l] -> PatternLHS l l (NodeWrap t) (NodeWrap t))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [Name l]
-> Parser g t (PatternLHS l l (NodeWrap t) (NodeWrap t))
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 (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 g (Parser g t)
self.report.variableIdentifier
Parser g t (PatternLHS l l (NodeWrap t) (NodeWrap t))
-> Parser g t (PatternLHS l l (NodeWrap t) (NodeWrap t))
-> Parser g t (PatternLHS l l (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
<|> Construct '[ 'PatternSynonyms] l l (NodeWrap t) (NodeWrap t)
-> Name l
-> Name l
-> Name l
-> PatternLHS l l (NodeWrap t) (NodeWrap t)
forall λ l (d :: * -> *) (s :: * -> *).
Construct '[ 'PatternSynonyms] λ l d s
-> Name λ -> Name λ -> Name λ -> PatternLHS λ l d s
Abstract.infixPatternLHS Construct '[ 'PatternSynonyms] l l (NodeWrap t) (NodeWrap t)
forall (es :: [Extension]) λ l (d :: * -> *) (s :: * -> *).
ExtendedWith es λ =>
Construct es λ l d s
forall l (d :: * -> *) (s :: * -> *).
Construct '[ 'PatternSynonyms] l l d s
Abstract.build
(Name l
-> Name l -> Name l -> PatternLHS l l (NodeWrap t) (NodeWrap t))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Name l -> Name l -> PatternLHS l l (NodeWrap t) (NodeWrap t))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> g (Parser g t)
self.report.variableIdentifier
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Name l -> Name l -> PatternLHS l l (NodeWrap t) (NodeWrap t))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Name l -> PatternLHS l l (NodeWrap t) (NodeWrap t))
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
<*> g (Parser g t)
self.report.constructorOperator
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Name l -> PatternLHS l l (NodeWrap t) (NodeWrap t))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
-> Parser g t (PatternLHS l l (NodeWrap t) (NodeWrap t))
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
<*> g (Parser g t)
self.report.variableIdentifier
Parser g t (PatternLHS l l (NodeWrap t) (NodeWrap t))
-> Parser g t (PatternLHS l l (NodeWrap t) (NodeWrap t))
-> Parser g t (PatternLHS l l (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
<|> Construct '[ 'PatternSynonyms] l l (NodeWrap t) (NodeWrap t)
-> Name l -> [Name l] -> PatternLHS l l (NodeWrap t) (NodeWrap t)
forall λ l (d :: * -> *) (s :: * -> *).
Construct '[ 'PatternSynonyms] λ l d s
-> Name λ -> [Name λ] -> PatternLHS λ l d s
Abstract.recordPatternLHS Construct '[ 'PatternSynonyms] l l (NodeWrap t) (NodeWrap t)
forall (es :: [Extension]) λ l (d :: * -> *) (s :: * -> *).
ExtendedWith es λ =>
Construct es λ l d s
forall l (d :: * -> *) (s :: * -> *).
Construct '[ 'PatternSynonyms] l l d s
Abstract.build
(Name l -> [Name l] -> PatternLHS l l (NodeWrap t) (NodeWrap t))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([Name l] -> PatternLHS l l (NodeWrap t) (NodeWrap t))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> g (Parser g t)
self.report.constructor
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([Name l] -> PatternLHS l l (NodeWrap t) (NodeWrap t))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [Name l]
-> Parser g t (PatternLHS l l (NodeWrap t) (NodeWrap t))
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 [Name l]
-> Fixed (ParserT ((,) [[Lexeme t]])) g t [Name l]
forall (m :: * -> *) a. TokenParsing m => m a -> m a
braces (g (Parser g t)
self.report.variable Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
-> Fixed (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]
`sepBy` Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall (m :: * -> *). TokenParsing m => m Char
comma)
patternClauses :: Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
PatternEquationClause l l (NodeWrap t) (NodeWrap t))]
patternClauses = ParserInput (Parser g t)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (m :: * -> *). LexicalParsing m => ParserInput m -> m ()
keyword t
ParserInput (Parser g t)
"where" Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
PatternEquationClause l l (NodeWrap t) (NodeWrap t))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
PatternEquationClause l l (NodeWrap t) (NodeWrap 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
*> Parser
g
t
((Down Int, ParsedLexemes t, Down Int),
PatternEquationClause l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
PatternEquationClause l l (NodeWrap t) (NodeWrap t))]
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 (PatternEquationClause l l (NodeWrap t) (NodeWrap t))
-> Parser
g
t
((Down Int, ParsedLexemes t, Down Int),
PatternEquationClause l l (NodeWrap t) (NodeWrap t))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap Parser g t (PatternEquationClause l l (NodeWrap t) (NodeWrap t))
patternClause)
patternClause :: Parser g t (PatternEquationClause l l (NodeWrap t) (NodeWrap t))
patternClause = forall λ l (d :: * -> *) (s :: * -> *).
Construct '[ 'PatternSynonyms] λ l d s
-> Supports 'PatternSynonyms λ =>
s (PatternEquationLHS l l d d)
-> s (EquationRHS l l d d)
-> [s (Declaration l l d d)]
-> PatternEquationClause λ l d s
Abstract.patternEquationClause @l Construct '[ 'PatternSynonyms] l l (NodeWrap t) (NodeWrap t)
forall (es :: [Extension]) λ l (d :: * -> *) (s :: * -> *).
ExtendedWith es λ =>
Construct es λ l d s
forall l (d :: * -> *) (s :: * -> *).
Construct '[ 'PatternSynonyms] l l d s
Abstract.build
(((Down Int, ParsedLexemes t, Down Int),
PatternEquationLHS l l (NodeWrap t) (NodeWrap t))
-> ((Down Int, ParsedLexemes t, Down Int),
EquationRHS l l (NodeWrap t) (NodeWrap t))
-> [((Down Int, ParsedLexemes t, Down Int),
Declaration l l (NodeWrap t) (NodeWrap t))]
-> PatternEquationClause l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
PatternEquationLHS l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
EquationRHS l l (NodeWrap t) (NodeWrap t))
-> [((Down Int, ParsedLexemes t, Down Int),
Declaration l l (NodeWrap t) (NodeWrap t))]
-> PatternEquationClause l l (NodeWrap t) (NodeWrap t))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser g t (PatternEquationLHS l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
PatternEquationLHS l l (NodeWrap t) (NodeWrap t))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap Parser g t (PatternEquationLHS l l (NodeWrap t) (NodeWrap t))
patternClauseLHS
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
EquationRHS l l (NodeWrap t) (NodeWrap t))
-> [((Down Int, ParsedLexemes t, Down Int),
Declaration l l (NodeWrap t) (NodeWrap t))]
-> PatternEquationClause l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
EquationRHS l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
Declaration l l (NodeWrap t) (NodeWrap t))]
-> PatternEquationClause l l (NodeWrap t) (NodeWrap t))
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
<*> Parser g t (EquationRHS l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
EquationRHS l l (NodeWrap t) (NodeWrap t))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap g (Parser g t)
self.report.rhs
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
Declaration l l (NodeWrap t) (NodeWrap t))]
-> PatternEquationClause l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Declaration l l (NodeWrap t) (NodeWrap t))]
-> Parser g t (PatternEquationClause l l (NodeWrap t) (NodeWrap t))
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
<*> g (Parser g t)
self.report.declarationLevel.whereClauses
patternClauseLHS :: Parser g t (PatternEquationLHS l l (NodeWrap t) (NodeWrap t))
patternClauseLHS =
Construct '[ 'PatternSynonyms] l l (NodeWrap t) (NodeWrap t)
-> Name l
-> [((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))]
-> PatternEquationLHS l l (NodeWrap t) (NodeWrap t)
forall λ l (d :: * -> *) (s :: * -> *).
Construct '[ 'PatternSynonyms] λ l d s
-> Name λ -> [s (Pattern l l d d)] -> PatternEquationLHS λ l d s
Abstract.prefixPatternEquationLHS Construct '[ 'PatternSynonyms] l l (NodeWrap t) (NodeWrap t)
forall (es :: [Extension]) λ l (d :: * -> *) (s :: * -> *).
ExtendedWith es λ =>
Construct es λ l d s
forall l (d :: * -> *) (s :: * -> *).
Construct '[ 'PatternSynonyms] l l d s
Abstract.build
(Name l
-> [((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))]
-> PatternEquationLHS l l (NodeWrap t) (NodeWrap t))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))]
-> PatternEquationLHS l l (NodeWrap t) (NodeWrap t))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> g (Parser g t)
self.report.constructor
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
([((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))]
-> PatternEquationLHS l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))]
-> Parser g t (PatternEquationLHS l l (NodeWrap t) (NodeWrap t))
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 (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))]
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 (Parser g t (Pattern l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap g (Parser g t)
self.report.pattern)
Parser g t (PatternEquationLHS l l (NodeWrap t) (NodeWrap t))
-> Parser g t (PatternEquationLHS l l (NodeWrap t) (NodeWrap t))
-> Parser g t (PatternEquationLHS l l (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
<|> Construct '[ 'PatternSynonyms] l l (NodeWrap t) (NodeWrap t)
-> ((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))
-> Name l
-> ((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))
-> PatternEquationLHS l l (NodeWrap t) (NodeWrap t)
forall λ l (d :: * -> *) (s :: * -> *).
Construct '[ 'PatternSynonyms] λ l d s
-> s (Pattern l l d d)
-> Name λ
-> s (Pattern l l d d)
-> PatternEquationLHS λ l d s
Abstract.infixPatternEquationLHS Construct '[ 'PatternSynonyms] l l (NodeWrap t) (NodeWrap t)
forall (es :: [Extension]) λ l (d :: * -> *) (s :: * -> *).
ExtendedWith es λ =>
Construct es λ l d s
forall l (d :: * -> *) (s :: * -> *).
Construct '[ 'PatternSynonyms] l l d s
Abstract.build
(((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))
-> Name l
-> ((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))
-> PatternEquationLHS l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Name l
-> ((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))
-> PatternEquationLHS l l (NodeWrap t) (NodeWrap t))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser g t (Pattern l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap g (Parser g t)
self.report.pattern
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(Name l
-> ((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))
-> PatternEquationLHS l l (NodeWrap t) (NodeWrap t))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t (Name l)
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))
-> PatternEquationLHS l l (NodeWrap t) (NodeWrap t))
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
<*> g (Parser g t)
self.report.constructorOperator
Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))
-> PatternEquationLHS l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))
-> Parser g t (PatternEquationLHS l l (NodeWrap t) (NodeWrap t))
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
<*> Parser g t (Pattern l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Pattern l l (NodeWrap t) (NodeWrap t))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap g (Parser g t)
self.report.pattern
standaloneDerivingMixin :: Abstract.ExtendedWith '[ 'StandaloneDeriving ] l => ExtensionOverlay l g t
standaloneDerivingMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'StandaloneDeriving] l =>
ExtensionOverlay l g t
standaloneDerivingMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
declarationLevel= super.report.declarationLevel{
topLevelDeclaration = super.report.declarationLevel.topLevelDeclaration
<|> Abstract.standaloneDerivingDeclaration Abstract.build <$ keyword "deriving" <* keyword "instance"
<*> self.extensions.optionalForall
<*> wrap self.report.declarationLevel.optionalContext
<*> wrap self.report.declarationLevel.instanceDesignator}}}
derivingStrategiesMixin :: forall l g t. Abstract.ExtendedWith '[ 'DerivingStrategies ] l => ExtensionOverlay l g t
derivingStrategiesMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'DerivingStrategies] l =>
ExtensionOverlay l g t
derivingStrategiesMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
declarationLevel= super.report.declarationLevel{
derivingClause = concatSome self.extensions.singleDerivingClause}},
extensions = super.extensions{
singleDerivingClause = super.report.declarationLevel.derivingClause
<|> takeSome (wrap $
Abstract.strategicDerive Abstract.build <$ keyword "deriving"
<*> wrap self.extensions.derivingStrategy
<*> (pure <$> wrap (Abstract.constructorType <$> wrap self.report.generalConstructor)
<<|> parens (wrap self.report.typeTerm `sepBy` comma))),
derivingStrategy = Abstract.stockStrategy @l Abstract.build <$ keyword "stock"
<|> Abstract.anyClassStrategy @l Abstract.build <$ keyword "anyclass"
<|> Abstract.newtypeStrategy @l Abstract.build <$ keyword "newtype"}}
standaloneDerivingStrategiesMixin :: (Abstract.ExtendedWith '[ 'StandaloneDeriving ] l,
Abstract.ExtendedWith '[ 'DerivingStrategies ] l)
=> ExtensionOverlay l g t
standaloneDerivingStrategiesMixin :: forall l (g :: (* -> *) -> *) t.
(ExtendedWith '[ 'StandaloneDeriving] l,
ExtendedWith '[ 'DerivingStrategies] l) =>
ExtensionOverlay l g t
standaloneDerivingStrategiesMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
declarationLevel= super.report.declarationLevel{
topLevelDeclaration = super.report.declarationLevel.topLevelDeclaration
<|> Abstract.standaloneStrategicDerivingDeclaration Abstract.build
<$ keyword "deriving"
<*> wrap self.extensions.derivingStrategy
<* keyword "instance"
<*> self.extensions.optionalForall
<*> wrap self.report.declarationLevel.optionalContext
<*> wrap self.report.declarationLevel.instanceDesignator}}}
derivingViaMixin :: forall l g t. Abstract.ExtendedWith '[ 'DerivingVia ] l => ExtensionOverlay l g t
derivingViaMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'DerivingVia] l =>
ExtensionOverlay l g t
derivingViaMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
singleDerivingClause =
super.extensions.singleDerivingClause
<|> takeSome (wrap $
Abstract.deriveVia Abstract.build <$ keyword "deriving"
<*> (parens (wrap self.report.typeTerm `sepBy` comma)
<<|> pure <$> wrap (Abstract.constructorType <$> wrap self.report.generalConstructor))
<* keyword "via"
<*> wrap self.report.typeTerm)}}
standaloneDerivingViaMixin :: forall l g t. (Abstract.ExtendedWith '[ 'StandaloneDeriving ] l,
Abstract.ExtendedWith '[ 'DerivingStrategies ] l,
Abstract.ExtendedWith '[ 'DerivingVia ] l)
=> ExtensionOverlay l g t
standaloneDerivingViaMixin :: forall l (g :: (* -> *) -> *) t.
(ExtendedWith '[ 'StandaloneDeriving] l,
ExtendedWith '[ 'DerivingStrategies] l,
ExtendedWith '[ 'DerivingVia] l) =>
ExtensionOverlay l g t
standaloneDerivingViaMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
declarationLevel= super.report.declarationLevel{
topLevelDeclaration = super.report.declarationLevel.topLevelDeclaration
<|> Abstract.standaloneStrategicDerivingDeclaration Abstract.build
<$ keyword "deriving"
<*> wrap derivingVia
<* keyword "instance"
<*> self.extensions.optionalForall
<*> wrap self.report.declarationLevel.optionalContext
<*> wrap self.report.declarationLevel.instanceDesignator}}}
where derivingVia :: Parser g t (DerivingStrategy l l (NodeWrap t) (NodeWrap t))
derivingVia = forall λ l (d :: * -> *) (s :: * -> *).
Construct '[ 'DerivingVia] λ l d s
-> s (Type l l d d) -> DerivingStrategy λ l d s
Abstract.derivingViaStrategy @l Construct '[ 'DerivingVia] l l (NodeWrap t) (NodeWrap t)
forall (es :: [Extension]) λ l (d :: * -> *) (s :: * -> *).
ExtendedWith es λ =>
Construct es λ l d s
forall l (d :: * -> *) (s :: * -> *).
Construct '[ 'DerivingVia] l l d s
Abstract.build (((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> DerivingStrategy l l (NodeWrap t) (NodeWrap t))
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> DerivingStrategy l l (NodeWrap t) (NodeWrap t))
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 (Parser g t)
-> Fixed (ParserT ((,) [[Lexeme t]])) g t ()
forall (m :: * -> *). LexicalParsing m => ParserInput m -> m ()
keyword t
ParserInput (Parser g t)
"via" Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
(((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> DerivingStrategy l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
-> Parser g t (DerivingStrategy l l (NodeWrap t) (NodeWrap t))
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
<*> Parser g t (Type l l (NodeWrap t) (NodeWrap t))
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
((Down Int, ParsedLexemes t, Down Int),
Type l l (NodeWrap t) (NodeWrap t))
forall (g :: (* -> *) -> *) t a.
(Apply g, Ord t, TextualMonoid t) =>
Parser g t a -> Parser g t (NodeWrap t a)
wrap g (Parser g t)
self.report.typeTerm
functionalDependenciesMixin :: forall l g t. (OutlineMonoid t, Abstract.ExtendedWith '[ 'FunctionalDependencies ] l,
Deep.Foldable (Serialization (Down Int) t) (Abstract.Declaration l l))
=> ExtensionOverlay l g t
functionalDependenciesMixin :: forall l (g :: (* -> *) -> *) t.
(OutlineMonoid t, ExtendedWith '[ 'FunctionalDependencies] l,
Foldable (Serialization (Down Int) t) (Declaration l l)) =>
ExtensionOverlay l g t
functionalDependenciesMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
declarationLevel= super.report.declarationLevel{
topLevelDeclaration = super.report.declarationLevel.topLevelDeclaration
<|> Abstract.fundepClassDeclaration Abstract.build
<$ keyword "class"
<*> wrap self.report.declarationLevel.optionalContext
<*> wrap self.report.declarationLevel.classLHS
<* delimiter "|"
<*> wrap (Abstract.functionalDependency Abstract.build
<$> many self.report.typeVar <* self.report.rightArrow <*> many self.report.typeVar)
`sepBy` comma
<*> moptional (keyword "where" *> blockOf (wrap self.report.declarationLevel.inClassDeclaration))}}}
constraintsAreTypesMixin :: forall l g t. Abstract.ExtendedHaskell l => ExtensionOverlay l g t
constraintsAreTypesMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedHaskell l =>
ExtensionOverlay l g t
constraintsAreTypesMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
extensions = super.extensions{
cType = super.extensions.cType <|> Abstract.constraintType <$> wrap self.extensions.equalityConstraint},
report= super.report{
typeTerm = super.report.typeTerm
<|> Abstract.constraintType <$> wrap self.extensions.implicitParameterConstraint,
declarationLevel= super.report.declarationLevel{
context = self.report.declarationLevel.constraint,
constraint = Abstract.typeConstraint <$> wrap self.extensions.cType}}}
instanceSignaturesMixin :: ExtensionOverlay l g t
instanceSignaturesMixin :: forall l (g :: (* -> *) -> *) t. ExtensionOverlay l g t
instanceSignaturesMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
declarationLevel= super.report.declarationLevel{
inInstanceDeclaration = super.report.declarationLevel.inInstanceDeclaration
<|> Abstract.typeSignature <$> self.report.declarationLevel.variables
<* self.report.doubleColon
<*> wrap self.report.declarationLevel.optionalTypeSignatureContext
<*> wrap self.report.typeTerm}}}
defaultSignaturesMixin :: Abstract.ExtendedWith '[ 'DefaultSignatures ] l => ExtensionOverlay l g t
defaultSignaturesMixin :: forall l (g :: (* -> *) -> *) t.
ExtendedWith '[ 'DefaultSignatures] l =>
ExtensionOverlay l g t
defaultSignaturesMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
declarationLevel= super.report.declarationLevel{
inClassDeclaration = super.report.declarationLevel.inClassDeclaration
<|> Abstract.defaultMethodSignature Abstract.build <$ keyword "default"
<*> self.report.variable
<* self.report.doubleColon
<*> wrap self.report.declarationLevel.optionalTypeSignatureContext
<*> wrap self.report.typeTerm}}}
negationConstraintMixin :: Parser g t t -> ExtensionOverlay l g t
negationConstraintMixin :: forall (g :: (* -> *) -> *) t l.
Parser g t t -> ExtensionOverlay l g t
negationConstraintMixin Parser g t t
prefixMinusFollow g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report= super.report{
variableSymbol = negationGuard *> super.report.variableSymbol,
qualifiedVariableSymbol = negationGuard *> super.report.qualifiedVariableSymbol,
prefixNegation = negationGuard *> super.report.prefixNegation}}
where negationGuard :: Fixed (ParserT ((,) [[Lexeme t]])) g t ()
negationGuard = Parser 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 (ParserInput (Parser g t)
-> Fixed
(ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *).
InputParsing m =>
ParserInput m -> m (ParserInput m)
string t
ParserInput (Parser g t)
"-" Parser g t t -> Parser g t t -> Parser 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
*> Parser g t t
prefixMinusFollow)
nondecreasingIndentationMixin :: (Deep.Foldable (Serialization (Down Int) t) (Abstract.Expression l l),
Deep.Foldable (Serialization (Down Int) t) (Abstract.Statement l l),
OutlineMonoid t)
=> ExtensionOverlay l g t
nondecreasingIndentationMixin :: forall t l (g :: (* -> *) -> *).
(Foldable (Serialization (Down Int) t) (Expression l l),
Foldable (Serialization (Down Int) t) (Statement l l),
OutlineMonoid t) =>
ExtensionOverlay l g t
nondecreasingIndentationMixin g (Parser g t)
self g (Parser g t)
super = g (Parser g t)
super{
report = super.report{
statements = Report.blockWith nonDecreasingIndentLine Report.blockTerminatorKeyword self.report.statement
>>= Report.verifyStatements}}
variableLexeme, constructorLexeme, 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
Report.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
-> String -> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> String -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"variable"
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
-> String -> Fixed (ParserT ((,) [[Lexeme t]])) g t t
forall a.
Fixed (ParserT ((,) [[Lexeme t]])) g t a
-> String -> Fixed (ParserT ((,) [[Lexeme t]])) g t a
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"constructor"
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
varStart :: Char -> Bool
varStart :: Char -> Bool
varStart Char
c = (Char -> Bool
Char.isLetter Char
c Bool -> Bool -> Bool
&& Bool -> Bool
not (Char -> Bool
Char.isUpper Char
c)) Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_'
isNameTailChar :: Char -> Bool
isNameTailChar :: Char -> Bool
isNameTailChar Char
c = Char -> Bool
Report.isNameTailChar Char
c Bool -> Bool -> Bool
|| Char -> Bool
Char.isMark Char
c
whiteSpaceTrailing :: (Show t, Factorial.Factorial t, Deep.Foldable (Serialization (Down Int) t) node)
=> NodeWrap t (node (NodeWrap t) (NodeWrap t)) -> Bool
whiteSpaceTrailing :: forall t (node :: (* -> *) -> (* -> *) -> *).
(Show t, Factorial t,
Foldable (Serialization (Down Int) t) node) =>
NodeWrap t (node (NodeWrap t) (NodeWrap t)) -> Bool
whiteSpaceTrailing NodeWrap t (node (NodeWrap t) (NodeWrap t))
node = case 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 of
ws :: [Lexeme t]
ws@(Lexeme t
_:[Lexeme t]
_) -> case [Lexeme t] -> Lexeme t
forall a. HasCallStack => [a] -> a
last [Lexeme t]
ws of
WhiteSpace{} -> Bool
True
Comment{} -> Bool
True
Lexeme t
_ -> Bool
False
[Lexeme t]
_ -> Bool
False
rewrap2 :: (NodeWrap t a -> NodeWrap t b -> c) -> NodeWrap t a -> NodeWrap t b -> NodeWrap t c
rewrap2 :: forall t a b c.
(NodeWrap t a -> NodeWrap t b -> c)
-> NodeWrap t a -> NodeWrap t b -> NodeWrap t c
rewrap2 NodeWrap t a -> NodeWrap t b -> c
f node1 :: NodeWrap t a
node1@((Down Int
start, ParsedLexemes t
_, Down Int
_), a
_) node2 :: NodeWrap t b
node2@((Down Int
_, ParsedLexemes t
_, Down Int
end), b
_) = ((Down Int
start, ParsedLexemes t
forall a. Monoid a => a
mempty, Down Int
end), NodeWrap t a -> NodeWrap t b -> c
f NodeWrap t a
node1 NodeWrap t b
node2)
blockOf' :: (Rank2.Apply g, Ord t, Show t, OutlineMonoid t, LexicalParsing (Parser g 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,
LexicalParsing (Parser g 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 (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)))
-> 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]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t String
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 Fixed (ParserT ((,) [[Lexeme t]])) g t Char
forall (m :: * -> *). TokenParsing m => m Char
semi Fixed (ParserT ((,) [[Lexeme t]])) g t String
-> Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))
-> Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap 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
*> 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 String
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap t (node (NodeWrap t) (NodeWrap 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
<* Fixed (ParserT ((,) [[Lexeme t]])) g t Char
-> Fixed (ParserT ((,) [[Lexeme t]])) g t String
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 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
>>= ([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))]
alignedBlock [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 :: ([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))]
alignedBlock [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap t (node (NodeWrap t) (NodeWrap t))]
cont Int
indent =
do rest <- Fixed (ParserT ((,) [[Lexeme t]])) g t t
Fixed (ParserT ((,) [[Lexeme t]])) g t (ParserInput (Parser g t))
forall (m :: * -> *). InputParsing m => m (ParserInput m)
getInput
item <- filter (oneExtendedLine indent rest) p
void (filter (indent >=) inputColumn)
<<|> lookAhead (void (Text.Parser.Char.satisfy (`elem` terminators))
<|> string "|" *> notSatisfyChar isSymbol
<|> (string "else" <|> string "in"
<|> string "of" <|> string "where") *> notSatisfyChar isNameTailChar
<|> eof)
indent' <- inputColumn
let cont' = [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap t (node (NodeWrap t) (NodeWrap t))]
cont ([NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap t (node (NodeWrap t) (NodeWrap t))])
-> ([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
[NodeWrap t (node (NodeWrap t) (NodeWrap t))]
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]
:)
if indent == indent'
then many semi *> alignedBlock cont' indent
else if indent < indent'
then many semi *> alignedBlock cont' indent <<|> cont' []
else some semi *> alignedBlock cont' indent <<|> cont' []
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 (m :: * -> *) a. DeterministicParsing m => m a -> m a -> m a
<<|> [NodeWrap t (node (NodeWrap t) (NodeWrap t))]
-> Fixed
(ParserT ((,) [[Lexeme t]]))
g
t
[NodeWrap t (node (NodeWrap t) (NodeWrap t))]
cont []
terminators :: [Char]
terminators :: String
terminators = String
",;)]}"
nonDecreasingIndentLine :: (Ord t, Show t, OutlineMonoid t, Deep.Foldable (Serialization (Down Int) t) node)
=> Int -> t -> NodeWrap t (node (NodeWrap t) (NodeWrap t)) -> Bool
nonDecreasingIndentLine :: 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
nonDecreasingIndentLine Int
indent t
_input NodeWrap t (node (NodeWrap t) (NodeWrap t))
node = Bool -> [Lexeme t] -> Bool
allIndented Bool
False (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 :: Bool -> [Lexeme t] -> Bool
allIndented Bool
nested (WhiteSpace t
_ : Token TokenType
Delimiter t
_tok : [Lexeme t]
rest) = Bool -> [Lexeme t] -> Bool
allIndented Bool
nested [Lexeme t]
rest
allIndented Bool
nested (WhiteSpace t
ws : rest :: [Lexeme t]
rest@(Token TokenType
_ t
tok : [Lexeme t]
_))
| (Char -> Bool) -> t -> Bool
forall t. TextualMonoid t => (Char -> Bool) -> t -> Bool
Textual.all Char -> Bool
Report.isLineChar t
ws = Bool -> [Lexeme t] -> Bool
allIndented Bool
nested [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
&& Bool -> Bool
not Bool
nested Bool -> Bool -> Bool
&& t
tok t -> Set t -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.notMember` Set t
forall t. (Ord t, TextualMonoid t) => Set t
Report.reservedWords
Bool -> Bool -> Bool
&& (Char -> Bool) -> Maybe Char -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` String
terminators) (t -> Maybe Char
forall t. TextualMonoid t => t -> Maybe Char
Textual.characterPrefix t
tok) = Bool
False
where tokenIndent :: Int
tokenIndent = t -> Int
forall t. OutlineMonoid t => t -> Int
Report.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 Bool
False (Token TokenType
Keyword t
k : [Lexeme t]
rest)
| t
k t -> [t] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [t
"do", t
"of", t
"let", t
"where"] = Bool -> [Lexeme t] -> Bool
allIndented Bool
True [Lexeme t]
rest
allIndented Bool
nested (Lexeme t
x : [Lexeme t]
rest) = Bool -> [Lexeme t] -> Bool
allIndented Bool
nested [Lexeme t]
rest
allIndented Bool
_ [] = Bool
True
terminators :: [Char]
terminators :: String
terminators = String
",;)]}"