Writing GHC plugin to modify AST despite failure to type-check

Hi there, I would like to write a GHC plugin — initially as a learning exercise, and maybe real-world use if it works — that automatically applies `liftIO` to `IO` actions, to get the benefit that libraries like `lifted-base` or `relude` provide, but applied to all libraries, automatically. As a simple example, this program will not type-check by default, but it will if I can write my plugin: ``` program :: MonadIO m => m () program = putStrLn "Hello world!" ``` (That's `putStrLn :: String -> IO ()` from the regular `Prelude`) The idea is roughly, "if you see an `IO a` action where a `MonadIO m => m a` action is expected, add `liftIO` to make the `IO a` action type-check. But how to implement it? A type-checker plugin runs when type-checking fails, which is when I want to take action. But it doesn't seem to allow me to change the AST so I can add the `liftIO` function. So then I tried... A `typeCheckResultAction` plugin (for lack of a better name) does allow me to change the AST, and I can use the types to guide how I do it. But it doesn't seem to run if type-checking fails, which is exactly when I want to be adding the `liftIO`s. Am I missing something about GHC's plugin system that would allow me to do what I want? Whether that be AST manipulation in a type-checking plugin, or running the `typeCheckResultAction` despite type-checking failing. Or is AST manipulation with type information impossible if type-checking fails? This is my first foray into anything GHC-related, so I apologize if this doesn't make sense, or isn't the right place to ask. Thanks, - Evan

You could set `-fdefer-type-errors` on the file, possibly using `dynflagsPlugin`. This will give your `typeCheckResultAction` an AST with all nodes containing type errors wrapped in an `evDelayedError` term. See Note [Deferring coercion errors to runtime] for more details. You can walk through the AST and replace these wrappers with `liftIO` (with the correct type and dictionary arguments) and things should work as you want. Of course, this will defer all type errors in the program, not just the ones that your plugin can solve. You could work around this by setting `log_action` to "upgrade" any type error warnings you didn't handle and arose as a result of `Reason Opt_DeferTypeErrors :: WarnReason` back to proper errors.

Another option is to use a constraint solver plugin to "tag" the locations with a coercion, and then use a CorePlugin [1] to replace the corresponding cast by a call to liftIO. I've created a constraint solver plugin to tag all the locations here: https://gist.github.com/christiaanb/5e2412bffce0fefb076d05198f94f2d8 As you can see, for:
{-# OPTIONS_GHC -fplugin=LiftIOPlugin -ddump-ds -ddump-tc -ddump-to-file #-} module Test where
import Control.Monad.IO.Class
program :: MonadIO m => m () program = putStrLn "Hello world!"
it results in the following desugar output
program = \ (@(m_a9Ky :: * -> *)) _ [Occ=Dead] -> (break<0>() putStrLn (GHC.CString.unpackCString# "Hello world!"#)) `cast` (Univ(representational plugin "tag_lift_io" :: IO, m_a9Ky) <()>_N :: IO () ~R# m_a9Ky ())
So now you'll need to make a CorePlugin to recognize that cast and replace
it with an application with `liftIO`.
Hopefully someone else can help you with suggestions on how to conjure a
proper `liftIO` out of thin air at that point in the compiler pipeline.
[1]
https://downloads.haskell.org/ghc/9.0.1/docs/html/libraries/ghc-9.0.1/GHC-Dr...
On Thu, 1 Jul 2021 at 10:24, Zubin Duggal
You could set `-fdefer-type-errors` on the file, possibly using `dynflagsPlugin`. This will give your `typeCheckResultAction` an AST with all nodes containing type errors wrapped in an `evDelayedError` term. See Note [Deferring coercion errors to runtime] for more details. You can walk through the AST and replace these wrappers with `liftIO` (with the correct type and dictionary arguments) and things should work as you want.
Of course, this will defer all type errors in the program, not just the ones that your plugin can solve. You could work around this by setting `log_action` to "upgrade" any type error warnings you didn't handle and arose as a result of `Reason Opt_DeferTypeErrors :: WarnReason` back to proper errors. _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

An issue with this approach is that it fails if you have a concrete monad instead of an mtl-style function. For example, with newtype MyIO a = MyIO (IO a) deriving newtype (Functor, Applicative, Monad, MonadIO) program :: MyIO () program = putStrLn "Hello world!" GHC will reject the program because it can't unify `IO` and `MyIO` before it can even get to the constraint solver plugin. In general, implementing a plugin like this is a nice way to understand and familiarise yourself with plugins and the GHC API, but for practical purposes it would be best to use something like the `lifted-base` or `unliftio` libraries to access lifted version of common IO operations. On 21/07/01 10:54, Christiaan Baaij wrote:
Another option is to use a constraint solver plugin to "tag" the locations with a coercion, and then use a CorePlugin [1] to replace the corresponding cast by a call to liftIO. I've created a constraint solver plugin to tag all the locations here: https://gist.github.com/christiaanb/5e2412bffce0fefb076d05198f94f2d8
As you can see, for:
{-# OPTIONS_GHC -fplugin=LiftIOPlugin -ddump-ds -ddump-tc -ddump-to-file #-} module Test where
import Control.Monad.IO.Class
program :: MonadIO m => m () program = putStrLn "Hello world!"
it results in the following desugar output
program = \ (@(m_a9Ky :: * -> *)) _ [Occ=Dead] -> (break<0>() putStrLn (GHC.CString.unpackCString# "Hello world!"#)) `cast` (Univ(representational plugin "tag_lift_io" :: IO, m_a9Ky) <()>_N :: IO () ~R# m_a9Ky ())
So now you'll need to make a CorePlugin to recognize that cast and replace it with an application with `liftIO`. Hopefully someone else can help you with suggestions on how to conjure a proper `liftIO` out of thin air at that point in the compiler pipeline.
[1] https://downloads.haskell.org/ghc/9.0.1/docs/html/libraries/ghc-9.0.1/GHC-Dr...
On Thu, 1 Jul 2021 at 10:24, Zubin Duggal
wrote: You could set `-fdefer-type-errors` on the file, possibly using `dynflagsPlugin`. This will give your `typeCheckResultAction` an AST with all nodes containing type errors wrapped in an `evDelayedError` term. See Note [Deferring coercion errors to runtime] for more details. You can walk through the AST and replace these wrappers with `liftIO` (with the correct type and dictionary arguments) and things should work as you want.
Of course, this will defer all type errors in the program, not just the ones that your plugin can solve. You could work around this by setting `log_action` to "upgrade" any type error warnings you didn't handle and arose as a result of `Reason Opt_DeferTypeErrors :: WarnReason` back to proper errors. _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

I was wrong, the constraint solver plugin is in fact called upon to solve constraints like `MyIO () ~ IO ()`, so Christiaan's method would work with suitable modifications to the plugin. On 21/07/01 18:07, Zubin Duggal wrote:
An issue with this approach is that it fails if you have a concrete monad instead of an mtl-style function.
For example, with
newtype MyIO a = MyIO (IO a) deriving newtype (Functor, Applicative, Monad, MonadIO)
program :: MyIO () program = putStrLn "Hello world!"
GHC will reject the program because it can't unify `IO` and `MyIO` before it can even get to the constraint solver plugin.
In general, implementing a plugin like this is a nice way to understand and familiarise yourself with plugins and the GHC API, but for practical purposes it would be best to use something like the `lifted-base` or `unliftio` libraries to access lifted version of common IO operations.
On 21/07/01 10:54, Christiaan Baaij wrote:
Another option is to use a constraint solver plugin to "tag" the locations with a coercion, and then use a CorePlugin [1] to replace the corresponding cast by a call to liftIO. I've created a constraint solver plugin to tag all the locations here: https://gist.github.com/christiaanb/5e2412bffce0fefb076d05198f94f2d8
As you can see, for:
{-# OPTIONS_GHC -fplugin=LiftIOPlugin -ddump-ds -ddump-tc -ddump-to-file #-} module Test where
import Control.Monad.IO.Class
program :: MonadIO m => m () program = putStrLn "Hello world!"
it results in the following desugar output
program = \ (@(m_a9Ky :: * -> *)) _ [Occ=Dead] -> (break<0>() putStrLn (GHC.CString.unpackCString# "Hello world!"#)) `cast` (Univ(representational plugin "tag_lift_io" :: IO, m_a9Ky) <()>_N :: IO () ~R# m_a9Ky ())
So now you'll need to make a CorePlugin to recognize that cast and replace it with an application with `liftIO`. Hopefully someone else can help you with suggestions on how to conjure a proper `liftIO` out of thin air at that point in the compiler pipeline.
[1] https://downloads.haskell.org/ghc/9.0.1/docs/html/libraries/ghc-9.0.1/GHC-Dr...
On Thu, 1 Jul 2021 at 10:24, Zubin Duggal
wrote: You could set `-fdefer-type-errors` on the file, possibly using `dynflagsPlugin`. This will give your `typeCheckResultAction` an AST with all nodes containing type errors wrapped in an `evDelayedError` term. See Note [Deferring coercion errors to runtime] for more details. You can walk through the AST and replace these wrappers with `liftIO` (with the correct type and dictionary arguments) and things should work as you want.
Of course, this will defer all type errors in the program, not just the ones that your plugin can solve. You could work around this by setting `log_action` to "upgrade" any type error warnings you didn't handle and arose as a result of `Reason Opt_DeferTypeErrors :: WarnReason` back to proper errors. _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
participants (3)
-
Christiaan Baaij
-
Evan Relf
-
Zubin Duggal