Skip to content

Commit 3da1b0e

Browse files
committed
[ #358 ] fixed for cpp-nostl by copypasting the C solution
1 parent eb1d9c2 commit 3da1b0e

File tree

1 file changed

+63
-62
lines changed

1 file changed

+63
-62
lines changed

source/src/BNFC/Backend/CPP/PrettyPrinter.hs

Lines changed: 63 additions & 62 deletions
Original file line numberDiff line numberDiff line change
@@ -23,11 +23,12 @@ module BNFC.Backend.CPP.PrettyPrinter (cf2CPPPrinter, prRender) where
2323

2424
import Prelude hiding ((<>))
2525

26+
import Data.Bifunctor (second)
2627
import Data.Char (toLower)
2728
import Data.Maybe (isJust)
2829

2930
import BNFC.CF
30-
import BNFC.Utils ((+++), when)
31+
import BNFC.Utils
3132
import BNFC.Backend.Common
3233
import BNFC.Backend.Common.NamedVariables
3334
import BNFC.Backend.Common.StrUtils (renderCharOrString)
@@ -451,84 +452,84 @@ genPrintVisitorList (cat@(ListCat c), rules) =
451452

452453
genPrintVisitorList _ = error "genPrintVisitorList expects a ListCat"
453454

454-
-- | This is the only part of the pretty printer that differs significantly
455+
-- This is the only part of the pretty printer that differs significantly
455456
-- between the versions with and without STL.
457+
-- The present version has been adapted from CFtoCPrinter.
456458
genPrintVisitorListNoStl :: (Cat, [Rule]) -> String
457459
genPrintVisitorListNoStl (cat@(ListCat c), rules) = unlines $ concat
458460
[ [ "void PrintAbsyn::visit" ++ cl ++ "("++ cl ++ " *" ++ vname ++ ")"
459461
, "{"
460-
, " while(" ++ vname +++ "!= 0)"
461-
, " {"
462-
, " if (" ++ vname ++ "->" ++ vname ++ "_ == 0)"
463-
, " {"
464-
, visitMember
465-
]
466-
, optsep
467-
, [ " " ++ vname +++ "= 0;"
468-
, " }"
469-
, " else"
470-
, " {"
471-
, visitMember
472-
, render $ nest 6 $ renderListSepByPrecedence "_i_" renderSep separators
473-
, " " ++ vname +++ "=" +++ vname ++ "->" ++ vname ++ "_;"
474-
, " }"
475-
, " }"
476-
, "}"
477-
, ""
462+
, " if (" ++ vname +++ "== 0)"
463+
, " { /* nil */"
464+
]
465+
, unlessNull (swRules isNilFun) $ \ docs ->
466+
[ render $ nest 4 $ vcat docs ]
467+
, [ " }" ]
468+
, unlessNull (swRules isOneFun) $ \ docs ->
469+
[ " else if (" ++ pre ++ vname ++ "_ == 0)"
470+
, " { /* last */"
471+
, render $ nest 4 $ vcat docs
472+
, " }"
473+
]
474+
, unlessNull (swRules isConsFun) $ \ docs ->
475+
[ " else"
476+
, " { /* cons */"
477+
, render $ nest 4 $ vcat docs
478+
, " }"
479+
]
480+
, [ "}"
481+
, ""
482+
]
478483
]
479-
]
480484
where
481-
visitMember
482-
| Just t <- maybeTokenCat c =
483-
" visit" ++ t ++ "(" ++ vname ++ "->" ++ member ++ ");"
484-
| otherwise =
485-
" " ++ vname ++ "->" ++ member ++ "->accept(this);"
486-
cl = identCat (normCat cat)
487-
ecl = identCat (normCatOfList cat)
488-
vname = map toLower cl
489-
member = map toLower ecl ++ "_"
490-
optsep = if isJust (hasSingletonRule rules) || null sep' then []
491-
else [ " render(" ++ sep' ++ ");" ]
492-
sep' = snd $ renderCharOrString $ getCons rules
493-
renderSep s = "render(" <> text (snd $ renderCharOrString s) <> ")"
494-
separators = getSeparatorByPrecedence rules
485+
cl = identCat (normCat cat)
486+
vname = map toLower cl
487+
pre = vname ++ "->"
488+
prules = sortRulesByPrecedence rules
489+
swRules f = switchByPrecedence "_i_" $
490+
map (second $ sep . map text . prPrintRule_ pre) $
491+
uniqOn fst $ filter f prules
492+
-- Discard duplicates, can only handle one rule per precedence.
495493
genPrintVisitorListNoStl _ = error "genPrintVisitorListNoStl expects a ListCat"
496494

497495
--Pretty Printer methods for a rule.
498496
prPrintRule :: Maybe String -> Rule -> String
499-
prPrintRule inPackage r@(Rule fun _ cats _) | isProperLabel fun = unlines
500-
[
501-
"void PrintAbsyn::visit" ++ funName fun ++ "(" ++ funName fun +++ "*" ++ fnm ++ ")",
502-
"{",
503-
" int oldi = _i_;",
504-
lparen,
505-
cats',
506-
rparen,
507-
" _i_ = oldi;",
508-
"}",
509-
""
497+
prPrintRule inPackage r@(Rule fun _ items _) | isProperLabel fun = unlines $ concat
498+
[ [ "void PrintAbsyn::visit" ++ funName fun ++ "(" ++ funName fun +++ "*" ++ fnm ++ ")"
499+
, "{"
500+
, " int oldi = _i_;"
501+
, parenCode "_L_PAREN"
502+
, ""
503+
]
504+
, prPrintRule_ (fnm ++ "->") r
505+
, [ ""
506+
, parenCode "_R_PAREN"
507+
, " _i_ = oldi;"
508+
, "}"
509+
, ""
510+
]
510511
]
511-
where
512-
p = precRule r
513-
(lparen, rparen) =
514-
(" if (oldi > " ++ show p ++ ") render(" ++ nsDefine inPackage "_L_PAREN" ++ ");\n",
515-
" if (oldi > " ++ show p ++ ") render(" ++ nsDefine inPackage "_R_PAREN" ++ ");\n")
516-
cats' = concatMap (prPrintCat fnm) (numVars cats)
517-
fnm = "p" --old names could cause conflicts
512+
where
513+
p = precRule r
514+
parenCode x = " if (oldi > " ++ show p ++ ") render(" ++ nsDefine inPackage x ++ ");"
515+
fnm = "p" --old names could cause conflicts
518516
prPrintRule _ _ = ""
519517

518+
prPrintRule_ :: IsFun a => String -> Rul a -> [String]
519+
prPrintRule_ pre (Rule _ _ items _) = map (prPrintItem pre) $ numVars items
520+
520521
--This goes on to recurse to the instance variables.
521-
prPrintCat :: String -> Either (Cat, Doc) String -> String
522-
prPrintCat _ (Right t) = " render(" ++ t' ++ ");\n"
523-
where t' = snd (renderCharOrString t)
524-
prPrintCat fnm (Left (c, nt))
522+
prPrintItem :: String -> Either (Cat, Doc) String -> String
523+
prPrintItem _ (Right t) = " render(" ++ snd (renderCharOrString t) ++ ");"
524+
prPrintItem pre (Left (c, nt))
525525
| Just t <- maybeTokenCat c
526-
= " visit" ++ t ++ "(" ++ fnm ++ "->" ++ s ++ ");\n"
527-
| isList c = " if(" ++ fnm ++ "->" ++ s ++ ") {" ++ accept ++ "}\n"
528-
| otherwise = " " ++ accept ++ "\n"
526+
= " visit" ++ t ++ "(" ++ pre ++ s ++ ");"
527+
| isList c = " " ++ setI (precCat c) ++
528+
"visit" ++ elt ++ "(" ++ pre ++ s ++ ");"
529+
| otherwise = " " ++ setI (precCat c) ++ pre ++ s ++ "->accept(this);"
529530
where
530-
s = render nt
531-
accept = setI (precCat c) ++ fnm ++ "->" ++ s ++ "->accept(this);"
531+
s = render nt
532+
elt = identCat $ normCat c
532533

533534
{- **** Abstract Syntax Tree Printer **** -}
534535

0 commit comments

Comments
 (0)