This is a live mirror of the Perl 5 development currently hosted at https://github.com/perl/perl5
Don't define Perl_isFOO_lc in the regex extension.
[perl5.git] / os2 / Changes
1 after 5.003_05:
2         PERLLIB_PREFIX was not active if it matches an element of @INC
3                 as a whole.
4         Do not need PERL_SBRK if crtdll-revision is >= 50.
5         Use -Zsmall-conv if crtdll-revision is >= 50 (in static perl!).
6 :7: warning: #warning <dirent.h> requires <sys/types.h>
7         We compile miniperl static. It cannot fork, thus there may be
8                 problems with pipes (since HAS_FORK is in
9                 place). Pipes are required by makemaker.
10         We compile perl___.exe A.OUT and dynamic. It should be able to
11                 fork.
12         If we can fork, we my_popen by popen unless "-|". Thus we
13                 write a cooky "-1" into the pid array to indicate
14                 this.
15         Apparently we can fork, and we can load dynamic extensions
16                 now, though probably not simultaneously.
17         *DB tests corrected for OS/2 one-user stat[2].
18         /bin/sh is intercepted and replaced by SH_PATH.
19         Note that having '\\' in the command line of one-arg `system'
20                 would trigger call via shell.
21         Segfault with system {'ls'} 'blah'; corrected.
22         Documentation of OS/2-different features added to main PODs.
23         New buitins in Cwd::
24
25                 Cwd::current_drive
26                 Cwd::sys_chdir          - leaves drive as it is.
27                 Cwd::change_drive
28                 Cwd::sys_is_absolute    - has drive letter and is_rooted
29                 Cwd::sys_is_rooted      - has leading [/\\] (maybe
30                                           after a drive)
31                 Cwd::sys_is_relative    - changes with current dir
32                 Cwd::sys_cwd            - Interface to cwd from EMX.
33                 Cwd::sys_abspath(name, dir)     
34                                         - Really really odious
35                                           function. Returns absolute
36                                           name of file which would 
37                                           have 'name' if CWD were 'dir'.
38                                         Dir defaults to the current dir.
39                 Cwd::extLibpath [type]  - Get/set current value of extended
40                 Cwd::extLibpath_set     - library search path.
41                         path [type]
42                                         The optional last argument redirects
43                                            to END-path if true,
44                                            default is to search BEGIN-path.
45                 (Note that some of these may be moved to different
46                   libraries - eventually).
47         Executables: 
48                 perl - can fork, can dynalink (but not simultaneously)
49                 perl_ - can fork, cannot dynalink
50                 perl__ - same as perl___, but PM.
51                 perl___ - cannot fork, can dynalink.
52         The build of the first one - perl - is rather convoluted, and
53           requires a build of miniperl_.
54
55 after 5.003_07:
56         custom tmpfile and tmpname which may use $TMP, $TEMP.
57         all the calls to OS/2 API wrapped so that it is safe to use
58                 them under DOS (may die(), though).
59         Tested that popen works under DOS with modified PDKSH and RSX.
60         File::Copy works under DOS.
61         MakeMaker modified to work under DOS (perlmain.c.tmp and sh -c true).
62
63 after 5.003_08:
64         OS2::PrfDB exports symbols as documented;
65         should work on OS/2 2.1 again.
66         uses reliable signals when spawing.
67         do not use popen() any more - no intermediate shell unless needed.
68
69 after 5.003_11:
70         Functions emx_{malloc,realloc,calloc,free} are exported from DLL.
71         get_sysinfo() bugs corrected (flags were not used and wrongly defined).
72
73 after 5.003_20:
74         _isterm is substituted instead of isatty, s?random instead of srand.
75         `register' disabled if -DDEBUGGING and not AOUT build: stupid SD386.
76         3-argument select() was stomping over memory.
77
78 after 5.003_21:
79         Can start scripts by executing 'dir/script' and
80         'script.sh'. Form without extension will call shell only if
81         the specified file exists (will not look on path) (to prohibit
82         trying to run shell commands directly). - Needed by magic.t.
83
84 after 5.003_27:
85         ALTERNATE_SHEBANG="extproc " supported, thus options on this
86         line are processed (possibly twice). -S is made legal on such
87         a line. This -S -x is not needed any more.
88         perl.dll may be used from non-EMX programs (via PERL_SYS_INIT
89         - the caller should have valid variable "env" with
90         environment). Known problems: $$ does not work - is 0, waitpid
91         returns immediately, thus Perl cannot wait for completion of
92         started programs.
93
94 after 5.004_01:
95         flock emulation added (disable by setting env PERL_USE_FLOCK=0),
96                 thanks to Rocco Caputo;
97         RSX bug with missing waitpid circumvented;
98         -S bug with full path with \ corrected.
99
100 before 5.004_02:
101         -S switch to perl enables a search with additional extensions 
102         .cmd, .btm, .bat, .pl as well.  This means that if you have
103         mycmd.pl or mycmd.bat on PATH, 
104                 perl -S mycmd
105         will work.  Perl will also look in the current directory first.
106         Moreover, a bug with \; in PATH being non-separator is fixed.
107
108 after 5.004_03:
109         $^E tracks calls to CRT now.  (May break if Perl masks some
110         changes to errno?)
111         $0 may be edited to longer lengths (at least under OS/2).
112         OS2::REXX->loads looks in the OS/2-ish fashion too.
113
114 after 5.004_04:
115         Default perl.exe was built with a shorter stack than expected.
116         Strip extensions DLLs too (unless debugging build).
117         ./os2.c being RO could stop cp.
118         When starting scripts, Perl will find them on path (using the same
119           extensions as for -S command-line switch).  If it finds magic
120           `extproc ' or `#!' cookies, it will start the scripts directly.
121         May use `cmd /c more <' as a pager.
122         If a program could not be started, this might have been hidden.
123         End of pipe was closed twice when `open'ing a pipeline.
124
125 after 5.004_53:
126         Minimal thread support added.  One needs to manually move pthread.h
127
128 after 5.004_64:
129         Make DLL names different if thread-enabled.
130         Emit more informative internal DLL descriptions.
131
132 5.004_72:
133         Updated OS2::Process (v0.2) included.
134         
135 after 5.004_73:
136         Fixed a bug with argv not NULL-terminated when starting scripts.
137         Support all the forms of starting scripts.
138         Support killing a child when receiving a signal during system()
139         (in two stage, on first send the same signal, on the next
140         send SIGKILL).
141         Add the same logic for scripts as in pdksh, including 
142                 stripping the path from #! line if needed, 
143                 calling EXECSHELL or COMSPEC for magic-less scripts;
144         Now pdksh is called only if one-arg system()/friends contains
145         metachars, or if magic-line asks for sh, or there is no magic
146         line and EXECSHELL is set to sh.
147         Shell is supplied the original command line if possible.
148
149 after 5.005_02:
150         Can start PM programs from non-PM sessions by plain system()
151                 and friends.  Can start DOS/Win programs.  Can start
152                 fullscreen programs from non-fullscreen sessions too.
153         In fact system(P_PM,...) was broken.
154         We mangle the name of perl*.DLL, to allow coexistence of different
155                 versions of Perl executables on the system.  Mangling of
156                 names of extension DLL is also changed, thus running two
157                 different versions of the executable with loaded
158                 extensions should not lead to conflicts (since 
159                 extension-full-name and Perl-version mangling work in the 
160                 same set ot 576 possible keys, this may lead to clashes).
161         $^E was reset on the second read, and contained ".\r\n" at the end.
162
163 after 5.005_53:
164         Would segfault system()ing non-existing program;
165         AOUT build was hosed;
166         warning-test for getpriority() might lock the system hard on 
167                 pre-fixpak22 configuration (calling getpriority() on 
168                 non-existing process triggers a system-wide bug).
169
170
171         PrfDB was using a bug in processing XSUBs returning U32.
172
173         Variable $OS2::emx_rev implemented (string and numeric values
174                 are the same as C variables _emx_rev and _emx_vprt).
175         Variable $OS2::emx_env implemented (same as C variable _emx_env).
176         Variable $OS2::os_ver implemented (_osmajor + 0.001 * _osminor).
177
178         Improved centralized management of HAB and HMQ.  To get Perl's
179                 HAB, call perl_hab_GET().  (After the initial call one
180                 can use Perl_hab instead.)  To require Perl's HMQ,
181                 call perl_hmq_GET(), to release it call perl_hmq_UNSET(),
182                 to obtain it between these calls use Perl_hmq.
183         HMQ management is refcounted, and the program will morph
184                 itself into/from PM if required.
185         If perl.h cannot be included, hab may be obtained by Perl_hab_GET().
186
187         New function OS2::Error(do_harderror,do_exception).  Returns
188                 undef if it was not called yet, otherwise bit 1 is
189                 set if on previous call do_harderror was enabled, bit
190                 2 is set if if on previous call do_exception was enabled.
191         This function enables/disables error popups associated with 
192                 hardware errors (Disk not ready etc.) and software exceptions.
193
194         New function OS2::Errors2Drive(drive).  Returns undef if it was 
195                 not called yet, otherwise return false if Errors were
196                 not requested to be written to a hard drive, or the
197                 drive letter if this was requested.
198         This function may redirect error popups associated with 
199                 hardware errors (Disk not ready etc.) and software exceptions
200                 to the file POPUPLOG.OS2 at the root directory of the
201                 specified drive.  Overrides OS2::Error() specified by 
202                 individual programs.  Given argument undef will
203                 disable redirection.  Has global effect, persists
204                 after the application exits.
205
206         New function OS2::SysInfo().  Returns a hash with system information.
207                 The keys of the hash are
208
209                 MAX_PATH_LENGTH, MAX_TEXT_SESSIONS, MAX_PM_SESSIONS,
210                 MAX_VDM_SESSIONS, BOOT_DRIVE, DYN_PRI_VARIATION,
211                 MAX_WAIT, MIN_SLICE, MAX_SLICE, PAGE_SIZE,
212                 VERSION_MAJOR, VERSION_MINOR, VERSION_REVISION,
213                 MS_COUNT, TIME_LOW, TIME_HIGH, TOTPHYSMEM, TOTRESMEM,
214                 TOTAVAILMEM, MAXPRMEM, MAXSHMEM, TIMER_INTERVAL,
215                 MAX_COMP_LENGTH, FOREGROUND_FS_SESSION,
216                 FOREGROUND_PROCESS
217
218         New function OS2::BootDrive(force).  Returns a letter without colon.
219
220         New functions OS2::MorphPM(serve)/OS2::UnMorphPM(serve).  Transforms
221                 the current application into a PM application and back.
222                 The argument true means that a real message loop is
223                 going to be performed.
224         OS2::MorphPM() returns the PM message queue handle as an integer.
225
226         New function OS2::Serve_Messages(force).  Fake on-demand
227                 retrieval of outstanding PM messages.  If force is false,
228                 will not dispatch messages if a real message loop is known to
229                 be present.  Returns number of messages retrieved.
230         Dies with "QUITing..." if WM_QUIT message is obtained.
231
232         New function OS2::Process_Messages(force [, cnt]).  Retrieval
233                 of PM messages until window creation/destruction.  
234                 If force is false, will not dispatch messages 
235                 if a real message loop is known to be present.  
236                 Returns change in number of windows.  If cnt is given,
237                 it is incremented by the number of messages retrieved.
238         Dies with "QUITing..." if WM_QUIT message is obtained.
239
240 after 5.005_54:
241         Opening pipes from/to processes could fail if (un)appropriate
242         combination of STDIN/STDOUT was closed.
243  
244         If the only shell-metachars of a command are ' 2>&1' at the
245         end of a command, it is executed without calling the external shell.
246
247 after 5.005_57:
248         Make UDP sockets return correct caller address (OS2 API bug);
249         Enable TCPIPV4 defines (works with Warp 3 IAK too?!);
250         Force Unix-domain sockets to start with "/socket", convert
251           '/' to '\' in the calls;
252         Make C<system 1, $cmd> to treat $cmd as in C<system $cmd>;
253         Autopatch Configure;
254         Find name and location of g[nu]patch.exe;
255         Autocopy perl????.dll to t/ when testing;
256
257 after 5.005_62:
258         Extract a lightweight DLL access module OS2::DLL from OS2::REXX
259            which would not load REXX runtime system;
260         Allow compile with os2.h which loads os2tk.h instead of os2emx.h;
261         Put the version of EMX CRTL into -D define;
262         Use _setsyserror() to store last error of OS/2 API for $^E;
263         New macro PERL_SYS_INIT3(argvp, argcp, envp);
264         Make Dynaloader return info on the failing module after failed dl_open();
265         OS2::REXX test were done for interactive testing (were writing
266           "ok" to stderr);
267         system() and friends return -1 on failure (was 0xFF00);
268         Put the full name of executable into $^X
269           (alas, uppercased - but with /);
270         t/io/fs.t was failing on HPFS386;
271         Remove extra ';' from defines for MQ operations.
272
273 pre 5.6.1:
274         Resolved: "Bad free()" messages (e.g., from DB_File) with -Zomf build.
275            The reason was: when an extension DLL was linked, the order of
276            libraries was similar to this:
277                 f1.obj f2.obj libperl.lib -llibr1 -llibr2
278            (with C RTL implicitly after this).  When libperl.lib overrides
279            some C RTL functions, they are correctly resolved when mentioned
280            in f1.obj and f2.obj.  However, the resolution for libr1.lib and
281            libr2.lib is implementation-dependent.
282
283            With -Zomf linking the symbols are resolved for libr1.lib and
284            libr2.lib *only if* they reside in .obj-file-sections of libperl.lib
285            which were already "picked up" for symbols in f1.obj f2.obj.
286            However, libperl.lib is an import library for a .DLL, so *each
287            symbol in libperl.lib sits in its own pseudo-section*!
288
289            Corollary: only those symbol from libperl.lib which were already
290            mentioned in f1.obj f2.obj would be used for libr1.lib and
291            libr2.lib.  Example: if f1.obj f2.obj do not mention calloc() but
292            libr1.lib and libr2.lib do, then .lib's will get calloc() of C RTL,
293            not one of libperl.lib.
294
295            Solution: create a small duplicate of libperl.lib with overriding
296            symbols only.  Put it *after* -llibr1 -llibr2 on the link line.
297            Map strdup() and putenv() to Perl_strdup() and Perl_putenv()
298            inside this library.
299
300         Resolved: rmdir() and mkdir() do not accept trailing slashes.
301            Wrappers are implemented.
302         Resolved: when loading modules, FP mask may be erroneously changed by
303            _DLLInitTerm() (e.g., TCP32IP).
304                 Solutions: a) dlopen() saves/restores the FP mask.
305                            b) When starting, reset FP mask to a sane value
306                                 (if the DLL was compile-time linked).
307         New functions in package OS2:
308                 unsigned _control87(unsigned new,unsigned mask) # as in EMX
309                 unsigned get_control87()
310                 # with default values good for handling exception mask:
311                 unsigned set_control87_em(new=MCW_EM,mask=MCW_EM)
312             Needed to guard against other situations when the FP mask is
313             stomped upon.  Apparently, IBM used a compiler (for some period
314             of time around '95?) which changes FP mask right and left...
315         Resolved: $^X was always uppercased (cosmetic).  Solution:
316             use argv[0] if it differs from what the OS returns only in case.
317         Resolved: when creating PM message queues, WinCancelShutdown() was
318             not called even if the application said that it would not serve
319             messages in this queue.  Could result in PM refusing to shutdown.
320
321             Solution: resolve WinCancelShutdown at run time, keep the refcount
322             of who is going to serve the queue.
323         Resolved: Perl_Deregister_MQ() segfaulted (pid/tid not initialized).
324         Resolved: FillWinError() would not fetch the error.
325             Solution: resolve WinGetLastError at run time, call it.
326         Resolved: OS2::REXX would ignore arguments given to a Perl function
327             imported into the REXX compartment via REXX_eval_with().
328         Resolved: OS2::REXX would treat arguments given to a Perl function
329             imported into the REXX compartment via _register() as ASCIIZ
330             strings inside of binary strings.
331         Resolved: OS2::REXX did not document _register().
332         Resolved: OS2::REXX would not report the error to REXX if an error
333             condition appeared during a call to Perl function from REXX
334             compartment.  As a result, the return string was not initialized.
335         A complete example of a mini-application added to OS2::REXX.
336         README.os2 updated to reflect the current state of Perl.
337
338 pre 5.7.2:
339         aout build: kid bootstrap_* were not associated with XS.
340         bldlevel did not contain enough info.
341         extLibpath* was failing on the call of the second type.
342         Configure defines flushNULL now (EMX -Zomf bug broke autodetection).
343         Configure did not find SIGBREAK.
344         extLibpath supports LIBSTRICT, better error detection.
345         crypt() used if present in -lcrypt or -lufc.
346         dumb getpw*(), getgr*() etc. supported; as in EMX, but if no
347             $ENV{PW_PASSWD}, the passwd field contains a string which
348             cannot be returned by crypt() (for security reasons).
349         The unwound recursion in detecting executable by script was
350             using static buffers.  Thus system('pod2text') would fail if the
351             current directory contained an empty file named 'perl'.
352         Put ordinals in the base DLL.
353         Enable EXE-compression.
354             Load time (ms):  Without /e:2: 70.6; With /e:2: 75.3; Lxlite: 62.8
355             Size drops from 750K to 627K, with lxlite to 515K.
356             lxlite /c:max gives 488K, but dumps core in t/TEST
357         os2ish.h defines SYSLOG constants ==> Sys::Syslog works.
358         Corrected warnings related to OS/2 code.
359             At one place = was put instead of ==.
360         Setting $^E should work.
361         Force "SYS0dddd=0xbar: " to error messages and to dlerror().
362             ($^E == 2 printed SYS0002 itself, but 110 did not.)
363         $OS2::nsyserror=0 switches off forcing SYSdddd on $^E.
364         perl_.exe does not require PM dlls any more (symbols resolved at
365             runtime on the as needed basis).
366         OS2::Process:
367             get/set: term size; codepages; screen's cursor; screen's contents
368             reliable session name setting;
369             process's parent pid, and the session id;
370             switching to and enumeration of sessions
371             window hierarchy inspection
372             post a message to a window
373         More robust getpriority() on older Warps.
374
375         New C APIs for runtime loading of entry points from DLLs
376         (useful for entry points not present on older versions of
377         OS/2, or with DLLs not present on floppy-boot stripped down
378         setups): CallORD(), DeclFuncByORD(), DeclVoidFuncByORD(),
379         DeclOSFuncByORD(), DeclWinFuncByORD(), AssignFuncPByORD().
380
381 pre 5.7.3:
382         Testing with PERL_TEST_NOVREXX=1 in environment makes tests
383         noninteractive (VREXX test requires pressing a button on a dialog).
384
385         New (ugly and voodooish) hack to work around a bug in EMX
386         runtime architecture:
387
388           EMX.DLL is *not* initialized from its _DLL_InitTerm()
389           routine, but the initialization is postponed until
390           immediately before main() is called by the principal
391           executable (may be the initialization also happens during
392           InitTerm of -Zso -Zsys DLLs?).  The only reason I can see is
393           to postpone the initialization until the "layout" structure
394           is available, so the type of the executable is known.
395           [Instead, one should have broken the initialization into two
396           steps, with no-layout-known initialization ASAP, and the
397           finishing touch done when "layout" is known.]
398
399           It is due to this hack that -Zsys, -Zso etc. are needed so
400           often.
401
402           If during initialization of the Perl runtime environment we
403           discover that EMX environment is not set up completely, this
404           can be because of either our DLL being called from an
405           uncompatible flavor of EMX executable, or from an
406           unrelated-to-EMX.DLL (e.g., -Zsys or compiled with a
407           different compiler) executable.  In the first case only the
408           CRTL is not completely initialized, in the other case
409           EMX.DLL may be not initialized too.
410
411           We detect which of these two situations takes place, then
412           explicitly call the initialization entry points of EMX.DLL
413           and of CRT.  The large caveat is that the init-entry point
414           of EMX.DLL also moves the stack pointer (another defect of
415           EMX architecture, the init() and
416           set_exception_handlers_on_stack() entry points should have
417           been separated).  Thus we need some inline-assembler to
418           compensate for this, and need to remove the installed
419           exception handler - it is useless anyway, since exception
420           handlers need to be on the stack.  [This one is on the
421           stack, but will be overwritten on exit from the function.]
422
423           We also install an extra hack to run our atexit() handlers
424           on termination of the process (since the principal
425           executable does not know about *this* CRTL, we need to do it
426           ourselves - and longjmp() out of the chain of exception
427           handlers at a proper moment :-().
428
429         The net result: Perl DLL can be now used with an arbitrary
430         application.  PERLREXX DLL is provided which makes Perl usable
431         from any REXX-enabled application.
432
433         New test targets added to test how well Perl DLL runs with
434         different flavors of executables (see all_harness etc).  To
435         avoid waiting for the user button press, run with env
436         PERL_TEST_NOVREXX=1.
437
438         Another hack: on init of Perl runtime environment, the
439         executable is tested for being an aout EMX executable.  The
440         test is the same done by gdb, so although this test is very
441         voodoo, it should be pretty robust (the beginning of the
442         executable code - at 0x10000 - is tested for a known bit
443         pattern).  The result is used to set $OS2::can_fork, which is
444         eventually used to set $Config::Config{can_fork}.
445
446         REXX::eval_REXX() made reenterable.  ADDRESS PERLEVAL
447         available for the run REXX code.  PERLLASTERROR available.
448
449         A .map file is created for the .dll.  Now easier to debug the
450         failures which do not happen with a debugging executable.
451
452         Duplicate libperl.lib as perl.lib etc. to make Embed happier.
453
454         File::Spec better adjusted to OS/2 (still does not support aa:/dir/).
455
456         New module OS::Process::Const with necessary constants for the
457         Perl calls which mimic OS/2 API calls.
458
459 After @14577:
460         $Config{pager} better (but needs work in the binary installer!).
461
462         New API: OS2::DLLname([type], [\&sub])
463
464         New OS2::Process APIs:
465
466                  process_hwnd winTitle_set winTitle swTitle_set bothTitle_set
467                  hWindowPos hWindowPos_set DesktopWindow
468                  ActiveWindow_set
469                  EnableWindow EnableWindowUpdate IsWindowEnabled
470                  IsWindowVisible IsWindowShowing WindowPtr WindowULong
471                  WindowUShort SetWindowBits SetWindowPtr
472                  SetWindowULong
473                  SetWindowUShort MPFROMSHORT MPVOID MPFROMCHAR
474                  MPFROM2SHORT
475                  MPFROMSH2CH MPFROMLONG
476
477         OS::Process::Const symbols exportable from OS::Process too.
478
479         OS::Process: prototypes on subroutines which do not naturally
480         take "vectors" as arguments (not backwards compatible!).
481
482         New C API: SaveCroakWinError(), WinError_2_Perl_rc,
483         DeclWinFuncByORD_CACHE(), DeclWinFuncByORD_CACHE_survive(),
484         DeclWinFuncByORD_CACHE_resetError_survive(),
485         DeclWinFunc_CACHE(), DeclWinFunc_CACHE_resetError(),
486         DeclWinFunc_CACHE_survive(),
487         DeclWinFunc_CACHE_resetError_survive(); many new OS2 entry
488         points conveniently available via wrappers which will do the
489         necessary run-time dynalinking.
490
491 After @15047:
492         makes PerlIO preserve the binary/text mode of filehandles
493         chosen by CRT library.  (However, TTY handles still are not
494         clean, since switching them to TERMIO mode and back changes
495         the NL translation law at runtime, and PerlIO level does not
496         know this.)
497
498 After @18156:
499         mkdir() rmdir() tolerate trailing slashes.
500         "localized" morphing to PM when already morphed would unmorph at end.
501         Convert \n to \r\n in REXX commands (Classic REXX would allow \r and
502                 \r\n, but not \n as line-ends).
503
504 After @19053:
505         Better detection of OS/2 in Configure scripts (if c:/ is not readable).
506         Better Configure support for \\ inside cpp-emited # lineno "filename".
507         Export pthread-support functions from threaded DLL.
508         [older change] If perl5.def file is present, the new perl5.def has
509                 compatible ordinals.
510         OS/2 code compiles with threads enabled; much more robust pthreads
511                 emulation (but some statics still present); survives fork().
512         New attributes supported with [f]stat() and chmod()
513                   archived is 0x1000000 =  0100000000
514                   hidden   is 0x2000000 =  0200000000
515                   system   is 0x4000000 =  0400000000
516                 If extra flag 0x8000000 = 01000000000 is missing during
517                 chmod(), these 3 flags are ignored; this extra flag
518                 is set in the result of stat() [this provides backward
519                 compatibility, as well as transparency of stat()/
520                 chmod() supporting DOSISH].
521         OS/2-specific modules use XSLoader now.
522         Remove DLLs manually after failing build (link386 would not?!).
523         Special-case stat()ing "/dev/nul" and "/dev/null" too.
524         Update dlopen() and friends: preserve i387 flags, better error messages,
525                 support name==NULL (load for "this" DLL);
526         OS2::DLL does not eval() generated functions, uses closes instead;
527                 new method wrapper_REXX() for DLL objects.
528
529 After @19774:
530         Use common typemap for OS2:: modules.
531         New test file os2/perlrexx.cmd (should be run manually; does not it
532                 exit too early???).
533         Export fork_with_resources(), croak_with_os2error() from DLL.
534         usleep() availability put in %Config{}.
535         Combine most (but not all!) statics into one struct.
536         New load-on-demand C functions 
537                 Dos32QueryHeaderInfo
538                 DosTmrQueryFreq
539                 DosTmrQueryTime
540                 WinQueryActiveDesktopPathname
541                 WinInvalidateRect
542                 WinCreateFrameControl
543                 WinQueryClipbrdFmtInfo
544                 WinQueryClipbrdOwner
545                 WinQueryClipbrdViewer
546                 WinQueryClipbrdData
547                 WinOpenClipbrd
548                 WinCloseClipbrd
549                 WinSetClipbrdData
550                 WinSetClipbrdOwner
551                 WinSetClipbrdViewer
552                 WinEnumClipbrdFmts 
553                 WinEmptyClipbrd
554                 WinAddAtom
555                 WinFindAtom
556                 WinDeleteAtom
557                 WinQueryAtomUsage
558                 WinQueryAtomName
559                 WinQueryAtomLength
560                 WinQuerySystemAtomTable
561                 WinCreateAtomTable
562                 WinDestroyAtomTable
563                 WinOpenWindowDC
564                 DevOpenDC
565                 DevQueryCaps
566                 DevCloseDC
567                 WinMessageBox
568                 WinMessageBox2
569                 WinQuerySysValue
570                 WinSetSysValue
571                 WinAlarm
572                 WinFlashWindow
573                 WinLoadPointer
574                 WinQuerySysPointer      
575         Check "\\SEM32\\PMDRAG.SEM" before loading PM-specific DLLs.
576         Handling of system {realname} was not correct in presence of
577                 exe-type deduction, #!-emulation etc.
578         Use optimized PUSHTARG etc. XSUB convention.
579         $^E stringification contains PMERR_INVALID_HWND, PMERR_INVALID_HMQ, 
580                 PMERR_CALL_FROM_WRONG_THREAD, PMERR_NO_MSG_QUEUE,
581                 PMERR_NOT_IN_A_PM_SESSION if these errors are not in .MSG file
582                 (at least on Warp3fp42).
583         PERLLIB_PREFIX augmented by PERLLIB_582_PREFIX, PERLLIB_58_PREFIX,
584                 PERLLIB_5_PREFIX (example for 5.8.2, the first one present is
585                 considered).
586         New flag bit 0x2 for OS2::MorphPM(): immediately unmorph after creation
587                 of message queue.
588         (De)Registring MQ preserves i386 flags.
589         When die()ing inside OS2:: API, include $^E in the message.
590         New function OS2::Timer(): returns Tmr-timer ticks (about 1MHz) since
591                 start of OS/2, converted to number of seconds (keep in mind
592                 that this timer uses a different crystal than the real-time
593                 clock; thus these values have only weak relationship to the
594                 wall clock time; behaviour with APM on is not defined).
595         New function OS2::DevCap() [XXX Wrong usage message!!!]
596                 Usage: OS2::DevCap([WHAT, [HOW=0]]); the default for WHAT is
597                 the memory device context, WHAT should be a device context
598                 (as integer) if HOW==0 and a window handle (as integer) if
599                 HOW==1.  Returns a hash with keys
600                         FAMILY IO_CAPS TECHNOLOGY DRIVER_VERSION WIDTH HEIGHT
601                         WIDTH_IN_CHARS HEIGHT_IN_CHARS HORIZONTAL_RESOLUTION
602                         VERTICAL_RESOLUTION CHAR_WIDTH CHAR_HEIGHT
603                         SMALL_CHAR_WIDTH SMALL_CHAR_HEIGHT COLORS COLOR_PLANES
604                         COLOR_BITCOUNT COLOR_TABLE_SUPPORT MOUSE_BUTTONS
605                         FOREGROUND_MIX_SUPPORT BACKGROUND_MIX_SUPPORT
606                         VIO_LOADABLE_FONTS WINDOW_BYTE_ALIGNMENT BITMAP_FORMATS
607                         RASTER_CAPS MARKER_HEIGHT MARKER_WIDTH DEVICE_FONTS
608                         GRAPHICS_SUBSET GRAPHICS_VERSION GRAPHICS_VECTOR_SUBSET
609                         DEVICE_WINDOWING ADDITIONAL_GRAPHICS PHYS_COLORS
610                         COLOR_INDEX GRAPHICS_CHAR_WIDTH GRAPHICS_CHAR_HEIGHT
611                         HORIZONTAL_FONT_RES VERTICAL_FONT_RES DEVICE_FONT_SIM
612                         LINEWIDTH_THICK DEVICE_POLYSET_POINTS
613         New function OS2::SysValues(which = -1, hwndDesktop = HWND_DESKTOP).
614                 If which != -1, returns the corresponding SysValue.  Otherwise
615                 returns a hash with keys:
616                         SWAPBUTTON DBLCLKTIME CXDBLCLK CYDBLCLK
617                         CXSIZEBORDER CYSIZEBORDER ALARM 7 8 CURSORRATE
618                         FIRSTSCROLLRATE SCROLLRATE NUMBEREDLISTS WARNINGFREQ
619                         NOTEFREQ ERRORFREQ WARNINGDURATION NOTEDURATION
620                         ERRORDURATION 19 CXSCREEN CYSCREEN CXVSCROLL CYHSCROLL
621                         CYVSCROLLARROW CXHSCROLLARROW CXBORDER CYBORDER
622                         CXDLGFRAME CYDLGFRAME CYTITLEBAR CYVSLIDER CXHSLIDER
623                         CXMINMAXBUTTON CYMINMAXBUTTON CYMENU
624                         CXFULLSCREEN CYFULLSCREEN CXICON CYICON
625                         CXPOINTER CYPOINTER DEBUG CPOINTERBUTTONS POINTERLEVEL
626                         CURSORLEVEL TRACKRECTLEVEL CTIMERS MOUSEPRESENT
627                         CXALIGN CYALIGN
628                         DESKTOPWORKAREAYTOP DESKTOPWORKAREAYBOTTOM
629                         DESKTOPWORKAREAXRIGHT DESKTOPWORKAREAXLEFT 55
630                         NOTRESERVED EXTRAKEYBEEP SETLIGHTS INSERTMODE 60 61 62 63
631                         MENUROLLDOWNDELAY MENUROLLUPDELAY ALTMNEMONIC
632                         TASKLISTMOUSEACCESS CXICONTEXTWIDTH CICONTEXTLINES
633                         CHORDTIME CXCHORD CYCHORD CXMOTIONSTART CYMOTIONSTART
634                         BEGINDRAG ENDDRAG SINGLESELECT OPEN CONTEXTMENU CONTEXTHELP
635                         TEXTEDIT BEGINSELECT ENDSELECT BEGINDRAGKB ENDDRAGKB
636                         SELECTKB OPENKB CONTEXTMENUKB CONTEXTHELPKB TEXTEDITKB
637                         BEGINSELECTKB ENDSELECTKB ANIMATION ANIMATIONSPEED
638                         MONOICONS KBDALTERED PRINTSCREEN                /* 97, the last one on one of the DDK header */
639                         LOCKSTARTINPUT DYNAMICDRAG 100 101 102 103 104 105 106 107
640         New function OS2::SysValues_set(which, val, hwndDesktop = HWND_DESKTOP).
641         Support new keys NUMPROCESSORS MAXHPRMEM MAXHSHMEM MAXPROCESSES
642                 VIRTUALADDRESSLIMIT INT10ENABLE from OS2::SysInfo(); support
643                 up to 10 unnamed values after the last named one.
644         New function OS2::SysInfoFor(id[,count=1]). [Wrong usage message!!!]
645         New function OS2::Beep(freq = 440, ms = 100).
646         New flags mod_name_C_function = 0x100, mod_name_HMODULE = 0x200 in
647                 addition to old mod_name_handle = 0, mod_name_shortname = 1,
648                 mod_name_full = 2 for OS2::DLLname(flag, cv); use an address
649                 (as integer) or module handle instead of cv.
650         New function OS2::_headerInfo(req,size[,handle,[offset]]).
651         New function OS2::libPath(); returns the value of LIBPATH.
652         New function OS2::mytype(which=0) to query current process type:
653                 0:      type immediately after startup or last fork();
654                 1:      type immediately after startup;
655                 2:      type before the first morphing;
656                 3:      type as set now in the header.
657         New function OS2::mytype_set(type);
658         New function OS2::incrMaxFHandles(delta = 0); returns updated value
659                 for the possible number of open file descriptors.
660         Make check_emx_runtime() thread-safe.
661         Fix float-to-string conversion in the range .0001..0.1 (would return
662                 in exponential notation, per gcvt()).
663         Make fork(): a) preserve i387 flags;
664                      b) preserve the dynamically loaded (system) DLLs;
665                      c) preserve morphed status;
666         Make sleep() work with time > 0xffffffff/1000.
667         Implement usleep() via _sleep2(); make select() with num_files==0
668                 thread-safe (via calling DosSleep()).
669         OS2::Process::Const() manages (MB|MBID|CF|CFI|SPTR)_.* constants too.
670         New (exported) functions from OS2::Process (some undocumented???):
671                 process_codepage_set
672                 TopLevel
673                 FocusWindow_set_keep_Zorder
674                 ActiveDesktopPathname
675                 InvalidateRect
676                 CreateFrameControl
677                 ClipbrdFmtInfo
678                 ClipbrdOwner
679                 ClipbrdViewer
680                 ClipbrdData
681                 OpenClipbrd
682                 CloseClipbrd
683                 ClipbrdData_set
684                 ClipbrdOwner_set
685                 ClipbrdViewer_set
686                 EnumClipbrdFmts
687                 EmptyClipbrd
688                 AddAtom
689                 FindAtom
690                 DeleteAtom
691                 AtomUsage
692                 AtomName
693                 AtomLength
694                 SystemAtomTable
695                 CreateAtomTable
696                 DestroyAtomTable
697                 _ClipbrdData_set
698                 ClipbrdText
699                 ClipbrdText_set
700                 _MessageBox
701                 MessageBox
702                 _MessageBox2
703                 MessageBox2
704                 LoadPointer
705                 SysPointer
706                 Alarm
707                 FlashWindow
708         Do not use AUTOLOAD in OS2::DLL; moved to OS2::DLL::dll.
709         New method OS2::DLL->module() (to replace botched ->new() method).
710         New functions call20(), call20_p(), call20_rp3(), call20_rp3_p(),
711                 call20_Dos(), call20_Win(), call20_Win_0OK(),
712                 call20_Win_0OK_survive() in OS2::DLL to call C functions via
713                 pointers.
714
715 After @20218:
716         select() workaround broke build of x2p.
717         New OS2::Process (exported, undocumented) functions:
718                 kbdChar
719                 kbdhChar
720                 kbdStatus
721                 _kbdStatus_set
722                 kbdhStatus
723                 kbdhStatus_set
724                 vioConfig
725                 viohConfig
726                 vioMode
727                 viohMode
728                 viohMode_set
729                 _vioMode_set
730                 _vioState
731                 _vioState_set
732                 vioFont
733                 vioFont_set
734         Make CheckOS2Error() macro return the error code.
735         New dynaloaded entry point DosReplaceModule().
736         New function OS2::replaceModule(target [, source [, backup]]).
737
738 After @21211:
739         Make Cwd::sys_abspath() default to '.' and taint the result.
740         Fix os2_process*.t to work if the default for VIO windows is maximized.
741         Fix to avoid non-existing PIDs for get_sysinfo() broke pid==0.
742         Restore default mode for pipes to be TEXT mode.
743
744 After @21379:
745         New OS2::Process functions: __term_mirror_screen() __term_mirror()
746                 io_term().
747         Fix a.out build: special-case thread::shared, pick up all the build
748                 static libraries, not only those for top-level modules.
749         Fix DLLname() test to work with the static build too.
750         New dynaloaded entry point RexxRegisterSubcomExe(); make OS2::REXX use
751                 it so it is not linked with REXX*.DLLs any more.
752         If system "./foo", and empty "./foo" and "./foo.exe" exist,
753                 argv[0] would be set to junk.
754         Make perl2cmd convert .pl files and keep the command-line switches.
755         Make XSLoader and Perl-specific parts of DynaLoader to die with static
756                 builds (new variable $OS2::is_static used);
757         Move perlmain.obj to the DLL; export main() as dll_perlmain(); create
758                 a library libperl_dllmain to translate the exported symbol
759                 back to main(); link the executables with this library instead
760                 of perlmain.obj.
761         Add /li to link386's options (line number info in the .map file).
762         Another break from fix to avoid non-existing PIDs for get_sysinfo().
763
764 After @21574:
765         Update import libraries when perl version changes (e.g., due to rsync).
766         New exported symbols dup() and dup2() [the wrappers have workaround
767                 for off-by-one error + double fault in the pre-Nov2003 kernels
768                 when a (wrong) filedescriptor which is limit+1 is dup()ed].
769         Enable disabling fd via a FILE* (to avoid close() during fclose()).
770         New dynaloaded entry point DosPerfSysCall().
771         New function OS2::perfSysCall(cmd = CMD_KI_RDCNT, ulParm1= 0,
772                                       ulParm2= 0, ulParm3= 0); when called
773                 with cmd == CMD_KI_RDCNT = 0x63 and no other parameters,
774                 returns: in the scalar context: the tick count of processor 1;
775                          in the list context: 4 tick counts per processor:
776                                 total/idle/busy/interrupt-time.
777                 with cmd == CMD_KI_GETQTY == 0x41 and no other parameters,
778                 returns the CPU count.  Currently in other cases the return
779                 is void.
780         New executables perl___<number> generated with decreased stack size
781                 (good when virtual memory is low; e.g. floppy boot).
782
783 After 5.8.2 (@21668):
784         Fixes to installperl scripts to avoid junk output, allow overwrite
785                 of existing files (File::Copy::copy is mapped to DosCopy()
786                 with flags which would not overwrite).
787         Disable DynaLoading of Perl modules with AOUT build (will core anyway).
788         For AOUT build: Quick hack to construct directories necessary for
789                 /*/% stuff [maybe better do it from hints/os2.sh?].
790         AOUT build: do -D__ST_MT_ERRNO__ to simplify linking with -Zmtd
791                 (e.g., to test GD: gd.dll linked with -Zmtd).
792         MANIFEST.SKIP was read without a drive part of the filename.
793         Rename Cwd::extLibpath*() to OS2::... (old names still preserved).
794         Install perl.lib and perl.a too.
795         New methods libPath_find(),has_f32(),handle(),fullname() for OS2::DLL.
796         Enable quad support using long long.
797         New C exported functions os2_execname(), async_mssleep(), msCounter(),
798                 InfoTable(), dir_subst(), Perl_OS2_handler_install(),
799                 fill_extLibpath().
800         async_mssleep() uses some undocumented features which allow usage of
801                 highest possible resolution of sleep() while preserving low
802                 priority (raise of resolution may be not available before
803                 Warp3fp40; resolution is 8ms/CLOCK_SCALE).
804                 usleep() and select(undef,undef,undef,$t) are using this
805                 interface for time up to 0.5sec.
806         New convenience macros os2win_croak_0OK(rc,msg), os2win_croak(rc,msg),
807                 os2cp_croak(rc,msg).
808         Supports ~installprefix, ~exe, ~dll in PERLLIB_PREFIX etc (actual
809                 directories are substituted).
810         New functions OS2::msCounter(), OS2::ms_sleep(), OS2::_InfoTable().
811         Checks stack when fixing EMX being under-initialized (-Zomf -Zsys
812                 produces 32K stack???).
813         New environment variables PERL_BEGINLIBPATH, PERL_PRE_BEGINLIBPATH,
814                 PERL_POST_BEGINLIBPATH, PERL_ENDLIBPATH, 
815                 PERL_PRE_ENDLIBPATH PERL_POST_ENDLIBPATH (~-enabled);
816                 PERL_EMXLOAD_SECS.
817         Better handling of FIRST_MAKEFILE (propagate to subdirs during test,
818                 do not require Makefile.PL present).
819         perl2cmd converter: do not rewrite if no change.
820         README.os2 updated with info on building binary distributions and
821                 custom perl executables (but not much else).