{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}

-- | Rendering of modules.
module Ormolu.Printer.Meat.Module
  ( p_hsModule,
  )
where

import Control.Monad
import qualified Data.Text as T
import GHC
import Ormolu.Imports
import Ormolu.Parser.CommentStream
import Ormolu.Parser.Pragma
import Ormolu.Parser.Shebang
import Ormolu.Printer.Combinators
import Ormolu.Printer.Comments
import Ormolu.Printer.Meat.Common
import Ormolu.Printer.Meat.Declaration
import Ormolu.Printer.Meat.Declaration.Warning
import Ormolu.Printer.Meat.ImportExport
import Ormolu.Printer.Meat.Pragma

-- | Render a module.
p_hsModule ::
  -- | Stack header
  Maybe (RealLocated Comment) ->
  -- | Shebangs
  [Shebang] ->
  -- | Pragmas and the associated comments
  [([RealLocated Comment], Pragma)] ->
  -- | Whether to use postfix qualified imports
  Bool ->
  -- | AST to print
  HsModule GhcPs ->
  R ()
p_hsModule :: Maybe (RealLocated Comment)
-> [Shebang]
-> [([RealLocated Comment], Pragma)]
-> Bool
-> HsModule GhcPs
-> R ()
p_hsModule Maybe (RealLocated Comment)
mstackHeader [Shebang]
shebangs [([RealLocated Comment], Pragma)]
pragmas Bool
qualifiedPost HsModule {[LHsDecl GhcPs]
[LImportDecl GhcPs]
Maybe (Located [LIE GhcPs])
Maybe LHsDocString
Maybe (Located WarningTxt)
Maybe (Located ModuleName)
hsmodName :: forall pass. HsModule pass -> Maybe (Located ModuleName)
hsmodExports :: forall pass. HsModule pass -> Maybe (Located [LIE pass])
hsmodImports :: forall pass. HsModule pass -> [LImportDecl pass]
hsmodDecls :: forall pass. HsModule pass -> [LHsDecl pass]
hsmodDeprecMessage :: forall pass. HsModule pass -> Maybe (Located WarningTxt)
hsmodHaddockModHeader :: forall pass. HsModule pass -> Maybe LHsDocString
hsmodHaddockModHeader :: Maybe LHsDocString
hsmodDeprecMessage :: Maybe (Located WarningTxt)
hsmodDecls :: [LHsDecl GhcPs]
hsmodImports :: [LImportDecl GhcPs]
hsmodExports :: Maybe (Located [LIE GhcPs])
hsmodName :: Maybe (Located ModuleName)
..} = do
  let deprecSpan :: [SrcSpan]
deprecSpan = [SrcSpan]
-> (Located WarningTxt -> [SrcSpan])
-> Maybe (Located WarningTxt)
-> [SrcSpan]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\(L SrcSpan
s WarningTxt
_) -> [SrcSpan
s]) Maybe (Located WarningTxt)
hsmodDeprecMessage
      exportSpans :: [SrcSpan]
exportSpans = [SrcSpan]
-> (Located [LIE GhcPs] -> [SrcSpan])
-> Maybe (Located [LIE GhcPs])
-> [SrcSpan]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\(L SrcSpan
s [LIE GhcPs]
_) -> [SrcSpan
s]) Maybe (Located [LIE GhcPs])
hsmodExports
  [SrcSpan] -> R () -> R ()
switchLayout ([SrcSpan]
deprecSpan [SrcSpan] -> [SrcSpan] -> [SrcSpan]
forall a. Semigroup a => a -> a -> a
<> [SrcSpan]
exportSpans) (R () -> R ()) -> R () -> R ()
forall a b. (a -> b) -> a -> b
$ do
    [Shebang] -> (Shebang -> R ()) -> R ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Shebang]
shebangs ((Shebang -> R ()) -> R ()) -> (Shebang -> R ()) -> R ()
forall a b. (a -> b) -> a -> b
$ \(Shebang Located String
x) ->
      Located String -> (String -> R ()) -> R ()
forall a. Located a -> (a -> R ()) -> R ()
located Located String
x ((String -> R ()) -> R ()) -> (String -> R ()) -> R ()
forall a b. (a -> b) -> a -> b
$ \String
shebang -> do
        Text -> R ()
txt (String -> Text
T.pack String
shebang)
        R ()
newline
    Maybe (RealLocated Comment)
-> (RealLocated Comment -> R ()) -> R ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ Maybe (RealLocated Comment)
mstackHeader ((RealLocated Comment -> R ()) -> R ())
-> (RealLocated Comment -> R ()) -> R ()
forall a b. (a -> b) -> a -> b
$ \(L RealSrcSpan
spn Comment
comment) -> do
      RealSrcSpan -> Comment -> R ()
spitCommentNow RealSrcSpan
spn Comment
comment
      R ()
newline
    R ()
newline
    [([RealLocated Comment], Pragma)] -> R ()
p_pragmas [([RealLocated Comment], Pragma)]
pragmas
    R ()
newline
    case Maybe (Located ModuleName)
hsmodName of
      Maybe (Located ModuleName)
Nothing -> () -> R ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
      Just Located ModuleName
hsmodName' -> do
        Located ModuleName -> (ModuleName -> R ()) -> R ()
forall a. Located a -> (a -> R ()) -> R ()
located Located ModuleName
hsmodName' ((ModuleName -> R ()) -> R ()) -> (ModuleName -> R ()) -> R ()
forall a b. (a -> b) -> a -> b
$ \ModuleName
name -> do
          Maybe LHsDocString -> (LHsDocString -> R ()) -> R ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ Maybe LHsDocString
hsmodHaddockModHeader (HaddockStyle -> Bool -> LHsDocString -> R ()
p_hsDocString HaddockStyle
Pipe Bool
True)
          ModuleName -> R ()
p_hsmodName ModuleName
name
        R ()
breakpoint
        Maybe (Located WarningTxt) -> (Located WarningTxt -> R ()) -> R ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ Maybe (Located WarningTxt)
hsmodDeprecMessage ((Located WarningTxt -> R ()) -> R ())
-> (Located WarningTxt -> R ()) -> R ()
forall a b. (a -> b) -> a -> b
$ \Located WarningTxt
w -> do
          (WarningTxt -> R ()) -> Located WarningTxt -> R ()
forall a. (a -> R ()) -> Located a -> R ()
located' WarningTxt -> R ()
p_moduleWarning Located WarningTxt
w
          R ()
breakpoint
        case Maybe (Located [LIE GhcPs])
hsmodExports of
          Maybe (Located [LIE GhcPs])
Nothing -> () -> R ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
          Just Located [LIE GhcPs]
l -> do
            Located [LIE GhcPs] -> ([LIE GhcPs] -> R ()) -> R ()
forall a. Located a -> (a -> R ()) -> R ()
located Located [LIE GhcPs]
l (([LIE GhcPs] -> R ()) -> R ()) -> ([LIE GhcPs] -> R ()) -> R ()
forall a b. (a -> b) -> a -> b
$ \[LIE GhcPs]
exports -> do
              R () -> R ()
inci ([LIE GhcPs] -> R ()
p_hsmodExports [LIE GhcPs]
exports)
            R ()
breakpoint
        Text -> R ()
txt Text
"where"
        R ()
newline
    R ()
newline
    [LImportDecl GhcPs] -> (LImportDecl GhcPs -> R ()) -> R ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ ([LImportDecl GhcPs] -> [LImportDecl GhcPs]
sortImports [LImportDecl GhcPs]
hsmodImports) ((ImportDecl GhcPs -> R ()) -> LImportDecl GhcPs -> R ()
forall a. (a -> R ()) -> Located a -> R ()
located' (Bool -> ImportDecl GhcPs -> R ()
p_hsmodImport Bool
qualifiedPost))
    R ()
newline
    [SrcSpan] -> R () -> R ()
switchLayout (LHsDecl GhcPs -> SrcSpan
forall a. HasSrcSpan a => a -> SrcSpan
getLoc (LHsDecl GhcPs -> SrcSpan) -> [LHsDecl GhcPs] -> [SrcSpan]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [LHsDecl GhcPs]
hsmodDecls) (R () -> R ()) -> R () -> R ()
forall a b. (a -> b) -> a -> b
$ do
      FamilyStyle -> [LHsDecl GhcPs] -> R ()
p_hsDecls FamilyStyle
Free [LHsDecl GhcPs]
hsmodDecls
      R ()
newline
      R ()
spitRemainingComments