Browse Source

Updated wspd wdir to match NCL

lon0
Bill Ladwig 6 years ago
parent
commit
8a86e76ead
  1. 36
      fortran/wrf_wind.f90
  2. 18
      src/wrf/extension.py

36
fortran/wrf_wind.f90

@ -1,23 +1,21 @@
! NCLFORTSTART ! NCLFORTSTART
SUBROUTINE DCOMPUTEWSPD(wspd, u, v, nx, ny) SUBROUTINE DCOMPUTEWSPD(wspd, u, v, n)
IMPLICIT NONE IMPLICIT NONE
!f2py threadsafe !f2py threadsafe
!f2py intent(in,out) :: wspd !f2py intent(in,out) :: wspd
INTEGER, INTENT(IN) :: nx, ny INTEGER, INTENT(IN) :: n
REAL(KIND=8), DIMENSION(nx,ny), INTENT(OUT) :: wspd REAL(KIND=8), DIMENSION(n), INTENT(OUT) :: wspd
REAL(KIND=8), DIMENSION(nx,ny), INTENT(IN) :: u, v REAL(KIND=8), DIMENSION(n), INTENT(IN) :: u, v
! NCLEND ! NCLEND
INTEGER i, j INTEGER i
!$OMP PARALLEL DO COLLAPSE(2) SCHEDULE(runtime) !$OMP PARALLEL DO SCHEDULE(runtime)
DO j = 1,ny DO i = 1,n
DO i = 1,nx wspd(i) = SQRT(u(i)*u(i) + v(i)*v(i))
wspd(i,j) = SQRT(u(i,j)*u(i,j) + v(i,j)*v(i,j))
END DO
END DO END DO
!$OMP END PARALLEL DO !$OMP END PARALLEL DO
@ -25,7 +23,7 @@ END SUBROUTINE DCOMPUTEWSPD
! NCLFORTSTART ! NCLFORTSTART
SUBROUTINE DCOMPUTEWDIR(wdir, u, v, nx, ny) SUBROUTINE DCOMPUTEWDIR(wdir, u, v, n)
USE wrf_constants, ONLY : DEG_PER_RAD USE wrf_constants, ONLY : DEG_PER_RAD
IMPLICIT NONE IMPLICIT NONE
@ -33,18 +31,16 @@ SUBROUTINE DCOMPUTEWDIR(wdir, u, v, nx, ny)
!f2py threadsafe !f2py threadsafe
!f2py intent(in,out) :: wdir !f2py intent(in,out) :: wdir
INTEGER, INTENT(IN) :: nx, ny INTEGER, INTENT(IN) :: n
REAL(KIND=8), DIMENSION(nx,ny), INTENT(OUT) :: wdir REAL(KIND=8), DIMENSION(n), INTENT(OUT) :: wdir
REAL(KIND=8), DIMENSION(nx,ny), INTENT(IN) :: u, v REAL(KIND=8), DIMENSION(n), INTENT(IN) :: u, v
! NCLEND ! NCLEND
INTEGER i, j INTEGER i
!$OMP PARALLEL DO COLLAPSE(2) SCHEDULE(runtime) !$OMP PARALLEL DO SCHEDULE(runtime)
DO j = 1,ny DO i = 1,n
DO i = 1,nx wdir(i) = MOD(270.0 - ATAN2(v(i), u(i)) * DEG_PER_RAD, 360.)
wdir(i,j) = MOD(270.0 - ATAN2(v(i,j), u(i,j)) * DEG_PER_RAD, 360.)
END DO
END DO END DO
!$OMP END PARALLEL DO !$OMP END PARALLEL DO

18
src/wrf/extension.py

@ -949,12 +949,15 @@ def _wspd(u, v, outview=None):
Located in wrf_wind.f90. Located in wrf_wind.f90.
""" """
shape = u.shape
if outview is None: if outview is None:
outview = np.empty_like(u) outview = np.empty_like(u)
result = dcomputewspd(outview, result = dcomputewspd(outview.ravel(order="A"),
u, u.ravel(order="A"),
v) v.ravel(order="A"))
result = np.reshape(result, shape, order="F")
return result return result
@ -969,12 +972,15 @@ def _wdir(u, v, outview=None):
Located in wrf_wind.f90. Located in wrf_wind.f90.
""" """
shape = u.shape
if outview is None: if outview is None:
outview = np.empty_like(u) outview = np.empty_like(u)
result = dcomputewdir(outview, result = dcomputewdir(outview.ravel(order="A"),
u, u.ravel(order="A"),
v) v.ravel(order="A"))
result = np.reshape(result, shape, order="F")
return result return result

Loading…
Cancel
Save