Ignore:
Timestamp:
Oct 30, 2024, 6:19:06 PM (9 days ago)
Author:
abarral
Message:

Turn compar1d.h date_cas.h into module
Move fcg_racmo.h to obsolete

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/dyn1d/mod_1D_cases_read2.f90

    r5270 r5302  
    315315  SUBROUTINE old_read_SCM_cas
    316316    use netcdf, only: nf90_get_var
     317    USE date_cas_mod_h
    317318    implicit none
    318     INCLUDE "date_cas.h"
    319319
    320320    INTEGER nid,rid,ierr
     
    10431043     ,hq_prof_cas,vq_prof_cas,lat_prof_cas,sens_prof_cas    &
    10441044     ,ustar_prof_cas,uw_prof_cas,vw_prof_cas,q1_prof_cas,q2_prof_cas)
    1045 
    1046 
     1045  USE compar1d_mod_h
     1046  USE date_cas_mod_h
    10471047  implicit none
    10481048
     
    10551055  ! pdt_cas: total time interval (in sec) between 2 forcing data
    10561056  !---------------------------------------------------------------------------------------
    1057 
    1058   INCLUDE "compar1d.h"
    1059   INCLUDE "date_cas.h"
    10601057
    10611058  ! inputs:
     
    12531250     ,ustar_prof_cas,uw_prof_cas,vw_prof_cas,q1_prof_cas,q2_prof_cas,tke_prof_cas)
    12541251
    1255 
     1252  USE compar1d_mod_h
     1253  USE date_cas_mod_h
    12561254  implicit none
    12571255
     
    12641262  ! pdt_cas: total time interval (in sec) between 2 forcing data
    12651263  !---------------------------------------------------------------------------------------
    1266 
    1267   INCLUDE "compar1d.h"
    1268   INCLUDE "date_cas.h"
    12691264
    12701265  ! inputs:
Note: See TracChangeset for help on using the changeset viewer.