Skip to content
Snippets Groups Projects
Commit 7b42ece5 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli Committed by Marge Bot
Browse files

Line wrap when pp long expressions (fixes #16874)

This commit fixes #16874 by using `fsep` rather than `sep` when pretty
printing long patterns and expressions.
parent 08ad7ef4
No related branches found
No related tags found
No related merge requests found
......@@ -1077,7 +1077,7 @@ ppr_apps (HsApp _ (L _ fun) arg) args
= ppr_apps fun (Left arg : args)
ppr_apps (HsAppType _ (L _ fun) arg) args
= ppr_apps fun (Right arg : args)
ppr_apps fun args = hang (ppr_expr fun) 2 (sep (map pp args))
ppr_apps fun args = hang (ppr_expr fun) 2 (fsep (map pp args))
where
pp (Left arg) = ppr arg
-- pp (Right (LHsWcTypeX (HsWC { hswc_body = L _ arg })))
......
......@@ -584,7 +584,7 @@ pprUserCon c details = pprPrefixOcc c <+> pprConArgs details
pprConArgs :: (OutputableBndrId (GhcPass p))
=> HsConPatDetails (GhcPass p) -> SDoc
pprConArgs (PrefixCon pats) = sep (map (pprParendLPat appPrec) pats)
pprConArgs (PrefixCon pats) = fsep (map (pprParendLPat appPrec) pats)
pprConArgs (InfixCon p1 p2) = sep [ pprParendLPat appPrec p1
, pprParendLPat appPrec p2 ]
pprConArgs (RecCon rpats) = ppr rpats
......
module Main where
type A = Int
data D = D A A A A A A A A A A A A A A A A A A A A A A A A A A A A A A A A A A A A A A A A A
test :: D -> D
test (D a b c d e f g h i j k l m n o p q r s t u v w x y z aa bb cc dd ee ff gg hh ii jj kk ll mm nn)
= D a b c d e f g h i j k l m n o p q r s t u v w x y z aa bb cc dd ee ff gg hh ii jj kk ll mm nn
main :: IO ()
main = print ()
T16874.hs:8:7: error:
• The constructor ‘D’ should have 41 arguments, but has been given 40
• In the pattern:
D a b c d e f g h i j k l m n o p q r s t u v w x y z aa bb cc dd
ee ff gg hh ii jj kk ll mm nn
In an equation for ‘test’:
test
(D a b c d e f g h i j k l m n o p q r s t u v w x y z aa bb cc dd
ee ff gg hh ii jj kk ll mm nn)
= D a b c d e f g h i j k l m n o p q r s t u v w x y z aa bb cc dd
ee ff gg hh ii jj kk ll mm nn
......@@ -527,6 +527,7 @@ test('T15883e', normal, compile_fail, [''])
test('T16821', normal, compile_fail, [''])
test('T16829a', normal, compile_fail, [''])
test('T16829b', normal, compile_fail, [''])
test('T16874', normal, compile_fail, [''])
test('UnliftedNewtypesFail', normal, compile_fail, [''])
test('UnliftedNewtypesNotEnabled', normal, compile_fail, [''])
test('UnliftedNewtypesCoerceFail', normal, compile_fail, [''])
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment