Review fixes

This commit is contained in:
Julian K. Arni 2015-02-19 10:29:19 +01:00
parent 0658ab674f
commit 5e4297a135
8 changed files with 32 additions and 42 deletions

View file

@ -46,7 +46,7 @@ library
build-depends: build-depends:
base >=4.7 && <5 base >=4.7 && <5
, bytestring == 0.10.* , bytestring == 0.10.*
, http-media >= 0.4 && < 0.5 , http-media >= 0.4 && < 0.6
, http-types == 0.8.* , http-types == 0.8.*
, text >= 1 && < 2 , text >= 1 && < 2
, template-haskell >= 2.7 && < 2.10 , template-haskell >= 2.7 && < 2.10

View file

@ -11,7 +11,6 @@
{-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE UndecidableInstances #-}
module Servant.API.ContentTypes where module Servant.API.ContentTypes where
import Control.Monad (join)
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import Data.ByteString.Lazy (ByteString) import Data.ByteString.Lazy (ByteString)
import Data.String.Conversions (cs) import Data.String.Conversions (cs)
@ -102,27 +101,25 @@ instance ( AllMimeRender ctyps a, IsNonEmpty ctyps
) => AllCTRender ctyps a where ) => AllCTRender ctyps a where
handleAcceptH _ (AcceptHeader accept) val = M.mapAcceptMedia lkup accept handleAcceptH _ (AcceptHeader accept) val = M.mapAcceptMedia lkup accept
where pctyps = Proxy :: Proxy ctyps where pctyps = Proxy :: Proxy ctyps
amrs = amr pctyps val amrs = allMimeRender pctyps val
lkup = zip (map fst amrs) $ map (\(a,b) -> (cs $ show a, b)) amrs lkup = fmap (\(a,b) -> (a, (cs $ show a, b))) amrs
-------------------------------------------------------------------------- --------------------------------------------------------------------------
-- * Unrender -- * Unrender
class Accept ctype => MimeUnrender ctype a where class Accept ctype => MimeUnrender ctype a where
fromByteString :: Proxy ctype -> ByteString -> Maybe a fromByteString :: Proxy ctype -> ByteString -> Either String a
class AllCTUnrender list a where class AllCTUnrender list a where
handleCTypeH :: Proxy list handleCTypeH :: Proxy list
-> ByteString -- Content-Type header -> ByteString -- Content-Type header
-> ByteString -- Request body -> ByteString -- Request body
-> Maybe a -> Maybe (Either String a)
instance ( AllMimeUnrender ctyps a, IsNonEmpty ctyps instance ( AllMimeUnrender ctyps a, IsNonEmpty ctyps
) => AllCTUnrender ctyps a where ) => AllCTUnrender ctyps a where
handleCTypeH _ ctypeH body = join $ M.mapContentMedia lkup (cs ctypeH) handleCTypeH _ ctypeH body = M.mapContentMedia lkup (cs ctypeH)
where lkup = amu (Proxy :: Proxy ctyps) body where lkup = allMimeUnrender (Proxy :: Proxy ctyps) body
-------------------------------------------------------------------------- --------------------------------------------------------------------------
-- * Utils (Internal) -- * Utils (Internal)
@ -132,50 +129,42 @@ instance ( AllMimeUnrender ctyps a, IsNonEmpty ctyps
-- Check that all elements of list are instances of MimeRender -- Check that all elements of list are instances of MimeRender
-------------------------------------------------------------------------- --------------------------------------------------------------------------
class AllMimeRender ls a where class AllMimeRender ls a where
amr :: Proxy ls allMimeRender :: Proxy ls
-> a -- value to serialize -> a -- value to serialize
-> [(M.MediaType, ByteString)] -- content-types/response pairs -> [(M.MediaType, ByteString)] -- content-types/response pairs
instance ( MimeRender ctyp a ) => AllMimeRender '[ctyp] a where instance ( MimeRender ctyp a ) => AllMimeRender '[ctyp] a where
amr _ a = [(contentType pctyp, toByteString pctyp a)] allMimeRender _ a = [(contentType pctyp, toByteString pctyp a)]
where pctyp = Proxy :: Proxy ctyp where pctyp = Proxy :: Proxy ctyp
instance ( MimeRender ctyp a instance ( MimeRender ctyp a
, MimeRender ctyp' a -- at least two elems to avoid overlap , AllMimeRender (ctyp' ': ctyps) a
, AllMimeRender ctyps a
) => AllMimeRender (ctyp ': ctyp' ': ctyps) a where ) => AllMimeRender (ctyp ': ctyp' ': ctyps) a where
amr _ a = (contentType pctyp, toByteString pctyp a) allMimeRender _ a = (contentType pctyp, toByteString pctyp a)
:(contentType pctyp', toByteString pctyp' a) :(allMimeRender pctyps a)
:(amr pctyps a)
where pctyp = Proxy :: Proxy ctyp where pctyp = Proxy :: Proxy ctyp
pctyps = Proxy :: Proxy ctyps pctyps = Proxy :: Proxy (ctyp' ': ctyps)
pctyp' = Proxy :: Proxy ctyp'
instance AllMimeRender '[] a where instance AllMimeRender '[] a where
amr _ _ = [] allMimeRender _ _ = []
-------------------------------------------------------------------------- --------------------------------------------------------------------------
-- Check that all elements of list are instances of MimeUnrender -- Check that all elements of list are instances of MimeUnrender
-------------------------------------------------------------------------- --------------------------------------------------------------------------
class AllMimeUnrender ls a where class AllMimeUnrender ls a where
amu :: Proxy ls -> ByteString -> [(M.MediaType, Maybe a)] allMimeUnrender :: Proxy ls -> ByteString -> [(M.MediaType, Either String a)]
instance ( MimeUnrender ctyp a ) => AllMimeUnrender '[ctyp] a where instance AllMimeUnrender '[] a where
amu _ val = [(contentType pctyp, fromByteString pctyp val)] allMimeUnrender _ _ = []
where pctyp = Proxy :: Proxy ctyp
instance ( MimeUnrender ctyp a instance ( MimeUnrender ctyp a
, MimeUnrender ctyp' a
, AllMimeUnrender ctyps a , AllMimeUnrender ctyps a
) => AllMimeUnrender (ctyp ': ctyp' ': ctyps) a where ) => AllMimeUnrender (ctyp ': ctyps) a where
amu _ val = (contentType pctyp, fromByteString pctyp val) allMimeUnrender _ val = (contentType pctyp, fromByteString pctyp val)
:(contentType pctyp', fromByteString pctyp' val) :(allMimeUnrender pctyps val)
:(amu pctyps val)
where pctyp = Proxy :: Proxy ctyp where pctyp = Proxy :: Proxy ctyp
pctyps = Proxy :: Proxy ctyps pctyps = Proxy :: Proxy ctyps
pctyp' = Proxy :: Proxy ctyp'
type family IsNonEmpty (ls::[*]) :: Constraint where type family IsNonEmpty (ls::[*]) :: Constraint where
IsNonEmpty '[] = 'False ~ 'True IsNonEmpty (x ': xs) = ()
IsNonEmpty x = ()

View file

@ -10,5 +10,5 @@ import Data.Typeable ( Typeable )
-- Example: -- Example:
-- --
-- > type MyApi = "books" :> Get '[JSON] [Book] -- > type MyApi = "books" :> Get '[JSON] [Book]
data Get (cts::[*]) a data Get (contentTypes::[*]) a
deriving Typeable deriving Typeable

View file

@ -1,4 +1,6 @@
{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
module Servant.API.Patch where module Servant.API.Patch where
import Data.Typeable ( Typeable ) import Data.Typeable ( Typeable )
@ -11,9 +13,9 @@ import Data.Typeable ( Typeable )
-- --
-- Example: -- Example:
-- --
-- > -- POST /books -- > -- PATCH /books
-- > -- with a JSON encoded Book as the request body -- > -- with a JSON encoded Book as the request body
-- > -- returning the just-created Book -- > -- returning the just-created Book
-- > type MyApi = "books" :> ReqBody Book :> Post Book -- > type MyApi = "books" :> ReqBody Book :> Patch '[JSON] Book
data Patch a data Patch (contentTypes::[*]) a
deriving Typeable deriving Typeable

View file

@ -15,5 +15,5 @@ import Data.Typeable ( Typeable )
-- > -- with a JSON encoded Book as the request body -- > -- with a JSON encoded Book as the request body
-- > -- returning the just-created Book -- > -- returning the just-created Book
-- > type MyApi = "books" :> ReqBody Book :> Post '[JSON] Book -- > type MyApi = "books" :> ReqBody Book :> Post '[JSON] Book
data Post (cts::[*]) a data Post (contentTypes::[*]) a
deriving Typeable deriving Typeable

View file

@ -13,5 +13,5 @@ import Data.Typeable ( Typeable )
-- > -- PUT /books/:isbn -- > -- PUT /books/:isbn
-- > -- with a Book as request body, returning the updated Book -- > -- with a Book as request body, returning the updated Book
-- > type MyApi = "books" :> Capture "isbn" Text :> ReqBody Book :> Put '[JSON] Book -- > type MyApi = "books" :> Capture "isbn" Text :> ReqBody Book :> Put '[JSON] Book
data Put (cts::[*]) a data Put (contentTypes::[*]) a
deriving Typeable deriving Typeable

View file

@ -8,4 +8,4 @@ module Servant.API.ReqBody where
-- --
-- > -- POST /books -- > -- POST /books
-- > type MyApi = "books" :> ReqBody '[JSON] Book :> Post Book -- > type MyApi = "books" :> ReqBody '[JSON] Book :> Post Book
data ReqBody (ls::[*]) a data ReqBody (contentTypes::[*]) a

View file

@ -180,7 +180,6 @@ type family IsSubList a b :: Constraint where
IsSubList '[x] (x ': xs) = () IsSubList '[x] (x ': xs) = ()
IsSubList '[x] (y ': ys) = IsSubList '[x] ys IsSubList '[x] (y ': ys) = IsSubList '[x] ys
IsSubList (x ': xs) y = IsSubList '[x] y `And` IsSubList xs y IsSubList (x ': xs) y = IsSubList '[x] y `And` IsSubList xs y
IsSubList a b = 'True ~ 'False
-- Phantom types for Param -- Phantom types for Param
data Matrix data Matrix