SFEMaNS  version 4.1 (work in progress)
Reference documentation for SFEMaNS
 All Classes Files Functions Variables Groups Pages
chaine_caractere_par.f90
Go to the documentation of this file.
1 !
2 !Authors: Jean-Luc Guermond, Lugi Quartapelle, Copyright 1994
3 !
5 
7 
8 CONTAINS
9 
10  FUNCTION last_c_leng (len_str, string) RESULT (leng)
11 
12  IMPLICIT NONE
13 
14  INTEGER, INTENT(IN) :: len_str
15  CHARACTER (LEN=len_str), INTENT(IN) :: string
16  INTEGER :: leng
17 
18  INTEGER :: i
19 
20  leng = len_str
21 
22  DO i=1,len_str
23  IF ( string(i:i) .EQ. ' ' ) THEN
24  leng = i-1; EXIT
25  ENDIF
26  ENDDO
27 
28  END FUNCTION last_c_leng
29 
30  !========================================================================
31 
32  FUNCTION eval_blank(len_str, string) RESULT (leng)
33 
34  IMPLICIT NONE
35 
36  INTEGER, INTENT(IN) :: len_str
37  CHARACTER (LEN=len_str), INTENT(IN) :: string
38  INTEGER :: leng
39 
40  INTEGER :: i
41 
42  leng = len_str
43 
44  DO i=1,len_str
45  IF ( string(i:i) .NE. ' ' ) THEN
46  leng = i; EXIT
47  ENDIF
48  ENDDO
49 
50  END FUNCTION eval_blank
51 
52  !========================================================================
53 
54  FUNCTION start_of_string (string) RESULT (start)
55 
56  IMPLICIT NONE
57 
58  CHARACTER (LEN=*), INTENT(IN) :: string
59  INTEGER :: start
60 
61  INTEGER :: i
62 
63  start = 1
64 
65  DO i = 1, len(string)
66  IF ( string(i:i) .NE. ' ' ) THEN
67  start = i; EXIT
68  ENDIF
69  ENDDO
70 
71  END FUNCTION start_of_string
72 
73  !========================================================================
74 
75  FUNCTION last_of_string (string) RESULT (last)
76 
77  IMPLICIT NONE
78 
79  CHARACTER (LEN=*), INTENT(IN) :: string
80  INTEGER :: last
81 
82  INTEGER :: i
83 
84  last = 1
85 
86  DO i = len(string), 1, -1
87  IF ( string(i:i) .NE. ' ' ) THEN
88  last = i; EXIT
89  ENDIF
90  ENDDO
91 
92  END FUNCTION last_of_string
93  !========================================================================
94 
95  SUBROUTINE read_until(unit, string)
96  USE my_util
97  IMPLICIT NONE
98  INTEGER, PARAMETER :: long_max=128
99  INTEGER, INTENT(IN) :: unit
100  CHARACTER(LEN=*), INTENT(IN) :: string
101  CHARACTER(len=long_max) :: control
102  INTEGER :: d_end, d_start
103 
104  rewind(unit)
105  DO WHILE (.true.)
106  READ(unit,'(64A)',err=11,end=22) control
107  d_start = start_of_string(control)
108  d_end = last_of_string(control)
109  IF (control(d_start:d_end)==string) RETURN
110  END DO
111 
112 11 CALL error_petsc(' Error reading data file at '//string)
113 22 CALL error_petsc(' Data string '//string//' not found ')
114  END SUBROUTINE read_until
115 
116  SUBROUTINE find_string(unit, string, okay)
117  USE my_util
118  IMPLICIT NONE
119  INTEGER, PARAMETER :: long_max=128
120  INTEGER, INTENT(IN) :: unit
121  CHARACTER(LEN=*), INTENT(IN) :: string
122  CHARACTER(len=long_max) :: control
123  INTEGER :: d_end, d_start
124  LOGICAL :: okay
125 
126  okay = .true.
127  rewind(unit)
128  DO WHILE (.true.)
129  READ(unit,'(64A)',err=11,end=22) control
130  d_start = start_of_string(control)
131  d_end = last_of_string(control)
132  IF (control(d_start:d_end)==string) RETURN
133  END DO
134 
135 11 CALL error_petsc(' Error reading data file at '//string)
136 22 okay = .false.
137  RETURN
138 
139  END SUBROUTINE find_string
140  !========================================================================
141 
142 END MODULE chaine_caractere
integer function eval_blank(len_str, string)
integer function, public start_of_string(string)
integer function, public last_of_string(string)
subroutine read_until(unit, string)
subroutine find_string(unit, string, okay)
integer function, public last_c_leng(len_str, string)
subroutine error_petsc(string)
Definition: my_util.f90:15