Changeset 5282


Ignore:
Timestamp:
Oct 28, 2024, 1:11:48 PM (4 hours ago)
Author:
abarral
Message:

Turn iniprint.h clesphys.h into modules
Remove unused description.h

Location:
LMDZ6/trunk/libf
Files:
1 deleted
147 edited
3 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3d/abort_gcm.F90

    r5271 r5282  
    66SUBROUTINE abort_gcm(modname, message, ierr)
    77
    8   USE IOIPSL
     8  USE iniprint_mod_h
     9USE IOIPSL
    910  !! ug Pour les sorties XIOS
    1011  USE wxios
    1112
    12 INCLUDE "iniprint.h"
    1313
    1414  !
  • LMDZ6/trunk/libf/dyn3d/advtrac.f90

    r5281 r5282  
    99   !            M.A Filiberti (04/2002)
    1010   !
     11   USE iniprint_mod_h
    1112   USE comgeom2_mod_h
    1213   USE comdissip_mod_h
     
    2223   !
    2324
    24 
    25    include "description.h"
    26    include "iniprint.h"
    2725
    2826   !---------------------------------------------------------------------------
  • LMDZ6/trunk/libf/dyn3d/bilan_dyn.f90

    r5281 r5282  
    1010  !             vQ..A=Cp T + L * ...
    1111
     12  USE iniprint_mod_h
    1213  USE comgeom2_mod_h
    1314  USE IOIPSL
     
    2324
    2425
    25   include "iniprint.h"
    2626
    2727  !====================================================================
  • LMDZ6/trunk/libf/dyn3d/conf_gcm.f90

    r5280 r5282  
    44SUBROUTINE conf_gcm( tapedef, etatinit )
    55
     6  USE iniprint_mod_h
    67  USE comdissnew_mod_h
    78  USE control_mod
     
    3940
    4041
    41   include "iniprint.h"
    4242
    4343  !   local:
  • LMDZ6/trunk/libf/dyn3d/dynetat0.f90

    r5281 r5282  
    66! Purpose: Initial state reading.
    77!-------------------------------------------------------------------------------
     8  USE iniprint_mod_h
    89  USE comgeom2_mod_h
    910  USE infotrac,    ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName, &
     
    3132
    3233
    33   include "description.h"
    34   include "iniprint.h"
    35 !===============================================================================
     34  !===============================================================================
    3635! Arguments:
    3736  CHARACTER(LEN=*), INTENT(IN) :: fichnom          !--- FILE NAME
  • LMDZ6/trunk/libf/dyn3d/dynredem.f90

    r5281 r5282  
    2323          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
    2424  USE comgeom2_mod_h
     25  USE iniprint_mod_h
    2526IMPLICIT NONE
    2627
    27 
    28   include "description.h"
    29   include "iniprint.h"
    30 !===============================================================================
     28  !===============================================================================
    3129! Arguments:
    3230  CHARACTER(LEN=*), INTENT(IN) :: fichnom          !--- FILE NAME
     
    174172          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
    175173  USE comgeom_mod_h
     174  USE iniprint_mod_h
    176175IMPLICIT NONE
    177176
    178177
    179   include "description.h"
    180   include "iniprint.h"
    181 !===============================================================================
     178  !===============================================================================
    182179! Arguments:
    183180  CHARACTER(LEN=*), INTENT(IN) :: fichnom              !-- FILE NAME
  • LMDZ6/trunk/libf/dyn3d/fluxstokenc.f90

    r5281 r5282  
    66  ! This routine is designed to work with ioipsl
    77
    8    USE comgeom_mod_h
     8   USE iniprint_mod_h
     9  USE comgeom_mod_h
    910  USE IOIPSL
    1011  !
     
    2223
    2324  include "tracstoke.h"
    24   include "iniprint.h"
    2525
    2626  REAL :: time_step,t_wrt, t_ops
  • LMDZ6/trunk/libf/dyn3d/friction.f90

    r5281 r5282  
    44!=======================================================================
    55SUBROUTINE friction(ucov,vcov,pdt)
     6  USE iniprint_mod_h
    67  USE comgeom2_mod_h
    78  USE control_mod
     
    2627
    2728
    28   include "iniprint.h"
    2929  include "academic.h"
    3030
  • LMDZ6/trunk/libf/dyn3d/gcm.f90

    r5281 r5282  
    55!
    66PROGRAM gcm
     7  USE iniprint_mod_h
    78  USE comgeom_mod_h
    89  USE comdissnew_mod_h
     
    5859  !   Declarations:
    5960  !   -------------
    60   include "description.h"
    61   include "iniprint.h"
    6261  include "tracstoke.h"
    6362
     
    116115  abort_message = 'last timestep reached'
    117116  modname = 'gcm'
    118   descript = 'Run GCM LMDZ'
    119117  lafin    = .FALSE.
    120118  dynhist_file = 'dyn_hist.nc'
  • LMDZ6/trunk/libf/dyn3d/guide_mod.f90

    r5281 r5282  
    88!            F. Codron 01/09
    99!=======================================================================
     10    USE iniprint_mod_h
    1011    USE getparam, only: ini_getparam, fin_getparam, getpar
    1112  USE Write_Field
     
    368369
    369370
    370     INCLUDE "iniprint.h"
    371371
    372372
  • LMDZ6/trunk/libf/dyn3d/iniacademic.f90

    r5281 r5282  
    44SUBROUTINE iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
    55
     6  USE iniprint_mod_h
    67  USE comgeom_mod_h
    78  USE filtreg_mod, ONLY: inifilr
     
    3839
    3940  include "academic.h"
    40   include "iniprint.h"
    4141
    4242  !   Arguments:
  • LMDZ6/trunk/libf/dyn3d/integrd.f90

    r5281 r5282  
    77        )
    88
     9  USE iniprint_mod_h
    910  USE comgeom_mod_h
    1011  use control_mod, only : planet_type
     
    3738
    3839
    39   include "iniprint.h"
    4040
    4141  !   Arguments:
  • LMDZ6/trunk/libf/dyn3d/leapfrog.F90

    r5281 r5282  
    66SUBROUTINE leapfrog(ucov,vcov,teta,ps,masse,phis,q,time_0)
    77  !IM : pour sortir les param. du modele dans un fis. netcdf 110106
     8  USE iniprint_mod_h
    89  USE comgeom_mod_h
    910  USE comdissnew_mod_h
     
    6162  !   Declarations:
    6263  !   -------------
    63   include "description.h"
    64   include "iniprint.h"
    6564  include "academic.h"
    6665
  • LMDZ6/trunk/libf/dyn3d/sw_case_williamson91_6.f90

    r5281 r5282  
    2626  !
    2727  !=======================================================================
     28  USE iniprint_mod_h
    2829  USE comgeom_mod_h
    2930  USE comconst_mod, ONLY: cpp, omeg, rad
     
    4041
    4142
    42   include "iniprint.h"
    4343
    4444  !   Arguments:
  • LMDZ6/trunk/libf/dyn3d/top_bound.F90

    r5281 r5282  
    44SUBROUTINE top_bound(vcov,ucov,teta,masse,dt)
    55
    6   USE comgeom2_mod_h
     6  USE iniprint_mod_h
     7USE comgeom2_mod_h
    78  USE comdissipn_mod_h
    89USE comconst_mod, ONLY: iflag_top_bound, mode_top_bound, &
     
    5859
    5960
    60 INCLUDE "iniprint.h"
    6161
    6262  !   Arguments:
  • LMDZ6/trunk/libf/dyn3d/vlsplt.F90

    r5281 r5282  
    142142USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
    143143          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
     144  USE iniprint_mod_h
    144145IMPLICIT NONE
    145146  !
    146147
    147148
    148   include "iniprint.h"
    149149  !
    150150  !
  • LMDZ6/trunk/libf/dyn3d_common/adaptdt.f90

    r5281 r5282  
    1414
    1515
    16 
    17   include "description.h"
    1816
    1917  !----------------------------------------------------------
  • LMDZ6/trunk/libf/dyn3d_common/advn.F90

    r5281 r5282  
    1515  !
    1616  !   --------------------------------------------------------------------
     17  USE iniprint_mod_h
    1718  USE comgeom_mod_h
    1819  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    2324
    2425
    25   include "iniprint.h"
    2626
    2727  !
     
    147147  !
    148148  !   --------------------------------------------------------------------
     149  USE iniprint_mod_h
    149150  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
    150 USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
     151  USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
    151152          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
    152153IMPLICIT NONE
    153154  !
    154 
    155 
    156   INCLUDE "iniprint.h"
    157155  !
    158156  !
     
    268266  !   --------------------------------------------------------------------
    269267  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
    270 USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
     268  USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
    271269          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
     270  USE iniprint_mod_h
    272271IMPLICIT NONE
    273   !
    274 
    275 
    276   INCLUDE "iniprint.h"
     272
    277273  !
    278274  !
     
    367363  !   --------------------------------------------------------------------
    368364  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
    369 USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
     365  USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
    370366          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
     367  USE iniprint_mod_h
    371368IMPLICIT NONE
    372   !
    373 
    374 
    375   INCLUDE "iniprint.h"
    376369  !
    377370  !
     
    492485  !   --------------------------------------------------------------------
    493486  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
    494 USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
     487  USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
    495488          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
     489  USE iniprint_mod_h
    496490IMPLICIT NONE
    497491  !
    498492
    499493
    500   include "iniprint.h"
    501494  !
    502495  !
     
    759752  !
    760753  !   --------------------------------------------------------------------
     754  USE iniprint_mod_h
    761755  USE comgeom_mod_h
    762756  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    767761
    768762
    769   INCLUDE "iniprint.h"
    770763  !
    771764  !
     
    893886  !
    894887  !   --------------------------------------------------------------------
     888  USE iniprint_mod_h
    895889  USE comgeom_mod_h
    896890  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    901895
    902896
    903   INCLUDE "iniprint.h"
    904897  !
    905898  !
  • LMDZ6/trunk/libf/dyn3d_common/diagedyn.f90

    r5281 r5282  
    5353  !======================================================================
    5454
     55  USE iniprint_mod_h
    5556  USE comgeom_mod_h
    5657  USE control_mod, ONLY : planet_type
     
    6364
    6465
    65   INCLUDE "iniprint.h"
    6666
    6767  ! Ehouarn: for now set these parameters to what is in Earth physics...
  • LMDZ6/trunk/libf/dyn3d_common/disvert.f90

    r5272 r5282  
    33SUBROUTINE disvert()
    44
     5  USE iniprint_mod_h
    56  use ioipsl, only: getin
    67  use new_unit_m, only: new_unit
     
    1718
    1819
    19   include "iniprint.h"
    2020
    2121!-------------------------------------------------------------------------------
  • LMDZ6/trunk/libf/dyn3d_common/disvert_noterre.f90

    r5272 r5282  
    66  !    On l'utilise aussi pour Venus et Titan, legerment modifiee.
    77
     8  USE iniprint_mod_h
    89  use IOIPSL
    910
     
    2021
    2122
    22   include "iniprint.h"
    2323  !
    2424  !=======================================================================
  • LMDZ6/trunk/libf/dyn3d_common/infotrac.f90

    r5271 r5282  
    117117
    118118SUBROUTINE init_infotrac
     119   USE iniprint_mod_h
    119120   USE control_mod, ONLY: planet_type
    120121   USE lmdz_reprobus_wrappers, ONLY: Init_chem_rep_trac
     
    142143! Declarations:
    143144
    144    INCLUDE "iniprint.h"
    145145
    146146!------------------------------------------------------------------------------------------------------------------------------
  • LMDZ6/trunk/libf/dyn3d_common/iniconst.f90

    r5272 r5282  
    44SUBROUTINE iniconst
    55
     6  USE iniprint_mod_h
    67  USE control_mod
    78  use IOIPSL
     
    1011                          unsim, pi, r, kappa, cpp, dtvr, dtphys
    1112  USE comvert_mod, ONLY: disvert_type, pressure_exner
    12  
     13
    1314  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
    1415USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
     
    2324
    2425
    25   include "iniprint.h"
    2626
    2727  character(len=*),parameter :: modname="iniconst"
  • LMDZ6/trunk/libf/dyn3d_common/inidissip.f90

    r5280 r5282  
    1111  !   -------------
    1212
     13  USE iniprint_mod_h
    1314  USE comdissipn_mod_h
    1415  USE control_mod, only : dissip_period,iperiod
     
    2324
    2425
    25   include "iniprint.h"
    2626
    2727  LOGICAL,INTENT(in) :: lstardis
  • LMDZ6/trunk/libf/dyn3d_common/initdynav.f90

    r5281 r5282  
    33subroutine initdynav(day0,anne0,tstep,t_ops,t_wrt)
    44
     5  USE iniprint_mod_h
    56  USE comgeom_mod_h
    67  USE IOIPSL
     
    3940
    4041
    41 
    42   include "description.h"
    43   include "iniprint.h"
    4442
    4543  !   Arguments
  • LMDZ6/trunk/libf/dyn3d_common/initfluxsto.f90

    r5281 r5282  
    66        fileid,filevid,filedid)
    77
    8    USE comgeom_mod_h
     8   USE iniprint_mod_h
     9  USE comgeom_mod_h
    910  USE IOIPSL
    1011  USE comconst_mod, ONLY: pi
     
    4546  !   Declarations
    4647
    47 
    48   include "description.h"
    49   include "iniprint.h"
    5048
    5149  !   Arguments
  • LMDZ6/trunk/libf/dyn3d_common/inithist.f90

    r5281 r5282  
    44subroutine inithist(day0,anne0,tstep,t_ops,t_wrt)
    55
    6    USE comgeom_mod_h
     6   USE iniprint_mod_h
     7  USE comgeom_mod_h
    78  USE IOIPSL
    89   USE infotrac, ONLY : nqtot
     
    4445  !   Declarations
    4546
    46 
    47   include "description.h"
    48   include "iniprint.h"
    4947
    5048  !   Arguments
  • LMDZ6/trunk/libf/dyn3d_common/interpre.f90

    r5281 r5282  
    1717
    1818
    19 
    20   include "description.h"
    2119
    2220  !---------------------------------------------------
  • LMDZ6/trunk/libf/dyn3d_common/sortvarc.f90

    r5281 r5282  
    66        vcov )
    77
     8  USE iniprint_mod_h
    89  USE comgeom_mod_h
    910  USE control_mod, ONLY: resetvarc
     
    3637
    3738
    38   INCLUDE "iniprint.h"
    3939
    4040  !   Arguments:
  • LMDZ6/trunk/libf/dyn3d_common/traceurpole.f90

    r5281 r5282  
    1111implicit none
    1212
    13 
    14 
    15   include "description.h"
    1613
    1714
  • LMDZ6/trunk/libf/dyn3d_common/writedynav.f90

    r5281 r5282  
    33subroutine writedynav(time, vcov, ucov, teta, ppk, phi, q, masse, ps, phis)
    44
     5  USE iniprint_mod_h
    56  USE comgeom_mod_h
    67  USE ioipsl
     
    3334  !   Declarations
    3435
    35 
    36   include "description.h"
    37   include "iniprint.h"
    3836
    3937  !   Arguments
  • LMDZ6/trunk/libf/dyn3d_common/writehist.f90

    r5281 r5282  
    33!
    44subroutine writehist(time,vcov,ucov,teta,phi,q,masse,ps,phis)
     5  USE iniprint_mod_h
    56  USE comgeom_mod_h
    67  USE ioipsl
     
    3536  !
    3637  !   Declarations
    37 
    38   include "description.h"
    39   include "iniprint.h"
    4038
    4139  !
  • LMDZ6/trunk/libf/dyn3dmem/abort_gcm.f90

    r5268 r5282  
    66SUBROUTINE abort_gcm(modname, message, ierr)
    77
     8  USE iniprint_mod_h
    89  USE IOIPSL
    910
    1011  USE parallel_lmdz
    11   INCLUDE "iniprint.h"
    1212
    1313  !
  • LMDZ6/trunk/libf/dyn3dmem/advtrac_loc.f90

    r5281 r5282  
    3030
    3131
    32    include "description.h"
    33 !   include "iniprint.h"
     32   !   include "iniprint.h"
    3433
    3534   !---------------------------------------------------------------------------
  • LMDZ6/trunk/libf/dyn3dmem/bilan_dyn_loc.f90

    r5281 r5282  
    1010  !             vQ..A=Cp T + L * ...
    1111
     12  USE iniprint_mod_h
    1213  USE comgeom2_mod_h
    1314  USE IOIPSL
     
    2728
    2829
    29   include "iniprint.h"
    3030
    3131  !====================================================================
  • LMDZ6/trunk/libf/dyn3dmem/call_calfis_mod.f90

    r5272 r5282  
    6868    CALL allocate_u(dqfi,llm,nqtot,d)
    6969    CALL allocate_u(dpfi,d)
    70  
     70
    7171  END SUBROUTINE call_calfis_allocate
    72  
    73  
     72
     73
    7474  SUBROUTINE call_calfis(itau,lafin,ucov_dyn,vcov_dyn,teta_dyn,masse_dyn,ps_dyn, &
    7575                         phis_dyn,q_dyn,flxw_dyn)
     
    9494  USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_PHYS, CPPKEY_DEBUGIO
    9595  USE strings_mod, ONLY: int2str
    96  
     96  USE iniprint_mod_h
    9797  IMPLICIT NONE
    98     INCLUDE "iniprint.h"
    9998
    10099    INTEGER,INTENT(IN) :: itau ! (time) iteration step number
  • LMDZ6/trunk/libf/dyn3dmem/conf_gcm.F90

    r5280 r5282  
    44SUBROUTINE conf_gcm( tapedef, etatinit )
    55
     6  USE iniprint_mod_h
    67  USE comdissnew_mod_h
    78  USE control_mod
     
    4445
    4546
    46   include "iniprint.h"
    4747
    4848  !   local:
  • LMDZ6/trunk/libf/dyn3dmem/dynetat0_loc.f90

    r5281 r5282  
    66! Purpose: Initial state reading.
    77!-------------------------------------------------------------------------------
     8  USE iniprint_mod_h
    89  USE comgeom_mod_h
    910  USE parallel_lmdz
     
    3132
    3233
    33   include "description.h"
    34   include "iniprint.h"
    35 !===============================================================================
     34  !===============================================================================
    3635! Arguments:
    3736  CHARACTER(LEN=*), INTENT(IN) :: fichnom          !--- FILE NAME
  • LMDZ6/trunk/libf/dyn3dmem/dynredem_loc.f90

    r5281 r5282  
    2727          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
    2828  USE comgeom_mod_h
     29  USE iniprint_mod_h
    2930  IMPLICIT NONE
    3031
    31   include "description.h"
    32   include "iniprint.h"
    33 !===============================================================================
     32  !===============================================================================
    3433! Arguments:
    3534  CHARACTER(LEN=*), INTENT(IN) :: fichnom          !--- FILE NAME
     
    180179
    181180  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
    182 USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
     181  USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
    183182          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
     183  USE iniprint_mod_h
    184184IMPLICIT NONE
    185185
    186186
    187   include "description.h"
    188   include "iniprint.h"
    189 !===============================================================================
     187  !===============================================================================
    190188! Arguments:
    191189  CHARACTER(LEN=*), INTENT(IN) :: fichnom              !-- FILE NAME
  • LMDZ6/trunk/libf/dyn3dmem/friction_loc.f90

    r5281 r5282  
    44!=======================================================================
    55SUBROUTINE friction_loc(ucov,vcov,pdt)
     6  USE iniprint_mod_h
    67  USE comgeom2_mod_h
    78  USE parallel_lmdz
     
    2728
    2829
    29   include "iniprint.h"
    3030  include "academic.h"
    3131
  • LMDZ6/trunk/libf/dyn3dmem/gcm.F90

    r5281 r5282  
    1313!  USE mod_interface_dyn_phys, ONLY: init_interface_dyn_phys
    1414!#endif
     15  USE iniprint_mod_h
    1516  USE comgeom_mod_h
    1617  USE comdissnew_mod_h
     
    6263  !   Declarations:
    6364  !   -------------
    64   include "description.h"
    65   include "iniprint.h"
    6665  include "tracstoke.h"
    6766
     
    122121  abort_message = 'last timestep reached'
    123122  modname = 'gcm'
    124   descript = 'Run GCM LMDZ'
    125123  lafin    = .FALSE.
    126124  dynhist_file = 'dyn_hist'
  • LMDZ6/trunk/libf/dyn3dmem/iniacademic_loc.f90

    r5281 r5282  
    44SUBROUTINE iniacademic_loc(vcov,ucov,teta,q,masse,ps,phis,time_0)
    55
     6  USE iniprint_mod_h
    67  USE comgeom_mod_h
    78  USE filtreg_mod, ONLY: inifilr
     
    3940
    4041  include "academic.h"
    41   include "iniprint.h"
    4242
    4343  !   Arguments:
  • LMDZ6/trunk/libf/dyn3dmem/initdynav_loc.f90

    r5281 r5282  
    55
    66  ! This routine needs IOIPSL
    7    USE comgeom_mod_h
     7   USE iniprint_mod_h
     8  USE comgeom_mod_h
    89  USE IOIPSL
    910
     
    5051
    5152
    52   include "description.h"
    53   include "iniprint.h"
    54 
    5553  !   Arguments
    5654  !
  • LMDZ6/trunk/libf/dyn3dmem/initfluxsto_p.f90

    r5281 r5282  
    77
    88  ! This routine needs IOIPSL
    9    USE comgeom_mod_h
     9   USE iniprint_mod_h
     10  USE comgeom_mod_h
    1011  USE IOIPSL
    1112
     
    5051  !   Declarations
    5152
    52 
    53   include "description.h"
    54   include "iniprint.h"
    5553
    5654  !   Arguments
  • LMDZ6/trunk/libf/dyn3dmem/inithist_loc.f90

    r5281 r5282  
    55
    66  ! This routine needs IOIPSL
    7    USE comgeom_mod_h
     7   USE iniprint_mod_h
     8  USE comgeom_mod_h
    89  USE IOIPSL
    910
     
    4748  !   Declarations
    4849
    49 
    50   include "description.h"
    51   include "iniprint.h"
    5250
    5351  !   Arguments
  • LMDZ6/trunk/libf/dyn3dmem/integrd_loc.f90

    r5281 r5282  
    55        (  nq,vcovm1,ucovm1,tetam1,psm1,massem1, &
    66        dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps0,masse,phis) !,finvmaold)
     7  USE iniprint_mod_h
    78  USE comgeom_mod_h
    89  USE parallel_lmdz
     
    4041
    4142
    42   include "iniprint.h"
    4343
    4444  !   Arguments:
  • LMDZ6/trunk/libf/dyn3dmem/leapfrog_loc.f90

    r5281 r5282  
    22        masse0,phis0,q0,time_0)
    33
    4    USE comgeom_mod_h
     4   USE iniprint_mod_h
     5  USE comgeom_mod_h
    56  USE comdissnew_mod_h
    67   USE misc_mod
     
    7778  !   Declarations:
    7879  !   -------------
    79   include "description.h"
    80   include "iniprint.h"
    8180  include "academic.h"
    8281
  • LMDZ6/trunk/libf/dyn3dmem/parallel_lmdz.F90

    r5272 r5282  
    8383 
    8484    subroutine init_parallel
    85     USE vampir
     85    USE iniprint_mod_h
     86      USE vampir
    8687    USE lmdz_mpi
    8788    USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    9192
    9293
    93       INCLUDE "iniprint.h"
    9494
    9595      integer :: ierr
     
    648648
    649649    subroutine Gather_Field(Field,ij,ll,rank)
     650    USE iniprint_mod_h
    650651    USE lmdz_mpi
    651652    USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    655656
    656657
    657     INCLUDE "iniprint.h"
    658658      INTEGER :: ij,ll,rank
    659659      REAL, dimension(ij,ll) :: Field
  • LMDZ6/trunk/libf/dyn3dmem/qminimum_loc.f90

    r5272 r5282  
    33!
    44SUBROUTINE qminimum_loc( q,nqtot,deltap )
     5  USE iniprint_mod_h
    56  USE parallel_lmdz
    67  USE infotrac, ONLY: niso, ntiso, iqIsoPha, tracers, addPhase, &
     
    1718
    1819
    19   include "iniprint.h"
    2020  !
    2121  INTEGER :: nqtot ! CRisi: on remplace nq par nqtot
  • LMDZ6/trunk/libf/dyn3dmem/sw_case_williamson91_6_loc.f90

    r5281 r5282  
    2626  !
    2727  !=======================================================================
     28  USE iniprint_mod_h
    2829  USE comgeom_mod_h
    2930  USE parallel_lmdz
     
    4142
    4243
    43   include "iniprint.h"
    4444
    4545  !   Arguments:
  • LMDZ6/trunk/libf/dyn3dmem/top_bound_loc.f90

    r5281 r5282  
    33!
    44SUBROUTINE top_bound_loc(vcov,ucov,teta,masse,dt)
     5  USE iniprint_mod_h
    56  USE comgeom2_mod_h
    67  USE comdissipn_mod_h
     
    5859
    5960
    60   INCLUDE "iniprint.h"
    6161
    6262  !   Arguments:
  • LMDZ6/trunk/libf/dyn3dmem/vlsplt_loc.F90

    r5281 r5282  
    1313  !
    1414  !   --------------------------------------------------------------------
     15  USE iniprint_mod_h
    1516  USE parallel_lmdz
    1617  USE infotrac, ONLY : nqtot,tracers, & ! CRisi                 &
     
    2324
    2425
    25   include "iniprint.h"
    2626  !
    2727  !
     
    887887  !
    888888  !   --------------------------------------------------------------------
     889  USE iniprint_mod_h
    889890  USE parallel_lmdz
    890891  USE vlz_mod
     
    899900
    900901
    901   include "iniprint.h"
    902902  !
    903903  !
  • LMDZ6/trunk/libf/dyn3dmem/vlspltqs_loc.F90

    r5281 r5282  
    422422  !
    423423  !   --------------------------------------------------------------------
     424  USE iniprint_mod_h
    424425  USE comgeom_mod_h
    425426  USE parallel_lmdz
     
    434435
    435436
    436   include "iniprint.h"
    437437  !
    438438  !
  • LMDZ6/trunk/libf/dyn3dmem/writedyn_xios.f90

    r5281 r5282  
    55     &                           masse,ps,phis)
    66
     7      USE iniprint_mod_h
    78      USE comgeom_mod_h
    89      USE lmdz_xios
     
    4041
    4142
    42       include "description.h"
    43       include "iniprint.h"
    44 
    45 !
     43      !
    4644!   Arguments
    4745!
  • LMDZ6/trunk/libf/dyn3dmem/writedynav_loc.f90

    r5281 r5282  
    66
    77  ! This routine needs IOIPSL
     8  USE iniprint_mod_h
    89  USE comgeom_mod_h
    910  USE ioipsl
     
    4950
    5051
    51   include "description.h"
    52   include "iniprint.h"
    53 
    5452  !
    5553  !   Arguments
  • LMDZ6/trunk/libf/dyn3dmem/writehist_loc.f90

    r5281 r5282  
    66
    77  ! This routine needs IOIPSL
     8  USE iniprint_mod_h
    89  USE comgeom_mod_h
    910  USE ioipsl
     
    4950
    5051
    51   include "description.h"
    52   include "iniprint.h"
    53 
    5452  !
    5553  !   Arguments
  • LMDZ6/trunk/libf/dynphy_lonlat/calfis.f90

    r5281 r5282  
    2929  !    Auteur :  P. Le Van, F. Hourdin
    3030  !   .........
     31  USE iniprint_mod_h
    3132  USE comgeom2_mod_h
    3233  USE infotrac, ONLY: nqtot, tracers
     
    9596  PARAMETER( ngridmx = 2+(jjm-1)*iim - 1/jjm   )
    9697
    97   include "iniprint.h"
    9898
    9999  !    Arguments :
  • LMDZ6/trunk/libf/dynphy_lonlat/calfis_loc.F90

    r5281 r5282  
    5151  USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_PHYS
    5252#ifdef CPP_PARA
     53  USE iniprint_mod_h
    5354  USE comgeom2_mod_h
    5455  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    112113  PARAMETER( ngridmx = 2+(jjm-1)*iim - 1/jjm   )
    113114
    114   include "iniprint.h"
    115115  !    Arguments :
    116116  !    -----------
  • LMDZ6/trunk/libf/dynphy_lonlat/inigeomphy_mod.f90

    r5268 r5282  
    99                     nbp, communicator, &
    1010                     rlatu,rlatv,rlonu,rlonv,aire,cu,cv)
     11  USE iniprint_mod_h
    1112  USE mod_grid_phy_lmdz, ONLY: klon_glo,  & ! number of atmospheric columns (on full grid)
    1213                               regular_lonlat, &  ! regular longitude-latitude grid type
     
    3435  ! =======================================================================
    3536
    36   include "iniprint.h"
    3737
    3838  INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers
  • LMDZ6/trunk/libf/dynphy_lonlat/phydev/iniphysiq_mod.f90

    r5268 r5282  
    1111                     rlatu,rlatv,rlonu,rlonv,aire,cu,cv, &
    1212                     prad,pg,pr,pcpp,iflag_phys)
     13  USE iniprint_mod_h
    1314  USE dimphy, ONLY: init_dimphy
    1415  USE inigeomphy_mod, ONLY: inigeomphy
     
    2223  !
    2324  !=======================================================================
    24   !   Initialisation of the physical constants and some positional and 
     25  !   Initialisation of the physical constants and some positional and
    2526  !   geometrical arrays for the physics
    2627  !=======================================================================
    27  
    28  
    29   include "iniprint.h"
     28
     29
    3030
    3131  REAL,INTENT(IN) :: prad ! radius of the planet (m)
  • LMDZ6/trunk/libf/dynphy_lonlat/phylmd/ce0l.F90

    r5281 r5282  
    3939#endif
    4040
     41  USE iniprint_mod_h
    4142  USE comgeom2_mod_h
    4243  USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, g, kappa, omeg, r, rad, &
     
    5657
    5758
    58   include "iniprint.h"
    5959 
    6060  REAL               :: masque(iip1,jjp1)             !--- CONTINENTAL MASK
  • LMDZ6/trunk/libf/dynphy_lonlat/phylmd/etat0dyn_netcdf.F90

    r5281 r5282  
    4646  USE comdissnew_mod_h
    4747  USE comgeom2_mod_h
     48  USE iniprint_mod_h
    4849IMPLICIT NONE
    4950
     
    5152  PUBLIC :: etat0dyn_netcdf
    5253
    53   include "iniprint.h"
    5454
    5555
  • LMDZ6/trunk/libf/dynphy_lonlat/phylmd/etat0phys_netcdf.f90

    r5281 r5282  
    5858  USE dimsoil_mod_h, ONLY: nsoilmx
    5959  USE comgeom2_mod_h
     60  USE clesphys_mod_h
     61  USE iniprint_mod_h
    6062  PRIVATE
    6163  PUBLIC :: etat0phys_netcdf
    6264
    63   include "iniprint.h"
    64   include "clesphys.h"
    6565  REAL, SAVE :: deg2rad
    6666  REAL, SAVE, ALLOCATABLE :: tsol(:)
  • LMDZ6/trunk/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90

    r5281 r5282  
    3838  USE bands, ONLY : distrib_phys
    3939#endif
     40  USE iniprint_mod_h
    4041  USE comgeom_mod_h
    4142  USE mod_phys_lmdz_omp_data, ONLY: klon_omp
     
    5556
    5657
    57   include "iniprint.h"
    5858  include "tracstoke.h"
    5959
  • LMDZ6/trunk/libf/dynphy_lonlat/phylmd/init_ssrf_m.f90

    r5281 r5282  
    33!*******************************************************************************
    44
     5  USE iniprint_mod_h
    56  USE comgeom2_mod_h
    67  USE indice_sol_mod,     ONLY: is_ter, is_oce, is_oce, is_lic, epsfra
     
    2021  PRIVATE
    2122  PUBLIC :: start_init_subsurf
    22   include "iniprint.h"
    2323
    2424CONTAINS
  • LMDZ6/trunk/libf/dynphy_lonlat/phylmd/limit_netcdf.F90

    r5281 r5282  
    7070!-------------------------------------------------------------------------------
    7171#ifndef CPP_1D
     72  USE iniprint_mod_h
    7273  USE comgeom2_mod_h
    7374  USE indice_sol_mod
     
    8990!-------------------------------------------------------------------------------
    9091! Arguments:
    91   include "iniprint.h"
    9292
    9393
  • LMDZ6/trunk/libf/misc/iniprint_mod_h.f90

    r5281 r5282  
    1 !
    2 ! $Header$
    3 !
    4 !
    5 ! gestion des impressions de sorties et de débogage
    6 ! lunout:    unité du fichier dans lequel se font les sorties
    7 !                           (par defaut 6, la sortie standard)
    8 ! prt_level: niveau d'impression souhaité (0 = minimum)
    9 !
    10       INTEGER lunout, prt_level
    11       COMMON /comprint/ lunout, prt_level
     1! Replaces iniprint.h
     2
     3MODULE iniprint_mod_h
     4  ! gestion des impressions de sorties et de débogage
     5  ! lunout:    unité du fichier dans lequel se font les sorties
     6  !                           (par defaut 6, la sortie standard)
     7  ! prt_level: niveau d'impression souhaité (0 = minimum)
     8
     9  IMPLICIT NONE; PRIVATE
     10  PUBLIC lunout, prt_level
     11
     12  INTEGER :: lunout, prt_level
     13
     14END MODULE iniprint_mod_h
  • LMDZ6/trunk/libf/misc/wxios.F90

    r5206 r5282  
    509509        CHARACTER (len=*), INTENT(IN), OPTIONAL :: positif
    510510        REAL, DIMENSION(axis_size, 2), INTENT(IN), OPTIONAL :: bnds
    511        
     511
    512512!        TYPE(xios_axisgroup) :: axgroup
    513513!        TYPE(xios_axis) :: ax
    514 !        CHARACTER(len=50) :: axis_id 
    515        
     514!        CHARACTER(len=50) :: axis_id
     515
    516516!        IF (len_trim(axisgroup_id).gt.len(axis_id)) THEN
    517517!          WRITE(lunout,*) "wxios_add_vaxis: error, size of axis_id too small!!"
     
    520520!        ENDIF
    521521!        axis_id=trim(axisgroup_id)
    522        
     522
    523523        !On récupère le groupe d'axes qui va bien:
    524524        !CALL xios_get_axisgroup_handle(axisgroup_id, axgroup)
    525        
     525
    526526        !On ajoute l'axe correspondant à ce fichier:
    527527        !CALL xios_add_axis(axgroup, ax, TRIM(ADJUSTL(axis_id)))
    528        
     528
    529529        !Et on le parametrise:
    530530        !CALL xios_set_axis_attr_hdl(ax, size=axis_size, value=axis_value)
    531        
     531
    532532        ! Ehouarn: New way to declare axis, without axis_group:
    533533        if (PRESENT(positif) .AND. PRESENT(bnds)) then
     
    552552
    553553    END SUBROUTINE wxios_add_vaxis
    554    
    555    
     554
     555
    556556    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    557557    ! Pour déclarer un fichier  !!!!!!!!!!!!!!!!!!!
     
    564564        CHARACTER(len=*), INTENT(IN) :: ffreq
    565565        INTEGER, INTENT(IN) :: flvl
    566        
     566
    567567        TYPE(xios_file) :: x_file
    568568        TYPE(xios_filegroup) :: x_fg
    569569        TYPE(xios_duration) :: nffreq
    570        
     570
    571571        !On regarde si le fichier n'est pas défini par XML:
    572572        IF (.NOT.xios_is_valid_file(fname)) THEN
     
    574574            CALL xios_get_handle("defile", x_fg)
    575575            CALL xios_add_child(x_fg, x_file, fname)
    576        
     576
    577577            !On reformate la fréquence:
    578578            CALL reformadate(ffreq, nffreq)
    579        
     579
    580580            !On configure:
    581581            CALL xios_set_attr(x_file, name="X"//fname,&
    582582                output_freq=nffreq, output_level=flvl, enabled=.TRUE.)
    583        
     583
    584584            IF (xios_is_valid_file("X"//fname)) THEN
    585585                IF (prt_level >= 10) THEN
     
    599599        END IF
    600600    END SUBROUTINE wxios_add_file
    601    
     601
    602602    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    603603    ! Pour créer un champ      !!!!!!!!!!!!!!!!!!!!
     
    605605    SUBROUTINE wxios_add_field(fieldname, fieldgroup, fieldlongname, fieldunit)
    606606        USE netcdf, only: nf90_fill_real
    607 
    608         IMPLICIT NONE
    609         INCLUDE 'iniprint.h'
     607        USE iniprint_mod_h
     608
     609        IMPLICIT NONE
    610610       
    611611        CHARACTER(len=*), INTENT(IN) :: fieldname
  • LMDZ6/trunk/libf/phylmd/Dust/phys_output_write_spl_mod.F90

    r5274 r5282  
    44MODULE phys_output_write_spl_mod
    55
    6 !JE20150620<<
    7 !JE20150620>>
    8 !JE20150620<<
    9 
    10   USE time_phylmdz_mod, ONLY: day_step_phy, start_time, itau_phy
     6
     7    USE time_phylmdz_mod, ONLY: day_step_phy, start_time, itau_phy
    118
    129  USE phytracr_spl_mod, ONLY : ok_chimeredust, id_prec, id_fine, id_coss, &
     
    6865       flux_sparam_sscoa,u10m_ss,v10m_ss
    6966
    70   USE dustemission_mod, ONLY : m1dflux, m2dflux, m3dflux 
     67  USE dustemission_mod, ONLY : m1dflux, m2dflux, m3dflux
    7168
    7269!  USE phytrac_mod, ONLY : d_tr_cl, d_tr_th, d_tr_cv, d_tr_lessi_impa, &
     
    8077  ! Author: Ulysse GERARD (effective implementation)
    8178
    82 CONTAINS 
     79CONTAINS
    8380
    8481  ! ug Routine pour définir (lors du premier passageà) ET sortir les variables
     
    195192         o_ptconvth, o_lmaxth, o_dtvdf, &
    196193         o_dtdis, o_dqvdf, o_dteva, o_dqeva, &
    197          o_ptconv, o_ratqs, o_dtthe, & 
     194         o_ptconv, o_ratqs, o_dtthe, &
    198195         o_duthe, o_dvthe, o_ftime_th, &
    199196         o_f_th, o_e_th, o_w_th, o_q_th, &
     
    409406          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
    410407          , RALPD, RBETD, RGAMD
     408    USE clesphys_mod_h
     409    USE iniprint_mod_h
    411410IMPLICIT NONE
    412411
    413412!   INCLUDE "temps.h"
    414     INCLUDE "clesphys.h"
    415413    INCLUDE "alpale.h"
    416414    INCLUDE "compbl.h"
    417415
    418416
    419     include "iniprint.h"
    420417
    421418    ! Input
  • LMDZ6/trunk/libf/phylmd/Dust/splaeropt_6bands_rrtm.f90

    r5268 r5282  
    66     tau_allaer, piz_allaer, cg_allaer )
    77
     8  USE clesphys_mod_h
    89  USE dimphy
    910  USE aero_mod
     
    1617  IMPLICIT NONE
    1718
    18   INCLUDE "clesphys.h"
    1919  !
    2020  ! Input arguments:
  • LMDZ6/trunk/libf/phylmd/Dust/splaeropt_lw_rrtm.f90

    r5268 r5282  
    88SUBROUTINE SPLAEROPT_LW_RRTM(ok_alw,zdm,tr_seri)
    99
     10  USE clesphys_mod_h
    1011  USE dimphy
    1112  USE aero_mod
     
    1617  IMPLICIT NONE
    1718
    18   INCLUDE "clesphys.h"
    1919  !
    2020  ! Input arguments:
  • LMDZ6/trunk/libf/phylmd/Dust/splaerosol_optic_rrtm.f90

    r5268 r5282  
    1111  !
    1212
     13  USE clesphys_mod_h
    1314  USE dimphy
    1415  USE aero_mod
     
    1819  IMPLICIT NONE
    1920
    20   INCLUDE "clesphys.h"
    2121
    2222
  • LMDZ6/trunk/libf/phylmd/StratAer/calcaerosolstrato_rrtm.f90

    r5272 r5282  
    44SUBROUTINE calcaerosolstrato_rrtm(pplay,t_seri,paprs,debut)
    55
     6  USE clesphys_mod_h
     7  USE iniprint_mod_h
    68  USE phys_state_var_mod, ONLY: tau_aero_sw_rrtm, piz_aero_sw_rrtm, cg_aero_sw_rrtm, tau_aero_lw_rrtm
    79  USE phys_local_var_mod, ONLY: mdw, tausum_aero, tausum_strat, tau_strat_550, tau_strat_1020, stratomask
     
    1719
    1820
    19   INCLUDE "clesphys.h"
    2021
    21   INCLUDE "iniprint.h"
    2222
    2323! Variable input
  • LMDZ6/trunk/libf/phylmd/acama_gwd_rando_m.f90

    r5274 r5282  
    44module ACAMA_GWD_rando_m
    55
    6   implicit none
     6  USE clesphys_mod_h
     7    implicit none
    78
    89contains
     
    1213
    1314    ! Parametrization of the momentum flux deposition due to a discrete
    14     ! number of gravity waves. 
     15    ! number of gravity waves.
    1516    ! Author: F. Lott, A. de la Camara
    1617    ! July, 24th, 2014
     
    3940
    4041
    41     include "clesphys.h"
    4242!  OFFLINE:
    4343!   include "dimensions_mod.f90"
  • LMDZ6/trunk/libf/phylmd/add_phys_tend_mod.f90

    r5274 r5282  
    9999!======================================================================
    100100
     101USE clesphys_mod_h
    101102USE dimphy, ONLY: klon, klev
    102103USE phys_state_var_mod, ONLY : phys_tstep
     
    122123IMPLICIT none
    123124
    124 INCLUDE "clesphys.h"
    125125
    126126! Arguments :
     
    515515!======================================================================
    516516
    517 USE phys_state_var_mod, ONLY : phys_tstep, ftsol
     517USE clesphys_mod_h
     518  USE phys_state_var_mod, ONLY : phys_tstep, ftsol
    518519USE geometry_mod, ONLY: longitude_deg, latitude_deg
    519520USE print_control_mod, ONLY: prt_level
     
    535536IMPLICIT none
    536537
    537   include "clesphys.h"
    538538
    539539! Arguments :
  • LMDZ6/trunk/libf/phylmd/albedo.f90

    r5274 r5282  
    22module albedo
    33
    4   USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
     4  USE clesphys_mod_h
     5    USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
    56          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
    67          , R_ecc, R_peri, R_incl                                      &
     
    2021  SUBROUTINE alboc(rjour, rlat, albedo)
    2122    USE dimphy
     23    USE clesphys_mod_h
    2224    ! ======================================================================
    2325    ! Auteur(s): Z.X. Li (LMD/CNRS) (adaptation du GCM du LMD)
     
    3133    ! albedo (out,R): albedo obtenu (de 0 a 1)
    3234    ! ======================================================================
    33 
    34     include "clesphys.h"
    3535
    3636    INTEGER npts ! il controle la precision de l'integration
     
    147147    ! albedo (out): albedo de surface de l'ocean
    148148    ! ======================================================================
    149     include "clesphys.h"
    150149    REAL, intent(in):: rmu0(klon)
    151150    real, intent(out):: albedo(klon)
  • LMDZ6/trunk/libf/phylmd/albsno.f90

    r5268 r5282  
    44SUBROUTINE albsno(klon, knon, dtime, agesno, alb_neig_grid, precip_snow)
    55
     6  USE clesphys_mod_h
    67  IMPLICIT NONE
    78
    8   INCLUDE "clesphys.h"
    99
    1010! Input arguments
  • LMDZ6/trunk/libf/phylmd/calcul_fluxs_mod.f90

    r5274 r5282  
    44MODULE calcul_fluxs_mod
    55
    6   IMPLICIT NONE
     6  USE clesphys_mod_h
     7    IMPLICIT NONE
    78
    89CONTAINS
     
    1415       tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, &
    1516       sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol, rhoa)
    16  
    17    
     17
     18
    1819    USE dimphy, ONLY : klon
    1920    USE indice_sol_mod
     
    3233          , RALPD, RBETD, RGAMD
    3334
    34     INCLUDE "clesphys.h"
    3535
    3636! Cette routine calcule les fluxs en h et q a l'interface et eventuellement
     
    299299       flux_u1, flux_v1)
    300300
     301    USE clesphys_mod_h
    301302    USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
    302303          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
     
    313314USE dimphy
    314315
    315     INCLUDE "clesphys.h"
    316316
    317317! Input arguments
  • LMDZ6/trunk/libf/phylmd/calltherm.F90

    r5217 r5282  
    4040#endif   
    4141#endif
    42 
     42      USE clesphys_mod_h
    4343      implicit none
    44       include "clesphys.h"
    4544      include "thermcell_old.h"
    4645
  • LMDZ6/trunk/libf/phylmd/carbon_cycle_mod.f90

    r5271 r5282  
    226226
    227227    USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     228    USE clesphys_mod_h
    228229IMPLICIT NONE
    229     INCLUDE "clesphys.h"
    230230
    231231! Local variables
     
    282282    USE mod_phys_lmdz_omp_transfert
    283283    USE dimphy, ONLY: klon
     284    USE iniprint_mod_h
     285    USE clesphys_mod_h
    284286
    285287    IMPLICIT NONE
     
    329331! Declarations
    330332
    331   INCLUDE "clesphys.h"
    332 
    333   INCLUDE "iniprint.h"
     333
    334334
    335335! Local variables
  • LMDZ6/trunk/libf/phylmd/cdrag_mod.f90

    r5274 r5282  
    4141          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
    4242          , RALPD, RBETD, RGAMD
     43  USE clesphys_mod_h
    4344
    4445  IMPLICIT NONE
     
    127128!******************************************************************
    128129  INCLUDE "YOETHF.h"
    129   INCLUDE "clesphys.h"
    130130
    131131
  • LMDZ6/trunk/libf/phylmd/change_srf_frac_mod.f90

    r5274 r5282  
    44MODULE change_srf_frac_mod
    55
    6   IMPLICIT NONE
     6  USE clesphys_mod_h
     7    IMPLICIT NONE
    78
    89CONTAINS
    9 ! 
     10!
    1011! Change Surface Fractions
    1112! Author J Ghattas 2008
     
    1415        pctsrf, evap, z0m, z0h, agesno,              &
    1516        alb_dir, alb_dif, tsurf, ustar, u10m, v10m, pbl_tke)
    16    
    17 
    18 
    19 !
    20 ! This subroutine is called from physiq.F at each timestep. 
     17
     18
     19
     20!
     21! This subroutine is called from physiq.F at each timestep.
    2122! 1- For each type of ocean (force, slab, couple) receive new fractions only if
    22 !    it's time to modify (is_modified=true). Otherwise nothing is done (is_modified=false).   
     23!    it's time to modify (is_modified=true). Otherwise nothing is done (is_modified=false).
    2324! If received new fraction :
    24 ! 2- Tests and ajustements are done on the fractions 
    25 ! 3- Initialize variables where a new fraction(new or melted ice) has appered, 
     25! 2- Tests and ajustements are done on the fractions
     26! 3- Initialize variables where a new fraction(new or melted ice) has appered,
    2627!
    2728
     
    4950
    5051!albedo SB >>>
    51     include "clesphys.h"
    5252!albedo SB <<<
    5353
  • LMDZ6/trunk/libf/phylmd/clcdrag.f90

    r5274 r5282  
    77     pcfm, pcfh)
    88
     9  USE clesphys_mod_h
    910  USE dimphy
    1011  USE indice_sol_mod
     
    5556
    5657  INCLUDE "YOETHF.h"
    57   INCLUDE "clesphys.h"
    5858!
    5959! Quelques constantes et options:
  • LMDZ6/trunk/libf/phylmd/clesphys_mod_h.f90

    r5281 r5282  
    1 ! $Id$
    2 !
    3 !  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
    4 !                 veillez \`a n'utiliser que des ! pour les commentaires
    5 !                 et \`a bien positionner les & des lignes de continuation
    6 !                 (les placer en colonne 6 et en colonne 73)
    7 !
    8 !..include cles_phys.h
    9 
    10        ! threshold on to activate SSO schemes
    11        REAL zrel_oro_t, zpmm_orodr_t, zpmm_orolf_t, zstd_orodr_t
    12        INTEGER iflag_cycle_diurne
    13        LOGICAL soil_model,new_oliq,ok_orodr,ok_orolf
    14        LOGICAL ok_limitvrai
    15        LOGICAL ok_all_xml
    16        LOGICAL ok_lwoff
    17        INTEGER nbapp_rad, iflag_con, nbapp_cv, nbapp_wk, iflag_ener_conserv
    18        REAL co2_ppm, co2_ppm0, solaire
    19        INTEGER iflag_thermals,nsplit_thermals
    20        INTEGER iflag_physiq
    21        REAL tau_thermals
    22 
    23 !FC
    24        REAL Cd_frein
    25        LOGICAL ok_suntime_rrtm
    26        REAL(kind=8) RCO2, RCH4, RN2O, RCFC11, RCFC12 
    27        REAL(kind=8) RCO2_act, RCH4_act, RN2O_act, RCFC11_act, RCFC12_act 
    28        REAL(kind=8) CH4_ppb, N2O_ppb, CFC11_ppt, CFC12_ppt
    29 !IM ajout CFMIP2/CMIP5
    30        REAL(kind=8) RCO2_per,RCH4_per,RN2O_per,RCFC11_per,RCFC12_per
    31        REAL(kind=8) CH4_ppb_per,N2O_ppb_per,CFC11_ppt_per,CFC12_ppt_per
    32 
    33 !OM ---> correction du bilan d'eau global
    34 !OM Correction sur precip KE
    35        REAL cvl_corr
    36 !OM Fonte calotte dans bilan eau
    37        LOGICAL ok_lic_melt
    38 !OB Depot de vapeur d eau sur la calotte pour le bilan eau
    39        LOGICAL ok_lic_cond
    40 
    41 !IM simulateur ISCCP
    42        INTEGER top_height, overlap
    43 !IM seuils cdrm, cdrh
    44        REAL cdmmax, cdhmax
    45 !IM pour les params différentes Olivier Torres
    46        INTEGER choix_bulk, nit_bulk, kz0
    47 !IM param. stabilite s/ terres et en dehors
    48        REAL ksta, ksta_ter, f_ri_cd_min
    49 !IM ok_kzmin : clef calcul Kzmin dans la CL de surface cf FH
    50        LOGICAL ok_kzmin
    51 !IM, MAFo fmagic, pmagic : parametres - additionnel et multiplicatif -
    52 !                          pour regler l albedo sur ocean
    53        REAL fmagic, pmagic
    54 ! Hauteur (imposee) du contenu en eau du sol
    55            REAL qsol0,albsno0,evap0
    56 ! Frottement au sol (Cdrag)
    57        Real f_cdrag_ter,f_cdrag_oce
    58        REAL min_wind_speed,f_gust_wk,f_gust_bl,f_qsat_oce,f_z0qh_oce
    59        REAL z0m_seaice,z0h_seaice
    60        REAL z0m_landice, z0h_landice
    61        INTEGER iflag_gusts,iflag_z0_oce
    62 
    63 ! Rugoro
    64        Real f_rugoro,z0min
    65 
    66 ! tau_gl : constante de rappel de la temperature a la surface de la glace
    67        REAL tau_gl
    68 
    69 !IM lev_histhf  : niveau sorties 6h
    70 !IM lev_histday : niveau sorties journalieres
    71 !IM lev_histmth : niveau sorties mensuelles
    72 !IM lev_histdayNMC : on peut sortir soit sur 8 (comme AR5) ou bien
    73 !                    sur 17 niveaux de pression
    74        INTEGER lev_histhf, lev_histday, lev_histmth
    75        INTEGER lev_histdayNMC
    76        Integer lev_histins, lev_histLES 
    77 !IM ok_histNMC  : sortie fichiers niveaux de pression (histmthNMC, histdayNMC, histhfNMC)
    78 !IM freq_outNMC : frequences de sortie fichiers niveaux de pression (histmthNMC, histdayNMC, histhfNMC)
    79 !IM freq_calNMC : frequences de calcul fis. hist*NMC.nc
    80        LOGICAL ok_histNMC(3)
    81        INTEGER levout_histNMC(3)
    82        REAL freq_outNMC(3) , freq_calNMC(3)
    83        CHARACTER(len=4) type_run
    84 ! aer_type: pour utiliser un fichier constant dans readaerosol
    85        CHARACTER(len=8) :: aer_type
    86        LOGICAL ok_regdyn
    87        REAL lonmin_ins, lonmax_ins, latmin_ins, latmax_ins
    88        REAL ecrit_ins, ecrit_hf, ecrit_day
    89        REAL ecrit_mth, ecrit_tra, ecrit_reg
    90        REAL ecrit_LES
    91        REAL freq_ISCCP, ecrit_ISCCP
    92        REAL freq_COSP, freq_AIRS
    93        LOGICAL :: ok_cosp,ok_mensuelCOSP,ok_journeCOSP,ok_hfCOSP
    94        LOGICAL :: ok_airs
    95        INTEGER :: ip_ebil_phy, iflag_rrtm, iflag_ice_thermo, NSW, iflag_albedo
    96        LOGICAL :: ok_ice_supersat, ok_plane_h2o, ok_plane_contrail
    97        LOGICAL :: ok_chlorophyll
    98        LOGICAL :: ok_strato
    99        LOGICAL :: ok_hines, ok_gwd_rando
    100        LOGICAL :: ok_qch4
    101        LOGICAL :: ok_conserv_q
    102        LOGICAL :: adjust_tropopause
    103        LOGICAL :: ok_daily_climoz
    104        LOGICAL :: ok_new_lscp
    105        LOGICAL :: ok_bs, ok_rad_bs
    106 ! flag to bypass or not the phytrac module
    107        INTEGER :: iflag_phytrac
    108 
    109 !AI flags pour ECRAD       
    110        LOGICAL :: ok_3Deffect
    111 
    112 !OB flag to activate water mass fixer in physiq
    113        LOGICAL :: ok_water_mass_fixer
    114 
    115        COMMON/clesphys/                                                 &
    116 ! REAL FIRST
    117 ! rajout choix_bulk et nit_bulk kz0 par Olivier Torres
    118      &       co2_ppm, solaire                                           &
    119      &     , RCO2, RCH4, RN2O, RCFC11, RCFC12                           &
    120      &     , RCO2_act, RCH4_act, RN2O_act, RCFC11_act, RCFC12_act       &
    121      &     , RCO2_per, RCH4_per, RN2O_per, RCFC11_per, RCFC12_per       &
    122      &     , CH4_ppb, N2O_ppb, CFC11_ppt, CFC12_ppt                     &
    123      &     , CH4_ppb_per, N2O_ppb_per, CFC11_ppt_per, CFC12_ppt_per     &
    124      &     , cdmmax,cdhmax,ksta,ksta_ter,f_ri_cd_min                    &
    125      &     , fmagic, pmagic                                             &
    126      &     , f_cdrag_ter,f_cdrag_oce,f_rugoro,z0min,tau_gl              &
    127      &     , min_wind_speed,f_gust_wk,f_gust_bl,f_qsat_oce,f_z0qh_oce   &
    128      &     , z0m_seaice,z0h_seaice,z0m_landice,z0h_landice              &
    129      &     , freq_outNMC, freq_calNMC                                   &
    130      &     , lonmin_ins, lonmax_ins, latmin_ins, latmax_ins             &
    131      &     , freq_ISCCP, ecrit_ISCCP, freq_COSP, freq_AIRS              &
    132      &     , cvl_corr                                                   &
    133      &     , qsol0,albsno0,evap0                                        &
    134      &     , co2_ppm0                                                   &
    135 !FC
    136      &     , Cd_frein,zrel_oro_t,zpmm_orodr_t,zpmm_orolf_t,zstd_orodr_t &
    137      &     , ecrit_LES                                                  &
    138      &     , ecrit_ins, ecrit_hf, ecrit_day                             &
    139      &     , ecrit_mth, ecrit_tra, ecrit_reg                            &
    140 ! THEN INTEGER AND LOGICALS
    141      &     , top_height                                                 &
    142      &     , iflag_cycle_diurne, soil_model, new_oliq                   &
    143      &     , ok_orodr, ok_orolf, ok_limitvrai, nbapp_rad                &
    144      &     , iflag_con, nbapp_cv, nbapp_wk                              &
    145      &     , choix_bulk, nit_bulk, kz0                                  &
    146      &     , iflag_ener_conserv                                         &
    147      &     , ok_suntime_rrtm                                            &
    148      &     , overlap                                                    &
    149      &     , ok_kzmin                                                   &
    150      &     , lev_histhf, lev_histday, lev_histmth                       &
    151      &     , lev_histins, lev_histLES, lev_histdayNMC, levout_histNMC   &
    152      &     , ok_histNMC                                                 &
    153      &     , type_run, ok_regdyn, ok_cosp, ok_airs                      &
    154      &     , ok_mensuelCOSP,ok_journeCOSP,ok_hfCOSP                     &
    155      &     , ip_ebil_phy                                                &
    156      &     , iflag_gusts ,iflag_z0_oce                                  &
    157      &     , ok_lic_melt, ok_lic_cond, aer_type                         &
    158      &     , iflag_rrtm, ok_strato,ok_hines, ok_qch4                    &
    159      &     , iflag_ice_thermo, ok_ice_supersat                          &
    160      &     , ok_plane_h2o, ok_plane_contrail                            &
    161      &     , ok_gwd_rando, NSW, iflag_albedo                            &
    162      &     , ok_chlorophyll,ok_conserv_q, adjust_tropopause             &
    163      &     , ok_daily_climoz, ok_all_xml, ok_lwoff                      &
    164      &     , iflag_phytrac, ok_new_lscp, ok_bs, ok_rad_bs               &
    165      &     ,  iflag_thermals,nsplit_thermals, tau_thermals              &
    166      &     , iflag_physiq, ok_3Deffect, ok_water_mass_fixer
    167        save /clesphys/
    168 !$OMP THREADPRIVATE(/clesphys/)
     1! Replaces clesphys.h
     2
     3MODULE clesphys_mod_h
     4  IMPLICIT NONE; PRIVATE
     5
     6  PUBLIC co2_ppm, solaire                                           &
     7          , RCO2, RCH4, RN2O, RCFC11, RCFC12                           &
     8          , RCO2_act, RCH4_act, RN2O_act, RCFC11_act, RCFC12_act       &
     9          , RCO2_per, RCH4_per, RN2O_per, RCFC11_per, RCFC12_per       &
     10          , CH4_ppb, N2O_ppb, CFC11_ppt, CFC12_ppt                     &
     11          , CH4_ppb_per, N2O_ppb_per, CFC11_ppt_per, CFC12_ppt_per     &
     12          , cdmmax, cdhmax, ksta, ksta_ter, f_ri_cd_min                    &
     13          , fmagic, pmagic                                             &
     14          , f_cdrag_ter, f_cdrag_oce, f_rugoro, z0min, tau_gl              &
     15          , min_wind_speed, f_gust_wk, f_gust_bl, f_qsat_oce, f_z0qh_oce   &
     16          , z0m_seaice, z0h_seaice, z0m_landice, z0h_landice              &
     17          , freq_outNMC, freq_calNMC                                   &
     18          , lonmin_ins, lonmax_ins, latmin_ins, latmax_ins             &
     19          , freq_ISCCP, ecrit_ISCCP, freq_COSP, freq_AIRS              &
     20          , cvl_corr                                                   &
     21          , qsol0, albsno0, evap0                                        &
     22          , co2_ppm0                                                   &
     23          , tau_thermals                                               &
     24          , Cd_frein, zrel_oro_t, zpmm_orodr_t, zpmm_orolf_t, zstd_orodr_t &
     25          , ecrit_LES                                                  &
     26          , ecrit_ins, ecrit_hf, ecrit_day                             &
     27          , ecrit_mth, ecrit_tra, ecrit_reg                            &
     28          , top_height                                                 &
     29          , iflag_cycle_diurne, soil_model, new_oliq                   &
     30          , ok_orodr, ok_orolf, ok_limitvrai, nbapp_rad                &
     31          , iflag_con, nbapp_cv, nbapp_wk                              &
     32          , choix_bulk, nit_bulk, kz0                                  &
     33          , iflag_ener_conserv                                         &
     34          , ok_suntime_rrtm                                            &
     35          , overlap                                                    &
     36          , ok_kzmin                                                   &
     37          , lev_histhf, lev_histday, lev_histmth                       &
     38          , lev_histins, lev_histLES, lev_histdayNMC, levout_histNMC   &
     39          , ok_histNMC                                                 &
     40          , type_run, ok_regdyn, ok_cosp, ok_airs                      &
     41          , ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP                     &
     42          , ip_ebil_phy                                                &
     43          , iflag_gusts, iflag_z0_oce                                  &
     44          , ok_lic_melt, ok_lic_cond, aer_type                         &
     45          , iflag_rrtm, ok_strato, ok_hines, ok_qch4                    &
     46          , iflag_ice_thermo, ok_ice_supersat                            &
     47          , ok_plane_h2o, ok_plane_contrail                            &
     48          , ok_gwd_rando, NSW, iflag_albedo                            &
     49          , ok_chlorophyll, ok_conserv_q, adjust_tropopause             &
     50          , ok_daily_climoz, ok_all_xml, ok_lwoff                      &
     51          , iflag_phytrac, ok_new_lscp, ok_bs, ok_rad_bs               &
     52          , iflag_thermals, nsplit_thermals              &
     53          , iflag_physiq, ok_3Deffect, ok_water_mass_fixer
     54
     55
     56  ! threshold on to activate SSO schemes
     57  ! threshold on to activate SSO schemes
     58  REAL zrel_oro_t, zpmm_orodr_t, zpmm_orolf_t, zstd_orodr_t
     59  INTEGER iflag_cycle_diurne
     60  LOGICAL soil_model, new_oliq, ok_orodr, ok_orolf
     61  LOGICAL ok_limitvrai
     62  LOGICAL ok_all_xml
     63  LOGICAL ok_lwoff
     64  INTEGER nbapp_rad, iflag_con, nbapp_cv, nbapp_wk, iflag_ener_conserv
     65  REAL co2_ppm, co2_ppm0, solaire
     66  INTEGER iflag_thermals, nsplit_thermals
     67  INTEGER iflag_physiq
     68  REAL tau_thermals
     69
     70  !FC
     71  REAL Cd_frein
     72  LOGICAL ok_suntime_rrtm
     73  REAL(kind = 8) RCO2, RCH4, RN2O, RCFC11, RCFC12
     74  REAL(kind = 8) RCO2_act, RCH4_act, RN2O_act, RCFC11_act, RCFC12_act
     75  REAL(kind = 8) CH4_ppb, N2O_ppb, CFC11_ppt, CFC12_ppt
     76  !IM ajout CFMIP2/CMIP5ok_bs
     77  REAL(kind = 8) RCO2_per, RCH4_per, RN2O_per, RCFC11_per, RCFC12_per
     78  REAL(kind = 8) CH4_ppb_per, N2O_ppb_per, CFC11_ppt_per, CFC12_ppt_per
     79
     80  !OM ---> correction du bilan d'eau global
     81  !OM Correction sur precip KE
     82  REAL cvl_corr
     83  !OM Fonte calotte dans bilan eau
     84  LOGICAL ok_lic_melt
     85  !OB Depot de vapeur d eau sur la calotte pour le bilan eau
     86  LOGICAL ok_lic_cond
     87
     88  !IM simulateur ISCCP
     89  INTEGER top_height, overlap
     90  !IM seuils cdrm, cdrh
     91  REAL cdmmax, cdhmax
     92  !IM pour les params différentes Olivier Torres
     93  INTEGER choix_bulk, nit_bulk, kz0
     94  !IM param. stabilite s/ terres et en dehors
     95  REAL ksta, ksta_ter, f_ri_cd_min
     96  !IM ok_kzmin : clef calcul Kzmin dans la CL de surface cf FH
     97  LOGICAL ok_kzmin
     98  !IM, MAFo fmagic, pmagic : parametres - additionnel et multiplicatif -
     99  !                          pour regler l albedo sur ocean
     100  REAL fmagic, pmagic
     101  ! Hauteur (imposee) du contenu en eau du sol
     102  REAL qsol0, albsno0, evap0
     103  ! Frottement au sol (Cdrag)
     104  Real f_cdrag_ter, f_cdrag_oce
     105  REAL min_wind_speed, f_gust_wk, f_gust_bl, f_qsat_oce, f_z0qh_oce
     106  REAL z0m_seaice, z0h_seaice
     107  REAL z0m_landice, z0h_landice
     108  INTEGER iflag_gusts, iflag_z0_oce
     109
     110  ! Rugoro
     111  Real f_rugoro, z0min
     112
     113  ! tau_gl : constante de rappel de la temperature a la surface de la glace
     114  REAL tau_gl
     115
     116  !IM lev_histhf  : niveau sorties 6h
     117  !IM lev_histday : niveau sorties journalieres
     118  !IM lev_histmth : niveau sorties mensuelles
     119  !IM lev_histdayNMC : on peut sortir soit sur 8 (comme AR5) ou bien
     120  !                    sur 17 niveaux de pression
     121  INTEGER lev_histhf, lev_histday, lev_histmth
     122  INTEGER lev_histdayNMC
     123  Integer lev_histins, lev_histLES
     124  !IM ok_histNMC  : sortie fichiers niveaux de pression (histmthNMC, histdayNMC, histhfNMC)
     125  !IM freq_outNMC : frequences de sortie fichiers niveaux de pression (histmthNMC, histdayNMC, histhfNMC)
     126  !IM freq_calNMC : frequences de calcul fis. hist*NMC.nc
     127  LOGICAL ok_histNMC(3)
     128  INTEGER levout_histNMC(3)
     129  REAL freq_outNMC(3), freq_calNMC(3)
     130  CHARACTER(len = 4) type_run
     131  ! aer_type: pour utiliser un fichier constant dans readaerosol
     132  CHARACTER(len = 8) :: aer_type
     133  LOGICAL ok_regdyn
     134  REAL lonmin_ins, lonmax_ins, latmin_ins, latmax_ins
     135  REAL ecrit_ins, ecrit_hf, ecrit_day
     136  REAL ecrit_mth, ecrit_tra, ecrit_reg
     137  REAL ecrit_LES
     138  REAL freq_ISCCP, ecrit_ISCCP
     139  REAL freq_COSP, freq_AIRS
     140  LOGICAL :: ok_cosp, ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP
     141  LOGICAL :: ok_airs
     142  INTEGER :: ip_ebil_phy, iflag_rrtm, iflag_ice_thermo, NSW, iflag_albedo
     143  LOGICAL :: ok_ice_supersat, ok_plane_h2o, ok_plane_contrail
     144  LOGICAL :: ok_chlorophyll
     145  LOGICAL :: ok_strato
     146  LOGICAL :: ok_hines, ok_gwd_rando
     147  LOGICAL :: ok_qch4
     148  LOGICAL :: ok_conserv_q
     149  LOGICAL :: adjust_tropopause
     150  LOGICAL :: ok_daily_climoz
     151  LOGICAL :: ok_new_lscp
     152  LOGICAL :: ok_bs, ok_rad_bs
     153  ! flag to bypass or not the phytrac module
     154  INTEGER :: iflag_phytrac
     155
     156  !AI flags pour ECRAD
     157  LOGICAL :: ok_3Deffect
     158
     159  !OB flag to activate water mass fixer in physiq
     160  LOGICAL :: ok_water_mass_fixer
     161
     162
     163  !$OMP THREADPRIVATE(co2_ppm, solaire                                           &
     164  !$OMP      , RCO2, RCH4, RN2O, RCFC11, RCFC12                           &
     165  !$OMP      , RCO2_act, RCH4_act, RN2O_act, RCFC11_act, RCFC12_act       &
     166  !$OMP      , RCO2_per, RCH4_per, RN2O_per, RCFC11_per, RCFC12_per       &
     167  !$OMP      , CH4_ppb, N2O_ppb, CFC11_ppt, CFC12_ppt                     &
     168  !$OMP      , CH4_ppb_per, N2O_ppb_per, CFC11_ppt_per, CFC12_ppt_per     &
     169  !$OMP      , cdmmax, cdhmax, ksta, ksta_ter, f_ri_cd_min                    &
     170  !$OMP      , fmagic, pmagic                                             &
     171  !$OMP      , f_cdrag_ter, f_cdrag_oce, f_rugoro, z0min, tau_gl              &
     172  !$OMP      , min_wind_speed, f_gust_wk, f_gust_bl, f_qsat_oce, f_z0qh_oce   &
     173  !$OMP      , z0m_seaice, z0h_seaice, z0m_landice, z0h_landice              &
     174  !$OMP      , freq_outNMC, freq_calNMC                                   &
     175  !$OMP      , lonmin_ins, lonmax_ins, latmin_ins, latmax_ins             &
     176  !$OMP      , freq_ISCCP, ecrit_ISCCP, freq_COSP, freq_AIRS              &
     177  !$OMP      , cvl_corr                                                   &
     178  !$OMP      , qsol0, albsno0, evap0                                        &
     179  !$OMP      , co2_ppm0                                                   &
     180  !$OMP      , tau_thermals                                               &
     181  !$OMP      , Cd_frein, zrel_oro_t, zpmm_orodr_t, zpmm_orolf_t, zstd_orodr_t &
     182  !$OMP      , ecrit_LES                                                  &
     183  !$OMP      , ecrit_ins, ecrit_hf, ecrit_day                             &
     184  !$OMP      , ecrit_mth, ecrit_tra, ecrit_reg                            &
     185  !$OMP      , top_height                                                 &
     186  !$OMP      , iflag_cycle_diurne, soil_model, new_oliq                   &
     187  !$OMP      , ok_orodr, ok_orolf, ok_limitvrai, nbapp_rad                &
     188  !$OMP      , iflag_con, nbapp_cv, nbapp_wk                              &
     189  !$OMP      , choix_bulk, nit_bulk, kz0                                  &
     190  !$OMP      , iflag_ener_conserv                                         &
     191  !$OMP      , ok_suntime_rrtm                                            &
     192  !$OMP      , overlap                                                    &
     193  !$OMP      , ok_kzmin                                                   &
     194  !$OMP      , lev_histhf, lev_histday, lev_histmth                       &
     195  !$OMP      , lev_histins, lev_histLES, lev_histdayNMC, levout_histNMC   &
     196  !$OMP      , ok_histNMC                                                 &
     197  !$OMP      , type_run, ok_regdyn, ok_cosp, ok_airs                      &
     198  !$OMP      , ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP                     &
     199  !$OMP      , ip_ebil_phy                                                &
     200  !$OMP      , iflag_gusts, iflag_z0_oce                                  &
     201  !$OMP      , ok_lic_melt, ok_lic_cond, aer_type                         &
     202  !$OMP      , iflag_rrtm, ok_strato, ok_hines, ok_qch4                    &
     203  !$OMP      , iflag_ice_thermo, ok_ice_supersat                            &
     204  !$OMP      , ok_plane_h2o, ok_plane_contrail                            &
     205  !$OMP      , ok_gwd_rando, NSW, iflag_albedo                            &
     206  !$OMP      , ok_chlorophyll, ok_conserv_q, adjust_tropopause             &
     207  !$OMP      , ok_daily_climoz, ok_all_xml, ok_lwoff                      &
     208  !$OMP      , iflag_phytrac, ok_new_lscp, ok_bs, ok_rad_bs               &
     209  !$OMP      , iflag_thermals, nsplit_thermals              &
     210  !$OMP      , iflag_physiq, ok_3Deffect, ok_water_mass_fixer)
     211
     212END MODULE clesphys_mod_h
  • LMDZ6/trunk/libf/phylmd/coare30_flux_cnrm_mod.f90

    r5274 r5282  
    7070!
    7171!
     72USE clesphys_mod_h
    7273!USE MODD_SEAFLUX_n, ONLY : SEAFLUX_t
    7374!
     
    242243INTEGER :: NGRVWAVES        ! Pour le choix du z0
    243244
    244 INCLUDE "clesphys.h"
    245245
    246246!--------------------------------------
  • LMDZ6/trunk/libf/phylmd/coef_diff_turb_mod.f90

    r5274 r5282  
    66! at surface(cdrag)
    77!
    8   IMPLICIT NONE
    9  
     8  USE clesphys_mod_h
     9    IMPLICIT NONE
     10
    1011CONTAINS
    1112!
     
    1516       ypaprs, ypplay, yu, yv, yq, yt, yts, yqsurf, ycdragm, &
    1617       ycoefm, ycoefh ,yq2, yeps, ydrgpro)
    17  
     18
    1819    USE dimphy
    1920    USE indice_sol_mod
     
    3233          , RALPD, RBETD, RGAMD
    3334!
    34 ! Calculate coefficients(ycoefm, ycoefh) for turbulent diffusion in the 
    35 ! atmosphere 
    36 ! NB! No values are calculated between surface and the first model layer. 
     35! Calculate coefficients(ycoefm, ycoefh) for turbulent diffusion in the
     36! atmosphere
     37! NB! No values are calculated between surface and the first model layer.
    3738!     ycoefm(:,1) and ycoefh(:,1) are not valid !!!
    3839!
     
    5657!****************************************************************************************
    5758    REAL, DIMENSION(klon,klev+1), INTENT(INOUT):: yq2
    58  
     59
    5960! Output arguments
    6061!****************************************************************************************
     
    7273! Include
    7374!****************************************************************************************
    74     INCLUDE "clesphys.h"
    7575    INCLUDE "compbl.h"
    7676    INCLUDE "YOETHF.h"
  • LMDZ6/trunk/libf/phylmd/coefcdrag.f90

    r5274 r5282  
    77                            cdram, cdrah, cdran, zri1, pref)
    88
     9      USE clesphys_mod_h
    910      USE indice_sol_mod
    1011
     
    6465
    6566      include "YOETHF.h"
    66       INCLUDE "clesphys.h"
    6767! Quelques constantes :
    6868      REAL, parameter :: RKAR=0.40, CB=5.0, CC=5.0, CD=5.0, cepdu2=(0.1)**2
  • LMDZ6/trunk/libf/phylmd/concvl.f90

    r5274 r5282  
    3030
    3131
     32  USE clesphys_mod_h
    3233  USE dimphy
    3334  USE infotrac_phy, ONLY: nbtr
     
    9899
    99100
    100   include "clesphys.h"
    101101
    102102  INTEGER, INTENT(IN)                           :: iflag_clos
  • LMDZ6/trunk/libf/phylmd/condsurf.f90

    r5270 r5282  
    22
    33SUBROUTINE condsurf(jour, jourvrai, lmt_bils)
     4  USE clesphys_mod_h
    45  USE dimphy
    56  USE mod_grid_phy_lmdz
     
    2425  INTEGER epais(2)
    2526
    26   include "clesphys.h"
    2727
    2828  INTEGER nannemax
  • LMDZ6/trunk/libf/phylmd/conf_phys_m.f90

    r5274 r5282  
    66MODULE conf_phys_m
    77
    8   IMPLICIT NONE
     8  USE clesphys_mod_h
     9    IMPLICIT NONE
    910
    1011CONTAINS
     
    1718       iflag_cld_th, &
    1819       ratqsbas,ratqshaut,tau_ratqs, &
    19        ok_ade, ok_aie, ok_alw, ok_cdnc, ok_volcan, flag_volc_surfstrat, aerosol_couple, & 
     20       ok_ade, ok_aie, ok_alw, ok_cdnc, ok_volcan, flag_volc_surfstrat, aerosol_couple, &
    2021       chemistry_couple, flag_aerosol, flag_aerosol_strat, flag_aer_feedback, &
    2122       flag_bc_internal_mixture, bl95_b0, bl95_b1,&
     
    5657
    5758    !IM : on inclut/initialise les taux de CH4, N2O, CFC11 et CFC12
    58     INCLUDE "clesphys.h"
    5959    INCLUDE "compbl.h"
    6060    INCLUDE "comsoil.h"
  • LMDZ6/trunk/libf/phylmd/cosp/cosp_output_write_mod.F90

    r4619 r5282  
    431431! ug Routine pour definir itau_iocosp depuis cosp_output_write_mod:
    432432  SUBROUTINE set_itau_iocosp(ito)
    433       IMPLICIT NONE
     433      USE clesphys_mod_h
     434    IMPLICIT NONE
    434435      INTEGER, INTENT(IN) :: ito
    435436      itau_iocosp = ito
     
    448449    IMPLICIT NONE
    449450
    450     INCLUDE "clesphys.h"
    451451
    452452    INTEGER                          :: iff
     
    456456    CHARACTER(LEN=20) :: typeecrit
    457457
    458     ! ug On récupère le type écrit de la structure:
    459     !       Assez moche, Ã|  refaire si meilleure méthode...
     458    ! ug On récupère le type écrit de la structure:
     459    !       Assez moche, �|  refaire si meilleure méthode...
    460460    IF (INDEX(var%cosp_typeecrit(iff), "once") > 0) THEN
    461461       typeecrit = 'once'
     
    499499
    500500 SUBROUTINE histdef3d_cosp (iff,var,nvertsave,ncols)
     501    USE clesphys_mod_h
    501502    USE ioipsl
    502503    USE dimphy
     
    509510    IMPLICIT NONE
    510511
    511     INCLUDE "clesphys.h"
    512512
    513513    INTEGER                        :: iff, klevs
     
    558558      END IF
    559559
    560     ! ug On récupère le type écrit de la structure:
    561     !       Assez moche, Ã|  refaire si meilleure méthode...
     560    ! ug On récupère le type écrit de la structure:
     561    !       Assez moche, �|  refaire si meilleure méthode...
    562562    IF (INDEX(var%cosp_typeecrit(iff), "once") > 0) THEN
    563563       typeecrit = 'once'
     
    602602
    603603 SUBROUTINE histwrite2d_cosp(var,field)
     604  USE clesphys_mod_h
    604605  USE dimphy
    605606  USE mod_phys_lmdz_para
     
    611612
    612613  IMPLICIT NONE
    613   INCLUDE 'clesphys.h'
    614614
    615615    TYPE(ctrl_outcosp), INTENT(IN) :: var
     
    628628    IF (prt_level >= 9) WRITE(lunout,*)'Begin histrwrite2d ',var%name
    629629
    630   ! On regarde si on est dans la phase de définition ou d'écriture:
     630  ! On regarde si on est dans la phase de définition ou d'écriture:
    631631  IF(.NOT.cosp_varsdefined) THEN
    632632!$OMP MASTER
    633       !Si phase de définition.... on définit
     633      !Si phase de définition.... on définit
    634634      CALL conf_cospoutputs(var%name,var%cles)
    635635      DO iff=1, 3
     
    640640!$OMP END MASTER
    641641  ELSE
    642     !Et sinon on.... écrit
     642    !Et sinon on.... écrit
    643643    IF (SIZE(field)/=klon) &
    644644  CALL abort_physic('iophy::histwrite2d_cosp','Field first DIMENSION not equal to klon',1)
     
    688688! AI sept 2013
    689689  SUBROUTINE histwrite3d_cosp(var, field, nverts, ncols)
     690  USE clesphys_mod_h
    690691  USE dimphy
    691692  USE mod_phys_lmdz_para
     
    697698
    698699  IMPLICIT NONE
    699   INCLUDE 'clesphys.h'
    700700
    701701    TYPE(ctrl_outcosp), INTENT(IN)    :: var
     
    725725               nom=var%name
    726726      END IF
    727   ! On regarde si on est dans la phase de définition ou d'écriture:
     727  ! On regarde si on est dans la phase de définition ou d'écriture:
    728728  IF(.NOT.cosp_varsdefined) THEN
    729       !Si phase de définition.... on définit
     729      !Si phase de définition.... on définit
    730730!$OMP MASTER
    731731      CALL conf_cospoutputs(var%name,var%cles)
     
    737737!$OMP END MASTER
    738738  ELSE
    739     !Et sinon on.... écrit
     739    !Et sinon on.... écrit
    740740    IF (SIZE(field,1)/=klon) &
    741741   CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)                                 
     
    784784! AI sept 2013
    785785  SUBROUTINE histwrite4d_cosp(var, field)
     786  USE clesphys_mod_h
    786787  USE dimphy
    787788  USE mod_phys_lmdz_para
     
    793794
    794795  IMPLICIT NONE
    795   INCLUDE 'clesphys.h'
    796796
    797797    TYPE(ctrl_outcosp), INTENT(IN)    :: var
     
    809809
    810810  IF(cosp_varsdefined) THEN
    811     !Et sinon on.... écrit
     811    !Et sinon on.... écrit
    812812    IF (SIZE(field,1)/=klon) &
    813813   CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)           
  • LMDZ6/trunk/libf/phylmd/cospv2/lmdz_cosp_output_write_mod.f90

    r5268 r5282  
    644644! ug Routine pour definir itau_iocosp depuis cosp_output_write_mod:
    645645  SUBROUTINE set_itau_iocosp(ito)
    646       IMPLICIT NONE
     646      USE clesphys_mod_h
     647    IMPLICIT NONE
    647648      INTEGER, INTENT(IN) :: ito
    648649      itau_iocosp = ito
     
    661662    IMPLICIT NONE
    662663
    663     INCLUDE "clesphys.h"
    664664
    665665    INTEGER                          :: iff
     
    669669    CHARACTER(LEN=20) :: typeecrit
    670670
    671     ! ug On récupère le type écrit de la structure:
    672     !       Assez moche, Ã|  refaire si meilleure méthode...
     671    ! ug On récupère le type écrit de la structure:
     672    !       Assez moche, �|  refaire si meilleure méthode...
    673673    IF (INDEX(var%cosp_typeecrit(iff), "once") > 0) THEN
    674674       typeecrit = 'once'
     
    704704
    705705 SUBROUTINE histdef3d_cosp (iff,var,nvertsave,ncols)
     706    USE clesphys_mod_h
    706707    USE ioipsl
    707708    USE dimphy
     
    716717    IMPLICIT NONE
    717718
    718     INCLUDE "clesphys.h"
    719719
    720720    INTEGER                        :: iff, klevs
     
    765765      END IF
    766766
    767     ! ug On récupère le type écrit de la structure:
    768     !       Assez moche, Ã|  refaire si meilleure méthode...
     767    ! ug On récupère le type écrit de la structure:
     768    !       Assez moche, �|  refaire si meilleure méthode...
    769769    IF (INDEX(var%cosp_typeecrit(iff), "once") > 0) THEN
    770770       typeecrit = 'once'
     
    800800
    801801 SUBROUTINE histwrite2d_cosp(var,field)
     802  USE clesphys_mod_h
    802803  USE dimphy
    803804  USE mod_phys_lmdz_para
     
    810811
    811812  IMPLICIT NONE
    812   INCLUDE 'clesphys.h'
    813813
    814814    TYPE(ctrl_outcosp), INTENT(IN) :: var
     
    827827    IF (prt_level >= 9) WRITE(lunout,*)'Begin histrwrite2d ',var%name
    828828
    829   ! On regarde si on est dans la phase de définition ou d'écriture:
     829  ! On regarde si on est dans la phase de définition ou d'écriture:
    830830  IF(.NOT.cosp_varsdefined) THEN
    831831!$OMP MASTER
    832832      print*,'var, cosp_varsdefined dans cosp_varsdefined ',var%name, cosp_varsdefined
    833       !Si phase de définition.... on définit
     833      !Si phase de définition.... on définit
    834834      CALL conf_cospoutputs(var%name,var%cles)
    835835      DO iff=1, 3
     
    840840!$OMP END MASTER
    841841  ELSE
    842     !Et sinon on.... écrit
     842    !Et sinon on.... écrit
    843843    IF (SIZE(field)/=klon) &
    844844  CALL abort_physic('iophy::histwrite2d_cosp','Field first DIMENSION not equal to klon',1)
     
    882882! AI sept 2013
    883883  SUBROUTINE histwrite3d_cosp(var, field, nverts, ncols)
     884  USE clesphys_mod_h
    884885  USE dimphy
    885886  USE mod_phys_lmdz_para
     
    893894
    894895  IMPLICIT NONE
    895   INCLUDE 'clesphys.h'
    896896
    897897    TYPE(ctrl_outcosp), INTENT(IN)    :: var
     
    921921               nom=var%name
    922922      END IF
    923   ! On regarde si on est dans la phase de définition ou d'écriture:
     923  ! On regarde si on est dans la phase de définition ou d'écriture:
    924924  IF(.NOT.cosp_varsdefined) THEN
    925       !Si phase de définition.... on définit
     925      !Si phase de définition.... on définit
    926926!$OMP MASTER
    927927      CALL conf_cospoutputs(var%name,var%cles)
     
    933933!$OMP END MASTER
    934934  ELSE
    935     !Et sinon on.... écrit
     935    !Et sinon on.... écrit
    936936    IF (SIZE(field,1)/=klon) &
    937937   CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)                                 
     
    973973! AI sept 2013
    974974  SUBROUTINE histwrite4d_cosp(var, field)
     975  USE clesphys_mod_h
    975976  USE dimphy
    976977  USE mod_phys_lmdz_para
     
    984985
    985986  IMPLICIT NONE
    986   INCLUDE 'clesphys.h'
    987987
    988988    TYPE(ctrl_outcosp), INTENT(IN)    :: var
     
    10001000
    10011001  IF(cosp_varsdefined) THEN
    1002     !Et sinon on.... écrit
     1002    !Et sinon on.... écrit
    10031003    IF (SIZE(field,1)/=klon) &
    10041004   CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)           
  • LMDZ6/trunk/libf/phylmd/create_etat0_unstruct_mod.f90

    r5273 r5282  
    2727  IMPLICIT NONE
    2828  INTEGER :: file_id, iret
    29  
     29
    3030   ! for coupling activate ocean fraction reading from file "ocean_fraction.nc"
    3131    IF (is_omp_master) THEN
     
    5252
    5353  END SUBROUTINE init_create_etat0_unstruct
    54  
    55  
     54
     55
    5656  SUBROUTINE init_param_gw(zmea, zpic, zval, zstd, zsig, zgam, zthe)
    5757  USE dimphy
    58     REAL, INTENT(IN) :: zmea(klon) 
     58    REAL, INTENT(IN) :: zmea(klon)
    5959    REAL, INTENT(IN) :: zpic(klon)
    60     REAL, INTENT(IN) :: zval(klon) 
    61     REAL, INTENT(IN) :: zstd(klon) 
    62     REAL, INTENT(IN) :: zsig(klon) 
    63     REAL, INTENT(IN) :: zgam(klon) 
     60    REAL, INTENT(IN) :: zval(klon)
     61    REAL, INTENT(IN) :: zstd(klon)
     62    REAL, INTENT(IN) :: zsig(klon)
     63    REAL, INTENT(IN) :: zgam(klon)
    6464    REAL, INTENT(IN) :: zthe(klon)
    6565
    66     ALLOCATE(zmea_gw(klon), zpic_gw(klon), zval_gw(klon), zstd_gw(klon), zsig_gw(klon), zgam_gw(klon), zthe_gw(klon)) 
    67    
     66    ALLOCATE(zmea_gw(klon), zpic_gw(klon), zval_gw(klon), zstd_gw(klon), zsig_gw(klon), zgam_gw(klon), zthe_gw(klon))
     67
    6868    zmea_gw(:)=zmea(:)
    6969    zpic_gw(:)=zpic(:)
     
    9393  USE ioipsl_getin_p_mod, ONLY: getin_p
    9494  USE dimsoil_mod_h, ONLY: nsoilmx
     95  USE clesphys_mod_h
    9596  IMPLICIT NONE
    96   include "clesphys.h"
    9797
    9898    LOGICAL :: no_ter_antartique   ! If true, no land points are allowed at Antartic
  • LMDZ6/trunk/libf/phylmd/create_limit_unstruct_mod.f90

    r5268 r5282  
    99
    1010  SUBROUTINE create_limit_unstruct
    11   USE dimphy
     11   USE dimphy
    1212  USE lmdz_xios
    1313  USE ioipsl,             ONLY : ioget_year_len
     
    1616  USE phys_state_var_mod
    1717  USE mod_phys_lmdz_para
     18  USE iniprint_mod_h
    1819  IMPLICIT NONE
    19     INCLUDE "iniprint.h"
    2020    REAL,    DIMENSION(:,:),ALLOCATABLE            :: sic
    2121    REAL,    DIMENSION(:,:),ALLOCATABLE            :: sst
     
    4141    INTEGER :: l,k
    4242    INTEGER :: nbad
    43     INTEGER :: sic_time_axis_size 
     43    INTEGER :: sic_time_axis_size
    4444    INTEGER :: sst_time_axis_size
    4545    CHARACTER(LEN=99)                  :: mess            ! error message
    46    
    47      
     46
     47
    4848    ndays=ioget_year_len(annee_ref)
    49    
     49
    5050    IF (is_omp_master) CALL xios_get_axis_attr("time_sic",n_glo=sic_time_axis_size)
    5151    CALL bcast_omp(sic_time_axis_size)
    5252    ALLOCATE(sic_mpi(klon_mpi,sic_time_axis_size))
    5353    ALLOCATE(sic(klon,sic_time_axis_size))
    54    
    55    
     54
     55
    5656    IF (is_omp_master) CALL xios_get_axis_attr("time_sst",n_glo=sst_time_axis_size)
    5757    CALL bcast_omp(sst_time_axis_size)
    5858    ALLOCATE(sst_mpi(klon_mpi,sst_time_axis_size))
    5959    ALLOCATE(sst(klon,sst_time_axis_size))
    60    
     60
    6161    IF (is_omp_master) THEN
    6262      CALL xios_recv_field("sic_limit",sic_mpi)
     
    6969    CALL scatter_omp(rugos_mpi,rugos)
    7070    CALL scatter_omp(albedo_mpi,albedo)
    71    
     71
    7272    ALLOCATE(sic_year(klon,ndays))
    7373    ALLOCATE(sst_year(klon,ndays))
     
    8888      CALL abort_physic('create_limit_unstruct',TRIM(mess),1)
    8989    ENDIF
    90    
     90
    9191    sic_year(:,:)=sic_year(:,:)/100.  ! convert percent to fraction
    9292    WHERE(sic_year(:,:)>1.0) sic_year(:,:)=1.0    ! Some fractions have some time large negative values
    9393    WHERE(sic_year(:,:)<0.0) sic_year(:,:)=0.0    ! probably better to apply alse this filter before horizontal interpolation
    94    
     94
    9595! sst
    9696    IF (sst_time_axis_size==lmdep) THEN
     
    106106
    107107
    108 ! rugos   
     108! rugos
    109109    DO l=1, lmdep
    110110      WHERE(NINT(zmasq(:))/=1) rugos(:,l)=0.001
     
    112112    CALL time_interpolation(ndays,rugos,'360_day',rugos_year)
    113113
    114 ! albedo   
     114! albedo
    115115    CALL time_interpolation(ndays,albedo,'360_day',albedo_year)
    116116
     
    151151      IF(nbad>0) WRITE(lunout,*) 'pb sous surface pour nb points = ',nbad
    152152    END DO
    153    
     153
    154154    ALLOCATE(sst_year_mpi(klon_mpi,ndays))
    155155    ALLOCATE(rugos_year_mpi(klon_mpi,ndays))
     
    157157    ALLOCATE(pctsrf_t_mpi(klon_mpi,nbsrf,ndays))
    158158    ALLOCATE(phy_bil_mpi(klon_mpi,ndays))
    159    
     159
    160160    CALL gather_omp(pctsrf_t   , pctsrf_t_mpi)
    161161    CALL gather_omp(sst_year   , sst_year_mpi)
     
    171171      CALL xios_send_field("sst_limout", sst_year_mpi)
    172172      CALL xios_send_field("bils_limout",phy_bil_mpi)
    173       CALL xios_send_field("alb_limout", albedo_year_mpi) 
    174       CALL xios_send_field("rug_limout", rugos_year_mpi) 
     173      CALL xios_send_field("alb_limout", albedo_year_mpi)
     174      CALL xios_send_field("rug_limout", rugos_year_mpi)
    175175    ENDIF
    176176  END SUBROUTINE create_limit_unstruct
    177  
    178  
     177
     178
    179179  SUBROUTINE time_interpolation(ndays,field_in,calendar,field_out)
    180180  USE pchsp_95_m, only: pchsp_95
     
    185185  USE time_phylmdz_mod, ONLY : annee_ref
    186186  USE mod_phys_lmdz_para
     187  USE iniprint_mod_h
    187188  IMPLICIT NONE
    188    INCLUDE "iniprint.h"
    189189
    190190   INTEGER,         INTENT(IN)  :: ndays
  • LMDZ6/trunk/libf/phylmd/dyn1d/old_lmdz1d.f90

    r5274 r5282  
    55      SUBROUTINE old_lmdz1d
    66
    7    USE ioipsl, only: ju2ymds, ymds2ju, ioconf_calendar,getin
     7   USE clesphys_mod_h
     8      USE ioipsl, only: ju2ymds, ymds2ju, ioconf_calendar,getin
    89   USE phys_state_var_mod, ONLY : phys_state_var_init, phys_state_var_end, &
    910       clwcon, detr_therm, &
     
    2324       u10m,v10m,ale_wake,ale_bl_stat
    2425
    25  
     26
    2627   USE dimphy
    2728   USE surface_data, only : type_ocean,ok_veget
    2829   USE pbl_surface_mod, only : ftsoil, pbl_surface_init, &
    2930                                 pbl_surface_final
    30    USE fonte_neige_mod, only : fonte_neige_init, fonte_neige_final 
     31   USE fonte_neige_mod, only : fonte_neige_init, fonte_neige_final
    3132
    3233   USE infotrac ! new
     
    6667
    6768!!      INCLUDE "control.h"
    68       INCLUDE "clesphys.h"
    6969!      INCLUDE "indicesol.h"
    7070
  • LMDZ6/trunk/libf/phylmd/dyn1d/scm.f90

    r5274 r5282  
    11SUBROUTINE scm
    22
    3    USE ioipsl, only: ju2ymds, ymds2ju, ioconf_calendar,getin
     3   USE clesphys_mod_h
     4      USE ioipsl, only: ju2ymds, ymds2ju, ioconf_calendar,getin
    45   USE phys_state_var_mod, ONLY : phys_state_var_init, phys_state_var_end, &
    56       clwcon, detr_therm, &
     
    1920       u10m,v10m,ale_wake,ale_bl_stat, ratqs_inter_
    2021
    21  
     22
    2223   USE dimphy
    2324   USE surface_data, only : type_ocean,ok_veget
    2425   USE pbl_surface_mod, only : ftsoil, pbl_surface_init, &
    2526                                 pbl_surface_final
    26    USE fonte_neige_mod, only : fonte_neige_init, fonte_neige_final 
     27   USE fonte_neige_mod, only : fonte_neige_init, fonte_neige_final
    2728
    2829   USE infotrac ! new
     
    6263
    6364!!      INCLUDE "control.h"
    64       INCLUDE "clesphys.h"
    6565!      INCLUDE "indicesol.h"
    6666
  • LMDZ6/trunk/libf/phylmd/ecrad/lmdz/readaerosol_optic_ecrad.f90

    r5268 r5282  
    1313  !
    1414
     15  USE clesphys_mod_h
    1516  USE dimphy
    1617  USE aero_mod
    1718  USE phys_local_var_mod, only: sconcso4,sconcno3,sconcoa,sconcbc,sconcss,sconcdust, &
    1819       concso4,concno3,concoa,concbc,concss,concdust,loadso4,loadoa,loadbc,loadss,loaddust, &
    19        loadno3,load_tmp1,load_tmp2,load_tmp3,load_tmp4,load_tmp5,load_tmp6,load_tmp7, & 
     20       loadno3,load_tmp1,load_tmp2,load_tmp3,load_tmp4,load_tmp5,load_tmp6,load_tmp7, &
    2021       load_tmp8,load_tmp9,load_tmp10
    2122
     
    2526  IMPLICIT NONE
    2627
    27   include "clesphys.h"
    2828
    2929  ! Input arguments
  • LMDZ6/trunk/libf/phylmd/ecrad/lmdz/readaerosolstrato_ecrad.F90

    r4853 r5282  
    2525#endif
    2626
     27    USE clesphys_mod_h
    2728    IMPLICIT NONE
    2829
    29     INCLUDE "clesphys.h"
    3030
    3131    CHARACTER (len = 80) :: abort_message
  • LMDZ6/trunk/libf/phylmd/ecumev6_flux.f90

    r5274 r5282  
    114114          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
    115115          , RALPD, RBETD, RGAMD
     116USE clesphys_mod_h
    116117IMPLICIT NONE
    117118!
     
    255256
    256257REAL    :: qsat_seawater2,qsat_seawater
    257 
    258 INCLUDE "clesphys.h"
    259258
    260259!REAL(KIND=JPRB) :: ZHOOK_HANDLE
  • LMDZ6/trunk/libf/phylmd/ener_conserv.f90

    r5274 r5282  
    2020
    2121! From module
     22USE clesphys_mod_h
    2223USE phys_local_var_mod, ONLY : d_u_vdf,d_v_vdf,d_t_vdf,d_u_ajs,d_v_ajs,d_t_ajs, &
    2324 &                             d_u_con,d_v_con,d_t_con,d_t_diss
     
    2728USE phys_state_var_mod, ONLY : du_gwd_front,du_gwd_rando
    2829USE phys_output_var_mod, ONLY : bils_ec,bils_ech,bils_tke,bils_kinetic,bils_enthalp,bils_latent,bils_diss
    29 USE add_phys_tend_mod, ONLY : fl_cor_ebil 
     30USE add_phys_tend_mod, ONLY : fl_cor_ebil
    3031USE infotrac_phy, ONLY: nqtot
    3132
     
    4647
    4748INCLUDE "YOETHF.h"
    48 INCLUDE "clesphys.h"
    4949INCLUDE "compbl.h"
    5050
  • LMDZ6/trunk/libf/phylmd/flott_gwd_rando_m.f90

    r5274 r5282  
    44module FLOTT_GWD_rando_m
    55
    6   implicit none
     6  USE clesphys_mod_h
     7      implicit none
    78
    89contains
     
    1213
    1314    ! Parametrization of the momentum flux deposition due to a discrete
    14     ! number of gravity waves. 
     15    ! number of gravity waves.
    1516    ! Author: F. Lott
    1617    ! July, 12th, 2012
     
    3940
    4041
    41       include "clesphys.h"
    4242    ! OFFLINE:
    4343    ! include "dimensions_mod.f90"
  • LMDZ6/trunk/libf/phylmd/fonte_neige_mod.F90

    r5274 r5282  
    246246#endif
    247247#endif
    248     USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
     248    USE clesphys_mod_h
     249  USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
    249250          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
    250251          , R_ecc, R_peri, R_incl                                      &
     
    258259          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
    259260          , RALPD, RBETD, RGAMD
    260        
     261
    261262! Routine de traitement de la fonte de la neige dans le cas du traitement
    262263! de sol simplifie!
     
    266267!   nisurf       surface a traiter
    267268!   knindex      index des mailles valables pour surface a traiter
    268 !   dtime       
     269!   dtime
    269270!   tsurf        temperature de surface
    270271!   precip_rain  precipitations liquides
     
    279280  INCLUDE "YOETHF.h"
    280281  INCLUDE "FCTTRE.h"
    281   INCLUDE "clesphys.h"
    282282
    283283! Input variables
  • LMDZ6/trunk/libf/phylmd/freinage.f90

    r5274 r5282  
    66
    77    !ONLINE:
     8    USE clesphys_mod_h
    89    use dimphy, only: klon, klev
    910!    USE control, ONLY: nvm
     
    2627
    2728
    28     include "clesphys.h"
    2929    include "YOEGWD.h"
    3030!FC
  • LMDZ6/trunk/libf/phylmd/infotrac_phy.F90

    r5271 r5282  
    130130
    131131SUBROUTINE init_infotrac_phy
     132   USE iniprint_mod_h
    132133   USE ioipsl_getin_p_mod, ONLY: getin_p
    133134   USE lmdz_reprobus_wrappers, ONLY: Init_chem_rep_trac
     
    155156! Declarations:
    156157
    157    INCLUDE "iniprint.h"
    158158
    159159!------------------------------------------------------------------------------------------------------------------------------
  • LMDZ6/trunk/libf/phylmd/ini_undefSTD.f90

    r5268 r5282  
    44
    55SUBROUTINE ini_undefstd(itap, itapm1)
     6  USE clesphys_mod_h
    67  USE dimphy
    78  USE phys_state_var_mod ! Variables sauvegardees de la physique
    89  USE phys_cal_mod, ONLY: mth_len
    910  IMPLICIT NONE
    10   include "clesphys.h"
    1111
    1212  ! ====================================================================
  • LMDZ6/trunk/libf/phylmd/iniradia.F90

    r2470 r5282  
    11SUBROUTINE iniradia(klon, klev, pres)
    22
     3  USE clesphys_mod_h
    34  IMPLICIT NONE
    45  ! ======================================================================
     
    1920  REAL pres(klev+1)
    2021
    21   include "clesphys.h"
    2222
    2323  ! CALL suphel     ! initialiser constantes et parametres phys.
  • LMDZ6/trunk/libf/phylmd/inlandsis/surf_inlandsis_mod.f90

    r5273 r5282  
    10281028
    10291029    SUBROUTINE sisvatetat0 (fichnom, ikl2i)
     1030        USE clesphys_mod_h
    10301031        USE dimphy
    10311032        USE mod_grid_phy_lmdz
     
    10381039        USE indice_sol_mod
    10391040        USE dimsoil_mod_h, ONLY: nsoilmx, nsnowmx, nsismx
     1041        USE clesphys_mod_h
    10401042        IMPLICIT none
    10411043        !======================================================================
     
    10461048
    10471049        !
    1048         include "clesphys.h"
    10491050        include "compbl.h"
    10501051
     
    12791280
    12801281        IMPLICIT none
    1281         include "clesphys.h"
    12821282        include "compbl.h"
    12831283
  • LMDZ6/trunk/libf/phylmd/iophy.F90

    r5267 r5282  
    207207
    208208 SUBROUTINE histbeg_phyxios(name,itau0,zjulian,dtime,ffreq,lev,nhori,nid_day)
    209 !  USE dimphy
     209  USE clesphys_mod_h
     210  USE dimphy
    210211  USE mod_phys_lmdz_para, ONLY: is_sequential, is_using_mpi, is_mpi_root, &
    211212                                jj_begin, jj_end, jj_nb
     
    214215  USE wxios, ONLY: wxios_add_file, using_xios
    215216  IMPLICIT NONE
    216   INCLUDE 'clesphys.h'
    217217   
    218218  CHARACTER*(*), INTENT(IN) :: name
     
    463463    USE aero_mod, ONLY : naero_tot, name_aero_tau
    464464    USE print_control_mod, ONLY: prt_level,lunout
    465 
     465    USE clesphys_mod_h
    466466    IMPLICIT NONE
    467 
    468     INCLUDE "clesphys.h"
    469467
    470468    INTEGER                          :: iff
     
    487485    CALL conf_physoutputs(nomvar,flag_var)
    488486
    489     IF(.NOT.lpoint) THEN 
     487    IF(.NOT.lpoint) THEN
    490488       IF ( flag_var(iff)<=lev_files(iff) ) THEN
    491489          CALL histdef (nid_files(iff),nomvar,titrevar,unitvar, &
    492490               nbp_lon,jj_nb,nhorim(iff), 1,1,1, -99, 32, &
    493                type_ecri(iff), zstophym,zoutm(iff))               
     491               type_ecri(iff), zstophym,zoutm(iff))
    494492       ENDIF
    495493    ELSE
     
    497495          CALL histdef (nid_files(iff),nomvar,titrevar,unitvar, &
    498496               npstn,1,nhorim(iff), 1,1,1, -99, 32, &
    499                type_ecri(iff), zstophym,zoutm(iff))               
     497               type_ecri(iff), zstophym,zoutm(iff))
    500498       ENDIF
    501499    ENDIF
    502500
    503     ! Set swaero_diag=true if at least one of the concerned variables are defined 
    504     IF (nomvar=='topswad' .OR. nomvar=='topswad0' .OR. nomvar=='solswad' .OR. nomvar=='solswad0' .OR. & 
    505         nomvar=='toplwad' .OR. nomvar=='toplwad0' .OR. nomvar=='sollwad' .OR. nomvar=='sollwad0' .OR. & 
    506         nomvar=='topswai' .OR. nomvar=='solswai' ) THEN 
     501    ! Set swaero_diag=true if at least one of the concerned variables are defined
     502    IF (nomvar=='topswad' .OR. nomvar=='topswad0' .OR. nomvar=='solswad' .OR. nomvar=='solswad0' .OR. &
     503        nomvar=='toplwad' .OR. nomvar=='toplwad0' .OR. nomvar=='sollwad' .OR. nomvar=='sollwad0' .OR. &
     504        nomvar=='topswai' .OR. nomvar=='solswai' ) THEN
    507505       IF  ( flag_var(iff)<=lev_files(iff) ) swaero_diag=.TRUE.
    508506    ENDIF
    509507
    510     ! Set dryaod_diag=true if at least one of the concerned variables are defined 
     508    ! Set dryaod_diag=true if at least one of the concerned variables are defined
    511509    IF (nomvar=='dryod550aer') THEN
    512510      IF  ( flag_var(iff)<=lev_files(iff) ) dryaod_diag=.TRUE.
     
    520518    ! Set ok_4xCO2atm=true if at least one of the concerned variables are
    521519    ! defined
    522     IF (nomvar=='rsut4co2'.OR.nomvar=='rlut4co2'.OR.nomvar=='rsutcs4co2' & 
     520    IF (nomvar=='rsut4co2'.OR.nomvar=='rlut4co2'.OR.nomvar=='rsutcs4co2' &
    523521        .OR. nomvar=='rlutcs4co2'.OR.nomvar=='rsu4co2'.OR.nomvar=='rsucs4co2' &
    524522        .OR.nomvar=='rsu4co2'.OR.nomvar=='rsucs4co2'.OR.nomvar=='rsd4co2'.OR. &
     
    526524        nomvar=='rld4co2'.OR.nomvar=='rldcs4co2') THEN
    527525        IF ( flag_var(iff)<=lev_files(iff) ) ok_4xCO2atm=.TRUE.
    528     ENDIF 
     526    ENDIF
    529527  END SUBROUTINE histdef2d_old
    530528
     
    539537    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    540538    USE print_control_mod, ONLY: prt_level,lunout
     539    USE clesphys_mod_h
    541540    IMPLICIT NONE
    542 
    543     INCLUDE "clesphys.h"
    544541
    545542    INTEGER                          :: iff
     
    587584                                   clef_stations, phys_out_filenames, lev_files, &
    588585                                   nid_files, nhorim, swaerofree_diag, swaero_diag, dryaod_diag,&
    589                                    ok_4xCO2atm 
    590     USE print_control_mod, ONLY: prt_level,lunout 
     586                                   ok_4xCO2atm
     587    USE print_control_mod, ONLY: prt_level,lunout
    591588    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    592589    USE aero_mod, ONLY : naero_tot, name_aero_tau
    593590    USE wxios, ONLY: wxios_add_field_to_file, using_xios
    594591    USE print_control_mod, ONLY: prt_level,lunout
     592    USE clesphys_mod_h
    595593    IMPLICIT NONE
    596594
    597     INCLUDE "clesphys.h"
    598595
    599596    INTEGER                          :: iff
     
    668665    ENDIF
    669666
    670     ! Set swaerofree_diag=true if at least one of the concerned variables are defined 
    671     IF (var%name=='SWupTOAcleanclr' .OR. var%name=='SWupSFCcleanclr' .OR. var%name=='SWdnSFCcleanclr' .OR. & 
     667    ! Set swaerofree_diag=true if at least one of the concerned variables are defined
     668    IF (var%name=='SWupTOAcleanclr' .OR. var%name=='SWupSFCcleanclr' .OR. var%name=='SWdnSFCcleanclr' .OR. &
    672669        var%name=='LWupTOAcleanclr' .OR. var%name=='LWdnSFCcleanclr' ) THEN
    673670       IF  ( var%flag(iff)<=lev_files(iff) ) swaerofree_diag=.TRUE.
     
    675672
    676673    ! set dryaod_dry=true if at least one of the concerned variables are defined
    677     IF (var%name=='dryod550aer') THEN 
     674    IF (var%name=='dryod550aer') THEN
    678675      IF  ( var%flag(iff)<=lev_files(iff) ) dryaod_diag=.TRUE.
    679676    ENDIF
    680677    !
    681     DO naero = 1, naero_tot-1 
     678    DO naero = 1, naero_tot-1
    682679      IF (var%name=='dryod550_'//name_aero_tau(naero)) THEN
    683680        IF  ( var%flag(iff)<=lev_files(iff) ) dryaod_diag=.TRUE.
     
    686683    ! Set ok_4xCO2atm=true if at least one of the concerned variables are
    687684    ! defined
    688     IF (var%name=='rsut4co2'.OR.var%name=='rlut4co2'.OR.var%name=='rsutcs4co2' & 
     685    IF (var%name=='rsut4co2'.OR.var%name=='rlut4co2'.OR.var%name=='rsutcs4co2' &
    689686        .OR. var%name=='rlutcs4co2'.OR.var%name=='rsu4co2'.OR.var%name=='rsucs4co2' &
    690687        .OR.var%name=='rsu4co2'.OR.var%name=='rsucs4co2'.OR.var%name=='rsd4co2'.OR. &
     
    692689        var%name=='rld4co2'.OR.var%name=='rldcs4co2') THEN
    693690        IF ( var%flag(iff)<=lev_files(iff) ) ok_4xCO2atm=.TRUE.
    694     ENDIF 
     691    ENDIF
    695692  END SUBROUTINE histdef2d
    696693
     
    708705    USE wxios, ONLY: wxios_add_field_to_file, using_xios
    709706    USE print_control_mod, ONLY: prt_level,lunout
     707    USE clesphys_mod_h
    710708    IMPLICIT NONE
    711709
    712     INCLUDE "clesphys.h"
    713710
    714711    INTEGER                          :: iff
     
    943940  SUBROUTINE histwrite2d_phy(var,field, STD_iff)
    944941
     942  USE clesphys_mod_h
    945943  USE mod_phys_lmdz_omp_transfert, ONLY: bcast_omp
    946944  USE dimphy, ONLY: klon, klev
     
    958956
    959957  IMPLICIT NONE
    960   INCLUDE 'clesphys.h'
    961958
    962959  TYPE(ctrl_out), INTENT(IN) :: var
     
    11561153  SUBROUTINE histwrite3d_phy(var, field, STD_iff)
    11571154
     1155  USE clesphys_mod_h
    11581156  USE mod_phys_lmdz_omp_transfert, ONLY: bcast_omp
    11591157  USE dimphy, ONLY: klon, klev
     
    11701168
    11711169  IMPLICIT NONE
    1172   INCLUDE 'clesphys.h'
    11731170
    11741171  TYPE(ctrl_out), INTENT(IN) :: var
  • LMDZ6/trunk/libf/phylmd/limit_slab.f90

    r5268 r5282  
    33SUBROUTINE limit_slab(itime, dtime, jour, lmt_bils, diff_sst, diff_siv)
    44
     5  USE clesphys_mod_h
    56  USE dimphy
    67  USE mod_grid_phy_lmdz, ONLY: klon_glo
    78  USE mod_phys_lmdz_para
    8   USE netcdf 
     9  USE netcdf
    910  USE indice_sol_mod
    1011  USE ocean_slab_mod, ONLY: nslay
     
    1213  IMPLICIT NONE
    1314
    14   INCLUDE "clesphys.h"
    1515
    1616! In- and ouput arguments
  • LMDZ6/trunk/libf/phylmd/moy_undefSTD.f90

    r5268 r5282  
    33
    44SUBROUTINE moy_undefstd(itap, itapm1)
     5  USE clesphys_mod_h
    56  USE netcdf
    67  USE dimphy
    78  USE phys_state_var_mod
    89  USE wxios, ONLY: missing_val_xios => missing_val, using_xios
    9  
     10
    1011  USE phys_cal_mod, ONLY: mth_len
    1112  IMPLICIT NONE
    12   include "clesphys.h"
    1313  REAL :: missing_val
    1414
  • LMDZ6/trunk/libf/phylmd/nuage.f90

    r5274 r5282  
    44    pct, pctlwp, ok_aie, mass_solu_aero, mass_solu_aero_pi, bl95_b0, bl95_b1, distcltop, &
    55    temp_cltop, cldtaupi, re, fl)
     6  USE clesphys_mod_h
    67  USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
    78          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
     
    5152
    5253  include "nuage.h" ! JBM 3/14
    53   include "clesphys.h"
    5454
    5555  REAL paprs(klon, klev+1), pplay(klon, klev)
  • LMDZ6/trunk/libf/phylmd/ocean_albedo.f90

    r5268 r5282  
    1818!!
    1919!!    IMPLICIT ARGUMENTS
    20 !!    ------------------ 
    21 !!     
     20!!    ------------------
     21!!
    2222!!    REFERENCE
    2323!!    ---------
    24 !!     
     24!!
    2525!!    AUTHOR
    2626!!    ------
     
    3737!!                  10/2016 O. Boucher :: some optimisation following R.
    3838!!                  Seferian's work in the CNRM Model
    39 !!       
     39!!
    4040!-------------------------------------------------------------------------------
    4141!
     
    4646USE dimphy
    4747USE phys_state_var_mod, ONLY : chl_con
     48USE clesphys_mod_h
    4849!
    4950!
     
    5354!              -------------------------
    5455!
    55 include "clesphys.h"
    5656!
    5757INTEGER, INTENT(IN) :: knon
  • LMDZ6/trunk/libf/phylmd/ocean_cpl_mod.f90

    r5274 r5282  
    88!
    99
    10   IMPLICIT NONE
     10  USE clesphys_mod_h
     11    IMPLICIT NONE
    1112  PRIVATE
    1213
     
    4041! Initialize module cpl_init
    4142    CALL cpl_init(dtime, rlon, rlat)
    42    
     43
    4344  END SUBROUTINE ocean_cpl_init
    4445!
     
    6061!
    6162! This subroutine treats the "open ocean", all grid points that are not entierly covered
    62 ! by ice. The subroutine first receives fields from coupler, then some calculations at 
     63! by ice. The subroutine first receives fields from coupler, then some calculations at
    6364! surface is done and finally it sends some fields to the coupler.
    6465!
     
    8283         cpl_send_ocean_fields
    8384    use config_ocean_skin_m, only: activate_ocean_skin
    84 
    85 
    86     INCLUDE "clesphys.h"
    87 !   
    88 ! Input arguments 
     85    USE clesphys_mod_h
     86! Input arguments
    8987!****************************************************************************************
    9088    INTEGER, INTENT(IN)                      :: itime, knon
     
    132130    REAL, DIMENSION(klon), INTENT(INOUT)     :: snow
    133131    REAL, DIMENSION(klon), INTENT(INOUT)     :: agesno
    134  
     132
    135133! Output arguments
    136134!****************************************************************************************
     
    139137    REAL, DIMENSION(klon), INTENT(OUT)       :: flux_u1, flux_v1
    140138    REAL, DIMENSION(klon), INTENT(OUT)       :: tsurf_new
    141     REAL, DIMENSION(klon), INTENT(OUT)       :: dflux_s, dflux_l     
     139    REAL, DIMENSION(klon), INTENT(OUT)       :: dflux_s, dflux_l
    142140    REAL, intent(out):: sens_prec_liq(:) ! (knon)
    143141
    144142    REAL, INTENT(OUT):: sss(:) ! (klon)
    145143    ! bulk salinity of the surface layer of the ocean, in ppt
    146  
     144
    147145
    148146! Local variables
     
    156154    REAL, DIMENSION(klon) :: u1_lay, v1_lay
    157155    LOGICAL               :: check=.FALSE.
    158     REAL sens_prec_sol(knon) 
    159     REAL, DIMENSION(klon) :: lat_prec_liq, lat_prec_sol   
     156    REAL sens_prec_sol(knon)
     157    REAL, DIMENSION(klon) :: lat_prec_liq, lat_prec_sol
    160158
    161159! End definitions
     
    180178    agesno(:) = 0.
    181179    lat_prec_liq = 0.; lat_prec_sol = 0.
    182    
     180
    183181
    184182    DO i = 1, knon
     
    203201
    204202    ! assertion: tsurf_new == tsurf_cpl
    205    
     203
    206204    do j = 1, knon
    207205      i = knindex(j)
     
    213211
    214212
    215    
     213
    216214! - Flux calculation at first modele level for U and V
    217215    CALL calcul_flux_wind(knon, dtime, &
     
    219217         AcoefU, AcoefV, BcoefU, BcoefV, &
    220218         p1lay, temp_air, &
    221          flux_u1, flux_v1) 
     219         flux_u1, flux_v1)
    222220
    223221!****************************************************************************************
     
    226224!****************************************************************************************
    227225    fder_new(:) = fder_old(:) + dflux_s(:) + dflux_l(:)
    228    
     226
    229227    iloc = MAXLOC(fder_new(1:klon))
    230228    IF (check .AND. fder_new(iloc(1))> 0.) THEN
     
    262260       tsurf_new, dflux_s, dflux_l, rhoa)
    263261!
    264 ! This subroutine treats the ocean where there is ice. The subroutine first receives 
    265 ! fields from coupler, then some calculations at surface is done and finally sends 
     262! This subroutine treats the ocean where there is ice. The subroutine first receives
     263! fields from coupler, then some calculations at surface is done and finally sends
    266264! some fields to the coupler.
    267 !   
     265!
    268266    USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
    269267          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
     
    285283
    286284
    287     INCLUDE "clesphys.h"
    288285
    289286! Input arguments
  • LMDZ6/trunk/libf/phylmd/ocean_forced_mod.F90

    r5274 r5282  
    5050#endif
    5151#endif
     52    USE clesphys_mod_h
    5253    USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
    5354          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
     
    6263          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
    6364          , RALPD, RBETD, RGAMD
    64     INCLUDE "clesphys.h"
    6565    INCLUDE "flux_arp.h"
    6666
     
    286286#endif
    287287#endif
     288    USE clesphys_mod_h
    288289    USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
    289290          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
     
    302303!   INCLUDE "indicesol.h"
    303304
    304     INCLUDE "clesphys.h"
    305305    INCLUDE "flux_arp.h"
    306306
  • LMDZ6/trunk/libf/phylmd/ocean_slab_mod.f90

    r5274 r5282  
    343343       tsurf_new, dflux_s, dflux_l, slab_bils)
    344344   
     345    USE clesphys_mod_h
    345346    USE calcul_fluxs_mod
    346347    USE slab_heat_transp_mod, ONLY: divgrad_phy,slab_ekman1,slab_ekman2,slab_gmdiff
    347348    USE mod_phys_lmdz_para
    348349
    349     INCLUDE "clesphys.h"
    350350
    351351! This routine
     
    682682       tsurf_new, dflux_s, dflux_l, swnet)
    683683
     684   USE clesphys_mod_h
    684685   USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
    685686          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
     
    697698
    698699
    699    INCLUDE "clesphys.h"
    700700
    701701! Input arguments
  • LMDZ6/trunk/libf/phylmd/paramlmdz_phy_mod.F90

    r5274 r5282  
    88  SUBROUTINE ini_paramLMDZ_phy(dtime,nid_ctesGCM)
    99
    10     USE iophy
     10    USE clesphys_mod_h
     11    USE iophy
    1112    USE dimphy
    1213    USE ioipsl, only: histbeg, histvert, histdef, histend, ymds2ju
     
    3132IMPLICIT NONE
    3233
    33     include "clesphys.h"
    3434
    3535
     
    166166#endif
    167167
     168    USE clesphys_mod_h
    168169    USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
    169170          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
     
    180181IMPLICIT NONE
    181182
    182     include "clesphys.h"
    183183
    184184
  • LMDZ6/trunk/libf/phylmd/pbl_surface_mod.F90

    r5274 r5282  
    407407#endif
    408408#endif
     409    USE clesphys_mod_h
    409410    USE ioipsl_getin_p_mod, ONLY : getin_p
    410411    use phys_state_var_mod, only: ds_ns, dt_ns, delta_sst, delta_sal, dter, &
     
    432433    INCLUDE "YOETHF.h"
    433434    INCLUDE "FCTTRE.h"
    434     INCLUDE "clesphys.h"
    435435    INCLUDE "compbl.h"
    436436    INCLUDE "flux_arp.h"
     
    42984298    ! Give default values where new fraction has appread
    42994299
     4300    USE clesphys_mod_h
    43004301    USE indice_sol_mod
    43014302    use phys_state_var_mod, only: delta_sal, ds_ns, dt_ns, delta_sst, dter, &
    43024303         dser, dt_ds
    43034304    use config_ocean_skin_m, only: activate_ocean_skin
    4304     INCLUDE "clesphys.h"
    43054305    INCLUDE "compbl.h"
    43064306
  • LMDZ6/trunk/libf/phylmd/phyaqua_mod.f90

    r5274 r5282  
    44MODULE phyaqua_mod
    55  ! Routines complementaires pour la physique planetaire.
    6   IMPLICIT NONE
     6  USE clesphys_mod_h
     7    IMPLICIT NONE
    78
    89CONTAINS
     
    5455
    5556
    56     include "clesphys.h"
    5757
    5858    INTEGER, INTENT (IN) :: nlon, year_len, iflag_phys
  • LMDZ6/trunk/libf/phylmd/phyetat0_mod.f90

    r5274 r5282  
    1010SUBROUTINE phyetat0 (fichnom, clesphy0, tabcntr0)
    1111
     12  USE clesphys_mod_h
    1213  USE dimphy, only: klon, zmasq, klev
    1314  USE iophy, ONLY : init_iophy_new
     
    6364  ! Objet: Lecture de l'etat initial pour la physique
    6465  !======================================================================
    65   include "clesphys.h"
    6666  include "alpale.h"
    6767  include "compbl.h"
  • LMDZ6/trunk/libf/phylmd/phyredem.f90

    r5273 r5282  
    99! Purpose: Write restart state for physics.
    1010!-------------------------------------------------------------------------------
     11  USE clesphys_mod_h
    1112  USE dimphy, ONLY: klon, klev
    1213  USE fonte_neige_mod,  ONLY : fonte_neige_final
     
    4243  USE ocean_slab_mod, ONLY : nslay, tslab, seaice, tice, fsic
    4344  USE time_phylmdz_mod, ONLY: annee_ref, day_end, itau_phy, pdtphys
    44   use config_ocean_skin_m, only: activate_ocean_skin 
     45  use config_ocean_skin_m, only: activate_ocean_skin
    4546  USE dimsoil_mod_h, ONLY: nsoilmx
    4647  IMPLICIT none
    47   include "clesphys.h"
    4848  include "alpale.h"
    4949  include "compbl.h"
  • LMDZ6/trunk/libf/phylmd/phys_output_mod.F90

    r5274 r5282  
    5757#endif
    5858
     59    USE clesphys_mod_h
    5960    USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_STRATAER
    6061
     
    7273          , RALPD, RBETD, RGAMD
    7374IMPLICIT NONE
    74     include "clesphys.h"
    7575
    7676
  • LMDZ6/trunk/libf/phylmd/phys_output_var_mod.f90

    r5268 r5282  
    164164 
    165165  REAL, SAVE, ALLOCATABLE:: tkt(:) ! (klon)
    166   ! épaisseur (m) de la couche de diffusion thermique (microlayer)
     166  ! paisseur (m) de la couche de diffusion thermique (microlayer)
    167167  ! cool skin thickness
    168168
    169169  REAL, SAVE, ALLOCATABLE:: tks(:) ! (klon)
    170   ! épaisseur (m) de la couche de diffusion de masse (microlayer)
     170  ! paisseur (m) de la couche de diffusion de masse (microlayer)
    171171 
    172172  REAL, SAVE, ALLOCATABLE:: taur(:) ! (klon) momentum flux due to rain, in Pa
     
    185185  !======================================================================
    186186  SUBROUTINE phys_output_var_init
     187    USE clesphys_mod_h
    187188    use dimphy
    188189    use config_ocean_skin_m, only: activate_ocean_skin
    189 
     190    USE clesphys_mod_h
    190191    IMPLICIT NONE
    191 
    192     include "clesphys.h"
    193 
    194     !------------------------------------------------
    195192
    196193    allocate(snow_o(klon), zfra_o(klon))
     
    213210    allocate(cloudth_sth(klon,klev))
    214211    allocate(cloudth_senv(klon,klev))
    215     cloudth_sth = 0. ; cloudth_senv = 0. 
     212    cloudth_sth = 0. ; cloudth_senv = 0.
    216213    allocate(cloudth_sigmath(klon,klev))
    217214    allocate(cloudth_sigmaenv(klon,klev))
     
    268265    IMPLICIT NONE
    269266
    270     include "clesphys.h"
    271267
    272268    deallocate(snow_o,zfra_o,itau_con)
  • LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90

    r5274 r5282  
    470470    USE YOESW, ONLY : RSUN
    471471#endif
     472    USE clesphys_mod_h
    472473    USE tracinca_mod, ONLY: config_inca
    473474    USE config_ocean_skin_m, ONLY: activate_ocean_skin
     
    490491IMPLICIT NONE
    491492
    492     INCLUDE "clesphys.h"
    493493    INCLUDE "alpale.h"
    494494    INCLUDE "compbl.h"
  • LMDZ6/trunk/libf/phylmd/phys_state_var_mod.F90

    r5208 r5282  
    539539USE infotrac_phy, ONLY : ntraciso=>ntiso,niso
    540540#endif
     541USE clesphys_mod_h
    541542USE indice_sol_mod
    542543use config_ocean_skin_m, only: activate_ocean_skin
     
    552553! climatology and the daylight climatology
    553554
    554 include "clesphys.h"
    555555
    556556      print*, 'is_initialized', is_initialized
     
    795795    SUBROUTINE phys_state_var_end
    796796      ! Useful only for lmdz1d.
    797 !USE dimphy
     797      USE clesphys_mod_h
    798798USE indice_sol_mod
    799799use config_ocean_skin_m, only: activate_ocean_skin
    800800use surface_data, only: type_ocean
    801801IMPLICIT NONE
    802 include "clesphys.h"
    803802
    804803      DEALLOCATE(pctsrf, ftsol, falb1, falb2)
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r5274 r5282  
    370370          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
    371371          , RALPD, RBETD, RGAMD
     372       USE clesphys_mod_h
    372373
    373374    IMPLICIT NONE
     
    423424
    424425    include "regdim.h"
    425     include "clesphys.h"
    426426    include "alpale.h"
    427427    include "dimpft.h"
  • LMDZ6/trunk/libf/phylmd/phytrac_mod.f90

    r5274 r5282  
    5858    USE infotrac_phy, ONLY: nbtr, type_trac
    5959    USE tracco2i_mod, ONLY: tracco2i_init
    60    
     60
    6161    IMPLICIT NONE
    6262
     
    7575    !===============================================================================
    7676    !    -- Do specific treatment according to chemestry model or local LMDZ tracers
    77     !     
     77    !
    7878    !===============================================================================
    7979    !   -- CO2 interactif --
    8080    IF (ANY(type_trac == ['co2i','inco'])) CALL tracco2i_init()
    8181
    82        !   -- type_trac == 'co2i' ! PC 
     82       !   -- type_trac == 'co2i' ! PC
    8383       !   -- CO2 interactif --
    84        !   -- source is updated with FF and BB emissions 
    85        !   -- and net fluxes from ocean and orchidee 
     84       !   -- source is updated with FF and BB emissions
     85       !   -- and net fluxes from ocean and orchidee
    8686       !   -- sign convention : positive into the atmosphere
    8787
     
    105105       da,        phi,      mp,       upwd,           &
    106106       phi2,      d1a,      dam,      sij, wght_cvfd, &   ! RomP +RL
    107        wdtrainA,  wdtrainM, sigd,     clw, elij,      &   ! RomP 
     107       wdtrainA,  wdtrainM, sigd,     clw, elij,      &   ! RomP
    108108       evap,      ep,       epmlmMm,  eplaMm,         &   ! RomP
    109109       dnwd,      aerosol_couple,     flxmass_w,      &
     
    111111       rfname,                                        &
    112112       d_tr_dyn,                                      &   ! RomP
    113        tr_seri, init_source)         
     113       tr_seri, init_source)
    114114    !
    115115    !======================================================================
     
    163163          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
    164164          , RALPD, RBETD, RGAMD
     165    USE clesphys_mod_h
    165166IMPLICIT NONE
    166167
    167168
    168     INCLUDE "clesphys.h"
    169169    !==========================================================================
    170170    !                   -- ARGUMENT DESCRIPTION --
  • LMDZ6/trunk/libf/phylmd/printflag.f90

    r5268 r5282  
    88  ! Auteur :  P. Le Van
    99
     10  USE clesphys_mod_h
    1011  IMPLICIT NONE
    1112
     
    1617  INTEGER radpas, radpas0
    1718
    18   include "clesphys.h"
    1919
    2020
  • LMDZ6/trunk/libf/phylmd/radiation_AR4.f90

    r5274 r5282  
    55    tauae, pizae, cgae, ptaua, pomegaa, ptopswad, psolswad, ptopswai, &
    66    psolswai, ok_ade, ok_aie)
     7  USE clesphys_mod_h
    78  USE dimphy
    89  USE print_control_mod, ONLY: lunout
     
    6061  ! IM ctes ds clesphys.h   REAL(KIND=8) RCO2  ! concentration CO2 (IPCC:
    6162  ! 353.E-06*44.011/28.97)
    62   include "clesphys.h"
    6363
    6464  REAL (KIND=8) ppsol(kdlon) ! SURFACE PRESSURE (PA)
     
    322322SUBROUTINE swu_lmdar4(psct, pcldsw, ppmb, ppsol, prmu0, pfrac, ptave, pwv, &
    323323    paki, pcld, pclear, pdsig, pfact, prmu, psec, pud)
     324  USE clesphys_mod_h
    324325  USE dimphy
    325326  USE radiation_ar4_param, ONLY: zpdh2o, zpdumg, zprh2o, zprumg, rtdh2o, &
     
    346347  REAL (KIND=8) psct
    347348  ! IM ctes ds clesphys.h   REAL(KIND=8) RCO2
    348   include "clesphys.h"
    349349  REAL (KIND=8) pcldsw(kdlon, kflev)
    350350  REAL (KIND=8) ppmb(kdlon, kflev+1)
     
    15471547    ptau, pcgaz, ppizaz, pray1, pray2, prefz, prj, prk, prmue, ptauaz, ptra1, &
    15481548    ptra2)
     1549  USE clesphys_mod_h
    15491550  USE dimphy
    15501551  IMPLICIT NONE
     
    22012202  ! REAL(KIND=8) RCFC12 ! CFC12 CONCENTRATION (IPCC: 484.E-12*
    22022203  ! 120.9140/28.97)
    2203   include "clesphys.h"
    22042204  REAL (KIND=8) pcldld(kdlon, kflev) ! DOWNWARD EFFECTIVE CLOUD COVER
    22052205  REAL (KIND=8) pcldlu(kdlon, kflev) ! UPWARD EFFECTIVE CLOUD COVER
     
    23452345! IM ctes ds clesphys.h   SUBROUTINE LWU(RCO2, RCH4, RN2O, RCFC11, RCFC12,
    23462346SUBROUTINE lwu_lmdar4(paer, pdp, ppmb, ppsol, poz, ptave, pview, pwv, pabcu)
     2347  USE clesphys_mod_h
    23472348  USE dimphy
    23482349  USE radiation_ar4_param, ONLY: tref, rt1, raer, at, bt, oct
     
    24002401  ! REAL(KIND=8) RCO2
    24012402  ! REAL(KIND=8) RCH4, RN2O, RCFC11, RCFC12
    2402   include "clesphys.h"
    24032403  REAL (KIND=8) paer(kdlon, kflev, 5)
    24042404  REAL (KIND=8) pdp(kdlon, kflev)
  • LMDZ6/trunk/libf/phylmd/radlwsw_m.F90

    r5274 r5282  
    9898          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
    9999          , RALPD, RBETD, RGAMD
     100    USE clesphys_mod_h
    100101
    101102    !======================================================================
     
    203204    ! ==============
    204205    include "YOETHF.h"
    205     include "clesphys.h"
    206206
    207207    ! Input arguments
  • LMDZ6/trunk/libf/phylmd/readaerosol_interp.f90

    r5274 r5282  
    1313! 4) Test for negative mass values
    1414
     15  USE clesphys_mod_h
    1516  USE ioipsl
    1617  USE dimphy, ONLY : klev,klon
    17   USE mod_phys_lmdz_para, ONLY : mpi_rank 
     18  USE mod_phys_lmdz_para, ONLY : mpi_rank
    1819  USE readaerosol_mod
    1920  USE aero_mod, ONLY : naero_spc, name_aero
     
    3839
    3940
    40   INCLUDE "chem.h"     
    41   INCLUDE "clesphys.h"
     41  INCLUDE "chem.h"
    4242
    4343!
  • LMDZ6/trunk/libf/phylmd/regr_pr_time_av_m.f90

    r5274 r5282  
    140140          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
    141141          , RALPD, RBETD, RGAMD
     142  USE clesphys_mod_h
    142143!-------------------------------------------------------------------------------
    143144! Arguments:
     
    159160!-------------------------------------------------------------------------------
    160161! Local variables:
    161   include "clesphys.h"
    162162
    163163  CHARACTER(LEN=80)  :: sub
  • LMDZ6/trunk/libf/phylmd/surf_land_bucket_mod.F90

    r5274 r5282  
    4444#endif
    4545#endif
     46    USE clesphys_mod_h
    4647    USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
    4748          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
     
    6061! Bucket calculations for surface.
    6162!
    62     INCLUDE "clesphys.h"
    6363
    6464! Input variables 
  • LMDZ6/trunk/libf/phylmd/surf_land_mod.F90

    r5274 r5282  
    7373#endif
    7474
     75    USE clesphys_mod_h
    7576    USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
    7677          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
     
    8889    USE dimsoil_mod_h, ONLY: nsoilmx
    8990
    90     INCLUDE "clesphys.h"
    9191    INCLUDE "dimpft.h"
    9292
  • LMDZ6/trunk/libf/phylmd/surf_landice_mod.F90

    r5274 r5282  
    4949 
    5050!FC
     51    USE clesphys_mod_h
    5152    USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
    5253          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
     
    7273!    INCLUDE "indicesol.h"
    7374
    74     INCLUDE "clesphys.h"
    7575
    7676! Input variables
  • LMDZ6/trunk/libf/phylmd/surf_ocean_mod.F90

    r5274 r5282  
    4343#endif
    4444#endif
     45    USE clesphys_mod_h
    4546    USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
    4647          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
     
    6566
    6667
    67     include "clesphys.h"
    6868    ! for cycle_diurne and for iflag_z0_oce==-1 (prescribed z0)
    6969
  • LMDZ6/trunk/libf/phylmd/surf_seaice_mod.F90

    r5274 r5282  
    3737  USE infotrac_phy, ONLY : ntiso,niso
    3838#endif
    39   USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
     39  USE clesphys_mod_h
     40    USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
    4041          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
    4142          , R_ecc, R_peri, R_incl                                      &
     
    5657! in here because it is the same calculation for the different modes of ocean.
    5758!
    58     INCLUDE "clesphys.h"
    5959
    6060
  • LMDZ6/trunk/libf/phylmd/sw_aeroAR4.f90

    r5274 r5282  
    2020     ok_ade, ok_aie, flag_aerosol, flag_aerosol_strat )
    2121
     22  USE clesphys_mod_h
    2223  USE dimphy
    2324  USE phys_output_mod, ONLY : swaero_diag
     
    3940
    4041
    41   INCLUDE "clesphys.h"
    4242  !
    4343  !     ------------------------------------------------------------------
  • LMDZ6/trunk/libf/phylmd/tracco2i_mod.f90

    r5274 r5282  
    3434    USE carbon_cycle_mod, ONLY: id_CO2, nbcf_in, fields_in, cfname_in
    3535    USE carbon_cycle_mod, ONLY: fco2_ocn_day, fco2_ff, fco2_bb, fco2_land, fco2_ocean
    36     USE carbon_cycle_mod, ONLY: read_fco2_ocean_cor,var_fco2_ocean_cor,fco2_ocean_cor 
    37     USE carbon_cycle_mod, ONLY: read_fco2_land_cor,var_fco2_land_cor,fco2_land_cor 
     36    USE carbon_cycle_mod, ONLY: read_fco2_ocean_cor,var_fco2_ocean_cor,fco2_ocean_cor
     37    USE carbon_cycle_mod, ONLY: read_fco2_land_cor,var_fco2_land_cor,fco2_land_cor
    3838    USE carbon_cycle_mod, ONLY: co2_send
    3939    USE carbon_cycle_mod, ONLY: fco2_land_nbp, fco2_land_nep, fco2_land_fLuc
     
    6262          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
    6363          , RALPD, RBETD, RGAMD
     64    USE clesphys_mod_h
    6465IMPLICIT NONE
    6566
    66     INCLUDE "clesphys.h"
    6767
    6868
  • LMDZ6/trunk/libf/phylmd/undefSTD.f90

    r5268 r5282  
    33
    44SUBROUTINE undefstd(itap, read_climoz)
     5  USE clesphys_mod_h
    56  USE netcdf
    67  USE dimphy
     
    910
    1011  IMPLICIT NONE
    11   include "clesphys.h"
    1212  REAL :: missing_val
    1313
  • LMDZ6/trunk/libf/phylmd/wx_pbl_mod.f90

    r5274 r5282  
    66! region (inside cold pools) and the (x) region (outside cold pools)
    77!
    8   USE dimphy
     8  USE clesphys_mod_h
     9    USE dimphy
    910
    1011  IMPLICIT NONE
     
    5152    INCLUDE "FCTTRE.h"
    5253    INCLUDE "YOETHF.h"
    53     INCLUDE "clesphys.h"
    5454!
    5555    INTEGER,                      INTENT(IN)        :: knon    ! number of grid cells
  • LMDZ6/trunk/libf/phylmd/wx_pbl_var_mod.f90

    r5274 r5282  
    315315                                 )
    316316!
     317    USE clesphys_mod_h
    317318    USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
    318319          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
     
    333334    INCLUDE "FCTTRE.h"
    334335    INCLUDE "YOETHF.h"
    335     INCLUDE "clesphys.h"
    336336!
    337337    INTEGER,                      INTENT(IN)        :: knon    ! number of grid cells
  • LMDZ6/trunk/libf/phylmdiso/add_phys_tend_mod.F90

    r5274 r5282  
    160160#endif 
    161161#endif
    162 USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
     162USE clesphys_mod_h
     163  USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
    163164          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
    164165          , R_ecc, R_peri, R_incl                                      &
     
    174175IMPLICIT none
    175176
    176   include "clesphys.h"
    177177
    178178! Arguments :
     
    693693!======================================================================
    694694
    695 USE phys_state_var_mod, ONLY : phys_tstep, ftsol
     695USE clesphys_mod_h
     696  USE phys_state_var_mod, ONLY : phys_tstep, ftsol
    696697USE geometry_mod, ONLY: longitude_deg, latitude_deg
    697698USE print_control_mod, ONLY: prt_level
     
    713714IMPLICIT none
    714715
    715   include "clesphys.h"
    716716
    717717! Arguments :
  • LMDZ6/trunk/libf/phylmdiso/change_srf_frac_mod.F90

    r5274 r5282  
    4141  USE infotrac_phy, ONLY: ntiso   
    4242#endif
     43    USE clesphys_mod_h
    4344    USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
    4445          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
     
    5354          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
    5455          , RALPD, RBETD, RGAMD
    55    
     56
    5657!albedo SB >>>
    57     include "clesphys.h"
    5858!albedo SB <<<
    5959
  • LMDZ6/trunk/libf/phylmdiso/clesphys_mod_h.f90

    r5281 r5282  
    1 link ../phylmd/clesphys.h
     1link ../phylmd/clesphys_mod_h.f90
  • LMDZ6/trunk/libf/phylmdiso/concvl.F90

    r5274 r5282  
    6161#endif
    6262#endif
     63  USE clesphys_mod_h
    6364  USE phys_local_var_mod, ONLY: omega
    6465  USE print_control_mod, ONLY: prt_level, lunout
     
    127128
    128129
    129   include "clesphys.h"
    130130
    131131  INTEGER, INTENT(IN)                           :: iflag_clos
  • LMDZ6/trunk/libf/phylmdiso/isotopes_routines_mod.F90

    r5274 r5282  
    1592215922#endif
    1592315923
    15924        implicit none   
     15924       USE clesphys_mod_h
     15925implicit none
    1592515926
    1592615927      ! equivalent de phyetat0 pour les isotopes
    15927 INCLUDE "clesphys.h"
    1592815928INCLUDE "compbl.h"
    1592915929
     
    1609716097  USE isotrac_mod, ONLY: index_iso,index_zone,izone_init
    1609816098#endif
     16099      USE clesphys_mod_h
    1609916100        implicit none
    16100 INCLUDE "clesphys.h"
    16101 !  INCLUDE "thermcell.h"
    1610216101INCLUDE "compbl.h"
    1610316102
     
    1647216471   USE isotrac_mod, ONLY: strtrac, initialisation_isotrac, index_iso, index_zone, izone_init
    1647316472#endif
     16473   USE clesphys_mod_h
    1647416474   IMPLICIT NONE
    16475 INCLUDE "clesphys.h"
    1647616475INCLUDE "compbl.h"
    1647716476
  • LMDZ6/trunk/libf/phylmdiso/phyaqua_mod.F90

    r5274 r5282  
    4545  USE infotrac_phy, ONLY: niso
    4646#endif
     47    USE clesphys_mod_h
    4748    USE dimsoil_mod_h, ONLY: nsoilmx
    4849
     
    6263
    6364
    64     include "clesphys.h"
    6565
    6666    INTEGER, INTENT (IN) :: nlon, year_len, iflag_phys
  • LMDZ6/trunk/libf/phylmdiso/phyetat0_mod.F90

    r5274 r5282  
    5959#endif
    6060#endif
     61  USE clesphys_mod_h
    6162  USE dimsoil_mod_h, ONLY: nsoilmx
    6263
     
    7879  ! Objet: Lecture de l'etat initial pour la physique
    7980  !======================================================================
    80   include "clesphys.h"
    8181  include "alpale.h"
    8282  include "compbl.h"
  • LMDZ6/trunk/libf/phylmdiso/phyredem.F90

    r5273 r5282  
    4646#endif
    4747#endif
     48  USE clesphys_mod_h
    4849  USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send, carbon_cycle_rad, RCO2_glo
    4950  USE indice_sol_mod, ONLY: nbsrf, is_oce, is_sic, is_ter, is_lic, epsfra
     
    5556
    5657  IMPLICIT none
    57   include "clesphys.h"
    5858  include "alpale.h"
    5959  include "compbl.h"
     
    512512    use isotrac_mod, only: index_zone,index_iso,strtrac
    513513#endif
    514       USE dimsoil_mod_h, ONLY: nsoilmx
     514      USE clesphys_mod_h
     515USE dimsoil_mod_h, ONLY: nsoilmx
    515516        implicit none
    516517
    517518        ! equivalent isotopique de phyredem
    518 INCLUDE "clesphys.h"
    519519INCLUDE "alpale.h"
    520520INCLUDE "compbl.h"
  • LMDZ6/trunk/libf/phylmdiso/physiq_mod.F90

    r5274 r5282  
    443443          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
    444444          , RALPD, RBETD, RGAMD
     445       USE clesphys_mod_h
    445446
    446447    IMPLICIT NONE
     
    496497
    497498    include "regdim.h"
    498     include "clesphys.h"
    499499    include "alpale.h"
    500500    include "dimpft.h"
Note: See TracChangeset for help on using the changeset viewer.