- Timestamp:
- Oct 29, 2017, 11:13:59 AM (7 years ago)
- Location:
- LMDZ6/branches/DYNAMICO-conv/libf
- Files:
-
- 1 added
- 8 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/branches/DYNAMICO-conv/libf/dynphy_lonlat/inigeomphy_mod.F90
r2963 r3049 76 76 REAL,ALLOCATABLE,SAVE :: boundslonfi(:,:) 77 77 REAL,ALLOCATABLE,SAVE :: boundslatfi(:,:) 78 !$OMP THREADPRIVATE (latfi,lonfi,cufi,cvfi,airefi,boundslonfi,boundslatfi) 78 INTEGER,ALLOCATABLE,SAVE :: ind_cell_glo_fi(:) 79 !$OMP THREADPRIVATE (latfi,lonfi,cufi,cvfi,airefi,boundslonfi,boundslatfi,ind_cell_glo_fi) 79 80 80 81 ! Initialize Physics distibution and parameters and interface with dynamics … … 93 94 94 95 DO i=1,iim 96 boundslon_reg(i,east)=rlonu(i+1) 95 97 boundslon_reg(i,west)=rlonu(i) 96 boundslon_reg(i,east)=rlonu(i+1)97 98 ENDDO 98 99 … … 204 205 ALLOCATE(boundslonfi(klon_omp,4)) 205 206 ALLOCATE(boundslatfi(klon_omp,4)) 207 ALLOCATE(ind_cell_glo_fi(klon_omp)) 206 208 207 209 … … 214 216 boundslonfi(1:klon_omp,:) = boundslonfi_glo(offset+klon_omp_begin:offset+klon_omp_end,:) 215 217 boundslatfi(1:klon_omp,:) = boundslatfi_glo(offset+klon_omp_begin:offset+klon_omp_end,:) 218 ind_cell_glo_fi(1:klon_omp)=(/ (i,i=offset+klon_omp_begin,offset+klon_omp_end) /) 216 219 217 220 ! copy over local grid longitudes and latitudes 218 221 CALL init_geometry(klon_omp,lonfi,latfi,boundslonfi,boundslatfi, & 219 airefi, cufi,cvfi)222 airefi,ind_cell_glo_fi,cufi,cvfi) 220 223 221 224 ! copy over preff , ap(), bp(), etc -
LMDZ6/branches/DYNAMICO-conv/libf/phy_common/geometry_mod.F90
r2395 r3049 30 30 !$OMP THREADPRIVATE(cell_area) 31 31 32 INTEGER,SAVE,ALLOCATABLE :: ind_cell_glo(:) ! global indice of a local cell 33 !$OMP THREADPRIVATE(ind_cell_glo) 32 34 33 35 CONTAINS … … 35 37 SUBROUTINE init_geometry(klon,longitude_,latitude_, & 36 38 boundslon_,boundslat_, & 37 cell_area_, dx_,dy_)39 cell_area_,ind_cell_glo_,dx_,dy_) 38 40 USE mod_grid_phy_lmdz, ONLY: nvertex 39 41 USE nrtype, ONLY : PI … … 45 47 REAL,INTENT(IN) :: boundslat_(klon,nvertex) 46 48 REAL,INTENT(IN) :: cell_area_(klon) 49 INTEGER,OPTIONAL,INTENT(IN) :: ind_cell_glo_(klon) 47 50 REAL,OPTIONAL,INTENT(IN) :: dx_(klon) 48 51 REAL,OPTIONAL,INTENT(IN) :: dy_(klon) … … 55 58 ALLOCATE(boundslat(klon,nvertex)) 56 59 ALLOCATE(cell_area(klon)) 60 IF (PRESENT(ind_cell_glo_)) ALLOCATE(ind_cell_glo(klon)) 57 61 IF (PRESENT(dx_)) ALLOCATE(dx(klon)) 58 62 IF (PRESENT(dy_))ALLOCATE(dy(klon)) … … 65 69 boundslat(:,:) = boundslat_(:,:) 66 70 cell_area(:) = cell_area_(:) 71 IF (PRESENT(ind_cell_glo_)) ind_cell_glo(:) = ind_cell_glo_(:) 67 72 IF (PRESENT(dx_)) dx(:) = dx_(:) 68 73 IF (PRESENT(dy_)) dy(:) = dy_(:) -
LMDZ6/branches/DYNAMICO-conv/libf/phy_common/mod_phys_lmdz_mpi_data.F90
r2429 r3049 3 3 ! 4 4 MODULE mod_phys_lmdz_mpi_data 5 ! USE mod_const_mpi6 5 7 6 INTEGER,SAVE :: ii_begin … … 36 35 INTEGER,SAVE :: mpi_size 37 36 INTEGER,SAVE :: mpi_master 38 ! INTEGER,SAVE :: mpi_root39 37 LOGICAL,SAVE :: is_mpi_root 40 38 LOGICAL,SAVE :: is_using_mpi 41 39 42 40 43 ! LOGICAL,SAVE :: is_north_pole44 ! LOGICAL,SAVE :: is_south_pole45 41 LOGICAL,SAVE :: is_north_pole_dyn 46 42 LOGICAL,SAVE :: is_south_pole_dyn … … 50 46 CONTAINS 51 47 52 ! SUBROUTINE Init_phys_lmdz_mpi_data(iim,jjp1,nb_proc,distrib)53 48 SUBROUTINE init_phys_lmdz_mpi_data(nbp, nbp_lon, nbp_lat, communicator) 54 ! USE mod_const_mpi, ONLY : COMM_LMDZ55 49 IMPLICIT NONE 56 50 #ifdef CPP_MPI 57 51 INCLUDE 'mpif.h' 58 52 #endif 59 INTEGER,INTENT( in) :: nbp60 INTEGER,INTENT( in) :: nbp_lon61 INTEGER,INTENT( in) :: nbp_lat62 INTEGER,INTENT( in) :: communicator53 INTEGER,INTENT(IN) :: nbp 54 INTEGER,INTENT(IN) :: nbp_lon 55 INTEGER,INTENT(IN) :: nbp_lat 56 INTEGER,INTENT(IN) :: communicator 63 57 64 58 INTEGER,ALLOCATABLE :: distrib(:) … … 189 183 190 184 SUBROUTINE print_module_data 191 !USE print_control_mod, ONLY: lunout185 USE print_control_mod, ONLY: lunout 192 186 IMPLICIT NONE 193 INCLUDE "iniprint.h"187 ! INCLUDE "iniprint.h" 194 188 195 189 WRITE(lunout,*) 'ii_begin =', ii_begin -
LMDZ6/branches/DYNAMICO-conv/libf/phy_common/mod_phys_lmdz_omp_data.F90
r2429 r3049 7 7 INTEGER,SAVE :: omp_rank 8 8 LOGICAL,SAVE :: is_omp_root 9 LOGICAL,SAVE :: is_omp_master ! alias of is_omp_root 9 10 LOGICAL,SAVE :: is_using_omp 10 11 LOGICAL,SAVE :: is_north_pole_phy, is_south_pole_phy … … 17 18 INTEGER,SAVE :: klon_omp_begin 18 19 INTEGER,SAVE :: klon_omp_end 19 !$OMP THREADPRIVATE(omp_rank,klon_omp,is_omp_root, klon_omp_begin,klon_omp_end)20 !$OMP THREADPRIVATE(omp_rank,klon_omp,is_omp_root,is_omp_master,klon_omp_begin,klon_omp_end) 20 21 !$OMP THREADPRIVATE(is_north_pole_phy, is_south_pole_phy) 21 22 … … 63 64 ENDIF 64 65 !$OMP END MASTER 65 66 is_omp_master=is_omp_root 66 67 67 68 !$OMP MASTER … … 106 107 107 108 SUBROUTINE Print_module_data 109 USE print_control_mod, ONLY: lunout 108 110 IMPLICIT NONE 109 INCLUDE "iniprint.h"111 ! INCLUDE "iniprint.h" 110 112 111 113 !$OMP CRITICAL -
LMDZ6/branches/DYNAMICO-conv/libf/phy_common/mod_phys_lmdz_para.F90
r2429 r3049 49 49 SUBROUTINE Test_transfert 50 50 USE mod_grid_phy_lmdz 51 USE print_control_mod, ONLY: lunout 51 52 IMPLICIT NONE 52 INCLUDE "iniprint.h"53 ! INCLUDE "iniprint.h" 53 54 54 55 REAL :: Test_Field1d_glo(klon_glo,nbp_lev) -
LMDZ6/branches/DYNAMICO-conv/libf/phy_common/print_control_mod.F90
r2326 r3049 7 7 !$OMP THREADPRIVATE(lunout,prt_level,debug) 8 8 9 ! NB: Module variable Initializations done by set_print_control 10 ! routine from init_print_control_mod to avoid circular 11 ! module dependencies 12 9 13 CONTAINS 10 14 11 SUBROUTINE init_print_control 12 USE ioipsl_getin_p_mod, ONLY : getin_p 13 USE mod_phys_lmdz_para, ONLY: is_omp_root, is_master 15 SUBROUTINE set_print_control(lunout_,prt_level_,debug_) 14 16 IMPLICIT NONE 15 16 LOGICAL :: opened 17 INTEGER :: number 17 INTEGER :: lunout_ 18 INTEGER :: prt_level_ 19 LOGICAL :: debug_ 20 21 lunout = lunout_ 22 prt_level = prt_level_ 23 debug = debug_ 18 24 19 !Config Key = prt_level 20 !Config Desc = niveau d'impressions de débogage 21 !Config Def = 0 22 !Config Help = Niveau d'impression pour le débogage 23 !Config (0 = minimum d'impression) 24 prt_level = 0 25 CALL getin_p('prt_level',prt_level) 26 27 !Config Key = lunout 28 !Config Desc = unite de fichier pour les impressions 29 !Config Def = 6 30 !Config Help = unite de fichier pour les impressions 31 !Config (defaut sortie standard = 6) 32 lunout=6 33 CALL getin_p('lunout', lunout) 34 35 IF (is_omp_root) THEN 36 IF (lunout /= 5 .and. lunout /= 6) THEN 37 INQUIRE(FILE='lmdz.out_0000',OPENED=opened,NUMBER=number) 38 IF (opened) THEN 39 lunout=number 40 ELSE 41 OPEN(UNIT=lunout,FILE='lmdz.out_0000',ACTION='write', & 42 STATUS='unknown',FORM='formatted') 43 ENDIF 44 ENDIF 45 ENDIF 46 47 !Config Key = debug 48 !Config Desc = mode debogage 49 !Config Def = false 50 !Config Help = positionne le mode debogage 51 52 debug = .FALSE. 53 CALL getin_p('debug',debug) 54 55 IF (is_master) THEN 56 WRITE(lunout,*)"init_print_control: prt_level=",prt_level 57 WRITE(lunout,*)"init_print_control: lunout=",lunout 58 WRITE(lunout,*)"init_print_control: debug=",debug 59 ENDIF 60 61 END SUBROUTINE init_print_control 25 END SUBROUTINE set_print_control 62 26 63 27 END MODULE print_control_mod -
LMDZ6/branches/DYNAMICO-conv/libf/phydev/inifis_mod.F90
r2311 r3049 1 ! $Id :$1 ! $Id$ 2 2 MODULE inifis_mod 3 3 … … 6 6 SUBROUTINE inifis(prad, pg, pr, pcpp) 7 7 ! Initialize some physical constants and settings 8 USE print_control_mod, ONLY: init_print_control8 USE init_print_control_mod, ONLY: init_print_control 9 9 USE comcstphy, ONLY: rradius, & ! planet radius (m) 10 10 rr, & ! recuced gas constant: R/molar mass of atm -
LMDZ6/branches/DYNAMICO-conv/libf/phylmd/inifis_mod.F90
r2311 r3049 6 6 SUBROUTINE inifis(punjours, prad, pg, pr, pcpp) 7 7 ! Initialize some physical constants and settings 8 USE print_control_mod, ONLY: init_print_control, lunout 8 USE init_print_control_mod, ONLY : init_print_control 9 USE print_control_mod, ONLY: lunout 9 10 IMPLICIT NONE 10 11
Note: See TracChangeset
for help on using the changeset viewer.