converting a json encoded radix tree to a haskell data type

I'm having trouble converting a JSON encoded Radix tree into a Haskell data type[1]. I've tried numerous ways to get the FromJSON instances to handle all cases, but failing miserably. [1] unfortunately these type layouts are unchangeable as they are auto generated types from Thrift Here is a stripped down version of what I'm working with. For the JSON file, all keys are unknown at parse time. I only know that a key will be a string and it's value will be another JSON object or a JSON array of fixed length. Any help is appreciated. -- radix.hs -- {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE OverloadedStrings #-} import Control.Monad (mzero) import Data.Int import Data.Typeable import Data.Aeson import qualified Data.ByteString.Lazy as BL import Data.Text.Lazy as TL import qualified Data.Vector as V data Things = MkThings { thing :: TL.Text, times :: ThingTimes } deriving (Show, Eq, Typeable) data ThingTimes = MkThingtimes { ml :: V.Vector Times } deriving (Show, Eq, Typeable) data Times = MkTimes { t1 :: Maybe Int32, t2 :: Maybe Int32 } deriving (Show, Eq, Typeable) instance FromJSON (V.Vector Things) where parseJSON _ = return V.empty decodeRadix ::BL.ByteString -> Either String (V.Vector Things) decodeRadix = eitherDecode main :: IO () main = do j <- BL.readFile "radix.json" case decodeRadix j of Left err -> error err Right r -> print r -- radix.hs -- -- radix.json -- { "a" : { "b" : [ 1, 2 ], "c" : { "d" : [ 3, null ] } }, "a2" : { "b2" : [ 4, 5 ] } } -- radix.json --

On Thu, Aug 27, 2015, at 08:04 AM, Adam Flott wrote:
data Things = MkThings { thing :: TL.Text, times :: ThingTimes } deriving (Show, Eq, Typeable)
data ThingTimes = MkThingtimes { ml :: V.Vector Times } deriving (Show, Eq, Typeable)
data Times = MkTimes { t1 :: Maybe Int32, t2 :: Maybe Int32 } deriving (Show, Eq, Typeable)
-- radix.json -- { "a" : { "b" : [ 1, 2 ], "c" : { "d" : [ 3, null ] } }, "a2" : { "b2" : [ 4, 5 ] } } -- radix.json --
It looks like your input file has Things nested inside Things, but your data types don't allow for that. Is that intentional? What value is that example input supposed to parse to? -Karl

On 08/27/2015 11:18 AM, Karl Voelker wrote:
On Thu, Aug 27, 2015, at 08:04 AM, Adam Flott wrote:
data Things = MkThings { thing :: TL.Text, times :: ThingTimes } deriving (Show, Eq, Typeable)
data ThingTimes = MkThingtimes { ml :: V.Vector Times } deriving (Show, Eq, Typeable)
data Times = MkTimes { t1 :: Maybe Int32, t2 :: Maybe Int32 } deriving (Show, Eq, Typeable)
-- radix.json -- { "a" : { "b" : [ 1, 2 ], "c" : { "d" : [ 3, null ] } }, "a2" : { "b2" : [ 4, 5 ] } } -- radix.json -- It looks like your input file has Things nested inside Things, but your data types don't allow for that. Is that intentional? What value is that example input supposed to parse to?
Vector [ MkThings "ab" (MkThingTimes (Vector [ Just 1, Just 2 ])), MkThings "abcd" (MkThingsTimes (Vector [ Just 3, Nothing)) MkThings "a2b2" (MkThingTimes (Vector [ Just 4, Just 5 ])) ]

I was trying this but ran into a bit of trouble. Are you super attached to
that data structure? I would expect a radix tree as you've described it to
look more like this:
data RadixTree = Node [(Text, RadixTree)] | Leaf Times
data Times = Times (Maybe Int) (Maybe Int)
In which case it is much easier to write the json instances. From there
you shouldn't have too much of a problem writing a recursive function to do
the rest, without dealing with all the aeson stuff at the same time.
Here's what I ended up with (I think it could be cleaned up a bit).
import Control.Monad
import Data.Text as T
import Data.Aeson
import Data.HashMap.Strict as HM
import Data.Vector as V hiding (mapM)
data RadixTree = Node [(Text, RadixTree)] | Leaf Times deriving Show
data Times = Times (Maybe Int) (Maybe Int) deriving Show
instance FromJSON RadixTree where
parseJSON (Object o) = do
let els = HM.toList o
contents <- mapM (\(t,v) -> do v' <- parseJSON v; return (t, v'))
(HM.toList o)
return $ Node contents
parseJSON a@(Array _) = Leaf <$> parseJSON a
parseJSON _ = mzero
instance FromJSON Times where
parseJSON (Array v) | (V.length v) >= 2 =
let v0 = v V.! 0
v1 = v V.! 1
in Times <$> parseJSON v0 <*> parseJSON v1
parseJSON _ = mzero
{-
tree2things :: RadixTree -> [(Text, (Maybe Int, Maybe Int))]
tree2things (Node xs) = _
tree2things (Leaf t) = _
-}
On Thu, Aug 27, 2015 at 11:30 AM, Adam Flott
On 08/27/2015 11:18 AM, Karl Voelker wrote:
On Thu, Aug 27, 2015, at 08:04 AM, Adam Flott wrote:
data Things = MkThings { thing :: TL.Text, times :: ThingTimes } deriving (Show, Eq, Typeable)
data ThingTimes = MkThingtimes { ml :: V.Vector Times } deriving (Show, Eq, Typeable)
data Times = MkTimes { t1 :: Maybe Int32, t2 :: Maybe Int32 } deriving (Show, Eq, Typeable)
-- radix.json -- { "a" : { "b" : [ 1, 2 ], "c" : { "d" : [ 3, null ] } }, "a2" : { "b2" : [ 4, 5 ] } } -- radix.json -- It looks like your input file has Things nested inside Things, but your data types don't allow for that. Is that intentional? What value is that example input supposed to parse to?
Vector [ MkThings "ab" (MkThingTimes (Vector [ Just 1, Just 2 ])), MkThings "abcd" (MkThingsTimes (Vector [ Just 3, Nothing)) MkThings "a2b2" (MkThingTimes (Vector [ Just 4, Just 5 ])) ] _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

I am attached to the data structure as it's what our Thrift message spits out and has to be mapped that way for the down stream consumers. On 08/27/2015 01:45 PM, David McBride wrote:
I was trying this but ran into a bit of trouble. Are you super attached to that data structure? I would expect a radix tree as you've described it to look more like this:
data RadixTree = Node [(Text, RadixTree)] | Leaf Times data Times = Times (Maybe Int) (Maybe Int)
In which case it is much easier to write the json instances. From there you shouldn't have too much of a problem writing a recursive function to do the rest, without dealing with all the aeson stuff at the same time. Here's what I ended up with (I think it could be cleaned up a bit).
import Control.Monad import Data.Text as T import Data.Aeson import Data.HashMap.Strict as HM import Data.Vector as V hiding (mapM)
data RadixTree = Node [(Text, RadixTree)] | Leaf Times deriving Show data Times = Times (Maybe Int) (Maybe Int) deriving Show
instance FromJSON RadixTree where parseJSON (Object o) = do let els = HM.toList o contents <- mapM (\(t,v) -> do v' <- parseJSON v; return (t, v')) (HM.toList o) return $ Node contents parseJSON a@(Array _) = Leaf <$> parseJSON a parseJSON _ = mzero
instance FromJSON Times where parseJSON (Array v) | (V.length v) >= 2 = let v0 = v V.! 0 v1 = v V.! 1 in Times <$> parseJSON v0 <*> parseJSON v1 parseJSON _ = mzero
{- tree2things :: RadixTree -> [(Text, (Maybe Int, Maybe Int))] tree2things (Node xs) = _ tree2things (Leaf t) = _ -}
On Thu, Aug 27, 2015 at 11:30 AM, Adam Flott
mailto:adam@adamflott.com> wrote: On 08/27/2015 11:18 AM, Karl Voelker wrote: > On Thu, Aug 27, 2015, at 08:04 AM, Adam Flott wrote: >> data Things = MkThings { >> thing :: TL.Text, >> times :: ThingTimes >> } deriving (Show, Eq, Typeable) >> >> data ThingTimes = MkThingtimes { >> ml :: V.Vector Times >> } deriving (Show, Eq, Typeable) >> >> data Times = MkTimes { >> t1 :: Maybe Int32, >> t2 :: Maybe Int32 >> } deriving (Show, Eq, Typeable) >> >> -- radix.json -- >> { >> "a" : { >> "b" : [ 1, 2 ], >> "c" : { >> "d" : [ 3, null ] >> } >> }, >> "a2" : { "b2" : [ 4, 5 ] } >> } >> -- radix.json -- > It looks like your input file has Things nested inside Things, but your > data types don't allow for that. Is that intentional? What value is that > example input supposed to parse to?
Vector [ MkThings "ab" (MkThingTimes (Vector [ Just 1, Just 2 ])), MkThings "abcd" (MkThingsTimes (Vector [ Just 3, Nothing)) MkThings "a2b2" (MkThingTimes (Vector [ Just 4, Just 5 ])) ] _______________________________________________ Beginners mailing list Beginners@haskell.org mailto:Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Well I went ahead and completed that function, but I didn't use your data
types exactly, but it should be a one to one mapping, just modify this
function with your constructors.
radix2things :: RadixTree -> [(Text, (Maybe Int, Maybe Int))]
radix2things r = conv' mempty r
where
conv' :: Text -> RadixTree -> [(Text, (Maybe Int, Maybe Int))]
conv' acc (Leaf (Times a b)) = [(acc, (a, b))]
conv' acc r@(Node ns) = P.concatMap (\(t,r) -> conv' (acc <> t) r) ns
And you'll get a result like:
*Main> case decode teststr of Nothing -> undefined; Just a -> conv a
[("a2b2",(Just 4,Just 5)),("ab",(Just 1,Just 2)),("acd",(Just 3,Nothing))]
Good luck.
On Thu, Aug 27, 2015 at 4:31 PM, Adam Flott
I am attached to the data structure as it's what our Thrift message spits out and has to be mapped that way for the down stream consumers.
On 08/27/2015 01:45 PM, David McBride wrote:
I was trying this but ran into a bit of trouble. Are you super attached to that data structure? I would expect a radix tree as you've described it to look more like this:
data RadixTree = Node [(Text, RadixTree)] | Leaf Times data Times = Times (Maybe Int) (Maybe Int)
In which case it is much easier to write the json instances. From there you shouldn't have too much of a problem writing a recursive function to do the rest, without dealing with all the aeson stuff at the same time. Here's what I ended up with (I think it could be cleaned up a bit).
import Control.Monad import Data.Text as T import Data.Aeson import Data.HashMap.Strict as HM import Data.Vector as V hiding (mapM)
data RadixTree = Node [(Text, RadixTree)] | Leaf Times deriving Show data Times = Times (Maybe Int) (Maybe Int) deriving Show
instance FromJSON RadixTree where parseJSON (Object o) = do let els = HM.toList o contents <- mapM (\(t,v) -> do v' <- parseJSON v; return (t, v')) (HM.toList o) return $ Node contents parseJSON a@(Array _) = Leaf <$> parseJSON a parseJSON _ = mzero
instance FromJSON Times where parseJSON (Array v) | (V.length v) >= 2 = let v0 = v V.! 0 v1 = v V.! 1 in Times <$> parseJSON v0 <*> parseJSON v1 parseJSON _ = mzero
{- tree2things :: RadixTree -> [(Text, (Maybe Int, Maybe Int))] tree2things (Node xs) = _ tree2things (Leaf t) = _ -}
On Thu, Aug 27, 2015 at 11:30 AM, Adam Flott
mailto:adam@adamflott.com> wrote: On 08/27/2015 11:18 AM, Karl Voelker wrote: > On Thu, Aug 27, 2015, at 08:04 AM, Adam Flott wrote: >> data Things = MkThings { >> thing :: TL.Text, >> times :: ThingTimes >> } deriving (Show, Eq, Typeable) >> >> data ThingTimes = MkThingtimes { >> ml :: V.Vector Times >> } deriving (Show, Eq, Typeable) >> >> data Times = MkTimes { >> t1 :: Maybe Int32, >> t2 :: Maybe Int32 >> } deriving (Show, Eq, Typeable) >> >> -- radix.json -- >> { >> "a" : { >> "b" : [ 1, 2 ], >> "c" : { >> "d" : [ 3, null ] >> } >> }, >> "a2" : { "b2" : [ 4, 5 ] } >> } >> -- radix.json -- > It looks like your input file has Things nested inside Things, but your > data types don't allow for that. Is that intentional? What value is that > example input supposed to parse to?
Vector [ MkThings "ab" (MkThingTimes (Vector [ Just 1, Just 2 ])), MkThings "abcd" (MkThingsTimes (Vector [ Just 3, Nothing)) MkThings "a2b2" (MkThingTimes (Vector [ Just 4, Just 5 ])) ] _______________________________________________ Beginners mailing list Beginners@haskell.org mailto:Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
participants (3)
-
Adam Flott
-
David McBride
-
Karl Voelker