Sigbjorn Finne wrote:
> [...] A new GC2 snapshot that includes support for %enum is now
> (finally) available, see
>
> ftp://ftp.dcs.gla.ac.uk/pub/haskell/glasgow/green-card/
>
> BTW, the snapshot includes a new lexer, so there might be a lexing
> buglet or two lurking in there..
I couldn't find a lexing buglet (yet >:-), but a few other glitches:
* A CTRL-G in the Makefile
* A layout buglet
* A malformed string
* A naming typo
---------------------------------------------------------------------------
diff -r -c green-card.orig/lib/ghc/Makefile green-card/lib/ghc/Makefile
*** green-card.orig/lib/ghc/Makefile Tue Jan 20 18:18:52 1998
--- green-card/lib/ghc/Makefile Fri Apr 10 17:01:39 1998
***************
*** 1,4 ****
! ^G# (GNU) Makefile for Green Card (GHC)
### User serviceable parts ###
#HC = /path/to/ghc
--- 1,4 ----
! # (GNU) Makefile for Green Card (GHC)
### User serviceable parts ###
#HC = /path/to/ghc
diff -r -c green-card.orig/src/FillIn.lhs green-card/src/FillIn.lhs
*** green-card.orig/src/FillIn.lhs Tue Apr 7 17:29:49 1998
--- green-card/src/FillIn.lhs Fri Apr 10 16:39:07 1998
***************
*** 106,112 ****
_ -> do
lss <- mapM fillIn procs
return (d':concat lss)
! where
procs =
[ ProcSpec (noSrcLoc, hname, ty)
Nothing
--- 106,112 ----
_ -> do
lss <- mapM fillIn procs
return (d':concat lss)
! where
procs =
[ ProcSpec (noSrcLoc, hname, ty)
Nothing
diff -r -c green-card.orig/src/Proc.lhs green-card/src/Proc.lhs
*** green-card.orig/src/Proc.lhs Tue Apr 7 17:29:49 1998
--- green-card/src/Proc.lhs Fri Apr 10 17:42:56 1998
***************
*** 199,211 ****
hole
marshall_alts = map ( \ (con, val) -> (text (upperName con), rhs (con,val)))
defs
unmarshall_alts = foldr mkIf (text ("error (\"unmarshall_"++nm++":\
! \ unknown value (\"++show arg1++\")\")\\n"))
defs
marshall_fun =
marshall_nm <+> text "::" <+> ppType (Arrow (TypeVar nm) ty) $$
hang (marshall_nm <+> text "arg1 = ")
! 2 (ppCases (text "x") marshall_alts)
unmarshall_fun =
unmarshall_nm <+> text "::" <+> ppType (Arrow ty (TypeVar nm)) $$
--- 199,211 ----
hole
marshall_alts = map ( \ (con, val) -> (text (upperName con), rhs (con,val)))
defs
unmarshall_alts = foldr mkIf (text ("error (\"unmarshall_"++nm++":\
! \ unknown value (\"++show arg1++\")\\n\")"))
defs
marshall_fun =
marshall_nm <+> text "::" <+> ppType (Arrow (TypeVar nm) ty) $$
hang (marshall_nm <+> text "arg1 = ")
! 2 (ppCases (text "arg1") marshall_alts)
unmarshall_fun =
unmarshall_nm <+> text "::" <+> ppType (Arrow ty (TypeVar nm)) $$
---------------------------------------------------------------------------
> --Sigbjorn
>
> Re: name mangling, the snapshot also support the (snappily named)
> cmd-line option:
>
> --name-mangling-scheme={std,classic}
>
> which control the mapping from external to Haskell names, i.e.,
>
> A_NAME std
> ======> a_NAME
> classic
> ======> aName (AName for constructors)
>
> The default is std.
I'm not completely happy with the "classic" mangling scheme. The problem
is that it mangles e.g. "glPushClientAttrib" to a spaghetti-like
"pushclientattrib" (assuming a %prefix gl). A slightly more complicated
scheme would be better: Only convert those words to lower case that are
completely upper case, e.g.:
GL_CURRENT_RASTER_TEXTURE_COORDS => CurrentRasterTextureCoords
glPushClientAttrib => pushClientAttrib
(assuming %prefix GL_ and %prefix gl). This Modula2-like naming
convention is not uncommon, see e.g. header files for Tcl, Python,
and GLIDE, so a more readable mangling scheme for this makes sense.
A patch for this:
---------------------------------------------------------------------------
diff -r -c green-card.orig/src/ListUtils.lhs green-card/src/ListUtils.lhs
*** green-card.orig/src/ListUtils.lhs Tue Apr 7 17:29:49 1998
--- green-card/src/ListUtils.lhs Fri Apr 10 17:26:24 1998
***************
*** 15,21 ****
, mkHaskellVar
) where
! import Char ( toLower, toUpper )
import Maybe ( fromMaybe )
\end{code}
--- 15,21 ----
, mkHaskellVar
) where
! import Char ( toLower, toUpper, isUpper )
import Maybe ( fromMaybe )
\end{code}
***************
*** 96,102 ****
caseWord :: String -> String
caseWord [] = []
! caseWord (c:cs) = toUpper c: map toLower cs
\end{code}
Convert C name to Haskell name by stripping prefixes and
--- 96,102 ----
caseWord :: String -> String
caseWord [] = []
! caseWord (c:cs) = toUpper c: if all isUpper cs then map toLower cs else cs
\end{code}
Convert C name to Haskell name by stripping prefixes and
--
Sven Panne Tel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen Oettingenstr. 67
mailto:[EMAIL PROTECTED] D-80538 Muenchen
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne