Changeset 4186 for palm/trunk/SOURCE


Ignore:
Timestamp:
Aug 23, 2019 4:06:14 PM (5 years ago)
Author:
suehring
Message:

Enable limitation of Obukhov length so that it does not become zero; to read input data from netcdf in init_3d_model use provided module variables instead of defining local ones; tests updated because changes in Obukhov lengths causes small differences during the initial phase of the run

Location:
palm/trunk/SOURCE
Files:
3 edited

Legend:

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

    r4185 r4186  
    2525! -----------------
    2626! $Id$
     27! Design change, use variables defined in netcdf_data_input_mod to read netcd
     28! variables rather than define local ones.
     29!
     30! 4185 2019-08-23 13:49:38Z oliver.maas
    2731! For initializing_actions = ' cyclic_fill':
    2832! Overwrite u_init, v_init, pt_init, q_init and s_init with the
     
    160164               input_file_static,                                              &
    161165               netcdf_data_input_init_3d,                                      &
     166               num_var_pids,                                                   &
    162167               open_read_file,                                                 &
    163                real_2d
     168               pids_id,                                                        &
     169               real_2d,                                                        &
     170               vars_pids
    164171               
    165172    USE nesting_offl_mod,                                                      &
     
    213220
    214221    IMPLICIT NONE
    215 
    216     CHARACTER(LEN=50), DIMENSION(:), ALLOCATABLE ::  vars_pids_static  !< variable names in static input file
    217222   
    218223    INTEGER(iwp) ::  i                    !< grid index in x direction
     
    223228    INTEGER(iwp) ::  l                    !< running index over surface orientation   
    224229    INTEGER(iwp) ::  m                    !< index of surface element in surface data type   
    225     INTEGER(iwp) ::  num_vars_pids_static !< number of variables in static input file
    226230    INTEGER(iwp) ::  nz_u_shift           !< topography-top index on u-grid, used to vertically shift initial profiles
    227231    INTEGER(iwp) ::  nz_v_shift           !< topography-top index on v-grid, used to vertically shift initial profiles
     
    233237    INTEGER(iwp) ::  nz_s_shift_l         !< topography-top index on scalar-grid, used to vertically shift initial profiles
    234238    INTEGER(iwp) ::  nzt_l                !< index of top PE boundary for multigrid level
    235     INTEGER(iwp) ::  pids_static_id       !< file id for static input file
    236239    INTEGER(iwp) ::  sr                   !< index of statistic region
    237240
     
    15411544       CALL open_read_file( TRIM( input_file_static ) //                    &
    15421545                            TRIM( coupling_char ),                          &
    1543                             pids_static_id )
     1546                            pids_id )
    15441547                           
    1545        CALL inquire_num_variables( pids_static_id, num_vars_pids_static )
     1548       CALL inquire_num_variables( pids_id, num_var_pids )
    15461549!
    15471550!--    Allocate memory to store variable names and read them
    1548        ALLOCATE( vars_pids_static(1:num_vars_pids_static) )
    1549        CALL inquire_variable_names( pids_static_id, vars_pids_static )
     1551       ALLOCATE( vars_pids(1:num_var_pids) )
     1552       CALL inquire_variable_names( pids_id, vars_pids )
    15501553!
    15511554!--    Input roughness length.
    1552        IF ( check_existence( vars_pids_static, 'z0' ) )  THEN
     1555       IF ( check_existence( vars_pids, 'z0' ) )  THEN
    15531556!
    15541557!--       Read _FillValue attribute
    1555           CALL get_attribute( pids_static_id, char_fill, tmp_2d%fill,          &
     1558          CALL get_attribute( pids_id, char_fill, tmp_2d%fill,          &
    15561559                              .FALSE., 'z0' )                                 
    15571560!                                                                             
    15581561!--       Read variable                                                       
    1559           CALL get_variable( pids_static_id, 'z0', tmp_2d%var,                 &
     1562          CALL get_variable( pids_id, 'z0', tmp_2d%var,                 &
    15601563                             nxl, nxr, nys, nyn )                             
    15611564!                                                                             
     
    15921595!
    15931596!--    Finally, close the input file.
    1594        CALL close_input_file( pids_static_id )
     1597       CALL close_input_file( pids_id )
    15951598#endif
    15961599       DEALLOCATE( tmp_2d%var )
  • palm/trunk/SOURCE/netcdf_data_input_mod.f90

    r4182 r4186  
    2525! -----------------
    2626! $Id$
     27! Minor formatting adjustments
     28!
     29! 4182 2019-08-22 15:20:23Z scharf
    2730! Corrected "Former revisions" section
    2831!
     
    50575060
    50585061#if defined( __netcdf4_parallel )
    5059 !      if __netcdf4_parallel is defined, parrallel NetCDF will be used unconditionally
     5062!
     5063!--    If __netcdf4_parallel is defined, parrallel NetCDF will be used
     5064!--    unconditionally
    50605065       nc_stat = NF90_OPEN( filename, IOR( NF90_WRITE, NF90_MPIIO ), id,  &
    50615066                            COMM = comm2d, INFO = MPI_INFO_NULL )
    5062        IF(nc_stat /= NF90_NOERR )  THEN                                       !possible NetCDF 3 file
    5063            nc_stat = NF90_OPEN( filename, NF90_NOWRITE, id )
    5064            collective_read = .FALSE.
     5067!
     5068!--    Check for possible Netcdf 3 file.
     5069       IF( nc_stat /= NF90_NOERR )  THEN
     5070          nc_stat = NF90_OPEN( filename, NF90_NOWRITE, id )
     5071          collective_read = .FALSE.
    50655072       ELSE
    5066            collective_read = .TRUE.
    5067        END IF
     5073          collective_read = .TRUE.
     5074       ENDIF
    50685075#else
    50695076!      All MPI processes open und read
  • palm/trunk/SOURCE/surface_layer_fluxes_mod.f90

    r4182 r4186  
    2626! -----------------
    2727! $Id$
     28! - To enable limitation of Obukhov length, move it before exit-cycle construct.
     29!   Further, change the limit to 10E-5 in order to get rid-off unrealistic
     30!   peaks in the heat fluxes during nighttime
     31! - Unused variable removed
     32!
     33! 4182 2019-08-22 15:20:23Z scharf
    2834! Corrected "Former revisions" section
    2935!
     
    129135    INTEGER(iwp) ::  l              !< loop index for surf type
    130136
    131     INTEGER(iwp), PARAMETER ::  num_steps = 15000  !< number of steps in the lookup table
    132 
    133137    LOGICAL      ::  coupled_run       !< Flag for coupled atmosphere-ocean runs
    134138    LOGICAL      ::  downward = .FALSE.!< Flag indicating downward-facing horizontal surface
     
    10081012             ENDIF
    10091013!
     1014!--          Assure that Obukhov length does not become zero. If the limit is
     1015!--          reached, exit the loop.
     1016             IF ( ABS( surf%ol(m) ) < 1E-5_wp )  THEN
     1017                surf%ol(m) = SIGN( 1E-5_wp, surf%ol(m) )
     1018                EXIT
     1019             ENDIF
     1020!
    10101021!--          Check for convergence
    10111022             IF ( ABS( ( surf%ol(m) - ol_m ) /  surf%ol(m) ) < 1.0E-4_wp )  THEN
     
    10131024             ELSE
    10141025                CYCLE
    1015              ENDIF
    1016 !
    1017 !--          Assure that Obukhov length does not become zero
    1018              IF ( ABS( surf%ol(m) ) < 1E-6_wp )                                &
    1019                 surf%ol(m) = SIGN( 10E-6_wp, surf%ol(m) )             
     1026             ENDIF             
    10201027
    10211028          ENDDO
Note: See TracChangeset for help on using the changeset viewer.