- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I try to read some data from a binary file written in the form of four 32 bits unsigned integers, iSub(0:3). One of the parameters need to be extracted has a length of 48 bits. It is defined in my code as Integer(kind=8); Int8. According to the documentation the low bits of Int8 are in bytes 0:31 of iSub(1) and bytes 32:47 are in bytes 0:15 of iSub(2).
I use the following code:
Int8 = ISHFT(( iSub(2) .AND. #FFFF),32) + iSub(1)
This works correctly, until iSub(1) reaching the maximum size of an Integer(kind=4).
Any recommendation how to overcome this limitation?
Tibor
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Int8 = ISHFT(INT(( IAND(iSub(2),Z'0000FFFF'),8),32) + IAND((int(iSub(1),8),Z'00000000FFFFFFFF'))
You also might consider using UNION
UNION MAP INTEGER(4) :: iSub(2) END MAP MAP INTEGER(8) :: iSubAsI8 END MAP MAP INTEGER(1) :: PADD(6) INTEGER(2) :: ZAP END MAP END UNION CALL YourRead(iSub) ZAP = 0 Print *, iSubAsI8
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Another way involves using TRANSFER. For a little endian machine:
program xyz implicit none integer :: i4(2) data i4 /Z'C0000000', Z'00010000'/ ! could have been read from file integer*8 :: i8 ! i8=transfer(i4,i8) print '(Z16)',i8 end program
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks for both of you for the helpful suggestion. I tried the solution based on the UNION contract and it worked.
The first solution of
Int8 = ISHFT(INT(( IAND(iSub(2),Z'0000FFFF'),8),32) + IAND((int(iSub(1),8),Z'00000000FFFFFFFF'))
might have a missing bracket
Thanks again.
Tibor
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Union map not is standard Fortran btw.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
jimdempseyatthecove (Blackbelt) wrote:..
You also might consider using UNION ..
Jim,
As suggested by Andrew, UNION is not supported by the Fortran standard. But you're on the right track to consider memory mapping in order to avoid needless copies of data using the other approach supported by the standard which is with TRANSFER. But note for cases such as the one mentioned by OP, you can achieve the same in standard-conforming fashion if the Fortran processor supports the standard feature of interoperability with a companion C processor and a derived type is used instead of the non-standard UNION. And note the feature introduced in Fortran 2008 revision of allowing objects with a POINTER attribute in a variable-definition context can make it convenient to work with such a derived type. See below:
module bitfield_m use, intrinsic :: iso_c_binding, only : I1 => c_int8_t, I4 => c_int32_t, I8 => c_int64_t, c_loc, & c_f_pointer implicit none private type, public :: bitfield_t ! Field of 8-bit integers private integer(I1) :: m_fields(8) = 0_i1 contains private procedure, pass(this) :: zap_fields procedure, pass(this), public :: int32 => get_int32 procedure, pass(this), public :: int64 => get_int64 generic, public :: zap => zap_fields end type bitfield_t contains subroutine zap_fields( this, idx ) ! Argument list class(bitfield_t), intent(inout) :: this integer, intent(in) :: idx(:) ! Local variable this%m_fields( idx ) = 0_i1 return end subroutine zap_fields function get_int32( this ) result(pvals) ! Argument list class(bitfield_t), intent(in), target :: this ! Function result integer(I4), pointer :: pvals(:) call c_f_pointer( cptr=c_loc(this%m_fields), fptr=pvals, shape=[ 2 ] ) return end function get_int32 function get_int64( this ) result(pval) ! Argument list class(bitfield_t), intent(in), target :: this ! Function result integer(I8), pointer :: pval call c_f_pointer( cptr=c_loc(this%m_fields), fptr=pval ) return end function get_int64 end module
program p use bitfield_m, only : bitfield_t implicit none character(len=*), parameter :: fmtg = "(g0,*(z0,1x))" type(bitfield_t) :: bits bits%int32() = [int( Z'C0000000'), int(Z'00010000')] call bits%zap( idx=[7,8] ) print fmtg, "Zapped value as a 64-bit integer: ", bits%int64() print fmtg, "Zapped value as 2 32-bit integers: ", bits%int32() stop end program p
Upon execution:
Zapped value as a 64-bit integer: C0000000 Zapped value as 2 32-bit integers: C0000000 0
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi FortranFan,
Thanks for the bitfield_m module and the example. It works well.
Tibor
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
FF
I haven't compiled your example. Can you look at the optimized disassembly to see if the compiler removed all the necessary standard conforming contortions?
mecej4's TRANSFER is (may be) the better choice. I'd wish the name could have been something different CAST or TRANSFORM may have been better linguistically. Transfer IMHO means to transport unchanged, IOW analogous to MOVE. In mecej4's usage, it behaves with MOVE with mold. Perhaps TRANSMORGRIFIER (for Clavin and Hobbes fans).
The problem with my UNION solution as it does not permit in situ coding (neither did the bitfield_t of FF's suggestion).
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Something like that would have done the job
int64 PROC STDCALL , il:DWORD,ih:DWORD mov eax,il mov edx,ih RET int64 ENDP
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
jimdempseyatthecove (Blackbelt) wrote:FF
I haven't compiled your example. Can you look at the optimized disassembly to see if the compiler removed all the necessary standard conforming contortions?
mecej4's TRANSFER is (may be) the better choice. ..
The problem with my UNION solution as it does not permit in situ coding (neither did the bitfield_t of FF's suggestion).
Jim Dempsey
Jim,
Though I have not looked at the disassemby, you'd be right in thinking the derived type case I show will result in far more instructions, perhaps 2X to 3X more, than with UNION. My point is with respect to standard conformance and also to have a portable and extensible solution, meaning with a suitably structured 'class' aka derived type, one can have a convenient utility to operate bitwise on large and different sets of data without having to make copies. TRANSFER is not a move process, it involves copies.
As to in situ coding, it's a matter of perspective I think. Just as in the earlier times but also now, "libraries" are expected to be kept handy including a whole bunch of utlities such as with bitwise manipulation. Then one just USEs them as needed and the BLOCK construct brings about a more verbose but clearer sense of "in situ" for scientific and technical coding in any way:
. . ! need to do bit maniputlation in situ? Use BLOCK block use bitfield_m, only : bitfield_t type(bitfield_t) :: foo foo%int32() = .. end block . .
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I think tkibedi needs to describe is situation a bit more:
>>a binary file written in the form of four 32 bits unsigned integers, iSub(0:3). One of the parameters need to be extracted has a length of 48 bits
In particular:
What is in the remaining data? (iow is the 1st 48-bit, assumed unsigned 48-bit, data followed by another 48-bit data, followed by ??)
Is the file very large and requires to be processed quickly?
Is this a once-only process, or repetitive process?
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi Jim and FortranFan,
This piece of code meant to read the so called header records from a file (unformatted, record length 32 bits) created by Pixie-16 digital data acquisition. Most of the variables extracted from these records are integers. Attached is the layout of the header record for one of the cards. There is a slight variation in bits 16:31 of record#2 and record#3 for the second digitiser card we used.
My problem was how to construct the EVTTIME (48 bits) from EVTTIME_LO (bits 0:31 of record#1) and EVTTIME_HI (bits 0:15 of record#2). In my code EVTTIME declared as Integer(kind=8). Speed is a real concern, as we have hundreds of GB data from a recent experiment.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I would suggest that the speed of bit manipulation is not important. Anything that involves reading very large amounts of data from files will be the thing that determines the processing time as this will be orders slower. Just adopt a simple and reliable (and standard) method such as transfer would be my choice.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Given that the data are already in position given little-endian hardware,
int8 = IAND(TRANSFER(iSub(1:2),int8),MASKR(48,KIND(int8)))
seems logical.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
You've shown the 4-word header, what does the remainder of the data look like?
If you already have C/C++ code for parsing your data stream, you might consider using the C interoperability feature to parse the data stream. Then use Fortran for the data manipulation.
Otherwise something like this (you finish and change names):
! Pixie16.f90 module Pixie16 type :: Pixie16_Header integer(4) :: FC_EL_HL_CID_SID_CH integer(8) :: FT_TS_TI_ET integer(4) :: OOR_TL_EE end type Pixie16_Header contains function Pixie16_Header_get_IsFinished(this) type(Pixie16_Header) :: this logical :: Pixie16_Header_get_IsFinished Pixie16_Header_get_IsFinished = (this%FC_EL_HL_CID_SID_CH < 0) end function Pixie16_Header_get_IsFinished function Pixie16_Header_get_EVTTIME(this) type(Pixie16_Header) :: this integer(8) :: Pixie16_Header_get_EVTTIME Pixie16_Header_get_EVTTIME = IAND(this%FT_TS_TI_ET, MASKR(48, kind(Pixie16_Header_get_EVTTIME))) end function Pixie16_Header_get_EVTTIME ! ... end module Pixie16 program Pixie16_Program use Pixie16 implicit none type(Pixie16_Header) :: header integer(8) :: time ! ... ! header = Read_Pixie16_Header if(Pixie16_Header_get_IsFinished(header)) then ! ... else time = Pixie16_Header_get_EVTTIME(header) ! ... endif ! ... end program Pixie16_Program
Jim Dempsey
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page