Skip to content

Commit

Permalink
Respect newlines in data declarations in more cases
Browse files Browse the repository at this point in the history
  • Loading branch information
mrkkrp committed Feb 5, 2024
1 parent 6cf491c commit ec9f6c4
Show file tree
Hide file tree
Showing 13 changed files with 89 additions and 41 deletions.
3 changes: 3 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,9 @@
* Now command line options for fixity overrides and module re-exports
overwrite information from `.ormolu` files. [Issue
1030](https://github.com/tweag/ormolu/issues/1030).
* Respect newlines in data declarations in more cases. [Issue
1077](https://github.com/tweag/ormolu/issues/1077) and [issue
947](https://github.com/tweag/ormolu/issues/947).

## Ormolu 0.7.3.0

Expand Down
File renamed without changes.
File renamed without changes.
6 changes: 6 additions & 0 deletions data/examples/declaration/data/ctype-1-out.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
data
{-# CTYPE "header.h" "an-ffi-type-with-along-name" #-}
AnFFITypeWithAlongName = AnFFITypeWithAlongName
{ a :: X,
b :: Y
}
6 changes: 6 additions & 0 deletions data/examples/declaration/data/ctype-1.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
data
{-# CTYPE "header.h" "an-ffi-type-with-along-name" #-}
AnFFITypeWithAlongName = AnFFITypeWithAlongName
{ a :: X,
b :: Y
}
Original file line number Diff line number Diff line change
@@ -1,5 +1,3 @@
module Main where

-- | Foo.
data Foo = Foo
{ -- | Something
Expand Down
Original file line number Diff line number Diff line change
@@ -1,5 +1,3 @@
module Main where

-- | Foo.

data Foo = Foo
Expand Down
11 changes: 11 additions & 0 deletions data/examples/declaration/data/field-layout/record-1-out.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
-- | Foo.
data Foo
= Foo
{ -- | Something
foo :: Foo Int Int,
-- | Something else
bar ::
Bar
Char
Char
}
10 changes: 10 additions & 0 deletions data/examples/declaration/data/field-layout/record-1.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
-- | Foo.

data Foo =
Foo
{ foo :: Foo Int Int
-- ^ Something
, bar :: Bar Char
Char
-- ^ Something else
}
7 changes: 7 additions & 0 deletions data/examples/declaration/data/field-layout/record-2-out.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
data IndexWithInfo schema
= forall x.
IndexWithInfo
{ checkedIndex :: Index schema x,
checkedIndexName :: U.Variable,
checkedIndexType :: Type x
}
7 changes: 7 additions & 0 deletions data/examples/declaration/data/field-layout/record-2.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
data IndexWithInfo schema =
forall x.
IndexWithInfo
{ checkedIndex :: Index schema x
, checkedIndexName :: U.Variable
, checkedIndexType :: Type x
}
3 changes: 2 additions & 1 deletion data/examples/declaration/data/simple-broken-out.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,8 @@
module Main where

-- | Here we go.
data Foo = Foo {unFoo :: Int}
data Foo
= Foo {unFoo :: Int}
deriving (Eq)

-- | And once again.
Expand Down
73 changes: 37 additions & 36 deletions src/Ormolu/Printer/Meat/Declaration/Data.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,42 +50,37 @@ p_dataDecl style name tyVars getTyVarLoc p_tyVar fixity HsDataDefn {..} = do
txt $ case style of
Associated -> mempty
Free -> " instance"
case unLoc <$> dd_cType of
Nothing -> pure ()
Just (CType prag header (type_, _)) -> do
space
p_sourceText prag
case header of
Nothing -> pure ()
Just (Header h _) -> space *> p_sourceText h
space
p_sourceText type_
txt " #-}"
let constructorSpans = getLocA name : fmap getTyVarLoc tyVars
sigSpans = maybeToList . fmap getLocA $ dd_kindSig
contextSpans = maybeToList . fmap getLocA $ dd_ctxt
ctypeSpans = maybeToList . fmap getLocA $ dd_cType
declHeaderSpans =
maybeToList (getLocA <$> dd_ctxt) ++ constructorSpans ++ sigSpans
switchLayout declHeaderSpans $ do
breakpoint
inci $ do
case dd_ctxt of
Nothing -> pure ()
Just ctxt -> do
located ctxt p_hsContext
space
txt "=>"
breakpoint
switchLayout constructorSpans $
p_infixDefHelper
(isInfix fixity)
True
(p_rdrName name)
(p_tyVar <$> tyVars)
forM_ dd_kindSig $ \k -> do
space
txt "::"
constructorSpans ++ sigSpans ++ contextSpans ++ ctypeSpans
switchLayout declHeaderSpans . inci $ do
case unLoc <$> dd_cType of
Nothing -> pure ()
Just (CType prag header (type_, _)) -> do
breakpoint
inci $ located k p_hsType
p_sourceText prag
case header of
Nothing -> pure ()
Just (Header h _) -> space *> p_sourceText h
space
p_sourceText type_
txt " #-}"
breakpoint
forM_ dd_ctxt p_lhsContext
switchLayout constructorSpans $
p_infixDefHelper
(isInfix fixity)
True
(p_rdrName name)
(p_tyVar <$> tyVars)
forM_ dd_kindSig $ \k -> do
space
txt "::"
breakpoint
inci $ located k p_hsType
let dd_cons' = case dd_cons of
NewTypeCon a -> [a]
DataTypeCons _ as -> as
Expand All @@ -100,12 +95,18 @@ p_dataDecl style name tyVars getTyVarLoc p_tyVar fixity HsDataDefn {..} = do
sepSemi (located' (p_conDecl False)) dd_cons'
else switchLayout (getLocA name : (getLocA <$> dd_cons')) . inci $ do
let singleConstRec = isSingleConstRec dd_cons'
compactLayoutAroundEquals =
onTheSameLine
(getLocA name)
(combineSrcSpans' (conDeclConsSpans (unLoc (head dd_cons'))))
conDeclConsSpans = \case
ConDeclGADT {..} -> getLocA <$> con_names
ConDeclH98 {..} -> getLocA con_name :| []
if hasHaddocks dd_cons'
then newline
else
if singleConstRec
then space
else breakpoint
else if singleConstRec && compactLayoutAroundEquals
then space
else breakpoint
equals
space
layout <- getLayout
Expand Down

0 comments on commit ec9f6c4

Please sign in to comment.