module Data.Aeson.Encode
    ( encode
    
    , encodeToByteStringBuilder
    , encodeToTextBuilder
    
    , fromValue
    ) where
import Data.Aeson.Types (Value(..))
import Data.Monoid (mappend)
import Data.Scientific (FPFormat(..), Scientific, base10Exponent)
import Data.Text.Lazy.Builder
import Data.Text.Lazy.Builder.Scientific (formatScientificBuilder)
import Numeric (showHex)
import qualified Data.HashMap.Strict as H
import qualified Data.Text as T
import qualified Data.Vector as V
import Data.Aeson.Encode.ByteString (encode, encodeToByteStringBuilder)
encodeToTextBuilder :: Value -> Builder
encodeToTextBuilder =
    go
  where
    go Null       =  "null"
    go (Bool b)   =  if b then "true" else "false"
    go (Number s) =  fromScientific s
    go (String s) =  string s
    go (Array v)
        | V.null v =  "[]"
        | otherwise = 
                      singleton '[' <>
                      go (V.unsafeHead v) <>
                      V.foldr f (singleton ']') (V.unsafeTail v)
      where f a z = singleton ',' <> go a <> z
    go (Object m) = 
        case H.toList m of
          (x:xs) -> singleton '{' <> one x <> foldr f (singleton '}') xs
          _      -> "{}"
      where f a z     = singleton ',' <> one a <> z
            one (k,v) = string k <> singleton ':' <> go v
fromValue :: Value -> Builder
fromValue = encodeToTextBuilder
string :: T.Text -> Builder
string s =  singleton '"' <> quote s <> singleton '"'
  where
    quote q = case T.uncons t of
                Nothing      -> fromText h
                Just (!c,t') -> fromText h <> escape c <> quote t'
        where (h,t) =  T.break isEscape q
    isEscape c = c == '\"' ||
                 c == '\\' ||
                 c < '\x20'
    escape '\"' = "\\\""
    escape '\\' = "\\\\"
    escape '\n' = "\\n"
    escape '\r' = "\\r"
    escape '\t' = "\\t"
    escape c
        | c < '\x20' = fromString $ "\\u" ++ replicate (4  length h) '0' ++ h
        | otherwise  = singleton c
        where h = showHex (fromEnum c) ""
fromScientific :: Scientific -> Builder
fromScientific s = formatScientificBuilder format prec s
  where
    (format, prec)
      | base10Exponent s < 0 = (Generic, Nothing)
      | otherwise            = (Fixed,   Just 0)
(<>) :: Builder -> Builder -> Builder
(<>) = mappend
infixr 6 <>