Send Beginners mailing list submissions to beginners@haskell.org To subscribe or unsubscribe via the World Wide Web, visit http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners or, via email, send a message with subject or body 'help' to beginners-requ...@haskell.org
You can reach the person managing the list at beginners-ow...@haskell.org When replying, please edit your Subject line so it is more specific than "Re: Contents of Beginners digest..." Today's Topics: 1. Re: converting a json encoded radix tree to a haskell data type (David McBride) 2. applicative style (Williams, Wes(AWF)) 3. Re: applicative style (Brandon Allbery) 4. applicative style (Williams, Wes(AWF)) ---------------------------------------------------------------------- Message: 1 Date: Fri, 28 Aug 2015 12:45:35 -0400 From: David McBride <toa...@gmail.com> To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell <beginners@haskell.org> Subject: Re: [Haskell-beginners] converting a json encoded radix tree to a haskell data type Message-ID: <CAN+Tr41G=O5O3Ah_3EuJi1PGg+=dyqua_jqq9cdt7ubg4n6...@mail.gmail.com> Content-Type: text/plain; charset="utf-8" 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 <a...@adamflott.com> wrote: > 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 <a...@adamflott.com > > <mailto:a...@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 > -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/beginners/attachments/20150828/61b5ef96/attachment-0001.html> ------------------------------ Message: 2 Date: Fri, 28 Aug 2015 17:12:29 +0000 From: "Williams, Wes(AWF)" <wewilli...@paypal.com> To: "beginners@haskell.org" <beginners@haskell.org> Subject: [Haskell-beginners] applicative style Message-ID: <d205e38b.dcca%wewilli...@paypalcorp.com> Content-Type: text/plain; charset="iso-8859-1" Hi haskellers, I am trying to understand why I get the following error in learning applicative style. Prelude> let estimates = [5,5,8,8,2,1,5,2] Prelude> (/) <$> Just $ foldl (+) 0 estimates <*> Just . fromIntegral $ length estimates <interactive>:54:1: Non type-variable argument in the constraint: Fractional (Maybe r) (Use FlexibleContexts to permit this) When checking that 'it' has the inferred type it :: forall a r. (Fractional (Maybe r), Num a, Num (Int -> Maybe a -> r)) => Maybe r -> Maybe r All the parts work individually. If use let and assign the parts to x and y it also works. E.g. This works let x = Just $ foldl (+) estimates Let y = Just . fromIntegral $ length estimates (/) <$> x <*> y I clearly do not understand exactly how these work. :-) Thanks for any help, -wes -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/beginners/attachments/20150828/52bd710e/attachment-0001.html> ------------------------------ Message: 3 Date: Fri, 28 Aug 2015 13:23:10 -0400 From: Brandon Allbery <allber...@gmail.com> To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell <beginners@haskell.org> Subject: Re: [Haskell-beginners] applicative style Message-ID: <CAKFCL4Xc+Vw22+s=tojr7swcjca8gqrkfqgdq95emstmuq6...@mail.gmail.com> Content-Type: text/plain; charset="utf-8" On Fri, Aug 28, 2015 at 1:12 PM, Williams, Wes(AWF) <wewilli...@paypal.com> wrote: > Num (Int -> Maybe a -> r)) That looks highly suspect. If it infers a function Num instance, you probably got your parentheses wrong. Or your $-s... ...in fact, that is the problem. That final $ does not do what you think; it produces (foldl (+) 0 estimates <*> Just . fromIntegral) (length estimates) when you presumably intended foldl (+) 0 estimates <+> (Just . fromIntegral) (length estimates) -- brandon s allbery kf8nh sine nomine associates allber...@gmail.com ballb...@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/beginners/attachments/20150828/ec409756/attachment-0001.html> ------------------------------ Message: 4 Date: Fri, 28 Aug 2015 18:31:39 +0000 From: "Williams, Wes(AWF)" <wewilli...@paypal.com> To: "beginners@haskell.org" <beginners@haskell.org> Subject: [Haskell-beginners] applicative style Message-ID: <d205f718.dcdc%wewilli...@paypalcorp.com> Content-Type: text/plain; charset="iso-8859-1" Awesome, I clearly am off on my understanding. How could I do this: "foldl (+) 0 estimates <+> (Just . fromIntegral) (length estimates)" without the parenthesis? Thanks, Wes -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/beginners/attachments/20150828/f3969198/attachment.html> ------------------------------ Subject: Digest Footer _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners ------------------------------ End of Beginners Digest, Vol 86, Issue 21 *****************************************