Statistiques
| Révision :

root / src / Read_geom.f90

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

1
SUBROUTINE Read_Geom(input)
2

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

    
34
  Use VarTypes
35
  Use Path_module, only : NGeomI
36
  Use Io_module
37

    
38
  IMPLICIT NONE
39

    
40

    
41
  CHARACTER(32), INTENT(IN) :: input    
42

    
43
  LOGICAL :: Debug
44

    
45

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

    
53
  debug=valid('Read_geom')
54
 if (debug) Call Header("Entering Read_Geom")
55
  if (debug) WRITE(*,*) "Input:",Trim(Input)
56
  if (debug) WRITE(*,*) "NgeomI:",NGeomI
57

    
58
  SELECT CASE(Input)
59
  CASE ('XYZ','CART')
60
     Call ReadGeom_cart
61
  CASE ('TURBOMOLE')
62
     Call ReadGeom_turbomole
63
  CASE ('VASP')
64
     Call ReadGeom_vasp
65
  CASE ('SIESTA')
66
     Call ReadGeom_siesta
67
  CASE Default
68
     WRITe(*,*) 'Input=',trim(Input),' UNKNOWN. Stop'
69
     STOP
70

    
71
  END SELECT
72

    
73

    
74
 if (debug) Call Header("Exiting Read_Geom")
75

    
76
END SUBROUTINE Read_Geom