Remove unused imports and variables
This commit is contained in:
parent
891a077311
commit
7da7f4eb35
11 changed files with 9 additions and 88 deletions
|
@ -32,7 +32,6 @@ import Control.Arrow
|
||||||
(left, (+++))
|
(left, (+++))
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
(unless)
|
(unless)
|
||||||
import qualified Data.ByteString as BS
|
|
||||||
import qualified Data.ByteString.Lazy as BL
|
import qualified Data.ByteString.Lazy as BL
|
||||||
import Data.Either
|
import Data.Either
|
||||||
(partitionEithers)
|
(partitionEithers)
|
||||||
|
@ -78,7 +77,7 @@ import Servant.API
|
||||||
ReflectMethod (..), RemoteHost, ReqBody', SBoolI, Stream,
|
ReflectMethod (..), RemoteHost, ReqBody', SBoolI, Stream,
|
||||||
StreamBody', Summary, ToHttpApiData, ToSourceIO (..), Vault,
|
StreamBody', Summary, ToHttpApiData, ToSourceIO (..), Vault,
|
||||||
Verb, WithNamedContext, WithStatus (..), contentType, getHeadersHList,
|
Verb, WithNamedContext, WithStatus (..), contentType, getHeadersHList,
|
||||||
getResponse, toEncodedUrlPiece, toUrlPiece, NamedRoutes)
|
getResponse, toEncodedUrlPiece, NamedRoutes)
|
||||||
import Servant.API.Generic
|
import Servant.API.Generic
|
||||||
(GenericMode(..), ToServant, ToServantApi
|
(GenericMode(..), ToServant, ToServantApi
|
||||||
, GenericServant, toServant, fromServant)
|
, GenericServant, toServant, fromServant)
|
||||||
|
|
|
@ -43,14 +43,12 @@ import qualified Data.ByteString as BS
|
||||||
import Data.ByteString.Builder
|
import Data.ByteString.Builder
|
||||||
(toLazyByteString)
|
(toLazyByteString)
|
||||||
import qualified Data.ByteString.Lazy as BSL
|
import qualified Data.ByteString.Lazy as BSL
|
||||||
import Data.Either
|
|
||||||
(either)
|
|
||||||
import Data.Foldable
|
import Data.Foldable
|
||||||
(foldl',toList)
|
(foldl',toList)
|
||||||
import Data.Functor.Alt
|
import Data.Functor.Alt
|
||||||
(Alt (..))
|
(Alt (..))
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
(maybe, maybeToList)
|
(maybeToList)
|
||||||
import Data.Proxy
|
import Data.Proxy
|
||||||
(Proxy (..))
|
(Proxy (..))
|
||||||
import Data.Sequence
|
import Data.Sequence
|
||||||
|
@ -63,7 +61,7 @@ import GHC.Generics
|
||||||
import Network.HTTP.Media
|
import Network.HTTP.Media
|
||||||
(renderHeader)
|
(renderHeader)
|
||||||
import Network.HTTP.Types
|
import Network.HTTP.Types
|
||||||
(hContentType, renderQuery, statusIsSuccessful, urlEncode, Status)
|
(hContentType, statusIsSuccessful, urlEncode, Status)
|
||||||
import Servant.Client.Core
|
import Servant.Client.Core
|
||||||
|
|
||||||
import qualified Network.HTTP.Client as Client
|
import qualified Network.HTTP.Client as Client
|
||||||
|
|
|
@ -24,8 +24,6 @@ import Control.DeepSeq
|
||||||
(NFData, force)
|
(NFData, force)
|
||||||
import Control.Exception
|
import Control.Exception
|
||||||
(evaluate, throwIO)
|
(evaluate, throwIO)
|
||||||
import Control.Monad
|
|
||||||
(unless)
|
|
||||||
import Control.Monad.Base
|
import Control.Monad.Base
|
||||||
(MonadBase (..))
|
(MonadBase (..))
|
||||||
import Control.Monad.Codensity
|
import Control.Monad.Codensity
|
||||||
|
|
|
@ -21,16 +21,9 @@
|
||||||
|
|
||||||
module Servant.StreamSpec (spec) where
|
module Servant.StreamSpec (spec) where
|
||||||
|
|
||||||
import Control.Monad
|
|
||||||
(when)
|
|
||||||
import Control.Monad.Codensity
|
|
||||||
(Codensity (..))
|
|
||||||
import Control.Monad.IO.Class
|
|
||||||
(MonadIO (..))
|
|
||||||
import Control.Monad.Trans.Except
|
import Control.Monad.Trans.Except
|
||||||
import qualified Data.ByteString as BS
|
import qualified Data.ByteString as BS
|
||||||
import Data.Proxy
|
import Data.Proxy
|
||||||
import qualified Data.TDigest as TD
|
|
||||||
import qualified Network.HTTP.Client as C
|
import qualified Network.HTTP.Client as C
|
||||||
import Prelude ()
|
import Prelude ()
|
||||||
import Prelude.Compat
|
import Prelude.Compat
|
||||||
|
@ -46,20 +39,10 @@ import System.Entropy
|
||||||
(getEntropy, getHardwareEntropy)
|
(getEntropy, getHardwareEntropy)
|
||||||
import System.IO.Unsafe
|
import System.IO.Unsafe
|
||||||
(unsafePerformIO)
|
(unsafePerformIO)
|
||||||
import System.Mem
|
|
||||||
(performGC)
|
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
import Servant.ClientTestUtils (Person(..))
|
import Servant.ClientTestUtils (Person(..))
|
||||||
import qualified Servant.ClientTestUtils as CT
|
import qualified Servant.ClientTestUtils as CT
|
||||||
|
|
||||||
#if MIN_VERSION_base(4,10,0)
|
|
||||||
import GHC.Stats
|
|
||||||
(gc, gcdetails_live_bytes, getRTSStats)
|
|
||||||
#else
|
|
||||||
import GHC.Stats
|
|
||||||
(currentBytesUsed, getGCStats)
|
|
||||||
#endif
|
|
||||||
|
|
||||||
-- This declaration simply checks that all instances are in place.
|
-- This declaration simply checks that all instances are in place.
|
||||||
-- Note: this is streaming client
|
-- Note: this is streaming client
|
||||||
_ = client comprehensiveAPI
|
_ = client comprehensiveAPI
|
||||||
|
@ -78,9 +61,9 @@ api :: Proxy StreamApi
|
||||||
api = Proxy
|
api = Proxy
|
||||||
|
|
||||||
getGetNL, getGetNS :: ClientM (SourceIO Person)
|
getGetNL, getGetNS :: ClientM (SourceIO Person)
|
||||||
getGetALot :: ClientM (SourceIO BS.ByteString)
|
_getGetALot :: ClientM (SourceIO BS.ByteString)
|
||||||
getStreamBody :: SourceT IO BS.ByteString -> ClientM (SourceIO BS.ByteString)
|
getStreamBody :: SourceT IO BS.ByteString -> ClientM (SourceIO BS.ByteString)
|
||||||
getGetNL :<|> getGetNS :<|> getGetALot :<|> getStreamBody = client api
|
getGetNL :<|> getGetNS :<|> _getGetALot :<|> getStreamBody = client api
|
||||||
|
|
||||||
alice :: Person
|
alice :: Person
|
||||||
alice = Person "Alice" 42
|
alice = Person "Alice" 42
|
||||||
|
@ -134,50 +117,3 @@ streamSpec = beforeAll (CT.startWaiApp server) $ afterAll CT.endWaiApp $ do
|
||||||
where
|
where
|
||||||
input = ["foo", "", "bar"]
|
input = ["foo", "", "bar"]
|
||||||
output = ["foo", "bar"]
|
output = ["foo", "bar"]
|
||||||
|
|
||||||
{-
|
|
||||||
it "streams in constant memory" $ \(_, baseUrl) -> do
|
|
||||||
Right rs <- runClient getGetALot baseUrl
|
|
||||||
performGC
|
|
||||||
-- usage0 <- getUsage
|
|
||||||
-- putStrLn $ "Start: " ++ show usage0
|
|
||||||
tdigest <- memoryUsage $ joinCodensitySourceT rs
|
|
||||||
|
|
||||||
-- putStrLn $ "Median: " ++ show (TD.median tdigest)
|
|
||||||
-- putStrLn $ "Mean: " ++ show (TD.mean tdigest)
|
|
||||||
-- putStrLn $ "Stddev: " ++ show (TD.stddev tdigest)
|
|
||||||
|
|
||||||
-- forM_ [0.01, 0.1, 0.2, 0.5, 0.8, 0.9, 0.99] $ \q ->
|
|
||||||
-- putStrLn $ "q" ++ show q ++ ": " ++ show (TD.quantile q tdigest)
|
|
||||||
|
|
||||||
let Just stddev = TD.stddev tdigest
|
|
||||||
|
|
||||||
-- standard deviation of 100k is ok, we generate 256M of data after all.
|
|
||||||
-- On my machine deviation is 40k-50k
|
|
||||||
stddev `shouldSatisfy` (< 100000)
|
|
||||||
|
|
||||||
memoryUsage :: SourceT IO BS.ByteString -> IO (TD.TDigest 25)
|
|
||||||
memoryUsage src = unSourceT src $ loop mempty (0 :: Int)
|
|
||||||
where
|
|
||||||
loop !acc !_ Stop = return acc
|
|
||||||
loop !_ !_ (Error err) = fail err -- !
|
|
||||||
loop !acc !n (Skip s) = loop acc n s
|
|
||||||
loop !acc !n (Effect ms) = ms >>= loop acc n
|
|
||||||
loop !acc !n (Yield _bs s) = do
|
|
||||||
usage <- liftIO getUsage
|
|
||||||
-- We perform GC in between as we generate garbage.
|
|
||||||
when (n `mod` 1024 == 0) $ liftIO performGC
|
|
||||||
loop (TD.insert usage acc) (n + 1) s
|
|
||||||
|
|
||||||
getUsage :: IO Double
|
|
||||||
getUsage = fromIntegral .
|
|
||||||
#if MIN_VERSION_base(4,10,0)
|
|
||||||
gcdetails_live_bytes . gc <$> getRTSStats
|
|
||||||
#else
|
|
||||||
currentBytesUsed <$> getGCStats
|
|
||||||
#endif
|
|
||||||
memUsed `shouldSatisfy` (< megabytes 22)
|
|
||||||
|
|
||||||
megabytes :: Num a => a -> a
|
|
||||||
megabytes n = n * (1000 ^ (2 :: Int))
|
|
||||||
-}
|
|
||||||
|
|
|
@ -17,8 +17,6 @@ import Data.Maybe
|
||||||
(fromMaybe)
|
(fromMaybe)
|
||||||
import Network.HTTP.Client
|
import Network.HTTP.Client
|
||||||
(defaultManagerSettings, newManager)
|
(defaultManagerSettings, newManager)
|
||||||
import Network.Wai
|
|
||||||
(Application)
|
|
||||||
import System.Environment
|
import System.Environment
|
||||||
(getArgs, lookupEnv)
|
(getArgs, lookupEnv)
|
||||||
import Text.Read
|
import Text.Read
|
||||||
|
|
|
@ -55,7 +55,7 @@ import Data.String.Conversions
|
||||||
import Data.Text
|
import Data.Text
|
||||||
(Text, unpack)
|
(Text, unpack)
|
||||||
import GHC.Generics
|
import GHC.Generics
|
||||||
(Generic, Rep, K1(K1), M1(M1), U1(U1), V1,
|
(K1(K1), M1(M1), U1(U1), V1,
|
||||||
(:*:)((:*:)), (:+:)(L1, R1))
|
(:*:)((:*:)), (:+:)(L1, R1))
|
||||||
import qualified GHC.Generics as G
|
import qualified GHC.Generics as G
|
||||||
import GHC.TypeLits
|
import GHC.TypeLits
|
||||||
|
@ -964,7 +964,7 @@ instance {-# OVERLAPPABLE #-}
|
||||||
|
|
||||||
instance (ReflectMethod method) =>
|
instance (ReflectMethod method) =>
|
||||||
HasDocs (NoContentVerb method) where
|
HasDocs (NoContentVerb method) where
|
||||||
docsFor Proxy (endpoint, action) DocOptions{..} =
|
docsFor Proxy (endpoint, action) _ =
|
||||||
single endpoint' action'
|
single endpoint' action'
|
||||||
|
|
||||||
where endpoint' = endpoint & method .~ method'
|
where endpoint' = endpoint & method .~ method'
|
||||||
|
@ -982,7 +982,7 @@ instance (ReflectMethod method) =>
|
||||||
instance {-# OVERLAPPABLE #-}
|
instance {-# OVERLAPPABLE #-}
|
||||||
(Accept ct, KnownNat status, ReflectMethod method)
|
(Accept ct, KnownNat status, ReflectMethod method)
|
||||||
=> HasDocs (Stream method status framing ct a) where
|
=> HasDocs (Stream method status framing ct a) where
|
||||||
docsFor Proxy (endpoint, action) DocOptions{..} =
|
docsFor Proxy (endpoint, action) _ =
|
||||||
single endpoint' action'
|
single endpoint' action'
|
||||||
|
|
||||||
where endpoint' = endpoint & method .~ method'
|
where endpoint' = endpoint & method .~ method'
|
||||||
|
|
|
@ -17,8 +17,6 @@ import Data.Void
|
||||||
(Void)
|
(Void)
|
||||||
import Network.HTTP.Client
|
import Network.HTTP.Client
|
||||||
(defaultManagerSettings, newManager)
|
(defaultManagerSettings, newManager)
|
||||||
import Network.Wai
|
|
||||||
(Application)
|
|
||||||
import System.Environment
|
import System.Environment
|
||||||
(getArgs, lookupEnv)
|
(getArgs, lookupEnv)
|
||||||
import Text.Read
|
import Text.Read
|
||||||
|
|
|
@ -15,8 +15,6 @@ import Data.Maybe
|
||||||
(fromMaybe)
|
(fromMaybe)
|
||||||
import Network.HTTP.Client
|
import Network.HTTP.Client
|
||||||
(defaultManagerSettings, newManager)
|
(defaultManagerSettings, newManager)
|
||||||
import Network.Wai
|
|
||||||
(Application)
|
|
||||||
import System.Environment
|
import System.Environment
|
||||||
(getArgs, lookupEnv)
|
(getArgs, lookupEnv)
|
||||||
import System.IO
|
import System.IO
|
||||||
|
|
|
@ -95,8 +95,6 @@ import Servant.API.TypeErrors
|
||||||
import Web.HttpApiData
|
import Web.HttpApiData
|
||||||
(FromHttpApiData, parseHeader, parseQueryParam, parseUrlPiece,
|
(FromHttpApiData, parseHeader, parseQueryParam, parseUrlPiece,
|
||||||
parseUrlPieces)
|
parseUrlPieces)
|
||||||
import Data.Kind
|
|
||||||
(Type)
|
|
||||||
|
|
||||||
import Servant.Server.Internal.BasicAuth
|
import Servant.Server.Internal.BasicAuth
|
||||||
import Servant.Server.Internal.Context
|
import Servant.Server.Internal.Context
|
||||||
|
@ -110,7 +108,7 @@ import Servant.Server.Internal.RoutingApplication
|
||||||
import Servant.Server.Internal.ServerError
|
import Servant.Server.Internal.ServerError
|
||||||
|
|
||||||
import GHC.TypeLits
|
import GHC.TypeLits
|
||||||
(ErrorMessage (..), TypeError)
|
(ErrorMessage (..))
|
||||||
import Servant.API.TypeLevel
|
import Servant.API.TypeLevel
|
||||||
(AtLeastOneFragment, FragmentUnique)
|
(AtLeastOneFragment, FragmentUnique)
|
||||||
|
|
||||||
|
|
|
@ -38,7 +38,6 @@ import Network.HTTP.Media (MediaType)
|
||||||
import Servant.API
|
import Servant.API
|
||||||
import Servant.API.Description (FoldDescription,
|
import Servant.API.Description (FoldDescription,
|
||||||
reflectDescription)
|
reflectDescription)
|
||||||
import Servant.API.Generic (ToServantApi, AsApi)
|
|
||||||
import Servant.API.Modifiers (FoldRequired)
|
import Servant.API.Modifiers (FoldRequired)
|
||||||
|
|
||||||
import Servant.Swagger.Internal.TypeLevel.API
|
import Servant.Swagger.Internal.TypeLevel.API
|
||||||
|
|
|
@ -16,7 +16,6 @@ module Servant.API.TypeErrors (
|
||||||
NoInstanceForSub,
|
NoInstanceForSub,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.Kind
|
|
||||||
import GHC.TypeLits
|
import GHC.TypeLits
|
||||||
|
|
||||||
-- | No instance exists for @tycls (expr :> ...)@ because
|
-- | No instance exists for @tycls (expr :> ...)@ because
|
||||||
|
|
Loading…
Reference in a new issue