63 TYPE(t_region
) :: region
68 INTEGER :: icont, ipatch, itile
71 CHARACTER(CHRLEN) :: rcsidentstring
73 INTEGER :: bctype, ncont, npatches, ntiles
74 INTEGER :: ivtilebeg, ivtileend
76 INTEGER :: ilev, n1, n2
79 REAL(RFREAL),
POINTER,
DIMENSION(:,:) :: pcv, pcvold, prhs, prhssum
81 TYPE(t_patch),
POINTER :: ppatch
87 rcsidentstring =
'$RCSfile: PLAG_InjcTileRKUpdate.F90,v $ $Revision: 1.5 $'
89 global => region%global
92 'PLAG_InjcTileRKUpdate.F90' )
97 ilev = region%currLevel
98 npatches = region%nPatches
101 npatches = region%grid%nPatches
103 ncont = region%plagInput%nCont
110 ppatch => region%levels(ilev)%patches(ipatch)
113 ppatch => region%patches(ipatch)
116 bctype = ppatch%bcType
121 IF ( (bctype >= bc_injection .AND. bctype <= bc_injection + bc_range) .OR. &
122 (bctype >= bc_inflow .AND. bctype <= bc_inflow + bc_range) )
THEN
124 IF ( (bctype >= bc_injection .AND. bctype <= bc_injection + bc_range) )
THEN
129 n1 = abs(ppatch%l1end -ppatch%l1beg ) + 1
130 n2 = abs(ppatch%l2end -ppatch%l2beg ) + 1
134 ntiles = ppatch%nBFaces
137 ptileplag => ppatch%tilePlag
140 pcvold => ptileplag%cvOld
141 prhs => ptileplag%rhs
142 prhssum => ptileplag%rhsSum
146 ivtilebeg = cv_tile_momnrm
147 ivtileend = cv_tile_last+ncont
150 ivtilebeg,ivtileend,pcv,pcvold,prhs,prhssum )
subroutine plag_injctilerkupdate(region, iStage)
subroutine registerfunction(global, funName, fileName)
subroutine rkupdategeneric(region, varType, iStage, icBeg, icEnd, ivBeg, ivEnd, cv, cvOld, rhs, rhsSum)
subroutine deregisterfunction(global)