{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
module Text.Pretty.Simple.Internal.ExprToOutput
  where
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative
#endif
import Control.Monad (when)
import Control.Monad.State (MonadState, execState, gets, modify)
import Data.Data (Data)
import Data.Foldable (traverse_)
import Data.Monoid ((<>))
import Data.Sequence (Seq, fromList, singleton)
import Data.List (intersperse)
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Text.Pretty.Simple.Internal.Expr (CommaSeparated(..), Expr(..))
import Text.Pretty.Simple.Internal.Output
       (NestLevel(..), Output(..), OutputType(..), unNestLevel)
newtype LineNum = LineNum { unLineNum :: Int }
  deriving (Data, Eq, Generic, Num, Ord, Read, Show, Typeable)
data PrinterState = PrinterState
  { currLine :: {-# UNPACK #-} !LineNum
  , nestLevel :: {-# UNPACK #-} !NestLevel
  , outputList :: !(Seq Output)
  } deriving (Eq, Data, Generic, Show, Typeable)
printerState :: LineNum -> NestLevel -> Seq Output -> PrinterState
printerState currLineNum nestNum output =
  PrinterState
  { currLine = currLineNum
  , nestLevel = nestNum
  , outputList = output
  }
addToOutputList
  :: MonadState PrinterState m
  => Seq Output -> m ()
addToOutputList output =
  modify
    (\printState ->
       printState {outputList = outputList printState `mappend` output})
addOutput
  :: MonadState PrinterState m
  => OutputType -> m ()
addOutput outputType = do
  nest <- gets nestLevel
  let output = Output nest outputType
  
  addToOutputList $ singleton output
addOutputs
  :: MonadState PrinterState m
  => Seq OutputType -> m ()
addOutputs outputTypes = do
  nest <- gets nestLevel
  let outputs = Output nest <$> outputTypes
  
  addToOutputList outputs
initPrinterState :: PrinterState
initPrinterState = printerState 0 (-1) []
putSurroundExpr
  :: MonadState PrinterState m
  => OutputType
  -> OutputType
  -> CommaSeparated [Expr] 
  -> m ()
putSurroundExpr startOutputType endOutputType (CommaSeparated []) = do
  addToNestLevel 1
  addOutputs [startOutputType, endOutputType]
  addToNestLevel (-1)
putSurroundExpr startOutputType endOutputType (CommaSeparated [exprs]) = do
  addToNestLevel 1
  let isExprsMultiLine = or $ map isMultiLine exprs
  when isExprsMultiLine $ do
      newLineAndDoIndent
  addOutputs [startOutputType, OutputOther " "]
  traverse_ putExpression exprs
  if isExprsMultiLine
    then do
      newLineAndDoIndent
    else addOutput $ OutputOther " "
  addOutput endOutputType
  addToNestLevel (-1)
  where
    isMultiLine (Brackets commaSeparated) = isMultiLine' commaSeparated
    isMultiLine (Braces commaSeparated) = isMultiLine' commaSeparated
    isMultiLine (Parens commaSeparated) = isMultiLine' commaSeparated
    isMultiLine _ = False
    isMultiLine' (CommaSeparated []) = False
    isMultiLine' (CommaSeparated [exprs']) = or $ map isMultiLine exprs'
    isMultiLine' _ = True
putSurroundExpr startOutputType endOutputType commaSeparated = do
  addToNestLevel 1
  newLineAndDoIndent
  addOutputs [startOutputType, OutputOther " "]
  putCommaSep commaSeparated
  newLineAndDoIndent
  addOutput endOutputType
  addToNestLevel (-1)
  addOutput $ OutputOther " "
putCommaSep
  :: forall m.
     MonadState PrinterState m
  => CommaSeparated [Expr] -> m ()
putCommaSep (CommaSeparated expressionsList) =
  sequence_ $ intersperse putComma evaledExpressionList
  where
    evaledExpressionList :: [m ()]
    evaledExpressionList =
      traverse_ putExpression <$> expressionsList
putComma
  :: MonadState PrinterState m
  => m ()
putComma = do
  newLineAndDoIndent
  addOutputs [OutputComma, OutputOther " "]
howManyLines :: [Expr] -> LineNum
howManyLines = currLine . runInitPrinterState
doIndent :: MonadState PrinterState m => m ()
doIndent = do
  nest <- gets $ unNestLevel . nestLevel
  addOutputs . fromList $ replicate nest OutputIndent
newLine
  :: MonadState PrinterState m
  => m ()
newLine = do
  addOutput OutputNewLine
  addToCurrentLine 1
newLineAndDoIndent
  :: MonadState PrinterState m
  => m ()
newLineAndDoIndent = newLine >> doIndent
addToNestLevel
  :: MonadState PrinterState m
  => NestLevel -> m ()
addToNestLevel diff =
  modify (\printState -> printState {nestLevel = nestLevel printState + diff})
addToCurrentLine
  :: MonadState PrinterState m
  => LineNum -> m ()
addToCurrentLine diff =
  modify (\printState -> printState {currLine = currLine printState + diff})
putExpression :: MonadState PrinterState m => Expr -> m ()
putExpression (Brackets commaSeparated) = do
  putSurroundExpr OutputOpenBracket OutputCloseBracket commaSeparated
putExpression (Braces commaSeparated) = do
  putSurroundExpr OutputOpenBrace OutputCloseBrace commaSeparated
putExpression (Parens commaSeparated) = do
  putSurroundExpr OutputOpenParen OutputCloseParen commaSeparated
putExpression (StringLit string) = do
  nest <- gets nestLevel
  when (nest < 0) $ addToNestLevel 1
  addOutput $ OutputStringLit string
putExpression (Other string) = do
  nest <- gets nestLevel
  when (nest < 0) $ addToNestLevel 1
  addOutput $ OutputOther string
runPrinterState :: PrinterState -> [Expr] -> PrinterState
runPrinterState initState expressions =
  execState (traverse_ putExpression expressions) initState
runInitPrinterState :: [Expr] -> PrinterState
runInitPrinterState = runPrinterState initPrinterState
expressionsToOutputs :: [Expr] -> Seq Output
expressionsToOutputs =
  outputList . runInitPrinterState . modificationsExprList
modificationsExprList :: [Expr] -> [Expr]
modificationsExprList = removeEmptyInnerCommaSeparatedExprList
removeEmptyInnerCommaSeparatedExprList :: [Expr] -> [Expr]
removeEmptyInnerCommaSeparatedExprList = fmap removeEmptyInnerCommaSeparatedExpr
removeEmptyInnerCommaSeparatedExpr :: Expr -> Expr
removeEmptyInnerCommaSeparatedExpr (Brackets commaSeparated) =
  Brackets $ removeEmptyInnerCommaSeparated commaSeparated
removeEmptyInnerCommaSeparatedExpr (Braces commaSeparated) =
  Braces $ removeEmptyInnerCommaSeparated commaSeparated
removeEmptyInnerCommaSeparatedExpr (Parens commaSeparated) =
  Parens $ removeEmptyInnerCommaSeparated commaSeparated
removeEmptyInnerCommaSeparatedExpr other = other
removeEmptyInnerCommaSeparated :: CommaSeparated [Expr] -> CommaSeparated [Expr]
removeEmptyInnerCommaSeparated (CommaSeparated commaSeps) =
  CommaSeparated . fmap removeEmptyInnerCommaSeparatedExprList $
  removeEmptyList commaSeps
removeEmptyList :: forall a . [[a]] -> [[a]]
removeEmptyList = foldl f []
  where
    f :: [[a]] -> [a] -> [[a]]
    f accum [] = accum
    f accum a = accum <> [a]