Skip to content

Commit

Permalink
Change a test for UnboxedSums
Browse files Browse the repository at this point in the history
The test is from mihaimaruseac#564.
  • Loading branch information
toku-sa-n committed Dec 27, 2022
1 parent a914ec0 commit d7f33ea
Show file tree
Hide file tree
Showing 3 changed files with 11 additions and 3 deletions.
2 changes: 1 addition & 1 deletion TESTS.md
Original file line number Diff line number Diff line change
Expand Up @@ -1643,7 +1643,7 @@ foo = undefined
```haskell
{-# LANGUAGE UnboxedSums #-}

f :: (# Int | Bool | String #)
f :: (# (# Int, String #) | String #) -> (# Int | String #)
```

#### Promoted types
Expand Down
7 changes: 5 additions & 2 deletions src/HIndent/Pretty.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1019,8 +1019,11 @@ prettyHsType (HsAppTy _ l r) = spaced $ fmap pretty [l, r]
prettyHsType (HsAppKindTy _ l r) = pretty l >> string " @" >> pretty r
prettyHsType (HsFunTy _ _ a b) = (pretty a >> string " -> ") |=> pretty b
prettyHsType (HsListTy _ xs) = brackets $ pretty xs
prettyHsType (HsTupleTy _ _ []) = string "()"
prettyHsType (HsTupleTy _ _ xs) = hvTuple' $ fmap pretty xs
prettyHsType (HsTupleTy _ HsUnboxedTuple []) = string "(# #)"
prettyHsType (HsTupleTy _ HsBoxedOrConstraintTuple []) = string "()"
prettyHsType (HsTupleTy _ HsUnboxedTuple xs) = hUnboxedTuple $ fmap pretty xs
prettyHsType (HsTupleTy _ HsBoxedOrConstraintTuple xs) =
hvTuple' $ fmap pretty xs
prettyHsType (HsSumTy _ xs) = unboxedSums $ hBarSep $ fmap pretty xs
-- For `HsOpTy`, we do not need a single quote for the infix operator. An
-- explicit promotion is necessary if there is a data constructor and
Expand Down
5 changes: 5 additions & 0 deletions src/HIndent/Pretty/Combinators/Lineup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ module HIndent.Pretty.Combinators.Lineup
, vTuple
, vTuple'
, hPromotedTuple
, hUnboxedTuple
, -- * Records
hvFields
, hFields
Expand Down Expand Up @@ -69,6 +70,10 @@ vTuple' = vLineup' ("(", ")")
hPromotedTuple :: [Printer ()] -> Printer ()
hPromotedTuple = promotedTupleParens . hCommaSep

-- | RUns printers to construct an unboxed tuple in a line.
hUnboxedTuple :: [Printer ()] -> Printer ()
hUnboxedTuple = unboxedSums . hCommaSep

-- | Applies 'hFields' if the result fits in a line or 'vFields' otherwise.
hvFields :: [Printer ()] -> Printer ()
hvFields = (<-|>) <$> hFields <*> vFields
Expand Down

0 comments on commit d7f33ea

Please sign in to comment.