Ignore:
Timestamp:
Sep 11, 2024, 6:03:07 PM (12 days ago)
Author:
abarral
Message:

Encapsulate files in modules

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/lmdz_dudv1.f90

    r5185 r5186  
    1 ! $Header$
     1MODULE lmdz_dudv1
     2  IMPLICIT NONE; PRIVATE
     3  PUBLIC dudv1
    24
    3 SUBROUTINE dudv1(vorpot, pbaru, pbarv, du, dv)
    4   USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
    5   USE lmdz_paramet
    6   IMPLICIT NONE
    7 
    8   !-----------------------------------------------------------------------
    9 
    10   !   Auteur:   P. Le Van
    11   !   -------
    12 
    13   !   Objet:
    14   !   ------
    15   !   calcul du terme de  rotation
    16   !   ce terme est ajoute a  d(ucov)/dt et a d(vcov)/dt  ..
    17   !   vorpot, pbaru et pbarv sont des arguments d'entree  pour le s-pg ..
    18   !   du  et dv              sont des arguments de sortie pour le s-pg ..
    19 
    20   !-----------------------------------------------------------------------
     5CONTAINS
    216
    227
     8  SUBROUTINE dudv1(vorpot, pbaru, pbarv, du, dv)
     9    USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
     10    USE lmdz_paramet
     11    IMPLICIT NONE
     12
     13    !-----------------------------------------------------------------------
     14
     15    !   Auteur:   P. Le Van
     16    !   -------
     17
     18    !   Objet:
     19    !   ------
     20    !   calcul du terme de  rotation
     21    !   ce terme est ajoute a  d(ucov)/dt et a d(vcov)/dt  ..
     22    !   vorpot, pbaru et pbarv sont des arguments d'entree  pour le s-pg ..
     23    !   du  et dv              sont des arguments de sortie pour le s-pg ..
     24
     25    !-----------------------------------------------------------------------
     26
     27    REAL :: vorpot(ip1jm, llm), pbaru(ip1jmp1, llm), &
     28            pbarv(ip1jm, llm), du(ip1jmp1, llm), dv(ip1jm, llm)
     29    INTEGER :: l, ij
     30
     31    DO l = 1, llm
     32
     33      DO ij = iip2, ip1jm - 1
     34        du(ij, l) = 0.125 * (vorpot(ij - iip1, l) + vorpot(ij, l)) * &
     35                (pbarv(ij - iip1, l) + pbarv(ij - iim, l) + &
     36                        pbarv(ij, l) + pbarv(ij + 1, l))
     37      END DO
     38
     39      DO ij = 1, ip1jm - 1
     40        dv(ij + 1, l) = - 0.125 * (vorpot(ij, l) + vorpot(ij + 1, l)) * &
     41                (pbaru(ij, l) + pbaru(ij + 1, l) + &
     42                        pbaru(ij + iip1, l) + pbaru(ij + iip2, l))
     43      END DO
     44
     45      !    .... correction  pour  dv( 1,j,l )  .....
     46      !    ....   dv(1,j,l)= dv(iip1,j,l) ....
     47
     48      !DIR$ IVDEP
     49      DO ij = 1, ip1jm, iip1
     50        dv(ij, l) = dv(ij + iim, l)
     51      END DO
     52
     53    END DO
     54
     55  END SUBROUTINE dudv1
    2356
    2457
    25   REAL :: vorpot(ip1jm, llm), pbaru(ip1jmp1, llm), &
    26           pbarv(ip1jm, llm), du(ip1jmp1, llm), dv(ip1jm, llm)
    27   INTEGER :: l, ij
    28 
    29 
    30   DO l = 1, llm
    31 
    32     DO ij = iip2, ip1jm - 1
    33       du(ij, l) = 0.125 * (vorpot(ij - iip1, l) + vorpot(ij, l)) * &
    34               (pbarv(ij - iip1, l) + pbarv(ij - iim, l) + &
    35                       pbarv(ij, l) + pbarv(ij + 1, l))
    36     END DO
    37 
    38     DO ij = 1, ip1jm - 1
    39       dv(ij + 1, l) = - 0.125 * (vorpot(ij, l) + vorpot(ij + 1, l)) * &
    40               (pbaru(ij, l) + pbaru(ij + 1, l) + &
    41                       pbaru(ij + iip1, l) + pbaru(ij + iip2, l))
    42     END DO
    43 
    44     !    .... correction  pour  dv( 1,j,l )  .....
    45     !    ....   dv(1,j,l)= dv(iip1,j,l) ....
    46 
    47     !DIR$ IVDEP
    48     DO ij = 1, ip1jm, iip1
    49       dv(ij, l) = dv(ij + iim, l)
    50     END DO
    51 
    52   END DO
    53 
    54 END SUBROUTINE dudv1
     58END MODULE lmdz_dudv1
Note: See TracChangeset for help on using the changeset viewer.