Skip to content

Commit

Permalink
Fix interaction of operators starting with # and UnboxedSums
Browse files Browse the repository at this point in the history
  • Loading branch information
amesgen committed Sep 1, 2023
1 parent 62e2cf1 commit 8b446c9
Show file tree
Hide file tree
Showing 6 changed files with 47 additions and 2 deletions.
3 changes: 3 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,9 @@
* Put `"this"` `PackageImports` at the end. [Issue
1048](https://github.com/tweag/ormolu/issues/1048).

* Format parenthesized operators starting with a `#` correctly in the presence
of `UnboxedSums`. [Issue 1062](https://github.com/tweag/ormolu/issues/1062).

## Ormolu 0.7.1.0

* Include `base` fixity information when formatting a Haskell file that's
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
{-# LANGUAGE UnboxedSums #-}

module Foo (( #<| )) where

( #<| ) :: Int -> Int -> Int
( #<| ) = (+)

(+) = (+)
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
{-# LANGUAGE UnboxedSums #-}

module Foo (( #<| )) where

( #<| ) :: Int -> Int -> Int
( #<| ) = (+)

(+) = (+)
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
module Foo ((#<|)) where

(#<|) :: Int -> Int -> Int
(#<|) = (+)

(+) = (+)
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
module Foo (( #<| )) where

( #<| ) :: Int -> Int -> Int
( #<| ) = (+)

(+) = (+)
18 changes: 16 additions & 2 deletions src/Ormolu/Printer/Meat/Common.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}

-- | Rendering of commonly useful bits.
module Ormolu.Printer.Meat.Common
Expand All @@ -20,8 +21,9 @@ import Data.Text qualified as T
import GHC.Hs.Doc
import GHC.Hs.Extension (GhcPs)
import GHC.Hs.ImpExp
import GHC.LanguageExtensions.Type (Extension (..))
import GHC.Parser.Annotation
import GHC.Types.Name.Occurrence (OccName (..))
import GHC.Types.Name.Occurrence (OccName (..), occNameString)
import GHC.Types.Name.Reader
import GHC.Types.SourceText
import GHC.Types.SrcLoc
Expand Down Expand Up @@ -62,15 +64,27 @@ p_ieWrappedName = \case
-- | Render a @'LocatedN' 'RdrName'@.
p_rdrName :: LocatedN RdrName -> R ()
p_rdrName l = located l $ \x -> do
unboxedSums <- isExtensionEnabled UnboxedSums
let wrapper = \case
EpAnn {anns} -> case anns of
NameAnnQuote {nann_quoted} -> tickPrefix . wrapper (ann nann_quoted)
NameAnn {nann_adornment = NameParens} -> parens N
NameAnn {nann_adornment = NameParens} ->
parens N . handleUnboxedSumsAndHashInteraction
NameAnn {nann_adornment = NameBackquotes} -> backticks
-- special case for unboxed unit tuples
NameAnnOnly {nann_adornment = NameParensHash} -> const $ txt "(# #)"
_ -> id
EpAnnNotUsed -> id

-- When UnboxedSums is enabled, `(#` is a single lexeme, so we have to
-- insert spaces when we have a parenthesized operator starting with `#`.
handleUnboxedSumsAndHashInteraction
| unboxedSums,
-- Qualified names do not start wth a `#`.
Unqual (occNameString -> '#' : _) <- x =
\y -> space *> y <* space
| otherwise = id

wrapper (ann . getLoc $ l) $ case x of
Unqual occName ->
atom occName
Expand Down

0 comments on commit 8b446c9

Please sign in to comment.