aboutsummaryrefslogtreecommitdiff
path: root/vendor/cabal-helper-0.8.1.2/tests
diff options
context:
space:
mode:
Diffstat (limited to 'vendor/cabal-helper-0.8.1.2/tests')
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/CompileTest.hs195
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/GhcSession.hs182
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/bkpregex/Setup.hs2
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/bkpregex/bkpregex.cabal29
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/bkpregex/regex-example/Main.hs12
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/bkpregex/regex-indef/Regex.hs14
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/bkpregex/regex-indef/Str.hsig9
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/bkpregex/regex-types/Regex/Types.hs7
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/bkpregex/str-impls/Str/ByteString.hs17
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/bkpregex/str-impls/Str/String.hs21
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/exeintlib/Exe.hs5
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/exeintlib/Setup.hs2
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/exeintlib/exeintlib.cabal31
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/exeintlib/intlib/IntLib.hs7
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/exeintlib/lib/Lib.hs8
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/exelib/Exe.hs5
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/exelib/Setup.hs2
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/exelib/exelib.cabal25
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/exelib/lib/Lib.hs8
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/fliblib/FLib.hs5
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/fliblib/Setup.hs2
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/fliblib/fliblib.cabal19
-rw-r--r--vendor/cabal-helper-0.8.1.2/tests/fliblib/lib/Lib.hs8
23 files changed, 0 insertions, 615 deletions
diff --git a/vendor/cabal-helper-0.8.1.2/tests/CompileTest.hs b/vendor/cabal-helper-0.8.1.2/tests/CompileTest.hs
deleted file mode 100644
index 4c1f752..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/CompileTest.hs
+++ /dev/null
@@ -1,195 +0,0 @@
-{-# LANGUAGE ScopedTypeVariables, GADTs #-}
-
-import System.Environment (getArgs)
-import System.Directory
-import System.FilePath
-import System.Process
-import System.Exit
-import System.IO
-import Control.Exception as E
-import Data.List
-import Data.Maybe
-import Data.Version
-import Data.Functor
-import Data.Function
-import qualified Distribution.Compat.ReadP as Dist
-import Distribution.Version (VersionRange, withinRange)
-import Distribution.Text
-import Control.Arrow
-import Control.Monad
-import Prelude
-
-import CabalHelper.Compiletime.Compat.Environment
-import CabalHelper.Compiletime.Compat.Version
-import CabalHelper.Compiletime.Compile
-import CabalHelper.Compiletime.Types
-import CabalHelper.Shared.Common
-
-runReadP'Dist :: Dist.ReadP t t -> String -> t
-runReadP'Dist p i = case filter ((=="") . snd) $ Dist.readP_to_S p i of
- (a,""):[] -> a
- _ -> error $ "Error parsing: " ++ show i
-
-withinRange'CH :: Version -> VersionRange -> Bool
-withinRange'CH v r =
- withinRange (fromDataVersion v) r
-
-setupHOME :: IO ()
-setupHOME = do
- tmp <- fromMaybe "/tmp" <$> lookupEnv "TMPDIR"
- let home = tmp </> "compile-test-home"
- _ <- rawSystem "rm" ["-r", home]
- createDirectory home
- setEnv "HOME" home
-
-main :: IO ()
-main = do
- args <- getArgs
- case args of
- "list-versions":[] -> do
- mapM_ print =<< (allCabalVersions <$> ghcVersion defaultOptions)
- "list-versions":ghc_ver_str:[] ->
- mapM_ print $ allCabalVersions (parseVer ghc_ver_str)
- _ ->
- test args
-
-test args = do
- let action
- | null args = testAllCabalVersions
- | otherwise = testCabalVersions $ map parseVer' args
-
- setupHOME
-
- _ <- rawSystem "cabal" ["update"]
-
- action
-
-parseVer' :: String -> Either HEAD Version
-parseVer' "HEAD" = Left HEAD
-parseVer' v = Right $ parseVer v
-
-allCabalVersions :: Version -> [Version]
-allCabalVersions ghc_ver = let
- cabal_versions :: [Version]
- cabal_versions = map parseVer
- -- "1.14.0" -- not supported at runtime
- [ "1.16.0"
- , "1.16.0.1"
- , "1.16.0.2"
- , "1.16.0.3"
- , "1.18.0"
- , "1.18.1"
- , "1.18.1.1"
- , "1.18.1.2"
- , "1.18.1.3"
- , "1.18.1.4"
- , "1.18.1.5"
- , "1.18.1.6"
- , "1.18.1.7"
- , "1.20.0.0"
- , "1.20.0.1"
- , "1.20.0.2"
- , "1.20.0.3"
- , "1.20.0.4"
- , "1.22.0.0"
- , "1.22.1.0"
- , "1.22.1.1"
- , "1.22.2.0"
- , "1.22.3.0"
- , "1.22.4.0"
- , "1.22.5.0"
- , "1.22.6.0"
- , "1.22.7.0"
- , "1.22.8.0"
- , "1.24.0.0"
- , "1.24.1.0"
- , "1.24.2.0"
- , "2.0.0.2"
- , "2.0.1.0"
- , "2.0.1.1"
- , "2.2.0.0"
- , "2.2.0.1"
- ]
-
- constraint :: VersionRange
- constraint =
- fromMaybe (snd $ last constraint_table) $
- fmap snd $
- find (and . (zipWith (==) `on` versionBranch) ghc_ver . fst) $
- constraint_table
-
- constraint_table =
- map (parseVer *** runReadP'Dist parse) $
- [ ("7.4" , ">= 1.14 && < 2")
- , ("7.6" , ">= 1.16 && < 2")
- , ("7.8" , ">= 1.18 && < 2")
- , ("7.10" , ">= 1.22.2 && < 2")
- , ("8.0.1", ">= 1.24 ")
- , ("8.0.2", ">= 1.24.2 ")
- , ("8.2.1", ">= 2.0.0.2 ")
- , ("8.2.2", ">= 2.0.0.2 ")
- , ("8.4.1", ">= 2.0.0.2 ")
- , ("8.4.2", ">= 2.2.0.1 ")
- ]
- in
- reverse $ filter (flip withinRange'CH constraint) cabal_versions
-
-
-testAllCabalVersions :: IO ()
-testAllCabalVersions = do
- ghc_ver <- ghcVersion defaultOptions
- let relevant_cabal_versions = allCabalVersions ghc_ver
- testCabalVersions $ map Right relevant_cabal_versions ++ [Left HEAD]
-
-testCabalVersions :: [Either HEAD Version] -> IO ()
-testCabalVersions versions = do
- rvs <- forM versions $ \ver -> do
- let sver = either show showVersion ver
- hPutStrLn stderr $ "\n\n\n\n\n\n====== Compiling with Cabal-" ++ sver
- compilePrivatePkgDb ver
-
- let printStatus (cv, rv) = putStrLn $ "- Cabal "++ver++" "++status
- where ver = case cv of Left _ -> "HEAD"; Right v -> showVersion v
- status = case rv of
- Right _ ->
- "succeeded"
- Left rvc ->
- "failed (exit code "++show rvc++")"
-
- let drvs = versions `zip` rvs
-
- mapM_ printStatus drvs
- if any isLeft' $ map snd $ filter ((/=Left HEAD) . fst) drvs
- then exitFailure
- else exitSuccess
-
- where
- isLeft' (Left _) = True
- isLeft' (Right _) = False
-
-compilePrivatePkgDb :: Either HEAD Version -> IO (Either ExitCode FilePath)
-compilePrivatePkgDb eCabalVer = do
- res <- E.try $ installCabal defaultOptions { oVerbose = True } eCabalVer
- case res of
- Right (db, cabalVer) ->
- compileWithPkg db cabalVer
- Left (ioe :: IOException) -> do
- print ioe
- return $ Left (ExitFailure 1)
-
-compileWithPkg :: PackageDbDir
- -> CabalVersion
- -> IO (Either ExitCode FilePath)
-compileWithPkg db cabalVer = do
- appdir <- appCacheDir
- let comp =
- CompileWithCabalPackage (Just db) cabalVer [cabalPkgId cabalVer] CPSGlobal
- compile
- comp
- (compPaths appdir (error "compile-test: distdir not available") comp)
- defaultOptions { oVerbose = True }
-
-
-cabalPkgId :: CabalVersion -> String
-cabalPkgId (CabalHEAD _commitid) = "Cabal"
-cabalPkgId (CabalVersion v) = "Cabal-" ++ showVersion v
diff --git a/vendor/cabal-helper-0.8.1.2/tests/GhcSession.hs b/vendor/cabal-helper-0.8.1.2/tests/GhcSession.hs
deleted file mode 100644
index 6e71075..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/GhcSession.hs
+++ /dev/null
@@ -1,182 +0,0 @@
-{-# LANGUAGE TupleSections, ScopedTypeVariables #-}
-module Main where
-
-import GHC
-import GHC.Paths (libdir)
-import DynFlags
-
-import qualified Control.Exception as E
-import Control.Monad
-import Control.Monad.IO.Class
-import Data.List
-import Data.Version
-import System.Environment (getArgs)
-import System.Exit
-import System.FilePath ((</>))
-import System.Directory
-import System.IO
-import System.IO.Temp
-import System.Process (rawSystem, readProcess)
-
-import Distribution.Helper
-
-import CabalHelper.Shared.Common
-
-
-main :: IO ()
-main = do
- args <- getArgs
- topdir <- getCurrentDirectory
- res <- mapM (setup topdir test) $ case args of
- [] -> [ ("tests/exelib" , parseVer "1.10", parseVer "0")
- , ("tests/exeintlib", parseVer "2.0", parseVer "0")
- , ("tests/fliblib" , parseVer "2.0", parseVer "0")
- , ("tests/bkpregex" , parseVer "2.0", parseVer "8.1")
- -- min Cabal lib ver -^ min GHC ver -^
- ]
- xs -> map (, parseVer "0", parseVer "0") xs
-
- if any (==False) $ concat res
- then exitFailure
- else exitSuccess
-
-cabalInstallVersion :: IO Version
-cabalInstallVersion =
- parseVer . trim <$> readProcess "cabal" ["--numeric-version"] ""
-
-ghcVersion :: IO Version
-ghcVersion =
- parseVer . trim <$> readProcess "ghc" ["--numeric-version"] ""
-
-cabalInstallBuiltinCabalVersion :: IO Version
-cabalInstallBuiltinCabalVersion =
- parseVer . trim <$> readProcess "cabal"
- ["act-as-setup", "--", "--numeric-version"] ""
-
-setup :: FilePath -> (FilePath -> IO [Bool]) -> (FilePath, Version, Version) -> IO [Bool]
-setup topdir act (srcdir, min_cabal_ver, min_ghc_ver) = do
- ci_ver <- cabalInstallVersion
- c_ver <- cabalInstallBuiltinCabalVersion
- g_ver <- ghcVersion
- let mreason
- | (ci_ver < parseVer "1.24") =
- Just $ "cabal-install-" ++ showVersion ci_ver ++ " is too old"
- | c_ver < min_cabal_ver =
- Just $ "Cabal-" ++ showVersion c_ver
- ++ " < " ++ showVersion min_cabal_ver
- | g_ver < min_ghc_ver =
- Just $ "ghc-" ++ showVersion g_ver
- ++ " < " ++ showVersion min_ghc_ver
- | otherwise =
- Nothing
-
- case mreason of
- Just reason -> do
- putStrLn $ "Skipping test '" ++ srcdir ++ "' because " ++ reason ++ "."
- return []
- Nothing -> do
- putStrLn $ "Running test '" ++ srcdir ++ "' ------------------------------"
- withSystemTempDirectory "cabal-helper.ghc-session.test" $ \dir -> do
- setCurrentDirectory $ topdir </> srcdir
- run "cabal" [ "sdist", "--output-dir", dir ]
-
- setCurrentDirectory dir
- run "cabal" [ "configure" ]
-
- act dir
-
-run :: String -> [String] -> IO ()
-run x xs = do
- print $ x:xs
- ExitSuccess <- rawSystem x xs
- return ()
-
-test :: FilePath -> IO [Bool]
-test dir = do
- let qe = mkQueryEnv dir (dir </> "dist")
- cs <- runQuery qe $ components $ (,,,) <$> entrypoints <.> ghcOptions <.> needsBuildOutput
- forM cs $ \(ep, opts, nb, cn) -> do
-
- putStrLn $ "\n" ++ show cn ++ ":::: " ++ show nb
-
- when (nb == ProduceBuildOutput) $ do
- run "cabal" [ "build" ]
-
- let opts' = "-Werror" : opts
-
- let sopts = intercalate " " $ map formatArg $ "\nghc" : opts'
- putStrLn $ "\n" ++ show cn ++ ": " ++ sopts
- hFlush stdout
- compileModule nb ep opts'
- where
- formatArg x
- | "-" `isPrefixOf` x = "\n "++x
- | otherwise = x
-
-
-compileModule :: NeedsBuildOutput -> ChEntrypoint -> [String] -> IO Bool
-compileModule nb ep opts = do
-
- putStrLn $ "compiling:" ++ show ep ++ " (" ++ show nb ++ ")"
-
- E.handle (\(ec :: ExitCode) -> print ec >> return False) $ do
-
- defaultErrorHandler defaultFatalMessager defaultFlushOut $ do
-
- runGhc (Just libdir) $ do
-
- handleSourceError (\e -> GHC.printException e >> return False) $ do
-
- let target = case nb of
- ProduceBuildOutput -> HscNothing -- AZ: what should this be?
- NoBuildOutput -> HscInterpreted
-
- dflags0 <- getSessionDynFlags
- let dflags1 = dflags0 {
- ghcMode = CompManager
- , ghcLink = LinkInMemory
- , hscTarget = target
- , optLevel = 0
- }
-
- (dflags2, _, _) <- parseDynamicFlags dflags1 (map noLoc opts)
- _ <- setSessionDynFlags dflags2
-
- ts <- mapM (\t -> guessTarget t Nothing) $
- case ep of
- ChLibEntrypoint ms ms' ss -> map unChModuleName $ ms ++ ms' ++ ss
- ChExeEntrypoint m' ms ->
- let
-
- -- The options first clear out includes, then put in the build dir. We want the
- -- first one after that, so "regex-example" in the following case
- --
- -- ,"-i"
- -- ,"-idist/build/regex-example"
- -- ,"-iregex-example"
- firstInclude = drop 2 $ head $ drop 2 $ filter (isPrefixOf "-i") opts
- m = firstInclude </> m'
- in [m] ++ map unChModuleName ms
- ChSetupEntrypoint -> ["Setup.hs"]
-
- let ts' = case nb of
- NoBuildOutput -> map (\t -> t { targetAllowObjCode = False }) ts
- ProduceBuildOutput -> ts
-
- setTargets ts'
- _ <- load LoadAllTargets
-
- when (nb == NoBuildOutput) $ do
- setContext $ case ep of
- ChLibEntrypoint ms ms' ss ->
- map (IIModule . mkModuleName . unChModuleName) $ ms ++ ms' ++ ss
- ChExeEntrypoint _ ms ->
- map (IIModule . mkModuleName . unChModuleName) $ ChModuleName "Main" : ms
- ChSetupEntrypoint ->
- map (IIModule . mkModuleName) ["Main"]
-
- liftIO $ print ExitSuccess
- return True
-
-unChModuleName :: ChModuleName -> String
-unChModuleName (ChModuleName mn) = mn
diff --git a/vendor/cabal-helper-0.8.1.2/tests/bkpregex/Setup.hs b/vendor/cabal-helper-0.8.1.2/tests/bkpregex/Setup.hs
deleted file mode 100644
index 9a994af..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/bkpregex/Setup.hs
+++ /dev/null
@@ -1,2 +0,0 @@
-import Distribution.Simple
-main = defaultMain
diff --git a/vendor/cabal-helper-0.8.1.2/tests/bkpregex/bkpregex.cabal b/vendor/cabal-helper-0.8.1.2/tests/bkpregex/bkpregex.cabal
deleted file mode 100644
index 5d8d813..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/bkpregex/bkpregex.cabal
+++ /dev/null
@@ -1,29 +0,0 @@
-name: bkpregex
-version: 0.1.0.0
-build-type: Simple
-cabal-version: 2.0
-
-library str-impls
- build-depends: base, bytestring
- exposed-modules: Str.String, Str.ByteString
- hs-source-dirs: str-impls
-
-library regex-types
- build-depends: base
- exposed-modules: Regex.Types
- hs-source-dirs: regex-types
-
-library regex-indef
- build-depends: base, regex-types
- signatures: Str
- exposed-modules: Regex
- hs-source-dirs: regex-indef
-
-executable regex-example
- main-is: Main.hs
- build-depends: base, regex-indef, regex-types, str-impls
- mixins: regex-indef (Regex as Regex.String)
- requires (Str as Str.String),
- regex-indef (Regex as Regex.ByteString)
- requires (Str as Str.ByteString)
- hs-source-dirs: regex-example
diff --git a/vendor/cabal-helper-0.8.1.2/tests/bkpregex/regex-example/Main.hs b/vendor/cabal-helper-0.8.1.2/tests/bkpregex/regex-example/Main.hs
deleted file mode 100644
index 76d2974..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/bkpregex/regex-example/Main.hs
+++ /dev/null
@@ -1,12 +0,0 @@
-{-# LANGUAGE OverloadedStrings #-}
-module Main where
-
-import Regex.Types
-import qualified Regex.String
-import qualified Regex.ByteString
-
-nocs = Rep (Alt (Sym 'a') (Sym 'b'))
-onec = Seq nocs (Sym 'c')
-evencs = Seq (Rep (Seq onec onec)) nocs
-main = print (Regex.String.accept evencs "acc") >>
- print (Regex.ByteString.accept evencs "acc")
diff --git a/vendor/cabal-helper-0.8.1.2/tests/bkpregex/regex-indef/Regex.hs b/vendor/cabal-helper-0.8.1.2/tests/bkpregex/regex-indef/Regex.hs
deleted file mode 100644
index 506566b..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/bkpregex/regex-indef/Regex.hs
+++ /dev/null
@@ -1,14 +0,0 @@
-module Regex where
-
-import Prelude hiding (null)
-import Str
-import Regex.Types
-
-accept :: Reg -> Str -> Bool
-accept Eps u = null u
-accept (Sym c) u = u == singleton c
-accept (Alt p q) u = accept p u || accept q u
-accept (Seq p q) u =
- or [accept p u1 && accept q u2 | (u1, u2) <- splits u]
-accept (Rep r) u =
- or [and [accept r ui | ui <- ps] | ps <- parts u]
diff --git a/vendor/cabal-helper-0.8.1.2/tests/bkpregex/regex-indef/Str.hsig b/vendor/cabal-helper-0.8.1.2/tests/bkpregex/regex-indef/Str.hsig
deleted file mode 100644
index 23bfb8c..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/bkpregex/regex-indef/Str.hsig
+++ /dev/null
@@ -1,9 +0,0 @@
-signature Str where
-
-data Str
-instance Eq Str
-
-null :: Str -> Bool
-singleton :: Char -> Str
-splits :: Str -> [(Str, Str)]
-parts :: Str -> [[Str]]
diff --git a/vendor/cabal-helper-0.8.1.2/tests/bkpregex/regex-types/Regex/Types.hs b/vendor/cabal-helper-0.8.1.2/tests/bkpregex/regex-types/Regex/Types.hs
deleted file mode 100644
index 2900749..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/bkpregex/regex-types/Regex/Types.hs
+++ /dev/null
@@ -1,7 +0,0 @@
-module Regex.Types where
-
-data Reg = Eps
- | Sym Char
- | Alt Reg Reg
- | Seq Reg Reg
- | Rep Reg
diff --git a/vendor/cabal-helper-0.8.1.2/tests/bkpregex/str-impls/Str/ByteString.hs b/vendor/cabal-helper-0.8.1.2/tests/bkpregex/str-impls/Str/ByteString.hs
deleted file mode 100644
index cd49fed..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/bkpregex/str-impls/Str/ByteString.hs
+++ /dev/null
@@ -1,17 +0,0 @@
-module Str.ByteString(module Data.ByteString.Char8, module Str.ByteString) where
-
-import Prelude hiding (length, null, splitAt)
-import Data.ByteString.Char8
-import Data.ByteString
-
-type Str = ByteString
-
-splits :: Str -> [(Str, Str)]
-splits s = fmap (\n -> splitAt n s) [0..length s]
-
-parts :: Str -> [[Str]]
-parts s | null s = [[]]
- | otherwise = do
- n <- [1..length s]
- let (l, r) = splitAt n s
- fmap (l:) (parts r)
diff --git a/vendor/cabal-helper-0.8.1.2/tests/bkpregex/str-impls/Str/String.hs b/vendor/cabal-helper-0.8.1.2/tests/bkpregex/str-impls/Str/String.hs
deleted file mode 100644
index bba89de..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/bkpregex/str-impls/Str/String.hs
+++ /dev/null
@@ -1,21 +0,0 @@
-module Str.String where
-
-import Prelude hiding (null)
-import qualified Prelude as P
-
-type Str = String
-
-null :: Str -> Bool
-null = P.null
-
-singleton :: Char -> Str
-singleton c = [c]
-
-splits :: Str -> [(Str, Str)]
-splits [] = [([], [])]
-splits (c:cs) = ([], c:cs):[(c:s1,s2) | (s1,s2) <- splits cs]
-
-parts :: Str -> [[Str]]
-parts [] = [[]]
-parts [c] = [[[c]]]
-parts (c:cs) = concat [[(c:p):ps, [c]:p:ps] | p:ps <- parts cs]
diff --git a/vendor/cabal-helper-0.8.1.2/tests/exeintlib/Exe.hs b/vendor/cabal-helper-0.8.1.2/tests/exeintlib/Exe.hs
deleted file mode 100644
index 200915f..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/exeintlib/Exe.hs
+++ /dev/null
@@ -1,5 +0,0 @@
-module Main where
-
-import Lib
-
-main = print lib
diff --git a/vendor/cabal-helper-0.8.1.2/tests/exeintlib/Setup.hs b/vendor/cabal-helper-0.8.1.2/tests/exeintlib/Setup.hs
deleted file mode 100644
index 9a994af..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/exeintlib/Setup.hs
+++ /dev/null
@@ -1,2 +0,0 @@
-import Distribution.Simple
-main = defaultMain
diff --git a/vendor/cabal-helper-0.8.1.2/tests/exeintlib/exeintlib.cabal b/vendor/cabal-helper-0.8.1.2/tests/exeintlib/exeintlib.cabal
deleted file mode 100644
index 7507152..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/exeintlib/exeintlib.cabal
+++ /dev/null
@@ -1,31 +0,0 @@
-name: exeintlib
-version: 0
-build-type: Simple
-cabal-version: >=2.0
-
-library
- exposed-modules: Lib
- hs-source-dirs: lib
- build-depends: base, filepath, intlib
- default-language: Haskell2010
-
-library intlib
- exposed-modules: IntLib
- hs-source-dirs: intlib
- build-depends: base, directory
- default-language: Haskell2010
-
-executable exe
- main-is: Exe.hs
- build-depends: base, exeintlib
- default-language: Haskell2010
-
-test-suite exe-test
- type: exitcode-stdio-1.0
- main-is: Exe.hs
- build-depends: base, exeintlib
-
-benchmark exe-bench
- type: exitcode-stdio-1.0
- main-is: Exe.hs
- build-depends: base, exeintlib
diff --git a/vendor/cabal-helper-0.8.1.2/tests/exeintlib/intlib/IntLib.hs b/vendor/cabal-helper-0.8.1.2/tests/exeintlib/intlib/IntLib.hs
deleted file mode 100644
index 6dde9d0..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/exeintlib/intlib/IntLib.hs
+++ /dev/null
@@ -1,7 +0,0 @@
-module IntLib where
-
-import System.Directory
-
-directory = doesFileExist "Exe.hs"
-
-intlib = 1
diff --git a/vendor/cabal-helper-0.8.1.2/tests/exeintlib/lib/Lib.hs b/vendor/cabal-helper-0.8.1.2/tests/exeintlib/lib/Lib.hs
deleted file mode 100644
index fe44c70..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/exeintlib/lib/Lib.hs
+++ /dev/null
@@ -1,8 +0,0 @@
-module Lib where
-
-import System.FilePath
-import IntLib
-
-filepath = "a" </> "b"
-
-lib = 1 + intlib
diff --git a/vendor/cabal-helper-0.8.1.2/tests/exelib/Exe.hs b/vendor/cabal-helper-0.8.1.2/tests/exelib/Exe.hs
deleted file mode 100644
index 7655927..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/exelib/Exe.hs
+++ /dev/null
@@ -1,5 +0,0 @@
-module Main where
-
-import Lib
-
-main = print foo
diff --git a/vendor/cabal-helper-0.8.1.2/tests/exelib/Setup.hs b/vendor/cabal-helper-0.8.1.2/tests/exelib/Setup.hs
deleted file mode 100644
index 9a994af..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/exelib/Setup.hs
+++ /dev/null
@@ -1,2 +0,0 @@
-import Distribution.Simple
-main = defaultMain
diff --git a/vendor/cabal-helper-0.8.1.2/tests/exelib/exelib.cabal b/vendor/cabal-helper-0.8.1.2/tests/exelib/exelib.cabal
deleted file mode 100644
index 2422998..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/exelib/exelib.cabal
+++ /dev/null
@@ -1,25 +0,0 @@
-name: exelib
-version: 0
-build-type: Simple
-cabal-version: >=1.10
-
-library
- exposed-modules: Lib
- hs-source-dirs: lib
- build-depends: base, filepath, directory
- default-language: Haskell2010
-
-executable exelib
- main-is: Exe.hs
- build-depends: base, exelib
- default-language: Haskell2010
-
-test-suite exe-test
- type: exitcode-stdio-1.0
- main-is: Exe.hs
- build-depends: base, exelib
-
-benchmark exe-bench
- type: exitcode-stdio-1.0
- main-is: Exe.hs
- build-depends: base, exelib
diff --git a/vendor/cabal-helper-0.8.1.2/tests/exelib/lib/Lib.hs b/vendor/cabal-helper-0.8.1.2/tests/exelib/lib/Lib.hs
deleted file mode 100644
index 417a0ad..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/exelib/lib/Lib.hs
+++ /dev/null
@@ -1,8 +0,0 @@
-module Lib where
-
-import System.Directory
-import System.FilePath
-
-filepath = "a" </> "b"
-directory = doesFileExist "Exe.hs"
-foo = 1
diff --git a/vendor/cabal-helper-0.8.1.2/tests/fliblib/FLib.hs b/vendor/cabal-helper-0.8.1.2/tests/fliblib/FLib.hs
deleted file mode 100644
index e6a9818..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/fliblib/FLib.hs
+++ /dev/null
@@ -1,5 +0,0 @@
-module FLib where
-
-import Lib
-
-flib = print foo
diff --git a/vendor/cabal-helper-0.8.1.2/tests/fliblib/Setup.hs b/vendor/cabal-helper-0.8.1.2/tests/fliblib/Setup.hs
deleted file mode 100644
index 9a994af..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/fliblib/Setup.hs
+++ /dev/null
@@ -1,2 +0,0 @@
-import Distribution.Simple
-main = defaultMain
diff --git a/vendor/cabal-helper-0.8.1.2/tests/fliblib/fliblib.cabal b/vendor/cabal-helper-0.8.1.2/tests/fliblib/fliblib.cabal
deleted file mode 100644
index 4610605..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/fliblib/fliblib.cabal
+++ /dev/null
@@ -1,19 +0,0 @@
-name: fliblib
-version: 0
-build-type: Simple
-cabal-version: >=1.10
-
-library
- exposed-modules: Lib
- hs-source-dirs: lib
- build-depends: base, filepath, directory
- default-language: Haskell2010
-
-foreign-library flib
- other-modules: FLib
- build-depends: base, fliblib
- hs-source-dirs: .
- type: native-shared
- if os(Windows)
- options: standalone
- default-language: Haskell2010 \ No newline at end of file
diff --git a/vendor/cabal-helper-0.8.1.2/tests/fliblib/lib/Lib.hs b/vendor/cabal-helper-0.8.1.2/tests/fliblib/lib/Lib.hs
deleted file mode 100644
index 417a0ad..0000000
--- a/vendor/cabal-helper-0.8.1.2/tests/fliblib/lib/Lib.hs
+++ /dev/null
@@ -1,8 +0,0 @@
-module Lib where
-
-import System.Directory
-import System.FilePath
-
-filepath = "a" </> "b"
-directory = doesFileExist "Exe.hs"
-foo = 1