Changeset 2663 in lmdz_wrf


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

Adding:

  • `deformation3D_1o': Subroutine to compute the first order deformation of a 3D field
  • `gradient3D_1o': Subroutine to compute the first order gradient of a 3D field
  • `matmodule3D': Subroutine to compute the module of a 3D matrix with 3 components
  • `tilting3D_1o': Subroutine to compute the first order tilting of a 3D field
  • `vecmodule3D': Function to compute the module of a 3D vector
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/tools/module_scientific.f90

    r2657 r2663  
    2727! fill3DR_2Dvec: Subroutine to fill a 3D float matrix from a series of indices from a 2D matrix
    2828! gradient2D_1o: Subroutine to compute the first order gradient of a 2D field
     29! gradient3D_1o: Subroutine to compute the first order gradient of a 3D field
    2930! gradient2D_c1o: Subroutine to compute the first order centered gradient of a 2D field
    3031! grid_within_polygon: Subroutine to determine which grid cells from a matrix lay inside a polygon
     
    110111! write_overlap_polys_ascii: Subroutine to write to an ASCII file the associated polygons at a given time-step
    111112! write_overlap_tracks_ascii: Subroutine to write to an ASCII the polygons associated to a trajectory at a given time step
     113
     114!! Vectorial calculus
     115! deformation3D_1o: Subroutine to compute the first order deformation of a 3D field
     116! gradient3D_1o: Subroutine to compute the first order gradient of a 3D field
     117! matmodule3D: Subroutine to compute the module of a 3D matrix with 3 components
     118! tilting3D_1o: Subroutine to compute the first order tilting of a 3D field
     119! vecmodule3D: Function to compute the module of a 3D vector
    112120
    113121!!! *Functions/Subroutines to sort values adpated. The method used is usually referred to as "selection" method.
     
    76417649  END SUBROUTINE gradient2D_1o
    76427650
     7651  SUBROUTINE gradient3D_1o(dx, dy, dz, var, dsx, dsy, dsz, grad)
     7652  ! Subroutine to compute the first order gradient of a 3D field
     7653  !   FROM: From: https://en.wikipedia.org/wiki/Finite_difference_coefficient
     7654
     7655    IMPLICIT NONE
     7656
     7657    INTEGER, INTENT(in)                                  :: dx, dy, dz
     7658    REAL(r_k), DIMENSION(dx,dy,dz), INTENT(in)           :: var, dsz
     7659    REAL(r_k), DIMENSION(dx,dy), INTENT(in)              :: dsx, dsy
     7660    REAL(r_k), DIMENSION(dx,dy,dz,3), INTENT(out)        :: grad
     7661
     7662! Local
     7663    INTEGER                                              :: i, j, k
     7664
     7665!!!!!!! Variables
     7666! dx, dy, dz: shape of the 3D field
     7667! var: variable
     7668! dsx, dsy, dsz: matrices of distances betweeen grid points along each axis
     7669! grad: gradient
     7670
     7671    fname = 'gradient3D_1o'
     7672
     7673    grad = fillval64
     7674
     7675    DO i=1, dx-1
     7676      DO j=1, dy-1
     7677        DO k=1, dz-1
     7678          grad(i,j,k,:) = (/ (var(i+1,j,k)-var(i,j,k))/dsx(i,j), (var(i,j+1,k)-var(i,j,k))/dsy(i,j),  &
     7679             (var(i,j,k+1)-var(i,j,k))/dsz(i,j,k) /)
     7680        END DO
     7681      END DO
     7682    END DO
     7683
     7684  END SUBROUTINE gradient3D_1o
     7685
    76437686  SUBROUTINE gradient2D_c1o(dx, dy, var, dsx, dsy, grad)
    76447687  ! Subroutine to compute the first order centerd gradient of a 2D field
     
    78337876  END SUBROUTINE lap2D_1o
    78347877
    7835 
    78367878  SUBROUTINE lap2D_c1o(dx, dy, dsx, dsy, var, lap)
    78377879  ! Subroutine to compute the first order centered laplacian of a 2D vectorial field
     
    78677909  END SUBROUTINE lap2D_c1o
    78687910
     7911  REAL(r_k) FUNCTION vecmodule3D(vec)
     7912  ! Function to compute the module of a 3D vector
     7913
     7914    IMPLICIT NONE
     7915
     7916    REAL(r_k), DIMENSION(3), INTENT(in)                  :: vec
     7917
     7918    fname = 'vecmodule3D'
     7919
     7920    vecmodule3D = SQRT(vec(1)*vec(1) + vec(2)*vec(2) + vec(3)*vec(3))
     7921
     7922  END FUNCTION vecmodule3D
     7923
     7924  SUBROUTINE FUNCTION matmodule3D(d1,d2,d3,mat)
     7925  ! Subroutine to compute the module of a 3D matrix with 3 components
     7926
     7927    IMPLICIT NONE
     7928
     7929    REAL(r_k), DIMENSION(d1,d2,d3,3), INTENT(in)         :: mat
     7930    REAL(r_k), DIMENSION(d1,d2,d3), INTENT(out)          :: matmodule
     7931
     7932    fname = 'matmodule3D'
     7933
     7934    matmodule3D = SQRT(vec(:,:,:,1)*vec(:,:,:,1) + vec(:,:,:,2)*vec(:,:,:,2) +                        &
     7935      vec(:,:,:,3)*vec(:,:,:,3))
     7936
     7937  END SUBROUTINE matmodule3D
     7938
     7939  SUBROUTINE deformation3D_1o(dx, dy, dz, vargrad, uagrad, vagrad, def)
     7940  ! Subroutine to compute the first order deformation of a 3D field
     7941  !   FROM: From: https://en.wikipedia.org/wiki/Finite_difference_coefficient
     7942
     7943    IMPLICIT NONE
     7944
     7945    INTEGER, INTENT(in)                                  :: dx, dy, dz
     7946    REAL(r_k), DIMENSION(dx,dy,dz,3), INTENT(in)         :: vargrad, uagrad, vagrad
     7947    REAL(r_k), DIMENSION(dx,dy,dz,3), INTENT(out)        :: def
     7948
     7949! Local
     7950    INTEGER                                              :: i, j, k
     7951
     7952!!!!!!! Variables
     7953! dx, dy, dz: shape of the 3D field
     7954! vargrad: gradient of the variable
     7955! uagrad, vagrad: gradient of x/y components of the wind field
     7956! def: deformation
     7957
     7958    fname = 'deformation3D_1o'
     7959
     7960    def = fillval64
     7961
     7962    def(:,:,:,1) = - uagrad(:,:,:,1)*vargrad(:,:,:1) - vagrad(:,:,:,1)*vargrad(:,:,:2)
     7963    def(:,:,:,2) = - uagrad(:,:,:,2)*vargrad(:,:,:1) - vagrad(:,:,:,2)*vargrad(:,:,:2)
     7964    def(:,:,:,3) = - uagrad(:,:,:,3)*vargrad(:,:,:1) - vagrad(:,:,:,3)*vargrad(:,:,:2)
     7965
     7966  END SUBROUTINE deformation3D_1o
     7967
     7968  SUBROUTINE tilting3D_1o(dx, dy, dz, vargrad, wagrad, tilt)
     7969  ! Subroutine to compute the first order tilting of a 3D field
     7970  !   FROM: From: https://en.wikipedia.org/wiki/Finite_difference_coefficient
     7971
     7972    IMPLICIT NONE
     7973
     7974    INTEGER, INTENT(in)                                  :: dx, dy, dz
     7975    REAL(r_k), DIMENSION(dx,dy,dz,3), INTENT(in)         :: vargrad, wagrad
     7976    REAL(r_k), DIMENSION(dx,dy,dz,3), INTENT(out)        :: tilt
     7977
     7978! Local
     7979    INTEGER                                              :: i, j, k
     7980
     7981!!!!!!! Variables
     7982! dx, dy, dz: shape of the 3D field
     7983! vargrad: gradient of the variable
     7984! wagrad: gradient of z component of the wind field
     7985! tilt: tilting
     7986
     7987    fname = 'tilting3D_1o'
     7988
     7989    tilt = fillval64
     7990
     7991    tilt(:,:,:,1) = - uagrad(:,:,:,1)*vargrad(:,:,:3)
     7992    tilt(:,:,:,2) = - vagrad(:,:,:,2)*vargrad(:,:,:3)
     7993    tilt(:,:,:,3) = - wagrad(:,:,:,3)*vargrad(:,:,:3)
     7994
     7995  END SUBROUTINE tilting3D_1o
     7996
    78697997END MODULE module_scientific
Note: See TracChangeset for help on using the changeset viewer.