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/addfi_loc.f90

    r5136 r5159  
    1010  USE lmdz_comgeom
    1111
     12  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
     13  USE lmdz_paramet
    1214  IMPLICIT NONE
    13   !
     15
    1416  !=======================================================================
    15   !
     17
    1618  !    Addition of the physical tendencies
    17   !
     19
    1820  !    Interface :
    1921  !    -----------
    20   !
     22
    2123  !  Input :
    2224  !  -------
     
    3234  !  pdhfi(ip1jmp1)         |      tendencies
    3335  !  pdtsfi(ip1jmp1)        |
    34   !
     36
    3537  !  Output :
    3638  !  --------
     
    3941  !  ph
    4042  !  pts
    41   !
    42   !
     43
     44
    4345  !=======================================================================
    44   !
     46
    4547  !-----------------------------------------------------------------------
    46   !
     48
    4749  !    0.  Declarations :
    4850  !    ------------------
    4951  !
    50   INCLUDE "dimensions.h"
    51   INCLUDE "paramet.h"
    52   !
     52
     53
     54
    5355  !    Arguments :
    5456  !    -----------
    55   !
     57
    5658  REAL, INTENT(IN) :: pdt ! time step for the integration (s)
    57   !
     59
    5860  REAL, INTENT(INOUT) :: pvcov(ijb_v:ije_v, llm) ! covariant meridional wind
    5961  REAL, INTENT(INOUT) :: pucov(ijb_u:ije_u, llm) ! covariant zonal wind
     
    6769  REAL, INTENT(IN) :: pdhfi(ijb_u:ije_u, llm)
    6870  REAL, INTENT(IN) :: pdpfi(ijb_u:ije_u)
    69   !
     71
    7072  LOGICAL, INTENT(IN) :: leapf, forward ! not used
    71   !
    72   !
     73
     74
    7375  !    Local variables :
    7476  !    -----------------
    75   !
     77
    7678  REAL :: xpn(iim), xps(iim), tpn, tps
    7779  INTEGER :: j, k, iq, ij
     
    8082
    8183  INTEGER :: ijb, ije
    82   !
     84
    8385  !-----------------------------------------------------------------------
    8486
     
    148150  !$OMP END DO NOWAIT
    149151
    150   !
     152
    151153  IF (pole_sud)  ije = ij_end
    152154  !$OMP MASTER
Note: See TracChangeset for help on using the changeset viewer.