diff options
| author | Yuchen Pei <hi@ypei.me> | 2022-06-03 18:09:46 +1000 | 
|---|---|---|
| committer | Yuchen Pei <hi@ypei.me> | 2022-06-03 18:09:46 +1000 | 
| commit | 5e3918fd16186c381a4a503e76588dbe60870717 (patch) | |
| tree | 9624ab94ce5d19b1b939f79c253e45bca0f0f54b | |
| parent | dbd46784650f143646986fbccb0cdcb7cb0acc48 (diff) | |
typecheckedsources no more warnings except two holes
| -rw-r--r-- | src/HaskellCodeExplorer/AST/TypecheckedSource.hs | 260 | 
1 files changed, 49 insertions, 211 deletions
| diff --git a/src/HaskellCodeExplorer/AST/TypecheckedSource.hs b/src/HaskellCodeExplorer/AST/TypecheckedSource.hs index cb7d323..d7cabd7 100644 --- a/src/HaskellCodeExplorer/AST/TypecheckedSource.hs +++ b/src/HaskellCodeExplorer/AST/TypecheckedSource.hs @@ -60,7 +60,6 @@ import GHC.Hs    , HsCmd(..)    , HsCmdTop(..)    , HsConDetails(..) -  , HsConPatDetails    , HsExpr(..)    , HsLocalBindsLR(..)    , HsOverLit(..) @@ -78,7 +77,6 @@ import GHC.Hs    , LHsExpr    , LHsRecField    , LHsRecUpdField -  , LHsTupArg    , LMatch    , LPat    , LStmtLR @@ -600,34 +598,27 @@ foldTypecheckedSource :: LHsBinds Id -> State ASTState ()  #endif  foldTypecheckedSource = foldLHsBindsLR -#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0) +-- src/HaskellCodeExplorer/AST/TypecheckedSource.hs:606:1: warning: [-Wincomplete-patterns] +--     Pattern match(es) are non-exhaustive +--     In an equation for ‘foldLHsExpr’: +--         Patterns of type ‘LHsExpr GhcTc’ not matched: +--             L (GHC.Parser.Annotation.SrcSpanAnn _ _) (HsGetField _ _ _) +--             L (GHC.Parser.Annotation.SrcSpanAnn _ _) (HsProjection _ _) +--             L (GHC.Parser.Annotation.SrcSpanAnn _ _) (HsPragE _ _ _)  foldLHsExpr :: LHsExpr GhcTc -> State ASTState (Maybe Type) -#else -foldLHsExpr :: LHsExpr Id -> State ASTState (Maybe Type) -#endif  foldLHsExpr (L _span (XExpr _)) = return Nothing -foldLHsExpr (L _ (HsOverLit _ (XOverLit _))) = return Nothing -foldLHsExpr (L _ (HsLam _ (XMatchGroup _))) = return Nothing -foldLHsExpr (L _ (HsLamCase _ (XMatchGroup _))) = return Nothing -foldLHsExpr (L _ (HsCase _ _ (XMatchGroup _))) = return Nothing  foldLHsExpr lhe@(L _ (HsVar _ (L _ identifier))) =    restoreTidyEnv $ do      (identifier', mbTypes) <- tidyIdentifier identifier      addIdentifierToIdSrcSpanMap (getLocA lhe) identifier' mbTypes      return . Just . varType $ identifier'  foldLHsExpr (L _ HsUnboundVar {}) = return Nothing -#if MIN_VERSION_GLASGOW_HASKELL(8,2,2,0) -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0) -foldLHsExpr (L _ (HsConLikeOut _ conLike)) = -#else -foldLHsExpr (L _ (HsConLikeOut conLike)) = -#endif +foldLHsExpr (L _ (HsConLikeOut _ _)) =    -- restoreTidyEnv $ do    --   let mbType = varType <$> conLikeWrapId_maybe conLike    --   mbType' <- maybe (return Nothing) (fmap Just . tidyType) mbType    --   return mbType'    restoreTidyEnv $ return Nothing -#endif  foldLHsExpr (L _ HsRecFld {}) = return Nothing  foldLHsExpr (L _ HsOverLabel {}) = return Nothing  foldLHsExpr lhe@(L _ expr@HsIPVar {}) = do @@ -655,7 +646,7 @@ foldLHsExpr lhe@(L _ (HsLit _ lit)) =           then Simple           else Composite)      return $ Just typ -foldLHsExpr lhe@(L span expr@(HsLam _ (MG (MatchGroupTc {..}) mg_alts _))) = +foldLHsExpr lhe@(L _ expr@(HsLam _ (MG (MatchGroupTc {..}) mg_alts _))) =    restoreTidyEnv $ do      typ <- tidyType $ mkVisFunTys mg_arg_tys mg_res_ty      addExprInfo (getLocA lhe) (Just typ) "HsLam" (exprSort expr) @@ -892,7 +883,6 @@ foldLHsRecField :: LHsRecField GhcTc (LHsExpr GhcTc) -> State ASTState (Maybe Ty  #else  foldLHsRecField :: LHsRecField Id (LHsExpr Id) -> State ASTState (Maybe Type)  #endif -foldLHsRecField (L _span (HsRecField _ (L _idSpan (XFieldOcc _)) _ _)) = return Nothing  foldLHsRecField lhr@(L _ (HsRecField _ (L idSpan (FieldOcc identifier _)) arg pun)) =    restoreTidyEnv $ do      (identifier', mbTypes) <- tidyIdentifier identifier @@ -926,7 +916,6 @@ data TupArg    deriving (Show, Eq)  foldHsTupArg :: HsTupArg GhcTc -> State ASTState (Maybe Type, TupArg) -foldHsTupArg (XTupArg _) = return (Nothing, TupArgMissing)  foldHsTupArg (Present _ expr) =    restoreTidyEnv $ do      typ <- foldLHsExpr expr @@ -940,22 +929,6 @@ foldHsTupArg (Missing typ) =      typ' <- tidyType $ scaledThing typ      return (Just typ', TupArgMissing) --- TODO: use foldHsTupArg -foldLHsTupArg :: LHsTupArg GhcTc -> State ASTState (Maybe Type, TupArg) -foldLHsTupArg (L _span (XTupArg _)) = return (Nothing, TupArgMissing) -foldLHsTupArg (L _span (Present _ expr)) = -  restoreTidyEnv $ do -    typ <- foldLHsExpr expr -    typ' <- -      case typ of -        Just t -> Just <$> tidyType t -        Nothing -> return Nothing -    return (typ', TupArgPresent) -foldLHsTupArg (L _ (Missing typ)) = -  restoreTidyEnv $ do -    typ' <- tidyType $ scaledThing typ -    return (Just typ', TupArgMissing) -  #if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)  foldLMatch :: LMatch GhcTc (LHsExpr GhcTc) -> State ASTState (Maybe Type)  #else @@ -965,9 +938,6 @@ foldLMatch (L _span Match {..}) = do    mapM_ foldLPat m_pats    _ <- foldGRHSs m_grhss    return Nothing -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0) -foldLMatch (L _span _) = return Nothing -#endif  #if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)  foldLMatchCmd :: LMatch GhcTc (LHsCmd GhcTc) -> State ASTState (Maybe Type) @@ -978,9 +948,6 @@ foldLMatchCmd (L _span Match {..}) = do    mapM_ foldLPat m_pats    _ <- foldGRHSsCmd m_grhss    return Nothing -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0) -foldLMatchCmd (L _span _) = return Nothing -#endif  #if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)  foldGRHSsCmd :: GRHSs GhcTc (LHsCmd GhcTc) -> State ASTState (Maybe Type) @@ -991,9 +958,6 @@ foldGRHSsCmd GRHSs {..} = do    mapM_ foldLGRHSCmd grhssGRHSs    _ <- foldHsLocalBindsLR grhssLocalBinds    return Nothing -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0) -foldGRHSsCmd (_) = return Nothing -#endif  #if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)  foldGRHSs :: GRHSs GhcTc (LHsExpr GhcTc) -> State ASTState (Maybe Type) @@ -1004,16 +968,8 @@ foldGRHSs GRHSs {..} = do    mapM_ foldLGRHS grhssGRHSs    _ <- foldHsLocalBindsLR grhssLocalBinds    return Nothing -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0) -foldGRHSs (_) = return Nothing -#endif -#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)  foldLStmtLR :: LStmtLR GhcTc GhcTc (LHsExpr GhcTc) -> State ASTState (Maybe Type) -#else -foldLStmtLR :: LStmtLR Id Id (LHsExpr Id) -> State ASTState (Maybe Type) -#endif -foldLStmtLR (L _span (XStmtLR _)) = return Nothing  foldLStmtLR lst@(L _ (LastStmt _ body _ _)) =    do typ <- foldLHsExpr body       addExprInfo (getLocA lst) typ "LastStmt" Composite @@ -1068,24 +1024,11 @@ foldApplicativeArg :: ApplicativeArg Id Id -> State ASTState (Maybe Type)  #endif  foldApplicativeArg appArg =    case appArg of -#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0) -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0) -    XApplicativeArg _ -> return Nothing      ApplicativeArgOne _ pat expr _bool -> do -#else -    ApplicativeArgOne pat expr _bool -> do -#endif -#else -    ApplicativeArgOne pat expr -> do -#endif        _ <- foldLPat pat        _ <- foldLHsExpr expr        return Nothing -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0)      ApplicativeArgMany _ exprStmts _ pat _ -> do -#else -    ApplicativeArgMany exprStmts _ pat -> do -#endif        mapM_ foldLStmtLR exprStmts        _ <- foldLPat pat        return Nothing @@ -1095,7 +1038,6 @@ foldLStmtLRCmd ::  #else  foldLStmtLRCmd :: LStmtLR Id Id (LHsCmd Id) -> State ASTState (Maybe Type)  #endif -foldLStmtLRCmd (L _ (XStmtLR _)) = return Nothing  foldLStmtLRCmd ls@(L _ (LastStmt _ body _syntaxExpr _)) = do    typ <- foldLHsCmd body    addExprInfo (getLocA ls) typ "LastStmt Cmd" Composite @@ -1133,61 +1075,25 @@ foldLStmtLRCmd ls@(L _ (ApplicativeStmt typ args _)) =      addExprInfo (getLocA ls) (Just typ') "ApplicativeStmt Cmd" Composite      return Nothing -#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)  foldLGRHS :: LGRHS GhcTc (LHsExpr GhcTc) -> State ASTState (Maybe Type) -#else -foldLGRHS :: LGRHS Id (LHsExpr Id) -> State ASTState (Maybe Type) -#endif -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0) -foldLGRHS (L _span (XGRHS _)) = return Nothing  foldLGRHS (L _span (GRHS _ guards body)) = do -#else -foldLGRHS (L _span (GRHS guards body)) = do -#endif    typ <- foldLHsExpr body    mapM_ foldLStmtLR guards    return typ -#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)  foldLGRHSCmd :: LGRHS GhcTc (LHsCmd GhcTc) -> State ASTState (Maybe Type) -#else -foldLGRHSCmd :: LGRHS Id (LHsCmd Id) -> State ASTState (Maybe Type) -#endif -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0) -foldLGRHSCmd (L _span (XGRHS _)) = return Nothing  foldLGRHSCmd (L _span (GRHS _ guards body)) = do -#else -foldLGRHSCmd (L _span (GRHS guards body)) = do -#endif    typ <- foldLHsCmd body    mapM_ foldLStmtLR guards    return typ -#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)  foldParStmtBlock :: ParStmtBlock GhcTc GhcTc -> State ASTState (Maybe Type) -#else -foldParStmtBlock :: ParStmtBlock Id Id -> State ASTState (Maybe Type) -#endif -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0) -foldParStmtBlock (XParStmtBlock _) = return Nothing  foldParStmtBlock (ParStmtBlock _ exprStmts _ids _syntaxExpr) = do -#else -foldParStmtBlock (ParStmtBlock exprStmts _ids _syntaxExpr) = do -#endif    mapM_ foldLStmtLR exprStmts    return Nothing -#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)  foldHsLocalBindsLR :: HsLocalBindsLR GhcTc GhcTc -> State ASTState (Maybe Type) -#else -foldHsLocalBindsLR :: HsLocalBindsLR Id Id -> State ASTState (Maybe Type) -#endif -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0) -foldHsLocalBindsLR (XHsLocalBindsLR _) = return Nothing  foldHsLocalBindsLR (HsValBinds _ binds) = do -#else -foldHsLocalBindsLR (HsValBinds binds) = do -#endif    _ <- foldHsValBindsLR binds    return Nothing  foldHsLocalBindsLR HsIPBinds {} = return Nothing @@ -1212,19 +1118,12 @@ foldHsValBindsLR (ValBindsOut binds _) = do    return Nothing  #endif -#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)  foldLHsBindsLR :: LHsBinds GhcTc -> State ASTState () -#else -foldLHsBindsLR :: LHsBinds Id -> State ASTState () -#endif  foldLHsBindsLR = mapM_ (`foldLHsBindLR` Nothing) . bagToList  foldLHsBindLR :: LHsBindLR GhcTc GhcTc                -> Maybe Id -- ^ Polymorphic id                -> State ASTState (Maybe Type) -foldLHsBindLR (L _span (XHsBindsLR _)) _ = return Nothing -foldLHsBindLR (L _span (PatSynBind _ (XPatSynBind _))) _ = return Nothing --- TODO: FIXME  foldLHsBindLR (L _span FunBind {..}) mbPolyId    | mg_origin fun_matches == FromSource =      restoreTidyEnv $ do @@ -1244,7 +1143,7 @@ foldLHsBindLR (L _ PatBind {..}) _ = do    _ <- foldLPat pat_lhs    _ <- foldGRHSs pat_rhs    return Nothing -foldLHsBindLR (L _ VarBind {..}) _ = return Nothing +foldLHsBindLR (L _ VarBind {}) _ = return Nothing  foldLHsBindLR (L _ AbsBinds {..}) _ = do    mapM_ (\(bind, typ) -> foldLHsBindLR bind (Just typ)) $      zip (bagToList abs_binds) (map abe_poly abs_exports) @@ -1278,8 +1177,6 @@ foldLHsBindLR (L _ (PatSynBind _ PSB {..})) _ =  foldLPat :: LPat GhcTc -> State ASTState (Maybe Type)  foldLPat (L _span (XPat _)) = return Nothing -foldLPat (L _ (NPat _ (L _ (XOverLit _)) _ _)) = return Nothing -foldLPat (L _ (NPlusKPat _ (L _ _) (L _ (XOverLit _)) _ _ _)) = return Nothing  foldLPat lp@(L _ (VarPat _ (L _ identifier))) = do    (identifier', _) <- tidyIdentifier identifier    addIdentifierToIdSrcSpanMap (getLocA lp) identifier' Nothing @@ -1292,9 +1189,9 @@ foldLPat lp@(L _ p@(LazyPat _ pat)) = do    mbType <- foldLPat pat    addExprInfo (getLocA lp) mbType "LazyPat" (patSort p)    return mbType -foldLPat lp@(L _ p@(AsPat _ id@(L _ identifier) pat)) = do +foldLPat lp@(L _ p@(AsPat _ ide@(L _ identifier) pat)) = do    (identifier', _) <- tidyIdentifier identifier -  addIdentifierToIdSrcSpanMap (getLocA id) identifier' Nothing +  addIdentifierToIdSrcSpanMap (getLocA ide) identifier' Nothing    addExprInfo (getLocA lp) (Just . varType $ identifier') "AsPat" (patSort p)    _ <- foldLPat pat    return . Just . varType $ identifier' @@ -1393,9 +1290,9 @@ foldLPat lp@(L _ pat@(NPat (L _spanLit OverLit {ol_type}) _ _ _)) = do    typ' <- tidyType ol_type    addExprInfo (getLocA lp) (Just typ') "NPat" (patSort pat)    return $ Just ol_type -foldLPat lp@(L _ pat@(NPlusKPat typ id@(L _ identifier) (L litSpan (OverLit (OverLitTc {..}) _ _)) _ _ _)) = do +foldLPat lp@(L _ pat@(NPlusKPat typ ide@(L _ identifier) (L litSpan (OverLit (OverLitTc {..}) _ _)) _ _ _)) = do    (identifier', _) <- tidyIdentifier identifier -  addIdentifierToIdSrcSpanMap (getLocA id) identifier' Nothing +  addIdentifierToIdSrcSpanMap (getLocA ide) identifier' Nothing    typ' <- tidyType typ    addExprInfo (getLocA lp) (Just typ') "NPlusKPat" (patSort pat)    olType' <- tidyType ol_type @@ -1434,129 +1331,74 @@ foldLPat (L _span (SigPatOut pat typ)) = do  --   return Nothing  foldLPat _ = return Nothing -#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0) -foldHsConPatDetails -  :: HsConPatDetails GhcTc -  -> State ASTState (Maybe Type) -#else -foldHsConPatDetails -  :: HsConPatDetails Id -  -> State ASTState (Maybe Type) -#endif -foldHsConPatDetails (PrefixCon _ args) = do -  mapM_ foldLPat args -  return Nothing -foldHsConPatDetails (RecCon rec) = do -  _ <- foldHsRecFieldsPat rec -  return Nothing -foldHsConPatDetails (InfixCon arg1 arg2) = do -  _ <- foldLPat arg1 -  _ <- foldLPat arg2 -  return Nothing - -#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0) -foldHsRecFieldsPat :: HsRecFields GhcTc (LPat GhcTc) -> State ASTState (Maybe Type) -#else -foldHsRecFieldsPat :: HsRecFields Id (LPat Id) -> State ASTState (Maybe Type) -#endif -foldHsRecFieldsPat HsRecFields {..} = do -  let onlyUserWritten = -        case rec_dotdot of -          Just i -> take $ unLoc i -          Nothing -> id -  mapM_ foldLHsRecFieldPat $ onlyUserWritten rec_flds -  return Nothing +-- no longer used +-- foldHsConPatDetails +--   :: HsConPatDetails GhcTc +--   -> State ASTState (Maybe Type) +-- foldHsConPatDetails (PrefixCon _ args) = do +--   mapM_ foldLPat args +--   return Nothing +-- foldHsConPatDetails (RecCon rec) = do +--   _ <- foldHsRecFieldsPat rec +--   return Nothing +-- foldHsConPatDetails (InfixCon arg1 arg2) = do +--   _ <- foldLPat arg1 +--   _ <- foldLPat arg2 +--   return Nothing -#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0) -foldLHsRecFieldPat :: LHsRecField GhcTc (LPat GhcTc) -> State ASTState (Maybe Type) -#else -foldLHsRecFieldPat :: LHsRecField Id (LPat Id) -> State ASTState (Maybe Type) -#endif -foldLHsRecFieldPat (L _ (HsRecField _ (L idSpan (FieldOcc identifier _)) arg pun)) = do -  (identifier', mbTypes) <- tidyIdentifier identifier -  addIdentifierToIdSrcSpanMap idSpan identifier' mbTypes -  unless pun $ void $ foldLPat arg -  return . Just . varType $ identifier' -foldLHsRecFieldPat (L _ (HsRecField _ (L _idSpan (XFieldOcc _)) _arg _pun)) = return Nothing +-- no longer used +-- foldHsRecFieldsPat :: HsRecFields GhcTc (LPat GhcTc) -> State ASTState (Maybe Type) +-- foldHsRecFieldsPat HsRecFields {..} = do +--   let onlyUserWritten = +--         case rec_dotdot of +--           Just i -> take $ unLoc i +--           Nothing -> id +--   mapM_ foldLHsRecFieldPat $ onlyUserWritten rec_flds +--   return Nothing +-- foldLHsRecFieldPat :: LHsRecField GhcTc (LPat GhcTc) -> State ASTState (Maybe Type) +-- foldLHsRecFieldPat (L _ (HsRecField _ (L idSpan (FieldOcc identifier _)) arg pun)) = do +--   (identifier', mbTypes) <- tidyIdentifier identifier +--   addIdentifierToIdSrcSpanMap idSpan identifier' mbTypes +--   unless pun $ void $ foldLPat arg +--   return . Just . varType $ identifier' +-- foldLHsRecFieldPat (L _ (HsRecField _ (L _idSpan (XFieldOcc _)) _arg _pun)) = return Nothing -#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)  foldLHsCmdTop :: LHsCmdTop GhcTc -> State ASTState (Maybe Type) -#else -foldLHsCmdTop :: LHsCmdTop Id -> State ASTState (Maybe Type) -#endif -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0) -foldLHsCmdTop (L _span (XCmdTop _)) = return Nothing  foldLHsCmdTop (L span (HsCmdTop _ cmd)) = do -#else -foldLHsCmdTop (L span (HsCmdTop cmd _ _ _)) = do -#endif    mbTyp <- foldLHsCmd cmd    addExprInfo span mbTyp "HsCmdTop" Composite    return mbTyp -#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0) +-- src/HaskellCodeExplorer/AST/TypecheckedSource.hs:1379:1: warning: [-Wincomplete-patterns] +--     Pattern match(es) are non-exhaustive +--     In an equation for ‘foldLHsCmd’: +--         Patterns of type ‘LHsCmd GhcTc’ not matched: +--             L (GHC.Parser.Annotation.SrcSpanAnn _ _) (HsCmdLamCase _ _)  foldLHsCmd :: LHsCmd GhcTc -> State ASTState (Maybe Type) -#else -foldLHsCmd :: LHsCmd Id -> State ASTState (Maybe Type) -#endif -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0)  foldLHsCmd (L _ (XCmd _)) = return Nothing -foldLHsCmd (L _ (HsCmdLam _ (XMatchGroup _))) = return Nothing -foldLHsCmd (L _ (HsCmdCase _ _ (XMatchGroup _))) = return Nothing  foldLHsCmd (L _ (HsCmdArrApp _ expr1 expr2 _ _)) = do -#else -foldLHsCmd (L _ (HsCmdArrApp expr1 expr2 _ _ _)) = do -#endif    _ <- foldLHsExpr expr1    _ <- foldLHsExpr expr2    return Nothing -#if MIN_VERSION_GLASGOW_HASKELL(8,2,2,0) -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0)  foldLHsCmd (L _ (HsCmdArrForm _ expr _  _ topCmds)) = do -#else -foldLHsCmd (L _ (HsCmdArrForm expr _  _ topCmds)) = do -#endif -#else -foldLHsCmd (L _ (HsCmdArrForm expr _ topCmds)) = do -#endif    _ <- foldLHsExpr expr    mapM_ foldLHsCmdTop topCmds    return Nothing -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0)  foldLHsCmd (L _ (HsCmdApp _ cmd expr)) = do -#else -foldLHsCmd (L _ (HsCmdApp cmd expr)) = do -#endif    _ <- foldLHsCmd cmd    _ <- foldLHsExpr expr    return Nothing -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0)  foldLHsCmd (L _ (HsCmdLam _ MG {..})) = do -#else -foldLHsCmd (L _ (HsCmdLam MG {..})) = do -#endif    mapM_ foldLMatchCmd $ unLoc mg_alts    return Nothing -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0)  foldLHsCmd (L _ (HsCmdCase _ expr MG {..})) = do -#else -foldLHsCmd (L _ (HsCmdCase expr MG {..})) = do -#endif    _ <- foldLHsExpr expr    mapM_ foldLMatchCmd $ unLoc mg_alts    return Nothing -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0)  foldLHsCmd (L _ (HsCmdPar _ cmd)) = do -#else -foldLHsCmd (L _ (HsCmdPar cmd)) = do -#endif    _ <- foldLHsCmd cmd    return Nothing -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0)  foldLHsCmd (L _ (HsCmdIf _ _ expr cmd1 cmd2)) = do -#else -foldLHsCmd (L _ (HsCmdIf _ expr cmd1 cmd2)) = do -#endif    _ <- foldLHsCmd cmd1    _ <- foldLHsCmd cmd2    _ <- foldLHsExpr expr @@ -1565,11 +1407,7 @@ foldLHsCmd (L _ (HsCmdLet _ binds cmd)) = do    _ <- foldLHsCmd cmd    _ <- foldHsLocalBindsLR binds    return Nothing -#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0)  foldLHsCmd (L _ (HsCmdDo _ stmts)) = do -#else -foldLHsCmd (L _ (HsCmdDo stmts _)) = do -#endif    mapM_ foldLStmtLRCmd $ unLoc stmts    return Nothing  -- no more hscmdwrap | 
