Skip to content

Commit

Permalink
[ re #345 ] layout: cosmetical changes: simplifications, code formatting
Browse files Browse the repository at this point in the history
  • Loading branch information
andreasabel committed Apr 6, 2021
1 parent 6349a61 commit e996ccb
Showing 1 changed file with 26 additions and 28 deletions.
54 changes: 26 additions & 28 deletions source/src/BNFC/Backend/Haskell/CFtoLayout.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,40 +9,38 @@ module BNFC.Backend.Haskell.CFtoLayout where

import Data.List (sort)
import BNFC.CF
import BNFC.Options (TokenText)
import BNFC.Backend.Haskell.Utils
import BNFC.Options ( TokenText )
import BNFC.PrettyPrint
import BNFC.Utils ( table )
import BNFC.Backend.Haskell.Utils ( tokenTextImport, tokenTextPackParens, tokenTextUnpack )

layoutOpen = "{"
layoutClose = "}"
layoutSep = ";"

cf2Layout :: TokenText -> String -> String -> CF -> String
cf2Layout tokenText layName lexName cf = unlines $ concat
[ [ "module " ++ layName ++ " where"
[ [ "-- Generated by the BNF Converter"
, ""
, "import Prelude"
, ""
, "import " ++ lexName
, "module " ++ layName ++ " where"
, ""
, "import Prelude"
]
, tokenTextImport tokenText
, [ "import Data.Maybe (isNothing, fromJust)"
, ""
, "-- Generated by the BNF Converter"
, [ ""
, "import " ++ lexName
, ""
, "-- local parameters"
, ""
, ""
, "topLayout :: Bool"
, "topLayout = " ++ show top
, ""
, "layoutWords, layoutStopWords :: [String]"
, "layoutWords = " ++ show lay
, "layoutStopWords = " ++ show stop
, render $ prettyList 2 "layoutWords =" "[" "]" "," $ map (text . show) lay
, render $ prettyList 2 "layoutStopWords =" "[" "]" "," $ map (text . show) stop
, ""
, "-- layout separators"
, ""
, ""
, "layoutOpen, layoutClose, layoutSep :: String"
, "layoutOpen = " ++ show layoutOpen
, "layoutClose = " ++ show layoutClose
Expand All @@ -57,7 +55,7 @@ cf2Layout tokenText layName lexName cf = unlines $ concat
, " tl = tp && topLayout"
, ""
, " res :: Maybe Token -- ^ The previous token, if any."
, " -> [Block] -- ^ A stack of layout blocks."
, " -> [Block] -- ^ A stack of layout blocks."
, " -> [Token] -> [Token]"
, ""
, " -- The stack should never be empty."
Expand Down Expand Up @@ -116,8 +114,7 @@ cf2Layout tokenText layName lexName cf = unlines $ concat
, " case st of"
, " Implicit n:_"
, " | newLine pt t0 && column t0 == n"
, " && not (isNothing pt ||"
, " isTokenIn [layoutSep,layoutOpen] (fromJust pt)) ->"
, " && maybe False (not . isTokenIn [layoutSep,layoutOpen]) pt ->"
, " let b':t0':b'':_ ="
, " addToken (afterPrev pt) layoutSep (t0:b:ts')"
, " in moveAlong st' [b',t0',b''] ts'"
Expand All @@ -140,7 +137,7 @@ cf2Layout tokenText layName lexName cf = unlines $ concat
, " -- Insert a semicolon after the previous token."
, " -- unless we are the beginning of the file,"
, " -- or the previous token is a semicolon or open brace."
, " if isNothing pt || isTokenIn [layoutSep,layoutOpen] (fromJust pt)"
, " if maybe True (isTokenIn [layoutSep,layoutOpen]) pt"
, " then moveAlong st [t0] ts"
, " else let b:t0':ts' = addToken (afterPrev pt) layoutSep (t0:ts)"
, " in moveAlong st [b,t0'] ts'"
Expand All @@ -155,8 +152,8 @@ cf2Layout tokenText layName lexName cf = unlines $ concat
, " -- If we are using top-level layout, insert a semicolon after"
, " -- the last token, if there isn't one already"
, " res (Just t) [Implicit _n] []"
, " | isTokenIn [layoutSep] t = []"
, " | otherwise = addToken (nextPos t) layoutSep []"
, " | isLayoutSep t = []"
, " | otherwise = [sToken (nextPos t) layoutSep]"
, ""
, " -- At EOF in an implicit, non-top-level block: close the block"
, " res (Just t) (Implicit _ : bs) [] ="
Expand Down Expand Up @@ -218,19 +215,16 @@ cf2Layout tokenText layName lexName cf = unlines $ concat
, "-- | Get the position immediately to the right of the given token."
, "nextPos :: Token -> Position"
, "nextPos t = Pn (g + s) l (c + s + 1)"
, " where Pn g l c = position t"
, " s = tokenLength t"
, " where"
, " Pn g l c = position t"
, " s = tokenLength t"
, ""
, "-- | Create a symbol token."
, "sToken :: Position -> String -> Token"
, "sToken p s = PT p (TS " ++ tokenTextPackParens tokenText "s" ++ " i)"
, " where"
, " i = case s of"
]
, [ " " ++ show s ++ " -> " ++ show i
| (s, i) <- zip resws [1..]
, "sToken p s = PT p $ TS " ++ tokenTextPackParens tokenText "s" ++ " $ case s of"
]
, [ " _ -> error $ \"not a reserved word: \" ++ show s"
, map (" " ++) $ table " -> " $ zipWith (\ s n -> [show s, show n]) resws [1..]
, [ " _ -> error $ \"not a reserved word: \" ++ show s"
, ""
, "-- | Get the position of a token."
, "position :: Token -> Position"
Expand Down Expand Up @@ -264,6 +258,10 @@ cf2Layout tokenText layName lexName cf = unlines $ concat
, "isLayoutOpen :: Token -> Bool"
, "isLayoutOpen = isTokenIn [layoutOpen]"
, ""
, "-- | Check if a token is the layout separator token."
, "isLayoutSep :: Token -> Bool"
, "isLayoutSep = isTokenIn [layoutSep]"
, ""
, "-- | Check if a token is the layout close token."
, "isLayoutClose :: Token -> Bool"
, "isLayoutClose = isTokenIn [layoutClose]"
Expand Down

0 comments on commit e996ccb

Please sign in to comment.