source: trunk/SpectralModelF90/PROJECTS/SIMU_ASARO/TEST2/user_module.f90 @ 2

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

initial import from /home2/xlvlod/IDRIS/SVN_BASE_TRUNK

File size: 7.7 KB
Line 
1module user_module   
2!! Routines to prescribe ics and forcing
3!! as functions of space/time
4!! flow_solve will include user_module.
5 public  :: user_defined_ics         
6 public  :: user_defined_forcing 
7   
8!!defns of background scalar profiles
9!!s1_bar(z), s2_bar(z)
10 public  :: eval_s1_bar
11 public  :: eval_s2_bar
12       
13 contains
14
15!===========================================================================
16    subroutine user_defined_ics(x,y,z,Lx,Ly,Lz, &
17                                u,v,w,s1,s2,f,beta,U0,  &
18                                g,rho_0,DGRAD)
19!
20!     inputs
21!      x,y,z     position in spatial domain            [m]
22!      Lx,Ly,Lz  domain lengths in x,y,z               [m]
23!      f         Coriolis param (set in problem_params)[1/s]
24!      g         gravity                 ""            [m/s2]
25!      rho_0     reference fluid density ""            [kg/m3]
26!      DGRAD     characteristic density gradient  ""   [kg/m4]
27!
28!     outputs
29!      u,v,w     speeds in x,y,z directions at (x,y,z)     [m/s]
30!      s1        e.g. could be perturbation temperature in [deg C]
31!      s2        e.g. could be perturbation salinity in    [psu]
32!
33!     note:
34!      s1 and s2 are defined relative to the ambient profiles
35!      s1_bar and s2_bar defined in the routines eval_s1_bar
36!      and eval_s2_bar below. There are corresponding quantities
37!      rho_bar and perturbation density pd that are computed
38!      via the eqn of state (routine eos) and used internally
39!      to compute buoyancy forces. They need not be set here.
40
41      implicit none
42      real(kind=8)          :: x,y,z,Lx,Ly,Lz,u,v,w,s1,s2
43      real(kind=8)          :: f,beta,g,rho_0,DGRAD,pi,fx,U0
44!===================================================================
45!       user declares any additional LOCAL variables needed here
46      real(kind=8)                      :: arg,c11,c12,c21,c22,omega_ics
47      real(kind=8)                      :: A_ics,k_ics,l_ics,m_ics,N2_ics,omega2
48
49!===================================================================
50! Example:
51! Initial conditions are a snapshot of an internal wave
52! in a uniform density stratification. I've got the scalars
53! set to "density" and "passive tracer". The ambient density
54! gradient (actually its absolute value) is a user specified
55! parameter in problem_params. Its value is made available
56! here in case it is needed. (Also f,g,rho_0)
57
58       u=0.
59       v=0.
60       w=0.
61       s1=0.
62       s2=0.
63
64       return
65      end subroutine user_defined_ics
66
67     
68 !===============================================================================     
69      subroutine user_defined_forcing(x,y,z,t,F1,F2,F3,F4,F5,  &
70                                      Lx,Ly,Lz,f,istep,iend_storm)
71!     User defined subroutine to add time/space dependent forcing to the
72!     equations of motion. Inputs and outputs for this routine are all in
73!     dimensional units.
74!
75
76!     inputs:
77!      x,y,z     spatial location at which forcing is to be defined, [m]
78!      t         time at which forcing is to be defined              [s]
79!      f,g,rho_0 Coriolis parameter, gravity, reference density [1/s,m/s2,kg/m3]
80
81!     outputs:
82!      F1-3      acceleration at x,y,z & t in x,y,z directions       [m/s2]
83!      F4        rhs of perturbation scalar (s1) eqn                 [(deg C)/s]
84!      F5        rhs of perturbation scalar (s2) eqn                 [(psu)/s]
85!                careful with F4,F5 you must take into account what you are
86!                using for eval_s1_bar & eval_s2_bar when you define this term
87!===============================================================================
88
89      implicit none
90      integer           ::  istep,iend_storm
91      real(kind=8)      ::  x,y,z
92      real(kind=8)      ::  u,v,w,s1,s2,F1,F2,F3,F4,F5
93      real(kind=8)      ::  t,Lx,Ly,Lz,f,g,rho_0
94
95!      real(kind=8),dimension(:),intent(in)      ::  x,y,z
96!      real(kind=8),dimension(:,:),intent(in)      ::  u,v,w,s1,s2
97!      real(kind=8)      ::  Lx,Ly,Lz,f,g,rho_0
98
99!!      local variable
100      real(kind=8)      ::   A_ics,xfreq,arg,sigma1,sigma2,FF,GG
101 
102      if ( istep .le. iend_storm ) then
103
104!=================FORCAGE XLV======= 
105!#      if ( x == 0. .and. z == 0. .and. y == 0. ) then
106        print*,'========='
107        print*,' Forcage, istep=',istep
108        print*,'========='
109!#      endif
110
111       A_ics=100.                                     ! displacement [m]
112       xfreq=1.2
113       arg= xfreq*f*t  ! generally -omega_ics*t but set t=0,
114       sigma1=20000.
115       sigma2=100.
116       FF=exp((-((x+Lx/2)**2))/(sigma1**2))
117       GG=exp((-((Lz/2-z)**2))/(sigma2**2))
118
119!     Define rhs values for evolution equations
120       s1=0.
121       s2=0.
122       w = 0.
123       u = -A_ics*xfreq*xfreq*f*f*sin(arg)*FF*GG          ! du/dt
124       v = 0.
125!===================================
126
127      else
128
129      F1= 0.
130      F2= 0.
131      F3= 0.
132      F4= 0.
133      F5= 0.
134
135      endif
136
137      return
138     end subroutine user_defined_forcing
139!============================================================================
140
141
142!============================================================================
143subroutine initialize_particles( positions,npts,Lx,Ly,Lz )
144     use Ziggurat
145   
146     implicit none
147     integer,  parameter  ::  DP=SELECTED_REAL_KIND( 12, 60 )
148     integer        :: npts,i,j            !! the number of particles
149     integer        :: myid,ierr 
150     real(kind=8)   :: positions(npts,3)   !! initial particle positions [m]
151     real(kind=8)   :: Lx,Ly,Lz            !! domain size in [m]
152     real(DP)       :: urv(3),L(3)         !! uniform random deviates in [0,1]
153     include 'mpif.h'
154     
155     !!   call zigset( iseed ) executed once during initialization
156     !!   rnor( ),rexp() also available
157     
158     call mpi_comm_rank (MPI_COMM_WORLD,myid,ierr)
159     
160     L(:)=(/Lx,Ly,Lz/)
161     do i=1,npts
162      do j=1,3
163       urv(j) = uni( )
164       positions(i,j)=L(j)*urv(j)
165      enddo
166     if(myid==0) write(0,*) i,positions(i,:)/Lz
167     enddo
168     
169   end subroutine initialize_particles
170!============================================================================   
171   
172   
173   
174!=============================================================================     
175      subroutine eval_s1_bar(z,Lz,s1_bar,s1_bar_z,s1_bar_zz) 
176!      input
177!      z            vertical z spatial position  [m]
178!      Lz           vertical size of computational domain [m]
179!
180!     output
181!      s1_bar, s1_bar_z, s1_bar_zz
182!      scalar concentration and z derivs   [dimensional units]
183
184      implicit none
185      real(kind=8) s1_bar,s1_bar_z,s1_bar_zz,z,Lz,dTdz,s1_min
186
187!     LOCAL variables: you may need some intermediate variables,
188!                      these need to be explicitly declared here
189      real(kind=8)   :: DTdz = 2.1e-3
190      real(kind=8)   :: s1_min = 15.0
191     
192! xlv
193      s1_bar    = s1_min + DTdz * z ! s1--> perturbation density [kg/m3]
194      s1_bar_z  = dTdz            ! d/dz s1_bar  [kg/m4]
195      s1_bar_zz = 0.0               ! dzz s1_bar  [kg/m5]
196 
197
198      return
199      end subroutine eval_s1_bar
200!=========================================================================
201
202
203         subroutine eval_s2_bar(z,Lz,s2_bar,s2_bar_z,s2_bar_zz) 
204!      input
205!      z            vertical z spatial position  [m]
206!      Lz           vertical size of computational domain [m]
207!           
208!     output
209!      s2_bar, s2_bar_z, s2_bar_zz
210!      scalar concentration and z derivs   [dimensional units]
211
212      implicit none
213      real(kind=8) s2_bar,s2_bar_z,s2_bar_zz,z,Lz
214!     LOCAL variables: you may need some intermediate variables,
215!                      these need to be explicitly declared here
216      real(kind=8)   :: s2_max=35.d0
217 
218
219          s2_bar = s2_max
220          s2_bar_z = 0.0
221          s2_bar_zz = 0.0       !     dzz s2_bar   [1/m2]
222
223      return
224     end subroutine eval_s2_bar
225
226
227
228end module user_module
Note: See TracBrowser for help on using the repository browser.