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:  creating a complement for a given given test         generator.
      (Alexander Dunlap)
   2. Re:  some insights into functional programming (Magnus Therning)
   3. Re:  brief example of ZipList? (Thomas Davie)
   4.  Re: Closure (Daniel Bastos)
   5.  some terminology (Michael P Mossey)
   6. Re:  some terminology (Brandon S. Allbery KF8NH)
   7.  Re: some terminology (Heinrich Apfelmus)
   8.  function parameter types after flip (Robert Ziemba)
   9. Re:  function parameter types after flip (Daniel Seidel)


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

Message: 1
Date: Mon, 10 Aug 2009 19:08:25 -0700
From: Alexander Dunlap <alexander.dun...@gmail.com>
Subject: Re: [Haskell-beginners] creating a complement for a given
        given test      generator.
To: Srikanth K <k.srikanth.opensou...@gmail.com>
Cc: beginners <beginners@haskell.org>
Message-ID:
        <57526e770908101908j15285e34l999b7e25f9831...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Mon, Aug 10, 2009 at 4:20 PM, Srikanth
K<k.srikanth.opensou...@gmail.com> wrote:
> Hi,
>    I am trying to use the quickcheck to generate some test-data to test an
> api, along the lines of
> http://www.haskell.org/haskellwiki/QuickCheck_as_Test_Set_Generator.
>
> For the sake of example, I choose the following function to test
>
>
> data Result = Valid | Invalid
> api_under_test :: (Int,Int) ->  Result
> api_under_test (x,y)
>    | (x == 1)  =   Valid
>    | otherwise = Invalid
>
>
> I had the following valid-generator which worked quite easily(trivial)
>
> validCombinations= [ (1,1), (1,2) ]
> validGen = elements validCombinations
> prop_valid_api_under_test =
>     forAll validGen $ \xs ->
>          (api_under_test xs) == (Valid)
>
> Now, I want to have a complement to state:
>      forall tuples not in validCombinations, the api_under_test must 
> return
> "Invalid".  (i.e.)
>
> prop_invalid_api_under_test =
>     forAll invalidGen $ \xs ->
>         (api_under_test xs) == (Invalid)
>
>
>
> However, inspite of all  googling, and reading the various docs including
> quickcheck, I am at loss on how I can elegantly define the "invalidGen"
> generator.  One possible way I can think is to have a customized generator,
> that would generate two random numbers and then look up the tuple generated
> against the validCombinations list.
>
> However, I feel there just might be a better way of solving this.
>
> Any suggestion on how I should be trying to solve this.
>
> - Srikanth
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>

The way I would do this is (untested)

prop_invalid_api_under_test xs = not (xs `elem` validCombinations) ==>
api_under_test xs = Invalid

using the (==>) function from QuickCheck.

Alex


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

Message: 2
Date: Tue, 11 Aug 2009 06:51:42 +0100
From: Magnus Therning <mag...@therning.org>
Subject: Re: [Haskell-beginners] some insights into functional
        programming
To: Michael P Mossey <m...@alumni.caltech.edu>
Cc: beginners <beginners@haskell.org>
Message-ID: <4a8106ee.2060...@therning.org>
Content-Type: text/plain; charset="utf-8"

Michael P Mossey wrote:
> Thanks for the ideas, Adam. I still have a few questions.
> 
> Adam Bergmark wrote:
>> The reason my is available in the lambda \x -> my >>= \y -> W (x+y) has to
>> do with scoping rules, Haskell (and almost all programming languages) use
>> static scoping, meaning a variable defined in an outer function is
>> available in the inner function, for instance, (\a -> \b -> (a,b)) 1 2 will
>> evauate to (1,2) since a is bound to 1 in the outer lambda, and the inner
>> one can refer to the outer one, if instead you write (\a -> \a -> (a,a)) 1
>> 2 the result will be (2,2) since the innermost a will be used (no ambiguity
>> here, but  if shadowing is done by accident it can be hard to find the
>> error).
> 
> 
> Because the lambda is executed by the implementation of >>=, doesn't the
> concept closure still apply? That value of 'my' has to "get into" the other
> routine.

I think you are both right.  AFAIU Adam comments on *visibility* of the
variables, while you look more at the fact that you pass the lambda as an
argument to (>>=).  The lambda can "see" the variable my due to scoping, and
(>>=) can trigger evaluation of the lambda due to closures.

I'm looking forward to be corrected by someone who knows more about this than
I do.

/M

-- 
Magnus Therning                        (OpenPGP: 0xAB4DFBA4)
magnus@therning.org          Jabber: magnus@therning.org
http://therning.org/magnus         identi.ca|twitter: magthe

-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 197 bytes
Desc: OpenPGP digital signature
Url : 
http://www.haskell.org/pipermail/beginners/attachments/20090811/303059f8/signature-0001.bin

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

Message: 3
Date: Tue, 11 Aug 2009 07:52:40 +0200
From: Thomas Davie <tom.da...@gmail.com>
Subject: Re: [Haskell-beginners] brief example of ZipList?
To: Michael P Mossey <m...@alumni.caltech.edu>
Cc: beginners <beginners@haskell.org>
Message-ID: <d2cc6290-e892-45d1-8850-8c73c1511...@gmail.com>
Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes

z1 :: ZipList (Int -> Int)
z1 = ZipList [succ,succ]

z2 :: ZipList Int
z2 = ZipList [1,2]

z3 :: ZipList Int
z3 = z1 <*> z2

Bob

On 11 Aug 2009, at 02:08, Michael P Mossey wrote:

> Can someone give me a brief example using ZipList? I want to do  
> something like
>
> z1 :: [Int -> Int]
> z1 = [succ,succ]
>
> z2 :: [Int]
> z2 = [1,2]
>
> z3 = z1 <*> z2
>
> But don't know to get it to regard these as ZipLists and not regular  
> lists.
>
> This is purely for learning purposes. No application in mind.
>
> -Mike
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners



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

Message: 4
Date: Wed, 12 Aug 2009 05:21:24 +0000 (UTC)
From: Daniel Bastos <dbasto...@toledo.com>
Subject: [Haskell-beginners] Re: Closure
To: beginners@haskell.org
Message-ID: <h5tjgk$6d...@ger.gmane.org>

In article <20090729202442.ga8...@seas.upenn.edu>,
Brent Yorgey wrote:

> With that said, on some level the idea of a closure is really just an
> implementation detail---I wouldn't say that understanding it is of
> fundamental importance in learning Haskell.  But learning things never
> hurts (except when it does).

So it sounds correct to say that a closure is a function that brings
an environment with it, such as variables defined outside of it. 

With this ability, we can construct functions on the fly because a
function can return a closure which is amended and, say, returned
again another closure more fully specified. 



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

Message: 5
Date: Wed, 12 Aug 2009 18:59:16 -0700
From: Michael P Mossey <m...@alumni.caltech.edu>
Subject: [Haskell-beginners] some terminology
To: beginners <beginners@haskell.org>
Message-ID: <4a837374.2050...@alumni.caltech.edu>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

I was looking at some code, saw a variable x, and said to myself, "Ah that 
variable is a monad." Then I realized "Monad" is the name of a type class. So 
maybe x should be called "an instance of a Monad." I think the word "instance" 
in this case is OO-like; but in Haskell "instance" refers to a type that is an 
instance of a type class. Or maybe it can refer to both? And Monad is a type 
class, not a type. Maybe I need the phrase "monadic type" to refer to an 
instance of a type class. So maybe x is just "a variable of a monadic type"?

Thanks,
Mike


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

Message: 6
Date: Wed, 12 Aug 2009 22:04:40 -0400
From: "Brandon S. Allbery KF8NH" <allb...@ece.cmu.edu>
Subject: Re: [Haskell-beginners] some terminology
To: Michael P Mossey <m...@alumni.caltech.edu>
Cc: beginners <beginners@haskell.org>
Message-ID: <f612113e-9b1e-41f3-97dd-082a0ebb6...@ece.cmu.edu>
Content-Type: text/plain; charset="us-ascii"

On Aug 12, 2009, at 21:59 , Michael P Mossey wrote:
> I was looking at some code, saw a variable x, and said to myself,  
> "Ah that variable is a monad." Then I realized "Monad" is the name  
> of a type class. So maybe x should be called "an instance of a  
> Monad." I think the word "instance" in this case is OO-like; but in  
> Haskell "instance" refers to a type that is an instance of a type  
> class. Or maybe it can refer to both? And Monad is a type class, not  
> a type. Maybe I need the phrase "monadic type" to refer to an  
> instance of a type class. So maybe x is just "a variable of a  
> monadic type"?


Strictly speaking, yes.  In practice the common shorthand is "in the X  
monad" or just "in X".

-- 
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university    KF8NH


-------------- next part --------------
A non-text attachment was scrubbed...
Name: PGP.sig
Type: application/pgp-signature
Size: 195 bytes
Desc: This is a digitally signed message part
Url : 
http://www.haskell.org/pipermail/beginners/attachments/20090812/8d3aff21/PGP-0001.bin

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

Message: 7
Date: Thu, 13 Aug 2009 11:14:17 +0200
From: Heinrich Apfelmus <apfel...@quantentunnel.de>
Subject: [Haskell-beginners] Re: some terminology
To: beginners@haskell.org
Message-ID: <h60lhc$fv...@ger.gmane.org>
Content-Type: text/plain; charset=ISO-8859-1

Michael P Mossey wrote:
> I was looking at some code, saw a variable x, and said to myself, "Ah
> that variable is a monad." Then I realized "Monad" is the name of a type
> class. So maybe x should be called "an instance of a Monad." I think the
> word "instance" in this case is OO-like; but in Haskell "instance"
> refers to a type that is an instance of a type class. Or maybe it can
> refer to both? And Monad is a type class, not a type. Maybe I need the
> phrase "monadic type" to refer to an instance of a type class. So maybe
> x is just "a variable of a monadic type"?

One common nomenclature is to say that  x  is a "monadic action" or just
 "action" for short. That's the terminology used in the

  Simon Peyton Jones.  Tackling the awkward squad.
  http://research.microsoft.decenturl.com/awkward-squad

tutorial.


Regards,
apfelmus

--
http://apfelmus.nfshost.com



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

Message: 8
Date: Thu, 13 Aug 2009 08:25:07 -0700
From: Robert Ziemba <rzie...@gmail.com>
Subject: [Haskell-beginners] function parameter types after flip
To: beginners@haskell.org
Message-ID:
        <65135790908130825o601a1d5ct6a605f276ce61...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Can anyone help me understand the behavior of the following
expressions in ghci?  I was trying to construct a flipped function
'elem' that would accept a list of characters first but I ran into
this problem with the type signature. Thank you.

Prelude Data.List Data.Char> :t elem
elem :: (Eq a) => a -> [a] -> Bool              -- OK
Prelude Data.List Data.Char> :t (flip elem)
(flip elem) :: (Eq a) => [a] -> a -> Bool       -- OK this is what I want
Prelude Data.List Data.Char> let fElem = (flip elem)
Prelude Data.List Data.Char> :t fElem
fElem :: [()] -> () -> Bool                           -- ?? Function
will not accept a [Char]


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

Message: 9
Date: Thu, 13 Aug 2009 17:35:22 +0200
From: Daniel Seidel <seid...@tcs.inf.tu-dresden.de>
Subject: Re: [Haskell-beginners] function parameter types after flip
To: Robert Ziemba <rzie...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <4a8432ba.1090...@tcs.inf.tu-dresden.de>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Robert Ziemba wrote:
> Can anyone help me understand the behavior of the following
> expressions in ghci?  I was trying to construct a flipped function
> 'elem' that would accept a list of characters first but I ran into
> this problem with the type signature. Thank you.
> 
> Prelude Data.List Data.Char> :t elem
> elem :: (Eq a) => a -> [a] -> Bool              -- OK
> Prelude Data.List Data.Char> :t (flip elem)
> (flip elem) :: (Eq a) => [a] -> a -> Bool       -- OK this is what I want
> Prelude Data.List Data.Char> let fElem = (flip elem)
> Prelude Data.List Data.Char> :t fElem
> fElem :: [()] -> () -> Bool                           -- ?? Function
> will not accept a [Char]

I think its due to the monomorphism restriction.
If you define it like

Prelude> let fElem x = (flip elem) x
Prelude> :t fElem
fElem :: (Eq a) => [a] -> a -> Bool

it works. For the details look at

http://haskell.org/haskellwiki/Monomorphism_restriction

... or wait for another answer (which I think will come).

Daniel.


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



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

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


End of Beginners Digest, Vol 14, Issue 7
****************************************

Reply via email to