Statistiques
| Révision :

root / src / freemv.f90

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

1 1 pfleura2
  Subroutine freemv(NFree,vfree)
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 1 pfleura2
34 12 pfleura2
   IMPLICIT NONE
35 12 pfleura2
36 1 pfleura2
  INTEGER, PARAMETER :: KINT=KIND(1)
37 1 pfleura2
  INTEGER, PARAMETER :: KREAL=KIND(1.0D0)
38 1 pfleura2
39 1 pfleura2
  INTEGER(KINT), INTENT(IN) :: Nfree
40 1 pfleura2
  REAL(KREAL), INTENT(OUT) :: Vfree(Nfree,Nfree)
41 1 pfleura2
42 1 pfleura2
! ======================================================================
43 1 pfleura2
!
44 1 pfleura2
! At the end, this should do:
45 1 pfleura2
! Construct displacement vectors that are free and which do not contain rigid motions.
46 1 pfleura2
! Output : vectors are orthonormal (in the non-mass-weighted metric)
47 1 pfleura2
!
48 1 pfleura2
! For now, it just returns an identity matrix (NFree,Nfree)
49 1 pfleura2
! v3.94
50 1 pfleura2
! We delete displacements that correspond to frozen atoms
51 1 pfleura2
!
52 1 pfleura2
! ======================================================================
53 1 pfleura2
  logical :: debug
54 1 pfleura2
  integer(KINT) :: I
55 1 pfleura2
56 1 pfleura2
  interface
57 1 pfleura2
     function valid(string) result (isValid)
58 1 pfleura2
       logical                  :: isValid
59 1 pfleura2
       character(*), intent(in) :: string
60 1 pfleura2
     end function valid
61 1 pfleura2
  end interface
62 1 pfleura2
63 1 pfleura2
  debug=valid('vfree')
64 1 pfleura2
65 1 pfleura2
  if (debug) WRITE(*,*) "================================= Entering Vfree ==============="
66 1 pfleura2
67 1 pfleura2
  Vfree=0.d0
68 1 pfleura2
  DO I=1,Nfree
69 1 pfleura2
     Vfree(I,I)=1.d0
70 1 pfleura2
  END DO
71 1 pfleura2
72 1 pfleura2
  if (debug) WRITE(*,*) "================================= Exiting Vfree ==============="
73 1 pfleura2
74 1 pfleura2
 END Subroutine freemv
75 1 pfleura2