Ignore:
Timestamp:
Jul 24, 2024, 4:23:34 PM (6 months ago)
Author:
abarral
Message:

rename modules properly lmdz_*
move some unused files to obsolete/
(lint) uppercase fortran keywords

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

Legend:

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

    r5099 r5117  
    1010  INTEGER,INTENT(IN) :: nfield,nlon,iim,jjmp1
    1111  REAL,INTENT(IN) :: fi(nlon,nfield)
    12   REAL,INTENT(out) :: ecrit(iim*jjmp1,nfield)
     12  REAL,INTENT(OUT) :: ecrit(iim*jjmp1,nfield)
    1313
    1414  INTEGER :: i, n, ig, jjm
  • LMDZ6/branches/Amaury_dev/libf/phydev/infotrac_phy.F90

    r4729 r5117  
    44MODULE infotrac_phy
    55
    6    USE strings_mod, ONLY: maxlen
     6   USE lmdz_strings, ONLY: maxlen
    77!   PUBLIC :: tracers, type_trac                            !--- Full tracers database, tracers type keyword
    88!   PUBLIC :: nqtot,   nbtr,   nqo,   nqCO2,   nqtottr      !--- Main dimensions
  • LMDZ6/branches/Amaury_dev/libf/phydev/iophy.F90

    r5116 r5117  
    33module iophy
    44
    5   ! abd  REAL,PRIVATE,allocatable,dimension(:),save :: io_lat
    6   ! abd  REAL,PRIVATE,allocatable,dimension(:),save :: io_lon
    7   REAL, allocatable, dimension(:), save :: io_lat
    8   REAL, allocatable, dimension(:), save :: io_lon
     5  ! abd  REAL,PRIVATE,ALLOCATABLE,DIMENSION(:),save :: io_lat
     6  ! abd  REAL,PRIVATE,ALLOCATABLE,DIMENSION(:),save :: io_lon
     7  REAL, ALLOCATABLE, DIMENSION(:), save :: io_lat
     8  REAL, ALLOCATABLE, DIMENSION(:), save :: io_lon
    99  INTEGER, save :: phys_domain_id
    1010  INTEGER, save :: npstn
    11   INTEGER, allocatable, dimension(:), save :: nptabij
     11  INTEGER, ALLOCATABLE, DIMENSION(:), save :: nptabij
    1212
    1313
     
    3434    USE lmdz_grid_phy, ONLY: nbp_lon, nbp_lat
    3535    USE ioipsl, ONLY: flio_dom_set
    36     use wxios, ONLY: wxios_domain_param, using_xios
    37     IMPLICIT NONE
    38     real, dimension(klon), intent(in) :: rlon
    39     real, dimension(klon), intent(in) :: rlat
    40 
    41     REAL, dimension(klon_glo) :: rlat_glo
    42     REAL, dimension(klon_glo) :: rlon_glo
     36    USE lmdz_wxios, ONLY: wxios_domain_param, using_xios
     37    IMPLICIT NONE
     38    REAL, DIMENSION(klon), INTENT(IN) :: rlon
     39    REAL, DIMENSION(klon), INTENT(IN) :: rlat
     40
     41    REAL, DIMENSION(klon_glo) :: rlat_glo
     42    REAL, DIMENSION(klon_glo) :: rlon_glo
    4343
    4444    INTEGER, DIMENSION(2) :: ddid
     
    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
     119      IF (prt_level>=10) THEN
    120120        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
    121121        WRITE(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " nbp_lon=", nbp_lon, " nbp_lat=", nbp_lat
     
    140140  SUBROUTINE histbeg_phy(name, itau0, zjulian, dtime, nhori, nid_day)
    141141    USE lmdz_phys_para, ONLY: is_sequential, jj_begin, jj_end, jj_nb
    142     use ioipsl, ONLY: histbeg
     142    USE ioipsl, ONLY: histbeg
    143143    USE lmdz_print_control, ONLY: prt_level, lunout
    144144    USE lmdz_grid_phy, ONLY: nbp_lon
    145145    IMPLICIT NONE
    146146
    147     character*(*), intent(IN) :: name
    148     integer, intent(in) :: itau0
    149     real, intent(in) :: zjulian
    150     real, intent(in) :: dtime
    151     integer, intent(out) :: nhori
    152     integer, intent(out) :: nid_day
    153 
    154     !$OMP MASTER
    155     if (is_sequential) THEN
     147    character*(*), INTENT(IN) :: name
     148    INTEGER, INTENT(IN) :: itau0
     149    REAL, INTENT(IN) :: zjulian
     150    REAL, INTENT(IN) :: dtime
     151    INTEGER, INTENT(OUT) :: nhori
     152    INTEGER, INTENT(OUT) :: nid_day
     153
     154    !$OMP MASTER
     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)
     
    170170  SUBROUTINE histbeg_phyxios(name, ffreq, lev)
    171171    USE lmdz_phys_para, ONLY: is_using_mpi, is_mpi_root
    172     use wxios, ONLY: wxios_add_file
     172    USE lmdz_wxios, ONLY: wxios_add_file
    173173    IMPLICIT NONE
    174174
    175175    character*(*), INTENT(IN) :: name
    176     !    integer, INTENT(IN) :: itau0
     176    !    INTEGER, INTENT(IN) :: itau0
    177177    !    REAL,INTENT(IN) :: zjulian
    178178    !    REAL,INTENT(IN) :: dtime
    179179    character(LEN = *), INTENT(IN) :: ffreq
    180180    INTEGER, INTENT(IN) :: lev
    181     !    integer,intent(out) :: nhori
    182     !    integer,intent(out) :: nid_day
     181    !    INTEGER,INTENT(OUT) :: nhori
     182    !    INTEGER,INTENT(OUT) :: nid_day
    183183
    184184    !$OMP MASTER
     
    207207    IMPLICIT NONE
    208208
    209     integer, intent(in) :: nid
    210     logical, intent(in) :: lpoint
    211     character*(*), intent(IN) :: name
    212     integer, intent(in) :: itau
    213     real, dimension(:), intent(in) :: field
    214     REAL, dimension(klon_mpi) :: buffer_omp
    215     INTEGER, allocatable, dimension(:) :: index2d
     209    INTEGER, INTENT(IN) :: nid
     210    logical, INTENT(IN) :: lpoint
     211    character*(*), INTENT(IN) :: name
     212    INTEGER, INTENT(IN) :: itau
     213    REAL, DIMENSION(:), INTENT(IN) :: field
     214    REAL, DIMENSION(klon_mpi) :: buffer_omp
     215    INTEGER, ALLOCATABLE, DIMENSION(:) :: index2d
    216216    REAL :: Field2d(nbp_lon, jj_nb)
    217217
    218218    INTEGER :: ip
    219     real, allocatable, dimension(:) :: fieldok
     219    REAL, ALLOCATABLE, DIMENSION(:) :: fieldok
    220220
    221221    IF (size(field)/=klon) CALL abort_physic('iophy::histwrite2d', 'Field first dimension not equal to klon', 1)
     
    267267    IMPLICIT NONE
    268268
    269     integer, intent(in) :: nid
    270     logical, intent(in) :: lpoint
    271     character*(*), intent(IN) :: name
    272     integer, intent(in) :: itau
    273     real, dimension(:, :), intent(in) :: field  ! --> field(klon,:)
    274     REAL, dimension(klon_mpi, size(field, 2)) :: buffer_omp
     269    INTEGER, INTENT(IN) :: nid
     270    logical, INTENT(IN) :: lpoint
     271    character*(*), INTENT(IN) :: name
     272    INTEGER, INTENT(IN) :: itau
     273    REAL, DIMENSION(:, :), INTENT(IN) :: field  ! --> field(klon,:)
     274    REAL, DIMENSION(klon_mpi, size(field, 2)) :: buffer_omp
    275275    REAL :: Field3d(nbp_lon, jj_nb, size(field, 2))
    276276    INTEGER :: ip, n, nlev
    277     INTEGER, ALLOCATABLE, dimension(:) :: index3d
    278     real, allocatable, dimension(:, :) :: fieldok
     277    INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d
     278    REAL, ALLOCATABLE, DIMENSION(:, :) :: fieldok
    279279
    280280    IF (size(field, 1)/=klon) CALL abort_physic('iophy::histwrite3d', 'Field first dimension not equal to klon', 1)
  • LMDZ6/branches/Amaury_dev/libf/phydev/phyetat0.F90

    r5116 r5117  
    1414  IMPLICIT NONE
    1515
    16   CHARACTER(len=*),INTENT(in) :: fichnom ! input file name
     16  CHARACTER(len=*),INTENT(IN) :: fichnom ! input file name
    1717
    1818  REAL :: lon_startphy(klon), lat_startphy(klon)
  • LMDZ6/branches/Amaury_dev/libf/phydev/phys_state_var_mod.F90

    r5116 r5117  
    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
    2424!    WRITE(*,*) "phys_state_var_init: warning, rlat already allocated"
    25 endif
     25ENDIF
    2626 
    2727  END SUBROUTINE phys_state_var_init
  • LMDZ6/branches/Amaury_dev/libf/phydev/physiq_mod.F90

    r5116 r5117  
    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 lmdz_wxios, ONLY: wxios_add_vaxis, wxios_set_cal, wxios_closedef
    2727      USE iophy, ONLY: histwrite_phy
    2828
     
    3131! Routine argument:
    3232
    33       integer,intent(in) :: nlon ! number of atmospheric colums
    34       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
    37       real,intent(in) :: pdtphys ! physics time step (s)
    38       real,intent(in) :: paprs(klon,klev+1) ! interlayer pressure (Pa)
    39       real,intent(in) :: pplay(klon,klev) ! mid-layer pressure (Pa)
    40       real,intent(in) :: pphi(klon,klev) ! geopotential at mid-layer
    41       real,intent(in) :: pphis(klon) ! surface geopotential
    42       real,intent(in) :: presnivs(klev) ! pseudo-pressure (Pa) of mid-layers
    43       real,intent(in) :: u(klon,klev) ! eastward zonal wind (m/s)
    44       real,intent(in) :: v(klon,klev) ! northward meridional wind (m/s)
    45       real,intent(in) :: t(klon,klev) ! temperature (K)
    46       real,intent(in) :: qx(klon,klev,nqtot) ! tracers (.../kg_air)
    47       real,intent(in) :: flxmass_w(klon,klev) ! vertical mass flux
    48       real,intent(out) :: d_u(klon,klev) ! physics tendency on u (m/s/s)
    49       real,intent(out) :: d_v(klon,klev) ! physics tendency on v (m/s/s)
    50       real,intent(out) :: d_t(klon,klev) ! physics tendency on t (K/s)
    51       real,intent(out) :: d_qx(klon,klev,nqtot) ! physics tendency on tracers
    52       real,intent(out) :: d_ps(klon) ! physics tendency on surface pressure
     33      INTEGER,INTENT(IN) :: nlon ! number of atmospheric colums
     34      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
     37      REAL,INTENT(IN) :: pdtphys ! physics time step (s)
     38      REAL,INTENT(IN) :: paprs(klon,klev+1) ! interlayer pressure (Pa)
     39      REAL,INTENT(IN) :: pplay(klon,klev) ! mid-layer pressure (Pa)
     40      REAL,INTENT(IN) :: pphi(klon,klev) ! geopotential at mid-layer
     41      REAL,INTENT(IN) :: pphis(klon) ! surface geopotential
     42      REAL,INTENT(IN) :: presnivs(klev) ! pseudo-pressure (Pa) of mid-layers
     43      REAL,INTENT(IN) :: u(klon,klev) ! eastward zonal wind (m/s)
     44      REAL,INTENT(IN) :: v(klon,klev) ! northward meridional wind (m/s)
     45      REAL,INTENT(IN) :: t(klon,klev) ! temperature (K)
     46      REAL,INTENT(IN) :: qx(klon,klev,nqtot) ! tracers (.../kg_air)
     47      REAL,INTENT(IN) :: flxmass_w(klon,klev) ! vertical mass flux
     48      REAL,INTENT(OUT) :: d_u(klon,klev) ! physics tendency on u (m/s/s)
     49      REAL,INTENT(OUT) :: d_v(klon,klev) ! physics tendency on v (m/s/s)
     50      REAL,INTENT(OUT) :: d_t(klon,klev) ! physics tendency on t (K/s)
     51      REAL,INTENT(OUT) :: d_qx(klon,klev,nqtot) ! physics tendency on tracers
     52      REAL,INTENT(OUT) :: d_ps(klon) ! physics tendency on surface pressure
    5353
    54 integer,save :: itau=0 ! counter to count number of calls to physics
     54INTEGER,save :: itau=0 ! counter to count number of calls to physics
    5555!$OMP THREADPRIVATE(itau)
    5656REAL :: temp_newton(klon,klev)
     
    6464REAL :: dtime
    6565INTEGER :: nhori ! horizontal coordinate ID
    66 integer,save :: nid_hist ! output file ID
     66INTEGER,save :: nid_hist ! output file ID
    6767!$OMP THREADPRIVATE(nid_hist)
    6868INTEGER :: zvertid ! vertical coordinate ID
    69 integer,save :: iwrite_phys ! output every iwrite_phys physics step
     69INTEGER,save :: iwrite_phys ! output every iwrite_phys physics step
    7070!$OMP THREADPRIVATE(iwrite_phys)
    71 integer,save :: iwrite_phys_omp ! intermediate variable to read iwrite_phys
     71INTEGER,save :: iwrite_phys_omp ! intermediate variable to read iwrite_phys
    7272                                ! (must be shared by all threads)
    7373REAL :: t_ops ! frequency of the IOIPSL operations (eg average over...)
Note: See TracChangeset for help on using the changeset viewer.