Skip to content

Commit d268f12

Browse files
authored
Merge pull request commercialhaskell#6669 from commercialhaskell/fix6665
Fix commercialhaskell#6665 Avoid partial functions
2 parents 06a1d16 + 833752e commit d268f12

File tree

1 file changed

+45
-23
lines changed

1 file changed

+45
-23
lines changed

tests/unit/Stack/ArgsSpec.hs

Lines changed: 45 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
1-
{-# OPTIONS_GHC -Wno-x-partial #-}
21
{-# LANGUAGE NoImplicitPrelude #-}
2+
{-# LANGUAGE OverloadedLists #-}
33

44
-- | Args parser test suite.
55

@@ -13,8 +13,8 @@ module Stack.ArgsSpec
1313
import Data.Attoparsec.Args ( EscapingMode (..), parseArgsFromString )
1414
import Data.Attoparsec.Interpreter ( interpreterArgsParser )
1515
import qualified Data.Attoparsec.Text as P
16+
import qualified Data.List.NonEmpty as NE
1617
import Data.Text ( pack )
17-
import Prelude ( head )
1818
import Stack.Constants ( stackProgName )
1919
import Stack.Prelude
2020
import Test.Hspec ( Spec, describe, it )
@@ -76,10 +76,10 @@ interpreterArgsSpec =
7676
describe "Failure cases" $ do
7777
checkFailures
7878
describe "Bare directives in literate files" $ do
79-
forM_ (interpreterGenValid lineComment []) $
80-
testAndCheck (acceptFailure True) []
81-
forM_ (interpreterGenValid blockComment []) $
82-
testAndCheck (acceptFailure True) []
79+
forM_ (interpreterGenValid lineComment "") $
80+
testAndCheck (acceptFailure True) ""
81+
forM_ (interpreterGenValid blockComment "") $
82+
testAndCheck (acceptFailure True) ""
8383
where
8484
parse isLiterate s =
8585
P.parseOnly (interpreterArgsParser isLiterate stackProgName) (pack s)
@@ -116,60 +116,82 @@ interpreterArgsSpec =
116116
(testAndCheck (acceptFailure False) "unused")
117117

118118
-- Generate a set of acceptable inputs for given format and args
119+
interpreterGenValid ::
120+
(String -> NonEmpty String)
121+
-> String
122+
-> NonEmpty String
119123
interpreterGenValid fmt args = shebang <++> newLine <++> fmt args
120124

121-
interpreterGenInvalid :: [String]
125+
interpreterGenInvalid :: NonEmpty String
122126
-- Generate a set of Invalid inputs
123127
interpreterGenInvalid =
124128
["-stack\n"] -- random input
125129
-- just the shebang
126-
<|> shebang <++> ["\n"]
130+
<> shebang <++> ["\n"]
127131
-- invalid shebang
128-
<|> blockSpace <++> [head (interpreterGenValid lineComment args)]
132+
<> blockSpace <++> [NE.head (interpreterGenValid lineComment args)]
129133
-- something between shebang and Stack comment
130-
<|> shebang
134+
<> shebang
131135
<++> newLine
132136
<++> blockSpace
133-
<++> ([head (lineComment args)] <|> [head (blockComment args)])
137+
<++> ([NE.head (lineComment args)] <> [NE.head (blockComment args)])
134138
-- unterminated block comment
135139
-- just chop the closing chars from a valid block comment
136-
<|> shebang
140+
<> shebang
137141
<++> ["\n"]
138-
<++> let c = head (blockComment args)
142+
<++> let c = NE.head (blockComment args)
139143
l = length c - 2
140144
in [assert (drop l c == "-}") (take l c)]
141145
-- nested block comment
142-
<|> shebang
146+
<> shebang
143147
<++> ["\n"]
144-
<++> [head (blockComment "--x {- nested -} --y")]
148+
<++> [NE.head (blockComment "--x {- nested -} --y")]
145149
where
146150
args = " --x --y"
147-
(<++>) = liftA2 (++)
151+
(<++>) = liftA2 (<>)
148152

149153
-- Generative grammar for the interpreter comments
154+
shebang :: NonEmpty String
150155
shebang = ["#!/usr/bin/env stack"]
151-
newLine = ["\n"] <|> ["\r\n"]
156+
157+
newLine :: NonEmpty String
158+
newLine = ["\n"] <> ["\r\n"]
152159

153160
-- A comment may be the last line or followed by something else
154-
postComment = [""] <|> newLine
161+
postComment :: NonEmpty String
162+
postComment = [""] <> newLine
155163

156164
-- A command starts with zero or more whitespace followed by "stack"
165+
makeComment ::
166+
(String -> String)
167+
-> NonEmpty String
168+
-> String
169+
-> NonEmpty String
157170
makeComment maker space args =
158-
let makePrefix s = (s <|> [""]) <++> [stackProgName]
159-
in (maker <$> (makePrefix space <++> [args])) <++> postComment
171+
let makePrefix :: NonEmpty String -> NonEmpty String
172+
makePrefix s = (s <> [""]) <++> [stackProgName]
173+
in (maker <$> (makePrefix space <&> (++ args))) <++> postComment
174+
175+
lineSpace :: NonEmpty String
176+
lineSpace = [" "] <> ["\t"]
160177

161-
lineSpace = [" "] <|> ["\t"]
178+
lineComment :: String -> NonEmpty String
162179
lineComment = makeComment makeLine lineSpace
163180
where
164181
makeLine s = "--" ++ s
165182

183+
literateLineComment :: String -> NonEmpty String
166184
literateLineComment = makeComment ("> --" ++) lineSpace
167185

168-
blockSpace = lineSpace <|> newLine
186+
blockSpace :: NonEmpty String
187+
blockSpace = lineSpace <> newLine
188+
189+
blockComment :: String -> NonEmpty String
169190
blockComment = makeComment makeBlock blockSpace
170191
where
171192
makeBlock s = "{-" ++ s ++ "-}"
172193

194+
literateBlockComment :: String -> NonEmpty String
173195
literateBlockComment = makeComment
174196
(\s -> "> {-" ++ s ++ "-}")
175-
(lineSpace <|> map (++ ">") newLine)
197+
(lineSpace <> NE.map (++ ">") newLine)

0 commit comments

Comments
 (0)