Ignore:
Timestamp:
Jul 23, 2024, 8:22:55 AM (6 months ago)
Author:
abarral
Message:

Handle DEBUG_IO in lmdz_cppkeys_wrapper.F90
Transform some files .F -> .[fF]90
[ne compile pas à cause de writefield_u non défini - en attente de réponse Laurent]

Location:
LMDZ6/branches/Amaury_dev/libf/phydev
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/phydev/iophy.F90

    r5099 r5101  
    103103   
    104104#ifndef CPP_IOIPSL_NO_OUTPUT
    105     call flio_dom_set(mpi_size,mpi_rank,ddid,dsg,dsl,dpf,dpl,dhs,dhe, &
     105    CALL flio_dom_set(mpi_size,mpi_rank,ddid,dsg,dsl,dpf,dpl,dhs,dhe, &
    106106                      'APPLE',phys_domain_id)
    107107#endif
     
    157157!$OMP MASTER   
    158158    if (is_sequential) then
    159       call histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
     159      CALL histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
    160160                   1,nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day)
    161161    else
    162       call histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
     162      CALL histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
    163163                   1,nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day,phys_domain_id)
    164164    endif
  • LMDZ6/branches/Amaury_dev/libf/phydev/phyetat0.F90

    r5099 r5101  
    77
    88  USE dimphy, only: klon
    9   USE iostart, ONLY : open_startphy,get_field,close_startphy
    10   USE iophy, ONLY : init_iophy_new
    11   USE geometry_mod, ONLY : longitude_deg, latitude_deg
     9  USE iostart, ONLY: open_startphy,get_field,close_startphy
     10  USE iophy, ONLY: init_iophy_new
     11  USE geometry_mod, ONLY: longitude_deg, latitude_deg
    1212
    1313  IMPLICIT NONE
  • LMDZ6/branches/Amaury_dev/libf/phydev/phyredem.F90

    r5099 r5101  
    44SUBROUTINE phyredem (fichnom)
    55
    6   USE geometry_mod, ONLY : longitude_deg, latitude_deg
     6  USE geometry_mod, ONLY: longitude_deg, latitude_deg
    77  USE iostart, ONLY: open_restartphy, close_restartphy, enddef_restartphy, put_field, put_var
    88
  • LMDZ6/branches/Amaury_dev/libf/phydev/phys_state_var_mod.F90

    r5099 r5101  
    77!======================================================================
    88
    9 !USE dimphy, only : klon
     9!USE dimphy, ONLY: klon
    1010 
    1111
     
    1717!======================================================================
    1818  SUBROUTINE phys_state_var_init()
    19 !  use dimphy, only : klon
     19!  use dimphy, ONLY: klon
    2020
    2121!  if (.not.allocated(rlat)) then
     
    2929!======================================================================
    3030  SUBROUTINE phys_state_var_end
    31 !  use dimphy, only : klon
     31!  use dimphy, ONLY: klon
    3232
    3333!  deallocate(rlat,rlon)
  • LMDZ6/branches/Amaury_dev/libf/phydev/physiq_mod.F90

    r5099 r5101  
    1313              d_u, d_v, d_t, d_qx, d_ps)
    1414
    15       USE dimphy, only : klon,klev
    16       USE infotrac_phy, only : nqtot
    17       USE geometry_mod, only : latitude
    18       USE comcstphy, only : rg
    19       USE iophy, only : histbeg_phy,histwrite_phy
    20       USE ioipsl, only : getin,histvert,histdef,histend,ymds2ju
    21       USE mod_phys_lmdz_para, only : jj_nb
    22       USE phys_state_var_mod, only : phys_state_var_init
     15      USE dimphy, ONLY: klon,klev
     16      USE infotrac_phy, ONLY: nqtot
     17      USE geometry_mod, ONLY: latitude
     18      USE comcstphy, ONLY: rg
     19      USE iophy, ONLY: histbeg_phy,histwrite_phy
     20      USE ioipsl, ONLY: getin,histvert,histdef,histend,ymds2ju
     21      USE mod_phys_lmdz_para, ONLY: jj_nb
     22      USE phys_state_var_mod, ONLY: phys_state_var_init
    2323      USE mod_grid_phy_lmdz, ONLY: nbp_lon,nbp_lat
    2424
     
    3333      integer,intent(in) :: nlon ! number of atmospheric colums
    3434      integer,intent(in) :: nlev ! number of vertical levels (should be =klev)
    35       logical,intent(in) :: debut ! signals first call to physics
    36       logical,intent(in) :: lafin ! signals last call to physics
     35      logical,intent(in) :: debut ! signals first CALL to physics
     36      logical,intent(in) :: lafin ! signals last CALL to physics
    3737      real,intent(in) :: pdtphys ! physics time step (s)
    3838      real,intent(in) :: paprs(klon,klev+1) ! interlayer pressure (Pa)
     
    7575
    7676! initializations
    77 if (debut) then ! Things to do only for the first call to physics
     77if (debut) then ! Things to do only for the first CALL to physics
    7878! load initial conditions for physics (including the grid)
    79   call phys_state_var_init() ! some initializations, required before calling phyetat0
    80   call phyetat0("startphy.nc")
     79  CALL phys_state_var_init() ! some initializations, required before calling phyetat0
     80  CALL phyetat0("startphy.nc")
    8181
    8282! Initialize outputs:
     
    8484!$OMP MASTER
    8585  iwrite_phys_omp=1 !default: output every physics timestep
    86   ! NB: getin() is not threadsafe; only one thread should call it.
    87   call getin("iwrite_phys",iwrite_phys_omp)
     86  ! NB: getin() is not threadsafe; only one thread should CALL it.
     87  CALL getin("iwrite_phys",iwrite_phys_omp)
    8888!$OMP END MASTER
    8989!$OMP BARRIER
     
    9393  ! compute zjulian for annee0=1979 and month=1 dayref=1 and hour=0.0
    9494  !CALL ymds2ju(annee0, month, dayref, hour, zjulian)
    95   call ymds2ju(1979, 1, 1, 0.0, zjulian)
     95  CALL ymds2ju(1979, 1, 1, 0.0, zjulian)
    9696  dtime=pdtphys
    9797#ifndef CPP_IOIPSL_NO_OUTPUT
    9898  ! Initialize IOIPSL output file
    99   call histbeg_phy("histins.nc",itau0,zjulian,dtime,nhori,nid_hist)
     99  CALL histbeg_phy("histins.nc",itau0,zjulian,dtime,nhori,nid_hist)
    100100#endif
    101101
     
    105105! IOIPSL
    106106  ! define vertical coordinate
    107   call histvert(nid_hist,"presnivs","Vertical levels","Pa",klev, &
     107  CALL histvert(nid_hist,"presnivs","Vertical levels","Pa",klev, &
    108108                presnivs,zvertid,'down')
    109109  ! define variables which will be written in "histins.nc" file
    110   call histdef(nid_hist,'temperature','Atmospheric temperature','K', &
     110  CALL histdef(nid_hist,'temperature','Atmospheric temperature','K', &
    111111               nbp_lon,jj_nb,nhori,klev,1,klev,zvertid,32, &
    112112               'inst(X)',t_ops,t_wrt)
    113   call histdef(nid_hist,'u','Eastward Zonal Wind','m/s', &
     113  CALL histdef(nid_hist,'u','Eastward Zonal Wind','m/s', &
    114114               nbp_lon,jj_nb,nhori,klev,1,klev,zvertid,32, &
    115115               'inst(X)',t_ops,t_wrt)
    116   call histdef(nid_hist,'v','Northward Meridional Wind','m/s', &
     116  CALL histdef(nid_hist,'v','Northward Meridional Wind','m/s', &
    117117               nbp_lon,jj_nb,nhori,klev,1,klev,zvertid,32, &
    118118               'inst(X)',t_ops,t_wrt)
    119   call histdef(nid_hist,'ps','Surface Pressure','Pa', &
     119  CALL histdef(nid_hist,'ps','Surface Pressure','Pa', &
    120120               nbp_lon,jj_nb,nhori,1,1,1,zvertid,32, &
    121121               'inst(X)',t_ops,t_wrt)
    122122  ! end definition sequence
    123   call histend(nid_hist)
     123  CALL histend(nid_hist)
    124124#endif
    125125
     
    166166#ifndef CPP_IOIPSL_NO_OUTPUT
    167167if (modulo(itau,iwrite_phys)==0) then
    168   call histwrite_phy(nid_hist,.false.,"temperature",itau,t)
    169   call histwrite_phy(nid_hist,.false.,"u",itau,u)
    170   call histwrite_phy(nid_hist,.false.,"v",itau,v)
    171   call histwrite_phy(nid_hist,.false.,"ps",itau,paprs(:,1))
     168  CALL histwrite_phy(nid_hist,.false.,"temperature",itau,t)
     169  CALL histwrite_phy(nid_hist,.false.,"u",itau,u)
     170  CALL histwrite_phy(nid_hist,.false.,"v",itau,v)
     171  CALL histwrite_phy(nid_hist,.false.,"ps",itau,paprs(:,1))
    172172endif
    173173#endif
     
    192192! if lastcall, then it is time to write "restartphy.nc" file
    193193if (lafin) then
    194   call phyredem("restartphy.nc")
     194  CALL phyredem("restartphy.nc")
    195195endif
    196196
Note: See TracChangeset for help on using the changeset viewer.