File: Spec.hs

package info (click to toggle)
haskell-shell-conduit 5.0.0-3
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 116 kB
  • sloc: haskell: 607; makefile: 6
file content (137 lines) | stat: -rw-r--r-- 5,583 bytes parent folder | download | duplicates (4)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
{-# LANGUAGE ExtendedDefaultRules #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE CPP #-}

import Test.Hspec
import Data.Conduit.Shell hiding (ignore) -- https://github.com/fpco/stackage/issues/2355#issue-212177275
import Data.Conduit.Shell.PATH (true, false)
import Data.Conduit.Shell.Segments (strings, ignore)
import qualified Data.Conduit.List as CL
import qualified Data.Conduit.Binary as CB
import qualified Data.ByteString.Char8 as S8
import Control.Applicative
import Data.ByteString
import Data.Char (toUpper)
import Data.Either (isRight, isLeft)
import Control.Exception (try)

main :: IO ()
main =
  hspec $
  do describe "SHELL path functions" $
       do it "false" $
            do val <- run $ strings (false <|> echo "failed")
               val `shouldBe` ["failed"]
          it "true" $
            do val <- run $ strings (true <|> echo "passed")
               val `shouldBe` []
     describe "ls" $
       do it "home directory check" $
            do val <- run $ strings (ls "/")
               val `shouldContain` ["home"]
          it "long option" $
            do val <- run $ strings (ls "-a" ["/"])
               val `shouldContain` ["home"]
     describe "multiple string usage" $
       do it "make two directory" $
            do val <-
                 run $
                 do ignore $ mkdir "-p" "mtest1" "mtest2" "mtest3"
                    strings $ ls "."
               run $ rmdir ["mtest1", "mtest2", "mtest3"]
               val `shouldContain` ["mtest1", "mtest2", "mtest3"]
     describe "list usage in variadic" $
       do it "two directory" $
            do val <-
                 run $
                 do ignore $ mkdir "-p" ["test1", "test2"]
                    strings $ ls "."
               run $ rmdir ["test1", "test2"]
               val `shouldContain` ["test1", "test2"]
     describe "shell calls" $
       do it "shell ls" $
            do val <- run $ do strings $ shell "ls /"
               val `shouldContain` ["home"]
     describe "ordering of arguments" $
       do it "echo -e" $
            do val <- run $ do strings $ echo "-e" "hello\n" "haskell"
#ifdef darwin_HOST_OS
               val `shouldBe` ["-e hello", " haskell"]
#else
               val `shouldBe` ["hello", " haskell"]
#endif
          it "mixed variant" $
            do val <- run $ strings $ echo "-e" ["hello\n", "haskell"]
#ifdef darwin_HOST_OS
               val `shouldBe` ["-e hello", " haskell"]
#else
               val `shouldBe` ["hello", " haskell"]
#endif
          it "list variant" $
            do val <- run $ strings $ echo ["-e", "hello\n", "haskell"]
#ifdef darwin_HOST_OS
               val `shouldBe` ["-e hello", " haskell"]
#else
               val `shouldBe` ["hello", " haskell"]
#endif
          it "list mixed variant - 1" $
            do val <- run $ strings $ echo "-e" ["hello\n", "haskell"]
#ifdef darwin_HOST_OS
               val `shouldBe` ["-e hello", " haskell"]
#else
               val `shouldBe` ["hello", " haskell"]
#endif
          it "list mixed variant - 2" $
            do val <- run $ strings $ echo "-e" ["hello\n", "haskell\n"] "world"
#ifdef darwin_HOST_OS
               val `shouldBe` ["-e hello", " haskell", " world"]
#else
               val `shouldBe` ["hello", " haskell", " world"]
#endif
          it "list mixed variant - 3" $
            do val <- run $ strings $ echo "-e" ["hello\n", "haskell\n"] "world\n" ["planet"]
#ifdef darwin_HOST_OS
               val `shouldBe` ["-e hello", " haskell", " world", " planet"]
#else
               val `shouldBe` ["hello", " haskell", " world", " planet"]
#endif
     describe "cd" $
       do it "cd /" $
            do val <-
                 run $
                 do ignore $ cd "/"
                    strings pwd
               val `shouldBe` ["/"]
          it "cd /home" $
            do val <-
                 run $
                 do ignore $ cd ["/home", undefined]
                    strings pwd
               val `shouldBe` ["/home"]
     describe "Piping" $
       do it "basic piping" $
            do (val :: [String]) <-
                 run $ strings (echo "hello" $| conduit (CL.map (S8.map toUpper)))
               val `shouldBe` ["HELLO"]
          it "piping of commands - example 1" $
             do val <- run $ strings (ls "/" $| grep "etc")
                val `shouldBe` ["etc"]
          it "piping of commands - example 2" $
             do val <- run $ strings (echo "hello" $| tr "[a-z]" "[A-Z]")
                val `shouldBe` ["HELLO"]
     describe "Exception" $
       do it "Basic exception handling - success" $
            do (val :: Either ProcessException () ) <- try $ run (ls "/bin")
               val `shouldSatisfy` isRight
          it "Basic exception handling - failure" $
            do (val :: Either ProcessException () ) <- try $ run (ls "/non_existent_directory")
               val `shouldSatisfy` isLeft
          it "Basic exception handling with <|> - success" $
            do (val :: Either ProcessException () ) <- try $ run (ls "/non_existent_directory" <|> ls "/bin")
               val `shouldSatisfy` isRight
          it "Basic exception handling with <|> - failure" $
            do (val :: Either ProcessException () ) <- try $ run (ls "/non_existent_directory" <|> ls "/non_existent_directory")
               val `shouldSatisfy` isLeft
          it "Basic exception handling with <|> - first success" $
            do (val :: Either ProcessException () ) <- try $ run (ls "/bin" <|> ls "/non_existent_directory")
               val `shouldSatisfy` isRight