GHC-8.2 readyness
This commit is contained in:
parent
ec930ac9a8
commit
b6cfd64b5a
13 changed files with 119 additions and 431 deletions
|
@ -1,165 +1,34 @@
|
|||
\begin{code}
|
||||
{-# LANGUAGE CPP #-}
|
||||
#ifndef MIN_VERSION_Cabal
|
||||
#define MIN_VERSION_Cabal(x,y,z) 0
|
||||
#endif
|
||||
#ifndef MIN_VERSION_directory
|
||||
#define MIN_VERSION_directory(x,y,z) 0
|
||||
#endif
|
||||
#if MIN_VERSION_Cabal(1,24,0)
|
||||
#define InstalledPackageId UnitId
|
||||
#endif
|
||||
{-# OPTIONS_GHC -Wall #-}
|
||||
module Main (main) where
|
||||
|
||||
import Control.Monad ( when )
|
||||
import Data.List ( nub )
|
||||
import Distribution.Package ( InstalledPackageId )
|
||||
import Distribution.Package ( PackageId, Package (..), packageVersion )
|
||||
import Distribution.PackageDescription ( PackageDescription(), TestSuite(..) , Library (..), BuildInfo (..))
|
||||
import Distribution.Simple ( defaultMainWithHooks, UserHooks(..), simpleUserHooks )
|
||||
import Distribution.Simple.Utils ( rewriteFile, createDirectoryIfMissingVerbose )
|
||||
import Distribution.Simple.BuildPaths ( autogenModulesDir )
|
||||
import Distribution.Simple.Setup ( BuildFlags(buildDistPref, buildVerbosity), fromFlag)
|
||||
import Distribution.Simple.LocalBuildInfo ( withPackageDB, withLibLBI, withTestLBI, LocalBuildInfo(), ComponentLocalBuildInfo(componentPackageDeps), compiler )
|
||||
import Distribution.Simple.Compiler ( showCompilerId , PackageDB (..))
|
||||
import Distribution.Text ( display , simpleParse )
|
||||
import System.FilePath ( (</>) )
|
||||
|
||||
#if MIN_VERSION_Cabal(1,25,0)
|
||||
import Distribution.Simple.BuildPaths ( autogenComponentModulesDir )
|
||||
#ifndef MIN_VERSION_cabal_doctest
|
||||
#define MIN_VERSION_cabal_doctest(x,y,z) 0
|
||||
#endif
|
||||
|
||||
#if MIN_VERSION_directory(1,2,2)
|
||||
import System.Directory (makeAbsolute)
|
||||
#if MIN_VERSION_cabal_doctest(1,0,0)
|
||||
|
||||
import Distribution.Extra.Doctest ( defaultMainWithDoctests )
|
||||
main :: IO ()
|
||||
main = defaultMainWithDoctests "doctests"
|
||||
|
||||
#else
|
||||
import System.Directory (getCurrentDirectory)
|
||||
import System.FilePath (isAbsolute)
|
||||
|
||||
makeAbsolute :: FilePath -> IO FilePath
|
||||
makeAbsolute p | isAbsolute p = return p
|
||||
| otherwise = do
|
||||
cwd <- getCurrentDirectory
|
||||
return $ cwd </> p
|
||||
#ifdef MIN_VERSION_Cabal
|
||||
-- If the macro is defined, we have new cabal-install,
|
||||
-- but for some reason we don't have cabal-doctest in package-db
|
||||
--
|
||||
-- Probably we are running cabal sdist, when otherwise using new-build
|
||||
-- workflow
|
||||
import Warning ()
|
||||
#endif
|
||||
|
||||
import Distribution.Simple
|
||||
|
||||
main :: IO ()
|
||||
main = defaultMainWithHooks simpleUserHooks
|
||||
{ buildHook = \pkg lbi hooks flags -> do
|
||||
generateBuildModule flags pkg lbi
|
||||
buildHook simpleUserHooks pkg lbi hooks flags
|
||||
}
|
||||
main = defaultMain
|
||||
|
||||
generateBuildModule :: BuildFlags -> PackageDescription -> LocalBuildInfo -> IO ()
|
||||
generateBuildModule flags pkg lbi = do
|
||||
let verbosity = fromFlag (buildVerbosity flags)
|
||||
let distPref = fromFlag (buildDistPref flags)
|
||||
|
||||
-- Package DBs
|
||||
let dbStack = withPackageDB lbi ++ [ SpecificPackageDB $ distPref </> "package.conf.inplace" ]
|
||||
let dbFlags = "-hide-all-packages" : packageDbArgs dbStack
|
||||
|
||||
withLibLBI pkg lbi $ \lib libcfg -> do
|
||||
let libBI = libBuildInfo lib
|
||||
|
||||
-- modules
|
||||
let modules = exposedModules lib ++ otherModules libBI
|
||||
-- it seems that doctest is happy to take in module names, not actual files!
|
||||
let module_sources = modules
|
||||
|
||||
-- We need the directory with library's cabal_macros.h!
|
||||
#if MIN_VERSION_Cabal(1,25,0)
|
||||
let libAutogenDir = autogenComponentModulesDir lbi libcfg
|
||||
#else
|
||||
let libAutogenDir = autogenModulesDir lbi
|
||||
#endif
|
||||
|
||||
-- Lib sources and includes
|
||||
iArgs <- mapM (fmap ("-i"++) . makeAbsolute) $ libAutogenDir : hsSourceDirs libBI
|
||||
includeArgs <- mapM (fmap ("-I"++) . makeAbsolute) $ includeDirs libBI
|
||||
|
||||
-- CPP includes, i.e. include cabal_macros.h
|
||||
let cppFlags = map ("-optP"++) $
|
||||
[ "-include", libAutogenDir ++ "/cabal_macros.h" ]
|
||||
++ cppOptions libBI
|
||||
|
||||
-- Actually we need to check whether testName suite == "doctests"
|
||||
-- pending https://github.com/haskell/cabal/pull/4229 getting into GHC HEAD tree
|
||||
withTestLBI pkg lbi $ \suite suitecfg -> when (testName suite == "doctests") $ do
|
||||
|
||||
-- get and create autogen dir
|
||||
#if MIN_VERSION_Cabal(1,25,0)
|
||||
let testAutogenDir = autogenComponentModulesDir lbi suitecfg
|
||||
#else
|
||||
let testAutogenDir = autogenModulesDir lbi
|
||||
#endif
|
||||
createDirectoryIfMissingVerbose verbosity True testAutogenDir
|
||||
|
||||
-- write autogen'd file
|
||||
rewriteFile (testAutogenDir </> "Build_doctests.hs") $ unlines
|
||||
[ "module Build_doctests where"
|
||||
, ""
|
||||
-- -package-id etc. flags
|
||||
, "pkgs :: [String]"
|
||||
, "pkgs = " ++ (show $ formatDeps $ testDeps libcfg suitecfg)
|
||||
, ""
|
||||
, "flags :: [String]"
|
||||
, "flags = " ++ show (iArgs ++ includeArgs ++ dbFlags ++ cppFlags)
|
||||
, ""
|
||||
, "module_sources :: [String]"
|
||||
, "module_sources = " ++ show (map display module_sources)
|
||||
]
|
||||
where
|
||||
-- we do this check in Setup, as then doctests don't need to depend on Cabal
|
||||
isOldCompiler = maybe False id $ do
|
||||
a <- simpleParse $ showCompilerId $ compiler lbi
|
||||
b <- simpleParse "7.5"
|
||||
return $ packageVersion (a :: PackageId) < b
|
||||
|
||||
formatDeps = map formatOne
|
||||
formatOne (installedPkgId, pkgId)
|
||||
-- The problem is how different cabal executables handle package databases
|
||||
-- when doctests depend on the library
|
||||
| packageId pkg == pkgId = "-package=" ++ display pkgId
|
||||
| otherwise = "-package-id=" ++ display installedPkgId
|
||||
|
||||
-- From Distribution.Simple.Program.GHC
|
||||
packageDbArgs :: [PackageDB] -> [String]
|
||||
packageDbArgs | isOldCompiler = packageDbArgsConf
|
||||
| otherwise = packageDbArgsDb
|
||||
|
||||
-- GHC <7.6 uses '-package-conf' instead of '-package-db'.
|
||||
packageDbArgsConf :: [PackageDB] -> [String]
|
||||
packageDbArgsConf dbstack = case dbstack of
|
||||
(GlobalPackageDB:UserPackageDB:dbs) -> concatMap specific dbs
|
||||
(GlobalPackageDB:dbs) -> ("-no-user-package-conf")
|
||||
: concatMap specific dbs
|
||||
_ -> ierror
|
||||
where
|
||||
specific (SpecificPackageDB db) = [ "-package-conf=" ++ db ]
|
||||
specific _ = ierror
|
||||
ierror = error $ "internal error: unexpected package db stack: "
|
||||
++ show dbstack
|
||||
|
||||
-- GHC >= 7.6 uses the '-package-db' flag. See
|
||||
-- https://ghc.haskell.org/trac/ghc/ticket/5977.
|
||||
packageDbArgsDb :: [PackageDB] -> [String]
|
||||
-- special cases to make arguments prettier in common scenarios
|
||||
packageDbArgsDb dbstack = case dbstack of
|
||||
(GlobalPackageDB:UserPackageDB:dbs)
|
||||
| all isSpecific dbs -> concatMap single dbs
|
||||
(GlobalPackageDB:dbs)
|
||||
| all isSpecific dbs -> "-no-user-package-db"
|
||||
: concatMap single dbs
|
||||
dbs -> "-clear-package-db"
|
||||
: concatMap single dbs
|
||||
where
|
||||
single (SpecificPackageDB db) = [ "-package-db=" ++ db ]
|
||||
single GlobalPackageDB = [ "-global-package-db" ]
|
||||
single UserPackageDB = [ "-user-package-db" ]
|
||||
isSpecific (SpecificPackageDB _) = True
|
||||
isSpecific _ = False
|
||||
|
||||
testDeps :: ComponentLocalBuildInfo -> ComponentLocalBuildInfo -> [(InstalledPackageId, PackageId)]
|
||||
testDeps xs ys = nub $ componentPackageDeps xs ++ componentPackageDeps ys
|
||||
|
||||
\end{code}
|
||||
|
|
|
@ -33,7 +33,9 @@ source-repository head
|
|||
|
||||
custom-setup
|
||||
setup-depends:
|
||||
Cabal >=1.14, base, filepath, directory
|
||||
base >= 4 && <5,
|
||||
Cabal,
|
||||
cabal-doctest >= 1.0.1 && <1.1
|
||||
|
||||
library
|
||||
exposed-modules:
|
||||
|
@ -159,4 +161,6 @@ test-suite doctests
|
|||
buildable: True
|
||||
default-language: Haskell2010
|
||||
ghc-options: -Wall -threaded
|
||||
if impl(ghc >= 8.2)
|
||||
x-doctest-options: -fdiagnostics-color=never
|
||||
include-dirs: include
|
||||
|
|
|
@ -228,5 +228,7 @@ layoutWithContext p context =
|
|||
--
|
||||
|
||||
-- $setup
|
||||
-- >>> :set -XDataKinds
|
||||
-- >>> :set -XTypeOperators
|
||||
-- >>> import Servant.API
|
||||
-- >>> import Servant.Server
|
||||
|
|
25
servant-server/test/doctests.hs
Normal file
25
servant-server/test/doctests.hs
Normal file
|
@ -0,0 +1,25 @@
|
|||
-----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : Main (doctests)
|
||||
-- Copyright : (C) 2012-14 Edward Kmett
|
||||
-- License : BSD-style (see the file LICENSE)
|
||||
-- Maintainer : Edward Kmett <ekmett@gmail.com>
|
||||
-- Stability : provisional
|
||||
-- Portability : portable
|
||||
--
|
||||
-- This module provides doctests for a project based on the actual versions
|
||||
-- of the packages it was built with. It requires a corresponding Setup.lhs
|
||||
-- to be added to the project
|
||||
-----------------------------------------------------------------------------
|
||||
module Main where
|
||||
|
||||
import Build_doctests (flags, pkgs, module_sources)
|
||||
import Data.Foldable (traverse_)
|
||||
import Test.DocTest
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
traverse_ putStrLn args
|
||||
doctest args
|
||||
where
|
||||
args = flags ++ pkgs ++ module_sources
|
|
@ -1,61 +0,0 @@
|
|||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
-----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : Main (doctests)
|
||||
-- Copyright : (C) 2012-14 Edward Kmett
|
||||
-- License : BSD-style (see the file LICENSE)
|
||||
-- Maintainer : Edward Kmett <ekmett@gmail.com>
|
||||
-- Stability : provisional
|
||||
-- Portability : portable
|
||||
--
|
||||
-- This module provides doctests for a project based on the actual versions
|
||||
-- of the packages it was built with. It requires a corresponding Setup.lhs
|
||||
-- to be added to the project
|
||||
-----------------------------------------------------------------------------
|
||||
module Main where
|
||||
|
||||
import Build_doctests (flags, pkgs, module_sources)
|
||||
import Data.Foldable (traverse_)
|
||||
import Test.DocTest
|
||||
|
||||
##if defined(mingw32_HOST_OS)
|
||||
##if defined(i386_HOST_ARCH)
|
||||
##define USE_CP
|
||||
import Control.Applicative
|
||||
import Control.Exception
|
||||
import Foreign.C.Types
|
||||
foreign import stdcall "windows.h SetConsoleCP" c_SetConsoleCP :: CUInt -> IO Bool
|
||||
foreign import stdcall "windows.h GetConsoleCP" c_GetConsoleCP :: IO CUInt
|
||||
##elif defined(x86_64_HOST_ARCH)
|
||||
##define USE_CP
|
||||
import Control.Applicative
|
||||
import Control.Exception
|
||||
import Foreign.C.Types
|
||||
foreign import ccall "windows.h SetConsoleCP" c_SetConsoleCP :: CUInt -> IO Bool
|
||||
foreign import ccall "windows.h GetConsoleCP" c_GetConsoleCP :: IO CUInt
|
||||
##endif
|
||||
##endif
|
||||
|
||||
-- | Run in a modified codepage where we can print UTF-8 values on Windows.
|
||||
withUnicode :: IO a -> IO a
|
||||
##ifdef USE_CP
|
||||
withUnicode m = do
|
||||
cp <- c_GetConsoleCP
|
||||
(c_SetConsoleCP 65001 >> m) `finally` c_SetConsoleCP cp
|
||||
##else
|
||||
withUnicode m = m
|
||||
##endif
|
||||
|
||||
main :: IO ()
|
||||
main = withUnicode $ do
|
||||
traverse_ putStrLn args
|
||||
doctest args
|
||||
where
|
||||
args =
|
||||
"-XOverloadedStrings" :
|
||||
"-XFlexibleInstances" :
|
||||
"-XMultiParamTypeClasses" :
|
||||
"-XDataKinds" :
|
||||
"-XTypeOperators" :
|
||||
flags ++ pkgs ++ module_sources
|
|
@ -1,165 +1,34 @@
|
|||
\begin{code}
|
||||
{-# LANGUAGE CPP #-}
|
||||
#ifndef MIN_VERSION_Cabal
|
||||
#define MIN_VERSION_Cabal(x,y,z) 0
|
||||
#endif
|
||||
#ifndef MIN_VERSION_directory
|
||||
#define MIN_VERSION_directory(x,y,z) 0
|
||||
#endif
|
||||
#if MIN_VERSION_Cabal(1,24,0)
|
||||
#define InstalledPackageId UnitId
|
||||
#endif
|
||||
{-# OPTIONS_GHC -Wall #-}
|
||||
module Main (main) where
|
||||
|
||||
import Control.Monad ( when )
|
||||
import Data.List ( nub )
|
||||
import Distribution.Package ( InstalledPackageId )
|
||||
import Distribution.Package ( PackageId, Package (..), packageVersion )
|
||||
import Distribution.PackageDescription ( PackageDescription(), TestSuite(..) , Library (..), BuildInfo (..))
|
||||
import Distribution.Simple ( defaultMainWithHooks, UserHooks(..), simpleUserHooks )
|
||||
import Distribution.Simple.Utils ( rewriteFile, createDirectoryIfMissingVerbose )
|
||||
import Distribution.Simple.BuildPaths ( autogenModulesDir )
|
||||
import Distribution.Simple.Setup ( BuildFlags(buildDistPref, buildVerbosity), fromFlag)
|
||||
import Distribution.Simple.LocalBuildInfo ( withPackageDB, withLibLBI, withTestLBI, LocalBuildInfo(), ComponentLocalBuildInfo(componentPackageDeps), compiler )
|
||||
import Distribution.Simple.Compiler ( showCompilerId , PackageDB (..))
|
||||
import Distribution.Text ( display , simpleParse )
|
||||
import System.FilePath ( (</>) )
|
||||
|
||||
#if MIN_VERSION_Cabal(1,25,0)
|
||||
import Distribution.Simple.BuildPaths ( autogenComponentModulesDir )
|
||||
#ifndef MIN_VERSION_cabal_doctest
|
||||
#define MIN_VERSION_cabal_doctest(x,y,z) 0
|
||||
#endif
|
||||
|
||||
#if MIN_VERSION_directory(1,2,2)
|
||||
import System.Directory (makeAbsolute)
|
||||
#if MIN_VERSION_cabal_doctest(1,0,0)
|
||||
|
||||
import Distribution.Extra.Doctest ( defaultMainWithDoctests )
|
||||
main :: IO ()
|
||||
main = defaultMainWithDoctests "doctests"
|
||||
|
||||
#else
|
||||
import System.Directory (getCurrentDirectory)
|
||||
import System.FilePath (isAbsolute)
|
||||
|
||||
makeAbsolute :: FilePath -> IO FilePath
|
||||
makeAbsolute p | isAbsolute p = return p
|
||||
| otherwise = do
|
||||
cwd <- getCurrentDirectory
|
||||
return $ cwd </> p
|
||||
#ifdef MIN_VERSION_Cabal
|
||||
-- If the macro is defined, we have new cabal-install,
|
||||
-- but for some reason we don't have cabal-doctest in package-db
|
||||
--
|
||||
-- Probably we are running cabal sdist, when otherwise using new-build
|
||||
-- workflow
|
||||
import Warning ()
|
||||
#endif
|
||||
|
||||
import Distribution.Simple
|
||||
|
||||
main :: IO ()
|
||||
main = defaultMainWithHooks simpleUserHooks
|
||||
{ buildHook = \pkg lbi hooks flags -> do
|
||||
generateBuildModule flags pkg lbi
|
||||
buildHook simpleUserHooks pkg lbi hooks flags
|
||||
}
|
||||
main = defaultMain
|
||||
|
||||
generateBuildModule :: BuildFlags -> PackageDescription -> LocalBuildInfo -> IO ()
|
||||
generateBuildModule flags pkg lbi = do
|
||||
let verbosity = fromFlag (buildVerbosity flags)
|
||||
let distPref = fromFlag (buildDistPref flags)
|
||||
|
||||
-- Package DBs
|
||||
let dbStack = withPackageDB lbi ++ [ SpecificPackageDB $ distPref </> "package.conf.inplace" ]
|
||||
let dbFlags = "-hide-all-packages" : packageDbArgs dbStack
|
||||
|
||||
withLibLBI pkg lbi $ \lib libcfg -> do
|
||||
let libBI = libBuildInfo lib
|
||||
|
||||
-- modules
|
||||
let modules = exposedModules lib ++ otherModules libBI
|
||||
-- it seems that doctest is happy to take in module names, not actual files!
|
||||
let module_sources = modules
|
||||
|
||||
-- We need the directory with library's cabal_macros.h!
|
||||
#if MIN_VERSION_Cabal(1,25,0)
|
||||
let libAutogenDir = autogenComponentModulesDir lbi libcfg
|
||||
#else
|
||||
let libAutogenDir = autogenModulesDir lbi
|
||||
#endif
|
||||
|
||||
-- Lib sources and includes
|
||||
iArgs <- mapM (fmap ("-i"++) . makeAbsolute) $ "test" : libAutogenDir : hsSourceDirs libBI
|
||||
includeArgs <- mapM (fmap ("-I"++) . makeAbsolute) $ includeDirs libBI
|
||||
|
||||
-- CPP includes, i.e. include cabal_macros.h
|
||||
let cppFlags = map ("-optP"++) $
|
||||
[ "-include", libAutogenDir ++ "/cabal_macros.h" ]
|
||||
++ cppOptions libBI
|
||||
|
||||
-- Actually we need to check whether testName suite == "doctests"
|
||||
-- pending https://github.com/haskell/cabal/pull/4229 getting into GHC HEAD tree
|
||||
withTestLBI pkg lbi $ \suite suitecfg -> when (testName suite == "doctests") $ do
|
||||
|
||||
-- get and create autogen dir
|
||||
#if MIN_VERSION_Cabal(1,25,0)
|
||||
let testAutogenDir = autogenComponentModulesDir lbi suitecfg
|
||||
#else
|
||||
let testAutogenDir = autogenModulesDir lbi
|
||||
#endif
|
||||
createDirectoryIfMissingVerbose verbosity True testAutogenDir
|
||||
|
||||
-- write autogen'd file
|
||||
rewriteFile (testAutogenDir </> "Build_doctests.hs") $ unlines
|
||||
[ "module Build_doctests where"
|
||||
, ""
|
||||
-- -package-id etc. flags
|
||||
, "pkgs :: [String]"
|
||||
, "pkgs = " ++ (show $ formatDeps $ testDeps libcfg suitecfg)
|
||||
, ""
|
||||
, "flags :: [String]"
|
||||
, "flags = " ++ show (iArgs ++ includeArgs ++ dbFlags ++ cppFlags)
|
||||
, ""
|
||||
, "module_sources :: [String]"
|
||||
, "module_sources = " ++ show ("Servant.Utils.LinksSpec" : map display module_sources)
|
||||
]
|
||||
where
|
||||
-- we do this check in Setup, as then doctests don't need to depend on Cabal
|
||||
isOldCompiler = maybe False id $ do
|
||||
a <- simpleParse $ showCompilerId $ compiler lbi
|
||||
b <- simpleParse "7.5"
|
||||
return $ packageVersion (a :: PackageId) < b
|
||||
|
||||
formatDeps = map formatOne
|
||||
formatOne (installedPkgId, pkgId)
|
||||
-- The problem is how different cabal executables handle package databases
|
||||
-- when doctests depend on the library
|
||||
| packageId pkg == pkgId = "-package=" ++ display pkgId
|
||||
| otherwise = "-package-id=" ++ display installedPkgId
|
||||
|
||||
-- From Distribution.Simple.Program.GHC
|
||||
packageDbArgs :: [PackageDB] -> [String]
|
||||
packageDbArgs | isOldCompiler = packageDbArgsConf
|
||||
| otherwise = packageDbArgsDb
|
||||
|
||||
-- GHC <7.6 uses '-package-conf' instead of '-package-db'.
|
||||
packageDbArgsConf :: [PackageDB] -> [String]
|
||||
packageDbArgsConf dbstack = case dbstack of
|
||||
(GlobalPackageDB:UserPackageDB:dbs) -> concatMap specific dbs
|
||||
(GlobalPackageDB:dbs) -> ("-no-user-package-conf")
|
||||
: concatMap specific dbs
|
||||
_ -> ierror
|
||||
where
|
||||
specific (SpecificPackageDB db) = [ "-package-conf=" ++ db ]
|
||||
specific _ = ierror
|
||||
ierror = error $ "internal error: unexpected package db stack: "
|
||||
++ show dbstack
|
||||
|
||||
-- GHC >= 7.6 uses the '-package-db' flag. See
|
||||
-- https://ghc.haskell.org/trac/ghc/ticket/5977.
|
||||
packageDbArgsDb :: [PackageDB] -> [String]
|
||||
-- special cases to make arguments prettier in common scenarios
|
||||
packageDbArgsDb dbstack = case dbstack of
|
||||
(GlobalPackageDB:UserPackageDB:dbs)
|
||||
| all isSpecific dbs -> concatMap single dbs
|
||||
(GlobalPackageDB:dbs)
|
||||
| all isSpecific dbs -> "-no-user-package-db"
|
||||
: concatMap single dbs
|
||||
dbs -> "-clear-package-db"
|
||||
: concatMap single dbs
|
||||
where
|
||||
single (SpecificPackageDB db) = [ "-package-db=" ++ db ]
|
||||
single GlobalPackageDB = [ "-global-package-db" ]
|
||||
single UserPackageDB = [ "-user-package-db" ]
|
||||
isSpecific (SpecificPackageDB _) = True
|
||||
isSpecific _ = False
|
||||
|
||||
testDeps :: ComponentLocalBuildInfo -> ComponentLocalBuildInfo -> [(InstalledPackageId, PackageId)]
|
||||
testDeps xs ys = nub $ componentPackageDeps xs ++ componentPackageDeps ys
|
||||
|
||||
\end{code}
|
||||
|
|
|
@ -27,7 +27,9 @@ source-repository head
|
|||
|
||||
custom-setup
|
||||
setup-depends:
|
||||
Cabal >=1.14, base, filepath, directory
|
||||
base >= 4 && <5,
|
||||
Cabal,
|
||||
cabal-doctest >= 1.0.2 && <1.1
|
||||
|
||||
library
|
||||
exposed-modules:
|
||||
|
@ -147,5 +149,8 @@ test-suite doctests
|
|||
buildable: True
|
||||
default-language: Haskell2010
|
||||
ghc-options: -Wall -threaded
|
||||
build-tools: hsc2hs
|
||||
if impl(ghc >= 8.2)
|
||||
x-doctest-options: -fdiagnostics-color=never
|
||||
include-dirs: include
|
||||
x-doctest-source-dirs: test
|
||||
x-doctest-modules: Servant.Utils.LinksSpec
|
||||
|
|
|
@ -419,6 +419,9 @@ instance MimeUnrender OctetStream BS.ByteString where
|
|||
|
||||
|
||||
-- $setup
|
||||
-- >>> :set -XFlexibleInstances
|
||||
-- >>> :set -XMultiParamTypeClasses
|
||||
-- >>> :set -XOverloadedStrings
|
||||
-- >>> import Servant.API
|
||||
-- >>> import Data.Aeson
|
||||
-- >>> import Data.Text
|
||||
|
|
25
servant/test/doctests.hs
Normal file
25
servant/test/doctests.hs
Normal file
|
@ -0,0 +1,25 @@
|
|||
-----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : Main (doctests)
|
||||
-- Copyright : (C) 2012-14 Edward Kmett
|
||||
-- License : BSD-style (see the file LICENSE)
|
||||
-- Maintainer : Edward Kmett <ekmett@gmail.com>
|
||||
-- Stability : provisional
|
||||
-- Portability : portable
|
||||
--
|
||||
-- This module provides doctests for a project based on the actual versions
|
||||
-- of the packages it was built with. It requires a corresponding Setup.lhs
|
||||
-- to be added to the project
|
||||
-----------------------------------------------------------------------------
|
||||
module Main where
|
||||
|
||||
import Build_doctests (flags, pkgs, module_sources)
|
||||
import Data.Foldable (traverse_)
|
||||
import Test.DocTest
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
traverse_ putStrLn args
|
||||
doctest args
|
||||
where
|
||||
args = flags ++ pkgs ++ module_sources
|
|
@ -1,59 +0,0 @@
|
|||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
-----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : Main (doctests)
|
||||
-- Copyright : (C) 2012-14 Edward Kmett
|
||||
-- License : BSD-style (see the file LICENSE)
|
||||
-- Maintainer : Edward Kmett <ekmett@gmail.com>
|
||||
-- Stability : provisional
|
||||
-- Portability : portable
|
||||
--
|
||||
-- This module provides doctests for a project based on the actual versions
|
||||
-- of the packages it was built with. It requires a corresponding Setup.lhs
|
||||
-- to be added to the project
|
||||
-----------------------------------------------------------------------------
|
||||
module Main where
|
||||
|
||||
import Build_doctests (flags, pkgs, module_sources)
|
||||
import Data.Foldable (traverse_)
|
||||
import Test.DocTest
|
||||
|
||||
##if defined(mingw32_HOST_OS)
|
||||
##if defined(i386_HOST_ARCH)
|
||||
##define USE_CP
|
||||
import Control.Applicative
|
||||
import Control.Exception
|
||||
import Foreign.C.Types
|
||||
foreign import stdcall "windows.h SetConsoleCP" c_SetConsoleCP :: CUInt -> IO Bool
|
||||
foreign import stdcall "windows.h GetConsoleCP" c_GetConsoleCP :: IO CUInt
|
||||
##elif defined(x86_64_HOST_ARCH)
|
||||
##define USE_CP
|
||||
import Control.Applicative
|
||||
import Control.Exception
|
||||
import Foreign.C.Types
|
||||
foreign import ccall "windows.h SetConsoleCP" c_SetConsoleCP :: CUInt -> IO Bool
|
||||
foreign import ccall "windows.h GetConsoleCP" c_GetConsoleCP :: IO CUInt
|
||||
##endif
|
||||
##endif
|
||||
|
||||
-- | Run in a modified codepage where we can print UTF-8 values on Windows.
|
||||
withUnicode :: IO a -> IO a
|
||||
##ifdef USE_CP
|
||||
withUnicode m = do
|
||||
cp <- c_GetConsoleCP
|
||||
(c_SetConsoleCP 65001 >> m) `finally` c_SetConsoleCP cp
|
||||
##else
|
||||
withUnicode m = m
|
||||
##endif
|
||||
|
||||
main :: IO ()
|
||||
main = withUnicode $ do
|
||||
traverse_ putStrLn args
|
||||
doctest args
|
||||
where
|
||||
args =
|
||||
"-XOverloadedStrings" :
|
||||
"-XFlexibleInstances" :
|
||||
"-XMultiParamTypeClasses" :
|
||||
flags ++ pkgs ++ module_sources
|
|
@ -8,18 +8,20 @@ packages:
|
|||
extra-deps:
|
||||
- aeson-compat-0.3.6
|
||||
- base-compat-0.9.1
|
||||
- cabal-doctest-1.0.2
|
||||
- call-stack-0.1.0
|
||||
- control-monad-omega-0.3.1
|
||||
- cryptonite-0.6
|
||||
- doctest-0.11.0
|
||||
- hspec-2.3.2
|
||||
- hspec-discover-2.3.2
|
||||
- hspec-core-2.3.2
|
||||
- hspec-wai-0.8.0
|
||||
- hspec-discover-2.3.2
|
||||
- hspec-expectations-0.8.2
|
||||
- call-stack-0.1.0
|
||||
- hspec-wai-0.8.0
|
||||
- http-api-data-0.3.6
|
||||
- natural-transformation-0.4
|
||||
- primitive-0.6.1.0
|
||||
- servant-js-0.9.3
|
||||
- should-not-typecheck-2.1.0
|
||||
- time-locale-compat-0.1.1.1
|
||||
- uri-bytestring-0.2.2.0
|
||||
|
|
|
@ -9,4 +9,6 @@ packages:
|
|||
extra-deps:
|
||||
- aeson-1.2.0.0
|
||||
- attoparsec-iso8601-1.0.0.0
|
||||
- cabal-doctest-1.0.2
|
||||
- http-api-data-0.3.7
|
||||
- servant-js-0.9.3
|
||||
|
|
12
stack.yaml
12
stack.yaml
|
@ -8,12 +8,14 @@ packages:
|
|||
- doc/tutorial
|
||||
extra-deps:
|
||||
- attoparsec-iso8601-1.0.0.0
|
||||
- http-api-data-0.3.7
|
||||
- servant-js-0.9.1
|
||||
- natural-transformation-0.4
|
||||
- cabal-doctest-1.0.2
|
||||
- hspec-2.3.2
|
||||
- hspec-discover-2.3.2
|
||||
- hspec-core-2.3.2
|
||||
- hspec-wai-0.8.0
|
||||
- hspec-discover-2.3.2
|
||||
- hspec-expectations-0.8.2
|
||||
- hspec-wai-0.8.0
|
||||
- http-api-data-0.3.7
|
||||
- natural-transformation-0.4
|
||||
- servant-js-0.9.1
|
||||
- servant-js-0.9.3
|
||||
resolver: lts-6.27
|
||||
|
|
Loading…
Reference in a new issue