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:  Ord and Eq instances for complex types (Mike Meyer)
   2. Re:  Ord and Eq instances for complex types (Daniel Fischer)
   3. Re:  recursion and pattern matching (Alia)
   4.  Data-List-Utils (CEO'Riley)


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

Message: 1
Date: Tue, 18 Oct 2011 16:16:01 -0700
From: Mike Meyer <m...@mired.org>
Subject: Re: [Haskell-beginners] Ord and Eq instances for complex
        types
To: Daniel Fischer <daniel.is.fisc...@googlemail.com>
Cc: beginners@haskell.org
Message-ID:
        <CAD=7u2cpzvvm1baztu5mv3t+m1_wy3bosh_obub6sfmnej5...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

On Tue, Oct 18, 2011 at 4:01 PM, Daniel Fischer <
daniel.is.fisc...@googlemail.com> wrote:

> On Wednesday 19 October 2011, 00:27:19, Mike Meyer wrote:
> > On Tue, Oct 18, 2011 at 2:47 PM, Daniel Fischer <
> > I was actually contemplating adding a quality field to the record.
> If you don't export the constructors and take care to create only hands
> with the correct quality, that is possible. I'm not sure if it gains
> anything, though.
>

That's pretty much what playing with it turned up.


> >
> > > instance Ord Hand where
> > >
> > >    compare h1 h2 =
> > >
> > >      case compare (quality h1) (quality h2) of
> > >
> > >        EQ -> case h1 of
> > >
> > >                StraightFlush c1 -> compare c1 (cards h2)
> > >                FourOfAKind r1 c1 ->
> > >
> > >                  case compare r1 (rank h2) of
> > >
> > >                    EQ -> compare c1 (cards h2)
> > >                    other -> other
> > >
> > >                ...
> > >
> > >        other -> other
> >
> > What I'd really like to do is collapse the three types of comparison
> > (i.e. - hand, rank hand, rank minorrank hand) into one comparison each.
> I don't see what you mean, could you elaborate?
>

The hand types break down into three cases:
ordered by the cards in the hand (HighCard, Straight, Flush, StraightFlush)
ordered by a rank and then the cards (PairOf, ThreeOfAKind, FourOfAKind)
ordered by two ranks and then the cards (TwoPair, FullHouse)

I'd like to be able to match against the pattern ignoring the constructor,
like so:

instance Order Hand where
   compare h1 h2 = case compare (quality h1) (quality h2) of
             EQ -> ex_compare h1 h2
             ne -> ne
      where   ex_compare (_ c1) (_ c2) = compare c1 c2
                   ex_compare (_ r1 c1) (_ r2 c2) = case compare r1 r2 of
...
                   ex_compare (_ r1 s1 c1) (_ r2 s2 c2) = case compare r1 r2
of ...

Or something similar.

     <mike
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111018/6336c1f2/attachment-0001.htm>

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

Message: 2
Date: Wed, 19 Oct 2011 01:36:39 +0200
From: Daniel Fischer <daniel.is.fisc...@googlemail.com>
Subject: Re: [Haskell-beginners] Ord and Eq instances for complex
        types
To: Mike Meyer <m...@mired.org>
Cc: beginners@haskell.org
Message-ID: <201110190136.39272.daniel.is.fisc...@googlemail.com>
Content-Type: Text/Plain;  charset="utf-8"

On Wednesday 19 October 2011, 01:16:01, Mike Meyer wrote:
> On Tue, Oct 18, 2011 at 4:01 PM, Daniel Fischer <
> 
> daniel.is.fisc...@googlemail.com> wrote:
> > On Wednesday 19 October 2011, 00:27:19, Mike Meyer wrote:
> > > On Tue, Oct 18, 2011 at 2:47 PM, Daniel Fischer <
> > > I was actually contemplating adding a quality field to the record.
> > 
> > If you don't export the constructors and take care to create only
> > hands with the correct quality, that is possible. I'm not sure if it
> > gains anything, though.
> 
> That's pretty much what playing with it turned up.
> 
> > > > instance Ord Hand where
> > > > 
> > > >    compare h1 h2 =
> > > >    
> > > >      case compare (quality h1) (quality h2) of
> > > >      
> > > >        EQ -> case h1 of
> > > >        
> > > >                StraightFlush c1 -> compare c1 (cards h2)
> > > >                FourOfAKind r1 c1 ->
> > > >                
> > > >                  case compare r1 (rank h2) of
> > > >                  
> > > >                    EQ -> compare c1 (cards h2)
> > > >                    other -> other
> > > >                
> > > >                ...
> > > >        
> > > >        other -> other
> > > 
> > > What I'd really like to do is collapse the three types of comparison
> > > (i.e. - hand, rank hand, rank minorrank hand) into one comparison
> > > each.
> > 
> > I don't see what you mean, could you elaborate?
> 
> The hand types break down into three cases:
> ordered by the cards in the hand (HighCard, Straight, Flush,
> StraightFlush) ordered by a rank and then the cards (PairOf,
> ThreeOfAKind, FourOfAKind) ordered by two ranks and then the cards
> (TwoPair, FullHouse)
> 
> I'd like to be able to match against the pattern ignoring the
> constructor, like so:

That's impossible, pattern matching is against (fully applied) 
constructors.

> 
> instance Order Hand where
>    compare h1 h2 = case compare (quality h1) (quality h2) of
>              EQ -> ex_compare h1 h2
>              ne -> ne
>       where   ex_compare (_ c1) (_ c2) = compare c1 c2
>                    ex_compare (_ r1 c1) (_ r2 c2) = case compare r1 r2
> of ...
>                    ex_compare (_ r1 s1 c1) (_ r2 s2 c2) = case compare
> r1 r2 of ...
> 
> Or something similar.

Guards?

ex_compare h1 h2
    | plain h1  = compare (cards h1) (cards h2)
    | oneRank h1 = compare (rank h1, cards h1) (rank h2, cards h2)
    | otherwise = compare (rank h1, minorRank h1, cards h1)
                          (rank h2, minorRank h2, cards h2)

plain HighCard{} = True
plain StraightFlush{} = True
plain _ = False

oneRank FullHouse{} = False
oneRank h = not (plain h)



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

Message: 3
Date: Tue, 18 Oct 2011 17:04:10 -0700 (PDT)
From: Alia <alia_kho...@yahoo.com>
Subject: Re: [Haskell-beginners] recursion and pattern matching
To: "beginners@haskell.org" <beginners@haskell.org>
Message-ID:
        <1318982650.72288.yahoomail...@web65713.mail.ac4.yahoo.com>
Content-Type: text/plain; charset=iso-8859-1

Ok, so having spent some further time on this. Methinks I have a solution below.

The aha moment occurred when I fell upon the definition of foldr and then 
looked at
the recursive functions.


foldr :: (a -> b -> b) -> b -> [a] -> b
foldr f z []???? = z
foldr f z (x:xs) = f x (foldr f z xs)

treeFold is implemented two ways, the first is as Brent advised, the second 
places
the accumulator after the function and follows from foldr. I suspect the first 
approach

is probably more practical because you can curry the accumulator away. 


The final check function verifies the equivalence of recursive and fold 
friendly functions. 


It was a cool exercise in all. Thanks Brent! (-:? 

AK




<Test.hs>


module Test

where

data Tree a b = EmptyTree | Node a b [Tree a b] 
????????????? deriving (Show, Read, Eq)? 

t =? Node "goal" 1.0 [
??????? Node "a2" 0.5 [
??????????? Node "a3" 3.0 [
??????????????? Node "a4" 1.0 [
??????????????????? Node "a5" 1.0 []
??????????????????? ]
??????????????? ]
??????????? ],
??????? Node "b2" 0.5 [
??????????? Node "b3.1" 2.0 [],
??????????? Node "b3.2" 2.0 [
??????????????? Node "b4" 10.0 []
??????????????? ]
??????????? ]
???? ]

maximum0 [] = 0
maximum0 xs = maximum xs

sumTree :: (Num b) => Tree a b -> b
sumTree EmptyTree = 0
sumTree (Node _ value children) = value + sum (map sumTree children)

count :: Tree a b -> Int
count EmptyTree = 0
count (Node _ value children) = 1 + sum (map count children) 

depth :: Tree a b -> Int
depth EmptyTree = 0
depth (Node _ value children) = 1 + maximum0 (map depth children)

treeFold :: c -> (a -> b -> [c] -> c) -> Tree a b -> c
treeFold acc f EmptyTree = acc
treeFold acc f (Node name value children) = f name value (map (treeFold acc f) 
children)

treeFold' :: (a -> b -> [c] -> c) -> c -> Tree a b -> c
treeFold' f z EmptyTree = z
treeFold' f z (Node name value children) = f name value (map (treeFold' f z) 
children)

sumTree' :: String -> Double -> [Double] -> Double
sumTree' name value xs = value + sum xs

count' :: (Num c) => a -> b -> [c] -> c
count' name value xs = 1 + sum xs

depth' :: (Num c, Ord c) => a -> b -> [c] -> c
depth' name value xs = 1 + maximum0 (xs)


check = [ count t? ? ?? == treeFold' count' 0 t
???????????? , sumTree t? == treeFold' sumTree' 0 t
???????????? , depth t? ? ?? == treeFold' depth' 0 t
???????????? ]


<Test.hs>



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

Message: 4
Date: Tue, 18 Oct 2011 19:09:04 -0500
From: "CEO'Riley" <ceori...@gmail.com>
Subject: [Haskell-beginners] Data-List-Utils
To: <beginners@haskell.org>
Message-ID: <01b701cc8df3$509875c0$f1c96140$@gmail.com>
Content-Type: text/plain; charset="us-ascii"



Hello,

 

I am new to Haskell and eager to learn what I believe is an exciting
language.  I have recently attempted to load the ProviderLookupApp module
attached and received the following error message:

 

ProviderLookupApp.hs:14:8:

    Could not find module `Data.List.Utils':

      Use -v to see a list of the files searched for.

 

I then located the Data.List.Utils module and attempted to load that but
received the error message:

 

Data.List.Utils.hs:63:8:

    Ambiguous module name `Control.Monad.State':

      it was found in multiple packages: monads-fd-0.2.0.0 mtl-2.0.1.0

Failed, modules loaded: none.

 

I am running in the Windows environment.  Any assistance in this matter
would be greatly appreciated.  Additionally, exactly how is the -v argument
used?  Thanks.

 

 

Regards,

CEO'Riley

Charles E. O'Riley Jr.

 

-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111018/7c54acbc/attachment.htm>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: image/jpeg
Size: 7023 bytes
Desc: not available
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111018/7c54acbc/attachment.jpeg>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: Data.List.Utils.hs
Type: application/octet-stream
Size: 15954 bytes
Desc: not available
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111018/7c54acbc/attachment.obj>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: ProviderLookupApp.hs
Type: application/octet-stream
Size: 7079 bytes
Desc: not available
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111018/7c54acbc/attachment-0001.obj>

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

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


End of Beginners Digest, Vol 40, Issue 30
*****************************************

Reply via email to