Compilation error

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 () }

Hi Mukesh, it seems like in
main = do let l = solve . convexHull . format . map ( map readInt . words ) . tail . lines printf "%.2f\n" l return ()
a String argument for l is missing, because solve . convexHull . format . map ( map readInt . words ) . tail . lines has type String -> Double and for String -> Double there is no instance to print it, that's what the error message tells. Cheers, Daniel.

Hi Mukesh! Mi guess is that you're simply not supplying any input to solve . convexHull . format . map ( map readInt . words ) . tail . lines So its type is a function which in turn can't be output via "printf". Also I think your composition is not correct: tail . lines "blabla" won't compile for example. tail $ lines "bla bla" will. But then on a one line input you'll get nothing... HTH, Thomas On 21.07.2011 11:23, mukesh tiwari wrote:
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 () }
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (3)
-
Daniel Seidel
-
mukesh tiwari
-
Thomas