Ignore:
Timestamp:
Mar 4, 2013 5:31:38 AM (11 years ago)
Author:
raasch
Message:

New:
---

Porting of FFT-solver for serial runs to GPU using CUDA FFT,
preprocessor lines in transpose routines rearranged, so that routines can also
be used in serial (non-parallel) mode,
transpositions also carried out in serial mode, routines fftx, fftxp replaced
by calls of fft_x, fft_x replaced by fft_x_1d in the 1D-decomposition routines
(Makefile, Makefile_check, fft_xy, poisfft, poisfft_hybrid, transpose, new: cuda_fft_interfaces)

--stdin argument for mpiexec on lckyuh, -y and -Y settings output to header (mrun)

Changed:


Module array_kind renamed precision_kind
(check_open, data_output_3d, fft_xy, modules, user_data_output_3d)

some format changes for coupled atmosphere-ocean runs (header)
small changes in code formatting (microphysics, prognostic_equations)

Errors:


bugfix: default value (0) assigned to coupling_start_time (modules)
bugfix: initial time for preruns of coupled runs is output as -coupling_start_time (data_output_profiles)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/prognostic_equations.f90

    r1093 r1106  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! small changes in code formatting
    2323!
    2424! Former revisions:
     
    418418
    419419!
    420 !--      If required, calculate tendencies for total water content, rain water
    421 !--      content, rain drop concentration and liquid temperature
    422 
    423          IF ( cloud_physics .AND. icloud_scheme == 0 )  THEN
    424 
    425             tend_q(:,j,i)  = 0.0
    426             tend_qr(:,j,i) = 0.0
    427             tend_nr(:,j,i) = 0.0
    428             tend_pt(:,j,i) = 0.0
    429 !
    430 !--         Droplet size distribution (dsd) properties are needed for the
    431 !--         computation of selfcollection, breakup, evaporation and
    432 !--         sedimentation of rain. 
    433             IF ( precipitation )  THEN
    434                CALL dsd_properties( i,j )
    435                CALL autoconversion( i,j )
    436                CALL accretion( i,j )
    437                CALL selfcollection_breakup( i,j )
    438                CALL evaporation_rain( i,j )
    439                CALL sedimentation_rain( i,j )
    440             ENDIF
    441 
    442             IF ( drizzle )  CALL sedimentation_cloud( i,j )
    443 
    444          ENDIF
     420!--       If required, calculate tendencies for total water content, rain water
     421!--       content, rain drop concentration and liquid temperature
     422          IF ( cloud_physics  .AND.  icloud_scheme == 0 )  THEN
     423
     424             tend_q(:,j,i)  = 0.0
     425             tend_qr(:,j,i) = 0.0
     426             tend_nr(:,j,i) = 0.0
     427             tend_pt(:,j,i) = 0.0
     428!
     429!--          Droplet size distribution (dsd) properties are needed for the
     430!--          computation of selfcollection, breakup, evaporation and
     431!--          sedimentation of rain
     432             IF ( precipitation )  THEN
     433                CALL dsd_properties( i,j )
     434                CALL autoconversion( i,j )
     435                CALL accretion( i,j )
     436                CALL selfcollection_breakup( i,j )
     437                CALL evaporation_rain( i,j )
     438                CALL sedimentation_rain( i,j )
     439             ENDIF
     440
     441             IF ( drizzle )  CALL sedimentation_cloud( i,j )
     442
     443          ENDIF
    445444
    446445!
     
    469468             ENDIF
    470469
     470!
    471471!--          Using microphysical tendencies (latent heat)
    472472             IF ( cloud_physics )  THEN
    473473                IF ( icloud_scheme == 0 )  THEN
    474474                   tend(:,j,i) = tend(:,j,i) + tend_pt(:,j,i)
    475                 ELSEIF ( icloud_scheme == 1 .AND. precipitation)  THEN
     475                ELSEIF ( icloud_scheme == 1  .AND.  precipitation )  THEN
    476476                   CALL impact_of_latent_heat( i, j )
    477477                ENDIF
     
    480480!
    481481!--          Consideration of heat sources within the plant canopy
    482              IF ( plant_canopy .AND. ( cthf /= 0.0 ) ) THEN
     482             IF ( plant_canopy  .AND.  cthf /= 0.0 ) THEN
    483483                CALL plant_canopy_model( i, j, 4 )
    484484             ENDIF
    485485
    486486!
    487 !--          If required, compute influence of large-scale subsidence/ascent
     487!--          If required, compute effect of large-scale subsidence/ascent
    488488             IF ( large_scale_subsidence )  THEN
    489489                CALL subsidence( i, j, tend, pt, pt_init )
    490490             ENDIF
    491 
    492491
    493492             CALL user_actions( i, j, 'pt-tendency' )
     
    600599                IF ( icloud_scheme == 0 )  THEN
    601600                   tend(:,j,i) = tend(:,j,i) + tend_q(:,j,i)
    602                 ELSEIF ( icloud_scheme == 1 .AND. precipitation )  THEN
     601                ELSEIF ( icloud_scheme == 1  .AND. precipitation )  THEN
    603602                   CALL calc_precipitation( i, j )
    604603                ENDIF
     
    606605!
    607606!--          Sink or source of scalar concentration due to canopy elements
    608              IF ( plant_canopy ) CALL plant_canopy_model( i, j, 5 )
     607             IF ( plant_canopy )  CALL plant_canopy_model( i, j, 5 )
    609608
    610609!
     
    645644!--          If required, calculate prognostic equations for rain water content
    646645!--          and rain drop concentration
    647              IF ( cloud_physics .AND. icloud_scheme == 0 )  THEN
     646             IF ( cloud_physics  .AND. icloud_scheme == 0 )  THEN
    648647!
    649648!--             Calculate prognostic equation for rain water content
     
    706705                IF ( timestep_scheme(1:5) == 'runge' )  THEN
    707706                   IF ( ws_scheme_sca )  THEN
    708                       CALL advec_s_ws( i, j, nr, 'nr', flux_s_nr,    &
    709                                     diss_s_nr, flux_l_nr, diss_l_nr, &
    710                                     i_omp_start, tn )
     707                      CALL advec_s_ws( i, j, nr, 'nr', flux_s_nr,       &
     708                                       diss_s_nr, flux_l_nr, diss_l_nr, &
     709                                       i_omp_start, tn )
    711710                   ELSE
    712711                      CALL advec_s_pw( i, j, nr )
Note: See TracChangeset for help on using the changeset viewer.