Ignore:
Timestamp:
Jul 23, 2024, 3:29:36 PM (2 months ago)
Author:
abarral
Message:

Handle CPP_INLANDSIS in lmdz_cppkeys_wrapper.F90
Remove obsolete key wrgrads_thermcell, _ADV_HALO, _ADV_HALLO, isminmax
Remove redundant uses of CPPKEY_INCA (thanks acozic)
Remove obsolete misc/write_field.F90
Remove unused ioipsl_* wrappers
Remove calls to WriteField_u with wrong signature
Convert .F -> .[fF]90
(lint) uppercase fortran operators
[note: 1d and iso still broken - working on it]

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

Legend:

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

    r5101 r5103  
    2525contains
    2626
    27   subroutine init_iophy_new(rlat,rlon)
     27  SUBROUTINE init_iophy_new(rlat,rlon)
    2828  USE dimphy, only: klon
    2929  USE mod_phys_lmdz_para, only: gather, bcast, &
     
    3434  USE print_control_mod, ONLY: lunout, prt_level
    3535  USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
    36 #ifdef CPP_IOIPSL
    3736  USE ioipsl, only: flio_dom_set
    38 #endif
    3937  use wxios, only: wxios_domain_param, using_xios
    4038  implicit none
     
    141139!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    142140 
    143   subroutine histbeg_phy(name,itau0,zjulian,dtime,nhori,nid_day)
     141  SUBROUTINE histbeg_phy(name,itau0,zjulian,dtime,nhori,nid_day)
    144142  USE mod_phys_lmdz_para, only: is_sequential, jj_begin, jj_end, jj_nb
    145143  use ioipsl, only: histbeg
     
    165163!$OMP END MASTER
    166164 
    167   end subroutine histbeg_phy
     165  END SUBROUTINE histbeg_phy
    168166
    169167!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    200198!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    201199 
    202   subroutine histwrite2d_phy(nid,lpoint,name,itau,field)
     200  SUBROUTINE histwrite2d_phy(nid,lpoint,name,itau,field)
    203201  USE dimphy, only: klon
    204202  USE mod_phys_lmdz_para, only: Gather_omp, grid1Dto2D_mpi, &
     
    242240     else
    243241      DO ip=1, npstn
    244 !     print*,'histwrite2d is_sequential npstn ip name nptabij',npstn,ip,name,nptabij(ip)
     242!     PRINT*,'histwrite2d is_sequential npstn ip name nptabij',npstn,ip,name,nptabij(ip)
    245243       IF(nptabij(ip)>=klon_mpi_begin.AND. &
    246244          nptabij(ip)<=klon_mpi_end) THEN
     
    255253    deallocate(fieldok)
    256254!$OMP END MASTER   
    257   end subroutine histwrite2d_phy
    258 
    259 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    260 
    261   subroutine histwrite3d_phy(nid,lpoint,name,itau,field)
     255  END SUBROUTINE histwrite2d_phy
     256
     257!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     258
     259  SUBROUTINE histwrite3d_phy(nid,lpoint,name,itau,field)
    262260  USE dimphy, only: klon
    263261  USE mod_phys_lmdz_para, only: Gather_omp, grid1Dto2D_mpi, &
     
    317315  deallocate(fieldok)
    318316!$OMP END MASTER   
    319   end subroutine histwrite3d_phy
     317  END SUBROUTINE histwrite3d_phy
    320318
    321319!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  • LMDZ6/branches/Amaury_dev/libf/phydev/physiq_mod.F90

    r5101 r5103  
    5656real :: temp_newton(klon,klev)
    5757integer :: k
    58 logical, save :: first=.true.
     58logical, save :: first=.TRUE.
    5959!$OMP THREADPRIVATE(first)
    6060
     
    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)
    7979  CALL phys_state_var_init() ! some initializations, required before calling phyetat0
     
    137137!$OMP END MASTER
    138138!$OMP BARRIER
    139 endif ! of if (debut)
     139END IF ! of if (debut)
    140140
    141141! increment local time counter itau
     
    154154d_v(1:klon,1)=-v(1:klon,1)/86400.
    155155! newtonian relaxation towards temp_newton()
    156 do k=1,klev
     156DO k=1,klev
    157157  temp_newton(1:klon,k)=280.+cos(latitude(1:klon))*40.-pphi(1:klon,k)/rg*6.e-3
    158158  d_t(1:klon,k)=(temp_newton(1:klon,k)-t(1:klon,k))/1.e5
    159 enddo
     159END DO
    160160
    161161
    162 print*,'PHYDEV: itau=',itau
     162PRINT*,'PHYDEV: itau=',itau
    163163
    164164! write some outputs:
    165165! IOIPSL
    166166#ifndef CPP_IOIPSL_NO_OUTPUT
    167 if (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))
    172 endif
     167IF (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))
     172END IF
    173173#endif
    174174
     
    191191
    192192! if lastcall, then it is time to write "restartphy.nc" file
    193 if (lafin) then
     193IF (lafin) then
    194194  CALL phyredem("restartphy.nc")
    195 endif
     195END IF
    196196
    197 end subroutine physiq
     197END SUBROUTINE physiq
    198198
    199199END MODULE physiq_mod
Note: See TracChangeset for help on using the changeset viewer.