RE: Qualified names in foreign export

2000-03-20 Thread Simon Peyton-Jones

| BTW. The fact that functions containing the letter z in their names
| will get zz in C names, unless explicitly specified differently,
| should be either changed or documented.

Thanks for pointing this out.  I've fixed it in my (soon to be committed)
copy.

If you foreign-export an operator, or a name with an apostrophe, thus

foreign export (++) :: Int - Int

you'll get a C procedure called ++, which probably won't work -- but
at least you get what you say.  And you can use the external-name
mechanism to say what you want.

I'll document this point too.

Simon



Re: Qualified names in foreign export

2000-03-08 Thread Sven Panne

Marcin 'Qrczak' Kowalczyk wrote:
 Shouldn't foreign exported names be allowed to be qualified?

IMHO not:

   module Foo where
   Foo.f = "This is not allowed, either."

 I've just accidentally reused a Prelude name for a function to be
 foreign exported and could not resolve the conflict with the first
 way that came to mind: qualifying.

You can use `hiding' + qualifying instead:

   module Foo where
   import Prelude hiding(elem)

   foreign export elem :: Int - IO ()
   elem = print

   isVowel :: Char - Bool
   isVowel = (`Prelude.elem` "aeiouAEIOU")

BTW, with -Wall ghc gives a false alarm:

   Foo.hs:1: Warning: definition but no type signature for `elem'

 BTW. The fact that functions containing the letter z in their names
 will get zz in C names, unless explicitly specified differently,
 should be either changed or documented.

There is discrepancy between the names allowed for _ccall_{,GC_} and
the foreign family. In the former case varids *and* conids are allowed,
in the latter only varids. My suggestion: Allow both kinds of names
for foreign, too, and do no mangling at all. This change and the
comment should make their way into the FFI doc.

Comments/opinions?

Cheers,
   Sven
-- 
Sven PanneTel.: +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.informatik.uni-muenchen.de/~Sven.Panne



Qualified names in foreign export

2000-03-07 Thread Marcin 'Qrczak' Kowalczyk

Shouldn't foreign exported names be allowed to be qualified?

I've just accidentally reused a Prelude name for a function to be
foreign exported and could not resolve the conflict with the first
way that came to mind: qualifying.

It's only not obvious what C name would it get by default. Probably
the unqualified one.

BTW. The fact that functions containing the letter z in their names
will get zz in C names, unless explicitly specified differently,
should be either changed or documented.

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/  GCS/M d- s+:-- a22 C+++$ UL++$ P+++ L++$ E-
  ^^  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK  5? X- R tv-- b+++ DI D- G+ e h! r--%++ y-