Correctly handle negate for unsigned integers
[matthijs/master-project/cλash.git] / Normalize.hs
1 {-# LANGUAGE PackageImports #-}
2 --
3 -- Functions to bring a Core expression in normal form. This module provides a
4 -- top level function "normalize", and defines the actual transformation passes that
5 -- are performed.
6 --
7 module Normalize (normalizeModule) where
8
9 -- Standard modules
10 import Debug.Trace
11 import qualified Maybe
12 import qualified "transformers" Control.Monad.Trans as Trans
13 import qualified Control.Monad as Monad
14 import qualified Control.Monad.Trans.Writer as Writer
15 import qualified Data.Map as Map
16 import qualified Data.Monoid as Monoid
17 import Data.Accessor
18
19 -- GHC API
20 import CoreSyn
21 import qualified UniqSupply
22 import qualified CoreUtils
23 import qualified Type
24 import qualified TcType
25 import qualified Id
26 import qualified Var
27 import qualified VarSet
28 import qualified NameSet
29 import qualified CoreFVs
30 import qualified CoreUtils
31 import qualified MkCore
32 import Outputable ( showSDoc, ppr, nest )
33
34 -- Local imports
35 import NormalizeTypes
36 import NormalizeTools
37 import CoreTools
38 import Pretty
39
40 --------------------------------
41 -- Start of transformations
42 --------------------------------
43
44 --------------------------------
45 -- η abstraction
46 --------------------------------
47 eta, etatop :: Transform
48 eta expr | is_fun expr && not (is_lam expr) = do
49   let arg_ty = (fst . Type.splitFunTy . CoreUtils.exprType) expr
50   id <- mkInternalVar "param" arg_ty
51   change (Lam id (App expr (Var id)))
52 -- Leave all other expressions unchanged
53 eta e = return e
54 etatop = notappargs ("eta", eta)
55
56 --------------------------------
57 -- β-reduction
58 --------------------------------
59 beta, betatop :: Transform
60 -- Substitute arg for x in expr
61 beta (App (Lam x expr) arg) = change $ substitute [(x, arg)] expr
62 -- Propagate the application into the let
63 beta (App (Let binds expr) arg) = change $ Let binds (App expr arg)
64 -- Propagate the application into each of the alternatives
65 beta (App (Case scrut b ty alts) arg) = change $ Case scrut b ty' alts'
66   where 
67     alts' = map (\(con, bndrs, expr) -> (con, bndrs, (App expr arg))) alts
68     ty' = CoreUtils.applyTypeToArg ty arg
69 -- Leave all other expressions unchanged
70 beta expr = return expr
71 -- Perform this transform everywhere
72 betatop = everywhere ("beta", beta)
73
74 --------------------------------
75 -- Cast propagation
76 --------------------------------
77 -- Try to move casts as much downward as possible.
78 castprop, castproptop :: Transform
79 castprop (Cast (Let binds expr) ty) = change $ Let binds (Cast expr ty)
80 castprop expr@(Cast (Case scrut b _ alts) ty) = change (Case scrut b ty alts')
81   where
82     alts' = map (\(con, bndrs, expr) -> (con, bndrs, (Cast expr ty))) alts
83 -- Leave all other expressions unchanged
84 castprop expr = return expr
85 -- Perform this transform everywhere
86 castproptop = everywhere ("castprop", castprop)
87
88 --------------------------------
89 -- let recursification
90 --------------------------------
91 letrec, letrectop :: Transform
92 letrec (Let (NonRec b expr) res) = change $ Let (Rec [(b, expr)]) res
93 -- Leave all other expressions unchanged
94 letrec expr = return expr
95 -- Perform this transform everywhere
96 letrectop = everywhere ("letrec", letrec)
97
98 --------------------------------
99 -- let simplification
100 --------------------------------
101 letsimpl, letsimpltop :: Transform
102 -- Don't simplifiy lets that are already simple
103 letsimpl expr@(Let _ (Var _)) = return expr
104 -- Put the "in ..." value of a let in its own binding, but not when the
105 -- expression is applicable (to prevent loops with inlinefun).
106 letsimpl (Let (Rec binds) expr) | not $ is_applicable expr = do
107   id <- mkInternalVar "foo" (CoreUtils.exprType expr)
108   let bind = (id, expr)
109   change $ Let (Rec (bind:binds)) (Var id)
110 -- Leave all other expressions unchanged
111 letsimpl expr = return expr
112 -- Perform this transform everywhere
113 letsimpltop = everywhere ("letsimpl", letsimpl)
114
115 --------------------------------
116 -- let flattening
117 --------------------------------
118 letflat, letflattop :: Transform
119 letflat (Let (Rec binds) expr) = do
120   -- Turn each binding into a list of bindings (possibly containing just one
121   -- element, of course)
122   bindss <- Monad.mapM flatbind binds
123   -- Concat all the bindings
124   let binds' = concat bindss
125   -- Return the new let. We don't use change here, since possibly nothing has
126   -- changed. If anything has changed, flatbind has already flagged that
127   -- change.
128   return $ Let (Rec binds') expr
129   where
130     -- Turns a binding of a let into a multiple bindings, or any other binding
131     -- into a list with just that binding
132     flatbind :: (CoreBndr, CoreExpr) -> TransformMonad [(CoreBndr, CoreExpr)]
133     flatbind (b, Let (Rec binds) expr) = change ((b, expr):binds)
134     flatbind (b, expr) = return [(b, expr)]
135 -- Leave all other expressions unchanged
136 letflat expr = return expr
137 -- Perform this transform everywhere
138 letflattop = everywhere ("letflat", letflat)
139
140 --------------------------------
141 -- Simple let binding removal
142 --------------------------------
143 -- Remove a = b bindings from let expressions everywhere
144 letremovetop :: Transform
145 letremovetop = everywhere ("letremove", inlinebind (\(b, e) -> case e of (Var v) | not $ Id.isDataConWorkId v -> return True; otherwise -> return False))
146
147 --------------------------------
148 -- Function inlining
149 --------------------------------
150 -- Remove a = B bindings, with B :: a -> b, or B :: forall x . T, from let
151 -- expressions everywhere. This means that any value that still needs to be
152 -- applied to something else (polymorphic values need to be applied to a
153 -- Type) will be inlined, and will eventually be applied to all their
154 -- arguments.
155 --
156 -- This is a tricky function, which is prone to create loops in the
157 -- transformations. To fix this, we make sure that no transformation will
158 -- create a new let binding with a function type. These other transformations
159 -- will just not work on those function-typed values at first, but the other
160 -- transformations (in particular β-reduction) should make sure that the type
161 -- of those values eventually becomes primitive.
162 inlinenonreptop :: Transform
163 inlinenonreptop = everywhere ("inlinenonrep", inlinebind ((Monad.liftM not) . isRepr . snd))
164
165 --------------------------------
166 -- Scrutinee simplification
167 --------------------------------
168 scrutsimpl,scrutsimpltop :: Transform
169 -- Don't touch scrutinees that are already simple
170 scrutsimpl expr@(Case (Var _) _ _ _) = return expr
171 -- Replace all other cases with a let that binds the scrutinee and a new
172 -- simple scrutinee, but not when the scrutinee is applicable (to prevent
173 -- loops with inlinefun, though I don't think a scrutinee can be
174 -- applicable...)
175 scrutsimpl (Case scrut b ty alts) | not $ is_applicable scrut = do
176   id <- mkInternalVar "scrut" (CoreUtils.exprType scrut)
177   change $ Let (Rec [(id, scrut)]) (Case (Var id) b ty alts)
178 -- Leave all other expressions unchanged
179 scrutsimpl expr = return expr
180 -- Perform this transform everywhere
181 scrutsimpltop = everywhere ("scrutsimpl", scrutsimpl)
182
183 --------------------------------
184 -- Case binder wildening
185 --------------------------------
186 casewild, casewildtop :: Transform
187 casewild expr@(Case scrut b ty alts) = do
188   (bindingss, alts') <- (Monad.liftM unzip) $ mapM doalt alts
189   let bindings = concat bindingss
190   -- Replace the case with a let with bindings and a case
191   let newlet = (Let (Rec bindings) (Case scrut b ty alts'))
192   -- If there are no non-wild binders, or this case is already a simple
193   -- selector (i.e., a single alt with exactly one binding), already a simple
194   -- selector altan no bindings (i.e., no wild binders in the original case),
195   -- don't change anything, otherwise, replace the case.
196   if null bindings || length alts == 1 && length bindings == 1 then return expr else change newlet 
197   where
198   -- Generate a single wild binder, since they are all the same
199   wild = Id.mkWildId
200   -- Wilden the binders of one alt, producing a list of bindings as a
201   -- sideeffect.
202   doalt :: CoreAlt -> TransformMonad ([(CoreBndr, CoreExpr)], CoreAlt)
203   doalt (con, bndrs, expr) = do
204     bindings_maybe <- Monad.zipWithM mkextracts bndrs [0..]
205     let bindings = Maybe.catMaybes bindings_maybe
206     -- We replace the binders with wild binders only. We can leave expr
207     -- unchanged, since the new bindings bind the same vars as the original
208     -- did.
209     let newalt = (con, wildbndrs, expr)
210     return (bindings, newalt)
211     where
212       -- Make all binders wild
213       wildbndrs = map (\bndr -> Id.mkWildId (Id.idType bndr)) bndrs
214       -- Creates a case statement to retrieve the ith element from the scrutinee
215       -- and binds that to b.
216       mkextracts :: CoreBndr -> Int -> TransformMonad (Maybe (CoreBndr, CoreExpr))
217       mkextracts b i =
218         -- TODO: Use free variables instead of is_wild. is_wild is a hack.
219         if is_wild b || Type.isFunTy (Id.idType b) 
220           -- Don't create extra bindings for binders that are already wild, or
221           -- for binders that bind function types (to prevent loops with
222           -- inlinefun).
223           then return Nothing
224           else do
225             -- Create on new binder that will actually capture a value in this
226             -- case statement, and return it
227             let bty = (Id.idType b)
228             id <- mkInternalVar "sel" bty
229             let binders = take i wildbndrs ++ [id] ++ drop (i+1) wildbndrs
230             return $ Just (b, Case scrut b bty [(con, binders, Var id)])
231 -- Leave all other expressions unchanged
232 casewild expr = return expr
233 -- Perform this transform everywhere
234 casewildtop = everywhere ("casewild", casewild)
235
236 --------------------------------
237 -- Case value simplification
238 --------------------------------
239 casevalsimpl, casevalsimpltop :: Transform
240 casevalsimpl expr@(Case scrut b ty alts) = do
241   -- Try to simplify each alternative, resulting in an optional binding and a
242   -- new alternative.
243   (bindings_maybe, alts') <- (Monad.liftM unzip) $ mapM doalt alts
244   let bindings = Maybe.catMaybes bindings_maybe
245   -- Create a new let around the case, that binds of the cases values.
246   let newlet = Let (Rec bindings) (Case scrut b ty alts')
247   -- If there were no values that needed and allowed simplification, don't
248   -- change the case.
249   if null bindings then return expr else change newlet 
250   where
251     doalt :: CoreAlt -> TransformMonad (Maybe (CoreBndr, CoreExpr), CoreAlt)
252     -- Don't simplify values that are already simple
253     doalt alt@(con, bndrs, Var _) = return (Nothing, alt)
254     -- Simplify each alt by creating a new id, binding the case value to it and
255     -- replacing the case value with that id. Only do this when the case value
256     -- does not use any of the binders bound by this alternative, for that would
257     -- cause those binders to become unbound when moving the value outside of
258     -- the case statement. Also, don't create a binding for applicable
259     -- expressions, to prevent loops with inlinefun.
260     doalt (con, bndrs, expr) | (not usesvars) && (not $ is_applicable expr) = do
261       id <- mkInternalVar "caseval" (CoreUtils.exprType expr)
262       -- We don't flag a change here, since casevalsimpl will do that above
263       -- based on Just we return here.
264       return $ (Just (id, expr), (con, bndrs, Var id))
265       -- Find if any of the binders are used by expr
266       where usesvars = (not . VarSet.isEmptyVarSet . (CoreFVs.exprSomeFreeVars (`elem` bndrs))) expr
267     -- Don't simplify anything else
268     doalt alt = return (Nothing, alt)
269 -- Leave all other expressions unchanged
270 casevalsimpl expr = return expr
271 -- Perform this transform everywhere
272 casevalsimpltop = everywhere ("casevalsimpl", casevalsimpl)
273
274 --------------------------------
275 -- Case removal
276 --------------------------------
277 -- Remove case statements that have only a single alternative and only wild
278 -- binders.
279 caseremove, caseremovetop :: Transform
280 -- Replace a useless case by the value of its single alternative
281 caseremove (Case scrut b ty [(con, bndrs, expr)]) | not usesvars = change expr
282     -- Find if any of the binders are used by expr
283     where usesvars = (not . VarSet.isEmptyVarSet . (CoreFVs.exprSomeFreeVars (`elem` bndrs))) expr
284 -- Leave all other expressions unchanged
285 caseremove expr = return expr
286 -- Perform this transform everywhere
287 caseremovetop = everywhere ("caseremove", caseremove)
288
289 --------------------------------
290 -- Argument extraction
291 --------------------------------
292 -- Make sure that all arguments of a representable type are simple variables.
293 appsimpl, appsimpltop :: Transform
294 -- Don't simplify arguments that are already simple.
295 appsimpl expr@(App f (Var v)) = return expr
296 -- Simplify all representable arguments. Do this by introducing a new Let
297 -- that binds the argument and passing the new binder in the application.
298 appsimpl expr@(App f arg) = do
299   -- Check runtime representability
300   repr <- isRepr arg
301   if repr
302     then do -- Extract representable arguments
303       id <- mkInternalVar "arg" (CoreUtils.exprType arg)
304       change $ Let (Rec [(id, arg)]) (App f (Var id))
305     else -- Leave non-representable arguments unchanged
306       return expr
307 -- Leave all other expressions unchanged
308 appsimpl expr = return expr
309 -- Perform this transform everywhere
310 appsimpltop = everywhere ("appsimpl", appsimpl)
311
312 --------------------------------
313 -- Function-typed argument propagation
314 --------------------------------
315 -- Remove all applications to function-typed arguments, by duplication the
316 -- function called with the function-typed parameter replaced by the free
317 -- variables of the argument passed in.
318 argprop, argproptop :: Transform
319 -- Transform any application of a named function (i.e., skip applications of
320 -- lambda's). Also skip applications that have arguments with free type
321 -- variables, since we can't inline those.
322 argprop expr@(App _ _) | is_var fexpr = do
323   -- Find the body of the function called
324   body_maybe <- Trans.lift $ getGlobalBind f
325   case body_maybe of
326     Just body -> do
327       -- Process each of the arguments in turn
328       (args', changed) <- Writer.listen $ mapM doarg args
329       -- See if any of the arguments changed
330       case Monoid.getAny changed of
331         True -> do
332           let (newargs', newparams', oldargs) = unzip3 args'
333           let newargs = concat newargs'
334           let newparams = concat newparams'
335           -- Create a new body that consists of a lambda for all new arguments and
336           -- the old body applied to some arguments.
337           let newbody = MkCore.mkCoreLams newparams (MkCore.mkCoreApps body oldargs)
338           -- Create a new function with the same name but a new body
339           newf <- mkFunction f newbody
340           -- Replace the original application with one of the new function to the
341           -- new arguments.
342           change $ MkCore.mkCoreApps (Var newf) newargs
343         False ->
344           -- Don't change the expression if none of the arguments changed
345           return expr
346       
347     -- If we don't have a body for the function called, leave it unchanged (it
348     -- should be a primitive function then).
349     Nothing -> return expr
350   where
351     -- Find the function called and the arguments
352     (fexpr, args) = collectArgs expr
353     Var f = fexpr
354
355     -- Process a single argument and return (args, bndrs, arg), where args are
356     -- the arguments to replace the given argument in the original
357     -- application, bndrs are the binders to include in the top-level lambda
358     -- in the new function body, and arg is the argument to apply to the old
359     -- function body.
360     doarg :: CoreExpr -> TransformMonad ([CoreExpr], [CoreBndr], CoreExpr)
361     doarg arg = do
362       repr <- isRepr arg
363       bndrs <- Trans.lift getGlobalBinders
364       let interesting var = Var.isLocalVar var && (not $ var `elem` bndrs)
365       if not repr && not (is_var arg && interesting (exprToVar arg)) && not (has_free_tyvars arg) 
366         then do
367           -- Propagate all complex arguments that are not representable, but not
368           -- arguments with free type variables (since those would require types
369           -- not known yet, which will always be known eventually).
370           -- Find interesting free variables, each of which should be passed to
371           -- the new function instead of the original function argument.
372           -- 
373           -- Interesting vars are those that are local, but not available from the
374           -- top level scope (functions from this module are defined as local, but
375           -- they're not local to this function, so we can freely move references
376           -- to them into another function).
377           let free_vars = VarSet.varSetElems $ CoreFVs.exprSomeFreeVars interesting arg
378           -- Mark the current expression as changed
379           setChanged
380           return (map Var free_vars, free_vars, arg)
381         else do
382           -- Representable types will not be propagated, and arguments with free
383           -- type variables will be propagated later.
384           -- TODO: preserve original naming?
385           id <- mkBinderFor arg "param"
386           -- Just pass the original argument to the new function, which binds it
387           -- to a new id and just pass that new id to the old function body.
388           return ([arg], [id], mkReferenceTo id) 
389 -- Leave all other expressions unchanged
390 argprop expr = return expr
391 -- Perform this transform everywhere
392 argproptop = everywhere ("argprop", argprop)
393
394 --------------------------------
395 -- Function-typed argument extraction
396 --------------------------------
397 -- This transform takes any function-typed argument that cannot be propagated
398 -- (because the function that is applied to it is a builtin function), and
399 -- puts it in a brand new top level binder. This allows us to for example
400 -- apply map to a lambda expression This will not conflict with inlinefun,
401 -- since that only inlines local let bindings, not top level bindings.
402 funextract, funextracttop :: Transform
403 funextract expr@(App _ _) | is_var fexpr = do
404   body_maybe <- Trans.lift $ getGlobalBind f
405   case body_maybe of
406     -- We don't have a function body for f, so we can perform this transform.
407     Nothing -> do
408       -- Find the new arguments
409       args' <- mapM doarg args
410       -- And update the arguments. We use return instead of changed, so the
411       -- changed flag doesn't get set if none of the args got changed.
412       return $ MkCore.mkCoreApps fexpr args'
413     -- We have a function body for f, leave this application to funprop
414     Just _ -> return expr
415   where
416     -- Find the function called and the arguments
417     (fexpr, args) = collectArgs expr
418     Var f = fexpr
419     -- Change any arguments that have a function type, but are not simple yet
420     -- (ie, a variable or application). This means to create a new function
421     -- for map (\f -> ...) b, but not for map (foo a) b.
422     --
423     -- We could use is_applicable here instead of is_fun, but I think
424     -- arguments to functions could only have forall typing when existential
425     -- typing is enabled. Not sure, though.
426     doarg arg | not (is_simple arg) && is_fun arg = do
427       -- Create a new top level binding that binds the argument. Its body will
428       -- be extended with lambda expressions, to take any free variables used
429       -- by the argument expression.
430       let free_vars = VarSet.varSetElems $ CoreFVs.exprFreeVars arg
431       let body = MkCore.mkCoreLams free_vars arg
432       id <- mkBinderFor body "fun"
433       Trans.lift $ addGlobalBind id body
434       -- Replace the argument with a reference to the new function, applied to
435       -- all vars it uses.
436       change $ MkCore.mkCoreApps (Var id) (map Var free_vars)
437     -- Leave all other arguments untouched
438     doarg arg = return arg
439
440 -- Leave all other expressions unchanged
441 funextract expr = return expr
442 -- Perform this transform everywhere
443 funextracttop = everywhere ("funextract", funextract)
444
445 --------------------------------
446 -- End of transformations
447 --------------------------------
448
449
450
451
452 -- What transforms to run?
453 transforms = [argproptop, funextracttop, etatop, betatop, castproptop, letremovetop, letrectop, letsimpltop, letflattop, casewildtop, scrutsimpltop, casevalsimpltop, caseremovetop, inlinenonreptop, appsimpltop]
454
455 -- Turns the given bind into VHDL
456 normalizeModule :: 
457   UniqSupply.UniqSupply -- ^ A UniqSupply we can use
458   -> [(CoreBndr, CoreExpr)]  -- ^ All bindings we know (i.e., in the current module)
459   -> [CoreBndr]  -- ^ The bindings to generate VHDL for (i.e., the top level bindings)
460   -> [Bool] -- ^ For each of the bindings to generate VHDL for, if it is stateful
461   -> [(CoreBndr, CoreExpr)] -- ^ The resulting VHDL
462
463 normalizeModule uniqsupply bindings generate_for statefuls = runTransformSession uniqsupply $ do
464   -- Put all the bindings in this module in the tsBindings map
465   putA tsBindings (Map.fromList bindings)
466   -- (Recursively) normalize each of the requested bindings
467   mapM normalizeBind generate_for
468   -- Get all initial bindings and the ones we produced
469   bindings_map <- getA tsBindings
470   let bindings = Map.assocs bindings_map
471   normalized_bindings <- getA tsNormalized
472   -- But return only the normalized bindings
473   return $ filter ((flip VarSet.elemVarSet normalized_bindings) . fst) bindings
474
475 normalizeBind :: CoreBndr -> TransformSession ()
476 normalizeBind bndr =
477   -- Don't normalize global variables, these should be either builtin
478   -- functions or data constructors.
479   Monad.when (Var.isLocalIdVar bndr) $ do
480     -- Skip binders that have a polymorphic type, since it's impossible to
481     -- create polymorphic hardware.
482     if is_poly (Var bndr)
483       then
484         -- This should really only happen at the top level... TODO: Give
485         -- a different error if this happens down in the recursion.
486         error $ "\nNormalize.normalizeBind: Function " ++ show bndr ++ " is polymorphic, can't normalize"
487       else do
488         normalized_funcs <- getA tsNormalized
489         -- See if this function was normalized already
490         if VarSet.elemVarSet bndr normalized_funcs
491           then
492             -- Yup, don't do it again
493             return ()
494           else do
495             -- Nope, note that it has been and do it.
496             modA tsNormalized (flip VarSet.extendVarSet bndr)
497             expr_maybe <- getGlobalBind bndr
498             case expr_maybe of 
499               Just expr -> do
500                 -- Introduce an empty Let at the top level, so there will always be
501                 -- a let in the expression (none of the transformations will remove
502                 -- the last let).
503                 let expr' = Let (Rec []) expr
504                 -- Normalize this expression
505                 trace ("Transforming " ++ (show bndr) ++ "\nBefore:\n\n" ++ showSDoc ( ppr expr' ) ++ "\n") $ return ()
506                 expr' <- dotransforms transforms expr'
507                 trace ("\nAfter:\n\n" ++ showSDoc ( ppr expr')) $ return ()
508                 -- And store the normalized version in the session
509                 modA tsBindings (Map.insert bndr expr')
510                 -- Find all vars used with a function type. All of these should be global
511                 -- binders (i.e., functions used), since any local binders with a function
512                 -- type should have been inlined already.
513                 let used_funcs_set = CoreFVs.exprSomeFreeVars (\v -> (Type.isFunTy . snd . Type.splitForAllTys . Id.idType) v) expr'
514                 let used_funcs = VarSet.varSetElems used_funcs_set
515                 -- Process each of the used functions recursively
516                 mapM normalizeBind used_funcs
517                 -- FIXME: Can't we inline these 'implicit' function calls or something?
518                 -- TODO: Add an extra let expression to the current finding, so the VHDL
519                 --       Will make a signa assignment for this 'implicit' function call
520                 --
521                 -- Find all the other free variables used that are used. This applies to
522                 -- variables that are actually a reference to a Class function. Example:
523                 --
524                 -- functiontest :: SizedInt D8 -> SizedInt D8
525                 -- functiontest = \a -> let r = a + 1 in r
526                 --
527                 -- The literal(Lit) '1' will be turned into a variable (Var)
528                 -- As it will call the 'fromInteger' class function that belongs
529                 -- to the Num class. So we need to translate the refenced function
530                 -- let used_vars_set = CoreFVs.exprSomeFreeVars (\v -> (Type.isAlgType . snd . Type.splitForAllTys . Id.idType) v) expr'
531                 -- let used_vars = VarSet.varSetElems used_vars_set
532                 -- -- Filter for dictionary args, they should not be translated
533                 -- -- FIXME: check for other non-translatable stuff as well
534                 -- let trans_vars = filter (\v -> (not . TcType.isDictTy . Id.idType) v) used_vars
535                 -- mapM normalizeBind trans_vars
536                 return ()
537               -- We don't have a value for this binder. This really shouldn't
538               -- happen for local id's...
539               Nothing -> error $ "\nNormalize.normalizeBind: No value found for binder " ++ pprString bndr ++ "? This should not happen!"