Changeset 3700


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

Location:
palm/trunk/SOURCE
Files:
1 deleted
10 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/Makefile

    r3687 r3700  
    690690        user_data_output_dvrp.f90 \
    691691        user_data_output_mask.f90 \
    692         user_define_netcdf_grid.f90 \
    693692        user_dvrp_coltab.f90 \
    694693        user_flight.f90\
     
    13521351        spectra_mod.o \
    13531352        turbulence_closure_mod.o \
    1354         urban_surface_mod.o
     1353        urban_surface_mod.o \
     1354        user_module.o
    13551355nesting_offl_mod.o: \
    13561356        cpulog_mod.o \
     
    17521752        modules.o \
    17531753        user_module.o
    1754 user_define_netcdf_grid.o: \
    1755         mod_kinds.o \
    1756         modules.o \
    1757         user_module.o
    17581754user_dvrp_coltab.o: \
    17591755        mod_kinds.o \
     
    17821778        mod_kinds.o \
    17831779        modules.o \
    1784         netcdf_interface_mod.o \
    1785         surface_mod.o \
    1786         user_module.o
     1780        surface_mod.o
    17871781user_init_plant_canopy.o: \
    17881782        mod_kinds.o \
     
    18161810        mod_kinds.o \
    18171811        modules.o \
    1818         netcdf_interface_mod.o \
    18191812        surface_mod.o
    18201813user_spectra.o: \
  • palm/trunk/SOURCE/bulk_cloud_model_mod.f90

    r3655 r3700  
    881881!> Initialization of the bulk cloud module
    882882!------------------------------------------------------------------------------!
    883     SUBROUTINE bcm_init !( dots_label, dots_unit, dots_num, dots_max )
     883    SUBROUTINE bcm_init
    884884
    885885       IMPLICIT NONE
     
    888888       INTEGER(iwp) ::  j !<
    889889       INTEGER(iwp) ::  k !<
    890 
    891 !        INTEGER(iwp) ::  dots_num
    892 !        INTEGER(iwp) ::  dots_max
    893 !        CHARACTER (LEN=13), DIMENSION(dots_max) :: dots_unit
    894 !        CHARACTER (LEN=13), DIMENSION(dots_max) :: dots_label
    895890
    896891       CALL location_message( 'initializing bulk cloud module', .FALSE. )
  • palm/trunk/SOURCE/check_parameters.f90

    r3668 r3700  
    780780    USE module_interface,                                                      &
    781781        ONLY:  module_interface_check_parameters,                              &
     782               module_interface_check_data_output_ts,                          &
    782783               module_interface_check_data_output_pr,                          &
    783784               module_interface_check_data_output
     
    790791        ONLY:  dopr_unit, do2d_unit, do3d_unit, netcdf_data_format,            &
    791792               netcdf_data_format_string, dots_unit, heatflux_output_unit,     &
    792                waterflux_output_unit, momentumflux_output_unit
     793               waterflux_output_unit, momentumflux_output_unit,                &
     794               dots_max, dots_num, dots_label
    793795
    794796    USE particle_attributes
     
    12531255    dots_unit(21)    = waterflux_output_unit
    12541256    dots_unit(19:20) = momentumflux_output_unit
     1257
     1258!
     1259!-- Add other module specific timeseries
     1260    CALL module_interface_check_data_output_ts( dots_max, dots_num, dots_label, dots_unit )
     1261
     1262!
     1263!-- Check if maximum number of allowed timeseries is exceeded
     1264    IF ( dots_num > dots_max )  THEN
     1265       WRITE( message_string, * ) 'number of time series quantities exceeds',  &
     1266                                  ' its maximum of dots_max = ', dots_max,     &
     1267                                  '&Please increase dots_max in modules.f90.'
     1268       CALL message( 'init_3d_model', 'PA0194', 1, 2, 0, 6, 0 )   
     1269    ENDIF
    12551270
    12561271!
  • palm/trunk/SOURCE/chemistry_model_mod.f90

    r3687 r3700  
    26422642    INTEGER(iwp) ::  m    !<
    26432643    INTEGER(iwp) ::  lpr  !< running index chem spcs
    2644 
    2645     !    REAL(wp),                                                                                      &
    2646     !    DIMENSION(dots_num_palm+1:dots_max) ::                                                         &
    2647     !          ts_value_l   !<
    26482644
    26492645    IF ( mode == 'profiles' )  THEN
  • palm/trunk/SOURCE/init_3d_model.f90

    r3685 r3700  
    617617
    618618    USE netcdf_interface,                                                      &
    619         ONLY:  dots_max, dots_num, dots_unit, dots_label
     619        ONLY:  dots_max
    620620
    621621    USE netcdf_data_input_mod,                                                 &
     
    734734              sums_l(nzb:nzt+1,pr_palm+max_pr_user+max_pr_cs,0:threads_per_task-1),      &
    735735              sums_l_l(nzb:nzt+1,0:statistic_regions,0:threads_per_task-1),    &
    736               sums_wsts_bc_l(nzb:nzt+1,0:statistic_regions),                   &
    737               ts_value(dots_max,0:statistic_regions) )
     736              sums_wsts_bc_l(nzb:nzt+1,0:statistic_regions) )
     737    ALLOCATE( ts_value(dots_max,0:statistic_regions) )
    738738    ALLOCATE( ptdf_x(nxlg:nxrg), ptdf_y(nysg:nyng) )
    739739
     
    20412041    rmask(:,nxlg:nxl-1,:) = 0.0_wp;  rmask(:,nxr+1:nxrg,:) = 0.0_wp
    20422042    rmask(nysg:nys-1,:,:) = 0.0_wp;  rmask(nyn+1:nyng,:,:) = 0.0_wp
    2043 
    2044 !
    2045 !-- Temporary solution to add LSM and radiation time series to the default
    2046 !-- output
    2047     IF ( land_surface  .OR.  radiation )  THEN
    2048        IF ( TRIM( radiation_scheme ) == 'rrtmg' )  THEN
    2049           dots_num = dots_num + 15
    2050        ELSE
    2051           dots_num = dots_num + 11
    2052        ENDIF
    2053     ENDIF
    20542043!
    20552044!-- To do: New concept for these non-topography grid points!
     
    23822371       ENDDO
    23832372    ENDIF
    2384 !
    2385 !-- Check if maximum number of allowed timeseries is exceeded
    2386     IF ( dots_num > dots_max )  THEN
    2387        WRITE( message_string, * ) 'number of time series quantities exceeds',  &
    2388                                   ' its maximum of dots_max = ', dots_max,     &
    2389                                   '&Please increase dots_max in modules.f90.'
    2390        CALL message( 'init_3d_model', 'PA0194', 1, 2, 0, 6, 0 )   
    2391     ENDIF
    23922373
    23932374!
  • palm/trunk/SOURCE/module_interface.f90

    r3687 r3700  
    216216              radiation_parin,                                                 &
    217217              radiation_check_parameters,                                      &
     218              radiation_check_data_output_ts,                                  &
    218219              radiation_check_data_output_pr,                                  &
    219220              radiation_check_data_output,                                     &
     
    271272       ONLY:  user_parin,                                                      &
    272273              user_check_parameters,                                           &
     274              user_check_data_output_ts,                                       &
    273275              user_check_data_output_pr,                                       &
    274276              user_check_data_output,                                          &
     
    307309      module_interface_parin,                                                  &
    308310      module_interface_check_parameters,                                       &
     311      module_interface_check_data_output_ts,                                   &
    309312      module_interface_check_data_output_pr,                                   &
    310313      module_interface_check_data_output,                                      &
     
    334337      MODULE PROCEDURE module_interface_check_parameters
    335338   END INTERFACE module_interface_check_parameters
     339
     340   INTERFACE module_interface_check_data_output_ts
     341      MODULE PROCEDURE module_interface_check_data_output_ts
     342   END INTERFACE module_interface_check_data_output_ts
    336343
    337344   INTERFACE module_interface_check_data_output_pr
     
    481488! Description:
    482489! ------------
     490!> Check module-specific data output of timeseries
     491!------------------------------------------------------------------------------!
     492SUBROUTINE module_interface_check_data_output_ts( dots_max, dots_num, dots_label, dots_unit )
     493
     494
     495   INTEGER(iwp),      INTENT(IN)    ::  dots_max !< variable output array index
     496   INTEGER(iwp),      INTENT(INOUT)    ::  dots_num !< variable output array index
     497   CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT) :: dots_label
     498   CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT) :: dots_unit
     499
     500
     501   IF ( radiation )  THEN
     502      CALL radiation_check_data_output_ts( dots_max, dots_num, dots_label, dots_unit )
     503   ENDIF
     504
     505   CALL user_check_data_output_ts( dots_max, dots_num, dots_label, dots_unit )
     506
     507
     508END SUBROUTINE module_interface_check_data_output_ts
     509
     510
     511!------------------------------------------------------------------------------!
     512! Description:
     513! ------------
    483514!> Check module-specific data output of profiles
    484515!------------------------------------------------------------------------------!
     
    522553   IF ( unit == 'illegal' )  THEN
    523554      unit = '' ! ToDo: Seems like a hack. Find a general soultion!
    524       CALL user_check_data_output_pr( variable, var_count, unit )
     555      CALL user_check_data_output_pr( variable, var_count, unit, dopr_unit )
    525556   ENDIF
    526557
  • palm/trunk/SOURCE/netcdf_interface_mod.f90

    r3665 r3700  
    673673        ONLY: lsm_define_netcdf_grid, nzb_soil, nzt_soil, nzs, zs
    674674
     675    USE user,                                                                  &
     676        ONLY:  user_define_netcdf_grid
     677
    675678    USE ocean_mod,                                                             &
    676679        ONLY:  ocean_define_netcdf_grid
  • palm/trunk/SOURCE/radiation_model_mod.f90

    r3685 r3700  
    11361136    END INTERFACE radiation_check_data_output
    11371137
     1138    INTERFACE radiation_check_data_output_ts
     1139       MODULE PROCEDURE radiation_check_data_output_ts
     1140    END INTERFACE radiation_check_data_output_ts
     1141
    11381142    INTERFACE radiation_check_data_output_pr
    11391143       MODULE PROCEDURE radiation_check_data_output_pr
     
    12411245!-- Public functions / NEEDS SORTING
    12421246    PUBLIC radiation_check_data_output, radiation_check_data_output_pr,        &
     1247           radiation_check_data_output_ts,                                     &
    12431248           radiation_check_parameters, radiation_control,                      &
    12441249           radiation_header, radiation_init, radiation_parin,                  &
     
    14481453
    14491454    END SUBROUTINE radiation_check_data_output
     1455
     1456
     1457!------------------------------------------------------------------------------!
     1458! Description:
     1459! ------------
     1460!> Set module-specific timeseries units and labels
     1461!------------------------------------------------------------------------------!
     1462 SUBROUTINE radiation_check_data_output_ts( dots_max, dots_num, dots_label, dots_unit )
     1463
     1464
     1465   INTEGER(iwp),      INTENT(IN)     ::  dots_max
     1466   INTEGER(iwp),      INTENT(INOUT)  ::  dots_num
     1467   CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT)  :: dots_label
     1468   CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT)  :: dots_unit
     1469
     1470!
     1471!-- Temporary solution to add LSM and radiation time series to the default
     1472!-- output
     1473    IF ( land_surface  .OR.  radiation )  THEN
     1474       IF ( TRIM( radiation_scheme ) == 'rrtmg' )  THEN
     1475          dots_num = dots_num + 15
     1476       ELSE
     1477          dots_num = dots_num + 11
     1478       ENDIF
     1479    ENDIF
     1480
     1481
     1482 END SUBROUTINE radiation_check_data_output_ts
    14501483
    14511484!------------------------------------------------------------------------------!
  • palm/trunk/SOURCE/user_init_land_surface.f90

    r3655 r3700  
    5858 
    5959
    60     USE control_parameters
    61    
    62     USE indices
    63    
    6460    USE kinds
    65    
     61
    6662    USE land_surface_model_mod
    6763
    68     USE netcdf_interface,                                                      &
    69         ONLY: dots_label, dots_unit, dots_num
    70    
    71     USE pegrid
    72 
    73     USE surface_mod   
    74 
    75     USE user
     64    USE surface_mod
    7665
    7766    IMPLICIT NONE
  • 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.