{-# LANGUAGE FlexibleContexts #-} module Saturn.Unstable.Type.Schedule where import qualified Data.Text.Lazy.Builder as Builder import qualified Saturn.Unstable.Type.Day as Day import qualified Saturn.Unstable.Type.Hour as Hour import qualified Saturn.Unstable.Type.Minute as Minute import qualified Saturn.Unstable.Type.Month as Month import qualified Saturn.Unstable.Type.Weekday as Weekday import qualified Text.Parsec as Parsec data Schedule = Schedule { Schedule -> Minute minute :: Minute.Minute, Schedule -> Hour hour :: Hour.Hour, Schedule -> Day day :: Day.Day, Schedule -> Month month :: Month.Month, Schedule -> Weekday weekday :: Weekday.Weekday } deriving (Schedule -> Schedule -> Bool (Schedule -> Schedule -> Bool) -> (Schedule -> Schedule -> Bool) -> Eq Schedule forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: Schedule -> Schedule -> Bool == :: Schedule -> Schedule -> Bool $c/= :: Schedule -> Schedule -> Bool /= :: Schedule -> Schedule -> Bool Eq, Int -> Schedule -> ShowS [Schedule] -> ShowS Schedule -> String (Int -> Schedule -> ShowS) -> (Schedule -> String) -> ([Schedule] -> ShowS) -> Show Schedule forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> Schedule -> ShowS showsPrec :: Int -> Schedule -> ShowS $cshow :: Schedule -> String show :: Schedule -> String $cshowList :: [Schedule] -> ShowS showList :: [Schedule] -> ShowS Show) parsec :: (Parsec.Stream s m Char) => Parsec.ParsecT s u m Schedule parsec :: forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Schedule parsec = Minute -> Hour -> Day -> Month -> Weekday -> Schedule Schedule (Minute -> Hour -> Day -> Month -> Weekday -> Schedule) -> ParsecT s u m Minute -> ParsecT s u m (Hour -> Day -> Month -> Weekday -> Schedule) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> ParsecT s u m Minute forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Minute Minute.parsec ParsecT s u m (Hour -> Day -> Month -> Weekday -> Schedule) -> ParsecT s u m () -> ParsecT s u m (Hour -> Day -> Month -> Weekday -> Schedule) forall a b. ParsecT s u m a -> ParsecT s u m b -> ParsecT s u m a forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a <* ParsecT s u m Char -> ParsecT s u m () forall s (m :: * -> *) t u a. Stream s m t => ParsecT s u m a -> ParsecT s u m () Parsec.skipMany1 (Char -> ParsecT s u m Char forall s (m :: * -> *) u. Stream s m Char => Char -> ParsecT s u m Char Parsec.char Char ' ') ParsecT s u m (Hour -> Day -> Month -> Weekday -> Schedule) -> ParsecT s u m Hour -> ParsecT s u m (Day -> Month -> Weekday -> Schedule) forall a b. ParsecT s u m (a -> b) -> ParsecT s u m a -> ParsecT s u m b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> ParsecT s u m Hour forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Hour Hour.parsec ParsecT s u m (Day -> Month -> Weekday -> Schedule) -> ParsecT s u m () -> ParsecT s u m (Day -> Month -> Weekday -> Schedule) forall a b. ParsecT s u m a -> ParsecT s u m b -> ParsecT s u m a forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a <* ParsecT s u m Char -> ParsecT s u m () forall s (m :: * -> *) t u a. Stream s m t => ParsecT s u m a -> ParsecT s u m () Parsec.skipMany1 (Char -> ParsecT s u m Char forall s (m :: * -> *) u. Stream s m Char => Char -> ParsecT s u m Char Parsec.char Char ' ') ParsecT s u m (Day -> Month -> Weekday -> Schedule) -> ParsecT s u m Day -> ParsecT s u m (Month -> Weekday -> Schedule) forall a b. ParsecT s u m (a -> b) -> ParsecT s u m a -> ParsecT s u m b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> ParsecT s u m Day forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Day Day.parsec ParsecT s u m (Month -> Weekday -> Schedule) -> ParsecT s u m () -> ParsecT s u m (Month -> Weekday -> Schedule) forall a b. ParsecT s u m a -> ParsecT s u m b -> ParsecT s u m a forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a <* ParsecT s u m Char -> ParsecT s u m () forall s (m :: * -> *) t u a. Stream s m t => ParsecT s u m a -> ParsecT s u m () Parsec.skipMany1 (Char -> ParsecT s u m Char forall s (m :: * -> *) u. Stream s m Char => Char -> ParsecT s u m Char Parsec.char Char ' ') ParsecT s u m (Month -> Weekday -> Schedule) -> ParsecT s u m Month -> ParsecT s u m (Weekday -> Schedule) forall a b. ParsecT s u m (a -> b) -> ParsecT s u m a -> ParsecT s u m b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> ParsecT s u m Month forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Month Month.parsec ParsecT s u m (Weekday -> Schedule) -> ParsecT s u m () -> ParsecT s u m (Weekday -> Schedule) forall a b. ParsecT s u m a -> ParsecT s u m b -> ParsecT s u m a forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a <* ParsecT s u m Char -> ParsecT s u m () forall s (m :: * -> *) t u a. Stream s m t => ParsecT s u m a -> ParsecT s u m () Parsec.skipMany1 (Char -> ParsecT s u m Char forall s (m :: * -> *) u. Stream s m Char => Char -> ParsecT s u m Char Parsec.char Char ' ') ParsecT s u m (Weekday -> Schedule) -> ParsecT s u m Weekday -> ParsecT s u m Schedule forall a b. ParsecT s u m (a -> b) -> ParsecT s u m a -> ParsecT s u m b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> ParsecT s u m Weekday forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Weekday Weekday.parsec toBuilder :: Schedule -> Builder.Builder toBuilder :: Schedule -> Builder toBuilder Schedule schedule = Minute -> Builder Minute.toBuilder (Schedule -> Minute minute Schedule schedule) Builder -> Builder -> Builder forall a. Semigroup a => a -> a -> a <> Char -> Builder Builder.singleton Char ' ' Builder -> Builder -> Builder forall a. Semigroup a => a -> a -> a <> Hour -> Builder Hour.toBuilder (Schedule -> Hour hour Schedule schedule) Builder -> Builder -> Builder forall a. Semigroup a => a -> a -> a <> Char -> Builder Builder.singleton Char ' ' Builder -> Builder -> Builder forall a. Semigroup a => a -> a -> a <> Day -> Builder Day.toBuilder (Schedule -> Day day Schedule schedule) Builder -> Builder -> Builder forall a. Semigroup a => a -> a -> a <> Char -> Builder Builder.singleton Char ' ' Builder -> Builder -> Builder forall a. Semigroup a => a -> a -> a <> Month -> Builder Month.toBuilder (Schedule -> Month month Schedule schedule) Builder -> Builder -> Builder forall a. Semigroup a => a -> a -> a <> Char -> Builder Builder.singleton Char ' ' Builder -> Builder -> Builder forall a. Semigroup a => a -> a -> a <> Weekday -> Builder Weekday.toBuilder (Schedule -> Weekday weekday Schedule schedule)