{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-warnings-deprecations #-}
module Options.Applicative.Help.Pretty
( module Text.PrettyPrint.ANSI.Leijen
, Doc
, indent
, renderPretty
, displayS
, (.$.)
, groupOrNestLine
, altSep
, hangAtIfOver
) where
#if !MIN_VERSION_base(4,11,0)
import Data.Semigroup ((<>))
#endif
import Text.PrettyPrint.ANSI.Leijen hiding (Doc, (<$>), (<>), columns, indent, renderPretty, displayS)
import qualified Text.PrettyPrint.ANSI.Leijen as PP
import Prelude
type Doc = PP.Doc
indent :: Int -> PP.Doc -> PP.Doc
indent :: Int -> Doc -> Doc
indent = Int -> Doc -> Doc
PP.indent
renderPretty :: Float -> Int -> PP.Doc -> SimpleDoc
renderPretty :: Float -> Int -> Doc -> SimpleDoc
renderPretty = Float -> Int -> Doc -> SimpleDoc
PP.renderPretty
displayS :: SimpleDoc -> ShowS
displayS :: SimpleDoc -> ShowS
displayS = SimpleDoc -> ShowS
PP.displayS
(.$.) :: Doc -> Doc -> Doc
.$. :: Doc -> Doc -> Doc
(.$.) = Doc -> Doc -> Doc
(PP.<$>)
ifNotAtRoot :: (Doc -> Doc) -> Doc -> Doc
ifNotAtRoot :: (Doc -> Doc) -> Doc -> Doc
ifNotAtRoot =
(Doc -> Doc) -> (Doc -> Doc) -> Doc -> Doc
ifElseAtRoot forall a. a -> a
id
ifAtRoot :: (Doc -> Doc) -> Doc -> Doc
ifAtRoot :: (Doc -> Doc) -> Doc -> Doc
ifAtRoot =
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Doc -> Doc) -> (Doc -> Doc) -> Doc -> Doc
ifElseAtRoot forall a. a -> a
id
ifElseAtRoot :: (Doc -> Doc) -> (Doc -> Doc) -> Doc -> Doc
ifElseAtRoot :: (Doc -> Doc) -> (Doc -> Doc) -> Doc -> Doc
ifElseAtRoot Doc -> Doc
f Doc -> Doc
g Doc
doc =
(Int -> Doc) -> Doc
nesting forall a b. (a -> b) -> a -> b
$ \Int
i ->
(Int -> Doc) -> Doc
column forall a b. (a -> b) -> a -> b
$ \Int
j ->
if Int
i forall a. Eq a => a -> a -> Bool
== Int
j
then Doc -> Doc
f Doc
doc
else Doc -> Doc
g Doc
doc
groupOrNestLine :: Doc -> Doc
groupOrNestLine :: Doc -> Doc
groupOrNestLine =
Doc -> Doc
group forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Doc -> Doc) -> Doc -> Doc
ifNotAtRoot (Doc
linebreak forall a. Semigroup a => a -> a -> a
<>) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Doc -> Doc
nest Int
2
altSep :: Doc -> Doc -> Doc
altSep :: Doc -> Doc -> Doc
altSep Doc
x Doc
y =
Doc -> Doc
group (Doc
x Doc -> Doc -> Doc
<+> Char -> Doc
char Char
'|' forall a. Semigroup a => a -> a -> a
<> Doc
line) Doc -> Doc -> Doc
<//> Doc
y
hangAtIfOver :: Int -> Int -> Doc -> Doc
hangAtIfOver :: Int -> Int -> Doc -> Doc
hangAtIfOver Int
i Int
j Doc
d =
(Int -> Doc) -> Doc
column forall a b. (a -> b) -> a -> b
$ \Int
k ->
if Int
k forall a. Ord a => a -> a -> Bool
<= Int
j then
Doc -> Doc
align Doc
d
else
Doc
linebreak forall a. Semigroup a => a -> a -> a
<> (Doc -> Doc) -> Doc -> Doc
ifAtRoot (Int -> Doc -> Doc
indent Int
i) Doc
d