Skip to content
Snippets Groups Projects
Commit a36d4853 authored by Behrens, Prof. Dr. Jörn's avatar Behrens, Prof. Dr. Jörn
Browse files

minor changes in initialization

parent bef1078b
No related branches found
No related tags found
No related merge requests found
...@@ -203,10 +203,11 @@ ...@@ -203,10 +203,11 @@
REAL (KIND = GRID_SR), DIMENSION(GRID_dimension) :: r_tmp REAL (KIND = GRID_SR), DIMENSION(GRID_dimension) :: r_tmp
INTEGER :: i_count, i_num, i_alct INTEGER :: i_count, i_num, i_alct
REAL (KIND = GRID_SR), DIMENSION(:,:), ALLOCATABLE :: r_coo REAL (KIND = GRID_SR), DIMENSION(:,:), ALLOCATABLE :: r_coo
REAL (KIND = GRID_SR), DIMENSION(GRID_dimspherical) :: r_spher
!---------- calculate center ! CAUTION: THIS IS NOT IMPLEMENTED YET !!! !---------- calculate center ! CAUTION: THIS IS NOT IMPLEMENTED YET !!!
r_centr= grid_geokart(r_sentr) ! r_centr= grid_geokart(r_sentr)
!---------- allocate workspace !---------- allocate workspace
...@@ -232,7 +233,8 @@ ...@@ -232,7 +233,8 @@
!---------- loop over the nodes !---------- loop over the nodes
node_loop: DO i_count= 1, i_num node_loop: DO i_count= 1, i_num
r_array(i_count)= coshill(r_coo(:,i_count),r_centr) r_spher = grid_kartgeo(r_coo(:,i_count))
r_array(i_count)= coshill(r_spher, r_sentr)
END DO node_loop END DO node_loop
!---------- deallocate workspace !---------- deallocate workspace
...@@ -259,10 +261,11 @@ ...@@ -259,10 +261,11 @@
REAL (KIND = GRID_SR), DIMENSION(:,:), ALLOCATABLE :: r_aux REAL (KIND = GRID_SR), DIMENSION(:,:), ALLOCATABLE :: r_aux
REAL (KIND = GRID_SR), DIMENSION(:,:), ALLOCATABLE :: r_coo REAL (KIND = GRID_SR), DIMENSION(:,:), ALLOCATABLE :: r_coo
INTEGER (KIND = GRID_SI), DIMENSION(1) :: i_valind INTEGER (KIND = GRID_SI), DIMENSION(1) :: i_valind
REAL (KIND = GRID_SR), DIMENSION(GRID_dimspherical) :: r_spher
!---------- get center !---------- get center
r_centr= grid_geokart(r_sentr) ! r_centr= grid_geokart(r_sentr)
!---------- allocate workspace !---------- allocate workspace
...@@ -283,15 +286,16 @@ ...@@ -283,15 +286,16 @@
!---------- compute radii of initial ball-type cosine hill density... !---------- compute radii of initial ball-type cosine hill density...
! i_ind = max(4 - abs(floor(0.5*i_stcnumlayers)-i_lay),0) i_ind = max(4 - abs(floor(0.5*i_stcnumlayers)-i_lay),0)
! r_rds = (GRID_RADIUS/ 6.0)*i_ind/4 r_rds = (1.0/ 6.0)*i_ind/4
r_aux = 0. r_aux = 0.
IF ((i_lay .GE. 2) .AND. (i_lay .LE. i_stcnumlayers -2)) then IF ((i_lay .GE. 2) .AND. (i_lay .LE. i_stcnumlayers -2)) then
!---------- loop over the nodes !---------- loop over the nodes
node_loop: DO i_count= 1, i_num node_loop: DO i_count= 1, i_num
r_aux(1,i_count)= coshill(r_coo(:,i_count),r_centr, r_radius=r_rds) r_spher = grid_kartgeo(r_coo(:,i_count))
r_aux(1,i_count)= coshill(r_spher, r_sentr, r_radius=r_rds)
END DO node_loop END DO node_loop
END IF END IF
...@@ -314,14 +318,14 @@ ...@@ -314,14 +318,14 @@
!---------- local declarations !---------- local declarations
IMPLICIT NONE IMPLICIT NONE
REAL (KIND = GRID_SR), DIMENSION(GRID_dimension) :: r_coor REAL (KIND = GRID_SR), DIMENSION(GRID_dimspherical) :: r_coor
REAL (KIND = GRID_SR), DIMENSION(GRID_dimension) :: r_centr REAL (KIND = GRID_SR), DIMENSION(GRID_dimspherical) :: r_centr
REAL (KIND = GRID_SR), OPTIONAL :: r_radius REAL (KIND = GRID_SR), OPTIONAL :: r_radius
REAL (KIND = GRID_SR) :: r_hill REAL (KIND = GRID_SR) :: r_hill
REAL (KIND = GRID_SR) :: r_maxheight=1.0 REAL (KIND = GRID_SR) :: r_maxheight=1.0
REAL (KIND = GRID_SR) :: r_maxrad REAL (KIND = GRID_SR) :: r_maxrad
REAL (KIND = GRID_SR) :: r_dist, r_tmp REAL (KIND = GRID_SR) :: r_dist, r_tmp
REAL (KIND = GRID_SR), DIMENSION(GRID_dimension) :: r_xy REAL (KIND = GRID_SR), DIMENSION(GRID_dimspherical) :: r_xy
!---------- watch out for optional argument !---------- watch out for optional argument
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please to comment