Skip to content

Commit

Permalink
Rename module
Browse files Browse the repository at this point in the history
  • Loading branch information
pbrisbin committed Jun 10, 2024
1 parent 838e55f commit 528c3e2
Show file tree
Hide file tree
Showing 4 changed files with 45 additions and 3 deletions.
2 changes: 1 addition & 1 deletion hspec-junit-formatter.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ library
Test.Hspec.JUnit
Test.Hspec.JUnit.Config
Test.Hspec.JUnit.Config.Env
Test.Hspec.JUnit.Format.V2
Test.Hspec.JUnit.Format
Test.Hspec.JUnit.Formatter
Test.Hspec.JUnit.Formatter.Env
Test.Hspec.JUnit.Render
Expand Down
42 changes: 42 additions & 0 deletions library/Test/Hspec/Api/Format/Compat.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,42 @@
{-# LANGUAGE CPP #-}

module Test.Hspec.Api.Format.Compat
( module Api
, reasonToText
) where

import Prelude

import Data.Maybe (fromMaybe)
import Data.Text (Text, pack, unpack)
import qualified Data.Text as T

#if MIN_VERSION_hspec_api(2,11,0)
import Test.Hspec.Api.Format.V2 as Api
#else
import Test.Hspec.Api.Format.V1 as Api
#endif

reasonToText :: FailureReason -> Text
reasonToText = \case
Error _ err -> pack $ show err
NoReason -> "no reason"
Reason err -> pack err
#if MIN_VERSION_hspec_api(2,11,0)
ColorizedReason err -> pack err
#endif
ExpectedButGot preface expected actual ->
T.unlines $
pack
<$> fromMaybe "" preface
: ( foundLines "expected" expected
<> foundLines " but got" actual
)

foundLines :: Show a => Text -> a -> [String]
foundLines msg found = case lines' of
[] -> []
first : rest ->
unpack (msg <> ": " <> first) : (unpack . (T.replicate 9 " " <>) <$> rest)
where
lines' = T.lines . pack $ show found
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Test.Hspec.JUnit.Format.V2
module Test.Hspec.JUnit.Format
( junit
) where

Expand Down
2 changes: 1 addition & 1 deletion library/Test/Hspec/JUnit/Formatter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ import qualified Test.Hspec.Core.Format as Core
import qualified Test.Hspec.Core.Formatters.V2 as V2
import Test.Hspec.Core.Runner as Core (Config (..))
import Test.Hspec.JUnit.Config
import Test.Hspec.JUnit.Format.V2
import Test.Hspec.JUnit.Format

-- | Register 'junit' as an available formatter and use it by default
use :: JUnitConfig -> SpecWith a -> SpecWith a
Expand Down

0 comments on commit 528c3e2

Please sign in to comment.