Skip to content

Commit

Permalink
Support GHC 9.12.1 (#39)
Browse files Browse the repository at this point in the history
* Support GHC 9.12.1

* Ran Fourmolu on PrintApi.CLI.Cmd.Dump
  • Loading branch information
mmhat authored Jan 12, 2025
1 parent 78bd292 commit 321c188
Show file tree
Hide file tree
Showing 6 changed files with 84 additions and 24 deletions.
14 changes: 11 additions & 3 deletions compat/9.10.1/GHC/Compat.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,19 @@
-- GHC 9.10.1 Compatibility
module GHC.Compat where
-- GHC 9.10.1 compatibility
module GHC.Compat
( mkNamePprCtxForModule
, mkShowSub
) where

import GHC (ModuleInfo)
import Data.Maybe (fromJust)
import GHC (Ghc, Module, ModuleInfo, NamePprCtx)
import GHC qualified
import GHC.Iface.Syntax (AltPpr (..), ShowForAllFlag (..), ShowHowMuch (..), ShowSub (..))

import PrintApi.IgnoredDeclarations

mkNamePprCtxForModule :: Module -> ModuleInfo -> Ghc NamePprCtx
mkNamePprCtxForModule _ mod_info = fromJust <$> GHC.mkNamePprCtxForModule mod_info

mkShowSub :: ModuleInfo -> ShowSub
mkShowSub mod_info =
let ss_how_much = ShowSome (Just (showOcc mod_info)) (AltPpr Nothing)
Expand Down
19 changes: 19 additions & 0 deletions compat/9.12.1/GHC/Compat.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
-- GHC 9.12.1 compatibility
module GHC.Compat
( GHC.mkNamePprCtxForModule
, mkShowSub
) where

import GHC (ModuleInfo)
import GHC qualified
import GHC.Iface.Syntax (AltPpr (..), ShowForAllFlag (..), ShowHowMuch (..), ShowSub (..))

import PrintApi.IgnoredDeclarations

mkShowSub :: ModuleInfo -> ShowSub
mkShowSub mod_info =
let ss_how_much = ShowSome (Just (showOcc mod_info)) (AltPpr Nothing)
in ShowSub
{ ss_how_much = ss_how_much
, ss_forall = ShowForAllMust
}
14 changes: 11 additions & 3 deletions compat/9.6.6/GHC/Compat.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,17 @@
-- GHC 9.6.6 Compatibility
module GHC.Compat where
-- GHC 9.6.6 compatibility
module GHC.Compat
( mkNamePprCtxForModule
, mkShowSub
) where

import GHC (ModuleInfo)
import Data.Maybe (fromJust)
import GHC (Ghc, Module, ModuleInfo, NamePprCtx)
import GHC qualified
import GHC.Iface.Syntax (AltPpr (..), ShowForAllFlag (..), ShowHowMuch (..), ShowSub (..))

mkNamePprCtxForModule :: Module -> ModuleInfo -> Ghc NamePprCtx
mkNamePprCtxForModule _ mod_info = fromJust <$> GHC.mkNamePprCtxForModule mod_info

mkShowSub :: ModuleInfo -> ShowSub
mkShowSub _mod_info =
let ss_how_much = ShowSome [] (AltPpr Nothing)
Expand Down
15 changes: 11 additions & 4 deletions compat/9.8.4/GHC/Compat.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,16 @@
-- GHC 9.10.1 Compatibility
module GHC.Compat where
-- GHC 9.8.4 compatibility
module GHC.Compat
( mkNamePprCtxForModule
, mkShowSub
) where

import GHC (ModuleInfo)
import Data.Maybe (fromJust)
import GHC (Ghc, Module, ModuleInfo, NamePprCtx)
import GHC qualified
import GHC.Iface.Syntax (AltPpr (..), ShowForAllFlag (..), ShowHowMuch (..), ShowSub (..))
import PrintApi.IgnoredDeclarations ()

mkNamePprCtxForModule :: Module -> ModuleInfo -> Ghc NamePprCtx
mkNamePprCtxForModule _ mod_info = fromJust <$> GHC.mkNamePprCtxForModule mod_info

mkShowSub :: ModuleInfo -> ShowSub
mkShowSub _ =
Expand Down
24 changes: 19 additions & 5 deletions print-api.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -12,10 +12,11 @@ maintainer: hecate+github@glitchbra.in
copyright: © 2023 Ben Gamari, 2024 Hécate Kleidukos
extra-source-files:
compat/9.10.1/GHC/Compat.hs
compat/9.12.1/GHC/Compat.hs
compat/9.6.6/GHC/Compat.hs
compat/9.8.4/GHC/Compat.hs

tested-with: GHC ==9.6.6 || ==9.8.4 || ==9.10.1
tested-with: GHC ==9.6.6 || ==9.8.4 || ==9.10.1 || ==9.12.1

common extensions
default-extensions:
Expand Down Expand Up @@ -69,14 +70,17 @@ library
import: ghc-options
hs-source-dirs: src

if impl(ghc ==9.10.1)
hs-source-dirs: compat/9.10.1
if impl(ghc ==9.6.6)
hs-source-dirs: compat/9.6.6

if impl(ghc ==9.8.4)
hs-source-dirs: compat/9.8.4

if impl(ghc ==9.6.6)
hs-source-dirs: compat/9.6.6
if impl(ghc ==9.10.1)
hs-source-dirs: compat/9.10.1

if impl(ghc ==9.12.1)
hs-source-dirs: compat/9.12.1

other-modules: Paths_print_api
autogen-modules: Paths_print_api
Expand Down Expand Up @@ -148,6 +152,16 @@ executable print-api-9.10.1
else
buildable: False

executable print-api-9.12.1
import: print-api-common
main-is: Main.hs

if impl(ghc ==9.12.1)
buildable: True

else
buildable: False

test-suite print-api-test
import: extensions
import: ghc-options
Expand Down
22 changes: 13 additions & 9 deletions src/PrintApi/CLI/Cmd/Dump.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,10 @@
-- Visibility : Public
--
-- The processing of package information
module PrintApi.CLI.Cmd.Dump where
module PrintApi.CLI.Cmd.Dump
( run
, computePackageAPI
) where

import Control.Monad.IO.Class
import Data.Function (on, (&))
Expand All @@ -23,14 +26,15 @@ import Data.Text (Text)
import Data.Text qualified as Text
import Data.Text.Encoding qualified as TE
import GHC
( ModuleInfo
( Module
, ModuleInfo
, getModuleInfo
, getNamePprCtx
, lookupName
, lookupQualifiedModule
, mkNamePprCtxForModule
, modInfoExports
, modInfoIface
, moduleName
, parseDynamicFlags
, runGhc
, setProgramDynFlags
Expand Down Expand Up @@ -157,13 +161,13 @@ reportModuleDecls usePublicOnly userIgnoredModules unitId moduleName
if usePublicOnly
then
if isVisible docs
then extractModuleDeclarations moduleName mod_info
then extractModuleDeclarations modl mod_info
else pure empty
else extractModuleDeclarations moduleName mod_info
else extractModuleDeclarations modl mod_info

extractModuleDeclarations :: ModuleName -> ModuleInfo -> Ghc SDoc
extractModuleDeclarations moduleName mod_info = do
Just name_ppr_ctx <- mkNamePprCtxForModule mod_info
extractModuleDeclarations :: Module -> ModuleInfo -> Ghc SDoc
extractModuleDeclarations modl mod_info = do
name_ppr_ctx <- Compat.mkNamePprCtxForModule modl mod_info
let names = modInfoExports mod_info
let sorted_names = List.sortBy (compare `on` nameOccName) names
things <-
Expand All @@ -190,7 +194,7 @@ extractModuleDeclarations moduleName mod_info = do
(text "{-# MINIMAL" <+> ppr (classMinimalDef cls) <+> text "#-}")
_ -> empty
]
pure $ withUserStyle name_ppr_ctx AllTheWay $ hang (modHeader moduleName) 2 contents <> text ""
pure $ withUserStyle name_ppr_ctx AllTheWay $ hang (modHeader (moduleName modl)) 2 contents <> text ""

reportInstances :: Ghc SDoc
reportInstances = do
Expand Down

0 comments on commit 321c188

Please # to comment.