Safe Haskell | None |
---|---|
Language | Haskell2010 |
Language.Haskell.Reserializer
Description
This module exports functions for reserializing the parsed tree from the tokens stored with every node.
Synopsis
- newtype ParsedLexemes s = Trailing [Lexeme s]
- data Lexeme s
- = WhiteSpace {
- lexemeText :: s
- | Comment {
- lexemeText :: s
- | Token {
- lexemeType :: TokenType
- lexemeText :: s
- = WhiteSpace {
- data TokenType
- type Wrapped pos s = (,) (pos, ParsedLexemes s, pos)
- adjustPositions :: (Factorial s, Position pos, Foldable (g (Const (Sum Int) :: Type -> Type)), Foldable (Fold (Wrapped pos s) (Sum Int)) g, Traversable (PositionAdjustment pos s) g) => Wrapped pos s (g (Wrapped pos s) (Wrapped pos s)) -> Wrapped pos s (g (Wrapped pos s) (Wrapped pos s))
- lexemes :: (Factorial s, Position pos, Foldable (Serialization pos s) g) => Wrapped pos s (g (Wrapped pos s) (Wrapped pos s)) -> [Lexeme s]
- reserialize :: (Monoid s, Factorial s, Position pos, Foldable (Serialization pos s) g) => Wrapped pos s (g (Wrapped pos s) (Wrapped pos s)) -> s
- reserializeNested :: forall s pos (f :: Type -> Type) g. (Monoid s, Factorial s, Position pos, Foldable f, Foldable (Folded f (Serialization pos s)) g) => Compose f (Wrapped pos s) (g (Compose f (Wrapped pos s)) (Compose f (Wrapped pos s))) -> s
- sourceLength :: forall g s pos. (Factorial s, Foldable (g (Const (Sum Int) :: Type -> Type)), Foldable (Fold (Wrapped pos s) (Sum Int)) g) => Wrapped pos s (g (Wrapped pos s) (Wrapped pos s)) -> Int
- joinWrapped :: (Position pos, Factorial s) => Wrapped pos s (Wrapped pos s a) -> Wrapped pos s a
- mergeLexemes :: (Position pos, Factorial s) => pos -> [Lexeme s] -> pos -> [Lexeme s] -> [Lexeme s]
- mapWrapping :: (pos -> pos') -> (s -> s') -> Wrapped pos s a -> Wrapped pos' s' a
- mapWrappings :: Functor (Map (Wrapped pos s) (Wrapped pos' s')) g => (pos -> pos') -> (s -> s') -> Wrapped pos s (g (Wrapped pos s) (Wrapped pos s)) -> Wrapped pos' s' (g (Wrapped pos' s') (Wrapped pos' s'))
- data PositionAdjustment pos s = PositionAdjustment
- data NestedPositionAdjustment (f :: Type -> Type) pos s = NestedPositionAdjustment
- data Serialization pos s
Documentation
newtype ParsedLexemes s Source #
Instances
Constructors
WhiteSpace | |
Fields
| |
Comment | |
Fields
| |
Token | |
Fields
|
Instances
Functor Lexeme Source # | |
Eq s => Eq (Lexeme s) Source # | |
Data s => Data (Lexeme s) Source # | |
Defined in Language.Haskell.Reserializer Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Lexeme s -> c (Lexeme s) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Lexeme s) # toConstr :: Lexeme s -> Constr # dataTypeOf :: Lexeme s -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Lexeme s)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Lexeme s)) # gmapT :: (forall b. Data b => b -> b) -> Lexeme s -> Lexeme s # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Lexeme s -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Lexeme s -> r # gmapQ :: (forall d. Data d => d -> u) -> Lexeme s -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Lexeme s -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Lexeme s -> m (Lexeme s) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Lexeme s -> m (Lexeme s) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Lexeme s -> m (Lexeme s) # | |
Show s => Show (Lexeme s) Source # | |
(Apply g, Ord t, Show t, TextualMonoid t) => LexicalParsing (Parser g t) Source # | |
Defined in Language.Haskell.Grammar Methods lexicalWhiteSpace :: Parser g t () # someLexicalSpace :: Parser g t () # lexicalComment :: Parser g t () # lexicalSemicolon :: Parser g t Char # lexicalToken :: Parser g t a -> Parser g t a # identifierToken :: Parser g t (ParserInput (Parser g t)) -> Parser g t (ParserInput (Parser g t)) # isIdentifierStartChar :: Char -> Bool # isIdentifierFollowChar :: Char -> Bool # identifier :: Parser g t (ParserInput (Parser g t)) # keyword :: ParserInput (Parser g t) -> Parser g t () # | |
(Apply g, Ord t, Show t, TextualMonoid t) => TokenParsing (Parser g t) Source # | |
Instances
Eq TokenType Source # | |
Data TokenType Source # | |
Defined in Language.Haskell.Reserializer Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TokenType -> c TokenType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TokenType # toConstr :: TokenType -> Constr # dataTypeOf :: TokenType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TokenType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenType) # gmapT :: (forall b. Data b => b -> b) -> TokenType -> TokenType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TokenType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TokenType -> r # gmapQ :: (forall d. Data d => d -> u) -> TokenType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TokenType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TokenType -> m TokenType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenType -> m TokenType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenType -> m TokenType # | |
Show TokenType Source # | |
type Wrapped pos s = (,) (pos, ParsedLexemes s, pos) Source #
adjustPositions :: (Factorial s, Position pos, Foldable (g (Const (Sum Int) :: Type -> Type)), Foldable (Fold (Wrapped pos s) (Sum Int)) g, Traversable (PositionAdjustment pos s) g) => Wrapped pos s (g (Wrapped pos s) (Wrapped pos s)) -> Wrapped pos s (g (Wrapped pos s) (Wrapped pos s)) Source #
Re-calculates the position of every node in the parse tree from the tokens stored with it and its children.
lexemes :: (Factorial s, Position pos, Foldable (Serialization pos s) g) => Wrapped pos s (g (Wrapped pos s) (Wrapped pos s)) -> [Lexeme s] Source #
Serializes the tree into the lexemes it was parsed from.
reserialize :: (Monoid s, Factorial s, Position pos, Foldable (Serialization pos s) g) => Wrapped pos s (g (Wrapped pos s) (Wrapped pos s)) -> s Source #
Serializes the tree back into the text it was parsed from.
reserializeNested :: forall s pos (f :: Type -> Type) g. (Monoid s, Factorial s, Position pos, Foldable f, Foldable (Folded f (Serialization pos s)) g) => Compose f (Wrapped pos s) (g (Compose f (Wrapped pos s)) (Compose f (Wrapped pos s))) -> s Source #
Serializes the tree just like reserialize
, but with an additional wrapping on every node.
sourceLength :: forall g s pos. (Factorial s, Foldable (g (Const (Sum Int) :: Type -> Type)), Foldable (Fold (Wrapped pos s) (Sum Int)) g) => Wrapped pos s (g (Wrapped pos s) (Wrapped pos s)) -> Int Source #
The length of the source code parsed into the argument node
joinWrapped :: (Position pos, Factorial s) => Wrapped pos s (Wrapped pos s a) -> Wrapped pos s a Source #
Join the two wrappings of a double-Wrapped
value into one.
mergeLexemes :: (Position pos, Factorial s) => pos -> [Lexeme s] -> pos -> [Lexeme s] -> [Lexeme s] Source #
Given two lists of lexemes where the first wraps the second and their starting positions, return a single list sorted by position.
mapWrapping :: (pos -> pos') -> (s -> s') -> Wrapped pos s a -> Wrapped pos' s' a Source #
mapWrappings :: Functor (Map (Wrapped pos s) (Wrapped pos' s')) g => (pos -> pos') -> (s -> s') -> Wrapped pos s (g (Wrapped pos s) (Wrapped pos s)) -> Wrapped pos' s' (g (Wrapped pos' s') (Wrapped pos' s')) Source #
Map the stored positions and lexeme inputs in the entire tree and its wrapping
data PositionAdjustment pos s Source #
Transformation type used by adjustPositions
Constructors
PositionAdjustment |
Instances
data NestedPositionAdjustment (f :: Type -> Type) pos s Source #
Constructors
NestedPositionAdjustment |
Instances
Transformation (NestedPositionAdjustment f pos s) Source # | |||||||||
Defined in Language.Haskell.Reserializer Associated Types
| |||||||||
(Factorial s, Position pos, Traversable f, Foldable (g (Const (Sum Int) :: Type -> Type)), Traversable (g (Compose f (Wrapped pos s))), Foldable (Fold (Compose f (Wrapped pos s)) (Sum Int)) g, Traversable (NestedPositionAdjustment f pos s) g) => Traversable (NestedPositionAdjustment f pos s) g Source # | |||||||||
Defined in Language.Haskell.Reserializer Methods traverse :: Codomain (NestedPositionAdjustment f pos s) ~ Compose m f0 => NestedPositionAdjustment f pos s -> Domain (NestedPositionAdjustment f pos s) (g (Domain (NestedPositionAdjustment f pos s)) (Domain (NestedPositionAdjustment f pos s))) -> m (f0 (g f0 f0)) # | |||||||||
(Factorial s, Traversable f, Foldable (g (Const (Sum Int) :: Type -> Type)), Position pos, Foldable (Fold (Compose f (Wrapped pos s)) (Sum Int)) g) => At (NestedPositionAdjustment f pos s) (g (Compose f (Wrapped pos s)) (Compose f (Wrapped pos s))) Source # | |||||||||
Defined in Language.Haskell.Reserializer Methods ($) :: NestedPositionAdjustment f pos s -> Domain (NestedPositionAdjustment f pos s) (g (Compose f (Wrapped pos s)) (Compose f (Wrapped pos s))) -> Codomain (NestedPositionAdjustment f pos s) (g (Compose f (Wrapped pos s)) (Compose f (Wrapped pos s))) # | |||||||||
type Codomain (NestedPositionAdjustment f pos s) Source # | |||||||||
Defined in Language.Haskell.Reserializer | |||||||||
type Domain (NestedPositionAdjustment f pos s) Source # | |||||||||
Defined in Language.Haskell.Reserializer |
data Serialization pos s Source #
Transformation type used by reserialize
Instances
Transformation (Serialization pos s) Source # | |||||||||
Defined in Language.Haskell.Reserializer Associated Types
| |||||||||
(Factorial s, Position pos) => At (Serialization pos s) a Source # | |||||||||
Defined in Language.Haskell.Reserializer Methods ($) :: Serialization pos s -> Domain (Serialization pos s) a -> Codomain (Serialization pos s) a # | |||||||||
(Factorial s, Position pos, Foldable f, Foldable (g (Compose f (Wrapped pos s))), Foldable (Folded f (Serialization pos s)) g) => Foldable (Folded f (Serialization pos s)) g Source # | |||||||||
Defined in Language.Haskell.Reserializer Methods foldMap :: (Codomain (Folded f (Serialization pos s)) ~ (Const m :: Type -> Type), Monoid m) => Folded f (Serialization pos s) -> Domain (Folded f (Serialization pos s)) (g (Domain (Folded f (Serialization pos s))) (Domain (Folded f (Serialization pos s)))) -> m # | |||||||||
(Factorial s, Position pos, Foldable (g (Wrapped pos s)), Foldable (Serialization pos s) g) => Foldable (Serialization pos s) g Source # | |||||||||
Defined in Language.Haskell.Reserializer Methods foldMap :: (Codomain (Serialization pos s) ~ (Const m :: Type -> Type), Monoid m) => Serialization pos s -> Domain (Serialization pos s) (g (Domain (Serialization pos s)) (Domain (Serialization pos s))) -> m # | |||||||||
type Codomain (Serialization pos s) Source # | |||||||||
Defined in Language.Haskell.Reserializer | |||||||||
type Domain (Serialization pos s) Source # | |||||||||
Defined in Language.Haskell.Reserializer |