/[lmdze]/trunk/IOIPSL/errioipsl.f90
ViewVC logotype

Contents of /trunk/IOIPSL/errioipsl.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 328 - (show annotations)
Thu Jun 13 14:40:06 2019 UTC (4 years, 11 months ago) by guez
File size: 1200 byte(s)
Change all `.f` suffixes to `.f90`. (The opposite was done in revision
82.)  Because of change of philosopy in GNUmakefile: we already had a
rewritten rule for `.f`, so it does not make the makefile longer to
replace it by a rule for `.f90`. And it spares us options of
makedepf90 and of the compiler. Also we prepare the way for a simpler
`CMakeLists.txt`.

1 MODULE errioipsl
2
3 ! From errioipsl.f90, version 2.0, 2004/04/05 14:47:47
4
5 IMPLICIT NONE
6
7 CONTAINS
8
9 SUBROUTINE histerr(plev, pcname, pstr1, pstr2, pstr3)
10
11 INTEGER, intent(in):: plev
12 !- plev : Category of message to be reported to the user
13 !- 1 = Note to the user
14 !- 2 = Warning to the user
15 !- 3 = Fatal error
16
17 CHARACTER(LEN=*), intent(in):: pcname
18 ! name of subroutine which has called histerr
19
20 CHARACTER(LEN=*), intent(in):: pstr1, pstr2, pstr3
21 ! strings containing the explanations to the user
22
23 ! Local:
24 CHARACTER(LEN=30), DIMENSION(3) :: pemsg = &
25 (/ "NOTE TO THE USER FROM ROUTINE ", &
26 "WARNING FROM ROUTINE ", &
27 "FATAL ERROR FROM ROUTINE " /)
28
29 !---------------------------------------------------------------------
30
31 IF ((plev >= 1).AND.(plev <= 3)) THEN
32 print '(A, " ", A)', TRIM(pemsg(plev)), TRIM(pcname)
33 print '(" --> ", a)', pstr1
34 print '(" --> ", a)', pstr2
35 print '(" --> ", a)', pstr3
36 ENDIF
37 IF (plev == 3) THEN
38 print *, 'Fatal error from IOIPSL'
39 STOP 1
40 ENDIF
41
42 END SUBROUTINE histerr
43
44 END MODULE errioipsl

  ViewVC Help
Powered by ViewVC 1.1.21