Skip to content

Commit

Permalink
Try allowing RawImage stuff on Windows
Browse files Browse the repository at this point in the history
  • Loading branch information
thomasjm committed Nov 18, 2023
1 parent f11b81a commit 815f553
Show file tree
Hide file tree
Showing 3 changed files with 1 addition and 13 deletions.
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}

module Test.Sandwich.Formatters.Slack.Internal.Markdown where

Expand All @@ -13,9 +12,7 @@ import Test.Sandwich.Formatters.Slack.Internal.Types

toMarkdown :: FailureReason -> T.Text
toMarkdown (Reason {..}) = T.pack failureReason
#ifndef mingw32_HOST_OS
toMarkdown (RawImage {..}) = T.pack failureFallback
#endif
toMarkdown (ChildrenFailed {failureNumChildren=n}) = [i|#{n} #{if n == 1 then ("child" :: T.Text) else "children"} failed|]
toMarkdown (ExpectedButGot {..}) = [i|Expected *#{failureValue1}* but got *#{failureValue2}*|]
toMarkdown (DidNotExpectButGot {..}) = [i|Did not expect *#{failureValue1}*|]
Expand Down
3 changes: 0 additions & 3 deletions sandwich/src/Test/Sandwich/Formatters/Print/FailureReason.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@

-- | Pretty printing failure reasons


module Test.Sandwich.Formatters.Print.FailureReason (
printFailureReason
) where
Expand All @@ -28,10 +27,8 @@ import Control.Monad
printFailureReason :: FailureReason -> ReaderT (PrintFormatter, Int, Handle) IO ()
printFailureReason (Reason _ s) = do
printShowBoxPrettyWithTitleString "Reason: " s
#ifndef mingw32_HOST_OS
printFailureReason (RawImage _ fallback _image) = do
forM_ (L.lines fallback) pin
#endif
printFailureReason (ChildrenFailed _ n) = do
picn midWhite ([i|#{n} #{if n == 1 then ("child" :: String) else "children"} failed|] :: String)
printFailureReason (ExpectedButGot _ seb1 seb2) = do
Expand Down
8 changes: 1 addition & 7 deletions sandwich/src/Test/Sandwich/Types/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,11 +32,8 @@ import Data.Maybe
import Data.String.Interpolate
import GHC.Stack
import GHC.TypeLits
import Safe

#ifndef mingw32_HOST_OS
import Graphics.Vty.Image (Image)
#endif
import Safe

#if !MIN_VERSION_base(4,13,0)
import Control.Monad.Fail
Expand Down Expand Up @@ -105,12 +102,9 @@ data FailureReason = Reason { failureCallStack :: Maybe CallStack
, failureAsyncException :: SomeAsyncExceptionWithEq }
| ChildrenFailed { failureCallStack :: Maybe CallStack
, failureNumChildren :: Int }
#ifndef mingw32_HOST_OS
| RawImage { failureCallStack :: Maybe CallStack
, failureFallback :: String
, failureRawImage :: Image }
#endif

deriving (Show, Typeable, Eq)

instance Exception FailureReason
Expand Down

0 comments on commit 815f553

Please sign in to comment.