Add CaptureTimes and QueryParamTime(s) to servant.

This commit is contained in:
Alex Mason 2015-12-02 16:37:12 +11:00
parent 6dac6e831c
commit 8780bf78cb
3 changed files with 36 additions and 0 deletions

View file

@ -42,6 +42,7 @@ library
Servant.API.ReqBody
Servant.API.ResponseHeaders
Servant.API.Sub
Servant.API.Times
Servant.API.Vault
Servant.Utils.Links
build-depends:

View file

@ -23,6 +23,10 @@ module Servant.API (
-- | Is the request made through HTTPS?
module Servant.API.Vault,
-- | Access the location for arbitrary data to be shared by applications and middleware
module Servant.API.Times,
-- | Capturing dates and times in URLs and params with specified formats.
-- * Actual endpoints, distinguished by HTTP method
module Servant.API.Get,
@ -83,6 +87,7 @@ import Servant.API.ResponseHeaders (AddHeader (addHeader),
HList (..), Headers (..),
getHeadersHList, getResponse)
import Servant.API.Sub ((:>))
import Servant.API.Times (CaptureTime, QueryParamTime, QueryParamTimes)
import Servant.API.Vault (Vault)
import Web.HttpApiData (FromHttpApiData (..), ToHttpApiData (..))
import Servant.Utils.Links (HasLink (..), IsElem, IsElem',

View file

@ -0,0 +1,30 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Servant.API.Times where
import Data.Typeable (Typeable)
import GHC.TypeLits (Symbol)
-- | Capture a value from the request path under a certain type @a@.
--
-- Example:
-- >>> -- GET /books/:isbn
-- >>> type MyApi = "books" :> Capture "isbn" Text :> Get '[JSON] Book
data CaptureTime (sym :: Symbol) (format :: Symbol) a
deriving (Typeable)
data QueryParamTime (sym :: Symbol) (format :: Symbol) a
deriving (Typeable)
data QueryParamTimes (sym :: Symbol) (format :: Symbol) a
deriving (Typeable)