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.  A strange expression in Quick Hull example (Zhi-Qiang Lei)
   2.  I am having trouble with the type declaration for creating
      an identity matrix. (KC)
   3. Re:  [Haskell-cafe] I am having trouble with the type
      declaration for creating an identity matrix. (KC)


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

Message: 1
Date: Wed, 25 Apr 2012 04:36:32 +0800
From: Zhi-Qiang Lei <zhiqiang....@gmail.com>
Subject: [Haskell-beginners] A strange expression in Quick Hull
        example
To: Haskell Beginer <beginners@haskell.org>
Message-ID: <ca3c2357-cbdc-44ae-8555-bab1c62b0...@gmail.com>
Content-Type: text/plain; charset="us-ascii"

I copy the Quick Hull snippet from 
http://darcs.haskell.org/packages/dph/examples/quickhull/QuickHull.hs
The "packed" expression in "hsplitList" is much confusing to me. Why does it 
have to zip points with cross? Is [ p | (c, p) <- cross, c > 0.0 ] not enough? 
Thanks.

data Point = Point !Double !Double
data Line  = Line  Point Point

instance Show Point where
  show (Point x y) = show (x, y)

distance :: Point -> Line -> Double
distance (Point xo yo) (Line (Point x1 y1) (Point x2 y2))
  = (x1 - xo) * (y2 - yo) - (y1 - yo) * (x2 - xo)
  
upper :: (a -> a -> Bool) -> [(a, b)] -> b
upper above = snd . foldl1 pick
  where
    pick left@(kl, _) right@(kr, _) | kl `above` kr = left
                                    | otherwise     = right

hsplitList :: [Point] -> Line -> [Point]
hsplitList points line@(Line p1 p2)
  | length packed < 2 = p1:packed
  | otherwise         = hsplitList packed (Line p1 pm) ++ hsplitList packed 
(Line pm p2)
  where
    cross  = [ (distance p line, p) | p <- points ]
    packed = [ p | (p, (c, _)) <- zip points cross, c > 0.0 ]

    pm     = upper (>) cross

quickHullList :: [Point] -> [Point]
quickHullList [] = []
quickHullList points
  = hsplitList points (Line minx maxx) ++ hsplitList points (Line maxx minx)
  where
    xs   = [ (x, p) | p@(Point x y) <- points ]
    minx = upper (<) xs
    maxx = upper (>) xs

Best regards,
Zhi-Qiang Lei
zhiqiang....@gmail.com

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

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

Message: 2
Date: Tue, 24 Apr 2012 14:20:16 -0700
From: KC <kc1...@gmail.com>
Subject: [Haskell-beginners] I am having trouble with the type
        declaration for creating an identity matrix.
To: haskell-cafe <haskell-c...@haskell.org>, beginners@haskell.org
Message-ID:
        <CAMLKXymLvdNWOBGN6zYeuxLncj4rQbfW=Q+fqvd=vr7RDu4G=a...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

initIdentityMat :: Int -> ST s (STUArray s (Int,Int) ((Int, Int), Double))
initIdentityMat m = newListArray ((1,m),(1,m)) ([((i,j), if i == j then 1.0
else 0.0) | i <- [1..m], j <- [1..m]] :: [((Int,Int), Double)])

Doesn't seem to compile, nor do minor variations of the type declaration.

-- 
--
Regards,
KC
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120424/fc9451fb/attachment-0001.htm>

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

Message: 3
Date: Tue, 24 Apr 2012 20:08:26 -0700
From: KC <kc1...@gmail.com>
Subject: Re: [Haskell-beginners] [Haskell-cafe] I am having trouble
        with the type declaration for creating an identity matrix.
To: kevin.char...@acm.org, haskell-cafe <haskell-c...@haskell.org>,
        beginners@haskell.org
Message-ID:
        <CAMLKXy=hkmtpdadtqy2qpqmsbgcxh4inkijvnvm1mycnfdc...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Thank you.

One is ONLY supposed to supply the list elements for "newListArray" which
fill the array in increasing order.


On Tue, Apr 24, 2012 at 3:21 PM, Kevin Charter <kchar...@gmail.com> wrote:

> On Tue, Apr 24, 2012 at 3:20 PM, KC <kc1...@gmail.com> wrote:
>
>> initIdentityMat :: Int -> ST s (STUArray s (Int,Int) ((Int, Int), Double))
>> initIdentityMat m = newListArray ((1,m),(1,m)) ([((i,j), if i == j then
>> 1.0 else 0.0) | i <- [1..m], j <- [1..m]] :: [((Int,Int), Double)])
>>
>> Doesn't seem to compile, nor do minor variations of the type declaration.
>>
>
> If you use Hoogle to find the type and API docs for 'newListArray', I
> believe you'll be able to figure out what's wrong, but I'll give you a
> hint. The list you're giving to 'newListArray' contains too much; and the
> pair you give it is only half correct.
>
> Kevin
>
> --
> Kevin Charter
> kevin.char...@acm.org
>



-- 
--
Regards,
KC
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120424/385f38ea/attachment-0001.htm>

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

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


End of Beginners Digest, Vol 46, Issue 42
*****************************************

Reply via email to