Skip to content

Commit

Permalink
Use single-line layout for parens around single-line content
Browse files Browse the repository at this point in the history
  • Loading branch information
amesgen authored and mrkkrp committed Jun 13, 2024
1 parent baeba91 commit 8bc5120
Show file tree
Hide file tree
Showing 13 changed files with 38 additions and 20 deletions.
5 changes: 5 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,8 @@
## Unreleased

* Use single-line layout for parens around single-line content. [Issue
1120](https://github.com/tweag/ormolu/issues/1120).

## Ormolu 0.7.6.0

* Fix Haddock comments on infix constructors
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,6 @@ instance (Eq a) => Eq (Foo a) where

instance (Num r, V.Vector v r, Factored m r) => Num (VT v m r) where
{-# SPECIALIZE instance
( (Factored m Int) => Num (VT U.Vector m Int)
)
((Factored m Int) => Num (VT U.Vector m Int))
#-}
VT x + VT y = VT $ V.zipWith (+) x y
3 changes: 1 addition & 2 deletions data/examples/declaration/splice/typed-splice-out.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
{-# LANGUAGE TemplateHaskell #-}

x =
$$( foo bar
)
$$(foo bar)

x = $$foo
4 changes: 4 additions & 0 deletions data/examples/declaration/type/parens-comments-out.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
type Test =
( -- a
x
)
3 changes: 3 additions & 0 deletions data/examples/declaration/type/parens-comments.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
type Test = (
-- a
x)
6 changes: 2 additions & 4 deletions data/examples/declaration/value/function/application-2-out.hs
Original file line number Diff line number Diff line change
@@ -1,13 +1,11 @@
{-# LANGUAGE TemplateHaskell #-}

foo = do
$( bar
)
$(bar)
baz

foo = do
$$( bar
)
$$(bar)
baz

foo = do
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,7 @@ foo f = proc a -> (f -< a)

bar f g = proc a ->
( ( (f)
( g
)
(g)
)
-<
( ( ( ( ( ( g
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
test =
( -- a
x
)
3 changes: 3 additions & 0 deletions data/examples/declaration/value/function/parens-comments.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
test = (
-- a
x)
3 changes: 1 addition & 2 deletions src/Ormolu/Printer/Meat/Declaration/Class.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,8 +49,7 @@ p_classDecl ctx name HsQTvs {..} fixity fdeps csigs cdefs cats catdefs cdocs = d
tyFams = (getLocA &&& fmap (TyClD NoExtField . FamDecl NoExtField)) <$> cats
docs = (getLocA &&& fmap (DocD NoExtField)) <$> cdocs
tyFamDefs =
( getLocA &&& fmap (InstD NoExtField . TyFamInstD NoExtField)
)
(getLocA &&& fmap (InstD NoExtField . TyFamInstD NoExtField))
<$> catdefs
allDecls =
snd <$> sortBy (leftmost_smallest `on` fst) (sigs <> vals <> tyFams <> tyFamDefs <> docs)
Expand Down
6 changes: 2 additions & 4 deletions src/Ormolu/Printer/Meat/Declaration/Instance.hs
Original file line number Diff line number Diff line change
Expand Up @@ -70,12 +70,10 @@ p_clsInstDecl ClsInstDecl {cid_ext = (mWarnTxt, _, _), ..} = do
let sigs = (getLocA &&& fmap (SigD NoExtField)) <$> cid_sigs
vals = (getLocA &&& fmap (ValD NoExtField)) <$> toList cid_binds
tyFamInsts =
( getLocA &&& fmap (InstD NoExtField . TyFamInstD NoExtField)
)
(getLocA &&& fmap (InstD NoExtField . TyFamInstD NoExtField))
<$> cid_tyfam_insts
dataFamInsts =
( getLocA &&& fmap (InstD NoExtField . DataFamInstD NoExtField)
)
(getLocA &&& fmap (InstD NoExtField . DataFamInstD NoExtField))
<$> cid_datafam_insts
allDecls =
snd <$> sortBy (leftmost_smallest `on` fst) (sigs <> vals <> tyFamInsts <> dataFamInsts)
Expand Down
7 changes: 5 additions & 2 deletions src/Ormolu/Printer/Meat/Declaration/Value.hs
Original file line number Diff line number Diff line change
Expand Up @@ -696,8 +696,11 @@ p_hsExpr' isApp s = \case
-- negated literals, as `- 1` and `-1` have differing AST.
when (negativeLiterals && isLiteral) space
located e p_hsExpr
HsPar _ e ->
parens s (located e (dontUseBraces . p_hsExpr))
HsPar _ e -> do
csSpans <-
fmap (flip RealSrcSpan Strict.Nothing . getLoc) <$> getEnclosingComments
switchLayout (locA e : csSpans) $
parens s (located e (dontUseBraces . p_hsExpr))
SectionL _ x op -> do
located x p_hsExpr
breakpoint
Expand Down
8 changes: 6 additions & 2 deletions src/Ormolu/Printer/Meat/Type.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ module Ormolu.Printer.Meat.Type
where

import Data.Choice (pattern With)
import GHC.Data.Strict qualified as Strict
import GHC.Hs hiding (isPromoted)
import GHC.Types.SourceText
import GHC.Types.SrcLoc
Expand Down Expand Up @@ -117,8 +118,11 @@ p_hsType' multilineArgs = \case
let opTree = BinaryOpBranches (tyOpTree x) op (tyOpTree y)
p_tyOpTree
(reassociateOpTree debug (Just . unLoc) modFixityMap opTree)
HsParTy _ t ->
parens N (located t p_hsType)
HsParTy _ t -> do
csSpans <-
fmap (flip RealSrcSpan Strict.Nothing . getLoc) <$> getEnclosingComments
switchLayout (locA t : csSpans) $
parens N (located t p_hsType)
HsIParamTy _ n t -> sitcc $ do
located n atom
space
Expand Down

0 comments on commit 8bc5120

Please sign in to comment.