{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
#include "version-compatibility-macros.h"
module Prettyprinter.Render.Util.SimpleDocTree (
SimpleDocTree(..),
treeForm,
unAnnotateST,
reAnnotateST,
alterAnnotationsST,
renderSimplyDecorated,
renderSimplyDecoratedA,
) where
import Control.Applicative
import Data.Text (Text)
import qualified Data.Text as T
import Data.Typeable (Typeable)
import GHC.Generics
import Prettyprinter
import Prettyprinter.Internal
import Prettyprinter.Render.Util.Panic
import qualified Control.Monad.Fail as Fail
#if !(MONOID_IN_PRELUDE)
import Data.Monoid (Monoid (..))
#endif
#if !(FOLDABLE_TRAVERSABLE_IN_PRELUDE)
import Data.Foldable (Foldable (..))
import Data.Traversable (Traversable (..))
#endif
renderSimplyDecorated
:: Monoid out
=> (Text -> out)
-> (ann -> out -> out)
-> SimpleDocTree ann
-> out
renderSimplyDecorated :: forall out ann.
Monoid out =>
(Text -> out) -> (ann -> out -> out) -> SimpleDocTree ann -> out
renderSimplyDecorated Text -> out
text ann -> out -> out
renderAnn = SimpleDocTree ann -> out
go
where
go :: SimpleDocTree ann -> out
go = \SimpleDocTree ann
sdt -> case SimpleDocTree ann
sdt of
SimpleDocTree ann
STEmpty -> forall a. Monoid a => a
mempty
STChar Char
c -> Text -> out
text (Char -> Text
T.singleton Char
c)
STText Int
_ Text
t -> Text -> out
text Text
t
STLine Int
i -> Text -> out
text (Char -> Text
T.singleton Char
'\n') forall a. Monoid a => a -> a -> a
`mappend` Text -> out
text (Int -> Text
textSpaces Int
i)
STAnn ann
ann SimpleDocTree ann
rest -> ann -> out -> out
renderAnn ann
ann (SimpleDocTree ann -> out
go SimpleDocTree ann
rest)
STConcat [SimpleDocTree ann]
xs -> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap SimpleDocTree ann -> out
go [SimpleDocTree ann]
xs
{-# INLINE renderSimplyDecorated #-}
renderSimplyDecoratedA
:: (Applicative f, Monoid out)
=> (Text -> f out)
-> (ann -> f out -> f out)
-> SimpleDocTree ann
-> f out
renderSimplyDecoratedA :: forall (f :: * -> *) out ann.
(Applicative f, Monoid out) =>
(Text -> f out)
-> (ann -> f out -> f out) -> SimpleDocTree ann -> f out
renderSimplyDecoratedA Text -> f out
text ann -> f out -> f out
renderAnn = SimpleDocTree ann -> f out
go
where
go :: SimpleDocTree ann -> f out
go = \SimpleDocTree ann
sdt -> case SimpleDocTree ann
sdt of
SimpleDocTree ann
STEmpty -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Monoid a => a
mempty
STChar Char
c -> Text -> f out
text (Char -> Text
T.singleton Char
c)
STText Int
_ Text
t -> Text -> f out
text Text
t
STLine Int
i -> Text -> f out
text (Char -> Text -> Text
T.cons Char
'\n' (Int -> Text
textSpaces Int
i))
STAnn ann
ann SimpleDocTree ann
rest -> ann -> f out -> f out
renderAnn ann
ann (SimpleDocTree ann -> f out
go SimpleDocTree ann
rest)
STConcat [SimpleDocTree ann]
xs -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Monoid a => [a] -> a
mconcat (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse SimpleDocTree ann -> f out
go [SimpleDocTree ann]
xs)
{-# INLINE renderSimplyDecoratedA #-}
newtype UniqueParser s a = UniqueParser { forall s a. UniqueParser s a -> s -> Maybe (a, s)
runParser :: s -> Maybe (a, s) }
deriving Typeable
instance Functor (UniqueParser s) where
fmap :: forall a b. (a -> b) -> UniqueParser s a -> UniqueParser s b
fmap a -> b
f (UniqueParser s -> Maybe (a, s)
mx) = forall s a. (s -> Maybe (a, s)) -> UniqueParser s a
UniqueParser (\s
s ->
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(a
x,s
s') -> (a -> b
f a
x, s
s')) (s -> Maybe (a, s)
mx s
s))
instance Applicative (UniqueParser s) where
pure :: forall a. a -> UniqueParser s a
pure a
x = forall s a. (s -> Maybe (a, s)) -> UniqueParser s a
UniqueParser (\s
rest -> forall a. a -> Maybe a
Just (a
x, s
rest))
UniqueParser s -> Maybe (a -> b, s)
mf <*> :: forall a b.
UniqueParser s (a -> b) -> UniqueParser s a -> UniqueParser s b
<*> UniqueParser s -> Maybe (a, s)
mx = forall s a. (s -> Maybe (a, s)) -> UniqueParser s a
UniqueParser (\s
s -> do
(a -> b
f, s
s') <- s -> Maybe (a -> b, s)
mf s
s
(a
x, s
s'') <- s -> Maybe (a, s)
mx s
s'
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> b
f a
x, s
s'') )
instance Monad (UniqueParser s) where
UniqueParser s -> Maybe (a, s)
p >>= :: forall a b.
UniqueParser s a -> (a -> UniqueParser s b) -> UniqueParser s b
>>= a -> UniqueParser s b
f = forall s a. (s -> Maybe (a, s)) -> UniqueParser s a
UniqueParser (\s
s -> do
(a
a', s
s') <- s -> Maybe (a, s)
p s
s
let UniqueParser s -> Maybe (b, s)
p' = a -> UniqueParser s b
f a
a'
s -> Maybe (b, s)
p' s
s' )
#if !(APPLICATIVE_MONAD)
return = pure
#endif
#if FAIL_IN_MONAD
fail = Fail.fail
#endif
instance Fail.MonadFail (UniqueParser s) where
fail :: forall a. String -> UniqueParser s a
fail String
_err = forall (f :: * -> *) a. Alternative f => f a
empty
instance Alternative (UniqueParser s) where
empty :: forall a. UniqueParser s a
empty = forall s a. (s -> Maybe (a, s)) -> UniqueParser s a
UniqueParser (forall a b. a -> b -> a
const forall (f :: * -> *) a. Alternative f => f a
empty)
UniqueParser s -> Maybe (a, s)
p <|> :: forall a. UniqueParser s a -> UniqueParser s a -> UniqueParser s a
<|> UniqueParser s -> Maybe (a, s)
q = forall s a. (s -> Maybe (a, s)) -> UniqueParser s a
UniqueParser (\s
s -> s -> Maybe (a, s)
p s
s forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> s -> Maybe (a, s)
q s
s)
data SimpleDocTok ann
= TokEmpty
| TokChar Char
| TokText !Int Text
| TokLine Int
| TokAnnPush ann
| TokAnnPop
deriving (SimpleDocTok ann -> SimpleDocTok ann -> Bool
forall ann. Eq ann => SimpleDocTok ann -> SimpleDocTok ann -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SimpleDocTok ann -> SimpleDocTok ann -> Bool
$c/= :: forall ann. Eq ann => SimpleDocTok ann -> SimpleDocTok ann -> Bool
== :: SimpleDocTok ann -> SimpleDocTok ann -> Bool
$c== :: forall ann. Eq ann => SimpleDocTok ann -> SimpleDocTok ann -> Bool
Eq, SimpleDocTok ann -> SimpleDocTok ann -> Ordering
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
forall {ann}. Ord ann => Eq (SimpleDocTok ann)
forall ann. Ord ann => SimpleDocTok ann -> SimpleDocTok ann -> Bool
forall ann.
Ord ann =>
SimpleDocTok ann -> SimpleDocTok ann -> Ordering
forall ann.
Ord ann =>
SimpleDocTok ann -> SimpleDocTok ann -> SimpleDocTok ann
min :: SimpleDocTok ann -> SimpleDocTok ann -> SimpleDocTok ann
$cmin :: forall ann.
Ord ann =>
SimpleDocTok ann -> SimpleDocTok ann -> SimpleDocTok ann
max :: SimpleDocTok ann -> SimpleDocTok ann -> SimpleDocTok ann
$cmax :: forall ann.
Ord ann =>
SimpleDocTok ann -> SimpleDocTok ann -> SimpleDocTok ann
>= :: SimpleDocTok ann -> SimpleDocTok ann -> Bool
$c>= :: forall ann. Ord ann => SimpleDocTok ann -> SimpleDocTok ann -> Bool
> :: SimpleDocTok ann -> SimpleDocTok ann -> Bool
$c> :: forall ann. Ord ann => SimpleDocTok ann -> SimpleDocTok ann -> Bool
<= :: SimpleDocTok ann -> SimpleDocTok ann -> Bool
$c<= :: forall ann. Ord ann => SimpleDocTok ann -> SimpleDocTok ann -> Bool
< :: SimpleDocTok ann -> SimpleDocTok ann -> Bool
$c< :: forall ann. Ord ann => SimpleDocTok ann -> SimpleDocTok ann -> Bool
compare :: SimpleDocTok ann -> SimpleDocTok ann -> Ordering
$ccompare :: forall ann.
Ord ann =>
SimpleDocTok ann -> SimpleDocTok ann -> Ordering
Ord, Int -> SimpleDocTok ann -> ShowS
forall ann. Show ann => Int -> SimpleDocTok ann -> ShowS
forall ann. Show ann => [SimpleDocTok ann] -> ShowS
forall ann. Show ann => SimpleDocTok ann -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SimpleDocTok ann] -> ShowS
$cshowList :: forall ann. Show ann => [SimpleDocTok ann] -> ShowS
show :: SimpleDocTok ann -> String
$cshow :: forall ann. Show ann => SimpleDocTok ann -> String
showsPrec :: Int -> SimpleDocTok ann -> ShowS
$cshowsPrec :: forall ann. Show ann => Int -> SimpleDocTok ann -> ShowS
Show, Typeable)
data SimpleDocTree ann
= STEmpty
| STChar Char
| STText !Int Text
| STLine !Int
| STAnn ann (SimpleDocTree ann)
| STConcat [SimpleDocTree ann]
deriving (SimpleDocTree ann -> SimpleDocTree ann -> Bool
forall ann.
Eq ann =>
SimpleDocTree ann -> SimpleDocTree ann -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SimpleDocTree ann -> SimpleDocTree ann -> Bool
$c/= :: forall ann.
Eq ann =>
SimpleDocTree ann -> SimpleDocTree ann -> Bool
== :: SimpleDocTree ann -> SimpleDocTree ann -> Bool
$c== :: forall ann.
Eq ann =>
SimpleDocTree ann -> SimpleDocTree ann -> Bool
Eq, SimpleDocTree ann -> SimpleDocTree ann -> Ordering
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
forall {ann}. Ord ann => Eq (SimpleDocTree ann)
forall ann.
Ord ann =>
SimpleDocTree ann -> SimpleDocTree ann -> Bool
forall ann.
Ord ann =>
SimpleDocTree ann -> SimpleDocTree ann -> Ordering
forall ann.
Ord ann =>
SimpleDocTree ann -> SimpleDocTree ann -> SimpleDocTree ann
min :: SimpleDocTree ann -> SimpleDocTree ann -> SimpleDocTree ann
$cmin :: forall ann.
Ord ann =>
SimpleDocTree ann -> SimpleDocTree ann -> SimpleDocTree ann
max :: SimpleDocTree ann -> SimpleDocTree ann -> SimpleDocTree ann
$cmax :: forall ann.
Ord ann =>
SimpleDocTree ann -> SimpleDocTree ann -> SimpleDocTree ann
>= :: SimpleDocTree ann -> SimpleDocTree ann -> Bool
$c>= :: forall ann.
Ord ann =>
SimpleDocTree ann -> SimpleDocTree ann -> Bool
> :: SimpleDocTree ann -> SimpleDocTree ann -> Bool
$c> :: forall ann.
Ord ann =>
SimpleDocTree ann -> SimpleDocTree ann -> Bool
<= :: SimpleDocTree ann -> SimpleDocTree ann -> Bool
$c<= :: forall ann.
Ord ann =>
SimpleDocTree ann -> SimpleDocTree ann -> Bool
< :: SimpleDocTree ann -> SimpleDocTree ann -> Bool
$c< :: forall ann.
Ord ann =>
SimpleDocTree ann -> SimpleDocTree ann -> Bool
compare :: SimpleDocTree ann -> SimpleDocTree ann -> Ordering
$ccompare :: forall ann.
Ord ann =>
SimpleDocTree ann -> SimpleDocTree ann -> Ordering
Ord, Int -> SimpleDocTree ann -> ShowS
forall ann. Show ann => Int -> SimpleDocTree ann -> ShowS
forall ann. Show ann => [SimpleDocTree ann] -> ShowS
forall ann. Show ann => SimpleDocTree ann -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SimpleDocTree ann] -> ShowS
$cshowList :: forall ann. Show ann => [SimpleDocTree ann] -> ShowS
show :: SimpleDocTree ann -> String
$cshow :: forall ann. Show ann => SimpleDocTree ann -> String
showsPrec :: Int -> SimpleDocTree ann -> ShowS
$cshowsPrec :: forall ann. Show ann => Int -> SimpleDocTree ann -> ShowS
Show, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall ann x. Rep (SimpleDocTree ann) x -> SimpleDocTree ann
forall ann x. SimpleDocTree ann -> Rep (SimpleDocTree ann) x
$cto :: forall ann x. Rep (SimpleDocTree ann) x -> SimpleDocTree ann
$cfrom :: forall ann x. SimpleDocTree ann -> Rep (SimpleDocTree ann) x
Generic, Typeable)
instance Functor SimpleDocTree where
fmap :: forall a b. (a -> b) -> SimpleDocTree a -> SimpleDocTree b
fmap = forall a b. (a -> b) -> SimpleDocTree a -> SimpleDocTree b
reAnnotateST
nextToken :: UniqueParser (SimpleDocStream ann) (SimpleDocTok ann)
nextToken :: forall ann. UniqueParser (SimpleDocStream ann) (SimpleDocTok ann)
nextToken = forall s a. (s -> Maybe (a, s)) -> UniqueParser s a
UniqueParser (\SimpleDocStream ann
sds -> case SimpleDocStream ann
sds of
SimpleDocStream ann
SFail -> forall void. void
panicUncaughtFail
SimpleDocStream ann
SEmpty -> forall (f :: * -> *) a. Alternative f => f a
empty
SChar Char
c SimpleDocStream ann
rest -> forall a. a -> Maybe a
Just (forall ann. Char -> SimpleDocTok ann
TokChar Char
c , SimpleDocStream ann
rest)
SText Int
l Text
t SimpleDocStream ann
rest -> forall a. a -> Maybe a
Just (forall ann. Int -> Text -> SimpleDocTok ann
TokText Int
l Text
t , SimpleDocStream ann
rest)
SLine Int
i SimpleDocStream ann
rest -> forall a. a -> Maybe a
Just (forall ann. Int -> SimpleDocTok ann
TokLine Int
i , SimpleDocStream ann
rest)
SAnnPush ann
ann SimpleDocStream ann
rest -> forall a. a -> Maybe a
Just (forall ann. ann -> SimpleDocTok ann
TokAnnPush ann
ann , SimpleDocStream ann
rest)
SAnnPop SimpleDocStream ann
rest -> forall a. a -> Maybe a
Just (forall ann. SimpleDocTok ann
TokAnnPop , SimpleDocStream ann
rest) )
sdocToTreeParser :: UniqueParser (SimpleDocStream ann) (SimpleDocTree ann)
sdocToTreeParser :: forall ann. UniqueParser (SimpleDocStream ann) (SimpleDocTree ann)
sdocToTreeParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall ann. [SimpleDocTree ann] -> SimpleDocTree ann
wrap (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall ann. UniqueParser (SimpleDocStream ann) (SimpleDocTree ann)
contentPiece)
where
wrap :: [SimpleDocTree ann] -> SimpleDocTree ann
wrap :: forall ann. [SimpleDocTree ann] -> SimpleDocTree ann
wrap = \[SimpleDocTree ann]
sdts -> case [SimpleDocTree ann]
sdts of
[] -> forall ann. SimpleDocTree ann
STEmpty
[SimpleDocTree ann
x] -> SimpleDocTree ann
x
[SimpleDocTree ann]
xs -> forall ann. [SimpleDocTree ann] -> SimpleDocTree ann
STConcat [SimpleDocTree ann]
xs
contentPiece :: UniqueParser (SimpleDocStream ann) (SimpleDocTree ann)
contentPiece = forall ann. UniqueParser (SimpleDocStream ann) (SimpleDocTok ann)
nextToken forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \SimpleDocTok ann
tok -> case SimpleDocTok ann
tok of
SimpleDocTok ann
TokEmpty -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall ann. SimpleDocTree ann
STEmpty
TokChar Char
c -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall ann. Char -> SimpleDocTree ann
STChar Char
c)
TokText Int
l Text
t -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall ann. Int -> Text -> SimpleDocTree ann
STText Int
l Text
t)
TokLine Int
i -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall ann. Int -> SimpleDocTree ann
STLine Int
i)
SimpleDocTok ann
TokAnnPop -> forall (f :: * -> *) a. Alternative f => f a
empty
TokAnnPush ann
ann -> do SimpleDocTree ann
annotatedContents <- forall ann. UniqueParser (SimpleDocStream ann) (SimpleDocTree ann)
sdocToTreeParser
SimpleDocTok ann
TokAnnPop <- forall ann. UniqueParser (SimpleDocStream ann) (SimpleDocTok ann)
nextToken
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall ann. ann -> SimpleDocTree ann -> SimpleDocTree ann
STAnn ann
ann SimpleDocTree ann
annotatedContents)
treeForm :: SimpleDocStream ann -> SimpleDocTree ann
treeForm :: forall ann. SimpleDocStream ann -> SimpleDocTree ann
treeForm SimpleDocStream ann
sdoc = case forall s a. UniqueParser s a -> s -> Maybe (a, s)
runParser forall ann. UniqueParser (SimpleDocStream ann) (SimpleDocTree ann)
sdocToTreeParser SimpleDocStream ann
sdoc of
Maybe (SimpleDocTree ann, SimpleDocStream ann)
Nothing -> forall void. void
panicSimpleDocTreeConversionFailed
Just (SimpleDocTree ann
sdoct, SimpleDocStream ann
SEmpty) -> SimpleDocTree ann
sdoct
Just (SimpleDocTree ann
_, SimpleDocStream ann
_unconsumed) -> forall void. void
panicInputNotFullyConsumed
unAnnotateST :: SimpleDocTree ann -> SimpleDocTree xxx
unAnnotateST :: forall ann xxx. SimpleDocTree ann -> SimpleDocTree xxx
unAnnotateST = forall ann ann'.
(ann -> [ann']) -> SimpleDocTree ann -> SimpleDocTree ann'
alterAnnotationsST (forall a b. a -> b -> a
const [])
reAnnotateST :: (ann -> ann') -> SimpleDocTree ann -> SimpleDocTree ann'
reAnnotateST :: forall a b. (a -> b) -> SimpleDocTree a -> SimpleDocTree b
reAnnotateST ann -> ann'
f = forall ann ann'.
(ann -> [ann']) -> SimpleDocTree ann -> SimpleDocTree ann'
alterAnnotationsST (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. ann -> ann'
f)
alterAnnotationsST :: (ann -> [ann']) -> SimpleDocTree ann -> SimpleDocTree ann'
alterAnnotationsST :: forall ann ann'.
(ann -> [ann']) -> SimpleDocTree ann -> SimpleDocTree ann'
alterAnnotationsST ann -> [ann']
re = SimpleDocTree ann -> SimpleDocTree ann'
go
where
go :: SimpleDocTree ann -> SimpleDocTree ann'
go = \SimpleDocTree ann
sdt -> case SimpleDocTree ann
sdt of
SimpleDocTree ann
STEmpty -> forall ann. SimpleDocTree ann
STEmpty
STChar Char
c -> forall ann. Char -> SimpleDocTree ann
STChar Char
c
STText Int
l Text
t -> forall ann. Int -> Text -> SimpleDocTree ann
STText Int
l Text
t
STLine Int
i -> forall ann. Int -> SimpleDocTree ann
STLine Int
i
STConcat [SimpleDocTree ann]
xs -> forall ann. [SimpleDocTree ann] -> SimpleDocTree ann
STConcat (forall a b. (a -> b) -> [a] -> [b]
map SimpleDocTree ann -> SimpleDocTree ann'
go [SimpleDocTree ann]
xs)
STAnn ann
ann SimpleDocTree ann
rest -> forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
Prelude.foldr forall ann. ann -> SimpleDocTree ann -> SimpleDocTree ann
STAnn (SimpleDocTree ann -> SimpleDocTree ann'
go SimpleDocTree ann
rest) (ann -> [ann']
re ann
ann)
instance Foldable SimpleDocTree where
foldMap :: forall m a. Monoid m => (a -> m) -> SimpleDocTree a -> m
foldMap a -> m
f = SimpleDocTree a -> m
go
where
go :: SimpleDocTree a -> m
go = \SimpleDocTree a
sdt -> case SimpleDocTree a
sdt of
SimpleDocTree a
STEmpty -> forall a. Monoid a => a
mempty
STChar Char
_ -> forall a. Monoid a => a
mempty
STText Int
_ Text
_ -> forall a. Monoid a => a
mempty
STLine Int
_ -> forall a. Monoid a => a
mempty
STAnn a
ann SimpleDocTree a
rest -> a -> m
f a
ann forall a. Monoid a => a -> a -> a
`mappend` SimpleDocTree a -> m
go SimpleDocTree a
rest
STConcat [SimpleDocTree a]
xs -> forall a. Monoid a => [a] -> a
mconcat (forall a b. (a -> b) -> [a] -> [b]
map SimpleDocTree a -> m
go [SimpleDocTree a]
xs)
instance Traversable SimpleDocTree where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> SimpleDocTree a -> f (SimpleDocTree b)
traverse a -> f b
f = SimpleDocTree a -> f (SimpleDocTree b)
go
where
go :: SimpleDocTree a -> f (SimpleDocTree b)
go = \SimpleDocTree a
sdt -> case SimpleDocTree a
sdt of
SimpleDocTree a
STEmpty -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall ann. SimpleDocTree ann
STEmpty
STChar Char
c -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall ann. Char -> SimpleDocTree ann
STChar Char
c)
STText Int
l Text
t -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall ann. Int -> Text -> SimpleDocTree ann
STText Int
l Text
t)
STLine Int
i -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall ann. Int -> SimpleDocTree ann
STLine Int
i)
STAnn a
ann SimpleDocTree a
rest -> forall ann. ann -> SimpleDocTree ann -> SimpleDocTree ann
STAnn forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
ann forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SimpleDocTree a -> f (SimpleDocTree b)
go SimpleDocTree a
rest
STConcat [SimpleDocTree a]
xs -> forall ann. [SimpleDocTree ann] -> SimpleDocTree ann
STConcat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse SimpleDocTree a -> f (SimpleDocTree b)
go [SimpleDocTree a]
xs