orgmode-parse-0.2.0: A collection of Attoparsec combinators for parsing org-mode flavored documents.

Copyright© 2014 Parnell Springmeyer
LicenseAll Rights Reserved
MaintainerParnell Springmeyer <parnell@digitalmentat.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.OrgMode.Types

Contents

Description

Types for the AST of an org-mode document.

Synopsis

Documentation

newtype Clock Source #

Constructors

Clock 

Instances

Eq Clock Source # 

Methods

(==) :: Clock -> Clock -> Bool #

(/=) :: Clock -> Clock -> Bool #

Show Clock Source # 

Methods

showsPrec :: Int -> Clock -> ShowS #

show :: Clock -> String #

showList :: [Clock] -> ShowS #

Generic Clock Source # 

Associated Types

type Rep Clock :: * -> * #

Methods

from :: Clock -> Rep Clock x #

to :: Rep Clock x -> Clock #

ToJSON Clock Source # 
FromJSON Clock Source # 
type Rep Clock Source # 
type Rep Clock = D1 (MetaData "Clock" "Data.OrgMode.Types" "orgmode-parse-0.2.0-DkbA3cUPAB66je85bX7gwH" True) (C1 (MetaCons "Clock" PrefixI True) (S1 (MetaSel (Just Symbol "unClock") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Timestamp, Maybe Duration))))

data DateTime Source #

A data type for parsed org-mode datetime stamps.

TODO: why do we have this data type and BracketedDateTime? They look almost exactly the same...

data Delay Source #

A data type representing a delay value.

Constructors

Delay 

Fields

Instances

data DelayType Source #

A sum type representing the delay type of a delay value.

Constructors

DelayAll 
DelayFirst 

Instances

Eq DelayType Source # 
Show DelayType Source # 
Generic DelayType Source # 

Associated Types

type Rep DelayType :: * -> * #

ToJSON DelayType Source # 
FromJSON DelayType Source # 
type Rep DelayType Source # 
type Rep DelayType = D1 (MetaData "DelayType" "Data.OrgMode.Types" "orgmode-parse-0.2.0-DkbA3cUPAB66je85bX7gwH" False) ((:+:) (C1 (MetaCons "DelayAll" PrefixI False) U1) (C1 (MetaCons "DelayFirst" PrefixI False) U1))

newtype Depth Source #

Headline nesting depth.

Constructors

Depth Int 

Instances

Eq Depth Source # 

Methods

(==) :: Depth -> Depth -> Bool #

(/=) :: Depth -> Depth -> Bool #

Num Depth Source # 
Show Depth Source # 

Methods

showsPrec :: Int -> Depth -> ShowS #

show :: Depth -> String #

showList :: [Depth] -> ShowS #

Generic Depth Source # 

Associated Types

type Rep Depth :: * -> * #

Methods

from :: Depth -> Rep Depth x #

to :: Rep Depth x -> Depth #

ToJSON Depth Source # 
FromJSON Depth Source # 
type Rep Depth Source # 
type Rep Depth = D1 (MetaData "Depth" "Data.OrgMode.Types" "orgmode-parse-0.2.0-DkbA3cUPAB66je85bX7gwH" True) (C1 (MetaCons "Depth" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

data Document Source #

Org-mode document.

Constructors

Document 

Fields

data Drawer Source #

Constructors

Drawer 

Fields

Instances

Eq Drawer Source # 

Methods

(==) :: Drawer -> Drawer -> Bool #

(/=) :: Drawer -> Drawer -> Bool #

Show Drawer Source # 
Generic Drawer Source # 

Associated Types

type Rep Drawer :: * -> * #

Methods

from :: Drawer -> Rep Drawer x #

to :: Rep Drawer x -> Drawer #

ToJSON Drawer Source # 
FromJSON Drawer Source # 
type Rep Drawer Source # 
type Rep Drawer = D1 (MetaData "Drawer" "Data.OrgMode.Types" "orgmode-parse-0.2.0-DkbA3cUPAB66je85bX7gwH" False) (C1 (MetaCons "Drawer" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "contents") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))

data Headline Source #

Headline within an org-mode document.

Constructors

Headline 

Fields

Instances

Eq Headline Source # 
Show Headline Source # 
Generic Headline Source # 

Associated Types

type Rep Headline :: * -> * #

Methods

from :: Headline -> Rep Headline x #

to :: Rep Headline x -> Headline #

ToJSON Headline Source # 
FromJSON Headline Source # 
type Rep Headline Source # 

newtype Logbook Source #

Constructors

Logbook 

Fields

Instances

Eq Logbook Source # 

Methods

(==) :: Logbook -> Logbook -> Bool #

(/=) :: Logbook -> Logbook -> Bool #

Show Logbook Source # 
Generic Logbook Source # 

Associated Types

type Rep Logbook :: * -> * #

Methods

from :: Logbook -> Rep Logbook x #

to :: Rep Logbook x -> Logbook #

Monoid Logbook Source # 
ToJSON Logbook Source # 
FromJSON Logbook Source # 
type Rep Logbook Source # 
type Rep Logbook = D1 (MetaData "Logbook" "Data.OrgMode.Types" "orgmode-parse-0.2.0-DkbA3cUPAB66je85bX7gwH" True) (C1 (MetaCons "Logbook" PrefixI True) (S1 (MetaSel (Just Symbol "unLogbook") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Clock])))

data PlanningKeyword Source #

A sum type representing the planning keywords.

Constructors

SCHEDULED 
DEADLINE 
CLOSED 

Instances

Enum PlanningKeyword Source # 
Eq PlanningKeyword Source # 
Ord PlanningKeyword Source # 
Show PlanningKeyword Source # 
Generic PlanningKeyword Source # 
Hashable PlanningKeyword Source # 
ToJSON PlanningKeyword Source # 
FromJSON PlanningKeyword Source # 
type Rep PlanningKeyword Source # 
type Rep PlanningKeyword = D1 (MetaData "PlanningKeyword" "Data.OrgMode.Types" "orgmode-parse-0.2.0-DkbA3cUPAB66je85bX7gwH" False) ((:+:) (C1 (MetaCons "SCHEDULED" PrefixI False) U1) ((:+:) (C1 (MetaCons "DEADLINE" PrefixI False) U1) (C1 (MetaCons "CLOSED" PrefixI False) U1)))

newtype Plannings Source #

A type representing a map of planning timestamps.

data Priority Source #

A sum type representing the three default priorities: A, B, and C.

Constructors

A 
B 
C 

data Repeater Source #

A data type representing a repeater interval in a org-mode timestamp.

Constructors

Repeater 

Fields

data RepeaterType Source #

A sum type representing the repeater type of a repeater interval in a org-mode timestamp.

data Section Source #

Section of text directly following a headline.

Constructors

Section 

Fields

Instances

Eq Section Source # 

Methods

(==) :: Section -> Section -> Bool #

(/=) :: Section -> Section -> Bool #

Show Section Source # 
Generic Section Source # 

Associated Types

type Rep Section :: * -> * #

Methods

from :: Section -> Rep Section x #

to :: Rep Section x -> Section #

ToJSON Section Source # 
FromJSON Section Source # 
type Rep Section Source # 

newtype StateKeyword Source #

A type representing a headline state keyword, e.g: TODO, DONE, WAITING, etc.

Constructors

StateKeyword 

Fields

data Stats Source #

A data type representing a stats value in a headline, e.g [2/3] in this headline:

* TODO [2/3] work on orgmode-parse

Constructors

StatsPct Int 
StatsOf Int Int 

type Tag = Text Source #

data TimePart Source #

A sum type representing an absolute time part of a bracketed org-mode datetime stamp or a time range between two absolute timestamps.

Constructors

AbsoluteTime AbsTime 
TimeStampRange (AbsTime, AbsTime) 

data TimeUnit Source #

A sum type representing the time units of a delay.

Instances

Eq TimeUnit Source # 
Show TimeUnit Source # 
Generic TimeUnit Source # 

Associated Types

type Rep TimeUnit :: * -> * #

Methods

from :: TimeUnit -> Rep TimeUnit x #

to :: Rep TimeUnit x -> TimeUnit #

ToJSON TimeUnit Source # 
FromJSON TimeUnit Source # 
type Rep TimeUnit Source # 
type Rep TimeUnit = D1 (MetaData "TimeUnit" "Data.OrgMode.Types" "orgmode-parse-0.2.0-DkbA3cUPAB66je85bX7gwH" False) ((:+:) ((:+:) (C1 (MetaCons "UnitYear" PrefixI False) U1) (C1 (MetaCons "UnitWeek" PrefixI False) U1)) ((:+:) (C1 (MetaCons "UnitMonth" PrefixI False) U1) ((:+:) (C1 (MetaCons "UnitDay" PrefixI False) U1) (C1 (MetaCons "UnitHour" PrefixI False) U1))))

data Timestamp Source #

A generic data type for parsed org-mode time stamps, e.g:

<2015-03-27 Fri 10:20>
[2015-03-27 Fri 10:20 +4h]
<2015-03-27 Fri 10:20>--<2015-03-28 Sat 10:20>

Constructors

Timestamp 

Fields

data YearMonthDay :: * #

Constructors

YearMonthDay 

Fields

Instances

Eq YearMonthDay 
Data YearMonthDay 

Methods

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

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

toConstr :: YearMonthDay -> Constr #

dataTypeOf :: YearMonthDay -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord YearMonthDay 
Show YearMonthDay 
Generic YearMonthDay 

Associated Types

type Rep YearMonthDay :: * -> * #

NFData YearMonthDay 

Methods

rnf :: YearMonthDay -> () #

FormatTime YearMonthDay 

Methods

showsTime :: TimeLocale -> YearMonthDay -> (Char -> ShowS) -> Char -> ShowS #

ParseTime YearMonthDay 
Unbox YearMonthDay 
Vector Vector YearMonthDay 
MVector MVector YearMonthDay 
type Rep YearMonthDay 
type Rep YearMonthDay = D1 (MetaData "YearMonthDay" "Data.Thyme.Calendar.Internal" "thyme-0.3.5.5-8kj7Nzp2FkjAKbNsooxC6S" False) (C1 (MetaCons "YearMonthDay" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "ymdYear") SourceUnpack SourceStrict DecidedStrict) (Rec0 Year)) ((:*:) (S1 (MetaSel (Just Symbol "ymdMonth") SourceUnpack SourceStrict DecidedStrict) (Rec0 Month)) (S1 (MetaSel (Just Symbol "ymdDay") SourceUnpack SourceStrict DecidedStrict) (Rec0 DayOfMonth)))))
data Vector YearMonthDay 
data MVector s YearMonthDay 

Orphan instances