[RISCV] Add shrinkwrap test cases showing gaps in current impl
[llvm-project.git] / flang / module / iso_fortran_env.f90
blob4e575b422c2a04ede985c9ca16e036163b4f2e57
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 logical8, logical16, logical32, logical64, &
30 selectedReal16, selectedBfloat16, selectedReal32, &
31 selectedReal64, selectedReal80, selectedReal64x2, &
32 selectedReal128, &
33 safeReal16, safeBfloat16, safeReal32, &
34 safeReal64, safeReal80, safeReal64x2, &
35 safeReal128, &
36 real16, bfloat16, real32, real64, &
37 real80, real64x2, real128, &
38 integer_kinds => __builtin_integer_kinds, &
39 real_kinds => __builtin_real_kinds, &
40 logical_kinds => __builtin_logical_kinds
42 implicit none
43 private
45 public :: event_type, notify_type, lock_type, team_type, &
46 atomic_int_kind, atomic_logical_kind, compiler_options, &
47 compiler_version
49 integer, parameter :: &
50 selectedASCII = selected_char_kind('ASCII'), &
51 selectedUCS_2 = selected_char_kind('UCS-2'), &
52 selectedUnicode = selected_char_kind('ISO_10646')
53 integer, parameter, public :: character_kinds(*) = [ &
54 pack([selectedASCII], selectedASCII >= 0), &
55 pack([selectedUCS_2], selectedUCS_2 >= 0), &
56 pack([selectedUnicode], selectedUnicode >= 0)]
58 public :: selectedInt8, selectedInt16, selectedInt32, selectedInt64, selectedInt128, &
59 safeInt8, safeInt16, safeInt32, safeInt64, safeInt128, &
60 int8, int16, int32, int64, int128
62 public :: logical8, logical16, logical32, logical64
64 public :: selectedReal16, selectedBfloat16, selectedReal32, &
65 selectedReal64, selectedReal80, selectedReal64x2, &
66 selectedReal128, &
67 safeReal16, safeBfloat16, safeReal32, &
68 safeReal64, safeReal80, safeReal64x2, &
69 safeReal128, &
70 real16, bfloat16, real32, real64, &
71 real80, real64x2, real128
73 public :: integer_kinds, real_kinds, logical_kinds
75 integer, parameter, public :: current_team = -1, &
76 initial_team = -2, &
77 parent_team = -3
79 integer, parameter, public :: character_storage_size = 8
80 integer, parameter, public :: file_storage_size = 8
82 intrinsic :: __builtin_numeric_storage_size
83 ! This value depends on any -fdefault-integer-N and -fdefault-real-N
84 ! compiler options that are active when the module file is read.
85 integer, parameter, public :: numeric_storage_size = &
86 __builtin_numeric_storage_size()
88 ! From Runtime/magic-numbers.h:
89 integer, parameter, public :: &
90 output_unit = FORTRAN_DEFAULT_OUTPUT_UNIT, &
91 input_unit = FORTRAN_DEFAULT_INPUT_UNIT, &
92 error_unit = FORTRAN_ERROR_UNIT, &
93 iostat_end = FORTRAN_RUNTIME_IOSTAT_END, &
94 iostat_eor = FORTRAN_RUNTIME_IOSTAT_EOR, &
95 iostat_inquire_internal_unit = FORTRAN_RUNTIME_IOSTAT_INQUIRE_INTERNAL_UNIT, &
96 stat_failed_image = FORTRAN_RUNTIME_STAT_FAILED_IMAGE, &
97 stat_locked = FORTRAN_RUNTIME_STAT_LOCKED, &
98 stat_locked_other_image = FORTRAN_RUNTIME_STAT_LOCKED_OTHER_IMAGE, &
99 stat_stopped_image = FORTRAN_RUNTIME_STAT_STOPPED_IMAGE, &
100 stat_unlocked = FORTRAN_RUNTIME_STAT_UNLOCKED, &
101 stat_unlocked_failed_image = FORTRAN_RUNTIME_STAT_UNLOCKED_FAILED_IMAGE
103 end module iso_fortran_env