diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs
index 614798873eba8fd5930679c93ef2cc53ed0304fd..a43aae1239c43649f33bcd026d1a68b36a902123 100644
--- a/compiler/stranal/DmdAnal.lhs
+++ b/compiler/stranal/DmdAnal.lhs
@@ -583,7 +583,7 @@ mkSigTy top_lvl rec_flag id rhs dmd_ty
     maybe_id_dmd = idDemandInfo_maybe id
 	-- Is Nothing the first time round
 
-    thunk_cpr_ok
+    thunk_cpr_ok   -- See Note [CPR for thunks]
 	| isTopLevel top_lvl       = False	-- Top level things don't get
 						-- their demandInfo set at all
 	| isRec rec_flag	   = False	-- Ditto recursive things
@@ -592,8 +592,8 @@ mkSigTy top_lvl rec_flag id rhs dmd_ty
 						-- See notes below
 \end{code}
 
-The thunk_cpr_ok stuff [CPR-AND-STRICTNESS]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Note [CPR for thunks]
+~~~~~~~~~~~~~~~~~~~~~
 If the rhs is a thunk, we usually forget the CPR info, because
 it is presumably shared (else it would have been inlined, and 
 so we'd lose sharing if w/w'd it into a function).  E.g.
@@ -653,8 +653,8 @@ have a CPR in it or not.  Simple solution:
 
 NB: strictly_demanded is never true of a top-level Id, or of a recursive Id.
 
-The Nothing case in thunk_cpr_ok [CPR-AND-STRICTNESS]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Note [Optimistic in the Nothing case]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 Demand info now has a 'Nothing' state, just like strictness info.
 The analysis works from 'dangerous' towards a 'safe' state; so we 
 start with botSig for 'Nothing' strictness infos, and we start with
@@ -1001,8 +1001,7 @@ extendSigsWithLam :: AnalEnv -> Id -> AnalEnv
 extendSigsWithLam env id
   = case idDemandInfo_maybe id of
 	Nothing	             -> extendAnalEnv NotTopLevel env id cprSig
-		-- Optimistic in the Nothing case;
-		-- See notes [CPR-AND-STRICTNESS]
+		-- See Note [Optimistic in the Nothing case]
 	Just (Eval (Prod _)) -> extendAnalEnv NotTopLevel env id cprSig
 	_                    -> env
 \end{code}
diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs
index 4b18b8ba7dcb089467ab153295b422f532234c1f..5a82b8ad9ec1787cb8274bdcce72e6f0bbc24b10 100644
--- a/compiler/stranal/WwLib.lhs
+++ b/compiler/stranal/WwLib.lhs
@@ -133,15 +133,10 @@ mkWwBodies fun_ty demands res_info one_shots
 	; (wrap_args, wrap_fn_args, work_fn_args, res_ty) <- mkWWargs emptyTvSubst fun_ty arg_info
 	; (work_args, wrap_fn_str,  work_fn_str) <- mkWWstr wrap_args
 
-        -- Don't do CPR if the worker doesn't have any value arguments
-        -- Then the worker is just a constant, so we don't want to unbox it.
-	; (wrap_fn_cpr, work_fn_cpr,  _cpr_res_ty)
-	       <- if any isId work_args then
-	             mkWWcpr res_ty res_info
-	          else
-	             return (id, id, res_ty)
-
-	; let (work_lam_args, work_call_args) = mkWorkerArgs work_args res_ty
+        -- Do CPR w/w.  See Note [Always do CPR w/w]
+	; (wrap_fn_cpr, work_fn_cpr,  cpr_res_ty) <- mkWWcpr res_ty res_info
+
+	; let (work_lam_args, work_call_args) = mkWorkerArgs work_args cpr_res_ty
 	; return ([idDemandInfo v | v <- work_call_args, isId v],
                   wrap_fn_args . wrap_fn_cpr . wrap_fn_str . applyToVars work_call_args . Var,
                   mkLams work_lam_args. work_fn_str . work_fn_cpr . work_fn_args) }
@@ -154,6 +149,18 @@ mkWwBodies fun_ty demands res_info one_shots
         -- fw from being inlined into f's RHS
 \end{code}
 
+Note [Always do CPR w/w]
+~~~~~~~~~~~~~~~~~~~~~~~~
+At one time we refrained from doing CPR w/w for thunks, on the grounds that
+we might duplicate work.  But that is already handled by the demand analyser,
+which doesn't give the CPR proprety if w/w might waste work: see
+Note [CPR for thunks] in DmdAnal.    
+
+And if something *has* been given the CPR property and we don't w/w, it's
+a disaster, because then the enclosing function might say it has the CPR
+property, but now doesn't and there a cascade of disaster.  A good example
+is Trac #5920.
+
 
 %************************************************************************
 %*									*