Remove unneeded module

This commit is contained in:
Julian K. Arni 2015-02-18 11:24:56 +01:00
parent dab3c9b62d
commit 21667cc049
3 changed files with 4 additions and 9 deletions

View file

@ -11,12 +11,11 @@
{-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE UndecidableInstances #-}
module Servant.API.ContentTypes where module Servant.API.ContentTypes where
import Data.Typeable
import Control.Monad (join) 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)
import Data.Typeable
import GHC.Exts (Constraint) import GHC.Exts (Constraint)
import qualified Network.HTTP.Media as M import qualified Network.HTTP.Media as M

View file

@ -1,4 +0,0 @@
module Servant.API.ContentTypes.HTML where
data HTML
deriving Typeable

View file

@ -20,7 +20,7 @@
-- >>> -- >>>
-- >>> -- >>>
-- >>> -- >>>
-- >>> type Hello = "hello" :> Get Int -- >>> type Hello = "hello" :> Get '[JSON] Int
-- >>> type Bye = "bye" :> QueryParam "name" String :> Delete -- >>> type Bye = "bye" :> QueryParam "name" String :> Delete
-- >>> type API = Hello :<|> Bye -- >>> type API = Hello :<|> Bye
-- >>> let api = Proxy :: Proxy API -- >>> let api = Proxy :: Proxy API
@ -40,7 +40,7 @@
-- function that accepts that input and generates a link. This is best shown -- function that accepts that input and generates a link. This is best shown
-- with an example. Here, a link is generated with no parameters: -- with an example. Here, a link is generated with no parameters:
-- --
-- >>> let hello = Proxy :: Proxy ("hello" :> Get Int) -- >>> let hello = Proxy :: Proxy ("hello" :> Get '[JSON] Int)
-- >>> print (safeLink api hello :: URI) -- >>> print (safeLink api hello :: URI)
-- hello -- hello
-- --
@ -74,7 +74,7 @@
-- <BLANKLINE> -- <BLANKLINE>
-- <interactive>:64:1: -- <interactive>:64:1:
-- Could not deduce (Or -- Could not deduce (Or
-- (IsElem' Delete (Get Int)) -- (IsElem' Delete (Get '[JSON] Int))
-- (IsElem' -- (IsElem'
-- ("hello" :> Delete) -- ("hello" :> Delete)
-- ("bye" :> (QueryParam "name" String :> Delete)))) -- ("bye" :> (QueryParam "name" String :> Delete))))