| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Org.Types
Synopsis
- data OrgDocument = OrgDocument {}
- type Properties = Map Text Text
- lookupProperty :: Text -> OrgDocument -> Maybe Text
- data OrgSection = OrgSection {
- sectionLevel :: Int
- sectionProperties :: Properties
- sectionTodo :: Maybe TodoKeyword
- sectionIsComment :: Bool
- sectionPriority :: Maybe Priority
- sectionTitle :: [OrgObject]
- sectionRawTitle :: Text
- sectionAnchor :: Id
- sectionTags :: [Tag]
- sectionPlanning :: PlanningInfo
- sectionChildren :: [OrgElement]
- sectionSubsections :: [OrgSection]
- data TodoKeyword = TodoKeyword {}
- data TodoState
- type Tag = Text
- data Priority
- data PlanningInfo = PlanningInfo {}
- lookupSectionProperty :: Text -> OrgSection -> Maybe Text
- type OrgContent = ([OrgElement], [OrgSection])
- documentContent :: OrgDocument -> OrgContent
- mapContentM :: Monad m => (OrgContent -> m OrgContent) -> OrgDocument -> m OrgDocument
- mapContent :: (OrgContent -> OrgContent) -> OrgDocument -> OrgDocument
- sectionContent :: OrgSection -> OrgContent
- mapSectionContentM :: Monad m => (OrgContent -> m OrgContent) -> OrgSection -> m OrgSection
- mapSectionContent :: (OrgContent -> OrgContent) -> OrgSection -> OrgSection
- data OrgElement = OrgElement {}
- data OrgElementData
- = Clock TimestampData (Maybe Time)
- | GreaterBlock { }
- | Drawer {
- drawerName :: Text
- drawerElements :: [OrgElement]
- | PlainList { }
- | ExportBlock Text Text
- | ExampleBlock (Map Text Text) [SrcLine]
- | SrcBlock {
- srcBlkLang :: Text
- srcBlkSwitches :: Map Text Text
- srcBlkArguments :: [(Text, Text)]
- srcBlkLines :: [SrcLine]
- | VerseBlock [[OrgObject]]
- | HorizontalRule
- | Keyword { }
- | LaTeXEnvironment Text Text
- | Paragraph [OrgObject]
- | Table [TableRow]
- | FootnoteDef Text [OrgElement]
- | Comment
- data GreaterBlockType
- data SrcLine
- srcLineContent :: SrcLine -> Text
- srcLinesToText :: [SrcLine] -> Text
- srcLineMap :: (Text -> Text) -> SrcLine -> SrcLine
- data ListType
- data OrderedStyle
- orderedStyle :: Text -> OrderedStyle
- data ListItem = ListItem Bullet (Maybe Int) (Maybe Checkbox) [OrgObject] [OrgElement]
- data Bullet
- data Checkbox
- listItemType :: ListItem -> ListType
- type Keywords = Map Text KeywordValue
- data KeywordValue
- = ValueKeyword Text
- | ParsedKeyword [OrgObject]
- | BackendKeyword [(Text, Text)]
- lookupValueKeyword :: Text -> Keywords -> Text
- lookupParsedKeyword :: Text -> Keywords -> [OrgObject]
- lookupBackendKeyword :: Text -> Keywords -> [(Text, Text)]
- keywordsFromList :: [(Text, KeywordValue)] -> Keywords
- data TableRow
- type TableCell = [OrgObject]
- data ColumnAlignment
- data OrgObject
- = 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 Text
- | LaTeXFragment FragmentType Text
- | ExportSnippet Text Text
- | FootnoteRef FootnoteRefData
- | Cite Citation
- | InlBabelCall BabelCall
- | Src Text Text Text
- | Link LinkTarget [OrgObject]
- | Target Id Text
- | Macro Text [Text]
- | StatisticCookie (Either (Int, Int) Int)
- data LinkTarget
- type Protocol = Text
- type Id = Text
- linkTargetToText :: LinkTarget -> Text
- data FragmentType
- data Citation = Citation {}
- data CiteReference = CiteReference {}
- data FootnoteRefData
- data TimestampData
- type DateTime = (Date, Maybe Time, Maybe TimestampMark, Maybe TimestampMark)
- type TimestampMark = (Text, Int, Char)
- type Date = (Int, Int, Int, Maybe Text)
- type Time = (Int, Int)
- data QuoteType
- data BabelCall = BabelCall {}
Document
data OrgDocument Source #
Constructors
| OrgDocument | |
Fields | |
Instances
Helpers
lookupProperty :: Text -> OrgDocument -> Maybe Text Source #
Sections
data OrgSection Source #
Constructors
| OrgSection | |
Fields
| |
Instances
data TodoKeyword Source #
A to-do keyword like TODO or DONE.
Constructors
| TodoKeyword | |
Instances
The states in which a todo item can be
Instances
| FromJSON TodoState Source # | |
| ToJSON TodoState Source # | |
| Data TodoState Source # | |
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 # | |
| Read TodoState Source # | |
| Show TodoState Source # | |
| NFData TodoState Source # | |
| Eq TodoState Source # | |
| Ord TodoState Source # | |
Defined in Org.Types | |
| type Rep TodoState Source # | |
Constructors
| LetterPriority Char | |
| NumericPriority Int |
Instances
| Data Priority Source # | |
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 # | |
| Read Priority Source # | |
| Show Priority Source # | |
| NFData Priority Source # | |
| Eq Priority Source # | |
| Ord Priority Source # | |
Defined in Org.Types | |
| type Rep Priority Source # | |
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.
Constructors
| PlanningInfo | |
Instances
Helpers
lookupSectionProperty :: Text -> OrgSection -> Maybe Text Source #
OrgContent
type OrgContent = ([OrgElement], [OrgSection]) Source #
mapContentM :: Monad m => (OrgContent -> m OrgContent) -> OrgDocument -> m OrgDocument Source #
mapContent :: (OrgContent -> OrgContent) -> OrgDocument -> OrgDocument Source #
mapSectionContentM :: Monad m => (OrgContent -> m OrgContent) -> OrgSection -> m OrgSection Source #
mapSectionContent :: (OrgContent -> OrgContent) -> OrgSection -> OrgSection Source #
Elements
data OrgElement Source #
Org element. Like a Pandoc Block.
Constructors
| OrgElement | |
Fields | |
Instances
data OrgElementData Source #
Constructors
| Clock | Clock |
Fields
| |
| GreaterBlock | Greater block |
Fields
| |
| Drawer | Drawer |
Fields
| |
| PlainList | Plain list |
| ExportBlock | Export block |
| ExampleBlock | Example block |
| SrcBlock | Source blocks |
Fields
| |
| VerseBlock [[OrgObject]] | |
| HorizontalRule | |
| Keyword | |
Fields | |
| LaTeXEnvironment | |
| Paragraph [OrgObject] | |
| Table [TableRow] | |
| FootnoteDef | |
Fields
| |
| Comment | |
Instances
Greater blocks
data GreaterBlockType Source #
Instances
Source blocks
Instances
srcLineContent :: SrcLine -> Text Source #
srcLinesToText :: [SrcLine] -> Text Source #
Lists
Constructors
| Ordered OrderedStyle | |
| Descriptive | |
| Unordered Char |
Instances
| Data ListType Source # | |
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 # | |
| Read ListType Source # | |
| Show ListType Source # | |
| NFData ListType Source # | |
| Eq ListType Source # | |
| Ord ListType Source # | |
Defined in Org.Types | |
| type Rep ListType Source # | |
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
orderedStyle :: Text -> OrderedStyle Source #
One item of a list. Parameters are bullet, counter cookie, checkbox and tag.
Instances
Instances
| Data Bullet Source # | |
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 # | |
| Read Bullet Source # | |
| Show Bullet Source # | |
| NFData Bullet Source # | |
| Eq Bullet Source # | |
| Ord Bullet Source # | |
| type Rep Bullet Source # | |
Defined in Org.Types type Rep Bullet = D1 ('MetaData "Bullet" "Org.Types" "org-parser-0.1.0.0-inplace" 'False) (C1 ('MetaCons "Bullet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char)) :+: C1 ('MetaCons "Counter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char))) | |
Constructors
| BoolBox Bool | |
| PartialBox |
Instances
| Data Checkbox Source # | |
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 # | |
| Read Checkbox Source # | |
| Show Checkbox Source # | |
| NFData Checkbox Source # | |
| Eq Checkbox Source # | |
| Ord Checkbox Source # | |
Defined in Org.Types | |
| type Rep Checkbox Source # | |
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)) | |
listItemType :: ListItem -> ListType Source #
Keywords
data KeywordValue Source #
Constructors
| ValueKeyword Text | |
| ParsedKeyword [OrgObject] | |
| BackendKeyword [(Text, Text)] |
Instances
keywordsFromList :: [(Text, KeywordValue)] -> Keywords Source #
Tables
Constructors
| StandardRow [TableCell] | |
| ColumnPropsRow [Maybe ColumnAlignment] | |
| RuleRow |
Instances
| Data TableRow Source # | |
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 # | |
| Read TableRow Source # | |
| Show TableRow Source # | |
| NFData TableRow Source # | |
| Eq TableRow Source # | |
| Ord TableRow Source # | |
Defined in Org.Types | |
| type Rep TableRow Source # | |
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 #
Constructors
| AlignLeft | |
| AlignCenter | |
| AlignRight |
Instances
Objects
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. |
Fields
| |
| LaTeXFragment FragmentType Text | |
| ExportSnippet | Inline export snippet (e.g. |
| FootnoteRef FootnoteRefData | Footnote reference. |
| Cite Citation | |
| InlBabelCall BabelCall | |
| Src | Inline source (e.g. |
| Link LinkTarget [OrgObject] | |
| Target | Inline target (e.g. |
Fields
| |
| Macro | Org inline macro (e.g. |
| StatisticCookie | Statistic cookies. |
Instances
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.
Constructors
| URILink Protocol Text | |
| InternalLink Id | |
| UnresolvedLink Text |
Instances
linkTargetToText :: LinkTarget -> Text Source #
LaTeX fragments
data FragmentType Source #
Constructors
| RawFragment | |
| InlMathFragment | |
| DispMathFragment |
Instances
Citations
Constructors
| Citation | |
Fields
| |
Instances
data CiteReference Source #
Instances
Footnote references
data FootnoteRefData Source #
Data for a footnote reference.
Constructors
| FootnoteRefLabel | Label-only footnote reference (e.g. |
Fields
| |
| FootnoteRefDef | Inline footnote definition (e.g. |
Instances
Timestamps
data TimestampData Source #
An Org timestamp, including repetition marks.
Constructors
| TimestampData Bool DateTime | |
| TimestampRange Bool DateTime DateTime |
Instances
type DateTime = (Date, Maybe Time, Maybe TimestampMark, Maybe TimestampMark) Source #
Quotes
Constructors
| SingleQuote | |
| DoubleQuote |
Instances
| Data QuoteType Source # | |
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 # | |
| Read QuoteType Source # | |
| Show QuoteType Source # | |
| NFData QuoteType Source # | |
| Eq QuoteType Source # | |
| Ord QuoteType Source # | |
Defined in Org.Types | |
| type Rep QuoteType Source # | |
Babel
Constructors
| BabelCall | |
Fields | |
Instances
| Data BabelCall Source # | |
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 # | |
| Read BabelCall Source # | |
| Show BabelCall Source # | |
| NFData BabelCall Source # | |
| Eq BabelCall Source # | |
| Ord BabelCall Source # | |
Defined in Org.Types | |
| type Rep BabelCall Source # | |
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)))) | |