fix build error for servant's spec
This commit is contained in:
parent
67abcff47f
commit
0dfd2434ac
2 changed files with 0 additions and 19 deletions
|
@ -6,11 +6,8 @@ module Servant.Utils.StaticFiles (
|
||||||
serveDirectory,
|
serveDirectory,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.String.Conversions
|
|
||||||
import Filesystem.Path.CurrentOS (decodeString)
|
import Filesystem.Path.CurrentOS (decodeString)
|
||||||
import Network.Wai
|
|
||||||
import Network.Wai.Application.Static
|
import Network.Wai.Application.Static
|
||||||
|
|
||||||
import Servant.API.Raw
|
import Servant.API.Raw
|
||||||
import Servant.Server
|
import Servant.Server
|
||||||
|
|
||||||
|
|
|
@ -6,12 +6,8 @@
|
||||||
module Servant.Utils.StaticFilesSpec where
|
module Servant.Utils.StaticFilesSpec where
|
||||||
|
|
||||||
import Control.Exception
|
import Control.Exception
|
||||||
import Data.Foldable
|
|
||||||
import Data.List
|
|
||||||
import Data.Proxy
|
import Data.Proxy
|
||||||
import Data.String.Conversions
|
|
||||||
import Network.Wai
|
import Network.Wai
|
||||||
import Network.Wai.Test
|
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import System.IO.Temp
|
import System.IO.Temp
|
||||||
import Test.Hspec hiding (pending)
|
import Test.Hspec hiding (pending)
|
||||||
|
@ -22,7 +18,6 @@ import Servant.API.Capture
|
||||||
import Servant.API.Get
|
import Servant.API.Get
|
||||||
import Servant.API.Raw
|
import Servant.API.Raw
|
||||||
import Servant.API.Sub
|
import Servant.API.Sub
|
||||||
import Servant.Docs
|
|
||||||
import Servant.Server
|
import Servant.Server
|
||||||
import Servant.ServerSpec
|
import Servant.ServerSpec
|
||||||
import Servant.Utils.StaticFiles
|
import Servant.Utils.StaticFiles
|
||||||
|
@ -30,10 +25,7 @@ import Servant.Utils.StaticFiles
|
||||||
type Api =
|
type Api =
|
||||||
"dummy_api" :> Capture "person_name" String :> Get Person
|
"dummy_api" :> Capture "person_name" String :> Get Person
|
||||||
:<|> "static" :> Raw
|
:<|> "static" :> Raw
|
||||||
:<|> "documentation" :> Raw
|
|
||||||
|
|
||||||
instance ToCapture (Capture "person_name" String) where
|
|
||||||
toCapture _proxy = DocCapture "person_name" "person_name_doc"
|
|
||||||
|
|
||||||
api :: Proxy Api
|
api :: Proxy Api
|
||||||
api = Proxy
|
api = Proxy
|
||||||
|
@ -45,7 +37,6 @@ server :: Server Api
|
||||||
server =
|
server =
|
||||||
(\ name -> return (Person name 42))
|
(\ name -> return (Person name 42))
|
||||||
:<|> serveDirectory "static"
|
:<|> serveDirectory "static"
|
||||||
:<|> serveDocumentation api
|
|
||||||
|
|
||||||
withStaticFiles :: IO () -> IO ()
|
withStaticFiles :: IO () -> IO ()
|
||||||
withStaticFiles action = withSystemTempDirectory "servant-test" $ \ tmpDir ->
|
withStaticFiles action = withSystemTempDirectory "servant-test" $ \ tmpDir ->
|
||||||
|
@ -71,10 +62,3 @@ spec = do
|
||||||
|
|
||||||
it "serves the contents of index.html when requesting the root of a directory" $ do
|
it "serves the contents of index.html when requesting the root of a directory" $ do
|
||||||
get "/static" `shouldRespondWith` "index"
|
get "/static" `shouldRespondWith` "index"
|
||||||
|
|
||||||
describe "serveDocumentation" $ do
|
|
||||||
it "serves documentation about the expose API" $ do
|
|
||||||
response <- get "/documentation"
|
|
||||||
liftIO $ forM_ ["person_name" :: String, "static", "dummy_api", "person_name_doc"] $
|
|
||||||
\ snippet ->
|
|
||||||
(snippet, cs (simpleBody response)) `shouldSatisfy` uncurry isInfixOf
|
|
||||||
|
|
Loading…
Reference in a new issue