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:  performance issues (Daniel Fischer)
   2. Re:  Question: Data Type for user selection (Hartmut)
   3.  Running a list of functions (Manfred Lotz)
   4. Re:  Running a list of functions (David Place)
   5. Re:  Running a list of functions (Manfred Lotz)
   6. Re:  Running a list of functions (Ozgur Akgun)
   7. Re:  Running a list of functions (Brandon Allbery)


----------------------------------------------------------------------

Message: 1
Date: Sat, 20 Aug 2011 12:04:52 +0200
From: Daniel Fischer <daniel.is.fisc...@googlemail.com>
Subject: Re: [Haskell-beginners] performance issues
To: Sunil S Nandihalli <sunil.nandiha...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <201108201204.52842.daniel.is.fisc...@googlemail.com>
Content-Type: Text/Plain;  charset="utf-8"

On Saturday 20 August 2011, 10:50:00, Sunil S Nandihalli wrote:
> Thanks Daniel for your response. sieve of Eratosthenes has a very
> elegant 1 line implementation thanks to laziness of haskell. Here is
> what I came up with
> 
> primesSieve = 2:3:5:7:11:(filter (\x->(all (\p-> 0/=(mod x p))
> (takeWhile (\p-> p*p<=x) primesSieve))) [13..])
> 

Umm, I meant a real sieve, using an array. It's more complicated to 
implement, but much faster.

> But didn't seem to make a difference in performance. I had missed the
> most obvious of things.... that is adding -O2 when compiling.. 

I never think of people compiling without optimisations, of course that's 
the very first thing to do.

> It gave
> a speedup of close to 100 times which was very surprising! ..

Not really, without optimisations, you get no specialisations etc, so 
instead of the appropriate operations for the type you use, you get the 
generic ones (with a dictionary lookup). The type-specific operations often 
allow further optimisations, so things often become orders of magnitude 
faster.

If you write overloaded functions, it's generally a good idea to tell GHC 
to specialise them for the most commonly used types (say Int and Integer in 
this example),

{-# SPECIALISE foo :: Int -> Int,
                      Integer -> Integer
  #-}

Then, when everything is compiled with optimisations, the specialised 
versions are used when there exists one.
(In your case, since main is in the same module, GHC usually specialises 
the function for the type used in main by itself [with -O2, at least when 
the functions are not exported], so it's not immediately necessary to add a 
specialise-pragma.)

> I remember people setting some compiler options in the source
> file itself. Can you shed some light on that?

A pragma

{-# OPTIONS_GHC -O2 #-}

at the top of the module.

> 
> Thanks,
> Sunil.



------------------------------

Message: 2
Date: Sat, 20 Aug 2011 15:22:04 +0200
From: Hartmut <hartmut0...@googlemail.com>
Subject: Re: [Haskell-beginners] Question: Data Type for user
        selection
To: beginners@haskell.org
Message-ID:
        <CAFz=thffzd_wc6_+1a7uv+7ave1pahwcw04c_2nik+0x4zx...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Now I have found a solution and everything is fine :-)
Thanks again for your help!


-- 3. MultiSelect -----------------------------------------
data MultiSelect a = EmptySel | SingleSel (ExtendedSelect a) | MultiSel
[(ExtendedSelect a)]

a1 = EmptySel
a2 = SingleSel x1i
a3 = MultiSel [x1i, x1e]


On Sat, Aug 20, 2011 at 12:03 AM, Hartmut <hartmut0...@googlemail.com>wrote:

> All,
> thank You All for your gentle help. Now I am a step further :-) But there
> raises up the next question:
> In the last line, I want the datatype MultiSelect being limited to a's
> which are of type "ExtendedSelect x".
> How can I add this contraint?
> Hartmut
>
> {-# LANGUAGE GADTs #-}
>
> module SelectionCriterias2 where
>
> data InclusiveOrExclusive = Inclusive | Exclusive
>
> -- 1. BasicSelect ------------------------------------------
> data BasicSelect a where
>   NumSelect :: Num a => a->BasicSelect a
>   ShowSelect :: Show a => a->BasicSelect a
>
> -- examples:
> x1 = NumSelect 10
> x2 = ShowSelect "Hello"
> x3 = NumSelect 120.1
>
> -- 2. ExtendedSelect ---------------------------------------
>
> data ExtendedSelect a = ExtendedSelect {
>   basicSel :: BasicSelect a,
>   inclOrExcl :: InclusiveOrExclusive
> }
>
> -- examples:
> x1i :: ExtendedSelect Integer
> x1i = ExtendedSelect { basicSel = x1, inclOrExcl = Inclusive }
> x1e = ExtendedSelect { basicSel = x1, inclOrExcl = Exclusive }
> x2i = ExtendedSelect { basicSel = x2, inclOrExcl = Inclusive }
> x2e = ExtendedSelect { basicSel = x2, inclOrExcl = Exclusive }
>
> -- Abbreviation/helper for the construction:
> extsel :: BasicSelect a -> InclusiveOrExclusive -> ExtendedSelect a
> extsel s ie = ExtendedSelect { basicSel = s, inclOrExcl = ie }
>
> -- examples:
> x3i = extsel x3 Inclusive
> x3e = extsel x3 Exclusive
>
> -- 3. MultiSelect -----------------------------------------
> data MultiSelect a = EmptySel | SingleSel a | MultiSel [a]
>
>
>
>
>
> On Wed, Aug 17, 2011 at 3:42 PM, Brent Yorgey <byor...@seas.upenn.edu>wrote:
>
>> On Tue, Aug 16, 2011 at 04:44:15PM +0200, Ertugrul Soeylemez wrote:
>> > Brent Yorgey <byor...@seas.upenn.edu> wrote:
>> >
>> > > > That's a bit of a contradiction, because you are using existentials
>> > > > yourself in your GADT.
>> > >
>> > > No, he isn't.
>> > >
>> > >    data BasicSelect a where
>> > >      SelectionNum :: Num a => a -> BasicSelect a
>> > >      SelectionStr :: Show a => a -> BasicSelect a
>> > >
>> > > 'a' shows up in the result type of both constructors, so there is no
>> > > existential quantification going on here.
>> >
>> > Oh, right.  How would one express this as an ADT?  Seems impossible to
>> > me.
>>
>> You cannot, with just Haskell 2010.  Strangely, if you try this:
>>
>>  data BasicSelect a = Num a  => SelectionNum a
>>                     | Show a => SelectionStr a
>>
>> you get this error (ghc 7.0.3):
>>
>>  Data constructor `SelectionNum' has existential type variables, or a
>>  context
>>    (Use -XExistentialQuantification or -XGADTs to allow this)
>>  In the definition of data constructor `SelectionNum'
>>  In the data type declaration for `BasicSelect'
>>
>> And enabling ExistentialQuantification makes the error go away!  So
>> apparently the ExistentialQuantification flag also enables type class
>> constraints on data constructors, even when no existential
>> quantification is involved.  Odd.
>>
>> -Brent
>>
>> _______________________________________________
>> 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/20110820/95761bd2/attachment-0001.htm>

------------------------------

Message: 3
Date: Sat, 20 Aug 2011 19:42:26 +0200
From: Manfred Lotz <manfred.l...@arcor.de>
Subject: [Haskell-beginners] Running a list of functions
To: beginners@haskell.org
Message-ID: <20110820194226.3d948...@arcor.com>
Content-Type: text/plain; charset=US-ASCII

Hi all,
Maybe a stupid question.

I have a list of functions [IO ()] and want to run those functions one
after another.

I did this 

     runList :: [IO ()] -> IO ()
     runList [] = return ()
     runList (f:fs) = do f
                         runList fs


which works fine.


However, I'm curious if there is a library function doing exactly this?



-- 
Manfred





------------------------------

Message: 4
Date: Sat, 20 Aug 2011 14:08:43 -0400
From: David Place <d...@vidplace.com>
Subject: Re: [Haskell-beginners] Running a list of functions
To: Manfred Lotz <manfred.l...@arcor.de>
Cc: beginners@haskell.org
Message-ID: <895a4397-aec5-4dd2-b247-8a57ed61f...@vidplace.com>
Content-Type: text/plain; charset=us-ascii

sequence_ :: Monad m => [m a] -> m ()
____________________
David Place   
Owner, Panpipes Ho! LLC
http://panpipesho.com
d...@vidplace.com



On Aug 20, 2011, at 1:42 PM, Manfred Lotz wrote:

> Hi all,
> Maybe a stupid question.
> 
> I have a list of functions [IO ()] and want to run those functions one
> after another.
> 
> I did this 
> 
>     runList :: [IO ()] -> IO ()
>     runList [] = return ()
>     runList (f:fs) = do f
>                         runList fs
> 
> 
> which works fine.
> 
> 
> However, I'm curious if there is a library function doing exactly this?
> 
> 
> 
> -- 
> Manfred
> 
> 
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners




------------------------------

Message: 5
Date: Sat, 20 Aug 2011 20:36:16 +0200
From: Manfred Lotz <manfred.l...@arcor.de>
Subject: Re: [Haskell-beginners] Running a list of functions
To: beginners@haskell.org
Message-ID: <20110820203616.59aeb...@arcor.com>
Content-Type: text/plain; charset=US-ASCII

On Sat, 20 Aug 2011 14:08:43 -0400
David Place <d...@vidplace.com> wrote:

> sequence_ :: Monad m => [m a] -> m ()

Thanks. I found sequence but I have to learn to add an underscore to a
funtion in order to see if this could be it.



-- 
Manfred





------------------------------

Message: 6
Date: Sat, 20 Aug 2011 20:21:48 +0100
From: Ozgur Akgun <ozgurak...@gmail.com>
Subject: Re: [Haskell-beginners] Running a list of functions
To: Manfred Lotz <manfred.l...@arcor.de>
Cc: beginners@haskell.org
Message-ID:
        <CALzazPBAiH29bZiGoUk2SG6e2CgWsg13WG9zLEoq=xcno9o...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi.

On 20 August 2011 19:36, Manfred Lotz <manfred.l...@arcor.de> wrote:

> On Sat, 20 Aug 2011 14:08:43 -0400
> David Place <d...@vidplace.com> wrote:
>
> > sequence_ :: Monad m => [m a] -> m ()
>
> Thanks. I found sequence but I have to learn to add an underscore to a
> funtion in order to see if this could be it.


Actually in this case sequence and sequence_ are identical. You have IO for
m, and () for a, so:

sequence  :: [IO ()] -> IO ()
sequence_ :: [IO ()] -> IO ()

Ozgur
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20110820/2cd4996b/attachment-0001.htm>

------------------------------

Message: 7
Date: Sat, 20 Aug 2011 15:31:18 -0400
From: Brandon Allbery <allber...@gmail.com>
Subject: Re: [Haskell-beginners] Running a list of functions
To: Ozgur Akgun <ozgurak...@gmail.com>
Cc: beginners@haskell.org, Manfred Lotz <manfred.l...@arcor.de>
Message-ID:
        <CAKFCL4WeqhMGiJpgWwoa1p9RKOMWpYGxsSn8zs8b=z=ynuc...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Sat, Aug 20, 2011 at 15:21, Ozgur Akgun <ozgurak...@gmail.com> wrote:

> sequence  :: [IO ()] -> IO ()
> sequence_ :: [IO ()] -> IO ()
>

sequence isn't ([IO ()] -> IO [()])?

-- 
brandon s allbery                                      allber...@gmail.com
wandering unix systems administrator (available)     (412) 475-9364 vm/sms
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20110820/09c85744/attachment.htm>

------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 38, Issue 37
*****************************************

Reply via email to