On 8/9/07, Marc Weber <[EMAIL PROTECTED]> wrote:
> > I wrote a code, but seems to give "Time limit exceeded"!
> ??
> Your code writes
> 15 to stdout which is correct (with the example given on the page)..
> You have to explain what you mean by >>seems to give "Time limit exceeded"<<
>
> > loop t fu
On 8/9/07, Brent Yorgey <[EMAIL PROTECTED]> wrote:
> On 8/9/07, Chaddaï Fouché <[EMAIL PROTECTED]> wrote:
> > I get "Wrong answer" with the following code for the same problem...
> > Is there something strange in this code :
>
> This problem description is not worded very well. You have to figure
On 8/9/07, Chaddaï Fouché <[EMAIL PROTECTED]> wrote:
>
> I get "Wrong answer" with the following code for the same problem...
> Is there something strange in this code :
This problem description is not worded very well. You have to figure out
the matching that maximizes the sum of hotnesses; you
Note that this code isn't more successful, clearly I have
misunderstood one requirement :
import qualified Data.ByteString.Char8 as B
import Data.List (unfoldr)
main = B.interact $ hot
hot = B.unlines . map (B.pack . show) . processList . tail . unfoldr readInt1
readInt1 cs = do
(n, cs') <- B
I get "Wrong answer" with the following code for the same problem...
Is there something strange in this code :
module Main where
import qualified Data.ByteString.Char8 as B
main =
B.getLine >>=
sequence_ . flip replicate hot . maybe 0 fst . B.readInt
hot = do
B.getLine
men <- B.
On 8/9/07, Marc Weber <[EMAIL PROTECTED]> wrote:
>
> > I wrote a code, but seems to give "Time limit exceeded"!
> ??
> Your code writes
> 15 to stdout which is correct (with the example given on the page)..
> You have to explain what you mean by >>seems to give "Time limit
> exceeded"<<
>
I think
> I wrote a code, but seems to give "Time limit exceeded"!
??
Your code writes
15 to stdout which is correct (with the example given on the page)..
You have to explain what you mean by >>seems to give "Time limit exceeded"<<
> loop t function
Does already exist.
sequence $ replicate 10 function
is
@Donald:
Thanks for the link.
> prod = sum . zipWith (*)
>
> This is the slow part. Prelude.read ist really slow.
>
> Futhermore use the recusion pattern again:
> to_int = map read
>
> What is n used for?
@Lutz:
Those are some nice tricks... Thanks!
Now, the 'n' is for getting the number of number
* Vimal wrote:
>>> Beginning of CODE
> loop t function
> | t == 1 = do function
> | otherwise = do { function; loop (t - 1) function }
>
> prod [] [] = 0
> prod (a:as) (b:bs) = a*b + prod as bs
prod = sum . zipWith (*)
> to_int :: [String] -> [Integer]
> to_int [] = []
> to_int (x:xs) = (read x
j.vimal:
> Hi
> I am practicing writing code in haskell, by solving problems at this
> site. http://spoj.pl.
> The problem http://spoj.pl/problems/FASHION , is pretty simple.
>
> 1. Given two lists A,B , of N numbers, sort them and take sum of products.
> i.e. Sum ai * bi
>
> I wrote a code,
Hi
I am practicing writing code in haskell, by solving problems at this
site. http://spoj.pl.
The problem http://spoj.pl/problems/FASHION , is pretty simple.
1. Given two lists A,B , of N numbers, sort them and take sum of products.
i.e. Sum ai * bi
I wrote a code, but seems to give "Time lim
11 matches
Mail list logo