{-# LANGUAGE OverloadedStrings #-}
module Floskell.Printers
( getConfig
, getOption
, cut
, oneline
, ignoreOneline
, write
, string
, int
, space
, newline
, blankline
, spaceOrNewline
, withTabStops
, atTabStop
, mayM_
, withPrefix
, withPostfix
, withIndentConfig
, withIndent
, withIndentFlex
, withIndentAfter
, withIndentBy
, withLayout
, inter
, getNextColumn
, column
, aligned
, indented
, onside
, depend
, depend'
, parens
, brackets
, group
, groupH
, groupV
, operator
, operatorH
, operatorV
, alignOnOperator
, withOperatorFormatting
, withOperatorFormattingH
, withOperatorFormattingV
, operatorSectionL
, operatorSectionR
, comma
) where
import Control.Applicative ( (<|>) )
import Control.Monad ( guard, unless, when )
import Control.Monad.Search ( cost, winner )
import Control.Monad.State.Strict ( get, gets, modify )
import Data.ByteString ( ByteString )
import qualified Data.ByteString as BS
import qualified Data.ByteString.Builder as BB
import qualified Data.ByteString.Lazy as BL
import Data.List ( intersperse )
import qualified Data.Map.Strict as Map
import Data.Monoid ( (<>) )
import qualified Floskell.Buffer as Buffer
import Floskell.Config
import Floskell.Types
getConfig :: (Config -> b) -> Printer b
getConfig :: forall b. (Config -> b) -> Printer b
getConfig Config -> b
f = Config -> b
f forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets PrintState -> Config
psConfig
getOption :: (OptionConfig -> a) -> Printer a
getOption :: forall a. (OptionConfig -> a) -> Printer a
getOption OptionConfig -> a
f = forall b. (Config -> b) -> Printer b
getConfig (OptionConfig -> a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> OptionConfig
cfgOptions)
linePenalty :: Bool -> Int -> Printer Penalty
linePenalty :: Bool -> Int -> Printer Penalty
linePenalty Bool
eol Int
col = do
Int
indentLevel <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets PrintState -> Int
psIndentLevel
PenaltyConfig
config <- forall b. (Config -> b) -> Printer b
getConfig Config -> PenaltyConfig
cfgPenalty
let maxcol :: Int
maxcol = PenaltyConfig -> Int
penaltyMaxLineLength PenaltyConfig
config
let pLinebreak :: Int
pLinebreak = forall {p}. Num p => Bool -> p -> p
onlyIf Bool
eol forall a b. (a -> b) -> a -> b
$ PenaltyConfig -> Int
penaltyLinebreak PenaltyConfig
config
let pIndent :: Int
pIndent = Int
indentLevel forall a. Num a => a -> a -> a
* PenaltyConfig -> Int
penaltyIndent PenaltyConfig
config
let pOverfull :: Int
pOverfull = forall {p}. Num p => Bool -> p -> p
onlyIf (Int
col forall a. Ord a => a -> a -> Bool
> Int
maxcol) forall a b. (a -> b) -> a -> b
$ PenaltyConfig -> Int
penaltyOverfull PenaltyConfig
config
forall a. Num a => a -> a -> a
* (Int
col forall a. Num a => a -> a -> a
- Int
maxcol) forall a. Num a => a -> a -> a
+ PenaltyConfig -> Int
penaltyOverfullOnce PenaltyConfig
config
forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Penalty
Penalty forall a b. (a -> b) -> a -> b
$ Int
pLinebreak forall a. Num a => a -> a -> a
+ Int
pIndent forall a. Num a => a -> a -> a
+ Int
pOverfull
where
onlyIf :: Bool -> p -> p
onlyIf Bool
cond p
penalty = if Bool
cond then p
penalty else p
0
cut :: Printer a -> Printer a
cut :: forall a. Printer a -> Printer a
cut = forall c (m :: * -> *) a. MonadSearch c m => m a -> m a
winner
closeEolComment :: Printer ()
= do
Bool
eol <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets PrintState -> Bool
psEolComment
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
eol Printer ()
newline
withOutputRestriction :: OutputRestriction -> Printer a -> Printer a
withOutputRestriction :: forall a. OutputRestriction -> Printer a -> Printer a
withOutputRestriction OutputRestriction
r Printer a
p = do
OutputRestriction
orig <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets PrintState -> OutputRestriction
psOutputRestriction
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ \PrintState
s -> PrintState
s { psOutputRestriction :: OutputRestriction
psOutputRestriction = OutputRestriction
r }
a
result <- Printer a
p
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ \PrintState
s -> PrintState
s { psOutputRestriction :: OutputRestriction
psOutputRestriction = OutputRestriction
orig }
forall (m :: * -> *) a. Monad m => a -> m a
return a
result
oneline :: Printer a -> Printer a
oneline :: forall a. Printer a -> Printer a
oneline Printer a
p = do
Printer ()
closeEolComment
forall a. OutputRestriction -> Printer a -> Printer a
withOutputRestriction OutputRestriction
NoOverflowOrLinebreak Printer a
p
ignoreOneline :: Printer a -> Printer a
ignoreOneline :: forall a. Printer a -> Printer a
ignoreOneline = forall a. OutputRestriction -> Printer a -> Printer a
withOutputRestriction OutputRestriction
Anything
write :: ByteString -> Printer ()
write :: ByteString -> Printer ()
write ByteString
x = do
Printer ()
closeEolComment
ByteString -> Printer ()
write' ByteString
x
where
write' :: ByteString -> Printer ()
write' ByteString
x' = do
PrintState
state <- forall s (m :: * -> *). MonadState s m => m s
get
let indentLevel :: Int
indentLevel = PrintState -> Int
psIndentLevel PrintState
state
out :: ByteString
out = if PrintState -> Bool
psNewline PrintState
state
then Int -> Word8 -> ByteString
BS.replicate Int
indentLevel Word8
32 forall a. Semigroup a => a -> a -> a
<> ByteString
x'
else ByteString
x'
buffer :: Buffer
buffer = PrintState -> Buffer
psBuffer PrintState
state
newCol :: Int
newCol = Buffer -> Int
Buffer.column Buffer
buffer forall a. Num a => a -> a -> a
+ ByteString -> Int
BS.length ByteString
out
forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ PrintState -> OutputRestriction
psOutputRestriction PrintState
state forall a. Eq a => a -> a -> Bool
== OutputRestriction
Anything Bool -> Bool -> Bool
|| Int
newCol
forall a. Ord a => a -> a -> Bool
< PenaltyConfig -> Int
penaltyMaxLineLength (Config -> PenaltyConfig
cfgPenalty (PrintState -> Config
psConfig PrintState
state))
Penalty
penalty <- Bool -> Int -> Printer Penalty
linePenalty Bool
False Int
newCol
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Penalty
penalty forall a. Eq a => a -> a -> Bool
/= forall a. Monoid a => a
mempty) forall a b. (a -> b) -> a -> b
$ forall c (m :: * -> *). MonadSearch c m => c -> c -> m ()
cost forall a. Monoid a => a
mempty Penalty
penalty
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\PrintState
s ->
PrintState
s { psBuffer :: Buffer
psBuffer = ByteString -> Buffer -> Buffer
Buffer.write ByteString
out Buffer
buffer, psEolComment :: Bool
psEolComment = Bool
False })
string :: String -> Printer ()
string :: String -> Printer ()
string = ByteString -> Printer ()
write forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> ByteString
BB.toLazyByteString forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Builder
BB.stringUtf8
int :: Int -> Printer ()
int :: Int -> Printer ()
int = String -> Printer ()
string forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
space :: Printer ()
space :: Printer ()
space = do
Bool
comment <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets PrintState -> Bool
psEolComment
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
comment forall a b. (a -> b) -> a -> b
$ ByteString -> Printer ()
write ByteString
" "
newline :: Printer ()
newline :: Printer ()
newline = do
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\PrintState
s ->
PrintState
s { psIndentLevel :: Int
psIndentLevel = PrintState -> Int
psIndentLevel PrintState
s forall a. Num a => a -> a -> a
+ PrintState -> Int
psOnside PrintState
s, psOnside :: Int
psOnside = Int
0 })
PrintState
state <- forall s (m :: * -> *). MonadState s m => m s
get
forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ PrintState -> OutputRestriction
psOutputRestriction PrintState
state forall a. Eq a => a -> a -> Bool
/= OutputRestriction
NoOverflowOrLinebreak
Penalty
penalty <- Bool -> Int -> Printer Penalty
linePenalty Bool
True (PrintState -> Int
psColumn PrintState
state)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Penalty
penalty forall a. Eq a => a -> a -> Bool
/= forall a. Monoid a => a
mempty) forall a b. (a -> b) -> a -> b
$ forall c (m :: * -> *). MonadSearch c m => c -> c -> m ()
cost Penalty
penalty forall a. Monoid a => a
mempty
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\PrintState
s -> PrintState
s { psBuffer :: Buffer
psBuffer = Buffer -> Buffer
Buffer.newline (PrintState -> Buffer
psBuffer PrintState
state)
, psEolComment :: Bool
psEolComment = Bool
False
})
blankline :: Printer ()
blankline :: Printer ()
blankline = Printer ()
newline forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Printer ()
newline
spaceOrNewline :: Printer ()
spaceOrNewline :: Printer ()
spaceOrNewline = Printer ()
space forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Printer ()
newline
withTabStops :: [(TabStop, Maybe Int)] -> Printer a -> Printer a
withTabStops :: forall a. [(TabStop, Maybe Int)] -> Printer a -> Printer a
withTabStops [(TabStop, Maybe Int)]
stops Printer a
p = do
Int
col <- Printer Int
getNextColumn
Map TabStop Int
oldstops <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets PrintState -> Map TabStop Int
psTabStops
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ \PrintState
s ->
PrintState
s { psTabStops :: Map TabStop Int
psTabStops =
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\(TabStop
k, Maybe Int
v) -> forall k a.
Ord k =>
(Maybe a -> Maybe a) -> k -> Map k a -> Map k a
Map.alter (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Int
x -> Int
col forall a. Num a => a -> a -> a
+ Int
x) Maybe Int
v) TabStop
k)
(PrintState -> Map TabStop Int
psTabStops PrintState
s)
[(TabStop, Maybe Int)]
stops
}
a
res <- Printer a
p
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ \PrintState
s -> PrintState
s { psTabStops :: Map TabStop Int
psTabStops = Map TabStop Int
oldstops }
forall (m :: * -> *) a. Monad m => a -> m a
return a
res
atTabStop :: TabStop -> Printer ()
atTabStop :: TabStop -> Printer ()
atTabStop TabStop
tabstop = do
Maybe Int
mstop <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup TabStop
tabstop forall b c a. (b -> c) -> (a -> b) -> a -> c
. PrintState -> Map TabStop Int
psTabStops)
forall a. Maybe a -> (a -> Printer ()) -> Printer ()
mayM_ Maybe Int
mstop forall a b. (a -> b) -> a -> b
$ \Int
stop -> do
Int
col <- Printer Int
getNextColumn
let padding :: Int
padding = forall a. Ord a => a -> a -> a
max Int
0 (Int
stop forall a. Num a => a -> a -> a
- Int
col)
ByteString -> Printer ()
write (Int -> Word8 -> ByteString
BS.replicate Int
padding Word8
32)
mayM_ :: Maybe a -> (a -> Printer ()) -> Printer ()
mayM_ :: forall a. Maybe a -> (a -> Printer ()) -> Printer ()
mayM_ Maybe a
Nothing a -> Printer ()
_ = forall (m :: * -> *) a. Monad m => a -> m a
return ()
mayM_ (Just a
x) a -> Printer ()
p = a -> Printer ()
p a
x
withPrefix :: Applicative f => f a -> (x -> f b) -> x -> f b
withPrefix :: forall (f :: * -> *) a x b.
Applicative f =>
f a -> (x -> f b) -> x -> f b
withPrefix f a
pre x -> f b
f x
x = f a
pre forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> x -> f b
f x
x
withPostfix :: Applicative f => f a -> (x -> f b) -> x -> f b
withPostfix :: forall (f :: * -> *) a x b.
Applicative f =>
f a -> (x -> f b) -> x -> f b
withPostfix f a
post x -> f b
f x
x = x -> f b
f x
x forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* f a
post
withIndentConfig
:: (IndentConfig -> Indent) -> Printer a -> (Int -> Printer a) -> Printer a
withIndentConfig :: forall a.
(IndentConfig -> Indent)
-> Printer a -> (Int -> Printer a) -> Printer a
withIndentConfig IndentConfig -> Indent
fn Printer a
align Int -> Printer a
indentby = do
Indent
cfg <- forall b. (Config -> b) -> Printer b
getConfig (IndentConfig -> Indent
fn forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> IndentConfig
cfgIndent)
case Indent
cfg of
Indent
Align -> Printer a
align
IndentBy Int
i -> Int -> Printer a
indentby Int
i
AlignOrIndentBy Int
i -> Printer a
align forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Int -> Printer a
indentby Int
i
withIndent :: (IndentConfig -> Indent) -> Printer a -> Printer a
withIndent :: forall a. (IndentConfig -> Indent) -> Printer a -> Printer a
withIndent IndentConfig -> Indent
fn Printer a
p = forall a.
(IndentConfig -> Indent)
-> Printer a -> (Int -> Printer a) -> Printer a
withIndentConfig IndentConfig -> Indent
fn Printer a
align Int -> Printer a
indentby
where
align :: Printer a
align = do
Printer ()
space
forall a. Printer a -> Printer a
aligned Printer a
p
indentby :: Int -> Printer a
indentby Int
i = forall a. Int -> Printer a -> Printer a
indented Int
i forall a b. (a -> b) -> a -> b
$ do
Printer ()
newline
Printer a
p
withIndentFlex :: (IndentConfig -> Indent) -> Printer a -> Printer a
withIndentFlex :: forall a. (IndentConfig -> Indent) -> Printer a -> Printer a
withIndentFlex IndentConfig -> Indent
fn Printer a
p = forall a.
(IndentConfig -> Indent)
-> Printer a -> (Int -> Printer a) -> Printer a
withIndentConfig IndentConfig -> Indent
fn Printer a
align Int -> Printer a
indentby
where
align :: Printer a
align = do
Printer ()
space
forall a. Printer a -> Printer a
aligned Printer a
p
indentby :: Int -> Printer a
indentby Int
i = forall a. Int -> Printer a -> Printer a
indented Int
i forall a b. (a -> b) -> a -> b
$ do
Printer ()
spaceOrNewline
Printer a
p
withIndentAfter
:: (IndentConfig -> Indent) -> Printer () -> Printer a -> Printer a
withIndentAfter :: forall a.
(IndentConfig -> Indent) -> Printer () -> Printer a -> Printer a
withIndentAfter IndentConfig -> Indent
fn Printer ()
before Printer a
p = forall a.
(IndentConfig -> Indent)
-> Printer a -> (Int -> Printer a) -> Printer a
withIndentConfig IndentConfig -> Indent
fn Printer a
align Int -> Printer a
indentby
where
align :: Printer a
align = forall a. Printer a -> Printer a
aligned forall a b. (a -> b) -> a -> b
$ do
forall a. ((Int, Int) -> (Int, Int)) -> Printer a -> Printer a
withIndentation forall a. a -> a
id Printer ()
before
Printer a
p
indentby :: Int -> Printer a
indentby Int
i = do
forall a. ((Int, Int) -> (Int, Int)) -> Printer a -> Printer a
withIndentation forall a. a -> a
id Printer ()
before
forall a. Int -> Printer a -> Printer a
indented Int
i Printer a
p
withIndentBy :: (IndentConfig -> Int) -> Printer a -> Printer a
withIndentBy :: forall a. (IndentConfig -> Int) -> Printer a -> Printer a
withIndentBy IndentConfig -> Int
fn = forall a. (IndentConfig -> Indent) -> Printer a -> Printer a
withIndent (Int -> Indent
IndentBy forall b c a. (b -> c) -> (a -> b) -> a -> c
. IndentConfig -> Int
fn)
withLayout :: (LayoutConfig -> Layout) -> Printer a -> Printer a -> Printer a
withLayout :: forall a.
(LayoutConfig -> Layout) -> Printer a -> Printer a -> Printer a
withLayout LayoutConfig -> Layout
fn Printer a
flex Printer a
vertical = do
Layout
cfg <- forall b. (Config -> b) -> Printer b
getConfig (LayoutConfig -> Layout
fn forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> LayoutConfig
cfgLayout)
case Layout
cfg of
Layout
Flex -> Printer a
flex
Layout
Vertical -> Printer a
vertical
Layout
TryOneline -> forall a. Printer a -> Printer a
oneline Printer a
flex forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Printer a
vertical
inter :: Printer () -> [Printer ()] -> Printer ()
inter :: Printer () -> [Printer ()] -> Printer ()
inter Printer ()
x = forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> [a] -> [a]
intersperse Printer ()
x
getNextColumn :: Printer Int
getNextColumn :: Printer Int
getNextColumn = do
PrintState
st <- forall s (m :: * -> *). MonadState s m => m s
get
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ if PrintState -> Bool
psEolComment PrintState
st
then PrintState -> Int
psIndentLevel PrintState
st forall a. Num a => a -> a -> a
+ PrintState -> Int
psOnside PrintState
st
else forall a. Ord a => a -> a -> a
max (PrintState -> Int
psColumn PrintState
st) (PrintState -> Int
psIndentLevel PrintState
st)
withIndentation :: ((Int, Int) -> (Int, Int)) -> Printer a -> Printer a
withIndentation :: forall a. ((Int, Int) -> (Int, Int)) -> Printer a -> Printer a
withIndentation (Int, Int) -> (Int, Int)
f Printer a
p = do
Int
prevIndent <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets PrintState -> Int
psIndentLevel
Int
prevOnside <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets PrintState -> Int
psOnside
let (Int
newIndent, Int
newOnside) = (Int, Int) -> (Int, Int)
f (Int
prevIndent, Int
prevOnside)
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\PrintState
s -> PrintState
s { psIndentLevel :: Int
psIndentLevel = Int
newIndent, psOnside :: Int
psOnside = Int
newOnside })
a
r <- Printer a
p
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\PrintState
s -> PrintState
s { psIndentLevel :: Int
psIndentLevel = Int
prevIndent, psOnside :: Int
psOnside = Int
prevOnside })
forall (m :: * -> *) a. Monad m => a -> m a
return a
r
column :: Int -> Printer a -> Printer a
column :: forall a. Int -> Printer a -> Printer a
column Int
i = forall a. ((Int, Int) -> (Int, Int)) -> Printer a -> Printer a
withIndentation forall a b. (a -> b) -> a -> b
$ \(Int
l, Int
o) -> (Int
i, if Int
i forall a. Ord a => a -> a -> Bool
> Int
l then Int
0 else Int
o)
aligned :: Printer a -> Printer a
aligned :: forall a. Printer a -> Printer a
aligned Printer a
p = do
Int
col <- Printer Int
getNextColumn
forall a. Int -> Printer a -> Printer a
column Int
col Printer a
p
indented :: Int -> Printer a -> Printer a
indented :: forall a. Int -> Printer a -> Printer a
indented Int
i Printer a
p = do
Int
level <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets PrintState -> Int
psIndentLevel
forall a. Int -> Printer a -> Printer a
column (Int
level forall a. Num a => a -> a -> a
+ Int
i) Printer a
p
onside :: Printer a -> Printer a
onside :: forall a. Printer a -> Printer a
onside Printer a
p = do
Printer ()
closeEolComment
Int
onsideIndent <- forall b. (Config -> b) -> Printer b
getConfig (IndentConfig -> Int
cfgIndentOnside forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> IndentConfig
cfgIndent)
forall a. ((Int, Int) -> (Int, Int)) -> Printer a -> Printer a
withIndentation (\(Int
l, Int
_) -> (Int
l, Int
onsideIndent)) Printer a
p
depend :: ByteString -> Printer a -> Printer a
depend :: forall a. ByteString -> Printer a -> Printer a
depend ByteString
kw = forall a. Printer () -> Printer a -> Printer a
depend' (ByteString -> Printer ()
write ByteString
kw)
depend' :: Printer () -> Printer a -> Printer a
depend' :: forall a. Printer () -> Printer a -> Printer a
depend' Printer ()
kw Printer a
p = do
Int
i <- forall b. (Config -> b) -> Printer b
getConfig (IndentConfig -> Int
cfgIndentOnside forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> IndentConfig
cfgIndent)
Printer ()
kw
Printer ()
space
forall a. Int -> Printer a -> Printer a
indented Int
i Printer a
p
parens :: Printer () -> Printer ()
parens :: Printer () -> Printer ()
parens Printer ()
p = do
ByteString -> Printer ()
write ByteString
"("
forall a. Printer a -> Printer a
aligned forall a b. (a -> b) -> a -> b
$ do
Printer ()
p
ByteString -> Printer ()
write ByteString
")"
brackets :: Printer () -> Printer ()
brackets :: Printer () -> Printer ()
brackets Printer ()
p = do
ByteString -> Printer ()
write ByteString
"["
forall a. Printer a -> Printer a
aligned forall a b. (a -> b) -> a -> b
$ do
Printer ()
p
ByteString -> Printer ()
write ByteString
"]"
group :: LayoutContext -> ByteString -> ByteString -> Printer () -> Printer ()
group :: LayoutContext
-> ByteString -> ByteString -> Printer () -> Printer ()
group LayoutContext
ctx ByteString
open ByteString
close Printer ()
p = do
Bool
force <- forall b. (Config -> b) -> Printer b
getConfig (Whitespace -> Bool
wsForceLinebreak forall b c a. (b -> c) -> (a -> b) -> a -> c
. LayoutContext -> ByteString -> GroupConfig -> Whitespace
cfgGroupWs LayoutContext
ctx ByteString
open forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> GroupConfig
cfgGroup)
if Bool
force then Printer ()
vert else forall a. Printer a -> Printer a
oneline Printer ()
hor forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Printer ()
vert
where
hor :: Printer ()
hor = LayoutContext
-> ByteString -> ByteString -> Printer () -> Printer ()
groupH LayoutContext
ctx ByteString
open ByteString
close Printer ()
p
vert :: Printer ()
vert = LayoutContext
-> ByteString -> ByteString -> Printer () -> Printer ()
groupV LayoutContext
ctx ByteString
open ByteString
close Printer ()
p
groupH :: LayoutContext -> ByteString -> ByteString -> Printer () -> Printer ()
groupH :: LayoutContext
-> ByteString -> ByteString -> Printer () -> Printer ()
groupH LayoutContext
ctx ByteString
open ByteString
close Printer ()
p = do
Whitespace
ws <- forall b. (Config -> b) -> Printer b
getConfig (LayoutContext -> ByteString -> GroupConfig -> Whitespace
cfgGroupWs LayoutContext
ctx ByteString
open forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> GroupConfig
cfgGroup)
ByteString -> Printer ()
write ByteString
open
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Location -> Whitespace -> Bool
wsSpace Location
Before Whitespace
ws) Printer ()
space
Printer ()
p
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Location -> Whitespace -> Bool
wsSpace Location
After Whitespace
ws) Printer ()
space
ByteString -> Printer ()
write ByteString
close
groupV :: LayoutContext -> ByteString -> ByteString -> Printer () -> Printer ()
groupV :: LayoutContext
-> ByteString -> ByteString -> Printer () -> Printer ()
groupV LayoutContext
ctx ByteString
open ByteString
close Printer ()
p = forall a. Printer a -> Printer a
aligned forall a b. (a -> b) -> a -> b
$ do
Whitespace
ws <- forall b. (Config -> b) -> Printer b
getConfig (LayoutContext -> ByteString -> GroupConfig -> Whitespace
cfgGroupWs LayoutContext
ctx ByteString
open forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> GroupConfig
cfgGroup)
ByteString -> Printer ()
write ByteString
open
if Location -> Whitespace -> Bool
wsLinebreak Location
Before Whitespace
ws then Printer ()
newline else forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Location -> Whitespace -> Bool
wsSpace Location
Before Whitespace
ws) Printer ()
space
Printer ()
p
if Location -> Whitespace -> Bool
wsLinebreak Location
After Whitespace
ws then Printer ()
newline else forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Location -> Whitespace -> Bool
wsSpace Location
After Whitespace
ws) Printer ()
space
ByteString -> Printer ()
write ByteString
close
operator :: LayoutContext -> ByteString -> Printer ()
operator :: LayoutContext -> ByteString -> Printer ()
operator LayoutContext
ctx ByteString
op = forall a.
LayoutContext
-> ByteString
-> Printer ()
-> (Printer () -> Printer a)
-> Printer a
withOperatorFormatting LayoutContext
ctx ByteString
op (ByteString -> Printer ()
write ByteString
op) forall a. a -> a
id
operatorH :: LayoutContext -> ByteString -> Printer ()
operatorH :: LayoutContext -> ByteString -> Printer ()
operatorH LayoutContext
ctx ByteString
op = forall a.
LayoutContext
-> ByteString
-> Printer ()
-> (Printer () -> Printer a)
-> Printer a
withOperatorFormattingH LayoutContext
ctx ByteString
op (ByteString -> Printer ()
write ByteString
op) forall a. a -> a
id
operatorV :: LayoutContext -> ByteString -> Printer ()
operatorV :: LayoutContext -> ByteString -> Printer ()
operatorV LayoutContext
ctx ByteString
op = forall a.
LayoutContext
-> ByteString
-> Printer ()
-> (Printer () -> Printer a)
-> Printer a
withOperatorFormattingV LayoutContext
ctx ByteString
op (ByteString -> Printer ()
write ByteString
op) forall a. a -> a
id
alignOnOperator :: LayoutContext -> ByteString -> Printer a -> Printer a
alignOnOperator :: forall a. LayoutContext -> ByteString -> Printer a -> Printer a
alignOnOperator LayoutContext
ctx ByteString
op Printer a
p =
forall a.
LayoutContext
-> ByteString
-> Printer ()
-> (Printer () -> Printer a)
-> Printer a
withOperatorFormatting LayoutContext
ctx ByteString
op (ByteString -> Printer ()
write ByteString
op) (forall a. Printer a -> Printer a
aligned forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Printer a
p))
withOperatorFormatting :: LayoutContext
-> ByteString
-> Printer ()
-> (Printer () -> Printer a)
-> Printer a
withOperatorFormatting :: forall a.
LayoutContext
-> ByteString
-> Printer ()
-> (Printer () -> Printer a)
-> Printer a
withOperatorFormatting LayoutContext
ctx ByteString
op Printer ()
opp Printer () -> Printer a
fn = do
Bool
force <- forall b. (Config -> b) -> Printer b
getConfig (Whitespace -> Bool
wsForceLinebreak forall b c a. (b -> c) -> (a -> b) -> a -> c
. LayoutContext -> ByteString -> OpConfig -> Whitespace
cfgOpWs LayoutContext
ctx ByteString
op forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> OpConfig
cfgOp)
if Bool
force then Printer a
vert else Printer a
hor forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Printer a
vert
where
hor :: Printer a
hor = forall a.
LayoutContext
-> ByteString
-> Printer ()
-> (Printer () -> Printer a)
-> Printer a
withOperatorFormattingH LayoutContext
ctx ByteString
op Printer ()
opp Printer () -> Printer a
fn
vert :: Printer a
vert = forall a.
LayoutContext
-> ByteString
-> Printer ()
-> (Printer () -> Printer a)
-> Printer a
withOperatorFormattingV LayoutContext
ctx ByteString
op Printer ()
opp Printer () -> Printer a
fn
withOperatorFormattingH :: LayoutContext
-> ByteString
-> Printer ()
-> (Printer () -> Printer a)
-> Printer a
withOperatorFormattingH :: forall a.
LayoutContext
-> ByteString
-> Printer ()
-> (Printer () -> Printer a)
-> Printer a
withOperatorFormattingH LayoutContext
ctx ByteString
op Printer ()
opp Printer () -> Printer a
fn = do
Whitespace
ws <- forall b. (Config -> b) -> Printer b
getConfig (LayoutContext -> ByteString -> OpConfig -> Whitespace
cfgOpWs LayoutContext
ctx ByteString
op forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> OpConfig
cfgOp)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Location -> Whitespace -> Bool
wsSpace Location
Before Whitespace
ws) Printer ()
space
Printer () -> Printer a
fn forall a b. (a -> b) -> a -> b
$ do
Printer ()
opp
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Location -> Whitespace -> Bool
wsSpace Location
After Whitespace
ws) Printer ()
space
withOperatorFormattingV :: LayoutContext
-> ByteString
-> Printer ()
-> (Printer () -> Printer a)
-> Printer a
withOperatorFormattingV :: forall a.
LayoutContext
-> ByteString
-> Printer ()
-> (Printer () -> Printer a)
-> Printer a
withOperatorFormattingV LayoutContext
ctx ByteString
op Printer ()
opp Printer () -> Printer a
fn = do
Whitespace
ws <- forall b. (Config -> b) -> Printer b
getConfig (LayoutContext -> ByteString -> OpConfig -> Whitespace
cfgOpWs LayoutContext
ctx ByteString
op forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> OpConfig
cfgOp)
if Location -> Whitespace -> Bool
wsLinebreak Location
Before Whitespace
ws then Printer ()
newline else forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Location -> Whitespace -> Bool
wsSpace Location
Before Whitespace
ws) Printer ()
space
Printer () -> Printer a
fn forall a b. (a -> b) -> a -> b
$ do
Printer ()
opp
if Location -> Whitespace -> Bool
wsLinebreak Location
After Whitespace
ws then Printer ()
newline else forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Location -> Whitespace -> Bool
wsSpace Location
After Whitespace
ws) Printer ()
space
operatorSectionL :: LayoutContext -> ByteString -> Printer () -> Printer ()
operatorSectionL :: LayoutContext -> ByteString -> Printer () -> Printer ()
operatorSectionL LayoutContext
ctx ByteString
op Printer ()
opp = do
Whitespace
ws <- forall b. (Config -> b) -> Printer b
getConfig (LayoutContext -> ByteString -> OpConfig -> Whitespace
cfgOpWs LayoutContext
ctx ByteString
op forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> OpConfig
cfgOp)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Location -> Whitespace -> Bool
wsSpace Location
Before Whitespace
ws) Printer ()
space
Printer ()
opp
operatorSectionR :: LayoutContext -> ByteString -> Printer () -> Printer ()
operatorSectionR :: LayoutContext -> ByteString -> Printer () -> Printer ()
operatorSectionR LayoutContext
ctx ByteString
op Printer ()
opp = do
Whitespace
ws <- forall b. (Config -> b) -> Printer b
getConfig (LayoutContext -> ByteString -> OpConfig -> Whitespace
cfgOpWs LayoutContext
ctx ByteString
op forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> OpConfig
cfgOp)
Printer ()
opp
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Location -> Whitespace -> Bool
wsSpace Location
After Whitespace
ws) Printer ()
space
comma :: Printer ()
comma :: Printer ()
comma = LayoutContext -> ByteString -> Printer ()
operator LayoutContext
Expression ByteString
","