summaryrefslogtreecommitdiffhomepage
path: root/tests/Language/Haskell/Stylish/Tests/Util.hs
diff options
context:
space:
mode:
authorSean Whitton <spwhitton@spwhitton.name>2021-01-17 11:15:37 -0700
committerSean Whitton <spwhitton@spwhitton.name>2021-01-17 11:15:37 -0700
commit3130faccf7c9a9a7697e246884e2b60fd4b1f9de (patch)
treeab171724845fe928ef05692c27351be933228ec2 /tests/Language/Haskell/Stylish/Tests/Util.hs
parentfd8bfa2853825504c2dbc7678154ac8d56d47035 (diff)
parent84770e33bb6286c163c3b2b10fa98d264f6672b8 (diff)
downloadstylish-haskell-3130faccf7c9a9a7697e246884e2b60fd4b1f9de.tar.gz
Merge tag 'v0.12.2.0'
v0.12.2.0 - 0.12.2.0 (2020-10-08) * align: Add a new option for aligning only adjacent items (by 1Computer1) * align: Add support for aligning MultiWayIf syntax (by 1Computer1) * data: Fix some issues with record field padding * module_header: Add separate_lists option * imports: Respect separate_lists for (..) imports * data: Make sorting deriving list optional (by Maxim Koltsov)
Diffstat (limited to 'tests/Language/Haskell/Stylish/Tests/Util.hs')
-rw-r--r--tests/Language/Haskell/Stylish/Tests/Util.hs61
1 files changed, 58 insertions, 3 deletions
diff --git a/tests/Language/Haskell/Stylish/Tests/Util.hs b/tests/Language/Haskell/Stylish/Tests/Util.hs
index f43b6b5..b3d200f 100644
--- a/tests/Language/Haskell/Stylish/Tests/Util.hs
+++ b/tests/Language/Haskell/Stylish/Tests/Util.hs
@@ -1,11 +1,21 @@
+{-# LANGUAGE BlockArguments #-}
+{-# LANGUAGE TypeFamilies #-}
module Language.Haskell.Stylish.Tests.Util
( testStep
+ , testStep'
+ , Snippet (..)
+ , testSnippet
+ , assertSnippet
, withTestDirTree
+ , (@=??)
) where
--------------------------------------------------------------------------------
import Control.Exception (bracket, try)
+import Control.Monad.Writer (execWriter, tell)
+import Data.List (intercalate)
+import GHC.Exts (IsList (..))
import System.Directory (createDirectory,
getCurrentDirectory,
getTemporaryDirectory,
@@ -14,6 +24,8 @@ import System.Directory (createDirectory,
import System.FilePath ((</>))
import System.IO.Error (isAlreadyExistsError)
import System.Random (randomIO)
+import Test.HUnit (Assertion, assertFailure,
+ (@=?))
--------------------------------------------------------------------------------
@@ -23,14 +35,45 @@ import Language.Haskell.Stylish.Step
--------------------------------------------------------------------------------
testStep :: Step -> String -> String
-testStep step str = case parseModule [] Nothing str of
- Left err -> error err
- Right module' -> unlines $ stepFilter step ls module'
+testStep s str = case s of
+ Step _ step ->
+ case parseModule [] Nothing str of
+ Left err -> error err
+ Right module' -> unlines $ step ls module'
where
ls = lines str
--------------------------------------------------------------------------------
+testStep' :: Step -> Lines -> Lines
+testStep' s ls = lines $ testStep s (unlines ls)
+
+
+--------------------------------------------------------------------------------
+-- | 'Lines' that show as a normal string.
+newtype Snippet = Snippet {unSnippet :: Lines} deriving (Eq)
+
+-- Prefix with one newline since so HUnit will use a newline after `got: ` or
+-- `expected: `.
+instance Show Snippet where show = unlines . ("" :) . unSnippet
+
+instance IsList Snippet where
+ type Item Snippet = String
+ fromList = Snippet
+ toList = unSnippet
+
+
+--------------------------------------------------------------------------------
+testSnippet :: Step -> Snippet -> Snippet
+testSnippet s = Snippet . lines . testStep s . unlines . unSnippet
+
+
+--------------------------------------------------------------------------------
+assertSnippet :: Step -> Snippet -> Snippet -> Assertion
+assertSnippet step input expected = expected @=? testSnippet step input
+
+
+--------------------------------------------------------------------------------
-- | Create a temporary directory with a randomised name built from the template
-- provided
createTempDirectory :: String -> IO FilePath
@@ -59,3 +102,15 @@ withTestDirTree action = bracket
setCurrentDirectory current *>
removeDirectoryRecursive temp)
(\(_, temp) -> setCurrentDirectory temp *> action)
+
+(@=??) :: Lines -> Lines -> Assertion
+expected @=?? actual =
+ if expected == actual then pure ()
+ else assertFailure $ intercalate "\n" $ execWriter do
+ tell ["Expected:"]
+ printLines expected
+ tell ["Got:"]
+ printLines actual
+ where
+ printLines =
+ mapM_ \line -> tell [" " <> line]