Skip to content

Commit

Permalink
X.P.OrgMode: More strictly enfore +s and +d ending with a space
Browse files Browse the repository at this point in the history
  • Loading branch information
slotThe committed Apr 27, 2024
1 parent cab938f commit 8efff53
Show file tree
Hide file tree
Showing 2 changed files with 9 additions and 2 deletions.
4 changes: 2 additions & 2 deletions XMonad/Prompt/OrgMode.hs
Expand Up @@ -514,8 +514,8 @@ ppNote clp todo = \case
-- | Parse the given string into a 'Note'.
pInput :: String -> Maybe Note
pInput inp = (`runParser` inp) . choice $
[ Scheduled <$> getLast "+s" <*> (Time <$> pDate <*> pOrgTime) <*> pPriority
, Deadline <$> getLast "+d" <*> (Time <$> pDate <*> pOrgTime) <*> pPriority
[ Scheduled <$> (getLast "+s" <* " ") <*> (Time <$> pDate <*> pOrgTime) <*> pPriority
, Deadline <$> (getLast "+d" <* " ") <*> (Time <$> pDate <*> pOrgTime) <*> pPriority
, do s <- munch1 (pure True)
let (s', p) = splitAt (length s - 3) s
pure $ case tryPrio p of
Expand Down
7 changes: 7 additions & 0 deletions tests/OrgMode.hs
Expand Up @@ -61,6 +61,13 @@ spec = do
`shouldBe` Just (Scheduled "todo" (Time {date = Today, tod = Just $ MomentInTime(HHMM 12 0)}) NoPriority)
pInput "todo +d 14:05 #B"
`shouldBe` Just (Deadline "todo" (Time {date = Today, tod = Just $ MomentInTime(HHMM 14 5)}) B)
it "parses `blah+d` and `blah +d` as normal messages, but `blah +d ` as a deadline for today" $ do
pInput "blah+d"
`shouldBe` Just (NormalMsg "blah+d" NoPriority)
pInput "blah +d"
`shouldBe` Just (NormalMsg "blah +d" NoPriority)
pInput "blah +d "
`shouldBe` Just (Deadline "blah" (Time {date = Today, tod = Nothing}) NoPriority)

context "no priority#b" $ do
it "parses to the correct thing" $
Expand Down

0 comments on commit 8efff53

Please sign in to comment.