module Database.PostgreSQL.Simple.ToField
    (
      Action(..)
    , ToField(..)
    , toJSONField
    , inQuotes
    ) where
import Blaze.ByteString.Builder (Builder, fromByteString, toByteString)
import Blaze.ByteString.Builder.Char8 (fromChar)
import Blaze.Text (integral, double, float)
import qualified Data.Aeson as JSON
import Data.ByteString (ByteString)
import Data.Int (Int8, Int16, Int32, Int64)
import Data.List (intersperse)
import Data.Monoid (mappend)
import Data.Time (Day, TimeOfDay, LocalTime, UTCTime, ZonedTime, NominalDiffTime)
import Data.Typeable (Typeable)
import Data.Word (Word, Word8, Word16, Word32, Word64)
import  Database.PostgreSQL.Simple.ToRow
import Database.PostgreSQL.Simple.Types
import qualified Blaze.ByteString.Builder.Char.Utf8 as Utf8
import qualified Data.ByteString as SB
import qualified Data.ByteString.Lazy as LB
import qualified Data.Text as ST
import qualified Data.Text.Encoding as ST
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.Builder as LT
import           Data.UUID   (UUID)
import qualified Data.UUID as UUID
import           Data.Vector (Vector)
import qualified Data.Vector as V
import qualified Database.PostgreSQL.LibPQ as PQ
import           Database.PostgreSQL.Simple.Time
import           Data.Scientific (Scientific)
#if MIN_VERSION_scientific(0,3,0)
import           Data.Text.Lazy.Builder.Scientific (scientificBuilder)
#else
import           Data.Scientific (scientificBuilder)
#endif
data Action =
    Plain Builder
    
    
    
    
  | Escape ByteString
    
    
    
  | EscapeByteA ByteString
    
    
  | EscapeIdentifier ByteString
    
    
    
  | Many [Action]
    
    deriving (Typeable)
instance Show Action where
    show (Plain b)            = "Plain " ++ show (toByteString b)
    show (Escape b)           = "Escape " ++ show b
    show (EscapeByteA b)      = "EscapeByteA " ++ show b
    show (EscapeIdentifier b) = "EscapeIdentifier " ++ show b
    show (Many b)             = "Many " ++ show b
class ToField a where
    toField :: a -> Action
    
instance ToField Action where
    toField a = a
    
instance (ToField a) => ToField (Maybe a) where
    toField Nothing  = renderNull
    toField (Just a) = toField a
    
instance (ToField a) => ToField (In [a]) where
    toField (In []) = Plain $ fromByteString "(null)"
    toField (In xs) = Many $
        Plain (fromChar '(') :
        (intersperse (Plain (fromChar ',')) . map toField $ xs) ++
        [Plain (fromChar ')')]
renderNull :: Action
renderNull = Plain (fromByteString "null")
instance ToField Null where
    toField _ = renderNull
    
instance ToField Default where
    toField _ = Plain (fromByteString "default")
    
instance ToField Bool where
    toField True  = Plain (fromByteString "true")
    toField False = Plain (fromByteString "false")
    
instance ToField Int8 where
    toField = Plain . integral
    
instance ToField Int16 where
    toField = Plain . integral
    
instance ToField Int32 where
    toField = Plain . integral
    
instance ToField Int where
    toField = Plain . integral
    
instance ToField Int64 where
    toField = Plain . integral
    
instance ToField Integer where
    toField = Plain . integral
    
instance ToField Word8 where
    toField = Plain . integral
    
instance ToField Word16 where
    toField = Plain . integral
    
instance ToField Word32 where
    toField = Plain . integral
    
instance ToField Word where
    toField = Plain . integral
    
instance ToField Word64 where
    toField = Plain . integral
    
instance ToField PQ.Oid where
    toField = Plain . integral . \(PQ.Oid x) -> x
    
instance ToField Float where
    toField v | isNaN v || isInfinite v = Plain (inQuotes (float v))
              | otherwise               = Plain (float v)
    
instance ToField Double where
    toField v | isNaN v || isInfinite v = Plain (inQuotes (double v))
              | otherwise               = Plain (double v)
    
instance ToField Scientific where
    toField x = toField (LT.toLazyText (scientificBuilder x))
    
instance ToField (Binary SB.ByteString) where
    toField (Binary bs) = EscapeByteA bs
    
instance ToField (Binary LB.ByteString) where
    toField (Binary bs) = (EscapeByteA . SB.concat . LB.toChunks) bs
    
instance ToField Identifier where
    toField (Identifier bs) = EscapeIdentifier (ST.encodeUtf8 bs)
    
instance ToField QualifiedIdentifier where
    toField (QualifiedIdentifier (Just s) t) =
        Many [ EscapeIdentifier (ST.encodeUtf8 s)
             , Plain (fromChar '.')
             , EscapeIdentifier (ST.encodeUtf8 t)
             ]
    toField (QualifiedIdentifier Nothing  t) =
               EscapeIdentifier (ST.encodeUtf8 t)
    
instance ToField SB.ByteString where
    toField = Escape
    
instance ToField LB.ByteString where
    toField = toField . SB.concat . LB.toChunks
    
instance ToField ST.Text where
    toField = Escape . ST.encodeUtf8
    
instance ToField [Char] where
    toField = Escape . toByteString . Utf8.fromString
    
instance ToField LT.Text where
    toField = toField . LT.toStrict
    
instance ToField UTCTime where
    toField = Plain . inQuotes . utcTimeToBuilder
    
instance ToField ZonedTime where
    toField = Plain . inQuotes . zonedTimeToBuilder
    
instance ToField LocalTime where
    toField = Plain . inQuotes . localTimeToBuilder
    
instance ToField Day where
    toField = Plain . inQuotes . dayToBuilder
    
instance ToField TimeOfDay where
    toField = Plain . inQuotes . timeOfDayToBuilder
    
instance ToField UTCTimestamp where
    toField = Plain . inQuotes . utcTimestampToBuilder
    
instance ToField ZonedTimestamp where
    toField = Plain . inQuotes . zonedTimestampToBuilder
    
instance ToField LocalTimestamp where
    toField = Plain . inQuotes . localTimestampToBuilder
    
instance ToField Date where
    toField = Plain . inQuotes . dateToBuilder
    
instance ToField NominalDiffTime where
    toField = Plain . inQuotes . nominalDiffTimeToBuilder
    
instance (ToField a) => ToField (PGArray a) where
    toField xs = Many $
        Plain (fromByteString "ARRAY[") :
        (intersperse (Plain (fromChar ',')) . map toField $ fromPGArray xs) ++
        [Plain (fromChar ']')]
        
        
instance (ToField a) => ToField (Vector a) where
    toField = toField . PGArray . V.toList
instance ToField UUID where
    toField = Plain . inQuotes . fromByteString . UUID.toASCIIBytes
instance ToField JSON.Value where
    toField = toField . JSON.encode
toJSONField :: JSON.ToJSON a => a -> Action
toJSONField = toField . JSON.toJSON
inQuotes :: Builder -> Builder
inQuotes b = quote `mappend` b `mappend` quote
  where quote = Utf8.fromChar '\''
interleaveFoldr :: (a -> [b] -> [b]) -> b -> [b] -> [a] -> [b]
interleaveFoldr f b bs as = foldr (\a bs -> b : f a bs) bs as
instance ToRow a => ToField (Values a) where
    toField (Values types rows) =
        case rows of
          []    -> case types of
                     []    -> error norows
                     (_:_) -> values $ typedRow (repeat (lit "null"))
                                                types
                                                [lit " LIMIT 0)"]
          (_:_) -> case types of
                     []    -> values $ untypedRows rows [litC ')']
                     (_:_) -> values $ typedRows rows types [litC ')']
      where
        funcname = "Database.PostgreSQL.Simple.toField :: Values a -> Action"
        norows   = funcname ++ "  either values or types must be non-empty"
        emptyrow = funcname ++ "  each row must contain at least one column"
        lit  = Plain . fromByteString
        litC = Plain . fromChar
        values x = Many (lit "(VALUES ": x)
        typedField :: (Action, QualifiedIdentifier) -> [Action] -> [Action]
        typedField (val,typ) rest = val : lit "::" : toField typ : rest
        typedRow :: [Action] -> [QualifiedIdentifier] -> [Action] -> [Action]
        typedRow (val:vals) (typ:typs) rest =
            litC '(' :
              typedField (val,typ) ( interleaveFoldr
                                        typedField
                                        (litC ',')
                                        (litC ')' : rest)
                                        (zip vals typs)   )
        typedRow _ _ _ = error emptyrow
        untypedRow :: [Action] -> [Action] -> [Action]
        untypedRow (val:vals) rest =
            litC '(' : val :
            interleaveFoldr
                 (:)
                 (litC ',')
                 (litC ')' : rest)
                 vals
        untypedRow _ _ = error emptyrow
        typedRows :: ToRow a => [a] -> [QualifiedIdentifier] -> [Action] -> [Action]
        typedRows [] _ _ = error funcname
        typedRows (val:vals) types rest =
            typedRow (toRow val) types (multiRows vals rest)
        untypedRows :: ToRow a => [a] -> [Action] -> [Action]
        untypedRows [] _ = error funcname
        untypedRows (val:vals) rest =
            untypedRow (toRow val) (multiRows vals rest)
        multiRows :: ToRow a => [a] -> [Action] -> [Action]
        multiRows vals rest = interleaveFoldr
                                (untypedRow . toRow)
                                (litC ',')
                                rest
                                vals