Changeset 2668 in lmdz_wrf


Ignore:
Timestamp:
Jul 12, 2019, 5:58:40 PM (5 years ago)
Author:
lfita
Message:

Adding:

  • `deltat3D': Subroutine to compute the temporal derivative of a 3D field
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/tools/module_scientific.f90

    r2667 r2668  
    107107! curl2D_c1o: Subroutine to compute the first order centered curl of a 2D vectorial field
    108108! deformation3D: Subroutine to compute the deformation of a 3D field
     109! deltat3D: Subroutine to compute the temporal derivative of a 3D field
    109110! divergence2D_1o: Subroutine to compute the first order divergence of a 2D vectorial field
    110111! divergence2D_c1o: Subroutine to compute the first order centered divergence of a 2D vectorial field
     
    79677968  SUBROUTINE tilting3D(dx, dy, dz, vargrad, wagrad, tilt)
    79687969  ! Subroutine to compute the tilting of a 3D field
    7969   !   FROM: From: https://en.wikipedia.org/wiki/Finite_difference_coefficient
    79707970
    79717971    IMPLICIT NONE
     
    79947994  END SUBROUTINE tilting3D
    79957995
     7996  SUBROUTINE deltat3D(dx, dy, dz, dt, var, ddt, dtkind, vardt)
     7997  ! Subroutine to compute the temporal derivative of a 3D field
     7998
     7999    IMPLICIT NONE
     8000
     8001    INTEGER, INTENT(in)                                  :: dx, dy, dz, dt
     8002    REAL(r_k), DIMENSION(dx,dy,dz,dt), INTENT(in)        :: vargrad
     8003    CHARACTER(LEN=*), INTENT(in)                         :: dtkind
     8004    REAL(r_k), DIMENSION(dx,dy,dz,dt), INTENT(out)       :: vardt
     8005
     8006! Local
     8007    INTEGER                                              :: i, j, k, it
     8008
     8009!!!!!!! Variables
     8010! dx, dy, dz: shape of the 3D field
     8011! dt: number of time-steps
     8012! var: variable [X]
     8013! ddt: delta t [s]
     8014! dtkind: kind of delta t to compute
     8015!   'backward': [X(it) - X(it-1)] / ddt
     8016!   'centered': [X(it+1) - 2*X(it) + X(it-1)] / 2*ddt
     8017!   'forward': [X(it+1) - X(it)] / ddt
     8018! vardt: temporal derivative of var [X s-1]
     8019
     8020    fname = 'deltat3D'
     8021
     8022    vardt = fillval64
     8023
     8024    IF (TRIM(dtkind) == 'backward') THEN
     8025      DO it=2, dt
     8026        vardt(:,:,:,it) = (var(:,:,:,it) - var(:,:,:,it-1))/ddt
     8027      END DO
     8028    ELSE IF (TRIM(dtkind) == 'centered') THEN
     8029      DO it=2, dt-1
     8030        vardt(:,:,:,it) = (var(:,:,:,it+1) - 2*var(:,:,:,it) + var(:,:,:,it-1))/(2.*ddt)
     8031      END DO
     8032    ELSE IF (TRIM(dtkind) == 'forward') THEN
     8033      DO it=1, dt-1
     8034        vardt(:,:,:,it) = (var(:,:,:,it+1) - var(:,:,:,it))/ddt
     8035      END DO
     8036    ELSE
     8037      msg = "kind of delta t '" // TRIM(dtkind) // "' not ready !!"
     8038      CALL ErrMsg(msg, fname, -1)
     8039    END IF   
     8040
     8041  END SUBROUTINE tilting3D
     8042
    79968043END MODULE module_scientific
     8044
Note: See TracChangeset for help on using the changeset viewer.