Ignore:
Timestamp:
Jul 24, 2024, 2:54:37 PM (6 months ago)
Author:
abarral
Message:

rename modules properly lmdz_*
move ismin, ismax, minmax into new lmdz_libmath.f90
(lint) uppercase fortran keywords

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

Legend:

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

    r1907 r5116  
    11module comcstphy
    22 
    3   real :: rradius ! planet radius (m)
    4   real :: rr      ! recuced gas constant: R/molar mass of atm
    5   real :: rg      ! gravity
    6   real :: rcpp    ! specific heat of the atmosphere
     3  REAL :: rradius ! planet radius (m)
     4  REAL :: rr      ! recuced gas constant: R/molar mass of atm
     5  REAL :: rg      ! gravity
     6  REAL :: rcpp    ! specific heat of the atmosphere
    77
    88end module comcstphy
  • LMDZ6/branches/Amaury_dev/libf/phydev/iophy.F90

    r5113 r5116  
    2525
    2626  SUBROUTINE init_iophy_new(rlat, rlon)
    27     USE dimphy, only: klon
    28     USE lmdz_phys_para, only: gather, bcast, &
     27    USE dimphy, ONLY: klon
     28    USE lmdz_phys_para, ONLY: gather, bcast, &
    2929            jj_nb, jj_begin, jj_end, ii_begin, ii_end, &
    3030            mpi_size, mpi_rank, klon_mpi, &
    3131            is_sequential, is_south_pole_dyn
    32     USE lmdz_grid_phy, only: nbp_lon, nbp_lat, klon_glo
     32    USE lmdz_grid_phy, ONLY: nbp_lon, nbp_lat, klon_glo
    3333    USE lmdz_print_control, ONLY: lunout, prt_level
    3434    USE lmdz_grid_phy, ONLY: nbp_lon, nbp_lat
    35     USE ioipsl, only: flio_dom_set
    36     use wxios, only: wxios_domain_param, using_xios
     35    USE ioipsl, ONLY: flio_dom_set
     36    use wxios, ONLY: wxios_domain_param, using_xios
    3737    IMPLICIT NONE
    3838    real, dimension(klon), intent(in) :: rlon
     
    5050    INTEGER, DIMENSION(2) :: dhe
    5151    INTEGER :: i
    52     integer :: data_ibegin, data_iend
     52    INTEGER :: data_ibegin, data_iend
    5353
    5454    CALL gather(rlat, rlat_glo)
     
    6161    io_lat(1) = rlat_glo(1)
    6262    io_lat(nbp_lat) = rlat_glo(klon_glo)
    63     IF ((nbp_lon * nbp_lat) > 1) then
     63    IF ((nbp_lon * nbp_lat) > 1) THEN
    6464      DO i = 2, nbp_lat - 1
    6565        io_lat(i) = rlat_glo(2 + (i - 2) * nbp_lon)
     
    9393    dpl = (/ nbp_lon, jj_end /)
    9494    dhs = (/ ii_begin - 1, 0 /)
    95     if (mpi_rank==mpi_size - 1) then
     95    if (mpi_rank==mpi_size - 1) THEN
    9696      dhe = (/0, 0/)
    9797    else
     
    117117      END IF
    118118
    119       if (prt_level>=10) then
    120         write(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " iibegin=", ii_begin, " ii_end=", ii_end, " jjbegin=", jj_begin, " jj_nb=", jj_nb, " jj_end=", jj_end
    121         write(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " nbp_lon=", nbp_lon, " nbp_lat=", nbp_lat
    122         write(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " data_ibegin=", data_ibegin, " data_iend=", data_iend
    123         write(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " data_ibegin=", data_ibegin, " data_iend=", data_iend
    124         write(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " is_south_pole=", is_south_pole_dyn
     119      if (prt_level>=10) THEN
     120        WRITE(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " iibegin=", ii_begin, " ii_end=", ii_end, " jjbegin=", jj_begin, " jj_nb=", jj_nb, " jj_end=", jj_end
     121        WRITE(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " nbp_lon=", nbp_lon, " nbp_lat=", nbp_lat
     122        WRITE(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " data_ibegin=", data_ibegin, " data_iend=", data_iend
     123        WRITE(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " data_ibegin=", data_ibegin, " data_iend=", data_iend
     124        WRITE(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " is_south_pole=", is_south_pole_dyn
    125125      endif
    126126
     
    139139
    140140  SUBROUTINE histbeg_phy(name, itau0, zjulian, dtime, nhori, nid_day)
    141     USE lmdz_phys_para, only: is_sequential, jj_begin, jj_end, jj_nb
    142     use ioipsl, only: histbeg
     141    USE lmdz_phys_para, ONLY: is_sequential, jj_begin, jj_end, jj_nb
     142    use ioipsl, ONLY: histbeg
    143143    USE lmdz_print_control, ONLY: prt_level, lunout
    144144    USE lmdz_grid_phy, ONLY: nbp_lon
     
    153153
    154154    !$OMP MASTER
    155     if (is_sequential) then
     155    if (is_sequential) THEN
    156156      CALL histbeg(name, nbp_lon, io_lon, jj_nb, io_lat(jj_begin:jj_end), &
    157157              1, nbp_lon, 1, jj_nb, itau0, zjulian, dtime, nhori, nid_day)
     
    169169  ! SUBROUTINE histbeg_phyxios(name,itau0,zjulian,dtime,ffreq,lev,nhori,nid_day)
    170170  SUBROUTINE histbeg_phyxios(name, ffreq, lev)
    171     USE lmdz_phys_para, only: is_using_mpi, is_mpi_root
    172     use wxios, only: wxios_add_file
     171    USE lmdz_phys_para, ONLY: is_using_mpi, is_mpi_root
     172    use wxios, ONLY: wxios_add_file
    173173    IMPLICIT NONE
    174174
     
    198198
    199199  SUBROUTINE histwrite2d_phy(nid, lpoint, name, itau, field)
    200     USE dimphy, only: klon
    201     USE lmdz_phys_para, only: Gather_omp, grid1Dto2D_mpi, &
     200    USE dimphy, ONLY: klon
     201    USE lmdz_phys_para, ONLY: Gather_omp, grid1Dto2D_mpi, &
    202202            is_sequential, klon_mpi_begin, klon_mpi_end, &
    203203            jj_nb, klon_mpi
    204     USE ioipsl, only: histwrite
     204    USE ioipsl, ONLY: histwrite
    205205    USE lmdz_grid_phy, ONLY: nbp_lon
    206206    USE lmdz_abort_physic, ONLY: abort_physic
     
    216216    REAL :: Field2d(nbp_lon, jj_nb)
    217217
    218     integer :: ip
     218    INTEGER :: ip
    219219    real, allocatable, dimension(:) :: fieldok
    220220
     
    224224    !$OMP MASTER
    225225    CALL grid1Dto2D_mpi(buffer_omp, Field2d)
    226     if(.NOT.lpoint) THEN
     226    IF(.NOT.lpoint) THEN
    227227      ALLOCATE(index2d(nbp_lon * jj_nb))
    228228      ALLOCATE(fieldok(nbp_lon * jj_nb))
     
    232232      ALLOCATE(index2d(npstn))
    233233
    234       if(is_sequential) then
     234      IF(is_sequential) THEN
    235235        !     klon_mpi_begin=1
    236236        !     klon_mpi_end=klon
     
    258258
    259259  SUBROUTINE histwrite3d_phy(nid, lpoint, name, itau, field)
    260     USE dimphy, only: klon
    261     USE lmdz_phys_para, only: Gather_omp, grid1Dto2D_mpi, &
     260    USE dimphy, ONLY: klon
     261    USE lmdz_phys_para, ONLY: Gather_omp, grid1Dto2D_mpi, &
    262262            is_sequential, klon_mpi_begin, klon_mpi_end, &
    263263            jj_nb, klon_mpi
    264     USE ioipsl, only: histwrite
     264    USE ioipsl, ONLY: histwrite
    265265    USE lmdz_grid_phy, ONLY: nbp_lon
    266266    USE lmdz_abort_physic, ONLY: abort_physic
     
    284284    !$OMP MASTER
    285285    CALL grid1Dto2D_mpi(buffer_omp, field3d)
    286     if(.NOT.lpoint) THEN
     286    IF(.NOT.lpoint) THEN
    287287      ALLOCATE(index3d(nbp_lon * jj_nb * nlev))
    288288      ALLOCATE(fieldok(nbp_lon * jj_nb, nlev))
     
    293293      ALLOCATE(fieldok(npstn, nlev))
    294294
    295       if(is_sequential) then
     295      IF(is_sequential) THEN
    296296        !      klon_mpi_begin=1
    297297        !      klon_mpi_end=klon
     
    323323
    324324  SUBROUTINE histwrite2d_xios(field_name, field)
    325     USE dimphy, only: klon
    326     USE lmdz_phys_para, only: gather_omp, grid1Dto2D_mpi, &
     325    USE dimphy, ONLY: klon
     326    USE lmdz_phys_para, ONLY: gather_omp, grid1Dto2D_mpi, &
    327327            jj_nb, klon_mpi
    328     USE lmdz_xios, only: xios_send_field
     328    USE lmdz_xios, ONLY: xios_send_field
    329329    USE lmdz_print_control, ONLY: prt_level, lunout
    330330    USE lmdz_grid_phy, ONLY: nbp_lon
     
    357357
    358358  SUBROUTINE histwrite3d_xios(field_name, field)
    359     USE dimphy, only: klon, klev
    360     USE lmdz_phys_para, only: gather_omp, grid1Dto2D_mpi, &
     359    USE dimphy, ONLY: klon, klev
     360    USE lmdz_phys_para, ONLY: gather_omp, grid1Dto2D_mpi, &
    361361            jj_nb, klon_mpi
    362     USE lmdz_xios, only: xios_send_field
     362    USE lmdz_xios, ONLY: xios_send_field
    363363    USE lmdz_print_control, ONLY: prt_level, lunout
    364364    USE lmdz_grid_phy, ONLY: nbp_lon
     
    373373    INTEGER :: ip, n, nlev
    374374
    375     IF (prt_level >= 10) write(lunout, *)'Begin histrwrite3d_xios ', trim(field_name)
     375    IF (prt_level >= 10) WRITE(lunout, *)'Begin histrwrite3d_xios ', trim(field_name)
    376376
    377377    !Et on.... écrit
     
    386386    !$OMP END MASTER
    387387
    388     IF (prt_level >= 10) write(lunout, *)'End histrwrite3d_xios ', trim(field_name)
     388    IF (prt_level >= 10) WRITE(lunout, *)'End histrwrite3d_xios ', trim(field_name)
    389389  END SUBROUTINE histwrite3d_xios
    390390
  • LMDZ6/branches/Amaury_dev/libf/phydev/phyetat0.F90

    r5112 r5116  
    66! and do some resulting initializations
    77
    8   USE dimphy, only: klon
     8  USE dimphy, ONLY: klon
    99  USE iostart, ONLY: open_startphy,get_field,close_startphy
    1010  USE iophy, ONLY: init_iophy_new
  • LMDZ6/branches/Amaury_dev/libf/phydev/phys_state_var_mod.F90

    r5101 r5116  
    1919!  use dimphy, ONLY: klon
    2020
    21 !  if (.not.allocated(rlat)) then
     21!  if (.not.allocated(rlat)) THEN
    2222!    ALLOCATE(rlat(klon),rlon(klon))
    2323!  else
    24 !    write(*,*) "phys_state_var_init: warning, rlat already allocated"
     24!    WRITE(*,*) "phys_state_var_init: warning, rlat already allocated"
    2525!  endif
    2626 
  • LMDZ6/branches/Amaury_dev/libf/phydev/physiq_mod.F90

    r5112 r5116  
    2424
    2525      USE lmdz_xios, ONLY: xios_update_calendar, using_xios
    26       USE wxios, only: wxios_add_vaxis, wxios_set_cal, wxios_closedef
     26      USE wxios, ONLY: wxios_add_vaxis, wxios_set_cal, wxios_closedef
    2727      USE iophy, ONLY: histwrite_phy
    2828
     
    5454integer,save :: itau=0 ! counter to count number of calls to physics
    5555!$OMP THREADPRIVATE(itau)
    56 real :: temp_newton(klon,klev)
    57 integer :: k
     56REAL :: temp_newton(klon,klev)
     57INTEGER :: k
    5858logical, save :: first=.TRUE.
    5959!$OMP THREADPRIVATE(first)
    6060
    6161! For I/Os
    62 integer :: itau0
    63 real :: zjulian
    64 real :: dtime
    65 integer :: nhori ! horizontal coordinate ID
     62INTEGER :: itau0
     63REAL :: zjulian
     64REAL :: dtime
     65INTEGER :: nhori ! horizontal coordinate ID
    6666integer,save :: nid_hist ! output file ID
    6767!$OMP THREADPRIVATE(nid_hist)
    68 integer :: zvertid ! vertical coordinate ID
     68INTEGER :: zvertid ! vertical coordinate ID
    6969integer,save :: iwrite_phys ! output every iwrite_phys physics step
    7070!$OMP THREADPRIVATE(iwrite_phys)
    7171integer,save :: iwrite_phys_omp ! intermediate variable to read iwrite_phys
    7272                                ! (must be shared by all threads)
    73 real :: t_ops ! frequency of the IOIPSL operations (eg average over...)
    74 real :: t_wrt ! frequency of the IOIPSL outputs
     73REAL :: t_ops ! frequency of the IOIPSL operations (eg average over...)
     74REAL :: t_wrt ! frequency of the IOIPSL outputs
    7575
    7676! initializations
     
    165165! IOIPSL
    166166#ifndef CPP_IOIPSL_NO_OUTPUT
    167 IF (modulo(itau,iwrite_phys)==0) then
     167IF (modulo(itau,iwrite_phys)==0) THEN
    168168  CALL histwrite_phy(nid_hist,.FALSE.,"temperature",itau,t)
    169169  CALL histwrite_phy(nid_hist,.FALSE.,"u",itau,u)
     
    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")
    195195END IF
Note: See TracChangeset for help on using the changeset viewer.