Skip to content

Commit

Permalink
Print unboxed expressions correctly
Browse files Browse the repository at this point in the history
This is a part of mihaimaruseac#638.
  • Loading branch information
toku-sa-n committed Dec 28, 2022
1 parent a30e6d0 commit 7e157db
Show file tree
Hide file tree
Showing 3 changed files with 15 additions and 6 deletions.
3 changes: 2 additions & 1 deletion TESTS.md
Original file line number Diff line number Diff line change
Expand Up @@ -1173,7 +1173,8 @@ Unboxed sum pattern matching.
```haskell
{-# LANGUAGE UnboxedSums #-}

f (# x | | | #) = undefined
f (# (# n, _ #) | #) = (# n | #)
f (# | b #) = (# | b #)
```

Pattern matching against a infix constructor with a module name prefix
Expand Down
13 changes: 10 additions & 3 deletions src/HIndent/Pretty.hs
Original file line number Diff line number Diff line change
Expand Up @@ -519,8 +519,14 @@ prettyHsExpr (ExplicitTuple _ full _) = horizontal <-|> vertical
fmap (\e -> unless (isMissing e) (space |=> pretty e)) full
isMissing Missing {} = True
isMissing _ = False
prettyHsExpr (ExplicitSum _ _ _ expr) =
unboxedParens $ spaced [string "|", pretty expr]
prettyHsExpr (ExplicitSum _ position numElem expr) = do
string "(#"
forM_ [1 .. numElem] $ \idx -> do
if idx == position
then string " " >> pretty expr >> string " "
else string " "
when (idx < numElem) $ string "|"
string "#)"
prettyHsExpr (HsCase _ cond arms) = do
string "case " |=> do
pretty cond
Expand Down Expand Up @@ -1258,7 +1264,8 @@ prettyPat (ParPat _ inner) = parens $ pretty inner
#endif
prettyPat (BangPat _ x) = string "!" >> pretty x
prettyPat (ListPat _ xs) = hList $ fmap pretty xs
prettyPat (TuplePat _ pats _) = hTuple $ fmap pretty pats
prettyPat (TuplePat _ pats Boxed) = hTuple $ fmap pretty pats
prettyPat (TuplePat _ pats Unboxed) = hUnboxedTuple $ fmap pretty pats
prettyPat (SumPat _ x position numElem) = do
string "(#"
forM_ [1 .. numElem] $ \idx -> do
Expand Down
5 changes: 3 additions & 2 deletions src/HIndent/Pretty/Combinators/Lineup.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,15 @@
-- | Printer combinators for lining up multiple elements.
module HIndent.Pretty.Combinators.Lineup
( -- * Tuples
hvTuple
-- * Tuples
( hvTuple
, hvTuple'
, hTuple
, vTuple
, vTuple'
, hPromotedTuple
, -- * Unboxed tuples
hvUnboxedTuple'
, hUnboxedTuple
, -- * Unboxed sums
hvUnboxedSum'
, -- * Records
Expand Down

0 comments on commit 7e157db

Please sign in to comment.