{-# LANGUAGE CPP #-}
module Test.Hspec.Core.Compat (
  module Imports
, module Test.Hspec.Core.Compat
, Typeable
) where

import           Control.Exception as Imports
import           Control.Arrow as Imports ((>>>), (&&&), first, second)
import           Control.Applicative as Imports
import           Control.Monad as Imports hiding (
    mapM
  , mapM_
  , forM
  , forM_
  , msum
  , sequence
  , sequence_
  )
import           Data.Maybe as Imports
import           Data.Foldable as Imports
import           GHC.Stack as Imports (HasCallStack, withFrozenCallStack)

import           System.IO
import           System.Exit
import           System.Environment

#if MIN_VERSION_base(4,11,0)
import           Data.Functor as Imports ((<&>))
#endif

import           Data.Traversable as Imports
#ifndef __MHS__
import           Data.Monoid as Imports hiding (First)
#else
import           Data.Monoid as Imports (Endo(..), Sum(..))
#endif
import           Data.List as Imports (
    stripPrefix
  , isPrefixOf
  , isInfixOf
  , isSuffixOf
  , intercalate
  , inits
  , tails
  , sortBy
  , sortOn
  )

import           Prelude as Imports hiding (
    all
  , and
  , any
  , concat
  , concatMap
  , elem
  , foldl
  , foldl1
  , foldr
  , foldr1
  , mapM
  , mapM_
  , maximum
  , minimum
  , notElem
  , or
  , product
  , sequence
  , sequence_
  , sum
  , length
  , null
  )

import           Data.Typeable
import           Data.IORef as Imports

#if MIN_VERSION_base(4,12,0)
import           GHC.ResponseFile as Imports (unescapeArgs)
#else
import           Data.Char
#endif

import           Text.Read as Imports (readMaybe)
import           System.Environment as Imports (lookupEnv)


import           Data.Bool as Imports (bool)

import           Control.Concurrent

#ifndef __MHS__
import           GHC.IO.Exception
#else
import           System.IO.Error
#endif
  ( ioe_type, IOErrorType(..) )

isUnsupportedOperation :: IOError -> Bool
isUnsupportedOperation :: IOError -> Bool
isUnsupportedOperation IOError
e = IOError -> IOErrorType
ioe_type IOError
e IOErrorType -> IOErrorType -> Bool
forall a. Eq a => a -> a -> Bool
== IOErrorType
UnsupportedOperation

showType :: Typeable a => a -> String
showType :: forall a. Typeable a => a -> String
showType = TyCon -> String
forall a. Show a => a -> String
show (TyCon -> String) -> (a -> TyCon) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TypeRep -> TyCon
typeRepTyCon (TypeRep -> TyCon) -> (a -> TypeRep) -> a -> TyCon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf

getDefaultConcurrentJobs :: IO Int
getDefaultConcurrentJobs :: IO Int
getDefaultConcurrentJobs = IO Int
getNumCapabilities

guarded :: Alternative m => (a -> Bool) -> a -> m a
guarded :: forall (m :: * -> *) a. Alternative m => (a -> Bool) -> a -> m a
guarded a -> Bool
p a
a = if a -> Bool
p a
a then a -> m a
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a else m a
forall a. m a
forall (f :: * -> *) a. Alternative f => f a
empty

#if !MIN_VERSION_base(4,11,0)
infixl 1 <&>
(<&>) :: Functor f => f a -> (a -> b) -> f b
(<&>) = flip (<$>)
#endif

endsWith :: Eq a => [a] -> [a] -> Bool
endsWith :: forall a. Eq a => [a] -> [a] -> Bool
endsWith = ([a] -> [a] -> Bool) -> [a] -> [a] -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip [a] -> [a] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isSuffixOf

pass :: Applicative m => m ()
pass :: forall (m :: * -> *). Applicative m => m ()
pass = () -> m ()
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()

die :: String -> IO a
die :: forall a. String -> IO a
die String
err = do
  String
name <- IO String
getProgName
  Handle -> String -> IO ()
hPutStrLn Handle
stderr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
name String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
": " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
err
  IO a
forall a. IO a
exitFailure

#if !MIN_VERSION_base(4,12,0)
unescapeArgs :: String -> [String]
unescapeArgs = filter (not . null) . unescape

data Quoting = NoneQ | SngQ | DblQ

unescape :: String -> [String]
unescape args = reverse . map reverse $ go args NoneQ False [] []
    where
      -- n.b., the order of these cases matters; these are cribbed from gcc
      -- case 1: end of input
      go []     _q    _bs   a as = a:as
      -- case 2: back-slash escape in progress
      go (c:cs) q     True  a as = go cs q     False (c:a) as
      -- case 3: no back-slash escape in progress, but got a back-slash
      go (c:cs) q     False a as
        | '\\' == c              = go cs q     True  a     as
      -- case 4: single-quote escaping in progress
      go (c:cs) SngQ  False a as
        | '\'' == c              = go cs NoneQ False a     as
        | otherwise              = go cs SngQ  False (c:a) as
      -- case 5: double-quote escaping in progress
      go (c:cs) DblQ  False a as
        | '"' == c               = go cs NoneQ False a     as
        | otherwise              = go cs DblQ  False (c:a) as
      -- case 6: no escaping is in progress
      go (c:cs) NoneQ False a as
        | isSpace c              = go cs NoneQ False []    (a:as)
        | '\'' == c              = go cs SngQ  False a     as
        | '"'  == c              = go cs DblQ  False a     as
        | otherwise              = go cs NoneQ False (c:a) as
#endif

unicodeOutputSupported :: Handle -> IO Bool
unicodeOutputSupported :: Handle -> IO Bool
unicodeOutputSupported Handle
_h = do
#ifndef __MHS__
  (Maybe String -> Maybe String -> Bool
forall a. Eq a => a -> a -> Bool
== String -> Maybe String
forall a. a -> Maybe a
Just String
"UTF-8") (Maybe String -> Bool)
-> (Maybe TextEncoding -> Maybe String)
-> Maybe TextEncoding
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TextEncoding -> String) -> Maybe TextEncoding -> Maybe String
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TextEncoding -> String
forall a. Show a => a -> String
show (Maybe TextEncoding -> Bool) -> IO (Maybe TextEncoding) -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Handle -> IO (Maybe TextEncoding)
hGetEncoding Handle
_h
#else
  return True

canonicalizePath :: FilePath -> IO FilePath
canonicalizePath = return
#endif