[C2hs] hierarchical modules

Duncan Coutts duncan.coutts at worcester.oxford.ac.uk
Fri Jul 23 19:31:48 EDT 2004


On Sat, 2004-07-17 at 02:01, Duncan Coutts wrote:
> Ok, it does break things, for example this would get lexed as a single
> identifier:
> 
> {#get GList.data#}
> 
> So either the lexer needs to be cleverer and lex module identifiers
> differently from ordinary identifiers or the parser will need to
> reconstruct the module identifier from a sequence of identifier and dot
> tokens (preferably the former since the latter would be modulo
> whitespace which is not strictly correct).

Here's a patch that implements the latter solution. It's not lovely
because it has to reconstruct an identifier from several identifiers and
Ident is a bit too abstract for this to be easy.

I tried altering the lexer but it's not clear to me how to recognise a
sequence of things easily. You can do sequences of things in a regexp,
but then its hard to return multiple tokens. Lexers can only be combined
by disjunction as far as I can see.

Unlike the last patch this one seems to work, gtk2hs builds ok with it.

Anyway, here's the patch (this time changing only the parser, not the
lexer):

diff -C2 -r1.4 CHS.hs
*** c2hs/chs/CHS.hs     20 May 2004 16:42:17 -0000      1.4
--- c2hs/chs/CHS.hs     23 Jul 2004 15:40:21 -0000
***************
*** 744,755 ****
    (qual, modid, toks') <-
      case toks of
!       CHSTokIdent _ ide                :toks -> return (False, ide, toks)
!       CHSTokQualif _: CHSTokIdent _ ide:toks -> return (True , ide, toks)
        _                                            -> syntaxError toks
!   chi <- loadCHI . identToLexeme $ modid
    toks'' <- parseEndHook toks'
    frags <- parseFrags toks''
    return $ CHSHook (CHSImport qual modid chi pos) : frags
   
  parseContext          :: Position -> [CHSToken] -> CST s [CHSFrag]
  parseContext pos toks  = do
--- 744,773 ----
    (qual, modid, toks') <-
      case toks of
!       CHSTokIdent _ ide                :toks ->
!         let (ide', toks') = rebuildModuleId ide toks
!          in return (False, ide', toks')
!       CHSTokQualif _: CHSTokIdent _ ide:toks ->
!         let (ide', toks') = rebuildModuleId ide toks
!          in return (True , ide', toks')
        _                                            -> syntaxError toks
!   chi <- loadCHI . moduleNameToFileName . identToLexeme $ modid
    toks'' <- parseEndHook toks'
    frags <- parseFrags toks''
    return $ CHSHook (CHSImport qual modid chi pos) : frags
   
+ -- Qualified module names do not get lexed as a single token so we need to
+ -- reconstruct it from a sequence of identifer and dot tokens.
+ --
+ rebuildModuleId ide (CHSTokDot _ : CHSTokIdent _ ide' : toks) =
+   let catIdent ide ide' = onlyPosIdent (posOf ide)  --FIXME: unpleasent hack
+                             (identToLexeme ide ++ '.' : identToLexeme ide')
+    in rebuildModuleId (catIdent ide ide') toks
+ rebuildModuleId ide                                     toks  = (ide, toks)
+
+ moduleNameToFileName :: String -> FilePath
+ moduleNameToFileName = map dotToSlash
+   where dotToSlash '.' = '/'
+         dotToSlash c   = c
+
  parseContext          :: Position -> [CHSToken] -> CST s [CHSFrag]
  parseContext pos toks  = do

Duncan





More information about the C2hs mailing list