Merge remote-tracking branch 'origin/merge-requests/158'

This commit is contained in:
Julian Ospald 2021-08-29 17:43:01 +02:00
commit dda38ec52b
Signed by: hasufell
GPG Key ID: 3786C5262ECB4A3F
8 changed files with 15 additions and 25 deletions

View File

@ -50,7 +50,7 @@ instance Pretty NoCompatiblePlatform where
pPrint (NoCompatiblePlatform str') = pPrint (NoCompatiblePlatform str') =
text ("Could not find a compatible platform. Got: " ++ str') text ("Could not find a compatible platform. Got: " ++ str')
-- | Unable to find a download for the requested versio/distro. -- | Unable to find a download for the requested version/distro.
data NoDownload = NoDownload data NoDownload = NoDownload
deriving Show deriving Show

View File

@ -142,9 +142,7 @@ getLinuxDistro = do
| otherwise -> UnknownLinux | otherwise -> UnknownLinux
pure (distro, parsedVer) pure (distro, parsedVer)
where where
hasWord t matches = foldr (\x y -> match (regex x) (T.unpack t) || y) hasWord t = any (\x -> match (regex x) (T.unpack t))
False
matches
where where
regex x = makeRegexOpts compIgnoreCase execBlank ([s|\<|] ++ x ++ [s|\>|]) regex x = makeRegexOpts compIgnoreCase execBlank ([s|\<|] ++ x ++ [s|\>|])

View File

@ -152,7 +152,7 @@ data Tag = Latest
| Recommended | Recommended
| Prerelease | Prerelease
| Base PVP | Base PVP
| Old -- ^ old version are hidden by default in TUI | Old -- ^ old versions are hidden by default in TUI
| UnknownTag String -- ^ used for upwardscompat | UnknownTag String -- ^ used for upwardscompat
deriving (Ord, Eq, GHC.Generic, Show) -- FIXME: manual JSON instance deriving (Ord, Eq, GHC.Generic, Show) -- FIXME: manual JSON instance
@ -241,7 +241,7 @@ instance NFData LinuxDistro
distroToString :: LinuxDistro -> String distroToString :: LinuxDistro -> String
distroToString Debian = "debian" distroToString Debian = "debian"
distroToString Ubuntu = "ubuntu" distroToString Ubuntu = "ubuntu"
distroToString Mint= "mint" distroToString Mint = "mint"
distroToString Fedora = "fedora" distroToString Fedora = "fedora"
distroToString CentOS = "centos" distroToString CentOS = "centos"
distroToString RedHat = "redhat" distroToString RedHat = "redhat"

View File

@ -42,7 +42,7 @@ import qualified Text.Megaparsec as MP
import qualified Text.Megaparsec.Char as MPC import qualified Text.Megaparsec.Char as MPC
deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } { fieldLabelModifier = removeLensFieldLabel } ''Architecture deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''Architecture
deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''LinuxDistro deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''LinuxDistro
deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''VSep deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''VSep
deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''VUnit deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''VUnit

View File

@ -131,7 +131,7 @@ execLogged exe args chdir lfile env = do
pure e pure e
tee :: Fd -> Fd -> IO () tee :: Fd -> Fd -> IO ()
tee fileFd fdIn = readTilEOF lineAction fdIn tee fileFd = readTilEOF lineAction
where where
lineAction :: ByteString -> IO () lineAction :: ByteString -> IO ()

View File

@ -75,7 +75,6 @@ import qualified System.Win32.File as Win32
-- >>> import Data.ByteString.Internal (c2w, w2c) -- >>> import Data.ByteString.Internal (c2w, w2c)
-- >>> import Test.QuickCheck -- >>> import Test.QuickCheck
-- >>> import Data.Word8 -- >>> import Data.Word8
-- >>> import Data.Word8
-- >>> import qualified Data.Text as T -- >>> import qualified Data.Text as T
-- >>> instance Arbitrary T.Text where arbitrary = T.pack <$> arbitrary -- >>> instance Arbitrary T.Text where arbitrary = T.pack <$> arbitrary
@ -520,7 +519,7 @@ forFold :: (Foldable t, Applicative m, Monoid b) => t a -> (a -> m b) -> m b
forFold = \t -> (`traverseFold` t) forFold = \t -> (`traverseFold` t)
-- | Strip @\\r@ and @\\n@ from 'ByteString's -- | Strip @\\r@ and @\\n@ from 'String's
-- --
-- >>> stripNewline "foo\n\n\n" -- >>> stripNewline "foo\n\n\n"
-- "foo" -- "foo"
@ -532,13 +531,10 @@ forFold = \t -> (`traverseFold` t)
-- prop> \t -> stripNewline (t <> "\n") === stripNewline t -- prop> \t -> stripNewline (t <> "\n") === stripNewline t
-- prop> \t -> not (any (isNewLine . c2w) t) ==> stripNewline t == t -- prop> \t -> not (any (isNewLine . c2w) t) ==> stripNewline t == t
stripNewline :: String -> String stripNewline :: String -> String
stripNewline s stripNewline = filter (`notElem` "\n\r")
| null s = []
| head s `elem` "\n\r" = stripNewline (tail s)
| otherwise = head s : stripNewline (tail s)
-- | Strip @\\r@ and @\\n@ from 'ByteString's -- | Strip @\\r@ and @\\n@ from 'Text's
-- --
-- >>> stripNewline' "foo\n\n\n" -- >>> stripNewline' "foo\n\n\n"
-- "foo" -- "foo"
@ -550,10 +546,7 @@ stripNewline s
-- prop> \t -> stripNewline' (t <> "\n") === stripNewline' t -- prop> \t -> stripNewline' (t <> "\n") === stripNewline' t
-- prop> \t -> not (T.any (isNewLine . c2w) t) ==> stripNewline' t == t -- prop> \t -> not (T.any (isNewLine . c2w) t) ==> stripNewline' t == t
stripNewline' :: T.Text -> T.Text stripNewline' :: T.Text -> T.Text
stripNewline' s stripNewline' = T.filter (`notElem` "\n\r")
| T.null s = mempty
| T.head s `elem` "\n\r" = stripNewline' (T.tail s)
| otherwise = T.singleton (T.head s) <> stripNewline' (T.tail s)
-- | Is the word8 a newline? -- | Is the word8 a newline?

View File

@ -44,15 +44,14 @@ import Language.Haskell.TH.Quote
-- The pattern portion is undefined. -- The pattern portion is undefined.
s :: QuasiQuoter s :: QuasiQuoter
s = QuasiQuoter s = QuasiQuoter
(\s' -> case and $ fmap isAscii s' of (\s' -> case all isAscii s' of
True -> (\a -> [|fromString a|]) . trimLeadingNewline . removeCRs $ s' True -> (\a -> [|fromString a|]) . trimLeadingNewline . removeCRs $ s'
False -> fail "Not ascii" False -> fail "Not ascii"
) )
(error "Cannot use q as a pattern") (error "Cannot use s as a pattern")
(error "Cannot use q as a type") (error "Cannot use s as a type")
(error "Cannot use q as a dec") (error "Cannot use s as a dec")
where where
removeCRs = filter (/= '\r') removeCRs = filter (/= '\r')
trimLeadingNewline ('\n' : xs) = xs trimLeadingNewline ('\n' : xs) = xs
trimLeadingNewline xs = xs trimLeadingNewline xs = xs

View File

@ -66,7 +66,7 @@ instance Arbitrary ByteString where
--------------------- ---------------------
instance Arbitrary Scheme where instance Arbitrary Scheme where
arbitrary = oneof [ pure (Scheme "http"), pure (Scheme "https") ] arbitrary = elements [ Scheme "http", Scheme "https" ]
instance Arbitrary Host where instance Arbitrary Host where
arbitrary = genericArbitrary arbitrary = genericArbitrary