SPOJ

From HaskellWiki
Revision as of 13:41, 24 September 2009 by Steve C (talk | contribs) (Update section on TEST problem)
Jump to navigation Jump to search

SPOJ (Sphere Online Judge) is an automated programming contest website. It has a large problemset archive, and accept solutions in many languages, including Haskell. Posting answers to questions is generally frowned upon as it enables cheating, but giving example solutions to a few of the simpler questions is OK as is allows beginners to get started on SPOJ.

Haskell and SPOJ

Many Online Judges support just a few languages such as C, C++, Pascal and Java. SPOJ is unique in that it supports many (currently over 30) languages, including Haskell. Most problems have a time limit which is calculated to be a comfortable time when solving the problem in C. But it can be a challenge (and sometimes impossible) to solve the problem, within this time limit, using other languages.

Getting Started: Solution to TEST

TEST description: the input consists of one number per line, the program should echo each number until 42 is reached, at which point the program should exit.

main :: IO ()
main = mapM_ putStrLn . takeWhile (/="42") . lines =<< getContents

or

main :: IO ()
main = interact f
  where f = unlines . takeWhile (/="42") . words

Solution to INTEST

INTEST description: the first line of input contains two numbers: n and k. The input then consists of n lines of numbers. The output of the program should be the count of the numbers which are divisible by k.

Prior to the installation of GHC 6.6.1, it was quite difficult, if not impossible, to pass this demonstration. This solution shows a simple, reasonably efficient manner of using the new ByteString library to achieve acceptable times.

import Data.List (unfoldr)
import qualified Data.ByteString.Char8 as SS

divisibleBy :: Int -> Int -> Bool
a `divisibleBy` n = a `rem` n == 0

readInt1 :: SS.ByteString -> Maybe (Int, SS.ByteString)
readInt1 cs = do
  (n, cs') <- SS.readInt cs
  return (n, SS.tail cs')

main = do
  cs <- SS.getContents  -- This is the only line of I/O
  let n:k:ns = unfoldr readInt1 cs
      count  = length $ filter (`divisibleBy` k) ns
  print count

Techniques for dealing with problems efficiently

This section accumulates some earned wisdom about writing Haskell programs which overcome some of the technical obstacles in SPOJ. These are not spoilers, hopefully, but useful tips in general about auxiliary issues.

I/O

SPOJ has finally installed the GHC version 6.6.1. This makes the new, alternative I/O module available: Data.ByteString. Hopefully, it will be possible to find solutions for many more problems -- which could not be solved efficiently in the past because of mundane issues like I/O.

Brief Details

ByteStrings come in two varieties: Strict (default), and Lazy. Strict ByteStrings, in brief, are implemented by a foreign pointer to a block of memory which is filled by low level operations. The ByteString data type points to this memory region and also contains two Ints which track relative position and length. This means that many operations on ByteStrings can re-use memory and merely manipulate the two Ints.

Data.ByteString.Lazy is a layer on top which provides the ByteString API, but now the data is only read in chunks of Strict ByteStrings when necessary.

Don Stewart and others have put a great deal of excellent work into the library to ensure that the high-level interface will be optimized into efficient code. However, it may behoove you to inspect the source code for yourself, which is quite accessible and available in the GHC repository under libraries/base/Data/.

For SPOJ purposes, the most common operation is reading some kind of list of Ints. The code for INTEST above demonstrates one simple way to take advantage of ByteString. Using a similar technique may suffice for many problems. However, there are more advanced possibilities which could offer improvements in some cases.

The module is normally imported qualified because it shares many names with standard Prelude functions. I use the prefix SS in my examples, for Strict byteString.

Span and Break

The span and break functions available from ByteString can be used to parse the occasional non-numeric value in input. For example, the following code skips a line:

import qualified Data.ByteString.Char8 as SS
-- ...
skipLine cs = snd $ SS.span (== '\n') cs'
  where (_, cs') = SS.break (== '\n') cs

The nice part about span and break is that when it is found in the form span (== c) for all characters c, it is optimized down to a simple memchr.

Lazy ByteStrings

In general, I find that the Strict ByteStrings are more than adequate, and sometimes more complicated usage does not result in better performance. There are cases where Lazy ByteStrings do seem handle better. You can use Lazy ByteStrings as a drop-in replacement for Strict, mostly. But that does not generally confer any advantage. The best part about Lazy ByteStrings is the function called toChunks. This function provides an interface to the lower-level portions which actually operate by reading chunks of data into Strict ByteStrings acting as buffers. The chunks are kept in a lazy list, so each chunk is only read on-demand. However, you are getting the data as efficiently as the library deems possible.

Don Stewart Discusses Chunked ByteString Input

Arrays

From time to time you may want to write an algorithm using Mutable Arrays in Haskell. While it may be tempting to jump right into arrays, you should consider that the Data.IntMap and Data.IntSet libraries are actually very fast and convenient. You may be surprised to find that they are more than sufficient. In fact, I would argue that unless you plan to use Unboxed Arrays, you should stick with these.

If you are set on using a mutable array, go ahead and read the wiki page Arrays for a summary of the choices available. I am going to assume that you know the basics as imparted on that page. In particular, I'll be talking about ST and IO arrays.

IO arrays are probably the easiest mutable arrays to use. They are fairly straightforward, but require you to stay in the IO monad. I made the mistake of avoiding IO arrays originally, but through some strange fluke, it turns out there are many cases where IO arrays still have the best performance.

ST arrays have the advantage that they can be easily constructed in monadic code, but then returned to the functional world (without invoking voodoo like unsafePerformIO). However, ST itself can make the resulting type expressions confusing. In fact, it appears that you cannot type-annotate certain expressions in ST monadic code without going outside Haskell'98.

Personally, I try to write my mutable array code monad-agnostic. This way I can compare IO array performance to ST array performance. However this can really make the type annotations confusing if you haven't seen it before!

After seeing a few examples, though, I think anyone can pick up on the pattern. The usage isn't that difficult, once you see how the types fit together.

Creating a mutable array

There is a set of functions defined to work with mutable arrays separate from those that work on immutable arrays. You will want to import Data.Array.{ST,IO} depending on what you use.

  a <- newArray (1, 10) 0

newArray expects bounds to be supplied just like for immutable arrays. The second argument is the initial value with which to initialize all the elements. A simple example of usage:

  runSTArray (newArray (1, 10) 0)

The runSTArray function is an efficient helper function which you use when you want to create an array in ST but return an immutable array. It also happens to be a special case where newArray doesn't need a type-annotation.

In general, you will have to supply some kind of type-annotation for newArray. Let's suppose you are using Unboxed Arrays and want to write the same code.

  runSTUArray (newArray (1, 10) 0)

But now GHC will spit at you an incomprehensible error message. Well it's not so bad actually, it says,

    No instance for (MArray (STUArray s) t (ST s))

GHC has the wrong idea about our array. We need to inform it that our array is indexed by Ints and contains Ints.

  runSTUArray (newArray (1,10) 0 :: ST s (STUArray s Int Int))

Remember the type of newArray:

  newArray :: (MArray a e m, Ix i) => (i, i) -> e -> m (a i e)

The result must be in a monad. That monad is ST s. s is the type-variable which represents the "state" which must remain contained within the monad. But the STUArray needs to know about that "state." The type-signature expresses that the monad and the array are sharing this "state."

At this point, you are pretty much ready to do anything with arrays. I'll show you one more example which uses the more general function runST.

runST (do 
  a <- newArray (1, 10) 1 :: ST s (STUArray s Int Int)
  mapM_ (\ i -> do
           x <- readArray a (i - 2)
           y <- readArray a (i - 1)
           writeArray a i (x + y))
        [3 .. 10]
  v  <- readArray a 10
  a' <- unsafeFreeze a
  return (v, a' :: Array Int Int))

This code computes the first 10 Fibonacci numbers and returns a pair containing the 10th and array turned immutable. Some notes:

  • unsafeFreeze turns the array immutable in-place and therefore renders it unsafe to perform any mutations after the fact. If you don't change the array after unsafeFreeze, it's perfectly fine. runSTArray uses this internally.
  • Second, I had to put the type-annotation for a' on the final line instead of the binding line. This is one of those little annoyances about ST which I mentioned earlier. The reason I did not say a' <- unsafeFreeze a :: ST s (Array Int Int) is because GHC views this s as being different from the one on the first line. Clearly, GHC can't allow you to mix "state" from different places. Of course, we know that's not happening, but without lexically scoped type variables, GHC can't discern.
  • Don't do runST $ do .... It doesn't work (at the moment). The reasons are obscure, having to do with unification and higher-rank polymorphism. Do runST (do ...) instead.

Hopefully at this point you can see that it isn't difficult to get mutable arrays, so long as you know how the type annotations are supposed to go. IO arrays have simpler type annotations, because the type-variable s is not necessary. So you can write the above example as:

do 
  a <- newArray (1, 10) 1 :: IO (IOUArray Int Int)
  mapM_ (\ i -> do
           x <- readArray a (i - 2)
           y <- readArray a (i - 1)
           writeArray a i (x + y))
        [3 .. 10]
  v  <- readArray a 10
  a' <- unsafeFreeze a :: IO (Array Int Int)
  return (v, a')

Generalized mutable arrays

Mutable arrays are instances of the typeclass MArray. MArray a e m is a multi-parameter type-class where a is the array-type, e is the element-type, and m is the monad.

Sometimes you will want to write your code so that it can operate on any mutable array. Generally, type-inference will be more than capable. The types generated can be a bit confusing, though. Other times, you may want to create a datatype, in which case you will need to know how to specify it for MArrays.

Here is an example which sums up an array of Ints:

sumArray a = do
  (s,e) <- getBounds a
  let loop sum i 
        | i > e     = return sum
        | otherwise = do
          x <- readArray a i
          loop (sum + x) (i + 1)
  loop 0 s

when we ask the type of this function we get a pretty hefty answer:

sumArray :: (MArray a e m, Num e, Ix i, Num i) => a i e -> m e

Our function works on any mutable array type a, with index type i, element type e, and in monad m.

We can create a datatype which contains a mutable array by simply satisfying the kind requirements for MArray:

data IntArray a = IA (a Int Int)

sumIntArray (IA a) = do
  (s,e) <- getBounds a
  let loop sum i
        | i > e     = return sum
        | otherwise = do
          x <- readArray a i
          loop (sum + x) (i + 1)
  loop 0 s

But keep in mind, you still may need to supply some kind of type annotation when you construct the datatype, so that newArray knows which kind of array to create.

Unsafe Array Access

There are two lower-level array access functions which can help you squeeze out a bit more performance: unsafeWrite and unsafeRead.

Just import Data.Array.Base (unsafeWrite, unsafeRead) and use these functions in place of writeArray and readArray when you feel it is safe. The first difference is that the normal array functions check array-bounds before doing anything. You can crash your program using the unsafe ones, if you access an index out-of-bounds. The second difference is that the unsafe functions do not perform any Index-arithmetic. They expect to be handed an array index that has already been converted into a zero-based, flat system. If you already use zero-based flat arrays, great. Otherwise, you may have to do a small bit of arithmetic first.

Garbage Collection

SPOJ has a fairly rigid framework for running programs, naturally. While it is, thankfully, possible to specify compiler options inside Haskell programs, the same is not true for RTS options. Unfortunately, sometimes there are circumstances where you would like to tweak runtime options like on the Garbage Collector. There is one technique that I have found which will allow you to tune the GC for your programs when they run on SPOJ.

The gist of it is to restart the program using System.Posix tools. The major hurdle is finding the location of the program executable so that it may be supplied to the executeFile function. The following code achieves this:

{-# OPTIONS -ffi #-}
-- or -fglasgow-exts
import System.Environment (getArgs)
import System.Posix.Process (executeFile)
import Foreign.C.Types (CInt)
import Foreign.C.String (CString, peekCString)
import Foreign (peek, alloca, peekElemOff, Ptr)

main = do
  flags    <- getArgs
  progname <- getFullProgName
  if null flags
    then 
      -- Supply an "argument" so that flags will not be null.
      -- RTS option -A100m will increase the allocation area size
      -- to 100 megabytes.
      executeFile progname False ["r","+RTS","-A100m"] Nothing
    else
      realMain

-- Now the trickier part: getProgName in GHC does not return the
-- full path, for "portability" reasons.  SPOJ does not run
-- programs from the current directory.  That means we need to
-- find the full path to the program some other way.

foreign import ccall unsafe "getProgArgv"
  getProgArgv :: Ptr CInt -> Ptr (Ptr CString) -> IO ()

-- As it turns out, the C function which getProgName uses actually
-- does return the full path.  But then getProgName cuts it out
-- before returning it.  This is a version of getProgName which
-- leaves the full path intact.

getFullProgName :: IO String
getFullProgName =
  alloca $ \ p_argc ->
  alloca $ \ p_argv -> do
    getProgArgv p_argc p_argv
    argv <- peek p_argv
    s    <- peekElemOff argv 0 >>= peekCString
    return s