Skip to content
Snippets Groups Projects
Verified Commit 20c6bb6a authored by Brandon S. Allbery's avatar Brandon S. Allbery
Browse files

avoid invalid filepaths on Windows

parent 6946384e
No related branches found
No related tags found
No related merge requests found
......@@ -5,8 +5,8 @@ module Test.QuickCheck.Instances.Cabal () where
import Control.Applicative (liftA2)
import Data.Bits (shiftR)
import Data.Char (isAlphaNum, isDigit)
import Data.List (intercalate)
import Data.Char (isAlphaNum, isDigit, toLower)
import Data.List (intercalate, isPrefixOf, isInfixOf)
import Data.List.NonEmpty (NonEmpty (..))
import Distribution.Utils.Generic (lowercase)
import Test.QuickCheck
......@@ -503,14 +503,25 @@ shortListOf1 bound gen = sized $ \n -> do
vectorOf k gen
arbitraryShortToken :: Gen String
arbitraryShortToken = arbitraryShortStringWithout "{}[]"
arbitraryShortToken = arbitraryShortStringWithout "{}[]" (const True)
arbitraryShortPath :: Gen String
arbitraryShortPath = arbitraryShortStringWithout "{}[],"
arbitraryShortStringWithout :: String -> Gen String
arbitraryShortStringWithout excludeChars =
shortListOf1 5 $ elements [c | c <- ['#' .. '~' ], c `notElem` excludeChars ]
arbitraryShortPath = arbitraryShortStringWithout "{}[],<>:|*?" (not . winDevice)
where
devices = ["con", "aux", "prn", "com", "lpt", "nul"]
winDevice :: String -> Bool
winDevice p = let p' = map toLower p in any (isDev p') devices
isDev :: String -> String -> Bool
isDev p s = s `isPrefixOf` p || ('\\' : s) `isInfixOf` p
arbitraryShortStringWithout :: String -> (String -> Bool) -> Gen String
arbitraryShortStringWithout excludeChars validp =
shortListOf1 5 $ elements (str 5)
where
str :: Int -> String
str 0 = error "could not generate valid string"
str n = let s = [c | c <- ['#' .. '~' ], c `notElem` excludeChars ]
in if validp s then s else str (n - 1)
-- |
intSqrt :: Int -> Int
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment