diff --git a/.github/workflows/ci.yml b/.github/workflows/ci.yml index 0b3ca67..43f9f20 100644 --- a/.github/workflows/ci.yml +++ b/.github/workflows/ci.yml @@ -15,6 +15,8 @@ jobs: - name: Set up PureScript toolchain uses: purescript-contrib/setup-purescript@main + with: + purs-tidy: "latest" - name: Cache PureScript dependencies uses: actions/cache@v2 @@ -25,9 +27,9 @@ jobs: output - name: Set up Node toolchain - uses: actions/setup-node@v1 + uses: actions/setup-node@v2 with: - node-version: "12.x" + node-version: "14.x" - name: Cache NPM dependencies uses: actions/cache@v2 @@ -49,3 +51,6 @@ jobs: - name: Run tests run: npm run test + + - name: Check formatting + run: purs-tidy check src test diff --git a/.gitignore b/.gitignore index 5a54e2f..6a45203 100644 --- a/.gitignore +++ b/.gitignore @@ -2,6 +2,7 @@ !.gitignore !.github !.editorconfig +!.tidyrc.json !.eslintrc.json output diff --git a/.tidyrc.json b/.tidyrc.json new file mode 100644 index 0000000..4f013c1 --- /dev/null +++ b/.tidyrc.json @@ -0,0 +1,10 @@ +{ + "importSort": "source", + "importWrap": "source", + "indent": 2, + "operatorsFile": null, + "ribbon": 1, + "typeArrowPlacement": "first", + "unicode": "never", + "width": null +} diff --git a/CHANGELOG.md b/CHANGELOG.md index 169b4e8..074fa5b 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -11,6 +11,7 @@ New features: Bugfixes: Other improvements: +- Added `purs-tidy` formatter (#77 by @thomashoneyman) ## [v6.0.0](https://github.com/purescript-contrib/purescript-formatters/releases/tag/v6.0.0) - 2021-10-16 diff --git a/src/Data/Formatter/DateTime.purs b/src/Data/Formatter/DateTime.purs index a096a0b..9e57fef 100644 --- a/src/Data/Formatter/DateTime.purs +++ b/src/Data/Formatter/DateTime.purs @@ -72,137 +72,138 @@ data FormatterCommand | MillisecondsTwoDigits | Placeholder String -derive instance eqFormatterCommand ∷ Eq FormatterCommand -derive instance ordFormatterCommand ∷ Ord FormatterCommand -derive instance genericFormatter ∷ Generic FormatterCommand _ -instance showFormatter ∷ Show FormatterCommand where +derive instance eqFormatterCommand :: Eq FormatterCommand +derive instance ordFormatterCommand :: Ord FormatterCommand +derive instance genericFormatter :: Generic FormatterCommand _ +instance showFormatter :: Show FormatterCommand where show = genericShow type Formatter = List.List FormatterCommand -printFormatterCommand ∷ FormatterCommand → String +printFormatterCommand :: FormatterCommand -> String printFormatterCommand = case _ of - YearFull → "YYYY" - YearTwoDigits → "YY" - YearAbsolute → "Y" - MonthFull → "MMMM" - MonthShort → "MMM" - MonthTwoDigits → "MM" - DayOfMonthTwoDigits → "DD" - DayOfMonth → "D" - UnixTimestamp → "X" - DayOfWeek → "E" - DayOfWeekName → "dddd" - DayOfWeekNameShort → "ddd" - Hours24 → "HH" - Hours12 → "hh" - Meridiem → "a" - Minutes → "m" - MinutesTwoDigits → "mm" - Seconds → "s" - SecondsTwoDigits → "ss" - MillisecondsShort → "S" - MillisecondsTwoDigits → "SS" - Milliseconds → "SSS" - Placeholder s → s - -printFormatter ∷ Formatter → String + YearFull -> "YYYY" + YearTwoDigits -> "YY" + YearAbsolute -> "Y" + MonthFull -> "MMMM" + MonthShort -> "MMM" + MonthTwoDigits -> "MM" + DayOfMonthTwoDigits -> "DD" + DayOfMonth -> "D" + UnixTimestamp -> "X" + DayOfWeek -> "E" + DayOfWeekName -> "dddd" + DayOfWeekNameShort -> "ddd" + Hours24 -> "HH" + Hours12 -> "hh" + Meridiem -> "a" + Minutes -> "m" + MinutesTwoDigits -> "mm" + Seconds -> "s" + SecondsTwoDigits -> "ss" + MillisecondsShort -> "S" + MillisecondsTwoDigits -> "SS" + Milliseconds -> "SSS" + Placeholder s -> s + +printFormatter :: Formatter -> String printFormatter = foldMap printFormatterCommand -parseFormatString ∷ String → Either String Formatter +parseFormatString :: String -> Either String Formatter parseFormatString = runP formatParser -placeholderContent ∷ P.Parser String String +placeholderContent :: P.Parser String String placeholderContent = CU.toCharArray "YMDEHhamsS" - # PS.noneOf - # Array.some - <#> CU.fromCharArray - -formatterCommandParser ∷ P.Parser String FormatterCommand -formatterCommandParser = (PC.try <<< PS.string) `oneOfAs` - [ Tuple "YYYY" YearFull - , Tuple "YY" YearTwoDigits - , Tuple "Y" YearAbsolute - , Tuple "MMMM" MonthFull - , Tuple "MMM" MonthShort - , Tuple "MM" MonthTwoDigits - , Tuple "DD" DayOfMonthTwoDigits - , Tuple "D" DayOfMonth - , Tuple "E" DayOfWeek - , Tuple "X" UnixTimestamp - , Tuple "dddd" DayOfWeekName - , Tuple "ddd" DayOfWeekNameShort - , Tuple "HH" Hours24 - , Tuple "hh" Hours12 - , Tuple "a" Meridiem - , Tuple "mm" MinutesTwoDigits - , Tuple "m" Minutes - , Tuple "ss" SecondsTwoDigits - , Tuple "s" Seconds - , Tuple "SSS" Milliseconds - , Tuple "SS" MillisecondsTwoDigits - , Tuple "S" MillisecondsShort - ] <|> (Placeholder <$> placeholderContent) - -formatParser ∷ P.Parser String Formatter + # PS.noneOf + # Array.some + <#> CU.fromCharArray + +formatterCommandParser :: P.Parser String FormatterCommand +formatterCommandParser = + (PC.try <<< PS.string) `oneOfAs` + [ Tuple "YYYY" YearFull + , Tuple "YY" YearTwoDigits + , Tuple "Y" YearAbsolute + , Tuple "MMMM" MonthFull + , Tuple "MMM" MonthShort + , Tuple "MM" MonthTwoDigits + , Tuple "DD" DayOfMonthTwoDigits + , Tuple "D" DayOfMonth + , Tuple "E" DayOfWeek + , Tuple "X" UnixTimestamp + , Tuple "dddd" DayOfWeekName + , Tuple "ddd" DayOfWeekNameShort + , Tuple "HH" Hours24 + , Tuple "hh" Hours12 + , Tuple "a" Meridiem + , Tuple "mm" MinutesTwoDigits + , Tuple "m" Minutes + , Tuple "ss" SecondsTwoDigits + , Tuple "s" Seconds + , Tuple "SSS" Milliseconds + , Tuple "SS" MillisecondsTwoDigits + , Tuple "S" MillisecondsShort + ] <|> (Placeholder <$> placeholderContent) + +formatParser :: P.Parser String Formatter formatParser = List.some formatterCommandParser -- | Formatting function that accepts a number that is a year, -- | and strips away the non-significant digits, leaving only the -- | ones and tens positions. -formatYearTwoDigits ∷ Int → String +formatYearTwoDigits :: Int -> String formatYearTwoDigits i = case dateLength of - 1 → "0" <> dateString - 2 → dateString - _ → Str.drop (dateLength - 2) dateString + 1 -> "0" <> dateString + 2 -> dateString + _ -> Str.drop (dateLength - 2) dateString where dateString = show $ abs i dateLength = Str.length $ dateString -fix12 ∷ Int → Int +fix12 :: Int -> Int fix12 h = if h == 0 then 12 else h -formatCommand ∷ DT.DateTime → FormatterCommand → String +formatCommand :: DT.DateTime -> FormatterCommand -> String formatCommand dt@(DT.DateTime d t) = case _ of - YearFull → padQuadrupleDigit $ fromEnum $ D.year d - YearTwoDigits → formatYearTwoDigits $ fromEnum $ D.year d - YearAbsolute → show $ fromEnum $ D.year d - MonthFull → show $ D.month d - MonthShort → printShortMonth $ D.month d - MonthTwoDigits → padSingleDigit $ fromEnum $ D.month d - DayOfMonthTwoDigits → padSingleDigit $ fromEnum $ D.day d - DayOfMonth → show $ fromEnum $ D.day d - UnixTimestamp → show $ Int.floor $ (_ / 1000.0) $ unwrap $ unInstant $ fromDateTime dt - DayOfWeek → show $ fromEnum $ D.weekday d - DayOfWeekName → show $ D.weekday d - DayOfWeekNameShort → Str.take 3 $ show $ D.weekday d - Hours24 → padSingleDigit (fromEnum $ T.hour t) - Hours12 → padSingleDigit $ fix12 $ (fromEnum $ T.hour t) `mod` 12 - Meridiem → if (fromEnum $ T.hour t) >= 12 then "PM" else "AM" - Minutes → show $ fromEnum $ T.minute t - MinutesTwoDigits → padSingleDigit <<< fromEnum $ T.minute t - Seconds → show $ fromEnum $ T.second t - SecondsTwoDigits → padSingleDigit <<< fromEnum $ T.second t - Milliseconds → padDoubleDigit <<< fromEnum $ T.millisecond t - MillisecondsShort → show $ (_ / 100) $ fromEnum $ T.millisecond t - MillisecondsTwoDigits → padSingleDigit $ (_ / 10) $ fromEnum $ T.millisecond t - Placeholder s → s - -padSingleDigit ∷ Int → String + YearFull -> padQuadrupleDigit $ fromEnum $ D.year d + YearTwoDigits -> formatYearTwoDigits $ fromEnum $ D.year d + YearAbsolute -> show $ fromEnum $ D.year d + MonthFull -> show $ D.month d + MonthShort -> printShortMonth $ D.month d + MonthTwoDigits -> padSingleDigit $ fromEnum $ D.month d + DayOfMonthTwoDigits -> padSingleDigit $ fromEnum $ D.day d + DayOfMonth -> show $ fromEnum $ D.day d + UnixTimestamp -> show $ Int.floor $ (_ / 1000.0) $ unwrap $ unInstant $ fromDateTime dt + DayOfWeek -> show $ fromEnum $ D.weekday d + DayOfWeekName -> show $ D.weekday d + DayOfWeekNameShort -> Str.take 3 $ show $ D.weekday d + Hours24 -> padSingleDigit (fromEnum $ T.hour t) + Hours12 -> padSingleDigit $ fix12 $ (fromEnum $ T.hour t) `mod` 12 + Meridiem -> if (fromEnum $ T.hour t) >= 12 then "PM" else "AM" + Minutes -> show $ fromEnum $ T.minute t + MinutesTwoDigits -> padSingleDigit <<< fromEnum $ T.minute t + Seconds -> show $ fromEnum $ T.second t + SecondsTwoDigits -> padSingleDigit <<< fromEnum $ T.second t + Milliseconds -> padDoubleDigit <<< fromEnum $ T.millisecond t + MillisecondsShort -> show $ (_ / 100) $ fromEnum $ T.millisecond t + MillisecondsTwoDigits -> padSingleDigit $ (_ / 10) $ fromEnum $ T.millisecond t + Placeholder s -> s + +padSingleDigit :: Int -> String padSingleDigit i | i < 0 = "-" <> padSingleDigit (-i) | i < 10 = "0" <> (show i) | otherwise = show i -padDoubleDigit ∷ Int → String +padDoubleDigit :: Int -> String padDoubleDigit i | i < 0 = "-" <> padDoubleDigit (-i) - | i < 10 = "00" <> (show i) + | i < 10 = "00" <> (show i) | i < 100 = "0" <> (show i) | otherwise = show i -padQuadrupleDigit ∷ Int → String +padQuadrupleDigit :: Int -> String padQuadrupleDigit i | i < 0 = "-" <> padQuadrupleDigit (-i) | i < 10 = "000" <> (show i) @@ -210,32 +211,32 @@ padQuadrupleDigit i | i < 1000 = "0" <> (show i) | otherwise = show i -format ∷ Formatter → DT.DateTime → String +format :: Formatter -> DT.DateTime -> String format f d = foldMap (formatCommand d) f -formatDateTime ∷ String → DT.DateTime → Either String String +formatDateTime :: String -> DT.DateTime -> Either String String formatDateTime pattern datetime = parseFormatString pattern <#> (_ `format` datetime) -unformat ∷ Formatter → String → Either String DT.DateTime +unformat :: Formatter -> String -> Either String DT.DateTime unformat = runP <<< unformatParser data Meridiem = AM | PM -derive instance eqMeridiem ∷ Eq Meridiem +derive instance eqMeridiem :: Eq Meridiem type UnformatAccum = - { year ∷ Maybe Int - , month ∷ Maybe Int - , day ∷ Maybe Int - , hour ∷ Maybe Int - , minute ∷ Maybe Int - , second ∷ Maybe Int - , millisecond ∷ Maybe Int - , meridiem ∷ Maybe Meridiem + { year :: Maybe Int + , month :: Maybe Int + , day :: Maybe Int + , hour :: Maybe Int + , minute :: Maybe Int + , second :: Maybe Int + , millisecond :: Maybe Int + , meridiem :: Maybe Meridiem } -initialAccum ∷ UnformatAccum +initialAccum :: UnformatAccum initialAccum = { year: Nothing , month: Nothing @@ -247,121 +248,126 @@ initialAccum = , meridiem: Nothing } -unformatAccumToDateTime ∷ UnformatAccum → Either String DT.DateTime +unformatAccumToDateTime :: UnformatAccum -> Either String DT.DateTime unformatAccumToDateTime a = applySecond (validAccum a) $ DT.DateTime - <$> (D.canonicalDate - <$> (maybe (Left "Incorrect year") pure $ toEnum $ fromMaybe zero a.year) - <*> (maybe (Left "Incorrect month") pure $ toEnum $ fromMaybe one a.month) - <*> (maybe (Left "Incorrect day") pure $ toEnum - $ adjustDay a.hour - $ fromMaybe one a.day)) - <*> (T.Time - <$> (maybe - (Left "Incorrect hour") pure - $ toEnum - $ fromMaybe zero - $ adjustMeridiem a.meridiem <$> a.hour) - <*> (maybe (Left "Incorrect minute") pure $ toEnum $ fromMaybe zero a.minute) - <*> (maybe (Left "Incorrect second") pure $ toEnum $ fromMaybe zero a.second) - <*> (maybe (Left "Incorrect millisecond") pure $ toEnum $ fromMaybe zero a.millisecond)) - -validAccum :: UnformatAccum → Either String Unit + <$> + ( D.canonicalDate + <$> (maybe (Left "Incorrect year") pure $ toEnum $ fromMaybe zero a.year) + <*> (maybe (Left "Incorrect month") pure $ toEnum $ fromMaybe one a.month) + <*> (maybe (Left "Incorrect day") pure $ toEnum $ adjustDay a.hour $ fromMaybe one a.day) + ) + <*> + ( T.Time + <$> (maybe (Left "Incorrect hour") pure $ toEnum $ fromMaybe zero $ adjustMeridiem a.meridiem <$> a.hour) + <*> (maybe (Left "Incorrect minute") pure $ toEnum $ fromMaybe zero a.minute) + <*> (maybe (Left "Incorrect second") pure $ toEnum $ fromMaybe zero a.second) + <*> (maybe (Left "Incorrect millisecond") pure $ toEnum $ fromMaybe zero a.millisecond) + ) + +validAccum :: UnformatAccum -> Either String Unit validAccum { hour, minute, second, millisecond } = case hour of - Just 24 → for_ [minute, second, millisecond] \val -> - when (fromMaybe 0 val > 0) $ Left "When hour is 24, other time components must be 0" - _ -> pure unit + Just 24 -> for_ [ minute, second, millisecond ] \val -> + when (fromMaybe 0 val > 0) $ Left "When hour is 24, other time components must be 0" + _ -> pure unit -adjustDay ∷ Maybe Int → Int → Int +adjustDay :: Maybe Int -> Int -> Int adjustDay (Just 24) n = n + 1 -adjustDay _ n = n +adjustDay _ n = n -adjustMeridiem ∷ Maybe Meridiem → Int → Int +adjustMeridiem :: Maybe Meridiem -> Int -> Int adjustMeridiem (Just AM) 12 = 0 adjustMeridiem (Just PM) 12 = 12 -adjustMeridiem (Just PM) n = n + 12 -adjustMeridiem (Just AM) n = n -adjustMeridiem Nothing 24 = 0 -adjustMeridiem Nothing n = n - -exactLength ∷ ∀ e. ReaderT { maxLength ∷ Int, length ∷ Int | e } (Either String) Unit -exactLength = ask >>= \({maxLength, length}) → lift if maxLength /= length - then Left $ "Expected " <> (show maxLength) <> " digits but got " <> (show length) - else Right unit - -validateRange ∷ ∀ e. Int → Int → ReaderT { num ∷ Int | e } (Either String) Unit -validateRange min max = ask >>= \({num}) → lift if num < min || num > max - then Left $ "Number is out of range [ " <> (show min) <> ", " <> (show max) <> " ]" - else Right unit +adjustMeridiem (Just PM) n = n + 12 +adjustMeridiem (Just AM) n = n +adjustMeridiem Nothing 24 = 0 +adjustMeridiem Nothing n = n + +exactLength :: forall e. ReaderT { maxLength :: Int, length :: Int | e } (Either String) Unit +exactLength = ask >>= \({ maxLength, length }) -> lift + if maxLength /= length then + Left $ "Expected " <> (show maxLength) <> " digits but got " <> (show length) + else + Right unit + +validateRange :: forall e. Int -> Int -> ReaderT { num :: Int | e } (Either String) Unit +validateRange min max = ask >>= \({ num }) -> lift + if num < min || num > max then + Left $ "Number is out of range [ " <> (show min) <> ", " <> (show max) <> " ]" + else + Right unit -- NOTE related discussion: https://github.com/purescript-contrib/purescript-parsing/issues/57 -- | Attempt a computation `n` times, requiring at least one success. -- | -- | The `Lazy` constraint is used to generate the result lazily, to ensure -- | termination. -takeSome :: ∀ f a. Alternative f ⇒ Z.Lazy (f (List.List a)) ⇒ Int → f a → f (List.List a) +takeSome :: forall f a. Alternative f => Z.Lazy (f (List.List a)) => Int -> f a -> f (List.List a) takeSome 0 _ = pure List.Nil -takeSome n v = List.Cons <$> v <*> Z.defer (\_ → takeMany (n - 1) v) +takeSome n v = List.Cons <$> v <*> Z.defer (\_ -> takeMany (n - 1) v) -- | Attempt a computation `n` times, returning as many successful results -- | as possible (possibly zero). -- | -- | The `Lazy` constraint is used to generate the result lazily, to ensure -- | termination. -takeMany :: ∀ f a. Alternative f ⇒ Z.Lazy (f (List.List a)) ⇒ Int → f a → f (List.List a) +takeMany :: forall f a. Alternative f => Z.Lazy (f (List.List a)) => Int -> f a -> f (List.List a) takeMany 0 _ = pure List.Nil takeMany n v = takeSome n v <|> pure List.Nil -parseSignedInt ∷ ∀ m - . Monad m - ⇒ Int - → ReaderT { length ∷ Int, num ∷ Int, maxLength ∷ Int } (Either String) Unit - → String - → P.ParserT String m Int +parseSignedInt + :: forall m + . Monad m + => Int + -> ReaderT { length :: Int, num :: Int, maxLength :: Int } (Either String) Unit + -> String + -> P.ParserT String m Int parseSignedInt maxLength validators errMsg = do - isNegative ← isJust <$> PC.optionMaybe (PS.char '-') + isNegative <- isJust <$> PC.optionMaybe (PS.char '-') (if isNegative then negate else identity) <$> parseInt maxLength validators errMsg -parseInt ∷ ∀ m - . Monad m - ⇒ Int - → ReaderT { length ∷ Int, num ∷ Int, maxLength ∷ Int } (Either String) Unit - → String - → P.ParserT String m Int +parseInt + :: forall m + . Monad m + => Int + -> ReaderT { length :: Int, num :: Int, maxLength :: Int } (Either String) Unit + -> String + -> P.ParserT String m Int parseInt maxLength validators errMsg = do - ds ← takeSome maxLength parseDigit + ds <- takeSome maxLength parseDigit let length = List.length ds num = foldDigits ds - case runReaderT validators {length, num, maxLength} of - Left err → P.fail $ errMsg <> "(" <> err <> ")" - Right _ → pure num + case runReaderT validators { length, num, maxLength } of + Left err -> P.fail $ errMsg <> "(" <> err <> ")" + Right _ -> pure num -unformatCommandParser ∷ FormatterCommand → P.ParserT String (State UnformatAccum) Unit +unformatCommandParser :: FormatterCommand -> P.ParserT String (State UnformatAccum) Unit unformatCommandParser = case _ of - YearFull → _{year = _} `modifyWithParser` + YearFull -> _ { year = _ } `modifyWithParser` (parseSignedInt 4 exactLength "Incorrect full year") - YearTwoDigits → _{year = _} `modifyWithParser` + YearTwoDigits -> _ { year = _ } `modifyWithParser` (parseSignedInt 2 exactLength "Incorrect 2-digit year") - YearAbsolute → _{year = _} `modifyWithParser` - (lift2 (*) - (PC.option 1 $ PC.try $ PS.string "-" <#> (const (-1))) - (List.some parseDigit <#> foldDigits)) - MonthFull → _{month = _} `modifyWithParser` + YearAbsolute -> _ { year = _ } `modifyWithParser` + ( lift2 (*) + (PC.option 1 $ PC.try $ PS.string "-" <#> (const (-1))) + (List.some parseDigit <#> foldDigits) + ) + MonthFull -> _ { month = _ } `modifyWithParser` (fromEnum <$> parseMonth) - MonthShort → _{month = _} `modifyWithParser` + MonthShort -> _ { month = _ } `modifyWithParser` (fromEnum <$> parseShortMonth) - MonthTwoDigits → _{month = _} `modifyWithParser` + MonthTwoDigits -> _ { month = _ } `modifyWithParser` (parseInt 2 (validateRange 1 12 <> exactLength) "Incorrect 2-digit month") - DayOfMonthTwoDigits → _{day = _} `modifyWithParser` + DayOfMonthTwoDigits -> _ { day = _ } `modifyWithParser` (parseInt 2 (validateRange 1 31 <> exactLength) "Incorrect day of month") - DayOfMonth → _{day = _} `modifyWithParser` + DayOfMonth -> _ { day = _ } `modifyWithParser` (parseInt 2 (validateRange 1 31) "Incorrect day of month") - UnixTimestamp → do - s ← map foldDigits $ List.some parseDigit + UnixTimestamp -> do + s <- map foldDigits $ List.some parseDigit case map toDateTime $ instant $ Dur.Milliseconds $ 1000.0 * Int.toNumber s of - Nothing → P.fail "Incorrect timestamp" - Just (DT.DateTime d t) → lift $ put + Nothing -> P.fail "Incorrect timestamp" + Just (DT.DateTime d t) -> lift $ put { year: Just $ fromEnum $ D.year d , month: Just $ fromEnum $ D.month d , day: Just $ fromEnum $ D.day d @@ -372,59 +378,59 @@ unformatCommandParser = case _ of , meridiem: Nothing } -- TODO we would need to use this value if we support date format using week number - DayOfWeek → void $ parseInt 1 (validateRange 1 7) "Incorrect day of week" - DayOfWeekName → _{day = _} `modifyWithParser` + DayOfWeek -> void $ parseInt 1 (validateRange 1 7) "Incorrect day of week" + DayOfWeekName -> _ { day = _ } `modifyWithParser` (fromEnum <$> parseDayOfWeekName) - DayOfWeekNameShort → _{day = _} `modifyWithParser` + DayOfWeekNameShort -> _ { day = _ } `modifyWithParser` (fromEnum <$> parseDayOfWeekNameShort) - Hours24 → _{hour = _} `modifyWithParser` + Hours24 -> _ { hour = _ } `modifyWithParser` (parseInt 2 (validateRange 0 24 <> exactLength) "Incorrect 24 hour") - Hours12 → _{hour = _} `modifyWithParser` + Hours12 -> _ { hour = _ } `modifyWithParser` (parseInt 2 (validateRange 0 12 <> exactLength) "Incorrect 12 hour") - Meridiem → _{meridiem = _} `modifyWithParser` parseMeridiem - MinutesTwoDigits → _{minute = _} `modifyWithParser` + Meridiem -> _ { meridiem = _ } `modifyWithParser` parseMeridiem + MinutesTwoDigits -> _ { minute = _ } `modifyWithParser` (parseInt 2 (validateRange 0 59 <> exactLength) "Incorrect 2-digit minute") - Minutes → _{minute = _} `modifyWithParser` + Minutes -> _ { minute = _ } `modifyWithParser` (parseInt 2 (validateRange 0 59) "Incorrect minute") - SecondsTwoDigits → _{second = _} `modifyWithParser` + SecondsTwoDigits -> _ { second = _ } `modifyWithParser` (parseInt 2 (validateRange 0 59 <> exactLength) "Incorrect 2-digit second") - Seconds → _{second = _} `modifyWithParser` + Seconds -> _ { second = _ } `modifyWithParser` (parseInt 2 (validateRange 0 59) "Incorrect second") - Milliseconds → _{millisecond = _} `modifyWithParser` + Milliseconds -> _ { millisecond = _ } `modifyWithParser` (parseInt 3 exactLength "Incorrect millisecond") - Placeholder s → void $ PS.string s - MillisecondsShort → _{millisecond = _} `modifyWithParser` + Placeholder s -> void $ PS.string s + MillisecondsShort -> _ { millisecond = _ } `modifyWithParser` (parseInt 1 exactLength "Incorrect 1-digit millisecond" <#> (_ * 100)) - MillisecondsTwoDigits → _{millisecond = _} `modifyWithParser` + MillisecondsTwoDigits -> _ { millisecond = _ } `modifyWithParser` (parseInt 2 exactLength "Incorrect 2-digit millisecond" <#> (_ * 10)) where - modifyWithParser ∷ ∀ s' s x. (s → Maybe x → s) → P.ParserT s' (State s) x → P.ParserT s' (State s) Unit + modifyWithParser :: forall s' s x. (s -> Maybe x -> s) -> P.ParserT s' (State s) x -> P.ParserT s' (State s) Unit modifyWithParser f p = do - v ← p + v <- p lift $ modify_ (flip f (Just v)) -unformatParser ∷ ∀ m. Monad m ⇒ Formatter → P.ParserT String m DT.DateTime +unformatParser :: forall m. Monad m => Formatter -> P.ParserT String m DT.DateTime unformatParser f = do - acc ← P.mapParserT unState $ foldMap unformatCommandParser f + acc <- P.mapParserT unState $ foldMap unformatCommandParser f either P.fail pure $ unformatAccumToDateTime acc where - unState ∷ ∀ x y n. Monad n ⇒ State UnformatAccum (Tuple (Either y Unit) x) → n (Tuple (Either y UnformatAccum) x) + unState :: forall x y n. Monad n => State UnformatAccum (Tuple (Either y Unit) x) -> n (Tuple (Either y UnformatAccum) x) unState s = case runState s initialAccum of - Tuple (Tuple e state) res → pure (Tuple (e $> res) state) + Tuple (Tuple e state) res -> pure (Tuple (e $> res) state) -unformatDateTime ∷ String → String → Either String DT.DateTime +unformatDateTime :: String -> String -> Either String DT.DateTime unformatDateTime pattern str = parseFormatString pattern >>= (_ `unformat` str) -parseMeridiem ∷ ∀ m. Monad m ⇒ P.ParserT String m Meridiem -parseMeridiem = (PC.try <<< PS.string) `oneOfAs` +parseMeridiem :: forall m. Monad m => P.ParserT String m Meridiem +parseMeridiem = (PC.try <<< PS.string) `oneOfAs` [ Tuple "am" AM , Tuple "AM" AM , Tuple "pm" PM , Tuple "PM" PM ] -parseDayOfWeekName ∷ ∀ m. Monad m ⇒ P.ParserT String m D.Weekday +parseDayOfWeekName :: forall m. Monad m => P.ParserT String m D.Weekday parseDayOfWeekName = (PC.try <<< PS.string) `oneOfAs` [ Tuple "Monday" D.Monday , Tuple "Tuesday" D.Tuesday @@ -435,7 +441,7 @@ parseDayOfWeekName = (PC.try <<< PS.string) `oneOfAs` , Tuple "Sunday" D.Sunday ] -parseDayOfWeekNameShort ∷ ∀ m. Monad m ⇒ P.ParserT String m D.Weekday +parseDayOfWeekNameShort :: forall m. Monad m => P.ParserT String m D.Weekday parseDayOfWeekNameShort = (PC.try <<< PS.string) `oneOfAs` [ Tuple "Mon" D.Monday , Tuple "Tue" D.Tuesday @@ -446,7 +452,7 @@ parseDayOfWeekNameShort = (PC.try <<< PS.string) `oneOfAs` , Tuple "Sun" D.Sunday ] -parseMonth ∷ ∀ m. Monad m ⇒ P.ParserT String m D.Month +parseMonth :: forall m. Monad m => P.ParserT String m D.Month parseMonth = (PC.try <<< PS.string) `oneOfAs` [ Tuple "January" D.January , Tuple "February" D.February @@ -462,7 +468,7 @@ parseMonth = (PC.try <<< PS.string) `oneOfAs` , Tuple "December" D.December ] -parseShortMonth ∷ ∀ m. Monad m ⇒ P.ParserT String m D.Month +parseShortMonth :: forall m. Monad m => P.ParserT String m D.Month parseShortMonth = (PC.try <<< PS.string) `oneOfAs` [ Tuple "Jan" D.January , Tuple "Feb" D.February @@ -478,17 +484,17 @@ parseShortMonth = (PC.try <<< PS.string) `oneOfAs` , Tuple "Dec" D.December ] -printShortMonth ∷ D.Month → String +printShortMonth :: D.Month -> String printShortMonth = case _ of - D.January → "Jan" - D.February → "Feb" - D.March → "Mar" - D.April → "Apr" - D.May → "May" - D.June → "Jun" - D.July → "Jul" - D.August → "Aug" - D.September → "Sep" - D.October → "Oct" - D.November → "Nov" - D.December → "Dec" + D.January -> "Jan" + D.February -> "Feb" + D.March -> "Mar" + D.April -> "Apr" + D.May -> "May" + D.June -> "Jun" + D.July -> "Jul" + D.August -> "Aug" + D.September -> "Sep" + D.October -> "Oct" + D.November -> "Nov" + D.December -> "Dec" diff --git a/src/Data/Formatter/Internal.purs b/src/Data/Formatter/Internal.purs index 95c66d5..8b64ad2 100644 --- a/src/Data/Formatter/Internal.purs +++ b/src/Data/Formatter/Internal.purs @@ -1,17 +1,17 @@ -module Data.Formatter.Internal where - -import Prelude - -import Data.Foldable (class Foldable, foldl) - -foldDigits ∷ ∀ f. Foldable f ⇒ f Int → Int -foldDigits = foldl (\acc d → acc * 10 + d) zero - -repeat ∷ ∀ a. Monoid a ⇒ a → Int → a -repeat = repeat' mempty - where - repeat' ∷ a → a → Int → a - repeat' accum _ count - | count < one = accum - repeat' accum part count = - repeat' (accum <> part) part (count - one) +module Data.Formatter.Internal where + +import Prelude + +import Data.Foldable (class Foldable, foldl) + +foldDigits :: forall f. Foldable f => f Int -> Int +foldDigits = foldl (\acc d -> acc * 10 + d) zero + +repeat :: forall a. Monoid a => a -> Int -> a +repeat = repeat' mempty + where + repeat' :: a -> a -> Int -> a + repeat' accum _ count + | count < one = accum + repeat' accum part count = + repeat' (accum <> part) part (count - one) diff --git a/src/Data/Formatter/Interval.purs b/src/Data/Formatter/Interval.purs index 737ae7f..a2470a5 100644 --- a/src/Data/Formatter/Interval.purs +++ b/src/Data/Formatter/Interval.purs @@ -20,22 +20,22 @@ import Data.Map (lookup) import Data.Maybe (maybe) import Data.Tuple (Tuple(..)) -formatRecurringInterval ∷ I.RecurringInterval IsoDuration DateTime → String +formatRecurringInterval :: I.RecurringInterval IsoDuration DateTime -> String formatRecurringInterval (I.RecurringInterval n i) = "R" <> (maybe "" formatInteger n) <> "/" <> (formatInterval i) -formatInterval ∷ I.Interval IsoDuration DateTime → String +formatInterval :: I.Interval IsoDuration DateTime -> String formatInterval (I.StartEnd x y) = (formatDateTime x) <> "/" <> (formatDateTime y) formatInterval (I.DurationEnd d x) = (formatIsoDuration d) <> "/" <> (formatDateTime x) formatInterval (I.StartDuration x d) = (formatDateTime x) <> "/" <> (formatIsoDuration d) formatInterval (I.DurationOnly d) = (formatIsoDuration d) -formatDateTime ∷ DateTime → String +formatDateTime :: DateTime -> String formatDateTime = FDT.format extendedDateTimeFormatInUTC -formatIsoDuration ∷ IsoDuration → String +formatIsoDuration :: IsoDuration -> String formatIsoDuration = formatDuration <<< unIsoDuration -formatDuration ∷ I.Duration → String +formatDuration :: I.Duration -> String formatDuration (I.Duration m) = "P" <> datePart <> timePart where datePart = componentToString `foldMap` dateComponentsToStr @@ -47,14 +47,14 @@ formatDuration (I.Duration m) = "P" <> datePart <> timePart dateComponentsToStr = [ Tuple I.Year "Y", Tuple I.Month "M", Tuple I.Week "W", Tuple I.Day "D" ] timeComponentsToStr = [ Tuple I.Hour "H", Tuple I.Minute "M", Tuple I.Second "S" ] -formatInteger ∷ Int → String +formatInteger :: Int -> String formatInteger = show -formatNumber ∷ Number → String +formatNumber :: Number -> String formatNumber n = if Int.toNumber (Int.floor n) == n then show (Int.floor n) else show n -unformatRecurringInterval ∷ String → Either String (I.RecurringInterval IsoDuration DateTime) +unformatRecurringInterval :: String -> Either String (I.RecurringInterval IsoDuration DateTime) unformatRecurringInterval = runP $ parseRecurringInterval parseIsoDuration parseDateTime -unformatInterval ∷ String → Either String (I.Interval IsoDuration DateTime) +unformatInterval :: String -> Either String (I.Interval IsoDuration DateTime) unformatInterval = runP $ parseInterval parseIsoDuration parseDateTime diff --git a/src/Data/Formatter/Number.purs b/src/Data/Formatter/Number.purs index adffdda..cc0a0e2 100644 --- a/src/Data/Formatter/Number.purs +++ b/src/Data/Formatter/Number.purs @@ -34,45 +34,43 @@ import Text.Parsing.Parser as P import Text.Parsing.Parser.Combinators as PC import Text.Parsing.Parser.String as PS - newtype Formatter = Formatter - { comma ∷ Boolean - , before ∷ Int - , after ∷ Int - , abbreviations ∷ Boolean - , sign ∷ Boolean + { comma :: Boolean + , before :: Int + , after :: Int + , abbreviations :: Boolean + , sign :: Boolean } -derive instance genericFormatter ∷ Generic Formatter _ -derive instance newtypeFormatter ∷ Newtype Formatter _ +derive instance genericFormatter :: Generic Formatter _ +derive instance newtypeFormatter :: Newtype Formatter _ -instance showFormatter ∷ Show Formatter where +instance showFormatter :: Show Formatter where show = genericShow -derive instance eqFormatter ∷ Eq Formatter +derive instance eqFormatter :: Eq Formatter -printFormatter ∷ Formatter → String +printFormatter :: Formatter -> String printFormatter (Formatter f) = - (if f.sign then "+" else "") + (if f.sign then "+" else "") <> repeat "0" (f.before - one) <> (if f.comma then "0,0" else "0") <> (if f.after > zero then "." else "") <> (repeat "0" f.after) <> (if f.abbreviations then "a" else "") -parseFormatString ∷ String → Either String Formatter +parseFormatString :: String -> Either String Formatter parseFormatString = runP formatParser - -formatParser ∷ P.Parser String Formatter +formatParser :: P.Parser String Formatter formatParser = do - sign ← PC.optionMaybe $ PC.try $ PS.string "+" - before ← some $ PS.string "0" - comma ← PC.optionMaybe $ PC.try $ PS.string ",0" - dot ← PC.optionMaybe $ PC.try $ PS.string "." - after ← for dot \_ → + sign <- PC.optionMaybe $ PC.try $ PS.string "+" + before <- some $ PS.string "0" + comma <- PC.optionMaybe $ PC.try $ PS.string ",0" + dot <- PC.optionMaybe $ PC.try $ PS.string "." + after <- for dot \_ -> PC.try $ many $ PS.string "0" - abbreviations ← PC.optionMaybe $ PC.try $ PS.string "a" + abbreviations <- PC.optionMaybe $ PC.try $ PS.string "a" pure $ Formatter { sign: isJust sign @@ -94,155 +92,157 @@ foreign import showNumberAsInt :: Number -> String -- | See [purescript-decimals](https://pursuit.purescript.org/packages/purescript-decimals/4.0.0) -- | for working with arbitrary precision decimals, which supports simple number -- | formatting for numbers that go beyond the precision available with `Number`. -format ∷ Formatter → Number → String -format (Formatter f) num = +format :: Formatter -> Number -> String +format (Formatter f) num = do let absed = Math.abs num - tens = - if absed > 0.0 - then max (Int.floor $ Math.log absed / Math.ln10) 0 - else 0 - in if f.abbreviations - then - let - thousands = tens / 3 - abbr | thousands == 0 = "" - | thousands == 1 = "K" - | thousands == 2 = "M" - | thousands == 3 = "G" - | thousands == 4 = "T" - | thousands == 5 = "P" - | thousands == 6 = "E" - | thousands == 7 = "Z" - | thousands == 8 = "Y" - | otherwise = "10e+" <> show (thousands * 3) - newNum = if thousands < 1 then num else num / Math.pow 1000.0 (Int.toNumber thousands) - in - format (Formatter f{abbreviations = false}) newNum <> abbr - else - let - zeros = f.before - tens - one - factor = Math.pow 10.0 (Int.toNumber (max 0 f.after)) - rounded = Math.round (absed * factor) / factor - integer = Math.floor rounded - leftoverDecimal = rounded - integer - leftover = Math.round $ leftoverDecimal * factor - leftoverWithZeros = - let leftoverString = showNumberAsInt leftover - leftoverLength = Str.length leftoverString - zeros' = repeat "0" (f.after - leftoverLength) - in zeros' <> leftoverString - shownInt = - if f.comma - then addCommas [] zero (Arr.reverse (CU.toCharArray (repeat "0" zeros <> showNumberAsInt integer))) - else repeat "0" zeros <> showNumberAsInt integer - - addCommas ∷ Array Char → Int → Array Char → String - addCommas acc counter input = case Arr.uncons input of - Nothing → CU.fromCharArray acc - Just {head, tail} | counter < 3 → - addCommas (Arr.cons head acc) (counter + one) tail - _ → - addCommas (Arr.cons ',' acc) zero input - in - (if num < zero then "-" else if num > zero && f.sign then "+" else "") - <> shownInt - <> (if f.after < 1 - then "" - else - "." - <> (if leftover == 0.0 then repeat "0" f.after else "") - <> (if leftover > 0.0 then leftoverWithZeros else "")) - - -unformat ∷ Formatter → String → Either String Number + tens + | absed > 0.0 = max (Int.floor $ Math.log absed / Math.ln10) 0 + | otherwise = 0 + + if f.abbreviations then do + let + thousands = tens / 3 + abbr + | thousands == 0 = "" + | thousands == 1 = "K" + | thousands == 2 = "M" + | thousands == 3 = "G" + | thousands == 4 = "T" + | thousands == 5 = "P" + | thousands == 6 = "E" + | thousands == 7 = "Z" + | thousands == 8 = "Y" + | otherwise = "10e+" <> show (thousands * 3) + newNum = if thousands < 1 then num else num / Math.pow 1000.0 (Int.toNumber thousands) + + format (Formatter f { abbreviations = false }) newNum <> abbr + else do + let + zeros = f.before - tens - one + factor = Math.pow 10.0 (Int.toNumber (max 0 f.after)) + rounded = Math.round (absed * factor) / factor + integer = Math.floor rounded + leftoverDecimal = rounded - integer + leftover = Math.round $ leftoverDecimal * factor + + leftoverWithZeros = do + let + leftoverString = showNumberAsInt leftover + leftoverLength = Str.length leftoverString + zeros' = repeat "0" (f.after - leftoverLength) + + zeros' <> leftoverString + + shownInt = + if f.comma then + addCommas [] zero (Arr.reverse (CU.toCharArray (repeat "0" zeros <> showNumberAsInt integer))) + else + repeat "0" zeros <> showNumberAsInt integer + + addCommas :: Array Char -> Int -> Array Char -> String + addCommas acc counter input = case Arr.uncons input of + Nothing -> CU.fromCharArray acc + Just { head, tail } | counter < 3 -> + addCommas (Arr.cons head acc) (counter + one) tail + _ -> + addCommas (Arr.cons ',' acc) zero input + + leftovers = + if f.after < 1 then "" + else + "." + <> (if leftover == 0.0 then repeat "0" f.after else "") + <> (if leftover > 0.0 then leftoverWithZeros else "") + + (if num < zero then "-" else if num > zero && f.sign then "+" else "") + <> shownInt + <> leftovers + +unformat :: Formatter -> String -> Either String Number unformat = runP <<< unformatParser -unformatParser ∷ Formatter → P.Parser String Number +unformatParser :: Formatter -> P.Parser String Number unformatParser (Formatter f) = do - minus ← PC.optionMaybe $ PC.try $ PS.string "-" - sign ← case minus of - Nothing | f.sign → + minus <- PC.optionMaybe $ PC.try $ PS.string "-" + sign <- case minus of + Nothing | f.sign -> (PS.string "+") $> 1.0 - Nothing | otherwise → + Nothing | otherwise -> pure 1.0 - Just _ → + Just _ -> pure (-1.0) let - digitsWithCommas ∷ P.Parser String (Array Int) + digitsWithCommas :: P.Parser String (Array Int) digitsWithCommas = - if not f.comma - then do + if not f.comma then some parseDigit <* PS.string "." - else - digitsWithCommas' [ ] + else + digitsWithCommas' [] - digitsWithCommas' ∷ Array Int → P.Parser String (Array Int) + digitsWithCommas' :: Array Int -> P.Parser String (Array Int) digitsWithCommas' accum = do - ds ← some parseDigit + ds <- some parseDigit + + when (Arr.null accum && Arr.length ds > 3) do + P.fail "Wrong number of digits between thousand separators" - when (Arr.null accum && Arr.length ds > 3) - $ P.fail "Wrong number of digits between thousand separators" - when (Arr.length ds /= 3) - $ P.fail "Wrong number of digits between thousand separators" + when (Arr.length ds /= 3) do + P.fail "Wrong number of digits between thousand separators" - sep ← PS.oneOf [',', '.'] + sep <- PS.oneOf [ ',', '.' ] case sep of - '.' → pure $ accum <> ds - ',' → digitsWithCommas' $ accum <> ds - _ → P.fail "Incorrect symbol, expected ',' or '.'" - - beforeDigits ← digitsWithCommas - before ← - if Arr.length beforeDigits < f.before - then P.fail "Error: too few digits before dot" - else pure $ Int.toNumber $ foldDigits beforeDigits - - afterDigits ← some parseDigit - after ← - if Arr.length afterDigits < f.after - then P.fail "Error: too few digits after dot" - else pure $ Int.toNumber $ foldDigits afterDigits - - abbr ← - if f.abbreviations - then do - letter ← PC.optionMaybe $ PC.try $ PS.oneOf ['K', 'M', 'G', 'T', 'P', 'E', 'Z', 'Y'] + '.' -> pure $ accum <> ds + ',' -> digitsWithCommas' $ accum <> ds + _ -> P.fail "Incorrect symbol, expected ',' or '.'" + + beforeDigits <- digitsWithCommas + before <- + if Arr.length beforeDigits < f.before then + P.fail "Error: too few digits before dot" + else + pure $ Int.toNumber $ foldDigits beforeDigits + + afterDigits <- some parseDigit + after <- + if Arr.length afterDigits < f.after then + P.fail "Error: too few digits after dot" + else + pure $ Int.toNumber $ foldDigits afterDigits + + abbr <- + if f.abbreviations then do + letter <- PC.optionMaybe $ PC.try $ PS.oneOf [ 'K', 'M', 'G', 'T', 'P', 'E', 'Z', 'Y' ] case letter of - Nothing → do - e ← PC.optionMaybe $ PS.string "10e+" + Nothing -> do + e <- PC.optionMaybe $ PS.string "10e+" case e of - Nothing → - pure 0 - Just _ → - map foldDigits $ many parseDigit - Just 'K' → pure 3 - Just 'M' → pure 6 - Just 'G' → pure 9 - Just 'T' → pure 12 - Just 'P' → pure 15 - Just 'E' → pure 18 - Just 'Z' → pure 21 - Just 'Y' → pure 24 - _ → pure 0 - else pure 0 - pure - $ Math.pow 10.0 (Int.toNumber abbr) - * sign - * (before + after / Math.pow 10.0 (Int.toNumber f.after)) - -formatNumber ∷ String → Number → Either String String -formatNumber pattern number = - parseFormatString pattern <#> flip format number - -unformatNumber ∷ String → String → Either String Number -unformatNumber pattern str = - parseFormatString pattern >>= flip unformat str + Nothing -> pure 0 + Just _ -> map foldDigits $ many parseDigit + Just 'K' -> pure 3 + Just 'M' -> pure 6 + Just 'G' -> pure 9 + Just 'T' -> pure 12 + Just 'P' -> pure 15 + Just 'E' -> pure 18 + Just 'Z' -> pure 21 + Just 'Y' -> pure 24 + _ -> pure 0 + else pure 0 + + pure $ + Math.pow 10.0 (Int.toNumber abbr) + * sign + * (before + after / Math.pow 10.0 (Int.toNumber f.after)) + +formatNumber :: String -> Number -> Either String String +formatNumber pattern number = parseFormatString pattern <#> flip format number + +unformatNumber :: String -> String -> Either String Number +unformatNumber pattern str = parseFormatString pattern >>= flip unformat str -- Supposed to be used in chaining, because after calling format number there is no -- good way to extract number back to show. -formatOrShowNumber ∷ String → Number → String -formatOrShowNumber patter number = - either (const $ show number) identity - $ formatNumber patter number +formatOrShowNumber :: String -> Number -> String +formatOrShowNumber patter number = either (const $ show number) identity $ formatNumber patter number diff --git a/src/Data/Formatter/Parser/Interval.purs b/src/Data/Formatter/Parser/Interval.purs index 330c9cd..4a9c4c3 100644 --- a/src/Data/Formatter/Parser/Interval.purs +++ b/src/Data/Formatter/Parser/Interval.purs @@ -24,57 +24,56 @@ import Text.Parsing.Parser as P import Text.Parsing.Parser.Combinators as PC import Text.Parsing.Parser.String as PS -parseRecurringInterval ∷ ∀ a b. P.Parser String a → P.Parser String b → P.Parser String (I.RecurringInterval a b) +parseRecurringInterval :: forall a b. P.Parser String a -> P.Parser String b -> P.Parser String (I.RecurringInterval a b) parseRecurringInterval duration date = I.RecurringInterval <$> (PS.string "R" *> parseMaybeInteger) <*> (PS.string "/" *> parseInterval duration date) -parseInterval ∷ ∀ a b. P.Parser String a → P.Parser String b → P.Parser String (I.Interval a b) -parseInterval duration date = [startEnd, durationEnd, startDuration, durationOnly] <#> PC.try # PC.choice +parseInterval :: forall a b. P.Parser String a -> P.Parser String b -> P.Parser String (I.Interval a b) +parseInterval duration date = [ startEnd, durationEnd, startDuration, durationOnly ] <#> PC.try # PC.choice where startEnd = I.StartEnd <$> date <* PS.string "/" <*> date durationEnd = I.DurationEnd <$> duration <* PS.string "/" <*> date startDuration = I.StartDuration <$> date <* PS.string "/" <*> duration durationOnly = I.DurationOnly <$> duration -parseIsoDuration ∷ P.Parser String IsoDuration +parseIsoDuration :: P.Parser String IsoDuration parseIsoDuration = do - dur ← parseDuration + dur <- parseDuration case mkIsoDuration dur of - Left errs → + Left errs -> do let errorStr = intercalate ", " (prettyError <$> errs) - in P.fail $ "Extracted Duration is not valid ISO duration (" <> errorStr <> ")" - Right a → pure a + P.fail $ "Extracted Duration is not valid ISO duration (" <> errorStr <> ")" + Right a -> pure a -parseDuration ∷ P.Parser String I.Duration +parseDuration :: P.Parser String I.Duration parseDuration = PS.string "P" *> (weekDuration <|> fullDuration) where weekDuration = mkComponentsParser [ Tuple I.week "W" ] fullDuration = (append <$> durationDatePart <*> durationTimePart) `failIfEmpty` "Must contain valid duration components" - durationDatePart = PC.option mempty $ PC.try $ mkComponentsParser [ Tuple I.year "Y" , Tuple I.month "M" , Tuple I.day "D" ] - durationTimePart = PC.option mempty $ (PC.try $ PS.string "T") *> (mkComponentsParser [ Tuple I.hour "H" , Tuple I.minute "M" , Tuple I.second "S" ]) + durationDatePart = PC.option mempty $ PC.try $ mkComponentsParser [ Tuple I.year "Y", Tuple I.month "M", Tuple I.day "D" ] + durationTimePart = PC.option mempty $ (PC.try $ PS.string "T") *> (mkComponentsParser [ Tuple I.hour "H", Tuple I.minute "M", Tuple I.second "S" ]) +failIfEmpty :: forall a. Monoid a => Eq a => P.Parser String a -> String -> P.Parser String a +failIfEmpty p str = p >>= \x -> if x == mempty then P.fail str else pure x -failIfEmpty ∷ ∀ a. Monoid a ⇒ Eq a ⇒ P.Parser String a → String → P.Parser String a -failIfEmpty p str = p >>= \x → if x == mempty then P.fail str else pure x - -mkComponentsParser ∷ Array (Tuple (Number → I.Duration) String) → P.Parser String I.Duration +mkComponentsParser :: Array (Tuple (Number -> I.Duration) String) -> P.Parser String I.Duration mkComponentsParser arr = p `failIfEmpty` ("None of valid duration components (" <> (show $ snd <$> arr) <> ") were present") where p = arr <#> applyDurations # sequence <#> foldFoldableMaybe - applyDurations ∷ Tuple (Number → I.Duration) String → P.Parser String (Maybe I.Duration) + + applyDurations :: Tuple (Number -> I.Duration) String -> P.Parser String (Maybe I.Duration) applyDurations (Tuple f c) = PC.optionMaybe $ PC.try (f <$> component c) - foldFoldableMaybe ∷ ∀ f a. Foldable f ⇒ Monoid a ⇒ f (Maybe a) → a + foldFoldableMaybe :: forall f a. Foldable f => Monoid a => f (Maybe a) -> a foldFoldableMaybe = foldMap fold - component ∷ String → P.Parser String Number + component :: String -> P.Parser String Number component designator = parseNumber <* PS.string designator - -- parser for DateTime in UTC time zone using "extended format" -parseDateTime ∷ ∀ m. Monad m ⇒ P.ParserT String m DateTime +parseDateTime :: forall m. Monad m => P.ParserT String m DateTime parseDateTime = unformatParser extendedDateTimeFormatInUTC -extendedDateTimeFormatInUTC ∷ Formatter +extendedDateTimeFormatInUTC :: Formatter extendedDateTimeFormatInUTC = parseFormatString "YYYY-MM-DDTHH:mm:ssZ" # either unsafeCrashWith identity -- the format must be valid ISO date format diff --git a/src/Data/Formatter/Parser/Number.purs b/src/Data/Formatter/Parser/Number.purs index 8741205..b7b3459 100644 --- a/src/Data/Formatter/Parser/Number.purs +++ b/src/Data/Formatter/Parser/Number.purs @@ -19,26 +19,25 @@ import Data.Maybe (Maybe(..)) import Data.Number (fromString) import Data.Foldable (foldMap) -parseInteger ∷ ∀ m. Monad m ⇒ P.ParserT String m Int +parseInteger :: forall m. Monad m => P.ParserT String m Int parseInteger = some parseDigit <#> foldDigits -parseMaybeInteger ∷ ∀ m. Monad m ⇒ P.ParserT String m (Maybe Int) +parseMaybeInteger :: forall m. Monad m => P.ParserT String m (Maybe Int) parseMaybeInteger = PC.optionMaybe parseInteger -parseFractional ∷ ∀ m. Monad m ⇒ P.ParserT String m Number +parseFractional :: forall m. Monad m => P.ParserT String m Number parseFractional = do digitStr <- (some parseDigit) <#> (foldMap show >>> ("0." <> _)) case fromString digitStr of - Just n -> pure n - Nothing -> P.fail ("Not a number: " <> digitStr) + Just n -> pure n + Nothing -> P.fail ("Not a number: " <> digitStr) -parseNumber ∷ ∀ m. Monad m ⇒ P.ParserT String m Number +parseNumber :: forall m. Monad m => P.ParserT String m Number parseNumber = (+) <$> (parseInteger <#> toNumber) - <*> (PC.option 0.0 $ PC.try $ PS.oneOf ['.', ','] *> parseFractional) + <*> (PC.option 0.0 $ PC.try $ PS.oneOf [ '.', ',' ] *> parseFractional) - -parseDigit ∷ ∀ m. Monad m ⇒ P.ParserT String m Int +parseDigit :: forall m. Monad m => P.ParserT String m Int parseDigit = PC.try $ PS.char `oneOfAs` [ Tuple '0' 0 , Tuple '1' 1 @@ -49,4 +48,5 @@ parseDigit = PC.try $ PS.char `oneOfAs` , Tuple '6' 6 , Tuple '7' 7 , Tuple '8' 8 - , Tuple '9' 9] + , Tuple '9' 9 + ] diff --git a/src/Data/Formatter/Parser/Utils.purs b/src/Data/Formatter/Parser/Utils.purs index fbe6de9..9696a8b 100644 --- a/src/Data/Formatter/Parser/Utils.purs +++ b/src/Data/Formatter/Parser/Utils.purs @@ -14,14 +14,14 @@ import Data.Bifunctor (lmap) import Data.Foldable (class Foldable) import Data.Either (Either) -oneOfAs ∷ ∀ c s m f a b. Functor f ⇒ Foldable f ⇒ Monad m ⇒ (a → ParserT s m b) → f (Tuple a c) → ParserT s m c -oneOfAs p xs = PC.choice $ (\(Tuple s r) → p s $> r) <$> xs +oneOfAs :: forall c s m f a b. Functor f => Foldable f => Monad m => (a -> ParserT s m b) -> f (Tuple a c) -> ParserT s m c +oneOfAs p xs = PC.choice $ (\(Tuple s r) -> p s $> r) <$> xs -runP ∷ ∀ a. Parser String a → String → Either String a +runP :: forall a. Parser String a -> String -> Either String a runP p s = lmap printError $ runParser s (p <* PS.eof) -printError ∷ ParseError → String -printError err = parseErrorMessage err <> " " <> (printPosition $ parseErrorPosition err) +printError :: ParseError -> String +printError err = parseErrorMessage err <> " " <> (printPosition $ parseErrorPosition err) -printPosition ∷ Position → String -printPosition (Position {line, column}) = "(line " <> show line <> ", col " <>show column <> ")" +printPosition :: Position -> String +printPosition (Position { line, column }) = "(line " <> show line <> ", col " <> show column <> ")" diff --git a/test/src/DateTime.purs b/test/src/DateTime.purs index 167ee66..1532f04 100644 --- a/test/src/DateTime.purs +++ b/test/src/DateTime.purs @@ -11,24 +11,24 @@ import Data.List (fromFoldable) import Effect.Aff.Class (class MonadAff) import Test.Utils (forAll, makeDateTime, describe, it, shouldEqual) -datetimeTest ∷ forall m. MonadReader Int m ⇒ MonadAff m ⇒ m Unit +datetimeTest :: forall m. MonadReader Int m => MonadAff m => m Unit datetimeTest = describe "Data.Formatter.DateTime" do - forAll (\a → a.format <> " | " <> a.dateStr) + forAll (\a -> a.format <> " | " <> a.dateStr) "formatDateTime/unformatDateTime should format/unformat dateTime" - [ { format: "MM/DD/YYYY", dateStr: "04/12/2017" , date: makeDateTime 2017 4 12 11 3 4 234} - , { format: "YYYY", dateStr: "0017" , date: makeDateTime 17 0 0 0 0 0 0} - , { format: "MMMM", dateStr: "April" , date: makeDateTime 2017 4 12 11 3 4 234} - , { format: "YYYY-DD-MM", dateStr: "2017-12-04" , date: makeDateTime 2017 4 12 11 3 4 234} - , { format: "YYYY-MMM", dateStr: "2017-Apr" , date: makeDateTime 2017 4 12 11 3 4 234} - , { format: "MMM D", dateStr: "Apr 1" , date: makeDateTime 2017 4 1 0 0 0 0} - , { format: "dddd, MMM D", dateStr: "Saturday, Apr 1" , date: makeDateTime 2017 4 1 0 0 0 0} - , { format: "ddd, MMM D", dateStr: "Sat, Apr 1" , date: makeDateTime 2017 4 1 0 0 0 0} - , { format: "E", dateStr: "6", date: makeDateTime 2017 4 1 0 0 0 0} - , { format: "hh:mm:ss:SSS a", dateStr: "11:03:04:234 AM" , date: makeDateTime 2017 4 12 11 3 4 234} - , { format: "YY", dateStr: "17" , date: makeDateTime 2017 4 12 11 3 4 234} - , { format: "YY", dateStr: "17" , date: makeDateTime 20017 4 12 0 0 0 0} -- Format 20017 with YY - , { format: "YY", dateStr: "00" , date: makeDateTime 0 4 12 0 0 0 0} -- Format 0 with YY - , { format: "YY", dateStr: "01" , date: makeDateTime (-1) 4 12 0 0 0 0} -- Format -1 with YY + [ { format: "MM/DD/YYYY", dateStr: "04/12/2017", date: makeDateTime 2017 4 12 11 3 4 234 } + , { format: "YYYY", dateStr: "0017", date: makeDateTime 17 0 0 0 0 0 0 } + , { format: "MMMM", dateStr: "April", date: makeDateTime 2017 4 12 11 3 4 234 } + , { format: "YYYY-DD-MM", dateStr: "2017-12-04", date: makeDateTime 2017 4 12 11 3 4 234 } + , { format: "YYYY-MMM", dateStr: "2017-Apr", date: makeDateTime 2017 4 12 11 3 4 234 } + , { format: "MMM D", dateStr: "Apr 1", date: makeDateTime 2017 4 1 0 0 0 0 } + , { format: "dddd, MMM D", dateStr: "Saturday, Apr 1", date: makeDateTime 2017 4 1 0 0 0 0 } + , { format: "ddd, MMM D", dateStr: "Sat, Apr 1", date: makeDateTime 2017 4 1 0 0 0 0 } + , { format: "E", dateStr: "6", date: makeDateTime 2017 4 1 0 0 0 0 } + , { format: "hh:mm:ss:SSS a", dateStr: "11:03:04:234 AM", date: makeDateTime 2017 4 12 11 3 4 234 } + , { format: "YY", dateStr: "17", date: makeDateTime 2017 4 12 11 3 4 234 } + , { format: "YY", dateStr: "17", date: makeDateTime 20017 4 12 0 0 0 0 } -- Format 20017 with YY + , { format: "YY", dateStr: "00", date: makeDateTime 0 4 12 0 0 0 0 } -- Format 0 with YY + , { format: "YY", dateStr: "01", date: makeDateTime (-1) 4 12 0 0 0 0 } -- Format -1 with YY , { format: "hh:m:s a", dateStr: "11:3:4 AM", date: makeDateTime 2017 4 12 11 3 4 234 } , { format: "hh a", dateStr: "12 AM", date: makeDateTime 0 1 1 0 0 0 0 } , { format: "hh a", dateStr: "12 PM", date: makeDateTime 0 1 1 12 0 0 0 } @@ -47,11 +47,11 @@ datetimeTest = describe "Data.Formatter.DateTime" do , { format: "HHmmssSSS", dateStr: "134530123", date: makeDateTime 2017 4 10 13 45 30 123 } , { format: "HHmm", dateStr: "1345", date: makeDateTime 2017 4 10 13 45 30 123 } , { format: "X", dateStr: "1499779279", date: makeDateTime 2017 7 11 13 21 19 0 } - , { format: "YYYY", dateStr: "-2000" , date: makeDateTime (-2000) 0 0 0 0 0 0 } + , { format: "YYYY", dateStr: "-2000", date: makeDateTime (-2000) 0 0 0 0 0 0 } ] - (\({ format, dateStr, date }) → do - (format `FDT.formatDateTime` date) `shouldEqual` (Right dateStr) - (void $ format `FDT.unformatDateTime` dateStr) `shouldEqual` (Right unit) + ( \({ format, dateStr, date }) -> do + (format `FDT.formatDateTime` date) `shouldEqual` (Right dateStr) + (void $ format `FDT.unformatDateTime` dateStr) `shouldEqual` (Right unit) ) describe "hour 24" do @@ -63,54 +63,53 @@ datetimeTest = describe "Data.Formatter.DateTime" do it "+1" $ shouldEqual (FDT.unformatDateTime "YYYY-DD-MM HH:mm:ss:SSS" "0000-01-01 24:00:00:000") - (Right $ makeDateTime 0 1 2 0 0 0 0 ) + (Right $ makeDateTime 0 1 2 0 0 0 0) describe "hour {0,12} {am,pm}" do let format = "hh a" - it "00 AM" $ FDT.unformatDateTime format "00 AM" `shouldEqual` (Right $ makeDateTime 0 1 1 0 0 0 0 ) - it "00 PM" $ FDT.unformatDateTime format "00 PM" `shouldEqual` (Right $ makeDateTime 0 1 1 12 0 0 0 ) - it "12 PM" $ FDT.unformatDateTime format "12 PM" `shouldEqual` (Right $ makeDateTime 0 1 1 12 0 0 0 ) - it "12 AM" $ FDT.unformatDateTime format "12 AM" `shouldEqual` (Right $ makeDateTime 0 1 1 0 0 0 0 ) + it "00 AM" $ FDT.unformatDateTime format "00 AM" `shouldEqual` (Right $ makeDateTime 0 1 1 0 0 0 0) + it "00 PM" $ FDT.unformatDateTime format "00 PM" `shouldEqual` (Right $ makeDateTime 0 1 1 12 0 0 0) + it "12 PM" $ FDT.unformatDateTime format "12 PM" `shouldEqual` (Right $ makeDateTime 0 1 1 12 0 0 0) + it "12 AM" $ FDT.unformatDateTime format "12 AM" `shouldEqual` (Right $ makeDateTime 0 1 1 0 0 0 0) describe "parseFormatString" do forAll _.str "should parse" dateformats - (\f → (FDT.parseFormatString f.str) `shouldEqual` (Right f.format)) + (\f -> (FDT.parseFormatString f.str) `shouldEqual` (Right f.format)) forAll _.str - "shouldn't parse" + "shouldn't parse" invalidDateformats - (\f → (FDT.parseFormatString f.str) `shouldEqual` (Left $ "Expected EOF " <> f.pos)) + (\f -> (FDT.parseFormatString f.str) `shouldEqual` (Left $ "Expected EOF " <> f.pos)) forAll - (\a → a.format <> " | " <> a.date) + (\a -> a.format <> " | " <> a.date) "s ≡ format (unformat s)" - [ {date: "2017-12-04 234", format: "YYYY-DD-MM SSS" } - , {date: "3456-09-10 333", format: "YYYY-DD-MM SSS" } - , {date: "111230003", format: "hhmmssSSS"} - , {date: "11123012", format: "hhmmssSS"} - , {date: "1112301", format: "hhmmssS"} - , {date: "1499779279", format: "X"} + [ { date: "2017-12-04 234", format: "YYYY-DD-MM SSS" } + , { date: "3456-09-10 333", format: "YYYY-DD-MM SSS" } + , { date: "111230003", format: "hhmmssSSS" } + , { date: "11123012", format: "hhmmssSS" } + , { date: "1112301", format: "hhmmssS" } + , { date: "1499779279", format: "X" } ] - (\({date, format}) → (FDT.unformatDateTime format date >>= FDT.formatDateTime format) `shouldEqual` (Right date)) + (\({ date, format }) -> (FDT.unformatDateTime format date >>= FDT.formatDateTime format) `shouldEqual` (Right date)) forAll - (\a → show a.date <> "|" <> FDT.printFormatter a.format) + (\a -> show a.date <> "|" <> FDT.printFormatter a.format) "s ≡ unformat (format s)" - (do - format ← dateformats - date ← dates - guard format.lossless - pure { date, format: format.format }) - (\({ date, format }) → FDT.unformat format (FDT.format format date) `shouldEqual` (Right date)) - - + ( do + format <- dateformats + date <- dates + guard format.lossless + pure { date, format: format.format } + ) + (\({ date, format }) -> FDT.unformat format (FDT.format format date) `shouldEqual` (Right date)) -dates ∷ Array DateTime +dates :: Array DateTime dates = [ makeDateTime 2017 4 12 11 3 4 234 , makeDateTime 2017 4 1 0 0 0 0 @@ -119,80 +118,80 @@ dates = , makeDateTime (-1) 4 12 0 0 0 0 ] -invalidDateformats ∷ Array { str ∷ String , pos ∷ String } +invalidDateformats :: Array { str :: String, pos :: String } invalidDateformats = [ { str: "YY-h-dddd HH:mm Z", pos: "(line 1, col 4)" } , { str: "YYYY-MM-DD M", pos: "(line 1, col 12)" } , { str: "YYYYM", pos: "(line 1, col 5)" } ] -dateformats ∷ Array { str ∷ String , lossless ∷ Boolean, format ∷ FDT.Formatter } +dateformats :: Array { str :: String, lossless :: Boolean, format :: FDT.Formatter } dateformats = [ { str: "YYYY-MM-DD" , lossless: false , format: fromFoldable - [ FDT.YearFull - , FDT.Placeholder "-" - , FDT.MonthTwoDigits - , FDT.Placeholder "-" - , FDT.DayOfMonthTwoDigits - ] + [ FDT.YearFull + , FDT.Placeholder "-" + , FDT.MonthTwoDigits + , FDT.Placeholder "-" + , FDT.DayOfMonthTwoDigits + ] } , { str: "Y-MM-DD HH:mm:ss:SSS" , lossless: true , format: fromFoldable - [ FDT.YearAbsolute - , FDT.Placeholder "-" - , FDT.MonthTwoDigits - , FDT.Placeholder "-" - , FDT.DayOfMonthTwoDigits - , FDT.Placeholder " " - , FDT.Hours24 - , FDT.Placeholder ":" - , FDT.MinutesTwoDigits - , FDT.Placeholder ":" - , FDT.SecondsTwoDigits - , FDT.Placeholder ":" - , FDT.Milliseconds - ] + [ FDT.YearAbsolute + , FDT.Placeholder "-" + , FDT.MonthTwoDigits + , FDT.Placeholder "-" + , FDT.DayOfMonthTwoDigits + , FDT.Placeholder " " + , FDT.Hours24 + , FDT.Placeholder ":" + , FDT.MinutesTwoDigits + , FDT.Placeholder ":" + , FDT.SecondsTwoDigits + , FDT.Placeholder ":" + , FDT.Milliseconds + ] } , { str: "YY-Z-DD HH:mm Z" , lossless: false , format: fromFoldable - [ FDT.YearTwoDigits - , FDT.Placeholder "-Z-" - , FDT.DayOfMonthTwoDigits - , FDT.Placeholder " " - , FDT.Hours24 - , FDT.Placeholder ":" - , FDT.MinutesTwoDigits - , FDT.Placeholder " Z" - ] + [ FDT.YearTwoDigits + , FDT.Placeholder "-Z-" + , FDT.DayOfMonthTwoDigits + , FDT.Placeholder " " + , FDT.Hours24 + , FDT.Placeholder ":" + , FDT.MinutesTwoDigits + , FDT.Placeholder " Z" + ] } , { str: "DD-MM-YYYY trololo HH-:-mm" , lossless: false , format: fromFoldable - [ FDT.DayOfMonthTwoDigits - , FDT.Placeholder "-" - , FDT.MonthTwoDigits - , FDT.Placeholder "-" - , FDT.YearFull - , FDT.Placeholder " trololo " - , FDT.Hours24 - , FDT.Placeholder "-:-" - , FDT.MinutesTwoDigits - ] + [ FDT.DayOfMonthTwoDigits + , FDT.Placeholder "-" + , FDT.MonthTwoDigits + , FDT.Placeholder "-" + , FDT.YearFull + , FDT.Placeholder " trololo " + , FDT.Hours24 + , FDT.Placeholder "-:-" + , FDT.MinutesTwoDigits + ] } , { str: "YYYY-DD-MM SSS" , lossless: false , format: fromFoldable - [ FDT.YearFull - , FDT.Placeholder "-" - , FDT.DayOfMonthTwoDigits - , FDT.Placeholder "-" - , FDT.MonthTwoDigits - , FDT.Placeholder " " - , FDT.Milliseconds - ] + [ FDT.YearFull + , FDT.Placeholder "-" + , FDT.DayOfMonthTwoDigits + , FDT.Placeholder "-" + , FDT.MonthTwoDigits + , FDT.Placeholder " " + , FDT.Milliseconds + ] } ] diff --git a/test/src/Interval.purs b/test/src/Interval.purs index 4bc3ff6..4160936 100644 --- a/test/src/Interval.purs +++ b/test/src/Interval.purs @@ -17,33 +17,32 @@ import Data.Maybe (Maybe(..)) import Partial.Unsafe (unsafeCrashWith) import Test.Utils (forAll, makeDateTime, describe, shouldEqual) -prop ∷ ∀ m e f. MonadReader Int m ⇒ MonadAff m ⇒ Foldable f ⇒ String → f {str ∷ String | e} → ({str ∷ String | e} → Aff Unit) → m Unit +prop :: forall m e f. MonadReader Int m => MonadAff m => Foldable f => String -> f { str :: String | e } -> ({ str :: String | e } -> Aff Unit) -> m Unit prop = forAll (show <<< _.str) -intervalTest ∷ forall m. MonadReader Int m ⇒ MonadAff m ⇒ m Unit +intervalTest :: forall m. MonadReader Int m => MonadAff m => m Unit intervalTest = describe "Data.Formatter.Interval" do - prop "shouldn't unformat invalid Interval" invalidIntervals \({str, err}) → do + prop "shouldn't unformat invalid Interval" invalidIntervals \({ str, err }) -> do (unformatInterval str) `shouldEqual` (Left $ err) - prop "shouldn't unformat invalid Duration" invalidDurations \({str, err}) → do + prop "shouldn't unformat invalid Duration" invalidDurations \({ str, err }) -> do (runP parseIsoDuration str) `shouldEqual` (Left $ err) - prop "should unformat RecurringInterval" arbRecurringInterval \({ str, interval }) → do + prop "should unformat RecurringInterval" arbRecurringInterval \({ str, interval }) -> do (unformatRecurringInterval str) `shouldEqual` (Right interval) - prop "format (unformat s) = s" arbRecurringInterval \({ str, formatedStr }) → do + prop "format (unformat s) = s" arbRecurringInterval \({ str, formatedStr }) -> do (formatRecurringInterval <$> (unformatRecurringInterval str)) `shouldEqual` (Right formatedStr) - prop "unformat (format s) = s" arbRecurringInterval \({ interval }) → do + prop "unformat (format s) = s" arbRecurringInterval \({ interval }) -> do (unformatRecurringInterval $ formatRecurringInterval interval) `shouldEqual` (Right interval) - -unsafeMkToIsoDuration ∷ I.Duration → IsoDuration +unsafeMkToIsoDuration :: I.Duration -> IsoDuration unsafeMkToIsoDuration d = mkIsoDuration d -- the duration must be valid ISO duration # either (\_ -> unsafeCrashWith "unsafeMkToIsoDuration failed") identity -durations ∷ Array { str∷ String, formatedStr∷ String, dur ∷ IsoDuration } +durations :: Array { str :: String, formatedStr :: String, dur :: IsoDuration } durations = [ { str: "P1W", formatedStr: "P1W", dur: I.week 1.0 } , { str: "P1.0W", formatedStr: "P1W", dur: I.week 1.0 } @@ -56,9 +55,9 @@ durations = , { str: "PT1M", formatedStr: "PT1M", dur: I.minute 1.0 } , { str: "PT1S", formatedStr: "PT1S", dur: I.second 1.0 } , { str: "PT1H1S", formatedStr: "PT1H1S", dur: I.hour 1.0 <> I.second 1.0 } - ] <#> (\a → a { dur = unsafeMkToIsoDuration a.dur }) + ] <#> (\a -> a { dur = unsafeMkToIsoDuration a.dur }) -invalidDurations ∷ Array { err ∷ String, str ∷ String} +invalidDurations :: Array { err :: String, str :: String } invalidDurations = [ { err: errInvalidISO "Hour" <> "(line 1, col 13)", str: "P1DT1.5H0M1S" } , { err: errInvalidISO "Year" <> "(line 1, col 10)", str: "P1.5Y0.5M" } @@ -81,11 +80,13 @@ invalidDurations = errPrefix = "Expected \"P\" " errEOF = "Expected EOF " errInvalidISO c = - "Extracted Duration is not valid ISO duration " <> - "(Invalid usage of Fractional value at component `" <> c <> "`) " + "Extracted Duration is not valid ISO duration " + <> "(Invalid usage of Fractional value at component `" + <> c + <> "`) " errNoTimeComponent = "None of valid duration components ([\"H\",\"M\",\"S\"]) were present " -invalidIntervals ∷ Array {err ∷ String, str ∷ String} +invalidIntervals :: Array { err :: String, str :: String } invalidIntervals = [ { err: "Expected \"P\" (line 1, col 1)", str: "2007-03-01T13:00:00ZP1Y2M10DT2H30M" } , { err: "Expected \"P\" (line 1, col 1)", str: "2007-03-01T13:00:00Z-P1Y2M10D" } @@ -106,32 +107,32 @@ invalidIntervals = , { err: "Expected EOF (line 1, col 8)", str: "P1Y0.5M/P1Y0.5M" } ] -recurrences ∷ Array { str ∷ String, rec ∷ Maybe Int } +recurrences :: Array { str :: String, rec :: Maybe Int } recurrences = - [ {str: "", rec: Nothing} - , {str: "18", rec: Just 18} + [ { str: "", rec: Nothing } + , { str: "18", rec: Just 18 } ] -dates ∷ Array { str∷ String, date ∷ DateTime } +dates :: Array { str :: String, date :: DateTime } dates = [ { str: "2015-07-23T11:12:13Z", date: makeDateTime 2015 7 23 11 12 13 0 } - , { str: "2015-07-22T00:00:00Z", date: makeDateTime 2015 7 22 0 0 0 0 } + , { str: "2015-07-22T00:00:00Z", date: makeDateTime 2015 7 22 0 0 0 0 } ] -type ArbRecurringInterval = Array { str ∷ String, formatedStr ∷ String, interval ∷ I.RecurringInterval IsoDuration DateTime} -type ArbInterval = Array { str ∷ String, formatedStr ∷ String, interval ∷ I.Interval IsoDuration DateTime} +type ArbRecurringInterval = Array { str :: String, formatedStr :: String, interval :: I.RecurringInterval IsoDuration DateTime } +type ArbInterval = Array { str :: String, formatedStr :: String, interval :: I.Interval IsoDuration DateTime } -arbRecurringInterval ∷ ArbRecurringInterval +arbRecurringInterval :: ArbRecurringInterval arbRecurringInterval = do - rec ← recurrences - i ← arbInterval + rec <- recurrences + i <- arbInterval pure - { str : "R" <> rec.str <> "/" <> i.str - , formatedStr : "R" <> rec.str <> "/" <> i.formatedStr + { str: "R" <> rec.str <> "/" <> i.str + , formatedStr: "R" <> rec.str <> "/" <> i.formatedStr , interval: I.RecurringInterval rec.rec i.interval } -arbInterval ∷ ArbInterval +arbInterval :: ArbInterval arbInterval = fold [ arbIntervalStartEnd , arbIntervalDurationEnd @@ -139,39 +140,39 @@ arbInterval = fold , arbIntervalDurationOnly ] -arbIntervalStartEnd ∷ ArbInterval +arbIntervalStartEnd :: ArbInterval arbIntervalStartEnd = do - start ← dates - end ← dates + start <- dates + end <- dates pure { str: start.str <> "/" <> end.str , formatedStr: start.str <> "/" <> end.str , interval: I.StartEnd start.date end.date } -arbIntervalDurationEnd ∷ ArbInterval +arbIntervalDurationEnd :: ArbInterval arbIntervalDurationEnd = do - dur ← durations - end ← dates + dur <- durations + end <- dates pure { str: dur.str <> "/" <> end.str , formatedStr: dur.formatedStr <> "/" <> end.str , interval: I.DurationEnd dur.dur end.date } -arbIntervalStartDuration ∷ ArbInterval +arbIntervalStartDuration :: ArbInterval arbIntervalStartDuration = do - dur ← durations - start ← dates + dur <- durations + start <- dates pure - { str: start.str <> "/" <> dur.str - , formatedStr: start.str <> "/" <> dur.formatedStr + { str: start.str <> "/" <> dur.str + , formatedStr: start.str <> "/" <> dur.formatedStr , interval: I.StartDuration start.date dur.dur } -arbIntervalDurationOnly ∷ ArbInterval +arbIntervalDurationOnly :: ArbInterval arbIntervalDurationOnly = do - dur ← durations + dur <- durations pure { str: dur.str , formatedStr: dur.formatedStr diff --git a/test/src/Main.purs b/test/src/Main.purs index c21fea9..4f71d29 100644 --- a/test/src/Main.purs +++ b/test/src/Main.purs @@ -9,7 +9,7 @@ import Test.DateTime (datetimeTest) import Test.Interval (intervalTest) import Test.Number (numberTest) -main ∷ Effect Unit +main :: Effect Unit main = launchAff_ $ flip runReaderT 0 do intervalTest datetimeTest diff --git a/test/src/Number.purs b/test/src/Number.purs index 00f4b0a..737e65d 100644 --- a/test/src/Number.purs +++ b/test/src/Number.purs @@ -9,52 +9,51 @@ import Effect.Aff.Class (class MonadAff) import Test.Utils (forAll, describe, shouldEqual) -numberTest ∷ forall m. MonadReader Int m ⇒ MonadAff m ⇒ m Unit +numberTest :: forall m. MonadReader Int m => MonadAff m => m Unit numberTest = describe "Data.Formatter.Number" do forAll _.str "should print formatter" numberformatts - (\({fmt, str}) → printFormatter fmt `shouldEqual` str) + (\({ fmt, str }) -> printFormatter fmt `shouldEqual` str) forAll _.str "parse format string" numberformatts - (\({fmt, str}) → parseFormatString str `shouldEqual` (Right fmt)) + (\({ fmt, str }) -> parseFormatString str `shouldEqual` (Right fmt)) forAll show "unformat (format n) = n" - [100.2, 100.1, 100.3, 10004000.0, -100.2, -100.1, -100.3, -10004000.0] - (\n → unformat fmt1 (format fmt1 n) `shouldEqual` (Right n)) + [ 100.2, 100.1, 100.3, 10004000.0, -100.2, -100.1, -100.3, -10004000.0 ] + (\n -> unformat fmt1 (format fmt1 n) `shouldEqual` (Right n)) forAll show "format (unformat n) = n" - ["001.12", "001.02", "-001.12", "-001.02"] - (\n → (format fmt1 <$> (unformat fmt1 n)) `shouldEqual` (Right n)) + [ "001.12", "001.02", "-001.12", "-001.02" ] + (\n -> (format fmt1 <$> (unformat fmt1 n)) `shouldEqual` (Right n)) forAll show "format (unformat n) = n" - ["+02.12", "+13.12", "-02.12", "-13.12"] - (\n → (format fmt3 <$> (unformat fmt3 n)) `shouldEqual` (Right n)) + [ "+02.12", "+13.12", "-02.12", "-13.12" ] + (\n -> (format fmt3 <$> (unformat fmt3 n)) `shouldEqual` (Right n)) - forAll (\{fmt: (Formatter fmt), input} -> "rounds up " <> show input <> " (" <> show fmt.after <> " digits)") + forAll (\{ fmt: (Formatter fmt), input } -> "rounds up " <> show input <> " (" <> show fmt.after <> " digits)") "rounding" - [ {fmt: fmt4, input: 1.99999, expected: "02"} - , {fmt: fmt1, input: 1.99999, expected: "002.00"} - , {fmt: fmt5, input: 1.99999, expected: "2.0000"} - , {fmt: fmt1, input: 1.89999, expected: "001.90"} - , {fmt: fmt5, input: 1.67899, expected: "1.6790"} - , {fmt: fmt6, input: 12.9, expected: "13"} - , {fmt: fmt7, input: 1.123456789012345678901234, expected: "1.1234567890123457"} - , {fmt: fmt6, input: 12345678901234567.8901234, expected: "12,345,678,901,234,568"} - , {fmt: fmt5, input: 123456789012.345678901234, expected: "123,456,789,012.3457"} + [ { fmt: fmt4, input: 1.99999, expected: "02" } + , { fmt: fmt1, input: 1.99999, expected: "002.00" } + , { fmt: fmt5, input: 1.99999, expected: "2.0000" } + , { fmt: fmt1, input: 1.89999, expected: "001.90" } + , { fmt: fmt5, input: 1.67899, expected: "1.6790" } + , { fmt: fmt6, input: 12.9, expected: "13" } + , { fmt: fmt7, input: 1.123456789012345678901234, expected: "1.1234567890123457" } + , { fmt: fmt6, input: 12345678901234567.8901234, expected: "12,345,678,901,234,568" } + , { fmt: fmt5, input: 123456789012.345678901234, expected: "123,456,789,012.3457" } ] - (\{fmt, input, expected} -> do - format fmt input `shouldEqual` expected - format fmt (negate input) `shouldEqual` ("-" <> expected) + ( \{ fmt, input, expected } -> do + format fmt input `shouldEqual` expected + format fmt (negate input) `shouldEqual` ("-" <> expected) ) - -fmt1 ∷ Formatter +fmt1 :: Formatter fmt1 = Formatter { comma: false , before: 3 @@ -63,7 +62,7 @@ fmt1 = Formatter , sign: false } -fmt2 ∷ Formatter +fmt2 :: Formatter fmt2 = Formatter { comma: true , before: 1 @@ -72,7 +71,7 @@ fmt2 = Formatter , sign: true } -fmt3 ∷ Formatter +fmt3 :: Formatter fmt3 = Formatter { comma: false , before: 2 @@ -81,7 +80,7 @@ fmt3 = Formatter , sign: true } -fmt4 ∷ Formatter +fmt4 :: Formatter fmt4 = Formatter { comma: false , before: 2 @@ -90,7 +89,7 @@ fmt4 = Formatter , sign: false } -fmt5 ∷ Formatter +fmt5 :: Formatter fmt5 = Formatter { comma: true , before: 1 @@ -99,7 +98,7 @@ fmt5 = Formatter , sign: false } -fmt6 ∷ Formatter +fmt6 :: Formatter fmt6 = Formatter { comma: true , before: 1 @@ -108,7 +107,7 @@ fmt6 = Formatter , sign: false } -fmt7 ∷ Formatter +fmt7 :: Formatter fmt7 = Formatter { comma: true , before: 1 @@ -117,7 +116,7 @@ fmt7 = Formatter , sign: false } -numberformatts ∷ Array { fmt ∷ Formatter, str ∷ String } +numberformatts :: Array { fmt :: Formatter, str :: String } numberformatts = [ { str: "000.00" , fmt: fmt1 diff --git a/test/src/Utils.purs b/test/src/Utils.purs index 6331d9b..2276fca 100644 --- a/test/src/Utils.purs +++ b/test/src/Utils.purs @@ -21,35 +21,37 @@ import Test.Assert (assertEqual) -- Provide similar API to purescript-spec to reduce code changes -describe :: forall m. MonadReader Int m ⇒ MonadAff m ⇒ String -> m Unit -> m Unit +describe :: forall m. MonadReader Int m => MonadAff m => String -> m Unit -> m Unit describe msg runTest = do indentation <- ask let spacing = guard (indentation > 0) " " liftEffect $ log $ (power ">>" indentation) <> spacing <> msg local (_ + 1) runTest -it :: forall m. MonadReader Int m ⇒ MonadAff m ⇒ String -> m Unit -> m Unit +it :: forall m. MonadReader Int m => MonadAff m => String -> m Unit -> m Unit it = describe -shouldEqual :: forall m a. MonadAff m ⇒ Eq a ⇒ Show a ⇒ a -> a -> m Unit +shouldEqual :: forall m a. MonadAff m => Eq a => Show a => a -> a -> m Unit shouldEqual actual expected = liftEffect $ assertEqual { actual, expected } ----------------------------------------------------------------- -forAll ∷ ∀ m a f. MonadReader Int m ⇒ MonadAff m ⇒ Foldable f ⇒ (a → String) → String → f a → (a → Aff Unit) → m Unit +forAll :: forall m a f. MonadReader Int m => MonadAff m => Foldable f => (a -> String) -> String -> f a -> (a -> Aff Unit) -> m Unit forAll itTitle title arb f = describe title do - for_ arb \a → it (itTitle a) (liftAff $ f a) + for_ arb \a -> it (itTitle a) (liftAff $ f a) -makeDateTime ∷ Int → Int → Int → Int → Int → Int → Int → DateTime +makeDateTime :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> DateTime makeDateTime year month day hour minute second millisecond = DateTime - (canonicalDate - (fromMaybe bottom $ toEnum year) - (fromMaybe bottom $ toEnum month) - (fromMaybe bottom $ toEnum day)) - (Time - (fromMaybe bottom $ toEnum hour ) - (fromMaybe bottom $ toEnum minute ) - (fromMaybe bottom $ toEnum second ) - (fromMaybe bottom $ toEnum millisecond)) + ( canonicalDate + (fromMaybe bottom $ toEnum year) + (fromMaybe bottom $ toEnum month) + (fromMaybe bottom $ toEnum day) + ) + ( Time + (fromMaybe bottom $ toEnum hour) + (fromMaybe bottom $ toEnum minute) + (fromMaybe bottom $ toEnum second) + (fromMaybe bottom $ toEnum millisecond) + )