Literate Programming

Steffen Mazanek steffen.mazanek@unibw-muenchen.de
23 Apr 2003 19:41:01 +0200


--=-k5K+GzgVVTA1TedU8Wav
Content-Type: text/plain
Content-Transfer-Encoding: 7bit

Hello.

Simon Marlow wrote:
>I don't think that's entirely fair.  Most of the libraries that come
>with GHC (and Hugs, and soon Nhc) are documented.  See for example
>
>  http://www.haskell.org/ghc/docs/latest/html/base/index.html
        
As far as I know (please correct me, if I err) one shortcoming of
Haddock is its restriction to .hs-files.
I think there are a lot of real literate programmers out there which
would prefer a Haskell documentation tool for their literate Haskell
scripts.
Therefore I present the tool lhs2hs, which may seem very puristic and
errorprone at this time (in fact it is). 
It transforms a .lhs-file into a .hs file. Furthermore tex-comments
are used to pass information to e.g. Haddock:
Example:

%%Haddock:this function...
%%Haddock:...

>testfun...

%%Haddock:another function...

\begin{code}
...
\end{code}

This .lhs file becomes transformed to

{-|
this function...
...
-}

testfun...

{-|
another function...
-}
...

Ok, its simple, but it can be useful and it is extensible!
I have attached the very first version. 
Type:
ghc --make Main.lhs -package util -o lhs2hs 
./lhs2hs -h Main.lhs
haddock -h Main.hs
latex Main.lhs

Another idea to simplify literate programming with Haskell:
allow XML (introduce a new file extension .xhs), e.g.:
<hscomment describes="quicksort">
sorts a list
</hscomment>
<hsdecl defines "quicksort">
quicksort...
</hsdecl>
This would allow more transformations!
Bye,
Steffen

--=-k5K+GzgVVTA1TedU8Wav
Content-Disposition: attachment; filename=Main.lhs
Content-Type: text/x-literate-haskell; name=Main.lhs; charset=ISO-8859-1
Content-Transfer-Encoding: 7bit

\documentclass[12pt]{report}
\usepackage{verbatim}

\begin{document}
\newenvironment{code}{\footnotesize\verbatim}{\endverbatim\normalsize}

\section*{Introduction}
This program's task is to transform a {\em literate 
haskell script} \texttt{name.lhs} into a "normal" haskell script 
\texttt{name.hs}.
Thereby special tex commentaries can be invoked.
This can be extremely useful when
you run e.g. documentation tools like Haddock." 

\section*{Invocation of Haddock}
Annotations in Tex have to start with \verb|%%Haddock:|.
Call \texttt{lhs2hs} with the option \texttt{-h}.


\section*{Implementation}

%%Haddock:Module      :  Main
%%Haddock:Copyright   :  (c) Steffen Mazanek 2003
%%Haddock:License     :  Go get it :-)
%%Haddock:
%%Haddock:Maintainer  :  steffen.mazanek@unibw-muenchen.de
%%Haddock:Stability   :  don't ask *g*
%%Haddock:Portability :  only with notebooks :-/
%%Haddock:
%%Haddock:This module provides a program which transforms
%%Haddock:literate Haskell scripts into /normal/ Haskell scripts.
%%Haddock:Cool, documenting projects is fun using lhs2hs!


\begin{code}
module Main where

import GetOpt
import System
import Monad
import List
\end{code}
%%Haddock:This is the main function which is invoked automatically whenever the executable is started.
%%Haddock:It reads the command line arguments and extracts several options and the files to transform.
\begin{code}
main::IO ()
main = do
          args <- getArgs
          case getOpt Permute options args of
            (flags, args, []    ) -> run flags args
            (_,     _,    errors) -> do sequence_ (map putStr errors)
                                        putStr usage
\end{code}

%%Haddock:The Flag data type is somewhat puristic but may evolve in the future.
%%Haddock:It looks a bit complicated at first but eases extensibility.

\begin{code}
data Flag = Flag_Haddock deriving (Show, Eq)
\end{code}

%%Haddock:"run" works out all the files step by step. Thereby the flags are checked
%%Haddock:and complying actions take place.

\begin{code}
run flags [] = putStrLn "Ready!"
run flags (a:args) = 
     do 
     when (not $ endsWith ".lhs" a)
           (putStrLn "You should invoke .lhs-files!")
     when (Flag_Haddock `elem` flags) $ do 
           putStrLn $ "Performing Haddock-Transformation on " ++ a
           c<-readFile a
           writeFile (takeWhile (/='.') a ++ ".hs") (perform haddock c) 
     run flags args
\end{code}
%%Haddock:As the name says "endsWith" is the counterpart of "startsWith".
\begin{code}
endsWith x = elem x . tails 

perform f = unlines.f.lines
\end{code}
Here something extremely stupid has happened. The inline \verb|\end{code}|
was ambiguous and rose a latex error. So we have added a senseless character (\verb|:|). 
%%Haddock:The transformation (and hence most of the complexity) are hidden by this function.
%%Haddock:It gets the lines of a particular file and performs e.g. some filter operations.
\begin{code}
haddock::[String]->[String]
haddock [] = []
haddock a@(x:xs) 
  | x == "\\begin{code}" = let (p1,p2) = splitCond (== '\\':"end{code}") xs in 
                                        p1 ++ haddock (tail p2)
  | x == [] = []:haddock xs
  | head x == '>' = tail x:haddock xs  
  --tex code
  | startsWith "%%Haddock:" x = 
        let (p1,p2) = splitCond (not.startsWith "%%Haddock:") a in 
        "{-|":map (tail.dropWhile (/=':')) p1 ++ "-}":haddock p2 
  | otherwise = haddock xs
\end{code}
%%Haddock:Somewhat standard but not to find in the libraries. Checks whether a particular
%%Haddock:String starts with a certain String or not.
%Dies ist ein normaler Latex-Kommentar
\begin{code}
startsWith [] _ = True
startsWith _ [] = False
startsWith (x:xs) (y:ys) = x == y && startsWith xs ys 
\end{code}
\begin{code}
splitCond::(a->Bool)->[a]->([a],[a])
splitCond p [] = ([],[])
splitCond p (x:xs) 
  | p x = ([], x:xs)
  | otherwise = let (p1,p2) = splitCond p xs in (x:p1,p2)

options =
  [
    Option ['h']  ["haddock"]  (NoArg Flag_Haddock)
        "use haddock comments"]

usage = "lhs2hs [options] file"
\end{code}
\end{document}

--=-k5K+GzgVVTA1TedU8Wav--