[Haskell-beginners] converting a json encoded radix tree to a haskell data type
Adam Flott
adam at adamflott.com
Thu Aug 27 20:31:25 UTC 2015
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 <adam at adamflott.com
> <mailto:adam at 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 at haskell.org <mailto:Beginners at haskell.org>
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
More information about the Beginners
mailing list