Statistiques
| Révision :

root / src / Warning.f90

Historique | Voir | Annoter | Télécharger (2,95 ko)

1 12 pfleura2
    SUBROUTINE Warning(routine, msg, file, line, unit)
2 12 pfleura2
3 5 pfleura2
! This routine prints a warning message and goes on
4 5 pfleura2
! Inspired  from Die in Siesta 3.1
5 5 pfleura2
6 12 pfleura2
!----------------------------------------------------------------------
7 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
8 12 pfleura2
!  Centre National de la Recherche Scientifique,
9 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
10 12 pfleura2
!
11 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
12 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
13 12 pfleura2
!
14 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
15 12 pfleura2
!  Contact: optnpath@gmail.com
16 12 pfleura2
!
17 12 pfleura2
! This file is part of "Opt'n Path".
18 12 pfleura2
!
19 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
20 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
21 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
22 12 pfleura2
!  or (at your option) any later version.
23 12 pfleura2
!
24 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
25 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
26 12 pfleura2
!
27 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
28 12 pfleura2
!  GNU Affero General Public License for more details.
29 12 pfleura2
!
30 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
31 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
32 12 pfleura2
!
33 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
34 12 pfleura2
! for commercial licensing opportunities.
35 12 pfleura2
!----------------------------------------------------------------------
36 12 pfleura2
37 5 pfleura2
      Use VarTypes
38 5 pfleura2
      Use io_module
39 5 pfleura2
40 5 pfleura2
      implicit none
41 5 pfleura2
42 5 pfleura2
43 5 pfleura2
  INTERFACE
44 5 pfleura2
     function valid(string) result (isValid)
45 5 pfleura2
       CHARACTER(*), intent(in) :: string
46 5 pfleura2
       logical                  :: isValid
47 5 pfleura2
     END function VALID
48 5 pfleura2
49 5 pfleura2
  END INTERFACE
50 5 pfleura2
!--------------------------------------------------------------- Input Variables
51 5 pfleura2
      character(len=*), intent(in)           :: routine, msg
52 5 pfleura2
      character(len=*), intent(in), optional :: file
53 5 pfleura2
      integer(KINT), intent(in), optional      :: line, unit
54 5 pfleura2
55 5 pfleura2
!--------------------------------------------------------------- Local Variables
56 5 pfleura2
      integer(KINT)                            :: warning_unit
57 5 pfleura2
58 5 pfleura2
      LOGICAL ::  Debug
59 5 pfleura2
60 5 pfleura2
!------------------------------------------------------------------------- BEGIN
61 5 pfleura2
      debug=valid('warning')
62 5 pfleura2
63 5 pfleura2
      if (debug) Call Header('Entering Warning')
64 5 pfleura2
      if (PRESENT(unit)) then
65 5 pfleura2
        warning_unit = unit
66 5 pfleura2
      else
67 5 pfleura2
        warning_unit = IOOUT
68 5 pfleura2
      endif
69 5 pfleura2
70 5 pfleura2
      write(warning_unit,'(a)') '*************************************************************'
71 5 pfleura2
      write(warning_unit,'(a)') '* WARNING *'
72 5 pfleura2
      write(warning_unit,'(a)') ' '
73 5 pfleura2
      write(warning_unit,'(3a)') TRIM(routine), ': ', TRIM(msg)
74 5 pfleura2
      write(warning_unit,'(a)') ' '
75 5 pfleura2
      if (PRESENT(file)) write(warning_unit,'(5x,2a)') 'File: ', file
76 5 pfleura2
      if (PRESENT(line)) write(warning_unit,'(5x,a,i5)') 'Line: ', line
77 5 pfleura2
      write(warning_unit,'(a)') '*************************************************************'
78 5 pfleura2
79 5 pfleura2
      if (debug) Call Header('Exiting Warning')
80 5 pfleura2
81 5 pfleura2
    END SUBROUTINE warning