Ignore:
Timestamp:
Jan 26, 2019 5:03:42 PM (5 years ago)
Author:
knoop
Message:

Moved user_define_netdf_grid into user_module.f90
Added module interface for the definition of additional timeseries

File:
1 edited

Legend:

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

    r3687 r3700  
    8686    USE statistics
    8787
    88     USE statistics,                                                            &
    89         ONLY:  statistic_regions, region
    90 
    9188    USE surface_mod
    9289
     
    9491
    9592    INTEGER(iwp) ::  dots_num_palm   !<
     93    INTEGER(iwp) ::  dots_num_user = 0  !<
    9694    INTEGER(iwp) ::  user_idummy     !<
    9795   
     
    117115       user_parin, &
    118116       user_check_parameters, &
     117       user_check_data_output_ts, &
    119118       user_check_data_output_pr, &
    120119       user_check_data_output, &
     
    143142       MODULE PROCEDURE user_check_parameters
    144143    END INTERFACE user_check_parameters
     144
     145    INTERFACE user_check_data_output_ts
     146       MODULE PROCEDURE user_check_data_output_ts
     147    END INTERFACE user_check_data_output_ts
    145148
    146149    INTERFACE user_check_data_output_pr
     
    322325! Description:
    323326! ------------
     327!> Set module-specific timeseries units and labels
     328!------------------------------------------------------------------------------!
     329 SUBROUTINE user_check_data_output_ts( dots_max, dots_num, dots_label, dots_unit )
     330
     331
     332   INTEGER(iwp),      INTENT(IN)     ::  dots_max
     333   INTEGER(iwp),      INTENT(INOUT)  ::  dots_num
     334   CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT)  :: dots_label
     335   CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT)  :: dots_unit
     336
     337
     338!-- Sample for user-defined time series
     339!-- For each time series quantity you have to give a label and a unit,
     340!-- which will be used for the NetCDF file. They must not contain more than
     341!-- seven characters. The value of dots_num has to be increased by the
     342!-- number of new time series quantities. Its old value has to be store in
     343!-- dots_num_palm. See routine user_statistics on how to output calculate
     344!-- and output these quantities.
     345
     346!    dots_num_palm = dots_num
     347
     348!    dots_num = dots_num + 1
     349!    dots_num_user = dots_num_user + 1
     350!    dots_label(dots_num) = 'abs_umx'
     351!    dots_unit(dots_num)  = 'm/s'
     352
     353!    dots_num = dots_num + 1
     354!    dots_num_user = dots_num_user + 1
     355!    dots_label(dots_num) = 'abs_vmx'
     356!    dots_unit(dots_num)  = 'm/s'
     357
     358
     359 END SUBROUTINE user_check_data_output_ts
     360
     361
     362!------------------------------------------------------------------------------!
     363! Description:
     364! ------------
    324365!> Set the unit of user defined profile output quantities. For those variables
    325366!> not recognized by the user, the parameter unit is set to "illegal", which
     
    327368!> to a program abort.
    328369!------------------------------------------------------------------------------!
    329  SUBROUTINE user_check_data_output_pr( variable, var_count, unit )
    330 
    331 
    332     USE netcdf_interface,                                                      &
    333         ONLY:  dopr_unit
     370 SUBROUTINE user_check_data_output_pr( variable, var_count, unit, dopr_unit )
     371
    334372
    335373    USE profil_parameter
     
    338376    CHARACTER (LEN=*) ::  unit     !<
    339377    CHARACTER (LEN=*) ::  variable !<
     378    CHARACTER (LEN=*) ::  dopr_unit !< local value of dopr_unit
    340379
    341380    INTEGER(iwp) ::  user_pr_index !<
     
    357396!          user_pr_index = pr_palm + 1
    358397!          dopr_index(var_count)  = user_pr_index    ! quantities' user-profile-number
    359 !          dopr_unit(var_count)   = 'm2/s2'  ! quantity unit
     398!          dopr_unit = 'm2/s2'  ! quantity unit
     399!          unit = dopr_unit
    360400!          hom(:,2,user_pr_index,:)       = SPREAD( zu, 2, statistic_regions+1 )
    361401!                                            ! grid on which the quantity is
     
    413453
    414454
    415     USE netcdf_interface,                                                      &
    416         ONLY: dots_label, dots_unit, dots_num
    417 
    418 
    419455    CHARACTER (LEN=20) :: field_char   !<
    420456!
     
    424460!    ALLOCATE( ustvst(nzb:nzt+1,nysg:nyng,nxlg:nxrg) );  ustvst = 0.0_wp
    425461
    426 !-- Sample for user-defined time series
    427 !-- For each time series quantity you have to give a label and a unit,
    428 !-- which will be used for the NetCDF file. They must not contain more than
    429 !-- seven characters. The value of dots_num has to be increased by the
    430 !-- number of new time series quantities. Its old value has to be store in
    431 !-- dots_num_palm. See routine user_statistics on how to output calculate
    432 !-- and output these quantities.
    433 !    dots_label(dots_num+1) = 'abs_umx'
    434 !    dots_unit(dots_num+1)  = 'm/s'
    435 !    dots_label(dots_num+2) = 'abs_vmx'
    436 !    dots_unit(dots_num+2)  = 'm/s'
    437 !
    438 !    dots_num_palm = dots_num
    439 !    dots_num = dots_num + 2
    440462
    441463 END SUBROUTINE user_init
     464
     465
     466!------------------------------------------------------------------------------!
     467! Description:
     468! ------------
     469!> Set the grids on which user-defined output quantities are defined.
     470!> Allowed values for grid_x are "x" and "xu", for grid_y "y" and "yv", and
     471!> for grid_z "zu" and "zw".
     472!------------------------------------------------------------------------------!
     473 SUBROUTINE user_define_netcdf_grid( variable, found, grid_x, grid_y, grid_z )
     474
     475
     476    CHARACTER (LEN=*) ::  grid_x     !<
     477    CHARACTER (LEN=*) ::  grid_y     !<
     478    CHARACTER (LEN=*) ::  grid_z     !<
     479    CHARACTER (LEN=*) ::  variable   !<
     480
     481    LOGICAL ::  found   !<
     482
     483
     484    SELECT CASE ( TRIM( variable ) )
     485
     486!
     487!--    Uncomment and extend the following lines, if necessary
     488!       CASE ( 'u2', 'u2_xy', 'u2_xz', 'u2_yz' )
     489!          found  = .TRUE.
     490!          grid_x = 'xu'
     491!          grid_y = 'y'
     492!          grid_z = 'zu'
     493
     494!       CASE ( 'u*v*', 'u*v*_xy', 'u*v*_xz', 'u*v*_yz' )
     495!          found  = .TRUE.
     496!          grid_x = 'x'
     497!          grid_y = 'y'
     498!          grid_z = 'zu'
     499
     500       CASE DEFAULT
     501          found  = .FALSE.
     502          grid_x = 'none'
     503          grid_y = 'none'
     504          grid_z = 'none'
     505
     506    END SELECT
     507
     508
     509 END SUBROUTINE user_define_netcdf_grid
     510
     511
    442512
    443513
     
    913983
    914984
    915     USE netcdf_interface,                                                      &
    916         ONLY:  dots_max
    917 
    918 
    919985    CHARACTER (LEN=*) ::  mode   !<
    920 
    921986    INTEGER(iwp) ::  i    !<
    922987    INTEGER(iwp) ::  j    !<
     
    925990    INTEGER(iwp) ::  tn   !<
    926991
    927     REAL(wp),                                                                  &
    928        DIMENSION(dots_num_palm+1:dots_max) ::                                  &
    929           ts_value_l   !<
    930 
     992    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ts_value_l   !<
    931993
    932994    IF ( mode == 'profiles' )  THEN
     
    9621024    ELSEIF ( mode == 'time_series' )  THEN
    9631025
     1026
     1027!       ALLOCATE ( ts_value_l(dots_num_user) )
    9641028!
    9651029!--    Sample on how to add values for the user-defined time series quantities.
     
    9681032!--    velocities u and v.
    9691033!       ts_value_l = 0.0_wp
    970 !       ts_value_l(dots_num_palm+1) = ABS( u_max )
    971 !       ts_value_l(dots_num_palm+2) = ABS( v_max )
     1034!       ts_value_l(1) = ABS( u_max )
     1035!       ts_value_l(2) = ABS( v_max )
    9721036!
    9731037!--     Collect / send values to PE0, because only PE0 outputs the time series.
     
    9811045!#if defined( __parallel )
    9821046!       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    983 !       CALL MPI_ALLREDUCE( ts_value_l(dots_num_palm+1),                         &
     1047!       CALL MPI_ALLREDUCE( ts_value_l(1),                         &
    9841048!                           ts_value(dots_num_palm+1,sr),                        &
    985 !                           dots_max-dots_num_palm, MPI_REAL, MPI_SUM, comm2d,   &
     1049!                           dots_num_user, MPI_REAL, MPI_MAX, comm2d,   &
    9861050!                           ierr )
    9871051!#else
    988 !       ts_value(dots_num_palm+1:,sr) = ts_value_l
     1052!       ts_value(dots_num_palm+1:dots_num_palm+dots_num_user,sr) = ts_value_l
    9891053!#endif
    9901054
Note: See TracChangeset for help on using the changeset viewer.