Coder Social home page Coder Social logo

oleg-n-cher / ofrontplus Goto Github PK

View Code? Open in Web Editor NEW
53.0 53.0 10.0 48.35 MB

Oberon family of languages to C translator for ARM, x64 and x86 architectures

License: Other

HTML 3.02% C 0.42% Batchfile 1.42% Modula-2 7.03% Shell 1.77% Rich Text Format 5.91% Component Pascal 44.17% C++ 26.88% Oberon 9.37%

ofrontplus's People

Contributors

eu-genes avatar kekcleader avatar oleg-n-cher avatar sgreenhill avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

ofrontplus's Issues

Error when calculating size of a post-defined type

Dear Josef,

today I've found error when compiled this code (see attach):

MODULE Err1;

TYPE
  ModuleDesc = RECORD types: ADR END;
  ADR = INTEGER;

PROCEDURE REGMOD;
VAR s: INTEGER;
BEGIN
  s := SIZE(ModuleDesc)
END REGMOD;

END Err1.

The error present in Ofront for BlackBox. The command line version works OK.

    PROCEDURE Base*(typ: OPT.Struct): INTEGER;
    BEGIN
        CASE typ^.form OF (* typ^.form = 0 *)

Josef, perhaps you can remember where it was corrected in command line version? And you can fix this error in Ofront for BlackBox.

I certainly will look, too. But I think you should know.

err1

Work under Windows 9x

There is a desire to make support that Ofront+ worked under old versions of Windows, so that it could be run really everywhere, on any computer, even very old.

Support for this should not be too complicated, we just need to get rid of using the functions such GetFileSizeEx, SetFilePointerEx in Platform.Windows.Mod. I'm sure this will be enough.

The option -d to be able to build a module into a dynamic library

It's implemented by adding the prefix __EXPORT to the exported functions and variables.

#if defined _WIN32 || defined __CYGWIN__
#  ifdef __GNUC__
#    define __EXPORT __attribute__((dllexport))
#  else
#    define __EXPORT extern "C" __declspec(dllexport)
#  endif
#else
#  if __GNUC__ >= 4 && !defined(__OS2__)
#    define __EXPORT __attribute__((visibility("default")))
#  else
#    define __EXPORT extern "C"
#  endif
#endif

A special char in single char strings

MODULE Test0DX;

PROCEDURE Wr (s: ARRAY OF CHAR); END Wr;

BEGIN Wr(0DX)
END Test0DX.

translated to C as:

	Test0DX_Wr((CHAR*)"
", 2);

Test0DX.c:24:20: warning: missing terminating " character
Test0DX.c:25:1: warning: missing terminating " character
Test0DX.c:25: warning 150: newline in string constant

I see, Josef and Dave have fixed this issue. It's time to add the solution to Ofront+ too!

Segmentation fault when handle array in nested procedure

Arthur has found this bug. It exists in Ofront v1.3, Ofront+ and voc.

MODULE SpeedTest;
IMPORT Out := Console;

(* VAR m: ARRAY 50 OF INTEGER; - If array is declared here - all is ok *)

PROCEDURE F3(n: INTEGER): INTEGER;
VAR i: INTEGER;
    m: ARRAY 50 OF INTEGER; (* Segmentation fault when handle m[45] *)

  PROCEDURE f(n: INTEGER): INTEGER;
  BEGIN
    Out.Ln; Out.String('DEBUG: f('); Out.Int(n, 0); Out.String(') = ...'); Out.Ln;
    Out.Int(m[n], 0); Out.Ln;
    IF m[n] = -1 THEN m[n] := f(n - 1) + f(n - 2) END;
    RETURN m[n]
  END f;

BEGIN
  FOR i := 3 TO LEN(m) - 1 DO m[i] := -1 END;
  m[1] := 1; m[2] := 1;
  RETURN f(n)
END F3;

BEGIN
  Out.String('START.'); Out.Ln;
  Out.String('F3(45) = '); Out.Int(F3(45), 0); Out.Ln
END SpeedTest.

jtempl/ofront#11

Adapt ASH for 64 bit

In SYSTEM.h we see:

#define __ASH(x, n) ((n)>=0?__ASHL(x,n):__ASHR(x,-(n)))
#define __ASHL(x, n)    ((long)(x)<<(n))
#define __ASHR(x, n)    ((long)(x)>>(n))

As we know, type "long long" is always 64 bit, while "long" may be 32 bit e.g. under MS Visual C/MinGW. So to adapt __ASHL, __ASHR for 64 bit, we can use cast to "long long", but isn't it overhead?

Ofront's docu:

NAME    ARGUMENT TYPE   RESULT TYPE FUNCTION
ASH(x, n)   x, n: integer type  LONGINT arithmetic shift (x * 2n)

Result is always LONGINT, but keep in mind the fact that type LONGINT previously cannot be 8 bytes in Ofront - we just now adapt it to this size.

Take look to BlackBox:

Name    Argument type   Result type Function
ASH(x, y)   x: <= INTEGER   INTEGER arithmetic shift (x * 2^y)
    x: LONGINT  LONGINT
    y: integer type

GPCP:

4.9.5 Changes for ASH

Prior to version 1.3.16 the builtin arithmetic shift function ASH only worked correctly
for the 32-bit integer type. From the current version onward two significant changes
have been made.
First, the function now has the following available signatures —
PROCEDURE ASH(arg : LONGINT; n : INTEGER) : LONGINT;
PROCEDURE ASH(arg : INTEGER; n : INTEGER) : INTEGER;
The return value is the shifted version of the first argument, and has the same type.
The second change is the behavior when shifts of greater than the data-word width
are attempted. Previously, shift amounts were applied modulo-wordwidth, which is the
usual semantic for machine instruction sets. The shift value is now range-checked, so
that INTEGER (LONGINT) shifts of magnitude greater than 31 (63, respectively) will
return a correctly sized zero (if arg is positive OR the shift is leftward) or negative-one
(if arg is negative AND the shift is rightward).

As we know, constants have an implicit type in Ofront:

CONST a = 10; (* type of it is SHORTINT *)
CONST a = LONG(10); (* type of it is INTEGER *)
CONST a = LONG(LONG(10)); (* type of it is LONGINT *)

So if we need LONGINT result for ASH, we can call ASH(LONG(argument)) or even ASH(LONG(LONG(argument))). As we see, LONGINT result by default for INTEGER argument is not so good idea as I thought at first.

So I suggest this way:

#define __ASHL(x, n)    (sizeof(x)==sizeof(long long)? (long long)(x)<<(n): (int)(x)<<(n))
#define __ASHR(x, n)    (sizeof(x)==sizeof(long long)? (long long)(x)>>(n): (int)(x)>>(n))

Thus, the advantage of my proposal is no overhead (while cast INTEGER argument to LONGINT and result from LONGINT to INTEGER back), and also compatibility with BlackBox and GPCP. Because the result of multiplication of two INTEGERs can always be LONGINT too, and so on. And it is normal practice in the care of very large numbers where they are excessive.

Adapt SYSTEM.LSH for 64 bit

As we see, Console.Mod has prerequisites to the fact that type LONGINT can be 64 bit:

IF SIZE(LONGINT) = 8 ...

Of course, the entire library libOberonV4 must be rebuilt with a new size of LONGINT, but Ofront now is not ready yet for this, so we'll just prepare it step by step.

To have LONGINT 64 bit, we'll define LONGINT as "long long", because "long" is 32 bit under MinGW64, and 64 bit under GCC64. And the type "long long" is 64 bit here and there.

typedef long long LONGINT;

Now I'd like to say about the macro __LSHL and __LSHR. If their argument x has the type "long long", a compiler shows warning:

SYSTEM.h:97:43: warning: left shift count >= width of type [-Wshift-count-overflow]
#define __LSHL(x, n, t) ((t)((unsigned)(x)<<(n)))
^
Console.c:98:11: note: in expansion of macro '__LSHL'
if (i == __LSHL(1, 63, LONGINT)) {
^
It was good described in the article http://norayr.am/log/?p=95
Norayr suggests to cast argument x into type "unsigned t", and after it do shift. For this, he must define all the types with help of preprocessor.

I suggest to rewrite these macro as:

#define __LSHL(x, n, t) (sizeof(t)==sizeof(long long)? (t)((unsigned long long)(x)<<(n)): (t)((unsigned)(x)<<(n)))
#define __LSHR(x, n, t) (sizeof(t)==sizeof(long long)? (t)((unsigned long long)(x)>>(n)): (t)((unsigned)(x)>>(n)))

It works under Windows and Linux. No loss of bits, no overhead. No need to use the preprocessor to define types.

Norayr's suggestion to сast into type "unsigned t" will work slightly differently, if type of x is SHORTINT. In this case, x will cast to unsigned SHORTINT and do shift of this type. My suggestion uses cast to "unsigned (int)" always (as originally written by Josef Templ), except when argument's size is as size of "long long". Given the fact that the operations with short (8 and 16 bit) types have no advantages on modern processors.

sysflag [1] for arrays other than open array value parameter

Currently, an array type declaration of the form

ARRAY[1] OF CHAR

is defined only for open array value parameters and means that the array is not
copied. Specifying the array sysflag, however, is allowed at other places as
well, where it is silently ignored by ofront.
While only the open array value parameter usage is defined in the
OfronUserGuide, it is a potential source for an error or misunderstanding.

Either the other usages should be marked by ofront as an error or they should
be supported. A possible semantics would be similar to RECORD[1], which means
untracked by the Garbage Collector. For this semantics a possible usage would
be in Module Args, where the argument vector argv is an untracked ARRAY OF
POINTER TO ARRAY OF CHAR.

Original issue reported on code.google.com by Josef Templ on 11 Oct 2013 at 11:35
jtempl/ofront#1

Inaccuracy in the implementation of __VAL()

Josef Templ wrote:

I don't remember it in detail but it seems that VAL is defined for variables not for values.
A variable is something in memory, a value is something in memory or in a register.
In C a value is an rhs (right hand side) expression, whereas a variable is an lhs (left hand side) expression (with respect to an assignment).
VAL tries to support all lhs expressions without turning them into rhs.
Sounds confusing? It is. But I am pretty sure that #define __VAL(t, x) ((t)(x))
would not work for all situations VAL is expected to work.

  • Josef
MODULE Input; IMPORT SYSTEM;

TYPE
  KeyboardEvent = RECORD END;
  Event = RECORD END;

PROCEDURE CheckAddKey (keybev: KeyboardEvent); END CheckAddKey;

PROCEDURE Available;
VAR
  event: Event;
BEGIN
  CheckAddKey(SYSTEM.VAL(KeyboardEvent, event));
END Available;

END Input.

Input.c: In function `Input_Available':
Input.c:32: error: conversion to non-scalar type requested

Bug of memory access after disposing it

Dear Josef,

please read the topic "Bug of memory access after disposing it"

vishapoberon/compiler#39

I think that since you are using the alloca(), you do not threaten by this problem. But using of the alloca() does not require __DEL() at all.

At the same time, the Ofront supports manual deallocation. So if you do as David:

define DUP(x, l, t) x=(void)memcpy((void)(uintptr_t)Platform_OSAllocate(l_sizeof(t)),x,l_sizeof(t))

define __DEL(x) Platform_OSFree((LONGINT)(uintptr_t)x)

you'll face exactly the same problems as we did.

It remains a matter of choice:

  1. either to prohibit the use of __DEL() at all. And remove of generating __DEL in the code. And use only alloca() mechanism.

  2. allow manual allocation and dispose of memory. Allow use another ways of memory allocation, except alloca(). Use and generate __DEL(). But the problem of the memory access in return after __DEL() need to be fixed.

I would like to know your opinion on this issue.

Oleg N. Cher

From: Josef Templ
Thu, 4 Aug 2016 11:17:57

alloca is much preferred.
It allocates memory on the stack and __DEL is empty then.
malloc/free on the other side is horribly slow compared to alloca
but it was not available on all platforms I ported ofront to.
That's why there is __DUP and __DEL.
I was not aware of the RETURN problem. Never appeared to me
but it obviously exists. An auxiliary variable solves the problem.
It could also be emitted only when needed but this is more complicated.

If possible, stay with alloca.

  • Josef

Allow SYSTEM.VAL(INTEGER, {80000000H..0FFFFFFFFH}) as a constant

I encountered such a situation. I have the module WinAPI.Mod, and there is a constant.

MODULE WinAPI;
  ...
  CW_USEDEFAULT * = 80000000H;
  ...
END WinAPI;

Ofront considers that it is an unsigned value of type LONGINT (64 bits). All right, it is exactly the same set of bits. Now, for example, we call a procedure where we need to pass a parameter of type INTEGER:

Call( CW_USEDEFAULT ); (* <-- Oops, overflow! *)

Of course, in Ofront all the constants are signed, so we need a mechanism to convert the constant value to the type INTEGER as a negative value that will match its set of bits inside the range of type INTEGER.

It's good that in Component Pascal we can explicitly specify the type of a hexadecimal constant, for example, like this:

  CW_USEDEFAULT_1 * = 80000000H; (* INTEGER *)
  CW_USEDEFAULT_2 * = 80000000L; (* LONGINT *)

But Ofront does not support such a solution. I decided to extend Dave's SYSTEM.VAL for constants by allow explicit conversion of such constants:

  SYSTEM.VAL (BYTE, {80H..0FFH});
  SYSTEM.VAL (SHORTINT, {8000H..0FFFFH});
  SYSTEM.VAL (INTEGER, {80000000H..0FFFFFFFFH});

Then we can define the constant and the call like this:

CONST
  CW_USEDEFAULT * = 80000000H;

  Call (SYSTEM.VAL (INTEGER, CW_USEDEFAULT ) );

To support this, I added some code in OPB module.

The precision should be increased for Int64

I haven't looked up the details but Entier seems to use a parameter
that specifies the precision.
If this is the case, the precision should be increased for Int64, I think.

  • Josef

If we look again at CPfront's CPV.Convert:

PROCEDURE Convert(n: OPT.Node; form, prec: SHORTINT);
BEGIN
    CASE form OF
    | Int8: OPG.WriteString("(_BYTE)"); Entier(n, 9)
    | Int16: OPG.WriteString("(SHORTINT)"); Entier(n, 9)
    | Int32: OPG.WriteString("(INTEGER)"); Entier(n, 9)
    | Int64: OPG.WriteString("(LONGINT)"); LEntier(n, 9)
    | Char8: OPG.WriteString("(SHORTCHAR)"); Entier(n, 9)
    | Char16: OPG.WriteString("(_CHAR)"); Entier(n, 9)
    | Set: OPG.WriteString("(SET)"); Entier(n, 9)
    | Real32: OPG.WriteString("(SHORTREAL)"); expr(n, prec)
    | Real64: OPG.WriteString("(REAL)"); expr(n, prec)
    ELSE expr(n, prec)
    END
END Convert;

It uses LEntier for Int64 type.

    PROCEDURE LEntier(n: OPT.Node; prec: SHORTINT);
    BEGIN
        IF n^.typ^.form IN {Real32, Real64} THEN
            OPG.WriteString("__ENTIERL("); expr(n, MinPrec); OPG.Write(CloseParen)
        ELSE expr(n, prec)
        END
    END LEntier;

SYSTEM.h:

#define __ENTIERL(x) SYSTEM_ENTIERL(x)

SYSTEM.c:

INTEGER SYSTEM_ENTIER(REAL x)
{
    INTEGER i;
    i = (INTEGER)x;
    if (i > x) i--;
    return i;
}

LONGINT SYSTEM_ENTIERL(REAL x)
{
    LONGINT i;
    i = (LONGINT)x;
    if (i > x) i--;
    return i;
}

Probably, I'll do the same. Thank you very much, Josef.

Browser shows the character 22X as """, no quotes for string constants

MODULE Mod1;
CONST

  Ch1* = "'";
  Ch2* = '"';
  Str1* = "'''''''''''";
  Str2* = '"""""""""""';
  Str3* = "@ptr";

END Mod1.

Browser shows:

DEFINITION Mod1;

  CONST
    Ch1 = "'";
    Ch2 = """;
    Str1 = ''''''''''';
    Str2 = """"""""""";
    Str3 = @ptr;

END Mod1.

Desirable behavior for the browser:

DEFINITION Mod1;

  CONST
    Ch1 = "'";
    Ch2 = '"';
    Str1 = "'''''''''''";
    Str2 = '"""""""""""';
    Str3 = "@ptr";

END Mod1.

Bug in using WriteFile

Dear David,

remember I wrote you that I have a memory access error. but I recently changed Platforms and Files modules, so I did not know exactly which module occurs error.

Now I can clarify this point.

You have used WriteFile in such way:

PROCEDURE -writefile(fd: LONGINT; p: LONGINT; l: LONGINT): INTEGER
"(INTEGER)WriteFile((HANDLE)(uintptr_t)fd, (void*)(uintptr_t)(p), (DWORD)l, 0,0)";

See two the last parameters? They are:

Out_opt LPDWORD lpNumberOfBytesWritten,
Inout_opt LPOVERLAPPED lpOverlapped

lpNumberOfBytesWritten [out, optional]
A pointer to the variable that receives the number of bytes written when using a synchronous hFile parameter. WriteFile sets this value to zero before doing any work or error checking. Use NULL for this parameter if this is an asynchronous operation to avoid potentially erroneous results.
This parameter can be NULL only when the lpOverlapped parameter is not NULL.

https://msdn.microsoft.com/en-us/library/windows/desktop/aa365747(v=vs.85).aspx

And you have passed both these parameters as NULL.

All this looks like nothing dangerous should not happened here, but that memory access error was caused exactly by this problem (under Windows XP).

I do propose this solution:

PROCEDURE -writefile(fd: FileHandle; p: MemAdr; l: INTEGER; VAR tmp: DWORD): BOOL "(INTEGER)WriteFile((HANDLE)fd, (void*)(p), (DWORD)l, (LPDWORD)tmp, 0)";

PROCEDURE Write*(h: FileHandle; p: MemAdr; l: INTEGER): ErrorCode;
VAR tmp: DWORD;
BEGIN
IF writefile(h, p, l, tmp) = 0 THEN RETURN err() ELSE RETURN 0 END
END Write;

Also you have used WriteFile in such way in procedures errstring() and errc(), so for full fixing this problem look at this commit:

65a6b22

I wrote to you earlier that the module Files.Mod now works without any problem under Windows XP, but I am sure that its work can not be guaranteed without this hotfix.

65a6b224eb077bfecd48a

Output REAL and LONGREAL

Dear all,

I'm writing about the following question in e-mail, and not in issue, because it's not a bug report, and rather the thinking.

Of course, I compare the output of Ofront for BlackBox and Ofront for command line. Now it comes to the real numbers, I noticed the Ofront for BlackBox gives:

      IF x >= 10.0 THEN x := 0.1*x; INC(e) END;
      x0 := Reals.Ten(n-1); x := x0*x + 0.5;
      IF x >= 10.0*x0 THEN x := x*0.1; INC(e) END;
        if (x >= (REAL)10) {
            x = 0.1000000014901161 * x;
            e += 1;
        }
        x0 = Reals_Ten(n - 1);
        x = x0 * x + 0.5;
        if (x >= (REAL)10 * x0) {
            x = x * 0.1000000014901161;
            e += 1;
        }

Ofront for command line gives:

        if (x >= (REAL)10) {
            x =   1.0000000e-001 * x;
            e += 1;
        }
        x0 = Reals_Ten(n - 1);
        x = x0 * x +   5.0000000e-001;
        if (x >= (REAL)10 * x0) {
            x = x *   1.0000000e-001;
            e += 1;
        }

Here we are seeing not only different precision in real numbers, but we see "0.5" and " 5.0000000e-001" (pay attention to the two extra spaces before the number).

This is controversial question what form is better to output real numbers - like "0.5" or "5.0000000e-001", but I certainly prefer the first way.

Ofront for BlackBox outputs real numbers by using TextMappers.Formatter.WriteReal that internally calls Strings.RealToStringForm

Ofront for command line outputs real numbers by using Texts.WriteReal and Texts.WriteLongReal taken from ETH Oberon.

I don't know exactly what I'll do with it (perhaps Arthur will help me), but I eventually would like to see the output of real numbers as in BlackBox.

Another problem I encountered - the exported real constants in sym-files. Make sure, my dear sirs, that your showdef is able to show LONGREAL constants in sym. files (see the attached pic).

If I'll have a solution of this problem, I'll let you know.

showdef

Oleg N. Cher

U_SET undeclared

IMPORT SYSTEM;
VAR
  attr, openFlags: SET;
BEGIN
  attr := SYSTEM.LSH(openFlags, -16);

KolFiles.c: In function 'KolFiles_FileCreate':
KolFiles.c:24: error: 'U_SET' undeclared (first use in this function)

BYTE instead of SYSTEM.BYTE

When you allow to specify SIZE(SHORTINT) = 2, SIZE(INTEGER) = 4, SIZE(LONGINT) = 8, the role of the type BYTE increases. So we want to use BYTE without importing the module SYSTEM, as it is done in Component Pascal (BlackBox / GPCP) and Ulm's Oberon System. In Oberon-07 Niklaus Wirth has done the same.

bba4088
dbcdd44

Infinite recursion in OPC.Stars

MODULE KolObj;

TYPE
TObj* = RECORD
name-: POINTER TO ARRAY OF CHAR;
END;

END KolObj.

stef@notebook:/$ ofront KolObj.Mod
KolObj.Mod translating KolObj new symbol file 391

MODULE KolSocket; IMPORT KolObj;

TYPE
TAsyncSocket* = RECORD (KolObj.TObj) END;

END KolSocket.

stef@notebook:/$ ofront KolSocket.Mod
Segmentation fault

It's infinite recursion in OPC.Stars - in line:

IF typ^.comp # DynArr THEN Stars (typ, openClause) END ;

Infinite recursion arise if variable pointers = 0. If change the line to:

IF typ^.comp # DynArr THEN
IF pointers # 0 THEN Stars (typ, openClause) END
END ;

the recursion not arises.

jtempl/ofront#6
jtempl/ofront@0ac725c

270e585

Output a module name and error position for HALT and ASSERT

So far we have had a very short output of the message about exceptional situations.

TestProc.Mod translating TestProc Terminated by Halt(-2). Index out of range.

There is a need to output also a name of the module in which the exception occurred, as well as the line and position of the source code. It is absolutely necessary for faster and easier search of bugs in programs.

So I implemented this output for exceptions.

TestProc.Mod translating TestProc
OfrontOPT 276:22 Terminated by Halt(-2). Index out of range.
^^^^^^^^^^^^
Module line:row

Remove file Ofront.par (a command line option will be enough)

Dave Brown once wrote to me that the file Ofront.par is a redundant possibility, since two digits it is enough to specify the sizes and alignment of a platform. So we replace the whole file with the option of two digits, which are passed to the translator at the command line.

(* target machine address size and alignment
	"21": 16 bit addresses, SIZE(SET) = 1 byte (e.g. Zilog Z80 CPU).
	"44": 32 bit addresses, 32 bit alignment (e.g. Unix/Linux 32 bit on x86).
	"48": 32 bit addresses, 64 bit alignment (e.g. Windows 32 bit on x86, Linux 32 bit on ARM).
	"88": 64 bit addresses, 64 bit alignment (e.g. 64 bit platforms).
*)

If the option is omitted, the compiler will issue a warning 156
warning 156 default target machine address size and alignment used
and this compilers address size and alignment will be used.

P.S. I know that potentially using the Ofront.par file can support more platform features than the one we are implementing now. But since many parameters there were not involved (BYTE, CHAR and BOOLEAN size # 1; BitOrder, ByteOrder, etc), getting rid of the Ofront.par makes perfect sense. Support for other platforms can be added later.

UTF-8 encoded sources (with BOM) support

Notepad on Windows encodes a text file in UTF-8 with special character 0FEFFX (0EFX, 0BBX, 0BFX) at position 0. Some programs for UNIX/Linux (e.g. pico, gedit) also support the files formed in this way.

I improved the module Texts to work with such text files. Now Ofront+ supports the sources encoded in UTF-8 with BOM.

Support "_" in identifiers

The possibility to write the character "_" in identifiers.

This feature is supported in Component Pascal (BlackBox / GPCP), Active Oberon, XDS and POW! Since OfrontPlus actively used for development on the WinAPI, it is not possible to rewrite all WinAPI's identifiers without "_".

Remember, this character is not present in the standards of Oberon / Oberon-2.

Oleg-N-Cher/OfrontPlus-bootstrap@62efaf3
8542fcb

Allow usage of SYSTEM.VAL in CONST section to explicitly define types of integer constants

This extension is implemented for voc by Dave Brown in the process of adapting the GC for 64-bit architectures. Thus, the LONGINT type is no longer a representation for the address type, because its size may be different.

Dave's proposal allows such code:

IMPORT SYSTEM;

TYPE
  ADDRESS = LONGINT; (* SYSTEM.ADRINT in future *)

CONST
  AddressZero = SYSTEM.VAL(ADDRESS, 0);

(* ... *)

BEGIN
  (* Put 64-bit zero on 64-bit architectures or 32-bit for 32-bit architectures: *)
  SYSTEM.PUT(adr, AddressZero);

SYSTEM.ADR(x): INTEGER, when SIZE(INTEGER) = SIZE(SYSTEM.PTR)

A little modification that generates SYSTEM.ADR(x): INTEGER, when SIZE(INTEGER) = SIZE(SYSTEM.PTR)

MODULE Heap;
IMPORT SYSTEM;
TYPE
  ADR = POINTER [1] TO ARRAY [1] 1 OF CHAR; (* 32 or 64 bits *)
VAR adr1, adr2: ADR; 
BEGIN
  adr1 := SYSTEM.VAL(ADR, SYSTEM.ADR(adr1));
  adr2 := SYSTEM.VAL(ADR, SYSTEM.ADR(adr2));

So when SIZE(INTEGER) = SIZE(SYSTEM.PTR), generated:

    Heap_adr1 = (Heap_ADR)((INTEGER)&Heap_adr1);
    Heap_adr2 = (Heap_ADR)((INTEGER)&Heap_adr2);

And when not:

    Heap_adr1 = (Heap_ADR)((LONGINT)&Heap_adr1);
    Heap_adr2 = (Heap_ADR)((LONGINT)&Heap_adr2);

4dbfb642ed6095

Sym-file isn't updated on POINTER [1] TO ARRAY [1] ...

To reproduce this error, do the following steps:

    MODULE SDL2; (* Save this file as SDL2.Mod *)
    IMPORT SYSTEM;
    TYPE Pixels* = POINTER [1] TO ARRAY [1] MAX(LONGINT) OF LONGINT;
    END SDL2.

    MODULE SDL2; (* Save this file as SDL2e.Mod *)
    IMPORT SYSTEM;
    TYPE Pixels* = POINTER [1] TO ARRAY [1] OF LONGINT;
    END SDL2.

zorko@zorko:~/ofront-1.3/bin$ ./ofront -se SDL2.Mod
SDL2.Mod translating SDL2 new symbol file 189
zorko@zorko:~/ofront-1.3/bin$ ./showdef SDL2.sym

DEFINITION SDL2;

  TYPE
    Pixels = POINTER [1] TO ARRAY [1] 2147483647 OF LONGINT;

END SDL2.

zorko@zorko:/ofront-1.3/bin$ ./ofront -se SDL2e.Mod_
SDL2e.Mod translating SDL2 216
_zorko@zorko:
/ofront-1.3/bin$ ./showdef SDL2.sym_

DEFINITION SDL2;

  TYPE
    Pixels = POINTER [1] TO ARRAY [1] 2147483647 OF LONGINT;

END SDL2.

zorko@zorko:~/ofront-1.3/bin$ rm SDL2.sym
zorko@zorko:~/ofront-1.3/bin$ ./ofront -se SDL2e.Mod
SDL2e.Mod translating SDL2 new symbol file 216
zorko@zorko:~/ofront-1.3/bin$ ./showdef SDL2.sym

DEFINITION SDL2;

  TYPE
    Pixels = POINTER [1] TO ARRAY [1] OF LONGINT;

END SDL2.

jtempl/ofront#7

Extra option ARRLEN in Ofront.par

I've added to Ofront+ the following feature.

Size of an array length had always the type LONGINT. It was good for LONGINT 32 bits, but LONGINT 64 bits seems too many for this usage.

So I added the ability to specify the type of array length in Ofront.par

ARRLEN 2

or

ARRLEN 4

or

ARRLEN 8

It is also very useful for old platforms where are restrictions on the size of the segment, etc. For example, now we can limit a string size to 127 bytes (for Z80), or to 32767 bytes (for DOS). There is no necessity to use LONGINT, even if LONGINT is 32 bits, when INTEGER or SHORTINT is enough.

The option ARRLEN is not necessary. If it's not specified in Ofront.par, the LONGINT type will be used as before.

P.S.

Unfortunately, there are restrictions on the placement position of the option ARRLEN in the file Ofront.par. The sequence of these options was firmly fixed, and I did not change the order of work with it. Therefore the option ARRLEN should be located between RECORD and ENDIAN.

RECORD  1   1
ARRLEN  4
ENDIAN  1   0

Add system flag [stdcall] for procedures

Examples of using the flag [stdcall]:

MODULE TestStdcall;
IMPORT SYSTEM;

VAR
  proc1*: PROCEDURE[stdcall] (i: INTEGER);
  proc2*: PROCEDURE[stdcall];

PROCEDURE*[stdcall]ProcTimes*; END ProcTimes;

PROCEDURE^[stdcall]ProcForw*;
PROCEDURE[stdcall]ProcForw*; END ProcForw;

END TestStdcall.

Also the additional feature to declare foreing procedures not through C level, but directly in Oberon, was added. This implemented by the definition of a procedure header without a body marked with the flag "-":

PROCEDURE- [stdcall] ExitWindowsEx* (uFlags: SET; dwReserved: INTEGER): INTEGER;

in C code:

__EXTERN INTEGER __STDCALL ExitWindowsEx(SET uFlags, INTEGER dwReserved);
#define WinAPI_ExitWindowsEx(uFlags, dwReserved)	ExitWindowsEx(uFlags, dwReserved)

The feature allows to declare bindings to libraries in a simpler way (similar to BlackBox).

P.S. The new features do not affect compatibility with binding ways already implemented before. Previously definition of a procedure without a body had no special meaning - just generated an empty macro:

#define Module_Proc

Now empty macro for a procedure can be generated by:

PROCEDURE- Empty " ";

Do you see any sense in this?

Allow using SYSTEM.ADR("A")

MODULE TestAdrChar; IMPORT SYSTEM;
VAR adr: LONGINT;
BEGIN
adr := SYSTEM.ADR("AA");
END TestAdrChar.

It's compiled and works. I prefer to a result of SYSTEM.ADR will be compatible
with SYSTEM.PTR, but this issue not about it.

If you change "AA" to "A", Ofront shows error "illegal use of object". It's
natural - "A" is a CHAR, but it may be a string too.

In context of being "A" as an argument of SYSTEM.ADR, I would propose to equate
a char to string here.

I use Ofront for system programming. And it's annoying me sometimes, that
strings used with SYSTEM.ADR must have LEN only > 1.

jtempl/ofront#5

7cbdd1c
d907fa0
a5e7d06
12a24d5

jtempl/ofront@e37d6c4

SYSTEM_ENUMR can be called for uninitialized record types

During module initialization command objects are allocated on the Oberon heap and may cause a garbage collector invocation (before heap expansion). This leads to a call of the EnumPtrs procedure for enumerating the globally anchored pointers of the currently initializing module. Since the type pointers are initialized (__INITYP) after the command registration (__REGCMD), this leads to a SIGSEGV trap in __ENUMR (mapped to SYSTEM_ENUMR) called by EnumPtrs when dereferencing the uninitialized type pointer. (Josef Templ)

jtempl/ofront#29

Oleg, you can call SYSTEM_GC(TRUE) inside REGCMD for reproducing the problem reliably.
In the real world the error occurs on occasion, depending on the heap utilization. It is not possible to reproduce it by means of a test program. (Josef Templ)

Allow unlimited length of strings (as in BB)

Now the maximum length of a string is 255 characters + 0X (OPS.MaxStrLen = 256).

If we want to specify huge arrays of string data, this length will not be enough. In BlackBox this restriction is removed. We decided to follow the same way.

Anonymous struct declared inside parameter list

Dear Josef, dear Dave,

Can we do something with it?

MODULE Test;
PROCEDURE Proc* (p: POINTER TO ARRAY OF INTEGER); END Proc;
END Test.

#include "SYSTEM.h"

export void Test_Proc (struct {
INTEGER len[1];
INTEGER data[1];
} *p);

void Test_Proc (struct {
INTEGER len[1];
INTEGER data[1];
} *p)

GCC version 5.1.0 shows this warnings:

Test.c:10:1: warning: anonymous struct declared inside parameter list
} *p);
^
Test.c:10:1: warning: its scope is only this definition or declaration, which is
probably not what you want
Test.c:18:1: warning: anonymous struct declared inside parameter list
} *p)
^
Test.c:15:6: error: conflicting types for 'Test_Proc'
void Test_Proc (struct {
^
Test.c:7:13: note: previous declaration of 'Test_Proc' was here
export void Test_Proc (struct {

--
Oleg N. Cher

SIZE(SHORTINT) = 2 support

Old Oberon systems and translators (ETH Oberon, XDS, OO2C, POW!) use old set of types:

SHORTINT = 1, INTEGER = 2, LONGINT = 4 bytes

In practice, we need to use types with size 8 bytes, etc. So it's useful when a developer can use modern set of types (in Ofront.par):

SHORTINT = 2, INTEGER = 4, LONGINT = 8 bytes

For supporting SIZE(SHORTINT) = 2, just add the line into OPM.GetProperties:

    IF IntSize = 4 THEN MinInt := MinLInt; MaxInt := MaxLInt END ;
    IF SIntSize = 2 THEN MinSInt := -8000H; MaxSInt := 7FFFH END ;
    ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

f1ef246
Oleg-N-Cher/OfrontPlus-bootstrap@f569abf

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.