File: noncol.f90

package info (click to toggle)
espresso 6.7-4
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid
  • size: 311,068 kB
  • sloc: f90: 447,429; ansic: 52,566; sh: 40,631; xml: 37,561; tcl: 20,077; lisp: 5,923; makefile: 4,503; python: 4,379; perl: 1,219; cpp: 761; fortran: 618; java: 568; awk: 128
file content (68 lines) | stat: -rw-r--r-- 3,015 bytes parent folder | download | duplicates (3)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
!
! Copyright (C) 2001-2003 PWSCF group
! This file is distributed under the terms of the
! GNU General Public License. See the file `License'
! in the root directory of the present distribution,
! or http://www.gnu.org/copyleft/gpl.txt .
!
!----------------------------------------------------------------------------
!
MODULE noncollin_module
  USE kinds, ONLY : DP
  USE parameters, ONLY : ntypx
  !
  SAVE
  !
  INTEGER :: &
      npol,               & !  number of coordinates of wfc
      report,             & !  print the local quantities (magnet. and rho)
                            !  every #report iterations
      nspin_lsda = 1,     & !  =1 when nspin=1,4 =2 when nspin=2 
      nspin_mag = 1,      & !  =1 when nspin=1,4 (domag=.false.), =2 when
                            !   nspin=2, =4 nspin=4 (domag=.true.)
      nspin_gga = 1,      & !  =1 when nspin=1,4 (domag=.false.)   
                            !  =2 when nspin=2,4 (domag=.true.) (needed with gga)
      i_cons = 0            !  indicator for constrained local quantities
  !
  INTEGER, ALLOCATABLE :: &
  !                         !  when spherical (non-overlapping) integration
      pointlist(:)          !  regions are defined around atoms this index
                            !  says for each point in the fft grid to which 
                            !  atom it is assigned (0 if no atom is selected)
  !
  LOGICAL :: &
      noncolin, &           !  true if noncollinear magnetism is allowed
      lsign=.FALSE.         !  if true use the sign feature to calculate
                            !  rhoup and rhodw
  !
  REAL (DP) :: &
      angle1(ntypx),       &!  Define the polar coordinates of the starting
      angle2(ntypx),       &!  magnetization's direction for each atom
      mcons(3,ntypx)=0.d0, &!  constrained values for local variables
      magtot_nc(3),        &!  total magnetization
      bfield(3)=0.d0,      &!  magnetic field used in some cases
      vtcon,               &!  contribution of the constraining fields to
                            !  the total energy
      r_m(ntypx) = 0.0d0,  &!  Radius for local integrations for each type
      lambda                !  prefactor in the penalty functional 
                            !  for constraints
  !
  REAL (DP), ALLOCATABLE :: &
      factlist(:),         &! weight factors for local integrations
      m_loc(:,:)            ! local integrated magnetization
  REAL(DP) ::              &
       ux(3)                 ! versor for deciding signs in gga
  !
  CONTAINS
    !
    !------------------------------------------------------------------------
    SUBROUTINE deallocate_noncol()
      !------------------------------------------------------------------------
      !
      IF ( ALLOCATED( pointlist) )       DEALLOCATE( pointlist )
      IF ( ALLOCATED( factlist ) )       DEALLOCATE( factlist )
      IF ( ALLOCATED( m_loc    ) )       DEALLOCATE( m_loc )
      !
    END SUBROUTINE deallocate_noncol
    !
END MODULE noncollin_module