How much memory is my logical array using?

It is too easy to race ahead when just typing. Do you see your programs slowing down significantly when running more codes?
That is, is the wallclock of your code much slower running multiple copies instead of just one?

If not, it is unlikey you need to worry about this.

1 Like

If you want to ensure that VARIABLE_NAME is composed of 1-byte logicals, then the best approach is to use LOGICAL*1 :: VARIABLE_NAME(193710244).

The use of KIND=1 is no guarantee of single bytes and there is no SELECTED_LOGICAL_KIND to verify (what?).

While some may object to LOGICAL*1, there is unfortunately no concept of byte in the Fortran standard, so if the compiler accepts byte syntax, then you know what you are getting.

The following compiles for me.

      integer, parameter :: n = 193710244
      logical*1, allocatable :: VARIABLE_NAME(:)
      integer num

      allocate ( VARIABLE_NAME(n) )
      VARIABLE_NAME = .true.
      variable_name(1:n:3) = .false.
      num = count ( variable_name )
      write (*,*) num, ' are true'

      end

Fortran 202X (likely 2023) introduces SELECTED_LOGICAL_KIND. Also this revision introduces additional named constants of LOGICAL8, etc. in ISO_FORTRAN_ENV module.

2 Likes

Interesting, are there compilers where integer*1 is not the same as integer(1) ?

Anyways, I guess the standard way to do that would be using

   use iso_fortran_env
   logical(kind=int8), allocatable :: VARIABLE_NAME(:)
1 Like

With gfortran, I can run this program:

program t
use iso_fortran_env
implicit none
logical(int8), allocatable :: aaa(:)

allocate(aaa(123),source=.true._int8)
print *, 'aaa has ',count(aaa)
end program

The only ugly thing IMHO is that I have to define .true._int8, because gfortran rightfully assumes that .true. with no trailing kind is of the default one, and that I can’t use it to do sourced allocation of another kind of logical. That is a really awkward thing anyway.

2 Likes

The situation with the current standard as well as the next revision is indeed inadequate in that the standard does not allow the practitioner to perform a suitable inquiry into the options supported by the processor. Thus the practitioner is left to do that separately a priori and then proceed with the program.

   use, intrinsic :: iso_fortran_env, only : lk => logical_kinds
   block
      print *, "Supported logical_kinds: ", lk
   end block
   block
      integer, parameter :: lk1 = lk(1), lk2 = lk(2), lk3 = lk(3), lk4 = lk(4)
      print *, "storage size lk1: ", storage_size(.true._lk1)
      print *, "storage size lk2: ", storage_size(.true._lk2)
      print *, "storage size lk3: ", storage_size(.true._lk3)
      print *, "storage size lk4: ", storage_size(.true._lk4)
   end block
end
C:\temp>gfortran p.f90 -o p.exe

C:\temp>p.exe
 Supported logical_kinds:            1           2           4           8          16
 storage size lk1:            8
 storage size lk2:           16
 storage size lk3:           32
 storage size lk4:           64

The KIND values associated with one type have no relation to those of another type, so this is definitely not standard or portable. In fact, many people believe that the KIND values for different types (integer, real, logical) should all be distinct so that the common mistake of mixing types and kinds can be detected at compile time. Some compilers already optionally allow for this convention. The exception to this is the KIND values for real and complex, which are required by the standard to match.

Also, some compilers assign KIND values of 1 to the default integer, real, or logical types, and 2 to the extended precision kinds (double precision and 64-bit integer). So on these compilers, declaring LOGICAL(1) would be a 32-bit quantity, not an 8-bit quantity. The NAG compiler documentation says, “The compiler option ‘-kind=sequential’ (the default), ‘-kind=byte’ or ‘-kind=unique’ selects the method.”

I personally would like to see a 1-bit logical kind value supported, along with a 1-bit integer kind. Bit strings have been one of the most frequently requested features in fortran since the 1980s.

I’ve been misled by the IBM compiler documentation, is that non-stantard behavior?

2 Likes

I would say that IBM is documenting their compiler, but what they say works for that compiler may not be portable to other compilers.

Other compilers do the same thing regarding KIND values. Gfortran documentation, for example, is full of examples like INTEGER(4) and REAL(8). Those do correctly document the KIND values in the gfortran compiler, but it is easy to see how someone reading that documentation might be misled to think that those values are portable or are defined in the fortran standard.

The fortran KIND system is very general, powerful, and open ended. I don’t think any other language has anything comparable. But there is a layer beyond which everything is compiler dependent (or even compiler-option dependent) and nonportable.

1 Like

Until SELECT_LOGICAL_KIND() is available the method I like is to create constants from the *_KINDS variables, like defining the BOOL kind in the following module. It is not foolproof as noted in the comments but has proven to be quite portable. It takes some explanation so earlier in the discussion once the compiler being used was identified I thought it was less distracting to just show how you could list the logical kinds available and make a second program to query their sizes and show that for the target compiler KIND=1 worked. This has worked with multiple compilers to make the BOOL kind the smallest available, so as far as tricks go I think it is a pretty safe one (?). If the OP decides to go with
regular logicals instead of one of the bit libraries I was going to suggest defining a kind in a module anyway so just the module would need changed and not the rest of the code; and mention this
method.

module M_logical
use ISO_FORTRAN_ENV, only : logical_kinds
! assumes LOGICAL_KINDS values are from smallest to largest storage size
integer,parameter :: bool=minval(LOGICAL_KINDS)
end module M_logical

program testit
use M_logical, only : bool
implicit none
logical(kind=bool) :: little
   write(*,*)"kind=default,bits=",storage_size(.true.)
   write(*,*)"kind=bool,bits=",storage_size(.true._bool)
   write(*,*)"little bits=",storage_size(little)
end program testit

If anyone does not shoot a hole in it, I might suggest this as a twitter post for using the smallest LOGICAL kind? Not sure why I used minval(LOGICAL_KINDS) instead of LOGICAL_KINDS(1). If I remember a reason I will add it. You could do without the module in this example, but I find putting kinds in a module pays off in general, and the real module defines other things, including a function that checks if the storage size of bool is not <= eight and warns about it that some of the codes call to warn that there is something to look at for the developer. It checks a lot of things so you know some assumptions are wrong when trying a new compiler or compiler options, or new machine.

What is the connection in the standard between the value of the KIND of a data type and the size of the type? That is, except for none?

I think the NAG compiler sets the default (i.e. 32-bit) logical KIND to 1. However, I don’t know what other logical KINDs, if any, it supports. If it does support an 8-bit logical KIND, then it would have to have a value larger than 1.

Anyways with “the smallest logical kind” presumably defined as the one with the smallest storage size of the type, the following can be considered even if a bit circuitous:

   use, intrinsic :: iso_fortran_env, only : logical_kinds
   integer, parameter :: LK = logical_kinds(minloc([( storage_size(logical(.true.,                  &
      logical_kinds(i))), integer :: i = 1, size(logical_kinds) )], dim=1))
   print *, "Storage size with logical kind of LK:", storage_size(.true._lk), " bits"
end
C:\temp>ifort /standard-semantics p.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.6.0 Build 20220226_000000
Copyright (C) 1985-2022 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
 Storage size with logical kind of LK:  8  bits
1 Like

NAG has a lot of modes, but I think they are all OK no matter which mode is being used:

 Type 	KIND Number 	KIND Number 	KIND Number 	Name 	Description
Name 	(sequential) 	(byte) 	(unique) 		
REAL 	1 	4 	301 	REAL32* 	Single precision floating-point
REAL 	2 	8 	302 	REAL64* 	Double precision floating-point
REAL 	3 	16 	303 	REAL128* 	Quad precision floating-point
					
COMPLEX 	1 	4 	301 	REAL32* 	Single precision complex
COMPLEX 	2 	8 	302 	REAL64* 	Double precision complex
COMPLEX 	3 	16 	303 	REAL128* 	Quadruple precision complex
					
LOGICAL 	1 	1 	201 	BYTE 	Single byte logical
LOGICAL 	2 	2 	202 	TWOBYTE 	Double byte logical
LOGICAL 	3 	4 	203 	WORD 	Default logical
LOGICAL 	4 	8 	204 	LOGICAL64 	Eight byte logical
					
INTEGER 	1 	1 	101 	INT8* 	8-bit integer
INTEGER 	2 	2 	102 	INT16* 	16-bit integer
INTEGER 	3 	4 	103 	INT32* 	32-bit (default) integer
INTEGER 	4 	8 	104 	INT64* 	64-bit integer
					
CHARACTER 	1 	1 	646 	ASCII 	ASCII or ISO 8859-1 character
CHARACTER 	2 	2 	213 	JIS 	JIS X 0213 character
CHARACTER 	3 	3 	5323 	UCS2 	Unicode (UCS-2) character
CHARACTER 	4 	4 	10646 	UCS4 	ISO 10646 (UCS-4) character

Although in unique mode the one-byte logical kind value is 201, which emphasizes why using “1” is not portable.

1 Like

None, but I know of no compiler that does not follow that order, hence the comment about the assumption in the module.

I tried something like that and could not get it to work except with ifort and could not see why. Congrats. I will try that. I did not think of specifying I in it; the only thing I think I did that I might change was on the use statement used LKS=> logical_kinds in attempt to make it shorter.

I am wondering what the argument “val” means for this function SELECTED_LOGICAL_KIND (val) ? It is certainly not precision !

With all the confusion between kind values ( and lack of advice in the standard ), a pragmatist like me identifies the simplicity and clarity of byte sized type definitions, such as “REAL * 8” or “LOGICAL * 1”, (although I have never needed to know what COMPLEX*8 implies)

NAG’s use of kind=4 for an 8-byte integer becomes a very confusing syntax if used in constants as 1234567890_4. The standard should have recomended that the prefered kind value should default to the byte size. I use Salford FTN95, which is similar to NAG’s kind values and provides signiicant portability issues for use of KIND.

1 Like
    16.9.182 SELECTED_LOGICAL_KIND (BITS)

 1  Description. Logical kind selection.

 2  Class. Transformational function.

 3  Argument. BITS shall be an integer scalar.

 4  Result Characteristics. Default integer scalar.

 5  Result Value. The result has a value equal to the value of the kind type parameter of a logical type whose
    storage size in bits is at least BITS, or if no such kind type parameter is available on the processor, the result is
    -1. If more than one kind type parameter meets the criterion, the value returned is the one with the smallest
    storage size, unless there are several such values, in which case the smallest of these kind values is returned.

 6  Example. Assume a processor supports four logical kinds with kind type parameter values 8, 16, 32, and 64 for
    representations with those storage sizes. On this processor, SELECTED_LOGICAL_KIND (1) has the value 8,
    SELECTED_LOGICAL_KIND (12) has the value 16, and SELECTED_LOGICAL_KIND (128) has the value
    -1.

That is why you should never use the literal KIND constant, neither in type declarations nor when specifying integer or real literal constants. You should always define a parameter, say ik, and use that instead:

   integer, parameter :: ik=...
   ...
   integer(ik) :: ival
   ...
   ival = 1234567890_ik

That general rule applies also to real KINDs. The main “gotcha” is when types and kinds are inadvertently mixed.

   integer, parameter :: wp=selected_real_kind(14)
   real(wp) :: x
   ...
   x = 1234567890_wp

That looks like a real literal because of the _wp KIND, but it isn’t, it is an integer literal. It is perfectly valid fortran, so the compiler does not know that you have made a mistake. This is the situation that the “unique” KIND convention avoids; in this case, the compiler can recognize the error at compile time.

The standard should have recomended that the prefered kind value should default to the byte size.

The standard is general in this respect, allowing for implementation on word addressable machines that do not even have bytes, many of which were in use in the 1980s when the KIND system was designed. Also, in the 1980s, there existed computers that supported more than one format in a given number of bytes. The VAX, for example, supported two different 8-byte floating point formats, each with different numbers of exponent and mantissa bits. [Ironically, an f90 compiler was never implemented on the VAX, the company went defunct first.]

Also, of course, the byte convention would have precluded the “unique” convention, which many programmers prefer.

I think the standard got this decision right.

1 Like

This is a bit misleading, as my understanding is multiple formats for the same byte-size real were not supported in the same program and IEEE 754 was well established by 1985.