Changeset 3801 for palm/trunk/UTIL/inifor/src/inifor_grid.f90
- Timestamp:
- Mar 15, 2019 5:14:25 PM (6 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/UTIL/inifor/src/inifor_grid.f90
r3785 r3801 26 26 ! ----------------- 27 27 ! $Id$ 28 ! Read COSMO rotated pole from HHL file 29 ! Check for PALM and averaging domains extending outside COSMO domain 30 ! 31 ! 3785 2019-03-06 10:41:14Z eckhard 28 32 ! Assigned names to averaging grids 29 33 ! Improved variable naming and minor clean-up … … 129 133 RHO_L, OMEGA, HECTO 130 134 USE inifor_io, & 131 ONLY: get_ netcdf_attribute, get_netcdf_dim_vector,&135 ONLY: get_cosmo_grid, get_netcdf_attribute, get_netcdf_dim_vector, & 132 136 get_netcdf_variable, parse_command_line_arguments, & 133 137 get_input_file_list, validate_config … … 195 199 REAL(dp) :: latmin_palm = 0.0_dp !< Minimunm latitude of PALM grid [COSMO rotated-pole rad] 196 200 REAL(dp) :: latmax_palm = 0.0_dp !< Maximum latitude of PALM grid [COSMO rotated-pole rad] 201 REAL(dp) :: lonmin_tot = 0.0_dp !< Minimunm longitude of required COSMO data [COSMO rotated-pole rad] 202 REAL(dp) :: lonmax_tot = 0.0_dp !< Maximum longitude of required COSMO data [COSMO rotated-pole rad] 203 REAL(dp) :: latmin_tot = 0.0_dp !< Minimunm latitude of required COSMO data [COSMO rotated-pole rad] 204 REAL(dp) :: latmax_tot = 0.0_dp !< Maximum latitude of required COSMO data [COSMO rotated-pole rad] 197 205 REAL(dp) :: latitude = 0.0_dp !< geographical latitude of the PALM-4U origin, from inipar namelist [deg] 198 206 REAL(dp) :: longitude = 0.0_dp !< geographical longitude of the PALM-4U origin, from inipar namelist [deg] … … 242 250 LOGICAL :: ls_forcing_variables_required !< flag controlling whether large-scale forcing variables are to be computed 243 251 LOGICAL :: surface_forcing_required !< flag controlling whether surface forcing variables are to be computed 252 LOGICAL :: palm_domain_outside_cosmo !< indicates whether COSMO grid covers the PALM domain and the geostrophic averaging domains 244 253 245 254 TYPE(nc_var), ALLOCATABLE, TARGET :: input_var_table(:) !< table of input variables 246 255 TYPE(nc_var), ALLOCATABLE, TARGET :: output_var_table(:) !< table of input variables 247 TYPE(nc_var) :: cosmo_var!< COSMO dummy variable, used for reading HHL, rlon, rlat256 TYPE(nc_var) :: cosmo_var !< COSMO dummy variable, used for reading HHL, rlon, rlat 248 257 249 258 TYPE(grid_definition), TARGET :: palm_grid !< PALM-4U grid in the target system (COSMO-DE rotated-pole) … … 356 365 357 366 ! 358 !-- COSMO-DE and -D2 rotated pole position359 phi_n = 40.0_dp * TO_RADIANS360 phi_equat = 50.0_dp * TO_RADIANS361 lambda_n = -170.0_dp * TO_RADIANS362 363 !364 367 !-- Defaultmain centre (_c) of the PALM-4U grid in the geographical system (_g) 365 368 origin_lat = 52.325079_dp * TO_RADIANS ! south-west of Berlin, origin used for the Dec 2017 showcase simulation … … 531 534 CALL report('setup_parameters', message) 532 535 533 !534 !-- Read in COSMO heights of half layers (vertical cell faces)535 cosmo_var % name = 'HHL'536 CALL get_netcdf_variable(cfg % hhl_file, cosmo_var, hhl)537 CALL get_netcdf_dim_vector(cfg % hhl_file, 'rlon', rlon)538 CALL get_netcdf_dim_vector(cfg % hhl_file, 'rlat', rlat)539 CALL get_netcdf_dim_vector(soil_files(1), 'depth_2', depths)540 536 CALL run_control('time', 'read') 541 537 542 CALL reverse(hhl) 543 nlon = SIZE(hhl, 1) 544 nlat = SIZE(hhl, 2) 545 nlev = SIZE(hhl, 3) 546 ndepths = SIZE(depths) 547 548 lonmin_cosmo = MINVAL(rlon) * TO_RADIANS 549 lonmax_cosmo = MAXVAL(rlon) * TO_RADIANS 550 latmin_cosmo = MINVAL(rlat) * TO_RADIANS 551 latmax_cosmo = MAXVAL(rlat) * TO_RADIANS 552 CALL run_control('time', 'comp') 553 554 ! 555 !-- Appoximate COSMO-DE heights of full layers (cell centres) 556 ALLOCATE( hfl(nlon, nlat, nlev-1) ) 557 ALLOCATE( d_depth(ndepths), d_depth_rho_inv(ndepths) ) 558 559 CALL run_control('time', 'alloc') 560 CALL get_soil_layer_thickness( depths, d_depth ) 561 d_depth_rho_inv = 1.0_dp / ( d_depth * RHO_L ) 562 563 ! 564 !-- Appoximate COSMO-DE heights of full layers (cell centres) 565 DO k = 1, nlev-1 566 hfl(:,:,k) = 0.5_dp * ( hhl(:,:,k) + & 567 hhl(:,:,k+1) ) 568 ENDDO 569 CALL run_control('time', 'comp') 570 538 CALL get_cosmo_grid( cfg, soil_files(1), rlon, rlat, hhl, hfl, depths, & 539 d_depth, d_depth_rho_inv, phi_n, lambda_n, & 540 phi_equat, & 541 lonmin_cosmo, lonmax_cosmo, & 542 latmin_cosmo, latmax_cosmo, & 543 nlon, nlat, nlev, ndepths ) 571 544 572 545 … … 680 653 averaging_width_ns = averaging_angle * EARTH_RADIUS 681 654 655 lonmin_tot = MIN(lam_centre - averaging_angle, lonmin_palm) 656 lonmax_tot = MAX(lam_centre + averaging_angle, lonmax_palm) 657 latmin_tot = MIN(phi_centre - averaging_angle, latmin_palm) 658 latmax_tot = MAX(phi_centre + averaging_angle, latmax_palm) 659 660 palm_domain_outside_cosmo = ANY( & 661 (/ lonmin_tot, -lonmax_tot, latmin_tot, -latmax_tot/) .LT. & 662 (/ lonmin_cosmo, -lonmax_cosmo, latmin_cosmo, -latmax_cosmo/) & 663 ) 664 665 IF ( palm_domain_outside_cosmo ) THEN 666 message = 'PALM domain or geostrophic averaging domains extend ' // & 667 'outside COSMO domain.' 668 CALL inifor_abort( 'setup_parameters', message ) 669 ENDIF 670 671 682 672 ! 683 673 !-- Coriolis parameter … … 686 676 phi_n * TO_DEGREES, & 687 677 gam * TO_DEGREES ) & 688 678 ) 689 679 690 680 END SUBROUTINE setup_parameters … … 694 684 ! Description: 695 685 ! ------------ 696 !> Defines the COSMO, PALM-4U, PALM-4U boundary grids, in part ucular their686 !> Defines the COSMO, PALM-4U, PALM-4U boundary grids, in particular their 697 687 !> coordinates and interpolation weights 698 688 !------------------------------------------------------------------------------! … … 1104 1094 latmin = phi_south, latmax = phi_north, & 1105 1095 kind='scalar', name='east geostrophic scalar') 1096 1106 1097 1107 1098 ! … … 4079 4070 4080 4071 4081 !------------------------------------------------------------------------------!4082 ! Description:4083 ! ------------4084 !> Fills the thickness array of the COSMO soil layers. Since COSMO's (i.e.4085 !> TERRA_ML's [1]) soil layer boundaries follow the rule4086 !>4087 !> depth(0) = 0.0, and4088 !> depth(k) = 0.01 * 3**(k-1), k in [1,2,3,...,7]4089 !>4090 !> and full levels are defined as the midpoints between two layer boundaries,4091 !> all except the first layer thicknesses equal the depth of the midpoint.4092 !>4093 !> [1] A Description of the Nonhydrostatic Regional COSMO Model Part II :4094 !> Physical Parameterization*, Sect. 11 TERRA_ML.4095 !> http://www.cosmo-model.org/content/model/documentation/core/cosmoPhysParamtr.pdf)4096 !>4097 !> Input parameters:4098 !> -----------------4099 !>4100 !> depths: array of full soil layer depths (cell midpoints)4101 !>4102 !>4103 !> Output parameters:4104 !> ------------------4105 !>4106 !> d_depth: array of soil layer thicknesses4107 !>4108 !------------------------------------------------------------------------------!4109 SUBROUTINE get_soil_layer_thickness(depths, d_depth)4110 4111 REAL(dp), INTENT(IN) :: depths(:)4112 REAL(dp), INTENT(OUT) :: d_depth(:)4113 4114 d_depth(:) = depths(:)4115 d_depth(1) = 2.0_dp * depths(1)4116 4117 END SUBROUTINE get_soil_layer_thickness4118 4119 4072 END MODULE inifor_grid 4120 4073 #endif
Note: See TracChangeset
for help on using the changeset viewer.