Lay out unboxed tuples in types

pull/186/head
Sergey Vinokurov 2018-09-18 09:03:28 +01:00
parent 281d7a2f81
commit 6898d3ef44
No known key found for this signature in database
GPG Key ID: D6CD29530F98D6B8
2 changed files with 10 additions and 8 deletions

View File

@ -658,5 +658,6 @@ spanKey = case foo of
#test unboxed-tuple and hashed name #test unboxed-tuple and hashed name
{-# LANGUAGE MagicHash, UnboxedTuples #-} {-# LANGUAGE MagicHash, UnboxedTuples #-}
spanKey :: _ -> (# Int#, Int# #)
spanKey = case foo of spanKey = case foo of
(# bar#, baz# #) -> (# baz# +# bar#, bar# #) (# bar#, baz# #) -> (# baz# +# bar#, bar# #)

View File

@ -234,7 +234,7 @@ layoutType ltype@(L _ typ) = docWrapNode ltype $ case typ of
list = List.tail cntxtDocs <&> \cntxtDoc -> list = List.tail cntxtDocs <&> \cntxtDoc ->
docCols ColTyOpPrefix docCols ColTyOpPrefix
[ docCommaSep [ docCommaSep
, docAddBaseY (BrIndentSpecial 2) , docAddBaseY (BrIndentSpecial 2)
$ cntxtDoc $ cntxtDoc
] ]
in docPar open $ docLines $ list ++ [close] in docPar open $ docLines $ list ++ [close]
@ -407,17 +407,18 @@ layoutType ltype@(L _ typ) = docWrapNode ltype $ case typ of
] ]
unboxedL = do unboxedL = do
docs <- docSharedWrapper layoutType `mapM` typs docs <- docSharedWrapper layoutType `mapM` typs
let start = docSeq [docLit $ Text.pack "(#", docSeparator]
end = docSeq [docSeparator, docLit $ Text.pack "#)"]
docAlt docAlt
[ docSeq $ [docLit $ Text.pack "(#"] [ docSeq $ [start]
++ List.intersperse docCommaSep docs ++ List.intersperse docCommaSep docs
++ [docLit $ Text.pack "#)"] ++ [end]
, let , let
start = docCols ColTyOpPrefix [docLit $ Text.pack "(#", head docs] start' = docCols ColTyOpPrefix [start, head docs]
lines = List.tail docs <&> \d -> lines = List.tail docs <&> \d ->
docCols ColTyOpPrefix [docCommaSep, d] docCols ColTyOpPrefix [docCommaSep, d]
end = docLit $ Text.pack "#)"
in docPar in docPar
(docAddBaseY (BrIndentSpecial 2) start) (docAddBaseY (BrIndentSpecial 2) start')
(docLines $ (docAddBaseY (BrIndentSpecial 2) <$> lines) ++ [end]) (docLines $ (docAddBaseY (BrIndentSpecial 2) <$> lines) ++ [end])
] ]
HsOpTy{} -> -- TODO HsOpTy{} -> -- TODO