Statistiques
| Révision :

root / src / CleanString.f90

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

1
    SUBROUTINE CleanString(String,CleanStr)
2
! This subroutine cleans a string, that is: it removes some characters
3
! from it that are in CleanString input variable
4

    
5
!----------------------------------------------------------------------
6
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
7
!  Centre National de la Recherche Scientifique,
8
!  Université Claude Bernard Lyon 1. All rights reserved.
9
!
10
!  This work is registered with the Agency for the Protection of Programs 
11
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
12
!
13
!  Authors: P. Fleurat-Lessard, P. Dayal
14
!  Contact: optnpath@gmail.com
15
!
16
! This file is part of "Opt'n Path".
17
!
18
!  "Opt'n Path" is free software: you can redistribute it and/or modify
19
!  it under the terms of the GNU Affero General Public License as
20
!  published by the Free Software Foundation, either version 3 of the License,
21
!  or (at your option) any later version.
22
!
23
!  "Opt'n Path" is distributed in the hope that it will be useful,
24
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
25
!
26
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
27
!  GNU Affero General Public License for more details.
28
!
29
!  You should have received a copy of the GNU Affero General Public License
30
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
31
!
32
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
33
! for commercial licensing opportunities.
34
!----------------------------------------------------------------------
35

    
36
      Use VarTypes
37

    
38
      IMPLICIT NONE
39

    
40
! Input Variables
41
      CHARACTER(*), INTENT(INOUT) :: String
42
      CHARACTER(*), INTENT(IN) :: CleanStr
43

    
44
      INTEGER(KINT) :: I
45
      LOGICAL :: Debug
46

    
47
  INTERFACE
48
     function valid(string) result (isValid)
49
       CHARACTER(*), intent(in) :: string
50
       logical                  :: isValid
51
     END function VALID
52

    
53
  end INTERFACE
54
  
55

    
56
      Debug=Valid("CleanString")
57
      
58
      if (debug) Call header("Entering CleanString")
59
         
60
      if (debug) THEN
61
         WRITE(*,*) "String:",String,"*END*"
62
         WRITE(*,*) "CleanStr:",CleanStr,"*END*"
63
      END IF
64

    
65
      I=Scan(TRIM(String),CleanStr)
66
      DO WHILE ((I/=0).AND.(I<=LEN(TRIM(String))))
67
         String=String(1:I-1) // String (I+1:)
68
         I=Scan(String,CleanStr)
69
         if (debug) THEN
70
            WRITE(*,*) "String:",String,"*END*",I,Len(TRIM(String))
71
            WRITE(*,*) "TRIMString:",TRIM(String),"*END*"
72
         END IF
73

    
74
      END DO
75

    
76
      if (debug) THEN
77
         WRITE(*,*) "String:",String,"*END*"
78
      END IF
79

    
80
      if (debug) Call header("Exiting CleanString")
81

    
82
    END SUBROUTINE CleanString