[Haskell-cafe] Interpreting profiling results

Patrick LeBoutillier patrick.leboutillier at gmail.com
Sun Jan 3 20:17:06 EST 2010


Hi,

This question didn't get any replies on the beginners list, I thought
I'd try it here...

I've written (and improved using other solutions I've found on the
net) a simple sudoku solver which I'm trying to profile. Here is the
code:


import Array
import List (transpose, nub, (\\))
import Data.List

data Sudoku = Sudoku { unit :: Int, cells :: Array (Int, Int) Int,
holes :: [(Int, Int)] }

cell :: Sudoku -> (Int, Int) -> Int
cell s i = (cells s) ! i

instance Read Sudoku where
 readsPrec _ s = [(Sudoku unit cells holes, "")]
   where unit = length . words . head . lines $ s
         cells = listArray ((1, 1), (unit, unit)) (map read . words $ s)
         holes = [ c | c <- indices cells, (cells ! c) == 0]

instance Show Sudoku where
 show s = unlines [unwords [show $ cell s (x,y) | x <- [1 .. unit s]]
| y <- [1 .. unit s]]

genNums :: Sudoku -> (Int, Int) -> [Int]
genNums s c@(i,j) = ([1 .. u] \\) . nub $ used
 where
   used = (row s u i j) ++ (col s u i j) ++ (square s sq u i j)
   u = unit s
   sq = truncate . sqrt . fromIntegral $ u

row s u i j = [cell s (i, y) | y <- [1 .. u]]

col s u i j = [cell s (x, j) | x <- [1 .. u]]

square s sq u i j = [cell s (x, y) | y <- [1 .. u], x <- [1 .. u], f x i, f y j]
 where f a b = div (a-1) sq == div (b-1) sq

solve :: Sudoku -> [Sudoku]
solve s =
 case holes s of
   [] -> [s]
   (h:hs) -> do
     n <- genNums s h
     let s' = Sudoku (unit s) ((cells s) // [(h, n)]) hs
     solve s'

main = print . head . solve . read =<< getContents


When I compile as such:

$ ghc -O2 --make Sudoku.hs -prof -auto-all -caf-all -fforce-recomp

and run it on the following puzzle:

0 2 3 4
3 4 1 0
2 1 4 0
0 3 2 1

I get the following profiling report:

       Fri Jan  1 10:34 2010 Time and Allocation Profiling Report  (Final)

          Sudoku +RTS -p -RTS

       total time  =        0.00 secs   (0 ticks @ 20 ms)
       total alloc =     165,728 bytes  (excludes profiling overheads)

COST CENTRE                    MODULE               %time %alloc

CAF                            GHC.Handle             0.0   10.7
CAF                            Text.Read.Lex          0.0    2.1
CAF                            GHC.Read               0.0    1.2
square                         Main                   0.0    2.8
solve                          Main                   0.0    1.3
show_aVx                       Main                   0.0    3.7
readsPrec_aYF                  Main                   0.0   60.6
main                           Main                   0.0    9.6
genNums                        Main                   0.0    5.0
cell                           Main                   0.0    1.2



                       individual    inherited
COST CENTRE              MODULE
      no.    entries  %time %alloc   %time %alloc

MAIN                     MAIN
        1           0   0.0    0.3     0.0  100.0
 main                    Main
      186           1   0.0    9.6     0.0   85.6
 show_aVx               Main
      196           2   0.0    3.7     0.0    3.7
  cell                  Main
      197          16   0.0    0.0     0.0    0.0
 solve                  Main
      188           5   0.0    1.3     0.0   11.8
  genNums               Main
      189           8   0.0    5.0     0.0   10.4
   square               Main
      194          88   0.0    2.8     0.0    3.2
    cell                Main
      195          16   0.0    0.4     0.0    0.4
   col                  Main
      192           4   0.0    0.7     0.0    1.1
    cell                Main
      193          16   0.0    0.4     0.0    0.4
   row                  Main
      190           4   0.0    0.7     0.0    1.1
    cell                Main
      191          16   0.0    0.4     0.0    0.4
 readsPrec_aYF          Main
      187           3   0.0   60.6     0.0   60.6
 CAF                     GHC.Read
      151           1   0.0    1.2     0.0    1.2
 CAF                     Text.Read.Lex
      144           8   0.0    2.1     0.0    2.1
 CAF                     GHC.Handle
      128           4   0.0   10.7     0.0   10.7
 CAF                     GHC.Conc
      127           1   0.0    0.0     0.0    0.0

Does the column 'entries' represent the number of times the function
was called? If so, I don't understand how the 'square' function could
be called 88 times when it's caller is only called 8 times. Same thing
with 'genNums' (called 8 times, and solve called 5 times)

What am I missing here?

Patrick

--
=====================
Patrick LeBoutillier
Rosemère, Québec, Canada


More information about the Haskell-Cafe mailing list