Statistiques
| Révision :

root / src / NoString.f90

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

1
      SUBROUTINE noString(String)
2

    
3
! This subroutine suppress the content of string variable
4
! strings can be delimited by ' or "
5
! example:
6
! Progexe='./siesta', -> Progexe=,
7

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

    
39
        use VarTypes
40

    
41
        IMPLICIT NONE
42

    
43
        CHARACTER(*), INTENT(INOUT) :: String
44
        CHARACTER(VLCHARS) :: Result
45
        INTEGER(KINT) :: i
46
        CHARACTER(2), PARAMETER :: Del='"' // "'"
47

    
48
        DO WHILE (scan(String,Del)/=0)
49
           I=Scan(String,Del)
50
           Result=String(:I-1)
51
           String=String(I+1:)
52
           I=Scan(String,Del)
53
           String=TRIM(Result) // String(I+1:)
54
        END DO
55

    
56
      END SUBROUTINE NoString
57