Statistiques
| Révision :

root / src / SearchInput.f90 @ 12

Historique | Voir | Annoter | Télécharger (3,08 ko)

1 12 pfleura2
    FUNCTION SearchInput(Input,String,Line,Clean)  Result(Found)
2 5 pfleura2
! This function search a string in an input block
3 5 pfleura2
4 12 pfleura2
!----------------------------------------------------------------------
5 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
6 12 pfleura2
!  Centre National de la Recherche Scientifique,
7 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
8 12 pfleura2
!
9 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
10 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
11 12 pfleura2
!
12 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
13 12 pfleura2
!  Contact: optnpath@gmail.com
14 12 pfleura2
!
15 12 pfleura2
! This file is part of "Opt'n Path".
16 12 pfleura2
!
17 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
18 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
19 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
20 12 pfleura2
!  or (at your option) any later version.
21 12 pfleura2
!
22 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
23 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
24 12 pfleura2
!
25 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
26 12 pfleura2
!  GNU Affero General Public License for more details.
27 12 pfleura2
!
28 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
29 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
30 12 pfleura2
!
31 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
32 12 pfleura2
! for commercial licensing opportunities.
33 12 pfleura2
!----------------------------------------------------------------------
34 12 pfleura2
35 5 pfleura2
      Use VarTypes
36 5 pfleura2
      Use io_module
37 5 pfleura2
38 5 pfleura2
      implicit none
39 5 pfleura2
40 5 pfleura2
41 5 pfleura2
  INTERFACE
42 5 pfleura2
     function valid(string) result (isValid)
43 5 pfleura2
       CHARACTER(*), intent(in) :: string
44 5 pfleura2
       logical                  :: isValid
45 5 pfleura2
     END function VALID
46 5 pfleura2
  END INTERFACE
47 5 pfleura2
48 5 pfleura2
! Input
49 5 pfleura2
      TYPE (Input_line), POINTER, INTENT(IN) :: Input
50 5 pfleura2
      CHARACTER(*), INTENT(IN) :: String
51 5 pfleura2
      CHARACTER(*), OPTIONAL, INTENT(IN) :: Clean
52 5 pfleura2
53 5 pfleura2
! Output
54 5 pfleura2
      TYPE (Input_line), POINTER, INTENT(OUT) :: Line
55 5 pfleura2
56 5 pfleura2
      LOGICAL :: Found, Debug
57 5 pfleura2
      CHARACTER(LCHARS) :: LineUp,UpString
58 5 pfleura2
59 5 pfleura2
      Debug=valid('SearchInput')
60 5 pfleura2
61 5 pfleura2
      if (debug) Call header('Entering SearchInput')
62 5 pfleura2
63 5 pfleura2
      UpString=String
64 5 pfleura2
      Call upcase(UpString)
65 5 pfleura2
66 5 pfleura2
      if (debug) WRITE(*,*) 'Looking for:',Upstring
67 5 pfleura2
68 5 pfleura2
      IF (present(Clean)) THEN
69 5 pfleura2
         Call CleanString(UpString,Clean)
70 5 pfleura2
      END IF
71 5 pfleura2
72 5 pfleura2
      if (debug) WRITE(*,*) 'Looking for clean:',TRIM(Upstring)
73 5 pfleura2
74 5 pfleura2
      Line => Input
75 5 pfleura2
      LineUp=Line%line
76 5 pfleura2
      Call UpCase(LineUp)
77 5 pfleura2
      IF (present(Clean)) THEN
78 5 pfleura2
         Call CleanString(LineUp,Clean)
79 5 pfleura2
      END IF
80 5 pfleura2
      if (debug) WRITE(*,*) 'Comparing with:',Trim(LineUp)
81 5 pfleura2
82 5 pfleura2
      Found=(INDEX(LineUp,TRIM(UpString))>0)
83 5 pfleura2
      DO WHILE (Associated(Line%next).AND.(.NOT.Found))
84 5 pfleura2
         Line => Line%Next
85 5 pfleura2
         LineUp=Line%line
86 5 pfleura2
         Call UpCase(LineUp)
87 5 pfleura2
         IF (present(Clean)) THEN
88 5 pfleura2
            Call CleanString(LineUp,Clean)
89 5 pfleura2
         END IF
90 5 pfleura2
         if (debug) WRITE(*,*) 'Comparing with:',Trim(LineUp)
91 5 pfleura2
92 5 pfleura2
         Found=(INDEX(LineUp,TRIM(UpString))>0)
93 5 pfleura2
      END DO
94 5 pfleura2
95 5 pfleura2
      If (.NOT.Found) Nullify(Line)
96 5 pfleura2
97 5 pfleura2
      if (debug) Call header('Exiting SearchInput')
98 5 pfleura2
99 5 pfleura2
      Return
100 5 pfleura2
!--------------------------------------------------------------------------- END
101 5 pfleura2
    END FUNCTION SearchInput