Changeset 3626


Ignore:
Timestamp:
Feb 13, 2025, 5:12:07 PM (3 hours ago)
Author:
emillour
Message:

Dynamico-Mars:
Cleanup: add some "only" clauses to all the "use" to help
identifying connections between Dynamico, the interface and the physics.
EM

Location:
trunk/ICOSA_LMDZ
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/ICOSA_LMDZ/bld.cfg

    r3226 r3626  
    5050bld::excl_dep        use::icosa
    5151bld::excl_dep        use::disvert_mod
     52bld::excl_dep        use::geometry
     53bld::excl_dep        use::spherical_geom_mod
    5254bld::excl_dep        use::mpi_mod
    5355bld::excl_dep        use::mpipara
     
    6870bld::excl_dep        use::dimphy
    6971bld::excl_dep        use::geometry_mod
     72bld::excl_dep        use::metric_var_mod
    7073bld::excl_dep        use::vertical_layers_mod
    7174bld::excl_dep        use::planete_mod
  • trunk/ICOSA_LMDZ/src/distrib_icosa_lmdz.f90

    r2000 r3626  
    2626
    2727  SUBROUTINE init_distrib_icosa_lmdz
     28! from LMDZ
    2829  USE mod_phys_lmdz_omp_data, ONLY: klon_omp_begin, klon_omp_end
    29   USE domain_mod
    30   USE dimensions
     30! from dynamico
     31  USE domain_mod, ONLY: domain, ndomain
     32  USE dimensions, ONLY: ii_begin, ii_end, jj_begin, jj_end, iim
     33  USE dimensions, ONLY: swap_dimensions
    3134  IMPLICIT NONE
    3235    INTEGER :: pos,pos_tmp,nindex
     
    8285                 
    8386  SUBROUTINE transfer_icosa_to_lmdz1d(f_field_icosa, field_lmdz)
    84   USE field_mod
     87! from dynamico
     88  USE prec, ONLY: rstd
     89  USE field_mod, ONLY: t_field, ASSIGNMENT(=)
    8590  IMPLICIT NONE
    8691    TYPE(t_field),POINTER :: f_field_icosa(:)
     
    105110 
    106111  SUBROUTINE transfer_icosa_to_lmdz2d(f_field_icosa, field_lmdz)
    107   USE field_mod
     112! from dynamico
     113  USE prec, ONLY: rstd
     114  USE field_mod, ONLY: t_field, ASSIGNMENT(=)
    108115  IMPLICIT NONE
    109116    TYPE(t_field),POINTER :: f_field_icosa(:)
     
    134141   
    135142  SUBROUTINE transfer_icosa_to_lmdz3d(f_field_icosa, field_lmdz)
    136   USE field_mod
     143! from dynamico
     144  USE prec, ONLY: rstd
     145  USE field_mod, ONLY: t_field, ASSIGNMENT(=)
    137146  IMPLICIT NONE
    138147    TYPE(t_field),POINTER :: f_field_icosa(:)
     
    162171     
    163172  SUBROUTINE transfer_lmdz1d_to_icosa(field_lmdz,f_field_icosa)
    164   USE field_mod
     173! from dynamico
     174  USE prec, ONLY: rstd
     175  USE field_mod, ONLY: t_field, ASSIGNMENT(=)
    165176  IMPLICIT NONE
    166177    REAL(rstd)         :: field_lmdz(:)
     
    184195
    185196  SUBROUTINE transfer_lmdz2d_to_icosa(field_lmdz,f_field_icosa)
    186   USE field_mod
     197! from dynamico
     198  USE prec, ONLY: rstd
     199  USE field_mod, ONLY: t_field, ASSIGNMENT(=)
    187200  IMPLICIT NONE
    188201    REAL(rstd)         :: field_lmdz(:,:)
     
    211224
    212225  SUBROUTINE transfer_lmdz3d_to_icosa(field_lmdz,f_field_icosa)
    213   USE field_mod
     226! from dynamico
     227  USE prec, ONLY: rstd
     228  USE field_mod, ONLY: t_field, ASSIGNMENT(=)
    214229  IMPLICIT NONE
    215230    REAL(rstd)         :: field_lmdz(:,:,:)
  • trunk/ICOSA_LMDZ/src/phymars/interface_icosa_lmdz.f90

    r3271 r3626  
    4949
    5050  SUBROUTINE initialize_physics
    51   USE distrib_icosa_lmdz_mod, ONLY : init_distrib_icosa_lmdz, transfer_icosa_to_lmdz
    5251! from dynamico
    53   USE domain_mod
    54   USE dimensions
    55   USE mpi_mod
    56   USE mpipara
    57   USE disvert_mod
    58   USE xios_mod
     52  USE prec, ONLY: rstd
     53  USE field_mod, ONLY: type_real, field_t, allocate_field, &
     54                       ASSIGNMENT(=)
     55  USE spherical_geom_mod, ONLY: xyz2lonlat
     56  USE domain_mod, ONLY: ndomain, domain
     57  USE dimensions, ONLY: ii_begin, ii_end, jj_begin, jj_end, iim, &
     58                        z_rup, z_up, z_lup, z_rdown, z_down, z_ldown, &
     59                        swap_dimensions
     60  USE geometry, ONLY: xyz_v, swap_geometry
     61  USE grid_param, ONLY: llm, nqtot
     62  USE mpi_mod, ONLY: MPI_INTEGER, MPI_SUM
     63  USE mpipara, ONLY: comm_icosa, ierr
     64  USE transfert_mod, ONLY: req_i0, init_message
     65  USE xios_mod, ONLY: xios_set_context
    5966  USE time_mod , init_time_icosa=> init_time
    60   USE transfert_mod
    6167 
    6268! from LMDZ
    6369  USE mod_grid_phy_lmdz, ONLY : unstructured
    6470  USE mod_phys_lmdz_omp_data, ONLY: klon_omp
    65   USE transfert_mod
    6671  USE physics_distribution_mod, ONLY : init_physics_distribution
    6772   
     
    153158
    154159  SUBROUTINE initialize_physics_omp
    155   USE distrib_icosa_lmdz_mod, ONLY : init_distrib_icosa_lmdz, transfer_icosa_to_lmdz
     160! from interface
     161  USE distrib_icosa_lmdz_mod, ONLY : init_distrib_icosa_lmdz, &
     162                                     transfer_icosa_to_lmdz
    156163! from dynamico
    157   USE domain_mod
    158   USE dimensions
    159   USE mpi_mod
    160   USE mpipara
    161   USE disvert_mod
    162   USE xios_mod
    163   USE time_mod , ONLY: init_time_icosa=> init_time, dt, itaumax, itau_physics
    164   USE omp_para
     164  USE prec, ONLY: rstd
     165  USE field_mod, ONLY: type_real, field_t, allocate_field, deallocate_field
     166  USE domain_mod, ONLY: ndomain, domain, assigned_domain
     167  USE dimensions, ONLY: ii_begin, ii_end, jj_begin, jj_end, iim, &
     168                        swap_dimensions
     169  USE geometry, ONLY: geom, swap_geometry
     170  USE grid_param, ONLY: llm, nqtot
     171  USE mpipara, ONLY: is_mpi_root, ierr
     172  USE disvert_mod, ONLY: ap, bp, presnivs
     173  USE time_mod , ONLY: init_time_icosa=> init_time, &
     174                       dt, itaumax, itau_physics, ndays
     175  USE omp_para, ONLY: is_omp_level_master
     176  USE transfert_mod, ONLY: bcast
     177  USE getin_mod, ONLY: getin
     178  USE earth_const, ONLY: cpp, g, kappa, radius, scale_height, preff
    165179
    166180! from LMDZ
     
    168182  USE mod_phys_lmdz_omp_data, ONLY: klon_omp
    169183  USE time_phylmdz_mod, ONLY: init_time_lmdz => init_time
    170   USE transfert_mod
    171184  USE physics_distribution_mod, ONLY : init_physics_distribution
    172185  USE dimphy, ONLY: init_dimphy
     
    176189  use comgeomfi_h, only: ini_fillgeom
    177190  use conf_phys_mod, only: conf_phys
    178  
     191
     192! other
    179193  USE netcdf 
    180194 
     
    433447
    434448  SUBROUTINE physics
    435   USE icosa
    436   USE time_mod
    437   USE disvert_mod
    438   USE transfert_mod
    439   USE mpipara
    440   USE xios_mod
    441   USE wxios
    442   USE trace
     449! from dynamico
     450  USE prec, ONLY: rstd
     451  USE dimensions, ONLY: ii_begin, ii_end, jj_begin, jj_end, iim,  &
     452                        z_rup, z_up, z_lup, z_rdown, z_down, z_ldown, &
     453                        t_right, t_rup, t_lup, t_ldown, &
     454                        u_right, u_rup, u_lup, u_left, u_ldown, u_rdown, &
     455                        swap_dimensions
     456  USE disvert_mod, ONLY: ap, bp
     457  USE transfert_mod, ONLY: req_e1_vect, init_message, transfert_message, &
     458                           send_message, wait_message
     459  USE metric_var_mod, ONLY: right, rup, lup, left, ldown, rdown
     460  USE geometry, ONLY: xyz_v, elon_i, elat_i, ep_e, centroid, le, ne, Ai, &
     461                      swap_geometry
     462  USE field_mod, ONLY: ASSIGNMENT(=)
     463  USE grid_param, ONLY: llm, nqtot
     464  USE earth_const, ONLY: cpp, g, kappa, preff
     465  USE xios_mod, ONLY: xios_set_context
     466  USE time_mod, ONLY: itau_physics, itaumax, itau0, dt
     467  USE domain_mod, ONLY: ndomain, domain, assigned_domain
     468  USE trace, ONLY: trace_start, trace_end
    443469  USE distrib_icosa_lmdz_mod, ONLY : transfer_icosa_to_lmdz, transfer_lmdz_to_icosa
    444470  USE physics_external_mod, ONLY : it, f_phis, f_ps, f_theta_rhodz, f_u, f_wflux, f_q
    445   USE write_field_mod
    446   USE checksum_mod
     471
    447472! from LMDZ
     473  USE wxios, ONLY: wxios_set_context
    448474  USE mod_phys_lmdz_omp_data, ONLY: klon_omp
    449475  USE geometry_mod, ONLY : cell_area
     
    719745
    720746    SUBROUTINE grid_icosa_to_physics
    721     USE pression_mod
    722     USE exner_mod
    723     USE theta2theta_rhodz_mod
    724     USE geopotential_mod
    725     USE omp_para
     747! from dynamico
     748    USE omp_para, ONLY: is_omp_first_level, ll_begin, ll_beginp1, &
     749                        ll_end, ll_endp1
    726750    IMPLICIT NONE
    727751   
     
    844868
    845869    SUBROUTINE grid_physics_to_icosa
    846     USE theta2theta_rhodz_mod
    847     USE omp_para
     870! from dynamico
     871    USE omp_para, ONLY: is_omp_first_level, ll_begin, &
     872                        ll_end, ll_endp1
    848873    IMPLICIT NONE
    849874      INTEGER :: i,j,ij,l,iq
Note: See TracChangeset for help on using the changeset viewer.