{-# LANGUAGE BlockArguments #-} {-# LANGUAGE PartialTypeSignatures #-} {-# LANGUAGE QuasiQuotes #-} module Main (main) where import Control.Monad.Reader import Data.ByteString.Char8 qualified as B import Data.ByteString.Lazy.Char8 qualified as LB import Data.Text qualified as T import Data.Text.Lazy qualified as LT import Process.Shell import Test.Hspec main :: IO () main = hspec do describe "output" do it "capture stdout" do (`shouldBe` "stdout") . fst @String @String =<< [sh|echo -n stdout|] it "capture stderr" do (`shouldBe` "stderr") . snd @String =<< [sh|>&2 echo -n stderr|] it "capture stdout and stderr interleaved" do (`shouldBe` ("stdout", "stderr")) =<< [sh| echo -n stdout >&2 echo -n stderr |] it "capture interleaved" do (`shouldBe` "stdout\nstderr\n") =<< [sh| echo stdout >&2 echo stderr |] describe "arguments" do it "passes `Int`" do (`shouldBe` "1") =<< let x = 1 :: Int in [sh|echo -n '#{x}'|] it "passes `Text`" do (`shouldBe` "foobar") =<< let x = T.pack "foobar" in [sh|echo -n '#{x}'|] (`shouldBe` "foobar") =<< let x = LT.pack "foobar" in [sh|echo -n '#{x}'|] it "passes `ByteString`" do (`shouldBe` "foobar") =<< let x = B.pack "foobar" in [sh|echo -n '#{x}'|] (`shouldBe` "foobar") =<< let x = LB.pack "foobar" in [sh|echo -n '#{x}'|] it "interpolates expressions" do (`shouldBe` "1") =<< let x = 1 :: Int in [sh|echo -n '#{show x}'|] it "interpolates monadic expressions" do (`shouldBe` "1") =<< let x = 1 :: Int in [sh|echo -n '#{{pure @IO x}}'|] it "interpolates monadic expressions" do (`shouldBe` "1") =<< runReaderT [sh|echo -n '#{{asks fst}}'|] (1 :: Int, 2 :: Int) it "preserves argument order" do (`shouldBe` "1 2") =<< let x = "1"; y = "2" in [sh|echo -n '#{x}' '#{y}'|] describe "quoting" do it "preserves arguments" do (`shouldBe` "foo\\ bar") =<< let x = "foo bar" in [sh|printf %q '#{x}'|] it "preserves special characters" do (`shouldBe` "foo\\ bar") =<< let x = "$foo $bar" in [sh|foo=foo; bar=bar; ( printf %q #{x} )|] it "escapes special characters" do (`shouldBe` "\\$foo\\ \\$bar") =<< let x = "$foo $bar" in [sh|foo=foo; bar=bar; ( printf %q '#{x}' )|] it "preserves empty arguments" do (`shouldBe` "''") =<< let x = "" in [sh|printf %q #{x}|] (`shouldBe` "''") =<< let x = "" in [sh|printf %q '#{x}'|] describe "parsing" do it "parses shell quotes" do (`shouldBe` "foobar") =<< [sh|echo -n 'foobar'|] it "parses double cross" do (`shouldBe` "0") =<< [sh|echo -n $#|]