module Data.JSON2.FromSQL where import Data.JSON2 import qualified Data.Map as Map -- | Conversion SQL-like JSON array to tree-like JSON object with use column. groupWithCol :: Json -> Json groupWithCol (JArray xs) = merges $ map objHT xs where merges xs = foldl merge emptyObj xs merge (JObject x) (JObject y) = JObject $ Map.unionWith (jConcat) x y jConcat(JArray xs) (JArray ys) = JArray (xs ++ ys) objHT (JArray ((JString x):xs)) = singleObj x [xs] objHT (JArray (x:xs)) = singleObj (toString x) [xs] objHT _ = emptyObj groupWithCol _ = emptyObj -- | Conversion SQL-like JSON array to tree-like JSON object with use columns. -- -- COMPLEX EXAMPLE : -- -- > import Database.HDBC -- > import Database.HDBC.Sqlite3 -- > import Data.JSON2 -- > -- > dbName = "..." -- > selectSql = "SELECT * from test" -- > -- > main = do -- > conn <- connectSqlite3 dbName -- > stmtSel <- prepare conn selectSql -- > execute stmtSel [] -- > q <- sFetchAllRows stmtSel -- > mapM print q -- > -- [Just "A",Just "1",Just "Pupkin",Just "1"] -- > -- [Just "A",Just "2",Just "Sidorov",Just "2"] -- > -- [Just "B",Just "22",Just "Petrov",Just "3"] -- > -- [Just "B",Just "22",Just "Ivanov",Just "4"] -- > -- [Just "B",Just "22",Just "Golubev",Just "5"] -- > -- [Just "B",Just "33",Just "Petrov",Just "6"] -- > let json = toJson (q :: [[Maybe String]]) -- > pprint json -- > -- [ -- > -- ["A", "1", "Pupkin", "1"], -- > -- ["A", "2", "Sidorov", "2"], -- > -- ["B", "22", "Petrov", "3"], -- > -- ["B", "22", "Ivanov", "4"], -- > -- ["B", "22", "Golubev", "5"], -- > -- ["B", "33", "Petrov", "6"] -- > -- ] -- > let json' = groupWithNCol 2 json -- > pprint json' -- > -- { -- > -- "A": { -- > -- "1": [["Pupkin", "1"]], -- > -- "2": [["Sidorov", "2"]] -- > -- }, -- > -- "B": { -- > -- "22": [["Petrov", "3"], ["Ivanov", "4"], ["Golubev", "5"]], -- > -- "33": [["Petrov", "6"]] -- > -- } -- > -- } -- > disconnect conn 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 (n-1)) . groupWithCol) xs) | otherwise = j {- j0 = toJson ["a"] j1 = toJson ["a", "aa", "aaa"] j2 = toJson ["a", "ab", "abb"] j3 = toJson ["a", "aa"] j4 = toJson ["b", "bb", "bbb"] j5 = toJson ["c", "87319827"] j6 = toJson ["a", "ab", "abb"] j7 = toJson ["a", "ab", "abb"] -}