Skip to content
Snippets Groups Projects
Commit d856620a authored by Ashley Yakeley's avatar Ashley Yakeley
Browse files

change internal members of ParseTime to allow newtype-deriving (#119)

parent a5785c53
No related branches found
No related tags found
No related merge requests found
...@@ -5,6 +5,7 @@ ...@@ -5,6 +5,7 @@
- deprecate iso8601DateFormat - deprecate iso8601DateFormat
- parsing: fix %_Q %-Q %_q %-q - parsing: fix %_Q %-Q %_q %-q
- formatting: fix %3ES %3Es - formatting: fix %3ES %3Es
- change internal members of ParseTime to allow newtype-deriving
## [1.9.3] ## [1.9.3]
- documentation fixes - documentation fixes
......
...@@ -110,7 +110,7 @@ readPTime :: ...@@ -110,7 +110,7 @@ readPTime ::
readPTime False l f = readPOnlyTime l f readPTime False l f = readPOnlyTime l f
readPTime True l f = (skipSpaces >> readPOnlyTime l f) <++ readPOnlyTime l f readPTime True l f = (skipSpaces >> readPOnlyTime l f) <++ readPOnlyTime l f
readPOnlyTime' :: ParseTime t => proxy t -> TimeLocale -> String -> ReadP t readPOnlyTime' :: ParseTime t => Proxy t -> TimeLocale -> String -> ReadP t
readPOnlyTime' pt l f = do readPOnlyTime' pt l f = do
pairs <- parseSpecifiers pt l f pairs <- parseSpecifiers pt l f
case buildTime l pairs of case buildTime l pairs of
......
...@@ -11,6 +11,7 @@ module Data.Time.Format.Parse.Class ...@@ -11,6 +11,7 @@ module Data.Time.Format.Parse.Class
import Data.Char import Data.Char
import Data.Maybe import Data.Maybe
import Data.Proxy
import Data.Time.Format.Locale import Data.Time.Format.Locale
import Text.ParserCombinators.ReadP import Text.ParserCombinators.ReadP
...@@ -23,12 +24,12 @@ data ParseNumericPadding ...@@ -23,12 +24,12 @@ data ParseNumericPadding
-- string. -- string.
class ParseTime t where class ParseTime t where
-- | @since 1.9.1 -- | @since 1.9.1
substituteTimeSpecifier :: proxy t -> TimeLocale -> Char -> Maybe String substituteTimeSpecifier :: Proxy t -> TimeLocale -> Char -> Maybe String
substituteTimeSpecifier _ _ _ = Nothing substituteTimeSpecifier _ _ _ = Nothing
-- | Get the string corresponding to the given format specifier. -- | Get the string corresponding to the given format specifier.
-- --
-- @since 1.9.1 -- @since 1.9.1
parseTimeSpecifier :: proxy t -> TimeLocale -> Maybe ParseNumericPadding -> Char -> ReadP String parseTimeSpecifier :: Proxy t -> TimeLocale -> Maybe ParseNumericPadding -> Char -> ReadP String
-- | Builds a time value from a parsed input string. -- | Builds a time value from a parsed input string.
-- If the input does not include all the information needed to -- If the input does not include all the information needed to
-- construct a complete value, any missing parts should be taken -- construct a complete value, any missing parts should be taken
...@@ -59,7 +60,7 @@ stringCI this = do ...@@ -59,7 +60,7 @@ stringCI this = do
s <- look s <- look
scan this s scan this s
parseSpecifiers :: ParseTime t => proxy t -> TimeLocale -> String -> ReadP [(Char, String)] parseSpecifiers :: ParseTime t => Proxy t -> TimeLocale -> String -> ReadP [(Char, String)]
parseSpecifiers pt locale = let parseSpecifiers pt locale = let
parse :: String -> ReadP [(Char, String)] parse :: String -> ReadP [(Char, String)]
parse [] = return [] parse [] = return []
......
...@@ -13,6 +13,7 @@ import Test.Calendar.Week ...@@ -13,6 +13,7 @@ import Test.Calendar.Week
import Test.Clock.Conversion import Test.Clock.Conversion
import Test.Clock.Resolution import Test.Clock.Resolution
import Test.Clock.TAI import Test.Clock.TAI
import Test.Format.Compile ()
import Test.Format.Format import Test.Format.Format
import Test.Format.ISO8601 import Test.Format.ISO8601
import Test.Format.ParseTime import Test.Format.ParseTime
......
-- Tests succeed if module compiles
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Test.Format.Compile
(
) where
import Data.Time
newtype WrappedUTCTime =
MkWrappedUTCTime UTCTime
deriving (FormatTime, ParseTime)
newtype Wrapped t =
MkWrapped t
deriving (FormatTime, ParseTime)
...@@ -35,11 +35,11 @@ formats = ...@@ -35,11 +35,11 @@ formats =
somestrings :: [String] somestrings :: [String]
somestrings = ["", " ", "-", "\n"] somestrings = ["", " ", "-", "\n"]
compareExpected :: (Eq t, Show t, ParseTime t) => String -> String -> String -> proxy t -> TestTree compareExpected :: (Eq t, Show t, ParseTime t) => String -> String -> String -> Proxy t -> TestTree
compareExpected testname fmt str proxy = compareExpected testname fmt str proxy =
testCase testname $ do testCase testname $ do
let let
found :: ParseTime t => proxy t -> Maybe t found :: ParseTime t => Proxy t -> Maybe t
found _ = parseTimeM False defaultTimeLocale fmt str found _ = parseTimeM False defaultTimeLocale fmt str
assertEqual "" Nothing $ found proxy assertEqual "" Nothing $ found proxy
......
...@@ -160,6 +160,7 @@ test-suite test-main ...@@ -160,6 +160,7 @@ test-suite test-main
Test.Clock.Conversion Test.Clock.Conversion
Test.Clock.Resolution Test.Clock.Resolution
Test.Clock.TAI Test.Clock.TAI
Test.Format.Compile
Test.Format.Format Test.Format.Format
Test.Format.ParseTime Test.Format.ParseTime
Test.Format.ISO8601 Test.Format.ISO8601
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment