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