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

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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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)           
Note: See TracChangeset for help on using the changeset viewer.