Skip to content
Snippets Groups Projects
Forked from Glasgow Haskell Compiler / GHC
5893 commits behind the upstream repository.
  • Vladislav Zavialov's avatar
    178c1fd8
    Check if the SDoc starts with a single quote (#22488) · 178c1fd8
    Vladislav Zavialov authored and Marge Bot's avatar Marge Bot committed
    This patch fixes pretty-printing of character literals
    inside promoted lists and tuples.
    
    When we pretty-print a promoted list or tuple whose first element
    starts with a single quote, we want to add a space between the opening
    bracket and the element:
    
    	'[True]    -- ok
    	'[ 'True]  -- ok
    	'['True]   -- not ok
    
    If we don't add the space, we accidentally produce a character
    literal '['.
    
    Before this patch, pprSpaceIfPromotedTyCon inspected the type as an AST
    and tried to guess if it would be rendered with a single quote. However,
    it missed the case when the inner type was itself a character literal:
    
    	'[ 'x']  -- ok
    	'['x']   -- not ok
    
    Instead of adding this particular case, I opted for a more future-proof
    solution: check the SDoc directly. This way we can detect if the single
    quote is actually there instead of trying to predict it from the AST.
    The new function is called spaceIfSingleQuote.
    178c1fd8
    History
    Check if the SDoc starts with a single quote (#22488)
    Vladislav Zavialov authored and Marge Bot's avatar Marge Bot committed
    This patch fixes pretty-printing of character literals
    inside promoted lists and tuples.
    
    When we pretty-print a promoted list or tuple whose first element
    starts with a single quote, we want to add a space between the opening
    bracket and the element:
    
    	'[True]    -- ok
    	'[ 'True]  -- ok
    	'['True]   -- not ok
    
    If we don't add the space, we accidentally produce a character
    literal '['.
    
    Before this patch, pprSpaceIfPromotedTyCon inspected the type as an AST
    and tried to guess if it would be rendered with a single quote. However,
    it missed the case when the inner type was itself a character literal:
    
    	'[ 'x']  -- ok
    	'['x']   -- not ok
    
    Instead of adding this particular case, I opted for a more future-proof
    solution: check the SDoc directly. This way we can detect if the single
    quote is actually there instead of trying to predict it from the AST.
    The new function is called spaceIfSingleQuote.
Code owners
Assign users and groups as approvers for specific file changes. Learn more.
T22488_docHead.hs 1.04 KiB
{-# LANGUAGE MagicHash #-}

module Main where

import Prelude hiding ((<>))
import Data.Foldable (for_, traverse_)
import Control.Monad (unless)
import Data.Maybe (listToMaybe)
import GHC.Data.FastString
import GHC.Utils.Ppr

check_docHead :: Doc -> IO ()
check_docHead d = do
  let str = renderStyle style{mode = LeftMode} d
  unless (fst (docHead d) == listToMaybe str) $
    putStrLn $ "Fail: " ++ show str

main :: IO ()
main =
  traverse_ check_docHead $
    units ++ pairs ++ triples ++ misc
  where
    units   = [id, nest 4] <*> [empty, text "", char 'x']
    ops     = [(<>), (<+>), ($$), ($+$), \a b -> hang a 4 b]
    pairs   = [id, nest 4] <*> (ops <*> units <*> units)
    triples =
      (ops <*> pairs <*> units) ++
      (ops <*> units <*> pairs)
    misc =
      [
        text "xString",
        ftext (fsLit "xFastString"),
        ftext (fsLit "") <> char 'x',
        ztext (zEncodeFS (fsLit "xFastZString")),
        ztext (zEncodeFS (fsLit "")) <> char 'x',
        ptext (mkPtrString# "xPtrString"#),
        ptext (mkPtrString# ""#)
      ]