Ignore:
Timestamp:
Jul 23, 2024, 7:14:34 PM (8 weeks ago)
Author:
abarral
Message:

Replace 1DUTILS.h by module lmdz_1dutils.f90
Replace 1DConv.h by module lmdz_old_1dconv.f90 (it's only used by old_* files)
Convert *.F to *.f90
Fix gradsdef.h formatting
Remove unnecessary "RETURN" at the end of functions/subroutines

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/convflu.f90

    r5104 r5105  
    22! $Header$
    33
    4       SUBROUTINE convflu( xflu,yflu,nbniv,convfl )
    5 c
    6 c  P. Le Van
    7 c
    8 c
    9 c    *******************************************************************
    10 c  ... calcule la (convergence horiz. * aire locale)du flux ayant pour
    11 c      composantes xflu et yflu ,variables extensives .  ......
    12 c    *******************************************************************
    13 c      xflu , yflu et nbniv sont des arguments d'entree pour le s-pg ..
    14 c      convfl                est  un argument de sortie pour le s-pg .
    15 c
    16 c     njxflu  est le nombre de lignes de latitude de xflu,
    17 c    ( = jjm ou jjp1 )
    18 c    nbniv   est le nombre de niveaux vert. de  xflu et de yflu .
    19 c
    20       IMPLICIT NONE
    21 c
    22       INCLUDE "dimensions.h"
    23       INCLUDE "paramet.h"
    24       REAL      xflu,yflu,convfl,convpn,convps
    25       INTEGER    l,ij,nbniv
    26       DIMENSION  xflu( ip1jmp1,nbniv ),yflu( ip1jm,nbniv ) ,
    27      *         convfl( ip1jmp1,nbniv )
    28 c
    29       REAL      SSUM
    30 c
    31 c
    32       INCLUDE "comgeom.h"
    33 c
    34       DO l = 1,nbniv
    35 c
    36       DO ij = iip2, ip1jm - 1
    37       convfl( ij + 1,l ) =  xflu(   ij,l ) - xflu( ij +  1,l )   +
    38      *                      yflu(ij +1,l ) - yflu( ij -iim,l )
    39       END DO
    40 c
    41 c
     4SUBROUTINE convflu( xflu,yflu,nbniv,convfl )
     5  !
     6  !  P. Le Van
     7  !
     8  !
     9  !    *******************************************************************
     10  !  ... calcule la (convergence horiz. * aire locale)du flux ayant pour
     11  !  composantes xflu et yflu ,variables extensives .  ......
     12  !    *******************************************************************
     13  !  xflu , yflu et nbniv sont des arguments d'entree pour le s-pg ..
     14  !  convfl                est  un argument de sortie pour le s-pg .
     15  !
     16  ! njxflu  est le nombre de lignes de latitude de xflu,
     17  ! ( = jjm ou jjp1 )
     18  ! nbniv   est le nombre de niveaux vert. de  xflu et de yflu .
     19  !
     20  IMPLICIT NONE
     21  !
     22  INCLUDE "dimensions.h"
     23  INCLUDE "paramet.h"
     24  REAL :: xflu,yflu,convfl,convpn,convps
     25  INTEGER :: l,ij,nbniv
     26  DIMENSION  xflu( ip1jmp1,nbniv ),yflu( ip1jm,nbniv ) , &
     27        convfl( ip1jmp1,nbniv )
     28  !
     29  REAL :: SSUM
     30  !
     31  !
     32  INCLUDE "comgeom.h"
     33  !
     34  DO l = 1,nbniv
     35  !
     36  DO ij = iip2, ip1jm - 1
     37  convfl( ij + 1,l ) =  xflu(   ij,l ) - xflu( ij +  1,l )   + &
     38        yflu(ij +1,l ) - yflu( ij -iim,l )
     39  END DO
     40  !
     41  !
    4242
    43 c    ....  correction pour  convfl( 1,j,l)  ......
    44 c    ....   convfl(1,j,l)= convfl(iip1,j,l) ...
    45 c
    46 CDIR$ IVDEP
    47       DO ij = iip2,ip1jm,iip1
    48       convfl( ij,l ) = convfl( ij + iim,l )
    49       END DO
    50 c
    51 c    ......  calcul aux poles  .......
    52 c
    53       convpn =   SSUM( iim, yflu(     1    ,l ),  1 )
    54       convps = - SSUM( iim, yflu( ip1jm-iim,l ),  1 )
    55       DO ij = 1,iip1
    56       convfl(     ij   ,l ) = convpn * aire(   ij     ) / apoln
    57       convfl( ij+ ip1jm,l ) = convps * aire( ij+ ip1jm) / apols
    58       END DO
    59 c
    60       END DO
    61       RETURN
    62       END
     43  ! ....  correction pour  convfl( 1,j,l)  ......
     44  ! ....   convfl(1,j,l)= convfl(iip1,j,l) ...
     45  !
     46  !DIR$ IVDEP
     47  DO ij = iip2,ip1jm,iip1
     48  convfl( ij,l ) = convfl( ij + iim,l )
     49  END DO
     50  !
     51  ! ......  calcul aux poles  .......
     52  !
     53  convpn =   SSUM( iim, yflu(     1    ,l ),  1 )
     54  convps = - SSUM( iim, yflu( ip1jm-iim,l ),  1 )
     55  DO ij = 1,iip1
     56  convfl(     ij   ,l ) = convpn * aire(   ij     ) / apoln
     57  convfl( ij+ ip1jm,l ) = convps * aire( ij+ ip1jm) / apols
     58  END DO
     59  !
     60  END DO
     61  RETURN
     62END SUBROUTINE convflu
Note: See TracChangeset for help on using the changeset viewer.