{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RecordWildCards #-}
module Language.Haskell.Stylish.Step.ModuleHeader
( Config (..)
, BreakWhere (..)
, OpenBracket (..)
, defaultConfig
, step
) where
import Control.Applicative ((<|>))
import Control.Monad (guard, unless, when)
import Data.Foldable (forM_)
import Data.Maybe (fromMaybe, isJust,
listToMaybe)
import qualified GHC.Hs as GHC
import qualified GHC.Types.SrcLoc as GHC
import Language.Haskell.Stylish.Comments
import qualified Language.Haskell.Stylish.Editor as Editor
import Language.Haskell.Stylish.GHC
import Language.Haskell.Stylish.Module
import Language.Haskell.Stylish.Ordering
import Language.Haskell.Stylish.Printer
import Language.Haskell.Stylish.Step
import qualified Language.Haskell.Stylish.Step.Imports as Imports
import Language.Haskell.Stylish.Util (flagEnds)
data Config = Config
{ Config -> Int
indent :: Int
, Config -> Bool
sort :: Bool
, Config -> Bool
separateLists :: Bool
, Config -> BreakWhere
breakWhere :: BreakWhere
, Config -> OpenBracket
openBracket :: OpenBracket
}
data OpenBracket
= SameLine
| NextLine
deriving (OpenBracket -> OpenBracket -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OpenBracket -> OpenBracket -> Bool
$c/= :: OpenBracket -> OpenBracket -> Bool
== :: OpenBracket -> OpenBracket -> Bool
$c== :: OpenBracket -> OpenBracket -> Bool
Eq, Int -> OpenBracket -> ShowS
[OpenBracket] -> ShowS
OpenBracket -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OpenBracket] -> ShowS
$cshowList :: [OpenBracket] -> ShowS
show :: OpenBracket -> String
$cshow :: OpenBracket -> String
showsPrec :: Int -> OpenBracket -> ShowS
$cshowsPrec :: Int -> OpenBracket -> ShowS
Show)
data BreakWhere
= Exports
| Single
| Inline
| Always
deriving (BreakWhere -> BreakWhere -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BreakWhere -> BreakWhere -> Bool
$c/= :: BreakWhere -> BreakWhere -> Bool
== :: BreakWhere -> BreakWhere -> Bool
$c== :: BreakWhere -> BreakWhere -> Bool
Eq, Int -> BreakWhere -> ShowS
[BreakWhere] -> ShowS
BreakWhere -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BreakWhere] -> ShowS
$cshowList :: [BreakWhere] -> ShowS
show :: BreakWhere -> String
$cshow :: BreakWhere -> String
showsPrec :: Int -> BreakWhere -> ShowS
$cshowsPrec :: Int -> BreakWhere -> ShowS
Show)
defaultConfig :: Config
defaultConfig :: Config
defaultConfig = Config
{ indent :: Int
indent = Int
4
, sort :: Bool
sort = Bool
True
, separateLists :: Bool
separateLists = Bool
True
, breakWhere :: BreakWhere
breakWhere = BreakWhere
Exports
, openBracket :: OpenBracket
openBracket = OpenBracket
NextLine
}
step :: Maybe Int -> Config -> Step
step :: Maybe Int -> Config -> Step
step Maybe Int
maxCols = String -> (Lines -> Module -> Lines) -> Step
makeStep String
"Module header" forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Int -> Config -> Lines -> Module -> Lines
printModuleHeader Maybe Int
maxCols
printModuleHeader :: Maybe Int -> Config -> Lines -> Module -> Lines
Maybe Int
maxCols Config
conf Lines
ls Module
lmodul =
let modul :: HsModule GhcPs
modul = forall l e. GenLocated l e -> e
GHC.unLoc Module
lmodul
name :: Maybe ModuleName
name = forall l e. GenLocated l e -> e
GHC.unLoc forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall p. HsModule p -> Maybe (XRec p ModuleName)
GHC.hsmodName HsModule GhcPs
modul
startLine :: Int
startLine = forall a. a -> Maybe a -> a
fromMaybe Int
1 forall a b. (a -> b) -> a -> b
$ Maybe Int
moduleLine forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
(forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap RealSrcSpan -> Int
GHC.srcSpanStartLine forall b c a. (b -> c) -> (a -> b) -> a -> c
. SrcSpan -> Maybe RealSrcSpan
GHC.srcSpanToRealSrcSpan forall a b. (a -> b) -> a -> b
$
forall l e. GenLocated l e -> l
GHC.getLoc Module
lmodul)
endLine :: Int
endLine = forall a. a -> Maybe a -> a
fromMaybe Int
1 forall a b. (a -> b) -> a -> b
$ Maybe Int
whereLine forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
(do
SrcSpan
loc <- forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
GHC.getLocA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall p. HsModule p -> Maybe (XRec p [LIE p])
GHC.hsmodExports HsModule GhcPs
modul
RealSrcSpan -> Int
GHC.srcSpanEndLine forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SrcSpan -> Maybe RealSrcSpan
GHC.srcSpanToRealSrcSpan SrcSpan
loc)
keywordLine :: AnnKeywordId -> Maybe Int
keywordLine AnnKeywordId
kw = forall a. [a] -> Maybe a
listToMaybe forall a b. (a -> b) -> a -> b
$ do
GHC.EpAnn {AnnsModule
Anchor
EpAnnComments
entry :: forall ann. EpAnn ann -> Anchor
anns :: forall ann. EpAnn ann -> ann
comments :: forall ann. EpAnn ann -> EpAnnComments
comments :: EpAnnComments
anns :: AnnsModule
entry :: Anchor
..} <- forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ XModulePs -> EpAnn AnnsModule
GHC.hsmodAnn forall a b. (a -> b) -> a -> b
$ forall p. HsModule p -> XCModule p
GHC.hsmodExt HsModule GhcPs
modul
GHC.AddEpAnn AnnKeywordId
kw' (GHC.EpaSpan RealSrcSpan
s Maybe BufSpan
_) <- AnnsModule -> [AddEpAnn]
GHC.am_main AnnsModule
anns
forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ AnnKeywordId
kw forall a. Eq a => a -> a -> Bool
== AnnKeywordId
kw'
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ RealSrcSpan -> Int
GHC.srcSpanEndLine RealSrcSpan
s
moduleLine :: Maybe Int
moduleLine = AnnKeywordId -> Maybe Int
keywordLine AnnKeywordId
GHC.AnnModule
whereLine :: Maybe Int
whereLine = AnnKeywordId -> Maybe Int
keywordLine AnnKeywordId
GHC.AnnWhere
commentOnLine :: Int -> Maybe LEpaComment
commentOnLine Int
l = forall a. [a] -> Maybe a
listToMaybe forall a b. (a -> b) -> a -> b
$ do
LEpaComment
comment <- forall a. EpAnn a -> [LEpaComment]
epAnnComments forall a b. (a -> b) -> a -> b
$ XModulePs -> EpAnn AnnsModule
GHC.hsmodAnn forall a b. (a -> b) -> a -> b
$ forall p. HsModule p -> XCModule p
GHC.hsmodExt HsModule GhcPs
modul
forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ RealSrcSpan -> Int
GHC.srcSpanStartLine (Anchor -> RealSrcSpan
GHC.anchor forall a b. (a -> b) -> a -> b
$ forall l e. GenLocated l e -> l
GHC.getLoc LEpaComment
comment) forall a. Eq a => a -> a -> Bool
== Int
l
forall (f :: * -> *) a. Applicative f => a -> f a
pure LEpaComment
comment
moduleComment :: Maybe LEpaComment
moduleComment = Maybe Int
moduleLine forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> Maybe LEpaComment
commentOnLine
whereComment :: Maybe LEpaComment
whereComment =
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Maybe Int
whereLine forall a. Eq a => a -> a -> Bool
/= Maybe Int
moduleLine) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe Int
whereLine forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> Maybe LEpaComment
commentOnLine
exportGroups :: Maybe [CommentGroup (GenLocated SrcSpanAnnA (IE GhcPs))]
exportGroups = case forall p. HsModule p -> Maybe (XRec p [LIE p])
GHC.hsmodExports HsModule GhcPs
modul of
Maybe (XRec GhcPs [LIE GhcPs])
Nothing -> forall a. Maybe a
Nothing
Just XRec GhcPs [LIE GhcPs]
lexports -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ [CommentGroup (GenLocated SrcSpanAnnA (IE GhcPs))]
-> [CommentGroup (GenLocated SrcSpanAnnA (IE GhcPs))]
doSort forall a b. (a -> b) -> a -> b
$ forall a.
(a -> Maybe RealSrcSpan)
-> [a] -> [LEpaComment] -> [CommentGroup a]
commentGroups
(SrcSpan -> Maybe RealSrcSpan
GHC.srcSpanToRealSrcSpan forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
GHC.getLocA)
(forall l e. GenLocated l e -> e
GHC.unLoc XRec GhcPs [LIE GhcPs]
lexports)
(forall a. EpAnn a -> [LEpaComment]
epAnnComments forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. SrcSpanAnn' a -> a
GHC.ann forall a b. (a -> b) -> a -> b
$ forall l e. GenLocated l e -> l
GHC.getLoc XRec GhcPs [LIE GhcPs]
lexports)
printedModuleHeader :: Lines
printedModuleHeader = forall a. PrinterConfig -> Printer a -> Lines
runPrinter_
(Maybe Int -> PrinterConfig
PrinterConfig Maybe Int
maxCols)
(Config
-> Maybe ModuleName
-> Maybe [CommentGroup (LIE GhcPs)]
-> Maybe LEpaComment
-> Maybe LEpaComment
-> P ()
printHeader
Config
conf Maybe ModuleName
name Maybe [CommentGroup (GenLocated SrcSpanAnnA (IE GhcPs))]
exportGroups Maybe LEpaComment
moduleComment Maybe LEpaComment
whereComment)
changes :: Edits
changes = Block String -> (Lines -> Lines) -> Edits
Editor.changeLines
(forall a. Int -> Int -> Block a
Editor.Block Int
startLine Int
endLine)
(forall a b. a -> b -> a
const Lines
printedModuleHeader) in
Edits -> Lines -> Lines
Editor.apply Edits
changes Lines
ls
where
doSort :: [CommentGroup (GenLocated SrcSpanAnnA (IE GhcPs))]
-> [CommentGroup (GenLocated SrcSpanAnnA (IE GhcPs))]
doSort = if Config -> Bool
sort Config
conf then forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. (a -> a -> Ordering) -> CommentGroup a -> CommentGroup a
commentGroupSort LIE GhcPs -> LIE GhcPs -> Ordering
compareLIE) else forall a. a -> a
id
printHeader
:: Config
-> Maybe GHC.ModuleName
-> Maybe [CommentGroup (GHC.LIE GHC.GhcPs)]
-> Maybe GHC.LEpaComment
-> Maybe GHC.LEpaComment
-> P ()
Config
conf Maybe ModuleName
mbName Maybe [CommentGroup (LIE GhcPs)]
mbExps Maybe LEpaComment
mbModuleComment Maybe LEpaComment
mbWhereComment = do
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ Maybe ModuleName
mbName forall a b. (a -> b) -> a -> b
$ \ModuleName
name -> do
String -> P ()
putText String
"module"
P ()
space
String -> P ()
putText (forall a. Outputable a => a -> String
showOutputable ModuleName
name)
case Maybe [CommentGroup (LIE GhcPs)]
mbExps of
Maybe [CommentGroup (LIE GhcPs)]
Nothing -> do
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall a. Maybe a -> Bool
isJust Maybe ModuleName
mbName) forall a b. (a -> b) -> a -> b
$ case Config -> BreakWhere
breakWhere Config
conf of
BreakWhere
Always -> do
P ()
attachModuleComment
P ()
newline
Int -> P ()
spaces (Config -> Int
indent Config
conf)
BreakWhere
_ -> P ()
space
String -> P ()
putText String
"where"
Just [CommentGroup (LIE GhcPs)]
exports -> case Config -> BreakWhere
breakWhere Config
conf of
BreakWhere
Single | [] <- [CommentGroup (LIE GhcPs)]
exports -> do
Config -> [LIE GhcPs] -> P ()
printSingleLineExportList Config
conf []
P ()
attachModuleComment
BreakWhere
Single | [CommentGroup (LIE GhcPs)
egroup] <- [CommentGroup (LIE GhcPs)]
exports
, Bool -> Bool
not (forall a. CommentGroup a -> Bool
commentGroupHasComments CommentGroup (LIE GhcPs)
egroup)
, [(GenLocated SrcSpanAnnA (IE GhcPs)
export, Maybe LEpaComment
_)] <- (forall a. CommentGroup a -> [(a, Maybe LEpaComment)]
cgItems CommentGroup (LIE GhcPs)
egroup) -> do
Config -> [LIE GhcPs] -> P ()
printSingleLineExportList Config
conf [GenLocated SrcSpanAnnA (IE GhcPs)
export]
P ()
attachModuleComment
BreakWhere
Inline | [] <- [CommentGroup (LIE GhcPs)]
exports -> do
Config -> [LIE GhcPs] -> P ()
printSingleLineExportList Config
conf []
P ()
attachModuleComment
BreakWhere
Inline | [CommentGroup (LIE GhcPs)
egroup] <- [CommentGroup (LIE GhcPs)]
exports, Bool -> Bool
not (forall a. CommentGroup a -> Bool
commentGroupHasComments CommentGroup (LIE GhcPs)
egroup) -> do
forall a. P a -> P a -> P a
wrapping
(Config -> [LIE GhcPs] -> P ()
printSingleLineExportList Config
conf forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst forall a b. (a -> b) -> a -> b
$ forall a. CommentGroup a -> [(a, Maybe LEpaComment)]
cgItems CommentGroup (LIE GhcPs)
egroup)
(do
P ()
attachOpenBracket
P ()
attachModuleComment
Config -> [CommentGroup (LIE GhcPs)] -> P ()
printMultiLineExportList Config
conf [CommentGroup (LIE GhcPs)]
exports)
BreakWhere
_ -> do
P ()
attachOpenBracket
P ()
attachModuleComment
Config -> [CommentGroup (LIE GhcPs)] -> P ()
printMultiLineExportList Config
conf [CommentGroup (LIE GhcPs)]
exports
Maybe EpaComment -> P ()
putMaybeLineComment forall a b. (a -> b) -> a -> b
$ forall l e. GenLocated l e -> e
GHC.unLoc forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe LEpaComment
mbWhereComment
where
attachModuleComment :: P ()
attachModuleComment = Maybe EpaComment -> P ()
putMaybeLineComment forall a b. (a -> b) -> a -> b
$ forall l e. GenLocated l e -> e
GHC.unLoc forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe LEpaComment
mbModuleComment
attachOpenBracket :: P ()
attachOpenBracket
| Config -> OpenBracket
openBracket Config
conf forall a. Eq a => a -> a -> Bool
== OpenBracket
SameLine = String -> P ()
putText String
" ("
| Bool
otherwise = forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
printSingleLineExportList
:: Config -> [GHC.LIE GHC.GhcPs] -> P ()
printSingleLineExportList :: Config -> [LIE GhcPs] -> P ()
printSingleLineExportList Config
conf [LIE GhcPs]
exports = do
P ()
space forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> P ()
putText String
"("
[LIE GhcPs] -> P ()
printExports [LIE GhcPs]
exports
String -> P ()
putText String
")" forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> P ()
space forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> P ()
putText String
"where"
where
printExports :: [GHC.LIE GHC.GhcPs] -> P ()
printExports :: [LIE GhcPs] -> P ()
printExports = \case
[] -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
[LIE GhcPs
e] -> Config -> LIE GhcPs -> P ()
putExport Config
conf LIE GhcPs
e
(LIE GhcPs
e:[LIE GhcPs]
es) -> Config -> LIE GhcPs -> P ()
putExport Config
conf LIE GhcPs
e forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> P ()
comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> P ()
space forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [LIE GhcPs] -> P ()
printExports [LIE GhcPs]
es
printMultiLineExportList
:: Config
-> [CommentGroup (GHC.LIE GHC.GhcPs)]
-> P ()
printMultiLineExportList :: Config -> [CommentGroup (LIE GhcPs)] -> P ()
printMultiLineExportList Config
conf [CommentGroup (LIE GhcPs)]
exports = do
P ()
newline
P ()
doIndent forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> P ()
putText String
firstChar forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [CommentGroup (LIE GhcPs)]
exports) P ()
space
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ forall {c}.
(CommentGroup (GenLocated SrcSpanAnnA (IE GhcPs)), Bool, c) -> P ()
printExport forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [(a, Bool, Bool)]
flagEnds [CommentGroup (LIE GhcPs)]
exports
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [CommentGroup (LIE GhcPs)]
exports) forall a b. (a -> b) -> a -> b
$ P ()
newline forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> P ()
doIndent
String -> P ()
putText String
")" forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> P ()
space forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> P ()
putText String
"where"
where
printExport :: (CommentGroup (GenLocated SrcSpanAnnA (IE GhcPs)), Bool, c) -> P ()
printExport (CommentGroup {[(GenLocated SrcSpanAnnA (IE GhcPs), Maybe LEpaComment)]
[LEpaComment]
Block String
cgFollowing :: forall a. CommentGroup a -> [LEpaComment]
cgPrior :: forall a. CommentGroup a -> [LEpaComment]
cgBlock :: forall a. CommentGroup a -> Block String
cgFollowing :: [LEpaComment]
cgItems :: [(GenLocated SrcSpanAnnA (IE GhcPs), Maybe LEpaComment)]
cgPrior :: [LEpaComment]
cgBlock :: Block String
cgItems :: forall a. CommentGroup a -> [(a, Maybe LEpaComment)]
..}, Bool
firstGroup, c
_lastGroup) = do
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (forall a. [a] -> [(a, Bool, Bool)]
flagEnds [LEpaComment]
cgPrior) forall a b. (a -> b) -> a -> b
$ \(LEpaComment
cmt, Bool
start, Bool
_end) -> do
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Bool
firstGroup Bool -> Bool -> Bool
&& Bool
start) forall a b. (a -> b) -> a -> b
$ P ()
space forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> P ()
space
EpaComment -> P ()
putComment forall a b. (a -> b) -> a -> b
$ forall l e. GenLocated l e -> e
GHC.unLoc LEpaComment
cmt
P ()
newline forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> P ()
doIndent
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (forall a. [a] -> [(a, Bool, Bool)]
flagEnds [(GenLocated SrcSpanAnnA (IE GhcPs), Maybe LEpaComment)]
cgItems) forall a b. (a -> b) -> a -> b
$ \((GenLocated SrcSpanAnnA (IE GhcPs)
export, Maybe LEpaComment
mbComment), Bool
start, Bool
_end) -> do
if Bool
firstGroup Bool -> Bool -> Bool
&& Bool
start then
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [LEpaComment]
cgPrior) forall a b. (a -> b) -> a -> b
$ P ()
space forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> P ()
space
else
P ()
comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> P ()
space
Config -> LIE GhcPs -> P ()
putExport Config
conf GenLocated SrcSpanAnnA (IE GhcPs)
export
Maybe EpaComment -> P ()
putMaybeLineComment forall a b. (a -> b) -> a -> b
$ forall l e. GenLocated l e -> e
GHC.unLoc forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe LEpaComment
mbComment
P ()
newline forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> P ()
doIndent
firstChar :: String
firstChar = case Config -> OpenBracket
openBracket Config
conf of
OpenBracket
SameLine -> String
" "
OpenBracket
NextLine -> String
"("
doIndent :: P ()
doIndent = Int -> P ()
spaces (Config -> Int
indent Config
conf)
putExport :: Config -> GHC.LIE GHC.GhcPs -> P ()
putExport :: Config -> LIE GhcPs -> P ()
putExport Config
conf = Bool -> IE GhcPs -> P ()
Imports.printImport (Config -> Bool
separateLists Config
conf) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall l e. GenLocated l e -> e
GHC.unLoc