These intrinsics allow for explicitly casting one type of variable to another or can be used to conditionally execute code blocks based on variable types when working with polymorphic variables.
Fortran provides five basic intrinsic data types:
These “types” can be of many “kinds”. Often different numeric kinds take up different storage sizes and therefore can represent different ranges; but a different kind can have other meanings. A character variable might represent ASCII characters or UTF-8 or Unicode characters, for example.
You can derive your own data types from these fundamental types as well.
Fortran allows a feature called implicit typing, i.e., you do not have to declare some variables before use. By default if a variable is not declared, then the first letter of its name will determine its type:
However, in most circles it is considered good programming practice to declare all the variables. For that to be enforced, you start your variable declaration section with a statement that turns off implicit typing: the statement
implicit none
For more information refer to the implicit statement.
aimag(3) - [TYPE:NUMERIC] Imaginary part of complex number
result = aimag(z)
elemental complex(kind=KIND) function aimag(z) complex(kind=KIND),intent(in) :: z
aimag(3) yields the imaginary part of the complex argument z.
This is similar to the modern complex-part-designator %IM which also designates the imaginary part of a value, accept a designator can appear on the left-hand side of an assignment as well, as in val%im=10.0.
The return value is a real value with the magnitude and sign of the imaginary component of the argument z.
That is, If z has the value (x,y), the result has the value y.
program demo_aimag use, intrinsic :: iso_fortran_env, only : real_kinds, & & real32, real64, real128 implicit none character(len=*),parameter :: g='(*(1x,g0))' complex :: z4 complex(kind=real64) :: z8 ! basics z4 = cmplx(1.e0, 2.e0) print *, 'value=',z4 print g, 'imaginary part=',aimag(z4),'or', z4%im ! other kinds other than the default may be supported z8 = cmplx(3.e0_real64, 4.e0_real64,kind=real64) print *, 'value=',z8 print g, 'imaginary part=',aimag(z8),'or', z8%im ! an elemental function can be passed an array print * print *, [z4,z4/2.0,z4+z4,z4**3] print * print *, aimag([z4,z4/2.0,z4+z4,z4**3]) end program demo_aimag
value= (1.00000000,2.00000000) imaginary part= 2.00000000 or 2.00000000 value= (3.0000000000000000,4.0000000000000000) imaginary part= 4.0000000000000000 or 4.0000000000000000 (1.00000000,2.00000000) (0.500000000,1.00000000) (2.00000000,4.00000000) (-11.0000000,-2.00000000) 2.00000000 1.00000000 4.00000000 -2.00000000
Fortran has strong support for complex values, including many intrinsics that take or produce complex values in addition to algebraic and logical expressions:
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
cmplx(3) - [TYPE:NUMERIC] Conversion to a complex type
result = cmplx(x [,kind]) | cmplx(x [,y] [,kind])
elemental complex(kind=KIND) function cmplx( x, y, kind ) type(TYPE(kind=**)),intent(in) :: x type(TYPE(kind=**)),intent(in),optional :: y integer(kind=**),intent(in),optional :: KIND
The type of the arguments does not affect the kind of the result except for a complex x value.
NOTE: a kind designated as ** may be any supported kind for the type
The cmplx(3) function converts numeric values to a complex value.
Even though constants can be used to define a complex variable using syntax like
z = (1.23456789, 9.87654321)
this will not work for variables. So you cannot enter
z = (a, b) ! NO ! (unless a and b are constants, not variables)
so to construct a complex value using non-complex values you must use the cmplx(3) function:
z = cmplx(a, b)
or assign values separately to the imaginary and real components using the %IM and %RE designators:
z%re = a z%im = b
If x is complex y is not allowed and cmplx essentially returns the input value except for an optional change of kind, which can be useful when passing a value to a procedure that requires the arguments to have a different kind (and does not return an altered value):
call something(cmplx(z,kind=real64))
would pass a copy of a value with kind=real64 even if z had a different kind
but otherwise is equivalent to a simple assign. So if z1 and z2 were complex:
z2 = z1 ! equivalent statements z2 = cmplx(z1)
If x is not complex x is only used to define the real component of the result but y is still optional – the imaginary part of the result will just be assigned a value of zero.
If y is present it is converted to the imaginary component.
Primarily in order to maintain upward compatibility you need to be careful when working with complex values of higher precision that the default.
It was necessary for Fortran to continue to specify that cmplx(3) always return a result of the default kind if the kind option is absent, since that is the behavior mandated by FORTRAN 77.
It might have been preferable to use the highest precision of the arguments for determining the return kind, but that is not the case. So with arguments with greater precision than default values you are required to use the kind argument or the greater precision values will be reduced to default precision.
This means cmplx(d1,d2), where d1 and d2 are doubleprecision, is treated as:
cmplx(sngl(d1), sngl(d2))
which looses precision.
So Fortran 90 extends the cmplx(3) intrinsic by adding an extra argument used to specify the desired kind of the complex result.
integer,parameter :: dp=kind(0.0d0) complex(kind=dp) :: z8 ! wrong ways to specify constant values ! note this was stored with default real precision ! z8 = cmplx(1.2345678901234567d0, 1.2345678901234567d0) print *, 'NO, Z8=',z8,real(z8),aimag(z8) z8 = cmplx(1.2345678901234567e0_dp, 1.2345678901234567e0_dp) ! again, note output components are just real print *, 'NO, Z8=',z8,real(z8),aimag(z8) ! ! YES ! ! kind= makes it work z8 = cmplx(1.2345678901234567d0, 1.2345678901234567d0,kind=dp) print *, 'YES, Z8=',z8,real(z8),aimag(z8)
A more recent alternative to using cmplx(3) is “F2018 component syntax” where real and imaginary parts of a complex entity can be accessed independently:
value%RE ! %RE specifies the real part or value%IM ! %IM specifies the imaginary part
Where the designator value is of course of complex type.
The type of a complex-part-designator is real, and its kind and shape are those of the designator. That is, you retain the precision of the complex value by default, unlike with cmplx.
The following are examples of complex part designators:
impedance%re !-- Same value as real(impedance) fft%im !-- Same value as AIMAG(fft) x%im = 0.0 !-- Sets the imaginary part of x to zero x(1:2)%re=[10,20] !-- even if x is an array
Note that if format statements are specified a complex value is treated as two real values.
For list-directed I/O (ie. using an asterisk for a format) and NAMELIST output the values are expected to be delimited by “(” and “)” and of the form “(realpart,imaginary_part)”. For NAMELIST input parenthesized values or lists of multiple _real values are acceptable.
result = CMPLX (REAL (X), AIMAG (X), KIND).
That is, a complex x value is copied to the result value with a possible change of kind.
The return value is of complex type, with magnitudes determined by the values x and y.
The common case when x is not complex is that the real component of the result is assigned the value of x and the imaginary part is zero or the value of y if y is present.
When x is complex y is not allowed and the result is the same value as x with a possible change of kind. That is, the real part is real(x, kind) and the imaginary part is real(y, kind).
program demo_aimag implicit none integer,parameter :: dp=kind(0.0d0) real(kind=dp) :: precise complex(kind=dp) :: z8 complex :: z4, zthree(3) precise=1.2345678901234567d0 ! basic z4 = cmplx(-3) print *, 'Z4=',z4 z4 = cmplx(1.23456789, 1.23456789) print *, 'Z4=',z4 ! with a format treat a complex as two real values print '(1x,g0,1x,g0,1x,g0)','Z4=',z4 ! working with higher precision values ! using kind=dp makes it keep DOUBLEPRECISION precision ! otherwise the result would be of default kind z8 = cmplx(precise, -precise ) print *, 'lost precision Z8=',z8 z8 = cmplx(precise, -precise ,kind=dp) print *, 'kept precision Z8=',z8 ! assignment of constant values does not require cmplx(3)00 ! The following is intuitive and works without calling cmplx(3) ! but does not work for variables just constants z8 = (1.1111111111111111d0, 2.2222222222222222d0 ) print *, 'Z8 defined with constants=',z8 ! what happens when you assign a complex to a real? precise=z8 print *, 'LHS=',precise,'RHS=',z8 ! elemental zthree=cmplx([10,20,30],-1) print *, 'zthree=',zthree ! descriptors are an alternative zthree(1:2)%re=[100,200] print *, 'zthree=',zthree end program demo_aimag
Z4= (-3.000000,0.0000000E+00) Z4= (1.234568,1.234568) Z4= 1.234568 1.234568 lost precision Z8= (1.23456788063049,-1.23456788063049) kept precision Z8= (1.23456789012346,-1.23456789012346) Z8 defined with constants= (1.11111111111111,2.22222222222222) LHS= 1.11111111111111 RHS= (1.11111111111111,2.22222222222222) zthree= (10.00000,-1.000000) (20.00000,-1.000000) (30.00000,-1.000000) zthree= (100.0000,-1.000000) (200.0000,-1.000000) (30.00000,-1.000000)
FORTRAN 77, KIND added in Fortran 90.
Fortran has strong support for complex values, including many intrinsics that take or produce complex values in addition to algebraic and logical expressions:
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
int(3) - [TYPE:NUMERIC] Truncate towards zero and convert to integer
result = int(a [,kind])
elemental integer(kind=KIND) function int(a, KIND ) TYPE(kind=**),intent(in) :: a integer,optional :: KIND
int(3) truncates towards zero and return an integer.
returns an integer variable applying the following rules:
Case:
The result is undefined if it cannot be represented in the specified integer type.
program demo_int use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64 implicit none integer :: i = 42 complex :: z = (-3.7, 1.0) real :: x=-10.5, y=10.5 print *, int(x), int(y) print *, int(i) print *, int(z), int(z,8) ! elemental print *, int([-10.9,-10.5,-10.3,10.3,10.5,10.9]) ! note int(3) truncates towards zero ! CAUTION: ! a number bigger than a default integer can represent ! produces an incorrect result and is not required to ! be detected by the program. x=real(huge(0))+1000.0 print *, int(x),x ! using a larger kind print *, int(x,kind=int64),x print *, int(& & B"111111111111111111111111111111111111111111111111111111111111111",& & kind=int64) print *, int(O"777777777777777777777",kind=int64) print *, int(Z"7FFFFFFFFFFFFFFF",kind=int64) ! elemental print * print *,int([ & & -2.7, -2.5, -2.2, -2.0, -1.5, -1.0, -0.5, & & 0.0, & & +0.5, +1.0, +1.5, +2.0, +2.2, +2.5, +2.7 ]) end program demo_int
> -10 10 > 42 > -3 -3 > -10 -10 -10 10 10 10 > -2147483648 2.14748467E+09 > 2147484672 2.14748467E+09 > 9223372036854775807 > 9223372036854775807 > 9223372036854775807 > > -2 -2 -2 -2 -1 > -1 0 0 0 1 > 1 2 2 2 2
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
nint(3) - [TYPE:NUMERIC] Nearest whole number
result = nint( a [,kind] )
elemental integer(kind=KIND) function nint(a, kind ) real(kind=**),intent(in) :: a integer(kind=**),intent(in),optional :: KIND
nint(3) rounds its argument to the nearest whole number with its sign preserved.
The user must ensure the value is a valid value for the range of the kind returned. If the processor cannot represent the result in the kind specified, the result is undefined.
If a is greater than zero, nint(a) has the value int(a+0.5).
If a is less than or equal to zero, nint(a) has the value int(a-0.5).
The result is the integer nearest a, or if there are two integers equally near a, the result is whichever such integer has the greater magnitude.
The result is undefined if it cannot be represented in the specified integer type.
program demo_nint implicit none integer,parameter :: dp=kind(0.0d0) real,allocatable :: in(:) integer,allocatable :: out(:) integer :: i real :: x4 real(kind=dp) :: x8 ! basic use x4 = 1.234E0 x8 = 4.721_dp print *, nint(x4), nint(-x4) print *, nint(x8), nint(-x8) ! elemental in = [ -2.7, -2.5, -2.2, -2.0, -1.5, -1.0, -0.5, -0.4, & & 0.0, & & +0.04, +0.5, +1.0, +1.5, +2.0, +2.2, +2.5, +2.7 ] out = nint(in) do i=1,size(in) write(*,*)in(i),out(i) enddo ! dusty corners ISSUES: block use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64 integer :: icheck ! make sure input is in range for the type returned write(*,*)'Range limits for typical KINDS:' write(*,'(1x,g0,1x,g0)') & & int8,huge(0_int8), & & int16,huge(0_int16), & & int32,huge(0_int32), & & int64,huge(0_int64) ! the standard does not require this to be an error . x8=12345.67e15 ! too big of a number icheck=selected_int_kind(ceiling(log10(x8))) write(*,*)'Any KIND big enough? ICHECK=',icheck print *, 'These are all wrong answers for ',x8 print *, nint(x8,kind=int8) print *, nint(x8,kind=int16) print *, nint(x8,kind=int32) print *, nint(x8,kind=int64) endblock ISSUES end program demo_nint
> 1 -1 > 5 -5 > -2.700000 -3 > -2.500000 -3 > -2.200000 -2 > -2.000000 -2 > -1.500000 -2 > -1.000000 -1 > -0.5000000 -1 > -0.4000000 0 > 0.0000000E+00 0 > 3.9999999E-02 0 > 0.5000000 1 > 1.000000 1 > 1.500000 2 > 2.000000 2 > 2.200000 2 > 2.500000 3 > 2.700000 3 > Range limits for typical KINDS: > 1 127 > 2 32767 > 4 2147483647 > 8 9223372036854775807 > Any KIND big enough? ICHECK= -1 > These are all wrong answers for 1.234566949990144E+019 > 0 > 0 > -2147483648 > -9223372036854775808
FORTRAN 77 , with KIND argument - Fortran 90
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
real(3) - [TYPE:NUMERIC] Convert to real type
result = real(x [,kind])
elemental real(kind=KIND) function real(x,KIND) TYPE(kind=**),intent(in) :: x integer(kind=**),intent(in),optional :: KIND
real(3) converts its argument x to a real type.
The real part of a complex value is returned. For complex values this is similar to the modern complex-part-designator %RE which also designates the real part of a complex value.
z=(3.0,4.0) ! if z is a complex value print *, z%re == real(z) ! these expressions are equivalent
program demo_real use,intrinsic :: iso_fortran_env, only : dp=>real64 implicit none complex :: zr = (1.0, 2.0) doubleprecision :: xd=huge(3.0d0) complex(kind=dp) :: zd=cmplx(4.0e0_dp,5.0e0_dp,kind=dp) print *, real(zr), aimag(zr) print *, dble(zd), aimag(zd) write(*,*)xd,real(xd,kind=kind(0.0d0)),dble(xd) end program demo_real
1.00000000 2.00000000 4.0000000000000000 5.0000000000000000 1.7976931348623157E+308 1.7976931348623157E+308 1.7976931348623157E+308
Fortran has strong support for complex values, including many intrinsics that take or produce complex values in addition to algebraic and logical expressions:
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
dble(3) - [TYPE:NUMERIC] Converstion to double precision real
result = dble(a)
elemental doubleprecision function dble(a) doubleprecision :: dble TYPE(kind=KIND),intent(in) :: a
dble(3) Converts a to double precision real type.
The return value is of type doubleprecision. For complex input, the returned value has the magnitude and sign of the real component of the input value.
program demo_dble implicit none real:: x = 2.18 integer :: i = 5 complex :: z = (2.3,1.14) print *, dble(x), dble(i), dble(z) end program demo_dble
2.1800000667572021 5.0000000000000000 2.2999999523162842
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
transfer(3) - [TYPE:MOLD] Transfer bit patterns
result = transfer(source, mold [,size] )
type(TYPE(kind=KIND)) function transfer(source,mold,size) type(TYPE(kind=KIND)),intent(in) :: source(..) type(TYPE(kind=KIND)),intent(in) :: mold(..) integer(kind=**),intent(in),optional :: size
transfer(3) copies the bitwise representation of source in memory into a variable or array of the same type and type parameters as mold.
This is approximately equivalent to the C concept of “casting” one type to another.
If size is absent but mold is an array (of any size or shape), the result is a one-dimensional array of the minimum length needed to contain the entirety of the bitwise representation of source.
If size is absent and mold is a scalar, the result is a scalar.
The result has the bit level representation of source.
If the bitwise representation of the result is longer than that of source, then the leading bits of the result correspond to those of source but any trailing bits are filled arbitrarily.
When the resulting bit representation does not correspond to a valid representation of a variable of the same type as mold, the results are undefined, and subsequent operations on the result cannot be guaranteed to produce sensible behavior. For example, it is possible to create logical variables for which var and .not. var both appear to be true.
program demo_transfer use,intrinsic :: iso_fortran_env, only : int32, real32 integer(kind=int32) :: i = 2143289344 real(kind=real32) :: x character(len=10) :: string character(len=1) :: chars(10) x=transfer(i, 1.0) ! prints "nan" on i686 ! the bit patterns are the same write(*,'(b0,1x,g0)')x,x ! create a NaN write(*,'(b0,1x,g0)')i,i ! a string to an array of characters string='abcdefghij' chars=transfer(string,chars) write(*,'(*("[",a,"]":,1x))')string write(*,'(*("[",a,"]":,1x))')chars end program demo_transfer
1111111110000000000000000000000 NaN 1111111110000000000000000000000 2143289344 [abcdefghij] [a] [b] [c] [d] [e] [f] [g] [h] [i] [j]
Joe Krahn: Fortran uses molding rather than casting.
Casting, as in C, is an in-place reinterpretation. A cast is a device that is built around an object to change its shape.
Fortran transfer(3) reinterprets data out-of-place. It can be considered molding rather than casting. A mold is a device that confers a shape onto an object placed into it.
The advantage of molding is that data is always valid in the context of the variable that holds it. For many cases, a decent compiler should optimize transfer(3) into a simple assignment.
There are disadvantages of this approach. It is problematic to define a union of data types because you must know the largest data object, which can vary by compiler or compile options. In many cases, an EQUIVALENCE would be far more effective, but Fortran Standards committees seem oblivious to the benefits of EQUIVALENCE when used sparingly.
fortran-lang intrinsic descriptions
logical(3) - [TYPE:LOGICAL] Conversion between kinds of logical values
result = logical(l [,kind])
elemental logical(kind=KIND) function logical(l,KIND) logical(kind=**),intent(in) :: l integer(kind=**),intent(in),optional :: KIND
logical(3) converts one kind of logical variable to another.
The return value is a logical value equal to l, with a kind corresponding to kind, or of the default logical kind if kind is not given.
Linux program demo_logical ! Access array containing the kind type parameter values supported by this ! compiler for entities of logical type use iso_fortran_env, only : logical_kinds implicit none integer :: i ! list kind values supported on this platform, which generally vary ! in storage size as alias declarations do i =1, size(logical_kinds) write(*,'(*(g0))')'integer,parameter :: boolean', & & logical_kinds(i),'=', logical_kinds(i) enddo end program demo_logical
> integer,parameter :: boolean1=1 > integer,parameter :: boolean2=2 > integer,parameter :: boolean4=4 > integer,parameter :: boolean8=8 > integer,parameter :: boolean16=16
Fortran 95 , related ISO_FORTRAN_ENV module - fortran 2009
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
kind(3) - [KIND:INQUIRY] Query kind of an entity
result = kind(x)
integer function kind(x) type(TYPE,kind=**),intent(in) :: x(..)
kind(x)(3) returns the kind value of the entity x.
The return value indicates the kind of the argument x.
Note that kinds are processor-dependent.
program demo_kind implicit none integer,parameter :: dc = kind(' ') integer,parameter :: dl = kind(.true.) print *, "The default character kind is ", dc print *, "The default logical kind is ", dl end program demo_kind
The default character kind is 1 The default logical kind is 4
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
out_of_range(3) - [TYPE:NUMERIC] Whether a value cannot be converted safely.
result = out_of_range (x, mold [, round])
elemental logical function(x, mold, round) TYPE,kind=KIND),intent(in) :: x TYPE,kind=KIND),intent(in) :: mold logical,intent(in),optional :: round
out_of_range(3) determines whether a value x can be converted safely to a real or integer variable the same type and kind as mold.
For example, if int8 is the kind value for an 8-bit binary integer type, out_of_range(-128.5, 0_int8) will have the value false and out_of_range(-128.5, 0_int8, .true.) will have the value .true. because the value will be truncated when converted to an integer and -128 is a representable value on a two’s complement machine in eight bits even though +128 is not.
From the standard:
Case (i): If mold is of type integer, and round is absent or present with the value false, the result is true if and only if the value of X is an IEEE infinity or NaN, or if the integer with largest magnitude that lies between zero and X inclusive is not representable by objects with the type and kind of mold.
Case (ii): If mold is of type integer, and round is present with the value true, the result is true if and only if the value of X is an IEEE infinity or NaN, or if the integer nearest X, or the integer of greater magnitude if two integers are equally near to X, is not representable by objects with the type and kind of mold.
Case (iii): Otherwise, the result is true if and only if the value of X is an IEEE infinity or NaN that is not supported by objects of the type and kind of mold, or if X is a finite number and the result of rounding the value of X (according to the IEEE rounding mode if appropriate) to the extended model for the kind of mold has magnitude larger than that of the largest finite number with the same sign as X that is representable by objects with the type and kind of mold.
mold is required to be a scalar because the only information taken from it is its type and kind. Allowing an array mold would require that it be conformable with x. round is scalar because allowing an array rounding mode would have severe performance difficulties on many processors.
program demo_out_of_range use, intrinsic :: iso_fortran_env, only : int8, int16, int32, int64 use, intrinsic :: iso_fortran_env, only : real32, real64, real128 implicit none integer :: i integer(kind=int8) :: i8, j8 ! compilers are not required to produce an error on out of range. ! here storing the default integers into 1-byte integers ! incorrectly can have unexpected results do i=127,130 i8=i j8=-i ! OUT_OF_RANGE(3f) can let you check if the value will fit write(*,*)i8,j8,' might have expected',i,-i, & & out_of_range( i,i8), & & out_of_range(-i,i8) enddo write(*,*) 'RANGE IS ',-1-huge(0_int8),'TO',huge(0_int8) ! the real -128.5 is truncated to -128 and is in range write(*,*) out_of_range ( -128.5, 0_int8) ! false ! the real -128.5 is rounded to -129 and is not in range write(*,*) out_of_range ( -128.5, 0_int8, .true.) ! true end program demo_out_of_range
> 127 -127 might have expected 127 -127 F F > -128 -128 might have expected 128 -128 T F > -127 127 might have expected 129 -129 T T > -126 126 might have expected 130 -130 T T > RANGE IS -128 TO 127 > F > T
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
selected_char_kind(3) - [KIND] Select character kind such as “Unicode”
result = selected_char_kind(name)
integer function selected_char_kind(name) character(len=*),intent(in) :: name
selected_char_kind(3) returns a kind parameter value for the character set named name.
If a name is not supported, -1 is returned. Otherwise the result is a value equal to that kind type parameter value.
The list of supported names is processor-dependent except for “DEFAULT”.
The NAME is interpreted without respect to case or trailing blanks.
Linux program demo_selected_char_kind use iso_fortran_env implicit none intrinsic date_and_time,selected_char_kind ! set some aliases for common character kinds ! as the numbers can vary from platform to platform integer, parameter :: default = selected_char_kind ("default") integer, parameter :: ascii = selected_char_kind ("ascii") integer, parameter :: ucs4 = selected_char_kind ('ISO_10646') integer, parameter :: utf8 = selected_char_kind ('utf-8') ! assuming ASCII and UCS4 are supported (ie. not equal to -1) ! define some string variables character(len=26, kind=ascii ) :: alphabet character(len=30, kind=ucs4 ) :: hello_world character(len=30, kind=ucs4 ) :: string write(*,*)'ASCII ',& & merge('Supported ','Not Supported',ascii /= -1) write(*,*)'ISO_10646 ',& & merge('Supported ','Not Supported',ucs4 /= -1) write(*,*)'UTF-8 ',& & merge('Supported ','Not Supported',utf8 /= -1) if(default.eq.ascii)then write(*,*)'ASCII is the default on this processor' endif ! for constants the kind precedes the value, somewhat like a ! BOZ constant alphabet = ascii_"abcdefghijklmnopqrstuvwxyz" write (*,*) alphabet hello_world = ucs4_'Hello World and Ni Hao -- ' & // char (int (z'4F60'), ucs4) & // char (int (z'597D'), ucs4) ! an encoding option is required on OPEN for non-default I/O if(ucs4 /= -1 )then open (output_unit, encoding='UTF-8') write (*,*) trim (hello_world) else write (*,*) 'cannot use utf-8' endif call create_date_string(string) write (*,*) trim (string) contains ! The following produces a Japanese date stamp. subroutine create_date_string(string) intrinsic date_and_time,selected_char_kind integer,parameter :: ucs4 = selected_char_kind("ISO_10646") character(len=1,kind=ucs4),parameter :: & nen = char(int( z'5e74' ),ucs4), & ! year gatsu = char(int( z'6708' ),ucs4), & ! month nichi = char(int( z'65e5' ),ucs4) ! day character(len= *, kind= ucs4) string integer values(8) call date_and_time(values=values) write(string,101) values(1),nen,values(2),gatsu,values(3),nichi 101 format(*(i0,a)) end subroutine create_date_string end program demo_selected_char_kind
The results are very processor-dependent
> ASCII Supported > ISO_10646 Supported > UTF-8 Not Supported > ASCII is the default on this processor > abcdefghijklmnopqrstuvwxyz > Hello World and Ni Hao -- 你好 > 2022年10月15日