| Copyright | © 2014 Parnell Springmeyer |
|---|---|
| License | All Rights Reserved |
| Maintainer | Parnell Springmeyer <parnell@digitalmentat.com> |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.OrgMode.Types
Contents
Description
Types for the AST of an org-mode document.
Synopsis
- data ActiveState
- data BracketedDateTime = BracketedDateTime {
- datePart :: YearMonthDay
- dayNamePart :: Maybe Weekday
- timePart :: Maybe TimePart
- repeat :: Maybe Repeater
- delayPart :: Maybe Delay
- activeState :: ActiveState
- newtype Clock = Clock {}
- data DateTime = DateTime {
- yearMonthDay :: YearMonthDay
- dayName :: Maybe Text
- hourMinute :: Maybe (Hour, Minute)
- repeater :: Maybe Repeater
- delay :: Maybe Delay
- data Delay = Delay {}
- data DelayType
- newtype Depth = Depth Int
- data Document = Document {}
- data Drawer = Drawer {}
- type Duration = (Hour, Minute)
- data Headline = Headline {}
- newtype Logbook = Logbook {}
- data PlanningKeyword
- newtype Plannings = Plns (HashMap PlanningKeyword Timestamp)
- data Priority
- newtype Properties = Properties {}
- data Repeater = Repeater {}
- data RepeaterType
- data Section = Section {}
- newtype StateKeyword = StateKeyword {}
- data Stats
- type Tag = Text
- data TimePart
- = AbsoluteTime AbsTime
- | TimeStampRange (AbsTime, AbsTime)
- data TimeUnit
- data Timestamp = Timestamp {}
- data YearMonthDay = YearMonthDay {}
Documentation
data ActiveState Source #
Sum type indicating the active state of a timestamp.
Instances
| Eq ActiveState Source # | |
Defined in Data.OrgMode.Types | |
| Read ActiveState Source # | |
Defined in Data.OrgMode.Types Methods readsPrec :: Int -> ReadS ActiveState # readList :: ReadS [ActiveState] # readPrec :: ReadPrec ActiveState # readListPrec :: ReadPrec [ActiveState] # | |
| Show ActiveState Source # | |
Defined in Data.OrgMode.Types Methods showsPrec :: Int -> ActiveState -> ShowS # show :: ActiveState -> String # showList :: [ActiveState] -> ShowS # | |
| Generic ActiveState Source # | |
Defined in Data.OrgMode.Types Associated Types type Rep ActiveState :: Type -> Type # | |
| ToJSON ActiveState Source # | |
Defined in Data.OrgMode.Types Methods toJSON :: ActiveState -> Value # toEncoding :: ActiveState -> Encoding # toJSONList :: [ActiveState] -> Value # toEncodingList :: [ActiveState] -> Encoding # | |
| FromJSON ActiveState Source # | |
Defined in Data.OrgMode.Types | |
| type Rep ActiveState Source # | |
data BracketedDateTime Source #
A data type for parsed org-mode bracketed datetime stamps, e.g:
[2015-03-27 Fri 10:20 +4h]
Constructors
| BracketedDateTime | |
Fields
| |
Instances
| Eq BracketedDateTime Source # | |
Defined in Data.OrgMode.Types Methods (==) :: BracketedDateTime -> BracketedDateTime -> Bool # (/=) :: BracketedDateTime -> BracketedDateTime -> Bool # | |
| Show BracketedDateTime Source # | |
Defined in Data.OrgMode.Types Methods showsPrec :: Int -> BracketedDateTime -> ShowS # show :: BracketedDateTime -> String # showList :: [BracketedDateTime] -> ShowS # | |
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...
Constructors
| DateTime | |
Fields
| |
Instances
| Eq DateTime Source # | |
| Show DateTime Source # | |
| Generic DateTime Source # | |
| ToJSON DateTime Source # | |
Defined in Data.OrgMode.Types | |
| FromJSON DateTime Source # | |
| type Rep DateTime Source # | |
Defined in Data.OrgMode.Types type Rep DateTime = D1 (MetaData "DateTime" "Data.OrgMode.Types" "orgmode-parse-0.2.3-1kLlNE5GDxmEjD7LH0fxqe" False) (C1 (MetaCons "DateTime" PrefixI True) ((S1 (MetaSel (Just "yearMonthDay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 YearMonthDay) :*: S1 (MetaSel (Just "dayName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "hourMinute") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Hour, Minute))) :*: (S1 (MetaSel (Just "repeater") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Repeater)) :*: S1 (MetaSel (Just "delay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Delay)))))) | |
A data type representing a delay value.
Constructors
| Delay | |
Instances
| Eq Delay Source # | |
| Show Delay Source # | |
| Generic Delay Source # | |
| ToJSON Delay Source # | |
Defined in Data.OrgMode.Types | |
| FromJSON Delay Source # | |
| type Rep Delay Source # | |
Defined in Data.OrgMode.Types type Rep Delay = D1 (MetaData "Delay" "Data.OrgMode.Types" "orgmode-parse-0.2.3-1kLlNE5GDxmEjD7LH0fxqe" False) (C1 (MetaCons "Delay" PrefixI True) (S1 (MetaSel (Just "delayType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DelayType) :*: (S1 (MetaSel (Just "delayValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "delayUnit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TimeUnit)))) | |
A sum type representing the delay type of a delay value.
Constructors
| DelayAll | |
| DelayFirst |
Headline nesting depth.
Org-mode document.
Constructors
| Document | |
Fields
| |
Instances
| Eq Document Source # | |
| Show Document Source # | |
| Generic Document Source # | |
| ToJSON Document Source # | |
Defined in Data.OrgMode.Types | |
| FromJSON Document Source # | |
| type Rep Document Source # | |
Defined in Data.OrgMode.Types type Rep Document = D1 (MetaData "Document" "Data.OrgMode.Types" "orgmode-parse-0.2.3-1kLlNE5GDxmEjD7LH0fxqe" False) (C1 (MetaCons "Document" PrefixI True) (S1 (MetaSel (Just "documentText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "documentHeadlines") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Headline]))) | |
Instances
| Eq Drawer Source # | |
| Show Drawer Source # | |
| Generic Drawer Source # | |
| ToJSON Drawer Source # | |
Defined in Data.OrgMode.Types | |
| FromJSON Drawer Source # | |
| type Rep Drawer Source # | |
Defined in Data.OrgMode.Types type Rep Drawer = D1 (MetaData "Drawer" "Data.OrgMode.Types" "orgmode-parse-0.2.3-1kLlNE5GDxmEjD7LH0fxqe" False) (C1 (MetaCons "Drawer" PrefixI True) (S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "contents") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) | |
Headline within an org-mode document.
Constructors
| Headline | |
Fields
| |
Instances
data PlanningKeyword Source #
A sum type representing the planning keywords.
Instances
A type representing a map of planning timestamps.
Constructors
| Plns (HashMap PlanningKeyword Timestamp) |
A sum type representing the three default priorities: A, B,
and C.
newtype Properties Source #
Constructors
| Properties | |
Fields | |
Instances
A data type representing a repeater interval in a org-mode timestamp.
Constructors
| Repeater | |
Fields
| |
Instances
| Eq Repeater Source # | |
| Show Repeater Source # | |
| Generic Repeater Source # | |
| ToJSON Repeater Source # | |
Defined in Data.OrgMode.Types | |
| FromJSON Repeater Source # | |
| type Rep Repeater Source # | |
Defined in Data.OrgMode.Types type Rep Repeater = D1 (MetaData "Repeater" "Data.OrgMode.Types" "orgmode-parse-0.2.3-1kLlNE5GDxmEjD7LH0fxqe" False) (C1 (MetaCons "Repeater" PrefixI True) (S1 (MetaSel (Just "repeaterType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RepeaterType) :*: (S1 (MetaSel (Just "repeaterValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "repeaterUnit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TimeUnit)))) | |
data RepeaterType Source #
A sum type representing the repeater type of a repeater interval in a org-mode timestamp.
Constructors
| RepeatCumulate | |
| RepeatCatchUp | |
| RepeatRestart |
Instances
Section of text directly following a headline.
Constructors
| Section | |
Fields
| |
Instances
newtype StateKeyword Source #
A type representing a headline state keyword, e.g: TODO,
DONE, WAITING, etc.
Constructors
| StateKeyword | |
Fields | |
Instances
| Eq StateKeyword Source # | |
Defined in Data.OrgMode.Types | |
| Show StateKeyword Source # | |
Defined in Data.OrgMode.Types Methods showsPrec :: Int -> StateKeyword -> ShowS # show :: StateKeyword -> String # showList :: [StateKeyword] -> ShowS # | |
| Generic StateKeyword Source # | |
Defined in Data.OrgMode.Types Associated Types type Rep StateKeyword :: Type -> Type # | |
| ToJSON StateKeyword Source # | |
Defined in Data.OrgMode.Types Methods toJSON :: StateKeyword -> Value # toEncoding :: StateKeyword -> Encoding # toJSONList :: [StateKeyword] -> Value # toEncodingList :: [StateKeyword] -> Encoding # | |
| FromJSON StateKeyword Source # | |
Defined in Data.OrgMode.Types | |
| type Rep StateKeyword Source # | |
Defined in Data.OrgMode.Types type Rep StateKeyword = D1 (MetaData "StateKeyword" "Data.OrgMode.Types" "orgmode-parse-0.2.3-1kLlNE5GDxmEjD7LH0fxqe" True) (C1 (MetaCons "StateKeyword" PrefixI True) (S1 (MetaSel (Just "unStateKeyword") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) | |
A data type representing a stats value in a headline, e.g [2/3]
in this headline:
* TODO [2/3] work on orgmode-parse
Instances
| Eq Stats Source # | |
| Show Stats Source # | |
| Generic Stats Source # | |
| ToJSON Stats Source # | |
Defined in Data.OrgMode.Types | |
| FromJSON Stats Source # | |
| type Rep Stats Source # | |
Defined in Data.OrgMode.Types type Rep Stats = D1 (MetaData "Stats" "Data.OrgMode.Types" "orgmode-parse-0.2.3-1kLlNE5GDxmEjD7LH0fxqe" False) (C1 (MetaCons "StatsPct" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "StatsOf" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) | |
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) |
A sum type representing the time units of a delay.
Instances
| Eq TimeUnit Source # | |
| Show TimeUnit Source # | |
| Generic TimeUnit Source # | |
| ToJSON TimeUnit Source # | |
Defined in Data.OrgMode.Types | |
| FromJSON TimeUnit Source # | |
| type Rep TimeUnit Source # | |
Defined in Data.OrgMode.Types type Rep TimeUnit = D1 (MetaData "TimeUnit" "Data.OrgMode.Types" "orgmode-parse-0.2.3-1kLlNE5GDxmEjD7LH0fxqe" False) ((C1 (MetaCons "UnitYear" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UnitWeek" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "UnitMonth" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "UnitDay" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UnitHour" PrefixI False) (U1 :: Type -> Type)))) | |
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 | |
Instances
| Eq Timestamp Source # | |
| Show Timestamp Source # | |
| Generic Timestamp Source # | |
| ToJSON Timestamp Source # | |
Defined in Data.OrgMode.Types | |
| FromJSON Timestamp Source # | |
| type Rep Timestamp Source # | |
Defined in Data.OrgMode.Types type Rep Timestamp = D1 (MetaData "Timestamp" "Data.OrgMode.Types" "orgmode-parse-0.2.3-1kLlNE5GDxmEjD7LH0fxqe" False) (C1 (MetaCons "Timestamp" PrefixI True) (S1 (MetaSel (Just "tsTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DateTime) :*: (S1 (MetaSel (Just "tsActive") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ActiveState) :*: S1 (MetaSel (Just "tsEndTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe DateTime))))) | |
data YearMonthDay #
Constructors
| YearMonthDay | |
Instances
Orphan instances
| ToJSON YearMonthDay Source # | |
Methods toJSON :: YearMonthDay -> Value # toEncoding :: YearMonthDay -> Encoding # toJSONList :: [YearMonthDay] -> Value # toEncodingList :: [YearMonthDay] -> Encoding # | |
| FromJSON YearMonthDay Source # | |