{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module BNFC.Backend.Common
( unicodeAndSymbols
, asciiKeywords
, flexEps
, switchByPrecedence
)
where
import Prelude hiding ((<>))
import Data.Bifunctor ( second )
import Data.Char
import BNFC.CF
import BNFC.Utils ( (>.>) )
import BNFC.PrettyPrint
unicodeAndSymbols :: CF -> [String]
unicodeAndSymbols :: CF -> [String]
unicodeAndSymbols CF
cf = (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (String -> Bool) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isAscii) (CF -> [String]
forall function. CFG function -> [String]
cfgKeywords CF
cf) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ CF -> [String]
forall function. CFG function -> [String]
cfgSymbols CF
cf
asciiKeywords :: CF -> [String]
asciiKeywords :: CF -> [String]
asciiKeywords = (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isAscii) ([String] -> [String]) -> (CF -> [String]) -> CF -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CF -> [String]
forall function. CFG function -> [String]
cfgKeywords
flexEps :: String
flexEps :: String
flexEps = String
"[^.\\n]?"
renderListSepByPrecedence
:: Doc
-> (String -> Doc)
-> [(Integer, String)]
-> Doc
renderListSepByPrecedence :: Doc -> (String -> Doc) -> [(Integer, String)] -> Doc
renderListSepByPrecedence Doc
var String -> Doc
render =
[Doc] -> Doc
vcat ([Doc] -> Doc)
-> ([(Integer, String)] -> [Doc]) -> [(Integer, String)] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc -> [(Integer, Doc)] -> [Doc]
switchByPrecedence Doc
var ([(Integer, Doc)] -> [Doc])
-> ([(Integer, String)] -> [(Integer, Doc)])
-> [(Integer, String)]
-> [Doc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Integer, String) -> (Integer, Doc))
-> [(Integer, String)] -> [(Integer, Doc)]
forall a b. (a -> b) -> [a] -> [b]
map ((String -> Doc) -> (Integer, String) -> (Integer, Doc)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second ((String -> Doc) -> (Integer, String) -> (Integer, Doc))
-> (String -> Doc) -> (Integer, String) -> (Integer, Doc)
forall a b. (a -> b) -> a -> b
$ String -> Doc
render (String -> Doc) -> (Doc -> Doc) -> String -> Doc
forall a b c. (a -> b) -> (b -> c) -> a -> c
>.> (Doc -> Doc -> Doc
<> Doc
";"))
switchByPrecedence
:: Doc
-> [(Integer, Doc)]
-> [Doc]
switchByPrecedence :: Doc -> [(Integer, Doc)] -> [Doc]
switchByPrecedence Doc
var = ((Integer, Doc) -> Bool) -> [(Integer, Doc)] -> [(Integer, Doc)]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> ((Integer, Doc) -> Bool) -> (Integer, Doc) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc -> Bool
isEmpty (Doc -> Bool) -> ((Integer, Doc) -> Doc) -> (Integer, Doc) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Integer, Doc) -> Doc
forall a b. (a, b) -> b
snd) ([(Integer, Doc)] -> [(Integer, Doc)])
-> ([(Integer, Doc)] -> [Doc]) -> [(Integer, Doc)] -> [Doc]
forall a b c. (a -> b) -> (b -> c) -> a -> c
>.> \case
[] -> []
[(Integer
_,Doc
doc)] -> [ Doc
doc ]
[(Integer, Doc)]
ds ->
[ Doc
"switch(" Doc -> Doc -> Doc
<> Doc
var Doc -> Doc -> Doc
<> Doc
")"
, Int -> [Doc] -> Doc
codeblock Int
2
[ Doc
"case" Doc -> Doc -> Doc
<+> Integer -> Doc
integer Integer
i Doc -> Doc -> Doc
<:> Doc
doc Doc -> Doc -> Doc
<+> Doc
"break;" | (Integer
i, Doc
doc) <- [(Integer, Doc)]
ds ]
]
where
Doc
a <:> :: Doc -> Doc -> Doc
<:> Doc
b = Doc
a Doc -> Doc -> Doc
<> Doc
":" Doc -> Doc -> Doc
<+> Doc
b