1
1
mirror of https://github.com/sol/hpack.git synced 2024-10-04 11:47:15 +03:00
hpack/test/Helper.hs
Simon Hengel 6b4c9e8c5c Support SPDX license identifiers (see #292)
- Require `cabal-version: 2.2` when SPDX license identifiers are used
- Map cabal-style licenses to SPDX license identifiers when
  `cabal-version` is 2.2 or higher
2018-07-11 19:27:15 +08:00

38 lines
1.1 KiB
Haskell

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ConstraintKinds #-}
module Helper (
module Test.Hspec
, module Test.Mockery.Directory
, module Control.Monad
, module Control.Applicative
, withTempDirectory
, module System.FilePath
, withCurrentDirectory
, yaml
) where
import Test.Hspec
import Test.Mockery.Directory
import Control.Monad
import Control.Applicative
import System.Directory (getCurrentDirectory, setCurrentDirectory, canonicalizePath)
import Control.Exception
import qualified System.IO.Temp as Temp
import System.FilePath
import Data.Yaml.TH (yamlQQ)
import Language.Haskell.TH.Quote (QuasiQuoter)
withCurrentDirectory :: FilePath -> IO a -> IO a
withCurrentDirectory dir action = do
bracket getCurrentDirectory setCurrentDirectory $ \ _ -> do
setCurrentDirectory dir
action
withTempDirectory :: (FilePath -> IO a) -> IO a
withTempDirectory action = Temp.withSystemTempDirectory "hspec" $ \dir -> do
canonicalizePath dir >>= action
yaml :: Language.Haskell.TH.Quote.QuasiQuoter
yaml = yamlQQ