Ignore:
Timestamp:
Aug 2, 2024, 9:58:25 PM (7 weeks ago)
Author:
abarral
Message:

Put dimensions.h and paramet.h into modules

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/convflu_loc.f90

    r5136 r5159  
    11SUBROUTINE convflu_loc( xflu,yflu,nbniv,convfl )
    2   !
     2
    33  !  P. Le Van
    4   !
    5   !
     4
     5
    66  !    *******************************************************************
    77  !  ... calcule la (convergence horiz. * aire locale)du flux ayant pour
     
    1010  !  xflu , yflu et nbniv sont des arguments d'entree pour le s-pg ..
    1111  !  convfl                est  un argument de sortie pour le s-pg .
    12   !
     12
    1313  ! njxflu  est le nombre de lignes de latitude de xflu,
    1414  ! ( = jjm ou jjp1 )
    1515  ! nbniv   est le nombre de niveaux vert. de  xflu et de yflu .
    16   !
     16
    1717  USE parallel_lmdz
    1818  USE lmdz_ssum_scopy, ONLY: ssum
    1919  USE lmdz_comgeom
    2020
     21USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
     22  USE lmdz_paramet
    2123  IMPLICIT NONE
    2224  !
    23   INCLUDE "dimensions.h"
    24   INCLUDE "paramet.h"
     25
     26
    2527  REAL :: xflu,yflu,convfl,convpn,convps
    2628  INTEGER :: l,ij,nbniv
    2729  DIMENSION  xflu( ijb_u:ije_u,nbniv ),yflu( ijb_v:ije_v,nbniv ) , &
    2830        convfl( ijb_u:ije_u,nbniv )
    29   !
     31
    3032  INTEGER :: ijb,ije
    3133
    3234!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    3335  DO l = 1,nbniv
    34   !
     36
    3537    ijb=ij_begin
    3638    ije=ij_end+iip1
     
    4345            yflu(ij +1,l ) - yflu( ij -iim,l )
    4446  END DO
    45   !
     47
    4648  !
    4749
    4850  ! ....  correction pour  convfl( 1,j,l)  ......
    4951  ! ....   convfl(1,j,l)= convfl(iip1,j,l) ...
    50   !
     52
    5153  !DIR$ IVDEP
    5254    DO ij = ijb,ije,iip1
    5355      convfl( ij,l ) = convfl( ij + iim,l )
    5456  END DO
    55   !
     57
    5658  ! ......  calcul aux poles  .......
    57   !
     59
    5860    IF (pole_nord) THEN
    5961
Note: See TracChangeset for help on using the changeset viewer.