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