Statistiques
| Révision :

root / src / Warning.f90

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

1
    SUBROUTINE Warning(routine, msg, file, line, unit)
2

    
3
! This routine prints a warning message and goes on
4
! Inspired  from Die in Siesta 3.1 
5

    
6
!----------------------------------------------------------------------
7
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
8
!  Centre National de la Recherche Scientifique,
9
!  Université Claude Bernard Lyon 1. All rights reserved.
10
!
11
!  This work is registered with the Agency for the Protection of Programs 
12
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
13
!
14
!  Authors: P. Fleurat-Lessard, P. Dayal
15
!  Contact: optnpath@gmail.com
16
!
17
! This file is part of "Opt'n Path".
18
!
19
!  "Opt'n Path" is free software: you can redistribute it and/or modify
20
!  it under the terms of the GNU Affero General Public License as
21
!  published by the Free Software Foundation, either version 3 of the License,
22
!  or (at your option) any later version.
23
!
24
!  "Opt'n Path" is distributed in the hope that it will be useful,
25
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
26
!
27
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
28
!  GNU Affero General Public License for more details.
29
!
30
!  You should have received a copy of the GNU Affero General Public License
31
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
32
!
33
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
34
! for commercial licensing opportunities.
35
!----------------------------------------------------------------------
36

    
37
      Use VarTypes
38
      Use io_module
39

    
40
      implicit none
41

    
42

    
43
  INTERFACE
44
     function valid(string) result (isValid)
45
       CHARACTER(*), intent(in) :: string
46
       logical                  :: isValid
47
     END function VALID
48

    
49
  END INTERFACE
50
!--------------------------------------------------------------- Input Variables
51
      character(len=*), intent(in)           :: routine, msg
52
      character(len=*), intent(in), optional :: file
53
      integer(KINT), intent(in), optional      :: line, unit
54

    
55
!--------------------------------------------------------------- Local Variables
56
      integer(KINT)                            :: warning_unit
57

    
58
      LOGICAL ::  Debug
59

    
60
!------------------------------------------------------------------------- BEGIN
61
      debug=valid('warning')
62

    
63
      if (debug) Call Header('Entering Warning')
64
      if (PRESENT(unit)) then
65
        warning_unit = unit
66
      else
67
        warning_unit = IOOUT
68
      endif
69

    
70
      write(warning_unit,'(a)') '*************************************************************'
71
      write(warning_unit,'(a)') '* WARNING *'
72
      write(warning_unit,'(a)') ' '
73
      write(warning_unit,'(3a)') TRIM(routine), ': ', TRIM(msg)
74
      write(warning_unit,'(a)') ' '
75
      if (PRESENT(file)) write(warning_unit,'(5x,2a)') 'File: ', file
76
      if (PRESENT(line)) write(warning_unit,'(5x,a,i5)') 'Line: ', line
77
      write(warning_unit,'(a)') '*************************************************************'
78

    
79
      if (debug) Call Header('Exiting Warning')
80

    
81
    END SUBROUTINE warning
82