Bytearray for socket packets

Hi all,

I’m trying to create a IPC packet and pass it to an external program (tev).
Tev is expecting a packet of the form:

[uint32_t total_length_in_bytes][byte operation_type][byte[] operation_specific_payload]

Where I’m struggling is to combine bytes defined by achar(byte, kind=ucs4) and achar(byte) as I need to pass a character array as the packet to the external program.

program test

implicit none

integer, parameter :: ucs4 = selected_char_kind("ISO_10646")
character(kind=ucs4) :: buffer(5)

!...
! open socket etc
!...

buffer(1) = achar(4,kind=ucs4) !size of packet
buffer(2) = achar(4) !create image operation
buffer(3)  = achar(1) !grab focus
call writebuffer(socket, buffer, size(buf))

end program test

writebuffer is a wrapper around a C function from the f90sockets library.

Does anyone have any idea how I could achieve this?
Many thanks in advance for all your help!

The writebuffer is a generic interface for four sub-procedures

  INTERFACE writebuffer
      MODULE PROCEDURE writebuffer_s, &
                       writebuffer_d, writebuffer_dv, &
                       writebuffer_i
                       
  END INTERFACE 

where the endings likely stand for string, double, double-vector, and integer. The string version has the interface:

  SUBROUTINE writebuffer_s (psockfd, fstring, plen)
      USE ISO_C_BINDING
    INTEGER, INTENT(IN)                      :: psockfd
    CHARACTER(LEN=*), INTENT(IN)             :: fstring
    INTEGER, INTENT(IN)                      :: plen

and expects a string of default kind and not the ucs4. The second actually has a size of 4 bytes in case you are using gfortran. Here’s a program to show the difference in storage size:

integer, parameter :: ucs4 = selected_char_kind("ISO_10646")
character :: char1
character(kind=ucs4) :: char2
print *, storage_size(char1), storage_size(char2)
end

To fill the the first four bytes of a default character buffer you can use the transfer intrinsic function to copy the bit representation from an integer to a string (and back):

character(len=4) :: char
integer :: i, j

char = repeat(achar(0),4)
write(*,'(B32.32)') char

do i = 0, 31
  char = transfer(2**i,char)
  j = transfer(char,j)
  write(*,'(B32.32,1X,I0)') char, j
end do

end

Open the box to see the output from the Intel Fortran compiler:

Intel Fortran Result
$ ifort storage_size.f90 
$ ./a.out
00000000000000000000000000000000
00000000000000000000000000000001 1
00000000000000000000000000000010 2
00000000000000000000000000000100 4
00000000000000000000000000001000 8
00000000000000000000000000010000 16
00000000000000000000000000100000 32
00000000000000000000000001000000 64
00000000000000000000000010000000 128
00000000000000000000000100000000 256
00000000000000000000001000000000 512
00000000000000000000010000000000 1024
00000000000000000000100000000000 2048
00000000000000000001000000000000 4096
00000000000000000010000000000000 8192
00000000000000000100000000000000 16384
00000000000000001000000000000000 32768
00000000000000010000000000000000 65536
00000000000000100000000000000000 131072
00000000000001000000000000000000 262144
00000000000010000000000000000000 524288
00000000000100000000000000000000 1048576
00000000001000000000000000000000 2097152
00000000010000000000000000000000 4194304
00000000100000000000000000000000 8388608
00000001000000000000000000000000 16777216
00000010000000000000000000000000 33554432
00000100000000000000000000000000 67108864
00001000000000000000000000000000 134217728
00010000000000000000000000000000 268435456
00100000000000000000000000000000 536870912
01000000000000000000000000000000 1073741824
10000000000000000000000000000000 -2147483648

With gfortran the integer round-trip (and hence the bit transfer) works correctly, but there seems to be a bug in the I/O runtime library.

gfortran result
$ gfortran storage_size.f90 
(base) ipribec@ipribec-T530:~/fortran$ ./a.out
00000000000000000000000000000000
00000000000000000000000000000001 1
00000000000000000000000000000010 2
00000000000000000000000000000100 4
00000000000000000000000000001000 8
00000000000000000000000000010000 16
00000000000000000000000000100000 32
00000000000000000000000001000000 64
00000000000000000000000010000000 128
00000000000000000000000000000000 256
00000000000000000000000000000000 512
00000000000000000000000000000000 1024
00000000000000000000000000000000 2048
00000000000000000000000000000000 4096
00000000000000000000000000000000 8192
00000000000000000000000000000000 16384
00000000000000000000000000000000 32768
00000000000000000000000000000000 65536
00000000000000000000000000000000 131072
00000000000000000000000000000000 262144
00000000000000000000000000000000 524288
00000000000000000000000000000000 1048576
00000000000000000000000000000000 2097152
00000000000000000000000000000000 4194304
00000000000000000000000000000000 8388608
00000000000000000000000000000000 16777216
00000000000000000000000000000000 33554432
00000000000000000000000000000000 67108864
00000000000000000000000000000000 134217728
00000000000000000000000000000000 268435456
00000000000000000000000000000000 536870912
00000000000000000000000000000000 1073741824
00000000000000000000000000000000 -2147483648

Also note the wraparound behavior due to signed integers. If your total length in bytes of the packet exceeds 2**32 - 1 you’ll need some additional work (that’s just about 4.3 Gb).

Filling the remaining bytes of your packet should be straightforward.

So in essence you should have something like this:

integer, parameter :: plen = 4 + 2 ! packet/buffer length in bytes
character(len=plen) :: buffer

buffer(1:4) = transfer(plen,buffer(1:4))
buffer(5) = achar(4)  ! create image operation
buffer(6) = achar(1)  ! grab focus (already part of operation specific payload)

call writebuffer(socket, buffer, plen)

If you have a larger payload you’ll need to increase plen. If you are working by chance on a big-endian processor (unlikely) you’ll also need to manipulate the bits around.

1 Like

Great thanks that worked!