source: trunk/00FlowSolve_PL/PROJECTS/OIS_2D/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.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_subs_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( user_subs_flag == 'no' ) return
26
27#if DEBUG_LEVEL >= 1
28  if( myid==0) then
29     write(0,*) ' '
30     write(0,*) 'hello world from initialize_user'
31  endif
32#endif
33
34
35
36  !========================================================
37  !ENABLE VERTICALLY VARYING EDDY VISCOSITY AND DIFFUSIVITY
38  !
39  allocate( Km_of_z(locnz), Kt_of_z(locnz) )
40
41  call set_diffusion
42
43  !========================================================
44
45
46
47  if( restart_flag == 'yes' ) return
48
49  ! we can also specify any non-zero initial conditions
50
51
52  num_champ=3+num_scalars
53
54  allocate ( vals(nx,ny,locnz,num_champ) )
55
56  !! appel de user_ics pour definir la condition initiale
57  do ifield=1,num_champ
58     call user_ics( Grid(0)%x(:,1)*L_scale , Grid(0)%y(:)*L_scale , Grid(0)%z(1,:)*L_scale, &
59                    ifield , nx , ny , locnz, vals(:,:,:,ifield) ) 
60  enddo
61
62  !! Orientation de la grille pour U & W, affectation des champs vals(:,:,:,ifield)
63  do k=1,locnz                                                                                           
64     do i=1,nx
65        alpha1=Grid(0)%x_xi(i,k)
66        alpha2=Grid(0)%x_zeta(i,k)
67        alpha3=Grid(0)%z_xi(i,k)
68        alpha4=Grid(0)%z_zeta(i,k)
69        if ( i == 10 .and. k == 10 ) print*,'alpha1-4=',alpha1,alpha2,alpha3,alpha4
70        do j=1,ny
71           U(i,j,k)=1./( alpha1*alpha4-alpha3*alpha2 ) * (  alpha4*vals(i,j,k,1) - alpha2*vals(i,j,k,3) )
72           W(i,j,k)=1./( alpha1*alpha4-alpha3*alpha2 ) * ( -alpha3*vals(i,j,k,1) + alpha1*vals(i,j,k,3) )
73        enddo
74     enddo
75  enddo
76  V = vals(:,:,:,2)
77  s1= vals(:,:,:,4)
78  if ( num_scalars > 1 ) s2 = vals(:,:,:,5)
79
80  !! adimensionnement
81  U=U/U_scale
82  V=V/U_scale
83  W=W/U_scale
84  s1=s1/s1_scale
85  s2=s2/s2_scale
86
87  !! affichage des min/max a l'ecran
88  call maxim
89
90
91  deallocate( vals )
92
93end subroutine initialize_user
Note: See TracBrowser for help on using the repository browser.