Skip to content

Commit c54d7ea

Browse files
committed
fixes
1 parent 37ec089 commit c54d7ea

File tree

8 files changed

+41
-46
lines changed

8 files changed

+41
-46
lines changed

cabal.project

Lines changed: 21 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -53,33 +53,14 @@ if impl(ghc >= 9.5)
5353
source-repository-package
5454
type:git
5555
location: https://github.com/wz1000/retrie
56-
tag: 3ad8ca0450ea4619bbc8007251582ffc828faa37
56+
tag: 0a2dbfc00e745737f249f16325b2815d2e3a14eb
5757

5858
package *
5959
ghc-options: -haddock
6060
test-show-details: direct
6161

6262
write-ghc-environment-files: never
6363

64-
if impl(ghc >= 9.5)
65-
allow-newer:
66-
-- ghc-9.6
67-
algebraic-graphs:transformers,
68-
cryptohash-md5:base,
69-
cryptohash-sha1:base,
70-
ekg-core:ghc-prim,
71-
focus:transformers,
72-
ghc-trace-events:base,
73-
implicit-hie-cradle:transformers,
74-
retrie:base,
75-
retrie:ghc,
76-
retrie:ghc-exactprint,
77-
retrie:mtl,
78-
retrie:transformers,
79-
semigroupoids:base,
80-
stm-hamt:transformers,
81-
entropy:Cabal,
82-
8364
-- head.hackage doesn't like index-state
8465
index-state: 2023-03-23T00:00:00Z
8566

@@ -138,3 +119,23 @@ allow-newer:
138119
uuid:time,
139120
vector-space:base,
140121
ekg-wai:time,
122+
123+
if impl(ghc >= 9.5)
124+
allow-newer:
125+
-- ghc-9.6
126+
algebraic-graphs:transformers,
127+
cryptohash-md5:base,
128+
cryptohash-sha1:base,
129+
ekg-core:ghc-prim,
130+
focus:transformers,
131+
ghc-trace-events:base,
132+
implicit-hie-cradle:transformers,
133+
retrie:base,
134+
retrie:ghc,
135+
retrie:ghc-exactprint,
136+
retrie:mtl,
137+
retrie:transformers,
138+
semigroupoids:base,
139+
stm-hamt:transformers,
140+
entropy:Cabal,
141+

plugins/hls-class-plugin/src/Ide/Plugin/Class/CodeLens.hs

Lines changed: 1 addition & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -90,14 +90,7 @@ codeLens state plId CodeLensParams{..} = pluginResponse $ do
9090
getBindSpanWithoutSig ClsInstDecl{..} =
9191
let bindNames = mapMaybe go (bagToList cid_binds)
9292
go (L l bind) = case bind of
93-
FunBind{..}
94-
-- `Generated` tagged for Template Haskell,
95-
-- here we filter out nonsence generated bindings
96-
-- that are nonsense for displaying code lenses.
97-
--
98-
-- See https://github.com/haskell/haskell-language-server/issues/3319
99-
| not $ isGenerated (mg_origin fun_matches)
100-
-> Just $ L l fun_id
93+
FunBind{..} -> Just $ L l fun_id
10194
_ -> Nothing
10295
-- Existed signatures' name
10396
sigNames = concat $ mapMaybe (\(L _ r) -> getSigName r) cid_sigs

plugins/hls-refactor-plugin/src/Development/IDE/GHC/ExactPrint.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -472,7 +472,7 @@ modifySmallestDeclWithM ::
472472
modifySmallestDeclWithM validSpan f a = do
473473
let modifyMatchingDecl [] = pure (DL.empty, Nothing)
474474
modifyMatchingDecl (ldecl@(L src _) : rest) =
475-
lift (validSpan $ locA src) >>= \case
475+
TransformT (lift $ validSpan $ locA src) >>= \case
476476
True -> do
477477
(decs', r) <- f ldecl
478478
pure $ (DL.fromList decs' <> DL.fromList rest, Just r)
@@ -581,7 +581,7 @@ modifyMgMatchesT' ::
581581
#if MIN_VERSION_ghc(9,5,0)
582582
modifyMgMatchesT' (MG xMg (L locMatches matches)) f def combineResults = do
583583
(unzip -> (matches', rs)) <- mapM f matches
584-
r' <- lift $ foldM combineResults def rs
584+
r' <- TransformT $ lift $ foldM combineResults def rs
585585
pure $ (MG xMg (L locMatches matches'), r')
586586
#else
587587
modifyMgMatchesT' (MG xMg (L locMatches matches) originMg) f def combineResults = do
@@ -704,7 +704,7 @@ annotate dflags needs_space ast = do
704704
uniq <- show <$> uniqueSrcSpanT
705705
let rendered = render dflags ast
706706
#if MIN_VERSION_ghc(9,4,0)
707-
expr' <- lift $ mapLeft (showSDoc dflags . ppr) $ parseAST dflags uniq rendered
707+
expr' <- TransformT $ lift $ mapLeft (showSDoc dflags . ppr) $ parseAST dflags uniq rendered
708708
pure $ setPrecedingLines expr' 0 (bool 0 1 needs_space)
709709
#elif MIN_VERSION_ghc(9,2,0)
710710
expr' <- lift $ mapLeft show $ parseAST dflags uniq rendered
@@ -745,7 +745,7 @@ annotateDecl dflags ast = do
745745
uniq <- show <$> uniqueSrcSpanT
746746
let rendered = render dflags ast
747747
#if MIN_VERSION_ghc(9,4,0)
748-
expr' <- lift $ mapLeft (showSDoc dflags . ppr) $ parseDecl dflags uniq rendered
748+
expr' <- TransformT $ lift $ mapLeft (showSDoc dflags . ppr) $ parseDecl dflags uniq rendered
749749
pure $ setPrecedingLines expr' 1 0
750750
#elif MIN_VERSION_ghc(9,2,0)
751751
expr' <- lift $ mapLeft show $ parseDecl dflags uniq rendered

plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction/ExactPrint.hs

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -311,7 +311,7 @@ liftParseAST df s = case parseAST df "" s of
311311
#else
312312
Right x -> pure (makeDeltaAst x)
313313
#endif
314-
Left _ -> lift $ Left $ "No parse: " <> s
314+
Left _ -> TransformT $ lift $ Left $ "No parse: " <> s
315315

316316
#if !MIN_VERSION_ghc(9,2,0)
317317
lookupAnn :: (Data a, Monad m)
@@ -344,7 +344,7 @@ lastMaybe other = Just $ last other
344344

345345
liftMaybe :: String -> Maybe a -> TransformT (Either String) a
346346
liftMaybe _ (Just x) = return x
347-
liftMaybe s _ = lift $ Left s
347+
liftMaybe s _ = TransformT $ lift $ Left s
348348

349349
------------------------------------------------------------------------------
350350
extendImport :: Maybe String -> String -> LImportDecl GhcPs -> Rewrite
@@ -389,7 +389,7 @@ extendImportTopLevel thing (L l it@ImportDecl{..})
389389
printOutputable (occName (unLoc rdr))
390390
`elem` map (printOutputable @OccName) (listify (const True) lies)
391391
when alreadyImported $
392-
lift (Left $ thing <> " already imported")
392+
TransformT $ lift (Left $ thing <> " already imported")
393393

394394
let lie = reLocA $ L src $ IEName
395395
#if MIN_VERSION_ghc(9,5,0)
@@ -399,7 +399,7 @@ extendImportTopLevel thing (L l it@ImportDecl{..})
399399
x = reLocA $ L top $ IEVar noExtField lie
400400

401401
if x `elem` lies
402-
then lift (Left $ thing <> " already imported")
402+
then TransformT $ lift (Left $ thing <> " already imported")
403403
else do
404404
#if !MIN_VERSION_ghc(9,2,0)
405405
anns <- getAnnsT
@@ -430,7 +430,7 @@ extendImportTopLevel thing (L l it@ImportDecl{..})
430430
return $ L l it{ideclHiding = Just (hide, L l' lies')}
431431
#endif
432432
#endif
433-
extendImportTopLevel _ _ = lift $ Left "Unable to extend the import list"
433+
extendImportTopLevel _ _ = TransformT $ lift $ Left "Unable to extend the import list"
434434

435435
wildCardSymbol :: String
436436
wildCardSymbol = ".."
@@ -466,7 +466,7 @@ extendImportViaParent df parent child (L l it@ImportDecl{..})
466466
#endif
467467
where
468468
go _hide _l' _pre ((L _ll' (IEThingAll _ (L _ ie))) : _xs)
469-
| parent == unIEWrappedName ie = lift . Left $ child <> " already included in " <> parent <> " imports"
469+
| parent == unIEWrappedName ie = TransformT $ lift . Left $ child <> " already included in " <> parent <> " imports"
470470
go hide l' pre (lAbs@(L ll' (IEThingAbs _ absIE@(L _ ie))) : xs)
471471
-- ThingAbs ie => ThingWith ie child
472472
| parent == unIEWrappedName ie = do
@@ -527,7 +527,7 @@ extendImportViaParent df parent child (L l it@ImportDecl{..})
527527
printOutputable (occName (unLoc childRdr))
528528
`elem` map (printOutputable @OccName) (listify (const True) lies')
529529
when alreadyImported $
530-
lift (Left $ child <> " already included in " <> parent <> " imports")
530+
TransformT $ lift (Left $ child <> " already included in " <> parent <> " imports")
531531

532532
let childLIE = reLocA $ L srcChild $ IEName
533533
#if MIN_VERSION_ghc(9,5,0)
@@ -606,7 +606,7 @@ extendImportViaParent df parent child (L l it@ImportDecl{..})
606606
#else
607607
return $ L l it{ideclHiding = Just (hide, L l' lies')}
608608
#endif
609-
extendImportViaParent _ _ _ _ = lift $ Left "Unable to extend the import list via parent"
609+
extendImportViaParent _ _ _ _ = TransformT $ lift $ Left "Unable to extend the import list via parent"
610610

611611
#if MIN_VERSION_ghc(9,2,0)
612612
-- Add an item in an import list, taking care of adding comma if needed.

plugins/hls-refactor-plugin/src/Development/IDE/Plugin/Plugins/AddArgument.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,7 @@ import GHC.Hs (IsUnicodeSyntax (..)
3434
import GHC.Types.SrcLoc (generatedSrcSpan)
3535
import Ide.PluginUtils (makeDiffTextEdit,
3636
responseError)
37-
import Language.Haskell.GHC.ExactPrint (TransformT,
37+
import Language.Haskell.GHC.ExactPrint (TransformT(..),
3838
noAnnSrcSpanDP1,
3939
runTransformT)
4040
import Language.Haskell.GHC.ExactPrint.Transform (d1)
@@ -87,7 +87,7 @@ appendFinalPatToMatches :: T.Text -> LHsDecl GhcPs -> TransformT (Either Respons
8787
appendFinalPatToMatches name = \case
8888
(L locDecl (ValD xVal fun@FunBind{fun_matches=mg,fun_id = idFunBind})) -> do
8989
(mg', numPatsMay) <- modifyMgMatchesT' mg (pure . second Just . addArgToMatch name) Nothing combineMatchNumPats
90-
numPats <- lift $ maybeToEither (responseError "Unexpected empty match group in HsDecl") numPatsMay
90+
numPats <- TransformT $ lift $ maybeToEither (responseError "Unexpected empty match group in HsDecl") numPatsMay
9191
let decl' = L locDecl (ValD xVal fun{fun_matches=mg'})
9292
pure (decl', Just (idFunBind, numPats))
9393
decl -> pure (decl, Nothing)

plugins/hls-splice-plugin/src/Ide/Plugin/Splice.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,7 @@ import Development.IDE.GHC.Compat as Compat hiding (getLoc)
5151
import Development.IDE.GHC.Compat.ExactPrint
5252
import qualified Development.IDE.GHC.Compat.Util as Util
5353
import Development.IDE.GHC.ExactPrint
54+
import Language.Haskell.GHC.ExactPrint.Transform (TransformT(TransformT))
5455
#if MIN_VERSION_ghc(9,4,1)
5556
import GHC.Data.Bag (Bag)
5657
#endif
@@ -381,7 +382,7 @@ manualCalcEdit clientCapabilities reportEditor ran ps hscEnv typechkd srcSpan _e
381382
(L _spn (SpliceD _ (SpliceDecl _ (L _ spl) _))) -> do
382383
eExpr <-
383384
eitherM (fail . show) pure
384-
$ lift
385+
$ TransformT $ lift
385386
( lift $
386387
Util.try @_ @SomeException $
387388
(fst <$> rnTopSpliceDecls spl)
@@ -394,7 +395,7 @@ manualCalcEdit clientCapabilities reportEditor ran ps hscEnv typechkd srcSpan _e
394395
(L _spn (matchSplice astP -> Just spl)) -> do
395396
eExpr <-
396397
eitherM (fail . show) pure
397-
$ lift
398+
$ TransformT $ lift
398399
( lift $
399400
Util.try @_ @SomeException $
400401
(fst <$> expandSplice astP spl)

stack-lts19.yaml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,7 @@ extra-deps:
4949
- ghc-lib-9.2.4.20220729
5050
- ghc-lib-parser-9.2.4.20220729
5151
- ghc-lib-parser-ex-9.2.0.4
52-
- hiedb-0.4.2.0
52+
- hiedb-0.4.3.0
5353
- hlint-3.4
5454
- implicit-hie-0.1.2.7@sha256:82bbbb1a8c05f99c8af3c16ac53e80c8648d8bf047b25ed5ce45a135bd736907,3122
5555
- implicit-hie-cradle-0.5.0.0@sha256:4276f60f3a59bc22df03fd918f73bca9f777de9568f85e3a8be8bd7566234a59,2368

stack.yaml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@ extra-deps:
4141
# needed for tests of hls-cabal-fmt-plugin
4242
- cabal-fmt-0.1.6@sha256:54041d50c8148c32d1e0a67aef7edeebac50ae33571bef22312f6815908eac19,3626
4343
- floskell-0.10.6@sha256:e77d194189e8540abe2ace2c7cb8efafc747ca35881a2fefcbd2d40a1292e036,3819
44-
- hiedb-0.4.2.0
44+
- hiedb-0.4.3.0
4545
- implicit-hie-0.1.2.7@sha256:82bbbb1a8c05f99c8af3c16ac53e80c8648d8bf047b25ed5ce45a135bd736907,3122
4646
- implicit-hie-cradle-0.5.0.0@sha256:4276f60f3a59bc22df03fd918f73bca9f777de9568f85e3a8be8bd7566234a59,2368
4747
- monad-dijkstra-0.1.1.3@sha256:d2fc098d7c122555e726830a12ae0423ac187f89de9228f32e56e2f6fc2238e1,1900

0 commit comments

Comments
 (0)