pro-abstract-0.3.0.0: Abstract syntax for writing documents
Safe HaskellNone
LanguageHaskell2010

ProAbstract.Tag

Documentation

data Tag ann Source #

Instances

Instances details
Eq ann => Eq (Tag ann) Source # 
Instance details

Defined in ProAbstract.Tag.TagType

Methods

(==) :: Tag ann -> Tag ann -> Bool #

(/=) :: Tag ann -> Tag ann -> Bool #

Show ann => Show (Tag ann) Source # 
Instance details

Defined in ProAbstract.Tag.TagType

Methods

showsPrec :: Int -> Tag ann -> ShowS #

show :: Tag ann -> String #

showList :: [Tag ann] -> ShowS #

Generic (Tag ann) Source # 
Instance details

Defined in ProAbstract.Tag.TagType

Associated Types

type Rep (Tag ann) :: Type -> Type #

Methods

from :: Tag ann -> Rep (Tag ann) x #

to :: Rep (Tag ann) x -> Tag ann #

NFData ann => NFData (Tag ann) Source # 
Instance details

Defined in ProAbstract.Tag.TagType

Methods

rnf :: Tag ann -> () #

Hashable ann => Hashable (Tag ann) Source # 
Instance details

Defined in ProAbstract.Tag.TagType

Methods

hashWithSalt :: Int -> Tag ann -> Int #

hash :: Tag ann -> Int #

HasMetadata (Tag ann) Source # 
Instance details

Defined in ProAbstract.Tag.TagType

Associated Types

type MetadataOpticKind (Tag ann) Source #

HasTag (Tag ann) Source # 
Instance details

Defined in ProAbstract.Tag.HasTag

Associated Types

type TagOpticKind (Tag ann) Source #

Methods

tag :: Optic' (TagOpticKind (Tag ann)) NoIx (Tag ann) (Tag (Annotation (Tag ann))) Source #

HasAnnotation (Tag ann) (Tag ann') Source # 
Instance details

Defined in ProAbstract.Tag.TagType

Methods

annotation :: Lens (Tag ann) (Tag ann') (Annotation (Tag ann)) (Annotation (Tag ann')) Source #

type Rep (Tag ann) Source # 
Instance details

Defined in ProAbstract.Tag.TagType

type Rep (Tag ann) = D1 ('MetaData "Tag" "ProAbstract.Tag.TagType" "pro-abstract-0.3.0.0-CFjEApBZPUR1EoNCheWNFg" 'False) (C1 ('MetaCons "Tag" 'PrefixI 'True) (S1 ('MetaSel ('Just "tagName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "tagMetadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Metadata) :*: S1 ('MetaSel ('Just "tagAnnotation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ann))))
type Annotation (Tag ann) Source # 
Instance details

Defined in ProAbstract.Tag.TagType

type Annotation (Tag ann) = ann
type MetadataOpticKind (Tag ann) Source # 
Instance details

Defined in ProAbstract.Tag.TagType

type TagOpticKind (Tag ann) Source # 
Instance details

Defined in ProAbstract.Tag.HasTag

type TagOpticKind (Tag ann) = A_Lens

class HasTag x where Source #

Associated Types

type TagOpticKind x :: OpticKind Source #

Instances

Instances details
HasTag (Tag ann) Source # 
Instance details

Defined in ProAbstract.Tag.HasTag

Associated Types

type TagOpticKind (Tag ann) Source #

Methods

tag :: Optic' (TagOpticKind (Tag ann)) NoIx (Tag ann) (Tag (Annotation (Tag ann))) Source #

HasTag (TaggedPlainBlock ann) Source # 
Instance details

Defined in ProAbstract.Structure.PlainBlock

Associated Types

type TagOpticKind (TaggedPlainBlock ann) Source #

HasTag (TaggedLines ann) Source # 
Instance details

Defined in ProAbstract.Structure.Inline

Associated Types

type TagOpticKind (TaggedLines ann) Source #

HasTag (Inline ann) Source # 
Instance details

Defined in ProAbstract.Structure.Inline

Associated Types

type TagOpticKind (Inline ann) Source #

Methods

tag :: Optic' (TagOpticKind (Inline ann)) NoIx (Inline ann) (Tag (Annotation (Inline ann))) Source #

HasTag (TaggedBlocks ann) Source # 
Instance details

Defined in ProAbstract.Structure.Block

Associated Types

type TagOpticKind (TaggedBlocks ann) Source #

HasTag (Block ann) Source # 
Instance details

Defined in ProAbstract.Structure.Block

Associated Types

type TagOpticKind (Block ann) Source #

Methods

tag :: Optic' (TagOpticKind (Block ann)) NoIx (Block ann) (Tag (Annotation (Block ann))) Source #

HasTag (BlockTag ann) Source # 
Instance details

Defined in ProAbstract.Structure.BlockTag

Associated Types

type TagOpticKind (BlockTag ann) Source #

class HasManyTags x where Source #

Instances

Instances details
HasManyTags (TaggedLines ann) Source # 
Instance details

Defined in ProAbstract.Structure.Inline

HasManyTags (Lines ann) Source # 
Instance details

Defined in ProAbstract.Structure.Inline

HasManyTags (Line ann) Source # 
Instance details

Defined in ProAbstract.Structure.Inline

HasManyTags (Inline ann) Source # 
Instance details

Defined in ProAbstract.Structure.Inline

HasManyTags (Paragraph ann) Source # 
Instance details

Defined in ProAbstract.Structure.Paragraph

HasManyTags (TaggedBlocks ann) Source # 
Instance details

Defined in ProAbstract.Structure.Block

HasManyTags (Blocks ann) Source # 
Instance details

Defined in ProAbstract.Structure.Block

HasManyTags (Block ann) Source # 
Instance details

Defined in ProAbstract.Structure.Block

HasManyTags (Document ann) Source # 
Instance details

Defined in ProAbstract.Structure.Document

HasManyTags (BlockTagContent ann) Source # 
Instance details

Defined in ProAbstract.Structure.BlockTagContent

HasManyTags (BlockTag ann) Source # 
Instance details

Defined in ProAbstract.Structure.BlockTag

class HasWitherableTags x where Source #

Minimal complete definition

witherTags

Methods

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

Instances details
HasWitherableTags (Lines ann) Source # 
Instance details

Defined in ProAbstract.Structure.Inline

Methods

witherTags :: Monad f => (Tag (Annotation (Lines ann)) -> f (Maybe (Tag (Annotation (Lines ann))))) -> Lines ann -> f (Lines ann) Source #

mapMaybeTags :: (Tag (Annotation (Lines ann)) -> Maybe (Tag (Annotation (Lines ann)))) -> Lines ann -> Lines ann Source #

HasWitherableTags (Line ann) Source # 
Instance details

Defined in ProAbstract.Structure.Inline

Methods

witherTags :: Monad f => (Tag (Annotation (Line ann)) -> f (Maybe (Tag (Annotation (Line ann))))) -> Line ann -> f (Line ann) Source #

mapMaybeTags :: (Tag (Annotation (Line ann)) -> Maybe (Tag (Annotation (Line ann)))) -> Line ann -> Line ann Source #

HasWitherableTags (Blocks ann) Source # 
Instance details

Defined in ProAbstract.Structure.Block

Methods

witherTags :: Monad f => (Tag (Annotation (Blocks ann)) -> f (Maybe (Tag (Annotation (Blocks ann))))) -> Blocks ann -> f (Blocks ann) Source #

mapMaybeTags :: (Tag (Annotation (Blocks ann)) -> Maybe (Tag (Annotation (Blocks ann)))) -> Blocks ann -> Blocks ann Source #

HasWitherableTags (Document ann) Source # 
Instance details

Defined in ProAbstract.Structure.Document

Methods

witherTags :: Monad f => (Tag (Annotation (Document ann)) -> f (Maybe (Tag (Annotation (Document ann))))) -> Document ann -> f (Document ann) Source #

mapMaybeTags :: (Tag (Annotation (Document ann)) -> Maybe (Tag (Annotation (Document ann)))) -> Document ann -> Document ann Source #

HasWitherableTags (BlockTagContent ann) Source # 
Instance details

Defined in ProAbstract.Structure.BlockTagContent

class HasManyBlockTags x => HasWitherableBlockTags x where Source #

Minimal complete definition

witherBlockTags

Methods

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 #

class HasManyTags x => HasWitherableInlineTags x where Source #

Minimal complete definition

witherInlineTags

Methods

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

Instances details
HasWitherableInlineTags (TaggedLines ann) Source # 
Instance details

Defined in ProAbstract.Structure.Inline

HasWitherableInlineTags (Lines ann) Source # 
Instance details

Defined in ProAbstract.Structure.Inline

Methods

witherInlineTags :: Monad f => (Tag (Annotation (Lines ann)) -> f (Maybe (Tag (Annotation (Lines ann))))) -> Lines ann -> f (Lines ann) Source #

mapMaybeInlineTags :: (Tag (Annotation (Lines ann)) -> Maybe (Tag (Annotation (Lines ann)))) -> Lines ann -> Lines ann Source #

HasWitherableInlineTags (Line ann) Source # 
Instance details

Defined in ProAbstract.Structure.Inline

Methods

witherInlineTags :: Monad f => (Tag (Annotation (Line ann)) -> f (Maybe (Tag (Annotation (Line ann))))) -> Line ann -> f (Line ann) Source #

mapMaybeInlineTags :: (Tag (Annotation (Line ann)) -> Maybe (Tag (Annotation (Line ann)))) -> Line ann -> Line ann Source #

HasWitherableInlineTags (Paragraph ann) Source # 
Instance details

Defined in ProAbstract.Structure.Paragraph

HasWitherableInlineTags (TaggedBlocks ann) Source # 
Instance details

Defined in ProAbstract.Structure.Block

HasWitherableInlineTags (Blocks ann) Source # 
Instance details

Defined in ProAbstract.Structure.Block

Methods

witherInlineTags :: Monad f => (Tag (Annotation (Blocks ann)) -> f (Maybe (Tag (Annotation (Blocks ann))))) -> Blocks ann -> f (Blocks ann) Source #

mapMaybeInlineTags :: (Tag (Annotation (Blocks ann)) -> Maybe (Tag (Annotation (Blocks ann)))) -> Blocks ann -> Blocks ann Source #

HasWitherableInlineTags (Block ann) Source # 
Instance details

Defined in ProAbstract.Structure.Block

Methods

witherInlineTags :: Monad f => (Tag (Annotation (Block ann)) -> f (Maybe (Tag (Annotation (Block ann))))) -> Block ann -> f (Block ann) Source #

mapMaybeInlineTags :: (Tag (Annotation (Block ann)) -> Maybe (Tag (Annotation (Block ann)))) -> Block ann -> Block ann Source #

HasWitherableInlineTags (Document ann) Source # 
Instance details

Defined in ProAbstract.Structure.Document

Methods

witherInlineTags :: Monad f => (Tag (Annotation (Document ann)) -> f (Maybe (Tag (Annotation (Document ann))))) -> Document ann -> f (Document ann) Source #

mapMaybeInlineTags :: (Tag (Annotation (Document ann)) -> Maybe (Tag (Annotation (Document ann)))) -> Document ann -> Document ann Source #

HasWitherableInlineTags (BlockTagContent ann) Source # 
Instance details

Defined in ProAbstract.Structure.BlockTagContent