Statistiques
| Révision :

root / src / Set_FileDelim.f90

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

1 12 pfleura2
    SUBROUTINE Set_FileDelim
2 12 pfleura2
!----------------------------------------------------------------------
3 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
4 12 pfleura2
!  Centre National de la Recherche Scientifique,
5 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
6 12 pfleura2
!
7 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
8 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
9 12 pfleura2
!
10 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
11 12 pfleura2
!  Contact: optnpath@gmail.com
12 12 pfleura2
!
13 12 pfleura2
! This file is part of "Opt'n Path".
14 12 pfleura2
!
15 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
16 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
17 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
18 12 pfleura2
!  or (at your option) any later version.
19 12 pfleura2
!
20 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
21 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
22 12 pfleura2
!
23 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
24 12 pfleura2
!  GNU Affero General Public License for more details.
25 12 pfleura2
!
26 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
27 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
28 12 pfleura2
!
29 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
30 12 pfleura2
! for commercial licensing opportunities.
31 12 pfleura2
!----------------------------------------------------------------------
32 12 pfleura2
33 12 pfleura2
      Use Io_module
34 12 pfleura2
35 12 pfleura2
      LOGICAL :: Debug
36 12 pfleura2
37 12 pfleura2
38 12 pfleura2
  INTERFACE
39 12 pfleura2
     function valid(string) result (isValid)
40 12 pfleura2
       CHARACTER(*), intent(in) :: string
41 12 pfleura2
       logical                  :: isValid
42 12 pfleura2
     END function VALID
43 12 pfleura2
  END INTERFACE
44 12 pfleura2
45 12 pfleura2
46 12 pfleura2
      Debug=valid("setfiledelim").OR.valid("set_filedelim")
47 12 pfleura2
      If (debug) Call Header('Entering Set_FileDelim')
48 12 pfleura2
      CALL getenv('DELIMITER',FileDelim)
49 12 pfleura2
      if (FileDelim==" ")  THEN
50 12 pfleura2
         If (debug) WRITE(*,*)" Filedelim empty. Setting it to default"
51 12 pfleura2
         FileDelim="/"
52 12 pfleura2
      END if
53 12 pfleura2
54 12 pfleura2
      If (debug) Call Header('EXIT Set_FileDelim')
55 12 pfleura2
56 12 pfleura2
    END SUBROUTINE Set_FileDelim