My Project
Functions/Subroutines | Variables
mod_meanflow Module Reference

Functions/Subroutines

subroutine read_meanflow
 
subroutine set_bndry_meanflow
 
subroutine bcond_meanflow
 
subroutine bracket (TMAP, STIME, L1, L2, FACT, BACT, IERR)
 

Variables

integer mf_rst_stcnt
 
integer inmf
 
integer intcell
 
integer intnode
 
integer intelel
 
integer intuv
 
integer nmfcell_gl
 
integer nmfcell
 
integer nmfcell_i
 
integer, dimension(:), allocatable mf_gl2loc
 
integer, dimension(:), allocatable i_mfcell_gl
 
integer, dimension(:), allocatable i_mfcell_n
 
real(sp), dimension(:,:), allocatable dmfqdis
 
real(sp), dimension(:), allocatable mfqdis
 
real(sp), dimension(:,:), allocatable mfdist
 
real(sp), dimension(:), allocatable anglemf
 
real(sp), dimension(:), allocatable mfarea
 
real(sp), dimension(:), allocatable vlctymf
 
type(bc) mf_tm
 
real(sp), dimension(:,:), allocatable rdismf
 
integer, dimension(:,:), allocatable node_mfcell
 

Function/Subroutine Documentation

◆ bcond_meanflow()

subroutine mod_meanflow::bcond_meanflow ( )

Definition at line 208 of file mod_meanflow.f90.

208 !
209 !------------------------------------------------------------------------------!
210  USE all_vars
211  USE bcs
212  USE mod_obcs
213 
214  INTEGER L1,L2,IERR,II
215  REAL(SP) :: FACT,UFACT
216  REAL(SP) :: THOUR
217 
218  thour = dti*float(iint)/3600.0
219  IF(nmfcell > 0)THEN
220  CALL bracket(mf_tm,thour,l1,l2,fact,ufact,ierr)
221  mfqdis(:) = ufact*dmfqdis(:,l1) + fact*dmfqdis(:,l2)
222  mfqdis = mfqdis*ramp
223  END IF
224 
225  RETURN
real(sp) dti
Definition: mod_main.f90:844
integer(itime) iint
Definition: mod_main.f90:850
real(sp) ramp
Definition: mod_main.f90:845
Here is the call graph for this function:

◆ bracket()

subroutine mod_meanflow::bracket ( type(bc), intent(in)  TMAP,
real(sp), intent(in)  STIME,
integer, intent(out)  L1,
integer, intent(out)  L2,
real(sp), intent(out)  FACT,
real(sp), intent(out)  BACT,
integer, intent(out)  IERR 
)

Definition at line 229 of file mod_meanflow.f90.

229 !==============================================================================|
230 ! DETERMINE DATA INTERVAL IN WHICH CURRENT TIME LIES |
231 ! |
232 ! L1: DATA INTERVAL PROCEEDING TIME |
233 ! L2: DATA INTERVAL AFTER TIME |
234 ! FACT: LINEAR INTERPOLATION COEFFICIENT (0->1) |
235 ! FACT = .5 : STIME LIES EXACTLY BETWEEN TWO DATA TIMES |
236 ! FACT = 1. : STIME OCCURS AT SECOND DATA TIME |
237 ! BACT = 1.-FACT
238 ! IERR: RETURNS INTEGER ERROR |
239 ! IERR = 0 : NO ERROR, TIME IS BRACKETED BY DATA TIMES |
240 ! IERR =-1 : STIME PROCEEDS ALL DATA TIMES |
241 ! IERR = 1 : STIME IS GREATER THAN ALL DATA TIMES |
242 ! |
243 ! IF STIME PROCEEDS DATA, IERR IS SET TO -1, L1 TO 1, AND FACT TO 0. !
244 ! IF STIME SUPERCEEDS DATA, IERR IS SET TO -1, L2 TO LMAX, AND FACT TO 1. !
245 !==============================================================================|
246  USE mod_types
247  IMPLICIT NONE
248 !------------------------------------------------------------------------------!
249  TYPE(BC), INTENT(IN) :: TMAP
250  REAL(SP), INTENT(IN) :: STIME
251  INTEGER, INTENT(OUT) :: L1,L2
252  REAL(SP), INTENT(OUT) :: FACT,BACT
253  INTEGER, INTENT(OUT) :: IERR
254 !------------------------------------------------------------------------------!
255  REAL(SP) T1,T2
256  INTEGER I,NTMAX
257 !==============================================================================|
258 
259  ntmax = tmap%NTIMES
260  IF(stime < tmap%TIMES(1))THEN
261  fact = 0.0_sp
262  bact = 1.0_sp
263  l1 = 1
264  l2 = 1
265  ierr = -1
266  RETURN
267  END IF
268 
269  IF(stime > tmap%TIMES(ntmax))THEN
270  fact = 1.0_sp
271  bact = 0.0_sp
272  l1 = ntmax
273  l2 = ntmax
274  ierr = 1
275  RETURN
276  END IF
277 
278  IF(ntmax == 1)THEN
279  fact = 1.0_sp
280  bact = 0.0_sp
281  l1 = 1
282  l2 = 1
283  ierr = 0
284  RETURN
285  END IF
286 
287 
288  DO i=2,tmap%NTIMES
289  t1 = tmap%TIMES(i-1)
290  t2 = tmap%TIMES(i)
291  IF(stime >= t1 .AND. stime <= t2)THEN
292  l1 = i-1
293  l2 = i
294  ierr = 0
295  fact = (stime-t1)/(t2-t1)
296  bact = 1.0_sp-fact
297  END IF
298  END DO
299 
300 
301  RETURN
real(sp), dimension(:,:), allocatable, target t2
Definition: mod_main.f90:1314
real(sp), dimension(:,:), allocatable, target t1
Definition: mod_main.f90:1307
Here is the caller graph for this function:

◆ read_meanflow()

subroutine mod_meanflow::read_meanflow ( )

Definition at line 65 of file mod_meanflow.f90.

65 
66 !------------------------------------------------------------------------------!
67  INTEGER :: k,i,j,i1,i2,i3,ii,NCNT,itemp,IERR
68  INTEGER, ALLOCATABLE :: temp1(:),temp2(:)
69  REAL(SP),ALLOCATABLE :: RTEMP1(:,:),RTEMP2(:,:)
70  REAL(SP) :: ttemp
71 
72  rewind(inmf)
73  READ(inmf,*) nmfcell_gl
74 
75  nmfcell_i = 0
76  nmfcell = 0
77  IF (nmfcell_gl > 0) THEN
78 
79  ALLOCATE(i_mfcell_gl(nmfcell_gl))
80  DO i=1,nmfcell_gl
81  READ(inmf,*)i_mfcell_gl(i)
82  ENDDO
83 
84 !----Read in Mean Flow Flux Vertical Distribution---------------------
85  ALLOCATE(rtemp1(nmfcell_gl,kbm1))
86  DO i = 1, nmfcell_gl
87  READ(inmf,*) j,(rtemp1(i,k),k = 1,kbm1)
88  END DO
89 
90 !----Read in Time Dependent DataSets ---------------------------------
91  READ(inmf,*) itemp
92  mf_tm%NTIMES = itemp
93  mf_tm%LABEL = "open boundary mean flow flux"
94  ALLOCATE(mf_tm%TIMES(itemp))
95  ALLOCATE(rtemp2(nmfcell_gl,itemp))
96  DO i = 1, itemp
97  READ(inmf,*) ttemp
98  mf_tm%TIMES(i) = ttemp
99  READ(inmf,*) (rtemp2(j,i),j = 1,nmfcell_gl)
100 !--------------------------------Jianzhong----------------------------
101  IF(msr)WRITE(ipt,*)maxval(rtemp2(1:nmfcell_gl,i))&
102  &,maxloc(rtemp2(1:nmfcell_gl,i)) ,minval(rtemp2(1:nmfcell_gl,i))&
103  &,minloc(rtemp2(1:nmfcell_gl,i))
104 !---------------------------------------------------------------------
105  ! WRITE(IOPRT,*) ttemp
106  ! WRITE(IOPRT,*) (RTEMP2(J,I),J = 1,nmfcell_GL)
107  END DO
108  CLOSE(inmf)
109 
110 !
111 !---Map to Local Domain----------------------------------------
112 
113  IF(serial)THEN
114  nmfcell_i = nmfcell_gl
115  nmfcell = nmfcell_gl
116  ALLOCATE(i_mfcell_n(nmfcell))
117  i_mfcell_n = i_mfcell_gl
118  ALLOCATE(mfdist(nmfcell,kbm1))
119  mfdist = rtemp1
120  ALLOCATE(dmfqdis(nmfcell,mf_tm%NTIMES))
121  dmfqdis = rtemp2
122  END IF
123 
124 
125  DEALLOCATE(rtemp1,rtemp2)
126 
127  ELSE ! if statement end for nmfcell_GL > 0
128  close(inmf)
129  END IF
130 
131 !--------------------------------------Jianzhong----------------------
132  WRITE(ipt,*)'NMFCELL_I=',nmfcell_i,'NMFCELL=',nmfcell,'IN THREAD:',myid
133 !---------------------------------------------------------------------
134 
135  RETURN
logical serial
Definition: mod_main.f90:100
logical msr
Definition: mod_main.f90:101
integer myid
Definition: mod_main.f90:67
integer ipt
Definition: mod_main.f90:922
integer kbm1
Definition: mod_main.f90:65
Here is the caller graph for this function:

◆ set_bndry_meanflow()

subroutine mod_meanflow::set_bndry_meanflow ( )

Definition at line 145 of file mod_meanflow.f90.

145 
146 !------------------------------------------------------------------------------!
147 
148  USE bcs
149  USE mod_obcs
150 
151  IMPLICIT NONE
152  REAL(DP) DX12,DY12,ATMP1,HTMP
153  INTEGER I,J,I1,I2,J1,J2,II,ITMP,JTMP
154 !------------------------------------------------------------------------------!
155 
156  IF(nmfcell > 0)THEN
157 
158  ALLOCATE(anglemf(nmfcell),mfarea(nmfcell),vlctymf(nmfcell),mfqdis(nmfcell))
159  ALLOCATE(node_mfcell(nmfcell,2),rdismf(nmfcell,2))
160 
161  DO i=1,nmfcell
162  ii=i_mfcell_n(i)
163  IF(i <= nmfcell_i .and. isbce(ii) /= 2) THEN
164  print*, 'NO.',i,'MEAN FLOW CELL'
165  print*, 'IS NOT A OPEN BOUNDARY ONE'
166  CALL pstop
167  END IF
168  itmp=0
169  DO j=1,3
170  IF(nbe(ii,j) == 0 .and. isonb(nv(ii,j)) /= 2) THEN
171  jtmp=j
172  itmp=itmp+1
173  END IF
174  END DO
175  IF(itmp /= 1) THEN
176  print*, 'NO OPEN BOUNDARY OR MORE THAN ONE OPEN BOUNDARY'
177  print*, 'IN NO.',i,'MEAN FLOW CELL'
178  CALL pstop
179  END IF
180  j1=jtmp+1-int((jtmp+1)/4)*3
181  j2=jtmp+2-int((jtmp+2)/4)*3
182  i1=nv(ii,j1)
183  i2=nv(ii,j2)
184 
185  node_mfcell(i,1)=i1
186  node_mfcell(i,2)=i2
187 
188  htmp=0.5_sp*(h(i1)+h(i2)) ! may be a problem here, should be replaced dy D
189  dy12=vy(i1)-vy(i2)
190  dx12=vx(i1)-vx(i2)
191  atmp1=atan2(dy12,dx12)
192  mfarea(i)=sqrt(dx12**2+dy12**2)*htmp ! for spherical coordinates is Phthagolean Theorem still valid?
193  anglemf(i)=atmp1+3.1415927/2.0
194  rdismf(i,1)=art1(i1)/(art1(i1)+art1(i2))
195  rdismf(i,2)=art1(i2)/(art1(i1)+art1(i2))
196  END DO
197  END IF
198 
199  RETURN
real(sp), dimension(:), allocatable, target h
Definition: mod_main.f90:1131
real(sp), dimension(:), allocatable, target art1
Definition: mod_main.f90:1010
real(sp), dimension(:), allocatable, target vx
Definition: mod_main.f90:1001
subroutine pstop
Definition: mod_utils.f90:273
real(sp), dimension(:), allocatable, target vy
Definition: mod_main.f90:1002
integer, dimension(:,:), allocatable, target nbe
Definition: mod_main.f90:1020
integer, dimension(:,:), allocatable, target nv
Definition: mod_main.f90:1018
integer, dimension(:), allocatable, target isbce
Definition: mod_main.f90:1027
integer, dimension(:), allocatable, target isonb
Definition: mod_main.f90:1024
Here is the caller graph for this function:

Variable Documentation

◆ anglemf

real(sp), dimension(:), allocatable mod_meanflow::anglemf

Definition at line 52 of file mod_meanflow.f90.

52  REAL(SP),ALLOCATABLE :: ANGLEMF(:),MFAREA(:),VLCTYMF(:)

◆ dmfqdis

real(sp), dimension(:,:), allocatable mod_meanflow::dmfqdis

Definition at line 51 of file mod_meanflow.f90.

51  REAL(SP),ALLOCATABLE :: DMFQDIS(:,:),MFQDIS(:),MFDIST(:,:)

◆ i_mfcell_gl

integer, dimension(:), allocatable mod_meanflow::i_mfcell_gl

Definition at line 50 of file mod_meanflow.f90.

50  INTEGER, ALLOCATABLE :: I_MFCELL_GL(:),I_MFCELL_N(:)

◆ i_mfcell_n

integer, dimension(:), allocatable mod_meanflow::i_mfcell_n

Definition at line 50 of file mod_meanflow.f90.

◆ inmf

integer mod_meanflow::inmf

Definition at line 47 of file mod_meanflow.f90.

47  INTEGER :: INMF,INTCELL,INTNODE,INTELEL,INTUV

◆ intcell

integer mod_meanflow::intcell

Definition at line 47 of file mod_meanflow.f90.

◆ intelel

integer mod_meanflow::intelel

Definition at line 47 of file mod_meanflow.f90.

◆ intnode

integer mod_meanflow::intnode

Definition at line 47 of file mod_meanflow.f90.

◆ intuv

integer mod_meanflow::intuv

Definition at line 47 of file mod_meanflow.f90.

◆ mf_gl2loc

integer, dimension(:), allocatable mod_meanflow::mf_gl2loc

Definition at line 49 of file mod_meanflow.f90.

49  INTEGER, ALLOCATABLE :: MF_GL2LOC(:)

◆ mf_rst_stcnt

integer mod_meanflow::mf_rst_stcnt

Definition at line 46 of file mod_meanflow.f90.

46  INTEGER :: MF_RST_STCNT

◆ mf_tm

type(bc) mod_meanflow::mf_tm

Definition at line 53 of file mod_meanflow.f90.

53  TYPE(BC) :: MF_TM !!TIME MAP FOR MEAN FLOW DATA

◆ mfarea

real(sp), dimension(:), allocatable mod_meanflow::mfarea

Definition at line 52 of file mod_meanflow.f90.

◆ mfdist

real(sp), dimension(:,:), allocatable mod_meanflow::mfdist

Definition at line 51 of file mod_meanflow.f90.

◆ mfqdis

real(sp), dimension(:), allocatable mod_meanflow::mfqdis

Definition at line 51 of file mod_meanflow.f90.

◆ nmfcell

integer mod_meanflow::nmfcell

Definition at line 48 of file mod_meanflow.f90.

◆ nmfcell_gl

integer mod_meanflow::nmfcell_gl

Definition at line 48 of file mod_meanflow.f90.

48  INTEGER :: nmfcell_GL, nmfcell, nmfcell_i

◆ nmfcell_i

integer mod_meanflow::nmfcell_i

Definition at line 48 of file mod_meanflow.f90.

◆ node_mfcell

integer, dimension(:,:), allocatable mod_meanflow::node_mfcell

Definition at line 55 of file mod_meanflow.f90.

55  INTEGER ,ALLOCATABLE :: NODE_MFCELL(:,:)

◆ rdismf

real(sp), dimension(:,:), allocatable mod_meanflow::rdismf

Definition at line 54 of file mod_meanflow.f90.

54  REAL(SP),ALLOCATABLE :: RDISMF(:,:)

◆ vlctymf

real(sp), dimension(:), allocatable mod_meanflow::vlctymf

Definition at line 52 of file mod_meanflow.f90.