source: trunk/00FlowSolve_PL/PROJECTS/NEW_SRC/initialize_user.f90

Last change on this file was 11, checked in by xlvlod, 18 years ago

Import initial

File size: 2.5 KB
Line 
1subroutine initialize_user
2  !=======================================================
3#define DEBUG_LEVEL 3
4
5  use mpi_parameters      , only: comm,myid
6  use dependent_variables
7  use grid_info           , only: Grid 
8  use counters_flags_etc  , only: user_ics_flag,restart_flag,ierr 
9  use dimensional_scales  , only: L_scale,U_scale,s1_scale,s2_scale
10  use user_parameters     , only: Km_of_z,Kt_of_z 
11  use user_routines       , only: user_ics 
12
13  implicit none
14
15  include '../input/problem_size.h'
16  include 'mpif.h'
17
18  integer    :: i,j,k,ifield,num_champ
19  real       :: alpha1,alpha2,alpha3,alpha4,Lx,Ly,Lz
20  real,dimension(:,:,:,:),allocatable   :: vals
21
22
23  !=======================================================
24
25#if DEBUG_LEVEL >= 1
26  if( myid==0) then
27     write(0,*) ' '
28     write(0,*) 'hello world from initialize_user'
29  endif
30#endif
31
32
33  !========================================================
34  !ENABLE VERTICALLY VARYING EDDY VISCOSITY AND DIFFUSIVITY
35  !
36  allocate( Km_of_z(locnz), Kt_of_z(locnz) )
37
38  call set_diffusion
39
40  !========================================================
41
42
43
44  if( restart_flag == 'yes' .or. user_ics_flag == 'no' ) return
45
46  ! we can also specify any non-zero initial conditions
47  U =0.
48  V =0.
49  W =0.
50  s1=0.
51  s2=0.
52
53
54  num_champ=3+num_scalars
55
56  allocate ( vals(nx,ny,locnz,num_champ) )
57
58  !! appel de user_ics pour definir la condition initiale
59  do ifield=1,num_champ
60     call user_ics( Grid(0)%x(:,1)*L_scale , Grid(0)%y(:)*L_scale , Grid(0)%z(1,:)*L_scale, &
61                    ifield , nx , ny , locnz, vals(:,:,:,ifield) ) 
62  enddo
63
64  !! Orientation de la grille pour U & W, affectation des champs vals(:,:,:,ifield)
65  do k=1,locnz                                                                                           
66     do i=1,nx
67        alpha1=Grid(0)%x_xi(i,k)
68        alpha2=Grid(0)%x_zeta(i,k)
69        alpha3=Grid(0)%z_xi(i,k)
70        alpha4=Grid(0)%z_zeta(i,k)
71        if ( i == 10 .and. k == 10 ) print*,'alpha1-4=',alpha1,alpha2,alpha3,alpha4
72        do j=1,ny
73           U(i,j,k)=1./( alpha1*alpha4-alpha3*alpha2 ) * (  alpha4*vals(i,j,k,1) - alpha2*vals(i,j,k,3) )
74           W(i,j,k)=1./( alpha1*alpha4-alpha3*alpha2 ) * ( -alpha3*vals(i,j,k,1) + alpha1*vals(i,j,k,3) )
75        enddo
76     enddo
77  enddo
78  V = vals(:,:,:,2)
79  s1= vals(:,:,:,4)
80  if ( num_scalars > 1 ) s2 = vals(:,:,:,5)
81
82  !! adimensionnement
83  U=U/U_scale
84  V=V/U_scale
85  W=W/U_scale
86  s1=s1/s1_scale
87  s2=s2/s2_scale
88
89  !! affichage des min/max a l'ecran
90  call maxim
91
92
93  deallocate( vals )
94
95end subroutine initialize_user
Note: See TracBrowser for help on using the repository browser.