Statistiques
| Révision :

root / src / InString.f90 @ 6

Historique | Voir | Annoter | Télécharger (1,91 ko)

1 5 pfleura2
! This function compares two strings
2 5 pfleura2
! Input, 5 variables out of which 3 optionals
3 5 pfleura2
! Line: the line to search in
4 5 pfleura2
! String: the stuff to search in Line
5 5 pfleura2
! Case [optional]: if present and true, the case is respected
6 5 pfleura2
! Clean [optional]: if present, Line is cleaned
7 5 pfleura2
! Back [optional] if present and true, the string is seach backwards
8 5 pfleura2
9 5 pfleura2
    FUNCTION InString(Line,String,Case,Clean,Back)  Result(Pos)
10 5 pfleura2
11 5 pfleura2
      Use VarTypes
12 5 pfleura2
      Use io_module
13 5 pfleura2
14 5 pfleura2
      implicit none
15 5 pfleura2
16 5 pfleura2
17 5 pfleura2
  INTERFACE
18 5 pfleura2
     function valid(string) result (isValid)
19 5 pfleura2
       CHARACTER(*), intent(in) :: string
20 5 pfleura2
       logical                  :: isValid
21 5 pfleura2
     END function VALID
22 5 pfleura2
  END INTERFACE
23 5 pfleura2
24 5 pfleura2
! Input
25 5 pfleura2
      CHARACTER(*), INTENT(IN) :: Line
26 5 pfleura2
      CHARACTER(*), INTENT(IN) :: String
27 5 pfleura2
      LOGICAL, OPTIONAL, INTENT(IN) :: Case
28 5 pfleura2
      LOGICAL, OPTIONAL, INTENT(IN) :: Back
29 5 pfleura2
      CHARACTER(*), OPTIONAL, INTENT(IN) :: Clean
30 5 pfleura2
31 5 pfleura2
! Output
32 5 pfleura2
! the position of String in Line (the first one) unless Back is present
33 5 pfleura2
      INTEGER(KINT) :: Pos
34 5 pfleura2
35 5 pfleura2
      CHARACTER(LCHARS) :: LineUp,UpString
36 5 pfleura2
      LOGICAL :: LCase, LBack, debug
37 5 pfleura2
38 5 pfleura2
      Debug=valid('InString')
39 5 pfleura2
40 5 pfleura2
      if (debug) Call header('Entering InString')
41 5 pfleura2
42 5 pfleura2
      if (present(Case)) THEN
43 5 pfleura2
         LCase=Case
44 5 pfleura2
      else
45 5 pfleura2
         LCase=.FALSE.
46 5 pfleura2
      END IF
47 5 pfleura2
48 5 pfleura2
      if (present(Back)) THEN
49 5 pfleura2
         LBack=Back
50 5 pfleura2
      ELSE
51 5 pfleura2
         LBack=.FALSE.
52 5 pfleura2
      END IF
53 5 pfleura2
54 5 pfleura2
      UpString=String
55 5 pfleura2
      if (.NOT.LCase) Call upcase(UpString)
56 5 pfleura2
57 5 pfleura2
      if (debug) WRITE(*,*) 'Looking for:',Upstring
58 5 pfleura2
59 5 pfleura2
      IF (present(Clean)) THEN
60 5 pfleura2
         Call CleanString(UpString,Clean)
61 5 pfleura2
      END IF
62 5 pfleura2
63 5 pfleura2
      if (debug) WRITE(*,*) 'Looking for clean:',TRIM(Upstring)
64 5 pfleura2
65 5 pfleura2
      LineUp=Line
66 5 pfleura2
      if (.NOT.LCase) Call UpCase(LineUp)
67 5 pfleura2
      IF (present(Clean)) THEN
68 5 pfleura2
         Call CleanString(LineUp,Clean)
69 5 pfleura2
      END IF
70 5 pfleura2
      if (debug) WRITE(*,*) 'Comparing with:',Trim(LineUp)
71 5 pfleura2
72 5 pfleura2
      Pos=INDEX(LineUp,TRIM(UpString),Back=LBack)
73 5 pfleura2
74 5 pfleura2
      if (debug) Call header('Exiting InString')
75 5 pfleura2
76 5 pfleura2
      Return
77 5 pfleura2
78 5 pfleura2
    END FUNCTION InString