LOGICALS - [SUMMARY] logical expressions and variables
Logical expressions and operators:
! comparisons .LT., .LE., .EQ., .GE., .GT., .NE. <, <=, ==, >=, >, /= ! operators .AND., .OR., .NOT., .EQV., .NEQV.
Information regarding Boolean variables, operators and expressions tends to be dispersed partly because it impinges on so many aspects of Fortran programming -- e.g., flow control, masking, comparison, and selection. This summary provides an abridged version of those many uses.
In Fortran, logicals are an intrinsic data type used to represent Boolean values - which can only be either the value .TRUE. or .FALSE.. Logical values (expressions or variables) are primarily used to control program flow through conditional statements like IF and DO WHILE loops, but have other valuable uses such as masking.
Logical expressions can be formed using relational operators (for comparisons) and logical operators (for combining logical values in complex expressions).
RELATIONAL OPERATORS (FOR COMPARISONS)
These relational operators compare arithmetic or character expressions and return a logical value (.TRUE. or .FALSE.).
Meaning Syntax Example Equal to .EQ. or == x .EQ. y Not equal to .NE. or /= x .NE. y Less than .LT. or < x .LT. y Less than or equal to .LE. or <= x .LE. y Greater than .GT. or > x .GT. y Greater than or equal to .GE. or >= x .GE. yNote that for string comparisons trailing spaces are not significant but leading blanks are, and that comparing floating point values should often be done within a tolerance as rounding can easily cause values intended to be equal to test as not equal, for example.
BOOLEAN OPERATORS (FOR LOGICAL DATA)
These operators combine one or more logical expressions.
Operator Description Example .AND. True if both operands are true. P .AND. Q .OR. True if either or both operands are true. P .OR. Q .NOT. Reverses the logical state of the operand. .NOT. P .EQV. True if both operands are the same (both true or both false). P .EQV. Q .NEQV. True if operands are different (one true, one false). P .NEQV. QIt is a common extension to allow the expressions P==Q and P/=Q where P and Q are logical, but the standard requires P.EQV.Q AND P.NEQV.Q. It is possible to overload == and /= to work with logicals instead of changing the statements if porting from a compiler supporting the extension to one that does not, but changing the statements to conform to the standard is preferred.
The order of operations is important in complex expressions:
Parentheses () can be used to explicitly control the order of evaluation.
o Arithmetic expressions are evaluated first. o Relational operators are applied next. o Logical operators are applied last, in the order: .NOT., then .AND., then .OR., and finally .EQV. and .NEQV..
Variables are declared using the LOGICAL keyword:
LOGICAL :: is_active LOGICAL :: file_exists, data_valid(100) LOGICAL,parameter :: T=.TRUE., F=.FALSE. LOGICAL,allocatable :: mask(:,:)You can assign the "truth" literals to these variables:
is_active = .TRUE. file_exists = .FALSE.Note: The periods (.) surrounding the truth values are mandatory in standard Fortran.
DIFFERENT KINDS (SIZES)
Many programs use nothing but the default logical kind. Many make extensive use of logical expressions but use no LOGICAL variables explicitly at all!
Most platforms however support multiple LOGICAL kinds that typically vary only in storage size.
The standard requires one default logical kind to be supported of the same storage size as a default INTEGER and REAL and one of kind C_BOOL compatible with the C compiler partner to the Fortran compiler (if that size is different from the default); but the following kind names are standard:
use,intrinsic :: iso_fortran_env, only : & LOGICAL8, LOGICAL16, LOGICAL32, LOGICAL64and if supported will be the kind value with the indicated size in bits.
These named constant kinds may not be supported by a particular platform (in which case the value of the kind name will be a negative integer value) and additional kinds may be available as well.
The most common reason for using non-default kinds is when large logical arrays are being declared. Using the smallest available kind is warranted when large masks or arrays are required and can improve performance as well as decrease memory requirements.
The next most common reason to not use default logicals is when the values are being passed to and from C. In this case KIND=C_BOOL is almost always the kind to choose. Conveniently C_BOOL is often also the smallest kind available.
It might be surprising, but the smallest available storage size of a LOGICAL variable is almost always one byte, not one bit. Fortran does include bit-level procedures, but they are not typically used in regard to LOGICAL values, but to manipulate data at the bit level. This is done much more rarely than is using logicals for conditionally selecting code or conditionally selecting values via masking which is the primary interest here.
The following example program illustrates Fortran features related to the kind and size of LOGICAL variables. It demonstrates ...
o selected_logical_kind() ! return a kind value based on a minimum size o logical(val,kind) ! return different logical kinds o logical_kinds() ! list of supported kinds o kind(val) ! return integer value of kind of a value program demo_different_logical_kinds use iso_fortran_env, only : logical_kinds use,intrinsic :: iso_fortran_env, only : & & LOGICAL8, LOGICAL16, LOGICAL32, LOGICAL64 use,intrinsic :: iso_c_binding, only : C_BOOL implicit none character(len=*),parameter :: all=(*(g0)) ! potentially save space and improve performance by using the ! smallest available kind integer,parameter :: lk=selected_logical_kind(1) logical(lk) :: smallest_storage(10,20)Typical (platform-specific) output:! C_BOOL is a kind compatible with C interfaces logical(kind=c_bool) :: boolean=.TRUE.
integer :: i ! The integer array constant LOGICAL_KINDS() contains the kind ! values for supported logical kinds for the current processor print all, list LOGICAL kind values available on this platform do i =1, size(logical_kinds) print all, integer,parameter :: boolean, & & logical_kinds(i),=, logical_kinds(i) enddo
print all, LOGICAL8 ==> KIND=,LOGICAL8 print all, LOGICAL16 ==> KIND=,LOGICAL16 print all, LOGICAL32 ==> KIND=,LOGICAL32 print all, LOGICAL64 ==> KIND=,LOGICAL64 print all, C_BOOL ==> KIND=,C_BOOL
print all, storage size of default logical = , storage_size(.true.) print all, storage size of smallest logical kind = , & storage_size(smallest_storage) print all, storage size of C_BOOL= , storage_size(boolean)
print all, kind of default logical = , kind(.true.) print all, kind of smallest logical kind = , kind(smallest_storage) print all, kind of C_BOOL= , kind(.true._c_bool)
end program demo_different_logical_kinds
> list LOGICAL kind values available on this platform > integer,parameter :: boolean1=1 > integer,parameter :: boolean2=2 > integer,parameter :: boolean4=4 > integer,parameter :: boolean8=8 > integer,parameter :: boolean16=16 > LOGICAL8 ==> KIND=1 > LOGICAL16 ==> KIND=2 > LOGICAL32 ==> KIND=4 > LOGICAL64 ==> KIND=8 > C_BOOL ==> KIND=1 > storage size of default logical = 32 > storage size of smallest logical kind = 8 > storage size of C_BOOL= 8 > kind of default logical = 4 > kind of smallest logical kind = 1 > kind of C_BOOL= 1In summary generally using KIND=C_BOOL is a good choice as it is compatible with the C interface bindings, and is typically the smallest at one byte per value; but this requires verification on any given platform.
Fortrans logical intrinsic operators are primarily used for evaluating and manipulating Boolean (true/false) values and conditions, but in addition masks are used in many intrinsics ...
result = all(mask [,dim]) result = any(mask [,dim]) result = count(mask [,dim] [,kind] ) result = findloc (array, value, dim [,mask] [,kind] [,back]) result = findloc (array, value [,mask] [,kind] [,back]) result = maxloc(array [,mask]) | maxloc(array [,dim] [,mask]) result = maxval(array [,mask]) | maxval(array [,dim] [,mask]) result = merge(tsource, fsource, mask) result = minloc(array [,mask]) | minloc(array [,dim] [,mask]) result = minval(array [,mask]) result = minval(array ,dim [,mask]) result = pack( array, mask [,vector] ) result = parity( mask [,dim] ) result = product(array [,dim] [,mask]) result = reduce(array, operation [,mask] [,identity] [,ordered] ) result = sum(array [,dim[,mask]] | [mask] ) result = unpack(vector, mask, field)
Here are the main uses of Fortran logical intrinsic procedures:
CONDITIONAL EXECUTION: The most common use is in IF statements and DO WHILE loops to control which blocks of code are executed based on whether a condition is true or false.
! Example using a logical expression directly in an IF statement IF (x > 0 .AND. y < 10) THEN PRINT *, "Condition met"
USAGE IN CONTROL FLOW: Logicals are essential for decision-making structures:
LOGICAL :: condition INTEGER :: xx = 10 condition = (x .GT. 5) .AND. (x .LT. 15)
IF (condition) THEN PRINT *, "x is between 5 and 15" ELSEIF(x < 0)then PRINT *, "x is negative"
PRINT *, "x is outside the range"
program demo_random_number use, intrinsic :: iso_fortran_env, only : dp=>real64 implicit none
integer :: i, first, last, rand_int, sumup, passes real(kind=kind(0.0d0)) :: rand_val ! generate a lot of random integers from -10 to 100 and add to sum ! until upper limit is reached, for no reason first=-10 last=100 sumup=0 passes=0 do while (sumup <= 1000000000) call random_number(rand_val) rand_int=first+floor((last+1-first)*rand_val) sumup=sumup+rand_int passes=passes+1 enddo write(*,*)sumup=,sumup,passes=,passes end program demo_random_number
Logical arrays can be used as masks to selectively apply operations to elements of other arrays. This is particularly efficient for numerical computations.
integer,parameter :: isz=10 real, dimension(isz) :: a logical, dimension(isz) :: maskA WHERE construct allows for multiple masks to be conditionally used.mask = (a > 5.0) ! Double elements of a where a is greater than 5.0 a(mask) = a(mask) * 2.0
WHERE(cond1) ... ELSEWHERE(cond2) ...
...
Examples of masked array assignment are:
WHERE (TEMP > 100.0) TEMP = TEMP - REDUCE_TEMPWHERE (PRESSURE <= 1.0) PRESSURE = PRESSURE + INC_PRESSURE TEMP = TEMP - 5.0
RAINING = .TRUE.
Intrinsic operators like .AND., .OR., .NOT., and .EQV. (equivalent) or [char46]NEQV. (not equivalent) are used to combine or negate logical expressions, creating more complex conditions.
LOGICAL :: condition1, condition2, result[verify] is very powerful when using expressions as masks for processing strings. For example, to determine if strings represent valid Fortran symbol names:condition1 = (value1 == 10) condition2 = (value2 /= 0) result = condition1 .OR. condition2
program fortran_symbol_name implicit none integer :: i ! some strings to inspect for being valid symbol names character(len=*),parameter :: symbols(*)=[character(len=10) :: & A_ , & 10 , & September , & A B, & _A , & ]Results:write(*,("|",*(g0,"|"))) symbols write(*,("|",*(1x,l1,8x,"|"))) fortran_name(symbols)
contains
elemental function fortran_name(line) result (lout) ! determine if a string is a valid Fortran name ! ignoring trailing spaces (but not leading spaces) character(len=*),parameter :: int=0123456789 character(len=*),parameter :: lower=abcdefghijklmnopqrstuvwxyz character(len=*),parameter :: upper=ABCDEFGHIJKLMNOPQRSTUVWXYZ character(len=*),parameter :: allowed=upper//lower//int//_ character(len=*),intent(in) :: line character(len=:),allocatable :: name logical :: lout name=trim(line) if(len(name).ne.0)then ! first character is alphameric lout = verify(name(1:1), lower//upper) == 0 & ! verify other characters allowed in a symbol name & .and. verify(name,allowed) == 0 & ! check conforms to allowable length & .and. len(name) <= 63 else lout = .false. endif end function fortran_name
end program fortran_symbol_name
> |A_ |10 |September |A B |_A | | > | T | F | T | F | F | F |
Intrinsic functions like ALL() and ANY() are used to check if all or any elements in a logical array satisfy a condition, often used in conjunction with array masking.
logical,parameter :: t=.true., f=.false. logical, dimension(5) :: status = [ t, f, t, t, t ]if (all(status)) then print *, "All statuses are true" endif
if (any(status)) then print *, "At least one status is true" endif
For handling individual bits within integer variables, Fortran offers intrinsic functions like IAND (bitwise AND), IOR (bitwise OR), IEOR (bitwise exclusive OR), and NOT (bitwise NOT). These are crucial in low-level programming and certain numerical algorithms.
integer :: a, b, cbut these return integer, not logical values and are mentioned only for reference.a = int(z0101) b = int(z0011) c = IAND(a, b) ! c will be 1 (0001) write(*,*(g0,z0,1x)),a=,a,b=,b,c=,c
A conditional expression is related to logicals in that it is used to selectively evaluate a chosen subexpression.
scalar-logical-expr ? expr [ : scalar-logical-expr ? expr ]... : expr )Each expr of a conditional-expr shall have the same declared type, kind type parameters, and rank.
Examples of a conditional expression are:
( ABS(RESIDUAL)<=TOLERANCE ? "ok" : "did not converge" ) ( I>0 .AND. I<=SIZE(A) ? A (I) : PRESENT(VAL) ? VAL : 0.0 )Conditional expressions are required to short-circuit (execute only the selected expression and not the other candidate) unlike the remainder of Fortran where short-circuiting behavior is typically left up to the processor.
That is, elsewhere in Fortran it is not necessary for a processor to evaluate all of the operands of an expression, or to evaluate entirely each operand -- but the processor is free to evaluate all of the operands. That is, all of the operands may or may not be evaluated.
This principle is most often applicable to logical expressions, zero-sized arrays, and zero-length strings, but it applies to all expressions.
For example, in evaluating the expression
X > Y .OR. L(Z)L(Z) may or may not be evaluated assuming "L" is a procedure name when the first condition (X > Y) is true.
Logicals are not allowed in numeric expressions, as in common in several other languages. There is no automatic promotion of LOGICAL to INTEGER allowed by the standard or vice-versa. That being said, it is a common extension to cast .FALSE. to zero(0) and .TRUE. to some none-zero number; but what values are used and how many bits are significant in the values varies widely between current popular compilers and so the extension should be avoided.
Sample program:
program logical_integer implicit none character(len=*),parameter :: all=(*(g0)) integer :: i1, i2 ! make T and F abbreviations for .TRUE. and .FALSE. logical,parameter :: T=.true., F=.false. logical :: l1, l2Results:print all, MERGE() is one method for transposing logical and integer ! converting a logical to an integer is not done ! with LOGICAL(3f) and INT(3f) or promotion by assignment; ! but can be done with MERGE(3f) with scalars or arrays. i1=merge(1,0,T) i2=merge(1,0,F) write(*,all) T-->,i1, F-->,I2 l1=merge(T,F,i1.eq.0) l2=merge(T,F,i2.eq.0) write(*,all) 0-->,l1, 1-->,l2 end program logical_integer
> MERGE() is one method for transposing logical and integer > T-->1 F-->0 > 0-->F 1-->T
The Lw edit descriptor indicates that the field occupies w positions. The input field so specified consists of optional blanks, optionally followed by a period, followed by a "T" for true or "F" for false. The "T" or "F" may be followed by additional characters in the field, which are ignored.
So, for example the strings ".TRUE." and ".FALSE." are acceptable input forms if "w" is sufficiently sized.
A lower-case letter is equivalent to the corresponding upper-case letter in a logical input field.
The output field consists of w−1 blanks followed by a T or F, depending on whether the internal value is true or false, respectively.
program logical_formatted implicit none character(len=*),parameter :: all=(*(g0)) character(len=:),allocatable :: line logical :: array(8), p, q print all, Logicals print as the right-justified string "T" or "F" write(*,("[",l10,"]")) .TRUE. write(*,("[",l0,"]")) .FALSE. print all, the first non-blank letter after an optional period print all, determines the value on input print all, repeat(1234567,8) line=.false. .true. T F TrustyFake!!!tr fffffff print all, line read(line,(8(L7))) array print all, array end program logical_formattedResults:
> Logicals print as the right-justified string "T" or "F" > [ T] > [F] > the first non-blank letter after an optional period > determines the value on input > 12345671234567123456712345671234567123456712345671234567 > .false. .true. T F TrustyFake!!!tr fffffff > FTTFTFTFThe G edit descriptor also may be used to edit logical data.
Bit-level procedures
Other
o ieor(3), ior(3), ishftc(3), ishft(3), iand(3). o result = iall(array [,mask]) | iall(array ,dim [,mask]) o result = iany(array [,mask]) | iany(array ,dim [,mask]) o result = iparity( array [,mask] ) | iparity( array, dim [,mask] ) o result = maskl( i [,kind] ) o result = maskr( i [,kind] ) o result = merge_bits(i, j, mask) ! Merge bits using a mask Fortran Tutorials(license: MIT) @urbanjost
o VERIFY(3) is very powerful when using expressions as masks for processing strings o [[iso_fortran_env]] module o iso_c_binding module o TRANSFER(3) - Transfer bit patterns
