{-# LANGUAGE CPP #-}
module Run (
  doctest
, doctestWithRepl

, Config(..)
, defaultConfig
, doctestWith

, Result
, Summary(..)
, isSuccess
, evaluateResult
, doctestWithResult

, runDocTests
#ifdef TEST
, expandDirs
#endif
) where

import           Imports

import           System.Directory (doesFileExist, doesDirectoryExist, getDirectoryContents)
import           System.Environment (getEnvironment)
import           System.Exit (exitFailure, exitSuccess)
import           System.FilePath ((</>), takeExtension)
import           System.IO
import           System.IO.CodePage (withCP65001)
import           System.Process (rawSystem)

import qualified Control.Exception as E

#if __GLASGOW_HASKELL__ < 900
import           Panic
#else
import           GHC.Utils.Panic
#endif

import           PackageDBs
import           Parse
import           Options hiding (Result(..))
import qualified Options
import           Runner
import           Location
import qualified Interpreter

-- | Run doctest with given list of arguments.
--
-- Example:
--
-- >>> doctest ["-iexample/src", "example/src/Example.hs"]
-- ...
-- Examples: 2  Tried: 2  Errors: 0  Failures: 0
--
-- This can be used to create a Cabal test suite that runs doctest for your
-- project.
--
-- If a directory is given, it is traversed to find all .hs and .lhs files
-- inside of it, ignoring hidden entries.
doctest :: [String] -> IO ()
doctest :: [String] -> IO ()
doctest = (String, [String]) -> [String] -> IO ()
doctestWithRepl (Config -> (String, [String])
repl Config
defaultConfig)

doctestWithRepl :: (String, [String]) -> [String] -> IO ()
doctestWithRepl :: (String, [String]) -> [String] -> IO ()
doctestWithRepl (String, [String])
repl [String]
args0 = case [String] -> Result Run
parseOptions [String]
args0 of
  Options.ProxyToGhc [String]
args -> String -> [String] -> IO ExitCode
rawSystem String
Interpreter.ghc [String]
args forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall e a. Exception e => e -> IO a
E.throwIO
  Options.Output String
s -> String -> IO ()
putStr String
s
  Options.Result (Run [String]
warnings Bool
magicMode Config
config) -> do
    forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Handle -> String -> IO ()
hPutStrLn Handle
stderr) [String]
warnings
    Handle -> IO ()
hFlush Handle
stderr

    Bool
i <- IO Bool
Interpreter.interpreterSupported
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
i forall a b. (a -> b) -> a -> b
$ do
      Handle -> String -> IO ()
hPutStrLn Handle
stderr String
"WARNING: GHC does not support --interactive, skipping tests"
      forall a. IO a
exitSuccess

    [String]
opts <- case Bool
magicMode of
      Bool
False -> forall (m :: * -> *) a. Monad m => a -> m a
return (Config -> [String]
ghcOptions Config
config)
      Bool
True -> do
        [String]
expandedArgs <- forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> IO [String]
expandDirs (Config -> [String]
ghcOptions Config
config)
        [String]
packageDBArgs <- IO [String]
getPackageDBArgs
        [String] -> [String]
addDistArgs <- IO ([String] -> [String])
getAddDistArgs
        forall (m :: * -> *) a. Monad m => a -> m a
return ([String] -> [String]
addDistArgs forall a b. (a -> b) -> a -> b
$ [String]
packageDBArgs forall a. [a] -> [a] -> [a]
++ [String]
expandedArgs)
    Config -> IO ()
doctestWith Config
config{(String, [String])
repl :: (String, [String])
repl :: (String, [String])
repl, ghcOptions :: [String]
ghcOptions = [String]
opts}

-- | Expand a reference to a directory to all .hs and .lhs files within it.
expandDirs :: String -> IO [String]
expandDirs :: String -> IO [String]
expandDirs String
fp0 = do
    Bool
isDir <- String -> IO Bool
doesDirectoryExist String
fp0
    if Bool
isDir
        then String -> IO [String]
findHaskellFiles String
fp0
        else forall (m :: * -> *) a. Monad m => a -> m a
return [String
fp0]
  where
    findHaskellFiles :: String -> IO [String]
findHaskellFiles String
dir = do
        [String]
contents <- String -> IO [String]
getDirectoryContents String
dir
        forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> IO [String]
go (forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Bool
hidden) [String]
contents)
      where
        go :: String -> IO [String]
go String
name = do
            Bool
isDir <- String -> IO Bool
doesDirectoryExist String
fp
            if Bool
isDir
                then String -> IO [String]
findHaskellFiles String
fp
                else if String -> Bool
isHaskellFile String
fp
                        then forall (m :: * -> *) a. Monad m => a -> m a
return [String
fp]
                        else forall (m :: * -> *) a. Monad m => a -> m a
return []
          where
            fp :: String
fp = String
dir String -> String -> String
</> String
name

    hidden :: String -> Bool
hidden (Char
'.':String
_) = Bool
True
    hidden String
_ = Bool
False

    isHaskellFile :: String -> Bool
isHaskellFile String
fp = String -> String
takeExtension String
fp forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
".hs", String
".lhs"]

-- | Get the necessary arguments to add the @cabal_macros.h@ file and autogen
-- directory, if present.
getAddDistArgs :: IO ([String] -> [String])
getAddDistArgs :: IO ([String] -> [String])
getAddDistArgs = do
    [(String, String)]
env <- IO [(String, String)]
getEnvironment
    let dist :: String
dist =
            case forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
"HASKELL_DIST_DIR" [(String, String)]
env of
                Maybe String
Nothing -> String
"dist"
                Just String
x -> String
x
        autogen :: String
autogen = String
dist forall a. [a] -> [a] -> [a]
++ String
"/build/autogen/"
        cabalMacros :: String
cabalMacros = String
autogen forall a. [a] -> [a] -> [a]
++ String
"cabal_macros.h"

    Bool
dirExists <- String -> IO Bool
doesDirectoryExist String
autogen
    if Bool
dirExists
        then do
            Bool
fileExists <- String -> IO Bool
doesFileExist String
cabalMacros
            forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ \[String]
rest ->
                  forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"-i", String
dist, String
"/build/autogen/"]
                forall a. a -> [a] -> [a]
: String
"-optP-include"
                forall a. a -> [a] -> [a]
: (if Bool
fileExists
                    then (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"-optP", String
dist, String
"/build/autogen/cabal_macros.h"]forall a. a -> [a] -> [a]
:)
                    else forall a. a -> a
id) [String]
rest
        else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. a -> a
id

doctestWith :: Config -> IO ()
doctestWith :: Config -> IO ()
doctestWith = Config -> IO Result
doctestWithResult forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Result -> IO ()
evaluateResult

type Result = Summary

isSuccess :: Result -> Bool
isSuccess :: Result -> Bool
isSuccess Result
s = Result -> Int
sErrors Result
s forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
&& Result -> Int
sFailures Result
s forall a. Eq a => a -> a -> Bool
== Int
0

evaluateResult :: Result -> IO ()
evaluateResult :: Result -> IO ()
evaluateResult Result
r = forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ Result -> Bool
isSuccess Result
r) forall a. IO a
exitFailure

doctestWithResult :: Config -> IO Result
doctestWithResult :: Config -> IO Result
doctestWithResult Config
config = do
  ([String] -> IO [Module [Located DocTest]]
extractDocTests (Config -> [String]
ghcOptions Config
config) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Config -> [Module [Located DocTest]] -> IO Result
runDocTests Config
config) forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`E.catch` \SomeException
e -> do
    case forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e of
      Just (UsageError String
err) -> do
        Handle -> String -> IO ()
hPutStrLn Handle
stderr (String
"doctest: " forall a. [a] -> [a] -> [a]
++ String
err)
        Handle -> String -> IO ()
hPutStrLn Handle
stderr String
"Try `doctest --help' for more information."
        forall a. IO a
exitFailure
      Maybe GhcException
_ -> forall e a. Exception e => e -> IO a
E.throwIO SomeException
e

runDocTests :: Config -> [Module [Located DocTest]] -> IO Result
runDocTests :: Config -> [Module [Located DocTest]] -> IO Result
runDocTests Config{Bool
[String]
(String, [String])
verbose :: Config -> Bool
preserveIt :: Config -> Bool
fastMode :: Config -> Bool
repl :: (String, [String])
verbose :: Bool
preserveIt :: Bool
fastMode :: Bool
ghcOptions :: [String]
ghcOptions :: Config -> [String]
repl :: Config -> (String, [String])
..} [Module [Located DocTest]]
modules = do
  forall a. (String, [String]) -> (Interpreter -> IO a) -> IO a
Interpreter.withInterpreter ((forall a. Semigroup a => a -> a -> a
<> [String]
ghcOptions) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String, [String])
repl) forall a b. (a -> b) -> a -> b
$ \ Interpreter
interpreter -> forall a. IO a -> IO a
withCP65001 forall a b. (a -> b) -> a -> b
$ do
    Bool
-> Bool
-> Bool
-> Interpreter
-> [Module [Located DocTest]]
-> IO Result
runModules Bool
fastMode Bool
preserveIt Bool
verbose Interpreter
interpreter [Module [Located DocTest]]
modules