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:  Is haskell a good choice for someone,        who never
      programmed before? (Marc Weber)
   2. Re:  Is haskell a good choice for someone,        who never
      programmed before? (Daniel Fischer)
   3. Re:  Re: multreplace (Patrick LeBoutillier)
   4.  Re: Is haskell a good choice for someone, who never
      programmed before? (prad)
   5. Re:  Re: multreplace (Daniel Fischer)
   6. Re:  Is haskell a good choice for someone, who    never
      programmed before? (edgar klerks)
   7. Re:  Re: Is haskell a good choice for someone,    who never
      programmed before? (Marc Weber)
   8. Re:  upgrade Hackage show to QuickCheck 2 for     lambdabot
      (Antoine Latter)


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

Message: 1
Date: Fri, 02 Jul 2010 22:59:22 +0200
From: Marc Weber <marco-owe...@gmx.de>
Subject: Re: [Haskell-beginners] Is haskell a good choice for someone,
        who never programmed before?
To: beginners <beginners@haskell.org>
Message-ID: <1278104050-sup-5...@nixos>
Content-Type: text/plain; charset=UTF-8

Hi Edgar

If he doesn't know any other languages it may be even easier to him.
Everyone who learned Basic and wants to start with Haskell has to change
his mind.

That said the only reason not to learn Haskell is
- there are existing solutions which work
- you want to use existing Java / .net libraries
- You want to target Flash or JavaScript only
  (or something like that)

Nothing of that applies.
I'd even say Haskell is nice for beginning because if something compiles
it usually works (unless you hit advanced issues).

> but I don't want to scare him away.
Either he is scared or he is not. That won't depend on Haskell IMHO.

> And mathematics, where to start?
Ask him what he is interested in most. Start with that. Ask him what he
wants to do ..
If you have answers to that question Haskellers can help you easier and
point you in the right direction.

Greetings
Marc Weber


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

Message: 2
Date: Fri, 2 Jul 2010 23:05:21 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Is haskell a good choice for someone,
        who never programmed before?
To: beginners@haskell.org
Message-ID: <201007022305.21817.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="utf-8"

On Friday 02 July 2010 22:59:22, Marc Weber wrote:
> If you have answers to that question Haskellers can help you easier and
> point you in the right direction.

That reminds me of another point: The community. You won't easily find a 
community nearly as helpful as the Haskell community.


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

Message: 3
Date: Fri, 2 Jul 2010 17:15:22 -0400
From: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Subject: Re: [Haskell-beginners] Re: multreplace
To: beginners@haskell.org
Message-ID:
        <aanlktiltfguvw-69rwhpumrlkw7bliiz1fcpkkl41...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

> multRepl = foldl (uncurry . replace)

Actually I've been thinking about this and I can't quite figure out
how it works:

I understand the type of replace is

  replace :: (Eq a) => [a] -> [a] -> [a] -> [a]

but I can't figure out how the type of (uncurry . replace) becomes

  uncurry . replace :: (Eq a) => [a] -> ([a], [a]) -> [a]

?


Patrick

-- 
=====================
Patrick LeBoutillier
Rosemère, Québec, Canada


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

Message: 4
Date: Fri, 2 Jul 2010 14:28:40 -0700
From: prad <p...@towardsfreedom.com>
Subject: [Haskell-beginners] Re: Is haskell a good choice for someone,
        who never programmed before?
To: beginners@haskell.org
Message-ID: <20100702142840.14790...@gom>
Content-Type: text/plain; charset=US-ASCII

On Fri, 2 Jul 2010 22:36:46 +0200
edgar klerks <edgar.kle...@gmail.com> wrote:

> Is haskell a good choice for someone, who never programmed before?
>
as a recent haskell newbie myself i would say definitely yes! my minor 
programming experience is just getting in the way.

marc weber wrote:
"Everyone who learned Basic and wants to start with Haskell has to
change his mind."

my god yes!
i find i'm actually having to learn programming concepts properly. i
can't just sit down and create a script through trial and error. :D
a mind replacement would likely be better for me than a simple change,
but i'll settle for the latter for now.


daniel fischer wrote:
"You won't easily find a community nearly as helpful as the Haskell
community."

having been on several excellent boards for various computer oriented
issues, i can with, without hesitation, state that this community is
the best i've come across.

when i ask a question, i'm not just given an answer ... i'm provided
with a technical paper with tips, ideas, details unparallelled to
anything else i've seen on any forum i've frequented over the past
decade. (actually, edgar you are a case in point, since you were the
first to assist me).

the entire spirit is different here!

-- 
In friendship,
prad

                                      ... with you on your journey
Towards Freedom
http://www.towardsfreedom.com (website)
Information, Inspiration, Imagination - truly a site for soaring I's




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

Message: 5
Date: Fri, 2 Jul 2010 23:30:18 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Re: multreplace
To: beginners@haskell.org
Message-ID: <201007022330.19195.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

On Friday 02 July 2010 23:15:22, Patrick LeBoutillier wrote:
> > multRepl = foldl (uncurry . replace)
>
> Actually I've been thinking about this and I can't quite figure out
> how it works:
>
> I understand the type of replace is
>
>   replace :: (Eq a) => [a] -> [a] -> [a] -> [a]
>
> but I can't figure out how the type of (uncurry . replace) becomes
>
>   uncurry . replace :: (Eq a) => [a] -> ([a], [a]) -> [a]
>
> ?

let's make it

foo :: a -> b -> c -> d

to not get confused by the fact that replace's arguments and result all 
have the same type.

So, what does uncurry . foo do?
Well, (f . g) x = f (g x), so when we apply (uncurry . foo) to an argument 
x, we get

uncurry (foo x)

Now, x is the first argument of foo, so x :: a, and

(foo x) :: b -> c -> d

That means (foo x) has just the type uncurry expects, hence

uncurry (foo x) :: (b, c) ->  d

Now write uncurry (foo x) again as

(uncurry . foo) x :: (b, c) -> d

and remove x again, so

(uncurry . foo) :: a -> (b, c) -> d

finally, remember that foo is actually replace and hence all four type 
variables stand for the same list type (with an Eq constraint).

>
>
> Patrick



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

Message: 6
Date: Fri, 2 Jul 2010 23:32:55 +0200
From: edgar klerks <edgar.kle...@gmail.com>
Subject: Re: [Haskell-beginners] Is haskell a good choice for someone,
        who     never programmed before?
To: Daniel Fischer <daniel.is.fisc...@web.de>, marco-owe...@gmx.de
Cc: beginners@haskell.org
Message-ID:
        <aanlktil70scnz-_kk-yofu0epcevooznlxpm68wby...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi Marc and Daniel,

On Fri, Jul 2, 2010 at 10:50 PM, Daniel Fischer <daniel.is.fisc...@web.de>wrote:

> On Friday 02 July 2010 22:36:46, edgar klerks wrote:
> > Hi All,
> >
> > I have a question. A friend of mine wants to learn a programming
> > language, because we work together. He studied economics and is busy in
> > the financial sector. I understood Haskell is used there pretty much, so
> > he got interested in it. But is haskell a good language for someone, who
> > never even tried a language like basic?
>
> Actually, the rumour goes that Haskell is easier to learn if your brain
> hasn't been conditioned by years of imperative programming.
>
>
I know, I don't want to be sour, but when I started to learn haskell it
almost hurt. I took me a couple of months to loose the imperative style of
thought. I have a physics background and picked up programming along the
way. For some reason they never used functional languages. Such a pity.

But now it is backwards, every time I have to go back to imperative style or
something alike I am kinda bored. Luckily I slowly start to find it easier
to implement stuff in Haskell instead of in other languages.

But it is true, that you have to unlearn yourself. And for some reason I
feel functional languages have the future.

I think haskell has some points over lisp, because there is a lot of noise
in the latter with the ()'s.

Marc Weber <marco-owe...@gmx.de> wrote:

Ask him what he is interested in most. Start with that. Ask him what he
> wants to do ..
> If you have answers to that question Haskellers can help you easier and
> point you in the right direction.
>
> He is interested in econometrics, I don't know much about it. I understood
they use a lot of linear algebra. I have some books and sylabi about that,
but more pointed towards physics.

On Friday 02 July 2010 22:59:22, Marc Weber wrote:
> If you have answers to that question Haskellers can help you easier and
> point you in the right direction.

That reminds me of another point: The community. You won't easily find a
community nearly as helpful as the Haskell community.

That is true, this one of the most helpful communities I encountered.
Haskell programmers seems also to be more knowledgeable than other
programmers in maths.

I bought 2 books now:

The road to haskell, logic and mathematics.
Simon Thompson's Craft of Functional Programming

And I have Real world haskell lying around, but I lend it to someone else. I
am "poisoning" my environment with haskell at the moment. :) I am a start up
in the financial business. And one of the further goals is to develop
financial tools for small and middle sized business. (Now we have some
projects, which should induce a cash flow. Hopefully) Therefore the guy has
to understand, what Haskell can do.

I shall try to find out, what direction of mathematics interest him the
most.

Tnx for your help!

Edgar
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100702/66aa93ad/attachment-0001.html

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

Message: 7
Date: Sat, 03 Jul 2010 00:32:38 +0200
From: Marc Weber <marco-owe...@gmx.de>
Subject: Re: [Haskell-beginners] Re: Is haskell a good choice for
        someone,        who never programmed before?
To: beginners <beginners@haskell.org>
Message-ID: <1278109831-sup-9...@nixos>
Content-Type: text/plain; charset=UTF-8

If you'd ask me only I'd eventually say that you should know both worlds
today .. At least a little bit. It always depends on the use case.

Marc Weber


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

Message: 8
Date: Fri, 2 Jul 2010 18:09:59 -0500
From: Antoine Latter <aslat...@gmail.com>
Subject: Re: [Haskell-beginners] upgrade Hackage show to QuickCheck 2
        for     lambdabot
To: Mark Wright <markwri...@internode.on.net>
Cc: beginners@haskell.org, haskell mailing list
        <haskell-c...@haskell.org>
Message-ID:
        <aanlktilzdbxac_arwbydvfog8cokpapgnc7lytofr...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Including the café.

On Jul 2, 2010 8:49 AM, "Mark Wright" <markwri...@internode.on.net> wrote:

Hi,

I'm trying to upgrade Hackage show to QuickCheck 2, after
applying the diffs below (which may not be correct, since I am
a beginner), I am left which this error message:

runghc ./Setup.hs build
Preprocessing library show-0.3.4...
Building show-0.3.4...
[4 of 4] Compiling ShowQ            ( ShowQ.hs, dist/build/ShowQ.o )

ShowQ.hs:104:20: Not in scope: `generate'

Compilation exited abnormally with code 1 at Fri Jul  2 23:07:17

The error occurs in this method:

tests :: Gen Result -> StdGen -> Int -> Int -> [[String]] -> IO String
tests gen rnd0 ntest nfail stamps
 | ntest == 500  = done "OK, passed" ntest stamps
 | nfail == 1000 = done "Arguments exhausted after" ntest stamps
 | otherwise = case ok result of
      Nothing    -> tests gen rnd1 ntest (nfail+1) stamps
      Just True  -> tests gen rnd1 (ntest+1) nfail (stamp result:stamps)
      Just False -> return $ "Falsifiable, after "
                              ++ show ntest
                              ++ " tests:\n"
                              ++ reason result
  where
     result      = generate (((+ 3) . (`div` 2)) ntest) rnd2 gen
     (rnd1,rnd2) = split rnd0

The QuickCheck 1 generate method is near the bottom this page:

http://hackage.haskell.org/packages/archive/QuickCheck/1.2.0.0/doc/html/Test-QuickCheck.html

but I can not find generate in QuickCheck 2.  I am wondering if
you have any ideas on how to fix it?

I'm trying to package lambdabot on Solaris.  I have already packaged
the Haskell Platform and about 90 packages, they are in:

http://pkgbuild.sourceforge.net/spec-files-extra/

Thanks very much, Mark

here are the diffs:

goanna% diff -wc show-0.3.4-orig/ShowQ.hs show-0.3.4/ShowQ.hs
*** show-0.3.4-orig/ShowQ.hs    Wed Jan 20 11:24:11 2010
--- show-0.3.4/ShowQ.hs Fri Jul  2 23:07:13 2010
***************
*** 12,22 ****
--- 12,25 ----

 import qualified Test.SmallCheck (smallCheck, Testable)
 import Test.QuickCheck
+ import Test.QuickCheck.Arbitrary
 import Data.Char
 import Data.List
 import Data.Word
 import Data.Int
 import System.Random
+ import Control.Exception (evaluate)
+ import Test.QuickCheck.Property (ok, stamp)

 type T = [Int]
 type I = Int
***************
*** 23,36 ****
--- 26,45 ----

 instance Arbitrary Char where
     arbitrary     = choose (minBound, maxBound)
+
+ instance CoArbitrary Char where
     coarbitrary c = variant (ord c `rem` 4)

 instance Arbitrary Word8 where
     arbitrary = choose (minBound, maxBound)
+
+ instance CoArbitrary Word8 where
     coarbitrary c = variant (fromIntegral ((fromIntegral c) `rem` 4))

 instance Arbitrary Ordering where
     arbitrary     = elements [LT,EQ,GT]
+
+ instance CoArbitrary Ordering where
     coarbitrary LT = variant 1
     coarbitrary EQ = variant 2
     coarbitrary GT = variant 0
***************
*** 37,42 ****
--- 46,53 ----

 instance Arbitrary Int64 where
   arbitrary     = sized $ \n -> choose (-fromIntegral n,fromIntegral n)
+
+ instance CoArbitrary Int64 where
   coarbitrary n = variant (fromIntegral (if n >= 0 then 2*n else 2*(-n) +
1))

 instance (Integral a, Arbitrary a) => Arbitrary (Ratio a) where
***************
*** 48,53 ****
--- 59,65 ----
                             else (b % a)
                          else (a % b)

+ instance (Integral a, CoArbitrary a) => CoArbitrary (Ratio a) where
   coarbitrary m = variant (fromIntegral $ if n >= 0 then 2*n else 2*(-n) +
1)
     where n = numerator m

***************
*** 87,93 ****
        Just False -> return $ "Falsifiable, after "
                                ++ show ntest
                                ++ " tests:\n"
!                                ++ unlines (arguments result)
    where
       result      = generate (((+ 3) . (`div` 2)) ntest) rnd2 gen
       (rnd1,rnd2) = split rnd0
--- 99,105 ----
        Just False -> return $ "Falsifiable, after "
                                ++ show ntest
                                ++ " tests:\n"
!                                ++ reason result
    where
       result      = generate (((+ 3) . (`div` 2)) ntest) rnd2 gen
       (rnd1,rnd2) = split rnd0
goanna%

_______________________________________________
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/20100702/02977a4b/attachment.html

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

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


End of Beginners Digest, Vol 25, Issue 8
****************************************

Reply via email to