xref: /netbsd-src/external/gpl3/gcc/dist/libgfortran/ieee/ieee_exceptions.F90 (revision b1e838363e3c6fc78a55519254d99869742dd33c)
1181254a7Smrg!    Implementation of the IEEE_EXCEPTIONS standard intrinsic module
2*b1e83836Smrg!    Copyright (C) 2013-2022 Free Software Foundation, Inc.
3181254a7Smrg!    Contributed by Francois-Xavier Coudert <fxcoudert@gcc.gnu.org>
4181254a7Smrg!
5181254a7Smrg! This file is part of the GNU Fortran runtime library (libgfortran).
6181254a7Smrg!
7181254a7Smrg! Libgfortran is free software; you can redistribute it and/or
8181254a7Smrg! modify it under the terms of the GNU General Public
9181254a7Smrg! License as published by the Free Software Foundation; either
10181254a7Smrg! version 3 of the License, or (at your option) any later version.
11181254a7Smrg!
12181254a7Smrg! Libgfortran is distributed in the hope that it will be useful,
13181254a7Smrg! but WITHOUT ANY WARRANTY; without even the implied warranty of
14181254a7Smrg! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15181254a7Smrg! GNU General Public License for more details.
16181254a7Smrg!
17181254a7Smrg! Under Section 7 of GPL version 3, you are granted additional
18181254a7Smrg! permissions described in the GCC Runtime Library Exception, version
19181254a7Smrg! 3.1, as published by the Free Software Foundation.
20181254a7Smrg!
21181254a7Smrg! You should have received a copy of the GNU General Public License and
22181254a7Smrg! a copy of the GCC Runtime Library Exception along with this program;
23181254a7Smrg! see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
24181254a7Smrg! <http://www.gnu.org/licenses/>.  */
25181254a7Smrg
26181254a7Smrg#include "config.h"
27181254a7Smrg#include "kinds.inc"
28181254a7Smrg#include "c99_protos.inc"
29181254a7Smrg#include "fpu-target.inc"
30181254a7Smrg
31181254a7Smrgmodule IEEE_EXCEPTIONS
32181254a7Smrg
33181254a7Smrg  implicit none
34181254a7Smrg  private
35181254a7Smrg
36181254a7Smrg! Derived types and named constants
37181254a7Smrg
38181254a7Smrg  type, public :: IEEE_FLAG_TYPE
39181254a7Smrg    private
40181254a7Smrg    integer :: hidden
41181254a7Smrg  end type
42181254a7Smrg
43181254a7Smrg  type(IEEE_FLAG_TYPE), parameter, public :: &
44181254a7Smrg    IEEE_INVALID        = IEEE_FLAG_TYPE(GFC_FPE_INVALID), &
45181254a7Smrg    IEEE_OVERFLOW       = IEEE_FLAG_TYPE(GFC_FPE_OVERFLOW), &
46181254a7Smrg    IEEE_DIVIDE_BY_ZERO = IEEE_FLAG_TYPE(GFC_FPE_ZERO), &
47181254a7Smrg    IEEE_UNDERFLOW      = IEEE_FLAG_TYPE(GFC_FPE_UNDERFLOW), &
48181254a7Smrg    IEEE_INEXACT        = IEEE_FLAG_TYPE(GFC_FPE_INEXACT)
49181254a7Smrg
50181254a7Smrg  type(IEEE_FLAG_TYPE), parameter, public :: &
51181254a7Smrg    IEEE_USUAL(3) = [ IEEE_OVERFLOW, IEEE_DIVIDE_BY_ZERO, IEEE_INVALID ], &
52181254a7Smrg    IEEE_ALL(5)   = [ IEEE_USUAL, IEEE_UNDERFLOW, IEEE_INEXACT ]
53181254a7Smrg
54181254a7Smrg  type, public :: IEEE_STATUS_TYPE
55181254a7Smrg    private
56181254a7Smrg    character(len=GFC_FPE_STATE_BUFFER_SIZE) :: hidden
57181254a7Smrg  end type
58181254a7Smrg
59181254a7Smrg  interface IEEE_SUPPORT_FLAG
60181254a7Smrg    module procedure IEEE_SUPPORT_FLAG_4, &
61181254a7Smrg                     IEEE_SUPPORT_FLAG_8, &
62181254a7Smrg#ifdef HAVE_GFC_REAL_10
63181254a7Smrg                     IEEE_SUPPORT_FLAG_10, &
64181254a7Smrg#endif
65181254a7Smrg#ifdef HAVE_GFC_REAL_16
66181254a7Smrg                     IEEE_SUPPORT_FLAG_16, &
67181254a7Smrg#endif
68181254a7Smrg                     IEEE_SUPPORT_FLAG_NOARG
69181254a7Smrg  end interface IEEE_SUPPORT_FLAG
70181254a7Smrg
71181254a7Smrg  public :: IEEE_SUPPORT_FLAG, IEEE_SUPPORT_HALTING
72181254a7Smrg  public :: IEEE_SET_HALTING_MODE, IEEE_GET_HALTING_MODE
73181254a7Smrg  public :: IEEE_SET_FLAG, IEEE_GET_FLAG
74181254a7Smrg  public :: IEEE_SET_STATUS, IEEE_GET_STATUS
75181254a7Smrg
76181254a7Smrgcontains
77181254a7Smrg
78181254a7Smrg! Saving and restoring floating-point status
79181254a7Smrg
80181254a7Smrg  subroutine IEEE_GET_STATUS (STATUS_VALUE)
81181254a7Smrg    implicit none
82181254a7Smrg    type(IEEE_STATUS_TYPE), intent(out) :: STATUS_VALUE
83181254a7Smrg
84181254a7Smrg    interface
85181254a7Smrg      subroutine helper(ptr) &
86181254a7Smrg          bind(c, name="_gfortrani_get_fpu_state")
87181254a7Smrg        use, intrinsic :: iso_c_binding, only : c_char
88181254a7Smrg        character(kind=c_char) :: ptr(*)
89181254a7Smrg      end subroutine
90181254a7Smrg    end interface
91181254a7Smrg
92181254a7Smrg    call helper(STATUS_VALUE%hidden)
93181254a7Smrg  end subroutine
94181254a7Smrg
95181254a7Smrg  subroutine IEEE_SET_STATUS (STATUS_VALUE)
96181254a7Smrg    implicit none
97181254a7Smrg    type(IEEE_STATUS_TYPE), intent(in) :: STATUS_VALUE
98181254a7Smrg
99181254a7Smrg    interface
100181254a7Smrg      subroutine helper(ptr) &
101181254a7Smrg          bind(c, name="_gfortrani_set_fpu_state")
102181254a7Smrg        use, intrinsic :: iso_c_binding, only : c_char
103181254a7Smrg        character(kind=c_char) :: ptr(*)
104181254a7Smrg      end subroutine
105181254a7Smrg    end interface
106181254a7Smrg
107181254a7Smrg    call helper(STATUS_VALUE%hidden)
108181254a7Smrg  end subroutine
109181254a7Smrg
110181254a7Smrg! Getting and setting flags
111181254a7Smrg
112181254a7Smrg  elemental subroutine IEEE_GET_FLAG (FLAG, FLAG_VALUE)
113181254a7Smrg    implicit none
114181254a7Smrg    type(IEEE_FLAG_TYPE), intent(in) :: FLAG
115181254a7Smrg    logical, intent(out) :: FLAG_VALUE
116181254a7Smrg
117181254a7Smrg    interface
118181254a7Smrg      pure integer function helper() &
119181254a7Smrg        bind(c, name="_gfortrani_get_fpu_except_flags")
120181254a7Smrg      end function
121181254a7Smrg    end interface
122181254a7Smrg
123181254a7Smrg    FLAG_VALUE = (IAND(helper(), FLAG%hidden) /= 0)
124181254a7Smrg  end subroutine
125181254a7Smrg
126181254a7Smrg  elemental subroutine IEEE_SET_FLAG (FLAG, FLAG_VALUE)
127181254a7Smrg    implicit none
128181254a7Smrg    type(IEEE_FLAG_TYPE), intent(in) :: FLAG
129181254a7Smrg    logical, intent(in) :: FLAG_VALUE
130181254a7Smrg
131181254a7Smrg    interface
132181254a7Smrg      pure subroutine helper(set, clear) &
133181254a7Smrg          bind(c, name="_gfortrani_set_fpu_except_flags")
134181254a7Smrg        integer, intent(in), value :: set, clear
135181254a7Smrg      end subroutine
136181254a7Smrg    end interface
137181254a7Smrg
138181254a7Smrg    if (FLAG_VALUE) then
139181254a7Smrg      call helper(FLAG%hidden, 0)
140181254a7Smrg    else
141181254a7Smrg      call helper(0, FLAG%hidden)
142181254a7Smrg    end if
143181254a7Smrg  end subroutine
144181254a7Smrg
145181254a7Smrg! Querying and changing the halting mode
146181254a7Smrg
147181254a7Smrg  elemental subroutine IEEE_GET_HALTING_MODE (FLAG, HALTING)
148181254a7Smrg    implicit none
149181254a7Smrg    type(IEEE_FLAG_TYPE), intent(in) :: FLAG
150181254a7Smrg    logical, intent(out) :: HALTING
151181254a7Smrg
152181254a7Smrg    interface
153181254a7Smrg      pure integer function helper() &
154181254a7Smrg          bind(c, name="_gfortrani_get_fpu_trap_exceptions")
155181254a7Smrg      end function
156181254a7Smrg    end interface
157181254a7Smrg
158181254a7Smrg    HALTING = (IAND(helper(), FLAG%hidden) /= 0)
159181254a7Smrg  end subroutine
160181254a7Smrg
161181254a7Smrg  elemental subroutine IEEE_SET_HALTING_MODE (FLAG, HALTING)
162181254a7Smrg    implicit none
163181254a7Smrg    type(IEEE_FLAG_TYPE), intent(in) :: FLAG
164181254a7Smrg    logical, intent(in) :: HALTING
165181254a7Smrg
166181254a7Smrg    interface
167181254a7Smrg      pure subroutine helper(trap, notrap) &
168181254a7Smrg          bind(c, name="_gfortrani_set_fpu_trap_exceptions")
169181254a7Smrg        integer, intent(in), value :: trap, notrap
170181254a7Smrg      end subroutine
171181254a7Smrg    end interface
172181254a7Smrg
173181254a7Smrg    if (HALTING) then
174181254a7Smrg      call helper(FLAG%hidden, 0)
175181254a7Smrg    else
176181254a7Smrg      call helper(0, FLAG%hidden)
177181254a7Smrg    end if
178181254a7Smrg  end subroutine
179181254a7Smrg
180181254a7Smrg! Querying support
181181254a7Smrg
182181254a7Smrg  pure logical function IEEE_SUPPORT_HALTING (FLAG)
183181254a7Smrg    implicit none
184181254a7Smrg    type(IEEE_FLAG_TYPE), intent(in) :: FLAG
185181254a7Smrg
186181254a7Smrg    interface
187181254a7Smrg      pure integer function helper(flag) &
188181254a7Smrg          bind(c, name="_gfortrani_support_fpu_trap")
189181254a7Smrg        integer, intent(in), value :: flag
190181254a7Smrg      end function
191181254a7Smrg    end interface
192181254a7Smrg
193181254a7Smrg    IEEE_SUPPORT_HALTING = (helper(FLAG%hidden) /= 0)
194181254a7Smrg  end function
195181254a7Smrg
196181254a7Smrg  pure logical function IEEE_SUPPORT_FLAG_NOARG (FLAG)
197181254a7Smrg    implicit none
198181254a7Smrg    type(IEEE_FLAG_TYPE), intent(in) :: FLAG
199181254a7Smrg
200181254a7Smrg    interface
201181254a7Smrg      pure integer function helper(flag) &
202181254a7Smrg          bind(c, name="_gfortrani_support_fpu_flag")
203181254a7Smrg        integer, intent(in), value :: flag
204181254a7Smrg      end function
205181254a7Smrg    end interface
206181254a7Smrg
207181254a7Smrg    IEEE_SUPPORT_FLAG_NOARG = (helper(FLAG%hidden) /= 0)
208181254a7Smrg  end function
209181254a7Smrg
210181254a7Smrg  pure logical function IEEE_SUPPORT_FLAG_4 (FLAG, X) result(res)
211181254a7Smrg    implicit none
212181254a7Smrg    type(IEEE_FLAG_TYPE), intent(in) :: FLAG
213181254a7Smrg    real(kind=4), intent(in) :: X
214181254a7Smrg    res = IEEE_SUPPORT_FLAG_NOARG(FLAG)
215181254a7Smrg  end function
216181254a7Smrg
217181254a7Smrg  pure logical function IEEE_SUPPORT_FLAG_8 (FLAG, X) result(res)
218181254a7Smrg    implicit none
219181254a7Smrg    type(IEEE_FLAG_TYPE), intent(in) :: FLAG
220181254a7Smrg    real(kind=8), intent(in) :: X
221181254a7Smrg    res = IEEE_SUPPORT_FLAG_NOARG(FLAG)
222181254a7Smrg  end function
223181254a7Smrg
224181254a7Smrg#ifdef HAVE_GFC_REAL_10
225181254a7Smrg  pure logical function IEEE_SUPPORT_FLAG_10 (FLAG, X) result(res)
226181254a7Smrg    implicit none
227181254a7Smrg    type(IEEE_FLAG_TYPE), intent(in) :: FLAG
228181254a7Smrg    real(kind=10), intent(in) :: X
229181254a7Smrg    res = IEEE_SUPPORT_FLAG_NOARG(FLAG)
230181254a7Smrg  end function
231181254a7Smrg#endif
232181254a7Smrg
233181254a7Smrg#ifdef HAVE_GFC_REAL_16
234181254a7Smrg  pure logical function IEEE_SUPPORT_FLAG_16 (FLAG, X) result(res)
235181254a7Smrg    implicit none
236181254a7Smrg    type(IEEE_FLAG_TYPE), intent(in) :: FLAG
237181254a7Smrg    real(kind=16), intent(in) :: X
238181254a7Smrg    res = IEEE_SUPPORT_FLAG_NOARG(FLAG)
239181254a7Smrg  end function
240181254a7Smrg#endif
241181254a7Smrg
242181254a7Smrgend module IEEE_EXCEPTIONS
243