Skip to content

Commit

Permalink
Remove restrictions against doing TUI stuff on windows
Browse files Browse the repository at this point in the history
  • Loading branch information
thomasjm committed Nov 18, 2023
1 parent ff277e8 commit 8fb2ca3
Show file tree
Hide file tree
Showing 6 changed files with 3 additions and 50 deletions.
6 changes: 0 additions & 6 deletions demos/demo-custom-exceptions/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,14 +3,9 @@
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE CPP #-}

module Main where

#ifdef mingw32_HOST_OS
main :: IO ()
main = putStrLn "Demo not enabled on Windows."
#else
import Brick
import Control.Exception
import Control.Monad.IO.Class
Expand Down Expand Up @@ -60,4 +55,3 @@ testOptions = defaultOptions {

main :: IO ()
main = runSandwich testOptions customExceptionsDemo
#endif
7 changes: 0 additions & 7 deletions demos/demo-tui/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,14 +2,9 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE CPP #-}

module Main where

#ifdef mingw32_HOST_OS
main :: IO ()
main = putStrLn "Demo not enabled on Windows."
#else
import Common
import Control.Concurrent
import Control.Monad.IO.Class
Expand Down Expand Up @@ -40,5 +35,3 @@ testOptions = defaultOptions {

main :: IO ()
main = runSandwichWithCommandLineArgs testOptions simple

#endif
11 changes: 1 addition & 10 deletions sandwich-slack/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,10 +10,7 @@ import GHC.Stack
import Test.Sandwich
import Test.Sandwich.Formatters.Print
import Test.Sandwich.Formatters.Slack

#ifndef mingw32_HOST_OS
import Test.Sandwich.Formatters.TerminalUI
#endif


simple :: TopSpec
Expand Down Expand Up @@ -42,18 +39,12 @@ slackFormatter = defaultSlackFormatter {
, slackFormatterVisibilityThreshold = Just 50
}

#ifndef mingw32_HOST_OS
baseFormatter = SomeFormatter defaultTerminalUIFormatter
#else
baseFormatter = SomeFormatter defaultPrintFormatter
#endif

main :: IO ()
main = runSandwich options simple
where
options = defaultOptions {
optionsTestArtifactsDirectory = TestArtifactsGeneratedDirectory "test_runs" (show <$> getCurrentTime)
, optionsFormatters = [baseFormatter, SomeFormatter slackFormatter]
, optionsFormatters = [SomeFormatter defaultTerminalUIFormatter, SomeFormatter slackFormatter]
}

-- * Util
Expand Down
3 changes: 0 additions & 3 deletions sandwich/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,10 +15,7 @@ import Test.Sandwich
import Test.Sandwich.Formatters.FailureReport
import Test.Sandwich.Formatters.LogSaver
import Test.Sandwich.Formatters.Print

#ifndef mingw32_HOST_OS
import Test.Sandwich.Formatters.TerminalUI
#endif


data Database = Database String
Expand Down
20 changes: 2 additions & 18 deletions sandwich/src/Test/Sandwich/ArgParsing.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,17 +19,14 @@ import Test.Sandwich.Formatters.FailureReport
import Test.Sandwich.Formatters.MarkdownSummary
import Test.Sandwich.Formatters.Print.Types
import Test.Sandwich.Formatters.Silent
import Test.Sandwich.Formatters.TerminalUI
import Test.Sandwich.Formatters.TerminalUI.Types
import Test.Sandwich.Internal.Running
import Test.Sandwich.Options
import Test.Sandwich.Types.ArgParsing
import Test.Sandwich.Types.RunTree
import Test.Sandwich.Types.Spec

#ifndef mingw32_HOST_OS
import Test.Sandwich.Formatters.TerminalUI
import Test.Sandwich.Formatters.TerminalUI.Types
#endif

#if MIN_VERSION_time(1,9,0)
import Data.Time.Format.ISO8601
formatTime = T.unpack . T.replace ":" "_" . T.pack . iso8601Show
Expand Down Expand Up @@ -115,9 +112,7 @@ formatter :: Parser FormatterType
formatter =
flag' Print (long "print" <> help "Print to stdout")
<|> flag' PrintFailures (long "print-failures" <> help "Print failures only to stdout")
#ifndef mingw32_HOST_OS
<|> flag' TUI (long "tui" <> help "Open terminal UI app")
#endif
<|> flag' Silent (long "silent" <> help "Run silently (print the run root only)")
<|> flag Auto Auto (long "auto" <> help "Automatically decide which formatter to use")

Expand Down Expand Up @@ -248,11 +243,9 @@ addOptionsFromArgs baseOptions (CommandLineOptions {..}) = do
-- you end up with no output and a hanging process (until you hit 'q'; stdin is still attached).
-- Seems like the best default is just the print formatter.
printFormatter
#ifndef mingw32_HOST_OS
(_, TUI) ->
let mainTerminalUiFormatter = headMay [x | SomeFormatter (cast -> Just x@(TerminalUIFormatter {})) <- optionsFormatters baseOptions]
in SomeFormatter $ (fromMaybe defaultTerminalUIFormatter mainTerminalUiFormatter) { terminalUILogLevel = optLogLevel }
#endif
(_, Print) -> printFormatter
(_, PrintFailures) -> failureReportFormatter
(_, Silent) -> silentFormatter
Expand Down Expand Up @@ -285,27 +278,18 @@ addOptionsFromArgs baseOptions (CommandLineOptions {..}) = do
isMainFormatter :: SomeFormatter -> Bool
isMainFormatter (SomeFormatter x) = case cast x of
Just (_ :: PrintFormatter) -> True
#ifdef mingw32_HOST_OS
Nothing -> False
#else
Nothing -> case cast x of
Just (_ :: TerminalUIFormatter) -> True
Nothing -> False
#endif

setVisibilityThreshold Nothing x = x
setVisibilityThreshold (Just v) x@(SomeFormatter f) = case cast f of
Just pf@(PrintFormatter {}) -> SomeFormatter (pf { printFormatterVisibilityThreshold = v })
Nothing -> case cast f of
#ifdef mingw32_HOST_OS
Just (frf :: FailureReportFormatter) -> SomeFormatter (frf { failureReportVisibilityThreshold = v })
Nothing -> x
#else
Just tuif@(TerminalUIFormatter {}) -> SomeFormatter (tuif { terminalUIVisibilityThreshold = v })
Nothing -> case cast f of
Just (frf :: FailureReportFormatter) -> SomeFormatter (frf { failureReportVisibilityThreshold = v })
Nothing -> x
#endif

isMarkdownSummaryFormatter :: SomeFormatter -> Bool
isMarkdownSummaryFormatter (SomeFormatter x) = case cast x of
Expand Down
6 changes: 0 additions & 6 deletions sandwich/src/Test/Sandwich/Types/ArgParsing.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,27 +11,21 @@ import GHC.Int

data FormatterType =
Print
#ifndef mingw32_HOST_OS
| TUI
#endif
| PrintFailures
| Auto
| Silent

instance Show FormatterType where
show Print = "print"
show PrintFailures = "print-failures"
#ifndef mingw32_HOST_OS
show TUI = "tui"
#endif
show Auto = "auto"
show Silent = "silent"

instance Read FormatterType where
readsPrec _ "print" = [(Print, "")]
#ifndef mingw32_HOST_OS
readsPrec _ "tui" = [(TUI, "")]
#endif
readsPrec _ "auto" = [(Auto, "")]
readsPrec _ "silent" = [(Silent, "")]
readsPrec _ _ = []
Expand Down

0 comments on commit 8fb2ca3

Please sign in to comment.