Statistiques
| Révision :

root / src / freemv.f90

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

1
  Subroutine freemv(NFree,vfree)
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
   IMPLICIT NONE
35

    
36
  INTEGER, PARAMETER :: KINT=KIND(1)
37
  INTEGER, PARAMETER :: KREAL=KIND(1.0D0)
38

    
39
  INTEGER(KINT), INTENT(IN) :: Nfree
40
  REAL(KREAL), INTENT(OUT) :: Vfree(Nfree,Nfree)
41

    
42
! ======================================================================
43
!
44
! At the end, this should do:
45
! Construct displacement vectors that are free and which do not contain rigid motions.
46
! Output : vectors are orthonormal (in the non-mass-weighted metric)
47
! 
48
! For now, it just returns an identity matrix (NFree,Nfree)
49
! v3.94
50
! We delete displacements that correspond to frozen atoms
51
!
52
! ======================================================================
53
  logical :: debug
54
  integer(KINT) :: I
55

    
56
  interface
57
     function valid(string) result (isValid)
58
       logical                  :: isValid
59
       character(*), intent(in) :: string
60
     end function valid
61
  end interface
62

    
63
  debug=valid('vfree')
64

    
65
  if (debug) WRITE(*,*) "================================= Entering Vfree ==============="
66
  
67
  Vfree=0.d0
68
  DO I=1,Nfree
69
     Vfree(I,I)=1.d0
70
  END DO
71

    
72
  if (debug) WRITE(*,*) "================================= Exiting Vfree ==============="
73

    
74
 END Subroutine freemv
75

    
76