~ubuntu-branches/ubuntu/precise/code-saturne/precise

« back to all changes in this revision

Viewing changes to src/lagr/lageje.f90

  • Committer: Package Import Robot
  • Author(s): Sylvestre Ledru
  • Date: 2011-11-24 00:00:08 UTC
  • mfrom: (6.1.9 sid)
  • Revision ID: package-import@ubuntu.com-20111124000008-2vo99e38267942q5
Tags: 2.1.0-3
Install a missing file

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
!-------------------------------------------------------------------------------
 
2
 
 
3
! This file is part of Code_Saturne, a general-purpose CFD tool.
 
4
!
 
5
! Copyright (C) 1998-2011 EDF S.A.
 
6
!
 
7
! This program is free software; you can redistribute it and/or modify it under
 
8
! the terms of the GNU General Public License as published by the Free Software
 
9
! Foundation; either version 2 of the License, or (at your option) any later
 
10
! version.
 
11
!
 
12
! This program is distributed in the hope that it will be useful, but WITHOUT
 
13
! ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
 
14
! FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
 
15
! details.
 
16
!
 
17
! You should have received a copy of the GNU General Public License along with
 
18
! this program; if not, write to the Free Software Foundation, Inc., 51 Franklin
 
19
! Street, Fifth Floor, Boston, MA 02110-1301, USA.
 
20
 
 
21
!-------------------------------------------------------------------------------
 
22
 
 
23
subroutine lageje &
 
24
!================
 
25
 
 
26
 ( marko ,                                                        &
 
27
   tempf , depint,                                                &
 
28
   dtp   , tstruc , vstruc , lvisq ,                              &
 
29
   dx    , vvue   , vpart  , taup  , yplus ,                      &
 
30
   unif1 , unif2  , dintrf, gnorm, vnorm, grpn, piiln)
 
31
 
 
32
!===============================================================================
 
33
!
 
34
! Purpose:
 
35
! --------
 
36
!
 
37
!   Subroutine of the Lagrangian particle-tracking module:
 
38
!   ------------------------------------------------------
 
39
!
 
40
!
 
41
!   Deposition submodel:
 
42
!
 
43
!   Management of the ejection coherent structure (marko = 3)
 
44
!
 
45
!-------------------------------------------------------------------------------
 
46
! Arguments
 
47
!__________________.____._____.________________________________________________.
 
48
! name             !type!mode ! role                                           !
 
49
!__________________!____!_____!________________________________________________!
 
50
! marko            ! i  ! --> ! state of the jump process                      !
 
51
! tempf            ! r  ! <-- ! temperature of the fluid                       !
 
52
! depint           !  r ! <-- ! interface location near-wall/core-flow         !
 
53
! rpart            ! r  ! <-- ! particle radius                                !
 
54
! kdifcl           ! r  ! <-- ! internal zone diffusion coefficient            !
 
55
! dtp              ! r  ! <-- ! Lagrangian timestep                            !
 
56
! tstruc           ! r  ! <-- ! coherent structure mean duration               !
 
57
! vstruc           ! r  ! <-- ! coherent structure velocity                    !
 
58
! lvisq            ! r  ! <-- ! wall-unit lengthscale                          !
 
59
! dx               ! r  ! <-> ! wall-normal displacement                       !
 
60
! vpart            ! r  ! <-> ! particle wall-normal velocity                  !
 
61
! vvue             ! r  ! <-> ! wall-normal velocity of the flow seen          !
 
62
! taup             ! r  ! <-- ! particle relaxation time                       !
 
63
! yplus            ! r  ! <-- ! particle wall-normal normalized distance       !
 
64
! unif1            ! r  ! <-- ! random number (uniform law)                    !
 
65
! unif2            ! r  ! <-- ! random number (uniform law)                    !
 
66
! dintrf           ! r  ! <-- ! extern-intern interface location               !
 
67
! gnorm            ! r  ! <-- ! wall-normal gravity component                  !
 
68
! vnorm            ! r  ! <-- ! wall-normal fluid (Eulerian) velocity          !
 
69
! grpn             ! r  ! <-- ! wall-normal pressure gradient                  !
 
70
! piiln            ! r  ! <-- ! SDE integration auxiliary term                 !
 
71
!-------------------------------------------------------------------------------
 
72
!     Type: i (integer), r (real), s (string), a (array), l (logical),
 
73
!           and composite types (ex: ra real array)
 
74
!     mode: <-- input, --> output, <-> modifies data, --- work array
 
75
 
 
76
 
 
77
!===============================================================================
 
78
!     Module files
 
79
!===============================================================================
 
80
 
 
81
use cstnum
 
82
 
 
83
!===============================================================================
 
84
 
 
85
implicit none
 
86
 
 
87
! Arguments
 
88
 
 
89
integer marko
 
90
 
 
91
double precision tempf
 
92
double precision tstruc, vstruc
 
93
double precision dtp, lvisq
 
94
double precision vpart  , vvue  , dx
 
95
 
 
96
double precision unif1 , unif2 , dintrf, depint
 
97
double precision taup  , yplus, gnorm, vnorm, grpn, piiln
 
98
 
 
99
! Local variables
 
100
 
 
101
double precision vpart0 , vvue0 , ypaux
 
102
 
 
103
!===============================================================================
 
104
 
 
105
vvue0  = vvue
 
106
vpart0 = vpart
 
107
 
 
108
! Gravity and ormal fluid velocity added
 
109
 
 
110
vvue   =  -vstruc + gnorm*taup + vnorm
 
111
 
 
112
vpart  =  vpart0*exp(-dtp/taup)                                 &
 
113
        + (1-exp(-dtp/taup))*vvue0
 
114
 
 
115
dx     =  vvue0*dtp + vvue0                                     &
 
116
        * taup*(exp(-dtp/taup)-1)                               &
 
117
        + vpart0*taup*(1-exp(-dtp/taup))
 
118
 
 
119
ypaux = yplus - dx / lvisq
 
120
 
 
121
!---------------------------------------------------------
 
122
!    Dissociation of cases by the arrival position
 
123
!---------------------------------------------------------
 
124
 
 
125
if (ypaux.gt.depint) then
 
126
  marko = -2
 
127
elseif (ypaux.lt.dintrf) then
 
128
  marko =  0
 
129
else
 
130
  if (unif1 .lt. (dtp/tstruc) ) then
 
131
    marko = 12
 
132
  else
 
133
    marko = 3
 
134
  endif
 
135
endif
 
136
 
 
137
return
 
138
end subroutine