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:  Lujvo forming with cmavo rafsi (Amy de Buitl?ir)
   2. Re:  Lujvo forming with cmavo rafsi (Daniel Fischer)
   3. Re:  Lujvo forming with cmavo rafsi (Brent Yorgey)
   4. Re:  Sqlite3 - INSERT statement question (Brent Yorgey)
   5.  ghci loading of hs files... (Patrick Lynch)
   6. Re:  Informal proof of bijective mapping between Naturals and
      Natural pairs (Brent Yorgey)
   7. Re:  Lujvo forming with cmavo rafsi (Alex Rozenshteyn)
   8. Re:  ghci loading of hs files... (Antoine Latter)


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

Message: 1
Date: Thu, 3 Feb 2011 19:58:27 +0000
From: Amy de Buitl?ir <a...@nualeargais.ie>
Subject: Re: [Haskell-beginners] Lujvo forming with cmavo rafsi
To: Alex Rozenshteyn <rpglove...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <AANLkTi=yn7btcbhg5ua93aoy5zwfsj9zquh+jucn0...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Alex, I think you might have better luck on one of the Lojban forums:
http://www.lojban.org/tiki/Lojbanic+Forums
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20110203/1540f21a/attachment-0001.htm>

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

Message: 2
Date: Thu, 3 Feb 2011 20:58:40 +0100
From: Daniel Fischer <daniel.is.fisc...@googlemail.com>
Subject: Re: [Haskell-beginners] Lujvo forming with cmavo rafsi
To: beginners@haskell.org
Message-ID: <201102032058.40744.daniel.is.fisc...@googlemail.com>
Content-Type: text/plain;  charset="utf-8"

On Thursday 03 February 2011 20:17:36, Alex Rozenshteyn wrote:
> If there was any part of my question you did not understand, feel free
> to point out a specific part, and I'll try my best to clarify.

The entire part between the first 'S' and the last 's' inclusive?

You know, it might help if you used a language spoken by more than a 
handful. From the look of it, I suspect it might be lojban, but I can't be 
sure.



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

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

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



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

Message: 4
Date: Thu, 3 Feb 2011 15:22:49 -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: <20110203202248.gb19...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

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: 5
Date: Thu, 03 Feb 2011 16:09:15 -0500
From: "Patrick Lynch" <kmandpjly...@verizon.net>
Subject: [Haskell-beginners] ghci loading of hs files...
To: <beginners@haskell.org>
Message-ID: <C1AECE69364242C4A0A8B71382C0363B@UserPC>
Content-Type: text/plain; charset="iso-8859-1"

...I'm using the book "Real World Haskell"...
...In Chapter 22, it uses two files, namely: ...\ch22\PodDB.hs and 
...\ch22\PodTypes.hs.

...This is the calling code in PodDB.hs:
   {-- snippet all --}
   module PodDB where
   import Database.HDBC
   import Database.HDBC.Sqlite3
   import PodTypes

...I was instructed to start ghci and invoke the command: ...> :load 
C:\Users\User\Downloads\rwh-examples2\examples\ch22\poddb.hs
...this gives the following error message:
     C:\Users\User\Downloads\rwh-examples2\examples\ch22\poddb.hs:6:7:
     Could not find module `PodTypes':
        Use -v to see a list of the files searched for.
     Failed, modules loaded: none.

...I then tried the command: :l 
C:\Users\User\Downloads\rwh-examples2\examples\ch22\poddb.hs 
C:\Users\User\Downloads\rwh-examples2\examples\ch22\podtypes.hs
...it loaded both files...

...is there someway to modify the code in PodDB.hs that would allow me to 
simply invoke the command, as mentioned by the author, :load PodDB.hs?

Thank you

-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20110203/c19a8a32/attachment-0001.htm>

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

Message: 6
Date: Thu, 3 Feb 2011 16:14:30 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Informal proof of bijective mapping
        between Naturals and Natural pairs
To: beginners@haskell.org
Message-ID: <20110203211430.ga19...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

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)



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

Message: 7
Date: Thu, 3 Feb 2011 16:32:04 -0500
From: Alex Rozenshteyn <rpglove...@gmail.com>
Subject: Re: [Haskell-beginners] Lujvo forming with cmavo rafsi
To: beginners@haskell.org
Message-ID:
        <AANLkTi=ENKrwAh-+-PBZ2ZVrRTck3qJN=soeuuaeg...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

...
I meant to email "lojban-beginners"

Apologies.

mea culpa

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

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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20110203/9191a9b6/attachment-0001.htm>

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

Message: 8
Date: Thu, 3 Feb 2011 15:36:07 -0600
From: Antoine Latter <aslat...@gmail.com>
Subject: Re: [Haskell-beginners] ghci loading of hs files...
To: Patrick Lynch <kmandpjly...@verizon.net>
Cc: beginners@haskell.org
Message-ID:
        <AANLkTin7efeQZ6OMdqRc0MVF15gDyKumRDezy9zMV=k...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Thu, Feb 3, 2011 at 3:09 PM, Patrick Lynch <kmandpjly...@verizon.net> wrote:
> ...I'm using the book "Real World Haskell"...
> ...In Chapter 22, it uses two files, namely: ...\ch22\PodDB.hs and
> ...\ch22\PodTypes.hs.
>
> ...This is the calling code in PodDB.hs:
> ?? {-- snippet all --}
> ?? module PodDB where
> ?? import Database.HDBC
> ?? import Database.HDBC.Sqlite3
> ?? import PodTypes
>
> ...I was instructed to start ghci and invoke the command: ...>?:load
> C:\Users\User\Downloads\rwh-examples2\examples\ch22\poddb.hs
> ...this gives the following error message:
> ???? C:\Users\User\Downloads\rwh-examples2\examples\ch22\poddb.hs:6:7:
> ???? Could not find module `PodTypes':
> ???? ?? Use -v to see a list of the files searched for.
> ???? Failed, modules loaded: none.
>
> ...I then tried the command: :l
> C:\Users\User\Downloads\rwh-examples2\examples\ch22\poddb.hs
> C:\Users\User\Downloads\rwh-examples2\examples\ch22\podtypes.hs
> ...it loaded both files...
>
> ...is there someway to modify the code in PodDB.hs that would allow me to
> simply invoke the command, as mentioned by the author, :load PodDB.hs?
>
> Thank you
>

Does "cd C:\Users\User\Downloads\rwh-examples2\examples\ch22" before
launching GHCi work?

You could also use the -i parameter for GHCi - it tells GHCi to look
in the specified directory for source files.

You won't be able to modify the code to do this - the notion that a
Haskell module corresponds to a file on disk (and that there is a
naming convention for this correspondence) isn't addressed in the
language definition.

This is why Haskell libraries on Hackage ship with meta-data
describing the layout of the source files for the library.

Antoine

>
> _______________________________________________
> 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 9
****************************************

Reply via email to