Skip to content

Commit

Permalink
Handle pretty and base <> collision
Browse files Browse the repository at this point in the history
  • Loading branch information
AndreasLoow committed Mar 27, 2018
1 parent 7c9e859 commit 39d32fb
Show file tree
Hide file tree
Showing 34 changed files with 140 additions and 6 deletions.
5 changes: 3 additions & 2 deletions source/BNFC.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ Executable bnfc
deepseq
build-tools: alex, happy
Main-is: Main.hs
HS-source-dirs: src/
HS-source-dirs: compat src
ghc-options: -W
extensions:
FlexibleContexts
Expand All @@ -77,6 +77,7 @@ Executable bnfc
PrintBNF,
ErrM,
-- BNFC core
Prelude',
BNFC.Utils,
BNFC.CF,
BNFC.ToCNFCore,
Expand Down Expand Up @@ -202,7 +203,7 @@ Test-suite unit-tests
hspec, QuickCheck >= 2.5, HUnit,
temporary, containers, deepseq
Main-is: unit-tests.hs
HS-source-dirs: src test
HS-source-dirs: compat src test
extensions:
FlexibleContexts
LambdaCase
Expand Down
15 changes: 15 additions & 0 deletions source/compat/Prelude'.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
{-# LANGUAGE CPP #-}

-- See #227 for what's going on here.

module Prelude'
(
module P
)
where

#if __GLASGOW_HASKELL__ >= 803
import Prelude as P hiding ((<>))
#else
import Prelude as P
#endif
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/C.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
BNF Converter: C Main file
Copyright (C) 2004 Author: Michael Pellauer
Expand All @@ -18,6 +20,8 @@
-}
module BNFC.Backend.C (makeC) where

import Prelude'

import BNFC.Utils
import BNFC.CF
import BNFC.Options
Expand Down
3 changes: 3 additions & 0 deletions source/src/BNFC/Backend/C/CFtoCAbs.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
BNF Converter: C Abstract syntax
Copyright (C) 2004 Author: Michael Pellauer
Expand Down Expand Up @@ -40,6 +42,7 @@

module BNFC.Backend.C.CFtoCAbs (cf2CAbs) where

import Prelude'

import BNFC.CF
import BNFC.PrettyPrint
Expand Down
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/C/CFtoCPrinter.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
BNF Converter: C Pretty Printer printer
Copyright (C) 2004 Author: Michael Pellauer
Expand Down Expand Up @@ -41,6 +43,8 @@

module BNFC.Backend.C.CFtoCPrinter (cf2CPrinter) where

import Prelude'

import BNFC.CF
import BNFC.Utils ((+++))
import BNFC.Backend.Common (renderListSepByPrecedence)
Expand Down
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/C/CFtoCSkel.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
BNF Converter: C Skeleton generator
Copyright (C) 2004 Author: Michael Pellauer
Expand Down Expand Up @@ -39,6 +41,8 @@

module BNFC.Backend.C.CFtoCSkel (cf2CSkel) where

import Prelude'

import BNFC.CF
import BNFC.Utils ( (+++) )
import BNFC.Backend.Common.NamedVariables
Expand Down
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/C/CFtoFlexC.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
BNF Converter: C flex generator
Copyright (C) 2004 Author: Michael Pellauer
Expand Down Expand Up @@ -37,6 +39,8 @@
-}
module BNFC.Backend.C.CFtoFlexC (cf2flex, lexComments, cMacros) where

import Prelude'

import Data.Maybe (fromMaybe)

import BNFC.CF
Expand Down
4 changes: 3 additions & 1 deletion source/src/BNFC/Backend/CPP/NoSTL/CFtoCPPAbs.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude, OverloadedStrings #-}
{-
BNF Converter: C++ abstract syntax generator
Copyright (C) 2004 Author: Michael Pellauer
Expand Down Expand Up @@ -41,6 +41,8 @@

module BNFC.Backend.CPP.NoSTL.CFtoCPPAbs (cf2CPPAbs) where

import Prelude'

import BNFC.CF
import BNFC.Utils((+++),(++++))
import BNFC.Backend.Common.NamedVariables
Expand Down
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/CPP/NoSTL/CFtoCVisitSkel.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
BNF Converter: C++ Skeleton generation
Copyright (C) 2004 Author: Michael Pellauer
Expand Down Expand Up @@ -39,6 +41,8 @@

module BNFC.Backend.CPP.NoSTL.CFtoCVisitSkel (cf2CVisitSkel) where

import Prelude'

import BNFC.CF
import BNFC.Utils ((+++))
import BNFC.Backend.Common.NamedVariables
Expand Down
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/CPP/PrettyPrinter.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
**************************************************************
BNF Converter Module
Expand All @@ -22,6 +24,8 @@

module BNFC.Backend.CPP.PrettyPrinter (cf2CPPPrinter, prRender) where

import Prelude'

import BNFC.CF
import BNFC.Utils ((+++))
import BNFC.Backend.Common
Expand Down
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/CPP/STL/CFtoBisonSTL.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
BNF Converter: C++ Bison generator
Copyright (C) 2004 Author: Michael Pellauer
Expand Down Expand Up @@ -44,6 +46,8 @@

module BNFC.Backend.CPP.STL.CFtoBisonSTL (cf2Bison, union) where

import Prelude'

import Data.Char (toLower,isUpper)
import Data.List (nub, intercalate)
import Data.Maybe (fromMaybe)
Expand Down
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/Common.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,11 @@
{-# LANGUAGE NoImplicitPrelude #-}

-- | Functions common to different backends.

module BNFC.Backend.Common (renderListSepByPrecedence) where

import Prelude'

import BNFC.PrettyPrint

-- | Helper function for c-like languages that generates the code printing
Expand Down
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/Common/Makefile.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,9 @@
{-# LANGUAGE NoImplicitPrelude #-}

module BNFC.Backend.Common.Makefile where

import Prelude'

import BNFC.Options (SharedOptions(..))
import BNFC.Backend.Base (mkfile, Backend)
import BNFC.PrettyPrint
Expand Down
3 changes: 3 additions & 0 deletions source/src/BNFC/Backend/Common/NamedVariables.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
BNF Converter: Named instance variables
Expand Down Expand Up @@ -67,6 +68,8 @@ This is what this module does.

module BNFC.Backend.Common.NamedVariables where

import Prelude'

import BNFC.CF
import Data.Char (toLower)
import Data.List (nub)
Expand Down
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/Haskell/CFtoAbstract.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
BNF Converter: Abstract syntax Generator
Copyright (C) 2004 Author: Markus Forberg
Expand All @@ -19,6 +21,8 @@

module BNFC.Backend.Haskell.CFtoAbstract (cf2Abstract) where

import Prelude'

import BNFC.CF
import BNFC.Utils((+++))
import BNFC.Backend.Haskell.Utils (catToType, catvars)
Expand Down
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/Haskell/CFtoPrinter.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
BNF Converter: Pretty-printer generator
Copyright (C) 2004 Author: Aarne Ranta
Expand All @@ -19,6 +21,8 @@

module BNFC.Backend.Haskell.CFtoPrinter (cf2Printer, compareRules) where

import Prelude'

import BNFC.Backend.Haskell.Utils (hsReservedWords)
import BNFC.CF
import BNFC.Utils
Expand Down
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/Haskell/CFtoTemplate.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
BNF Converter: Template Generator
Copyright (C) 2004 Author: Markus Forberg
Expand All @@ -20,6 +22,8 @@

module BNFC.Backend.Haskell.CFtoTemplate (cf2Template) where

import Prelude'

import BNFC.Backend.Haskell.Utils (catvars)
import BNFC.CF
import BNFC.PrettyPrint
Expand Down
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/Haskell/MkErrM.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
BNF Converter: Haskell error monad
Copyright (C) 2004-2007 Author: Markus Forberg, Peter Gammie,
Expand All @@ -19,6 +21,8 @@
-}
module BNFC.Backend.Haskell.MkErrM where

import Prelude'

import BNFC.PrettyPrint

mkErrM :: String -> Bool -> Doc
Expand Down
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/Haskell/Utils.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,14 @@
{-# LANGUAGE NoImplicitPrelude #-}

module BNFC.Backend.Haskell.Utils
( parserName
, hsReservedWords
, catToType
, catvars
) where

import Prelude'

import Text.PrettyPrint
import BNFC.CF (Cat(..), identCat, normCat)
import BNFC.Utils (mkNames, NameStyle(..))
Expand Down
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/Java.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
BNF Converter: Java Top File
Copyright (C) 2004 Author: Markus Forsberg, Peter Gammie,
Expand Down Expand Up @@ -35,6 +37,8 @@

module BNFC.Backend.Java ( makeJava ) where

import Prelude'

import System.FilePath (pathSeparator, isPathSeparator)
import Data.List ( intersperse )

Expand Down
6 changes: 5 additions & 1 deletion source/src/BNFC/Backend/Java/CFtoAntlr4Lexer.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
BNF Converter: Java Antlr4 Lexer generator
Copyright (C) 2015 Author: Gabriele Paganelli
Expand Down Expand Up @@ -38,6 +40,8 @@

module BNFC.Backend.Java.CFtoAntlr4Lexer ( cf2AntlrLex ) where

import Prelude'

import Text.PrettyPrint
import BNFC.CF
import BNFC.Backend.Java.RegToAntlrLexer
Expand Down Expand Up @@ -197,4 +201,4 @@ lexMultiComment :: (String, String) -> Doc
lexMultiComment (b,e) =
"'" <> text (escapeChars b)
<>"' (.)*? '"<> text (escapeChars e)
<> "'"
<> "'"
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/Java/CFtoComposVisitor.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
BNF Converter: Java 1.5 Compositional Vistor generator
Copyright (C) 2006 Bjorn Bringert
Expand All @@ -20,6 +22,8 @@

module BNFC.Backend.Java.CFtoComposVisitor (cf2ComposVisitor) where

import Prelude'

import Data.List
import Data.Either (lefts)
import BNFC.CF
Expand Down
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/Java/CFtoFoldVisitor.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
BNF Converter: Java 1.5 Fold Vistor generator
Copyright (C) 2006 Bjorn Bringert
Expand All @@ -20,6 +22,8 @@

module BNFC.Backend.Java.CFtoFoldVisitor (cf2FoldVisitor) where

import Prelude'

import BNFC.CF
import BNFC.Backend.Java.CFtoJavaAbs15 (typename)
import BNFC.Utils ((+++))
Expand Down
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/Java/CFtoJLex15.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
BNF Converter: Java JLex generator
Copyright (C) 2004 Author: Michael Pellauer
Expand Down Expand Up @@ -39,6 +41,8 @@

module BNFC.Backend.Java.CFtoJLex15 ( cf2jlex ) where

import Prelude'

import BNFC.CF
import BNFC.Backend.Common.NamedVariables
import BNFC.Backend.Java.RegToJLex
Expand Down
4 changes: 3 additions & 1 deletion source/src/BNFC/Backend/Java/CFtoJavaAbs15.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude, OverloadedStrings #-}
{-
BNF Converter: Java 1.5 Abstract Syntax
Copyright (C) 2004 Author: Michael Pellauer, Bjorn Bringert
Expand Down Expand Up @@ -46,6 +46,8 @@

module BNFC.Backend.Java.CFtoJavaAbs15 (cf2JavaAbs, typename, cat2JavaType) where

import Prelude'

import BNFC.CF
import BNFC.Options (RecordPositions(..))
import BNFC.Utils((+++),(++++))
Expand Down
4 changes: 4 additions & 0 deletions source/src/BNFC/Backend/Java/CFtoJavaPrinter15.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}

{-
BNF Converter: Java Pretty Printer generator
Copyright (C) 2004 Author: Michael Pellauer, Bjorn Bringert
Expand Down Expand Up @@ -46,6 +48,8 @@
-}
module BNFC.Backend.Java.CFtoJavaPrinter15 ( cf2JavaPrinter ) where

import Prelude'

import BNFC.Backend.Java.CFtoJavaAbs15

import BNFC.CF
Expand Down
Loading

0 comments on commit 39d32fb

Please sign in to comment.