File: /nfs/home/0/users/jenkins/mfix.git/model/remove_comment.f

1     !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2     !                                                                      !
3     !  Subroutine Name: REMOVE_COMMENT (LINE, LSTART, MAXCOL)              !
4     !  Author: P.Nicoletti                                Date: -unknown-  !
5     !  Reviewer: J.Musser                                 Date: 19-Sept-13 !
6     !                                                                      !
7     !  Purpose: Remove comments                                            !
8     !                                                                      !
9     !           Example:  IN: > LINE ::  "MW_g( 3 ) =  32.0 ! Oxygen"      !
10     !                     OUT > LINE ::  "MW_g( 3 ) =  32.0         "      !
11     !                                                                      !
12     !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
13           SUBROUTINE REMOVE_COMMENT(LINE, LSTART, MAXCOL)
14     
15           IMPLICIT NONE
16     
17     ! Passed Variables: Dummy argument format required by ODEPACK.
18     !---------------------------------------------------------------------//
19     ! Input data line
20           CHARACTER(len=*), intent(INOUT) :: LINE
21     !Start of comments
22           INTEGER, intent(IN) :: LSTART
23     ! Maximum column of input data line to search
24           INTEGER, intent(IN) :: MAXCOL
25     
26     ! Local Variables:
27     !---------------------------------------------------------------------//
28     ! Loop index
29           INTEGER :: L
30     
31           DO L = LSTART, MAXCOL
32              LINE(L:L) = ' '
33           END DO
34     
35           RETURN
36           END SUBROUTINE REMOVE_COMMENT
37     
38     
39     !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
40     !                                                                      !
41     !  Subroutine Name: REMOVE_PAR_BLANKS (LINE)                           !
42     !  Author: J.Musser                                   Date: 19-Spt-13  !
43     !                                                                      !
44     !  Purpose: Remove blanks within parentheses. This addition was need   !
45     !           to resolve portability issues on ALCF machines.            !
46     !                                                                      !
47     !           Example:  IN: > LINE :: "MW_g( 3 ) = 32.0"                 !
48     !                     OUT > LINE :: "MW_g(3)   = 32.0"                 !
49     !                                                                      !
50     !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
51           SUBROUTINE REMOVE_PAR_BLANKS(LINE)
52     
53           IMPLICIT NONE
54     
55     ! Passed Variables: Dummy argument format required by ODEPACK.
56     !---------------------------------------------------------------------//
57     ! Input data line
58           CHARACTER(len=*), intent(INOUT) :: LINE
59     
60     ! Local Variables:
61     !---------------------------------------------------------------------//
62     ! Loop index
63           INTEGER :: L
64     ! Search positions
65           INTEGER :: POS, lP, rP
66     ! Flag for space replacement
67           LOGICAL :: searchRight
68     ! Internal search flag
69           LOGICAL :: replace
70     ! Debug flag
71           LOGICAL, parameter :: verbose = .FALSE.
72     
73     
74     ! Exit if the string is empty.
75           IF(len_trim(LINE) == 0) return
76     
77     ! Get the position of the first left parentheses.
78           lP = index(LINE,"(")
79     
80     ! Initialize the loop flag.
81           searchRight = (lP /= 0)
82           DO WHILE(searchRight)
83     ! Find the position of the first right parentheses.
84             rP = lP + index(LINE(lP:),")")
85     ! Check if there are any blank spaces:
86             IF(index(LINE(lP:rP-1)," ") /= 0) THEN
87     
88                IF(verbose) WRITE(*,"(3X,'Removing spaces: ')")
89                IF(verbose) WRITE(*,"(5X,'Before: ',A)") trim(LINE)
90     
91     ! Initialize the loop flag and sub-string position.
92                 replace = .TRUE.
93                 POS = lP+1
94                 DO WHILE(replace)
95     ! If a blank is located, slide all entries to the left one position and
96     ! add a blank to the end of the sub-string.
97                    IF(LINE(POS:POS) == " ") THEN
98                       DO L=POS,rP-2
99                          LINE(L:L) = LINE(L+1:L+1)
100                       ENDDO
101                       LINE(rP-1:rP-1) = " "
102                    ELSE
103     ! If there the character is not a space, increment character index.
104                       POS = POS + 1
105                    ENDIF
106     ! Exit if all that remains in the sub-string are empty spaces.
107                    replace = (len_trim(LINE(POS:rP-1)) /= 0)
108                 ENDDO
109                IF(verbose) WRITE(*,"(5X,'After:  ',A)") trim(LINE)
110             ENDIF
111     ! Check if there is another set of parentheses.
112             lP = rP + index(LINE(rP+1:),"(")
113     ! Exit if no addition parentheses pair is found.
114             searchRight = (lP.NE.rP)
115           ENDDO
116     
117           return
118           END SUBROUTINE REMOVE_PAR_BLANKS
119