Fix hlint for GHC 8.10, apply suggestions

This commit is contained in:
Tom Smalley 2021-06-07 13:50:28 +01:00
parent 6a7782a61e
commit a11cedfa60
7 changed files with 10 additions and 9 deletions

View File

@ -176,7 +176,9 @@ library
Reflex.Dom.Builder.Class.TH
test-suite hlint
build-depends: base, hlint
build-depends:
base,
hlint >= 3.0 && < 4.0
hs-source-dirs: test
main-is: hlint.hs
type: exitcode-stdio-1.0

View File

@ -9,11 +9,12 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
#if !MIN_VERSION_base(4,9,0)
{-# LANGUAGE ImpredicativeTypes #-}
#else
{-# LANGUAGE Rank2Types #-} -- Implied by ImpredicativeTypes
#endif
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}

View File

@ -2,7 +2,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE FlexibleContexts #-}
@ -1877,14 +1876,14 @@ hoistTraverseWithKeyWithAdjust base mapPatch updateChildUnreadiness applyDomUpda
getHydrationMode >>= \case
HydrationMode_Hydrating -> addHydrationStepWithSetup (holdIncremental children0 children') $ \children -> do
dm :: DMap k (Compose (TraverseChild t m (Some k)) v') <- sample $ currentIncremental children
phs <- traverse id $ weakenDMapWith (either _traverseChildHydration_delayed (pure . _traverseChildImmediate_placeholder) . _traverseChild_mode . getCompose) dm
phs <- sequenceA $ weakenDMapWith (either _traverseChildHydration_delayed (pure . _traverseChildImmediate_placeholder) . _traverseChild_mode . getCompose) dm
liftIO $ writeIORef placeholders $! phs
insertAfterPreviousNode lastPlaceholder
HydrationMode_Immediate -> do
let activate i = do
append $ toNode $ _traverseChildImmediate_fragment i
pure $ _traverseChildImmediate_placeholder i
phs <- traverse id $ weakenDMapWith (either (error "impossible") activate . _traverseChild_mode . getCompose) children0
phs <- sequenceA $ weakenDMapWith (either (error "impossible") activate . _traverseChild_mode . getCompose) children0
liftIO $ writeIORef placeholders $! phs
append $ toNode lastPlaceholder
requestDomAction_ $ ffor children' $ \p -> do

View File

@ -274,7 +274,7 @@ instance SupportsStaticDomBuilder t m => DomBuilder t (StaticDomBuilderT t m) wh
--TODO: Do not escape quotation marks; see https://stackoverflow.com/questions/25612166/what-characters-must-be-escaped-in-html-5
shouldEscape <- asks _staticDomBuilderEnv_shouldEscape
let escape = if shouldEscape then fromHtmlEscapedText else byteString . encodeUtf8
modify . (:) =<< (\c -> "<!--" <> c <> "-->") <$> case mSetContents of
(modify . (:)) . (\c -> "<!--" <> c <> "-->") =<< case mSetContents of
Nothing -> return (pure (escape initialContents))
Just setContents -> hold (escape initialContents) $ fmapCheap escape setContents --Only because it doesn't get optimized when profiling is on
return $ CommentNode ()

View File

@ -5,7 +5,6 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE ScopedTypeVariables #-}

View File

@ -117,7 +117,7 @@ virtualList heightPx rowPx maxIndex i0 setI keyToIndex items0 itemsUpdate itemBu
"overflow" =: "hidden" <>
"position" =: "relative"
mkRow k = toStyleAttr $ "height" =: (T.pack (show rowPx) <> "px") <>
"top" =: ((<>"px") $ T.pack $ show $ keyToIndex k * rowPx) <>
"top" =: (<> "px") (T.pack $ show $ keyToIndex k * rowPx) <>
"position" =: "absolute" <>
"width" =: "100%"
findWindow sizeIncrement windowSize startingPosition =

View File

@ -1,4 +1,4 @@
import Language.Haskell.HLint3 (hlint)
import Language.Haskell.HLint (hlint)
import System.Exit (exitFailure, exitSuccess)
main :: IO ()