Statistiques
| Révision :

root / src / CleanString.f90 @ 12

Historique | Voir | Annoter | Télécharger (2,57 ko)

1 5 pfleura2
    SUBROUTINE CleanString(String,CleanStr)
2 5 pfleura2
! This subroutine cleans a string, that is: it removes some characters
3 5 pfleura2
! from it that are in CleanString input variable
4 5 pfleura2
5 12 pfleura2
!----------------------------------------------------------------------
6 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
7 12 pfleura2
!  Centre National de la Recherche Scientifique,
8 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
9 12 pfleura2
!
10 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
11 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
12 12 pfleura2
!
13 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
14 12 pfleura2
!  Contact: optnpath@gmail.com
15 12 pfleura2
!
16 12 pfleura2
! This file is part of "Opt'n Path".
17 12 pfleura2
!
18 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
19 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
20 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
21 12 pfleura2
!  or (at your option) any later version.
22 12 pfleura2
!
23 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
24 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
25 12 pfleura2
!
26 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
27 12 pfleura2
!  GNU Affero General Public License for more details.
28 12 pfleura2
!
29 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
30 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
31 12 pfleura2
!
32 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
33 12 pfleura2
! for commercial licensing opportunities.
34 12 pfleura2
!----------------------------------------------------------------------
35 12 pfleura2
36 5 pfleura2
      Use VarTypes
37 5 pfleura2
38 5 pfleura2
      IMPLICIT NONE
39 5 pfleura2
40 5 pfleura2
! Input Variables
41 5 pfleura2
      CHARACTER(*), INTENT(INOUT) :: String
42 5 pfleura2
      CHARACTER(*), INTENT(IN) :: CleanStr
43 5 pfleura2
44 8 pfleura2
      INTEGER(KINT) :: I
45 12 pfleura2
      LOGICAL :: Debug
46 12 pfleura2
47 12 pfleura2
  INTERFACE
48 12 pfleura2
     function valid(string) result (isValid)
49 12 pfleura2
       CHARACTER(*), intent(in) :: string
50 12 pfleura2
       logical                  :: isValid
51 12 pfleura2
     END function VALID
52 12 pfleura2
53 12 pfleura2
  end INTERFACE
54 12 pfleura2
55 12 pfleura2
56 12 pfleura2
      Debug=Valid("CleanString")
57 5 pfleura2
58 12 pfleura2
      if (debug) Call header("Entering CleanString")
59 12 pfleura2
60 12 pfleura2
      if (debug) THEN
61 12 pfleura2
         WRITE(*,*) "String:",String,"*END*"
62 12 pfleura2
         WRITE(*,*) "CleanStr:",CleanStr,"*END*"
63 12 pfleura2
      END IF
64 5 pfleura2
65 12 pfleura2
      I=Scan(TRIM(String),CleanStr)
66 12 pfleura2
      DO WHILE ((I/=0).AND.(I<=LEN(TRIM(String))))
67 5 pfleura2
         String=String(1:I-1) // String (I+1:)
68 5 pfleura2
         I=Scan(String,CleanStr)
69 12 pfleura2
         if (debug) THEN
70 12 pfleura2
            WRITE(*,*) "String:",String,"*END*",I,Len(TRIM(String))
71 12 pfleura2
            WRITE(*,*) "TRIMString:",TRIM(String),"*END*"
72 12 pfleura2
         END IF
73 12 pfleura2
74 5 pfleura2
      END DO
75 5 pfleura2
76 12 pfleura2
      if (debug) THEN
77 12 pfleura2
         WRITE(*,*) "String:",String,"*END*"
78 12 pfleura2
      END IF
79 12 pfleura2
80 12 pfleura2
      if (debug) Call header("Exiting CleanString")
81 12 pfleura2
82 5 pfleura2
    END SUBROUTINE CleanString