diff --git a/compiler/specialise/SpecConstr.lhs b/compiler/specialise/SpecConstr.lhs
index c4b46aa5b22c086829112ea91ed793ed29c7c9d5..44dc6f00ef0b9c8b31fea34636bbec1e3a93e9d5 100644
--- a/compiler/specialise/SpecConstr.lhs
+++ b/compiler/specialise/SpecConstr.lhs
@@ -1,6 +1,6 @@
-ToDo [Nov 2010]
+ToDo [Oct 2013]
 ~~~~~~~~~~~~~~~
-1. Use a library type rather than an annotation for ForceSpecConstr
+1. Nuke ForceSpecConstr for good (it is subsumed by GHC.Types.SPEC in ghc-prim)
 2. Nuke NoSpecConstr
 
 %
@@ -56,7 +56,7 @@ import Data.List
 import TyCon            ( TyCon, tyConName )
 import PrelNames        ( specTyConName )
 
--- See Note [SpecConstrAnnotation]
+-- See Note [Forcing specialisation]
 #ifndef GHCI
 type SpecConstrAnnotation = ()
 #else
@@ -423,28 +423,40 @@ But fspec doesn't have decent strictness info.  As it happened,
 and hence f.  But now f's strictness is less than its arity, which
 breaks an invariant.
 
-Note [SpecConstrAnnotation]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~
-SpecConstrAnnotation is defined in GHC.Exts, and is only guaranteed to
-be available in stage 2 (well, until the bootstrap compiler can be
-guaranteed to have it)
-
-So we define it to be () in stage1 (ie when GHCI is undefined), and
-'#ifdef' out the code that uses it.
-
-See also Note [Forcing specialisation]
 
 Note [Forcing specialisation]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-With stream fusion and in other similar cases, we want to fully specialise
-some (but not necessarily all!) loops regardless of their size and the
-number of specialisations. We allow a library to specify this by annotating
-a type with ForceSpecConstr and then adding a parameter of that type to the
-loop. Here is a (simplified) example from the vector library:
+
+With stream fusion and in other similar cases, we want to fully
+specialise some (but not necessarily all!) loops regardless of their
+size and the number of specialisations.
+
+We allow a library to do this, in one of two ways (one which is
+deprecated):
+
+  1) Add a parameter of type GHC.Types.SPEC (from ghc-prim) to the loop body.
+
+  2) (Deprecated) Annotate a type with ForceSpecConstr from GHC.Exts,
+     and then add *that* type as a parameter to the loop body
+
+The reason #2 is deprecated is because it requires GHCi, which isn't
+available for things like a cross compiler using stage1.
+
+Here's a (simplified) example from the `vector` package. You may bring
+the special 'force specialization' type into scope by saying:
+
+  import GHC.Types (SPEC(..))
+
+or by defining your own type (again, deprecated):
 
   data SPEC = SPEC | SPEC2
   {-# ANN type SPEC ForceSpecConstr #-}
 
+(Note this is the exact same definition of GHC.Types.SPEC, just
+without the annotation.)
+
+After that, you say:
+
   foldl :: (a -> b -> a) -> a -> Stream b -> a
   {-# INLINE foldl #-}
   foldl f z (Stream step s _) = foldl_loop SPEC z s
@@ -494,12 +506,6 @@ can be used in Stream states and (c) some types are fixed by the user
 (e.g., the accumulator here) but we still want to specialise as much
 as possible.
 
-ForceSpecConstr is done by way of an annotation:
-  data SPEC = SPEC | SPEC2
-  {-# ANN type SPEC ForceSpecConstr #-}
-But SPEC is the *only* type so annotated, so it'd be better to
-use a particular library type.
-
 Alternatives to ForceSpecConstr
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 Instead of giving the loop an extra argument of type SPEC, we
@@ -906,7 +912,7 @@ decreaseSpecCount env n_specs
         -- See Note [Avoiding exponential blowup]
 
 ---------------------------------------------------
--- See Note [SpecConstrAnnotation]
+-- See Note [Forcing specialisation]
 ignoreType    :: ScEnv -> Type   -> Bool
 ignoreDataCon  :: ScEnv -> DataCon -> Bool
 forceSpecBndr :: ScEnv -> Var    -> Bool
diff --git a/docs/users_guide/7.8.1-notes.xml b/docs/users_guide/7.8.1-notes.xml
index eee3174e54be33a4109f460a9ef17ea5f879b85d..81ce955fb769c4cd4f10c12d0d1b50e0a46c0a4b 100644
--- a/docs/users_guide/7.8.1-notes.xml
+++ b/docs/users_guide/7.8.1-notes.xml
@@ -809,6 +809,17 @@
                      pragma.
                </para>
            </listitem>
+            <listitem>
+                <para>
+                    There is a new type exposed by
+                    <literal>GHC.Types</literal>, called
+                    <literal>SPEC</literal>, which can be used to
+                    inform GHC to perform call-pattern specialisation
+                    extremely aggressively. See <xref
+                    linkend="options-optimise"/> for more details
+                    concerning <literal>-fspec-constr</literal>.
+               </para>
+           </listitem>
        </itemizedlist>
     </sect3>
 
diff --git a/docs/users_guide/using.xml b/docs/users_guide/using.xml
index 97a650ab0d1906508ea42e3d60161dba765ce4f8..8ce96a8d598107ddc174459aeed9014b5c41c0e7 100644
--- a/docs/users_guide/using.xml
+++ b/docs/users_guide/using.xml
@@ -1616,7 +1616,7 @@ module M where
             orphan rules or instances.  The flag <option>-fwarn-auto-orphans</option>
             warns about automatically-generated orphan rules, notably as a result of
             specialising functions, for type classes (<literal>Specialise</literal>)
-            or argument values (<literal>SpecConstr</literal>).</para>
+            or argument values (<literal>-fspec-constr</literal>).</para>
         </listitem>
       </varlistentry>
 
@@ -2187,7 +2187,7 @@ f "2"    = 2
             <para><emphasis>Off by default.</emphasis>Run demand analysis
             again, at the end of the simplification pipeline.  We found some opportunities
             for discovering strictness that were not visible earlier; and optimisations like
-            <literal>SpecConstr</literal> can create functions with unused arguments which
+            <literal>-fspec-constr</literal> can create functions with unused arguments which
             are eliminated by late demand analysis.  Improvements are modest, but so is the
             cost.  See notes on the <ulink href="http://ghc.haskell.org/trac/ghc/wiki/LateDmd">Trac wiki page</ulink>.
             </para>
@@ -2475,6 +2475,44 @@ last (x : xs) = last' x xs
             strict recursive branch of the function is created similar to the
             above example.
             </para>
+
+            <para>It is also possible for library writers to instruct
+            GHC to perform call-pattern specialisation extremely
+            aggressively. This is necessary for some highly optimized
+            libraries, where we may want to specialize regardless of
+            the number of specialisations, or the size of the code. As
+            an example, consider a simplified use-case from the
+            <literal>vector</literal> library:</para>
+<programlisting>
+import GHC.Types (SPEC(..))
+
+foldl :: (a -> b -> a) -> a -> Stream b -> a
+{-# INLINE foldl #-}
+foldl f z (Stream step s _) = foldl_loop SPEC z s
+  where
+    foldl_loop !sPEC z s = case step s of
+                            Yield x s' -> foldl_loop sPEC (f z x) s'
+                            Skip       -> foldl_loop sPEC z s'
+                            Done       -> z
+</programlisting>
+
+            <para>Here, after GHC inlines the body of
+            <literal>foldl</literal> to a call site, it will perform
+            call-pattern specialization very aggressively on
+            <literal>foldl_loop</literal> due to the use of
+            <literal>SPEC</literal> in the argument of the loop
+            body. <literal>SPEC</literal> from
+            <literal>GHC.Types</literal> is specifically recognized by
+            the compiler.</para>
+
+            <para>(NB: it is extremely important you use
+            <literal>seq</literal> or a bang pattern on the
+            <literal>SPEC</literal> argument!)</para>
+
+            <para>In particular, after inlining this will
+            expose <literal>f</literal> to the loop body directly,
+            allowing heavy specialisation over the recursive
+            cases.</para>
           </listitem>
         </varlistentry>