[commit: ghc] master: testsuite: Add test for #16104 (312c957)

git at git.haskell.org git at git.haskell.org
Wed Jan 16 05:52:16 UTC 2019


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/312c957f1cc7ff2ba3bc7eb258c477ed4a7e14c8/ghc

>---------------------------------------------------------------

commit 312c957f1cc7ff2ba3bc7eb258c477ed4a7e14c8
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Tue Jan 15 11:48:59 2019 -0500

    testsuite: Add test for #16104


>---------------------------------------------------------------

312c957f1cc7ff2ba3bc7eb258c477ed4a7e14c8
 testsuite/tests/plugins/T16104.hs        |  4 ++++
 testsuite/tests/plugins/T16104_Plugin.hs | 20 ++++++++++++++++++++
 testsuite/tests/plugins/all.T            |  2 ++
 3 files changed, 26 insertions(+)

diff --git a/testsuite/tests/plugins/T16104.hs b/testsuite/tests/plugins/T16104.hs
new file mode 100644
index 0000000..bfef697
--- /dev/null
+++ b/testsuite/tests/plugins/T16104.hs
@@ -0,0 +1,4 @@
+{-# OPTIONS_GHC -fplugin T16104_Plugin #-}
+
+main :: IO ()
+main = return ()
diff --git a/testsuite/tests/plugins/T16104_Plugin.hs b/testsuite/tests/plugins/T16104_Plugin.hs
new file mode 100644
index 0000000..cad54f6
--- /dev/null
+++ b/testsuite/tests/plugins/T16104_Plugin.hs
@@ -0,0 +1,20 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module TestPlugin (plugin) where
+
+import GhcPlugins
+import Data.Bits
+
+plugin :: Plugin
+plugin = defaultPlugin {installCoreToDos = install}
+  where install _ todos = return (test : todos)
+
+        test = CoreDoPluginPass "Test" check
+
+        check :: ModGuts -> CoreM ModGuts
+        check m = do mbN <- thNameToGhcName 'complement
+                     case mbN of
+                       Just _  -> liftIO $ putStrLn "Found complement!"
+                       Nothing -> error "Failed to locate complement"
+
+                     return m
diff --git a/testsuite/tests/plugins/all.T b/testsuite/tests/plugins/all.T
index da6294e..2e3be77 100644
--- a/testsuite/tests/plugins/all.T
+++ b/testsuite/tests/plugins/all.T
@@ -208,3 +208,5 @@ test('T15858',
       extra_hc_opts("-package-db plugin-recomp/pkg.plugins01/local.package.conf ")
       ],
      ghci_script, ['T15858.script'])
+
+test('T16104', default, compile, [''])



More information about the ghc-commits mailing list