Send Beginners mailing list submissions to beginners@haskell.org To subscribe or unsubscribe via the World Wide Web, visit http://www.haskell.org/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. reverse 'lookup' (Patrick LeBoutillier) 2. Re: reverse 'lookup' (Yitzchak Gale) 3. Evaluate behaviour (Tom Hobbs) 4. Re: reverse 'lookup' (Alex Rozenshteyn) 5. Re: Evaluate behaviour (Elvio Rogelio Toccalino) 6. Re: Evaluate behaviour (Elvio Rogelio Toccalino) 7. Re: Dynamic Programming in Haskell (Heinrich Apfelmus) ---------------------------------------------------------------------- Message: 1 Date: Wed, 7 Jul 2010 13:28:03 -0400 From: Patrick LeBoutillier <patrick.leboutill...@gmail.com> Subject: [Haskell-beginners] reverse 'lookup' To: beginners <beginners@haskell.org> Message-ID: <aanlktilcidi6bbr9it0chufwidxd4_nxmvkc9bdp7...@mail.gmail.com> Content-Type: text/plain; charset=ISO-8859-1 Hi, The lookup function can locate something in a a-list: lookup :: Eq a => a -> [(a,b)] -> Maybe b is there an easy way to do a reverse lookup: rlookup :: Eq b => b -> [(a,b)] -> Maybe a or perhaps a builtin function to flip a pair: (a, b) -> (b, a) Thanks, Patrick -- ===================== Patrick LeBoutillier Rosemère, Québec, Canada ------------------------------ Message: 2 Date: Wed, 7 Jul 2010 20:54:48 +0300 From: Yitzchak Gale <g...@sefer.org> Subject: Re: [Haskell-beginners] reverse 'lookup' To: Patrick LeBoutillier <patrick.leboutill...@gmail.com> Cc: beginners <beginners@haskell.org> Message-ID: <aanlktilaey3uurkcn0uadi2aotpaxf_v2aozvje2c...@mail.gmail.com> Content-Type: text/plain; charset=ISO-8859-1 Patrick LeBoutillier wrote: > is there... perhaps a builtin function to flip a pair: > (a, b) -> (b, a) The function swap (x, y) = (y, x) will be added to Data.Tuple in the next release of the base libraries. In the meantime, it is easy enough to define it yourself, and then, of course rlookup x = lookup x . map swap Or, you could use the find function from Data.List and write: rlookup x = find ((== x) . snd) Regards, Yitz ------------------------------ Message: 3 Date: Wed, 07 Jul 2010 20:51:40 +0100 From: "Tom Hobbs" <tvho...@googlemail.com> Subject: [Haskell-beginners] Evaluate behaviour To: "beginners@haskell.org" <beginners@haskell.org> Message-ID: <op.vfhn4dlpk73...@localhost.localdomain> Content-Type: text/plain; charset=utf-8; format=flowed; delsp=yes Hi guys, Thanks to everyone who helped me, I hit a milestone this evening and finally got the (small) bit of functionality I was working on, working! A huge "thank you" to everyone who has taken the time to use very small words to explain things to me! (I just need to sort out some nicer error handling now...) Just one more question... for today. Here's my code; import Network import System.IO (hGetLine,hClose,hPutStrLn,hSetBuffering,BufferMode(..),Handle,stdout) import Data.Bits import Data.Binary import Data.Binary.Put import Data.Binary.Get import qualified Data.ByteString.Lazy as L import qualified Data.ByteString.UTF8 as UTF import Control.Monad import Control.Exception (evaluate) ping a t = do h <- connectTo a (PortNumber t) hSetBuffering h NoBuffering L.hPut h (encode (0xFAB10000 :: Word32)) numStrings <- fmap (fromIntegral . runGet getWord64be) $ L.hGet h 8 names <- (fmap (runGet $ readStrings numStrings) $ L.hGetContents h) evaluate names hClose h return names readStrings :: Int -> Get [String] readStrings n = replicateM n $ do len <- getWord32be name <- getByteString $ fromIntegral len return $ UTF.toString name This works in GHCi exactly as I want it to. Note the call to "evaluate" in the ping function which allows me to close the handle before returning the IO [String]. This behaviour prints out the list of Strings as read from the handle in GHCi, exactly what I wanted it to do. Here's the strange part; If I remove the evalute line, and instead have; names <- evaluate (fmap (runGet $ readStrings numStrings) $ L.hGetContents h) GHCI claims that this is okay, but when I call ping I don't get any output. I don't get any errors either, but I would expect to see the same list of Strings as before. Can anyone explain to me why that happpens? I'm assuming it's something to do with the "<-" magic, but I don't know what. Thanks, Tom -- Using Opera's revolutionary e-mail client: http://www.opera.com/mail/ ------------------------------ Message: 4 Date: Wed, 7 Jul 2010 20:25:50 -0400 From: Alex Rozenshteyn <rpglove...@gmail.com> Subject: Re: [Haskell-beginners] reverse 'lookup' To: g...@sefer.org Cc: beginners <beginners@haskell.org> Message-ID: <aanlktikit_cwddzagte5e0ojaxbhxezvgnloaiykx...@mail.gmail.com> Content-Type: text/plain; charset="utf-8" Incidentally (and more as a curiosity than anything else) Prelude> :t uncurry . flip . curry $ id uncurry . flip . curry $ id :: (b, a) -> (a, b) On Wed, Jul 7, 2010 at 1:54 PM, Yitzchak Gale <g...@sefer.org> wrote: > Patrick LeBoutillier wrote: > > is there... perhaps a builtin function to flip a pair: > > (a, b) -> (b, a) > > The function > > swap (x, y) = (y, x) > > will be added to Data.Tuple in the next release > of the base libraries. In the meantime, it is easy > enough to define it yourself, and then, of course > > rlookup x = lookup x . map swap > > Or, you could use the find function from Data.List > and write: > > rlookup x = find ((== x) . snd) > > Regards, > Yitz > _______________________________________________ > Beginners mailing list > Beginners@haskell.org > http://www.haskell.org/mailman/listinfo/beginners > -- Alex R -------------- next part -------------- An HTML attachment was scrubbed... URL: http://www.haskell.org/pipermail/beginners/attachments/20100707/1565decf/attachment-0001.html ------------------------------ Message: 5 Date: Thu, 8 Jul 2010 00:56:06 -0300 From: Elvio Rogelio Toccalino <elviotoccal...@gmail.com> Subject: Re: [Haskell-beginners] Evaluate behaviour To: Tom Hobbs <tvho...@googlemail.com> Cc: "beginners@haskell.org" <beginners@haskell.org> Message-ID: <aanlktil2zkxvg-wznjwdeljqd4o6lumthhdxfcffi...@mail.gmail.com> Content-Type: text/plain; charset=ISO-8859-1 This is a common behaviour, Tom. I suggest you read about the "semi-closed" state of Handles in the documentation for System.IO. It's kind of Zen :D Basically, you are reading lazily from a bytestring (1 chunk at a time)... Although it may seem as your program read and processed the whole bytestring, it didn't (it's lazy!). If you close the handle before "using" the output (when you 'return' it from your main function), you're shutting down the incoming data channel before a single request for a chunk of the bytestring is made. Check it out for yourself... don't hClose the handle, just leave it be. (It's messy, I know, but experiment with it.) 2010/7/7, Tom Hobbs <tvho...@googlemail.com>: > Hi guys, > > Thanks to everyone who helped me, I hit a milestone this evening and > finally got the (small) bit of functionality I was working on, working! A > huge "thank you" to everyone who has taken the time to use very small > words to explain things to me! (I just need to sort out some nicer error > handling now...) > > Just one more question... for today. > > Here's my code; > > import Network > import System.IO > (hGetLine,hClose,hPutStrLn,hSetBuffering,BufferMode(..),Handle,stdout) > import Data.Bits > import Data.Binary > import Data.Binary.Put > import Data.Binary.Get > import qualified Data.ByteString.Lazy as L > import qualified Data.ByteString.UTF8 as UTF > import Control.Monad > import Control.Exception (evaluate) > > ping a t = do > h <- connectTo a (PortNumber t) > hSetBuffering h NoBuffering > L.hPut h (encode (0xFAB10000 :: Word32)) > numStrings <- fmap (fromIntegral . runGet getWord64be) $ L.hGet h 8 > names <- (fmap (runGet $ readStrings numStrings) $ L.hGetContents h) > evaluate names > hClose h > return names > > readStrings :: Int -> Get [String] > readStrings n = replicateM n $ do > len <- getWord32be > name <- getByteString $ fromIntegral len > return $ UTF.toString name > > This works in GHCi exactly as I want it to. Note the call to "evaluate" > in the ping function which allows me to close the handle before returning > the IO [String]. This behaviour prints out the list of Strings as read > from the handle in GHCi, exactly what I wanted it to do. Here's the > strange part; > > If I remove the evalute line, and instead have; > > names <- evaluate (fmap (runGet $ readStrings numStrings) $ L.hGetContents > h) > > GHCI claims that this is okay, but when I call ping I don't get any > output. I don't get any errors either, but I would expect to see the same > list of Strings as before. > > Can anyone explain to me why that happpens? I'm assuming it's something > to do with the "<-" magic, but I don't know what. > > Thanks, > > Tom > > > -- > Using Opera's revolutionary e-mail client: http://www.opera.com/mail/ > _______________________________________________ > Beginners mailing list > Beginners@haskell.org > http://www.haskell.org/mailman/listinfo/beginners > ------------------------------ Message: 6 Date: Thu, 8 Jul 2010 01:17:48 -0300 From: Elvio Rogelio Toccalino <elviotoccal...@gmail.com> Subject: Re: [Haskell-beginners] Evaluate behaviour To: Tom Hobbs <tvho...@googlemail.com> Cc: "beginners@haskell.org" <beginners@haskell.org> Message-ID: <aanlktinfty_kiy2_derqog0koiylvip03vioihyfy...@mail.gmail.com> Content-Type: text/plain; charset=ISO-8859-1 ...Oh, I just saw this: """ instead have; names <- evaluate (fmap (runGet $ readStrings numStrings) $ L.hGetContents h) """ My apologizes, I was tackling a different question. I believe the magic attributed to the (<-) operator results from the following: let FUN be "(fmap (runGet $ readStrings numStrings) $ L.hGetContents h)" then FUN :: IO [String] This: names <- FUN evaluate names bounds the result of the FUN computation to 'names'. Evaluate is run on names, therefore 'evaluate'ing the result of the FUN computation. On the other hand, this: names <- evaluate FUN bounds to 'names' the results of 'evaluate'ing FUN. The action is executed and the argument (FUN) is evaluated to WHNF. Let's see, evaluate :: a -> IO a evaluate FUN :: IO (IO [String]) names <- evaluate FUN ... and 'names' is bound to a [String] which has been evaluated to WHNF. You end up closing a handle before reading your input. If my reasoning is wrong, please (please!) let me know, you'd be helping me greatly. 2010/7/8, Elvio Rogelio Toccalino <elviotoccal...@gmail.com>: > This is a common behaviour, Tom. I suggest you read about the > "semi-closed" state of Handles in the documentation for System.IO. > > It's kind of Zen :D > > Basically, you are reading lazily from a bytestring (1 chunk at a > time)... Although it may seem as your program read and processed the > whole bytestring, it didn't (it's lazy!). If you close the handle > before "using" the output (when you 'return' it from your main > function), you're shutting down the incoming data channel before a > single request for a chunk of the bytestring is made. > > Check it out for yourself... don't hClose the handle, just leave it > be. (It's messy, I know, but experiment with it.) > > 2010/7/7, Tom Hobbs <tvho...@googlemail.com>: >> Hi guys, >> >> Thanks to everyone who helped me, I hit a milestone this evening and >> finally got the (small) bit of functionality I was working on, working! >> A >> huge "thank you" to everyone who has taken the time to use very small >> words to explain things to me! (I just need to sort out some nicer error >> handling now...) >> >> Just one more question... for today. >> >> Here's my code; >> >> import Network >> import System.IO >> (hGetLine,hClose,hPutStrLn,hSetBuffering,BufferMode(..),Handle,stdout) >> import Data.Bits >> import Data.Binary >> import Data.Binary.Put >> import Data.Binary.Get >> import qualified Data.ByteString.Lazy as L >> import qualified Data.ByteString.UTF8 as UTF >> import Control.Monad >> import Control.Exception (evaluate) >> >> ping a t = do >> h <- connectTo a (PortNumber t) >> hSetBuffering h NoBuffering >> L.hPut h (encode (0xFAB10000 :: Word32)) >> numStrings <- fmap (fromIntegral . runGet getWord64be) $ L.hGet h 8 >> names <- (fmap (runGet $ readStrings numStrings) $ L.hGetContents h) >> evaluate names >> hClose h >> return names >> >> readStrings :: Int -> Get [String] >> readStrings n = replicateM n $ do >> len <- getWord32be >> name <- getByteString $ fromIntegral len >> return $ UTF.toString name >> >> This works in GHCi exactly as I want it to. Note the call to "evaluate" >> in the ping function which allows me to close the handle before returning >> the IO [String]. This behaviour prints out the list of Strings as read >> from the handle in GHCi, exactly what I wanted it to do. Here's the >> strange part; >> >> If I remove the evalute line, and instead have; >> >> names <- evaluate (fmap (runGet $ readStrings numStrings) $ >> L.hGetContents >> h) >> >> GHCI claims that this is okay, but when I call ping I don't get any >> output. I don't get any errors either, but I would expect to see the >> same >> list of Strings as before. >> >> Can anyone explain to me why that happpens? I'm assuming it's something >> to do with the "<-" magic, but I don't know what. >> >> Thanks, >> >> Tom >> >> >> -- >> Using Opera's revolutionary e-mail client: http://www.opera.com/mail/ >> _______________________________________________ >> Beginners mailing list >> Beginners@haskell.org >> http://www.haskell.org/mailman/listinfo/beginners >> > ------------------------------ Message: 7 Date: Thu, 08 Jul 2010 10:20:29 +0200 From: Heinrich Apfelmus <apfel...@quantentunnel.de> Subject: [Haskell-beginners] Re: Dynamic Programming in Haskell To: beginners@haskell.org Message-ID: <i141oe$3s...@dough.gmane.org> Content-Type: text/plain; charset=UTF-8; format=flowed Daniel Fischer wrote: > Heinrich Apfelmus wrote: >> I didn't need to debug this code, because it's obviously correct. Put >> differently, instead of spending my effort on debugging, I have spent it >> on making the solution elegant. > > Well done. > Chapeau! :) Well, apart from the fact that the "obviousness" of this code also depends on the correctness of this particular division into subproblems, there is one piece of the code that is quite error-prone, namely the definition of chain and chain' : chain = memoize n chain' chain' i j | i == j = Matrix (dimensions ! i) | otherwise = best [mul (chain i k) (chain (k+1) j) | k <- [i..j-1] ] It is really easy to accidentally write chain' instead of chain and vice versa, leading to a black hole or a loss of memoization. (Using more distinct names doesn't necessarily help because there is almost no semantic difference between the two functions.) Trouble is that the type system won't catch such mistakes because the two functions have the same type. However, we can give chain and chain' different types by using the fixed point combinator and writing: chain = fix (memoize n . chain') chain' chain i j | i == j = Matrix (dimensions ! i) | otherwise = best [mul (chain i k) (chain (k+1) j) | k <- [i..j-1] ] Shadowing the variable chain in the definition of chain' is both intentional and harmless, since both variables chain will be bound to the very same function. In any case, chain' and chain now have different types and the burden of checking whether we've used them correctly is left to the compiler. (For those who don't know the fixed point combinator yet: I have recently made a short video about it: http://apfelmus.nfshost.com/blog/2010/07/02-fixed-points-video.html ) Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ------------------------------ _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners End of Beginners Digest, Vol 25, Issue 25 *****************************************