[commit: ghc] master: Add "ticks-exhausted" comment (47b3f58)
git at git.haskell.org
git at git.haskell.org
Tue Jan 26 10:48:40 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/47b3f58889caa71bf096a149e58c2a9b94b75a7d/ghc
>---------------------------------------------------------------
commit 47b3f58889caa71bf096a149e58c2a9b94b75a7d
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Tue Jan 26 09:24:33 2016 +0000
Add "ticks-exhausted" comment
This code deliberately builds a subtle negative-occurrence-of-data-type
example, described in the paper, so with -O it'll give "simplifier
ticks exhausted".
This patch just adds a comment to explain.
>---------------------------------------------------------------
47b3f58889caa71bf096a149e58c2a9b94b75a7d
testsuite/tests/dependent/should_compile/dynamic-paper.hs | 7 +++++++
1 file changed, 7 insertions(+)
diff --git a/testsuite/tests/dependent/should_compile/dynamic-paper.hs b/testsuite/tests/dependent/should_compile/dynamic-paper.hs
index 4e89209..fd63871 100644
--- a/testsuite/tests/dependent/should_compile/dynamic-paper.hs
+++ b/testsuite/tests/dependent/should_compile/dynamic-paper.hs
@@ -1,6 +1,9 @@
{- This is the code extracted from "A reflection on types", by Simon PJ,
Stephanie Weirich, Richard Eisenberg, and Dimitrios Vytiniotis, 2016. -}
+-- NB: it includes a negative-recursive function (see delta1), and
+-- so will give "simplifer ticks exhausted", at least with -O
+
{-# LANGUAGE RankNTypes, PolyKinds, TypeOperators,
ScopedTypeVariables, GADTs, FlexibleInstances,
UndecidableInstances, RebindableSyntax,
@@ -239,6 +242,10 @@ tcMaybe = TyCon { tc_module = Module { mod_pkg = "base"
rt = undefined
delta1 :: Dynamic -> Dynamic
+-- NB: this function behaves like a negative-recursive data type
+-- and hence leads compiler into an infinite inlining loop,
+-- and we get "simplifier ticks exhausted".
+-- See Section 7 of the paper "A reflection on types"
delta1 dn = case fromDynamic dn of
Just f -> f dn
Nothing -> dn
More information about the ghc-commits
mailing list