Changeset 2938 for palm/trunk/SOURCE/netcdf_data_input_mod.f90
- Timestamp:
- Mar 27, 2018 3:52:42 PM (7 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/netcdf_data_input_mod.f90
r2930 r2938 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Initial read of geostrophic wind components from dynamic driver. 28 ! 29 ! 2773 2018-01-30 14:12:54Z suehring 27 30 ! Revise checks for surface_fraction. 28 31 ! … … 126 129 REAL(wp), DIMENSION(:), ALLOCATABLE :: zw_atmos !< vertical levels at w grid in dynamic input file 127 130 131 REAL(wp), DIMENSION(:,:), ALLOCATABLE :: ug !< domain-averaged geostrophic component 132 REAL(wp), DIMENSION(:,:), ALLOCATABLE :: vg !< domain-averaged geostrophic component 133 128 134 REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: u_left !< u-component at left boundary 129 135 REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: v_left !< v-component at left boundary … … 180 186 LOGICAL :: from_file_tsoil = .FALSE. !< flag indicating whether soil temperature is already initialized from file 181 187 LOGICAL :: from_file_u = .FALSE. !< flag indicating whether u is already initialized from file 188 LOGICAL :: from_file_ug = .FALSE. !< flag indicating whether ug is already initialized from file 182 189 LOGICAL :: from_file_v = .FALSE. !< flag indicating whether v is already initialized from file 183 LOGICAL :: from_file_w = .FALSE. !< flag indicating whether w is already initialized from file 190 LOGICAL :: from_file_vg = .FALSE. !< flag indicating whether ug is already initialized from file 191 LOGICAL :: from_file_w = .FALSE. !< flag indicating whether w is already initialized from file 192 184 193 185 194 REAL(wp) :: fill_msoil !< fill value for soil moisture … … 422 431 MODULE PROCEDURE get_variable_4d_real 423 432 END INTERFACE get_variable 433 434 INTERFACE get_variable_pr 435 MODULE PROCEDURE get_variable_pr 436 END INTERFACE get_variable_pr 424 437 425 438 INTERFACE get_attribute … … 2025 2038 ENDIF 2026 2039 ! 2027 !-- Read geostrophic wind components 2028 ! IF ( check_existence( var_names, 'ls_forcing_ug' ) ) THEN 2029 ! 2030 ! ENDIF 2031 ! IF ( check_existence( var_names, 'ls_forcing_vg' ) ) THEN 2032 ! 2033 ! ENDIF 2034 2040 !-- Read initial geostrophic wind components at 2041 !-- t = 0 (index 1 in file). 2042 IF ( check_existence( var_names, 'ls_forcing_ug' ) ) THEN 2043 ALLOCATE( init_3d%ug_init(nzb:nzt+1) ) 2044 CALL get_variable_pr( id_dynamic, 'ls_forcing_ug', 1, & 2045 init_3d%ug_init ) 2046 init_3d%from_file_ug = .TRUE. 2047 ELSE 2048 init_3d%from_file_ug = .FALSE. 2049 ENDIF 2050 IF ( check_existence( var_names, 'ls_forcing_vg' ) ) THEN 2051 ALLOCATE( init_3d%vg_init(nzb:nzt+1) ) 2052 CALL get_variable_pr( id_dynamic, 'ls_forcing_vg', 1, & 2053 init_3d%vg_init ) 2054 init_3d%from_file_vg = .TRUE. 2055 ELSE 2056 init_3d%from_file_vg = .FALSE. 2057 ENDIF 2035 2058 ! 2036 2059 !-- Read inital 3D data of u, v, w, pt and q, … … 2222 2245 !-- Read soil moisture 2223 2246 IF ( land_surface ) THEN 2247 2224 2248 IF ( check_existence( var_names, 'init_soil_m' ) ) THEN 2225 2249 ! … … 2240 2264 ! 2241 2265 !-- level-of-detail 2 - read 3D initialization data 2242 ELSEIF ( init_3d%lod_msoil == 2 ) THEN ! need to be corrected2266 ELSEIF ( init_3d%lod_msoil == 2 ) THEN 2243 2267 ALLOCATE ( init_3d%msoil(0:init_3d%nzs-1,nys:nyn,nxl:nxr) ) 2244 2268 DO i = nxl, nxr … … 2272 2296 ! 2273 2297 !-- level-of-detail 2 - read 3D initialization data 2274 ELSEIF ( init_3d%lod_tsoil == 2 ) THEN ! need to be corrected2298 ELSEIF ( init_3d%lod_tsoil == 2 ) THEN 2275 2299 ALLOCATE ( init_3d%tsoil(0:init_3d%nzs-1,nys:nyn,nxl:nxr) ) 2276 2300 DO i = nxl, nxr … … 2346 2370 2347 2371 USE control_parameters, & 2348 ONLY: force_bound_l, force_bound_n, force_bound_r, force_bound_s, & 2372 ONLY: bc_lr_cyc, bc_ns_cyc, force_bound_l, force_bound_n, & 2373 force_bound_r, force_bound_s, & 2349 2374 forcing, humidity, message_string, neutral, simulated_time 2375 2350 2376 2351 2377 USE indices, & … … 2430 2456 force%tind = MINLOC( ABS( force%time - simulated_time ), DIM = 1 )& 2431 2457 - 1 2432 force%tind_p = force%tind + 1 2458 force%tind_p = force%tind + 1 2459 ! 2460 !-- Read geostrophic wind components. In case of forcing, this is only 2461 !-- required if cyclic boundary conditions are applied. 2462 IF ( bc_lr_cyc .AND. bc_ns_cyc ) THEN 2463 DO t = force%tind, force%tind_p 2464 CALL get_variable_pr( id_dynamic, 'ls_forcing_ug', t+1, & 2465 force%ug(t-force%tind,:) ) 2466 CALL get_variable_pr( id_dynamic, 'ls_forcing_vg', t+1, & 2467 force%ug(t-force%tind,:) ) 2468 ENDDO 2469 ENDIF 2433 2470 ! 2434 2471 !-- Read data at lateral and top boundaries. Please note, at left and … … 3832 3869 END SUBROUTINE get_variable_1d_real 3833 3870 3871 3872 !------------------------------------------------------------------------------! 3873 ! Description: 3874 ! ------------ 3875 !> Reads a time-dependent 1D float variable from file. 3876 !------------------------------------------------------------------------------! 3877 SUBROUTINE get_variable_pr( id, variable_name, t, var ) 3878 #if defined( __netcdf ) 3879 3880 USE pegrid 3881 3882 IMPLICIT NONE 3883 3884 CHARACTER(LEN=*) :: variable_name !< variable name 3885 3886 INTEGER(iwp), INTENT(IN) :: id !< file id 3887 INTEGER(iwp), DIMENSION(1:2) :: id_dim !< dimension ids 3888 INTEGER(iwp) :: id_var !< dimension id 3889 INTEGER(iwp) :: n_file !< number of data-points in file along z dimension 3890 INTEGER(iwp), INTENT(IN) :: t !< timestep number 3891 3892 REAL(wp), DIMENSION(:), INTENT(INOUT) :: var !< variable to be read 3893 3894 ! 3895 !-- First, inquire variable ID 3896 nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var ) 3897 ! 3898 !-- Inquire dimension size of vertical dimension 3899 nc_stat = NF90_INQUIRE_VARIABLE( id, id_var, DIMIDS = id_dim ) 3900 nc_stat = NF90_INQUIRE_DIMENSION( id, id_dim(1), LEN = n_file ) 3901 ! 3902 !-- Read variable. 3903 nc_stat = NF90_GET_VAR( id, id_var, var, & 3904 start = (/ 1, t /), & 3905 count = (/ n_file, 1 /) ) 3906 CALL handle_error( 'get_variable_pr', 527 ) 3907 3908 #endif 3909 END SUBROUTINE get_variable_pr 3910 3911 3834 3912 !------------------------------------------------------------------------------! 3835 3913 ! Description:
Note: See TracChangeset
for help on using the changeset viewer.