new Library Infrastructure spec.

Keith Wansbrough Keith.Wansbrough at cl.cam.ac.uk
Tue Jun 8 05:46:11 EDT 2004


Isaac wrote:

> > 2. In section 4.1, the syntax for pkg.desc is discussed.  I think the
> >    simplest and least surprising syntax to use would be the RFC-2822
> >    email message header syntax (specifically sections 2.2 and 2.2.3).
> >    That is, each field is first written as
> 
> I'm leaning toward the Haskell read / show syntax.


I think Haskell read / show syntax is the right syntax for the
individual field bodies, but I'm not sure it's the right syntax for
the entire file.  You want to be able to handle optional fields
(possibly with defaults) and future extensions, and these are much
easier if you have a first phase that parses the file into a list of
(fieldname,fieldbody) pairs.  I stand by my assertion that RFC-2822
(email) message header format is the right format to use for this.

I retract my earlier BNF, though: that BNF didn't handle line breaks
within strings properly.  I think that we should really do it as two
passes: a String -> [(String,String)] pass, and then a
[(String,String)] -> PackageDescription pass.

I've attached some code.

--KW 8-)
-------------- next part --------------
-- an idea for splitting fields a la RFC2822.
-- for Haskell Libraries email list 2004-06-08.

module Fieldsplit where

import Char

fieldsplit :: String -> [(String,String)]
fieldsplit s =
  goheader (lines s)
      where goheader [] = []
            goheader ("":ls) = goheader ls  -- in RFC-2822, this marks the end of headers
            goheader (r@(c:_):ls) | isSpace c = error "Missing field header"
                                  | otherwise = case break (== ':') r of
                                                  (h,':':r') -> gobody h ls [r']
                                                  _          -> error "Missing colon"

            gobody h (r@(c:_):ls) rs | isSpace c = gobody h ls (r:rs)
            gobody h ls           rs             = (h, unwords (reverse rs)) : goheader ls
-------------- next part --------------
Keith Wansbrough <kw217 at cl.cam.ac.uk>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.


More information about the Libraries mailing list