source: trunk/00FlowSolve_PL/SRC/initialize_user.f90 @ 2

Last change on this file since 2 was 2, checked in by xlvlod, 17 years ago

initial import from /home2/xlvlod/IDRIS/SVN_BASE_TRUNK

File size: 2.9 KB
Line 
1subroutine initialize_user
2#define DEBUG_LEVEL 3
3
4use mpi_parameters
5use user_parameters
6use dependent_variables
7use dimensional_scales
8use immersed_boundary
9use grid_info
10use counters_flags_etc
11
12use dimensional_scales
13use pde_parameters
14implicit none
15
16include '../input/problem_size.h'
17include 'mpif.h'
18
19real       :: xval,yval,zval,rho_total
20real       :: near_surface_window
21real       :: near_x1_window
22real       :: near_x0_window,window_scale
23
24if( user_subs_flag == 'no' ) return
25
26#if DEBUG_LEVEL >= 1
27 if( myid==0) then
28  write(0,*) ' '
29  write(0,*) ' '
30  write(0,*) 'hello world from initialize_user'
31  write(0,*) ' setting parameters for surface BCs'
32 endif
33#endif
34
35 x_0 = 600.
36 x_1 = 1200.            ! [m]   left ice/water interface
37!!! x_2 = x_1+200.        ! [m]   right ice/water interface
38 x_2 = x_1
39 V_0 = 0.40           ! [m/s] max ice speed at x_1
40 window_scale=5.0
41
42allocate( surface_V_of_x(nx) )
43
44! define surface velocity for sheared ice motion
45  do i=1,nx
46   xval = Grid(0)%x(i,1)*L_scale
47    if(xval >= x_0) then
48     near_x0_window = 1.0 - exp( -( (xval-x_0)/(window_scale) )**2  )  ! decay like gaussian w/ given scale
49    else
50     near_x0_window = 0.0
51    endif
52    if( xval >= x_1 ) then
53     near_x1_window = exp( -( (xval-x_1)/(window_scale) )**2  )  ! decay like gaussian w/ given scale
54    else
55     near_x1_window = 1.0
56    endif
57     surface_V_of_x(i) = -V_0*((xval-x_0)/x_1)*near_x1_window*near_x0_window/U_scale
58  enddo
59
60!========================================================
61!ENABLE VERTICALLY VARYING EDDY VISCOSITY AND DIFFUSIVITY
62!
63allocate( Km_of_z(locnz), Kt_of_z(locnz) )
64
65  call set_diffusion
66
67!========================================================
68
69if( restart_flag == 'yes' ) return
70!
71  print*,'nx=',nx,'  ny=',ny,'  locnz=',locnz
72! we can also specify any non-zero initial conditions
73! here if desired, I've just re-set zeros here to illustrate
74  do i=1,nx
75!!! xlv Quelle valeur pour k ? 
76!!!   xval = Grid(0)%x(i,k)*L_scale   ! dimensional x position
77!!!
78   do j=1,ny
79    yval = Grid(0)%y(j)*L_scale    ! dimensional y position
80     do k=1,locnz
81!!! xlv
82      xval = Grid(0)%x(i,k)*L_scale   ! dimensional x positio
83!!!     
84      zval = Grid(0)%z(i,k)*L_scale   ! dimensional z position
85
86      near_surface_window = exp( -( (zval-L_scale)/(5.0) )**2  )  ! decay like gaussian w/ 5m scale
87      v(i,j,k)= 0.0*surface_V_of_x(i)*near_surface_window
88      u(i,j,k)=0.0/U_scale
89      w(i,j,k)=0.0/U_scale
90
91!!!      s1(i,j,k)=0.0/s1_scale
92!!!      s2(i,j,k)=0.0/s2_scale
93      s1(i,j,k)=0.0
94      s2(i,j,k)=0.0
95
96!     Contravariant rather than cartesian components are actually needed
97!     I'm assuming a stretched but cartesian grid for this problem
98!     no transformations needed for v or pd
99      u(i,j,k) = u(i,j,k)/Grid(0)%x_xi(i,k)       ! u --> U
100      w(i,j,k) = w(i,j,k)/Grid(0)%z_zeta(i,k)     ! w --> W
101
102     enddo
103    enddo
104   enddo
105
106end subroutine initialize_user
Note: See TracBrowser for help on using the repository browser.