Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
PERI_coCprInitSolutionFlo.F90
Go to the documentation of this file.
1 ! *********************************************************************
2 ! * Rocstar Simulation Suite *
3 ! * Copyright@2015, Illinois Rocstar LLC. All rights reserved. *
4 ! * *
5 ! * Illinois Rocstar LLC *
6 ! * Champaign, IL *
7 ! * www.illinoisrocstar.com *
8 ! * sales@illinoisrocstar.com *
9 ! * *
10 ! * License: See LICENSE file in top level of distribution package or *
11 ! * http://opensource.org/licenses/NCSA *
12 ! *********************************************************************
13 ! *********************************************************************
14 ! * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, *
15 ! * EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES *
16 ! * OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND *
17 ! * NONINFRINGEMENT. IN NO EVENT SHALL THE CONTRIBUTORS OR *
18 ! * COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER *
19 ! * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, *
20 ! * Arising FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE *
21 ! * USE OR OTHER DEALINGS WITH THE SOFTWARE. *
22 ! *********************************************************************
23 !******************************************************************************
24 !
25 ! Purpose: Initialisation of CPR solutions
26 !
27 ! Description: IF starts from t=0, set density and pressure as single values
28 ! as function of axial position using 1D compressible relations,
29 ! can be found in AIAA-86-1447 (Traineau, Hervat and Kuentsmann).
30 ! The remaining conservative variables are due to Taylor solution
31 ! which vary in injection normal direction.
32 ! IF restart from t/=0, read solution from main solution file
33 ! and cpr pressure gradient from specific cpr solution file.
34 !
35 ! Input: region = data of current region
36 !
37 ! Output: CPR solution to start simulation
38 !
39 ! Notes: none.
40 !
41 !******************************************************************************
42 !
43 ! $Id: PERI_coCprInitSolutionFlo.F90,v 1.3 2008/12/06 08:44:36 mtcampbe Exp $
44 !
45 ! Copyright: (c) 2001 by the University of Illinois
46 !
47 !******************************************************************************
48 
49 SUBROUTINE peri_cocprinitsolution( region )
50 
51  USE moddatatypes
52  USE moddatastruct, ONLY : t_region
53  USE modglobal, ONLY : t_global
55  USE moderror
56  USE modparameters
58  IMPLICIT NONE
59 
60 #include "Indexing.h"
61 
62 ! ... parameters
63  TYPE (t_region) :: region
64 
65 ! ... loop variables
66  INTEGER :: i, j, k, jr
67 
68 ! ... local variables
69  CHARACTER(CHRLEN) :: rcsidentstring
70  TYPE(t_global), POINTER :: global
71 
72  INTEGER :: ilev, ipcbeg, ipcend, jpcbeg, jpcend, kpcbeg, kpcend
73  INTEGER :: icoff, ijcoff, inoff, ijnoff, ijkc, ijkcr, ijkn, ijkn1
74  REAL(RFREAL), POINTER :: xyz(:,:), cv(:,:), dv(:,:)
75  REAL(RFREAL) :: pi, gamma, gogampls, delta, minj, mfrat, refmassflux
76  REAL(RFREAL) :: throatmflux, cpreps, headpres, headtemp, headsv, rgas
77  REAL(RFREAL) :: phi, mach, yp, ym, yc, dy, denom, choklen, hvinj
78  REAL(RFREAL) :: rho, pres, vm, eo
79 
80 !******************************************************************************
81 
82  rcsidentstring = '$RCSfile: PERI_coCprInitSolutionFlo.F90,v $ $Revision: 1.3 $'
83 
84  global => region%global
85  CALL registerfunction( global,'PERI_CoCprInitSolution',&
86  'PERI_coCprInitSolutionFlo.F90' )
87 
88 ! get parameters and pointers ----------------------------------------------
89 
90  ilev = region%currLevel
91  CALL rflo_getdimensphys( region,ilev,ipcbeg,ipcend, &
92  jpcbeg,jpcend,kpcbeg,kpcend )
93  CALL rflo_getcelloffset( region,ilev,icoff,ijcoff )
94  CALL rflo_getnodeoffset( region,ilev,inoff,ijnoff )
95 
96  xyz => region%levels(ilev)%grid%xyz
97  cv => region%levels(ilev)%mixt%cv
98  dv => region%levels(ilev)%mixt%dv
99 
100  pi = global%pi
101  rgas = 287._rfreal
102  gamma = global%refGamma
103  gogampls = gamma / (gamma + 1._rfreal)
104  cpreps = region%periInput%cprEpsilon
105  headpres = region%periInput%headPres
106  headtemp = region%periInput%headTemp
107  delta = global%refLength
108 write(*,*)global%currentTime
109  IF ((global%flowType==flow_unsteady .AND. &
110  global%currentTime < peri_real_small) .OR. &
111  (global%flowType==flow_steady .AND. global%currentIter==0)) THEN
112 
113 ! - first cleanup conservative variables cv
114  cv(:,:) = 0._rfreal
115 write(*,*)headpres,headtemp
116 ! - refMassFlux is the mass flux at the streamwise location x/h=1/cprEpsilon
117  minj = region%periInput%minjRate
118  refmassflux = region%periInput%bulkmFlux
119 
120 ! - bulk averaged mass flux corresponding to CPR sonic conditions
121  throatmflux = 2._rfreal*delta*gamma*headpres/ &
122  sqrt(2._rfreal*gogampls*rgas*headtemp)
123 
124 ! - non dimensinal distance head end to choking location L/h:
125  headsv = sqrt( gamma*rgas*headtemp )
126  denom = headsv*minj*sqrt( 2._rfreal*(gamma+1._rfreal) )
127  choklen = headpres*gamma/denom
128 
129 ! - mfRat is ratio of bulk mass flux to mass flux corresp. to sonic conditions
130  mfrat = refmassflux/throatmflux
131 
132 ! - or mfRat can be defined as axial coordinate normalized by choklen
133  mfrat = 1._rfreal/cpreps/choklen
134 
135 ! - compute nondimensional axial parameter phi defined as
136  phi = sqrt(1._rfreal - mfrat*mfrat)
137 
138 ! - pressure and density axial distribution
139  rho = 0.5_rfreal*headpres*(1._rfreal+phi)/(rgas*headtemp)
140  pres = (1.d0+gamma*phi)*headpres/(1._rfreal+gamma)
141  cv(cv_mixt_dens,:) = rho
142  dv(dv_mixt_pres,:) = pres
143  dv(dv_mixt_wvel,:) = 0._rfreal
144 
145 ! - mach number and head-end injection velocity
146  mach = sqrt((1._rfreal-phi)/(1._rfreal+gamma*phi))
147  hvinj= minj*rgas*headtemp/headpres
148 write(*,*)cv(cv_mixt_dens,1),dv(dv_mixt_pres,1),choklen,mach
149 write(*,*)mfrat,phi,mach,hvinj
150 
151  DO k = kpcbeg, kpcbeg
152  DO i = ipcbeg, ipcbeg
153  DO j = jpcbeg-region%nDumCells, jpcend+region%nDumCells
154  ijkc = indijk( i , j , k ,icoff,ijcoff)
155  jr = max( j, jpcbeg )
156  jr = min( jr,jpcend )
157  ijkn = indijk( i , jr , k ,inoff,ijnoff)
158  ijkn1 = indijk( i , jr+1, k ,inoff,ijnoff)
159  dy = xyz(ycoord,ijkn1)-xyz(ycoord,ijkn)
160  yp = xyz(ycoord,ijkn1)
161  ym = xyz(ycoord,ijkn)
162  yc = 0.5_rfreal*(xyz(ycoord,ijkn1)+xyz(ycoord,ijkn))
163  IF (dy < 0._rfreal) THEN
164  CALL errorstop( region%global,err_peri_geo,__line__, &
165  'grid contains negative spacing' )
166  ENDIF
167 
168 ! dv(DV_MIXT_UVEL,ijkC) = 0.5_RFREAL*pi*refMassFlux* &
169 ! (SIN(0.5_RFREAL*pi*yp/delta)- &
170 ! SIN(0.5_RFREAL*pi*ym/delta))/(pi*dy*rho)
171 ! dv(DV_MIXT_VVEL,ijkC) = cprEps*refMassFlux*(COS(0.5_RFREAL*pi*yp/ &
172 ! delta)-COS(0.5_RFREAL*pi*ym/delta))/(pi*dy*rho)
173 
174  dv(dv_mixt_uvel,ijkc) = minj/rho*0.5_rfreal*pi/cpreps* &
175  cos( 0.5_rfreal*pi*yc/delta )
176  dv(dv_mixt_vvel,ijkc) = -minj/rho*sin( 0.5_rfreal*pi*yc/delta )
177 
178  vm = sqrt( dv(dv_mixt_uvel,ijkc)*dv(dv_mixt_uvel,ijkc) + &
179  dv(dv_mixt_vvel,ijkc)*dv(dv_mixt_vvel,ijkc) + &
180  dv(dv_mixt_wvel,ijkc)*dv(dv_mixt_wvel,ijkc))
181  eo = mixtperf_eo_dgpvm(rho,gamma,pres,vm)
182  cv(cv_mixt_xmom,ijkc) = rho*dv(dv_mixt_uvel,ijkc)
183  cv(cv_mixt_ymom,ijkc) = rho*dv(dv_mixt_vvel,ijkc)
184  cv(cv_mixt_zmom,ijkc) = rho*dv(dv_mixt_wvel,ijkc)
185  cv(cv_mixt_ener,ijkc) = rho*eo
186  END DO
187  DO j = 1, region%nDumCells
188  ijkn = indijk( i , jpcbeg , k ,inoff,ijnoff)
189  ijkn1 = indijk( i , jpcend+1 , k ,inoff,ijnoff)
190  yp = xyz(ycoord,ijkn1)
191  ym = xyz(ycoord,ijkn)
192  ijkcr = indijk( i , jpcbeg+j-1, k ,icoff,ijcoff)
193  ijkc = indijk( i , jpcbeg-j , k ,icoff,ijcoff)
194  IF (ym == region%periInput%minmax(1)) THEN
195  cv(cv_mixt_xmom,ijkc) = -cv(cv_mixt_xmom,ijkcr)
196  ENDIF
197  ijkcr = indijk( i , jpcend-j+1, k ,icoff,ijcoff)
198  ijkc = indijk( i , jpcend+j , k ,icoff,ijcoff)
199  IF (yp == region%periInput%minmax(2)) THEN
200  cv(cv_mixt_xmom,ijkc) = -cv(cv_mixt_xmom,ijkcr)
201  ENDIF
202  END DO
203  END DO
204  END DO
205 
206  DO k = kpcbeg-region%nDumCells, kpcend+region%nDumCells
207  DO j = jpcbeg-region%nDumCells, jpcend+region%nDumCells
208  DO i = ipcbeg-region%nDumCells, ipcend+region%nDumCells
209  ijkc = indijk( i , j , k ,icoff,ijcoff)
210  ijkcr = indijk(ipcbeg, j ,kpcbeg ,icoff,ijcoff)
211  cv(cv_mixt_dens,ijkc) = cv(cv_mixt_dens,ijkcr)
212  cv(cv_mixt_xmom,ijkc) = cv(cv_mixt_xmom,ijkcr)
213  cv(cv_mixt_ymom,ijkc) = cv(cv_mixt_ymom,ijkcr)
214  cv(cv_mixt_zmom,ijkc) = cv(cv_mixt_zmom,ijkcr)
215  cv(cv_mixt_ener,ijkc) = cv(cv_mixt_ener,ijkcr)
216 !IF (i==ipcbeg.AND.k==kpcbeg) &
217 !write(*,*)j,cv(2,ijkC),cv(3,ijkC),cv(4,ijkC),cv(5,ijkC)
218 IF(j==1.AND.k==2) write(*,*)i,j,k,cv(1:5,ijkc)
219  END DO
220  END DO
221  END DO
222 
223  ELSE
224 
225 ! - previous pressure gradient is read from main solution file
226 
227  region%periInput%meanPgrad = global%moduleVar(1)
228  write(*,*) region%procId,' cprMeanPgrad ', region%periInput%meanPgrad
229 
230  ENDIF
231 
232 ! finalize --------------------------------------------------------
233 
234  CALL deregisterfunction( global )
235 
236 END SUBROUTINE peri_cocprinitsolution
237 
238 !******************************************************************************
239 !
240 ! RCS Revision history:
241 !
242 ! $Log: PERI_coCprInitSolutionFlo.F90,v $
243 ! Revision 1.3 2008/12/06 08:44:36 mtcampbe
244 ! Updated license.
245 !
246 ! Revision 1.2 2008/11/19 22:17:49 mtcampbe
247 ! Added Illinois Open Source License/Copyright
248 !
249 ! Revision 1.1 2004/06/08 23:56:56 wasistho
250 ! changed nomenclature
251 !
252 ! Revision 1.2 2003/05/15 02:57:05 jblazek
253 ! Inlined index function.
254 !
255 ! Revision 1.1.1.1 2003/03/29 03:36:30 wasistho
256 ! install ROCPERI
257 !
258 !
259 !
260 !******************************************************************************
261 
262 
263 
264 
265 
266 
267 
real(rfreal) function mixtperf_eo_dgpvm(D, G, P, Vm)
Definition: MixtPerf_E.F90:55
j indices k indices k
Definition: Indexing.h:6
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE kpcbeg
Vector_n max(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:354
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
double sqrt(double d)
Definition: double.h:73
subroutine peri_cocprinitsolution(region)
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE jpcbeg
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE ipcend
subroutine rflo_getnodeoffset(region, iLev, iNodeOffset, ijNodeOffset)
static const double pi
Definition: smooth_medial.C:43
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE ipcbeg
NT & sin
blockLoc i
Definition: read.cpp:79
subroutine rflo_getcelloffset(region, iLev, iCellOffset, ijCellOffset)
RT delta(int i) const
Definition: Direction_2.h:159
Vector_n min(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:346
j indices j
Definition: Indexing.h:6
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE jpcend
NT dy
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469
CGAL_BEGIN_NAMESPACE void const NT NT NT NT & denom
NT & cos
subroutine rflo_getdimensphys(region, iLev, ipcbeg, ipcend, jpcbeg, jpcend, kpcbeg, kpcend)