[Clang] Make OpenMP offloading consistently use the bound architecture (#125135)
[llvm-project.git] / flang / module / iso_fortran_env.f90
blob3729b95a339f302bbdd04925b1d90c4010f0a1b8
1 !===-- module/iso_fortran_env.f90 ------------------------------------------===!
3 ! Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4 ! See https://llvm.org/LICENSE.txt for license information.
5 ! SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
7 !===------------------------------------------------------------------------===!
9 ! See Fortran 2023, subclause 16.10.2
11 #include '../include/flang/Runtime/magic-numbers.h'
13 module iso_fortran_env
15 use __fortran_builtins, only: &
16 event_type => __builtin_event_type, &
17 notify_type => __builtin_notify_type, &
18 lock_type => __builtin_lock_type, &
19 team_type => __builtin_team_type, &
20 atomic_int_kind => __builtin_atomic_int_kind, &
21 atomic_logical_kind => __builtin_atomic_logical_kind, &
22 compiler_options => __builtin_compiler_options, &
23 compiler_version => __builtin_compiler_version
25 use iso_fortran_env_impl, only: &
26 selectedInt8, selectedInt16, selectedInt32, selectedInt64, selectedInt128, &
27 safeInt8, safeInt16, safeInt32, safeInt64, safeInt128, &
28 int8, int16, int32, int64, int128, &
29 selectedUInt8, selectedUInt16, selectedUInt32, selectedUInt64, selectedUInt128, &
30 safeUInt8, safeUInt16, safeUInt32, safeUInt64, safeUInt128, &
31 uint8, uint16, uint32, uint64, uint128, &
32 logical8, logical16, logical32, logical64, &
33 selectedReal16, selectedBfloat16, selectedReal32, &
34 selectedReal64, selectedReal80, selectedReal64x2, &
35 selectedReal128, &
36 safeReal16, safeBfloat16, safeReal32, &
37 safeReal64, safeReal80, safeReal64x2, &
38 safeReal128, &
39 real16, bfloat16, real32, real64, &
40 real80, real64x2, real128, &
41 integer_kinds => __builtin_integer_kinds, &
42 real_kinds => __builtin_real_kinds, &
43 logical_kinds => __builtin_logical_kinds
45 implicit none
46 private
48 public :: event_type, notify_type, lock_type, team_type, &
49 atomic_int_kind, atomic_logical_kind, compiler_options, &
50 compiler_version
52 integer, parameter :: &
53 selectedASCII = selected_char_kind('ASCII'), &
54 selectedUCS_2 = selected_char_kind('UCS-2'), &
55 selectedUnicode = selected_char_kind('ISO_10646')
56 integer, parameter, public :: character_kinds(*) = [ &
57 pack([selectedASCII], selectedASCII >= 0), &
58 pack([selectedUCS_2], selectedUCS_2 >= 0), &
59 pack([selectedUnicode], selectedUnicode >= 0)]
61 public :: selectedInt8, selectedInt16, selectedInt32, selectedInt64, selectedInt128, &
62 safeInt8, safeInt16, safeInt32, safeInt64, safeInt128, &
63 int8, int16, int32, int64, int128
65 public :: selectedUInt8, selectedUInt16, selectedUInt32, selectedUInt64, selectedUInt128, &
66 safeUInt8, safeUInt16, safeUInt32, safeUInt64, safeUInt128, &
67 uint8, uint16, uint32, uint64, uint128
69 public :: logical8, logical16, logical32, logical64
71 public :: selectedReal16, selectedBfloat16, selectedReal32, &
72 selectedReal64, selectedReal80, selectedReal64x2, &
73 selectedReal128, &
74 safeReal16, safeBfloat16, safeReal32, &
75 safeReal64, safeReal80, safeReal64x2, &
76 safeReal128, &
77 real16, bfloat16, real32, real64, &
78 real80, real64x2, real128
80 public :: integer_kinds, real_kinds, logical_kinds
82 integer, parameter, public :: current_team = -1, &
83 initial_team = -2, &
84 parent_team = -3
86 integer, parameter, public :: character_storage_size = 8
87 integer, parameter, public :: file_storage_size = 8
89 intrinsic :: __builtin_numeric_storage_size
90 ! This value depends on any -fdefault-integer-N and -fdefault-real-N
91 ! compiler options that are active when the module file is read.
92 integer, parameter, public :: numeric_storage_size = &
93 __builtin_numeric_storage_size()
95 ! From Runtime/magic-numbers.h:
96 integer, parameter, public :: &
97 output_unit = FORTRAN_DEFAULT_OUTPUT_UNIT, &
98 input_unit = FORTRAN_DEFAULT_INPUT_UNIT, &
99 error_unit = FORTRAN_ERROR_UNIT, &
100 iostat_end = FORTRAN_RUNTIME_IOSTAT_END, &
101 iostat_eor = FORTRAN_RUNTIME_IOSTAT_EOR, &
102 iostat_inquire_internal_unit = FORTRAN_RUNTIME_IOSTAT_INQUIRE_INTERNAL_UNIT, &
103 stat_failed_image = FORTRAN_RUNTIME_STAT_FAILED_IMAGE, &
104 stat_locked = FORTRAN_RUNTIME_STAT_LOCKED, &
105 stat_locked_other_image = FORTRAN_RUNTIME_STAT_LOCKED_OTHER_IMAGE, &
106 stat_stopped_image = FORTRAN_RUNTIME_STAT_STOPPED_IMAGE, &
107 stat_unlocked = FORTRAN_RUNTIME_STAT_UNLOCKED, &
108 stat_unlocked_failed_image = FORTRAN_RUNTIME_STAT_UNLOCKED_FAILED_IMAGE
110 end module iso_fortran_env