Greetings Gentlemen (and Ladies),

As part of my small and simple framework for making presentations in Haskell I have a module which, given some text, makes a .tex file and then converts it to .svg for loading into a cairo canvas. It features simple caching (performs md5 on the contents of the .tex file and uses that as the file name... if an .svg by that name exists, it'll get loaded rather than regenerated).

Unfortunately, it also segfaults once in a while, probably indicating I have some kind of race condition ... but I can't figure out why. This is the only point in my code that I think I'm using any concurrency, although I'm compiling with ghc --make -threaded. Compiling without -threaded results in a deadlock.

Ubuntu 8.10, 64-bit, GHC 6.8.2.

Any advice? I'm attaching the module in question (79 lines).

Sincerely,

Rafal Kolanski.
module LatexSVG (updateSVG, updateSVG') where

import System.Process
import Control.Concurrent (forkIO)
import Control.Monad (when)
import System.IO
import System.Directory (doesFileExist)
import System.Exit

workingDir = "tex/"

prefix = unlines $
           ["\\documentclass{minimal} ",
            "\\usepackage{graphicx,latexsym,amsmath,url,color}",
            "\\usepackage{amssymb,amsmath,wasysym, pst-node, color}",
            "\\usepackage{url}",
            "\\usepackage{isabelle,isabellesym}",
            "%\\usepackage{mathpartir}",
            "\\definecolor{dblue}{rgb}{0,0,0.4}",
            "\\definecolor{blue}{rgb}{0,0,0.6}",
            "\\definecolor{green}{rgb}{0,0.6,0}",
            "\\definecolor{gray}{rgb}{0.7,0.7,0.7}",
            "\\definecolor{dblue}{rgb}{0,0,0.6}",
            "\\definecolor{darkgray}{rgb}{0.4,0.4,0.4}",
            "\\definecolor{red}{rgb}{0.6,0,0}",
            "\\begin{document}"]

suffix = "\n\\end{document}"

-- Pass text to md5sum and drop the final "  -" when returning
hashMD5 text = do
    (inp,out,err,pid) <- runInteractiveProcess "md5sum" [] Nothing Nothing
    forkIO $ do 
        hPutStrLn inp text
        hClose inp
    exit <- waitForProcess pid
    case exit of ExitFailure _ -> error "md5sum fail" 
                 _ -> return ()
    md5hash <- hGetContents out
    return $ takeWhile (\x -> x /= ' ') md5hash

blindExecWithFail cmd args dir = do
    (inp,out,err,pid) <- runInteractiveProcess cmd args (Just dir) Nothing
    exit <- waitForProcess pid
    case exit of ExitFailure _ -> error $ cmd ++ " " ++ (show args) ++ "fail" 
                 _ -> return ()

generateSVG text filebase = do
    -- Create a .tex file
    writeFile (workingDir ++ filebase ++ ".tex") text
    -- Run pdflatex over it
    blindExecWithFail "pdflatex" [filebase] workingDir
    -- Run pstoedit on resulting .pdf
    blindExecWithFail "pstoedit" 
                      ["-page 1","-dt","-psarg","-r9600x9600", 
                       filebase ++ ".pdf", filebase ++ ".sk"] 
                      workingDir
    -- Run skconvert on resulting .sk
    blindExecWithFail "skconvert" 
                      [filebase ++ ".sk", filebase ++ ".svg"]
                      workingDir

updateSVG' :: [Char] -> [Char] -> [Char] -> IO [Char]
updateSVG' prefix suffix text = do
    -- Hash the tex
    let tex = prefix ++ text ++ suffix
    md5hash <- hashMD5 tex
    -- Filenames are the hash prefixed with hash and ending with extension
    let filebase = "hash" ++ md5hash
    -- See if an svg file by that name exists
    svge <- doesFileExist $ workingDir ++ filebase ++ ".svg"
    when (not svge) $! do
        putStrLn $ filebase ++ ".svg does not exist, creating"
        generateSVG tex filebase
    return $ workingDir ++ filebase ++ ".svg"

updateSVG :: [Char] -> IO [Char]
updateSVG = updateSVG' prefix suffix

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to