{-# LANGUAGE CPP                #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric      #-}
{-# LANGUAGE OverloadedStrings  #-}
#include "version-compatibility-macros.h"
module Data.Text.Prettyprint.Doc.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 Data.Text.Prettyprint.Doc
import Data.Text.Prettyprint.Doc.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 text renderAnn = go
  where
    go = \sdt -> case sdt of
        STEmpty        -> mempty
        STChar c       -> text (T.singleton c)
        STText _ t     -> text t
        STLine i       -> text (T.singleton '\n' <> T.replicate i " ")
        STAnn ann rest -> renderAnn ann (go rest)
        STConcat xs    -> foldMap go xs
{-# INLINE renderSimplyDecorated #-}
renderSimplyDecoratedA
    :: (Applicative f, Monoid out)
    => (Text -> f out)         
    -> (ann -> f out -> f out) 
    -> SimpleDocTree ann
    -> f out
renderSimplyDecoratedA text renderAnn = go
  where
    go = \sdt -> case sdt of
        STEmpty        -> pure mempty
        STChar c       -> text (T.singleton c)
        STText _ t     -> text t
        STLine i       -> text (T.singleton '\n' <> T.replicate i " ")
        STAnn ann rest -> renderAnn ann (go rest)
        STConcat xs    -> fmap mconcat (traverse go xs)
{-# INLINE renderSimplyDecoratedA #-}
newtype UniqueParser s a = UniqueParser { runParser :: s -> Maybe (a, s) }
  deriving Typeable
instance Functor (UniqueParser s) where
    fmap f (UniqueParser mx) = UniqueParser (\s ->
        fmap (\(x,s') -> (f x, s')) (mx s))
instance Applicative (UniqueParser s) where
    pure x = UniqueParser (\rest -> Just (x, rest))
    UniqueParser mf <*> UniqueParser mx = UniqueParser (\s -> do
        (f, s') <- mf s
        (x, s'') <- mx s'
        pure (f x, s'') )
instance Monad (UniqueParser s) where
    UniqueParser p >>= f = UniqueParser (\s -> do
        (a', s') <- p s
        let UniqueParser p' = f a'
        p' s' )
#if !(APPLICATIVE_MONAD)
    return = pure
#endif
#if FAIL_IN_MONAD
    fail = Fail.fail
#endif
instance Fail.MonadFail (UniqueParser s) where
    fail _err = empty
instance Alternative (UniqueParser s) where
    empty = UniqueParser (const empty)
    UniqueParser p <|> UniqueParser q = UniqueParser (\s -> p s <|> q s)
data SimpleDocTok ann
    = TokEmpty
    | TokChar Char
    | TokText !Int Text
    | TokLine Int
    | TokAnnPush ann
    | TokAnnPop
    deriving (Eq, Ord, Show, Typeable)
data SimpleDocTree ann
    = STEmpty
    | STChar Char
    
    
    
    | STText !Int Text
    
    | STLine !Int
    
    | STAnn ann (SimpleDocTree ann)
    
    | STConcat [SimpleDocTree ann]
    deriving (Eq, Ord, Show, Generic, Typeable)
instance Functor SimpleDocTree where
    fmap = reAnnotateST
nextToken :: UniqueParser (SimpleDocStream ann) (SimpleDocTok ann)
nextToken = UniqueParser (\sds -> case sds of
    SFail             -> panicUncaughtFail
    SEmpty            -> empty
    SChar c rest      -> Just (TokChar c      , rest)
    SText l t rest    -> Just (TokText l t    , rest)
    SLine i rest      -> Just (TokLine i      , rest)
    SAnnPush ann rest -> Just (TokAnnPush ann , rest)
    SAnnPop rest      -> Just (TokAnnPop      , rest) )
sdocToTreeParser :: UniqueParser (SimpleDocStream ann) (SimpleDocTree ann)
sdocToTreeParser = fmap wrap (many contentPiece)
  where
    wrap :: [SimpleDocTree ann] -> SimpleDocTree ann
    wrap = \sdts -> case sdts of
        []  -> STEmpty
        [x] -> x
        xs  -> STConcat xs
    contentPiece = nextToken >>= \tok -> case tok of
        TokEmpty       -> pure STEmpty
        TokChar c      -> pure (STChar c)
        TokText l t    -> pure (STText l t)
        TokLine i      -> pure (STLine i)
        TokAnnPop      -> empty
        TokAnnPush ann -> do annotatedContents <- sdocToTreeParser
                             TokAnnPop <- nextToken
                             pure (STAnn ann annotatedContents)
treeForm :: SimpleDocStream ann -> SimpleDocTree ann
treeForm sdoc = case runParser sdocToTreeParser sdoc of
    Nothing               -> panicSimpleDocTreeConversionFailed
    Just (sdoct, SEmpty)  -> sdoct
    Just (_, _unconsumed) -> panicInputNotFullyConsumed
unAnnotateST :: SimpleDocTree ann -> SimpleDocTree xxx
unAnnotateST = alterAnnotationsST (const [])
reAnnotateST :: (ann -> ann') -> SimpleDocTree ann -> SimpleDocTree ann'
reAnnotateST f = alterAnnotationsST (pure . f)
alterAnnotationsST :: (ann -> [ann']) -> SimpleDocTree ann -> SimpleDocTree ann'
alterAnnotationsST re = go
  where
    go = \sdt -> case sdt of
        STEmpty        -> STEmpty
        STChar c       -> STChar c
        STText l t     -> STText l t
        STLine i       -> STLine i
        STConcat xs    -> STConcat (map go xs)
        STAnn ann rest -> Prelude.foldr STAnn (go rest) (re ann)
instance Foldable SimpleDocTree where
    foldMap f = go
      where
        go = \sdt -> case sdt of
            STEmpty        -> mempty
            STChar _       -> mempty
            STText _ _     -> mempty
            STLine _       -> mempty
            STAnn ann rest -> f ann `mappend` go rest
            STConcat xs    -> mconcat (map go xs)
instance Traversable SimpleDocTree where
    traverse f = go
      where
        go = \sdt -> case sdt of
            STEmpty        -> pure STEmpty
            STChar c       -> pure (STChar c)
            STText l t     -> pure (STText l t)
            STLine i       -> pure (STLine i)
            STAnn ann rest -> STAnn <$> f ann <*> go rest
            STConcat xs    -> STConcat <$> traverse go xs