org-parser-0.1.0.0: Parser for Org Mode documents.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Org.Types

Synopsis

Document

data OrgDocument Source #

Instances

Instances details
Generic OrgDocument Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep OrgDocument :: Type -> Type Source #

Read OrgDocument Source # 
Instance details

Defined in Org.Types

Show OrgDocument Source # 
Instance details

Defined in Org.Types

NFData OrgDocument Source # 
Instance details

Defined in Org.Types

Methods

rnf :: OrgDocument -> () Source #

Eq OrgDocument Source # 
Instance details

Defined in Org.Types

Ord OrgDocument Source # 
Instance details

Defined in Org.Types

MultiSub MWTag OrgDocument 
Instance details

Defined in Org.Walk

Associated Types

type SubTypes MWTag OrgDocument :: Spec

type HasSubTag MWTag OrgDocument

type Rep OrgDocument Source # 
Instance details

Defined in Org.Types

type Rep OrgDocument = D1 ('MetaData "OrgDocument" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "OrgDocument" 'PrefixI 'True) (S1 ('MetaSel ('Just "documentProperties") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Properties) :*: (S1 ('MetaSel ('Just "documentChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgElement]) :*: S1 ('MetaSel ('Just "documentSections") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgSection]))))
type HasSubTag MWTag OrgDocument 
Instance details

Defined in Org.Walk

type HasSubTag MWTag OrgDocument = GSubTag
type SubTypes MWTag OrgDocument 
Instance details

Defined in Org.Walk

type SubTypes MWTag OrgDocument = 'SpecList '[ToSpec (List OrgElement), ToSpec (List OrgSection)]

Helpers

Sections

data OrgSection Source #

Constructors

OrgSection 

Fields

Instances

Instances details
Data OrgSection Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrgSection -> c OrgSection Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrgSection Source #

toConstr :: OrgSection -> Constr Source #

dataTypeOf :: OrgSection -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OrgSection) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrgSection) Source #

gmapT :: (forall b. Data b => b -> b) -> OrgSection -> OrgSection Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrgSection -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrgSection -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> OrgSection -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrgSection -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrgSection -> m OrgSection Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrgSection -> m OrgSection Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrgSection -> m OrgSection Source #

Generic OrgSection Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep OrgSection :: Type -> Type Source #

Read OrgSection Source # 
Instance details

Defined in Org.Types

Show OrgSection Source # 
Instance details

Defined in Org.Types

NFData OrgSection Source # 
Instance details

Defined in Org.Types

Methods

rnf :: OrgSection -> () Source #

Eq OrgSection Source # 
Instance details

Defined in Org.Types

Ord OrgSection Source # 
Instance details

Defined in Org.Types

MultiSub MWTag OrgSection 
Instance details

Defined in Org.Walk

Associated Types

type SubTypes MWTag OrgSection :: Spec

type HasSubTag MWTag OrgSection

type Rep OrgSection Source # 
Instance details

Defined in Org.Types

type Rep OrgSection = D1 ('MetaData "OrgSection" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "OrgSection" 'PrefixI 'True) (((S1 ('MetaSel ('Just "sectionLevel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "sectionProperties") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Properties) :*: S1 ('MetaSel ('Just "sectionTodo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TodoKeyword)))) :*: (S1 ('MetaSel ('Just "sectionIsComment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "sectionPriority") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Priority)) :*: S1 ('MetaSel ('Just "sectionTitle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgObject])))) :*: ((S1 ('MetaSel ('Just "sectionRawTitle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "sectionAnchor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Id) :*: S1 ('MetaSel ('Just "sectionTags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag]))) :*: (S1 ('MetaSel ('Just "sectionPlanning") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PlanningInfo) :*: (S1 ('MetaSel ('Just "sectionChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgElement]) :*: S1 ('MetaSel ('Just "sectionSubsections") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgSection]))))))
type HasSubTag MWTag OrgSection 
Instance details

Defined in Org.Walk

type HasSubTag MWTag OrgSection = GSubTag
type SubTypes MWTag OrgSection 
Instance details

Defined in Org.Walk

type SubTypes MWTag OrgSection = 'SpecList '[ToSpec (List OrgObject), ToSpec (List OrgElement), ToSpec (List OrgSection)]

data TodoKeyword Source #

A to-do keyword like TODO or DONE.

Constructors

TodoKeyword 

Instances

Instances details
FromJSON TodoKeyword Source # 
Instance details

Defined in Org.Types

ToJSON TodoKeyword Source # 
Instance details

Defined in Org.Types

Data TodoKeyword Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TodoKeyword -> c TodoKeyword Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TodoKeyword Source #

toConstr :: TodoKeyword -> Constr Source #

dataTypeOf :: TodoKeyword -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TodoKeyword) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TodoKeyword) Source #

gmapT :: (forall b. Data b => b -> b) -> TodoKeyword -> TodoKeyword Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TodoKeyword -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TodoKeyword -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TodoKeyword -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TodoKeyword -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TodoKeyword -> m TodoKeyword Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TodoKeyword -> m TodoKeyword Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TodoKeyword -> m TodoKeyword Source #

Generic TodoKeyword Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep TodoKeyword :: Type -> Type Source #

Read TodoKeyword Source # 
Instance details

Defined in Org.Types

Show TodoKeyword Source # 
Instance details

Defined in Org.Types

NFData TodoKeyword Source # 
Instance details

Defined in Org.Types

Methods

rnf :: TodoKeyword -> () Source #

Eq TodoKeyword Source # 
Instance details

Defined in Org.Types

Ord TodoKeyword Source # 
Instance details

Defined in Org.Types

type Rep TodoKeyword Source # 
Instance details

Defined in Org.Types

type Rep TodoKeyword = D1 ('MetaData "TodoKeyword" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "TodoKeyword" 'PrefixI 'True) (S1 ('MetaSel ('Just "todoState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TodoState) :*: S1 ('MetaSel ('Just "todoName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data TodoState Source #

The states in which a todo item can be

Constructors

Todo 
Done 

Instances

Instances details
FromJSON TodoState Source # 
Instance details

Defined in Org.Types

ToJSON TodoState Source # 
Instance details

Defined in Org.Types

Data TodoState Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TodoState -> c TodoState Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TodoState Source #

toConstr :: TodoState -> Constr Source #

dataTypeOf :: TodoState -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TodoState) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TodoState) Source #

gmapT :: (forall b. Data b => b -> b) -> TodoState -> TodoState Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TodoState -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TodoState -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TodoState -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TodoState -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TodoState -> m TodoState Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TodoState -> m TodoState Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TodoState -> m TodoState Source #

Generic TodoState Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep TodoState :: Type -> Type Source #

Read TodoState Source # 
Instance details

Defined in Org.Types

Show TodoState Source # 
Instance details

Defined in Org.Types

NFData TodoState Source # 
Instance details

Defined in Org.Types

Methods

rnf :: TodoState -> () Source #

Eq TodoState Source # 
Instance details

Defined in Org.Types

Ord TodoState Source # 
Instance details

Defined in Org.Types

type Rep TodoState Source # 
Instance details

Defined in Org.Types

type Rep TodoState = D1 ('MetaData "TodoState" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "Todo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Done" 'PrefixI 'False) (U1 :: Type -> Type))

type Tag = Text Source #

data Priority Source #

Instances

Instances details
Data Priority Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Priority -> c Priority Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Priority Source #

toConstr :: Priority -> Constr Source #

dataTypeOf :: Priority -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Priority) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Priority) Source #

gmapT :: (forall b. Data b => b -> b) -> Priority -> Priority Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Priority -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Priority -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Priority -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Priority -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Priority -> m Priority Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Priority -> m Priority Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Priority -> m Priority Source #

Generic Priority Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep Priority :: Type -> Type Source #

Read Priority Source # 
Instance details

Defined in Org.Types

Show Priority Source # 
Instance details

Defined in Org.Types

NFData Priority Source # 
Instance details

Defined in Org.Types

Methods

rnf :: Priority -> () Source #

Eq Priority Source # 
Instance details

Defined in Org.Types

Ord Priority Source # 
Instance details

Defined in Org.Types

type Rep Priority Source # 
Instance details

Defined in Org.Types

type Rep Priority = D1 ('MetaData "Priority" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "LetterPriority" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char)) :+: C1 ('MetaCons "NumericPriority" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data PlanningInfo Source #

Planning information for a subtree/headline.

Instances

Instances details
Data PlanningInfo Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlanningInfo -> c PlanningInfo Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlanningInfo Source #

toConstr :: PlanningInfo -> Constr Source #

dataTypeOf :: PlanningInfo -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PlanningInfo) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlanningInfo) Source #

gmapT :: (forall b. Data b => b -> b) -> PlanningInfo -> PlanningInfo Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlanningInfo -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlanningInfo -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> PlanningInfo -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlanningInfo -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlanningInfo -> m PlanningInfo Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlanningInfo -> m PlanningInfo Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlanningInfo -> m PlanningInfo Source #

Generic PlanningInfo Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep PlanningInfo :: Type -> Type Source #

Read PlanningInfo Source # 
Instance details

Defined in Org.Types

Show PlanningInfo Source # 
Instance details

Defined in Org.Types

NFData PlanningInfo Source # 
Instance details

Defined in Org.Types

Methods

rnf :: PlanningInfo -> () Source #

Eq PlanningInfo Source # 
Instance details

Defined in Org.Types

Ord PlanningInfo Source # 
Instance details

Defined in Org.Types

type Rep PlanningInfo Source # 
Instance details

Defined in Org.Types

type Rep PlanningInfo = D1 ('MetaData "PlanningInfo" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "PlanningInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "planningClosed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TimestampData)) :*: (S1 ('MetaSel ('Just "planningDeadline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TimestampData)) :*: S1 ('MetaSel ('Just "planningScheduled") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TimestampData)))))

Helpers

OrgContent

Elements

data OrgElement Source #

Org element. Like a Pandoc Block.

Instances

Instances details
Data OrgElement Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrgElement -> c OrgElement Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrgElement Source #

toConstr :: OrgElement -> Constr Source #

dataTypeOf :: OrgElement -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OrgElement) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrgElement) Source #

gmapT :: (forall b. Data b => b -> b) -> OrgElement -> OrgElement Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrgElement -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrgElement -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> OrgElement -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrgElement -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrgElement -> m OrgElement Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrgElement -> m OrgElement Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrgElement -> m OrgElement Source #

IsString OrgElements Source # 
Instance details

Defined in Org.Builder

Monoid OrgElements Source # 
Instance details

Defined in Org.Builder

Semigroup OrgElements Source # 
Instance details

Defined in Org.Builder

Generic OrgElement Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep OrgElement :: Type -> Type Source #

Read OrgElement Source # 
Instance details

Defined in Org.Types

Show OrgElement Source # 
Instance details

Defined in Org.Types

NFData OrgElement Source # 
Instance details

Defined in Org.Types

Methods

rnf :: OrgElement -> () Source #

Eq OrgElement Source # 
Instance details

Defined in Org.Types

Ord OrgElement Source # 
Instance details

Defined in Org.Types

MultiSub MWTag OrgElement 
Instance details

Defined in Org.Walk

Associated Types

type SubTypes MWTag OrgElement :: Spec

type HasSubTag MWTag OrgElement

type Rep OrgElement Source # 
Instance details

Defined in Org.Types

type Rep OrgElement = D1 ('MetaData "OrgElement" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "OrgElement" 'PrefixI 'True) (S1 ('MetaSel ('Just "affiliatedKeywords") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Keywords) :*: S1 ('MetaSel ('Just "elementData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OrgElementData)))
type HasSubTag MWTag OrgElement 
Instance details

Defined in Org.Walk

type HasSubTag MWTag OrgElement = GSubTag
type SubTypes MWTag OrgElement 
Instance details

Defined in Org.Walk

type SubTypes MWTag OrgElement = 'SpecList '[ToSpec OrgElementData, ToSpec (Trav (Map Text) (Under KeywordValue 'NoSel (List OrgObject)))]

data OrgElementData Source #

Constructors

Clock

Clock

Fields

GreaterBlock

Greater block

Fields

Drawer

Drawer

Fields

PlainList

Plain list

Fields

ExportBlock

Export block

Fields

ExampleBlock

Example block

Fields

SrcBlock

Source blocks

Fields

VerseBlock [[OrgObject]] 
HorizontalRule 
Keyword 
LaTeXEnvironment 

Fields

  • Text

    Environment name

  • Text

    Environment contents

Paragraph [OrgObject] 
Table [TableRow] 
FootnoteDef 

Fields

Comment 

Instances

Instances details
Data OrgElementData Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrgElementData -> c OrgElementData Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrgElementData Source #

toConstr :: OrgElementData -> Constr Source #

dataTypeOf :: OrgElementData -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OrgElementData) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrgElementData) Source #

gmapT :: (forall b. Data b => b -> b) -> OrgElementData -> OrgElementData Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrgElementData -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrgElementData -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> OrgElementData -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrgElementData -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrgElementData -> m OrgElementData Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrgElementData -> m OrgElementData Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrgElementData -> m OrgElementData Source #

Generic OrgElementData Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep OrgElementData :: Type -> Type Source #

Read OrgElementData Source # 
Instance details

Defined in Org.Types

Show OrgElementData Source # 
Instance details

Defined in Org.Types

NFData OrgElementData Source # 
Instance details

Defined in Org.Types

Methods

rnf :: OrgElementData -> () Source #

Eq OrgElementData Source # 
Instance details

Defined in Org.Types

Ord OrgElementData Source # 
Instance details

Defined in Org.Types

MultiSub MWTag OrgElementData 
Instance details

Defined in Org.Walk

Associated Types

type SubTypes MWTag OrgElementData :: Spec

type HasSubTag MWTag OrgElementData

type Rep OrgElementData Source # 
Instance details

Defined in Org.Types

type Rep OrgElementData = D1 ('MetaData "OrgElementData" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (((C1 ('MetaCons "Clock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimestampData) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Time))) :+: (C1 ('MetaCons "GreaterBlock" 'PrefixI 'True) (S1 ('MetaSel ('Just "blkType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GreaterBlockType) :*: S1 ('MetaSel ('Just "blkElements") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgElement])) :+: C1 ('MetaCons "Drawer" 'PrefixI 'True) (S1 ('MetaSel ('Just "drawerName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "drawerElements") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgElement])))) :+: ((C1 ('MetaCons "PlainList" 'PrefixI 'True) (S1 ('MetaSel ('Just "listType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ListType) :*: S1 ('MetaSel ('Just "listItems") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ListItem])) :+: C1 ('MetaCons "ExportBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :+: (C1 ('MetaCons "ExampleBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text Text)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SrcLine])) :+: C1 ('MetaCons "SrcBlock" 'PrefixI 'True) ((S1 ('MetaSel ('Just "srcBlkLang") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "srcBlkSwitches") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text Text))) :*: (S1 ('MetaSel ('Just "srcBlkArguments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Text, Text)]) :*: S1 ('MetaSel ('Just "srcBlkLines") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SrcLine])))))) :+: (((C1 ('MetaCons "VerseBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [[OrgObject]])) :+: C1 ('MetaCons "HorizontalRule" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Keyword" 'PrefixI 'True) (S1 ('MetaSel ('Just "keywordKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "keywordValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KeywordValue)) :+: C1 ('MetaCons "LaTeXEnvironment" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) :+: ((C1 ('MetaCons "Paragraph" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgObject])) :+: C1 ('MetaCons "Table" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TableRow]))) :+: (C1 ('MetaCons "FootnoteDef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgElement])) :+: C1 ('MetaCons "Comment" 'PrefixI 'False) (U1 :: Type -> Type)))))
type HasSubTag MWTag OrgElementData 
Instance details

Defined in Org.Walk

type HasSubTag MWTag OrgElementData = GSubTag
type SubTypes MWTag OrgElementData 
Instance details

Defined in Org.Walk

type SubTypes MWTag OrgElementData = 'SpecList '[ToSpec (List OrgElement), ToSpec (List OrgObject), ToSpec (Under KeywordValue 'NoSel (List OrgObject)), ToSpec (List ListItem), ToSpec (List (Under TableRow 'NoSel (DoubleList OrgObject))), ToSpec (DoubleList OrgObject)]

Greater blocks

data GreaterBlockType Source #

Constructors

Center 
Quote 
Special Text 

Instances

Instances details
Data GreaterBlockType Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GreaterBlockType -> c GreaterBlockType Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GreaterBlockType Source #

toConstr :: GreaterBlockType -> Constr Source #

dataTypeOf :: GreaterBlockType -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GreaterBlockType) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GreaterBlockType) Source #

gmapT :: (forall b. Data b => b -> b) -> GreaterBlockType -> GreaterBlockType Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GreaterBlockType -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GreaterBlockType -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GreaterBlockType -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GreaterBlockType -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GreaterBlockType -> m GreaterBlockType Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GreaterBlockType -> m GreaterBlockType Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GreaterBlockType -> m GreaterBlockType Source #

Generic GreaterBlockType Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep GreaterBlockType :: Type -> Type Source #

Read GreaterBlockType Source # 
Instance details

Defined in Org.Types

Show GreaterBlockType Source # 
Instance details

Defined in Org.Types

NFData GreaterBlockType Source # 
Instance details

Defined in Org.Types

Methods

rnf :: GreaterBlockType -> () Source #

Eq GreaterBlockType Source # 
Instance details

Defined in Org.Types

Ord GreaterBlockType Source # 
Instance details

Defined in Org.Types

type Rep GreaterBlockType Source # 
Instance details

Defined in Org.Types

type Rep GreaterBlockType = D1 ('MetaData "GreaterBlockType" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "Center" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Quote" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Special" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

Source blocks

data SrcLine Source #

Constructors

SrcLine Text 
RefLine 

Fields

  • Id

    Reference id (its anchor)

  • Text

    Reference name (how it appears)

  • Text

    Line contents

Instances

Instances details
Data SrcLine Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcLine -> c SrcLine Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcLine Source #

toConstr :: SrcLine -> Constr Source #

dataTypeOf :: SrcLine -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcLine) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcLine) Source #

gmapT :: (forall b. Data b => b -> b) -> SrcLine -> SrcLine Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcLine -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcLine -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> SrcLine -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcLine -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcLine -> m SrcLine Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcLine -> m SrcLine Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcLine -> m SrcLine Source #

Generic SrcLine Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep SrcLine :: Type -> Type Source #

Read SrcLine Source # 
Instance details

Defined in Org.Types

Show SrcLine Source # 
Instance details

Defined in Org.Types

NFData SrcLine Source # 
Instance details

Defined in Org.Types

Methods

rnf :: SrcLine -> () Source #

Eq SrcLine Source # 
Instance details

Defined in Org.Types

Ord SrcLine Source # 
Instance details

Defined in Org.Types

type Rep SrcLine Source # 
Instance details

Defined in Org.Types

Lists

data ListType Source #

Instances

Instances details
Data ListType Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ListType -> c ListType Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ListType Source #

toConstr :: ListType -> Constr Source #

dataTypeOf :: ListType -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ListType) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListType) Source #

gmapT :: (forall b. Data b => b -> b) -> ListType -> ListType Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ListType -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ListType -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ListType -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ListType -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ListType -> m ListType Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ListType -> m ListType Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ListType -> m ListType Source #

Generic ListType Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep ListType :: Type -> Type Source #

Read ListType Source # 
Instance details

Defined in Org.Types

Show ListType Source # 
Instance details

Defined in Org.Types

NFData ListType Source # 
Instance details

Defined in Org.Types

Methods

rnf :: ListType -> () Source #

Eq ListType Source # 
Instance details

Defined in Org.Types

Ord ListType Source # 
Instance details

Defined in Org.Types

type Rep ListType Source # 
Instance details

Defined in Org.Types

type Rep ListType = D1 ('MetaData "ListType" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "Ordered" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OrderedStyle)) :+: (C1 ('MetaCons "Descriptive" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unordered" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char))))

data OrderedStyle Source #

Constructors

OrderedNum 
OrderedAlpha 

Instances

Instances details
Data OrderedStyle Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderedStyle -> c OrderedStyle Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrderedStyle Source #

toConstr :: OrderedStyle -> Constr Source #

dataTypeOf :: OrderedStyle -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OrderedStyle) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrderedStyle) Source #

gmapT :: (forall b. Data b => b -> b) -> OrderedStyle -> OrderedStyle Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderedStyle -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderedStyle -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> OrderedStyle -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderedStyle -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderedStyle -> m OrderedStyle Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderedStyle -> m OrderedStyle Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderedStyle -> m OrderedStyle Source #

Generic OrderedStyle Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep OrderedStyle :: Type -> Type Source #

Read OrderedStyle Source # 
Instance details

Defined in Org.Types

Show OrderedStyle Source # 
Instance details

Defined in Org.Types

NFData OrderedStyle Source # 
Instance details

Defined in Org.Types

Methods

rnf :: OrderedStyle -> () Source #

Eq OrderedStyle Source # 
Instance details

Defined in Org.Types

Ord OrderedStyle Source # 
Instance details

Defined in Org.Types

type Rep OrderedStyle Source # 
Instance details

Defined in Org.Types

type Rep OrderedStyle = D1 ('MetaData "OrderedStyle" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "OrderedNum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OrderedAlpha" 'PrefixI 'False) (U1 :: Type -> Type))

data ListItem Source #

One item of a list. Parameters are bullet, counter cookie, checkbox and tag.

Instances

Instances details
Data ListItem Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ListItem -> c ListItem Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ListItem Source #

toConstr :: ListItem -> Constr Source #

dataTypeOf :: ListItem -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ListItem) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListItem) Source #

gmapT :: (forall b. Data b => b -> b) -> ListItem -> ListItem Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ListItem -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ListItem -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ListItem -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ListItem -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ListItem -> m ListItem Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ListItem -> m ListItem Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ListItem -> m ListItem Source #

Generic ListItem Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep ListItem :: Type -> Type Source #

Read ListItem Source # 
Instance details

Defined in Org.Types

Show ListItem Source # 
Instance details

Defined in Org.Types

NFData ListItem Source # 
Instance details

Defined in Org.Types

Methods

rnf :: ListItem -> () Source #

Eq ListItem Source # 
Instance details

Defined in Org.Types

Ord ListItem Source # 
Instance details

Defined in Org.Types

MultiSub MWTag ListItem 
Instance details

Defined in Org.Walk

Associated Types

type SubTypes MWTag ListItem :: Spec

type HasSubTag MWTag ListItem

type Rep ListItem Source # 
Instance details

Defined in Org.Types

type HasSubTag MWTag ListItem 
Instance details

Defined in Org.Walk

type HasSubTag MWTag ListItem = GSubTag
type SubTypes MWTag ListItem 
Instance details

Defined in Org.Walk

type SubTypes MWTag ListItem = 'SpecList '[ToSpec (List OrgObject), ToSpec (List OrgElement)]

data Bullet Source #

Constructors

Bullet Char 
Counter Text Char 

Instances

Instances details
Data Bullet Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bullet -> c Bullet Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bullet Source #

toConstr :: Bullet -> Constr Source #

dataTypeOf :: Bullet -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bullet) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bullet) Source #

gmapT :: (forall b. Data b => b -> b) -> Bullet -> Bullet Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bullet -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bullet -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Bullet -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Bullet -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bullet -> m Bullet Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bullet -> m Bullet Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bullet -> m Bullet Source #

Generic Bullet Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep Bullet :: Type -> Type Source #

Read Bullet Source # 
Instance details

Defined in Org.Types

Show Bullet Source # 
Instance details

Defined in Org.Types

NFData Bullet Source # 
Instance details

Defined in Org.Types

Methods

rnf :: Bullet -> () Source #

Eq Bullet Source # 
Instance details

Defined in Org.Types

Ord Bullet Source # 
Instance details

Defined in Org.Types

type Rep Bullet Source # 
Instance details

Defined in Org.Types

data Checkbox Source #

Constructors

BoolBox Bool 
PartialBox 

Instances

Instances details
Data Checkbox Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Checkbox -> c Checkbox Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Checkbox Source #

toConstr :: Checkbox -> Constr Source #

dataTypeOf :: Checkbox -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Checkbox) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Checkbox) Source #

gmapT :: (forall b. Data b => b -> b) -> Checkbox -> Checkbox Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Checkbox -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Checkbox -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Checkbox -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Checkbox -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Checkbox -> m Checkbox Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Checkbox -> m Checkbox Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Checkbox -> m Checkbox Source #

Generic Checkbox Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep Checkbox :: Type -> Type Source #

Read Checkbox Source # 
Instance details

Defined in Org.Types

Show Checkbox Source # 
Instance details

Defined in Org.Types

NFData Checkbox Source # 
Instance details

Defined in Org.Types

Methods

rnf :: Checkbox -> () Source #

Eq Checkbox Source # 
Instance details

Defined in Org.Types

Ord Checkbox Source # 
Instance details

Defined in Org.Types

type Rep Checkbox Source # 
Instance details

Defined in Org.Types

type Rep Checkbox = D1 ('MetaData "Checkbox" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "BoolBox" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: C1 ('MetaCons "PartialBox" 'PrefixI 'False) (U1 :: Type -> Type))

Keywords

data KeywordValue Source #

Instances

Instances details
Data KeywordValue Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KeywordValue -> c KeywordValue Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c KeywordValue Source #

toConstr :: KeywordValue -> Constr Source #

dataTypeOf :: KeywordValue -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c KeywordValue) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KeywordValue) Source #

gmapT :: (forall b. Data b => b -> b) -> KeywordValue -> KeywordValue Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KeywordValue -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KeywordValue -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> KeywordValue -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> KeywordValue -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> KeywordValue -> m KeywordValue Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KeywordValue -> m KeywordValue Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KeywordValue -> m KeywordValue Source #

Semigroup KeywordValue Source # 
Instance details

Defined in Org.Types

Generic KeywordValue Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep KeywordValue :: Type -> Type Source #

Read KeywordValue Source # 
Instance details

Defined in Org.Types

Show KeywordValue Source # 
Instance details

Defined in Org.Types

NFData KeywordValue Source # 
Instance details

Defined in Org.Types

Methods

rnf :: KeywordValue -> () Source #

Eq KeywordValue Source # 
Instance details

Defined in Org.Types

Ord KeywordValue Source # 
Instance details

Defined in Org.Types

type Rep KeywordValue Source # 
Instance details

Defined in Org.Types

Tables

data TableRow Source #

Instances

Instances details
Data TableRow Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableRow -> c TableRow Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableRow Source #

toConstr :: TableRow -> Constr Source #

dataTypeOf :: TableRow -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableRow) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableRow) Source #

gmapT :: (forall b. Data b => b -> b) -> TableRow -> TableRow Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableRow -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableRow -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TableRow -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TableRow -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TableRow -> m TableRow Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TableRow -> m TableRow Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TableRow -> m TableRow Source #

Generic TableRow Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep TableRow :: Type -> Type Source #

Read TableRow Source # 
Instance details

Defined in Org.Types

Show TableRow Source # 
Instance details

Defined in Org.Types

NFData TableRow Source # 
Instance details

Defined in Org.Types

Methods

rnf :: TableRow -> () Source #

Eq TableRow Source # 
Instance details

Defined in Org.Types

Ord TableRow Source # 
Instance details

Defined in Org.Types

type Rep TableRow Source # 
Instance details

Defined in Org.Types

type Rep TableRow = D1 ('MetaData "TableRow" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "StandardRow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TableCell])) :+: (C1 ('MetaCons "ColumnPropsRow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Maybe ColumnAlignment])) :+: C1 ('MetaCons "RuleRow" 'PrefixI 'False) (U1 :: Type -> Type)))

data ColumnAlignment Source #

Instances

Instances details
Data ColumnAlignment Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ColumnAlignment -> c ColumnAlignment Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ColumnAlignment Source #

toConstr :: ColumnAlignment -> Constr Source #

dataTypeOf :: ColumnAlignment -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ColumnAlignment) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColumnAlignment) Source #

gmapT :: (forall b. Data b => b -> b) -> ColumnAlignment -> ColumnAlignment Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColumnAlignment -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColumnAlignment -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ColumnAlignment -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ColumnAlignment -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ColumnAlignment -> m ColumnAlignment Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ColumnAlignment -> m ColumnAlignment Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ColumnAlignment -> m ColumnAlignment Source #

Generic ColumnAlignment Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep ColumnAlignment :: Type -> Type Source #

Read ColumnAlignment Source # 
Instance details

Defined in Org.Types

Show ColumnAlignment Source # 
Instance details

Defined in Org.Types

NFData ColumnAlignment Source # 
Instance details

Defined in Org.Types

Methods

rnf :: ColumnAlignment -> () Source #

Eq ColumnAlignment Source # 
Instance details

Defined in Org.Types

Ord ColumnAlignment Source # 
Instance details

Defined in Org.Types

type Rep ColumnAlignment Source # 
Instance details

Defined in Org.Types

type Rep ColumnAlignment = D1 ('MetaData "ColumnAlignment" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "AlignLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AlignCenter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlignRight" 'PrefixI 'False) (U1 :: Type -> Type)))

Objects

data OrgObject Source #

Objects (inline elements).

Constructors

Plain Text 
LineBreak 
Italic [OrgObject] 
Underline [OrgObject] 
Bold [OrgObject] 
Strikethrough [OrgObject] 
Superscript [OrgObject] 
Subscript [OrgObject] 
Quoted QuoteType [OrgObject] 
Code Text 
Verbatim Text 
Timestamp TimestampData 
Entity

Entity (e.g. \alpha{})

Fields

  • Text

    Name (e.g. alpha)

LaTeXFragment FragmentType Text 
ExportSnippet

Inline export snippet (e.g. @@html:<br/>@@)

Fields

  • Text

    Back-end (e.g. html)

  • Text

    Value (e.g. <br/>)

FootnoteRef FootnoteRefData

Footnote reference.

Cite Citation 
InlBabelCall BabelCall 
Src

Inline source (e.g. src_html[:foo bar]{<br/>})

Fields

  • Text

    Language (e.g. html)

  • Text

    Parameters (e.g. :foo bar)

  • Text

    Value (e.g. <br/>)

Link LinkTarget [OrgObject] 
Target

Inline target (e.g. <<<foo>>>)

Fields

  • Id

    Anchor (Warning: this field is not populated by the parser! --- in the near future, fields like this one and the Id type will be removed in favor of AST extensibility). See also the documentation for LinkTarget

  • Text

    Name

Macro

Org inline macro (e.g. {{{poem(red,blue)}}})

Fields

  • Text

    Macro name (e.g. "poem")

  • [Text]

    Arguments (e.g. ["red", "blue"])

StatisticCookie

Statistic cookies.

Fields

Instances

Instances details
Data OrgObject Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrgObject -> c OrgObject Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrgObject Source #

toConstr :: OrgObject -> Constr Source #

dataTypeOf :: OrgObject -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OrgObject) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrgObject) Source #

gmapT :: (forall b. Data b => b -> b) -> OrgObject -> OrgObject Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrgObject -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrgObject -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> OrgObject -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrgObject -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrgObject -> m OrgObject Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrgObject -> m OrgObject Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrgObject -> m OrgObject Source #

IsString OrgObjects Source # 
Instance details

Defined in Org.Builder

Monoid OrgObjects Source # 
Instance details

Defined in Org.Builder

Semigroup OrgObjects Source # 
Instance details

Defined in Org.Builder

Generic OrgObject Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep OrgObject :: Type -> Type Source #

Read OrgObject Source # 
Instance details

Defined in Org.Types

Show OrgObject Source # 
Instance details

Defined in Org.Types

NFData OrgObject Source # 
Instance details

Defined in Org.Types

Methods

rnf :: OrgObject -> () Source #

Eq OrgObject Source # 
Instance details

Defined in Org.Types

Ord OrgObject Source # 
Instance details

Defined in Org.Types

MultiSub MWTag OrgObject 
Instance details

Defined in Org.Walk

Associated Types

type SubTypes MWTag OrgObject :: Spec

type HasSubTag MWTag OrgObject

type Rep OrgObject Source # 
Instance details

Defined in Org.Types

type Rep OrgObject = D1 ('MetaData "OrgObject" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) ((((C1 ('MetaCons "Plain" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "LineBreak" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Italic" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgObject])) :+: (C1 ('MetaCons "Underline" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgObject])) :+: C1 ('MetaCons "Bold" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgObject]))))) :+: ((C1 ('MetaCons "Strikethrough" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgObject])) :+: (C1 ('MetaCons "Superscript" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgObject])) :+: C1 ('MetaCons "Subscript" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgObject])))) :+: (C1 ('MetaCons "Quoted" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QuoteType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgObject])) :+: (C1 ('MetaCons "Code" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "Verbatim" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))))) :+: (((C1 ('MetaCons "Timestamp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimestampData)) :+: (C1 ('MetaCons "Entity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "LaTeXFragment" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FragmentType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) :+: (C1 ('MetaCons "ExportSnippet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "FootnoteRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FootnoteRefData)) :+: C1 ('MetaCons "Cite" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Citation))))) :+: ((C1 ('MetaCons "InlBabelCall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BabelCall)) :+: (C1 ('MetaCons "Src" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :+: C1 ('MetaCons "Link" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LinkTarget) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgObject])))) :+: (C1 ('MetaCons "Target" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Id) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "Macro" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])) :+: C1 ('MetaCons "StatisticCookie" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either (Int, Int) Int))))))))
type HasSubTag MWTag OrgObject 
Instance details

Defined in Org.Walk

type HasSubTag MWTag OrgObject = GSubTag
type SubTypes MWTag OrgObject 
Instance details

Defined in Org.Walk

type SubTypes MWTag OrgObject = 'SpecList '[ToSpec (List OrgObject), ToSpec (Under FootnoteRefData 'NoSel (List OrgElement)), ToSpec Citation]

Links

data LinkTarget Source #

Link target. Note that the parser does not resolve internal links. Instead, they should be resolved using the functions in org-exporters package. In the near future, the InternalLink constructor and Id type will be removed in favor of AST extensibility. See also the documentation for Target.

Instances

Instances details
Data LinkTarget Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LinkTarget -> c LinkTarget Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LinkTarget Source #

toConstr :: LinkTarget -> Constr Source #

dataTypeOf :: LinkTarget -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LinkTarget) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LinkTarget) Source #

gmapT :: (forall b. Data b => b -> b) -> LinkTarget -> LinkTarget Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LinkTarget -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LinkTarget -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> LinkTarget -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LinkTarget -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LinkTarget -> m LinkTarget Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LinkTarget -> m LinkTarget Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LinkTarget -> m LinkTarget Source #

Generic LinkTarget Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep LinkTarget :: Type -> Type Source #

Read LinkTarget Source # 
Instance details

Defined in Org.Types

Show LinkTarget Source # 
Instance details

Defined in Org.Types

NFData LinkTarget Source # 
Instance details

Defined in Org.Types

Methods

rnf :: LinkTarget -> () Source #

Eq LinkTarget Source # 
Instance details

Defined in Org.Types

Ord LinkTarget Source # 
Instance details

Defined in Org.Types

type Rep LinkTarget Source # 
Instance details

Defined in Org.Types

type Id = Text Source #

LaTeX fragments

data FragmentType Source #

Instances

Instances details
Data FragmentType Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FragmentType -> c FragmentType Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FragmentType Source #

toConstr :: FragmentType -> Constr Source #

dataTypeOf :: FragmentType -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FragmentType) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FragmentType) Source #

gmapT :: (forall b. Data b => b -> b) -> FragmentType -> FragmentType Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FragmentType -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FragmentType -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FragmentType -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FragmentType -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FragmentType -> m FragmentType Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FragmentType -> m FragmentType Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FragmentType -> m FragmentType Source #

Generic FragmentType Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep FragmentType :: Type -> Type Source #

Read FragmentType Source # 
Instance details

Defined in Org.Types

Show FragmentType Source # 
Instance details

Defined in Org.Types

NFData FragmentType Source # 
Instance details

Defined in Org.Types

Methods

rnf :: FragmentType -> () Source #

Eq FragmentType Source # 
Instance details

Defined in Org.Types

Ord FragmentType Source # 
Instance details

Defined in Org.Types

type Rep FragmentType Source # 
Instance details

Defined in Org.Types

type Rep FragmentType = D1 ('MetaData "FragmentType" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "RawFragment" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "InlMathFragment" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DispMathFragment" 'PrefixI 'False) (U1 :: Type -> Type)))

Citations

data Citation Source #

Instances

Instances details
Data Citation Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Citation -> c Citation Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Citation Source #

toConstr :: Citation -> Constr Source #

dataTypeOf :: Citation -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Citation) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Citation) Source #

gmapT :: (forall b. Data b => b -> b) -> Citation -> Citation Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Citation -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Citation -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Citation -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Citation -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Citation -> m Citation Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Citation -> m Citation Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Citation -> m Citation Source #

Generic Citation Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep Citation :: Type -> Type Source #

Read Citation Source # 
Instance details

Defined in Org.Types

Show Citation Source # 
Instance details

Defined in Org.Types

NFData Citation Source # 
Instance details

Defined in Org.Types

Methods

rnf :: Citation -> () Source #

Eq Citation Source # 
Instance details

Defined in Org.Types

Ord Citation Source # 
Instance details

Defined in Org.Types

MultiSub MWTag Citation 
Instance details

Defined in Org.Walk

Associated Types

type SubTypes MWTag Citation :: Spec

type HasSubTag MWTag Citation

type Rep Citation Source # 
Instance details

Defined in Org.Types

type Rep Citation = D1 ('MetaData "Citation" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "Citation" 'PrefixI 'True) ((S1 ('MetaSel ('Just "citationStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "citationVariant") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "citationPrefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgObject]) :*: (S1 ('MetaSel ('Just "citationSuffix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgObject]) :*: S1 ('MetaSel ('Just "citationReferences") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [CiteReference])))))
type HasSubTag MWTag Citation 
Instance details

Defined in Org.Walk

type HasSubTag MWTag Citation = GSubTag
type SubTypes MWTag Citation 
Instance details

Defined in Org.Walk

type SubTypes MWTag Citation = 'SpecList '[ToSpec (List OrgObject), ToSpec (List (Under CiteReference 'NoSel (List OrgObject)))]

data CiteReference Source #

Constructors

CiteReference 

Instances

Instances details
Data CiteReference Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CiteReference -> c CiteReference Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CiteReference Source #

toConstr :: CiteReference -> Constr Source #

dataTypeOf :: CiteReference -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CiteReference) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CiteReference) Source #

gmapT :: (forall b. Data b => b -> b) -> CiteReference -> CiteReference Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CiteReference -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CiteReference -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> CiteReference -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CiteReference -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CiteReference -> m CiteReference Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CiteReference -> m CiteReference Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CiteReference -> m CiteReference Source #

Generic CiteReference Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep CiteReference :: Type -> Type Source #

Read CiteReference Source # 
Instance details

Defined in Org.Types

Show CiteReference Source # 
Instance details

Defined in Org.Types

NFData CiteReference Source # 
Instance details

Defined in Org.Types

Methods

rnf :: CiteReference -> () Source #

Eq CiteReference Source # 
Instance details

Defined in Org.Types

Ord CiteReference Source # 
Instance details

Defined in Org.Types

type Rep CiteReference Source # 
Instance details

Defined in Org.Types

type Rep CiteReference = D1 ('MetaData "CiteReference" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "CiteReference" 'PrefixI 'True) (S1 ('MetaSel ('Just "refId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "refPrefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgObject]) :*: S1 ('MetaSel ('Just "refSuffix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OrgObject]))))

Footnote references

data FootnoteRefData Source #

Data for a footnote reference.

Constructors

FootnoteRefLabel

Label-only footnote reference (e.g. [fn:foo])

Fields

  • Text

    Label (e.g. foo)

FootnoteRefDef

Inline footnote definition (e.g. [fn:foo::bar])

Fields

Instances

Instances details
Data FootnoteRefData Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FootnoteRefData -> c FootnoteRefData Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FootnoteRefData Source #

toConstr :: FootnoteRefData -> Constr Source #

dataTypeOf :: FootnoteRefData -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FootnoteRefData) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FootnoteRefData) Source #

gmapT :: (forall b. Data b => b -> b) -> FootnoteRefData -> FootnoteRefData Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FootnoteRefData -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FootnoteRefData -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FootnoteRefData -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FootnoteRefData -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FootnoteRefData -> m FootnoteRefData Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FootnoteRefData -> m FootnoteRefData Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FootnoteRefData -> m FootnoteRefData Source #

Generic FootnoteRefData Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep FootnoteRefData :: Type -> Type Source #

Read FootnoteRefData Source # 
Instance details

Defined in Org.Types

Show FootnoteRefData Source # 
Instance details

Defined in Org.Types

NFData FootnoteRefData Source # 
Instance details

Defined in Org.Types

Methods

rnf :: FootnoteRefData -> () Source #

Eq FootnoteRefData Source # 
Instance details

Defined in Org.Types

Ord FootnoteRefData Source # 
Instance details

Defined in Org.Types

type Rep FootnoteRefData Source # 
Instance details

Defined in Org.Types

Timestamps

data TimestampData Source #

An Org timestamp, including repetition marks.

Instances

Instances details
Data TimestampData Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimestampData -> c TimestampData Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimestampData Source #

toConstr :: TimestampData -> Constr Source #

dataTypeOf :: TimestampData -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TimestampData) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimestampData) Source #

gmapT :: (forall b. Data b => b -> b) -> TimestampData -> TimestampData Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimestampData -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimestampData -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TimestampData -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TimestampData -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimestampData -> m TimestampData Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimestampData -> m TimestampData Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimestampData -> m TimestampData Source #

Generic TimestampData Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep TimestampData :: Type -> Type Source #

Read TimestampData Source # 
Instance details

Defined in Org.Types

Show TimestampData Source # 
Instance details

Defined in Org.Types

NFData TimestampData Source # 
Instance details

Defined in Org.Types

Methods

rnf :: TimestampData -> () Source #

Eq TimestampData Source # 
Instance details

Defined in Org.Types

Ord TimestampData Source # 
Instance details

Defined in Org.Types

type Rep TimestampData Source # 
Instance details

Defined in Org.Types

type Time = (Int, Int) Source #

Quotes

data QuoteType Source #

Constructors

SingleQuote 
DoubleQuote 

Instances

Instances details
Data QuoteType Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QuoteType -> c QuoteType Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QuoteType Source #

toConstr :: QuoteType -> Constr Source #

dataTypeOf :: QuoteType -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c QuoteType) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QuoteType) Source #

gmapT :: (forall b. Data b => b -> b) -> QuoteType -> QuoteType Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QuoteType -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QuoteType -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> QuoteType -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> QuoteType -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType Source #

Generic QuoteType Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep QuoteType :: Type -> Type Source #

Read QuoteType Source # 
Instance details

Defined in Org.Types

Show QuoteType Source # 
Instance details

Defined in Org.Types

NFData QuoteType Source # 
Instance details

Defined in Org.Types

Methods

rnf :: QuoteType -> () Source #

Eq QuoteType Source # 
Instance details

Defined in Org.Types

Ord QuoteType Source # 
Instance details

Defined in Org.Types

type Rep QuoteType Source # 
Instance details

Defined in Org.Types

type Rep QuoteType = D1 ('MetaData "QuoteType" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "SingleQuote" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DoubleQuote" 'PrefixI 'False) (U1 :: Type -> Type))

Babel

data BabelCall Source #

Instances

Instances details
Data BabelCall Source # 
Instance details

Defined in Org.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BabelCall -> c BabelCall Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BabelCall Source #

toConstr :: BabelCall -> Constr Source #

dataTypeOf :: BabelCall -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BabelCall) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BabelCall) Source #

gmapT :: (forall b. Data b => b -> b) -> BabelCall -> BabelCall Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BabelCall -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BabelCall -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> BabelCall -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BabelCall -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BabelCall -> m BabelCall Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BabelCall -> m BabelCall Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BabelCall -> m BabelCall Source #

Generic BabelCall Source # 
Instance details

Defined in Org.Types

Associated Types

type Rep BabelCall :: Type -> Type Source #

Read BabelCall Source # 
Instance details

Defined in Org.Types

Show BabelCall Source # 
Instance details

Defined in Org.Types

NFData BabelCall Source # 
Instance details

Defined in Org.Types

Methods

rnf :: BabelCall -> () Source #

Eq BabelCall Source # 
Instance details

Defined in Org.Types

Ord BabelCall Source # 
Instance details

Defined in Org.Types

type Rep BabelCall Source # 
Instance details

Defined in Org.Types

type Rep BabelCall = D1 ('MetaData "BabelCall" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "BabelCall" 'PrefixI 'True) ((S1 ('MetaSel ('Just "babelCallName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "babelCallHeader1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "babelCallHeader2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "babelCallArguments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))