{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module GHC.Utils.Outputable (
Outputable(..), OutputableBndr(..), OutputableP(..),
SDoc, runSDoc, PDoc(..),
docToSDoc,
interppSP, interpp'SP, interpp'SP',
pprQuotedList, pprWithCommas, quotedListWithOr, quotedListWithNor,
pprWithBars,
empty, isEmpty, nest,
char,
text, ftext, ptext, ztext,
int, intWithCommas, integer, word, float, double, rational, doublePrec,
parens, cparen, brackets, braces, quotes, quote,
doubleQuotes, angleBrackets,
semi, comma, colon, dcolon, space, equals, dot, vbar,
arrow, lollipop, larrow, darrow, arrowt, larrowt, arrowtt, larrowtt,
lambda,
lparen, rparen, lbrack, rbrack, lbrace, rbrace, underscore, mulArrow,
blankLine, forAllLit, bullet,
(<>), (<+>), hcat, hsep,
($$), ($+$), vcat,
sep, cat,
fsep, fcat,
hang, hangNotEmpty, punctuate, ppWhen, ppUnless,
ppWhenOption, ppUnlessOption,
speakNth, speakN, speakNOf, plural, singular,
isOrAre, doOrDoes, itsOrTheir, thisOrThese, hasOrHave,
unicodeSyntax,
coloured, keyword,
printSDoc, printSDocLn,
bufLeftRenderSDoc,
pprCode,
showSDocOneLine,
showSDocUnsafe,
showPprUnsafe,
renderWithContext,
pprDebugAndThen,
pprInfixVar, pprPrefixVar,
pprHsChar, pprHsString, pprHsBytes,
primFloatSuffix, primCharSuffix, primDoubleSuffix,
primInt8Suffix, primWord8Suffix,
primInt16Suffix, primWord16Suffix,
primInt32Suffix, primWord32Suffix,
primInt64Suffix, primWord64Suffix,
primIntSuffix, primWordSuffix,
pprPrimChar, pprPrimInt, pprPrimWord,
pprPrimInt8, pprPrimWord8,
pprPrimInt16, pprPrimWord16,
pprPrimInt32, pprPrimWord32,
pprPrimInt64, pprPrimWord64,
pprFastFilePath, pprFilePathString,
BindingSite(..),
PprStyle(..), LabelStyle(..), PrintUnqualified(..),
QueryQualifyName, QueryQualifyModule, QueryQualifyPackage,
reallyAlwaysQualify, reallyAlwaysQualifyNames,
alwaysQualify, alwaysQualifyNames, alwaysQualifyModules,
neverQualify, neverQualifyNames, neverQualifyModules,
alwaysQualifyPackages, neverQualifyPackages,
QualifyName(..), queryQual,
sdocOption,
updSDocContext,
SDocContext (..), sdocWithContext, defaultSDocContext,
getPprStyle, withPprStyle, setStyleColoured,
pprDeeper, pprDeeperList, pprSetDepth,
codeStyle, userStyle, dumpStyle, asmStyle,
qualName, qualModule, qualPackage,
mkErrStyle, defaultErrStyle, defaultDumpStyle, mkDumpStyle, defaultUserStyle,
mkUserStyle, cmdlineParserStyle, Depth(..),
withUserStyle, withErrStyle,
ifPprDebug, whenPprDebug, getPprDebug,
) where
import GHC.Prelude
import {-# SOURCE #-} GHC.Unit.Types ( Unit, Module, moduleName )
import {-# SOURCE #-} GHC.Unit.Module.Name( ModuleName )
import {-# SOURCE #-} GHC.Types.Name.Occurrence( OccName )
import GHC.Utils.BufHandle (BufHandle)
import GHC.Data.FastString
import qualified GHC.Utils.Ppr as Pretty
import qualified GHC.Utils.Ppr.Colour as Col
import GHC.Utils.Ppr ( Doc, Mode(..) )
import GHC.Serialized
import GHC.LanguageExtensions (Extension)
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import Data.Char
import qualified Data.Map as M
import Data.Int
import qualified Data.IntMap as IM
import Data.Set (Set)
import qualified Data.Set as Set
import qualified Data.IntSet as IntSet
import Data.String
import Data.Word
import System.IO ( Handle )
import System.FilePath
import Text.Printf
import Numeric (showFFloat)
import Data.Graph (SCC(..))
import Data.List (intersperse)
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.List.NonEmpty as NEL
import Data.Time
import Data.Time.Format.ISO8601
import GHC.Fingerprint
import GHC.Show ( showMultiLineString )
import GHC.Utils.Exception
import GHC.Exts (oneShot)
data PprStyle
= PprUser PrintUnqualified Depth Coloured
| PprDump PrintUnqualified
| PprCode !LabelStyle
data LabelStyle
= CStyle
| AsmStyle
deriving (LabelStyle -> LabelStyle -> Bool
(LabelStyle -> LabelStyle -> Bool)
-> (LabelStyle -> LabelStyle -> Bool) -> Eq LabelStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LabelStyle -> LabelStyle -> Bool
== :: LabelStyle -> LabelStyle -> Bool
$c/= :: LabelStyle -> LabelStyle -> Bool
/= :: LabelStyle -> LabelStyle -> Bool
Eq,Eq LabelStyle
Eq LabelStyle
-> (LabelStyle -> LabelStyle -> Ordering)
-> (LabelStyle -> LabelStyle -> Bool)
-> (LabelStyle -> LabelStyle -> Bool)
-> (LabelStyle -> LabelStyle -> Bool)
-> (LabelStyle -> LabelStyle -> Bool)
-> (LabelStyle -> LabelStyle -> LabelStyle)
-> (LabelStyle -> LabelStyle -> LabelStyle)
-> Ord LabelStyle
LabelStyle -> LabelStyle -> Bool
LabelStyle -> LabelStyle -> Ordering
LabelStyle -> LabelStyle -> LabelStyle
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: LabelStyle -> LabelStyle -> Ordering
compare :: LabelStyle -> LabelStyle -> Ordering
$c< :: LabelStyle -> LabelStyle -> Bool
< :: LabelStyle -> LabelStyle -> Bool
$c<= :: LabelStyle -> LabelStyle -> Bool
<= :: LabelStyle -> LabelStyle -> Bool
$c> :: LabelStyle -> LabelStyle -> Bool
> :: LabelStyle -> LabelStyle -> Bool
$c>= :: LabelStyle -> LabelStyle -> Bool
>= :: LabelStyle -> LabelStyle -> Bool
$cmax :: LabelStyle -> LabelStyle -> LabelStyle
max :: LabelStyle -> LabelStyle -> LabelStyle
$cmin :: LabelStyle -> LabelStyle -> LabelStyle
min :: LabelStyle -> LabelStyle -> LabelStyle
Ord,Int -> LabelStyle -> ShowS
[LabelStyle] -> ShowS
LabelStyle -> String
(Int -> LabelStyle -> ShowS)
-> (LabelStyle -> String)
-> ([LabelStyle] -> ShowS)
-> Show LabelStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LabelStyle -> ShowS
showsPrec :: Int -> LabelStyle -> ShowS
$cshow :: LabelStyle -> String
show :: LabelStyle -> String
$cshowList :: [LabelStyle] -> ShowS
showList :: [LabelStyle] -> ShowS
Show)
data Depth
= AllTheWay
| PartWay Int
| DefaultDepth
data Coloured
= Uncoloured
| Coloured
data PrintUnqualified = QueryQualify {
PrintUnqualified -> QueryQualifyName
queryQualifyName :: QueryQualifyName,
PrintUnqualified -> QueryQualifyModule
queryQualifyModule :: QueryQualifyModule,
PrintUnqualified -> QueryQualifyPackage
queryQualifyPackage :: QueryQualifyPackage
}
type QueryQualifyName = Module -> OccName -> QualifyName
type QueryQualifyModule = Module -> Bool
type QueryQualifyPackage = Unit -> Bool
data QualifyName
= NameUnqual
| NameQual ModuleName
| NameNotInScope1
| NameNotInScope2
instance Outputable QualifyName where
ppr :: QualifyName -> SDoc
ppr QualifyName
NameUnqual = String -> SDoc
text String
"NameUnqual"
ppr (NameQual ModuleName
_mod) = String -> SDoc
text String
"NameQual"
ppr QualifyName
NameNotInScope1 = String -> SDoc
text String
"NameNotInScope1"
ppr QualifyName
NameNotInScope2 = String -> SDoc
text String
"NameNotInScope2"
reallyAlwaysQualifyNames :: QueryQualifyName
reallyAlwaysQualifyNames :: QueryQualifyName
reallyAlwaysQualifyNames Module
_ OccName
_ = QualifyName
NameNotInScope2
alwaysQualifyNames :: QueryQualifyName
alwaysQualifyNames :: QueryQualifyName
alwaysQualifyNames Module
m OccName
_ = ModuleName -> QualifyName
NameQual (Module -> ModuleName
forall a. GenModule a -> ModuleName
moduleName Module
m)
neverQualifyNames :: QueryQualifyName
neverQualifyNames :: QueryQualifyName
neverQualifyNames Module
_ OccName
_ = QualifyName
NameUnqual
alwaysQualifyModules :: QueryQualifyModule
alwaysQualifyModules :: QueryQualifyModule
alwaysQualifyModules Module
_ = Bool
True
neverQualifyModules :: QueryQualifyModule
neverQualifyModules :: QueryQualifyModule
neverQualifyModules Module
_ = Bool
False
alwaysQualifyPackages :: QueryQualifyPackage
alwaysQualifyPackages :: QueryQualifyPackage
alwaysQualifyPackages Unit
_ = Bool
True
neverQualifyPackages :: QueryQualifyPackage
neverQualifyPackages :: QueryQualifyPackage
neverQualifyPackages Unit
_ = Bool
False
reallyAlwaysQualify, alwaysQualify, neverQualify :: PrintUnqualified
reallyAlwaysQualify :: PrintUnqualified
reallyAlwaysQualify
= QueryQualifyName
-> QueryQualifyModule -> QueryQualifyPackage -> PrintUnqualified
QueryQualify QueryQualifyName
reallyAlwaysQualifyNames
QueryQualifyModule
alwaysQualifyModules
QueryQualifyPackage
alwaysQualifyPackages
alwaysQualify :: PrintUnqualified
alwaysQualify = QueryQualifyName
-> QueryQualifyModule -> QueryQualifyPackage -> PrintUnqualified
QueryQualify QueryQualifyName
alwaysQualifyNames
QueryQualifyModule
alwaysQualifyModules
QueryQualifyPackage
alwaysQualifyPackages
neverQualify :: PrintUnqualified
neverQualify = QueryQualifyName
-> QueryQualifyModule -> QueryQualifyPackage -> PrintUnqualified
QueryQualify QueryQualifyName
neverQualifyNames
QueryQualifyModule
neverQualifyModules
QueryQualifyPackage
neverQualifyPackages
defaultUserStyle :: PprStyle
defaultUserStyle :: PprStyle
defaultUserStyle = PrintUnqualified -> Depth -> PprStyle
mkUserStyle PrintUnqualified
neverQualify Depth
AllTheWay
defaultDumpStyle :: PprStyle
defaultDumpStyle :: PprStyle
defaultDumpStyle = PrintUnqualified -> PprStyle
PprDump PrintUnqualified
neverQualify
mkDumpStyle :: PrintUnqualified -> PprStyle
mkDumpStyle :: PrintUnqualified -> PprStyle
mkDumpStyle PrintUnqualified
print_unqual = PrintUnqualified -> PprStyle
PprDump PrintUnqualified
print_unqual
defaultErrStyle :: PprStyle
defaultErrStyle :: PprStyle
defaultErrStyle = PrintUnqualified -> PprStyle
mkErrStyle PrintUnqualified
neverQualify
mkErrStyle :: PrintUnqualified -> PprStyle
mkErrStyle :: PrintUnqualified -> PprStyle
mkErrStyle PrintUnqualified
unqual = PrintUnqualified -> Depth -> PprStyle
mkUserStyle PrintUnqualified
unqual Depth
DefaultDepth
cmdlineParserStyle :: PprStyle
cmdlineParserStyle :: PprStyle
cmdlineParserStyle = PrintUnqualified -> Depth -> PprStyle
mkUserStyle PrintUnqualified
alwaysQualify Depth
AllTheWay
mkUserStyle :: PrintUnqualified -> Depth -> PprStyle
mkUserStyle :: PrintUnqualified -> Depth -> PprStyle
mkUserStyle PrintUnqualified
unqual Depth
depth = PrintUnqualified -> Depth -> Coloured -> PprStyle
PprUser PrintUnqualified
unqual Depth
depth Coloured
Uncoloured
withUserStyle :: PrintUnqualified -> Depth -> SDoc -> SDoc
withUserStyle :: PrintUnqualified -> Depth -> SDoc -> SDoc
withUserStyle PrintUnqualified
unqual Depth
depth SDoc
doc = PprStyle -> SDoc -> SDoc
withPprStyle (PrintUnqualified -> Depth -> Coloured -> PprStyle
PprUser PrintUnqualified
unqual Depth
depth Coloured
Uncoloured) SDoc
doc
withErrStyle :: PrintUnqualified -> SDoc -> SDoc
withErrStyle :: PrintUnqualified -> SDoc -> SDoc
withErrStyle PrintUnqualified
unqual SDoc
doc =
PprStyle -> SDoc -> SDoc
withPprStyle (PrintUnqualified -> PprStyle
mkErrStyle PrintUnqualified
unqual) SDoc
doc
setStyleColoured :: Bool -> PprStyle -> PprStyle
setStyleColoured :: Bool -> PprStyle -> PprStyle
setStyleColoured Bool
col PprStyle
style =
case PprStyle
style of
PprUser PrintUnqualified
q Depth
d Coloured
_ -> PrintUnqualified -> Depth -> Coloured -> PprStyle
PprUser PrintUnqualified
q Depth
d Coloured
c
PprStyle
_ -> PprStyle
style
where
c :: Coloured
c | Bool
col = Coloured
Coloured
| Bool
otherwise = Coloured
Uncoloured
instance Outputable PprStyle where
ppr :: PprStyle -> SDoc
ppr (PprUser {}) = String -> SDoc
text String
"user-style"
ppr (PprCode {}) = String -> SDoc
text String
"code-style"
ppr (PprDump {}) = String -> SDoc
text String
"dump-style"
newtype SDoc = SDoc' (SDocContext -> Doc)
{-# COMPLETE SDoc #-}
pattern SDoc :: (SDocContext -> Doc) -> SDoc
pattern $mSDoc :: forall {r}.
SDoc -> ((SDocContext -> Doc) -> r) -> ((# #) -> r) -> r
$bSDoc :: (SDocContext -> Doc) -> SDoc
SDoc m <- SDoc' m
where
SDoc SDocContext -> Doc
m = (SDocContext -> Doc) -> SDoc
SDoc' ((SDocContext -> Doc) -> SDocContext -> Doc
forall a b. (a -> b) -> a -> b
oneShot SDocContext -> Doc
m)
runSDoc :: SDoc -> (SDocContext -> Doc)
runSDoc :: SDoc -> SDocContext -> Doc
runSDoc (SDoc SDocContext -> Doc
m) = SDocContext -> Doc
m
data SDocContext = SDC
{ SDocContext -> PprStyle
sdocStyle :: !PprStyle
, SDocContext -> Scheme
sdocColScheme :: !Col.Scheme
, SDocContext -> PprColour
sdocLastColour :: !Col.PprColour
, SDocContext -> Bool
sdocShouldUseColor :: !Bool
, SDocContext -> Int
sdocDefaultDepth :: !Int
, SDocContext -> Int
sdocLineLength :: !Int
, SDocContext -> Bool
sdocCanUseUnicode :: !Bool
, SDocContext -> Bool
sdocHexWordLiterals :: !Bool
, SDocContext -> Bool
sdocPprDebug :: !Bool
, SDocContext -> Bool
sdocPrintUnicodeSyntax :: !Bool
, SDocContext -> Bool
sdocPrintCaseAsLet :: !Bool
, SDocContext -> Bool
sdocPrintTypecheckerElaboration :: !Bool
, SDocContext -> Bool
sdocPrintAxiomIncomps :: !Bool
, SDocContext -> Bool
sdocPrintExplicitKinds :: !Bool
, SDocContext -> Bool
sdocPrintExplicitCoercions :: !Bool
, SDocContext -> Bool
sdocPrintExplicitRuntimeReps :: !Bool
, SDocContext -> Bool
sdocPrintExplicitForalls :: !Bool
, SDocContext -> Bool
sdocPrintPotentialInstances :: !Bool
, SDocContext -> Bool
sdocPrintEqualityRelations :: !Bool
, SDocContext -> Bool
sdocSuppressTicks :: !Bool
, SDocContext -> Bool
sdocSuppressTypeSignatures :: !Bool
, SDocContext -> Bool
sdocSuppressTypeApplications :: !Bool
, SDocContext -> Bool
sdocSuppressIdInfo :: !Bool
, SDocContext -> Bool
sdocSuppressCoercions :: !Bool
, SDocContext -> Bool
sdocSuppressUnfoldings :: !Bool
, SDocContext -> Bool
sdocSuppressVarKinds :: !Bool
, SDocContext -> Bool
sdocSuppressUniques :: !Bool
, SDocContext -> Bool
sdocSuppressModulePrefixes :: !Bool
, SDocContext -> Bool
sdocSuppressStgExts :: !Bool
, SDocContext -> Bool
sdocErrorSpans :: !Bool
, SDocContext -> Bool
sdocStarIsType :: !Bool
, SDocContext -> Bool
sdocLinearTypes :: !Bool
, SDocContext -> Bool
sdocImpredicativeTypes :: !Bool
, SDocContext -> Bool
sdocPrintTypeAbbreviations :: !Bool
, SDocContext -> FastString -> SDoc
sdocUnitIdForUser :: !(FastString -> SDoc)
}
instance IsString SDoc where
fromString :: String -> SDoc
fromString = String -> SDoc
text
instance Outputable SDoc where
ppr :: SDoc -> SDoc
ppr = SDoc -> SDoc
forall a. a -> a
id
defaultSDocContext :: SDocContext
defaultSDocContext :: SDocContext
defaultSDocContext = SDC
{ sdocStyle :: PprStyle
sdocStyle = PprStyle
defaultDumpStyle
, sdocColScheme :: Scheme
sdocColScheme = Scheme
Col.defaultScheme
, sdocLastColour :: PprColour
sdocLastColour = PprColour
Col.colReset
, sdocShouldUseColor :: Bool
sdocShouldUseColor = Bool
False
, sdocDefaultDepth :: Int
sdocDefaultDepth = Int
5
, sdocLineLength :: Int
sdocLineLength = Int
100
, sdocCanUseUnicode :: Bool
sdocCanUseUnicode = Bool
False
, sdocHexWordLiterals :: Bool
sdocHexWordLiterals = Bool
False
, sdocPprDebug :: Bool
sdocPprDebug = Bool
False
, sdocPrintUnicodeSyntax :: Bool
sdocPrintUnicodeSyntax = Bool
False
, sdocPrintCaseAsLet :: Bool
sdocPrintCaseAsLet = Bool
False
, sdocPrintTypecheckerElaboration :: Bool
sdocPrintTypecheckerElaboration = Bool
False
, sdocPrintAxiomIncomps :: Bool
sdocPrintAxiomIncomps = Bool
False
, sdocPrintExplicitKinds :: Bool
sdocPrintExplicitKinds = Bool
False
, sdocPrintExplicitCoercions :: Bool
sdocPrintExplicitCoercions = Bool
False
, sdocPrintExplicitRuntimeReps :: Bool
sdocPrintExplicitRuntimeReps = Bool
False
, sdocPrintExplicitForalls :: Bool
sdocPrintExplicitForalls = Bool
False
, sdocPrintPotentialInstances :: Bool
sdocPrintPotentialInstances = Bool
False
, sdocPrintEqualityRelations :: Bool
sdocPrintEqualityRelations = Bool
False
, sdocSuppressTicks :: Bool
sdocSuppressTicks = Bool
False
, sdocSuppressTypeSignatures :: Bool
sdocSuppressTypeSignatures = Bool
False
, sdocSuppressTypeApplications :: Bool
sdocSuppressTypeApplications = Bool
False
, sdocSuppressIdInfo :: Bool
sdocSuppressIdInfo = Bool
False
, sdocSuppressCoercions :: Bool
sdocSuppressCoercions = Bool
False
, sdocSuppressUnfoldings :: Bool
sdocSuppressUnfoldings = Bool
False
, sdocSuppressVarKinds :: Bool
sdocSuppressVarKinds = Bool
False
, sdocSuppressUniques :: Bool
sdocSuppressUniques = Bool
False
, sdocSuppressModulePrefixes :: Bool
sdocSuppressModulePrefixes = Bool
False
, sdocSuppressStgExts :: Bool
sdocSuppressStgExts = Bool
False
, sdocErrorSpans :: Bool
sdocErrorSpans = Bool
False
, sdocStarIsType :: Bool
sdocStarIsType = Bool
False
, sdocImpredicativeTypes :: Bool
sdocImpredicativeTypes = Bool
False
, sdocLinearTypes :: Bool
sdocLinearTypes = Bool
False
, sdocPrintTypeAbbreviations :: Bool
sdocPrintTypeAbbreviations = Bool
True
, sdocUnitIdForUser :: FastString -> SDoc
sdocUnitIdForUser = FastString -> SDoc
ftext
}
withPprStyle :: PprStyle -> SDoc -> SDoc
{-# INLINE CONLIKE withPprStyle #-}
withPprStyle :: PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
sty SDoc
d = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctxt -> SDoc -> SDocContext -> Doc
runSDoc SDoc
d SDocContext
ctxt{sdocStyle :: PprStyle
sdocStyle=PprStyle
sty}
pprDeeper :: SDoc -> SDoc
pprDeeper :: SDoc -> SDoc
pprDeeper SDoc
d = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx -> case SDocContext -> PprStyle
sdocStyle SDocContext
ctx of
PprUser PrintUnqualified
q Depth
depth Coloured
c ->
let deeper :: Int -> Doc
deeper Int
0 = String -> Doc
Pretty.text String
"..."
deeper Int
n = SDoc -> SDocContext -> Doc
runSDoc SDoc
d SDocContext
ctx{sdocStyle :: PprStyle
sdocStyle = PrintUnqualified -> Depth -> Coloured -> PprStyle
PprUser PrintUnqualified
q (Int -> Depth
PartWay (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)) Coloured
c}
in case Depth
depth of
Depth
DefaultDepth -> Int -> Doc
deeper (SDocContext -> Int
sdocDefaultDepth SDocContext
ctx)
PartWay Int
n -> Int -> Doc
deeper Int
n
Depth
AllTheWay -> SDoc -> SDocContext -> Doc
runSDoc SDoc
d SDocContext
ctx
PprStyle
_ -> SDoc -> SDocContext -> Doc
runSDoc SDoc
d SDocContext
ctx
pprDeeperList :: ([SDoc] -> SDoc) -> [SDoc] -> SDoc
pprDeeperList :: ([SDoc] -> SDoc) -> [SDoc] -> SDoc
pprDeeperList [SDoc] -> SDoc
f [SDoc]
ds
| [SDoc] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [SDoc]
ds = [SDoc] -> SDoc
f []
| Bool
otherwise = (SDocContext -> Doc) -> SDoc
SDoc SDocContext -> Doc
work
where
work :: SDocContext -> Doc
work ctx :: SDocContext
ctx@SDC{sdocStyle :: SDocContext -> PprStyle
sdocStyle=PprUser PrintUnqualified
q Depth
depth Coloured
c}
| Depth
DefaultDepth <- Depth
depth
= SDocContext -> Doc
work (SDocContext
ctx { sdocStyle :: PprStyle
sdocStyle = PrintUnqualified -> Depth -> Coloured -> PprStyle
PprUser PrintUnqualified
q (Int -> Depth
PartWay (SDocContext -> Int
sdocDefaultDepth SDocContext
ctx)) Coloured
c })
| PartWay Int
0 <- Depth
depth
= String -> Doc
Pretty.text String
"..."
| PartWay Int
n <- Depth
depth
= let
go :: Int -> [SDoc] -> [SDoc]
go Int
_ [] = []
go Int
i (SDoc
d:[SDoc]
ds) | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
n = [String -> SDoc
text String
"...."]
| Bool
otherwise = SDoc
d SDoc -> [SDoc] -> [SDoc]
forall a. a -> [a] -> [a]
: Int -> [SDoc] -> [SDoc]
go (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) [SDoc]
ds
in SDoc -> SDocContext -> Doc
runSDoc ([SDoc] -> SDoc
f (Int -> [SDoc] -> [SDoc]
go Int
0 [SDoc]
ds)) SDocContext
ctx{sdocStyle :: PprStyle
sdocStyle = PrintUnqualified -> Depth -> Coloured -> PprStyle
PprUser PrintUnqualified
q (Int -> Depth
PartWay (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)) Coloured
c}
work SDocContext
other_ctx = SDoc -> SDocContext -> Doc
runSDoc ([SDoc] -> SDoc
f [SDoc]
ds) SDocContext
other_ctx
pprSetDepth :: Depth -> SDoc -> SDoc
pprSetDepth :: Depth -> SDoc -> SDoc
pprSetDepth Depth
depth SDoc
doc = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx ->
case SDocContext
ctx of
SDC{sdocStyle :: SDocContext -> PprStyle
sdocStyle=PprUser PrintUnqualified
q Depth
_ Coloured
c} ->
SDoc -> SDocContext -> Doc
runSDoc SDoc
doc SDocContext
ctx{sdocStyle :: PprStyle
sdocStyle = PrintUnqualified -> Depth -> Coloured -> PprStyle
PprUser PrintUnqualified
q Depth
depth Coloured
c}
SDocContext
_ ->
SDoc -> SDocContext -> Doc
runSDoc SDoc
doc SDocContext
ctx
getPprStyle :: (PprStyle -> SDoc) -> SDoc
{-# INLINE CONLIKE getPprStyle #-}
getPprStyle :: (PprStyle -> SDoc) -> SDoc
getPprStyle PprStyle -> SDoc
df = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx -> SDoc -> SDocContext -> Doc
runSDoc (PprStyle -> SDoc
df (SDocContext -> PprStyle
sdocStyle SDocContext
ctx)) SDocContext
ctx
sdocWithContext :: (SDocContext -> SDoc) -> SDoc
{-# INLINE CONLIKE sdocWithContext #-}
sdocWithContext :: (SDocContext -> SDoc) -> SDoc
sdocWithContext SDocContext -> SDoc
f = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx -> SDoc -> SDocContext -> Doc
runSDoc (SDocContext -> SDoc
f SDocContext
ctx) SDocContext
ctx
sdocOption :: (SDocContext -> a) -> (a -> SDoc) -> SDoc
{-# INLINE CONLIKE sdocOption #-}
sdocOption :: forall a. (SDocContext -> a) -> (a -> SDoc) -> SDoc
sdocOption SDocContext -> a
f a -> SDoc
g = (SDocContext -> SDoc) -> SDoc
sdocWithContext (a -> SDoc
g (a -> SDoc) -> (SDocContext -> a) -> SDocContext -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SDocContext -> a
f)
updSDocContext :: (SDocContext -> SDocContext) -> SDoc -> SDoc
{-# INLINE CONLIKE updSDocContext #-}
updSDocContext :: (SDocContext -> SDocContext) -> SDoc -> SDoc
updSDocContext SDocContext -> SDocContext
upd SDoc
doc
= (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx -> SDoc -> SDocContext -> Doc
runSDoc SDoc
doc (SDocContext -> SDocContext
upd SDocContext
ctx)
qualName :: PprStyle -> QueryQualifyName
qualName :: PprStyle -> QueryQualifyName
qualName (PprUser PrintUnqualified
q Depth
_ Coloured
_) Module
mod OccName
occ = PrintUnqualified -> QueryQualifyName
queryQualifyName PrintUnqualified
q Module
mod OccName
occ
qualName (PprDump PrintUnqualified
q) Module
mod OccName
occ = PrintUnqualified -> QueryQualifyName
queryQualifyName PrintUnqualified
q Module
mod OccName
occ
qualName PprStyle
_other Module
mod OccName
_ = ModuleName -> QualifyName
NameQual (Module -> ModuleName
forall a. GenModule a -> ModuleName
moduleName Module
mod)
qualModule :: PprStyle -> QueryQualifyModule
qualModule :: PprStyle -> QueryQualifyModule
qualModule (PprUser PrintUnqualified
q Depth
_ Coloured
_) Module
m = PrintUnqualified -> QueryQualifyModule
queryQualifyModule PrintUnqualified
q Module
m
qualModule (PprDump PrintUnqualified
q) Module
m = PrintUnqualified -> QueryQualifyModule
queryQualifyModule PrintUnqualified
q Module
m
qualModule PprStyle
_other Module
_m = Bool
True
qualPackage :: PprStyle -> QueryQualifyPackage
qualPackage :: PprStyle -> QueryQualifyPackage
qualPackage (PprUser PrintUnqualified
q Depth
_ Coloured
_) Unit
m = PrintUnqualified -> QueryQualifyPackage
queryQualifyPackage PrintUnqualified
q Unit
m
qualPackage (PprDump PrintUnqualified
q) Unit
m = PrintUnqualified -> QueryQualifyPackage
queryQualifyPackage PrintUnqualified
q Unit
m
qualPackage PprStyle
_other Unit
_m = Bool
True
queryQual :: PprStyle -> PrintUnqualified
queryQual :: PprStyle -> PrintUnqualified
queryQual PprStyle
s = QueryQualifyName
-> QueryQualifyModule -> QueryQualifyPackage -> PrintUnqualified
QueryQualify (PprStyle -> QueryQualifyName
qualName PprStyle
s)
(PprStyle -> QueryQualifyModule
qualModule PprStyle
s)
(PprStyle -> QueryQualifyPackage
qualPackage PprStyle
s)
codeStyle :: PprStyle -> Bool
codeStyle :: PprStyle -> Bool
codeStyle (PprCode LabelStyle
_) = Bool
True
codeStyle PprStyle
_ = Bool
False
asmStyle :: PprStyle -> Bool
asmStyle :: PprStyle -> Bool
asmStyle (PprCode LabelStyle
AsmStyle) = Bool
True
asmStyle PprStyle
_other = Bool
False
dumpStyle :: PprStyle -> Bool
dumpStyle :: PprStyle -> Bool
dumpStyle (PprDump {}) = Bool
True
dumpStyle PprStyle
_other = Bool
False
userStyle :: PprStyle -> Bool
userStyle :: PprStyle -> Bool
userStyle (PprUser {}) = Bool
True
userStyle PprStyle
_other = Bool
False
getPprDebug :: (Bool -> SDoc) -> SDoc
{-# INLINE CONLIKE getPprDebug #-}
getPprDebug :: (Bool -> SDoc) -> SDoc
getPprDebug Bool -> SDoc
d = (SDocContext -> SDoc) -> SDoc
sdocWithContext ((SDocContext -> SDoc) -> SDoc) -> (SDocContext -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx -> Bool -> SDoc
d (SDocContext -> Bool
sdocPprDebug SDocContext
ctx)
ifPprDebug :: SDoc -> SDoc -> SDoc
{-# INLINE CONLIKE ifPprDebug #-}
ifPprDebug :: SDoc -> SDoc -> SDoc
ifPprDebug SDoc
yes SDoc
no = (Bool -> SDoc) -> SDoc
getPprDebug ((Bool -> SDoc) -> SDoc) -> (Bool -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \Bool
dbg -> if Bool
dbg then SDoc
yes else SDoc
no
whenPprDebug :: SDoc -> SDoc
{-# INLINE CONLIKE whenPprDebug #-}
whenPprDebug :: SDoc -> SDoc
whenPprDebug SDoc
d = SDoc -> SDoc -> SDoc
ifPprDebug SDoc
d SDoc
empty
printSDoc :: SDocContext -> Mode -> Handle -> SDoc -> IO ()
printSDoc :: SDocContext -> Mode -> Handle -> SDoc -> IO ()
printSDoc SDocContext
ctx Mode
mode Handle
handle SDoc
doc =
Mode -> Int -> Handle -> Doc -> IO ()
Pretty.printDoc_ Mode
mode Int
cols Handle
handle (SDoc -> SDocContext -> Doc
runSDoc SDoc
doc SDocContext
ctx)
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
`finally`
Mode -> Int -> Handle -> Doc -> IO ()
Pretty.printDoc_ Mode
mode Int
cols Handle
handle
(SDoc -> SDocContext -> Doc
runSDoc (PprColour -> SDoc -> SDoc
coloured PprColour
Col.colReset SDoc
empty) SDocContext
ctx)
where
cols :: Int
cols = SDocContext -> Int
sdocLineLength SDocContext
ctx
printSDocLn :: SDocContext -> Mode -> Handle -> SDoc -> IO ()
printSDocLn :: SDocContext -> Mode -> Handle -> SDoc -> IO ()
printSDocLn SDocContext
ctx Mode
mode Handle
handle SDoc
doc =
SDocContext -> Mode -> Handle -> SDoc -> IO ()
printSDoc SDocContext
ctx Mode
mode Handle
handle (SDoc
doc SDoc -> SDoc -> SDoc
$$ String -> SDoc
text String
"")
bufLeftRenderSDoc :: SDocContext -> BufHandle -> SDoc -> IO ()
bufLeftRenderSDoc :: SDocContext -> BufHandle -> SDoc -> IO ()
bufLeftRenderSDoc SDocContext
ctx BufHandle
bufHandle SDoc
doc =
BufHandle -> Doc -> IO ()
Pretty.bufLeftRender BufHandle
bufHandle (SDoc -> SDocContext -> Doc
runSDoc SDoc
doc SDocContext
ctx)
pprCode :: LabelStyle -> SDoc -> SDoc
{-# INLINE CONLIKE pprCode #-}
pprCode :: LabelStyle -> SDoc -> SDoc
pprCode LabelStyle
cs SDoc
d = PprStyle -> SDoc -> SDoc
withPprStyle (LabelStyle -> PprStyle
PprCode LabelStyle
cs) SDoc
d
renderWithContext :: SDocContext -> SDoc -> String
renderWithContext :: SDocContext -> SDoc -> String
renderWithContext SDocContext
ctx SDoc
sdoc
= let s :: Style
s = Style
Pretty.style{ mode :: Mode
Pretty.mode = Bool -> Mode
PageMode Bool
False,
lineLength :: Int
Pretty.lineLength = SDocContext -> Int
sdocLineLength SDocContext
ctx }
in Style -> Doc -> String
Pretty.renderStyle Style
s (Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$ SDoc -> SDocContext -> Doc
runSDoc SDoc
sdoc SDocContext
ctx
showSDocOneLine :: SDocContext -> SDoc -> String
showSDocOneLine :: SDocContext -> SDoc -> String
showSDocOneLine SDocContext
ctx SDoc
d
= let s :: Style
s = Style
Pretty.style{ mode :: Mode
Pretty.mode = Mode
OneLineMode,
lineLength :: Int
Pretty.lineLength = SDocContext -> Int
sdocLineLength SDocContext
ctx } in
Style -> Doc -> String
Pretty.renderStyle Style
s (Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$
SDoc -> SDocContext -> Doc
runSDoc SDoc
d SDocContext
ctx
showSDocUnsafe :: SDoc -> String
showSDocUnsafe :: SDoc -> String
showSDocUnsafe SDoc
sdoc = SDocContext -> SDoc -> String
renderWithContext SDocContext
defaultSDocContext SDoc
sdoc
showPprUnsafe :: Outputable a => a -> String
showPprUnsafe :: forall a. Outputable a => a -> String
showPprUnsafe a
a = SDocContext -> SDoc -> String
renderWithContext SDocContext
defaultSDocContext (a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
a)
pprDebugAndThen :: SDocContext -> (String -> a) -> SDoc -> SDoc -> a
pprDebugAndThen :: forall a. SDocContext -> (String -> a) -> SDoc -> SDoc -> a
pprDebugAndThen SDocContext
ctx String -> a
cont SDoc
heading SDoc
pretty_msg
= String -> a
cont (SDocContext -> SDoc -> String
renderWithContext SDocContext
ctx SDoc
doc)
where
doc :: SDoc
doc = PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultDumpStyle ([SDoc] -> SDoc
sep [SDoc
heading, Int -> SDoc -> SDoc
nest Int
2 SDoc
pretty_msg])
isEmpty :: SDocContext -> SDoc -> Bool
isEmpty :: SDocContext -> SDoc -> Bool
isEmpty SDocContext
ctx SDoc
sdoc = Doc -> Bool
Pretty.isEmpty (Doc -> Bool) -> Doc -> Bool
forall a b. (a -> b) -> a -> b
$ SDoc -> SDocContext -> Doc
runSDoc SDoc
sdoc (SDocContext
ctx {sdocPprDebug :: Bool
sdocPprDebug = Bool
True})
docToSDoc :: Doc -> SDoc
docToSDoc :: Doc -> SDoc
docToSDoc Doc
d = (SDocContext -> Doc) -> SDoc
SDoc (\SDocContext
_ -> Doc
d)
empty :: SDoc
char :: Char -> SDoc
text :: String -> SDoc
ftext :: FastString -> SDoc
ptext :: PtrString -> SDoc
ztext :: FastZString -> SDoc
int :: Int -> SDoc
integer :: Integer -> SDoc
word :: Integer -> SDoc
float :: Float -> SDoc
double :: Double -> SDoc
rational :: Rational -> SDoc
{-# INLINE CONLIKE empty #-}
empty :: SDoc
empty = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Doc
Pretty.empty
{-# INLINE CONLIKE char #-}
char :: Char -> SDoc
char Char
c = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Char -> Doc
Pretty.char Char
c
{-# INLINE CONLIKE text #-}
text :: String -> SDoc
text String
s = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> Doc
Pretty.text String
s
{-# INLINE CONLIKE ftext #-}
ftext :: FastString -> SDoc
ftext FastString
s = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ FastString -> Doc
Pretty.ftext FastString
s
{-# INLINE CONLIKE ptext #-}
ptext :: PtrString -> SDoc
ptext PtrString
s = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ PtrString -> Doc
Pretty.ptext PtrString
s
{-# INLINE CONLIKE ztext #-}
ztext :: FastZString -> SDoc
ztext FastZString
s = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ FastZString -> Doc
Pretty.ztext FastZString
s
{-# INLINE CONLIKE int #-}
int :: Int -> SDoc
int Int
n = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Int -> Doc
Pretty.int Int
n
{-# INLINE CONLIKE integer #-}
integer :: Integer -> SDoc
integer Integer
n = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Integer -> Doc
Pretty.integer Integer
n
{-# INLINE CONLIKE float #-}
float :: Float -> SDoc
float Float
n = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Float -> Doc
Pretty.float Float
n
{-# INLINE CONLIKE double #-}
double :: Double -> SDoc
double Double
n = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Double -> Doc
Pretty.double Double
n
{-# INLINE CONLIKE rational #-}
rational :: Rational -> SDoc
rational Rational
n = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Rational -> Doc
Pretty.rational Rational
n
{-# INLINE CONLIKE word #-}
word :: Integer -> SDoc
word Integer
n = (SDocContext -> Bool) -> (Bool -> SDoc) -> SDoc
forall a. (SDocContext -> a) -> (a -> SDoc) -> SDoc
sdocOption SDocContext -> Bool
sdocHexWordLiterals ((Bool -> SDoc) -> SDoc) -> (Bool -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \case
Bool
True -> Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Integer -> Doc
Pretty.hex Integer
n
Bool
False -> Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Integer -> Doc
Pretty.integer Integer
n
doublePrec :: Int -> Double -> SDoc
doublePrec :: Int -> Double -> SDoc
doublePrec Int
p Double
n = String -> SDoc
text (Maybe Int -> Double -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
p) Double
n String
"")
parens, braces, brackets, quotes, quote,
doubleQuotes, angleBrackets :: SDoc -> SDoc
{-# INLINE CONLIKE parens #-}
parens :: SDoc -> SDoc
parens SDoc
d = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ Doc -> Doc
Pretty.parens (Doc -> Doc) -> (SDocContext -> Doc) -> SDocContext -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SDoc -> SDocContext -> Doc
runSDoc SDoc
d
{-# INLINE CONLIKE braces #-}
braces :: SDoc -> SDoc
braces SDoc
d = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ Doc -> Doc
Pretty.braces (Doc -> Doc) -> (SDocContext -> Doc) -> SDocContext -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SDoc -> SDocContext -> Doc
runSDoc SDoc
d
{-# INLINE CONLIKE brackets #-}
brackets :: SDoc -> SDoc
brackets SDoc
d = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ Doc -> Doc
Pretty.brackets (Doc -> Doc) -> (SDocContext -> Doc) -> SDocContext -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SDoc -> SDocContext -> Doc
runSDoc SDoc
d
{-# INLINE CONLIKE quote #-}
quote :: SDoc -> SDoc
quote SDoc
d = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ Doc -> Doc
Pretty.quote (Doc -> Doc) -> (SDocContext -> Doc) -> SDocContext -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SDoc -> SDocContext -> Doc
runSDoc SDoc
d
{-# INLINE CONLIKE doubleQuotes #-}
doubleQuotes :: SDoc -> SDoc
doubleQuotes SDoc
d = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ Doc -> Doc
Pretty.doubleQuotes (Doc -> Doc) -> (SDocContext -> Doc) -> SDocContext -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SDoc -> SDocContext -> Doc
runSDoc SDoc
d
{-# INLINE CONLIKE angleBrackets #-}
angleBrackets :: SDoc -> SDoc
angleBrackets SDoc
d = Char -> SDoc
char Char
'<' SDoc -> SDoc -> SDoc
<> SDoc
d SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'>'
cparen :: Bool -> SDoc -> SDoc
{-# INLINE CONLIKE cparen #-}
cparen :: Bool -> SDoc -> SDoc
cparen Bool
b SDoc
d = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ Bool -> Doc -> Doc
Pretty.maybeParens Bool
b (Doc -> Doc) -> (SDocContext -> Doc) -> SDocContext -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SDoc -> SDocContext -> Doc
runSDoc SDoc
d
quotes :: SDoc -> SDoc
quotes SDoc
d = (SDocContext -> Bool) -> (Bool -> SDoc) -> SDoc
forall a. (SDocContext -> a) -> (a -> SDoc) -> SDoc
sdocOption SDocContext -> Bool
sdocCanUseUnicode ((Bool -> SDoc) -> SDoc) -> (Bool -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \case
Bool
True -> Char -> SDoc
char Char
'‘' SDoc -> SDoc -> SDoc
<> SDoc
d SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'’'
Bool
False -> (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
sty ->
let pp_d :: Doc
pp_d = SDoc -> SDocContext -> Doc
runSDoc SDoc
d SDocContext
sty
str :: String
str = Doc -> String
forall a. Show a => a -> String
show Doc
pp_d
in case String
str of
[] -> Doc -> Doc
Pretty.quotes Doc
pp_d
Char
'\'' : String
_ -> Doc
pp_d
String
_ | Char
'\'' <- String -> Char
forall a. HasCallStack => [a] -> a
last String
str -> Doc
pp_d
| Bool
otherwise -> Doc -> Doc
Pretty.quotes Doc
pp_d
semi, comma, colon, equals, space, dcolon, underscore, dot, vbar :: SDoc
arrow, lollipop, larrow, darrow, arrowt, larrowt, arrowtt, larrowtt, lambda :: SDoc
lparen, rparen, lbrack, rbrack, lbrace, rbrace, blankLine :: SDoc
blankLine :: SDoc
blankLine = Doc -> SDoc
docToSDoc Doc
Pretty.emptyText
dcolon :: SDoc
dcolon = SDoc -> SDoc -> SDoc
unicodeSyntax (Char -> SDoc
char Char
'∷') (Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> Doc
Pretty.text String
"::")
arrow :: SDoc
arrow = SDoc -> SDoc -> SDoc
unicodeSyntax (Char -> SDoc
char Char
'→') (Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> Doc
Pretty.text String
"->")
lollipop :: SDoc
lollipop = SDoc -> SDoc -> SDoc
unicodeSyntax (Char -> SDoc
char Char
'⊸') (Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> Doc
Pretty.text String
"%1 ->")
larrow :: SDoc
larrow = SDoc -> SDoc -> SDoc
unicodeSyntax (Char -> SDoc
char Char
'←') (Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> Doc
Pretty.text String
"<-")
darrow :: SDoc
darrow = SDoc -> SDoc -> SDoc
unicodeSyntax (Char -> SDoc
char Char
'⇒') (Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> Doc
Pretty.text String
"=>")
arrowt :: SDoc
arrowt = SDoc -> SDoc -> SDoc
unicodeSyntax (Char -> SDoc
char Char
'⤚') (Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> Doc
Pretty.text String
">-")
larrowt :: SDoc
larrowt = SDoc -> SDoc -> SDoc
unicodeSyntax (Char -> SDoc
char Char
'⤙') (Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> Doc
Pretty.text String
"-<")
arrowtt :: SDoc
arrowtt = SDoc -> SDoc -> SDoc
unicodeSyntax (Char -> SDoc
char Char
'⤜') (Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> Doc
Pretty.text String
">>-")
larrowtt :: SDoc
larrowtt = SDoc -> SDoc -> SDoc
unicodeSyntax (Char -> SDoc
char Char
'⤛') (Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> Doc
Pretty.text String
"-<<")
lambda :: SDoc
lambda = SDoc -> SDoc -> SDoc
unicodeSyntax (Char -> SDoc
char Char
'λ') (Char -> SDoc
char Char
'\\')
semi :: SDoc
semi = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Doc
Pretty.semi
comma :: SDoc
comma = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Doc
Pretty.comma
colon :: SDoc
colon = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Doc
Pretty.colon
equals :: SDoc
equals = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Doc
Pretty.equals
space :: SDoc
space = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Doc
Pretty.space
underscore :: SDoc
underscore = Char -> SDoc
char Char
'_'
dot :: SDoc
dot = Char -> SDoc
char Char
'.'
vbar :: SDoc
vbar = Char -> SDoc
char Char
'|'
lparen :: SDoc
lparen = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Doc
Pretty.lparen
rparen :: SDoc
rparen = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Doc
Pretty.rparen
lbrack :: SDoc
lbrack = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Doc
Pretty.lbrack
rbrack :: SDoc
rbrack = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Doc
Pretty.rbrack
lbrace :: SDoc
lbrace = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Doc
Pretty.lbrace
rbrace :: SDoc
rbrace = Doc -> SDoc
docToSDoc (Doc -> SDoc) -> Doc -> SDoc
forall a b. (a -> b) -> a -> b
$ Doc
Pretty.rbrace
mulArrow :: SDoc -> SDoc
mulArrow :: SDoc -> SDoc
mulArrow SDoc
d = String -> SDoc
text String
"%" SDoc -> SDoc -> SDoc
<> SDoc
d SDoc -> SDoc -> SDoc
<+> SDoc
arrow
forAllLit :: SDoc
forAllLit :: SDoc
forAllLit = SDoc -> SDoc -> SDoc
unicodeSyntax (Char -> SDoc
char Char
'∀') (String -> SDoc
text String
"forall")
bullet :: SDoc
bullet :: SDoc
bullet = SDoc -> SDoc -> SDoc
unicode (Char -> SDoc
char Char
'•') (Char -> SDoc
char Char
'*')
unicodeSyntax :: SDoc -> SDoc -> SDoc
unicodeSyntax :: SDoc -> SDoc -> SDoc
unicodeSyntax SDoc
unicode SDoc
plain =
(SDocContext -> Bool) -> (Bool -> SDoc) -> SDoc
forall a. (SDocContext -> a) -> (a -> SDoc) -> SDoc
sdocOption SDocContext -> Bool
sdocCanUseUnicode ((Bool -> SDoc) -> SDoc) -> (Bool -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \Bool
can_use_unicode ->
(SDocContext -> Bool) -> (Bool -> SDoc) -> SDoc
forall a. (SDocContext -> a) -> (a -> SDoc) -> SDoc
sdocOption SDocContext -> Bool
sdocPrintUnicodeSyntax ((Bool -> SDoc) -> SDoc) -> (Bool -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \Bool
print_unicode_syntax ->
if Bool
can_use_unicode Bool -> Bool -> Bool
&& Bool
print_unicode_syntax
then SDoc
unicode
else SDoc
plain
unicode :: SDoc -> SDoc -> SDoc
unicode :: SDoc -> SDoc -> SDoc
unicode SDoc
unicode SDoc
plain = (SDocContext -> Bool) -> (Bool -> SDoc) -> SDoc
forall a. (SDocContext -> a) -> (a -> SDoc) -> SDoc
sdocOption SDocContext -> Bool
sdocCanUseUnicode ((Bool -> SDoc) -> SDoc) -> (Bool -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \case
Bool
True -> SDoc
unicode
Bool
False -> SDoc
plain
nest :: Int -> SDoc -> SDoc
(<>) :: SDoc -> SDoc -> SDoc
(<+>) :: SDoc -> SDoc -> SDoc
($$) :: SDoc -> SDoc -> SDoc
($+$) :: SDoc -> SDoc -> SDoc
{-# INLINE CONLIKE nest #-}
nest :: Int -> SDoc -> SDoc
nest Int
n SDoc
d = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ Int -> Doc -> Doc
Pretty.nest Int
n (Doc -> Doc) -> (SDocContext -> Doc) -> SDocContext -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SDoc -> SDocContext -> Doc
runSDoc SDoc
d
{-# INLINE CONLIKE (<>) #-}
<> :: SDoc -> SDoc -> SDoc
(<>) SDoc
d1 SDoc
d2 = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx -> Doc -> Doc -> Doc
(Pretty.<>) (SDoc -> SDocContext -> Doc
runSDoc SDoc
d1 SDocContext
ctx) (SDoc -> SDocContext -> Doc
runSDoc SDoc
d2 SDocContext
ctx)
{-# INLINE CONLIKE (<+>) #-}
<+> :: SDoc -> SDoc -> SDoc
(<+>) SDoc
d1 SDoc
d2 = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx -> Doc -> Doc -> Doc
(Pretty.<+>) (SDoc -> SDocContext -> Doc
runSDoc SDoc
d1 SDocContext
ctx) (SDoc -> SDocContext -> Doc
runSDoc SDoc
d2 SDocContext
ctx)
{-# INLINE CONLIKE ($$) #-}
$$ :: SDoc -> SDoc -> SDoc
($$) SDoc
d1 SDoc
d2 = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx -> Doc -> Doc -> Doc
(Pretty.$$) (SDoc -> SDocContext -> Doc
runSDoc SDoc
d1 SDocContext
ctx) (SDoc -> SDocContext -> Doc
runSDoc SDoc
d2 SDocContext
ctx)
{-# INLINE CONLIKE ($+$) #-}
$+$ :: SDoc -> SDoc -> SDoc
($+$) SDoc
d1 SDoc
d2 = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx -> Doc -> Doc -> Doc
(Pretty.$+$) (SDoc -> SDocContext -> Doc
runSDoc SDoc
d1 SDocContext
ctx) (SDoc -> SDocContext -> Doc
runSDoc SDoc
d2 SDocContext
ctx)
hcat :: [SDoc] -> SDoc
hsep :: [SDoc] -> SDoc
vcat :: [SDoc] -> SDoc
sep :: [SDoc] -> SDoc
cat :: [SDoc] -> SDoc
fsep :: [SDoc] -> SDoc
fcat :: [SDoc] -> SDoc
{-# INLINE CONLIKE hcat #-}
hcat :: [SDoc] -> SDoc
hcat [SDoc]
ds = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx -> [Doc] -> Doc
Pretty.hcat [SDoc -> SDocContext -> Doc
runSDoc SDoc
d SDocContext
ctx | SDoc
d <- [SDoc]
ds]
{-# INLINE CONLIKE hsep #-}
hsep :: [SDoc] -> SDoc
hsep [SDoc]
ds = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx -> [Doc] -> Doc
Pretty.hsep [SDoc -> SDocContext -> Doc
runSDoc SDoc
d SDocContext
ctx | SDoc
d <- [SDoc]
ds]
{-# INLINE CONLIKE vcat #-}
vcat :: [SDoc] -> SDoc
vcat [SDoc]
ds = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx -> [Doc] -> Doc
Pretty.vcat [SDoc -> SDocContext -> Doc
runSDoc SDoc
d SDocContext
ctx | SDoc
d <- [SDoc]
ds]
{-# INLINE CONLIKE sep #-}
sep :: [SDoc] -> SDoc
sep [SDoc]
ds = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx -> [Doc] -> Doc
Pretty.sep [SDoc -> SDocContext -> Doc
runSDoc SDoc
d SDocContext
ctx | SDoc
d <- [SDoc]
ds]
{-# INLINE CONLIKE cat #-}
cat :: [SDoc] -> SDoc
cat [SDoc]
ds = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx -> [Doc] -> Doc
Pretty.cat [SDoc -> SDocContext -> Doc
runSDoc SDoc
d SDocContext
ctx | SDoc
d <- [SDoc]
ds]
{-# INLINE CONLIKE fsep #-}
fsep :: [SDoc] -> SDoc
fsep [SDoc]
ds = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx -> [Doc] -> Doc
Pretty.fsep [SDoc -> SDocContext -> Doc
runSDoc SDoc
d SDocContext
ctx | SDoc
d <- [SDoc]
ds]
{-# INLINE CONLIKE fcat #-}
fcat :: [SDoc] -> SDoc
fcat [SDoc]
ds = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx -> [Doc] -> Doc
Pretty.fcat [SDoc -> SDocContext -> Doc
runSDoc SDoc
d SDocContext
ctx | SDoc
d <- [SDoc]
ds]
hang :: SDoc
-> Int
-> SDoc
-> SDoc
{-# INLINE CONLIKE hang #-}
hang :: SDoc -> Int -> SDoc -> SDoc
hang SDoc
d1 Int
n SDoc
d2 = (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
sty -> Doc -> Int -> Doc -> Doc
Pretty.hang (SDoc -> SDocContext -> Doc
runSDoc SDoc
d1 SDocContext
sty) Int
n (SDoc -> SDocContext -> Doc
runSDoc SDoc
d2 SDocContext
sty)
hangNotEmpty :: SDoc -> Int -> SDoc -> SDoc
{-# INLINE CONLIKE hangNotEmpty #-}
hangNotEmpty :: SDoc -> Int -> SDoc -> SDoc
hangNotEmpty SDoc
d1 Int
n SDoc
d2 =
(SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx -> Doc -> Int -> Doc -> Doc
Pretty.hangNotEmpty (SDoc -> SDocContext -> Doc
runSDoc SDoc
d1 SDocContext
ctx) Int
n (SDoc -> SDocContext -> Doc
runSDoc SDoc
d2 SDocContext
ctx)
punctuate :: SDoc
-> [SDoc]
-> [SDoc]
punctuate :: SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
_ [] = []
punctuate SDoc
p (SDoc
d:[SDoc]
ds) = SDoc -> [SDoc] -> [SDoc]
go SDoc
d [SDoc]
ds
where
go :: SDoc -> [SDoc] -> [SDoc]
go SDoc
d [] = [SDoc
d]
go SDoc
d (SDoc
e:[SDoc]
es) = (SDoc
d SDoc -> SDoc -> SDoc
<> SDoc
p) SDoc -> [SDoc] -> [SDoc]
forall a. a -> [a] -> [a]
: SDoc -> [SDoc] -> [SDoc]
go SDoc
e [SDoc]
es
ppWhen, ppUnless :: Bool -> SDoc -> SDoc
{-# INLINE CONLIKE ppWhen #-}
ppWhen :: Bool -> SDoc -> SDoc
ppWhen Bool
True SDoc
doc = SDoc
doc
ppWhen Bool
False SDoc
_ = SDoc
empty
{-# INLINE CONLIKE ppUnless #-}
ppUnless :: Bool -> SDoc -> SDoc
ppUnless Bool
True SDoc
_ = SDoc
empty
ppUnless Bool
False SDoc
doc = SDoc
doc
{-# INLINE CONLIKE ppWhenOption #-}
ppWhenOption :: (SDocContext -> Bool) -> SDoc -> SDoc
ppWhenOption :: (SDocContext -> Bool) -> SDoc -> SDoc
ppWhenOption SDocContext -> Bool
f SDoc
doc = (SDocContext -> Bool) -> (Bool -> SDoc) -> SDoc
forall a. (SDocContext -> a) -> (a -> SDoc) -> SDoc
sdocOption SDocContext -> Bool
f ((Bool -> SDoc) -> SDoc) -> (Bool -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \case
Bool
True -> SDoc
doc
Bool
False -> SDoc
empty
{-# INLINE CONLIKE ppUnlessOption #-}
ppUnlessOption :: (SDocContext -> Bool) -> SDoc -> SDoc
ppUnlessOption :: (SDocContext -> Bool) -> SDoc -> SDoc
ppUnlessOption SDocContext -> Bool
f SDoc
doc = (SDocContext -> Bool) -> (Bool -> SDoc) -> SDoc
forall a. (SDocContext -> a) -> (a -> SDoc) -> SDoc
sdocOption SDocContext -> Bool
f ((Bool -> SDoc) -> SDoc) -> (Bool -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \case
Bool
True -> SDoc
empty
Bool
False -> SDoc
doc
coloured :: Col.PprColour -> SDoc -> SDoc
coloured :: PprColour -> SDoc -> SDoc
coloured PprColour
col SDoc
sdoc = (SDocContext -> Bool) -> (Bool -> SDoc) -> SDoc
forall a. (SDocContext -> a) -> (a -> SDoc) -> SDoc
sdocOption SDocContext -> Bool
sdocShouldUseColor ((Bool -> SDoc) -> SDoc) -> (Bool -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \case
Bool
True -> (SDocContext -> Doc) -> SDoc
SDoc ((SDocContext -> Doc) -> SDoc) -> (SDocContext -> Doc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \case
ctx :: SDocContext
ctx@SDC{ sdocLastColour :: SDocContext -> PprColour
sdocLastColour = PprColour
lastCol, sdocStyle :: SDocContext -> PprStyle
sdocStyle = PprUser PrintUnqualified
_ Depth
_ Coloured
Coloured } ->
let ctx' :: SDocContext
ctx' = SDocContext
ctx{ sdocLastColour :: PprColour
sdocLastColour = PprColour
lastCol PprColour -> PprColour -> PprColour
forall a. Monoid a => a -> a -> a
`mappend` PprColour
col } in
String -> Doc
Pretty.zeroWidthText (PprColour -> String
Col.renderColour PprColour
col)
Doc -> Doc -> Doc
Pretty.<> SDoc -> SDocContext -> Doc
runSDoc SDoc
sdoc SDocContext
ctx'
Doc -> Doc -> Doc
Pretty.<> String -> Doc
Pretty.zeroWidthText (PprColour -> String
Col.renderColourAfresh PprColour
lastCol)
SDocContext
ctx -> SDoc -> SDocContext -> Doc
runSDoc SDoc
sdoc SDocContext
ctx
Bool
False -> SDoc
sdoc
keyword :: SDoc -> SDoc
keyword :: SDoc -> SDoc
keyword = PprColour -> SDoc -> SDoc
coloured PprColour
Col.colBold
class Outputable a where
ppr :: a -> SDoc
instance Outputable Char where
ppr :: Char -> SDoc
ppr Char
c = String -> SDoc
text [Char
c]
instance Outputable Bool where
ppr :: Bool -> SDoc
ppr Bool
True = String -> SDoc
text String
"True"
ppr Bool
False = String -> SDoc
text String
"False"
instance Outputable Ordering where
ppr :: Ordering -> SDoc
ppr Ordering
LT = String -> SDoc
text String
"LT"
ppr Ordering
EQ = String -> SDoc
text String
"EQ"
ppr Ordering
GT = String -> SDoc
text String
"GT"
instance Outputable Int32 where
ppr :: Int32 -> SDoc
ppr Int32
n = Integer -> SDoc
integer (Integer -> SDoc) -> Integer -> SDoc
forall a b. (a -> b) -> a -> b
$ Int32 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
n
instance Outputable Int64 where
ppr :: Int64 -> SDoc
ppr Int64
n = Integer -> SDoc
integer (Integer -> SDoc) -> Integer -> SDoc
forall a b. (a -> b) -> a -> b
$ Int64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
n
instance Outputable Int where
ppr :: Int -> SDoc
ppr Int
n = Int -> SDoc
int Int
n
instance Outputable Integer where
ppr :: Integer -> SDoc
ppr Integer
n = Integer -> SDoc
integer Integer
n
instance Outputable Word16 where
ppr :: Word16 -> SDoc
ppr Word16
n = Integer -> SDoc
integer (Integer -> SDoc) -> Integer -> SDoc
forall a b. (a -> b) -> a -> b
$ Word16 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
n
instance Outputable Word32 where
ppr :: Word32 -> SDoc
ppr Word32
n = Integer -> SDoc
integer (Integer -> SDoc) -> Integer -> SDoc
forall a b. (a -> b) -> a -> b
$ Word32 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
n
instance Outputable Word64 where
ppr :: Word64 -> SDoc
ppr Word64
n = Integer -> SDoc
integer (Integer -> SDoc) -> Integer -> SDoc
forall a b. (a -> b) -> a -> b
$ Word64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
n
instance Outputable Word where
ppr :: Word -> SDoc
ppr Word
n = Integer -> SDoc
integer (Integer -> SDoc) -> Integer -> SDoc
forall a b. (a -> b) -> a -> b
$ Word -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
n
instance Outputable Float where
ppr :: Float -> SDoc
ppr Float
f = Float -> SDoc
float Float
f
instance Outputable Double where
ppr :: Double -> SDoc
ppr Double
f = Double -> SDoc
double Double
f
instance Outputable () where
ppr :: () -> SDoc
ppr ()
_ = String -> SDoc
text String
"()"
instance Outputable UTCTime where
ppr :: UTCTime -> SDoc
ppr = String -> SDoc
text (String -> SDoc) -> (UTCTime -> String) -> UTCTime -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Format UTCTime -> UTCTime -> String
forall t. Format t -> t -> String
formatShow Format UTCTime
forall t. ISO8601 t => Format t
iso8601Format
instance (Outputable a) => Outputable [a] where
ppr :: [a] -> SDoc
ppr [a]
xs = SDoc -> SDoc
brackets ([SDoc] -> SDoc
fsep (SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
comma ((a -> SDoc) -> [a] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map a -> SDoc
forall a. Outputable a => a -> SDoc
ppr [a]
xs)))
instance (Outputable a) => Outputable (NonEmpty a) where
ppr :: NonEmpty a -> SDoc
ppr = [a] -> SDoc
forall a. Outputable a => a -> SDoc
ppr ([a] -> SDoc) -> (NonEmpty a -> [a]) -> NonEmpty a -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty a -> [a]
forall a. NonEmpty a -> [a]
NEL.toList
instance (Outputable a) => Outputable (Set a) where
ppr :: Set a -> SDoc
ppr Set a
s = SDoc -> SDoc
braces ([SDoc] -> SDoc
fsep (SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
comma ((a -> SDoc) -> [a] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map a -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Set a -> [a]
forall a. Set a -> [a]
Set.toList Set a
s))))
instance Outputable IntSet.IntSet where
ppr :: IntSet -> SDoc
ppr IntSet
s = SDoc -> SDoc
braces ([SDoc] -> SDoc
fsep (SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
comma ((Int -> SDoc) -> [Int] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr (IntSet -> [Int]
IntSet.toList IntSet
s))))
instance (Outputable a, Outputable b) => Outputable (a, b) where
ppr :: (a, b) -> SDoc
ppr (a
x,b
y) = SDoc -> SDoc
parens ([SDoc] -> SDoc
sep [a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
x SDoc -> SDoc -> SDoc
<> SDoc
comma, b -> SDoc
forall a. Outputable a => a -> SDoc
ppr b
y])
instance Outputable a => Outputable (Maybe a) where
ppr :: Maybe a -> SDoc
ppr Maybe a
Nothing = String -> SDoc
text String
"Nothing"
ppr (Just a
x) = String -> SDoc
text String
"Just" SDoc -> SDoc -> SDoc
<+> a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
x
instance (Outputable a, Outputable b) => Outputable (Either a b) where
ppr :: Either a b -> SDoc
ppr (Left a
x) = String -> SDoc
text String
"Left" SDoc -> SDoc -> SDoc
<+> a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
x
ppr (Right b
y) = String -> SDoc
text String
"Right" SDoc -> SDoc -> SDoc
<+> b -> SDoc
forall a. Outputable a => a -> SDoc
ppr b
y
instance (Outputable a, Outputable b, Outputable c) => Outputable (a, b, c) where
ppr :: (a, b, c) -> SDoc
ppr (a
x,b
y,c
z) =
SDoc -> SDoc
parens ([SDoc] -> SDoc
sep [a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
x SDoc -> SDoc -> SDoc
<> SDoc
comma,
b -> SDoc
forall a. Outputable a => a -> SDoc
ppr b
y SDoc -> SDoc -> SDoc
<> SDoc
comma,
c -> SDoc
forall a. Outputable a => a -> SDoc
ppr c
z ])
instance (Outputable a, Outputable b, Outputable c, Outputable d) =>
Outputable (a, b, c, d) where
ppr :: (a, b, c, d) -> SDoc
ppr (a
a,b
b,c
c,d
d) =
SDoc -> SDoc
parens ([SDoc] -> SDoc
sep [a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
a SDoc -> SDoc -> SDoc
<> SDoc
comma,
b -> SDoc
forall a. Outputable a => a -> SDoc
ppr b
b SDoc -> SDoc -> SDoc
<> SDoc
comma,
c -> SDoc
forall a. Outputable a => a -> SDoc
ppr c
c SDoc -> SDoc -> SDoc
<> SDoc
comma,
d -> SDoc
forall a. Outputable a => a -> SDoc
ppr d
d])
instance (Outputable a, Outputable b, Outputable c, Outputable d, Outputable e) =>
Outputable (a, b, c, d, e) where
ppr :: (a, b, c, d, e) -> SDoc
ppr (a
a,b
b,c
c,d
d,e
e) =
SDoc -> SDoc
parens ([SDoc] -> SDoc
sep [a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
a SDoc -> SDoc -> SDoc
<> SDoc
comma,
b -> SDoc
forall a. Outputable a => a -> SDoc
ppr b
b SDoc -> SDoc -> SDoc
<> SDoc
comma,
c -> SDoc
forall a. Outputable a => a -> SDoc
ppr c
c SDoc -> SDoc -> SDoc
<> SDoc
comma,
d -> SDoc
forall a. Outputable a => a -> SDoc
ppr d
d SDoc -> SDoc -> SDoc
<> SDoc
comma,
e -> SDoc
forall a. Outputable a => a -> SDoc
ppr e
e])
instance (Outputable a, Outputable b, Outputable c, Outputable d, Outputable e, Outputable f) =>
Outputable (a, b, c, d, e, f) where
ppr :: (a, b, c, d, e, f) -> SDoc
ppr (a
a,b
b,c
c,d
d,e
e,f
f) =
SDoc -> SDoc
parens ([SDoc] -> SDoc
sep [a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
a SDoc -> SDoc -> SDoc
<> SDoc
comma,
b -> SDoc
forall a. Outputable a => a -> SDoc
ppr b
b SDoc -> SDoc -> SDoc
<> SDoc
comma,
c -> SDoc
forall a. Outputable a => a -> SDoc
ppr c
c SDoc -> SDoc -> SDoc
<> SDoc
comma,
d -> SDoc
forall a. Outputable a => a -> SDoc
ppr d
d SDoc -> SDoc -> SDoc
<> SDoc
comma,
e -> SDoc
forall a. Outputable a => a -> SDoc
ppr e
e SDoc -> SDoc -> SDoc
<> SDoc
comma,
f -> SDoc
forall a. Outputable a => a -> SDoc
ppr f
f])
instance (Outputable a, Outputable b, Outputable c, Outputable d, Outputable e, Outputable f, Outputable g) =>
Outputable (a, b, c, d, e, f, g) where
ppr :: (a, b, c, d, e, f, g) -> SDoc
ppr (a
a,b
b,c
c,d
d,e
e,f
f,g
g) =
SDoc -> SDoc
parens ([SDoc] -> SDoc
sep [a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
a SDoc -> SDoc -> SDoc
<> SDoc
comma,
b -> SDoc
forall a. Outputable a => a -> SDoc
ppr b
b SDoc -> SDoc -> SDoc
<> SDoc
comma,
c -> SDoc
forall a. Outputable a => a -> SDoc
ppr c
c SDoc -> SDoc -> SDoc
<> SDoc
comma,
d -> SDoc
forall a. Outputable a => a -> SDoc
ppr d
d SDoc -> SDoc -> SDoc
<> SDoc
comma,
e -> SDoc
forall a. Outputable a => a -> SDoc
ppr e
e SDoc -> SDoc -> SDoc
<> SDoc
comma,
f -> SDoc
forall a. Outputable a => a -> SDoc
ppr f
f SDoc -> SDoc -> SDoc
<> SDoc
comma,
g -> SDoc
forall a. Outputable a => a -> SDoc
ppr g
g])
instance Outputable FastString where
ppr :: FastString -> SDoc
ppr FastString
fs = FastString -> SDoc
ftext FastString
fs
deriving newtype instance Outputable NonDetFastString
deriving newtype instance Outputable LexicalFastString
instance (Outputable key, Outputable elt) => Outputable (M.Map key elt) where
ppr :: Map key elt -> SDoc
ppr Map key elt
m = [(key, elt)] -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Map key elt -> [(key, elt)]
forall k a. Map k a -> [(k, a)]
M.toList Map key elt
m)
instance (Outputable elt) => Outputable (IM.IntMap elt) where
ppr :: IntMap elt -> SDoc
ppr IntMap elt
m = [(Int, elt)] -> SDoc
forall a. Outputable a => a -> SDoc
ppr (IntMap elt -> [(Int, elt)]
forall a. IntMap a -> [(Int, a)]
IM.toList IntMap elt
m)
instance Outputable Fingerprint where
ppr :: Fingerprint -> SDoc
ppr (Fingerprint Word64
w1 Word64
w2) = String -> SDoc
text (String -> Word64 -> Word64 -> String
forall r. PrintfType r => String -> r
printf String
"%016x%016x" Word64
w1 Word64
w2)
instance Outputable a => Outputable (SCC a) where
ppr :: SCC a -> SDoc
ppr (AcyclicSCC a
v) = String -> SDoc
text String
"NONREC" SDoc -> SDoc -> SDoc
$$ (Int -> SDoc -> SDoc
nest Int
3 (a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
v))
ppr (CyclicSCC [a]
vs) = String -> SDoc
text String
"REC" SDoc -> SDoc -> SDoc
$$ (Int -> SDoc -> SDoc
nest Int
3 ([SDoc] -> SDoc
vcat ((a -> SDoc) -> [a] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map a -> SDoc
forall a. Outputable a => a -> SDoc
ppr [a]
vs)))
instance Outputable Serialized where
ppr :: Serialized -> SDoc
ppr (Serialized TypeRep
the_type [Word8]
bytes) = Int -> SDoc
int ([Word8] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Word8]
bytes) SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"of type" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text (TypeRep -> String
forall a. Show a => a -> String
show TypeRep
the_type)
instance Outputable Extension where
ppr :: Extension -> SDoc
ppr = String -> SDoc
text (String -> SDoc) -> (Extension -> String) -> Extension -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Extension -> String
forall a. Show a => a -> String
show
class OutputableP env a where
pdoc :: env -> a -> SDoc
newtype PDoc a = PDoc a
instance Outputable a => OutputableP env (PDoc a) where
pdoc :: env -> PDoc a -> SDoc
pdoc env
_ (PDoc a
a) = a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
a
instance OutputableP env a => OutputableP env [a] where
pdoc :: env -> [a] -> SDoc
pdoc env
env [a]
xs = [SDoc] -> SDoc
forall a. Outputable a => a -> SDoc
ppr ((a -> SDoc) -> [a] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (env -> a -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc env
env) [a]
xs)
instance OutputableP env a => OutputableP env (Maybe a) where
pdoc :: env -> Maybe a -> SDoc
pdoc env
env Maybe a
xs = Maybe SDoc -> SDoc
forall a. Outputable a => a -> SDoc
ppr ((a -> SDoc) -> Maybe a -> Maybe SDoc
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (env -> a -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc env
env) Maybe a
xs)
instance (OutputableP env a, OutputableP env b) => OutputableP env (a, b) where
pdoc :: env -> (a, b) -> SDoc
pdoc env
env (a
a,b
b) = (SDoc, SDoc) -> SDoc
forall a. Outputable a => a -> SDoc
ppr (env -> a -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc env
env a
a, env -> b -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc env
env b
b)
instance (OutputableP env a, OutputableP env b, OutputableP env c) => OutputableP env (a, b, c) where
pdoc :: env -> (a, b, c) -> SDoc
pdoc env
env (a
a,b
b,c
c) = (SDoc, SDoc, SDoc) -> SDoc
forall a. Outputable a => a -> SDoc
ppr (env -> a -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc env
env a
a, env -> b -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc env
env b
b, env -> c -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc env
env c
c)
instance (OutputableP env key, OutputableP env elt) => OutputableP env (M.Map key elt) where
pdoc :: env -> Map key elt -> SDoc
pdoc env
env Map key elt
m = [(SDoc, SDoc)] -> SDoc
forall a. Outputable a => a -> SDoc
ppr ([(SDoc, SDoc)] -> SDoc) -> [(SDoc, SDoc)] -> SDoc
forall a b. (a -> b) -> a -> b
$ ((key, elt) -> (SDoc, SDoc)) -> [(key, elt)] -> [(SDoc, SDoc)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(key
x,elt
y) -> (env -> key -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc env
env key
x, env -> elt -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc env
env elt
y)) ([(key, elt)] -> [(SDoc, SDoc)]) -> [(key, elt)] -> [(SDoc, SDoc)]
forall a b. (a -> b) -> a -> b
$ Map key elt -> [(key, elt)]
forall k a. Map k a -> [(k, a)]
M.toList Map key elt
m
instance OutputableP env a => OutputableP env (SCC a) where
pdoc :: env -> SCC a -> SDoc
pdoc env
env SCC a
scc = SCC SDoc -> SDoc
forall a. Outputable a => a -> SDoc
ppr ((a -> SDoc) -> SCC a -> SCC SDoc
forall a b. (a -> b) -> SCC a -> SCC b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (env -> a -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc env
env) SCC a
scc)
instance OutputableP env SDoc where
pdoc :: env -> SDoc -> SDoc
pdoc env
_ SDoc
x = SDoc
x
instance (OutputableP env a) => OutputableP env (Set a) where
pdoc :: env -> Set a -> SDoc
pdoc env
env Set a
s = SDoc -> SDoc
braces ([SDoc] -> SDoc
fsep (SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
comma ((a -> SDoc) -> [a] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (env -> a -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc env
env) (Set a -> [a]
forall a. Set a -> [a]
Set.toList Set a
s))))
data BindingSite
= LambdaBind
| CaseBind
| CasePatBind
| LetBind
deriving BindingSite -> BindingSite -> Bool
(BindingSite -> BindingSite -> Bool)
-> (BindingSite -> BindingSite -> Bool) -> Eq BindingSite
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BindingSite -> BindingSite -> Bool
== :: BindingSite -> BindingSite -> Bool
$c/= :: BindingSite -> BindingSite -> Bool
/= :: BindingSite -> BindingSite -> Bool
Eq
class Outputable a => OutputableBndr a where
pprBndr :: BindingSite -> a -> SDoc
pprBndr BindingSite
_b a
x = a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
x
pprPrefixOcc, pprInfixOcc :: a -> SDoc
bndrIsJoin_maybe :: a -> Maybe Int
bndrIsJoin_maybe a
_ = Maybe Int
forall a. Maybe a
Nothing
pprHsChar :: Char -> SDoc
pprHsChar :: Char -> SDoc
pprHsChar Char
c | Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
> Char
'\x10ffff' = Char -> SDoc
char Char
'\\' SDoc -> SDoc -> SDoc
<> String -> SDoc
text (Word32 -> String
forall a. Show a => a -> String
show (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
c) :: Word32))
| Bool
otherwise = String -> SDoc
text (Char -> String
forall a. Show a => a -> String
show Char
c)
pprHsString :: FastString -> SDoc
pprHsString :: FastString -> SDoc
pprHsString FastString
fs = [SDoc] -> SDoc
vcat ((String -> SDoc) -> [String] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map String -> SDoc
text (String -> [String]
showMultiLineString (FastString -> String
unpackFS FastString
fs)))
pprHsBytes :: ByteString -> SDoc
pprHsBytes :: ByteString -> SDoc
pprHsBytes ByteString
bs = let escaped :: String
escaped = (Word8 -> String) -> [Word8] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Word8 -> String
escape ([Word8] -> String) -> [Word8] -> String
forall a b. (a -> b) -> a -> b
$ ByteString -> [Word8]
BS.unpack ByteString
bs
in [SDoc] -> SDoc
vcat ((String -> SDoc) -> [String] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map String -> SDoc
text (String -> [String]
showMultiLineString String
escaped)) SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'#'
where escape :: Word8 -> String
escape :: Word8 -> String
escape Word8
w = let c :: Char
c = Int -> Char
chr (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w)
in if Char -> Bool
isAscii Char
c
then [Char
c]
else Char
'\\' Char -> ShowS
forall a. a -> [a] -> [a]
: Word8 -> String
forall a. Show a => a -> String
show Word8
w
primCharSuffix, primFloatSuffix, primDoubleSuffix,
primIntSuffix, primWordSuffix,
primInt8Suffix, primWord8Suffix,
primInt16Suffix, primWord16Suffix,
primInt32Suffix, primWord32Suffix,
primInt64Suffix, primWord64Suffix
:: SDoc
primCharSuffix :: SDoc
primCharSuffix = Char -> SDoc
char Char
'#'
primFloatSuffix :: SDoc
primFloatSuffix = Char -> SDoc
char Char
'#'
primIntSuffix :: SDoc
primIntSuffix = Char -> SDoc
char Char
'#'
primDoubleSuffix :: SDoc
primDoubleSuffix = String -> SDoc
text String
"##"
primWordSuffix :: SDoc
primWordSuffix = String -> SDoc
text String
"##"
primInt8Suffix :: SDoc
primInt8Suffix = String -> SDoc
text String
"#8"
primWord8Suffix :: SDoc
primWord8Suffix = String -> SDoc
text String
"##8"
primInt16Suffix :: SDoc
primInt16Suffix = String -> SDoc
text String
"#16"
primWord16Suffix :: SDoc
primWord16Suffix = String -> SDoc
text String
"##16"
primInt32Suffix :: SDoc
primInt32Suffix = String -> SDoc
text String
"#32"
primWord32Suffix :: SDoc
primWord32Suffix = String -> SDoc
text String
"##32"
primInt64Suffix :: SDoc
primInt64Suffix = String -> SDoc
text String
"#64"
primWord64Suffix :: SDoc
primWord64Suffix = String -> SDoc
text String
"##64"
pprPrimChar :: Char -> SDoc
pprPrimInt, pprPrimWord,
pprPrimInt8, pprPrimWord8,
pprPrimInt16, pprPrimWord16,
pprPrimInt32, pprPrimWord32,
pprPrimInt64, pprPrimWord64
:: Integer -> SDoc
pprPrimChar :: Char -> SDoc
pprPrimChar Char
c = Char -> SDoc
pprHsChar Char
c SDoc -> SDoc -> SDoc
<> SDoc
primCharSuffix
pprPrimInt :: Integer -> SDoc
pprPrimInt Integer
i = Integer -> SDoc
integer Integer
i SDoc -> SDoc -> SDoc
<> SDoc
primIntSuffix
pprPrimWord :: Integer -> SDoc
pprPrimWord Integer
w = Integer -> SDoc
word Integer
w SDoc -> SDoc -> SDoc
<> SDoc
primWordSuffix
pprPrimInt8 :: Integer -> SDoc
pprPrimInt8 Integer
i = Integer -> SDoc
integer Integer
i SDoc -> SDoc -> SDoc
<> SDoc
primInt8Suffix
pprPrimInt16 :: Integer -> SDoc
pprPrimInt16 Integer
i = Integer -> SDoc
integer Integer
i SDoc -> SDoc -> SDoc
<> SDoc
primInt16Suffix
pprPrimInt32 :: Integer -> SDoc
pprPrimInt32 Integer
i = Integer -> SDoc
integer Integer
i SDoc -> SDoc -> SDoc
<> SDoc
primInt32Suffix
pprPrimInt64 :: Integer -> SDoc
pprPrimInt64 Integer
i = Integer -> SDoc
integer Integer
i SDoc -> SDoc -> SDoc
<> SDoc
primInt64Suffix
pprPrimWord8 :: Integer -> SDoc
pprPrimWord8 Integer
w = Integer -> SDoc
word Integer
w SDoc -> SDoc -> SDoc
<> SDoc
primWord8Suffix
pprPrimWord16 :: Integer -> SDoc
pprPrimWord16 Integer
w = Integer -> SDoc
word Integer
w SDoc -> SDoc -> SDoc
<> SDoc
primWord16Suffix
pprPrimWord32 :: Integer -> SDoc
pprPrimWord32 Integer
w = Integer -> SDoc
word Integer
w SDoc -> SDoc -> SDoc
<> SDoc
primWord32Suffix
pprPrimWord64 :: Integer -> SDoc
pprPrimWord64 Integer
w = Integer -> SDoc
word Integer
w SDoc -> SDoc -> SDoc
<> SDoc
primWord64Suffix
pprPrefixVar :: Bool -> SDoc -> SDoc
pprPrefixVar :: Bool -> SDoc -> SDoc
pprPrefixVar Bool
is_operator SDoc
pp_v
| Bool
is_operator = SDoc -> SDoc
parens SDoc
pp_v
| Bool
otherwise = SDoc
pp_v
pprInfixVar :: Bool -> SDoc -> SDoc
pprInfixVar :: Bool -> SDoc -> SDoc
pprInfixVar Bool
is_operator SDoc
pp_v
| Bool
is_operator = SDoc
pp_v
| Bool
otherwise = Char -> SDoc
char Char
'`' SDoc -> SDoc -> SDoc
<> SDoc
pp_v SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'`'
pprFastFilePath :: FastString -> SDoc
pprFastFilePath :: FastString -> SDoc
pprFastFilePath FastString
path = String -> SDoc
text (String -> SDoc) -> String -> SDoc
forall a b. (a -> b) -> a -> b
$ ShowS
normalise ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ FastString -> String
unpackFS FastString
path
pprFilePathString :: FilePath -> SDoc
pprFilePathString :: String -> SDoc
pprFilePathString String
path = SDoc -> SDoc
doubleQuotes (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text (ShowS
escape (ShowS
normalise String
path))
where
escape :: ShowS
escape [] = []
escape (Char
'\\':String
xs) = Char
'\\'Char -> ShowS
forall a. a -> [a] -> [a]
:Char
'\\'Char -> ShowS
forall a. a -> [a] -> [a]
:ShowS
escape String
xs
escape (Char
x:String
xs) = Char
xChar -> ShowS
forall a. a -> [a] -> [a]
:ShowS
escape String
xs
pprWithCommas :: (a -> SDoc)
-> [a]
-> SDoc
pprWithCommas :: forall a. (a -> SDoc) -> [a] -> SDoc
pprWithCommas a -> SDoc
pp [a]
xs = [SDoc] -> SDoc
fsep (SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
comma ((a -> SDoc) -> [a] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map a -> SDoc
pp [a]
xs))
pprWithBars :: (a -> SDoc)
-> [a]
-> SDoc
pprWithBars :: forall a. (a -> SDoc) -> [a] -> SDoc
pprWithBars a -> SDoc
pp [a]
xs = [SDoc] -> SDoc
fsep (SDoc -> [SDoc] -> [SDoc]
forall a. a -> [a] -> [a]
intersperse SDoc
vbar ((a -> SDoc) -> [a] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map a -> SDoc
pp [a]
xs))
interppSP :: Outputable a => [a] -> SDoc
interppSP :: forall a. Outputable a => [a] -> SDoc
interppSP [a]
xs = [SDoc] -> SDoc
sep ((a -> SDoc) -> [a] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map a -> SDoc
forall a. Outputable a => a -> SDoc
ppr [a]
xs)
interpp'SP :: Outputable a => [a] -> SDoc
interpp'SP :: forall a. Outputable a => [a] -> SDoc
interpp'SP [a]
xs = (a -> SDoc) -> [a] -> SDoc
forall a. (a -> SDoc) -> [a] -> SDoc
interpp'SP' a -> SDoc
forall a. Outputable a => a -> SDoc
ppr [a]
xs
interpp'SP' :: (a -> SDoc) -> [a] -> SDoc
interpp'SP' :: forall a. (a -> SDoc) -> [a] -> SDoc
interpp'SP' a -> SDoc
f [a]
xs = [SDoc] -> SDoc
sep (SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
comma ((a -> SDoc) -> [a] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map a -> SDoc
f [a]
xs))
pprQuotedList :: Outputable a => [a] -> SDoc
pprQuotedList :: forall a. Outputable a => [a] -> SDoc
pprQuotedList = [SDoc] -> SDoc
quotedList ([SDoc] -> SDoc) -> ([a] -> [SDoc]) -> [a] -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> SDoc) -> [a] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map a -> SDoc
forall a. Outputable a => a -> SDoc
ppr
quotedList :: [SDoc] -> SDoc
quotedList :: [SDoc] -> SDoc
quotedList [SDoc]
xs = [SDoc] -> SDoc
fsep (SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
comma ((SDoc -> SDoc) -> [SDoc] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map SDoc -> SDoc
quotes [SDoc]
xs))
quotedListWithOr :: [SDoc] -> SDoc
quotedListWithOr :: [SDoc] -> SDoc
quotedListWithOr xs :: [SDoc]
xs@(SDoc
_:SDoc
_:[SDoc]
_) = [SDoc] -> SDoc
quotedList ([SDoc] -> [SDoc]
forall a. HasCallStack => [a] -> [a]
init [SDoc]
xs) SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"or" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes ([SDoc] -> SDoc
forall a. HasCallStack => [a] -> a
last [SDoc]
xs)
quotedListWithOr [SDoc]
xs = [SDoc] -> SDoc
quotedList [SDoc]
xs
quotedListWithNor :: [SDoc] -> SDoc
quotedListWithNor :: [SDoc] -> SDoc
quotedListWithNor xs :: [SDoc]
xs@(SDoc
_:SDoc
_:[SDoc]
_) = [SDoc] -> SDoc
quotedList ([SDoc] -> [SDoc]
forall a. HasCallStack => [a] -> [a]
init [SDoc]
xs) SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"nor" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes ([SDoc] -> SDoc
forall a. HasCallStack => [a] -> a
last [SDoc]
xs)
quotedListWithNor [SDoc]
xs = [SDoc] -> SDoc
quotedList [SDoc]
xs
intWithCommas :: Integral a => a -> SDoc
intWithCommas :: forall a. Integral a => a -> SDoc
intWithCommas a
n
| a
n a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0 = Char -> SDoc
char Char
'-' SDoc -> SDoc -> SDoc
<> a -> SDoc
forall a. Integral a => a -> SDoc
intWithCommas (-a
n)
| a
q a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0 = Int -> SDoc
int (a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
r)
| Bool
otherwise = a -> SDoc
forall a. Integral a => a -> SDoc
intWithCommas a
q SDoc -> SDoc -> SDoc
<> SDoc
comma SDoc -> SDoc -> SDoc
<> SDoc
zeroes SDoc -> SDoc -> SDoc
<> Int -> SDoc
int (a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
r)
where
(a
q,a
r) = a
n a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
`quotRem` a
1000
zeroes :: SDoc
zeroes | a
r a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
100 = SDoc
empty
| a
r a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
10 = Char -> SDoc
char Char
'0'
| Bool
otherwise = String -> SDoc
text String
"00"
speakNth :: Int -> SDoc
speakNth :: Int -> SDoc
speakNth Int
1 = String -> SDoc
text String
"first"
speakNth Int
2 = String -> SDoc
text String
"second"
speakNth Int
3 = String -> SDoc
text String
"third"
speakNth Int
4 = String -> SDoc
text String
"fourth"
speakNth Int
5 = String -> SDoc
text String
"fifth"
speakNth Int
6 = String -> SDoc
text String
"sixth"
speakNth Int
n = [SDoc] -> SDoc
hcat [ Int -> SDoc
int Int
n, String -> SDoc
text String
suffix ]
where
suffix :: String
suffix | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
20 = String
"th"
| Int
last_dig Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = String
"st"
| Int
last_dig Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2 = String
"nd"
| Int
last_dig Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
3 = String
"rd"
| Bool
otherwise = String
"th"
last_dig :: Int
last_dig = Int
n Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
10
speakN :: Int -> SDoc
speakN :: Int -> SDoc
speakN Int
0 = String -> SDoc
text String
"none"
speakN Int
1 = String -> SDoc
text String
"one"
speakN Int
2 = String -> SDoc
text String
"two"
speakN Int
3 = String -> SDoc
text String
"three"
speakN Int
4 = String -> SDoc
text String
"four"
speakN Int
5 = String -> SDoc
text String
"five"
speakN Int
6 = String -> SDoc
text String
"six"
speakN Int
n = Int -> SDoc
int Int
n
speakNOf :: Int -> SDoc -> SDoc
speakNOf :: Int -> SDoc -> SDoc
speakNOf Int
0 SDoc
d = String -> SDoc
text String
"no" SDoc -> SDoc -> SDoc
<+> SDoc
d SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
's'
speakNOf Int
1 SDoc
d = String -> SDoc
text String
"one" SDoc -> SDoc -> SDoc
<+> SDoc
d
speakNOf Int
n SDoc
d = Int -> SDoc
speakN Int
n SDoc -> SDoc -> SDoc
<+> SDoc
d SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
's'
plural :: [a] -> SDoc
plural :: forall a. [a] -> SDoc
plural [a
_] = SDoc
empty
plural [a]
_ = Char -> SDoc
char Char
's'
singular :: [a] -> SDoc
singular :: forall a. [a] -> SDoc
singular [a
_] = Char -> SDoc
char Char
's'
singular [a]
_ = SDoc
empty
isOrAre :: [a] -> SDoc
isOrAre :: forall a. [a] -> SDoc
isOrAre [a
_] = String -> SDoc
text String
"is"
isOrAre [a]
_ = String -> SDoc
text String
"are"
doOrDoes :: [a] -> SDoc
doOrDoes :: forall a. [a] -> SDoc
doOrDoes [a
_] = String -> SDoc
text String
"does"
doOrDoes [a]
_ = String -> SDoc
text String
"do"
itsOrTheir :: [a] -> SDoc
itsOrTheir :: forall a. [a] -> SDoc
itsOrTheir [a
_] = String -> SDoc
text String
"its"
itsOrTheir [a]
_ = String -> SDoc
text String
"their"
thisOrThese :: [a] -> SDoc
thisOrThese :: forall a. [a] -> SDoc
thisOrThese [a
_] = String -> SDoc
text String
"This"
thisOrThese [a]
_ = String -> SDoc
text String
"These"
hasOrHave :: [a] -> SDoc
hasOrHave :: forall a. [a] -> SDoc
hasOrHave [a
_] = String -> SDoc
text String
"has"
hasOrHave [a]
_ = String -> SDoc
text String
"have"