[commit: ghc] master: SimplEnv: Add Haddock headings to export list (15517f3)
git at git.haskell.org
git at git.haskell.org
Sat Mar 5 20:15:18 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/15517f3c4444e5bf5cb3da1bf909c2d418eaf741/ghc
>---------------------------------------------------------------
commit 15517f3c4444e5bf5cb3da1bf909c2d418eaf741
Author: Ben Gamari <ben at smart-cactus.org>
Date: Fri Mar 4 23:15:34 2016 +0100
SimplEnv: Add Haddock headings to export list
>---------------------------------------------------------------
15517f3c4444e5bf5cb3da1bf909c2d418eaf741
compiler/simplCore/SimplEnv.hs | 12 ++++++++----
1 file changed, 8 insertions(+), 4 deletions(-)
diff --git a/compiler/simplCore/SimplEnv.hs b/compiler/simplCore/SimplEnv.hs
index 53fe9f4..da82943 100644
--- a/compiler/simplCore/SimplEnv.hs
+++ b/compiler/simplCore/SimplEnv.hs
@@ -7,14 +7,15 @@
{-# LANGUAGE CPP #-}
module SimplEnv (
+ -- * Basic types
InId, InBind, InExpr, InAlt, InArg, InType, InBndr, InVar,
OutId, OutTyVar, OutBind, OutExpr, OutAlt, OutArg, OutType, OutBndr, OutVar,
InCoercion, OutCoercion,
- -- The simplifier mode
+ -- * The simplifier mode
setMode, getMode, updMode,
- -- Environments
+ -- * Environments
SimplEnv(..), StaticEnv, pprSimplEnv, -- Temp not abstract
mkSimplEnv, extendIdSubst,
SimplEnv.extendTvSubst, SimplEnv.extendCvSubst,
@@ -22,14 +23,16 @@ module SimplEnv (
getInScope, setInScope, setInScopeSet, modifyInScope, addNewInScopeIds,
getSimplRules,
+ -- * Substitution results
SimplSR(..), mkContEx, substId, lookupRecBndr, refineFromInScope,
+ -- * Simplifying 'Id' binders
simplNonRecBndr, simplRecBndrs,
simplBinder, simplBinders,
substTy, substTyVar, getTCvSubst,
substCo, substCoVar,
- -- Floats
+ -- * Floats
Floats, emptyFloats, isEmptyFloats, addNonRec, addFloats, extendFloats,
wrapFloats, setFloats, zapFloats, addRecFloats, mapFloats,
doFloatFromRhs, getFloatBinds
@@ -38,7 +41,7 @@ module SimplEnv (
#include "HsVersions.h"
import SimplMonad
-import CoreMonad ( SimplifierMode(..) )
+import CoreMonad ( SimplifierMode(..) )
import CoreSyn
import CoreUtils
import Var
@@ -139,6 +142,7 @@ pprSimplEnv env
type SimplIdSubst = IdEnv SimplSR -- IdId |--> OutExpr
-- See Note [Extending the Subst] in CoreSubst
+-- | A substitution result.
data SimplSR
= DoneEx OutExpr -- Completed term
| DoneId OutId -- Completed term variable
More information about the ghc-commits
mailing list