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. Re: Beginners Digest, Vol 45, Issue 35 (Lorenzo Bolla) 2. Re: Beginners Digest, Vol 45, Issue 35 (Chadda? Fouch?) 3. Re: Non ghc specific FRP (using uhc js backend) (Ertugrul S?ylemez) 4. Re: Beginners Digest, Vol 45, Issue 35 (Ramesh Kumar) ---------------------------------------------------------------------- Message: 1 Date: Thu, 29 Mar 2012 11:19:57 +0100 From: Lorenzo Bolla <lbo...@gmail.com> Subject: Re: [Haskell-beginners] Beginners Digest, Vol 45, Issue 35 To: Chadda? Fouch? <chaddai.fou...@gmail.com> Cc: beginners@haskell.org Message-ID: <cadjgtrwegdp4gvovop83bs3+v3yw1pkghdv8qewyb8rz9gg...@mail.gmail.com> Content-Type: text/plain; charset="utf-8" Your second solution, a part from non preserving the ordering of the initial sequence, also requires the type of the list elements to be an instance of Ord. I've fixed a bug in your first version, where the return values of isIn where reversed. Here they are: module Main where import Data.List (sort, group) -- Need ordering on "a" uniqueS :: Ord a => [a] -> [a] uniqueS = concat . filter (null . drop 1) . group . sort -- Fixed Chaddai's solution -- Only need equivalent relation on "a" unique :: Eq a => [a] -> [a] unique xs = [x | x <- xs, isIn x xs 2] where isIn :: Eq a => a -> [a] -> Int -> Bool isIn _ _ 0 = False isIn _ [] _ = True isIn y (x:xs) n | y == x = isIn y xs (n-1) | otherwise = isIn y xs n main :: IO () main = do print $ uniqueS xs print $ unique xs where xs = [1,2,3,3,5,2,1,4] L. On Thu, Mar 29, 2012 at 9:30 AM, Chadda? Fouch? <chaddai.fou...@gmail.com>wrote: > On Thu, Mar 29, 2012 at 10:28 AM, Chadda? Fouch? > <chaddai.fou...@gmail.com> wrote: > >> unique xs = nub (sort xs) > > oops, I meant : > > > unique = concat . filter (null . drop 1) . group . sort > > -- > Jeda? > -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://www.haskell.org/pipermail/beginners/attachments/20120329/b99e57c8/attachment-0001.htm> ------------------------------ Message: 2 Date: Fri, 30 Mar 2012 01:11:45 +0200 From: Chadda? Fouch? <chaddai.fou...@gmail.com> Subject: Re: [Haskell-beginners] Beginners Digest, Vol 45, Issue 35 To: Lorenzo Bolla <lbo...@gmail.com> Cc: beginners@haskell.org Message-ID: <canfjzrym_2kfergoc_ksawzz4bz7xkq8+gmqyk0_kfmc5-0...@mail.gmail.com> Content-Type: text/plain; charset=UTF-8 On Thu, Mar 29, 2012 at 12:19 PM, Lorenzo Bolla <lbo...@gmail.com> wrote: > Your second solution, a part from non preserving the ordering of the initial > sequence, also requires the type of the list elements to be an instance of > Ord. Sure, but that's an almost inevitable price to get a O(n log n) algorithm : you must add a constraint, whether Ord or Hashable or something like that. Though a solution with Data.Map in two traversal can preserve the order and still be O(n log n) if the order is important : > uniqueM :: (Ord a) => [a] -> [a] > uniqueM xs = filter ((==1).(m M.!)) xs > where > m = M.fromListWith (+) $ zip xs (repeat 1) (fromListWith' would be better here but I don't know why, it still isn't in Data.Map despite it being a very often useful function) > I've fixed a bug in your first version, where the return values of isIn > where reversed. No, no, my version of isIn was correct (according to my logic at least) : "isIn y xs 0" is always True since x is always at least 0 times in ys, and "isIn y [] n" with n /= 0 is always False since y is never in [] more than 0 times. The error was in my list comprehension, of course which should have been : [x | x <- xs, not (isIn x xs 2)]. I had first written it as a recursive function before I saw that list comprehension were admitted and rewrote it a bit hastily :) Maybe isIn should have named isInAtLeast... > > module Main where > > import Data.List (sort, group) > > -- Need ordering on "a" > uniqueS :: Ord a => [a] -> [a] > uniqueS = concat . filter (null . drop 1) . group . sort > > -- Fixed Chaddai's solution > -- Only need equivalent relation on "a" > unique :: Eq a => [a] -> [a] > unique xs = [x | x <- xs, isIn x xs 2] > ? ? ? ? where isIn :: Eq a => a -> [a] -> Int -> Bool > ? ? ? ? ? ? ? isIn _ _ 0 = False > ? ? ? ? ? ? ? isIn _ [] _ = True > ? ? ? ? ? ? ? isIn y (x:xs) n > ? ? ? ? ? ? ? ? ? ? | y == x ? ?= isIn y xs (n-1) > ? ? ? ? ? ? ? ? ? ? | otherwise = isIn y xs n -- Jeda? ------------------------------ Message: 3 Date: Fri, 30 Mar 2012 01:28:05 +0200 From: Ertugrul S?ylemez <e...@ertes.de> Subject: Re: [Haskell-beginners] Non ghc specific FRP (using uhc js backend) To: beginners@haskell.org Message-ID: <20120330012805.12882...@tritium.streitmacht.eu> Content-Type: text/plain; charset="utf-8" Nathan H?sken <nathan.hues...@posteo.de> wrote: > I read that it is ghc specific because of mutable references. I am > trying to use the js backend of uhc and that does not support this. I > have tried to use other FRP libraries with uhc (by compiling a file > which does nothing but import the library) and all failed because of > something missing in Control.Concurrent. > > So I am wondering: Is it a property FRP that it needs something like > mutable references for an efficient implementation. > Is there a FRP library that can be used (or can be changed so that it > can be used) with uhc and its js backend? Well, for one thing there is the Flapjax project, which is an FRP library implemented in JavaScript. If you want to stay in Haskell, my Netwire library is based on the automaton arrow, so it's a pure library with no need for mutable references or anything. However, it does require two extensions UHC apparently doesn't support: arrow syntax and type families. For the former there is a preprocessor you can use. The latter is more tricky. You can get around the type families requirement by implementing the wire arrow as a monad transformer instead of an arrow transformer. This will require some refactoring though, so you might not want to do that. My suggestion is to give Heinrich's reactive-banana library a try. It's less flexible, but gets along with comparably few language extensions and is also easier to learn. If you like the AFRP approach you can also wait for a new library I'm currently working on, which will be a simplified, more flexible variant of the wire arrow as defined by Netwire. You might observe it as a new version of Netwire, but more likely I will make it its own library. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/ -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: not available URL: <http://www.haskell.org/pipermail/beginners/attachments/20120330/2b276298/attachment-0001.pgp> ------------------------------ Message: 4 Date: Fri, 30 Mar 2012 02:05:07 -0700 (PDT) From: Ramesh Kumar <rameshkumar.techdynam...@ymail.com> Subject: Re: [Haskell-beginners] Beginners Digest, Vol 45, Issue 35 To: Chadda? Fouch? <chaddai.fou...@gmail.com>, Lorenzo Bolla <lbo...@gmail.com> Cc: "beginners@haskell.org" <beginners@haskell.org> Message-ID: <1333098307.7455.yahoomail...@web120202.mail.ne1.yahoo.com> Content-Type: text/plain; charset="iso-8859-1" Folks, Thank you so much for the replies, ideas and comments about my query. 1) However, I'm puzzled, how do you analyze performance when it comes to programs written in a functional language like Haskell. Correct me if I am wrong, functional language programs don't really run like the usual top to bottom flows we have with other (imperative) languages. They're much like Prolog programs, I am tempted to think. 2) Is there any popular paper/tutorial/writeup/book which touches on the performance aspects of Haskell programs? Thank you so much. Ramesh >________________________________ > From: Chadda? Fouch? <chaddai.fou...@gmail.com> >To: Lorenzo Bolla <lbo...@gmail.com> >Cc: beginners@haskell.org >Sent: Friday, March 30, 2012 7:11 AM >Subject: Re: [Haskell-beginners] Beginners Digest, Vol 45, Issue 35 > >On Thu, Mar 29, 2012 at 12:19 PM, Lorenzo Bolla <lbo...@gmail.com> wrote: >> Your second solution, a part from non preserving the ordering of the initial >> sequence, also requires the type of the list elements to be an instance of >> Ord. > >Sure, but that's an almost inevitable price to get a O(n log n) >algorithm : you must add a constraint, whether Ord or Hashable or >something like that. >Though a solution with Data.Map in two traversal can preserve the >order and still be O(n log n) if the order is important : > >> uniqueM :: (Ord a) => [a] -> [a] >> uniqueM xs = filter ((==1).(m M.!)) xs >>? where >>? ? m = M.fromListWith (+) $ zip xs (repeat 1) > >(fromListWith' would be better here but I don't know why, it still >isn't in Data.Map despite it being a very often useful function) > >> I've fixed a bug in your first version, where the return values of isIn >> where reversed. > >No, no, my version of isIn was correct (according to my logic at >least) : "isIn y xs 0" is always True since x is always at least 0 >times in ys, and "isIn y [] n" with n /= 0 is always False since y is >never in [] more than 0 times. The error was in my list comprehension, >of course which should have been : [x | x <- xs, not (isIn x xs 2)]. I >had first written it as a recursive function before I saw that list >comprehension were admitted and rewrote it a bit hastily :) >Maybe isIn should have named isInAtLeast... > >> >> module Main where >> >> import Data.List (sort, group) >> >> -- Need ordering on "a" >> uniqueS :: Ord a => [a] -> [a] >> uniqueS = concat . filter (null . drop 1) . group . sort >> >> -- Fixed Chaddai's solution >> -- Only need equivalent relation on "a" >> unique :: Eq a => [a] -> [a] >> unique xs = [x | x <- xs, isIn x xs 2] >> ? ? ? ? where isIn :: Eq a => a -> [a] -> Int -> Bool >> ? ? ? ? ? ? ? isIn _ _ 0 = False >> ? ? ? ? ? ? ? isIn _ [] _ = True >> ? ? ? ? ? ? ? isIn y (x:xs) n >> ? ? ? ? ? ? ? ? ? ? | y == x ? ?= isIn y xs (n-1) >> ? ? ? ? ? ? ? ? ? ? | otherwise = isIn y xs n > >-- >Jeda? > >_______________________________________________ >Beginners mailing list >Beginners@haskell.org >http://www.haskell.org/mailman/listinfo/beginners > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://www.haskell.org/pipermail/beginners/attachments/20120330/f9c801df/attachment-0001.htm> ------------------------------ _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners End of Beginners Digest, Vol 45, Issue 39 *****************************************