fix warnings

This commit is contained in:
Ryan Mulligan 2023-01-01 15:30:30 -08:00
parent da82da1b5d
commit 121ddb518c
9 changed files with 16 additions and 20 deletions

View File

@ -23,6 +23,7 @@ import Data.Aeson
(.!=),
(.:),
(.:!),
Key,
)
import Data.Aeson.Types (Parser, prependFailure)
import qualified Data.ByteString.Lazy.Char8 as BSL
@ -289,13 +290,13 @@ cpeMatches = concatMap rows
where
rows cve = fmap (CPEMatchRow cve) (cveCPEMatches cve)
guardAttr :: (Eq a, FromJSON a, Show a) => Object -> Text -> a -> Parser ()
guardAttr :: (Eq a, FromJSON a, Show a) => Object -> Key -> a -> Parser ()
guardAttr object attribute expected = do
actual <- object .: attribute
unless (actual == expected) $
fail $
"unexpected "
<> T.unpack attribute
<> show attribute
<> ", expected "
<> show expected
<> ", got "

View File

@ -18,7 +18,7 @@ import qualified Data.Text as T
import qualified Data.Text.IO as T
import Language.Haskell.TH.Env (envQ)
import OurPrelude
import System.Exit
import System.Exit()
import Text.Regex.Applicative.Text (RE', (=~))
import qualified Text.Regex.Applicative.Text as RE
import Utils (UpdateEnv (..), nixBuildOptions)

View File

@ -187,7 +187,7 @@ checkExistingUpdatePR env attrPath = do
searchResult <-
ExceptT $
liftIO $
GH.github (authFrom env) (GH.searchIssuesR search)
(GH.github (authFrom env) (GH.searchIssuesR search) GH.FetchAll)
& fmap (first (T.pack . show))
if T.length (openPRReport searchResult) == 0
then return ()

View File

@ -36,7 +36,7 @@ import OurPrelude hiding (throw)
import System.Directory (doesDirectoryExist, doesFileExist, getModificationTime, getCurrentDirectory, setCurrentDirectory)
import System.Environment (getEnv)
import System.Environment.XDG.BaseDir (getUserCacheDir)
import System.Exit
import System.Exit()
import System.IO.Error (tryIOError)
import System.Posix.Env (setEnv)
import qualified System.Process.Typed

View File

@ -46,7 +46,7 @@ import qualified Polysemy.Error as Error
import qualified System.Process.Typed as TP
import qualified Process
import qualified Process as P
import System.Exit
import System.Exit()
import Utils (UpdateEnv (..), nixBuildOptions, nixCommonOptions, srcOrMain)
import Prelude hiding (log)

View File

@ -15,7 +15,7 @@ import OurPrelude
import Polysemy.Output (Output, output)
import qualified Process as P
import System.Environment.XDG.BaseDir (getUserCacheDir)
import System.Exit (ExitCode (..))
import System.Exit ()
import qualified Utils
import Prelude hiding (log)

View File

@ -27,7 +27,7 @@ import OurPrelude
import qualified Polysemy.Error as Error
import Polysemy.Output (Output, output)
import qualified Process
import System.Exit
import System.Exit()
import Utils (UpdateEnv (..))
import qualified Utils
( runLog,

View File

@ -4,7 +4,7 @@ module Time where
import qualified Data.Text as T
import Data.Time.Clock (UTCTime, addUTCTime, getCurrentTime)
import Data.Time.Format (defaultTimeLocale, formatTime, iso8601DateFormat)
import Data.Time.Format.ISO8601 (iso8601Show)
import OurPrelude
data Time m a where
@ -25,7 +25,7 @@ runPure t =
-- | Return the UTC time 1 hour ago
-- $setup
-- >>> import Data.Time.Format (parseTimeOrError)
-- >>> import Data.Time.Format (parseTimeOrError, defaultTimeLocale)
-- >>> let exampleCurrentTime = parseTimeOrError False defaultTimeLocale "%Y-%-m-%-d" "2019-06-06" :: UTCTime
--
-- Examples:
@ -47,14 +47,9 @@ twoHoursAgo = now <&> addUTCTime (fromInteger $ -60 * 60 * 2)
-- | Return the current ISO8601 date and time without timezone
--
-- TODO: switch to Data.Time.Format.ISO8601 once time-1.9.0 is available
-- unix depends on an earlier version currently https://github.com/haskell/unix/issues/131
--
-- Examples:
--
-- >>> run $ runPure exampleCurrentTime runDate
-- "2019-06-06T00:00:00"
-- "2019-06-06T00:00:00Z"
runDate :: Member Time r => Sem r Text
runDate =
now <&> formatTime defaultTimeLocale (iso8601DateFormat (Just "%H:%M:%S"))
<&> T.pack
runDate = now <&> iso8601Show <&> T.pack

View File

@ -198,7 +198,7 @@ updateLoop o log (Right (pName, oldVer, newVer, url) : moreUpdates) = do
log $ "Failed to update: " <> updateInfoLine
if ".0" `T.isSuffixOf` newVer
then
let Just newNewVersion = ".0" `T.stripSuffix` newVer
let newNewVersion = fromJust (".0" `T.stripSuffix` newVer)
in updateLoop
o
log
@ -368,8 +368,8 @@ updateAttrPath log mergeBase updateEnv@UpdateEnv {..} attrPath = do
if hasUpdateScript
then do
-- Already checked that these are Just above.
let Just oldVer = oldVerMay
let Just newVer = newVerMay
let oldVer = fromJust oldVerMay
let newVer = fromJust newVerMay
return $
UpdateEnv
packageName