File: WithCliSpec.hs

package info (click to toggle)
haskell-getopt-generics 0.13.1.0-2
  • links: PTS
  • area: main
  • in suites: forky, sid, trixie
  • size: 260 kB
  • sloc: haskell: 1,644; makefile: 6
file content (98 lines) | stat: -rw-r--r-- 3,705 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
{-# LANGUAGE DeriveGeneric #-}

module WithCliSpec where

import           System.Environment
import           System.Exit
import           System.IO
import           System.IO.Silently
import           Test.Hspec

import           WithCli

data Foo
  = Foo {
    bar :: Maybe Int,
    baz :: String,
    bool :: Bool
  }
  deriving (Eq, Show, Generic)

instance HasArguments Foo

spec :: Spec
spec = do
  describe "withCli" $ do
    context "no arguments" $ do
      it "executes the operation in case of no command line arguments" $ do
        let main :: IO ()
            main = putStrLn "success"
        (capture_ $ withArgs [] $ withCli main)
          `shouldReturn` "success\n"

      it "produces nice error messages" $ do
        let main :: IO ()
            main = putStrLn "success"
        output <- hCapture_ [stderr] (withArgs ["foo"] (withCli main) `shouldThrow` (== ExitFailure 1))
        output `shouldBe` "unknown argument: foo\n"

    context "1 argument" $ do
      it "parses Ints" $ do
        let main :: Int -> IO ()
            main n = putStrLn ("success: " ++ show n)
        (capture_ $ withArgs ["12"] $ withCli main)
          `shouldReturn` "success: 12\n"

      it "error parsing" $ do
        let main :: Int -> IO ()
            main n = putStrLn ("error: " ++ show n)
        output <- hCapture_ [stderr] (withArgs (words "12 foo") (withCli main)
          `shouldThrow` (== ExitFailure 1))
        output `shouldBe` "unknown argument: foo\n"

      context "record types" $ do
        it "parses command line arguments" $ do
          withArgs (words "--bar 4 --baz foo") $
            withCli $ \ foo -> do
              foo `shouldBe` Foo (Just 4) "foo" False

    context "optional positional arguments with Maybe" $ do
      it "allows optional positional arguments" $ do
        let main :: Maybe Int -> IO ()
            main = print
        (capture_ $ withCli main)
          `shouldReturn` "Nothing\n"
        (capture_ $ withArgs ["23"] $ withCli main)
          `shouldReturn` "Just 23\n"

      it "allows multiple optional positional arguments" $ do
        let main :: Maybe Int -> Maybe String -> IO ()
            main i s = print (i, s)
        (capture_ $ withCli main)
          `shouldReturn` "(Nothing,Nothing)\n"
        (capture_ $ withArgs ["23"] $ withCli main)
          `shouldReturn` "(Just 23,Nothing)\n"
        (capture_ $ withArgs ["23", "foo"] $ withCli main)
          `shouldReturn` "(Just 23,Just \"foo\")\n"

      it "allows optional positional arguments after non-optional arguments" $ do
        let main :: Int -> Maybe String -> IO ()
            main i s = print (i, s)
        (hCapture_ [stderr] $ withCli main `shouldThrow` (== ExitFailure 1))
          `shouldReturn` "missing argument of type INTEGER\n"
        (capture_ $ withArgs ["23"] $ withCli main)
          `shouldReturn` "(23,Nothing)\n"
        (capture_ $ withArgs ["23", "foo"] $ withCli main)
          `shouldReturn` "(23,Just \"foo\")\n"

      it "disallows optional positional arguments before non-optional ones with a proper error message" $ do
        let main :: Maybe Int -> String -> IO ()
            main = error "main"
        hCapture_ [stderr] (withCli main `shouldThrow` (== ExitFailure 1))
          `shouldReturn` "cannot use Maybes for optional arguments before any non-optional arguments\n"

      it "shows optional arguments with nested square brackets in help output" $ do
        let main :: Int -> Maybe String -> Maybe String -> IO ()
            main = error "main"
        output <- capture_ (withArgs ["-h"] (withCli main) `shouldThrow` (== ExitSuccess))
        output `shouldContain` "[OPTIONS] INTEGER [STRING [STRING]]"