Compare commits
14 Commits
2b77142617
...
34c8fd93d7
Author | SHA1 | Date |
---|---|---|
|
34c8fd93d7 | |
|
a9091daeb9 | |
|
9c5a490938 | |
|
e38836fdab | |
|
860c8771ae | |
|
47bcdb045b | |
|
6008cb26ac | |
|
7e56701bc2 | |
|
94fcf56b28 | |
|
b057c49727 | |
|
7bf2879ac0 | |
|
e7cdff440d | |
|
91300f5316 | |
|
687b59c62f |
|
@ -170,6 +170,8 @@ test-suite brittany-test-suite
|
||||||
|
|
||||||
build-depends:
|
build-depends:
|
||||||
, hspec >= 2.8.3 && < 2.10
|
, hspec >= 2.8.3 && < 2.10
|
||||||
|
, HUnit >= 1.6.2 && < 1.7
|
||||||
|
, ansi-terminal >= 0.11.4 && < 0.12
|
||||||
, parsec ^>= 3.1.14
|
, parsec ^>= 3.1.14
|
||||||
, these ^>= 1.1
|
, these ^>= 1.1
|
||||||
hs-source-dirs: source/test-suite
|
hs-source-dirs: source/test-suite
|
||||||
|
|
|
@ -145,7 +145,7 @@ doop =
|
||||||
#expected
|
#expected
|
||||||
doop =
|
doop =
|
||||||
some long invocation == loooooooooongman + (third nested expression) - 4
|
some long invocation == loooooooooongman + (third nested expression) - 4
|
||||||
&& {- meow -} 5 - 6 > 7 `mod` loooooooooongwoman
|
&& {- meow -} 5 - 6 > 7 `mod` loooooooooongwoman
|
||||||
|| ill just invoke a function with these args
|
|| ill just invoke a function with these args
|
||||||
|| foo
|
|| foo
|
||||||
&& dooasdoiaosdoi ** oaisdoioasido
|
&& dooasdoiaosdoi ** oaisdoioasido
|
||||||
|
@ -165,7 +165,7 @@ doop =
|
||||||
-- brittany { lconfig_fixityBasedAddAlignParens: True }
|
-- brittany { lconfig_fixityBasedAddAlignParens: True }
|
||||||
doop =
|
doop =
|
||||||
( ( some long invocation == loooooooooongman + (third nested expression) - 4
|
( ( some long invocation == loooooooooongman + (third nested expression) - 4
|
||||||
&& {- meow -} 5 - 6 > 7 `mod` loooooooooongwoman
|
&& {- meow -} 5 - 6 > 7 `mod` loooooooooongwoman
|
||||||
)
|
)
|
||||||
|| ill just invoke a function with these args
|
|| ill just invoke a function with these args
|
||||||
|| ( foo
|
|| ( foo
|
||||||
|
|
|
@ -57,9 +57,9 @@ test = Proxy @'[{- comment -} 'True ]
|
||||||
#test with-comment-4
|
#test with-comment-4
|
||||||
test
|
test
|
||||||
:: Proxy '[{- comment -}
|
:: Proxy '[{- comment -}
|
||||||
'True ]
|
'True ]
|
||||||
test = Proxy @'[{- comment -}
|
test = Proxy @'[{- comment -}
|
||||||
'True ]
|
'True ]
|
||||||
|
|
||||||
#test with-comment-5
|
#test with-comment-5
|
||||||
test
|
test
|
||||||
|
@ -69,9 +69,9 @@ test = Proxy @'[{- comment -} True]
|
||||||
#test with-comment-6
|
#test with-comment-6
|
||||||
test
|
test
|
||||||
:: Proxy '[{- comment -}
|
:: Proxy '[{- comment -}
|
||||||
True]
|
True]
|
||||||
test = Proxy @'[{- comment -}
|
test = Proxy @'[{- comment -}
|
||||||
True]
|
True]
|
||||||
|
|
||||||
#test explicit-list-type non-promoted
|
#test explicit-list-type non-promoted
|
||||||
type Foo = '[Bool, Bool, Bool]
|
type Foo = '[Bool, Bool, Bool]
|
||||||
|
|
|
@ -329,11 +329,13 @@ func =
|
||||||
foooooooooooooooooooooooooooooooo
|
foooooooooooooooooooooooooooooooo
|
||||||
|
|
||||||
#test opapp-specialcasing-3
|
#test opapp-specialcasing-3
|
||||||
func = fooooooooooooooooooooooooooooooooo + foooooooooooooooooooooooooooooooo
|
func =
|
||||||
[ foooooooooooooooooooooooooooooooo
|
fooooooooooooooooooooooooooooooooo
|
||||||
, foooooooooooooooooooooooooooooooo
|
+ foooooooooooooooooooooooooooooooo
|
||||||
, foooooooooooooooooooooooooooooooo
|
[ foooooooooooooooooooooooooooooooo
|
||||||
]
|
, foooooooooooooooooooooooooooooooo
|
||||||
|
, foooooooooooooooooooooooooooooooo
|
||||||
|
]
|
||||||
|
|
||||||
#test opapp-indenting
|
#test opapp-indenting
|
||||||
parserPrim =
|
parserPrim =
|
||||||
|
@ -956,3 +958,43 @@ func = other $ meep
|
||||||
[q|hello
|
[q|hello
|
||||||
world|]
|
world|]
|
||||||
(some other very long linnnnnnnnnnnnnnnnnnnnnnnnnnnnnnnnnnnnnne)
|
(some other very long linnnnnnnnnnnnnnnnnnnnnnnnnnnnnnnnnnnnnne)
|
||||||
|
|
||||||
|
#test multiline-lambda-whitespace
|
||||||
|
func =
|
||||||
|
Text.intercalate
|
||||||
|
"\n"
|
||||||
|
( (\(abc, def) ->
|
||||||
|
abc ++ def ++ "lkajsdljkasdlkjasldjkljkasd" ++ asdasdasdasd
|
||||||
|
)
|
||||||
|
<$> mylist
|
||||||
|
)
|
||||||
|
|
||||||
|
#test operator newline behaviour
|
||||||
|
func =
|
||||||
|
fromIntegral aaaaaaaaaaaaaaaaaaa
|
||||||
|
/ fromIntegral (aaaaaaaaaaaaaaaaaaa + bbbbbbbbbbbbbbbbbb)
|
||||||
|
|
||||||
|
#test multi-constructor associated data decl
|
||||||
|
data POtfuggj
|
||||||
|
instance BMGuwigoc POtfuggj where
|
||||||
|
data KVeeweknc POtfuggj r
|
||||||
|
= ILpieakli
|
||||||
|
| USilcnhkYaraposqu (WeyOoovf (Nubwlhtjd EculdW.QaeopznkAc r))
|
||||||
|
deriving stock (Lirylfj1, Jexr)
|
||||||
|
deriving anyclass Qart2.Vrzxuvcf
|
||||||
|
|
||||||
|
#test bang-type
|
||||||
|
data LabeledBool = LabeledBool !Int !Bool
|
||||||
|
|
||||||
|
#test block-comment after let
|
||||||
|
func = do
|
||||||
|
let cipInuihz = Vuozczdm.yhEfun tuhiuRasohy
|
||||||
|
let {- CAZEB mecwbd "Caa ||" -}
|
||||||
|
doeeRbaviceQzymin a b = olivhuwqbaq
|
||||||
|
iqnz biwomeJhhujy _ _ | biwomeJhhujy < volpoqAsizmHdwpl = pure 0
|
||||||
|
pure True
|
||||||
|
|
||||||
|
#test comment-inside-decl
|
||||||
|
func False = 0
|
||||||
|
-- comment
|
||||||
|
func True = 1
|
||||||
|
|
|
@ -1278,11 +1278,13 @@ func =
|
||||||
foooooooooooooooooooooooooooooooo
|
foooooooooooooooooooooooooooooooo
|
||||||
|
|
||||||
#test opapp-specialcasing-3
|
#test opapp-specialcasing-3
|
||||||
func = fooooooooooooooooooooooooooooooooo + foooooooooooooooooooooooooooooooo
|
func =
|
||||||
[ foooooooooooooooooooooooooooooooo
|
fooooooooooooooooooooooooooooooooo
|
||||||
, foooooooooooooooooooooooooooooooo
|
+ foooooooooooooooooooooooooooooooo
|
||||||
, foooooooooooooooooooooooooooooooo
|
[ foooooooooooooooooooooooooooooooo
|
||||||
]
|
, foooooooooooooooooooooooooooooooo
|
||||||
|
, foooooooooooooooooooooooooooooooo
|
||||||
|
]
|
||||||
|
|
||||||
#test opapp-indenting
|
#test opapp-indenting
|
||||||
parserPrim =
|
parserPrim =
|
||||||
|
|
|
@ -10,6 +10,8 @@ module Language.Haskell.Brittany.Internal
|
||||||
-- re-export from utils:
|
-- re-export from utils:
|
||||||
, extractCommentConfigs
|
, extractCommentConfigs
|
||||||
, TraceFunc(TraceFunc)
|
, TraceFunc(TraceFunc)
|
||||||
|
, Splitting.splitModuleDecls
|
||||||
|
, Splitting.extractDeclMap
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
|
@ -17,7 +19,6 @@ import Control.Monad.Trans.Except
|
||||||
import Data.CZipWith
|
import Data.CZipWith
|
||||||
import qualified Data.Text as Text
|
import qualified Data.Text as Text
|
||||||
import qualified Data.Text.Lazy as TextL
|
import qualified Data.Text.Lazy as TextL
|
||||||
import qualified GHC hiding ( parseModule )
|
|
||||||
import qualified GHC.Driver.Session as GHC
|
import qualified GHC.Driver.Session as GHC
|
||||||
import GHC.Hs
|
import GHC.Hs
|
||||||
import qualified GHC.LanguageExtensions.Type as GHC
|
import qualified GHC.LanguageExtensions.Type as GHC
|
||||||
|
@ -29,6 +30,8 @@ import Language.Haskell.Brittany.Internal.S3_ToBriDocTools
|
||||||
import Language.Haskell.Brittany.Internal.Prelude
|
import Language.Haskell.Brittany.Internal.Prelude
|
||||||
import qualified Language.Haskell.Brittany.Internal.S1_Parsing
|
import qualified Language.Haskell.Brittany.Internal.S1_Parsing
|
||||||
as Parsing
|
as Parsing
|
||||||
|
import qualified Language.Haskell.Brittany.Internal.S2_SplitModule
|
||||||
|
as Splitting
|
||||||
import Language.Haskell.Brittany.Internal.StepOrchestrate
|
import Language.Haskell.Brittany.Internal.StepOrchestrate
|
||||||
( processModule )
|
( processModule )
|
||||||
import Language.Haskell.Brittany.Internal.Types
|
import Language.Haskell.Brittany.Internal.Types
|
||||||
|
@ -79,9 +82,13 @@ parsePrintModule traceFunc configWithDebugs inputText = runExceptT $ do
|
||||||
case parseResult of
|
case parseResult of
|
||||||
Left err -> throwE [ErrorInput err]
|
Left err -> throwE [ErrorInput err]
|
||||||
Right x -> pure x
|
Right x -> pure x
|
||||||
|
let moduleElementList = Splitting.splitModuleDecls parsedSource
|
||||||
(inlineConf, perItemConf) <-
|
(inlineConf, perItemConf) <-
|
||||||
mapExceptT (fmap $ bimap (\(a, b) -> [ErrorMacroConfig a b]) id)
|
mapExceptT (fmap $ bimap (\(a, b) -> [ErrorMacroConfig a b]) id)
|
||||||
$ extractCommentConfigs (useTraceFunc traceFunc) parsedSource
|
$ extractCommentConfigs
|
||||||
|
(useTraceFunc traceFunc)
|
||||||
|
(Splitting.extractDeclMap parsedSource)
|
||||||
|
moduleElementList
|
||||||
let moduleConfig = cZipWith fromOptionIdentity config inlineConf
|
let moduleConfig = cZipWith fromOptionIdentity config inlineConf
|
||||||
let disableFormatting =
|
let disableFormatting =
|
||||||
moduleConfig & _conf_disable_formatting & confUnpack
|
moduleConfig & _conf_disable_formatting & confUnpack
|
||||||
|
@ -96,11 +103,12 @@ parsePrintModule traceFunc configWithDebugs inputText = runExceptT $ do
|
||||||
& _econf_omit_output_valid_check
|
& _econf_omit_output_valid_check
|
||||||
& confUnpack
|
& confUnpack
|
||||||
(ews, outRaw) <- if hasCPP || omitCheck
|
(ews, outRaw) <- if hasCPP || omitCheck
|
||||||
then lift $ processModule traceFunc moduleConfig perItemConf parsedSource
|
then lift
|
||||||
|
$ processModule traceFunc moduleConfig perItemConf moduleElementList
|
||||||
else lift $ pPrintModuleAndCheck traceFunc
|
else lift $ pPrintModuleAndCheck traceFunc
|
||||||
moduleConfig
|
moduleConfig
|
||||||
perItemConf
|
perItemConf
|
||||||
parsedSource
|
moduleElementList
|
||||||
let hackF s = fromMaybe s
|
let hackF s = fromMaybe s
|
||||||
$ TextL.stripPrefix (TextL.pack "-- BRITANY_INCLUDE_HACK ") s
|
$ TextL.stripPrefix (TextL.pack "-- BRITANY_INCLUDE_HACK ") s
|
||||||
pure $ if hackAroundIncludes
|
pure $ if hackAroundIncludes
|
||||||
|
@ -134,17 +142,17 @@ pPrintModuleAndCheck
|
||||||
:: TraceFunc
|
:: TraceFunc
|
||||||
-> Config
|
-> Config
|
||||||
-> PerItemConfig
|
-> PerItemConfig
|
||||||
-> GHC.ParsedSource
|
-> FinalList ModuleElement p
|
||||||
-> IO ([BrittanyError], TextL.Text)
|
-> IO ([BrittanyError], TextL.Text)
|
||||||
pPrintModuleAndCheck traceFunc conf inlineConf parsedModule = do
|
pPrintModuleAndCheck traceFunc conf inlineConf moduleElementList = do
|
||||||
let ghcOptions = conf & _conf_forward & _options_ghc & runIdentity
|
let ghcOptions = conf & _conf_forward & _options_ghc & runIdentity
|
||||||
(errs, output) <- processModule traceFunc conf inlineConf parsedModule
|
(errs, output) <- processModule traceFunc conf inlineConf moduleElementList
|
||||||
parseResult <- Parsing.parseModuleFromString ghcOptions
|
parseResult <- Parsing.parseModuleFromString ghcOptions
|
||||||
"output"
|
"output"
|
||||||
(\_ -> return $ Right ())
|
(\_ -> return $ Right ())
|
||||||
(TextL.unpack output)
|
(TextL.unpack output)
|
||||||
let errs' = errs ++ case parseResult of
|
let errs' = errs ++ case parseResult of
|
||||||
Left{} -> [ErrorOutputCheck]
|
Left x -> [ErrorOutputCheck x]
|
||||||
Right{} -> []
|
Right{} -> []
|
||||||
return (errs', output)
|
return (errs', output)
|
||||||
|
|
||||||
|
@ -162,10 +170,14 @@ parsePrintModuleTests conf filename input = do
|
||||||
case parseResult of
|
case parseResult of
|
||||||
Left err -> return $ Left err
|
Left err -> return $ Left err
|
||||||
Right (parsedModule, _) -> runExceptT $ do
|
Right (parsedModule, _) -> runExceptT $ do
|
||||||
|
let moduleElementList = Splitting.splitModuleDecls parsedModule
|
||||||
(inlineConf, perItemConf) <-
|
(inlineConf, perItemConf) <-
|
||||||
mapExceptT
|
mapExceptT
|
||||||
(fmap (bimap (\(a, _) -> "when parsing inline config: " ++ a) id))
|
(fmap (bimap (\(a, _) -> "when parsing inline config: " ++ a) id))
|
||||||
$ extractCommentConfigs (\_ -> pure ()) parsedModule
|
$ extractCommentConfigs
|
||||||
|
(\_ -> pure ())
|
||||||
|
(Splitting.extractDeclMap parsedModule)
|
||||||
|
moduleElementList
|
||||||
let moduleConf = cZipWith fromOptionIdentity conf inlineConf
|
let moduleConf = cZipWith fromOptionIdentity conf inlineConf
|
||||||
let omitCheck =
|
let omitCheck =
|
||||||
conf
|
conf
|
||||||
|
@ -176,11 +188,11 @@ parsePrintModuleTests conf filename input = do
|
||||||
then lift $ processModule (TraceFunc $ \_ -> pure ())
|
then lift $ processModule (TraceFunc $ \_ -> pure ())
|
||||||
moduleConf
|
moduleConf
|
||||||
perItemConf
|
perItemConf
|
||||||
parsedModule
|
moduleElementList
|
||||||
else lift $ pPrintModuleAndCheck (TraceFunc $ \_ -> pure ())
|
else lift $ pPrintModuleAndCheck (TraceFunc $ \_ -> pure ())
|
||||||
moduleConf
|
moduleConf
|
||||||
perItemConf
|
perItemConf
|
||||||
parsedModule
|
moduleElementList
|
||||||
if null errs
|
if null errs
|
||||||
then pure $ TextL.toStrict $ ltext
|
then pure $ TextL.toStrict $ ltext
|
||||||
else throwE
|
else throwE
|
||||||
|
@ -195,7 +207,7 @@ parsePrintModuleTests conf filename input = do
|
||||||
LayoutWarning str -> str
|
LayoutWarning str -> str
|
||||||
ErrorUnknownNode str _ -> str
|
ErrorUnknownNode str _ -> str
|
||||||
ErrorMacroConfig str _ -> "when parsing inline config: " ++ str
|
ErrorMacroConfig str _ -> "when parsing inline config: " ++ str
|
||||||
ErrorOutputCheck -> "Output is not syntactically valid."
|
ErrorOutputCheck str -> "Output is not syntactically valid: " ++ str
|
||||||
-- this approach would for if there was a pure GHC.parseDynamicFilePragma.
|
-- this approach would for if there was a pure GHC.parseDynamicFilePragma.
|
||||||
-- Unfortunately that does not exist yet, so we cannot provide a nominally
|
-- Unfortunately that does not exist yet, so we cannot provide a nominally
|
||||||
-- pure interface.
|
-- pure interface.
|
||||||
|
|
|
@ -64,6 +64,8 @@ keywords =
|
||||||
, "proc"
|
, "proc"
|
||||||
, "rec"
|
, "rec"
|
||||||
, "family"
|
, "family"
|
||||||
|
, "stock"
|
||||||
|
, "anyclass"
|
||||||
]
|
]
|
||||||
|
|
||||||
extraKWs :: [String]
|
extraKWs :: [String]
|
||||||
|
|
|
@ -64,6 +64,7 @@ staticDefaultConfig = Config
|
||||||
, _lconfig_fixityBasedAddAlignParens = coerce False
|
, _lconfig_fixityBasedAddAlignParens = coerce False
|
||||||
, _lconfig_operatorParenthesisRefactorMode = coerce PRMKeep
|
, _lconfig_operatorParenthesisRefactorMode = coerce PRMKeep
|
||||||
, _lconfig_operatorAllowUnqualify = coerce True
|
, _lconfig_operatorAllowUnqualify = coerce True
|
||||||
|
, _lconfig_allowSinglelineRecord = coerce True
|
||||||
}
|
}
|
||||||
, _conf_errorHandling = ErrorHandlingConfig
|
, _conf_errorHandling = ErrorHandlingConfig
|
||||||
{ _econf_produceOutputOnErrors = coerce False
|
{ _econf_produceOutputOnErrors = coerce False
|
||||||
|
@ -163,7 +164,7 @@ cmdlineConfigParser = do
|
||||||
, _lconfig_allowSingleLineExportList = mempty
|
, _lconfig_allowSingleLineExportList = mempty
|
||||||
, _lconfig_allowHangingQuasiQuotes = mempty
|
, _lconfig_allowHangingQuasiQuotes = mempty
|
||||||
, _lconfig_experimentalSemicolonNewlines = mempty
|
, _lconfig_experimentalSemicolonNewlines = mempty
|
||||||
-- , _lconfig_allowSinglelineRecord = mempty
|
, _lconfig_allowSinglelineRecord = mempty
|
||||||
, _lconfig_fixityAwareOps = mempty
|
, _lconfig_fixityAwareOps = mempty
|
||||||
, _lconfig_fixityAwareTypeOps = mempty
|
, _lconfig_fixityAwareTypeOps = mempty
|
||||||
, _lconfig_fixityBasedAddAlignParens = mempty
|
, _lconfig_fixityBasedAddAlignParens = mempty
|
||||||
|
|
|
@ -26,7 +26,7 @@ import Control.Monad.Trans.Except
|
||||||
|
|
||||||
import Language.Haskell.Brittany.Internal.Config.Config
|
import Language.Haskell.Brittany.Internal.Config.Config
|
||||||
import Language.Haskell.Brittany.Internal.Config.Types
|
import Language.Haskell.Brittany.Internal.Config.Types
|
||||||
import Language.Haskell.Brittany.Internal.Util.AST
|
import Language.Haskell.Brittany.Internal.Types
|
||||||
import Language.Haskell.Brittany.Internal.Config.Types.Instances1 ()
|
import Language.Haskell.Brittany.Internal.Config.Types.Instances1 ()
|
||||||
import Language.Haskell.Brittany.Internal.Config.Types.Instances2 ()
|
import Language.Haskell.Brittany.Internal.Config.Types.Instances2 ()
|
||||||
-- import Language.Haskell.Brittany.Internal.Utils
|
-- import Language.Haskell.Brittany.Internal.Utils
|
||||||
|
@ -44,46 +44,26 @@ data InlineConfigTarget
|
||||||
|
|
||||||
extractCommentConfigs
|
extractCommentConfigs
|
||||||
:: (String -> IO ())
|
:: (String -> IO ())
|
||||||
-> GHC.ParsedSource
|
-> Map GHC.RealSrcSpan [String]
|
||||||
|
-> FinalList ModuleElement a
|
||||||
-> ExceptT (String, String) IO (CConfig Maybe, PerItemConfig)
|
-> ExceptT (String, String) IO (CConfig Maybe, PerItemConfig)
|
||||||
extractCommentConfigs _putErrorLn modul = do
|
extractCommentConfigs _putErrorLn declMap moduleElementList = do
|
||||||
let (L _ (GHC.HsModule modAnn _ _ _ _ decls _ _)) = modul
|
let comments = concatMapFinal (void moduleElementList) $ \case
|
||||||
let declMap :: Map GHC.RealSrcSpan [String]
|
MEExactModuleHead modul -> case GHC.hsmodAnn $ GHC.unLoc modul of
|
||||||
declMap = Map.fromList
|
GHC.EpAnn _ _ (GHC.EpaComments prior) -> prior
|
||||||
[ ( case span of
|
GHC.EpAnn _ _ (GHC.EpaCommentsBalanced prior following) ->
|
||||||
GHC.RealSrcSpan s _ -> s
|
prior ++ following
|
||||||
GHC.UnhelpfulSpan _ -> error "unexpected UnhelpfulSpan"
|
GHC.EpAnnNotUsed -> []
|
||||||
, getDeclBindingNames decl
|
MEPrettyModuleHead{} -> []
|
||||||
)
|
MEImportDecl{} -> []
|
||||||
| decl <- decls
|
MEDecl{} -> []
|
||||||
, let (L (GHC.SrcSpanAnn _ span) _) = decl
|
MEComment (_, comment) -> [comment]
|
||||||
]
|
MEWhitespace{} -> []
|
||||||
let epAnnComms = \case
|
|
||||||
GHC.EpAnn _ _ (GHC.EpaComments prior) -> prior
|
|
||||||
GHC.EpAnn _ _ (GHC.EpaCommentsBalanced prior following) ->
|
|
||||||
prior ++ following
|
|
||||||
GHC.EpAnnNotUsed -> []
|
|
||||||
let gatheredComments =
|
|
||||||
join
|
|
||||||
$ epAnnComms modAnn
|
|
||||||
: [ epAnnComms epAnn | L (GHC.SrcSpanAnn epAnn _) _x <- decls ]
|
|
||||||
-- gatheredComments `forM_` \comm@(L anchor _) -> do
|
|
||||||
-- liftIO $ putErrorLn $ showOutputable comm
|
|
||||||
-- case Map.lookupLE (GHC.anchor anchor) declMap of
|
|
||||||
-- Nothing -> pure ()
|
|
||||||
-- Just (pos, le) -> do
|
|
||||||
-- liftIO $ putErrorLn $ " le = " ++ show (toConstr le) ++ " at " ++ show
|
|
||||||
-- (ExactPrint.Utils.ss2deltaEnd pos (GHC.anchor anchor))
|
|
||||||
-- case Map.lookupGE (GHC.anchor anchor) declMap of
|
|
||||||
-- Nothing -> pure ()
|
|
||||||
-- Just (pos, ge) -> do
|
|
||||||
-- liftIO $ putErrorLn $ " ge = " ++ show (toConstr ge) ++ " at " ++ show
|
|
||||||
-- (ExactPrint.Utils.ss2deltaStart (GHC.anchor anchor) pos)
|
|
||||||
lineConfigs <- sequence
|
lineConfigs <- sequence
|
||||||
[ case Butcher.runCmdParserSimpleString line2 parser of
|
[ case Butcher.runCmdParserSimpleString line2 parser of
|
||||||
Left err -> throwE (err, line2)
|
Left err -> throwE (err, line2)
|
||||||
Right (target, conf) -> pure $ (GHC.anchor anchr, target, conf)
|
Right (target, conf) -> pure $ (GHC.anchor anchr, target, conf)
|
||||||
| L anchr (EpaComment comm _) <- gatheredComments
|
| L anchr (EpaComment comm _) <- comments
|
||||||
, Just line1 <- case comm of
|
, Just line1 <- case comm of
|
||||||
EpaLineComment l ->
|
EpaLineComment l ->
|
||||||
[ List.stripPrefix "-- BRITTANY" l
|
[ List.stripPrefix "-- BRITTANY" l
|
||||||
|
|
|
@ -135,14 +135,14 @@ data CLayoutConfig f = LayoutConfig
|
||||||
-- The implementation for this is a bit hacky and not tested; it might
|
-- The implementation for this is a bit hacky and not tested; it might
|
||||||
-- break output syntax or not work properly for every kind of brace. So
|
-- break output syntax or not work properly for every kind of brace. So
|
||||||
-- far I have considered `do` and `case-of`.
|
-- far I have considered `do` and `case-of`.
|
||||||
-- , _lconfig_allowSinglelineRecord :: f (Last Bool)
|
, _lconfig_allowSinglelineRecord :: f (Last Bool)
|
||||||
-- -- if true, layouts record data decls as a single line when possible, e.g.
|
-- if true, layouts record data decls as a single line when possible, e.g.
|
||||||
-- -- > MyPoint { x :: Double, y :: Double }
|
-- > MyPoint { x :: Double, y :: Double }
|
||||||
-- -- if false, always use the multi-line layout
|
-- if false, always use the multi-line layout
|
||||||
-- -- > MyPoint
|
-- > MyPoint
|
||||||
-- -- > { x :: Double
|
-- > { x :: Double
|
||||||
-- -- > , y :: Double
|
-- > , y :: Double
|
||||||
-- -- > }
|
-- > }
|
||||||
, _lconfig_fixityAwareOps :: f (Last Bool)
|
, _lconfig_fixityAwareOps :: f (Last Bool)
|
||||||
-- enables fixity-based layouting, e.g.
|
-- enables fixity-based layouting, e.g.
|
||||||
-- > foo =
|
-- > foo =
|
||||||
|
|
|
@ -3,15 +3,17 @@
|
||||||
-- TODO92
|
-- TODO92
|
||||||
|
|
||||||
module Language.Haskell.Brittany.Internal.S2_SplitModule
|
module Language.Haskell.Brittany.Internal.S2_SplitModule
|
||||||
( splitModule
|
( extractDeclMap
|
||||||
)
|
, splitModuleDecls
|
||||||
where
|
, splitModuleStart
|
||||||
|
) where
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
import Language.Haskell.Brittany.Internal.Prelude
|
import Language.Haskell.Brittany.Internal.Prelude
|
||||||
|
|
||||||
import qualified Data.Generics as SYB
|
import qualified Data.Generics as SYB
|
||||||
|
import qualified Data.Map as Map
|
||||||
import qualified GHC
|
import qualified GHC
|
||||||
import GHC ( AddEpAnn(AddEpAnn)
|
import GHC ( AddEpAnn(AddEpAnn)
|
||||||
, Anchor(Anchor)
|
, Anchor(Anchor)
|
||||||
|
@ -56,88 +58,104 @@ import GHC.Parser.Annotation ( DeltaPos
|
||||||
)
|
)
|
||||||
, EpaCommentTok(EpaEofComment)
|
, EpaCommentTok(EpaEofComment)
|
||||||
)
|
)
|
||||||
import GHC.Types.SrcLoc ( realSrcSpanEnd )
|
import GHC.Types.SrcLoc ( realSrcSpanEnd
|
||||||
|
, realSrcSpanStart
|
||||||
|
)
|
||||||
import qualified Language.Haskell.GHC.ExactPrint.Types
|
import qualified Language.Haskell.GHC.ExactPrint.Types
|
||||||
as ExactPrint
|
as ExactPrint
|
||||||
import qualified Language.Haskell.GHC.ExactPrint.Utils
|
import qualified Language.Haskell.GHC.ExactPrint.Utils
|
||||||
as ExactPrint
|
as ExactPrint
|
||||||
import Safe ( maximumMay )
|
import Safe ( maximumMay )
|
||||||
|
import qualified Control.Monad.Trans.Writer.Strict
|
||||||
|
as WriterS
|
||||||
|
|
||||||
import Language.Haskell.Brittany.Internal.Components.BriDoc
|
import Language.Haskell.Brittany.Internal.Components.BriDoc
|
||||||
import Language.Haskell.Brittany.Internal.ToBriDoc.Module
|
import Language.Haskell.Brittany.Internal.ToBriDoc.Module
|
||||||
import Language.Haskell.Brittany.Internal.Types
|
import Language.Haskell.Brittany.Internal.Types
|
||||||
|
import Language.Haskell.Brittany.Internal.Util.AST
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
splitModule
|
extractDeclMap :: GHC.ParsedSource -> Map GHC.RealSrcSpan [String]
|
||||||
:: Bool
|
extractDeclMap modul =
|
||||||
-> GHC.ParsedSource
|
Map.fromList
|
||||||
-> Maybe GHC.RealSrcLoc
|
[ ( case span of
|
||||||
-> FinalList ModuleElement ExactPrint.Pos
|
GHC.RealSrcSpan s _ -> s
|
||||||
splitModule shouldReformatHead lmod posWhere = do
|
GHC.UnhelpfulSpan _ -> error "unexpected UnhelpfulSpan"
|
||||||
|
, getDeclBindingNames decl
|
||||||
|
)
|
||||||
|
| decl <- decls
|
||||||
|
, let (L (GHC.SrcSpanAnn _ span) _) = decl
|
||||||
|
]
|
||||||
|
where (L _ (GHC.HsModule _ _ _ _ _ decls _ _)) = modul
|
||||||
|
|
||||||
|
splitModuleDecls :: GHC.ParsedSource -> FinalList ModuleElement ExactPrint.Pos
|
||||||
|
splitModuleDecls lmod = do
|
||||||
let L moduleSpan modl = lmod
|
let L moduleSpan modl = lmod
|
||||||
HsModule _ _layout _name _exports imports decls _ _ = modl
|
HsModule _ _layout _name _exports _imports decls _ _ = modl
|
||||||
(hsModAnn', finalComments) = case GHC.hsmodAnn modl of
|
(hsModAnn', finalComments) = case GHC.hsmodAnn modl of
|
||||||
EpAnn a modAnns (EpaCommentsBalanced prior post) ->
|
EpAnn a modAnns (EpaCommentsBalanced prior post) ->
|
||||||
(EpAnn a modAnns (EpaCommentsBalanced prior []), post)
|
(EpAnn a modAnns (EpaCommentsBalanced prior []), post)
|
||||||
_ -> (GHC.hsmodAnn modl, [])
|
_ -> (GHC.hsmodAnn modl, [])
|
||||||
moduleWithoutComments =
|
moduleWithoutComments = L moduleSpan modl { GHC.hsmodAnn = hsModAnn'
|
||||||
L moduleSpan modl { GHC.hsmodAnn = hsModAnn', GHC.hsmodDecls = [] }
|
, GHC.hsmodDecls = []
|
||||||
lastSpan <- if shouldReformatHead
|
}
|
||||||
then do
|
lastSpan <- do
|
||||||
finalYield $ MEPrettyModuleHead moduleWithoutComments
|
finalYield $ MEExactModuleHead moduleWithoutComments
|
||||||
let locBeforeImports =
|
pure
|
||||||
maximumMay
|
$ maybe (1, 1) (ExactPrint.ss2posEnd)
|
||||||
$ [ realSrcSpanEnd $ anchor a
|
$ maximumMay
|
||||||
| L a _ <- case hsModAnn' of
|
$ [ GHC.anchor a
|
||||||
EpAnn _ _ (EpaComments cs ) -> cs
|
| L a _ <- GHC.priorComments $ case hsModAnn' of
|
||||||
EpAnn _ _ (EpaCommentsBalanced cs1 cs2) -> cs1 ++ cs2
|
EpAnn _ _ cs -> cs
|
||||||
EpAnnNotUsed -> error "unexpected EpAnnNotUsed"
|
EpAnnNotUsed -> error "unexpected EpAnnNotUsed"
|
||||||
]
|
]
|
||||||
++ [ pos | Just pos <- [posWhere] ]
|
++ [ s | AddEpAnn _ (EpaSpan s) <- GHC.am_main $ GHC.anns hsModAnn' ]
|
||||||
let (importLines, lastSpan) = finalToList $ transformToImportLine
|
++ [ GHC.anchor a
|
||||||
( maybe 0 srcLocLine locBeforeImports
|
| L da _ <- GHC.hsmodImports modl
|
||||||
, maybe 1 srcLocCol locBeforeImports
|
, L a _ <- case GHC.ann da of
|
||||||
)
|
EpAnn _ _ (EpaComments l ) -> l
|
||||||
imports
|
EpAnn _ _ (EpaCommentsBalanced _ l) -> l
|
||||||
let commentedImports = groupifyImportLines importLines
|
EpAnnNotUsed -> []
|
||||||
sortCommentedImports commentedImports `forM_` \case
|
]
|
||||||
EmptyLines n ->
|
++ [ span
|
||||||
finalYield $ MEWhitespace $ DifferentLine n 1
|
| L (SrcSpanAnn _ (GHC.RealSrcSpan span _)) _ <- GHC.hsmodImports modl
|
||||||
SamelineComment{} ->
|
]
|
||||||
error "brittany internal error: splitModule SamelineComment"
|
|
||||||
NewlineComment comm -> finalYield $ MEComment comm
|
|
||||||
ImportStatement record -> do
|
|
||||||
forM_ (commentsBefore record) $ finalYield . MEComment
|
|
||||||
finalYield
|
|
||||||
$ MEImportDecl (importStatement record) (commentsSameline record)
|
|
||||||
forM_ (commentsAfter record) $ finalYield . MEComment
|
|
||||||
pure $ lastSpan
|
|
||||||
else do
|
|
||||||
finalYield $ MEExactModuleHead moduleWithoutComments
|
|
||||||
pure
|
|
||||||
$ maybe (1, 1) (ExactPrint.ss2posEnd)
|
|
||||||
$ maximumMay
|
|
||||||
$ [ GHC.anchor a
|
|
||||||
| L a _ <- GHC.priorComments $ case hsModAnn' of
|
|
||||||
EpAnn _ _ cs -> cs
|
|
||||||
EpAnnNotUsed -> error "unexpected EpAnnNotUsed"
|
|
||||||
]
|
|
||||||
++ [ s | AddEpAnn _ (EpaSpan s) <- GHC.am_main $ GHC.anns hsModAnn' ]
|
|
||||||
++ [ GHC.anchor a
|
|
||||||
| L da _ <- GHC.hsmodImports modl
|
|
||||||
, L a _ <- case GHC.ann da of
|
|
||||||
EpAnn _ _ (EpaComments l ) -> l
|
|
||||||
EpAnn _ _ (EpaCommentsBalanced _ l) -> l
|
|
||||||
EpAnnNotUsed -> []
|
|
||||||
]
|
|
||||||
++ [ span
|
|
||||||
| L (SrcSpanAnn _ (GHC.RealSrcSpan span _)) _ <- GHC.hsmodImports
|
|
||||||
modl
|
|
||||||
]
|
|
||||||
spanAfterDecls <- enrichDecls lastSpan decls
|
spanAfterDecls <- enrichDecls lastSpan decls
|
||||||
enrichComms spanAfterDecls finalComments
|
enrichComms spanAfterDecls finalComments
|
||||||
|
|
||||||
|
splitModuleStart
|
||||||
|
:: GHC.ParsedSource
|
||||||
|
-> Maybe GHC.RealSrcLoc
|
||||||
|
-> FinalList ModuleElement ExactPrint.Pos
|
||||||
|
splitModuleStart modul posWhere = do
|
||||||
|
finalYield $ MEPrettyModuleHead modul
|
||||||
|
let locBeforeImports =
|
||||||
|
maximumMay
|
||||||
|
$ [ realSrcSpanEnd $ anchor a
|
||||||
|
| L a _ <- case GHC.hsmodAnn $ unLoc modul of
|
||||||
|
EpAnn _ _ (EpaComments cs ) -> cs
|
||||||
|
EpAnn _ _ (EpaCommentsBalanced cs1 cs2) -> cs1 ++ cs2
|
||||||
|
EpAnnNotUsed -> error "unexpected EpAnnNotUsed"
|
||||||
|
]
|
||||||
|
++ [ pos | Just pos <- [posWhere] ]
|
||||||
|
let (importLines, lastSpan) = finalToList $ transformToImportLine
|
||||||
|
( maybe 0 srcLocLine locBeforeImports
|
||||||
|
, maybe 1 srcLocCol locBeforeImports
|
||||||
|
)
|
||||||
|
(GHC.hsmodImports $ unLoc modul)
|
||||||
|
let commentedImports = groupifyImportLines importLines
|
||||||
|
sortCommentedImports commentedImports `forM_` \case
|
||||||
|
EmptyLines n -> finalYield $ MEWhitespace $ DifferentLine n 1
|
||||||
|
SamelineComment{} ->
|
||||||
|
error "brittany internal error: splitModuleStart SamelineComment"
|
||||||
|
NewlineComment comm -> finalYield $ MEComment comm
|
||||||
|
ImportStatement record -> do
|
||||||
|
forM_ (commentsBefore record) $ finalYield . MEComment
|
||||||
|
finalYield $ MEImportDecl (importStatement record)
|
||||||
|
(commentsSameline record)
|
||||||
|
forM_ (commentsAfter record) $ finalYield . MEComment
|
||||||
|
pure $ lastSpan
|
||||||
|
|
||||||
enrichComms
|
enrichComms
|
||||||
:: ExactPrint.Pos -> [LEpaComment] -> FinalList ModuleElement ExactPrint.Pos
|
:: ExactPrint.Pos -> [LEpaComment] -> FinalList ModuleElement ExactPrint.Pos
|
||||||
|
@ -148,52 +166,57 @@ enrichComms lastSpanEnd = \case
|
||||||
SameLine i -> SameLine i
|
SameLine i -> SameLine i
|
||||||
DifferentLine l c -> DifferentLine (l - 1) c
|
DifferentLine l c -> DifferentLine (l - 1) c
|
||||||
enrichComms (ExactPrint.ss2posEnd span) commRest
|
enrichComms (ExactPrint.ss2posEnd span) commRest
|
||||||
(L (Anchor span _) (EpaComment comm _) : commRest) -> do
|
lcomm@(L (Anchor span _) _) : commRest -> do
|
||||||
case ExactPrint.ss2delta lastSpanEnd span of
|
case ExactPrint.ss2delta lastSpanEnd span of
|
||||||
SameLine i -> do
|
SameLine i -> do
|
||||||
finalYield $ MEComment (i, comm)
|
finalYield $ MEComment (i, lcomm)
|
||||||
DifferentLine l c -> do
|
DifferentLine l c -> do
|
||||||
finalYield $ MEWhitespace $ DifferentLine (l - 1) c
|
finalYield $ MEWhitespace $ DifferentLine (l - 1) c
|
||||||
finalYield $ MEComment (0, comm)
|
finalYield $ MEComment (0, lcomm)
|
||||||
enrichComms (ExactPrint.ss2posEnd span) commRest
|
enrichComms (ExactPrint.ss2posEnd span) commRest
|
||||||
|
|
||||||
enrichDecls
|
enrichDecls
|
||||||
:: ExactPrint.Pos -> [LHsDecl GhcPs] -> FinalList ModuleElement ExactPrint.Pos
|
:: ExactPrint.Pos -> [LHsDecl GhcPs] -> FinalList ModuleElement ExactPrint.Pos
|
||||||
enrichDecls lastSpanEnd = \case
|
enrichDecls lastSpanEnd = \case
|
||||||
[] -> finalPure $ lastSpanEnd
|
[] -> finalPure $ lastSpanEnd
|
||||||
(L (SrcSpanAnn dAnn rlspan@(GHC.RealSrcSpan span _)) decl : declRest) ->
|
ldecl@(L (SrcSpanAnn dAnn (GHC.RealSrcSpan span _)) _) : declRest ->
|
||||||
case dAnn of
|
case dAnn of
|
||||||
EpAnn dAnchor items (EpaComments dComments) -> do
|
EpAnn _dAnchor _items (EpaComments _dComments) -> do
|
||||||
let
|
let
|
||||||
withoutComments =
|
commentExtract
|
||||||
(L (SrcSpanAnn (EpAnn dAnchor items (EpaComments [])) rlspan) decl)
|
:: [LEpaComment] -> WriterS.Writer [LEpaComment] [LEpaComment]
|
||||||
commentExtract = \case
|
commentExtract comms = do
|
||||||
L (GHC.Anchor anch _) EpaComment{} -> ExactPrint.ss2posEnd anch
|
let (innerComments, outerComments) =
|
||||||
-- It would be really nice if `ExactPrint.ss2posEnd span` was
|
partition
|
||||||
-- sufficient. But for some reason the comments are not
|
(\(L (Anchor anch _) _) ->
|
||||||
-- (consistently) included in the length of the anchor. I.e.
|
( realSrcSpanStart anch < realSrcSpanEnd span
|
||||||
-- there are cases where a syntax tree node has an anchor from
|
&& realSrcSpanEnd anch > realSrcSpanStart span
|
||||||
-- pos A -> pos B. But then somewhere _below_ that node is a
|
)
|
||||||
-- comment that has an anchor pos B -> pos C.
|
)
|
||||||
-- We simply detect this here.
|
comms
|
||||||
-- We probably do some redundant `SYB.everything` lookups
|
WriterS.tell outerComments
|
||||||
-- throughout the code now. But optimizing it is not easy, and
|
pure innerComments
|
||||||
-- at worst it is larger constant factor on the size of the
|
(ldecl', extractedComments) = WriterS.runWriter
|
||||||
-- input, so it isn't _that_ bad.
|
$ SYB.everywhereM (SYB.mkM commentExtract) ldecl
|
||||||
fixedSpanEnd = SYB.everything
|
|
||||||
max
|
|
||||||
(SYB.mkQ (ExactPrint.ss2posEnd span) commentExtract)
|
|
||||||
decl
|
|
||||||
case ExactPrint.ss2delta lastSpanEnd span of
|
case ExactPrint.ss2delta lastSpanEnd span of
|
||||||
SameLine{} -> pure ()
|
SameLine{} -> pure ()
|
||||||
DifferentLine n _ ->
|
DifferentLine n _ ->
|
||||||
finalYield $ MEWhitespace $ DifferentLine (n - 1) 1
|
finalYield $ MEWhitespace $ DifferentLine (n - 1) 1
|
||||||
let (afterComms, span2) = finalToList $ enrichComms fixedSpanEnd (reverse dComments)
|
let fixedSpanEnd = ExactPrint.ss2posEnd span
|
||||||
let (immediate, later) = List.span (\case
|
let (afterComms, span2) = finalToList
|
||||||
MEComment{} -> True
|
$ enrichComms fixedSpanEnd
|
||||||
_ -> False
|
(List.sortOn (\(L l _) -> l) extractedComments)
|
||||||
) afterComms
|
let (immediate, later) =
|
||||||
finalYield $ MEDecl withoutComments [ comm | MEComment comm <- immediate ]
|
List.span
|
||||||
|
(\case
|
||||||
|
MEComment{} -> True
|
||||||
|
_ -> False
|
||||||
|
)
|
||||||
|
afterComms
|
||||||
|
finalYield
|
||||||
|
$ MEDecl
|
||||||
|
ldecl'
|
||||||
|
[ (ind, GHC.ac_tok comm) | MEComment (ind, L _ comm) <- immediate ]
|
||||||
later `forM_` finalYield
|
later `forM_` finalYield
|
||||||
enrichDecls span2 declRest
|
enrichDecls span2 declRest
|
||||||
EpAnn _anchor _items (EpaCommentsBalanced{}) ->
|
EpAnn _anchor _items (EpaCommentsBalanced{}) ->
|
||||||
|
@ -207,8 +230,8 @@ enrichDecls lastSpanEnd = \case
|
||||||
|
|
||||||
data ImportLine
|
data ImportLine
|
||||||
= EmptyLines Int
|
= EmptyLines Int
|
||||||
| SamelineComment (Int, EpaCommentTok)
|
| SamelineComment (Int, LEpaComment)
|
||||||
| NewlineComment (Int, EpaCommentTok) -- indentation and comment
|
| NewlineComment (Int, LEpaComment) -- indentation and comment
|
||||||
| ImportStatement ImportStatementRecord
|
| ImportStatement ImportStatementRecord
|
||||||
|
|
||||||
instance Show ImportLine where
|
instance Show ImportLine where
|
||||||
|
@ -221,10 +244,10 @@ instance Show ImportLine where
|
||||||
(length $ commentsAfter r)
|
(length $ commentsAfter r)
|
||||||
|
|
||||||
data ImportStatementRecord = ImportStatementRecord
|
data ImportStatementRecord = ImportStatementRecord
|
||||||
{ commentsBefore :: [(Int, EpaCommentTok)]
|
{ commentsBefore :: [(Int, LEpaComment)]
|
||||||
, importStatement :: LImportDecl GhcPs
|
, importStatement :: LImportDecl GhcPs
|
||||||
, commentsSameline :: [(Int, EpaCommentTok)]
|
, commentsSameline :: [(Int, EpaCommentTok)]
|
||||||
, commentsAfter :: [(Int, EpaCommentTok)]
|
, commentsAfter :: [(Int, LEpaComment)]
|
||||||
}
|
}
|
||||||
|
|
||||||
instance Show ImportStatementRecord where
|
instance Show ImportStatementRecord where
|
||||||
|
@ -243,13 +266,13 @@ transformToImportLine startPos is =
|
||||||
:: [LEpaComment] -> ExactPrint.Pos -> FinalList ImportLine ExactPrint.Pos
|
:: [LEpaComment] -> ExactPrint.Pos -> FinalList ImportLine ExactPrint.Pos
|
||||||
flattenComms = \case
|
flattenComms = \case
|
||||||
[] -> finalPure
|
[] -> finalPure
|
||||||
(L (Anchor span _) (EpaComment comm _) : commRest) -> \lastSpanEnd -> do
|
lcomm@(L (Anchor span _) _) : commRest -> \lastSpanEnd -> do
|
||||||
case ExactPrint.ss2delta lastSpanEnd span of
|
case ExactPrint.ss2delta lastSpanEnd span of
|
||||||
SameLine i -> do
|
SameLine i -> do
|
||||||
finalYield $ SamelineComment (i, comm)
|
finalYield $ SamelineComment (i, lcomm)
|
||||||
DifferentLine l c -> do
|
DifferentLine l c -> do
|
||||||
finalYield $ EmptyLines (l - 1)
|
finalYield $ EmptyLines (l - 1)
|
||||||
finalYield $ NewlineComment (c - 1, comm)
|
finalYield $ NewlineComment (c - 1, lcomm)
|
||||||
flattenComms commRest (ExactPrint.ss2posEnd span)
|
flattenComms commRest (ExactPrint.ss2posEnd span)
|
||||||
flattenDecls
|
flattenDecls
|
||||||
:: [LImportDecl GhcPs]
|
:: [LImportDecl GhcPs]
|
||||||
|
@ -258,43 +281,41 @@ transformToImportLine startPos is =
|
||||||
flattenDecls = \case
|
flattenDecls = \case
|
||||||
[] -> finalPure
|
[] -> finalPure
|
||||||
(L (SrcSpanAnn epAnn srcSpan@(RealSrcSpan declSpan _)) decl : declRest)
|
(L (SrcSpanAnn epAnn srcSpan@(RealSrcSpan declSpan _)) decl : declRest)
|
||||||
-> \lastSpanEnd ->
|
-> \lastSpanEnd ->
|
||||||
let (commsBefore, commsAfter, cleanEpAnn) = case epAnn of
|
let (commsBefore, commsAfter, cleanEpAnn) = case epAnn of
|
||||||
EpAnn anch s (EpaComments cs) ->
|
EpAnn anch s (EpaComments cs) ->
|
||||||
([], reverse cs, EpAnn anch s (EpaComments []))
|
([], reverse cs, EpAnn anch s (EpaComments []))
|
||||||
EpAnn anch s (EpaCommentsBalanced cs1 cs2) ->
|
EpAnn anch s (EpaCommentsBalanced cs1 cs2) ->
|
||||||
(reverse cs1, reverse cs2, EpAnn anch s (EpaComments []))
|
(reverse cs1, reverse cs2, EpAnn anch s (EpaComments []))
|
||||||
EpAnnNotUsed -> ([], [], EpAnnNotUsed)
|
EpAnnNotUsed -> ([], [], EpAnnNotUsed)
|
||||||
in
|
in do
|
||||||
do
|
span1 <- flattenComms commsBefore lastSpanEnd
|
||||||
span1 <- flattenComms commsBefore lastSpanEnd
|
let newlines = case ExactPrint.ss2delta span1 declSpan of
|
||||||
let newlines = case ExactPrint.ss2delta span1 declSpan of
|
SameLine _ -> 0
|
||||||
SameLine _ -> 0
|
DifferentLine i _ -> i - 1
|
||||||
DifferentLine i _ -> i - 1
|
finalYield $ EmptyLines newlines
|
||||||
finalYield
|
finalYield $ ImportStatement ImportStatementRecord
|
||||||
$ EmptyLines newlines
|
{ commentsBefore = []
|
||||||
finalYield $ ImportStatement ImportStatementRecord
|
, importStatement = L (SrcSpanAnn cleanEpAnn srcSpan) decl
|
||||||
{ commentsBefore = []
|
, commentsSameline = []
|
||||||
, importStatement = L (SrcSpanAnn cleanEpAnn srcSpan) decl
|
, commentsAfter = []
|
||||||
, commentsSameline = []
|
}
|
||||||
, commentsAfter = []
|
span2 <- flattenComms commsAfter (ExactPrint.ss2posEnd declSpan)
|
||||||
}
|
flattenDecls declRest span2
|
||||||
span2 <- flattenComms commsAfter (ExactPrint.ss2posEnd declSpan)
|
|
||||||
flattenDecls declRest span2
|
|
||||||
(L (SrcSpanAnn _epAnn UnhelpfulSpan{}) _decl : _declRest) ->
|
(L (SrcSpanAnn _epAnn UnhelpfulSpan{}) _decl : _declRest) ->
|
||||||
error "UnhelpfulSpan"
|
error "UnhelpfulSpan"
|
||||||
in
|
in
|
||||||
flattenDecls is startPos
|
flattenDecls is startPos
|
||||||
|
|
||||||
data Partial = PartialCommsOnly [(Int, EpaCommentTok)]
|
data Partial = PartialCommsOnly [(Int, LEpaComment)]
|
||||||
| PartialImport ImportStatementRecord
|
| PartialImport ImportStatementRecord
|
||||||
|
|
||||||
groupifyImportLines :: [ImportLine] -> [ImportLine]
|
groupifyImportLines :: [ImportLine] -> [ImportLine]
|
||||||
groupifyImportLines ls = finalToList_ $ go (PartialCommsOnly []) ls
|
groupifyImportLines ls = finalToList_ $ go (PartialCommsOnly []) ls
|
||||||
where
|
where
|
||||||
go acc [] = case acc of
|
go acc [] = case acc of
|
||||||
PartialCommsOnly comms ->
|
PartialCommsOnly comms -> reverse comms `forM_` \comm ->
|
||||||
reverse comms `forM_` \comm -> finalYield $ NewlineComment comm
|
finalYield $ NewlineComment comm
|
||||||
PartialImport partialRecord ->
|
PartialImport partialRecord ->
|
||||||
finalYield $ ImportStatement $ unpartial partialRecord
|
finalYield $ ImportStatement $ unpartial partialRecord
|
||||||
go acc (line1 : lineR) = do
|
go acc (line1 : lineR) = do
|
||||||
|
@ -306,9 +327,10 @@ groupifyImportLines ls = finalToList_ $ go (PartialCommsOnly []) ls
|
||||||
pure $ PartialCommsOnly []
|
pure $ PartialCommsOnly []
|
||||||
SamelineComment comm -> do
|
SamelineComment comm -> do
|
||||||
pure $ PartialCommsOnly (comm : comms)
|
pure $ PartialCommsOnly (comm : comms)
|
||||||
NewlineComment comm -> pure $ PartialCommsOnly (comm : comms)
|
NewlineComment comm -> pure $ PartialCommsOnly (comm : comms)
|
||||||
ImportStatement record ->
|
ImportStatement record -> pure $ PartialImport $ record
|
||||||
pure $ PartialImport $ record { commentsBefore = comms }
|
{ commentsBefore = comms
|
||||||
|
}
|
||||||
PartialImport partialRecord -> case line1 of
|
PartialImport partialRecord -> case line1 of
|
||||||
e@EmptyLines{} -> do
|
e@EmptyLines{} -> do
|
||||||
finalYield $ ImportStatement $ unpartial partialRecord
|
finalYield $ ImportStatement $ unpartial partialRecord
|
||||||
|
@ -317,7 +339,8 @@ groupifyImportLines ls = finalToList_ $ go (PartialCommsOnly []) ls
|
||||||
SamelineComment comm -> do
|
SamelineComment comm -> do
|
||||||
if (null $ commentsAfter partialRecord)
|
if (null $ commentsAfter partialRecord)
|
||||||
then pure $ PartialImport partialRecord
|
then pure $ PartialImport partialRecord
|
||||||
{ commentsSameline = comm : commentsSameline partialRecord
|
{ commentsSameline = tokenOnly comm
|
||||||
|
: commentsSameline partialRecord
|
||||||
}
|
}
|
||||||
else pure $ PartialImport partialRecord
|
else pure $ PartialImport partialRecord
|
||||||
{ commentsAfter = comm : commentsAfter partialRecord
|
{ commentsAfter = comm : commentsAfter partialRecord
|
||||||
|
@ -333,6 +356,8 @@ groupifyImportLines ls = finalToList_ $ go (PartialCommsOnly []) ls
|
||||||
pure $ PartialImport $ record { commentsBefore = contestedComments }
|
pure $ PartialImport $ record { commentsBefore = contestedComments }
|
||||||
-- comments in between will stay connected to the following decl
|
-- comments in between will stay connected to the following decl
|
||||||
go newAcc lineR
|
go newAcc lineR
|
||||||
|
tokenOnly :: (Int, LEpaComment) -> (Int, EpaCommentTok)
|
||||||
|
tokenOnly (ind, L _ (EpaComment tok _)) = (ind, tok)
|
||||||
unpartial :: ImportStatementRecord -> ImportStatementRecord
|
unpartial :: ImportStatementRecord -> ImportStatementRecord
|
||||||
unpartial partialRecord = ImportStatementRecord
|
unpartial partialRecord = ImportStatementRecord
|
||||||
{ commentsBefore = reverse (commentsBefore partialRecord)
|
{ commentsBefore = reverse (commentsBefore partialRecord)
|
||||||
|
@ -345,7 +370,7 @@ groupifyImportLines ls = finalToList_ $ go (PartialCommsOnly []) ls
|
||||||
sortCommentedImports :: [ImportLine] -> [ImportLine]
|
sortCommentedImports :: [ImportLine] -> [ImportLine]
|
||||||
sortCommentedImports =
|
sortCommentedImports =
|
||||||
-- TODO92 we don't need this unpackImports, it is implied later in the process
|
-- TODO92 we don't need this unpackImports, it is implied later in the process
|
||||||
mergeGroups . map (fmap (sortGroups)) . groupify
|
mergeGroups . map (fmap (sortGroups)) . groupify
|
||||||
where
|
where
|
||||||
-- unpackImports :: [ImportLine] -> [ImportLine]
|
-- unpackImports :: [ImportLine] -> [ImportLine]
|
||||||
-- unpackImports xs = xs >>= \case
|
-- unpackImports xs = xs >>= \case
|
||||||
|
@ -361,8 +386,8 @@ sortCommentedImports =
|
||||||
Left x -> [x]
|
Left x -> [x]
|
||||||
Right y -> ImportStatement <$> y
|
Right y -> ImportStatement <$> y
|
||||||
sortGroups :: [ImportStatementRecord] -> [ImportStatementRecord]
|
sortGroups :: [ImportStatementRecord] -> [ImportStatementRecord]
|
||||||
sortGroups =
|
sortGroups = List.sortOn
|
||||||
List.sortOn (moduleNameString . unLoc . ideclName . unLoc . importStatement)
|
(moduleNameString . unLoc . ideclName . unLoc . importStatement)
|
||||||
groupify :: [ImportLine] -> [Either ImportLine [ImportStatementRecord]]
|
groupify :: [ImportLine] -> [Either ImportLine [ImportStatementRecord]]
|
||||||
groupify cs = go [] cs
|
groupify cs = go [] cs
|
||||||
where
|
where
|
||||||
|
|
|
@ -389,6 +389,9 @@ docSeq :: [ToBriDocM BriDocNumbered] -> ToBriDocM BriDocNumbered
|
||||||
docSeq [] = docEmpty
|
docSeq [] = docEmpty
|
||||||
docSeq l = allocateNode . BDSeq =<< sequence l
|
docSeq l = allocateNode . BDSeq =<< sequence l
|
||||||
|
|
||||||
|
docSeqSep :: [ToBriDocM BriDocNumbered] -> ToBriDocM BriDocNumbered
|
||||||
|
docSeqSep = docSeq . List.intersperse docSeparator
|
||||||
|
|
||||||
docLines :: [ToBriDocM BriDocNumbered] -> ToBriDocM BriDocNumbered
|
docLines :: [ToBriDocM BriDocNumbered] -> ToBriDocM BriDocNumbered
|
||||||
docLines l = allocateNode . BDLines =<< sequence l
|
docLines l = allocateNode . BDLines =<< sequence l
|
||||||
|
|
||||||
|
@ -720,6 +723,10 @@ instance DocFlushCommsPost (Maybe GHC.RealSrcSpan) (ToBriDocM BriDocNumbered) wh
|
||||||
bd <- bdm
|
bd <- bdm
|
||||||
pure (i1, BDFlushCommentsPost (GHC.realSrcSpanEnd loc) shouldMark bd)
|
pure (i1, BDFlushCommentsPost (GHC.realSrcSpanEnd loc) shouldMark bd)
|
||||||
|
|
||||||
|
instance DocFlushCommsPost GHC.EpaLocation (ToBriDocM BriDocNumbered) where
|
||||||
|
docFlushCommsPost shouldMark epaLocation =
|
||||||
|
docFlushCommsPost shouldMark (Just $ GHC.epaLocationRealSrcSpan epaLocation)
|
||||||
|
|
||||||
instance DocFlushCommsPost ann (ToBriDocM BriDocNumbered)
|
instance DocFlushCommsPost ann (ToBriDocM BriDocNumbered)
|
||||||
=> DocFlushCommsPost ann (ToBriDocM [BriDocNumbered]) where
|
=> DocFlushCommsPost ann (ToBriDocM [BriDocNumbered]) where
|
||||||
docFlushCommsPost shouldMark loc bdm = do
|
docFlushCommsPost shouldMark loc bdm = do
|
||||||
|
|
|
@ -275,21 +275,53 @@ layoutBriDocM = \case
|
||||||
layoutBriDocM bd
|
layoutBriDocM bd
|
||||||
BDFlushCommentsPrior loc bd -> do
|
BDFlushCommentsPrior loc bd -> do
|
||||||
comms <- takeBefore loc
|
comms <- takeBefore loc
|
||||||
|
startCurY <- mGet <&> _lstate_curY
|
||||||
printComments comms
|
printComments comms
|
||||||
mModify (\s -> s + CommentCounter (length comms))
|
mModify (\s -> s + CommentCounter (length comms))
|
||||||
mModify $ \s -> s
|
mModify $ \s -> s
|
||||||
{ _lstate_markerForDelta = Nothing
|
{ _lstate_markerForDelta = Nothing
|
||||||
, _lstate_plannedSpace = case _lstate_markerForDelta s of
|
, _lstate_plannedSpace =
|
||||||
|
case _lstate_markerForDelta s of
|
||||||
Nothing -> _lstate_plannedSpace s
|
Nothing -> _lstate_plannedSpace s
|
||||||
Just m ->
|
Just m ->
|
||||||
let p1 = (srcLocLine m, srcLocCol m)
|
let p1 = (srcLocLine m, srcLocCol m)
|
||||||
p2 = (srcLocLine loc, srcLocCol loc)
|
p2 = (srcLocLine loc, srcLocCol loc)
|
||||||
-- traceShow (m, ExactPrint.pos2delta p1 p2) $ pure ()
|
in -- trace ("_lstate_plannedSpace = " ++ show (_lstate_plannedSpace s)
|
||||||
in case ExactPrint.pos2delta p1 p2 of
|
-- ++ ", _lstate_markerForDelta = " ++ show (_lstate_markerForDelta s)
|
||||||
SameLine{} -> _lstate_plannedSpace s
|
-- ++ ", _lstate_curY = " ++ show (_lstate_curY s)
|
||||||
|
-- ++ ", p1 = " ++ show p1
|
||||||
|
-- ++ ", p2 = " ++ show p2
|
||||||
|
-- ++ ", startCurY = " ++ show startCurY
|
||||||
|
-- -- ++ ", delta = " ++ show (ExactPrint.pos2delta p1 p2)
|
||||||
|
-- ) $
|
||||||
|
case ExactPrint.pos2delta p1 p2 of
|
||||||
|
SameLine iDelta -> case _lstate_plannedSpace s of
|
||||||
|
-- There is a delta after a marker. That should only happen
|
||||||
|
-- after a block-comment. And the marker-delta is SameLine,
|
||||||
|
-- so if layout doesn't force a newline we respect the marker
|
||||||
|
-- delta (i.e. respect whitespace immediately after a block
|
||||||
|
-- comment) or we just use the plan.
|
||||||
|
PlannedNone -> PlannedSameline iDelta
|
||||||
|
PlannedSameline i -> PlannedSameline (max (iDelta - 0) i)
|
||||||
|
p@PlannedNewline{} -> p
|
||||||
|
p@PlannedDelta{} -> p
|
||||||
DifferentLine n _ -> case _lstate_plannedSpace s of
|
DifferentLine n _ -> case _lstate_plannedSpace s of
|
||||||
PlannedNone -> PlannedNone
|
-- Marker with DifferentLine delta means that we want to
|
||||||
PlannedSameline i -> PlannedDelta n (_lstate_curY s + i)
|
-- reproduce the newlines that were present in the input.
|
||||||
|
-- These will be emptylines in cases where it makes sense to
|
||||||
|
-- reproduce them, e.g. between statements in a do-block.
|
||||||
|
PlannedNone -> PlannedDelta n startCurY
|
||||||
|
-- ^^^^^^^^^
|
||||||
|
--
|
||||||
|
-- after a block-comment, _lstate_curY
|
||||||
|
-- matches the end of the comment.
|
||||||
|
-- But to not break layout we need to
|
||||||
|
-- restore the original.
|
||||||
|
-- E.g. consider > let {-comm-}
|
||||||
|
-- > x = 13
|
||||||
|
--
|
||||||
|
-- vvvvvvvvvvvvvvv
|
||||||
|
PlannedSameline i -> PlannedDelta n (startCurY + i)
|
||||||
PlannedNewline{} -> PlannedNewline n
|
PlannedNewline{} -> PlannedNewline n
|
||||||
PlannedDelta _ i -> PlannedDelta n i
|
PlannedDelta _ i -> PlannedDelta n i
|
||||||
}
|
}
|
||||||
|
|
|
@ -1,9 +1,9 @@
|
||||||
{-# LANGUAGE NoImplicitPrelude #-}
|
{-# LANGUAGE NoImplicitPrelude #-}
|
||||||
|
{-# LANGUAGE DataKinds #-}
|
||||||
|
|
||||||
module Language.Haskell.Brittany.Internal.StepOrchestrate
|
module Language.Haskell.Brittany.Internal.StepOrchestrate
|
||||||
( processModule
|
( processModule
|
||||||
)
|
) where
|
||||||
where
|
|
||||||
|
|
||||||
import Language.Haskell.Brittany.Internal.Prelude
|
import Language.Haskell.Brittany.Internal.Prelude
|
||||||
|
|
||||||
|
@ -15,7 +15,8 @@ import qualified Data.Text.Lazy as TextL
|
||||||
import qualified Data.Text.Lazy.Builder as TextL.Builder
|
import qualified Data.Text.Lazy.Builder as TextL.Builder
|
||||||
import qualified Data.Text.Lazy.Builder as Text.Builder
|
import qualified Data.Text.Lazy.Builder as Text.Builder
|
||||||
import qualified GHC
|
import qualified GHC
|
||||||
import GHC ( EpaCommentTok
|
import GHC ( EpaComment(EpaComment)
|
||||||
|
, EpaCommentTok
|
||||||
( EpaBlockComment
|
( EpaBlockComment
|
||||||
, EpaEofComment
|
, EpaEofComment
|
||||||
, EpaLineComment
|
, EpaLineComment
|
||||||
|
@ -36,7 +37,7 @@ import Language.Haskell.Brittany.Internal.Config.Types
|
||||||
import Language.Haskell.Brittany.Internal.Config.Types.Instances2
|
import Language.Haskell.Brittany.Internal.Config.Types.Instances2
|
||||||
( )
|
( )
|
||||||
import Language.Haskell.Brittany.Internal.S2_SplitModule
|
import Language.Haskell.Brittany.Internal.S2_SplitModule
|
||||||
( splitModule )
|
( splitModuleStart )
|
||||||
import Language.Haskell.Brittany.Internal.S3_ToBriDocTools
|
import Language.Haskell.Brittany.Internal.S3_ToBriDocTools
|
||||||
import Language.Haskell.Brittany.Internal.S4_WriteBriDoc
|
import Language.Haskell.Brittany.Internal.S4_WriteBriDoc
|
||||||
( ppBriDoc )
|
( ppBriDoc )
|
||||||
|
@ -46,7 +47,8 @@ import Language.Haskell.Brittany.Internal.ToBriDoc.Module
|
||||||
import Language.Haskell.Brittany.Internal.Types
|
import Language.Haskell.Brittany.Internal.Types
|
||||||
import Language.Haskell.Brittany.Internal.Util.AST
|
import Language.Haskell.Brittany.Internal.Util.AST
|
||||||
import Language.Haskell.Brittany.Internal.Utils
|
import Language.Haskell.Brittany.Internal.Utils
|
||||||
import Language.Haskell.Brittany.Internal.ToBriDoc (layouters)
|
import Language.Haskell.Brittany.Internal.ToBriDoc
|
||||||
|
( layouters )
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
@ -58,86 +60,26 @@ processModule
|
||||||
:: TraceFunc
|
:: TraceFunc
|
||||||
-> Config
|
-> Config
|
||||||
-> PerItemConfig
|
-> PerItemConfig
|
||||||
-> GHC.ParsedSource
|
-> FinalList ModuleElement p
|
||||||
-> IO ([BrittanyError], TextL.Text)
|
-> IO ([BrittanyError], TextL.Text)
|
||||||
processModule traceFunc conf inlineConf parsedModule = do
|
processModule traceFunc conf inlineConf moduleElems = do
|
||||||
let shouldReformatHead =
|
let FinalList moduleElementsStream = moduleElems
|
||||||
conf & _conf_layout & _lconfig_reformatModulePreamble & confUnpack
|
((out, errs), debugStrings) =
|
||||||
let
|
runIdentity
|
||||||
wrapNonDeclToBriDoc = MultiRWSS.withMultiReader conf
|
$ MultiRWSS.runMultiRWSTNil
|
||||||
. MultiRWSS.withMultiState_ (CommentCounter 0)
|
$ MultiRWSS.withMultiWriterAW
|
||||||
FinalList moduleElementsStream = splitModule
|
$ MultiRWSS.withMultiWriterAW
|
||||||
shouldReformatHead
|
$ MultiRWSS.withMultiWriterW
|
||||||
parsedModule
|
$ MultiRWSS.withMultiReader traceFunc
|
||||||
(fmap GHC.realSrcSpanStart $ obtainAnnPos (GHC.hsmodAnn $ GHC.unLoc parsedModule) GHC.AnnWhere)
|
$ moduleElementsStream
|
||||||
((out, errs), debugStrings) =
|
(\modElem cont -> do
|
||||||
runIdentity
|
processModuleElement modElem
|
||||||
$ MultiRWSS.runMultiRWSTNil
|
cont
|
||||||
$ MultiRWSS.withMultiWriterAW
|
)
|
||||||
$ MultiRWSS.withMultiWriterAW
|
(\x -> do
|
||||||
$ MultiRWSS.withMultiWriterW
|
|
||||||
$ MultiRWSS.withMultiReader traceFunc
|
|
||||||
$ moduleElementsStream
|
|
||||||
(\modElem cont -> do
|
|
||||||
case modElem of
|
|
||||||
MEExactModuleHead modHead -> wrapNonDeclToBriDoc $ do
|
|
||||||
bdMay <- ppModuleHead modHead
|
|
||||||
case bdMay of
|
|
||||||
Nothing -> pure ()
|
|
||||||
Just bd -> ppBriDoc bd True
|
|
||||||
MEPrettyModuleHead (L loc modHead) -> wrapNonDeclToBriDoc $ do
|
|
||||||
case modHead of
|
|
||||||
HsModule epAnn _layoutInfo Nothing Nothing _ _ _ _ -> do
|
|
||||||
(bd, _) <-
|
|
||||||
briDocMToPPM layouters
|
|
||||||
$ maybe id
|
|
||||||
docFlushRemaining
|
|
||||||
(srcSpanFileName_maybe loc)
|
|
||||||
$ docHandleComms epAnn docSeparator
|
|
||||||
ppBriDoc bd True
|
|
||||||
HsModule _ _layoutInfo Nothing Just{} _ _ _ _ -> error
|
|
||||||
"brittany internal error: exports without module name"
|
|
||||||
HsModule epAnn _layoutInfo (Just n) les _ _ _ _ -> do
|
|
||||||
(bd, _) <-
|
|
||||||
briDocMToPPM layouters
|
|
||||||
$ maybe id
|
|
||||||
docFlushRemaining
|
|
||||||
(srcSpanFileName_maybe loc)
|
|
||||||
$ moduleNameExportBridoc epAnn n les
|
|
||||||
ppBriDoc bd True
|
|
||||||
MEImportDecl importDecl immediateAfterComms ->
|
|
||||||
wrapNonDeclToBriDoc $ do
|
|
||||||
(bd, _) <-
|
|
||||||
briDocMToPPM layouters
|
|
||||||
$ docSeq
|
|
||||||
( layoutImport importDecl
|
|
||||||
: map commentToDoc immediateAfterComms
|
|
||||||
)
|
|
||||||
ppBriDoc bd False
|
|
||||||
MEDecl decl immediateAfterComms -> do
|
|
||||||
let declConfig = getDeclConfig conf inlineConf decl
|
|
||||||
MultiRWSS.withMultiReader declConfig
|
|
||||||
$ MultiRWSS.withMultiState_ (CommentCounter 0)
|
|
||||||
$ ppToplevelDecl decl immediateAfterComms
|
|
||||||
MEComment (ind, EpaLineComment str) -> do
|
|
||||||
mTell $ TextL.Builder.fromString (replicate ind ' ' ++ str)
|
|
||||||
mTell $ TextL.Builder.fromString "\n"
|
|
||||||
MEComment (ind, EpaBlockComment str) -> do
|
|
||||||
mTell $ TextL.Builder.fromString (replicate ind ' ' ++ str)
|
|
||||||
mTell $ TextL.Builder.fromString "\n"
|
|
||||||
MEComment (_, EpaEofComment) -> pure ()
|
|
||||||
MEComment _ ->
|
|
||||||
mTell $ TextL.Builder.fromString "some other comment"
|
|
||||||
MEWhitespace dp -> do
|
|
||||||
-- mTell $ TextL.Builder.fromString "B"
|
|
||||||
-- mTell $ TextL.Builder.fromString ("whitespace " ++ show dp)
|
|
||||||
ppmMoveToExactLoc dp
|
|
||||||
cont
|
|
||||||
)
|
|
||||||
(\x -> do
|
|
||||||
-- mTell $ TextL.Builder.fromString "\n"
|
-- mTell $ TextL.Builder.fromString "\n"
|
||||||
pure x
|
pure x
|
||||||
)
|
)
|
||||||
-- _tracer =
|
-- _tracer =
|
||||||
-- -- if Seq.null debugStrings
|
-- -- if Seq.null debugStrings
|
||||||
-- -- then id
|
-- -- then id
|
||||||
|
@ -151,13 +93,94 @@ processModule traceFunc conf inlineConf parsedModule = do
|
||||||
-- MEExactModuleHead{} -> useTraceFunc traceFunc "MEExactModuleHead"
|
-- MEExactModuleHead{} -> useTraceFunc traceFunc "MEExactModuleHead"
|
||||||
-- MEPrettyModuleHead{} -> useTraceFunc traceFunc "MEPrettyModuleHead"
|
-- MEPrettyModuleHead{} -> useTraceFunc traceFunc "MEPrettyModuleHead"
|
||||||
-- MEImportDecl{} -> useTraceFunc traceFunc "MEImportDecl"
|
-- MEImportDecl{} -> useTraceFunc traceFunc "MEImportDecl"
|
||||||
-- MEDecl{} -> useTraceFunc traceFunc "MEDecl"
|
-- MEDecl decl _ ->
|
||||||
-- MEComment{} -> useTraceFunc traceFunc "MEComment"
|
-- useTraceFunc
|
||||||
|
-- traceFunc
|
||||||
|
-- ("MEDecl " ++ intercalate "," (getDeclBindingNames decl))
|
||||||
|
-- MEComment (y, L _ (EpaComment (EpaLineComment str) _)) ->
|
||||||
|
-- useTraceFunc traceFunc ("MEComment " ++ show y ++ " " ++ str)
|
||||||
|
-- MEComment (y, L _ (EpaComment (EpaBlockComment str) _)) ->
|
||||||
|
-- useTraceFunc traceFunc ("MEComment " ++ show y ++ " " ++ take 5 str)
|
||||||
|
-- MEComment (y, _) ->
|
||||||
|
-- useTraceFunc traceFunc ("MEComment " ++ show y ++ " _")
|
||||||
-- MEWhitespace dp -> useTraceFunc traceFunc ("MEWhitespace " ++ show dp)
|
-- MEWhitespace dp -> useTraceFunc traceFunc ("MEWhitespace " ++ show dp)
|
||||||
-- rest
|
-- rest
|
||||||
-- )
|
-- )
|
||||||
-- (\_ -> pure ())
|
-- (\_ -> pure ())
|
||||||
pure (errs, TextL.Builder.toLazyText out)
|
pure (errs, TextL.Builder.toLazyText out)
|
||||||
|
where
|
||||||
|
shouldReformatHead =
|
||||||
|
conf & _conf_layout & _lconfig_reformatModulePreamble & confUnpack
|
||||||
|
wrapNonDeclToBriDoc =
|
||||||
|
MultiRWSS.withMultiReader conf . MultiRWSS.withMultiState_
|
||||||
|
(CommentCounter 0)
|
||||||
|
processModuleElement
|
||||||
|
:: ModuleElement
|
||||||
|
-> MultiRWSS.MultiRWST
|
||||||
|
'[TraceFunc]
|
||||||
|
'[Text.Builder.Builder , [BrittanyError] , Seq String]
|
||||||
|
'[]
|
||||||
|
Identity
|
||||||
|
()
|
||||||
|
processModuleElement = \case
|
||||||
|
MEExactModuleHead modHead -> if shouldReformatHead
|
||||||
|
then do
|
||||||
|
let FinalList startElems =
|
||||||
|
splitModuleStart
|
||||||
|
modHead
|
||||||
|
( fmap GHC.realSrcSpanStart
|
||||||
|
$ obtainAnnPos (GHC.hsmodAnn $ GHC.unLoc modHead) GHC.AnnWhere
|
||||||
|
)
|
||||||
|
startElems
|
||||||
|
(\modElem cont -> do
|
||||||
|
processModuleElement modElem
|
||||||
|
cont
|
||||||
|
)
|
||||||
|
(\_ -> pure ())
|
||||||
|
else wrapNonDeclToBriDoc $ do
|
||||||
|
bdMay <- ppModuleHead modHead
|
||||||
|
case bdMay of
|
||||||
|
Nothing -> pure ()
|
||||||
|
Just bd -> do
|
||||||
|
ppBriDoc bd True
|
||||||
|
mTell $ Text.Builder.fromString "\n"
|
||||||
|
MEPrettyModuleHead (L loc modHead) -> wrapNonDeclToBriDoc $ do
|
||||||
|
case modHead of
|
||||||
|
HsModule epAnn _layoutInfo Nothing Nothing _ _ _ _ -> do
|
||||||
|
(bd, _) <-
|
||||||
|
briDocMToPPM layouters
|
||||||
|
$ maybe id docFlushRemaining (srcSpanFileName_maybe loc)
|
||||||
|
$ docHandleComms epAnn docSeparator
|
||||||
|
ppBriDoc bd True
|
||||||
|
HsModule _ _layoutInfo Nothing Just{} _ _ _ _ ->
|
||||||
|
error "brittany internal error: exports without module name"
|
||||||
|
HsModule epAnn _layoutInfo (Just n) les _ _ _ _ -> do
|
||||||
|
(bd, _) <-
|
||||||
|
briDocMToPPM layouters
|
||||||
|
$ maybe id docFlushRemaining (srcSpanFileName_maybe loc)
|
||||||
|
$ moduleNameExportBridoc epAnn n les
|
||||||
|
ppBriDoc bd True
|
||||||
|
MEImportDecl importDecl immediateAfterComms -> wrapNonDeclToBriDoc $ do
|
||||||
|
(bd, _) <- briDocMToPPM layouters $ docSeq
|
||||||
|
(layoutImport importDecl : map commentToDoc immediateAfterComms)
|
||||||
|
ppBriDoc bd False
|
||||||
|
MEDecl decl immediateAfterComms -> do
|
||||||
|
let declConfig = getDeclConfig conf inlineConf decl
|
||||||
|
MultiRWSS.withMultiReader declConfig
|
||||||
|
$ MultiRWSS.withMultiState_ (CommentCounter 0)
|
||||||
|
$ ppToplevelDecl decl immediateAfterComms
|
||||||
|
MEComment (ind, L _ (EpaComment (EpaLineComment str) _)) -> do
|
||||||
|
mTell $ TextL.Builder.fromString (replicate ind ' ' ++ str)
|
||||||
|
mTell $ TextL.Builder.fromString "\n"
|
||||||
|
MEComment (ind, L _ (EpaComment (EpaBlockComment str) _)) -> do
|
||||||
|
mTell $ TextL.Builder.fromString (replicate ind ' ' ++ str)
|
||||||
|
mTell $ TextL.Builder.fromString "\n"
|
||||||
|
MEComment (_, L _ (EpaComment EpaEofComment _)) -> pure ()
|
||||||
|
MEComment _ -> mTell $ TextL.Builder.fromString "some other comment"
|
||||||
|
MEWhitespace dp -> do
|
||||||
|
-- mTell $ TextL.Builder.fromString "B"
|
||||||
|
-- mTell $ TextL.Builder.fromString ("whitespace " ++ show dp)
|
||||||
|
ppmMoveToExactLoc dp
|
||||||
|
|
||||||
commentToDoc :: (Int, EpaCommentTok) -> ToBriDocM BriDocNumbered
|
commentToDoc :: (Int, EpaCommentTok) -> ToBriDocM BriDocNumbered
|
||||||
commentToDoc (indent, c) = case c of
|
commentToDoc (indent, c) = case c of
|
||||||
|
@ -197,17 +220,13 @@ processDefault x = do
|
||||||
_ -> mTell $ Text.Builder.fromString $ List.dropWhileEnd ((==) '\n') str
|
_ -> mTell $ Text.Builder.fromString $ List.dropWhileEnd ((==) '\n') str
|
||||||
|
|
||||||
|
|
||||||
getDeclConfig
|
getDeclConfig :: Config -> PerItemConfig -> GHC.LHsDecl GhcPs -> Config
|
||||||
:: Config
|
|
||||||
-> PerItemConfig
|
|
||||||
-> GHC.LHsDecl GhcPs
|
|
||||||
-> Config
|
|
||||||
getDeclConfig config inlineConf decl = cZipWith fromOptionIdentity config
|
getDeclConfig config inlineConf decl = cZipWith fromOptionIdentity config
|
||||||
$ mconcat (catMaybes (mBindingConfs ++ [mDeclConf]))
|
$ mconcat (catMaybes (mBindingConfs ++ [mDeclConf]))
|
||||||
where
|
where
|
||||||
declBindingNames = getDeclBindingNames decl
|
declBindingNames = getDeclBindingNames decl
|
||||||
mBindingConfs =
|
mBindingConfs = declBindingNames <&> \n ->
|
||||||
declBindingNames <&> \n -> Map.lookup n $ _icd_perBinding inlineConf
|
Map.lookup n $ _icd_perBinding inlineConf
|
||||||
mDeclConf = case GHC.locA $ GHC.getLoc decl of
|
mDeclConf = case GHC.locA $ GHC.getLoc decl of
|
||||||
GHC.RealSrcSpan x _ -> Map.lookup x $ _icd_perAnchor inlineConf
|
GHC.RealSrcSpan x _ -> Map.lookup x $ _icd_perAnchor inlineConf
|
||||||
GHC.UnhelpfulSpan{} -> Nothing
|
GHC.UnhelpfulSpan{} -> Nothing
|
||||||
|
@ -217,16 +236,15 @@ ppToplevelDecl decl immediateAfterComms = do
|
||||||
exactprintOnly <- mAsk <&> \declConfig ->
|
exactprintOnly <- mAsk <&> \declConfig ->
|
||||||
declConfig & _conf_roundtrip_exactprint_only & confUnpack
|
declConfig & _conf_roundtrip_exactprint_only & confUnpack
|
||||||
bd <- fmap fst $ if exactprintOnly
|
bd <- fmap fst $ if exactprintOnly
|
||||||
then briDocMToPPM layouters
|
then briDocMToPPM layouters $ docSeq
|
||||||
$ docSeq
|
(briDocByExactNoComment decl : map commentToDoc immediateAfterComms)
|
||||||
(briDocByExactNoComment decl : map commentToDoc immediateAfterComms)
|
|
||||||
else do
|
else do
|
||||||
let innerDoc = case decl of
|
let innerDoc = case decl of
|
||||||
L (SrcSpanAnn _ (GHC.RealSrcSpan s _)) _ ->
|
L (SrcSpanAnn _ (GHC.RealSrcSpan s _)) _ ->
|
||||||
docFlushRemaining (GHC.srcSpanFile s) $ layoutDecl decl
|
docFlushRemaining (GHC.srcSpanFile s) $ layoutDecl decl
|
||||||
_ -> layoutDecl decl
|
_ -> layoutDecl decl
|
||||||
(r, errorCount) <- briDocMToPPM layouters
|
(r, errorCount) <- briDocMToPPM layouters $ docSeq
|
||||||
$ docSeq (innerDoc : map commentToDoc immediateAfterComms)
|
(innerDoc : map commentToDoc immediateAfterComms)
|
||||||
if errorCount == 0
|
if errorCount == 0
|
||||||
then pure (r, 0)
|
then pure (r, 0)
|
||||||
else briDocMToPPM layouters $ briDocByExactNoComment decl
|
else briDocMToPPM layouters $ briDocByExactNoComment decl
|
||||||
|
|
|
@ -15,7 +15,7 @@ import Language.Haskell.Brittany.Internal.Components.BriDoc
|
||||||
|
|
||||||
|
|
||||||
layoutDataDecl
|
layoutDataDecl
|
||||||
:: LTyClDecl GhcPs
|
:: Maybe (LTyClDecl GhcPs)
|
||||||
-> EpAnn [AddEpAnn]
|
-> EpAnn [AddEpAnn]
|
||||||
-> LIdP GhcPs
|
-> LIdP GhcPs
|
||||||
-> LHsQTyVars GhcPs
|
-> LHsQTyVars GhcPs
|
||||||
|
@ -35,7 +35,7 @@ layoutDataDecl ltycl declEpAnn name (HsQTvs _ bndrs) pats defn = case defn of
|
||||||
then do
|
then do
|
||||||
nameStr <- lrdrNameToTextAnn name
|
nameStr <- lrdrNameToTextAnn name
|
||||||
consNameStr <- lrdrNameToTextAnn consName
|
consNameStr <- lrdrNameToTextAnn consName
|
||||||
tyVarLine <- shareDoc $ createBndrDoc bndrs
|
tyVars <- mapM shareDoc $ createBndrDoc bndrs
|
||||||
patDocs <- mapM shareDoc $ layoutHsTyPats pats
|
patDocs <- mapM shareDoc $ layoutHsTyPats pats
|
||||||
-- headDoc <- fmap return $ docSeq
|
-- headDoc <- fmap return $ docSeq
|
||||||
-- [ appSep $ docLitS "newtype")
|
-- [ appSep $ docLitS "newtype")
|
||||||
|
@ -43,181 +43,252 @@ layoutDataDecl ltycl declEpAnn name (HsQTvs _ bndrs) pats defn = case defn of
|
||||||
-- , appSep tyVarLine
|
-- , appSep tyVarLine
|
||||||
-- ]
|
-- ]
|
||||||
rhsDoc <- return <$> createDetailsDoc consNameStr details
|
rhsDoc <- return <$> createDetailsDoc consNameStr details
|
||||||
docHandleComms declEpAnn $ createDerivingPar mDerivs $ docSeq
|
docHandleComms declEpAnn $ createDerivingPar mDerivs $ docAlt
|
||||||
[ appSep $ docLitS "newtype"
|
[ -- newtype Tagged s b = Tagged { unTagged :: b }
|
||||||
, appSep $ docLit nameStr
|
docSeq
|
||||||
, appSep tyVarLine
|
[ appSep $ docLitS "newtype"
|
||||||
, docSeq $ [x | p <- patDocs, x <- [p, docSeparator]]
|
, appSep $ docLit nameStr
|
||||||
, docSeparator
|
, appSep (docSeqSep tyVars)
|
||||||
, docLitS "="
|
, docSeq $ [x | p <- patDocs, x <- [p, docSeparator]]
|
||||||
, docSeparator
|
, docSeparator
|
||||||
, docHandleComms epAnn $ rhsDoc
|
, docLitS "="
|
||||||
|
, docSeparator
|
||||||
|
, docForceParSpacing $ docHandleComms epAnn $ rhsDoc
|
||||||
|
]
|
||||||
|
, -- newtype Tagged s b
|
||||||
|
-- = Tagged { unTagged :: b }
|
||||||
|
-- newtype Tagged s
|
||||||
|
-- b
|
||||||
|
-- = Tagged { unTagged :: b }
|
||||||
|
docAddBaseY BrIndentRegular $ docPar
|
||||||
|
( docSeq
|
||||||
|
[ appSep $ docLitS "newtype"
|
||||||
|
, appSep $ docLit nameStr
|
||||||
|
, docAlt
|
||||||
|
[ docForceSingleline $ docSeq
|
||||||
|
[ appSep (docSeqSep tyVars)
|
||||||
|
, docSeq $ [x | p <- patDocs, x <- [p, docSeparator]]
|
||||||
|
]
|
||||||
|
, docSetBaseY $ docLines
|
||||||
|
$ map docForceSingleline $ tyVars ++ patDocs
|
||||||
|
]
|
||||||
|
]
|
||||||
|
)
|
||||||
|
( docSeq
|
||||||
|
[ docLitS "="
|
||||||
|
, docSeparator
|
||||||
|
, docHandleComms epAnn $ rhsDoc
|
||||||
|
]
|
||||||
|
)
|
||||||
|
, -- newtype Tagged
|
||||||
|
-- s
|
||||||
|
-- b
|
||||||
|
-- = Tagged { unTagged :: b }
|
||||||
|
docAddBaseY BrIndentRegular $ docPar
|
||||||
|
( docSeq
|
||||||
|
[ appSep $ docLitS "newtype"
|
||||||
|
, appSep $ docLit nameStr
|
||||||
|
-- , appSep tyVarLine
|
||||||
|
-- , docSeq $ [x | p <- patDocs, x <- [p, docSeparator]]
|
||||||
|
]
|
||||||
|
)
|
||||||
|
( docLines
|
||||||
|
$ map (docEnsureIndent BrIndentRegular) tyVars
|
||||||
|
++ map (docEnsureIndent BrIndentRegular) patDocs
|
||||||
|
++ [ docSeq
|
||||||
|
[ docLitS "="
|
||||||
|
, docSeparator
|
||||||
|
, docHandleComms epAnn $ rhsDoc
|
||||||
|
]
|
||||||
|
]
|
||||||
|
)
|
||||||
]
|
]
|
||||||
else briDocByExactNoComment ltycl
|
else maybe
|
||||||
_ -> briDocByExactNoComment ltycl
|
(error
|
||||||
|
$ "Unsupported form of DataFamInstDecl:"
|
||||||
|
++ " ConDeclH98 with context"
|
||||||
|
)
|
||||||
|
briDocByExactNoComment
|
||||||
|
ltycl
|
||||||
|
_ -> maybe
|
||||||
|
(error
|
||||||
|
$ "Unsupported form of DataFamInstDecl:"
|
||||||
|
++ " ConDeclH98 with forall"
|
||||||
|
)
|
||||||
|
briDocByExactNoComment
|
||||||
|
ltycl
|
||||||
|
HsDataDefn NoExtField NewType _ _ Just{} _ _ -> maybe
|
||||||
|
(error $ "Unsupported form of DataFamInstDecl: NewType _ _ Just _ _")
|
||||||
|
briDocByExactNoComment
|
||||||
|
ltycl
|
||||||
|
HsDataDefn NoExtField NewType _ _ Nothing _ _ -> maybe
|
||||||
|
(error $ "Unsupported form of DataFamInstDecl: NewType _ _ Nothing _ _")
|
||||||
|
briDocByExactNoComment
|
||||||
|
ltycl
|
||||||
|
|
||||||
|
-- data MyData = MyData ..
|
||||||
-- data MyData a b
|
-- data MyData = MyData { .. }
|
||||||
-- (zero constructors)
|
HsDataDefn NoExtField DataType ctxMay _ctype Nothing conss mDerivs -> do
|
||||||
HsDataDefn NoExtField DataType ctxMay _ctype Nothing [] mDerivs -> do
|
|
||||||
lhsContextDoc <- case ctxMay of
|
lhsContextDoc <- case ctxMay of
|
||||||
Just (L _ lhsContext) -> shareDoc $ createContextDoc lhsContext
|
Just (L _ lhsContext) -> shareDoc $ createContextDoc lhsContext
|
||||||
Nothing -> pure docEmpty
|
Nothing -> pure docEmpty
|
||||||
nameStr <- lrdrNameToTextAnn name
|
nameStr <- lrdrNameToTextAnn name
|
||||||
tyVarLine <- return <$> createBndrDoc bndrs
|
tyVarLine <- shareDoc $ docSeqSep $ createBndrDoc bndrs
|
||||||
patDocs <- mapM shareDoc $ layoutHsTyPats pats
|
patDocs <- mapM shareDoc $ layoutHsTyPats pats
|
||||||
docHandleComms declEpAnn $ createDerivingPar mDerivs $ docSeq
|
lhsDoc <- shareDoc $ docSeq
|
||||||
[ appSep $ docLitS "data"
|
[ -- TOOD92 docNodeAnnKW ltycl (Just GHC.AnnData) $
|
||||||
, lhsContextDoc
|
appSep $ docLitS "data"
|
||||||
|
, docForceSingleline $ lhsContextDoc
|
||||||
, appSep $ docLit nameStr
|
, appSep $ docLit nameStr
|
||||||
, appSep tyVarLine
|
, appSep tyVarLine
|
||||||
, docSeq $ [x | p <- patDocs, x <- [p, docSeparator]]
|
, docSeq $ [x | p <- patDocs, x <- [p, docSeparator]]
|
||||||
]
|
]
|
||||||
|
let prefixes = "=" : repeat "|"
|
||||||
-- data MyData = MyData ..
|
layoutConssResult <- mapM layoutConDecl (zip prefixes conss)
|
||||||
-- data MyData = MyData { .. }
|
case sequence layoutConssResult of
|
||||||
HsDataDefn NoExtField DataType ctxMay _ctype Nothing [cons] mDerivs ->
|
Left err -> maybe (error err) briDocByExactNoComment ltycl
|
||||||
case cons of
|
Right [] -> do
|
||||||
(L _ (ConDeclH98 epAnn consName _hasExt qvars mRhsContext details _conDoc))
|
docHandleComms declEpAnn $ createDerivingPar mDerivs $ docSeq
|
||||||
-> do
|
[ appSep $ docLitS "data"
|
||||||
lhsContextDoc <- case ctxMay of
|
, lhsContextDoc
|
||||||
Just (L _ lhsContext) -> shareDoc $ createContextDoc lhsContext
|
, appSep $ docLit nameStr
|
||||||
Nothing -> pure docEmpty
|
, appSep tyVarLine
|
||||||
nameStr <- lrdrNameToTextAnn name
|
, docSeq $ [x | p <- patDocs, x <- [p, docSeparator]]
|
||||||
consNameStr <- lrdrNameToTextAnn consName
|
]
|
||||||
tyVarLine <- return <$> createBndrDoc bndrs
|
Right [(consDocSl, consDocMl)] -> do
|
||||||
patDocs <- mapM shareDoc $ layoutHsTyPats pats
|
docHandleComms declEpAnn $ createDerivingPar mDerivs $ docAlt
|
||||||
forallDocMay <- case createForallDoc qvars of
|
[ -- data D = forall a . Show a => D a
|
||||||
Nothing -> pure Nothing
|
docSeq [lhsDoc, consDocSl]
|
||||||
Just x -> Just . pure <$> x
|
, -- data D
|
||||||
rhsContextDocMay <- case mRhsContext of
|
-- = forall a . Show a => D a
|
||||||
Nothing -> pure Nothing
|
-- data D
|
||||||
Just (L _ ctxt) -> Just . pure <$> createContextDoc ctxt
|
-- = forall a
|
||||||
rhsDoc <- return <$> createDetailsDoc consNameStr details
|
-- . Show a =>
|
||||||
let posEqual = obtainAnnPos epAnn AnnEqual
|
-- D a
|
||||||
consDoc <-
|
docAddBaseY BrIndentRegular
|
||||||
shareDoc
|
$ docPar lhsDoc
|
||||||
$ docHandleComms epAnn
|
(docNonBottomSpacing $ docAlt [consDocSl, consDocMl])
|
||||||
$ docHandleComms posEqual
|
, -- data
|
||||||
$ docNonBottomSpacing
|
-- Show a =>
|
||||||
$ case (forallDocMay, rhsContextDocMay) of
|
-- D
|
||||||
(Just forallDoc, Just rhsContextDoc) -> docLines
|
-- = rhsDoc
|
||||||
[ docSeq
|
-- This alternative is only for -XDatatypeContexts.
|
||||||
[docLitS "=", docSeparator, docForceSingleline forallDoc]
|
-- But I think it is rather unlikely this will trigger without
|
||||||
|
-- -XDataTypeContexts, especially with the `docNonBottomSpacing`
|
||||||
|
-- above, so while not strictly necessary, this should not
|
||||||
|
-- hurt.
|
||||||
|
docAddBaseY BrIndentRegular $ docPar
|
||||||
|
(-- TODO92 docNodeAnnKW ltycl (Just GHC.AnnData) $
|
||||||
|
docLitS "data")
|
||||||
|
(docLines
|
||||||
|
[ lhsContextDoc
|
||||||
|
, docSeq
|
||||||
|
[ appSep $ docLit nameStr
|
||||||
|
, tyVarLine
|
||||||
|
, docSeq $ [x | p <- patDocs, x <- [p, docSeparator]]
|
||||||
|
]
|
||||||
|
, consDocMl
|
||||||
|
]
|
||||||
|
)
|
||||||
|
]
|
||||||
|
Right consDocTuples -> do
|
||||||
|
docHandleComms declEpAnn
|
||||||
|
$ createDerivingPar mDerivs
|
||||||
|
$ docAddBaseY BrIndentRegular
|
||||||
|
$ docPar
|
||||||
|
(docAlt
|
||||||
|
[ -- data Show a => D a
|
||||||
|
lhsDoc
|
||||||
|
, -- data
|
||||||
|
-- Show a =>
|
||||||
|
-- D
|
||||||
|
-- This alternative is only for -XDatatypeContexts.
|
||||||
|
-- But I think it is rather unlikely this will trigger without
|
||||||
|
-- -XDataTypeContexts, especially with the `docNonBottomSpacing`
|
||||||
|
-- above, so while not strictly necessary, this should not
|
||||||
|
-- hurt.
|
||||||
|
docAddBaseY BrIndentRegular $ docPar
|
||||||
|
(-- TODO92 docNodeAnnKW ltycl (Just GHC.AnnData) $
|
||||||
|
docLitS "data")
|
||||||
|
(docLines
|
||||||
|
[ lhsContextDoc
|
||||||
, docSeq
|
, docSeq
|
||||||
[ docLitS "."
|
[ appSep $ docLit nameStr
|
||||||
, docSeparator
|
, tyVarLine
|
||||||
, docSetBaseY $ docLines [rhsContextDoc, docSetBaseY rhsDoc]
|
, docSeq $ [x | p <- patDocs, x <- [p, docSeparator]]
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
(Just forallDoc, Nothing) -> docLines
|
)
|
||||||
[ docSeq
|
]
|
||||||
[docLitS "=", docSeparator, docForceSingleline forallDoc]
|
)
|
||||||
, docSeq [docLitS ".", docSeparator, rhsDoc]
|
(docLines $ [docAlt [sl, ml] | (sl, ml) <- consDocTuples])
|
||||||
]
|
|
||||||
(Nothing, Just rhsContextDoc) -> docSeq
|
HsDataDefn NoExtField DataType _ _ Just{} _ _ -> maybe
|
||||||
[ docLitS "="
|
(error $ "Unsupported form of DataFamInstDecl: DataType _ _ Just _ _")
|
||||||
, docSeparator
|
briDocByExactNoComment
|
||||||
, docSetBaseY $ docLines [rhsContextDoc, docSetBaseY rhsDoc]
|
ltycl
|
||||||
]
|
|
||||||
(Nothing, Nothing) ->
|
layoutConDecl
|
||||||
docSeq [docLitS "=", docSeparator, rhsDoc]
|
:: (String, LConDecl GhcPs)
|
||||||
docHandleComms declEpAnn $ createDerivingPar mDerivs $ docAlt
|
-> ToBriDocM
|
||||||
[ -- data D = forall a . Show a => D a
|
(Either String (ToBriDocM BriDocNumbered, ToBriDocM BriDocNumbered))
|
||||||
docSeq
|
layoutConDecl (prefix, L _ con) = case con of
|
||||||
[ -- TOOD92 docNodeAnnKW ltycl (Just GHC.AnnData) $
|
ConDeclH98 epAnn consName _hasExt qvars mRhsContext details _conDoc -> do
|
||||||
docSeq
|
consNameStr <- lrdrNameToTextAnn consName
|
||||||
[ appSep $ docLitS "data"
|
forallDocMay <- case createForallDoc qvars of
|
||||||
, docForceSingleline $ lhsContextDoc
|
Nothing -> pure Nothing
|
||||||
, appSep $ docLit nameStr
|
Just x -> Just . pure <$> x
|
||||||
, appSep tyVarLine
|
rhsContextDocMay <- case mRhsContext of
|
||||||
, docSeq $ [x | p <- patDocs, x <- [p, docSeparator]]
|
Nothing -> pure Nothing
|
||||||
|
Just (L _ ctxt) -> Just . pure <$> createContextDoc ctxt
|
||||||
|
detailsDoc <- shareDoc $ createDetailsDoc consNameStr details
|
||||||
|
let posEqual = obtainAnnPos epAnn AnnEqual
|
||||||
|
pure $ Right
|
||||||
|
( docSeq
|
||||||
|
[ docHandleComms epAnn $ docHandleComms posEqual $ docLitS prefix
|
||||||
|
, docSeparator
|
||||||
|
, docSetIndentLevel $ docSeq
|
||||||
|
[ case forallDocMay of
|
||||||
|
Nothing -> docEmpty
|
||||||
|
Just forallDoc -> docSeq
|
||||||
|
[ docForceSingleline forallDoc
|
||||||
|
, docSeparator
|
||||||
|
, docLitS "."
|
||||||
|
, docSeparator
|
||||||
]
|
]
|
||||||
, docHandleComms epAnn $ docHandleComms posEqual $ docLitS "="
|
, maybe docEmpty docForceSingleline rhsContextDocMay
|
||||||
, docSeparator
|
, detailsDoc
|
||||||
, docSetIndentLevel $ docSeq
|
]
|
||||||
[ case forallDocMay of
|
]
|
||||||
Nothing -> docEmpty
|
, docHandleComms epAnn
|
||||||
Just forallDoc ->
|
$ docHandleComms posEqual
|
||||||
docSeq
|
$ docNonBottomSpacing
|
||||||
[ docForceSingleline forallDoc
|
$ case (forallDocMay, rhsContextDocMay) of
|
||||||
, docSeparator
|
(Just forallDoc, Just rhsContextDoc) -> docLines
|
||||||
, docLitS "."
|
[ docSeq
|
||||||
, docSeparator
|
[docLitS prefix, docSeparator, docForceSingleline forallDoc]
|
||||||
]
|
, docSeq
|
||||||
, maybe docEmpty docForceSingleline rhsContextDocMay
|
[ docLitS "."
|
||||||
, rhsDoc
|
, docSeparator
|
||||||
|
, docSetBaseY $ docLines [rhsContextDoc, docSetBaseY detailsDoc]
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
, -- data D
|
(Just forallDoc, Nothing) -> docLines
|
||||||
-- = forall a . Show a => D a
|
[ docSeq
|
||||||
docAddBaseY BrIndentRegular $ docPar
|
[docLitS prefix, docSeparator, docForceSingleline forallDoc]
|
||||||
( -- TODO92 docNodeAnnKW ltycl (Just GHC.AnnData) $
|
, docSeq [docLitS ".", docSeparator, detailsDoc]
|
||||||
docSeq
|
]
|
||||||
[ appSep $ docLitS "data"
|
(Nothing, Just rhsContextDoc) -> docSeq
|
||||||
, docForceSingleline lhsContextDoc
|
[ docLitS prefix
|
||||||
, appSep $ docLit nameStr
|
, docSeparator
|
||||||
, tyVarLine
|
, docSetBaseY $ docLines [rhsContextDoc, docSetBaseY detailsDoc]
|
||||||
, docSeq $ [x | p <- patDocs, x <- [p, docSeparator]]
|
]
|
||||||
]
|
(Nothing, Nothing) -> docSeq
|
||||||
)
|
[docLitS prefix, docSeparator, detailsDoc]
|
||||||
(docSeq
|
)
|
||||||
[ docHandleComms epAnn $ docHandleComms posEqual $ docLitS "="
|
ConDeclGADT{} -> pure
|
||||||
, docSeparator
|
$ Left "Unsupported: ConDeclGADT inside DataFamInstDecl"
|
||||||
, docSetIndentLevel $ docSeq
|
|
||||||
[ case forallDocMay of
|
|
||||||
Nothing -> docEmpty
|
|
||||||
Just forallDoc ->
|
|
||||||
docSeq
|
|
||||||
[ docForceSingleline forallDoc
|
|
||||||
, docSeparator
|
|
||||||
, docLitS "."
|
|
||||||
, docSeparator
|
|
||||||
]
|
|
||||||
, maybe docEmpty docForceSingleline rhsContextDocMay
|
|
||||||
, rhsDoc
|
|
||||||
]
|
|
||||||
]
|
|
||||||
)
|
|
||||||
, -- data D
|
|
||||||
-- = forall a
|
|
||||||
-- . Show a =>
|
|
||||||
-- D a
|
|
||||||
docAddBaseY BrIndentRegular $ docPar
|
|
||||||
( -- TODO92 docNodeAnnKW ltycl (Just GHC.AnnData) $
|
|
||||||
docSeq
|
|
||||||
[ appSep $ docLitS "data"
|
|
||||||
, docForceSingleline lhsContextDoc
|
|
||||||
, appSep $ docLit nameStr
|
|
||||||
, tyVarLine
|
|
||||||
, docSeq $ [x | p <- patDocs, x <- [p, docSeparator]]
|
|
||||||
]
|
|
||||||
)
|
|
||||||
consDoc
|
|
||||||
, -- data
|
|
||||||
-- Show a =>
|
|
||||||
-- D
|
|
||||||
-- = forall a
|
|
||||||
-- . Show a =>
|
|
||||||
-- D a
|
|
||||||
-- This alternative is only for -XDatatypeContexts.
|
|
||||||
-- But I think it is rather unlikely this will trigger without
|
|
||||||
-- -XDataTypeContexts, especially with the `docNonBottomSpacing`
|
|
||||||
-- above, so while not strictly necessary, this should not
|
|
||||||
-- hurt.
|
|
||||||
docAddBaseY BrIndentRegular $ docPar
|
|
||||||
(docLitS "data")
|
|
||||||
(docLines
|
|
||||||
[ lhsContextDoc
|
|
||||||
, -- TODO92 docNodeAnnKW ltycl (Just GHC.AnnData) $
|
|
||||||
docSeq [appSep $ docLit nameStr, tyVarLine, docSeq $ [x | p <- patDocs, x <- [p, docSeparator]]]
|
|
||||||
, consDoc
|
|
||||||
]
|
|
||||||
)
|
|
||||||
]
|
|
||||||
_ -> briDocByExactNoComment ltycl
|
|
||||||
|
|
||||||
_ -> briDocByExactNoComment ltycl
|
|
||||||
|
|
||||||
layoutHsTyPats
|
layoutHsTyPats
|
||||||
:: [LHsTypeArg GhcPs] -> [ToBriDocM BriDocNumbered]
|
:: [LHsTypeArg GhcPs] -> [ToBriDocM BriDocNumbered]
|
||||||
|
@ -253,25 +324,24 @@ createContextDoc (t1 : tR) = do
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
|
|
||||||
createBndrDoc :: [LHsTyVarBndr flag GhcPs] -> ToBriDocM BriDocNumbered
|
createBndrDoc :: [LHsTyVarBndr flag GhcPs] -> [ToBriDocM BriDocNumbered]
|
||||||
createBndrDoc bs = do
|
createBndrDoc = map $ \x -> do
|
||||||
tyVarDocs <- bs `forM` \case
|
(vname, mKind) <- case x of
|
||||||
(L _ (UserTyVar _ _ext vname)) -> return $ (lrdrNameToText vname, Nothing)
|
(L _ (UserTyVar _ _ext vname)) -> return $ (lrdrNameToText vname, Nothing)
|
||||||
(L _ (KindedTyVar _ _ext lrdrName kind)) -> do
|
(L _ (KindedTyVar _ _ext lrdrName kind)) -> do
|
||||||
d <- shareDoc $ callLayouter layout_type kind
|
d <- shareDoc $ callLayouter layout_type kind
|
||||||
return $ (lrdrNameToText lrdrName, Just $ d)
|
return $ (lrdrNameToText lrdrName, Just $ d)
|
||||||
docSeq $ List.intersperse docSeparator $ tyVarDocs <&> \(vname, mKind) ->
|
case mKind of
|
||||||
case mKind of
|
Nothing -> docLit vname
|
||||||
Nothing -> docLit vname
|
Just kind -> docSeq
|
||||||
Just kind -> docSeq
|
[ docLitS "("
|
||||||
[ docLitS "("
|
, docLit vname
|
||||||
, docLit vname
|
, docSeparator
|
||||||
, docSeparator
|
, docLitS "::"
|
||||||
, docLitS "::"
|
, docSeparator
|
||||||
, docSeparator
|
, kind
|
||||||
, kind
|
, docLitS ")"
|
||||||
, docLitS ")"
|
]
|
||||||
]
|
|
||||||
|
|
||||||
createDerivingPar
|
createDerivingPar
|
||||||
:: HsDeriving GhcPs -> ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered
|
:: HsDeriving GhcPs -> ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered
|
||||||
|
@ -385,8 +455,7 @@ createDetailsDoc consNameStr details = case details of
|
||||||
let ((fName1, fType1), fDocR) = case mkFieldDocs fields of
|
let ((fName1, fType1), fDocR) = case mkFieldDocs fields of
|
||||||
(doc1:docR) -> (doc1, docR)
|
(doc1:docR) -> (doc1, docR)
|
||||||
_ -> error "cannot happen (TM)"
|
_ -> error "cannot happen (TM)"
|
||||||
-- allowSingleline <- mAsk <&> _conf_layout .> _lconfig_allowSinglelineRecord .> confUnpack
|
allowSingleline <- mAsk <&> _conf_layout .> _lconfig_allowSinglelineRecord .> confUnpack
|
||||||
let allowSingleline = False
|
|
||||||
docAddBaseY BrIndentRegular $ runFilteredAlternative $ do
|
docAddBaseY BrIndentRegular $ runFilteredAlternative $ do
|
||||||
-- single-line: { i :: Int, b :: Bool }
|
-- single-line: { i :: Int, b :: Bool }
|
||||||
addAlternativeCond allowSingleline $ docSeq
|
addAlternativeCond allowSingleline $ docSeq
|
||||||
|
@ -412,7 +481,7 @@ createDetailsDoc consNameStr details = case details of
|
||||||
, docSeparator
|
, docSeparator
|
||||||
, docHandleComms posClose $ docLitS "}"
|
, docHandleComms posClose $ docLitS "}"
|
||||||
]
|
]
|
||||||
addAlternative $ docPar
|
addAlternative $ docSetParSpacing $ docPar
|
||||||
(docLit consNameStr)
|
(docLit consNameStr)
|
||||||
(docNonBottomSpacingS $ docLines
|
(docNonBottomSpacingS $ docLines
|
||||||
[ docAlt
|
[ docAlt
|
||||||
|
@ -468,7 +537,7 @@ createForallDoc
|
||||||
:: [LHsTyVarBndr flag GhcPs] -> Maybe (ToBriDocM BriDocNumbered)
|
:: [LHsTyVarBndr flag GhcPs] -> Maybe (ToBriDocM BriDocNumbered)
|
||||||
createForallDoc [] = Nothing
|
createForallDoc [] = Nothing
|
||||||
createForallDoc lhsTyVarBndrs =
|
createForallDoc lhsTyVarBndrs =
|
||||||
Just $ docSeq [docLitS "forall ", createBndrDoc lhsTyVarBndrs]
|
Just $ docSeq [docLitS "forall ", docSeqSep $ createBndrDoc lhsTyVarBndrs]
|
||||||
|
|
||||||
createNamesAndTypeDoc
|
createNamesAndTypeDoc
|
||||||
:: LConDeclField GhcPs
|
:: LConDeclField GhcPs
|
||||||
|
|
|
@ -238,7 +238,10 @@ layoutGrhs (L _ (GRHS epAnn guards body)) = do
|
||||||
guardDocs <- case guards of
|
guardDocs <- case guards of
|
||||||
[] -> pure []
|
[] -> pure []
|
||||||
_ -> docFlushCommsPost False posArrow $ callLayouter layout_stmt `mapM` guards
|
_ -> docFlushCommsPost False posArrow $ callLayouter layout_stmt `mapM` guards
|
||||||
bodyDoc <- callLayouter layout_expr body
|
let bodyEndPos = case locA $ getLoc body of
|
||||||
|
GHC.RealSrcSpan s _ -> Just s
|
||||||
|
GHC.UnhelpfulSpan{} -> Nothing
|
||||||
|
bodyDoc <- docFlushCommsPost True bodyEndPos $ callLayouter layout_expr body
|
||||||
return (Just epAnn, guardDocs, bodyDoc)
|
return (Just epAnn, guardDocs, bodyDoc)
|
||||||
|
|
||||||
layoutPatternBind
|
layoutPatternBind
|
||||||
|
@ -260,7 +263,7 @@ layoutPatternBind funId binderDoc lmatch@(L _ match) = do
|
||||||
let t' = fixPatternBindIdentifier match t
|
let t' = fixPatternBindIdentifier match t
|
||||||
docLit t'
|
docLit t'
|
||||||
_ -> pure Nothing
|
_ -> pure Nothing
|
||||||
patDoc <- docHandleComms lmatch $ case (mIdDoc, patDocs) of -- TODO92 we use lmatch twice here!
|
patDoc <- case (mIdDoc, patDocs) of
|
||||||
(Just idDoc, p1 : p2 : pr) | isInfix -> if null pr
|
(Just idDoc, p1 : p2 : pr) | isInfix -> if null pr
|
||||||
then docCols
|
then docCols
|
||||||
ColPatternsFuncInfix
|
ColPatternsFuncInfix
|
||||||
|
@ -805,7 +808,7 @@ layoutTyCl ltycl@(L _loc tycl) = case tycl of
|
||||||
typeDoc
|
typeDoc
|
||||||
DataDecl epAnn name tyVars _ dataDefn -> do
|
DataDecl epAnn name tyVars _ dataDefn -> do
|
||||||
layouters <- mAsk
|
layouters <- mAsk
|
||||||
layout_dataDecl layouters ltycl epAnn name tyVars [] dataDefn
|
layout_dataDecl layouters (Just ltycl) epAnn name tyVars [] dataDefn
|
||||||
_ -> briDocByExactNoComment ltycl
|
_ -> briDocByExactNoComment ltycl
|
||||||
|
|
||||||
layoutTyVarBndr :: Bool -> ToBriDoc (HsTyVarBndr ())
|
layoutTyVarBndr :: Bool -> ToBriDoc (HsTyVarBndr ())
|
||||||
|
@ -973,7 +976,7 @@ layoutClsInst (L declLoc _) cid = do
|
||||||
layouters <- mAsk
|
layouters <- mAsk
|
||||||
layout_dataDecl
|
layout_dataDecl
|
||||||
layouters
|
layouters
|
||||||
(error "Unsupported form of DataFamInstDecl")
|
Nothing
|
||||||
epAnn
|
epAnn
|
||||||
tycon
|
tycon
|
||||||
(case bndrs of
|
(case bndrs of
|
||||||
|
|
|
@ -556,7 +556,10 @@ layoutExpr lexpr@(L _ expr) = do
|
||||||
-- to making brittany idempotent, even though the result is non-optimal
|
-- to making brittany idempotent, even though the result is non-optimal
|
||||||
-- if "let" is moved horizontally as part of the transformation, as the
|
-- if "let" is moved horizontally as part of the transformation, as the
|
||||||
-- comments before the first let item are moved horizontally with it.
|
-- comments before the first let item are moved horizontally with it.
|
||||||
letDoc <- shareDoc $ wrapLet $ docLit $ Text.pack "let"
|
letDoc <- shareDoc
|
||||||
|
$ docFlushCommsPost True spanLet
|
||||||
|
$ wrapLet
|
||||||
|
$ docLitS "let"
|
||||||
inDoc <- shareDoc $ wrapIn $ docLit $ Text.pack "in"
|
inDoc <- shareDoc $ wrapIn $ docLit $ Text.pack "in"
|
||||||
docSetBaseAndIndent $ case fmap snd mBindDocs of
|
docSetBaseAndIndent $ case fmap snd mBindDocs of
|
||||||
Just [bindDoc] -> runFilteredAlternative $ do
|
Just [bindDoc] -> runFilteredAlternative $ do
|
||||||
|
|
|
@ -198,6 +198,9 @@ layoutOpTree allowSinglelinePar = \case
|
||||||
pure (pure op, subDoc)
|
pure (pure op, subDoc)
|
||||||
sharedOpsFlat <- flattenList docOps
|
sharedOpsFlat <- flattenList docOps
|
||||||
sharedOps <- simpleTransform docOps
|
sharedOps <- simpleTransform docOps
|
||||||
|
let lastWrap = if getPrec fixity <= 1
|
||||||
|
then docForceParSpacing
|
||||||
|
else docForceSingleline
|
||||||
coreAlternative hasParen
|
coreAlternative hasParen
|
||||||
locO
|
locO
|
||||||
locC
|
locC
|
||||||
|
@ -205,11 +208,12 @@ layoutOpTree allowSinglelinePar = \case
|
||||||
docL
|
docL
|
||||||
sharedOps
|
sharedOps
|
||||||
sharedOpsFlat
|
sharedOpsFlat
|
||||||
docForceParSpacing
|
lastWrap
|
||||||
OpLeaf l -> pure l
|
OpLeaf l -> pure l
|
||||||
where
|
where
|
||||||
isPrec0 = \case
|
isPrec0 x = getPrec x == 0
|
||||||
Fixity _ prec _ -> prec == 0
|
getPrec = \case
|
||||||
|
Fixity _ prec _ -> prec
|
||||||
coreAlternative
|
coreAlternative
|
||||||
:: Bool
|
:: Bool
|
||||||
-> Maybe GHC.RealSrcLoc
|
-> Maybe GHC.RealSrcLoc
|
||||||
|
@ -223,7 +227,10 @@ layoutOpTree allowSinglelinePar = \case
|
||||||
coreAlternative hasParen locO locC fixity docL sharedOps sharedOpsFlat lastWrap
|
coreAlternative hasParen locO locC fixity docL sharedOps sharedOpsFlat lastWrap
|
||||||
= do
|
= do
|
||||||
indentPolicy <- askLayoutConf _lconfig_indentPolicy
|
indentPolicy <- askLayoutConf _lconfig_indentPolicy
|
||||||
let wrapParenIfSl x inner = if x then wrapParenSl inner else docSetParSpacing inner
|
let zeroOps = null sharedOps
|
||||||
|
wrapParenIfSl x inner = if x
|
||||||
|
then wrapParenSl inner
|
||||||
|
else docSetParSpacing inner
|
||||||
wrapParenSl inner = docAlt
|
wrapParenSl inner = docAlt
|
||||||
[ docSeq
|
[ docSeq
|
||||||
[ docLit $ Text.pack "("
|
[ docLit $ Text.pack "("
|
||||||
|
@ -241,7 +248,7 @@ layoutOpTree allowSinglelinePar = \case
|
||||||
wrapParenMl innerHead innerLines = docSetBaseY $ docLines
|
wrapParenMl innerHead innerLines = docSetBaseY $ docLines
|
||||||
( [ docCols
|
( [ docCols
|
||||||
ColOpPrefix
|
ColOpPrefix
|
||||||
[ appSep $ docLit $ Text.pack "("
|
[ (if zeroOps then id else appSep) $ docLit $ Text.pack "("
|
||||||
, docHandleComms locO $ innerHead
|
, docHandleComms locO $ innerHead
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
|
@ -265,33 +272,35 @@ layoutOpTree allowSinglelinePar = \case
|
||||||
$ wrapParenIfSl hasParen
|
$ wrapParenIfSl hasParen
|
||||||
$ docSetParSpacing
|
$ docSetParSpacing
|
||||||
$ docSeq
|
$ docSeq
|
||||||
([docForceSingleline docL] ++ case splitFirstLast sharedOpsFlat of
|
([docForceSingleline docL] ++ case splitFirstLast sharedOpsFlat of
|
||||||
FirstLastEmpty -> []
|
FirstLastEmpty -> []
|
||||||
FirstLastSingleton (od, ed) ->
|
FirstLastSingleton (od, ed) ->
|
||||||
[docSeparator, docForceSingleline od, docSeparator, lastWrap ed]
|
[ docSeparator
|
||||||
FirstLast (od1, ed1) ems (odN, edN) ->
|
, docForceSingleline od
|
||||||
( [ docSeparator
|
, docSeparator
|
||||||
, docForceSingleline od1
|
, lastWrap ed
|
||||||
, docSeparator
|
]
|
||||||
, docForceSingleline ed1
|
FirstLast (od1, ed1) ems (odN, edN) ->
|
||||||
]
|
( [ docSeparator
|
||||||
++ join
|
, docForceSingleline od1
|
||||||
[ [ docSeparator
|
|
||||||
, docForceSingleline od
|
|
||||||
, docSeparator
|
, docSeparator
|
||||||
, docForceSingleline ed
|
, docForceSingleline ed1
|
||||||
]
|
]
|
||||||
| (od, ed) <- ems
|
++ join
|
||||||
]
|
[ [ docSeparator
|
||||||
++ [ docSeparator
|
, docForceSingleline od
|
||||||
, docForceSingleline odN
|
, docSeparator
|
||||||
, docSeparator
|
, docForceSingleline ed
|
||||||
, lastWrap edN
|
]
|
||||||
]
|
| (od, ed) <- ems
|
||||||
|
]
|
||||||
|
++ [ docSeparator
|
||||||
|
, docForceSingleline odN
|
||||||
|
, docSeparator
|
||||||
|
, lastWrap edN
|
||||||
|
]
|
||||||
|
)
|
||||||
)
|
)
|
||||||
)
|
|
||||||
-- this case rather leads to some unfortunate layouting than to anything
|
|
||||||
-- useful; disabling for now. (it interfers with cols stuff.)
|
|
||||||
-- one
|
-- one
|
||||||
-- + two
|
-- + two
|
||||||
-- + three
|
-- + three
|
||||||
|
@ -305,15 +314,14 @@ layoutOpTree allowSinglelinePar = \case
|
||||||
IndentPolicyMultiple -> docForceSingleline
|
IndentPolicyMultiple -> docForceSingleline
|
||||||
IndentPolicyFree -> id
|
IndentPolicyFree -> id
|
||||||
let curIsPrec0 = case fixity of
|
let curIsPrec0 = case fixity of
|
||||||
Nothing -> False
|
Nothing -> False
|
||||||
Just (Fixity _ prec _) -> prec == 0
|
Just (Fixity _ prec _) -> prec == 0
|
||||||
case sharedOps of
|
case sharedOps of
|
||||||
[(od, ed)] | curIsPrec0 ->
|
[(od, ed)] | curIsPrec0 ->
|
||||||
addAlternativeCond (not hasParen && isSingleOp)
|
addAlternativeCond (not hasParen && isSingleOp)
|
||||||
$ docSetParSpacing
|
$ docSetParSpacing
|
||||||
$ docPar
|
$ docPar (docHandleComms locO $ docForceSingleline $ docL)
|
||||||
(docHandleComms locO $ docForceSingleline $ docL)
|
(docSeq [od, docSeparator, singlelineUnlessFree ed])
|
||||||
(docSeq [od, docSeparator, singlelineUnlessFree ed])
|
|
||||||
_ -> pure ()
|
_ -> pure ()
|
||||||
-- > ( one
|
-- > ( one
|
||||||
-- > + two
|
-- > + two
|
||||||
|
@ -331,9 +339,9 @@ layoutOpTree allowSinglelinePar = \case
|
||||||
-- > + three
|
-- > + three
|
||||||
addAlternative
|
addAlternative
|
||||||
$ wrapParenMlIf
|
$ wrapParenMlIf
|
||||||
hasParen
|
hasParen
|
||||||
-- ((if not hasParen then docAddBaseY BrIndentRegular else id) docL)
|
-- ((if not hasParen then docAddBaseY BrIndentRegular else id) docL)
|
||||||
(if hasParen then docSetBaseY docL else docL)
|
(if hasParen then docSetBaseY docL else docL)
|
||||||
((if hasParen then sharedOps else sharedOpsFlat) <&> \(od, ed) ->
|
((if hasParen then sharedOps else sharedOpsFlat) <&> \(od, ed) ->
|
||||||
docCols ColOpPrefix [appSep od, docSetBaseY ed]
|
docCols ColOpPrefix [appSep od, docSetBaseY ed]
|
||||||
)
|
)
|
||||||
|
|
|
@ -47,18 +47,20 @@ layoutStmt lstmt@(L _ stmt) = do
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
LetStmt epAnn binds -> docHandleComms epAnn $ do
|
LetStmt epAnn binds -> docHandleComms epAnn $ do
|
||||||
|
let spanLet = obtainAnnPos epAnn AnnLet
|
||||||
|
letDoc <- shareDoc $ docFlushCommsPost True spanLet $ docLitS "let"
|
||||||
let isFree = indentPolicy == IndentPolicyFree
|
let isFree = indentPolicy == IndentPolicyFree
|
||||||
let indentFourPlus = indentAmount >= 4
|
let indentFourPlus = indentAmount >= 4
|
||||||
(wrapBinds, bindrDocsMay) <- callLayouter layout_localBinds binds
|
(wrapBinds, bindrDocsMay) <- callLayouter layout_localBinds binds
|
||||||
case bindrDocsMay of
|
case bindrDocsMay of
|
||||||
Nothing -> docLit $ Text.pack "let"
|
Nothing -> letDoc
|
||||||
-- i just tested the above, and it is indeed allowed. heh.
|
-- i just tested the above, and it is indeed allowed. heh.
|
||||||
Just (_, []) -> docLit $ Text.pack "let" -- this probably never happens
|
Just (_, []) -> letDoc -- this probably never happens
|
||||||
Just (_, [bindDoc]) -> docAlt
|
Just (_, [bindDoc]) -> docAlt
|
||||||
[ -- let bind = expr
|
[ -- let bind = expr
|
||||||
docCols
|
docCols
|
||||||
ColDoLet
|
ColDoLet
|
||||||
[ appSep $ docLit $ Text.pack "let"
|
[ appSep $ letDoc
|
||||||
, let
|
, let
|
||||||
f = case indentPolicy of
|
f = case indentPolicy of
|
||||||
IndentPolicyFree -> docSetBaseAndIndent
|
IndentPolicyFree -> docSetBaseAndIndent
|
||||||
|
@ -71,7 +73,7 @@ layoutStmt lstmt@(L _ stmt) = do
|
||||||
, -- let
|
, -- let
|
||||||
-- bind = expr
|
-- bind = expr
|
||||||
docAddBaseY BrIndentRegular $ docPar
|
docAddBaseY BrIndentRegular $ docPar
|
||||||
(docLit $ Text.pack "let")
|
letDoc
|
||||||
(wrapBinds $ docSetBaseAndIndent $ return bindDoc)
|
(wrapBinds $ docSetBaseAndIndent $ return bindDoc)
|
||||||
]
|
]
|
||||||
Just (_, bindDocs) -> runFilteredAlternative $ do
|
Just (_, bindDocs) -> runFilteredAlternative $ do
|
||||||
|
@ -79,7 +81,7 @@ layoutStmt lstmt@(L _ stmt) = do
|
||||||
-- bbb = exprb
|
-- bbb = exprb
|
||||||
-- ccc = exprc
|
-- ccc = exprc
|
||||||
addAlternativeCond (isFree || indentFourPlus) $ docSeq
|
addAlternativeCond (isFree || indentFourPlus) $ docSeq
|
||||||
[ appSep $ docLit $ Text.pack "let"
|
[ appSep $ letDoc
|
||||||
, let
|
, let
|
||||||
f = if indentFourPlus
|
f = if indentFourPlus
|
||||||
then docEnsureIndent BrIndentRegular
|
then docEnsureIndent BrIndentRegular
|
||||||
|
@ -93,7 +95,7 @@ layoutStmt lstmt@(L _ stmt) = do
|
||||||
addAlternativeCond (not indentFourPlus)
|
addAlternativeCond (not indentFourPlus)
|
||||||
$ docAddBaseY BrIndentRegular
|
$ docAddBaseY BrIndentRegular
|
||||||
$ docPar
|
$ docPar
|
||||||
(docLit $ Text.pack "let")
|
letDoc
|
||||||
(wrapBinds $ docSetBaseAndIndent $ docLines $ return <$> bindDocs)
|
(wrapBinds $ docSetBaseAndIndent $ docLines $ return <$> bindDocs)
|
||||||
RecStmt epAnn (L _ stmts) _ _ _ _ _ ->
|
RecStmt epAnn (L _ stmts) _ _ _ _ _ ->
|
||||||
docHandleComms epAnn $ runFilteredAlternative $ do
|
docHandleComms epAnn $ runFilteredAlternative $ do
|
||||||
|
|
|
@ -370,7 +370,9 @@ layoutType ltype@(L _ typ) = docHandleComms ltype $ case typ of
|
||||||
]
|
]
|
||||||
)
|
)
|
||||||
]
|
]
|
||||||
HsBangTy{} -> -- TODO
|
HsBangTy epAnn (HsSrcBang NoSourceText NoSrcUnpack SrcStrict) innerTy -> do
|
||||||
|
docHandleComms epAnn $ docSeq [docLitS "!", layoutType innerTy]
|
||||||
|
HsBangTy {} ->
|
||||||
briDocByExactInlineOnly "HsBangTy{}" ltype
|
briDocByExactInlineOnly "HsBangTy{}" ltype
|
||||||
-- HsBangTy bang typ1 -> do
|
-- HsBangTy bang typ1 -> do
|
||||||
-- let bangStr = case bang of
|
-- let bangStr = case bang of
|
||||||
|
|
|
@ -24,6 +24,7 @@ import GHC ( Anno
|
||||||
, ParsedSource
|
, ParsedSource
|
||||||
, XRec
|
, XRec
|
||||||
, LImportDecl
|
, LImportDecl
|
||||||
|
, LEpaComment
|
||||||
)
|
)
|
||||||
import GHC.Utils.Outputable(Outputable)
|
import GHC.Utils.Outputable(Outputable)
|
||||||
import Language.Haskell.Brittany.Internal.Config.Types
|
import Language.Haskell.Brittany.Internal.Config.Types
|
||||||
|
@ -52,7 +53,7 @@ data BrittanyError
|
||||||
| forall ast . (Data.Data.Data (XRec GhcPs ast), Outputable (Anno ast)) => ErrorUnknownNode String (XRec GhcPs ast)
|
| forall ast . (Data.Data.Data (XRec GhcPs ast), Outputable (Anno ast)) => ErrorUnknownNode String (XRec GhcPs ast)
|
||||||
-- ^ internal error: pretty-printing is not implemented for type of node
|
-- ^ internal error: pretty-printing is not implemented for type of node
|
||||||
-- in the syntax-tree
|
-- in the syntax-tree
|
||||||
| ErrorOutputCheck
|
| ErrorOutputCheck String
|
||||||
-- ^ checking the output for syntactic validity failed
|
-- ^ checking the output for syntactic validity failed
|
||||||
|
|
||||||
|
|
||||||
|
@ -89,6 +90,8 @@ finalToList_ :: FinalList a () -> [a]
|
||||||
finalToList_ (FinalList l) = l (:) (\() -> [])
|
finalToList_ (FinalList l) = l (:) (\() -> [])
|
||||||
finalToList :: FinalList a b -> ([a], b)
|
finalToList :: FinalList a b -> ([a], b)
|
||||||
finalToList (FinalList l) = l (\x (a, b) -> (x:a, b)) (\b -> ([], b))
|
finalToList (FinalList l) = l (\x (a, b) -> (x:a, b)) (\b -> ([], b))
|
||||||
|
concatMapFinal :: FinalList a () -> (a -> [b]) -> [b]
|
||||||
|
concatMapFinal (FinalList l) f = l (\x rest -> f x ++ rest) (\() -> [])
|
||||||
|
|
||||||
instance Functor (FinalList a) where
|
instance Functor (FinalList a) where
|
||||||
fmap = _finalRMap
|
fmap = _finalRMap
|
||||||
|
@ -119,7 +122,7 @@ data ModuleElement
|
||||||
-- ^ an import decl, only occurs if pretty-printing the module head.
|
-- ^ an import decl, only occurs if pretty-printing the module head.
|
||||||
| MEDecl (LHsDecl GhcPs) [(Int, EpaCommentTok)]
|
| MEDecl (LHsDecl GhcPs) [(Int, EpaCommentTok)]
|
||||||
-- ^ a top-level declaration
|
-- ^ a top-level declaration
|
||||||
| MEComment (Int, EpaCommentTok)
|
| MEComment (Int, LEpaComment)
|
||||||
-- ^ a top-level comment, i.e. a comment located between top-level elements
|
-- ^ a top-level comment, i.e. a comment located between top-level elements
|
||||||
-- (and not associated to some nested node, which might in theory happen).
|
-- (and not associated to some nested node, which might in theory happen).
|
||||||
-- The Int carries the indentation of the comment.
|
-- The Int carries the indentation of the comment.
|
||||||
|
@ -236,7 +239,7 @@ data Layouters = Layouters
|
||||||
)
|
)
|
||||||
)
|
)
|
||||||
, layout_dataDecl
|
, layout_dataDecl
|
||||||
:: GHC.LTyClDecl GhcPs
|
:: Maybe (GHC.LTyClDecl GhcPs)
|
||||||
-> GHC.EpAnn [GHC.AddEpAnn]
|
-> GHC.EpAnn [GHC.AddEpAnn]
|
||||||
-> GHC.LIdP GhcPs
|
-> GHC.LIdP GhcPs
|
||||||
-> GHC.LHsQTyVars GhcPs
|
-> GHC.LHsQTyVars GhcPs
|
||||||
|
|
|
@ -152,7 +152,7 @@ layoutWriteComment absolute isBlock dp commentLines s = do -- TODO92 we don't mo
|
||||||
mSet state
|
mSet state
|
||||||
{ _lstate_plannedSpace = if isBlock
|
{ _lstate_plannedSpace = if isBlock
|
||||||
then case _lstate_plannedSpace state of
|
then case _lstate_plannedSpace state of
|
||||||
PlannedNone -> PlannedSameline 1
|
p@PlannedNone -> p
|
||||||
p@PlannedSameline{} -> p
|
p@PlannedSameline{} -> p
|
||||||
PlannedNewline l ->
|
PlannedNewline l ->
|
||||||
if l <= y then PlannedSameline 1 else PlannedNewline (l - y)
|
if l <= y then PlannedSameline 1 else PlannedNewline (l - y)
|
||||||
|
|
|
@ -381,9 +381,15 @@ coreIO putErrorLnIO config suppressOutput checkMode inputPathM outputPathM =
|
||||||
putErrorLn left
|
putErrorLn left
|
||||||
ExceptT.throwE 60
|
ExceptT.throwE 60
|
||||||
Right (parsedSource, hasCPP) -> do
|
Right (parsedSource, hasCPP) -> do
|
||||||
|
let moduleElementList = splitModuleDecls parsedSource
|
||||||
(inlineConf, perItemConf) <- do
|
(inlineConf, perItemConf) <- do
|
||||||
resE <-
|
resE <-
|
||||||
liftIO $ ExceptT.runExceptT $ extractCommentConfigs putErrorLnIO parsedSource
|
liftIO
|
||||||
|
$ ExceptT.runExceptT
|
||||||
|
$ extractCommentConfigs
|
||||||
|
putErrorLnIO
|
||||||
|
(extractDeclMap parsedSource)
|
||||||
|
moduleElementList
|
||||||
case resE of
|
case resE of
|
||||||
Left (err, input) -> do
|
Left (err, input) -> do
|
||||||
putErrorLn $ "Error: parse error in inline configuration:"
|
putErrorLn $ "Error: parse error in inline configuration:"
|
||||||
|
@ -414,9 +420,9 @@ coreIO putErrorLnIO config suppressOutput checkMode inputPathM outputPathM =
|
||||||
.> _econf_omit_output_valid_check
|
.> _econf_omit_output_valid_check
|
||||||
.> confUnpack
|
.> confUnpack
|
||||||
(ews, outRaw) <- if hasCPP || omitCheck
|
(ews, outRaw) <- if hasCPP || omitCheck
|
||||||
then liftIO $ processModule (TraceFunc putErrorLnIO) moduleConf perItemConf parsedSource
|
then liftIO $ processModule (TraceFunc putErrorLnIO) moduleConf perItemConf moduleElementList
|
||||||
else liftIO
|
else liftIO
|
||||||
$ pPrintModuleAndCheck (TraceFunc putErrorLnIO) moduleConf perItemConf parsedSource
|
$ pPrintModuleAndCheck (TraceFunc putErrorLnIO) moduleConf perItemConf moduleElementList
|
||||||
let
|
let
|
||||||
hackF s = fromMaybe s $ TextL.stripPrefix
|
hackF s = fromMaybe s $ TextL.stripPrefix
|
||||||
(TextL.pack "-- BRITANY_INCLUDE_HACK ")
|
(TextL.pack "-- BRITANY_INCLUDE_HACK ")
|
||||||
|
|
|
@ -15,6 +15,7 @@ import Language.Haskell.Brittany.Internal
|
||||||
import Language.Haskell.Brittany.Internal.Config.Config
|
import Language.Haskell.Brittany.Internal.Config.Config
|
||||||
import Language.Haskell.Brittany.Internal.Config.Types
|
import Language.Haskell.Brittany.Internal.Config.Types
|
||||||
import Language.Haskell.Brittany.Internal.Prelude
|
import Language.Haskell.Brittany.Internal.Prelude
|
||||||
|
import Test.HUnit (assertEqual)
|
||||||
import qualified System.Directory
|
import qualified System.Directory
|
||||||
import System.FilePath ((</>))
|
import System.FilePath ((</>))
|
||||||
import System.Timeout (timeout)
|
import System.Timeout (timeout)
|
||||||
|
@ -22,6 +23,7 @@ import Test.Hspec
|
||||||
import qualified Text.Parsec as Parsec
|
import qualified Text.Parsec as Parsec
|
||||||
import Text.Parsec.Text (Parser)
|
import Text.Parsec.Text (Parser)
|
||||||
import qualified Data.List.Extra
|
import qualified Data.List.Extra
|
||||||
|
import qualified System.Console.ANSI as ANSI
|
||||||
|
|
||||||
hush :: Either a b -> Maybe b
|
hush :: Either a b -> Maybe b
|
||||||
hush = either (const Nothing) Just
|
hush = either (const Nothing) Just
|
||||||
|
@ -282,9 +284,15 @@ roundTripEqual c t =
|
||||||
`shouldReturn` Right (PPTextWrapper t)
|
`shouldReturn` Right (PPTextWrapper t)
|
||||||
|
|
||||||
goldenTest :: Config -> Text -> Text -> Expectation
|
goldenTest :: Config -> Text -> Text -> Expectation
|
||||||
goldenTest c input expected =
|
goldenTest c input expected = do
|
||||||
fmap (fmap PPTextWrapper) (parsePrintModuleTests c "TestFakeFileName.hs" input)
|
result <- parsePrintModuleTests c "TestFakeFileName.hs" input
|
||||||
`shouldReturn` Right (PPTextWrapper expected)
|
assertEqual
|
||||||
|
( ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Dull ANSI.Red]
|
||||||
|
++ "golden input: see test source!"
|
||||||
|
++ ANSI.setSGRCode [ANSI.Reset]
|
||||||
|
)
|
||||||
|
(Right (PPTextWrapper expected))
|
||||||
|
(fmap PPTextWrapper result)
|
||||||
|
|
||||||
newtype PPTextWrapper = PPTextWrapper Text
|
newtype PPTextWrapper = PPTextWrapper Text
|
||||||
deriving Eq
|
deriving Eq
|
||||||
|
@ -315,7 +323,7 @@ defaultTestConfig = Config
|
||||||
, _lconfig_allowSingleLineExportList = coerce True
|
, _lconfig_allowSingleLineExportList = coerce True
|
||||||
, _lconfig_allowHangingQuasiQuotes = coerce True
|
, _lconfig_allowHangingQuasiQuotes = coerce True
|
||||||
, _lconfig_experimentalSemicolonNewlines = coerce False
|
, _lconfig_experimentalSemicolonNewlines = coerce False
|
||||||
-- , _lconfig_allowSinglelineRecord = coerce False
|
, _lconfig_allowSinglelineRecord = coerce False
|
||||||
, _lconfig_fixityAwareOps = coerce True
|
, _lconfig_fixityAwareOps = coerce True
|
||||||
, _lconfig_fixityAwareTypeOps = coerce True
|
, _lconfig_fixityAwareTypeOps = coerce True
|
||||||
, _lconfig_fixityBasedAddAlignParens = coerce False
|
, _lconfig_fixityBasedAddAlignParens = coerce False
|
||||||
|
|
Loading…
Reference in New Issue