Rebased to latest upstream

This commit is contained in:
Daniel Larsson 2015-01-15 10:44:45 +01:00
parent 0b2f2ae490
commit fcf5402861
4 changed files with 4 additions and 4 deletions

View file

@ -29,7 +29,6 @@
module Servant.QQ (sitemap) where module Servant.QQ (sitemap) where
import Control.Monad ( void ) import Control.Monad ( void )
import Control.Applicative ( (<$>) )
import Language.Haskell.TH.Quote ( QuasiQuoter(..) ) import Language.Haskell.TH.Quote ( QuasiQuoter(..) )
import Language.Haskell.TH import Language.Haskell.TH
( mkName, Type(AppT, ConT, LitT), TyLit(StrTyLit) ) ( mkName, Type(AppT, ConT, LitT), TyLit(StrTyLit) )

View file

@ -53,8 +53,8 @@ import GHC.TypeLits ( KnownSymbol, Symbol, symbolVal )
import Servant.API.Capture ( Capture ) import Servant.API.Capture ( Capture )
import Servant.API.ReqBody ( ReqBody ) import Servant.API.ReqBody ( ReqBody )
import Servant.API.QueryParam ( QueryParam ) import Servant.API.QueryParam ( QueryParam, QueryParams, QueryFlag )
import Servant.API.MatrixParam ( MatrixParam ) import Servant.API.MatrixParam ( MatrixParam, MatrixParams, MatrixFlag )
import Servant.API.Get ( Get ) import Servant.API.Get ( Get )
import Servant.API.Post ( Post ) import Servant.API.Post ( Post )
import Servant.API.Put ( Put ) import Servant.API.Put ( Put )

View file

@ -15,6 +15,7 @@ import Servant.API
( (:<|>), ( (:<|>),
ReqBody, ReqBody,
QueryParam, QueryParam,
MatrixParam,
Put, Put,
Get, Get,
Post, Post,

View file

@ -6,7 +6,7 @@ module Servant.Utils.LinksSpec where
import Test.Hspec ( Spec, it, describe ) import Test.Hspec ( Spec, it, describe )
import Servant.API import Servant.API
( type (:<|>), ReqBody, QueryParam, Get, Post, Capture, type (:>) ) ( type (:<|>), ReqBody, QueryParam, MatrixParam, MatrixParams, MatrixFlag, Get, Post, Capture, type (:>) )
import Servant.QQSpec ( (~>) ) import Servant.QQSpec ( (~>) )
import Servant.Utils.Links ( IsElem, IsLink ) import Servant.Utils.Links ( IsElem, IsLink )