Skip to content

Commit

Permalink
Fix constant
Browse files Browse the repository at this point in the history
  • Loading branch information
mkrack committed Sep 27, 2021
1 parent aabf307 commit 05cc756
Showing 1 changed file with 15 additions and 15 deletions.
30 changes: 15 additions & 15 deletions src/pw/pw_methods.F
Original file line number Diff line number Diff line change
Expand Up @@ -249,7 +249,7 @@ SUBROUTINE pw_copy(pw1, pw2)
! " grid 2 :", pw2%pw_grid%id_nr, &
! " spherical :", pw2%pw_grid%spherical, &
! " reference :", pw2%pw_grid%reference
!ENDIF
!END IF
CALL pw_copy_match(pw1, pw2)
END IF

Expand All @@ -269,7 +269,7 @@ SUBROUTINE pw_copy(pw1, pw2)
" grid 2 :", pw2%pw_grid%id_nr, &
" spherical :", pw2%pw_grid%spherical, &
" reference :", pw2%pw_grid%reference
ENDIF
END IF
CPABORT("Incompatible grids")
END IF

Expand Down Expand Up @@ -615,7 +615,7 @@ SUBROUTINE pw_derive(pw, n)

! im can take the values 1, -1, i, -i
! skip this if im == 1
IF (ABS(REAL(im, KIND=dp) - 1.0_dp) > 1.e-10) THEN
IF (ABS(REAL(im, KIND=dp) - 1.0_dp) > 1.0E-10_dp) THEN
!$OMP PARALLEL WORKSHARE DEFAULT(NONE) SHARED(pw,cnt,im)
pw%cc(:) = im*pw%cc(:)
!$OMP END PARALLEL WORKSHARE
Expand Down Expand Up @@ -1065,7 +1065,7 @@ SUBROUTINE pw_axpy(pw1, pw2, alpha)
" grid 2 :", pw2%pw_grid%id_nr, &
" sperical :", pw2%pw_grid%spherical, &
" reference :", pw2%pw_grid%reference
ENDIF
END IF
CPABORT("Grids not compatible")

END IF
Expand All @@ -1084,7 +1084,7 @@ SUBROUTINE pw_axpy(pw1, pw2, alpha)
" grid 2 :", pw2%pw_grid%id_nr, &
" sperical :", pw2%pw_grid%spherical, &
" reference :", pw2%pw_grid%reference
ENDIF
END IF
CPABORT("Grids not compatible")

END IF
Expand Down Expand Up @@ -1220,7 +1220,7 @@ SUBROUTINE pw_gather_s(pw, c, scale)

IF (pw%in_use /= COMPLEXDATA1D) THEN
CPABORT("Data field has to be COMPLEXDATA1D")
ENDIF
END IF

! after the gather we are in g-space
pw%in_space = RECIPROCALSPACE
Expand Down Expand Up @@ -1288,11 +1288,11 @@ SUBROUTINE pw_gather_p(pw, c, scale)

IF (pw%in_use /= COMPLEXDATA1D) THEN
CPABORT("Data field has to be COMPLEXDATA1D")
ENDIF
END IF

IF (pw%pw_grid%para%mode /= PW_MODE_DISTRIBUTED) THEN
CPABORT("This grid type is not distributed")
ENDIF
END IF

! after the gather we are in g-space
pw%in_space = RECIPROCALSPACE
Expand Down Expand Up @@ -1369,11 +1369,11 @@ SUBROUTINE pw_scatter_s(pw, c, scale)

IF (pw%in_use /= COMPLEXDATA1D) THEN
CPABORT("Data field has to be COMPLEXDATA1D")
ENDIF
END IF

IF (pw%in_space /= RECIPROCALSPACE) THEN
CPABORT("Data has to be in RECIPROCALSPACE")
ENDIF
END IF

mapl => pw%pw_grid%mapl%pos
mapm => pw%pw_grid%mapm%pos
Expand Down Expand Up @@ -1475,15 +1475,15 @@ SUBROUTINE pw_scatter_p(pw, c, scale)

IF (pw%in_use /= COMPLEXDATA1D) THEN
CPABORT("Data field has to be COMPLEXDATA1D")
ENDIF
END IF

IF (pw%in_space /= RECIPROCALSPACE) THEN
CPABORT("Data has to be in RECIPROCALSPACE")
ENDIF
END IF

IF (pw%pw_grid%para%mode /= PW_MODE_DISTRIBUTED) THEN
CPABORT("This grid type is not distributed")
ENDIF
END IF

mapl => pw%pw_grid%mapl%pos
mapm => pw%pw_grid%mapm%pos
Expand Down Expand Up @@ -1704,7 +1704,7 @@ SUBROUTINE fft_wrap_pw1pw2(pw1, pw2, debug)
CALL copy_rc(pw1%cr3d, c_out)
CALL fft3d(dir, n, c_out, scale=norm, debug=test)
CALL pw_gather(pw2, c_out)
ENDIF
END IF
DEALLOCATE (c_out)
#else
ALLOCATE (c_out(n(1), n(2), n(3)))
Expand Down Expand Up @@ -2125,7 +2125,7 @@ FUNCTION pw_integral_ab(pw1, pw2) RESULT(integral_value)
integral_value = integral_value*pw1%pw_grid%dvol
ELSE
integral_value = integral_value*pw1%pw_grid%vol
ENDIF
END IF
IF (pw1%in_use == COMPLEXDATA1D) THEN
IF (pw1%pw_grid%grid_span == HALFSPACE) THEN
integral_value = 2.0_dp*integral_value
Expand Down

0 comments on commit 05cc756

Please sign in to comment.