Merge pull request #186 from sergv/unboxed-tuples

Unboxed tuples
pull/187/head
Lennart Spitzner 2018-09-30 21:19:15 +02:00 committed by GitHub
commit 6dc5561d08
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
8 changed files with 82 additions and 37 deletions

View File

@ -292,7 +292,7 @@ script:
canew) canew)
better_wait cabal new-build -j$JOBS --ghc-options="-j1 +RTS -M500M -RTS" --disable-tests --disable-benchmarks better_wait cabal new-build -j$JOBS --ghc-options="-j1 +RTS -M500M -RTS" --disable-tests --disable-benchmarks
better_wait cabal new-build -j$JOBS --ghc-options="-j1 +RTS -M500M -RTS" --enable-tests --enable-benchmarks better_wait cabal new-build -j$JOBS --ghc-options="-j1 +RTS -M500M -RTS" --enable-tests --enable-benchmarks
cabal new-test --ghc-options="-j1 +RTS -M500M -RTS" cabal new-test -j1 --ghc-options="-j1 +RTS -M500M -RTS"
;; ;;
esac esac
set +ex set +ex

View File

@ -335,8 +335,9 @@ test-suite littests
ghc-options: { ghc-options: {
-Wall -Wall
-fno-warn-unused-imports -fno-warn-unused-imports
-threaded
-rtsopts -rtsopts
-with-rtsopts "-M2G" -with-rtsopts "-M2G -N"
} }
test-suite libinterfacetests test-suite libinterfacetests

View File

@ -81,3 +81,17 @@ import Test ( type (++)
, pattern Foo , pattern Foo
, pattern (:.) , pattern (:.)
) )
###############################################################################
## UnboxedTuples + MagicHash
#test unboxed-tuple and vanilla names
{-# LANGUAGE UnboxedTuples #-}
spanKey :: (# Int, Int #) -> (# Int, Int #)
spanKey = case foo of
(# bar, baz #) -> (# baz, bar #)
#test unboxed-tuple and hashed name
{-# LANGUAGE MagicHash, UnboxedTuples #-}
spanKey :: (# Int#, Int# #) -> (# Int#, Int# #)
spanKey = case foo of
(# bar#, baz# #) -> (# baz# +# bar#, bar# #)

View File

@ -1,12 +1,13 @@
{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE QuasiQuotes #-}
module Main where module Main (main) where
#include "prelude.inc" #include "prelude.inc"
import Test.Hspec import Test.Hspec
import Test.Hspec.Runner ( hspecWith, defaultConfig, configConcurrentJobs )
import NeatInterpolation import NeatInterpolation
@ -22,6 +23,7 @@ import Language.Haskell.Brittany.Internal.Config.Types
import Language.Haskell.Brittany.Internal.Config import Language.Haskell.Brittany.Internal.Config
import Data.Coerce ( coerce ) import Data.Coerce ( coerce )
import GHC.Conc ( getNumCapabilities )
import qualified Data.Text.IO as Text.IO import qualified Data.Text.IO as Text.IO
import System.FilePath ( (</>) ) import System.FilePath ( (</>) )
@ -48,7 +50,8 @@ main = do
let groups = createChunks =<< inputs let groups = createChunks =<< inputs
inputCtxFree <- Text.IO.readFile "src-literatetests/30-tests-context-free.blt" inputCtxFree <- Text.IO.readFile "src-literatetests/30-tests-context-free.blt"
let groupsCtxFree = createChunks inputCtxFree let groupsCtxFree = createChunks inputCtxFree
hspec $ do jobs <- getNumCapabilities
hspecWith (defaultConfig { configConcurrentJobs = Just jobs }) $ do
groups `forM_` \(groupname, tests) -> do groups `forM_` \(groupname, tests) -> do
describe (Text.unpack groupname) $ tests `forM_` \(name, pend, inp) -> do describe (Text.unpack groupname) $ tests `forM_` \(name, pend, inp) -> do
(if pend then before_ pending else id) (if pend then before_ pending else id)

View File

@ -50,7 +50,12 @@ module Language.Haskell.Brittany.Internal.LayouterBasics
, appSep , appSep
, docCommaSep , docCommaSep
, docParenLSep , docParenLSep
, docParenL
, docParenR , docParenR
, docParenHashLSep
, docParenHashRSep
, docBracketL
, docBracketR
, docTick , docTick
, spacifyDocs , spacifyDocs
, briDocMToPPM , briDocMToPPM
@ -530,11 +535,33 @@ docCommaSep :: ToBriDocM BriDocNumbered
docCommaSep = appSep $ docLit $ Text.pack "," docCommaSep = appSep $ docLit $ Text.pack ","
docParenLSep :: ToBriDocM BriDocNumbered docParenLSep :: ToBriDocM BriDocNumbered
docParenLSep = appSep $ docLit $ Text.pack "(" docParenLSep = appSep docParenL
-- TODO: we don't make consistent use of these (yet). However, I think the
-- most readable approach overall might be something else: define
-- `lit = docLit . Text.pack` and `prepSep = docSeq [docSeparator, x]`.
-- I think those two would make the usage most readable.
-- lit "(" and appSep (lit "(") are understandable and short without
-- introducing a new top-level binding for all types of parentheses.
docParenL :: ToBriDocM BriDocNumbered
docParenL = docLit $ Text.pack "("
docParenR :: ToBriDocM BriDocNumbered docParenR :: ToBriDocM BriDocNumbered
docParenR = docLit $ Text.pack ")" docParenR = docLit $ Text.pack ")"
docParenHashLSep :: ToBriDocM BriDocNumbered
docParenHashLSep = docSeq [docLit $ Text.pack "(#", docSeparator]
docParenHashRSep :: ToBriDocM BriDocNumbered
docParenHashRSep = docSeq [docSeparator, docLit $ Text.pack "#)"]
docBracketL :: ToBriDocM BriDocNumbered
docBracketL = docLit $ Text.pack "["
docBracketR :: ToBriDocM BriDocNumbered
docBracketR = docLit $ Text.pack "]"
docTick :: ToBriDocM BriDocNumbered docTick :: ToBriDocM BriDocNumbered
docTick = docLit $ Text.pack "'" docTick = docLit $ Text.pack "'"

View File

@ -371,8 +371,8 @@ layoutExpr lexpr@(L _ expr) = do
$ \(arg, exprM) -> docWrapNode arg $ maybe docEmpty layoutExpr exprM $ \(arg, exprM) -> docWrapNode arg $ maybe docEmpty layoutExpr exprM
hasComments <- hasAnyCommentsBelow lexpr hasComments <- hasAnyCommentsBelow lexpr
let (openLit, closeLit) = case boxity of let (openLit, closeLit) = case boxity of
Boxed -> (docLit $ Text.pack "(", docLit $ Text.pack ")") Boxed -> (docLit $ Text.pack "(", docLit $ Text.pack ")")
Unboxed -> (docLit $ Text.pack "(#", docLit $ Text.pack "#)") Unboxed -> (docParenHashLSep, docParenHashRSep)
case splitFirstLast argDocs of case splitFirstLast argDocs of
FirstLastEmpty -> docSeq FirstLastEmpty -> docSeq
[ openLit [ openLit

View File

@ -140,8 +140,8 @@ layoutPat lpat@(L _ pat) = docWrapNode lpat $ case pat of
-- (nestedpat1, nestedpat2, nestedpat3) -> expr -- (nestedpat1, nestedpat2, nestedpat3) -> expr
-- (#nestedpat1, nestedpat2, nestedpat3#) -> expr -- (#nestedpat1, nestedpat2, nestedpat3#) -> expr
case boxity of case boxity of
Boxed -> wrapPatListy args "(" ")" Boxed -> wrapPatListy args "()" docParenL docParenR
Unboxed -> wrapPatListy args "(#" "#)" Unboxed -> wrapPatListy args "(##)" docParenHashLSep docParenHashRSep
AsPat asName asPat -> do AsPat asName asPat -> do
-- bind@nestedpat -> expr -- bind@nestedpat -> expr
wrapPatPrepend asPat (docLit $ lrdrNameToText asName <> Text.pack "@") wrapPatPrepend asPat (docLit $ lrdrNameToText asName <> Text.pack "@")
@ -172,7 +172,7 @@ layoutPat lpat@(L _ pat) = docWrapNode lpat $ case pat of
ListPat elems _ _ -> ListPat elems _ _ ->
-- [] -> expr1 -- [] -> expr1
-- [nestedpat1, nestedpat2, nestedpat3] -> expr2 -- [nestedpat1, nestedpat2, nestedpat3] -> expr2
wrapPatListy elems "[" "]" wrapPatListy elems "[]" docBracketL docBracketR
BangPat pat1 -> do BangPat pat1 -> do
-- !nestedpat -> expr -- !nestedpat -> expr
wrapPatPrepend pat1 (docLit $ Text.pack "!") wrapPatPrepend pat1 (docLit $ Text.pack "!")
@ -212,18 +212,18 @@ wrapPatPrepend pat prepElem = do
wrapPatListy wrapPatListy
:: [Located (Pat GhcPs)] :: [Located (Pat GhcPs)]
-> String -> String
-> String -> ToBriDocM BriDocNumbered
-> ToBriDocM BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered) -> ToBriDocM (Seq BriDocNumbered)
wrapPatListy elems start end = do wrapPatListy elems both start end = do
elemDocs <- Seq.fromList elems `forM` (layoutPat >=> colsWrapPat) elemDocs <- Seq.fromList elems `forM` (layoutPat >=> colsWrapPat)
sDoc <- docLit $ Text.pack start
eDoc <- docLit $ Text.pack end
case Seq.viewl elemDocs of case Seq.viewl elemDocs of
Seq.EmptyL -> fmap Seq.singleton $ docLit $ Text.pack $ start ++ end Seq.EmptyL -> fmap Seq.singleton $ docLit $ Text.pack both
x1 Seq.:< rest -> do x1 Seq.:< rest -> do
rest' <- rest `forM` \bd -> docSeq sDoc <- start
[ docLit $ Text.pack "," eDoc <- end
, docSeparator rest' <- rest `forM` \bd -> docSeq
, return bd [ docCommaSep
] , return bd
return $ (sDoc Seq.<| x1 Seq.<| rest') Seq.|> eDoc ]
return $ (sDoc Seq.<| x1 Seq.<| rest') Seq.|> eDoc

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]
@ -392,32 +392,32 @@ layoutType ltype@(L _ typ) = docWrapNode ltype $ case typ of
unitL = docLit $ Text.pack "()" unitL = docLit $ Text.pack "()"
simpleL = do simpleL = do
docs <- docSharedWrapper layoutType `mapM` typs docs <- docSharedWrapper layoutType `mapM` typs
let end = docLit $ Text.pack ")"
lines = List.tail docs <&> \d ->
docCols ColTyOpPrefix [docCommaSep, d]
docAlt docAlt
[ docSeq $ [docLit $ Text.pack "("] [ docSeq $ [docLit $ Text.pack "("]
++ List.intersperse docCommaSep (docForceSingleline <$> docs) ++ List.intersperse docCommaSep (docForceSingleline <$> docs)
++ [docLit $ Text.pack ")"] ++ [end]
, let , let line1 = docCols ColTyOpPrefix [docParenLSep, head docs]
start = docCols ColTyOpPrefix [docParenLSep, head docs]
lines = List.tail docs <&> \d ->
docCols ColTyOpPrefix [docCommaSep, d]
end = docLit $ Text.pack ")"
in docPar in docPar
(docAddBaseY (BrIndentSpecial 2) $ start) (docAddBaseY (BrIndentSpecial 2) $ line1)
(docLines $ (docAddBaseY (BrIndentSpecial 2) <$> lines) ++ [end]) (docLines $ (docAddBaseY (BrIndentSpecial 2) <$> lines) ++ [end])
] ]
unboxedL = do unboxedL = do
docs <- docSharedWrapper layoutType `mapM` typs docs <- docSharedWrapper layoutType `mapM` typs
let start = docParenHashLSep
end = docParenHashRSep
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] line1 = 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) line1)
(docLines $ (docAddBaseY (BrIndentSpecial 2) <$> lines) ++ [end]) (docLines $ (docAddBaseY (BrIndentSpecial 2) <$> lines) ++ [end])
] ]
HsOpTy{} -> -- TODO HsOpTy{} -> -- TODO