Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class CanBePlain x where
- class CanFork x where
- class IsTaggedOrBare a where
- type TaggedType a
- type BareType a
- taggedOrBare :: Iso' a (TaggedOrBare a)
- class HasManyPlainBlocks x where
- allPlainBlocks :: Traversal' x (TaggedPlainBlock (Annotation x))
- class HasManyPlainInlines x where
- allPlainInlines :: Traversal' x (Fragment (Annotation x))
- class HasAnnotation x x' where
- annotation :: Lens x x' (Annotation x) (Annotation x')
- type HasAnnotation' x = HasAnnotation x x
- class HasManyAnnotations x x' where
- allAnnotations :: Traversal x x' (Annotation x) (Annotation x')
- class HasContent x x' where
- type HasContent' x = HasContent x x
- class HasContents x x' where
- type HasContents' x = HasContents x x
- class HasMetadata x where
- type MetadataOpticKind x
- metadata :: Optic' (MetadataOpticKind x) NoIx x Metadata
- class HasManyMetadata x where
- class HasTag x where
- type TagOpticKind x :: OpticKind
- tag :: Optic' (TagOpticKind x) NoIx x (Tag (Annotation x))
- class HasManyTags x where
- allTags :: Traversal' x (Tag (Annotation x))
- allInlineTags :: Traversal' x (Tag (Annotation x))
- class HasManyTags x => HasManyBlockTags x where
- allBlockTags :: Traversal' x (Tag (Annotation x))
- class HasWitherableTags x where
- witherTags :: Monad f => (Tag (Annotation x) -> f (Maybe (Tag (Annotation x)))) -> x -> f x
- mapMaybeTags :: (Tag (Annotation x) -> Maybe (Tag (Annotation x))) -> x -> x
- class HasManyTags x => HasWitherableInlineTags x where
- witherInlineTags :: Monad f => (Tag (Annotation x) -> f (Maybe (Tag (Annotation x)))) -> x -> f x
- mapMaybeInlineTags :: (Tag (Annotation x) -> Maybe (Tag (Annotation x))) -> x -> x
- class HasManyBlockTags x => HasWitherableBlockTags x where
- witherBlockTags :: Monad f => (Tag (Annotation x) -> f (Maybe (Tag (Annotation x)))) -> x -> f x
- mapMaybeBlockTags :: (Tag (Annotation x) -> Maybe (Tag (Annotation x))) -> x -> x
- class HasManyParagraphs x where
- allParagraphs :: Traversal' x (Paragraph (Annotation x))
- class CanBeTagless a where
- tagless :: KindOfText txt -> AffineFold a txt
- class CanHaveTaglessContent a where
- taglessContent :: KindOfText t -> AffineFold a t
- data KindOfText txt where
- TextLine :: KindOfText Text
- TextStanza :: KindOfText (Seq Text)
- TextParagraphs :: KindOfText (Seq (Seq Text))
Block and inline choices
class CanBePlain x where Source #
Instances
CanBePlain (Inline ann) Source # | |
CanBePlain (Block ann) Source # | |
CanBePlain (BlockTagContent ann) Source # | |
Defined in ProAbstract.Structure.BlockTagContent plain :: Prism' (BlockTagContent ann) (Plain (BlockTagContent ann)) Source # | |
CanBePlain (BlockTag ann) Source # | |
class IsTaggedOrBare a where Source #
taggedOrBare :: Iso' a (TaggedOrBare a) Source #
Instances
IsTaggedOrBare (Inline ann) Source # | |
Defined in ProAbstract.Structure.IsTaggedOrBare taggedOrBare :: Iso' (Inline ann) (TaggedOrBare (Inline ann)) Source # | |
IsTaggedOrBare (Block ann) Source # | |
Defined in ProAbstract.Structure.IsTaggedOrBare taggedOrBare :: Iso' (Block ann) (TaggedOrBare (Block ann)) Source # | |
IsTaggedOrBare (TaggedOrBare a) Source # | |
Defined in ProAbstract.Structure.IsTaggedOrBare type TaggedType (TaggedOrBare a) Source # type BareType (TaggedOrBare a) Source # taggedOrBare :: Iso' (TaggedOrBare a) (TaggedOrBare (TaggedOrBare a)) Source # |
Plaintext traversals
class HasManyPlainBlocks x where Source #
allPlainBlocks :: Traversal' x (TaggedPlainBlock (Annotation x)) Source #
Instances
class HasManyPlainInlines x where Source #
allPlainInlines :: Traversal' x (Fragment (Annotation x)) Source #
Instances
Annotation
class HasAnnotation x x' where Source #
annotation :: Lens x x' (Annotation x) (Annotation x') Source #
Instances
type HasAnnotation' x = HasAnnotation x x Source #
class HasManyAnnotations x x' where Source #
allAnnotations :: Traversal x x' (Annotation x) (Annotation x') Source #
Instances
Content
class HasContent x x' where Source #
Instances
HasContent (Fragment ann) (Fragment ann) Source # | |
HasContent (TaggedPlainBlock ann) (TaggedPlainBlock ann) Source # | |
Defined in ProAbstract.Structure.PlainBlock content :: Lens (TaggedPlainBlock ann) (TaggedPlainBlock ann) (Content (TaggedPlainBlock ann)) (Content (TaggedPlainBlock ann)) Source # | |
HasContent (TaggedLines ann) (TaggedLines ann) Source # | |
Defined in ProAbstract.Structure.Inline content :: Lens (TaggedLines ann) (TaggedLines ann) (Content (TaggedLines ann)) (Content (TaggedLines ann)) Source # | |
HasContent (Paragraph ann) (Paragraph ann) Source # | |
HasContent (TaggedBlocks ann) (TaggedBlocks ann) Source # | |
Defined in ProAbstract.Structure.Block content :: Lens (TaggedBlocks ann) (TaggedBlocks ann) (Content (TaggedBlocks ann)) (Content (TaggedBlocks ann)) Source # | |
HasContent (Document ann) (Document ann') Source # | |
HasContent (BlockTag ann) (BlockTag ann) Source # | |
type HasContent' x = HasContent x x Source #
class HasContents x x' where Source #
Instances
type HasContents' x = HasContents x x Source #
Metadata
class HasMetadata x where Source #
type MetadataOpticKind x Source #
Instances
class HasManyMetadata x where Source #
allMetadata :: Traversal' x Metadata Source #
Instances
Tags
type TagOpticKind x :: OpticKind Source #
tag :: Optic' (TagOpticKind x) NoIx x (Tag (Annotation x)) Source #
Instances
Traversal
class HasManyTags x where Source #
allTags :: Traversal' x (Tag (Annotation x)) Source #
allInlineTags :: Traversal' x (Tag (Annotation x)) Source #
Instances
class HasManyTags x => HasManyBlockTags x where Source #
allBlockTags :: Traversal' x (Tag (Annotation x)) Source #
Instances
HasManyBlockTags (TaggedBlocks ann) Source # | |
Defined in ProAbstract.Structure.Block allBlockTags :: Traversal' (TaggedBlocks ann) (Tag (Annotation (TaggedBlocks ann))) Source # | |
HasManyBlockTags (Blocks ann) Source # | |
Defined in ProAbstract.Structure.Block allBlockTags :: Traversal' (Blocks ann) (Tag (Annotation (Blocks ann))) Source # | |
HasManyBlockTags (Block ann) Source # | |
Defined in ProAbstract.Structure.Block allBlockTags :: Traversal' (Block ann) (Tag (Annotation (Block ann))) Source # | |
HasManyBlockTags (Document ann) Source # | |
Defined in ProAbstract.Structure.Document allBlockTags :: Traversal' (Document ann) (Tag (Annotation (Document ann))) Source # | |
HasManyBlockTags (BlockTagContent ann) Source # | |
Defined in ProAbstract.Structure.BlockTagContent allBlockTags :: Traversal' (BlockTagContent ann) (Tag (Annotation (BlockTagContent ann))) Source # |
Withering
class HasWitherableTags x where Source #
witherTags :: Monad f => (Tag (Annotation x) -> f (Maybe (Tag (Annotation x)))) -> x -> f x Source #
mapMaybeTags :: (Tag (Annotation x) -> Maybe (Tag (Annotation x))) -> x -> x Source #
Instances
class HasManyTags x => HasWitherableInlineTags x where Source #
witherInlineTags :: Monad f => (Tag (Annotation x) -> f (Maybe (Tag (Annotation x)))) -> x -> f x Source #
mapMaybeInlineTags :: (Tag (Annotation x) -> Maybe (Tag (Annotation x))) -> x -> x Source #
Instances
class HasManyBlockTags x => HasWitherableBlockTags x where Source #
witherBlockTags :: Monad f => (Tag (Annotation x) -> f (Maybe (Tag (Annotation x)))) -> x -> f x Source #
mapMaybeBlockTags :: (Tag (Annotation x) -> Maybe (Tag (Annotation x))) -> x -> x Source #
Instances
Paragraphs
class HasManyParagraphs x where Source #
allParagraphs :: Traversal' x (Paragraph (Annotation x)) Source #
Instances
Getting text from tagless content
class CanBeTagless a where Source #
tagless :: KindOfText txt -> AffineFold a txt Source #
Instances
class CanHaveTaglessContent a where Source #
taglessContent :: KindOfText t -> AffineFold a t Source #
Instances
data KindOfText txt where Source #
TextLine :: KindOfText Text | |
TextStanza :: KindOfText (Seq Text) | |
TextParagraphs :: KindOfText (Seq (Seq Text)) |