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:  Sqlite3 - INSERT statement question (Patrick Lynch)
   2. Re:  Lujvo forming with cmavo rafsi (Brent Yorgey)
   3. Re:  Sqlite3 - INSERT statement question (Brent Yorgey)
   4. Re:  Lujvo forming with cmavo rafsi (Amy de Buitl?ir)
   5.  gtk2hs [GIMP ToolKit] (Patrick Lynch)
   6. Re:  Lujvo forming with cmavo rafsi (Alex Rozenshteyn)
   7. Re:  Informal proof of bijective mapping between Naturals and
      Natural pairs (Lyndon Maydwell)


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

Message: 1
Date: Thu, 03 Feb 2011 16:37:19 -0500
From: "Patrick Lynch" <kmandpjly...@verizon.net>
Subject: Re: [Haskell-beginners] Sqlite3 - INSERT statement question
To: "Brent Yorgey" <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID: <692E3A18977A4762AFEF454471AB194F@UserPC>
Content-Type: text/plain; format=flowed; charset=iso-8859-1;
        reply-type=original

...BTW: do you know if there is a good tutorial on Haskell and Sqlite3....
...I'm pretty good at SQL, and if I can get thru Chapters 21, 22 and 23 in 
"Real World Haskell"...I'd like to take a careful look at one...
...If there isn't a good tutorial available, I think I'll write one initally 
for my own use and if it is any good I'll share it with the group...

...Overall, I found the installation of Sqlite3 on Windows Vista to be a 
major challenge - I still don't think that I have the procedure to do it 
again...but I need to install it on my Mac...not looking forward to 
that...I've been fighting with the Apple support people already...bummer...

...As for installing gtk2hs, I'm getting nowhere with this...I'll tackle it 
next week...

Thanks again for your help...I hope that I can repay your kindness 
someday...

Ciao

----- Original Message ----- 
From: "Brent Yorgey" <byor...@seas.upenn.edu>
To: "Patrick Lynch" <kmandpjly...@verizon.net>
Cc: <beginners@haskell.org>
Sent: Thursday, February 03, 2011 3:22 PM
Subject: Re: [Haskell-beginners] Sqlite3 - INSERT statement question


> On Thu, Feb 03, 2011 at 02:09:41PM -0500, Patrick Lynch wrote:
>> ...looks good, thank you - see following: [note: the '1' on the 2nd
>> line indicates a successful command execution] --
>>
>> Prelude Database.HDBC Database.HDBC.Sqlite3> run conn "INSERT INTO
>> test VALUES (?, ?)" [toSql (0::Int), toSql ("zero"::[Char])]
>> 1
>
> Great. Note that the ::[Char] annotation is not strictly necessary,
> since the type of "zero" is unambiguous*.  But of course it can't hurt
> anything.
>
> -Brent
>
> * Well, unless you have enabled -XOverloadedStrings... 




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

Message: 2
Date: Thu, 3 Feb 2011 16:42:45 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Lujvo forming with cmavo rafsi
To: beginners@haskell.org
Message-ID: <20110203214245.ga22...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Thu, Feb 03, 2011 at 04:32:04PM -0500, Alex Rozenshteyn wrote:
> 
> mea culpa

Hmm, more lojban, eh? ;)  Seriously, no need to apologize, it was an
innocent mistake and we all do stuff like this on occasion.  At least
I know I do.

> I hope you all got a good laugh at my expense.

The funniest part (to me) was that you didn't realize what you had
done even when lots of people on the "lojban-beginners" mailing list
were very confused. =)

Anyway, since we are already off-topic, I will highly recommend the
book "Being Wrong: Adventures in the Margin of Error", by Kathryn
Schulz (for everyone, not just you) which gives some fascinating
perspectives on incidents such as this one.

-Brent

> 
> On Thu, Feb 3, 2011 at 3:21 PM, Brent Yorgey <byor...@seas.upenn.edu> wrote:
> 
> > On Thu, Feb 03, 2011 at 02:17:36PM -0500, Alex Rozenshteyn wrote:
> > > I think brent's reply was making fun of me and didn't have much meaning
> > > beyond that.
> >
> > Yes, I was poking some light-hearted fun at you for sending
> > (mistakenly, I presume) a lojban question to a Haskell mailing
> > list. =)
> >
> > -Brent
> >
> > _______________________________________________
> > Beginners mailing list
> > Beginners@haskell.org
> > http://www.haskell.org/mailman/listinfo/beginners
> >
> 
> 
> 
> -- 
>           Alex R

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




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

Message: 3
Date: Thu, 3 Feb 2011 16:49:24 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Sqlite3 - INSERT statement question
To: Patrick Lynch <kmandpjly...@verizon.net>
Cc: beginners@haskell.org
Message-ID: <20110203214924.gb22...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Thu, Feb 03, 2011 at 04:37:19PM -0500, Patrick Lynch wrote:
> ...BTW: do you know if there is a good tutorial on Haskell and Sqlite3....
> ...I'm pretty good at SQL, and if I can get thru Chapters 21, 22 and
> 23 in "Real World Haskell"...I'd like to take a careful look at
> one...
> ...If there isn't a good tutorial available, I think I'll write one
> initally for my own use and if it is any good I'll share it with the
> group...

I don't know, but if Google doesn't turn anything up, then there
probably isn't.  If you wrote one, I'm sure others would find it
useful -- even a tutorial that isn't any good is a much better place
to start than no tutorial at all!  Just put it on a wiki and let
others improve it.

> Thanks again for your help...I hope that I can repay your kindness
> someday...

A beer should suffice! =)

-Brent



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

Message: 4
Date: Thu, 3 Feb 2011 22:13:00 +0000
From: Amy de Buitl?ir <a...@nualeargais.ie>
Subject: Re: [Haskell-beginners] Lujvo forming with cmavo rafsi
To: Brent Yorgey <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID:
        <AANLkTi=B_q8U61gqyQz=z0kvqqta0skv3mnhxpf2s...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

To me the funniest part was that it reminded me of when I first started
learning Haskell and reading this list. Most of the messages on this list
were just as incomprehensible (to me). In fact, until I noticed the
reference to TV tropes, I assumed this was something to do with category
theory or some other area of maths that I don't know anything about yet.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20110203/d748167d/attachment-0001.htm>

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

Message: 5
Date: Thu, 03 Feb 2011 17:32:48 -0500
From: "Patrick Lynch" <kmandpjly...@verizon.net>
Subject: [Haskell-beginners] gtk2hs [GIMP ToolKit]
To: <beginners@haskell.org>
Message-ID: <157C22E9F4F44B769CB65BBFB22B7017@UserPC>
Content-Type: text/plain; charset="iso-8859-1"

...I'm going to try to install gtk2hs again...
...I'll be using the link http://www.haskell.org/haskellwiki/Gtk2Hs
...I'd appreciate any help...
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20110203/dccd5e11/attachment-0001.htm>

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

Message: 6
Date: Thu, 3 Feb 2011 17:48:57 -0500
From: Alex Rozenshteyn <rpglove...@gmail.com>
Subject: Re: [Haskell-beginners] Lujvo forming with cmavo rafsi
To: Brent Yorgey <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID:
        <aanlktinjwq0jn_vspy-wcn6zhbuvkytb3iqx1vjrs...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

>From my perspective, one person was just being a bit silly at me, and one
person had no idea what I was talking about (I assumed it was someone who
was subscribed but hadn't been actively learning).

Then I didn't check my email for the next three messages.

So it wasn't exactly "lots of people".

On Thu, Feb 3, 2011 at 4:42 PM, Brent Yorgey <byor...@seas.upenn.edu> wrote:

> On Thu, Feb 03, 2011 at 04:32:04PM -0500, Alex Rozenshteyn wrote:
> >
> > mea culpa
>
> Hmm, more lojban, eh? ;)  Seriously, no need to apologize, it was an
> innocent mistake and we all do stuff like this on occasion.  At least
> I know I do.
>
> > I hope you all got a good laugh at my expense.
>
> The funniest part (to me) was that you didn't realize what you had
> done even when lots of people on the "lojban-beginners" mailing list
> were very confused. =)
>
> Anyway, since we are already off-topic, I will highly recommend the
> book "Being Wrong: Adventures in the Margin of Error", by Kathryn
> Schulz (for everyone, not just you) which gives some fascinating
> perspectives on incidents such as this one.
>
> -Brent
>
> >
> > On Thu, Feb 3, 2011 at 3:21 PM, Brent Yorgey <byor...@seas.upenn.edu>
> wrote:
> >
> > > On Thu, Feb 03, 2011 at 02:17:36PM -0500, Alex Rozenshteyn wrote:
> > > > I think brent's reply was making fun of me and didn't have much
> meaning
> > > > beyond that.
> > >
> > > Yes, I was poking some light-hearted fun at you for sending
> > > (mistakenly, I presume) a lojban question to a Haskell mailing
> > > list. =)
> > >
> > > -Brent
> > >
> > > _______________________________________________
> > > Beginners mailing list
> > > Beginners@haskell.org
> > > http://www.haskell.org/mailman/listinfo/beginners
> > >
> >
> >
> >
> > --
> >           Alex R
>
> > _______________________________________________
> > 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
>



-- 
          Alex R
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20110203/6acdcbd2/attachment.htm>

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

Message: 7
Date: Fri, 4 Feb 2011 08:06:59 +0800
From: Lyndon Maydwell <maydw...@gmail.com>
Subject: Re: [Haskell-beginners] Informal proof of bijective mapping
        between Naturals and Natural pairs
To: Brent Yorgey <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID:
        <aanlktinisjev9_bc-guanxayyskajd-bxrcpsapud...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

Thanks for your feedback Brent!

The diagonal approach seems like it is much cleaner to me. There are
certainly many less concepts required to understand the proof.

I agree completely about the variable names, and the removal of 'y' by
currying. I should really take the time to tidy things like this up
:-)

One advantage I can think of for my system is that you could split the
primes not just into even/odd, but any number of lists. This would
mean that it is then trivial to apply the same approach to tuples of
any size. I guess that the equivalent progression in the diagonal
approach would be to use higher-dimensional spaces, and take 'plane'
intersections. Although with this approach the proof could probably be
expressed as succinctly, it would probably get very messy in terms of
implementation.

Michael Katelman also linked me to
http://en.wikipedia.org/wiki/Pairing_function, which seems very
relevant.

Probably the most trivial higher-arity aproach would just be a
'exponentiation' of any proven pairing function, with the right or
left or both tuple element(s) representing another tuple, rather than
just a number.

I was also wondering if the prime approach could be related to
cryptography in some way.

Anyway. Thanks again!

On Fri, Feb 4, 2011 at 5:14 AM, Brent Yorgey <byor...@seas.upenn.edu> wrote:
> Hi Lyndon,
>
> On Tue, Feb 01, 2011 at 12:43:14AM +0800, Lyndon Maydwell wrote:
>> Hi Beginners.
>>
>> I was musing over weather Naturals were isomorphic to Natural pairs
>> and wrote the following "proof".
>
> Indeed they are. ?This is a classic result first due to Cantor, who
> came at it from the point of view of discovering that the natural
> numbers have the same cardinality (size) as the positive rational
> numbers (which can be thought of as pairs of naturals).
>
> Your proof is great -- it has the advantage of working on rather
> elementary principles.
>
> However, there are many such bijections. ?Here's another one, shorter
> than yours although somewhat harder to understand just by looking at
> the code:
>
> ?f :: (Integer, Integer) -> Integer
> ?f (x,y) = (r*r + r) `div` 2 + x
> ? ?where r = x + y
>
> ?f' :: Integer -> (Integer, Integer)
> ?f' n = (n - t, r - (n - t))
> ? ?where r = floor $ (sqrt(1 + 8*(fromIntegral n)) - 1) / 2
> ? ? ? ? ?t = (r*r + r) `div` 2
>
> ?*Main Test.QuickCheck> quickCheck (\(NonNegative x) (NonNegative y) -> f' (f 
> (x,y)) == (x,y))
> ?+++ OK, passed 100 tests.
> ?*Main Test.QuickCheck> quickCheck (\(NonNegative x) -> f (f' x) == x)
> ?+++ OK, passed 100 tests.
>
> This one looks a bit complicated but at heart it's rather simple: we
> think of the pairs of naturals as residing in a grid, like so:
>
> ?. ? ? ? . ? ? .
> ?: ? ? ? : ? ? :
> ?(0,2) (1,2) (2,2) ?...
> ?(0,1) (1,1) (2,1) ?...
> ?(0,0) (1,0) (2,0) ?...
>
> and we imagine listing them by diagonals, like
>
> ?(0,0) (0,1) (1,0) (0,2) (1,1) (2,0) (0,3) ...
>
> Now, the math to go back and forth between a pair and its index in
> this listing by diagonals isn't quite as nice-looking as one might
> hope (essentially we have to use the formula for triangular numbers
> and solve a quadratic equation) but it's not too bad. ?(Actually, what
> I wrote above won't work once you get to integers big enough that the
> sqrt starts losing precision, but you could write an accurate integer
> square root operation to get around that.)
>
> Some comments on your code style are interspersed below.
>
>> import Control.Monad.Logic
>> import Data.Maybe
>> import Data.List
>> import Data.Numbers.Primes
>> import Test.QuickCheck
>>
>> -- This program demonstrates a mapping between the pairs of natural
>> numbers and a subset of co-primes.
>> -- The property should hold for all sized lists, not just pairs.
>> Ordering is preserved.
>> -- Question: Are we able to compress the range to create a bijection?
>> -- Answer: Yes! We can use the breadth-wise indces of the products,
>> rather than the products themselves.
>>
>> -- Pair to Number
>>
>> x_p = (evens !!)
>> y_p = (odds ?!!)
>>
>> xy_p x y = x_p x * y_p y
>>
>> xy_c x = ns_nc . xy_p x
>
> The definition of xy_c strikes me as a gratuitous use of points-free
> style just for its own sake. ?It's hard to read because of the
> asymmetric treatment of x and the (implicit) second argument. ?I would
> find it much clearer to just write
>
> ?xy_c x y = ns_nc (xy_p x y)
>
> If you really want to do it points-free you could use a 'double
> composition' operator,
>
> ?oo = (.) . (.)
> ?xy_c = ns_nc `oo` xy_p
>
> but I don't recommend it.
>
> Also, most of the difficulty I had reading your code was due to your
> choice of function names, which were too telegraphic and didn't give
> me any clues as to what they did. ?Of course naming is rather an
> idiomatic thing, but if you want others to read your code I suggest
> trying to use names that are a bit more descriptive/suggestive.
>
>>
>> -- Number to Pair
>>
>> p_xy n = (x,y)
>> ? where
>> ? ? x = fromJust $ findIndex (`divides` n) evens
>> ? ? y = fromJust $ findIndex (`divides` n) odds
>>
>> c_xy = p_xy . nc_ns
>>
>> -- Sparse Number to Compact Number
>>
>> numbers = odds >>- \x -> evens >>- \y -> return (x*y) -- I don't
>> really understand LogicT... :-(
>>
>> ns_nc n = fromJust $ findIndex (==n) numbers
>>
>> -- Compact Numner to Sparse Number
>>
>> nc_ns = (numbers !!)
>>
>> -- Helpers
>>
>> evens = map (primes !!) [0,2..]
>> odds ?= map (primes !!) [1,3..]
>
> This strikes me as a rather inefficient way to define evens and odds.
> It would be better to do something like
>
> ?deinterlace :: [a] -> ([a],[a])
> ?deinterlace (x1:x2:xs) = (x1:l1, x2:l2)
> ? ?where (l1,l2) = deinterlace xs
>
> ?(evens, odds) = deinterlace primes
>
>>
>> x `divides` y = y `mod` x == 0
>>
>> -- Id referencing properties
>>
>> prop_p1 = forAll (elements [(x,y) | x <- [1..6], y <- [1..7]]) f
>> ? where
>> ? ? f (x,y) = (x,y) == c_xy (xy_c x y)
>>
>> prop_p2 = forAll (elements [1..100]) f
>> ? where
>> ? ? f c = c == uncurry xy_c (c_xy c)
>
> _______________________________________________
> 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 32, Issue 10
*****************************************

Reply via email to