module Data.SCargot.Print
(
encodeOne
, encode
, encodeOneLazy
, encodeLazy
, SExprPrinter
, Indent(..)
, setFromCarrier
, setMaxWidth
, removeMaxWidth
, setIndentAmount
, setIndentStrategy
, basicPrint
, flatPrint
, unconstrainedPrint
) where
import qualified Data.Foldable as F
import Data.Monoid ((<>))
import qualified Data.Sequence as Seq
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as B
import qualified Data.Traversable as T
import Data.SCargot.Repr
data Indent
= Swing
| SwingAfter Int
| Align
deriving (Eq, Show)
data SExprPrinter atom carrier = SExprPrinter
{ atomPrinter :: atom -> Text
, fromCarrier :: carrier -> SExpr atom
, swingIndent :: SExpr atom -> Indent
, indentAmount :: Int
, maxWidth :: Maybe Int
, indentPrint :: Bool
}
flatPrint :: (atom -> Text) -> SExprPrinter atom (SExpr atom)
flatPrint printer = SExprPrinter
{ atomPrinter = printer
, fromCarrier = id
, swingIndent = const Swing
, indentAmount = 2
, maxWidth = Nothing
, indentPrint = False
}
basicPrint :: (atom -> Text) -> SExprPrinter atom (SExpr atom)
basicPrint printer = SExprPrinter
{ atomPrinter = printer
, fromCarrier = id
, swingIndent = const Swing
, indentAmount = 2
, maxWidth = Just 80
, indentPrint = True
}
unconstrainedPrint :: (atom -> Text) -> SExprPrinter atom (SExpr atom)
unconstrainedPrint printer = SExprPrinter
{ atomPrinter = printer
, fromCarrier = id
, swingIndent = const Swing
, indentAmount = 2
, maxWidth = Nothing
, indentPrint = True
}
data Size = Size
{ sizeSum :: !Int
, sizeMax :: !Int
} deriving (Show)
data Intermediate
= IAtom Text
| IList Indent Size Intermediate (Seq.Seq Intermediate) (Maybe Text)
| IEmpty
sizeOf :: Intermediate -> Size
sizeOf IEmpty = Size 2 2
sizeOf (IAtom t) = Size len len where len = T.length t
sizeOf (IList _ s _ _ _) = s
concatSize :: Size -> Size -> Size
concatSize l r = Size
{ sizeSum = sizeSum l + 1 + sizeSum r
, sizeMax = sizeMax l `max` sizeMax r
}
toIntermediate :: SExprPrinter a (SExpr a) -> SExpr a -> Intermediate
toIntermediate
SExprPrinter { atomPrinter = printAtom
, swingIndent = swing
} = headOf
where
headOf (SAtom a) = IAtom (printAtom a)
headOf SNil = IEmpty
headOf (SCons x xs) =
gather (swing x) hd Seq.empty xs (sizeOf hd) where hd = headOf x
gather sw hd rs SNil sz =
IList sw sz hd rs Nothing
gather sw hd rs (SAtom a) sz =
IList sw (sz `concatSize` aSize) hd rs (Just aStr)
where aSize = Size (T.length aStr) (T.length aStr)
aStr = printAtom a
gather sw hd rs (SCons x xs) sz =
gather sw hd (rs Seq.|> x') xs (sz `concatSize` sizeOf x')
where x' = headOf x
unboundIndentPrintSExpr :: SExprPrinter a (SExpr a) -> SExpr a -> TL.Text
unboundIndentPrintSExpr spec = finalize . go . toIntermediate spec
where
finalize = B.toLazyText . joinLinesS
go :: Intermediate -> Seq.Seq B.Builder
go (IAtom t) = Seq.singleton (B.fromText t)
go IEmpty = Seq.singleton (B.fromString "()")
go (IList iv _ initial values rest)
| Just strings <- T.traverse ppBasic (initial Seq.<| values) =
Seq.singleton (B.fromString "(" <> buildUnwords strings <> pTail rest)
| Swing <- iv =
let butLast = insertParen (go initial) <> fmap doIndent (F.foldMap go values)
in handleTail rest butLast
| SwingAfter n <- iv =
let (hs, xs) = Seq.splitAt n (initial Seq.<| values)
hd = B.fromString "(" <> buildUnwords (F.foldMap go hs)
butLast = hd Seq.<| fmap doIndent (F.foldMap go xs)
in handleTail rest butLast
| otherwise =
let
len = 2 + F.maximum (fmap (TL.length . B.toLazyText) (go initial))
in case Seq.viewl values of
Seq.EmptyL -> insertParen (insertCloseParen (go initial))
y Seq.:< ys ->
let hd = B.fromString "(" <> buildUnwords (F.foldMap go (Seq.fromList [initial, y]))
butLast = hd Seq.<| fmap (doIndentOf (fromIntegral len)) (F.foldMap go ys)
in handleTail rest butLast
doIndent :: B.Builder -> B.Builder
doIndent = doIndentOf (indentAmount spec)
doIndentOf :: Int -> B.Builder -> B.Builder
doIndentOf n b = B.fromText (T.replicate n " ") <> b
insertParen :: Seq.Seq B.Builder -> Seq.Seq B.Builder
insertParen s = case Seq.viewl s of
Seq.EmptyL -> s
x Seq.:< xs -> (B.fromString "(" <> x) Seq.<| xs
handleTail :: Maybe Text -> Seq.Seq B.Builder -> Seq.Seq B.Builder
handleTail Nothing = insertCloseParen
handleTail (Just t) =
(Seq.|> (B.fromString " . " <> B.fromText t <> B.fromString ")"))
insertCloseParen :: Seq.Seq B.Builder -> Seq.Seq B.Builder
insertCloseParen s = case Seq.viewr s of
Seq.EmptyR -> Seq.singleton (B.fromString ")")
xs Seq.:> x -> xs Seq.|> (x <> B.fromString ")")
buildUnwords sq =
case Seq.viewl sq of
Seq.EmptyL -> mempty
t Seq.:< ts -> t <> F.foldMap (\ x -> B.fromString " " <> x) ts
pTail Nothing = B.fromString ")"
pTail (Just t) = B.fromString " . " <> B.fromText t <> B.fromString ")"
ppBasic (IAtom t) = Just (B.fromText t)
ppBasic (IEmpty) = Just (B.fromString "()")
ppBasic _ = Nothing
setFromCarrier :: (c -> b) -> SExprPrinter a b -> SExprPrinter a c
setFromCarrier fc pr = pr { fromCarrier = fromCarrier pr . fc }
setMaxWidth :: Int -> SExprPrinter atom carrier -> SExprPrinter atom carrier
setMaxWidth n pr = pr { maxWidth = Just n }
removeMaxWidth :: SExprPrinter atom carrier -> SExprPrinter atom carrier
removeMaxWidth pr = pr { maxWidth = Nothing }
setIndentAmount :: Int -> SExprPrinter atom carrier -> SExprPrinter atom carrier
setIndentAmount n pr = pr { indentAmount = n }
setIndentStrategy :: (SExpr atom -> Indent) -> SExprPrinter atom carrier -> SExprPrinter atom carrier
setIndentStrategy st pr = pr { swingIndent = st }
indent :: Int -> B.Builder -> B.Builder
indent n ts = B.fromText (T.replicate n " ") <> ts
joinLinesS :: Seq.Seq B.Builder -> B.Builder
joinLinesS s = case Seq.viewl s of
Seq.EmptyL -> ""
t Seq.:< ts
| F.null ts -> t
| otherwise -> t <> B.fromString "\n" <> joinLinesS ts
unwordsS :: Seq.Seq B.Builder -> B.Builder
unwordsS s = case Seq.viewl s of
Seq.EmptyL -> ""
t Seq.:< ts
| F.null ts -> t
| otherwise -> t <> " " <> joinLinesS ts
indentAllS :: Int -> Seq.Seq B.Builder -> B.Builder
indentAllS n = ("\n" <>) . joinLinesS . fmap (indent n)
indentSubsequentS :: Int -> Seq.Seq B.Builder -> B.Builder
indentSubsequentS n s = case Seq.viewl s of
Seq.EmptyL -> ""
t Seq.:< ts
| F.null ts -> t
| otherwise -> joinLinesS (t Seq.<| fmap (indent n) ts)
prettyPrintSExpr :: SExprPrinter a (SExpr a) -> SExpr a -> TL.Text
prettyPrintSExpr pr@SExprPrinter { .. } expr = case maxWidth of
Nothing
| indentPrint -> unboundIndentPrintSExpr pr (fromCarrier expr)
| otherwise -> flatPrintSExpr (fmap atomPrinter (fromCarrier expr))
Just w -> indentPrintSExpr' w pr expr
indentPrintSExpr' :: Int -> SExprPrinter a (SExpr a) -> SExpr a -> TL.Text
indentPrintSExpr' maxAmt pr@SExprPrinter { .. } = B.toLazyText . pp 0 . toIntermediate pr
where
pp _ IEmpty = B.fromString "()"
pp _ (IAtom t) = B.fromText t
pp ind (IList i sz h values end) =
B.fromString "(" <> hd <> body <> tl <> B.fromString ")"
where
tl = case end of
Nothing -> mempty
Just x -> B.fromString " . " <> B.fromText x
hd = pp (ind+1) h
headWidth = sizeSum (sizeOf h)
indented =
case i of
SwingAfter n ->
let (l, ls) = Seq.splitAt n values
t = unwordsS (fmap (pp (ind+1)) l)
ts = indentAllS (ind + indentAmount)
(fmap (pp (ind + indentAmount)) ls)
in t <> ts
Swing ->
indentAllS (ind + indentAmount)
(fmap (pp (ind + indentAmount)) values)
Align ->
indentSubsequentS (ind + headWidth + 1)
(fmap (pp (ind + headWidth + 1)) values)
body
| length values == 0 = mempty
| sizeSum sz + ind > maxAmt = B.fromString " " <> indented
| otherwise =
B.fromString " " <> unwordsS (fmap (pp (ind + 1)) values)
flatPrintSExpr :: SExpr Text -> TL.Text
flatPrintSExpr = B.toLazyText . pHead
where
pHead (SCons x xs) =
B.fromString "(" <> pHead x <> pTail xs
pHead (SAtom t) =
B.fromText t
pHead SNil =
B.fromString "()"
pTail (SCons x xs) =
B.fromString " " <> pHead x <> pTail xs
pTail (SAtom t) =
B.fromString " . " <> B.fromText t <> B.fromString ")"
pTail SNil =
B.fromString ")"
encodeOne :: SExprPrinter atom carrier -> carrier -> Text
encodeOne s@(SExprPrinter { .. }) =
TL.toStrict . prettyPrintSExpr (s { fromCarrier = id }) . fromCarrier
encode :: SExprPrinter atom carrier -> [carrier] -> Text
encode spec =
T.intercalate "\n\n" . map (encodeOne spec)
encodeOneLazy :: SExprPrinter atom carrier -> carrier -> TL.Text
encodeOneLazy s@(SExprPrinter { .. }) =
prettyPrintSExpr (s { fromCarrier = id }) . fromCarrier
encodeLazy :: SExprPrinter atom carrier -> [carrier] -> TL.Text
encodeLazy spec = TL.intercalate "\n\n" . map (encodeOneLazy spec)