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.  Parse error in pattern (Zhi-Qiang Lei)
   2. Re:  Parse error in pattern (Brent Yorgey)
   3. Re:  Parse error in pattern (Zhi-Qiang Lei)
   4.  Imperfect Graham Scan (Zhi-Qiang Lei)
   5.  Guard in class def (Henry Lockyer)


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

Message: 1
Date: Sun, 8 Jan 2012 00:11:29 +0800
From: Zhi-Qiang Lei <zhiqiang....@gmail.com>
Subject: [Haskell-beginners] Parse error in pattern
To: Haskell Beginer <beginners@haskell.org>
Message-ID: <443ad4ba-0495-4621-8601-006f27f1a...@gmail.com>
Content-Type: text/plain; charset=us-ascii

Hi,

I am writing a Graham Scan function. What puzzles me is it cannot be compiled. 
Does anyone know what is wrong with "scan"? Thanks.

==== compile ====
bogon% ghc GrahamScan.hs                                                        
                                     -- NORMAL --
[1 of 1] Compiling Main             ( GrahamScan.hs, GrahamScan.o )

GrahamScan.hs:30:1: Parse error in pattern: scan
==== compile ====

==== code ====
data Point a = Point {
    x :: a,
    y :: b
}

instance Ord (Point a) where
    compare (Point x1 y1) (Point x2 y2) = compare (y1, x1) (y2, x2)

data Vector a = Vector {
    start   :: Point a,
    end     :: Point a
}

cosine :: Vector a -> Ratio a
cosine (Vector (Point x1 y1) (Point x2 y2)) = (x2 - x1) / ((x2 - x1) ^ 2 + (y2 
- y1) ^ 2)

instance Ord (Vector a) where
    compare a b = compare (f a) (f b) where
        f = negate . cosine

sort' :: [Point a] -> [Point a]
sort' xs = minPoint : fmap end sortedVectors where
    sortedVectors   = sort $ map (Vector minPoint) $ delete minPoint xs
    minPoint        = minimum xs

ccw :: Point a -> Point a -> Point a -> Bool
ccw (Point x1 y1) (Point x2 y2) (Point x3 y3) = (x2 - x1) * (y3 - y1) - (y2 - 
y1) * (x3 - x1) > 0

scan :: [Point a] -> [Point a]
scan p1 : p2 : p3 : xs
    | ccw p1 p2 p3  = p1 : scan (p2 : p3 : xs)
    | otherwise     = scan (p1 : p3 : xs)
scan xs = xs

grahamScan :: [Point a] -> [Point a]
grahamScan = scan . sort'
==== code ====

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




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

Message: 2
Date: Sat, 7 Jan 2012 11:49:51 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Parse error in pattern
To: beginners@haskell.org
Message-ID: <20120107164950.ga8...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Sun, Jan 08, 2012 at 12:11:29AM +0800, Zhi-Qiang Lei wrote:
> 
> scan :: [Point a] -> [Point a]
> scan p1 : p2 : p3 : xs

Patterns with constructors and multiple components must be surrounded
by parentheses.  So this should be

  scan (p1 : p2 : p3 : xs)

-Brent



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

Message: 3
Date: Sun, 8 Jan 2012 01:10:31 +0800
From: Zhi-Qiang Lei <zhiqiang....@gmail.com>
Subject: Re: [Haskell-beginners] Parse error in pattern
To: Brent Yorgey <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID: <cbb8409f-7616-4b88-b4d9-dd2a6b175...@gmail.com>
Content-Type: text/plain; charset=us-ascii

What an idiot am I! Thank you very much.

On Jan 8, 2012, at 12:49 AM, Brent Yorgey wrote:

> On Sun, Jan 08, 2012 at 12:11:29AM +0800, Zhi-Qiang Lei wrote:
>> 
>> scan :: [Point a] -> [Point a]
>> scan p1 : p2 : p3 : xs
> 
> Patterns with constructors and multiple components must be surrounded
> by parentheses.  So this should be
> 
>  scan (p1 : p2 : p3 : xs)
> 
> -Brent
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners


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




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

Message: 4
Date: Sun, 8 Jan 2012 15:31:44 +0800
From: Zhi-Qiang Lei <zhiqiang....@gmail.com>
Subject: [Haskell-beginners] Imperfect Graham Scan
To: Haskell Beginer <beginners@haskell.org>
Message-ID: <c42afd95-446b-4eda-b78d-cd0cb2818...@gmail.com>
Content-Type: text/plain; charset=us-ascii

Hi,

The Graham Scan function I wrote, looks like running well. But when I put it in 
QuickCheck, it just failed in some case. Anyone can show me some clues about 
the problem? Thanks.

When I test it in ghci with some example, it returns the right result.
*Main> let xs = [Point {x = 1.0, y = 1.0},Point {x = 0.0, y = 4.0},Point {x = 
0.0, y = 6.0},Point {x = 3.0, y = 5.0},Point {x = 4.0, y = 4.0},Point {x = 4.0, 
y = 1.0},Point {x = 3.0, y = 3.0},Point {x = 2.0, y = 2.0},Point {x = 5.0, y = 
5.0}]
*Main> grahamScan xs
[Point {x = 1.0, y = 1.0},Point {x = 4.0, y = 1.0},Point {x = 5.0, y = 
5.0},Point {x = 0.0, y = 6.0},Point {x = 0.0, y = 4.0}]
*Main> grahamScan it
[Point {x = 1.0, y = 1.0},Point {x = 4.0, y = 1.0},Point {x = 5.0, y = 
5.0},Point {x = 0.0, y = 6.0},Point {x = 0.0, y = 4.0}]

However, QuickCheck find some points which can fail it. Could it be a data type 
overflow problem?

prop_scan_idempotent xs = not (null xs) ==> (grahamScan . grahamScan) xs == 
grahamScan xs

*Main> quickCheck prop_scan_idempotent 
*** Failed! Falsifiable (after 13 tests and 4 shrinks):    
[Point {x = -6.29996952110807, y = -91.37172300100718},Point {x = 
9.353314917365527, y = 64.35532141764591},Point {x = -23.826685687218355, y = 
60.32049750442556},Point {x = -1.4281411275074123, y = 31.54197550020998},Point 
{x = -2.911218918860731, y = 15.564623822256719}]

=== code ===
module GrahamScan (grahamScan, Point(..))
where

import Data.List
import Data.Ratio

data Point = Point {
    x :: Double,
    y :: Double
} deriving (Eq, Show)

instance Ord Point where
    compare (Point x1 y1) (Point x2 y2) = compare (y1, x1) (y2, x2)

data Vector = Vector {
    start   :: Point,
    end     :: Point
} deriving (Eq)

cosine :: Vector -> Double
cosine (Vector (Point x1 y1) (Point x2 y2)) = (x2 - x1) / ((x2 - x1) ^ 2 + (y2 
- y1) ^ 2)

instance Ord Vector where
    compare a b = compare (f a) (f b) where
        f = negate . cosine

sort' :: [Point] -> [Point]
sort' xs = pivot : fmap end sortedVectors where
    sortedVectors   = sort . fmap (Vector pivot) . delete pivot $ xs
    pivot           = minimum xs

counterClockwise :: Point -> Point -> Point -> Bool
counterClockwise (Point x1 y1) (Point x2 y2) (Point x3 y3) = (x2 - x1) * (y3 - 
y1) > (y2 - y1) * (x3 - x1)

scan :: [Point] -> [Point]
scan (p1 : p2 : p3 : xs)
    | counterClockwise p1 p2 p3 = p1 : scan (p2 : p3 : xs)
    | otherwise                 = scan (p1 : p3 : xs)
scan xs = xs

grahamScan :: [Point] -> [Point]
grahamScan = scan . sort' . nub
=== code ===


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




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

Message: 5
Date: Sun, 8 Jan 2012 09:29:51 +0000
From: Henry Lockyer <henry.lock...@ntlworld.com>
Subject: [Haskell-beginners] Guard in class def
To: Beginners@haskell.org
Message-ID: <1ae62183-9a20-4d39-bdeb-650f62f5e...@ntlworld.com>
Content-Type: text/plain; charset=us-ascii

Hi,
I was just looking through the 'Monad Transformers' chapter in Real World 
Haskell. They are using the "reader" monad to illustrate the transformer 
structure  but I fell off at the first bend when I saw the following:

class (Monad m) => MonadReader r m | m -> r where
  ask     :: m r
  local  :: (r -> r) -> m a -> m a


Could someone explain the use of a guard here / how to read this with the "| m 
-> r"  ?  
I haven't come across this usage before (as far as I have noticed :-) and the 
meaning hasn't jumped out at me yet...

Thanks in advance.

Henry


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

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


End of Beginners Digest, Vol 43, Issue 10
*****************************************

Reply via email to