{-# LANGUAGE OverloadedStrings #-}
module Text.ICalendar.Parser.Parameters where
import Control.Applicative
import Control.Monad (void, when)
import Control.Monad.Except
import Control.Monad.RWS (MonadWriter (tell))
import Data.ByteString.Lazy.Char8 (ByteString)
import qualified Data.ByteString.Lazy.Char8 as B
import Data.CaseInsensitive (CI)
import Data.Char
import Data.Default
import Data.Maybe
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as T
import Codec.MIME.Parse (parseMIMEType)
import Codec.MIME.Type (MIMEType, mimeType)
import qualified Text.Parsec as P
import Text.Parsec.Combinator hiding (optional)
import Text.Parsec.Perm
import Text.Parsec.Prim hiding ((<|>))
import Text.ICalendar.Parser.Common
import Text.ICalendar.Types
parseAlarmTriggerRelationship :: CI Text
-> ContentParser AlarmTriggerRelationship
parseAlarmTriggerRelationship :: CI Text -> ContentParser AlarmTriggerRelationship
parseAlarmTriggerRelationship CI Text
"START" = AlarmTriggerRelationship -> ContentParser AlarmTriggerRelationship
forall a.
a
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) a
forall (m :: * -> *) a. Monad m => a -> m a
return AlarmTriggerRelationship
Start
parseAlarmTriggerRelationship CI Text
"END" = AlarmTriggerRelationship -> ContentParser AlarmTriggerRelationship
forall a.
a
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) a
forall (m :: * -> *) a. Monad m => a -> m a
return AlarmTriggerRelationship
End
parseAlarmTriggerRelationship CI Text
x =
String -> ContentParser AlarmTriggerRelationship
forall a.
String
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (String -> ContentParser AlarmTriggerRelationship)
-> String -> ContentParser AlarmTriggerRelationship
forall a b. (a -> b) -> a -> b
$ String
"parseAlarmTriggerRelationship: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ CI Text -> String
forall a. Show a => a -> String
show CI Text
x
parseRelationshipType :: CI Text -> RelationshipType
parseRelationshipType :: CI Text -> RelationshipType
parseRelationshipType CI Text
"PARENT" = RelationshipType
Parent
parseRelationshipType CI Text
"CHILD" = RelationshipType
Child
parseRelationshipType CI Text
"SIBLING" = RelationshipType
Sibling
parseRelationshipType CI Text
x = CI Text -> RelationshipType
RelationshipTypeX CI Text
x
parseBool :: CI Text -> ContentParser Bool
parseBool :: CI Text -> ContentParser Bool
parseBool CI Text
"TRUE" = Bool -> ContentParser Bool
forall a.
a
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
parseBool CI Text
"FALSE" = Bool -> ContentParser Bool
forall a.
a
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
parseBool CI Text
x = String -> ContentParser Bool
forall a.
String
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (String -> ContentParser Bool) -> String -> ContentParser Bool
forall a b. (a -> b) -> a -> b
$ String
"parseBool: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ CI Text -> String
forall a. Show a => a -> String
show CI Text
x
parseRange :: CI Text -> ContentParser Range
parseRange :: CI Text -> ContentParser Range
parseRange CI Text
"THISANDFUTURE" = Range -> ContentParser Range
forall a.
a
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) a
forall (m :: * -> *) a. Monad m => a -> m a
return Range
ThisAndFuture
parseRange CI Text
"THISANDPRIOR" = do [String]
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell [String
"THISANDPRIOIR RANGE is deprecated."]
Range -> ContentParser Range
forall a.
a
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) a
forall (m :: * -> *) a. Monad m => a -> m a
return Range
ThisAndPrior
parseRange CI Text
x = String -> ContentParser Range
forall a.
String
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (String -> ContentParser Range) -> String -> ContentParser Range
forall a b. (a -> b) -> a -> b
$ String
"parseRange: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ CI Text -> String
forall a. Show a => a -> String
show CI Text
x
parseFBType :: CI Text -> FBType
parseFBType :: CI Text -> FBType
parseFBType CI Text
"FREE" = FBType
Free
parseFBType CI Text
"BUSY" = FBType
Busy
parseFBType CI Text
"BUSY-UNAVAILABLE" = FBType
BusyUnavailable
parseFBType CI Text
"BUSY-TENTATIVE" = FBType
BusyTentative
parseFBType CI Text
x = CI Text -> FBType
FBTypeX CI Text
x
parsePartStat :: CI Text -> PartStat
parsePartStat :: CI Text -> PartStat
parsePartStat CI Text
"NEEDS-ACTION" = PartStat
PartStatNeedsAction
parsePartStat CI Text
"ACCEPTED" = PartStat
Accepted
parsePartStat CI Text
"DECLINED" = PartStat
Declined
parsePartStat CI Text
"TENTATIVE" = PartStat
Tentative
parsePartStat CI Text
"DELEGATED" = PartStat
Delegated
parsePartStat CI Text
"COMPLETED" = PartStat
PartStatCompleted
parsePartStat CI Text
"IN-PROCESS" = PartStat
InProcess
parsePartStat CI Text
x = CI Text -> PartStat
PartStatX CI Text
x
parseRole :: CI Text -> Role
parseRole :: CI Text -> Role
parseRole CI Text
"CHAIR" = Role
Chair
parseRole CI Text
"REQ-PARTICIPANT" = Role
ReqParticipant
parseRole CI Text
"OPT-PARTICIPANT" = Role
OptParticipant
parseRole CI Text
"NON-PARTICIPANT" = Role
NonParticipant
parseRole CI Text
x = CI Text -> Role
RoleX CI Text
x
parseCUType :: CI Text -> CUType
parseCUType :: CI Text -> CUType
parseCUType CI Text
"INDIVIDUAL" = CUType
Individual
parseCUType CI Text
"GROUP" = CUType
Group
parseCUType CI Text
"RESOURCE" = CUType
Resource
parseCUType CI Text
"ROOM" = CUType
Room
parseCUType CI Text
"UNKNOWN" = CUType
Unknown
parseCUType CI Text
x = CI Text -> CUType
CUTypeX CI Text
x
parseMime :: Text -> ContentParser MIMEType
parseMime :: Text -> ContentParser MIMEType
parseMime Text
t = let m :: Maybe MIMEType
m = Type -> MIMEType
mimeType (Type -> MIMEType)
-> (Text -> Maybe Type) -> Text -> Maybe MIMEType
forall (f :: * -> *) (g :: * -> *) a b.
(Functor f, Functor g) =>
(a -> b) -> f (g a) -> f (g b)
.: Text -> Maybe Type
parseMIMEType (Text -> Maybe MIMEType) -> Text -> Maybe MIMEType
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.toStrict Text
t
in ContentParser MIMEType
-> (MIMEType -> ContentParser MIMEType)
-> Maybe MIMEType
-> ContentParser MIMEType
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> ContentParser MIMEType
forall a.
String
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (String -> ContentParser MIMEType)
-> String -> ContentParser MIMEType
forall a b. (a -> b) -> a -> b
$ String
"parseMime: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
t) MIMEType -> ContentParser MIMEType
forall a.
a
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MIMEType
m
parseDuration :: String
-> ByteString
-> ContentParser Duration
parseDuration :: String -> ByteString -> ContentParser Duration
parseDuration String
what ByteString
bs =
case Parsec ByteString DecodingFunctions Duration
-> DecodingFunctions
-> String
-> ByteString
-> Either ParseError Duration
forall s t u a.
Stream s Identity t =>
Parsec s u a -> u -> String -> s -> Either ParseError a
runParser Parsec ByteString DecodingFunctions Duration
dur DecodingFunctions
forall a. Default a => a
def String
what ByteString
bs of
Left ParseError
e -> String -> ContentParser Duration
forall a.
String
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (String -> ContentParser Duration)
-> String -> ContentParser Duration
forall a b. (a -> b) -> a -> b
$ String
"Invalid duration: "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
unlines [ByteString -> String
forall a. Show a => a -> String
show ByteString
bs, ParseError -> String
forall a. Show a => a -> String
show ParseError
e]
Right Duration
x -> Duration -> ContentParser Duration
forall a.
a
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) a
forall (m :: * -> *) a. Monad m => a -> m a
return Duration
x
where dur :: Parsec ByteString DecodingFunctions Duration
dur = do Sign
si <- ParsecT ByteString DecodingFunctions Identity Sign
forall {u}. ParsecT ByteString u Identity Sign
sign
Char
_ <- Char -> ParsecT ByteString DecodingFunctions Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
'P'
Maybe Int
day <- ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int))
-> (ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Int)
-> ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int))
-> ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int)
forall a b. (a -> b) -> a -> b
$ ParsecT ByteString DecodingFunctions Identity Int
digits ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Char
-> ParsecT ByteString DecodingFunctions Identity Int
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT ByteString DecodingFunctions Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
'D'
Maybe (Maybe Int, Maybe Int, Maybe Int)
time <- ParsecT
ByteString
DecodingFunctions
Identity
(Maybe Int, Maybe Int, Maybe Int)
-> ParsecT
ByteString
DecodingFunctions
Identity
(Maybe (Maybe Int, Maybe Int, Maybe Int))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT
ByteString
DecodingFunctions
Identity
(Maybe Int, Maybe Int, Maybe Int)
-> ParsecT
ByteString
DecodingFunctions
Identity
(Maybe (Maybe Int, Maybe Int, Maybe Int)))
-> ParsecT
ByteString
DecodingFunctions
Identity
(Maybe Int, Maybe Int, Maybe Int)
-> ParsecT
ByteString
DecodingFunctions
Identity
(Maybe (Maybe Int, Maybe Int, Maybe Int))
forall a b. (a -> b) -> a -> b
$ do
Char
_ <- Char -> ParsecT ByteString DecodingFunctions Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
'T'
Maybe Int
h <- ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int))
-> (ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Int)
-> ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int))
-> ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int)
forall a b. (a -> b) -> a -> b
$ ParsecT ByteString DecodingFunctions Identity Int
digits ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Char
-> ParsecT ByteString DecodingFunctions Identity Int
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT ByteString DecodingFunctions Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
'H'
Maybe Int
m <- ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int))
-> (ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Int)
-> ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int))
-> ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int)
forall a b. (a -> b) -> a -> b
$ ParsecT ByteString DecodingFunctions Identity Int
digits ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Char
-> ParsecT ByteString DecodingFunctions Identity Int
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT ByteString DecodingFunctions Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
'M'
Maybe Int
s <- ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int))
-> (ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Int)
-> ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int))
-> ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int)
forall a b. (a -> b) -> a -> b
$ ParsecT ByteString DecodingFunctions Identity Int
digits ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Char
-> ParsecT ByteString DecodingFunctions Identity Int
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT ByteString DecodingFunctions Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
'S'
(Maybe Int, Maybe Int, Maybe Int)
-> ParsecT
ByteString
DecodingFunctions
Identity
(Maybe Int, Maybe Int, Maybe Int)
forall a. a -> ParsecT ByteString DecodingFunctions Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Int
h, Maybe Int
m, Maybe Int
s)
Maybe Int
week <- ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int))
-> (ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Int)
-> ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int))
-> ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Int)
forall a b. (a -> b) -> a -> b
$ ParsecT ByteString DecodingFunctions Identity Int
digits ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Char
-> ParsecT ByteString DecodingFunctions Identity Int
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT ByteString DecodingFunctions Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
'W'
ParsecT ByteString DecodingFunctions Identity ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
P.eof
case (Maybe Int
day, Maybe (Maybe Int, Maybe Int, Maybe Int)
time, Maybe Int
week) of
(Just Int
d, Maybe (Maybe Int, Maybe Int, Maybe Int)
x, Maybe Int
Nothing) ->
let (Int
h, Int
m, Int
s) = Maybe (Maybe Int, Maybe Int, Maybe Int) -> (Int, Int, Int)
forall {a} {b} {c}.
(Num a, Num b, Num c) =>
Maybe (Maybe a, Maybe b, Maybe c) -> (a, b, c)
deMHms Maybe (Maybe Int, Maybe Int, Maybe Int)
x
in Duration -> Parsec ByteString DecodingFunctions Duration
forall a. a -> ParsecT ByteString DecodingFunctions Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Duration -> Parsec ByteString DecodingFunctions Duration)
-> Duration -> Parsec ByteString DecodingFunctions Duration
forall a b. (a -> b) -> a -> b
$ Sign -> Int -> Int -> Int -> Int -> Duration
DurationDate Sign
si Int
d Int
h Int
m Int
s
(Maybe Int
Nothing, x :: Maybe (Maybe Int, Maybe Int, Maybe Int)
x@(Just (Maybe Int, Maybe Int, Maybe Int)
_), Maybe Int
Nothing) ->
let (Int
h, Int
m, Int
s) = Maybe (Maybe Int, Maybe Int, Maybe Int) -> (Int, Int, Int)
forall {a} {b} {c}.
(Num a, Num b, Num c) =>
Maybe (Maybe a, Maybe b, Maybe c) -> (a, b, c)
deMHms Maybe (Maybe Int, Maybe Int, Maybe Int)
x
in Duration -> Parsec ByteString DecodingFunctions Duration
forall a. a -> ParsecT ByteString DecodingFunctions Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Duration -> Parsec ByteString DecodingFunctions Duration)
-> Duration -> Parsec ByteString DecodingFunctions Duration
forall a b. (a -> b) -> a -> b
$ Sign -> Int -> Int -> Int -> Duration
DurationTime Sign
si Int
h Int
m Int
s
(Maybe Int
Nothing, Maybe (Maybe Int, Maybe Int, Maybe Int)
Nothing, Just Int
w) ->
Duration -> Parsec ByteString DecodingFunctions Duration
forall a. a -> ParsecT ByteString DecodingFunctions Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Duration -> Parsec ByteString DecodingFunctions Duration)
-> Duration -> Parsec ByteString DecodingFunctions Duration
forall a b. (a -> b) -> a -> b
$ Sign -> Int -> Duration
DurationWeek Sign
si Int
w
(Maybe Int
_, Maybe (Maybe Int, Maybe Int, Maybe Int)
_, Maybe Int
_) -> String -> Parsec ByteString DecodingFunctions Duration
forall a. String -> ParsecT ByteString DecodingFunctions Identity a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Invalid."
sign :: ParsecT ByteString u Identity Sign
sign = Sign -> Maybe Sign -> Sign
forall a. a -> Maybe a -> a
fromMaybe Sign
Positive (Maybe Sign -> Sign)
-> ParsecT ByteString u Identity (Maybe Sign)
-> ParsecT ByteString u Identity Sign
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT ByteString u Identity Sign
-> ParsecT ByteString u Identity (Maybe Sign)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Sign
Positive Sign
-> ParsecT ByteString u Identity Char
-> ParsecT ByteString u Identity Sign
forall a b.
a
-> ParsecT ByteString u Identity b
-> ParsecT ByteString u Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT ByteString u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
'+'
ParsecT ByteString u Identity Sign
-> ParsecT ByteString u Identity Sign
-> ParsecT ByteString u Identity Sign
forall a.
ParsecT ByteString u Identity a
-> ParsecT ByteString u Identity a
-> ParsecT ByteString u Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Sign
Negative Sign
-> ParsecT ByteString u Identity Char
-> ParsecT ByteString u Identity Sign
forall a b.
a
-> ParsecT ByteString u Identity b
-> ParsecT ByteString u Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT ByteString u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
'-')
deMHms :: Maybe (Maybe a, Maybe b, Maybe c) -> (a, b, c)
deMHms (Just (Maybe a
h, Maybe b
m, Maybe c
s)) = (a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe a
0 Maybe a
h, b -> Maybe b -> b
forall a. a -> Maybe a -> a
fromMaybe b
0 Maybe b
m, c -> Maybe c -> c
forall a. a -> Maybe a -> a
fromMaybe c
0 Maybe c
s)
deMHms Maybe (Maybe a, Maybe b, Maybe c)
Nothing = (a
0, b
0, c
0)
parseRecur :: DTStart -> TextParser (ContentParser Recur)
parseRecur :: DTStart -> TextParser (ContentParser Recur)
parseRecur DTStart
dts =
StreamPermParser ByteString DecodingFunctions (ContentParser Recur)
-> TextParser (ContentParser Recur)
forall s tok st a.
Stream s Identity tok =>
StreamPermParser s st a -> Parsec s st a
permute (Frequency
-> Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int)
-> Int
-> [Int]
-> [Int]
-> [Int]
-> [Either (Int, Weekday) Weekday]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> ContentParser Recur
forall {m :: * -> *}.
Monad m =>
Frequency
-> Maybe (Either (m (Either Date DateTime)) Int)
-> Int
-> [Int]
-> [Int]
-> [Int]
-> [Either (Int, Weekday) Weekday]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> m Recur
mkRecur (Frequency
-> Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int)
-> Int
-> [Int]
-> [Int]
-> [Int]
-> [Either (Int, Weekday) Weekday]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> ContentParser Recur)
-> Parsec ByteString DecodingFunctions Frequency
-> StreamPermParser
ByteString
DecodingFunctions
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int)
-> Int
-> [Int]
-> [Int]
-> [Int]
-> [Either (Int, Weekday) Weekday]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> ContentParser Recur)
forall s tok a b st.
Stream s Identity tok =>
(a -> b) -> Parsec s st a -> StreamPermParser s st b
<$$> (Parsec ByteString DecodingFunctions Frequency
freq Parsec ByteString DecodingFunctions Frequency
-> ParsecT ByteString DecodingFunctions Identity (Maybe Char)
-> Parsec ByteString DecodingFunctions Frequency
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT ByteString DecodingFunctions Identity (Maybe Char)
forall {u}. ParsecT ByteString u Identity (Maybe Char)
term)
StreamPermParser
ByteString
DecodingFunctions
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int)
-> Int
-> [Int]
-> [Int]
-> [Int]
-> [Either (Int, Weekday) Weekday]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> ContentParser Recur)
-> (Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int),
Parsec
ByteString
DecodingFunctions
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int)))
-> StreamPermParser
ByteString
DecodingFunctions
(Int
-> [Int]
-> [Int]
-> [Int]
-> [Either (Int, Weekday) Weekday]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> ContentParser Recur)
forall s tok st a b.
Stream s Identity tok =>
StreamPermParser s st (a -> b)
-> (a, Parsec s st a) -> StreamPermParser s st b
<|?> (Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int)
forall a. Maybe a
Nothing, Parsec
ByteString
DecodingFunctions
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int))
untilCount Parsec
ByteString
DecodingFunctions
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int))
-> ParsecT ByteString DecodingFunctions Identity (Maybe Char)
-> Parsec
ByteString
DecodingFunctions
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int))
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT ByteString DecodingFunctions Identity (Maybe Char)
forall {u}. ParsecT ByteString u Identity (Maybe Char)
term)
StreamPermParser
ByteString
DecodingFunctions
(Int
-> [Int]
-> [Int]
-> [Int]
-> [Either (Int, Weekday) Weekday]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> ContentParser Recur)
-> (Int, ParsecT ByteString DecodingFunctions Identity Int)
-> StreamPermParser
ByteString
DecodingFunctions
([Int]
-> [Int]
-> [Int]
-> [Either (Int, Weekday) Weekday]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> ContentParser Recur)
forall s tok st a b.
Stream s Identity tok =>
StreamPermParser s st (a -> b)
-> (a, Parsec s st a) -> StreamPermParser s st b
<|?> (Int
1, String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"INTERVAL=" ParsecT ByteString DecodingFunctions Identity ()
-> ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Int
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT ByteString DecodingFunctions Identity Int
digits ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity (Maybe Char)
-> ParsecT ByteString DecodingFunctions Identity Int
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT ByteString DecodingFunctions Identity (Maybe Char)
forall {u}. ParsecT ByteString u Identity (Maybe Char)
term)
StreamPermParser
ByteString
DecodingFunctions
([Int]
-> [Int]
-> [Int]
-> [Either (Int, Weekday) Weekday]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> ContentParser Recur)
-> ([Int], Parsec ByteString DecodingFunctions [Int])
-> StreamPermParser
ByteString
DecodingFunctions
([Int]
-> [Int]
-> [Either (Int, Weekday) Weekday]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> ContentParser Recur)
forall s tok st a b.
Stream s Identity tok =>
StreamPermParser s st (a -> b)
-> (a, Parsec s st a) -> StreamPermParser s st b
<|?> ([], String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"BYSECOND=" ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions [Int]
-> Parsec ByteString DecodingFunctions [Int]
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec ByteString DecodingFunctions [Int]
digitsN Parsec ByteString DecodingFunctions [Int]
-> ParsecT ByteString DecodingFunctions Identity (Maybe Char)
-> Parsec ByteString DecodingFunctions [Int]
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT ByteString DecodingFunctions Identity (Maybe Char)
forall {u}. ParsecT ByteString u Identity (Maybe Char)
term)
StreamPermParser
ByteString
DecodingFunctions
([Int]
-> [Int]
-> [Either (Int, Weekday) Weekday]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> ContentParser Recur)
-> ([Int], Parsec ByteString DecodingFunctions [Int])
-> StreamPermParser
ByteString
DecodingFunctions
([Int]
-> [Either (Int, Weekday) Weekday]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> ContentParser Recur)
forall s tok st a b.
Stream s Identity tok =>
StreamPermParser s st (a -> b)
-> (a, Parsec s st a) -> StreamPermParser s st b
<|?> ([], String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"BYMINUTE=" ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions [Int]
-> Parsec ByteString DecodingFunctions [Int]
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec ByteString DecodingFunctions [Int]
digitsN Parsec ByteString DecodingFunctions [Int]
-> ParsecT ByteString DecodingFunctions Identity (Maybe Char)
-> Parsec ByteString DecodingFunctions [Int]
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT ByteString DecodingFunctions Identity (Maybe Char)
forall {u}. ParsecT ByteString u Identity (Maybe Char)
term)
StreamPermParser
ByteString
DecodingFunctions
([Int]
-> [Either (Int, Weekday) Weekday]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> ContentParser Recur)
-> ([Int], Parsec ByteString DecodingFunctions [Int])
-> StreamPermParser
ByteString
DecodingFunctions
([Either (Int, Weekday) Weekday]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> ContentParser Recur)
forall s tok st a b.
Stream s Identity tok =>
StreamPermParser s st (a -> b)
-> (a, Parsec s st a) -> StreamPermParser s st b
<|?> ([], String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"BYHOUR=" ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions [Int]
-> Parsec ByteString DecodingFunctions [Int]
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec ByteString DecodingFunctions [Int]
digitsN Parsec ByteString DecodingFunctions [Int]
-> ParsecT ByteString DecodingFunctions Identity (Maybe Char)
-> Parsec ByteString DecodingFunctions [Int]
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT ByteString DecodingFunctions Identity (Maybe Char)
forall {u}. ParsecT ByteString u Identity (Maybe Char)
term)
StreamPermParser
ByteString
DecodingFunctions
([Either (Int, Weekday) Weekday]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> ContentParser Recur)
-> ([Either (Int, Weekday) Weekday],
Parsec
ByteString DecodingFunctions [Either (Int, Weekday) Weekday])
-> StreamPermParser
ByteString
DecodingFunctions
([Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> ContentParser Recur)
forall s tok st a b.
Stream s Identity tok =>
StreamPermParser s st (a -> b)
-> (a, Parsec s st a) -> StreamPermParser s st b
<|?> ([], String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"BYDAY=" ParsecT ByteString DecodingFunctions Identity ()
-> Parsec
ByteString DecodingFunctions [Either (Int, Weekday) Weekday]
-> Parsec
ByteString DecodingFunctions [Either (Int, Weekday) Weekday]
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT
ByteString
DecodingFunctions
Identity
(Either (Int, Weekday) Weekday)
-> ParsecT ByteString DecodingFunctions Identity Char
-> Parsec
ByteString DecodingFunctions [Either (Int, Weekday) Weekday]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepBy ParsecT
ByteString
DecodingFunctions
Identity
(Either (Int, Weekday) Weekday)
wday (Char -> ParsecT ByteString DecodingFunctions Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
',')
Parsec ByteString DecodingFunctions [Either (Int, Weekday) Weekday]
-> ParsecT ByteString DecodingFunctions Identity (Maybe Char)
-> Parsec
ByteString DecodingFunctions [Either (Int, Weekday) Weekday]
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT ByteString DecodingFunctions Identity (Maybe Char)
forall {u}. ParsecT ByteString u Identity (Maybe Char)
term)
StreamPermParser
ByteString
DecodingFunctions
([Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> ContentParser Recur)
-> ([Int], Parsec ByteString DecodingFunctions [Int])
-> StreamPermParser
ByteString
DecodingFunctions
([Int]
-> [Int] -> [Int] -> [Int] -> Weekday -> ContentParser Recur)
forall s tok st a b.
Stream s Identity tok =>
StreamPermParser s st (a -> b)
-> (a, Parsec s st a) -> StreamPermParser s st b
<|?> ([], String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"BYMONTHDAY=" ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions [Int]
-> Parsec ByteString DecodingFunctions [Int]
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec ByteString DecodingFunctions [Int]
onum Parsec ByteString DecodingFunctions [Int]
-> ParsecT ByteString DecodingFunctions Identity (Maybe Char)
-> Parsec ByteString DecodingFunctions [Int]
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT ByteString DecodingFunctions Identity (Maybe Char)
forall {u}. ParsecT ByteString u Identity (Maybe Char)
term)
StreamPermParser
ByteString
DecodingFunctions
([Int]
-> [Int] -> [Int] -> [Int] -> Weekday -> ContentParser Recur)
-> ([Int], Parsec ByteString DecodingFunctions [Int])
-> StreamPermParser
ByteString
DecodingFunctions
([Int] -> [Int] -> [Int] -> Weekday -> ContentParser Recur)
forall s tok st a b.
Stream s Identity tok =>
StreamPermParser s st (a -> b)
-> (a, Parsec s st a) -> StreamPermParser s st b
<|?> ([], String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"BYYEARDAY=" ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions [Int]
-> Parsec ByteString DecodingFunctions [Int]
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec ByteString DecodingFunctions [Int]
onum Parsec ByteString DecodingFunctions [Int]
-> ParsecT ByteString DecodingFunctions Identity (Maybe Char)
-> Parsec ByteString DecodingFunctions [Int]
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT ByteString DecodingFunctions Identity (Maybe Char)
forall {u}. ParsecT ByteString u Identity (Maybe Char)
term)
StreamPermParser
ByteString
DecodingFunctions
([Int] -> [Int] -> [Int] -> Weekday -> ContentParser Recur)
-> ([Int], Parsec ByteString DecodingFunctions [Int])
-> StreamPermParser
ByteString
DecodingFunctions
([Int] -> [Int] -> Weekday -> ContentParser Recur)
forall s tok st a b.
Stream s Identity tok =>
StreamPermParser s st (a -> b)
-> (a, Parsec s st a) -> StreamPermParser s st b
<|?> ([], String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"BYWEEKNO=" ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions [Int]
-> Parsec ByteString DecodingFunctions [Int]
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec ByteString DecodingFunctions [Int]
onum Parsec ByteString DecodingFunctions [Int]
-> ParsecT ByteString DecodingFunctions Identity (Maybe Char)
-> Parsec ByteString DecodingFunctions [Int]
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT ByteString DecodingFunctions Identity (Maybe Char)
forall {u}. ParsecT ByteString u Identity (Maybe Char)
term)
StreamPermParser
ByteString
DecodingFunctions
([Int] -> [Int] -> Weekday -> ContentParser Recur)
-> ([Int], Parsec ByteString DecodingFunctions [Int])
-> StreamPermParser
ByteString
DecodingFunctions
([Int] -> Weekday -> ContentParser Recur)
forall s tok st a b.
Stream s Identity tok =>
StreamPermParser s st (a -> b)
-> (a, Parsec s st a) -> StreamPermParser s st b
<|?> ([], String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"BYMONTH=" ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions [Int]
-> Parsec ByteString DecodingFunctions [Int]
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec ByteString DecodingFunctions [Int]
digitsN Parsec ByteString DecodingFunctions [Int]
-> ParsecT ByteString DecodingFunctions Identity (Maybe Char)
-> Parsec ByteString DecodingFunctions [Int]
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT ByteString DecodingFunctions Identity (Maybe Char)
forall {u}. ParsecT ByteString u Identity (Maybe Char)
term)
StreamPermParser
ByteString
DecodingFunctions
([Int] -> Weekday -> ContentParser Recur)
-> ([Int], Parsec ByteString DecodingFunctions [Int])
-> StreamPermParser
ByteString DecodingFunctions (Weekday -> ContentParser Recur)
forall s tok st a b.
Stream s Identity tok =>
StreamPermParser s st (a -> b)
-> (a, Parsec s st a) -> StreamPermParser s st b
<|?> ([], String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"BYSETPOS=" ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions [Int]
-> Parsec ByteString DecodingFunctions [Int]
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec ByteString DecodingFunctions [Int]
onum Parsec ByteString DecodingFunctions [Int]
-> ParsecT ByteString DecodingFunctions Identity (Maybe Char)
-> Parsec ByteString DecodingFunctions [Int]
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT ByteString DecodingFunctions Identity (Maybe Char)
forall {u}. ParsecT ByteString u Identity (Maybe Char)
term)
StreamPermParser
ByteString DecodingFunctions (Weekday -> ContentParser Recur)
-> (Weekday, Parsec ByteString DecodingFunctions Weekday)
-> StreamPermParser
ByteString DecodingFunctions (ContentParser Recur)
forall s tok st a b.
Stream s Identity tok =>
StreamPermParser s st (a -> b)
-> (a, Parsec s st a) -> StreamPermParser s st b
<|?> (Weekday
Monday, String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"WKST=" ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions Weekday
-> Parsec ByteString DecodingFunctions Weekday
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec ByteString DecodingFunctions Weekday
weekday Parsec ByteString DecodingFunctions Weekday
-> ParsecT ByteString DecodingFunctions Identity (Maybe Char)
-> Parsec ByteString DecodingFunctions Weekday
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT ByteString DecodingFunctions Identity (Maybe Char)
forall {u}. ParsecT ByteString u Identity (Maybe Char)
term))
TextParser (ContentParser Recur)
-> ParsecT ByteString DecodingFunctions Identity ()
-> TextParser (ContentParser Recur)
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT ByteString DecodingFunctions Identity ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
P.eof
where freq :: Parsec ByteString DecodingFunctions Frequency
freq = String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"FREQ=" ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions Frequency
-> Parsec ByteString DecodingFunctions Frequency
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec ByteString DecodingFunctions Frequency
frequency
frequency :: Parsec ByteString DecodingFunctions Frequency
frequency = Frequency
Secondly Frequency
-> ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions Frequency
forall a b.
a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"SECONDLY"
Parsec ByteString DecodingFunctions Frequency
-> Parsec ByteString DecodingFunctions Frequency
-> Parsec ByteString DecodingFunctions Frequency
forall a.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Frequency
Minutely Frequency
-> ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions Frequency
forall a b.
a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"MINUTELY"
Parsec ByteString DecodingFunctions Frequency
-> Parsec ByteString DecodingFunctions Frequency
-> Parsec ByteString DecodingFunctions Frequency
forall a.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Frequency
Hourly Frequency
-> ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions Frequency
forall a b.
a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"HOURLY"
Parsec ByteString DecodingFunctions Frequency
-> Parsec ByteString DecodingFunctions Frequency
-> Parsec ByteString DecodingFunctions Frequency
forall a.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Frequency
Daily Frequency
-> ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions Frequency
forall a b.
a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"DAILY"
Parsec ByteString DecodingFunctions Frequency
-> Parsec ByteString DecodingFunctions Frequency
-> Parsec ByteString DecodingFunctions Frequency
forall a.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Frequency
Weekly Frequency
-> ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions Frequency
forall a b.
a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"WEEKLY"
Parsec ByteString DecodingFunctions Frequency
-> Parsec ByteString DecodingFunctions Frequency
-> Parsec ByteString DecodingFunctions Frequency
forall a.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Frequency
Monthly Frequency
-> ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions Frequency
forall a b.
a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"MONTHLY"
Parsec ByteString DecodingFunctions Frequency
-> Parsec ByteString DecodingFunctions Frequency
-> Parsec ByteString DecodingFunctions Frequency
forall a.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Frequency
Yearly Frequency
-> ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions Frequency
forall a b.
a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"YEARLY"
weekday :: Parsec ByteString DecodingFunctions Weekday
weekday = Weekday
Sunday Weekday
-> ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions Weekday
forall a b.
a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"SU"
Parsec ByteString DecodingFunctions Weekday
-> Parsec ByteString DecodingFunctions Weekday
-> Parsec ByteString DecodingFunctions Weekday
forall a.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Weekday
Monday Weekday
-> ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions Weekday
forall a b.
a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"MO"
Parsec ByteString DecodingFunctions Weekday
-> Parsec ByteString DecodingFunctions Weekday
-> Parsec ByteString DecodingFunctions Weekday
forall a.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Weekday
Tuesday Weekday
-> ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions Weekday
forall a b.
a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"TU"
Parsec ByteString DecodingFunctions Weekday
-> Parsec ByteString DecodingFunctions Weekday
-> Parsec ByteString DecodingFunctions Weekday
forall a.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Weekday
Wednesday Weekday
-> ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions Weekday
forall a b.
a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"WE"
Parsec ByteString DecodingFunctions Weekday
-> Parsec ByteString DecodingFunctions Weekday
-> Parsec ByteString DecodingFunctions Weekday
forall a.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Weekday
Thursday Weekday
-> ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions Weekday
forall a b.
a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"TH"
Parsec ByteString DecodingFunctions Weekday
-> Parsec ByteString DecodingFunctions Weekday
-> Parsec ByteString DecodingFunctions Weekday
forall a.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Weekday
Friday Weekday
-> ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions Weekday
forall a b.
a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"FR"
Parsec ByteString DecodingFunctions Weekday
-> Parsec ByteString DecodingFunctions Weekday
-> Parsec ByteString DecodingFunctions Weekday
forall a.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Weekday
Saturday Weekday
-> ParsecT ByteString DecodingFunctions Identity ()
-> Parsec ByteString DecodingFunctions Weekday
forall a b.
a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"SA"
wday :: ParsecT
ByteString
DecodingFunctions
Identity
(Either (Int, Weekday) Weekday)
wday = Weekday -> Either (Int, Weekday) Weekday
forall a b. b -> Either a b
Right (Weekday -> Either (Int, Weekday) Weekday)
-> Parsec ByteString DecodingFunctions Weekday
-> ParsecT
ByteString
DecodingFunctions
Identity
(Either (Int, Weekday) Weekday)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parsec ByteString DecodingFunctions Weekday
weekday
ParsecT
ByteString
DecodingFunctions
Identity
(Either (Int, Weekday) Weekday)
-> ParsecT
ByteString
DecodingFunctions
Identity
(Either (Int, Weekday) Weekday)
-> ParsecT
ByteString
DecodingFunctions
Identity
(Either (Int, Weekday) Weekday)
forall a.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((Int, Weekday) -> Either (Int, Weekday) Weekday
forall a b. a -> Either a b
Left ((Int, Weekday) -> Either (Int, Weekday) Weekday)
-> (Weekday -> (Int, Weekday))
-> Weekday
-> Either (Int, Weekday) Weekday
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Weekday -> (Int, Weekday))
-> Weekday -> Either (Int, Weekday) Weekday)
-> (Int -> Weekday -> (Int, Weekday))
-> Int
-> Weekday
-> Either (Int, Weekday) Weekday
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,) (Int -> Weekday -> Either (Int, Weekday) Weekday)
-> ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT
ByteString
DecodingFunctions
Identity
(Weekday -> Either (Int, Weekday) Weekday)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TextParser (Int -> Int)
neg TextParser (Int -> Int)
-> ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Int
forall a b.
ParsecT ByteString DecodingFunctions Identity (a -> b)
-> ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT ByteString DecodingFunctions Identity Int
digits) ParsecT
ByteString
DecodingFunctions
Identity
(Weekday -> Either (Int, Weekday) Weekday)
-> Parsec ByteString DecodingFunctions Weekday
-> ParsecT
ByteString
DecodingFunctions
Identity
(Either (Int, Weekday) Weekday)
forall a b.
ParsecT ByteString DecodingFunctions Identity (a -> b)
-> ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parsec ByteString DecodingFunctions Weekday
weekday
onum :: Parsec ByteString DecodingFunctions [Int]
onum = ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Char
-> Parsec ByteString DecodingFunctions [Int]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepBy1 (TextParser (Int -> Int)
neg TextParser (Int -> Int)
-> ParsecT ByteString DecodingFunctions Identity Int
-> ParsecT ByteString DecodingFunctions Identity Int
forall a b.
ParsecT ByteString DecodingFunctions Identity (a -> b)
-> ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT ByteString DecodingFunctions Identity Int
digits) (Char -> ParsecT ByteString DecodingFunctions Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
',')
untilCount :: Parsec
ByteString
DecodingFunctions
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int))
untilCount = String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"UNTIL=" ParsecT ByteString DecodingFunctions Identity ()
-> Parsec
ByteString
DecodingFunctions
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int))
-> Parsec
ByteString
DecodingFunctions
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int))
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec
ByteString
DecodingFunctions
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int))
forall {u} {b}.
ParsecT
ByteString
u
Identity
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
b))
until'
Parsec
ByteString
DecodingFunctions
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int))
-> Parsec
ByteString
DecodingFunctions
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int))
-> Parsec
ByteString
DecodingFunctions
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int))
forall a.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> String -> ParsecT ByteString DecodingFunctions Identity ()
istring String
"COUNT=" ParsecT ByteString DecodingFunctions Identity ()
-> Parsec
ByteString
DecodingFunctions
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int))
-> Parsec
ByteString
DecodingFunctions
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int))
forall a b.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity b
-> ParsecT ByteString DecodingFunctions Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int
-> Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int)
forall a. a -> Maybe a
Just (Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int
-> Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int))
-> (Int
-> Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int)
-> Int
-> Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int
-> Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int
forall a b. b -> Either a b
Right (Int
-> Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int))
-> ParsecT ByteString DecodingFunctions Identity Int
-> Parsec
ByteString
DecodingFunctions
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
Int))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT ByteString DecodingFunctions Identity Int
digits)
until' :: ParsecT
ByteString
u
Identity
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
b))
until' = do String
txt <- ParsecT ByteString u Identity Char
-> ParsecT ByteString u Identity ()
-> ParsecT ByteString u Identity String
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill ParsecT ByteString u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
P.anyChar (ParsecT ByteString u Identity Char
-> ParsecT ByteString u Identity ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Char -> ParsecT ByteString u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
';') ParsecT ByteString u Identity ()
-> ParsecT ByteString u Identity ()
-> ParsecT ByteString u Identity ()
forall a.
ParsecT ByteString u Identity a
-> ParsecT ByteString u Identity a
-> ParsecT ByteString u Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT ByteString u Identity ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
P.eof)
Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
b)
-> ParsecT
ByteString
u
Identity
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
b))
forall a. a -> ParsecT ByteString u Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
b)
-> ParsecT
ByteString
u
Identity
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
b)))
-> (ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime)
-> Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
b))
-> ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime)
-> ParsecT
ByteString
u
Identity
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
b
-> Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
b)
forall a. a -> Maybe a
Just (Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
b
-> Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
b))
-> (ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime)
-> Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
b)
-> ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime)
-> Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime)
-> Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
b
forall a b. a -> Either a b
Left (ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime)
-> ParsecT
ByteString
u
Identity
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
b)))
-> ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime)
-> ParsecT
ByteString
u
Identity
(Maybe
(Either
(ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime))
b))
forall a b. (a -> b) -> a -> b
$
case DTStart
dts of
DTStartDateTime DateTime
_ OtherParams
_ ->
DateTime -> Either Date DateTime
forall a b. b -> Either a b
Right (DateTime -> Either Date DateTime)
-> ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
DateTime
-> ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
-> ByteString
-> ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
DateTime
parseDateTime Maybe Text
forall a. Maybe a
Nothing (String -> ByteString
B.pack String
txt)
DTStartDate Date
_ OtherParams
_ ->
Date -> Either Date DateTime
forall a b. a -> Either a b
Left (Date -> Either Date DateTime)
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) Date
-> ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
(Either Date DateTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) Date
parseDate (String -> ByteString
B.pack String
txt)
term :: ParsecT ByteString u Identity (Maybe Char)
term = ParsecT ByteString u Identity Char
-> ParsecT ByteString u Identity (Maybe Char)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Char -> ParsecT ByteString u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
';')
istring :: String -> TextParser ()
istring :: String -> ParsecT ByteString DecodingFunctions Identity ()
istring = ParsecT ByteString DecodingFunctions Identity String
-> ParsecT ByteString DecodingFunctions Identity ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT ByteString DecodingFunctions Identity String
-> ParsecT ByteString DecodingFunctions Identity ())
-> (String -> ParsecT ByteString DecodingFunctions Identity String)
-> String
-> ParsecT ByteString DecodingFunctions Identity ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT ByteString DecodingFunctions Identity String
-> ParsecT ByteString DecodingFunctions Identity String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT ByteString DecodingFunctions Identity String
-> ParsecT ByteString DecodingFunctions Identity String)
-> (String -> ParsecT ByteString DecodingFunctions Identity String)
-> String
-> ParsecT ByteString DecodingFunctions Identity String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> ParsecT ByteString DecodingFunctions Identity Char)
-> String -> ParsecT ByteString DecodingFunctions Identity String
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (\Char
c -> Char -> ParsecT ByteString DecodingFunctions Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
c ParsecT ByteString DecodingFunctions Identity Char
-> ParsecT ByteString DecodingFunctions Identity Char
-> ParsecT ByteString DecodingFunctions Identity Char
forall a.
ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
-> ParsecT ByteString DecodingFunctions Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Char -> ParsecT ByteString DecodingFunctions Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char (Char -> Char
toLower Char
c))
mkRecur :: Frequency
-> Maybe (Either (m (Either Date DateTime)) Int)
-> Int
-> [Int]
-> [Int]
-> [Int]
-> [Either (Int, Weekday) Weekday]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> m Recur
mkRecur Frequency
f Maybe (Either (m (Either Date DateTime)) Int)
uc Int
i [Int]
s [Int]
m [Int]
h [Either (Int, Weekday) Weekday]
d [Int]
md [Int]
yd [Int]
wn [Int]
mo [Int]
sp Weekday
wkst = do
Maybe (Either (Either Date DateTime) Int)
uc' <- case Maybe (Either (m (Either Date DateTime)) Int)
uc of
Just (Left m (Either Date DateTime)
x) -> Either (Either Date DateTime) Int
-> Maybe (Either (Either Date DateTime) Int)
forall a. a -> Maybe a
Just (Either (Either Date DateTime) Int
-> Maybe (Either (Either Date DateTime) Int))
-> (Either Date DateTime -> Either (Either Date DateTime) Int)
-> Either Date DateTime
-> Maybe (Either (Either Date DateTime) Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either Date DateTime -> Either (Either Date DateTime) Int
forall a b. a -> Either a b
Left (Either Date DateTime -> Maybe (Either (Either Date DateTime) Int))
-> m (Either Date DateTime)
-> m (Maybe (Either (Either Date DateTime) Int))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m (Either Date DateTime)
x
Just (Right Int
y) -> Maybe (Either (Either Date DateTime) Int)
-> m (Maybe (Either (Either Date DateTime) Int))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe (Either (Either Date DateTime) Int)
-> m (Maybe (Either (Either Date DateTime) Int)))
-> (Either (Either Date DateTime) Int
-> Maybe (Either (Either Date DateTime) Int))
-> Either (Either Date DateTime) Int
-> m (Maybe (Either (Either Date DateTime) Int))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either (Either Date DateTime) Int
-> Maybe (Either (Either Date DateTime) Int)
forall a. a -> Maybe a
Just (Either (Either Date DateTime) Int
-> m (Maybe (Either (Either Date DateTime) Int)))
-> Either (Either Date DateTime) Int
-> m (Maybe (Either (Either Date DateTime) Int))
forall a b. (a -> b) -> a -> b
$ Int -> Either (Either Date DateTime) Int
forall a b. b -> Either a b
Right Int
y
Maybe (Either (m (Either Date DateTime)) Int)
Nothing -> Maybe (Either (Either Date DateTime) Int)
-> m (Maybe (Either (Either Date DateTime) Int))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (Either (Either Date DateTime) Int)
forall a. Maybe a
Nothing
Recur -> m Recur
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Recur -> m Recur) -> Recur -> m Recur
forall a b. (a -> b) -> a -> b
$ Frequency
-> Maybe (Either (Either Date DateTime) Int)
-> Int
-> [Int]
-> [Int]
-> [Int]
-> [Either (Int, Weekday) Weekday]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Weekday
-> Recur
Recur Frequency
f Maybe (Either (Either Date DateTime) Int)
uc' Int
i [Int]
s [Int]
m [Int]
h [Either (Int, Weekday) Weekday]
d [Int]
md [Int]
yd [Int]
wn [Int]
mo [Int]
sp Weekday
wkst
parseUTCPeriod :: ByteString -> ContentParser UTCPeriod
parseUTCPeriod :: ByteString -> ContentParser UTCPeriod
parseUTCPeriod ByteString
bs = do
let (ByteString
dateTime', ByteString
x) = Int64 -> ByteString -> ByteString
B.drop Int64
1 (ByteString -> ByteString)
-> (ByteString, ByteString) -> (ByteString, ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Bool) -> ByteString -> (ByteString, ByteString)
B.break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'/') ByteString
bs
Bool
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ()
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ByteString -> Bool
B.null ByteString
x) (ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ()
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ())
-> (String
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ())
-> String
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ()
forall a.
String
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (String
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ())
-> String
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ()
forall a b. (a -> b) -> a -> b
$ String
"Invalid UTCperiod: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ ByteString -> String
forall a. Show a => a -> String
show ByteString
bs
UTCTime
dateTime <- DateTime -> ContentParser UTCTime
mustBeUTC (DateTime -> ContentParser UTCTime)
-> ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
DateTime
-> ContentParser UTCTime
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe Text
-> ByteString
-> ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
DateTime
parseDateTime Maybe Text
forall a. Maybe a
Nothing ByteString
dateTime'
case ByteString -> Char
B.head ByteString
x of
Char
z | Char
z Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (String
"+-P"::String) -> UTCTime -> Duration -> UTCPeriod
UTCPeriodDuration UTCTime
dateTime
(Duration -> UTCPeriod)
-> ContentParser Duration -> ContentParser UTCPeriod
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> ByteString -> ContentParser Duration
parseDuration String
"period" ByteString
x
Char
_ -> UTCTime -> UTCTime -> UTCPeriod
UTCPeriodDates UTCTime
dateTime (UTCTime -> UTCPeriod)
-> ContentParser UTCTime -> ContentParser UTCPeriod
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DateTime -> ContentParser UTCTime
mustBeUTC (DateTime -> ContentParser UTCTime)
-> ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
DateTime
-> ContentParser UTCTime
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe Text
-> ByteString
-> ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
DateTime
parseDateTime Maybe Text
forall a. Maybe a
Nothing ByteString
x)
parsePeriod :: Maybe Text -> ByteString -> ContentParser Period
parsePeriod :: Maybe Text -> ByteString -> ContentParser Period
parsePeriod Maybe Text
tzid ByteString
bs = do
let (ByteString
dateTime', ByteString
x) = Int64 -> ByteString -> ByteString
B.drop Int64
1 (ByteString -> ByteString)
-> (ByteString, ByteString) -> (ByteString, ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Bool) -> ByteString -> (ByteString, ByteString)
B.break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'/') ByteString
bs
Bool
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ()
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ByteString -> Bool
B.null ByteString
x) (ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ()
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ())
-> (String
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ())
-> String
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ()
forall a.
String
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (String
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ())
-> String
-> ExceptT
String (RWS DecodingFunctions [String] (SourcePos, [Content])) ()
forall a b. (a -> b) -> a -> b
$ String
"Invalid period: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ ByteString -> String
forall a. Show a => a -> String
show ByteString
bs
DateTime
dateTime <- Maybe Text
-> ByteString
-> ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
DateTime
parseDateTime Maybe Text
tzid ByteString
dateTime'
case ByteString -> Char
B.head ByteString
x of
Char
z | Char
z Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (String
"+-P"::String) -> DateTime -> Duration -> Period
PeriodDuration DateTime
dateTime
(Duration -> Period)
-> ContentParser Duration -> ContentParser Period
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> ByteString -> ContentParser Duration
parseDuration String
"period" ByteString
x
Char
_ -> DateTime -> DateTime -> Period
PeriodDates DateTime
dateTime (DateTime -> Period)
-> ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
DateTime
-> ContentParser Period
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
-> ByteString
-> ExceptT
String
(RWS DecodingFunctions [String] (SourcePos, [Content]))
DateTime
parseDateTime Maybe Text
tzid ByteString
x