{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
#include "version-compatibility-macros.h"
module Data.Text.Prettyprint.Doc.Render.Util.StackMachine (
renderSimplyDecorated,
renderSimplyDecoratedA,
StackMachine,
execStackMachine,
pushStyle,
unsafePopStyle,
unsafePeekStyle,
writeOutput,
) where
import Control.Applicative
import Data.Text (Text)
import qualified Data.Text as T
import Data.Text.Prettyprint.Doc (SimpleDocStream (..))
import Data.Text.Prettyprint.Doc.Render.Util.Panic
#if !(SEMIGROUP_MONOID_SUPERCLASS)
import Data.Monoid
#endif
renderSimplyDecorated
:: Monoid out
=> (Text -> out)
-> (ann -> out)
-> (ann -> out)
-> SimpleDocStream ann
-> out
renderSimplyDecorated text push pop = go []
where
go _ SFail = panicUncaughtFail
go [] SEmpty = mempty
go (_:_) SEmpty = panicInputNotFullyConsumed
go stack (SChar c rest) = text (T.singleton c) <> go stack rest
go stack (SText _l t rest) = text t <> go stack rest
go stack (SLine i rest) = text (T.singleton '\n') <> text (T.replicate i " ") <> go stack rest
go stack (SAnnPush ann rest) = push ann <> go (ann : stack) rest
go (ann:stack) (SAnnPop rest) = pop ann <> go stack rest
go [] SAnnPop{} = panicUnpairedPop
{-# INLINE renderSimplyDecorated #-}
renderSimplyDecoratedA
:: (Applicative f, Monoid out)
=> (Text -> f out)
-> (ann -> f out)
-> (ann -> f out)
-> SimpleDocStream ann
-> f out
renderSimplyDecoratedA text push pop = go []
where
go _ SFail = panicUncaughtFail
go [] SEmpty = pure mempty
go (_:_) SEmpty = panicInputNotFullyConsumed
go stack (SChar c rest) = text (T.singleton c) <++> go stack rest
go stack (SText _l t rest) = text t <++> go stack rest
go stack (SLine i rest) = text (T.singleton '\n') <++> text (T.replicate i " ") <++> go stack rest
go stack (SAnnPush ann rest) = push ann <++> go (ann : stack) rest
go (ann:stack) (SAnnPop rest) = pop ann <++> go stack rest
go [] SAnnPop{} = panicUnpairedPop
(<++>) = liftA2 mappend
{-# INLINE renderSimplyDecoratedA #-}
newtype StackMachine output style a = StackMachine ([style] -> (a, output, [style]))
{-# DEPRECATED StackMachine "Writing your own stack machine is probably more efficient and customizable; also consider using »renderSimplyDecorated(A)« instead" #-}
instance Functor (StackMachine output style) where
fmap f (StackMachine r) = StackMachine (\s ->
let (x1, w1, s1) = r s
in (f x1, w1, s1))
instance Monoid output => Applicative (StackMachine output style) where
pure x = StackMachine (\s -> (x, mempty, s))
StackMachine f <*> StackMachine x = StackMachine (\s ->
let (f1, w1, s1) = f s
(x2, w2, s2) = x s1
!w12 = w1 <> w2
in (f1 x2, w12, s2))
instance Monoid output => Monad (StackMachine output style) where
#if !(APPLICATIVE_MONAD)
return = pure
#endif
StackMachine r >>= f = StackMachine (\s ->
let (x1, w1, s1) = r s
StackMachine r1 = f x1
(x2, w2, s2) = r1 s1
!w12 = w1 <> w2
in (x2, w12, s2))
pushStyle :: Monoid output => style -> StackMachine output style ()
pushStyle style = StackMachine (\styles -> ((), mempty, style : styles))
unsafePopStyle :: Monoid output => StackMachine output style style
unsafePopStyle = StackMachine (\stack -> case stack of
x:xs -> (x, mempty, xs)
[] -> panicPoppedEmpty )
unsafePeekStyle :: Monoid output => StackMachine output style style
unsafePeekStyle = StackMachine (\styles -> case styles of
x:_ -> (x, mempty, styles)
[] -> panicPeekedEmpty )
writeOutput :: output -> StackMachine output style ()
writeOutput w = StackMachine (\styles -> ((), w, styles))
execStackMachine :: [styles] -> StackMachine output styles a -> (output, [styles])
execStackMachine styles (StackMachine r) = let (_, w, s) = r styles in (w, s)