Statistiques
| Révision :

root / src / Read_geom.f90 @ 12

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

1 1 pfleura2
SUBROUTINE Read_Geom(input)
2 1 pfleura2
3 12 pfleura2
!----------------------------------------------------------------------
4 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
5 12 pfleura2
!  Centre National de la Recherche Scientifique,
6 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
7 12 pfleura2
!
8 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
9 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
10 12 pfleura2
!
11 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
12 12 pfleura2
!  Contact: optnpath@gmail.com
13 12 pfleura2
!
14 12 pfleura2
! This file is part of "Opt'n Path".
15 12 pfleura2
!
16 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
17 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
18 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
19 12 pfleura2
!  or (at your option) any later version.
20 12 pfleura2
!
21 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
22 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
23 12 pfleura2
!
24 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
25 12 pfleura2
!  GNU Affero General Public License for more details.
26 12 pfleura2
!
27 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
28 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
29 12 pfleura2
!
30 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
31 12 pfleura2
! for commercial licensing opportunities.
32 12 pfleura2
!----------------------------------------------------------------------
33 12 pfleura2
34 5 pfleura2
  Use VarTypes
35 5 pfleura2
  Use Path_module, only : NGeomI
36 1 pfleura2
  Use Io_module
37 1 pfleura2
38 1 pfleura2
  IMPLICIT NONE
39 1 pfleura2
40 1 pfleura2
41 1 pfleura2
  CHARACTER(32), INTENT(IN) :: input
42 1 pfleura2
43 8 pfleura2
  LOGICAL :: Debug
44 1 pfleura2
45 1 pfleura2
46 1 pfleura2
  INTERFACE
47 1 pfleura2
     function valid(string) result (isValid)
48 1 pfleura2
       CHARACTER(*), intent(in) :: string
49 1 pfleura2
       logical                  :: isValid
50 1 pfleura2
     END function VALID
51 1 pfleura2
  END INTERFACE
52 1 pfleura2
53 1 pfleura2
  debug=valid('Read_geom')
54 1 pfleura2
 if (debug) Call Header("Entering Read_Geom")
55 1 pfleura2
  if (debug) WRITE(*,*) "Input:",Trim(Input)
56 1 pfleura2
  if (debug) WRITE(*,*) "NgeomI:",NGeomI
57 1 pfleura2
58 1 pfleura2
  SELECT CASE(Input)
59 1 pfleura2
  CASE ('XYZ','CART')
60 5 pfleura2
     Call ReadGeom_cart
61 1 pfleura2
  CASE ('TURBOMOLE')
62 5 pfleura2
     Call ReadGeom_turbomole
63 1 pfleura2
  CASE ('VASP')
64 5 pfleura2
     Call ReadGeom_vasp
65 5 pfleura2
  CASE ('SIESTA')
66 5 pfleura2
     Call ReadGeom_siesta
67 1 pfleura2
  CASE Default
68 1 pfleura2
     WRITe(*,*) 'Input=',trim(Input),' UNKNOWN. Stop'
69 1 pfleura2
     STOP
70 1 pfleura2
71 1 pfleura2
  END SELECT
72 1 pfleura2
73 1 pfleura2
74 1 pfleura2
 if (debug) Call Header("Exiting Read_Geom")
75 1 pfleura2
76 1 pfleura2
END SUBROUTINE Read_Geom