{-# LANGUAGE FlexibleInstances, DefaultSignatures, UndecidableInstances
    , OverloadedStrings #-}
module Text.ANTLR.Pretty where
import Control.Monad.Trans.State.Lazy
import qualified Data.Map.Strict as M
import Data.Data (toConstr, Data(..))
import qualified Data.Text as T
data PState = PState
  { indent   :: Int     
  , vis_chrs :: Int     
  , str :: T.Text       
  , columns_soft :: Int 
  , columns_hard :: Int 
  , curr_col :: Int     
  , curr_row :: Int     
  }
type PrettyM val = State PState val
type Pretty = PrettyM ()
class Prettify t where
  {-# MINIMAL prettify #-}
  
  prettify :: t -> Pretty
  default prettify :: (Show t) => t -> Pretty
  prettify = rshow
  
  prettifyList :: [t] -> Pretty
  prettifyList = prettifyList_
initPState = PState
  { indent       = 0   
  , vis_chrs     = 0   
  , str          = T.empty 
  , columns_soft = 100  
  , columns_hard = 120  
  , curr_col     = 0   
  , curr_row     = 0   
  }
pLine :: T.Text -> Pretty
pLine s = do
  pStr s
  _pNewLine
pStr' :: String -> Pretty
pStr' = pStr . T.pack
pStr :: T.Text -> Pretty
pStr s = do
  pstate <- get
  _doIf _pNewLine (T.length s + curr_col pstate > columns_hard pstate && curr_col pstate /= 0)
  pstate <- get
  _doIf _pIndent  (curr_col pstate == 0 && indent pstate > 0)
  pstate <- get
  put $ pstate
    { str = T.append (str pstate) s
    , curr_col = (curr_col pstate) + T.length s
    }
  pstate <- get
  _doIf _pNewLine (curr_col pstate > columns_soft pstate)
pChr :: Char -> Pretty
pChr c = pStr $ T.singleton c
_doIf fncn True  = fncn
_doIf fncn False = return ()
_pIndent :: Pretty
_pIndent = do
  pstate <- get
  put $ pstate
    { str      = str pstate `T.append` T.replicate (indent pstate) (T.singleton ' ')
    , curr_col = curr_col pstate + indent pstate
    , vis_chrs = vis_chrs pstate + indent pstate
    }
_pNewLine :: Pretty
_pNewLine = do
  pstate <- get
  put $ pstate
    { str = T.snoc (str pstate) '\n'
    , curr_col = 0
    , curr_row = curr_row pstate + 1
    }
pshow :: (Prettify t) => t -> T.Text
pshow t = str $ execState (prettify t) initPState
pshow' :: (Prettify t) => t -> String
pshow' = T.unpack . pshow
pshowIndent :: (Prettify t) => Int -> t -> T.Text
pshowIndent i t = str $ execState (prettify t) $ initPState { indent = i }
rshow :: (Show t) => t -> Pretty
rshow t = do
  pstate <- get
  let s = show t
  put $ pstate
    { str      = str pstate `T.append` T.pack s
    , curr_row = curr_row pstate + (T.length . T.filter (== '\n')) (T.pack s)
    , curr_col = curr_col pstate 
    }
pParens fncn = do
  pChr '('
  fncn
  pChr ')'
incrIndent :: Int -> Pretty
incrIndent n = do
  pstate <- get
  put $ pstate { indent = indent pstate + n }
setIndent :: Int -> Pretty
setIndent n = do
  pstate <- get
  put $ pstate { indent = n }
pCount :: (Prettify v) => v -> PrettyM Int
pCount v = do
  i0 <- indent <$> get
  prettify v
  i1 <- indent <$> get
  return (i1 - i0)
pListLines :: (Prettify v) => [v] -> Pretty
pListLines vs = do
  pStr $ T.pack "[ "
  col0 <- curr_col <$> get
  i0   <- indent   <$> get
  setIndent (col0 - 2)
  sepBy (pLine T.empty >> (pStr $ T.pack ", ")) (map prettify vs)
  pLine T.empty >> pChr ']'
  setIndent i0 
instance (Prettify k, Prettify v) => Prettify (M.Map k v) where
  prettify m = do
    
    pStr "Map: "; incrIndent 5
    prettify $ M.toList m 
    incrIndent (-5)
instance (Prettify v) => Prettify (Maybe v) where
  prettify Nothing  = pStr "Nope"
  prettify (Just v) = pStr "Yep" >> pParens (prettify v)
prettifyList_ [] = pStr "[]"
prettifyList_ vs = do
  pChr '['
  sepBy (pStr ", ") (map prettify vs)
  pChr ']'
instance (Prettify v) => Prettify [v] where
  prettify = prettifyList
instance (Prettify a, Prettify b) => Prettify (a,b) where
  prettify (a,b) = do
    pChr '('
    prettify a
    pChr ','
    prettify b
    pChr ')'
instance (Prettify a, Prettify b, Prettify c) => Prettify (a,b,c) where
  prettify (a,b,c) = do
    pChr '('
    prettify a
    pChr ','
    prettify b
    pChr ','
    prettify c
    pChr ')'
instance (Prettify a, Prettify b, Prettify c, Prettify d) => Prettify (a,b,c,d) where
  prettify (a,b,c,d) = do
    pChr '('
    prettify a
    pChr ','
    prettify b
    pChr ','
    prettify c
    pChr ','
    prettify d
    pChr ')'
sepBy s [] = return ()
sepBy s (v:vs) = foldl (_sepBy s) v vs
_sepBy s ma mb = ma >> s >> mb
instance Prettify Char where
  prettify = pChr
  prettifyList = pStr . T.pack
instance Prettify () where prettify = rshow
instance Prettify Bool where prettify = rshow
instance Prettify Int where prettify = rshow
instance Prettify Double where prettify = rshow