Statistiques
| Révision :

root / src / upcase.f90 @ 12

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

1 1 pfleura2
      SUBROUTINE Upcase(String)
2 1 pfleura2
3 1 pfleura2
! This subroutine converts a string into its Upcase
4 1 pfleura2
! version
5 1 pfleura2
6 12 pfleura2
!----------------------------------------------------------------------
7 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
8 12 pfleura2
!  Centre National de la Recherche Scientifique,
9 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
10 12 pfleura2
!
11 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
12 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
13 12 pfleura2
!
14 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
15 12 pfleura2
!  Contact: optnpath@gmail.com
16 12 pfleura2
!
17 12 pfleura2
! This file is part of "Opt'n Path".
18 12 pfleura2
!
19 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
20 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
21 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
22 12 pfleura2
!  or (at your option) any later version.
23 12 pfleura2
!
24 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
25 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
26 12 pfleura2
!
27 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
28 12 pfleura2
!  GNU Affero General Public License for more details.
29 12 pfleura2
!
30 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
31 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
32 12 pfleura2
!
33 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
34 12 pfleura2
! for commercial licensing opportunities.
35 12 pfleura2
!----------------------------------------------------------------------
36 12 pfleura2
37 2 pfleura2
        IMPLICIT NONE
38 2 pfleura2
39 1 pfleura2
        integer, parameter :: KINT = kind(1)
40 1 pfleura2
41 1 pfleura2
        CHARACTER(*), INTENT(INOUT) :: String
42 5 pfleura2
        INTEGER(KINT) :: i,ic, length,Del,ia,iz
43 5 pfleura2
44 5 pfleura2
! We define some variables
45 5 pfleura2
! By doing this, we do not depend on the ASCII coding of the
46 5 pfleura2
! characters
47 5 pfleura2
        DEL = IACHAR('a') - IACHAR('A')
48 5 pfleura2
        ia=IACHAR('a')
49 5 pfleura2
        iz=IACHAR('z')
50 5 pfleura2
51 1 pfleura2
        length=len_trim(string)
52 1 pfleura2
        DO I=1, length
53 1 pfleura2
          ic=ICHAR(String(i:i))
54 5 pfleura2
          if ((ic.ge.ia).and.(ic.le.iz)) ic=ic-DEL
55 1 pfleura2
          String(i:i)=ACHAR(ic)
56 1 pfleura2
        END DO
57 1 pfleura2
58 1 pfleura2
        RETURN
59 1 pfleura2
      END SUBROUTINE Upcase