{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Ormolu.Printer.Meat.Common
( FamilyStyle (..),
p_hsmodName,
p_ieWrappedName,
p_rdrName,
doesNotNeedExtraParens,
p_qualName,
p_infixDefHelper,
p_hsDocString,
p_hsDocName,
)
where
import Control.Monad
import Data.List (isPrefixOf)
import Data.Maybe (isJust)
import qualified Data.Text as T
import GHC hiding (GhcPs, IE)
import Name (nameStableString)
import OccName (OccName (..))
import Ormolu.Printer.Combinators
import Ormolu.Utils
import RdrName (RdrName (..))
data FamilyStyle
=
Associated
|
Free
p_hsmodName :: ModuleName -> R ()
p_hsmodName mname = do
txt "module"
space
atom mname
p_ieWrappedName :: IEWrappedName RdrName -> R ()
p_ieWrappedName = \case
IEName x -> p_rdrName x
IEPattern x -> do
txt "pattern"
space
p_rdrName x
IEType x -> do
txt "type"
space
p_rdrName x
p_rdrName :: Located RdrName -> R ()
p_rdrName l@(L spn _) = located l $ \x -> do
ids <- getAnns spn
let backticksWrapper =
if AnnBackquote `elem` ids
then backticks
else id
parensWrapper =
if AnnOpenP `elem` ids
then parens N
else id
singleQuoteWrapper =
if AnnSimpleQuote `elem` ids
then \y -> do
txt "'"
y
else id
m =
case x of
Unqual occName ->
atom occName
Qual mname occName ->
p_qualName mname occName
Orig _ occName ->
atom occName
Exact name ->
atom name
m' = backticksWrapper (singleQuoteWrapper m)
if doesNotNeedExtraParens x
then m'
else parensWrapper m'
doesNotNeedExtraParens :: RdrName -> Bool
doesNotNeedExtraParens = \case
Exact name ->
let s = nameStableString name
in
("$ghc-prim$GHC.Tuple$" `isPrefixOf` s)
|| ("$ghc-prim$GHC.Types$[]" `isPrefixOf` s)
_ -> False
p_qualName :: ModuleName -> OccName -> R ()
p_qualName mname occName = do
atom mname
txt "."
atom occName
p_infixDefHelper ::
Bool ->
(R () -> R ()) ->
R () ->
[R ()] ->
R ()
p_infixDefHelper isInfix inci' name args =
case (isInfix, args) of
(True, p0 : p1 : ps) -> do
let parens' =
if null ps
then id
else parens N
parens' $ do
p0
breakpoint
inci $ sitcc $ do
name
space
p1
unless (null ps) . inci' $ do
breakpoint
sitcc (sep breakpoint sitcc ps)
(_, ps) -> do
name
unless (null ps) $ do
breakpoint
inci' $ sitcc (sep breakpoint sitcc args)
p_hsDocString ::
HaddockStyle ->
Bool ->
LHsDocString ->
R ()
p_hsDocString hstyle needsNewline (L l str) = do
goesAfterComment <- isJust <$> getLastCommentSpan
when goesAfterComment newline
forM_ (zip (splitDocString str) (True : repeat False)) $ \(x, isFirst) -> do
if isFirst
then case hstyle of
Pipe -> txt "-- |"
Caret -> txt "-- ^"
Asterisk n -> txt ("-- " <> T.replicate n "*")
Named name -> p_hsDocName name
else newline >> txt "--"
space
unless (T.null x) (txt x)
when needsNewline newline
case l of
UnhelpfulSpan _ ->
getEnclosingSpan (const True) >>= mapM_ (setLastCommentSpan (Just hstyle))
RealSrcSpan spn -> setLastCommentSpan (Just hstyle) spn
p_hsDocName :: String -> R ()
p_hsDocName name = txt ("-- $" <> T.pack name)