
Hi, I'm trying to use the GHC API (8.2.2) to extract the rewrite rules from a module, but have run into some difficulties. I've written the following code (all code is also attached as files): module Main where import GHC import GHC.Paths import HscTypes main :: IO () main = do loadProj "Test.hs" loadProj :: FilePath -> IO () loadProj src = do modgutss <- runGhc (Just libdir) $ do flags <- getSessionDynFlags _ <- setSessionDynFlags flags target <- guessTarget src Nothing _ <- setTargets [target] _ <- load LoadAllTargets mod_graph <- getModuleGraph parsed_mods <- mapM parseModule mod_graph typed_mods <- mapM typecheckModule parsed_mods desug_mods <- mapM desugarModule typed_mods return $ map coreModule desug_mods let rules = map (\mg -> ( moduleNameString . moduleName $ mg_module mg , length $ mg_rules mg) ) modgutss print $ rules return () It loads Test.hs (see below my signature) which contains a single rewrite rule. Then, it obtains the ModGuts, and prints a tuple of the name of the module, and the length of the rule list. I would expect this to be ("Test", 1), but, in fact, what gets printed is ("Test", 0). For some reason, the ModGuts does not have the rewrite rule from the file. I'm guessing I'm misunderstanding something about how the GHC API works. If anyone has any advice about how to fix this code to load rewrite rules (or even where to begin looking) I would appreciate it! Thanks, Bill Hallahan Test.hs: module Test where import Prelude hiding (map) map :: (a -> b) -> [a] -> [b] map f (x:xs) = f x:map f xs map _ [] = [] {-# NOINLINE [0] map #-} {-# RULES "map/map" forall f g xs . map f (map g xs) = map (f . g) xs #-}

You might need to enable optimization for RULES to get picked up at all.
On Thu, Apr 11, 2019 at 11:03 PM Bill Hallahan
Hi,
I'm trying to use the GHC API (8.2.2) to extract the rewrite rules from a module, but have run into some difficulties. I've written the following code (all code is also attached as files):
module Main where
import GHC import GHC.Paths import HscTypes
main :: IO () main = do loadProj "Test.hs"
loadProj :: FilePath -> IO () loadProj src = do modgutss <- runGhc (Just libdir) $ do flags <- getSessionDynFlags _ <- setSessionDynFlags flags
target <- guessTarget src Nothing _ <- setTargets [target] _ <- load LoadAllTargets
mod_graph <- getModuleGraph parsed_mods <- mapM parseModule mod_graph typed_mods <- mapM typecheckModule parsed_mods desug_mods <- mapM desugarModule typed_mods
return $ map coreModule desug_mods
let rules = map (\mg -> ( moduleNameString . moduleName $ mg_module mg , length $ mg_rules mg) ) modgutss print $ rules
return ()
It loads Test.hs (see below my signature) which contains a single rewrite rule. Then, it obtains the ModGuts, and prints a tuple of the name of the module, and the length of the rule list. I would expect this to be ("Test", 1), but, in fact, what gets printed is ("Test", 0). For some reason, the ModGuts does not have the rewrite rule from the file.
I'm guessing I'm misunderstanding something about how the GHC API works. If anyone has any advice about how to fix this code to load rewrite rules (or even where to begin looking) I would appreciate it!
Thanks, Bill Hallahan
Test.hs: module Test where
import Prelude hiding (map)
map :: (a -> b) -> [a] -> [b] map f (x:xs) = f x:map f xs map _ [] = [] {-# NOINLINE [0] map #-}
{-# RULES "map/map" forall f g xs . map f (map g xs) = map (f . g) xs #-} _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
-- brandon s allbery kf8nh allbery.b@gmail.com

Thanks Brandon! Unfortunately, I don't think this is right (or at least it's not sufficient.) If I change the code to use: _ <- setSessionDynFlags $ gopt_set flags Opt_EnableRewriteRules I still read in 0 rewrite rules. (Unless I'm setting the wrong flag/not enough flags?) Bill
On Apr 11, 2019, at 11:06 PM, Brandon Allbery
wrote: You might need to enable optimization for RULES to get picked up at all.
On Thu, Apr 11, 2019 at 11:03 PM Bill Hallahan
mailto:william.hallahan@yale.edu> wrote: Hi, I'm trying to use the GHC API (8.2.2) to extract the rewrite rules from a module, but have run into some difficulties. I've written the following code (all code is also attached as files):
module Main where
import GHC import GHC.Paths import HscTypes
main :: IO () main = do loadProj "Test.hs"
loadProj :: FilePath -> IO () loadProj src = do modgutss <- runGhc (Just libdir) $ do flags <- getSessionDynFlags _ <- setSessionDynFlags flags
target <- guessTarget src Nothing _ <- setTargets [target] _ <- load LoadAllTargets
mod_graph <- getModuleGraph parsed_mods <- mapM parseModule mod_graph typed_mods <- mapM typecheckModule parsed_mods desug_mods <- mapM desugarModule typed_mods
return $ map coreModule desug_mods
let rules = map (\mg -> ( moduleNameString . moduleName $ mg_module mg , length $ mg_rules mg) ) modgutss print $ rules
return ()
It loads Test.hs (see below my signature) which contains a single rewrite rule. Then, it obtains the ModGuts, and prints a tuple of the name of the module, and the length of the rule list. I would expect this to be ("Test", 1), but, in fact, what gets printed is ("Test", 0). For some reason, the ModGuts does not have the rewrite rule from the file.
I'm guessing I'm misunderstanding something about how the GHC API works. If anyone has any advice about how to fix this code to load rewrite rules (or even where to begin looking) I would appreciate it!
Thanks, Bill Hallahan
Test.hs: module Test where
import Prelude hiding (map)
map :: (a -> b) -> [a] -> [b] map f (x:xs) = f x:map f xs map _ [] = [] {-# NOINLINE [0] map #-}
{-# RULES "map/map" forall f g xs . map f (map g xs) = map (f . g) xs #-} _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org mailto:ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
-- brandon s allbery kf8nh allbery.b@gmail.com mailto:allbery.b@gmail.com

Hi Bill, You may try to set the DynFlag Opt_IgnoreInterfacePragmas to False. If set to True,, which is the default, GHC doesn't load a lot of optimization stuff. Good luck and kind regards Roland Am Donnerstag, den 11.04.2019, 23:02 -0400 schrieb Bill Hallahan:
Hi,
I'm trying to use the GHC API (8.2.2) to extract the rewrite rules from a module, but have run into some difficulties. I've written the following code (all code is also attached as files):
module Main where
import GHC import GHC.Paths import HscTypes
main :: IO () main = do loadProj "Test.hs"
loadProj :: FilePath -> IO () loadProj src = do modgutss <- runGhc (Just libdir) $ do flags <- getSessionDynFlags _ <- setSessionDynFlags flags
target <- guessTarget src Nothing _ <- setTargets [target] _ <- load LoadAllTargets mod_graph <- getModuleGraph parsed_mods <- mapM parseModule mod_graph typed_mods <- mapM typecheckModule parsed_mods desug_mods <- mapM desugarModule typed_mods
return $ map coreModule desug_mods
let rules = map (\mg -> ( moduleNameString . moduleName $ mg_module mg , length $ mg_rules mg) ) modgutss print $ rules
return ()
It loads Test.hs (see below my signature) which contains a single rewrite rule. Then, it obtains the ModGuts, and prints a tuple of the name of the module, and the length of the rule list. I would expect this to be ("Test", 1), but, in fact, what gets printed is ("Test", 0). For some reason, the ModGuts does not have the rewrite rule from the file.
I'm guessing I'm misunderstanding something about how the GHC API works. If anyone has any advice about how to fix this code to load rewrite rules (or even where to begin looking) I would appreciate it!
Thanks, Bill Hallahan
Test.hs: module Test where
import Prelude hiding (map)
map :: (a -> b) -> [a] -> [b] map f (x:xs) = f x:map f xs map _ [] = [] {-# NOINLINE [0] map #-}
{-# RULES "map/map" forall f g xs . map f (map g xs) = map (f . g) xs #-} _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Thanks Roland. Unfortunately, this also doesn't seem to work- I tried unsetting Opt_IgnoreInterfacePragmas both with and without setting Opt_EnableRewriteRules, and no combination results in the rules being loaded. Bill
On Apr 12, 2019, at 4:25 AM, Roland Senn
wrote: Opt_IgnoreInterfacePragmas

I figured out what was happening to the rules. In case anyone finds this thread later: rules for local functions do not go in the ModGuts or CgGuts, but are instead put in the IdInfo in individual Id's. A description of this is in the [Overall plumbing for rules] note in Rules: http://hackage.haskell.org/package/ghc-8.6.1/docs/src/Rules.html -Bill
On Apr 12, 2019, at 11:04 AM, Bill Hallahan
wrote: Thanks Roland. Unfortunately, this also doesn't seem to work- I tried unsetting Opt_IgnoreInterfacePragmas both with and without setting Opt_EnableRewriteRules, and no combination results in the rules being loaded.
Bill
On Apr 12, 2019, at 4:25 AM, Roland Senn
mailto:rsx@bluewin.ch> wrote: Opt_IgnoreInterfacePragmas
participants (3)
-
Bill Hallahan
-
Brandon Allbery
-
Roland Senn