Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

reading derived types from a file

Paul_Dent
New Contributor I
848 Views

I want to create a neat way to read in stadrad file types,  like .bmp in particular right now.

Such files are binary and havbe a defined format including headers etc.

So I the idea to cerate a derived  type that exactly mirrored the file structure, or at least its fixed size parts like the header.

 

For example, the header of a .bmp file is as mirrored by this derived  type:

TYPE BMPFILEHEADER
SEQUENCE
CHARACTER*2 SIGNATURE
INTEGER*4 FILESIZE
BYTE RESERVED(4)
INTEGER*4 DATAOFFSET
END TYPE BMPFILEHEADER

 

When I first tried to compile it I got the error " structure contains one or more misaligned data types.  Well, yes, I can see that: The first 2-buye entry shoves the 4-bute entries following to straddle two 32-bit entities.

So I used the compile option "allow padding to align structures". Now it comples fine.

I don't know what exactly padding does, but I assume it merely locates the first 4-byte integer "filessize" on a 4-byte boundary by inserting two dummy byts after the 2-byte filed "SIGNATURE"

Now if I define

TYPE (BMPFILEHEADER)::HEADER

and

OPEN(9,FILE="SHAPE.BMP",ACCESS="SEQUENTIAL",FORM="BINARY",STATUS="OLD")
 READ(9)HEADER
WRITE(*,*)HEADER%SIGNATURE
WRITE(*,*)HEADER%FILESIZE

I expect to see

BM

the file szie

In fact I get

BM

15

Now if instead I do:

READ(9)HEADER%SIGNATURE
READ(9)HEADER%FILESIZE

WRITE(*,*)HEADER%SIGNATURE
WRITE(*,*)HEADER%FILESIZE

I get

BM
1045030

which is correct. The number is 000FF226 in hex

What this shows me is that read operation is not reading the variables as defined, but is also reading the invisible padding that was added for aligment and so getting 000F instead of the correct number.

I think this is an implemenation error, is it not? The read statement should only be reading as many bytes as declared variables have, and ignoring any padding added for processor hardware convenience.

 

Paul Dent

 

 

 

 

 

 

0 Kudos
9 Replies
MWind2
New Contributor III
784 Views

I get a warning and not an error for the first type. The results when run match what the signature and file size should be. There are several discussions about this like Solved: warning #6379: The structure contains one or more misaligned fields. - Intel Communities

My take is that the type for io is a type that reflects the bytes on disk, and if one uses the type in computation intensively, then converting the disk type to a computationally aligned type may help in speed, but if saved back to disk, then a conversion back to disk type would have to be done. 

0 Kudos
jimdempseyatthecove
Black Belt
731 Views

1>>Such files are binary and havbe a defined format including headers etc.

2>>I got the error " structure contains one or more misaligned data types. 

1 == you are required to use the defined format

2 == This should have been a warning and not an error.

Other than for performance reasons, misaligned data should not be in error. Running with a warning is ok.

 

Jim Dempsey

0 Kudos
Steve_Lionel
Black Belt Retired Employee
723 Views

The problem here is that the BMP header is 14 bytes - allowing padding means that your type won't match the file format. And, yes, the misalignment warning is just a warning (unless you've enabled turning warnings into errors). A more annoying problem is that the standard does not guarantee a lack of padding in SEQUENCE types - only that the order of components won't change. Some compilers will pack by default, others won't.

One might then try an interoperable type, but here the compiler will insert padding after the two-character header if the "companion C processor" would do so - which it will (in the absence of #pragma pack). There's no standard Fortran way to get the packing unless you did something like this:

 

use, intrinsic :: iso_c_binding
type, bind(C) :: BMPFILEHEADER
character :: SIGNATURE(2)
integer(C_INT8_T) :: FILESIZE8(4)
integer(C_INT8_T) :: RESERVED(4)
integer(C_INT8_T) :: DATAOFFSET8(4)
end type BMPFILEHEADER

 

and then used TRANSFER to convert between the arrays of 8-bit integers and a 32-bit integer. A bit clumsy but you'd have to do this only once.

0 Kudos
Arjen_Markus
Honored Contributor I
717 Views

Another solution is to read the 14 bytes into a character string of 14 long and transfer the various pieces explicitly. Then you have all control and you put the values into a structure that is convenient for computing. Reverse the process to write the header to file.

0 Kudos
Steve_Lionel
Black Belt Retired Employee
714 Views

FWIW, I've added to a list of proposals for Fortran 202Y the ability to declare "packed" interoperable types.

0 Kudos
Paul_Dent
New Contributor I
614 Views

Thank you for all the replies.  Yes it was only warning, not an error, before I allowed padding. I never think of trying to run a program with a warning. In this case, you all seem to be indicating it would have worked fine.

In my particular example, it was easy to workaround: I just read the odd 2 bytes of file ID in first. Then I checked that it was "BM" before continuing. Maybe that's what you're supposed to do, because if wasn't BM, the .BMP format wouldnlt apply.

 

But in general, wouldn't it be logical to think that if a file had a weird structure, like 3 bytes of this and 5 bytes of that etc, you should be able to create a derived type that mirrored the structure and read it in or write it out in one shot?

For a particular machine the compiler may well have to insert padding for alignment reasons, but the READ and WRITE statements should ignore the padding and read or write the variable lengths as declared.

If this is what you've proposed for FORTRAN 202x Steve, sounds good to me.

 

Paul

 

0 Kudos
Steve_Lionel
Black Belt Retired Employee
568 Views

BMP file format - Wikipedia

Yes, it is what I proposed - for Fortran 202y - 202x is in its final stages. (I wrote about that today - Doctor Fortran in "It's Getting Drafty in Here" - Doctor Fortran (stevelionel.com))

0 Kudos
andrew_4619
Honored Contributor II
521 Views

When I did some BMP stuff some years back that was capturing windows and was full of windows sdk calls anyway I did the bmp file io using the SDK "WriteFile" which takes the address and the number of bytes to write. That avoids any extra padding bytes causing an issue.

0 Kudos
FortranFan
Honored Contributor II
464 Views

@Paul_Dent ,

You write, "I want to create a neat way to read in stadrad file types,  like .bmp" and what appears a "neat way" to you is the READ statement. "READ(9)HEADER", and you set your language scope as some dialect of Fortran 90 plus some nonstandard extensions in Intel Fortran.  This limits you greatly and you have encountered the first issue already, the one with padding of type components.

Instead you may want to consider current standard Fortran with is fully supported by the free Intel oneAPI IFORT compiler and explore your options.  Here's a starting point:

module bmp_m
   use, intrinsic :: iso_c_binding, only : c_char, c_int16_t, c_int32_t
   integer, parameter :: HEADER_BYTES = 14
   type :: bmp_t
      private
      character(kind=c_char, len=HEADER_BYTES) :: m_header_string
      character(kind=c_char, len=:), allocatable :: m_data
      character(kind=c_char, len=2), public :: header_field = ""
      integer(kind=c_int32_t), public :: file_size = 0
      integer(kind=c_int32_t), public :: offset = 0
      integer(kind=c_int16_t), public :: reserved1 = 0
      integer(kind=c_int16_t), public :: reserved2 = 0
   contains
      private
      procedure, pass(dtv) :: read_bmp_t
      generic, public :: read(unformatted) => read_bmp_t
   end type
contains
   subroutine read_bmp_t( dtv, lun, istat, imsg )
      ! Argument list
      class(bmp_t), intent(inout)     :: dtv
      integer, intent(in)             :: lun
      integer, intent(out)            :: istat
      character(len=*), intent(inout) :: imsg
      istat = 0
      blk_read: block
         read( lun, iostat=istat, iomsg=imsg ) dtv%m_header_string
         if (istat /= 0 ) exit blk_read
         dtv%header_field = dtv%m_header_string(1:2)
         dtv%file_size = transfer( source=dtv%m_header_string(3:6), mold=dtv%file_size )
         dtv%reserved1 = transfer( source=dtv%m_header_string(7:8), mold=dtv%reserved1 )
         dtv%reserved2 = transfer( source=dtv%m_header_string(9:10), mold=dtv%reserved2 )
         dtv%offset = transfer( source=dtv%m_header_string(11:14), mold=dtv%offset )
         if (dtv%file_size > HEADER_BYTES) allocate( character(kind=c_char,len=(dtv%file_size - HEADER_BYTES)) :: dtv%m_data, stat=istat )
         if ( istat /= 0 ) exit blk_read
         read( lun, iostat=istat, iomsg=imsg ) dtv%m_data
      end block blk_read
   end subroutine 
end module

The above you can consume using the following main program that includes your "neat way" to read the file:

   use bmp_m, only : bmp_t
   type(bmp_t) :: bmp
   integer :: lun, istat
   character(len=256) :: imsg
   open( newunit=lun, file="anime_mf.bmp", form="unformatted", access="stream", iostat=istat, iomsg=imsg )
   if ( istat /= 0 ) then
      print *, imsg
      stop
   end if
   read( lun, iostat=istat, iomsg=imsg ) bmp
   if ( istat /= 0 ) then
      print *, imsg
      stop
   end if
   print *, "Header field: ", bmp%header_field 
   print *, "File size: ", bmp%file_size 
   print *, "Data offset: ", bmp%offset 
end    

You can then run the program using the attached BMP file:

C:\temp>ifort /standard-semantics p.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.5.0 Build 20211109_000000
Copyright (C) 1985-2021 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 14.30.30706.0
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\temp>p.exe
 Header field: BM
 File size:  2672578
 Data offset:  1078

Attached is the file tried out with the above program that indeed has a file size on >WinNT 5.0 format of 2,672,578 bytes

 

Citation: the original PNG version of the BMP file is here: https://github.com/cat-milk/Anime-Girls-Holding-Programming-Books/blob/master/Fortran

Makise_Kurisu_Modern_Fortran_Explained.png

0 Kudos
Reply