Statistiques
| Révision :

root / src / valid.f90

Historique | Voir | Annoter | Télécharger (5,4 ko)

1
      function valid(string) result (isValid)
2

    
3
! This function returns true or false depending on the string you give as a parameter
4
! Its purpose is to centralize the debugging flags into only one external file
5
! so that debugging can be turned on or off easily at runtime.
6
! (basically as it was done in ADF...
7
! except that my version is much more basic (much much much more !) )
8

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

    
40
      use Io_module
41

    
42
      IMPLICIT NONE
43

    
44
      interface
45
         subroutine upcase(string)
46
           character(*), intent(inout) :: string
47
         end subroutine upcase
48
      end interface
49

    
50
      CHARACTER(*), intent(in) :: string
51
      logical                  :: isValid
52
      INTEGER(4), PARAMETER :: NMax=500
53

    
54
      CHARACTER(64),save :: List(NMax)
55
      LOGICAL,save       :: Value(NMax)
56
      LOGICAL,save       :: TInit=.False.
57
      CHARACTER(132) :: LINE, ValTMP, LString
58
      LOGICAL       :: ValueTMP, Found
59
      LOGICAL,SAVE       :: Tall=.False., FValidFile, ValAll
60
      INTEGER(4) :: ios, i, j
61
      INTEGER(4), SAVE ::  NEntries
62
      LOGICAL, SAVE :: Debug=.FALSE.
63

    
64
      IF (.not.TInit) THEN
65
         NEntries=0
66
         TInit=.TRUE.
67
         INQUIRE(FILE=DebugFile,EXIST=FValidFile)
68
         if (FValidFile) THEN
69
            OPEN(IOTMP,File=DebugFile,IOSTAT=ios)
70

    
71
! The file exists so we will read it !
72
            DO While (ios==0)
73
               READ(IOTMP,'(A)',ERR=999,END=999) LINE
74
               if (Debug) WRITE(*,*) 'LINE READ',trim(Line)
75
               if (ios==0) THEN
76
                  Line=AdjustL(Line)
77
                  if (debug) WRITE(*,*) 'LINE ADJ',trim(Line)
78
                  call Upcase(Line)
79
                  if (debug) WRITE(*,*) 'LINE UP',trim(Line)
80
                  if (Line(1:1)/='#') THEN
81
! This is not a comment, we go on
82
                     i=index(Line,' ')
83
! We take the first word, it will be our value
84
                     ValTMP=Line(1:i-1)
85
                     j=len_trim(line)
86
                     Line=adjustL((Line(i+1:j)))
87
                     if (debug) WRITE(*,*) 'VALID INIT ',NEntries,trim(ValTMP), &
88
        ' - ',trim(Line)
89
                     if (ValTMP(1:1)=='.') ValTmp=ValTMP(2:)
90
                     if (ValTMP(1:1)=='F') ValueTMP=.False.
91
                     if (ValTMP(1:1)=='T') ValueTMP=.True.
92
                     if (Line(1:1)=='*') THEN
93
                        ValAll=ValueTMP
94
                        TAll=.True.
95
                     ELSE
96
                        if (Tall) ValueTMP=ValAll
97
                        NEntries=NEntries+1
98
                        Value(NEntries)=ValueTMP
99
                        Line=AdjustL(Line)
100
                        List(NEntries)=Line(1:64)
101
                     END IF
102
                  END IF
103
               END IF
104
            END DO
105
 999     CONTINUE
106
         CLOSE(IOTMP)
107
         if (debug) THEN
108
            WRITE(*,*) "DBG Valid, " // Trim(DebugFile) // "read, with " &
109
                 ,NEntries
110
            DO I=1,NEntries
111
               WRITE(*,*) List(I),Value(I)
112
            END DO
113
         END IF
114
       END IF
115
      END IF
116

    
117
      IF (.NOT.FValidFile) THEN
118
         isValid=.FALSE.
119
         Return
120
      END IF
121

    
122
! The INIT file has been read !
123
      LString=trim(adjustL(String))
124
      Call UPcase(LString)
125
      Found=.false.
126
      Do I=1,NEntries
127
         if (trim(List(I)).eq.trim(LString)) THEN
128
            Found=.TRUE.
129
            isValid=Value(I)
130
!            WRITE(*,*) 'zoeurezoiru'
131
         END IF
132
!         WRITE(*,*) I,' : ',trim(list(I)),' - ',trim(LSTRING),' *'
133
      END DO
134

    
135
!      WRITE(*,*) 'Found:',Found,'isval',isvalid
136
!      WRITE(*,*) 'Debug is ',isvalid," for ",Trim(LString)
137

    
138
      if (.NOT.Found) THEN
139
         IF (Tall) THEN
140
            if (debug) THEN
141
               WRITE(*,*) 'The option ',String,' is not recognized.'
142
               WRITE(*,*) 'Assigning value ',ValAll
143
            END IF
144
            isValid=ValAll
145
         ELSE
146
            isValid=.FALSE.
147
         END IF
148
         NEntries=Nentries+1
149
         If (NEntries>NMax) THEN
150
            WRITE(*,*) 'Error: NEntries > NMax in Valid ! recompile'
151
            STOP
152
         END IF
153
         List(Nentries)=Trim(LString)
154
         Value(Nentries)=Valall
155
      END IF
156

    
157
      END function valid