Proper Way to Represent C `unsigned char`?

Thanks for pointing that out, I added a comment to the line.

I don’t understand the difference between problem one and two. For me they sound identical. SOURCE has only 8 bits defined, therefore only the first byte of the RESULT (int32) is set, and the following 3 Bytes are undefined. I was just lucky to get zeros.

Look at the definition of the I8INDX value. That should make it clear.

Ah, I see. So problem one means it practically comes down to deciding whether it is little-endian or big-endian, and theoretically it would be possible to have an architecture which is neither.

2 Likes

The PDP-11 was a middle-endian machine. But I don’t see it being used for Raylib games anymore.

2 Likes

And I am happy GTK4 is not available on PDP-11! :sweat_smile:

3 Likes

By the way, besides Tso-Coding there is also a github page by xeenpl, who have started a port of raylib.
GitHub - xeenypl/raylib.f90: raylib bindings for fortran.
Maybe thiscan be used as a starting point.

I am incidentally working on my own Fraylib (Fortran raylib bindings.) It is not in Github as a “work in progress” (a very common thing in Github) and will never be there even when finished - I will release it in SourceForge instead, when it is ready.) However the “problem” mentioned in this thread is not raylib-specific. Basically any C library that uses unsigned_something will have the same issues. What I do to deal with this is to first define unsigned types such as as

integer, parameter, public :: c_unsigned_int  = c_int,&
                              c_unsigned_char = c_signed_char

This step may seem useless at first glance but later on in the code it helps figuring out what is unsigned and what’s not. Now, for raylib’s Color struct, my Fortran implementation is

type, bind(c), public :: Color
  integer(kind=c_unsigned_char) :: r, g, b, a
end type Color
interface Color
  module procedure Color_constructor_List, Color_constructor_Vector
end interface Color

contains

pure elemental function toUint8(x)
integer(kind=int8) :: toUint8
integer, intent(in) :: x
toUint8=transfer(x, 0_int8)
end function toUint8

function Color_constructor_List(r32, g32, b32, a32) result(res)
type(Color) :: res
integer, intent(in) :: r32, g32, b32, a32
res=Color(toUint8(r32), toUint8(g32), toUint8(b32), toUint8(a32))
end function Color_constructor_List

function Color_constructor_Vector(vec) result(res)
type(Color) :: res
integer, dimension(4), intent(in) :: vec
res=Color(toUint8(vec(1)), toUint8(vec(2)), toUint8(vec(3)), toUint8(vec(4)))
end function Color_constructor_Vector

Here, a simple function toUint8 is used to convert 32-bit integers to “unsigned” 8-bit. Notice that I overload Color. This gives me a lot of flexibility: I can now set up a color using four normal (32-bit) integers, or a vector containing four normal integers, or I can still use four 8-bit integers. All the following are valid:

type(Color) :: c1, c2, c3
c = Color(255, 0, 0, 255)   ! The most common usage in Fortran programs using raylib
c = Color([255, 0, 0, 255]) ! Useful in some cases
c = Color(toUint8(255), toUint8(0), toUint8(0), toUint8(255)) ! Masochistic, but possible

As for printing unsigned variables, I use a conversion function such as

elemental function toInt(b) result(res)
integer :: res
integer(kind=int8), intent(in) :: b
res=int(b); if (res<0) res=256+res
end function uint8ToInt

and a function to print Colors.

I’m not saying the above ideal or pleasant, but it works and frankly, unsigned types are my least concern when porting C libraries. My main concern is always the excessive use of pointers. Pointers are not evil, but excessive use of them for everything is extremely annoying. Since strings and arrays are second-class citizens in C (basically non-existant,) C libraries are full of pointers, meaning you have to deal with them accordingly and per-case when porting the library to Fortran. Not only that, but many C libraries do crazy things with pointers, making them hard to port. Even raylib, which does not do particularly crazy things with pointers, still has some interoperability difficulties.

Edit: For color constants such are raylib’s RED, the quick way is to define RED as a vector of four integers then use Color type’s overloading to get the color type:

integer, dimension(4), parameter :: RED = [255, 0, 0, 255]
...
type(Color) :: c
c = Color(RED)

Alternatively, one can define RED as type(Color):

type(Color) :: RED = Color(255, 0, 0, 255)

but this cannot be a parameter so an initialization subroutine will be needed to set up predefined colors. I didn’t like this approach, defining RED as a vector of four integers then use Color(RED) is good enough for me.

Could a function with an empty list of arguments do what @Pap wants? Something like

type(Color) function RED() 
  RED = Color(255,  0,  0, 255)
end function RED

I didn’t necessarily want the color constants to look exactly the same as in C. I was just discussing the possible ways to implement color parameters.
Your idea of doing this is not bad at all, but In this case RED is now a function and, as such, it must be called with the mandatory parentheses (even though there are no function arguments,) so it will be called like, e.g.,

call ClearBackground(RED())

instead of

call ClearBackground(Color(RED))

I’m not sure which one is “better”, and none is exactly as in C - which is just ClearBackground(RED). The only way I can think of to make it identical is to use an initialization function, like

module Initialization
use raylib_structs ! or wherever you define the Fortran equivalent of raylib C structs
implicit none
private
...
type(Color), public :: RED, GREEN ! etc

public :: InitColors
...
contains
...
subroutine InitColors
RED   = Color(255, 0, 0, 255)
GREEN = Color(0, 228, 48, 255)
...
end subroutine InitColors
...
end module Initialization

This solution would also save… a tiny amount of processor cycles, if you use a specific color constant too many times in your program (you probably won’t.)
If raylib itself had an initialization function that you must call in the beginning, I would definitely add InitColors in its Fortran equivalent. But raylib doesn’t have such a mandatory initialization function (actually it kind of has, hidden inside InitWindow - but that’s not the same thing.)
So, making it exactly the same a in C adds the extra “burden” to remember to call InitColors before you use any color constant. Much ado about nothing (sic), if you ask me. So I settled with Color(RED), but @Harper 's way works equally well.

A common mistake when porting C libraries is to try hard to make the Fortran equivalent look identical to C. My recommendation is “do it only if it makes sense”.
First of all, the Fortran way of doing things is far superior, so I see no reason to try to imitate C. For example C functions cannot return arrays so the common way to do that in C is to return a pointer (you can also return a struct containing said array but… come on now.). I see no reason to blindly do such things in Fortran; I would rather make the Fortran equivalent to return an allocatable array, unless said array is too large - in this case I would consider returning a pointer to that array (and even then, it wouldn’t look exactly the same, Fortran pointers are not the same as C pointers.)
Second, even if I wanted to imitate C at all costs, it is a futile attempt: the languages are very different in too many ways to make this possible.

By the way, the above reasons also explain why automating the translation of C header files to Fortran modules has too many pitfalls, and the resulting Fortran module usually needs so many heavy modifications to be usable - to the point of making automation more frustrating that useful.

What I try (and I strongly recommend) is to port a C library in such a way that “translating” an existing C program using said library to Fortran would be straightforward (but won’t necessarily look exactly the same.)

Gfortran now has experimental support for unsigned integer types in the current development version and it is planned to integrate support in the version 15 to be released next spring.

Note, however, that this feature is not yet standardized, although this is planned for Fortran202y.

7 Likes

In the gfortran mailing list there is now the impession that unsigned integers will likely not be integrated in Fortran 202Y, so that gfortran will end up with an incompatible extension to the Fortran standard.

https://gcc.gnu.org/pipermail/fortran/2024-October/061218.html

While it is true that there are general purpose languages that do not support unsigned integers (Python, Java), I really was kind of looking forward to this feature as it would make the interaction with C libraries that deal with things like RGB values or IP addresses more straightforward.

Disclaimer: I now consider myself now an occasional hobbyist Fortran programmer and no longer program Fortran on a professional level (Due to leaving academics not due to Fortran…).
So I guess my personal opinion is not really important, but my hint to the unsigned support in gfortran got some likes, so it might be interesting for other Fortran programmers, too.

2 Likes

This is being actively discussed in Unsigned integers · Issue #2 · j3-fortran/fortran_proposals · GitHub.

The issue is in figuring out how to support all use cases correctly and what the default behavior should be. My understanding of the committee is that they had the same concerns, which I agree with.

1 Like