various code clean ups, fixing some issues from @jkarni

This commit is contained in:
Alex Mason 2016-09-02 15:57:51 +10:00
parent f3f61dbbac
commit 840eae8cfe
2 changed files with 15 additions and 15 deletions

View file

@ -318,7 +318,7 @@ captureTimeSpec = do
with (return (serve with (return (serve
(Proxy :: Proxy (Capture "datetime" (FTime TimeFormatWSpace UTCTime) :> Raw)) (Proxy :: Proxy (Capture "datetime" (FTime TimeFormatWSpace UTCTime) :> Raw))
(\ (FTime day )request_ respond -> (\ (FTime _day) request_ respond ->
respond $ responseLBS ok200 [] (cs $ show $ pathInfo request_)))) $ do respond $ responseLBS ok200 [] (cs $ show $ pathInfo request_)))) $ do
it "strips the captured path snippet from pathInfo" $ do it "strips the captured path snippet from pathInfo" $ do
get "/2015-12-02%2012:34:56+1000/foo" `shouldRespondWith` (fromString (show ["foo" :: String])) get "/2015-12-02%2012:34:56+1000/foo" `shouldRespondWith` (fromString (show ["foo" :: String]))

View file

@ -1,10 +1,10 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE PolyKinds #-} {-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
module Servant.API.Times module Servant.API.Times
@ -18,17 +18,17 @@ module Servant.API.Times
, ISO8601DateTimeZ , ISO8601DateTimeZ
) where ) where
import Data.Typeable (Typeable) import Data.Typeable (Typeable)
import GHC.TypeLits -- (Symbol) import GHC.TypeLits (Symbol,KnownSymbol,symbolVal)
import Web.HttpApiData import Web.HttpApiData
import qualified Data.Time.Format as T import qualified Data.Time.Format as T
#if !MIN_VERSION_time(1,5,0) #if !MIN_VERSION_time(1,5,0)
import System.Locale as T import qualified System.Locale as T
#endif #endif
import Data.Text (pack, Text) import Data.Text (pack, Text)
import Data.Proxy import Data.Proxy
import Control.Monad ((>=>)) import Control.Monad ((>=>))
import Control.Arrow (first) import Control.Arrow (first)
type ISO8601Date = "%Y-%m-%d" type ISO8601Date = "%Y-%m-%d"
@ -49,7 +49,7 @@ newtype FTime (format :: Symbol) t = FTime {getFTime :: t}
deriving (Typeable, Eq, Ord) deriving (Typeable, Eq, Ord)
instance (KnownSymbol format, T.FormatTime t) => Show (FTime format t) where instance (KnownSymbol format, T.FormatTime t) => Show (FTime format t) where
showsPrec i t = showParen (i > 1) (\str -> renderTime t ++ str) showsPrec i t = showParen (i > 1) (renderTime t ++)
instance (KnownSymbol format, T.ParseTime t) => Read (FTime format t) where instance (KnownSymbol format, T.ParseTime t) => Read (FTime format t) where
readsPrec i str = res readsPrec i str = res