module Saturn.Unstable.Type.ScheduleSpec where import qualified Data.Text.Lazy.Builder as Builder import qualified Data.Word as Word import qualified Saturn.Unstable.Type.DaySpec as DaySpec import qualified Saturn.Unstable.Type.HourSpec as HourSpec import qualified Saturn.Unstable.Type.MinuteSpec as MinuteSpec import qualified Saturn.Unstable.Type.MonthSpec as MonthSpec import qualified Saturn.Unstable.Type.Schedule as Schedule import qualified Saturn.Unstable.Type.WeekdaySpec as WeekdaySpec import qualified Test.Hspec as Hspec import qualified Test.QuickCheck as QuickCheck import qualified Text.Parsec as Parsec spec :: Hspec.Spec spec :: Spec spec = forall a. HasCallStack => String -> SpecWith a -> SpecWith a Hspec.describe String "Saturn.Unstable.Type.Schedule" forall a b. (a -> b) -> a -> b $ do forall a. (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) Hspec.it String "round trips" forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a prop. (Show a, Testable prop) => Gen a -> (a -> [a]) -> (a -> prop) -> Property QuickCheck.forAllShrink Gen Schedule arbitrary Schedule -> [Schedule] shrink forall a b. (a -> b) -> a -> b $ \Schedule x -> do forall s t a. Stream s Identity t => Parsec s () a -> String -> s -> Either ParseError a Parsec.parse forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Schedule Schedule.parsec String "" (Builder -> Text Builder.toLazyText forall a b. (a -> b) -> a -> b $ Schedule -> Builder Schedule.toBuilder Schedule x) forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation `Hspec.shouldBe` forall a b. b -> Either a b Right Schedule x arbitrary :: QuickCheck.Gen Schedule.Schedule arbitrary :: Gen Schedule arbitrary = Minute -> Hour -> Day -> Month -> Weekday -> Schedule Schedule.Schedule forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Gen Minute MinuteSpec.arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Gen Hour HourSpec.arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Gen Day DaySpec.arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Gen Month MonthSpec.arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Gen Weekday WeekdaySpec.arbitrary shrink :: Schedule.Schedule -> [Schedule.Schedule] shrink :: Schedule -> [Schedule] shrink Schedule schedule = ( \(Minute minute, Hour hour, Day day, Month month, Weekday weekday) -> Schedule.Schedule { minute :: Minute Schedule.minute = Minute minute, hour :: Hour Schedule.hour = Hour hour, day :: Day Schedule.day = Day day, month :: Month Schedule.month = Month month, weekday :: Weekday Schedule.weekday = Weekday weekday } ) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> forall t1 t2 t3 t4 t5. (t1 -> [t1]) -> (t2 -> [t2]) -> (t3 -> [t3]) -> (t4 -> [t4]) -> (t5 -> [t5]) -> (t1, t2, t3, t4, t5) -> [(t1, t2, t3, t4, t5)] liftShrink5 Minute -> [Minute] MinuteSpec.shrink Hour -> [Hour] HourSpec.shrink Day -> [Day] DaySpec.shrink Month -> [Month] MonthSpec.shrink Weekday -> [Weekday] WeekdaySpec.shrink ( Schedule -> Minute Schedule.minute Schedule schedule, Schedule -> Hour Schedule.hour Schedule schedule, Schedule -> Day Schedule.day Schedule schedule, Schedule -> Month Schedule.month Schedule schedule, Schedule -> Weekday Schedule.weekday Schedule schedule ) liftShrink5 :: (t1 -> [t1]) -> (t2 -> [t2]) -> (t3 -> [t3]) -> (t4 -> [t4]) -> (t5 -> [t5]) -> (t1, t2, t3, t4, t5) -> [(t1, t2, t3, t4, t5)] liftShrink5 :: forall t1 t2 t3 t4 t5. (t1 -> [t1]) -> (t2 -> [t2]) -> (t3 -> [t3]) -> (t4 -> [t4]) -> (t5 -> [t5]) -> (t1, t2, t3, t4, t5) -> [(t1, t2, t3, t4, t5)] liftShrink5 t1 -> [t1] f1 t2 -> [t2] f2 t3 -> [t3] f3 t4 -> [t4] f4 t5 -> [t5] f5 (t1 x1, t2 x2, t3 x3, t4 x4, t5 x5) = (\((t1 y1, t2 y2), (t3 y3, (t4 y4, t5 y5))) -> (t1 y1, t2 y2, t3 y3, t4 y4, t5 y5)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> forall (f :: * -> * -> *) a b. Arbitrary2 f => (a -> [a]) -> (b -> [b]) -> f a b -> [f a b] QuickCheck.liftShrink2 (forall (f :: * -> * -> *) a b. Arbitrary2 f => (a -> [a]) -> (b -> [b]) -> f a b -> [f a b] QuickCheck.liftShrink2 t1 -> [t1] f1 t2 -> [t2] f2) (forall (f :: * -> * -> *) a b. Arbitrary2 f => (a -> [a]) -> (b -> [b]) -> f a b -> [f a b] QuickCheck.liftShrink2 t3 -> [t3] f3 (forall (f :: * -> * -> *) a b. Arbitrary2 f => (a -> [a]) -> (b -> [b]) -> f a b -> [f a b] QuickCheck.liftShrink2 t4 -> [t4] f4 t5 -> [t5] f5)) ((t1 x1, t2 x2), (t3 x3, (t4 x4, t5 x5))) new :: (MonadFail m) => [[Word.Word8]] -> [[Word.Word8]] -> [[Word.Word8]] -> [[Word.Word8]] -> [[Word.Word8]] -> m Schedule.Schedule new :: forall (m :: * -> *). MonadFail m => [[Word8]] -> [[Word8]] -> [[Word8]] -> [[Word8]] -> [[Word8]] -> m Schedule new [[Word8]] minutes [[Word8]] hours [[Word8]] days [[Word8]] months [[Word8]] weekdays = Minute -> Hour -> Day -> Month -> Weekday -> Schedule Schedule.Schedule forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> forall (m :: * -> *). MonadFail m => [[Word8]] -> m Minute MinuteSpec.new [[Word8]] minutes forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> forall (m :: * -> *). MonadFail m => [[Word8]] -> m Hour HourSpec.new [[Word8]] hours forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> forall (m :: * -> *). MonadFail m => [[Word8]] -> m Day DaySpec.new [[Word8]] days forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> forall (m :: * -> *). MonadFail m => [[Word8]] -> m Month MonthSpec.new [[Word8]] months forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> forall (m :: * -> *). MonadFail m => [[Word8]] -> m Weekday WeekdaySpec.new [[Word8]] weekdays