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:  Typeclasses vs. Data (Thomas)
   2. Re:  Typeclasses vs. Data (David Place)
   3. Re:  Typeclasses vs. Data (Felipe Almeida Lessa)
   4.  Compilation error (mukesh tiwari)


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

Message: 1
Date: Thu, 21 Jul 2011 01:41:52 +0200
From: Thomas <hask...@phirho.com>
Subject: Re: [Haskell-beginners] Typeclasses vs. Data
To: beginners@haskell.org
Message-ID: <4e2767c0....@phirho.com>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hello David!

Yes, I should have posted the signatures, too. Sorry.
I managed to simplify the problem even further. It still doesn't help me 
understand how to avoid the error, though.

class Continuation a where
    resume :: a -> Int -> Int

data BeginCont a = BeginCont a Int deriving (Show)
instance (Continuation a) => Continuation (BeginCont a) where
   resume (BeginCont k es) v = eval_begin es k

eval :: Continuation a => Int -> a -> Int
eval n k = if n < 1
        then resume k n
        else eval_begin (n - 1) k

eval_begin :: Continuation a => Int -> a -> Int
eval_begin n k = eval n (if (n < 0) then k else (BeginCont k (n - 1)))

It's pretty clear that in the mutual recursion between "eval" and 
"eval_begin" the parameter "k" is "growing" from "a" to "BeginCont a" 
and so on. But how to resolve that?
(And it works perfectly in the case of the "data" definition.)

Anyway, thank you!
Regards,
Thomas



On 21.07.2011 00:40, David Place wrote:
 > On Jul 20, 2011, at 6:26 PM, Thomas wrote:
 >
 >> Thank you for taking the time.
 >> Here is a complete fragment that shows the error:
 >
 > Hi, Thomas.
 >
 > I'm very sympathetic.  I hate it when I get an error like this.  I 
looked at your code and the solution didn't jump off the page, maybe it 
will for someone else.  In the meantime, I suggest this strategy. 
Carefully give type signatures to all of your functions.  This way you 
can help the type checker give better error messages.  The type 
inference algorithm can go away into crazy land if you give it a 
nonsense definition.
 >
 > ___________________
 > David Place
 > Owner, Panpipes Ho! LLC
 > http://panpipesho.com
 > d...@vidplace.com
 >
 >




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

Message: 2
Date: Wed, 20 Jul 2011 20:49:46 -0400
From: David Place <d...@vidplace.com>
Subject: Re: [Haskell-beginners] Typeclasses vs. Data
To: Thomas <hask...@phirho.com>
Cc: beginners@haskell.org
Message-ID: <5bd8c85b-8b2e-42d3-9c3f-2ce73a193...@vidplace.com>
Content-Type: text/plain; charset=iso-8859-1

On Jul 20, 2011, at 7:41 PM, Thomas wrote:

> It's pretty clear that in the mutual recursion between "eval" and 
> "eval_begin" the parameter "k" is "growing" from "a" to "BeginCont a" and so 
> on. But how to resolve that?

Progress, though?  You're getting a different error message.

>     Couldn't match type `a' with `BeginCont a'
>       `a' is a rigid type variable bound by
>           the type signature for
>             eval_begin :: Continuation a => Int -> a -> Int
>           at ../Desktop/devl/hs/TryPQ.hs:16:1
>     In the return type of a call of `BeginCont'
>     In the expression: (BeginCont k (n - 1))
>     In the second argument of `eval', namely
>       `(if (n < 0) then k else (BeginCont k (n - 1)))'






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

Message: 3
Date: Thu, 21 Jul 2011 00:27:26 -0300
From: Felipe Almeida Lessa <felipe.le...@gmail.com>
Subject: Re: [Haskell-beginners] Typeclasses vs. Data
To: Thomas <hask...@phirho.com>
Cc: beginners@haskell.org
Message-ID:
        <CANd=ogfwa1ne6qpeq8ztpbju53dn+-yba1fdmdl2krtowug...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Wed, Jul 20, 2011 at 8:41 PM, Thomas <hask...@phirho.com> wrote:
> eval_begin :: Continuation a => Int -> a -> Int
> eval_begin n k = eval n (if (n < 0) then k else (BeginCont k (n - 1)))

Although 'eval n' is polymorphic, the if expression needs to have just
one type, either 'a' or 'BeginCont a', and they can't be unified.  The
solution is pretty simple, though, since eval's return type doesn't
mention 'a' at all:

  eval_begin :: Continuation a => Int -> a -> Int
  eval_begin n k = if (n < 0) then eval n k else eval n (BeginCont k (n - 1))

Note that 'eval n' is repeated.  If you don't to repeat it on your
real world code you may give it an explicit name.  However you'll need
to provide a type signature from GHC 7.0 onwards:

  eval_begin :: Continuation a => Int -> a -> Int
  eval_begin n k =
    let eval' :: Continuation a => a -> Int
        eval' = eval n
    in if (n < 0) then eval' k else eval' (BeginCont k (n - 1))

HTH, =)

-- 
Felipe.



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

Message: 4
Date: Thu, 21 Jul 2011 14:53:05 +0530
From: mukesh tiwari <mukeshtiwari.ii...@gmail.com>
Subject: [Haskell-beginners] Compilation error
To: beginners@haskell.org
Message-ID:
        <CAFHZvE_93AHBoTPD1HLCAuTWtjVGf++Z+E4Zme+eFH+=4wj...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Kindly some one please tell me why this code in not compiling . I have to
round  a Double value up to two decimal places and  i wrote this code for
this problem [ http://www.spoj.pl/problems/QCJ4 ] .
Thank you
Mukesh Tiwari

import Data.List
import qualified Data.Sequence as DS
import Text.Printf

data Point a = P a a deriving ( Show , Eq  , Ord  )
data Turn = S | L | R deriving ( Show , Eq , Ord , Enum  ) -- straight left
right

compPoint :: ( Num  a , Ord a ) => Point a -> Point a -> Ordering
compPoint ( P x1 y1 ) ( P x2 y2 )
  | compare x1 x2 == EQ = compare y1 y2
  | otherwise = compare x1 x2

findMinx :: ( Num a , Ord a ) => [ Point a ] -> [ Point a ]
findMinx xs = sortBy ( \x  y  -> compPoint  x y  ) xs

compAngle ::(Num a , Ord a ) => Point a -> Point a -> Point a -> Ordering
compAngle ( P x1 y1 ) ( P x2 y2 ) ( P x0 y0 ) = compare ( (  y1 - y0 ) * (
x2 - x0 )  ) ( ( y2 - y0) * ( x1 - x0 ) )

sortByangle :: ( Num a , Ord a ) => [ Point a ] -> [ Point a ]
sortByangle (z:xs) = z : sortBy ( \x y -> compAngle x y z ) xs

convexHull ::( Num a , Ord a ) => [ Point a ] -> [ Point a ]
convexHull xs = reverse . findHull [y,x]  $ ys where
(x:y:ys) = sortByangle.findMinx $ xs

findTurn :: ( Num a , Ord a , Eq a ) => Point a -> Point a -> Point a ->
Turn
findTurn ( P x0 y0 ) ( P x1 y1 ) ( P x2 y2 )
 | ( y1 - y0 ) * ( x2- x0 ) < ( y2 - y0 ) * ( x1 - x0 ) = L
 | ( y1 - y0 ) * ( x2- x0 ) == ( y2 - y0 ) * ( x1 - x0 ) = S
 | otherwise = R

findHull :: ( Num a , Ord a  )  => [ Point a ] ->   [ Point a ] -> [ Point a
]
findHull [x]  ( z : ys )  = findHull [ z , x ]  ys  --incase of second point
 on line from x to z
findHull xs  [] = xs
findHull ( y : x : xs )  ( z:ys )
  | findTurn x y z == R = findHull (  x : xs )   ( z:ys )
  | findTurn x y z == S = findHull (  x : xs )   ( z:ys )
  | otherwise = findHull ( z : y : x : xs  )   ys

--from here on testing part for SPOJ

format::(Num a , Ord a ) => [[a]] -> [Point a]
format xs = map (\[x0 , y0] -> P x0 y0 ) xs

helpSqrt :: (  Floating  a ) => Point a -> Point a ->  a
helpSqrt ( P x0 y0 ) ( P x1 y1 ) =  sqrt  $  ( x0 - x1 ) ^ 2 + ( y0 - y1 ) ^
2

solve :: ( Num a , RealFrac a , Floating a  ) => [ Point a ] ->  a
solve xs =  d   where
 d =  snd . foldl ( \(  P x0 y0  , s )  ( P x1 y1 ) -> ( P x0 y0   , max s
 $ 2.0 *  helpSqrt  ( P  x0 y0  ) ( P x1 y1 ) ) )  ( P x y  , 0 ) $   xs
where
( P x y ) = cMass xs


cMass :: ( Num a , RealFrac a , Floating a  ) => [ Point a ] -> Point a
cMass xs = P x y where
( P x0 y0 ) = foldl ( \( P x1 y1 ) (P x2 y2 ) -> P ( x1 + x2 ) ( y1 + y2 ) )
( P 0 0 ) xs
n = genericLength xs
x = x0 / n
y = x0 / n



readInt  ::( Num a , Read a ) =>   String -> a
readInt  = read


main = do
        let l =   solve . convexHull . format . map  ( map readInt . words )
. tail . lines
printf "%.2f\n"  l
return ()

{--
main = interact $ solve . convexHull . format . map  ( map readInt . words )
. tail . lines
--}

The error is
[1 of 1] Compiling Main             ( qcj4_6044.hs, qcj4_6044.o )

qcj4_6044.hs:69:1:
    No instance for (PrintfArg (String -> a))
      arising from a use of `printf' at qcj4_6044.hs:69:1-18
    Possible fix:
      add an instance declaration for (PrintfArg (String -> a))
    In a stmt of a 'do' expression: printf "%.2f\n" l
    In the expression:
        do { let l = solve
                   .   convexHull . format . map (map readInt . words) .
tail . lines;
             printf "%.2f\n" l;
             return () }
    In the definition of `main':
        main = do { let l = ...;
                    printf "%.2f\n" l;
                    return () }
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20110721/11fb036c/attachment-0001.htm>

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

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


End of Beginners Digest, Vol 37, Issue 41
*****************************************

Reply via email to