Ignore:
Timestamp:
Oct 30, 2024, 6:19:06 PM (39 hours 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_read_std.f90

    r5285 r5302  
    9090  SUBROUTINE read_SCM_cas
    9191    use netcdf, only: nf90_get_var
     92    USE date_cas_mod_h
    9293    implicit none
    93     INCLUDE "date_cas.h"
    9494
    9595    INTEGER nid,rid,ierr
     
    330330    !program reading forcing of the case study
    331331    use netcdf, only: nf90_get_var
     332    USE compar1d_mod_h
    332333    implicit none
    333     INCLUDE "compar1d.h"
    334334
    335335    integer ntime,nlevel,k,t
     
    653653       ,lat_prof_cas,sens_prof_cas                                        &
    654654       ,ustar_prof_cas,uw_prof_cas,vw_prof_cas,q1_prof_cas,q2_prof_cas,tkes_prof_cas)
    655 
    656 
    657 
    658 
    659 
    660 
     655    USE compar1d_mod_h
     656    USE date_cas_mod_h
    661657    implicit none
    662658
     
    669665    ! pdt_cas: total time interval (in sec) between 2 forcing data
    670666    !---------------------------------------------------------------------------------------
    671 
    672     INCLUDE "compar1d.h"
    673     INCLUDE "date_cas.h"
    674667
    675668    ! inputs:
Note: See TracChangeset for help on using the changeset viewer.