{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS -fno-warn-orphans #-}
module Data.OrgMode.Types
( ActiveState (..)
, BracketedDateTime (..)
, Clock (..)
, DateTime (..)
, Delay (..)
, DelayType (..)
, Depth (..)
, Document (..)
, Drawer (..)
, Duration
, Headline (..)
, Logbook (..)
, PlanningKeyword (..)
, Plannings (..)
, Priority (..)
, Properties (..)
, Repeater (..)
, RepeaterType (..)
, Section (..)
, StateKeyword (..)
, Stats (..)
, Tag
, TimePart (..)
, TimeUnit (..)
, Timestamp (..)
, YearMonthDay (..)
) where
import Control.Monad (mzero)
import Data.Aeson ((.:), (.=))
import qualified Data.Aeson as Aeson
import Data.Hashable (Hashable (..))
import Data.HashMap.Strict (HashMap, fromList, keys, toList)
import Data.Text (Text, pack)
import Data.Thyme.Calendar (YearMonthDay (..))
import Data.Thyme.LocalTime (Hour, Hours, Minute, Minutes)
import GHC.Generics
import Data.Semigroup (Semigroup)
data Document = Document
{ documentText :: Text
, documentHeadlines :: [Headline]
} deriving (Show, Eq, Generic)
instance Aeson.ToJSON Document
instance Aeson.FromJSON Document
data Headline = Headline
{ depth :: Depth
, stateKeyword :: Maybe StateKeyword
, priority :: Maybe Priority
, title :: Text
, timestamp :: Maybe Timestamp
, stats :: Maybe Stats
, tags :: [Tag]
, section :: Section
, subHeadlines :: [Headline]
} deriving (Show, Eq, Generic)
newtype Depth = Depth Int
deriving (Eq, Show, Num, Generic)
instance Aeson.ToJSON Depth
instance Aeson.FromJSON Depth
data Section = Section
{ sectionTimestamp :: Maybe Timestamp
, sectionPlannings :: Plannings
, sectionClocks :: [Clock]
, sectionProperties :: Properties
, sectionLogbook :: Logbook
, sectionDrawers :: [Drawer]
, sectionParagraph :: Text
} deriving (Show, Eq, Generic)
newtype Properties = Properties { unProperties :: HashMap Text Text }
deriving (Show, Eq, Generic, Semigroup, Monoid)
instance Aeson.ToJSON Properties
instance Aeson.FromJSON Properties
newtype Logbook = Logbook { unLogbook :: [Clock] }
deriving (Show, Eq, Generic, Semigroup, Monoid)
instance Aeson.ToJSON Logbook
instance Aeson.FromJSON Logbook
data Drawer = Drawer
{ name :: Text
, contents :: Text
} deriving (Show, Eq, Generic)
instance Aeson.ToJSON Drawer
instance Aeson.FromJSON Drawer
data ActiveState
= Active
| Inactive
deriving (Show, Eq, Read, Generic)
instance Aeson.ToJSON ActiveState
instance Aeson.FromJSON ActiveState
newtype Clock = Clock { unClock :: (Maybe Timestamp, Maybe Duration) }
deriving (Show, Eq, Generic)
instance Aeson.ToJSON Clock
instance Aeson.FromJSON Clock
data Timestamp = Timestamp
{ tsTime :: DateTime
, tsActive :: ActiveState
, tsEndTime :: Maybe DateTime
} deriving (Show, Eq, Generic)
instance Aeson.ToJSON Timestamp
instance Aeson.FromJSON Timestamp
instance Aeson.ToJSON YearMonthDay where
toJSON (YearMonthDay y m d) =
Aeson.object
[ "ymdYear" .= y
, "ymdMonth" .= m
, "ymdDay" .= d
]
instance Aeson.FromJSON YearMonthDay where
parseJSON (Aeson.Object v) = do
y <- v .: "ymdYear"
m <- v .: "ymdMonth"
d <- v .: "ymdDay"
pure (YearMonthDay y m d)
parseJSON _ = mzero
type Weekday = Text
type AbsTime = (Hours, Minutes)
data BracketedDateTime = BracketedDateTime
{ datePart :: YearMonthDay
, dayNamePart :: Maybe Weekday
, timePart :: Maybe TimePart
, repeat :: Maybe Repeater
, delayPart :: Maybe Delay
, activeState :: ActiveState
} deriving (Show, Eq)
data TimePart
= AbsoluteTime AbsTime
| TimeStampRange (AbsTime, AbsTime)
deriving (Eq, Ord, Show)
data DateTime = DateTime {
yearMonthDay :: YearMonthDay
, dayName :: Maybe Text
, hourMinute :: Maybe (Hour,Minute)
, repeater :: Maybe Repeater
, delay :: Maybe Delay
} deriving (Show, Eq, Generic)
instance Aeson.ToJSON DateTime
instance Aeson.FromJSON DateTime
data RepeaterType
= RepeatCumulate
| RepeatCatchUp
| RepeatRestart
deriving (Show, Eq, Generic)
instance Aeson.ToJSON RepeaterType
instance Aeson.FromJSON RepeaterType
data Repeater = Repeater
{ repeaterType :: RepeaterType
, repeaterValue :: Int
, repeaterUnit :: TimeUnit
} deriving (Show, Eq, Generic)
instance Aeson.ToJSON Repeater
instance Aeson.FromJSON Repeater
data DelayType
= DelayAll
| DelayFirst
deriving (Show, Eq, Generic)
instance Aeson.ToJSON DelayType
instance Aeson.FromJSON DelayType
data Delay = Delay
{ delayType :: DelayType
, delayValue :: Int
, delayUnit :: TimeUnit
} deriving (Show, Eq, Generic)
instance Aeson.ToJSON Delay
instance Aeson.FromJSON Delay
data TimeUnit
= UnitYear
| UnitWeek
| UnitMonth
| UnitDay
| UnitHour
deriving (Show, Eq, Generic)
instance Aeson.ToJSON TimeUnit
instance Aeson.FromJSON TimeUnit
newtype StateKeyword = StateKeyword {unStateKeyword :: Text}
deriving (Show, Eq, Generic)
instance Aeson.ToJSON StateKeyword
instance Aeson.FromJSON StateKeyword
data PlanningKeyword = SCHEDULED | DEADLINE | CLOSED
deriving (Show, Eq, Enum, Ord, Generic)
instance Aeson.ToJSON PlanningKeyword
instance Aeson.FromJSON PlanningKeyword
newtype Plannings = Plns (HashMap PlanningKeyword Timestamp)
deriving (Show, Eq, Generic)
instance Aeson.ToJSON Plannings where
toJSON (Plns hm) = Aeson.object $ map jPair (toList hm)
where jPair (k, v) = pack (show k) .= Aeson.toJSON v
instance Aeson.FromJSON Plannings where
parseJSON (Aeson.Object v) = Plns . fromList <$> traverse jPair (keys v)
where jPair k = v .: k
parseJSON _ = mzero
instance Aeson.ToJSON Section
instance Aeson.FromJSON Section
instance Aeson.ToJSON Headline
instance Aeson.FromJSON Headline
data Priority = A | B | C
deriving (Show, Read, Eq, Ord, Generic)
instance Aeson.ToJSON Priority
instance Aeson.FromJSON Priority
type Tag = Text
data Stats = StatsPct Int
| StatsOf Int Int
deriving (Show, Eq, Generic)
instance Aeson.ToJSON Stats
instance Aeson.FromJSON Stats
type Duration = (Hour,Minute)
instance Hashable PlanningKeyword where
hashWithSalt salt k = hashWithSalt salt (fromEnum k)