RE: ghc with shared libraries ?

2000-04-11 Thread Ian Jackson

Simon Marlow writes ("RE: ghc with shared libraries ?"):
> Still can't be done, I'm afraid.  At least for Haskell libraries; you could
> compile parts of the RTS and libHS_cbits shared, but we haven't done that.
> 
> This message has more details:
>   
> http://www.mail-archive.com/glasgow-haskell-bugs@haskell.org/msg02765.html

I read that message and I'm afraid I'm puzzled.

Do you mean that GHC-compiled Haskell libraries don't have a stable
ABI ?  I can see that that might be true, but it might also be
possible to have a souped-up dynamic linker that could fix things up
(possibly with, as you say in the message, adverse effects on the
sharedness of the library).

But if that's all that the problem is it doesn't explain why even when
exactly the same object files are put together via dynamic linking
instead of just static it doesn't work (as I infer from people's
messages - I haven't tried it).

I was under the impression that at least on sensible platforms like
Linux, the relocation and linking that is done by the dynamic linker
is very similar to that done by the compile-time linker.  In fact, on
Linux you don't even need to compile your code -fpic: without it there
are simply lots more relocations in the resulting object files and
hence in the shared library, and you end up not sharing most of the
text (because the dynamic linker has to edit it when relocating it).
So without -fpic things work, but there's just a performance penalty.

You say:
> ... for example the assumption that  a data object consists of a symbol
> followed by a fixed amount of data, so that certain data objects can be
> copied into the binary's data segment at runtime.  GHC's object files don't
> follow these rules, so can't be made into shared objects easily.

It seems to me that this view of `data object' is simply the
definition of what ought to go into the initialised data segment of
the resulting shared object.  Unix shared libraries don't have a view
about what a `data object' is.

So perhaps this can be solved by putting things in more appropriate
sections and/or making intra-segment references more explicit in some
way so that the right relocation data is put there for the dynamic
linker ?

Ian.




RE: [Socket] accept & recvFrom

2000-03-21 Thread Ian Jackson

Simon Marlow writes ("RE: [Socket] accept & recvFrom"):
...
> You're suggesting removing [Socket.recvFrom]?  Again, I've no objection (because
> I don't use it :-)  but it's harder to make a case for removing something
> from  a library.  In this case, recvFrom is the dual of sendTo, so it at
> least looks consistent.  I agree it's hard to imagine a situation where you
> might use it.

Speaking as a UNIX networking type of person, I too think that the
sendTo function is, well, rather weird, I have to say :-).  That
doesn't mean I think it should be removed, but I can't imagine using
it myself.

However, there is the potential objection to both recvFrom and sendTo
in Socket that they have name clashes with the functions sendTo and
recvFrom in SocketPrim, which do exactly what I would have expected
(and are essential for use of datagrams).

Also, of course, stupid people might try to use sendTo and recvFrom to
have a communication with (eg) an SMTP server, but hopefully such
people will not be able to figure out Haskell well enough to get that
far :-).

Ian.




RE: Change to Posix.lhs

2000-03-19 Thread Ian Jackson

Simon Marlow writes ("RE: Change to Posix.lhs"):
> Should we use a Maybe rather than an exception here?  Probably, but then
> System.getVar doesn't return a Maybe, and the Posix library as a whole has a
> tendency towards exceptions rather than Maybe returns.  So I'm swithering(*)
> on this one.

The most common use for environment variables is to allow built-in
defaults to be overridden, and in this case they are (obviously)
optional.

Requiring the programmer to do tedious exception-handling for
nonexceptional conditions seems like a bad idea.  I agree with Volker
Stolz that nearly no-one would want to use the exception-throwing
version (though it should probably be left in for those rare cases).

Using Maybe makes it easy to provide compiled-in defaults using
fromMaybe.

Ian.



GHC 4.04.19990916 produces coredumping executable

1999-12-06 Thread Ian Jackson

I have a program (no doubt pretty grotty - I'm still messing around
learning Haskell) which causes GHC (4.04.19990916) to produce an
executable which coredumps.

The source is attached (and is quite small).

I'm using a GHC binary package from Debian GNU/Linux, binary package
version 4.04.19990916-0slink1 built by Michael Weber
<[EMAIL PROTECTED]>.  As soon as I get it to compile
I'll try a compiler installation I built myself.

-davenant:stalk> make XHCFLAGS=-dcore-lint
ghc -syslib posix -syslib exts -syslib misc -dcore-lint -c XSM.hs
ghc: module version changed to 1; reason: no old .hi file
ghc -syslib posix -syslib exts -syslib misc -dcore-lint -c server.hs
ghc: module version changed to 1; reason: no old .hi file
ghc -syslib posix -syslib exts -syslib misc -dcore-lint -o nettlestalk server.o XSM.o
-davenant:stalk> ./nettlestalk 
foo
Segmentation fault (core dumped)
-davenant:stalk> gcc -v
Reading specs from /usr/lib/gcc-lib/i486-linux/egcs-2.91.66/specs
gcc version egcs-2.91.66 Debian GNU/Linux (egcs-1.1.2 release)
-davenant:stalk> dpkg -l 'ghc*' 'libc6*' 'gcc*'
Desired=Unknown/Install/Remove/Purge
| Status=Not/Installed/Config-files/Unpacked/Failed-config/Half-installed
|/ Err?=(none)/Hold/Reinst-required/X=both-problems (Status,Err: uppercase=bad)
||/ NameVersionDescription
+++-===-==-
ii  ghc44.04.19990916- GHC - the Glasgow Haskell Compilation system
un  ghc4-doc (no description available)
ii  ghc4-libsrc 4.04.19990916- Library Sources of GHC - the Glasgow Haskell
ii  libc6   2.1.1-12   GNU C Library: Shared libraries and timezone
ii  libc6-dbg   2.1.1-12   GNU C Library: Libraries with debugging symb
ii  libc6-dev   2.1.1-12   GNU C Library: Development libraries and hea
pn  libc6-doc(no description available)
ii  libc6-pic   2.1.1-12   GNU C Library: PIC archive library
ii  libc6-prof  2.1.1-12   GNU C Library: Profiling libraries.
un  libc6.1  (no description available)
ii  gcc 2.91.66-2  The GNU (EGCS) C compiler.
ii  gcc-doc 2.95.1-2   Documentation for the GNU compilers (gcc, go
pn  gcc-docs (no description available)
pn  gcc-i386-gnu (no description available)
pn  gcc-m68k-linux   (no description available)
un  gcc-m68k-palmos  (no description available)
un  gcc-ss   (no description available)
pn  gccchecker   (no description available)
-davenant:stalk> uname -av
Linux davenant 2.2.12 #4 Sun Sep 19 23:27:21 BST 1999 i586 unknown
-davenant:stalk> 

Ian.



-- X-war (Warcraft/Starcraft/C&C-alike) server prototype

-- Copyright (C)1999 Ian Jackson <[EMAIL PROTECTED]>
--
-- This program is free software; you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation; either version 2, or (at your option)
-- any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-- GNU General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this program; if not, write to the Free Software Foundation,
-- Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
--
-- $Id: server.hs,v 1.7 1999/12/05 16:29:04 ian Exp $

import Int
import FiniteMap
import IOExts

import XSM

type UnitID = Int32
type Coord = Int
type HitPoints = Int
type PlayerNum = Int
type Interval = Int {-ms-}

data Orders =   OrdersNone |
OrdersAttack UnitID |
OrdersMove { ordmvx, ordmvy::Int }
instance Show Orders where
showsPrec _ OrdersNone = ("None"++)
showsPrec _ (OrdersAttack v) = ("Attack "++).(shows v)
showsPrec _ (OrdersMove x y) = ("Move "++).(shows x).(" "++).(shows y)

data UnitBase = UnitBase {
ubpn :: PlayerNum,
ubx, uby :: Coord,
ubhp :: HitPoints,
ubcloak :: Bool,
uborders :: Orders
}

instance Show UnitBase where
showsPrec _ (UnitBase pn x y hp cloak orders) = (
("UnitBase { ubpn="++) . (shows pn) .
(", ubx="++) . (shows x) .
(", uby="++) . (shows y) .
(", ubhp="++) . (shows hp) .
(", ubcloak="++) . (shows cloak) .
(", uborders="++) . (shows orders) .
(" }++"++)
)

data Unit = Unit UnitID UnitBase UnitT

Re: GHC 4.04.19990916 produces coredumping executable

1999-12-06 Thread Ian Jackson

I wrote:
> I have a program (no doubt pretty grotty - I'm still messing around
> learning Haskell) which causes GHC (4.04.19990916) to produce an
> executable which coredumps.
...
> I'm using a GHC binary package from Debian GNU/Linux, binary package
> version 4.04.19990916-0slink1 built by Michael Weber
> <[EMAIL PROTECTED]>.  As soon as I get it to compile
> I'll try a compiler installation I built myself.

I've managed to build the Debian source 4.04.19990916-2 and it says:
-davenant:stalk> ./nettlestalk 
foo
nettlestalk: fatal error: No threads to run!  Deadlock?
-davenant:stalk> 

My program doesn't use the Concurrent Haskell extensions.  ISTR seeing
something about this on the mailing list or somewhere, and that it
might be cured by using a later version ?  I can't see a later version
mentioned at http://www.haskell.org/ghc/download_ghc_404.html, unless
I want to use the CVS HEAD ...

Aside: Unfortunately I seem to have fallen off many of the Haskell
lists because haskell.org's DNS is broken and has been for some
considerable time.  I mailed [EMAIL PROTECTED] (which seems to be the
supposed contact) and left a message on the phone number in WHOIS, but
this is not having any effect.  Can someone closer to the people at
Yale please try to help get this fixed ?  haskell.org really needs a
secondary nameserver which isn't at Yale.  I'd be happy to provide
one, but I need to be put in touch with the relevant admins !  For
correspondence about this, please mail me at
[EMAIL PROTECTED]  This mailbox is closer to the
system running the nameserver, and also applies less strict checks to
incoming mail.

Ian.



GHC Select and Time modules - struct timeval

1999-12-01 Thread Ian Jackson

Firstly, let me say that I'm very new to Haskell, so it may be that
I'm just going about things in a fundamentally wrong way.

I'm writing an application in Haskell which, if I were to write it in
C, would be an event-driven select-loop based program.  It needs to
handle timeouts, and know when particular external (network) events
happen.

I was pleased to see that GHC has a library misc/Select which will
allow me to call select(2).  This will allow me to build the
event-processing arrangements.

My first observation is that the timeout is represented as a TimeOut,
which is Maybe Int, where the integer is in microseconds.  Ints only
have an advertised range of around +/-2^29, which corresponds to
something under 10 minutes.  This is too short for my application.  I
think that Select.TimeOut should be Maybe Integer - or, alternatively,
that a new type TimeVal or something should be created to represent
the full precision and range of struct timeval, and then TimeOut would
be Maybe TimeVal.

My second problem is that to know what timeout parameter to pass to
select I need to know what the current time is, to the precision of
the timeout for select.  In a C program I would use gettimeofday,
which (effectively) returns a struct timeval.

GHC does provide access to gettimeofday in the form of the
getClockTime call in the std/Time library.  It returns a ClockTime,
which, as the comments suggest, is advertised in the Library Report
only as an abstract type.  In fact, the ClockTime is concrete in GHC
and is pretty much the TimeVal type I suggest above.

However, arithmetic operations on ClockTimes all take place after
conversion to and from civil time (y/m/d/h/m/s&c).  I can't take
ClockTimes and simply (eg) add a number of us to calculate the next
event point, or subtract a pair of ClockTimes to get the core of a
TimeOut - without unpicking it myself and converting to an Integer,
anyway.

So, it all seems somewhat irregular.  This clearly needs to be fixed,
and I think I can do it, but in order for my patch to be accepted I
think I should ask what the best way would be.

Questions include:

* Is it reasonable to consider the internal construction of a
ClockTime exposed ?  (I presume not.)

* Should there be a conversion from ClockTime to Integer ?  In what
units should the Integer be - us or ps ?

* How much is the interface in misc/Select.lhs cast in stone ?  Would
it be reasonable to simply change hSelect to take an Integer, or a
ClockTime ?

Any and all advice, specific or general, appreciated.

Ian.