newbie questions
Max Ischenko
max@malva.ua
Wed, 8 Jan 2003 09:19:10 +0200
Hello!
I'm started to learn Haskell and have some questions.
After reading a "Gentle introduction..." I've decided to write a
simple program -- a complement to Literate.hs from hugs demos which
reads a plain haskell source file and converts it to literate haskell
source.
The source code of this program follows.
Now the questions:
- To be able to run it both in Hugs and by GHC I need an
`import Data.Char(isSpace) for GHC`. Can this be conditionally
included in a source for GHC only?
- Am I reinventing the wheel with my `pad` function? Could I use some
standard function(s) instead?
- What if I'd want to do a more complex processing, like handling {--}
comments? The `classify` function analize one line at a time and
I'd want too see a surronding context? Should I use another pass,
just like for `addblanks`?
module Lit where
import System(getArgs)
-- classification of the haskell source lines
data Classified = Program String | Blank | Comment String
deriving (Show)
classify :: String -> Classified
classify ('-':'-':xs) = Comment (dropWhile isSpace xs)
classify s | all isSpace s = Blank
| otherwise = Program s
unclassify :: Classified -> String
unclassify (Program s) = "> " ++ s
unclassify (Comment s) = s
unclassify Blank = []
process :: String -> String
process hs = unlines (map unclassify (addblanks (clines hs)))
clines hs = map classify (lines hs)
-- inserts a blank between a program line and a comment line where needed
addblanks :: [Classified] -> [Classified]
addblanks = pad needBlank Blank
needBlank :: Classified -> Classified -> Bool
needBlank (Program p) (Comment c) = True
needBlank (Comment c) (Program p) = True
needBlank _ _ = False
-- inserts a value between those adjanced elements for which
-- function p returns True
pad :: (a -> a -> Bool) -> a -> [a] -> [a]
pad p value [] = []
pad p value (x:[]) = [x]
pad p value (x:xs) | p x (head xs) = x:value:rest
| otherwise = x:rest
where rest = pad p value xs
usage err = err ++ "\n" ++ "USAGE: lit <filename>"
main :: IO ()
main = do strs <- getArgs
case strs of
[] -> ioError (userError (usage "Not enough arguments."))
[str] -> mklit str
_ -> ioError (userError (usage "Too many arguments."))
-- takes a filename without suffix, reads a plain haskell source
-- and creates a literate haskell source.
mklit :: String -> IO ()
mklit f = do hs <- readFile (f ++ ".hs")
writeFile (f ++ ".lhs") (process hs)
--
Bst rgrds, M.A.X.: Mechanical Artificial Xenomorph.