Reimplement time handling using a new type which carries a format string in its type.
This commit is contained in:
parent
7174e1e1fd
commit
74ebec9176
3 changed files with 71 additions and 15 deletions
|
@ -59,6 +59,7 @@ library
|
||||||
, string-conversions >= 0.3 && < 0.5
|
, string-conversions >= 0.3 && < 0.5
|
||||||
, network-uri >= 2.6
|
, network-uri >= 2.6
|
||||||
, vault >= 0.3 && <0.4
|
, vault >= 0.3 && <0.4
|
||||||
|
, time >= 1.5 && < 1.6
|
||||||
hs-source-dirs: src
|
hs-source-dirs: src
|
||||||
default-language: Haskell2010
|
default-language: Haskell2010
|
||||||
other-extensions: CPP
|
other-extensions: CPP
|
||||||
|
|
|
@ -87,7 +87,7 @@ import Servant.API.ResponseHeaders (AddHeader (addHeader),
|
||||||
HList (..), Headers (..),
|
HList (..), Headers (..),
|
||||||
getHeadersHList, getResponse)
|
getHeadersHList, getResponse)
|
||||||
import Servant.API.Sub ((:>))
|
import Servant.API.Sub ((:>))
|
||||||
import Servant.API.Times (CaptureTime, QueryParamTime, QueryParamTimes)
|
import Servant.API.Times (FTime(..), toProxy, getFormat, renderTime, parseTime)
|
||||||
import Servant.API.Vault (Vault)
|
import Servant.API.Vault (Vault)
|
||||||
import Web.HttpApiData (FromHttpApiData (..), ToHttpApiData (..))
|
import Web.HttpApiData (FromHttpApiData (..), ToHttpApiData (..))
|
||||||
import Servant.Utils.Links (HasLink (..), IsElem, IsElem',
|
import Servant.Utils.Links (HasLink (..), IsElem, IsElem',
|
||||||
|
|
|
@ -6,33 +6,88 @@
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
|
|
||||||
module Servant.API.Times where
|
module Servant.API.Times
|
||||||
|
( FTime(..)
|
||||||
|
, toProxy
|
||||||
|
, getFormat
|
||||||
|
, renderTime
|
||||||
|
, parseTime
|
||||||
|
) where
|
||||||
|
|
||||||
import Data.Typeable (Typeable)
|
import Data.Typeable (Typeable)
|
||||||
import GHC.TypeLits (Symbol)
|
import GHC.TypeLits -- (Symbol)
|
||||||
|
import Web.HttpApiData
|
||||||
|
import qualified Data.Time.Format as T
|
||||||
|
import Data.Text (pack, Text)
|
||||||
|
import Data.Proxy
|
||||||
|
import Control.Monad ((>=>))
|
||||||
|
import Control.Arrow (first)
|
||||||
|
|
||||||
|
-- | A wrapper around a time type which can be parsed/rendered to with `format',
|
||||||
-- | Capture data/time value from a path in the `format', as understood
|
-- as specified in 'Data.Time.Format'.
|
||||||
-- by 'Data.Time.Format.
|
|
||||||
--
|
--
|
||||||
-- Example:
|
-- Example:
|
||||||
-- >>> -- GET /events/:date
|
-- >>> -- GET /events/:date
|
||||||
-- >>> type MyApi = "events" :> CaptureTime "date" "%Y-%m-%d" Day :> Get '[JSON] Book
|
-- >>> type MyApi = "events" :> Capture "date" (FTime "%Y-%m-%d" Day) :> Get '[JSON] [Event]
|
||||||
data CaptureTime (sym :: Symbol) (format :: Symbol) a
|
newtype FTime (format :: Symbol) t = FTime {getFTime :: t}
|
||||||
deriving (Typeable)
|
deriving (Typeable, Eq, Ord)
|
||||||
|
|
||||||
|
instance (KnownSymbol format, T.FormatTime t) => Show (FTime format t) where
|
||||||
|
showsPrec i t = showParen (i > 1) (\str -> renderTime t ++ str)
|
||||||
|
|
||||||
|
instance (KnownSymbol format, T.ParseTime t) => Read (FTime format t) where
|
||||||
|
readsPrec i str = res
|
||||||
|
where
|
||||||
|
res = fmap (first FTime)
|
||||||
|
(readParen (i > 1)
|
||||||
|
(T.readSTime False T.defaultTimeLocale fmt)
|
||||||
|
str
|
||||||
|
)
|
||||||
|
|
||||||
|
toFTimeTy :: [(FTime format t, String)] -> FTime format t
|
||||||
|
toFTimeTy _ = undefined
|
||||||
|
|
||||||
|
fmt = getFormat (toFTimeTy res)
|
||||||
|
|
||||||
|
|
||||||
data QueryParamTime (sym :: Symbol) (format :: Symbol) a
|
|
||||||
deriving (Typeable)
|
instance (KnownSymbol format, T.FormatTime t) => ToHttpApiData (FTime format t) where
|
||||||
|
toUrlPiece = toUrlPiece . renderTime
|
||||||
|
toHeader = toHeader . renderTime
|
||||||
|
toQueryParam = toQueryParam . renderTime
|
||||||
|
|
||||||
|
|
||||||
data QueryParamTimes (sym :: Symbol) (format :: Symbol) a
|
instance (KnownSymbol format, T.ParseTime t) => FromHttpApiData (FTime format t) where
|
||||||
deriving (Typeable)
|
parseUrlPiece = parseUrlPiece >=> parseTime
|
||||||
|
parseHeader = parseHeader >=> parseTime
|
||||||
|
parseQueryParam = parseQueryParam >=> parseTime
|
||||||
|
|
||||||
|
|
||||||
|
toProxy :: FTime format t -> Proxy format
|
||||||
|
toProxy _ = Proxy
|
||||||
|
|
||||||
|
getFormat :: KnownSymbol format => FTime format t -> String
|
||||||
|
getFormat t = symbolVal (toProxy t)
|
||||||
|
|
||||||
|
renderTime :: (KnownSymbol format, T.FormatTime t) => FTime format t -> String
|
||||||
|
renderTime tt@(FTime t) = T.formatTime T.defaultTimeLocale (getFormat tt) t
|
||||||
|
|
||||||
|
parseTime :: (KnownSymbol format, T.ParseTime t) => String -> Either Text (FTime format t)
|
||||||
|
parseTime str = res
|
||||||
|
where
|
||||||
|
res = case T.parseTimeM False T.defaultTimeLocale fmt str of
|
||||||
|
Nothing -> Left . pack $ "Could not parse time string \"" ++ str ++ "\" with format \"" ++ fmt ++ "\""
|
||||||
|
Just t -> Right (FTime t)
|
||||||
|
|
||||||
|
fmt = getFormat (toFTimeTy res)
|
||||||
|
|
||||||
|
toFTimeTy :: Either Text (FTime format t) -> FTime format a
|
||||||
|
toFTimeTy _ = undefined
|
||||||
|
|
||||||
-- $setup
|
-- $setup
|
||||||
-- >>> import Servant.API
|
-- >>> import Servant.API
|
||||||
-- >>> import Data.Aeson
|
-- >>> import Data.Aeson
|
||||||
-- >>> import Data.Text
|
-- >>> import Data.Text
|
||||||
-- >>> import Data.Time.Calendar
|
-- >>> import Data.Time.Calendar
|
||||||
-- >>> data Book
|
-- >>> data Event
|
||||||
-- >>> instance ToJSON Book where { toJSON = undefined }
|
-- >>> instance ToJSON Event where { toJSON = undefined }
|
||||||
|
|
Loading…
Reference in a new issue