Statistiques
| Révision :

root / src / NoString.f90 @ 12

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

1 10 pfleura2
      SUBROUTINE noString(String)
2 10 pfleura2
3 10 pfleura2
! This subroutine suppress the content of string variable
4 10 pfleura2
! strings can be delimited by ' or "
5 10 pfleura2
! example:
6 10 pfleura2
! Progexe='./siesta', -> Progexe=,
7 10 pfleura2
8 12 pfleura2
!----------------------------------------------------------------------
9 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
10 12 pfleura2
!  Centre National de la Recherche Scientifique,
11 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
12 12 pfleura2
!
13 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
14 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
15 12 pfleura2
!
16 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
17 12 pfleura2
!  Contact: optnpath@gmail.com
18 12 pfleura2
!
19 12 pfleura2
! This file is part of "Opt'n Path".
20 12 pfleura2
!
21 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
22 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
23 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
24 12 pfleura2
!  or (at your option) any later version.
25 12 pfleura2
!
26 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
27 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
28 12 pfleura2
!
29 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
30 12 pfleura2
!  GNU Affero General Public License for more details.
31 12 pfleura2
!
32 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
33 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
34 12 pfleura2
!
35 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
36 12 pfleura2
! for commercial licensing opportunities.
37 12 pfleura2
!----------------------------------------------------------------------
38 12 pfleura2
39 10 pfleura2
        use VarTypes
40 10 pfleura2
41 10 pfleura2
        IMPLICIT NONE
42 10 pfleura2
43 10 pfleura2
        CHARACTER(*), INTENT(INOUT) :: String
44 10 pfleura2
        CHARACTER(VLCHARS) :: Result
45 10 pfleura2
        INTEGER(KINT) :: i
46 10 pfleura2
        CHARACTER(2), PARAMETER :: Del='"' // "'"
47 10 pfleura2
48 10 pfleura2
        DO WHILE (scan(String,Del)/=0)
49 10 pfleura2
           I=Scan(String,Del)
50 10 pfleura2
           Result=String(:I-1)
51 10 pfleura2
           String=String(I+1:)
52 10 pfleura2
           I=Scan(String,Del)
53 10 pfleura2
           String=TRIM(Result) // String(I+1:)
54 10 pfleura2
        END DO
55 10 pfleura2
56 10 pfleura2
      END SUBROUTINE NoString