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-09 Thread Sigbjorn Finne


Sven Panne <[EMAIL PROTECTED]> writes:
> 
> Marcin 'Qrczak' Kowalczyk wrote:
> > [...] Maybe it would be enough to allow to omit a type signature for
> > foreign export? It's probably already somewhere else. But GHC allows
> > the foreign export signature to be more specific than the real
> > signature: it does not constrain the type of the function itself!
> 
> To be honest, I never knew that the following is indeed allowed:
> 
>module Foo where
>foreign export bar :: Int -> IO ()
>bar :: a -> IO ()
>bar _ = putStrLn "baz"
> 
> I'm not sure what the rationale behind this is. Could somebody explain
> this?
> 

The rationale is just that you don't want to force the Haskell programmer
to write monomorphic wrappers for the cases where it is useful, e.g.,

  foreign export "printInt" print :: Int -> IO ()

--sigbjorn



Re: Qualified names in foreign export

2000-03-09 Thread Marcin 'Qrczak' Kowalczyk

Thu, 09 Mar 2000 16:01:37 +0100, Sven Panne <[EMAIL PROTECTED]> 
pisze:

> To be honest, I never knew that the following is indeed allowed:
> 
>module Foo where
>foreign export bar :: Int -> IO ()
>bar :: a -> IO ()
>bar _ = putStrLn "baz"
> 
> I'm not sure what the rationale behind this is. Could somebody
> explain this?

I've found a possible use:

fact:: Integral a => (a -> a)
foreign export fact :: Int32 -> Int32

And generally exporting with a more restricted type looks absolutely
clean for me, however little it gives (very easy to simulate). I can
imagine a module which manages some abstract expressions, expression's
representation contains values of several types, classes organize
functions operating on these types, but only functions operating
on the whole expressions are exported and the type is made concrete
outside the module.

> > Another thing. Would it be better to allow foreign exporting
> > arbitrary expressions? [...]
> 
> I don't think that I fully understand what you mean. Can you give
> some examples?


-- exportFun has an overloaded type, one of its instances being
-- exportFun :: (Value->Value->Value) -> (Val->Val->IO Val)

hsSort:: Value -> Value -> Value
hsSort cmp = list id . sortBy cmp' . viewList id
where ...

foreign export "hsSort" (exportFun hsSort) :: Val -> Val -> IO Val


Now I am required to write something like

hsSort:: Val -> Val -> IO Val
hsSort = exportFun hsSort'
where
hsSort' cmp = list id . sortBy cmp' . viewList id
where ...

foreign export hsSort :: Val -> Val -> IO Val


But adding this is probably not worth the complication.

-- 
 __("$ 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-




Re: Qualified names in foreign export

2000-03-09 Thread Sven Panne

Marcin 'Qrczak' Kowalczyk wrote:
> [...] Maybe it would be enough to allow to omit a type signature for
> foreign export? It's probably already somewhere else. But GHC allows
> the foreign export signature to be more specific than the real
> signature: it does not constrain the type of the function itself!

To be honest, I never knew that the following is indeed allowed:

   module Foo where
   foreign export bar :: Int -> IO ()
   bar :: a -> IO ()
   bar _ = putStrLn "baz"

I'm not sure what the rationale behind this is. Could somebody explain
this?

> [...] It would be possible to reexport a function with a more
> restricted type. I cannot think now about a particular situation
> where it is useful though.

Neither me.

> [...] Hmm, an idea: allow such names in foreign import/export, but
> silently make the first letter lowercase in the Haskell name. Maybe
> a bit confusing, but still looks better for me than allowing unusual
> Haskell names because the original name is not Haskellish.
> 
> But IMHO if the same name is not appropriate for both Haskell and C,
> most clear is to simply specify them separately...

After a little thought I've changed my mind again and I'm totally
happy with simple varids.  :-}  Implicit conversions are not nice.

> What should foreign export do with a Haskell name containing an
> apostrophe, or with an operator name (and without a C name)? IMHO
> report an error.

Operators are no varids, so this is a non-problem, but in the
case of apostrophes I think that an error would be the easiest
and cleanest thing.

> Another thing. Would it be better to allow foreign exporting
> arbitrary expressions? [...]

I don't think that I fully understand what you mean. Can you give some
examples?

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



Re: Qualified names in foreign export

2000-03-08 Thread Marcin 'Qrczak' Kowalczyk

Wed, 08 Mar 2000 17:19:42 +0100, Sven Panne <[EMAIL PROTECTED]> 
pisze:

> But you can't give a signature for something from another module.

And that's bad! Hope that type signatures will be some day allowed in
the export list. Module's interface should be allowed to be explicitly
specified in a single place, as in most statically typed languages.

The proposition of syntax for values is quite obvious. It only does
not work with the same type signature for several things, unless we
*require* those signatures or change syntax more.

I imagine something like "type T" for types (even those actually
defined with data), "class C", maybe even value constructor
signatures... But I don't imagine a complete interface description,
which would have to include kind information and instances.

> Hmmm, foreign export has a dual function: Giving a signature and
> making Haskell stuff usable from the outside world. This is not
> nice, signatures and exports are two things for "normal" Haskell.

Yes. OTOH I find convenient to have explicit type signatures somewhere
for more complex things like foreign export dynamic, and the convention
is consistent: there is a type signature for the value as Haskell
sees it.

Maybe it would be enough to allow to omit a type signature for foreign
export? It's probably already somewhere else. But GHC allows the
foreign export signature to be more specific than the real signature:
it does not constrain the type of the function itself! So it's not
that bad, and it's important to know the exact signature for a foreign
exported function to match it with C.

This suggests allowing more specific type signatures for exported
things (after type signatures in export list are allowed at all).
It would be possible to reexport a function with a more restricted
type. I cannot think now about a particular situation where it is
useful though.

> > Functions syntactically looking like constructors? Weird for me...
> 
> This weirdness has been recognized a long time ago in Redmond, and
> has made its way into "the" API. (Never called DescribePixelFormat
> or RegisterClassEx?:-)

Never programmed for Windows, and happy with it :-)

Hmm, an idea: allow such names in foreign import/export, but silently
make the first letter lowercase in the Haskell name. Maybe a bit
confusing, but still looks better for me than allowing unusual Haskell
names because the original name is not Haskellish.

But IMHO if the same name is not appropriate for both Haskell and C,
most clear is to simply specify them separately...

What should foreign export do with a Haskell name containing an
apostrophe, or with an operator name (and without a C name)? IMHO
report an error.

Another thing. Would it be better to allow foreign exporting arbitrary
expressions? For example in my Haskell<->OCaml interface a function
to be foreign exported is normally wrapped with some special function
(which converts types of arguments and result), and otherwise the
unwrapped function can be used in the rest of the Haskell program.

-- 
 __("$ 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-




Re: Qualified names in foreign export

2000-03-08 Thread Sven Panne

Marcin 'Qrczak' Kowalczyk wrote:
> [...] Foreign export does not define a function - it mentions an
> existing function for exporting.

... and gives a type signature, so my example was a bit misleading,
but the argument still remains. And a related bug in GHC:

   module Blah where
   Blah.f :: String -- GHC allows this (incorrectly)
   Blah.f = "GHC/H98 don't allow this"

> Qualified names are allowed in export list in a module header.
> Function from another module can be exported too.

But you can't give a signature for something from another module.
Hmmm, foreign export has a dual function: Giving a signature and
making Haskell stuff usable from the outside world. This is not
nice, signatures and exports are two things for "normal" Haskell.

> Not that I desperately need exporting functions with ambiguous
> names :-)

But nevertheless, it's very useful for the Obfuscated Haskell Contest.

> Functions syntactically looking like constructors? Weird for me...

This weirdness has been recognized a long time ago in Redmond, and has
made its way into "the" API. (Never called DescribePixelFormat or 
RegisterClassEx? :-)

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



Re: Qualified names in foreign export

2000-03-08 Thread Marcin 'Qrczak' Kowalczyk

Wed, 08 Mar 2000 15:57:45 +0100, Sven Panne <[EMAIL PROTECTED]> 
pisze:

> > Shouldn't foreign exported names be allowed to be qualified?
> 
> IMHO not:
> 
>module Foo where
>Foo.f = "This is not allowed, either."

Foreign export does not define a function - it mentions an existing
function for exporting.

Qualified names are allowed in export list in a module header.
Function from another module can be exported too.

Not that I desperately need exporting functions with ambiguous names :-)

> 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.

Functions syntactically looking like constructors? Weird for me...

-- 
 __("$ 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-




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