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:  Can I upload file using http-enumerator,     hxt? (??????? ???)
   2.  Spoj BWHEELER problem - input problem (Artur Tadra?a)
   3.  (no subject) (Alia)
   4. Re:  Spoj BWHEELER problem - input problem (David McBride)


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

Message: 1
Date: Sat, 14 Jan 2012 22:46:28 +0700
From: ??????? ??? <leon.v.niki...@pravmail.ru>
Subject: Re: [Haskell-beginners] Can I upload file using
        http-enumerator,        hxt?
To: beginners@haskell.org
Message-ID: <3911326555...@web141.yandex.ru>
Content-Type: text/plain; charset="us-ascii"

An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120114/563aee25/attachment-0001.htm>

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

Message: 2
Date: Sat, 14 Jan 2012 21:34:53 +0100
From: Artur Tadra?a <artur.tadr...@gmail.com>
Subject: [Haskell-beginners] Spoj BWHEELER problem - input problem
To: beginners@haskell.org
Message-ID:
        <ca+u-+khbrb5zq8yjfadd-81ak4yhycmra3njo5q2nfqtkqc...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-2"

Hello

While learning Haskell I'm trying to solve some simple problems on
spoj.ploccasionally. Currently I'm working on:
http://www.spoj.pl/problems/BWHEELER/. I figured out how to solve it but I
have some problems with reading input (that's my guess)

Here is my solution:

import Data.List
import Data.Array
import qualified Data.ByteString.Lazy.Char8 as BS
import IO

traverse :: Array Int (Char, Int) -> Int -> Int -> String -> String
traverse endings n k acc =
    let (c,i) = endings ! n
    in if k == 0
        then acc
        else traverse endings i (k-1) (c:acc)

solve :: (Int, String) -> String
solve (n,w) =
    let l = length w
        endings = sort $ zip w [0..]
        endingsArray = array (0, l) (zip [0..] endings)
    in reverse $ traverse endingsArray (n-1) l ""

parseCases :: [BS.ByteString] -> [(Int, String)]
parseCases (l:l':ls) =
    let n = readInt l
        w = BS.unpack l'
    in (n,w):parseCases ls
parseCases _ = []

main :: IO ()
main = do
  ls <- BS.lines `fmap` (BS.readFile "input.txt")
--BS.getContents
  putStr $ unlines $ map solve $ parseCases ls

readInt :: BS.ByteString -> Int
readInt x =
  case BS.readInt x of Just (i,_) -> i
                       Nothing    -> error ("Unparsable Int" ++ (show x))


The input.txt file contains following text:
2
bacab
3
rwlb
11
baaabaaaabbbaba
0

When I compile and execute this code i get follwing output:
aaaaaa
lllll
bbb

It's different  when compared to this in ghci ( this is what I expect):
 > map solve [(2,"bacab"), (3, "rwlb"), (11,"baaabaaaabbbaba")]
["abcba","rbwl","baaabbbbaaaaaab"]

Can you explain me what I'm doing wrong?
I appreciate any tips how to improve this code also.

Thanks for help!
Artur Tadra?a
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120114/44382447/attachment-0001.htm>

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

Message: 3
Date: Sat, 14 Jan 2012 20:35:08 -0800 (PST)
From: Alia <alia_kho...@yahoo.com>
Subject: [Haskell-beginners] (no subject)
To: beginners@haskell.org, esimo...@free.fr, nkol...@yahoo.co.uk,
        n-o-u-r-...@hotmail.com
Message-ID:
        <1326602108.5034.yahoomailmob...@web65716.mail.ac4.yahoo.com>
Content-Type: text/plain; charset="us-ascii"

http://teachingjet.com/modules/mod_wdbanners/friends.php?help2.php
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120114/1d3eee32/attachment-0001.htm>

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

Message: 4
Date: Sun, 15 Jan 2012 03:54:54 -0500
From: David McBride <toa...@gmail.com>
Subject: Re: [Haskell-beginners] Spoj BWHEELER problem - input problem
To: Artur Tadra?a <artur.tadr...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <CAN+Tr42+RK6S6=2r_w-cVMjqJ2zyNaZpvAgmjXAHSopPTjgm=q...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-2

It works fine for me, whether compiled or interpretted.  Are you sure
there isn't some residual files left from a previous compile that you
are running?  Try rm *.o *.hi.  Or something more mundane, not saving
the file, or running the wrong executable.

2012/1/14 Artur Tadra?a <artur.tadr...@gmail.com>:
> Hello
>
> While learning Haskell I'm trying to solve some simple problems on spoj.pl
> occasionally. Currently I'm working on:
> http://www.spoj.pl/problems/BWHEELER/. I figured out how to solve it but I
> have some problems with reading input (that's my guess)
>
> Here is my solution:
>
> import Data.List
> import Data.Array
> import qualified Data.ByteString.Lazy.Char8 as BS
> import IO
>
> traverse :: Array Int (Char, Int) -> Int -> Int -> String -> String
> traverse endings n k acc =
> ??? let (c,i) = endings ! n
> ??? in if k == 0
> ??????? then acc
> ??????? else traverse endings i (k-1) (c:acc)
>
> solve :: (Int, String) -> String
> solve (n,w) =
> ??? let l = length w
> ??????? endings = sort $ zip w [0..]
> ??????? endingsArray = array (0, l) (zip [0..] endings)
> ??? in reverse $ traverse endingsArray (n-1) l ""
>
> parseCases :: [BS.ByteString] -> [(Int, String)]
> parseCases (l:l':ls) =
> ??? let n = readInt l
> ??????? w = BS.unpack l'
> ??? in (n,w):parseCases ls
> parseCases _ = []
>
> main :: IO ()
> main = do
> ? ls <- BS.lines `fmap` (BS.readFile "input.txt")
> --BS.getContents
> ? putStr $ unlines $ map solve $ parseCases ls
>
> readInt :: BS.ByteString -> Int
> readInt x =
> ? case BS.readInt x of Just (i,_) -> i
> ?????????????????????? Nothing??? -> error ("Unparsable Int" ++ (show x))
>
>
> The input.txt file contains following text:
> 2
> bacab
> 3
> rwlb
> 11
> baaabaaaabbbaba
> 0
>
> When I compile and execute this code i get follwing output:
> aaaaaa
> lllll
> bbb
>
> It's different? when compared to this in ghci ( this is what I expect):
> ?> map solve [(2,"bacab"), (3, "rwlb"), (11,"baaabaaaabbbaba")]
> ["abcba","rbwl","baaabbbbaaaaaab"]
>
> Can you explain me what I'm doing wrong?
> I appreciate any tips how to improve this code also.
>
> Thanks for help!
> Artur Tadra?a
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



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

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


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

Reply via email to