Skip to content

Commit

Permalink
Add a DynFlags plugin.
Browse files Browse the repository at this point in the history
This only has an effect on GHC 8.10 and later. Older versions need to manually
set the relevant flags.

TODO: warn when we had to override flags set by the user (ideally, we'd only
warn when they explicitly differ, not when we're overriding behavior set by
`-O2` or something.

This also currently doesn't work, because some of our tests break when we don't
ignore interface pragmas (I was hoping this would go away when we removed the
presimplifier, but it didn't).

Fixes #43.
  • Loading branch information
sellout committed Apr 16, 2022
1 parent 09f997b commit 1b35cd2
Show file tree
Hide file tree
Showing 14 changed files with 65 additions and 46 deletions.
23 changes: 23 additions & 0 deletions ghc/Categorifier/GHC/Driver.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,13 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE PartialTypeSignatures #-}

module Categorifier.GHC.Driver
( module DynFlags,
module HscTypes,
module Outputable,
module Plugins,
defaultPurePlugin,
pureDynflagsAndCorePlugin,
)
where

Expand Down Expand Up @@ -33,3 +35,24 @@ defaultPurePlugin = defaultPlugin {pluginRecompile = purePlugin}
#else
defaultPurePlugin = defaultPlugin
#endif

-- | Builds a pure plugin that has both `DynFlags` and `Core` components. Prior to GHC 8.10, the
-- `DynFlags` component will be ignored and so the flags must be manually configured to match.
pureDynflagsAndCorePlugin ::
([CommandLineOption] -> DynFlags -> IO DynFlags) ->
-- | @([CommandLineOption] -> [CoreToDo] -> CoreM [CoreToDo])@, but skipped to avoid import issues
_ ->
Plugin
#if MIN_VERSION_ghc(9, 2, 0)
pureDynflagsAndCorePlugin dynflags core =
defaultPurePlugin
{ driverPlugin =
\opts hsc -> (\newFlags -> hsc {hsc_dflags = newFlags}) <$> dynflags opts (hsc_dflags hsc),
installCoreToDos = core
}
#elif MIN_VERSION_ghc(8, 10, 0)
pureDynflagsAndCorePlugin dynflags core =
defaultPurePlugin {dynflagsPlugin = dynflags, installCoreToDos = core}
#else
pureDynflagsAndCorePlugin _ core = defaultPurePlugin {installCoreToDos = core}
#endif
1 change: 0 additions & 1 deletion ghc/categorifier-ghc.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,6 @@ library
Paths_categorifier_ghc
ghc-options:
-O2
-fignore-interface-pragmas
-Wall
build-depends:
, PyF
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -92,7 +92,6 @@ test-suite adjunctions-hierarchy-optimized
-fplugin-opt Categorifier:maker-map:Categorifier.Adjunctions.Integration.makerMapFun
-fplugin-opt Categorifier:maker-map:Categorifier.Core.MakerMap.baseMakerMapFun
-O2
-fignore-interface-pragmas
build-depends:
, adjunctions
, base
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -82,7 +82,6 @@ test-suite categories-hierarchy-optimized
-- -fplugin-opt Categorifier:defer-failures
-fplugin-opt Categorifier:hierarchy:Categorifier.Hierarchy.Categories.hierarchy
-O2
-fignore-interface-pragmas
build-depends:
, adjunctions
, base
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -88,7 +88,6 @@ test-suite concat-extensions-hierarchy-optimized
-fplugin-opt Categorifier:hierarchy:Categorifier.Hierarchy.ConCat.functionHierarchy
-fplugin-opt Categorifier:hierarchy:Categorifier.Hierarchy.ConCatExtensions.hierarchy
-O2
-fignore-interface-pragmas
build-depends:
, adjunctions
, base
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -96,7 +96,6 @@ test-suite concat-class-hierarchy-optimized
-- ConCat includes support for `index` and `tabulate`
-fplugin-opt Categorifier:maker-map:Categorifier.Adjunctions.Integration.makerMapFun
-O2
-fignore-interface-pragmas
build-depends:
, base
, categorifier-adjunctions-integration
Expand Down Expand Up @@ -159,7 +158,6 @@ test-suite concat-function-hierarchy-optimized
-- ConCat includes support for `index` and `tabulate`
-fplugin-opt Categorifier:maker-map:Categorifier.Adjunctions.Integration.makerMapFun
-O2
-fignore-interface-pragmas
build-depends:
, adjunctions
, base
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -88,7 +88,6 @@ test-suite unconcat-hierarchy-optimized
-fplugin-opt Categorifier:hierarchy:Categorifier.Hierarchy.UnconCat.hierarchy
-fplugin-opt Categorifier:hierarchy:Categorifier.Hierarchy.ConCat.functionHierarchy
-O2
-fignore-interface-pragmas
build-depends:
, adjunctions
, base
Expand Down
1 change: 0 additions & 1 deletion plugin-test/categorifier-plugin-test.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -127,7 +127,6 @@ test-suite base-hierarchy-optimized
-fplugin-opt Categorifier:defer-failures
-fplugin-opt Categorifier:hierarchy:Categorifier.Hierarchy.baseHierarchy
-O2
-fignore-interface-pragmas
build-depends:
, adjunctions
, base
Expand Down
17 changes: 9 additions & 8 deletions plugin/Categorifier.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@ where
import Categorifier.CommandLineOptions (OptionGroup, partitionOptions)
import Categorifier.Common.IO.Exception (throwIOAsException)
import qualified Categorifier.Core
import qualified Categorifier.DynFlags
import qualified Categorifier.GHC.Core as GhcPlugins
import qualified Categorifier.GHC.Driver as GhcPlugins
import Control.Applicative (liftA2)
Expand All @@ -30,14 +31,14 @@ import PyF (fmt)
-- for more information.
plugin :: GhcPlugins.Plugin
plugin =
GhcPlugins.defaultPurePlugin
{ GhcPlugins.installCoreToDos =
\opts ->
join
. GhcPlugins.liftIO
. liftA2 Categorifier.Core.install (partitionOptions' opts)
. pure
}
GhcPlugins.pureDynflagsAndCorePlugin
(\_opts -> pure . Categorifier.DynFlags.plugin)
( \opts ->
join
. GhcPlugins.liftIO
. liftA2 Categorifier.Core.install (partitionOptions' opts)
. pure
)

partitionOptions' :: [GhcPlugins.CommandLineOption] -> IO (Map OptionGroup [Text])
partitionOptions' opts =
Expand Down
8 changes: 3 additions & 5 deletions plugin/Categorifier/Core/ErrorHandling.hs
Original file line number Diff line number Diff line change
Expand Up @@ -232,11 +232,9 @@ required by {showE expr}.|]
`inlinable` pragma to the definition or compiling with
`-fexpose-all-unfoldings` to make _every_ operation inlinable. It's also
important that the module containing the call to `categorify` is compiled
with `-fno-ignore-interface-pragmas` (also implied by `-O`). If the
unfolding that's missing is for `$j` (GHC-internal join points), you may
need to bump `-funfolding-creation-threshold` on the modules you're
depending on. If there is still no unfolding available, please file an issue
against the plugin.|]
with `-fno-ignore-interface-pragmas` (also implied by `-O` and enabled
automatically on GHC 8.10.1 or later). If there is still no unfolding
available, please file an issue against the plugin.|]
Plugins.BootUnfolding ->
[fmt|
The identifier is defined in an hi-boot file, so can't be inlined.|]
Expand Down
24 changes: 24 additions & 0 deletions plugin/Categorifier/DynFlags.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,24 @@
module Categorifier.DynFlags
( plugin,
)
where

import qualified Categorifier.GHC.Driver as GHC

plugin :: GHC.DynFlags -> GHC.DynFlags
plugin = setUpDynFlags

-- | This sets up flags that allow the plugin to do what it needs to.
--
-- For a compiler that doesn't support this plugin (before GHC 8.10), the following GHC options
-- approximate it:
--
-- [@-fno-ignore-interface-pragmas@]: Ensures we can inline definitions that we don't know how to
-- interpret directly to the target category. This flag is also
-- implied by @-O@ and @-O2@.
-- [@-fno-unbox-strict-fields@]: This is needed because we don't yet support unboxed tuples, and
-- this avoids _some_ instances of them appearing.
setUpDynFlags :: GHC.DynFlags -> GHC.DynFlags
setUpDynFlags =
GHC.unSetGeneralFlag' GHC.Opt_IgnoreInterfacePragmas
. GHC.unSetGeneralFlag' GHC.Opt_UnboxStrictFields
28 changes: 5 additions & 23 deletions plugin/README.md
Original file line number Diff line number Diff line change
Expand Up @@ -11,8 +11,9 @@ directly, as well as ones that are depended on (transitively) by the ones that u

### targets you want to use `categorify` in

- enable the plugin with `-fplugin=Categorifier`,
- ensure inlining is available with `-fno-ignore-interface-pragmas` (implied by `-O` or `-O2`), and
- enable the plugin with `-fplugin=Categorifier`;
- if you are using a version of GHC older than 8.10.1, use the flags described in
[Categorifier.DynFlags](./Categorifier/DynFlags.hs); and
- import `Categorifier.Categorify` to make `categorify` available (you must import the _entire_ module,
but it may be qualified).

Expand All @@ -32,26 +33,6 @@ directly, as well as ones that are depended on (transitively) by the ones that u
- define `Categorifier.HasRep` instances for any types that you use in a converted function (the plugin
will tell you if you are missing any when you try to convert)

### fine-tuning inlining sizes

It can be difficult to find a reasonable setting for the various inlining thresholds. This attempts
to lay out an approach for identifying one.

There are two significant GHC flags for adjusting inlining, `-funfolding-creation-threshold` and
`-funfolding-use-threshold`. They allow you to set an upper bound on the "size" of unfoldings that
will be considered for inlining.

1. set both the `creation` (globally) threshold very high, say `10000`;
2. test to see if the inlining issue goes away (if so, skip to step 5);
3. set the `use` (in `categorify` modules) threshold to match the `creation` threshold;
4. do a binary search on the `use` thresholds to minimize them as much as possible;
5. do a binary search on the `creation` thresholds to minimize them as much as possible (the lower
bound here is probably the minimum of 750 (the default) and the `use` threshold).

If either if these values is too small, you'll end up with errors complaining that some definition
couldn't be inlined. If they're too big, you'll get errors about "simplifier ticks exhausted" (in
which case, you can bump `-fsimpl-tick-factor`) and things will take a lot longer to compile.

### defining `HasRep` instances

You should generally use `Categorifier.Client.deriveHasRep` for all `HasRep` instances. However, for
Expand Down Expand Up @@ -145,7 +126,8 @@ This is ostensibly a more correct approach, given the way GHC is structured, but
There are a bunch of modules, this calls out the most important ones when diving in.

- [Categorifier](./Categorifier.hs) - this is the entrypoint of the plugin, everything that hooks into
GHC starts from here;
GHC starts from here, with there being three immediate subcomponents: command-line option
handling, `DynFlags` settings, and the Core pass;
- [Categorifier.Core.Categorify](./Categorifier/Core/Categorify.hs) - the high-level logic of the
categorical transformation as described in Conal's paper, it tries to define as clearly as
possible the mapping from **Hask** to abstract categories;
Expand Down
2 changes: 1 addition & 1 deletion plugin/categorifier-plugin.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ library
-- __TODO__: move ...PrimOp to other-modules
Categorifier.Core.PrimOp
Categorifier.Core.Types
Categorifier.DynFlags
Categorifier.Hierarchy
other-modules:
Categorifier.Benchmark
Expand All @@ -41,7 +42,6 @@ library
Paths_categorifier_plugin
ghc-options:
-O2
-fignore-interface-pragmas
-Wall
build-depends:
, PyF
Expand Down
1 change: 0 additions & 1 deletion th/categorifier-th.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,6 @@ library
Paths_categorifier_th
ghc-options:
-O2
-fignore-interface-pragmas
-Wall
build-depends:
, PyF
Expand Down

0 comments on commit 1b35cd2

Please sign in to comment.