module Database.JSON2.HDBC ( groupWithCol, groupWithNCol)
where
import Database.HDBC.SqlValue
import Database.HDBC.Locale
import Data.JSON2
import Data.JSON2.Instances.Time
import Data.Time
import qualified Data.Map as Map
instance ToJson SqlValue where
toJson (SqlString x) = toJson x
toJson (SqlByteString x) = toJson x
toJson (SqlWord32 x) = toJson x
toJson (SqlWord64 x) = toJson x
toJson (SqlInt32 x) = toJson x
toJson (SqlInt64 x) = toJson x
toJson (SqlInteger x) = toJson x
toJson (SqlChar x) = toJson x
toJson (SqlBool x) = toJson x
toJson (SqlDouble x) = toJson x
toJson (SqlRational x) = toJson x
toJson (SqlLocalDate x) = toJson x
toJson (SqlLocalTimeOfDay x) = toJson x
toJson (SqlZonedLocalTimeOfDay t z) = toJson (t,z)
toJson (SqlLocalTime x) = toJson x
toJson (SqlZonedTime x) = toJson x
toJson (SqlUTCTime x) = toJson x
toJson (SqlDiffTime x) = toJson x
toJson (SqlPOSIXTime x) = toJson x
toJson SqlNull = JNull
groupWithCol :: Json -> Json
groupWithCol (JArray xs) = mergesC $ map objHT xs where
mergesC = foldl mergeC emptyObj
mergeC (JObject x) (JObject y) = JObject $ Map.unionWith (jConcat) x y
jConcat(JArray xs) (JArray ys) = JArray (xs ++ ys)
objHT (JArray ((JString x):xs)) = x .= [xs]
objHT (JArray (x:xs)) = (toString x) .= [xs]
objHT _ = emptyObj
groupWithCol _ = emptyObj
groupWithNCol :: Int -> Json -> Json
groupWithNCol n j | n > 0 = mapj (n 1) (groupWithCol j)
| otherwise = j
where
mapj n j@(JObject xs)
| n > 0 = JObject ( Map.map ((mapj (n1)) . groupWithCol) xs)
| otherwise = j