Preserve the name of the expression bracket

Both `[e|...|]` and `[||]` mean the same thing, and instead of sticking to a
single style, we can just preserve what user wrote.
This commit is contained in:
Utku Demir 2019-08-16 14:19:40 +12:00 committed by Mark Karpov
parent a3559a2a07
commit e598b72be5
8 changed files with 31 additions and 12 deletions

View File

@ -1,7 +1,7 @@
{-# LANGUAGE TemplateHaskell #-}
foo =
[e|
[|
foo bar
|]

View File

@ -10,7 +10,7 @@ $$foo
foo bar
[e|booya|]
[|booya|]
-- TemplateHaskell allows Q () at the top level
do

View File

@ -10,6 +10,8 @@ module Ormolu.Printer.Combinators
( -- * The 'R' monad
R
, runR
, getAnns
, getEnclosingSpan
-- * Combinators
-- ** Basic
, txt
@ -25,6 +27,7 @@ module Ormolu.Printer.Combinators
-- ** Formatting lists
, sep
, sepSemi
, canUseBraces
, useBraces
, dontUseBraces
-- ** Wrapping

View File

@ -8,6 +8,7 @@ module Ormolu.Printer.Comments
( spitPrecedingComments
, spitFollowingComments
, spitRemainingComments
, isNewlineModified
, hasMoreComments
)
where
@ -77,7 +78,9 @@ spitFollowingComment
-> R (Maybe RealSrcSpan) -- ^ Location of this comment
spitFollowingComment (L ref a) mlastSpn = do
mnSpn <- nextEltSpan
meSpn <- getEnclosingSpan ref
-- Get first enclosing span that is not equal to reference span, i.e. it's
-- truly something enclosing the AST element.
meSpn <- getEnclosingSpan (/= ref)
newlineModified <- isNewlineModified
i <- getIndent
withPoppedComment (commentFollowsElt ref mnSpn meSpn mlastSpn) $ \l comment ->

View File

@ -76,7 +76,7 @@ data RC = RC
, rcDebug :: Bool
-- ^ Whether to print debugging info as we go
, rcEnclosingSpans :: [RealSrcSpan]
-- ^ Span of enclosing element of AST
-- ^ Spans of enclosing elements of AST
, rcAnns :: Anns
-- ^ Collection of annotations
, rcCanUseBraces :: Bool
@ -326,11 +326,13 @@ setIndent i m' = do
R (local modRC m)
traceR "set_indent_after" Nothing
-- | Get 'RealSrcSpan' of enclosing span for given referencne span.
-- | Get the first enclosing 'RealSrcSpan' that satisfies given predicate.
getEnclosingSpan :: RealSrcSpan -> R (Maybe RealSrcSpan)
getEnclosingSpan r =
listToMaybe . dropWhile (== r) <$> R (asks rcEnclosingSpans)
getEnclosingSpan
:: (RealSrcSpan -> Bool) -- ^ Predicate to use
-> R (Maybe RealSrcSpan)
getEnclosingSpan f =
listToMaybe . filter f <$> R (asks rcEnclosingSpans)
-- | Set 'RealSrcSpan' of enclosing span for the given computation.

View File

@ -20,7 +20,6 @@ import GHC hiding (GhcPs, IE)
import Name (nameStableString)
import OccName (OccName (..))
import Ormolu.Printer.Combinators
import Ormolu.Printer.Internal (getAnns)
import RdrName (RdrName (..))
-- | Data and type family style.

View File

@ -10,7 +10,6 @@ module Ormolu.Printer.Meat.Declaration.Value
)
where
import Ormolu.Printer.Internal
import Bag (bagToList)
import BasicTypes
import Control.Monad
@ -847,7 +846,12 @@ p_hsSpliceTH isTyped expr = \case
p_hsBracket :: HsBracket GhcPs -> R ()
p_hsBracket = \case
ExpBr NoExt expr -> quote "e" (located expr p_hsExpr)
ExpBr NoExt expr -> do
anns <- getEnclosingAnns
let name = case anns of
AnnOpenEQ:_ -> ""
_ -> "e"
quote name (located expr p_hsExpr)
PatBr NoExt pat -> quote "p" (located pat p_pat)
DecBrL NoExt decls -> quote "d" (p_hsDecls Free decls)
DecBrG NoExt _ -> notImplemented "DecBrG" -- result of renamer
@ -967,3 +971,12 @@ withGuards = any (checkOne . unLoc)
checkOne :: GRHS GhcPs (Located body) -> Bool
checkOne (GRHS NoExt [] _) = False
checkOne _ = True
-- | Get annotations for the enclosing element.
getEnclosingAnns :: R [AnnKeywordId]
getEnclosingAnns = do
e <- getEnclosingSpan (const True)
case e of
Nothing -> return []
Just e' -> getAnns (RealSrcSpan e')

View File

@ -16,7 +16,6 @@ import Ormolu.Imports
import Ormolu.Parser.Pragma
import Ormolu.Printer.Combinators
import Ormolu.Printer.Comments
import Ormolu.Printer.Internal (isNewlineModified)
import Ormolu.Printer.Meat.Common
import Ormolu.Printer.Meat.Declaration
import Ormolu.Printer.Meat.Declaration.Warning