Changeset 4517 for palm/trunk/SOURCE/chemistry_model_mod.f90
- Timestamp:
- May 3, 2020 2:29:30 PM (5 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/chemistry_model_mod.f90
r4511 r4517 27 27 ! ----------------- 28 28 ! $Id$ 29 ! added restart with MPI-IO 30 ! 31 ! 4511 2020-04-30 12:20:40Z raasch 29 32 ! decycling replaced by explicit setting of lateral boundary conditions 30 33 ! … … 312 315 max_pr_user, & 313 316 monotonic_limiter_z, & 317 restart_data_format_output, & 314 318 scalar_advec, & 315 319 timestep_scheme, use_prescribed_profile_data, ws_scheme_sca, air_chemistry … … 329 333 USE cpulog, & 330 334 ONLY: cpu_log, log_point_s 335 336 USE restart_data_mpi_io_mod, & 337 ONLY: rrd_mpi_io, wrd_mpi_io 331 338 332 339 USE statistics … … 501 508 502 509 INTERFACE chem_rrd_local 503 MODULE PROCEDURE chem_rrd_local 510 MODULE PROCEDURE chem_rrd_local_ftn 511 MODULE PROCEDURE chem_rrd_local_mpi 504 512 END INTERFACE chem_rrd_local 505 513 … … 3042 3050 ! Description: 3043 3051 ! ------------ 3044 !> Subroutine to read restart data of chemical species3045 !------------------------------------------------------------------------------! 3046 SUBROUTINE chem_rrd_local ( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc, &3047 nxr_on_file, nynf, nync, nyn_on_file, nysf, nysc, &3048 nys_on_file, tmp_3d, found )3052 !> Read module-specific local restart data arrays (Fortran binary format). 3053 !------------------------------------------------------------------------------! 3054 SUBROUTINE chem_rrd_local_ftn( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc, & 3055 nxr_on_file, nynf, nync, nyn_on_file, nysf, nysc, & 3056 nys_on_file, tmp_3d, found ) 3049 3057 3050 3058 USE control_parameters … … 3076 3084 3077 3085 3078 IF ( ALLOCATED( chem_species) ) THEN3086 IF ( ALLOCATED( chem_species ) ) THEN 3079 3087 3080 3088 DO lsp = 1, nspec … … 3105 3113 3106 3114 3107 END SUBROUTINE chem_rrd_local 3115 END SUBROUTINE chem_rrd_local_ftn 3116 3117 3118 !------------------------------------------------------------------------------! 3119 ! Description: 3120 ! ------------ 3121 !> Read module-specific local restart data arrays (Fortran binary format). 3122 !------------------------------------------------------------------------------! 3123 SUBROUTINE chem_rrd_local_mpi 3124 3125 IMPLICIT NONE 3126 3127 INTEGER(iwp) :: lsp !< 3128 3129 IF ( ALLOCATED( chem_species ) ) THEN 3130 3131 DO lsp = 1, nspec 3132 3133 CALL rrd_mpi_io( TRIM( chem_species(lsp)%name ), chem_species(lsp)%conc ) 3134 CALL rrd_mpi_io( TRIM( chem_species(lsp)%name )//'_av', chem_species(lsp)%conc_av ) 3135 3136 ENDDO 3137 3138 ENDIF 3139 3140 END SUBROUTINE chem_rrd_local_mpi 3108 3141 3109 3142 … … 3208 3241 INTEGER(iwp) :: lsp !< running index for chem spcs. 3209 3242 3210 DO lsp = 1, nspec 3211 CALL wrd_write_string( TRIM( chem_species(lsp)%name ) ) 3212 WRITE ( 14 ) chem_species(lsp)%conc 3213 CALL wrd_write_string( TRIM( chem_species(lsp)%name )//'_av' ) 3214 WRITE ( 14 ) chem_species(lsp)%conc_av 3215 ENDDO 3243 IF ( TRIM( restart_data_format_output ) == 'fortran_binary' ) THEN 3244 3245 DO lsp = 1, nspec 3246 CALL wrd_write_string( TRIM( chem_species(lsp)%name ) ) 3247 WRITE ( 14 ) chem_species(lsp)%conc 3248 CALL wrd_write_string( TRIM( chem_species(lsp)%name )//'_av' ) 3249 WRITE ( 14 ) chem_species(lsp)%conc_av 3250 ENDDO 3251 3252 ELSEIF ( TRIM( restart_data_format_output ) == 'mpi' ) THEN 3253 3254 DO lsp = 1, nspec 3255 CALL wrd_mpi_io( TRIM( chem_species(lsp)%name ), chem_species(lsp)%conc ) 3256 CALL wrd_mpi_io( TRIM( chem_species(lsp)%name ) // '_av', chem_species(lsp)%conc_av ) 3257 ENDDO 3258 3259 ENDIF 3216 3260 3217 3261 END SUBROUTINE chem_wrd_local
Note: See TracChangeset
for help on using the changeset viewer.