forked from xcompact3d/Incompact3d
-
Notifications
You must be signed in to change notification settings - Fork 1
/
Copy pathCase-ABL.f90
1257 lines (1097 loc) · 40.6 KB
/
Case-ABL.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
894
895
896
897
898
899
900
901
902
903
904
905
906
907
908
909
910
911
912
913
914
915
916
917
918
919
920
921
922
923
924
925
926
927
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
944
945
946
947
948
949
950
951
952
953
954
955
956
957
958
959
960
961
962
963
964
965
966
967
968
969
970
971
972
973
974
975
976
977
978
979
980
981
982
983
984
985
986
987
988
989
990
991
992
993
994
995
996
997
998
999
1000
!Copyright (c) 2012-2022, Xcompact3d
!This file is part of Xcompact3d (xcompact3d.com)
!SPDX-License-Identifier: BSD 3-Clause
module abl
use decomp_2d_constants
use decomp_2d_mpi
use decomp_2d
contains
!*******************************************************************************
!
subroutine init_abl(ux1,uy1,uz1,ep1,phi1)
!
!*******************************************************************************
use decomp_2d_io
use variables
use param
use MPI
implicit none
real(mytype),dimension(xsize(1),xsize(2),xsize(3)) :: ux1,uy1,uz1,ep1
real(mytype),dimension(xsize(1),xsize(2),xsize(3),numscalar) :: phi1
real(mytype) :: y, phinoise
integer :: k,j,i,ierror,ii,code
integer, dimension (:), allocatable :: seed
ux1=zero
uy1=zero
uz1=zero
phi1=zero
bxx1=zero;bxy1=zero;bxz1=zero
byx1=zero;byy1=zero;byz1=zero
bzx1=zero;bzy1=zero;bzz1=zero
! ABL not yet set up for iLES, stretched grids, and non-constant explicit models.
if (ilesmod == 0.or.istret /= 0.or.jles.gt.1) then
write(*,*) 'Simulation stopped: run with different options'
call MPI_ABORT(MPI_COMM_WORLD,code,ierror); stop
endif
! Generation of a random noise
if (iin /= 0) then
call system_clock(count=code)
call random_seed(size = ii)
call random_seed(put = code+63946*(nrank+1)*(/ (i - 1, i = 1, ii) /)) !
call random_number(ux1)
call random_number(uy1)
call random_number(uz1)
do k=1,xsize(3)
do j=1,xsize(2)
do i=1,xsize(1)
ux1(i,j,k)=init_noise*(ux1(i,j,k)*two-one)
uy1(i,j,k)=init_noise*(uy1(i,j,k)*two-one)
uz1(i,j,k)=init_noise*(uz1(i,j,k)*two-one)
enddo
enddo
enddo
endif
! Initialize with log-law or geostrophic wind
do k=1,xsize(3)
do j=1,xsize(2)
if (istret == 0) y=real(j+xstart(2)-1-1,mytype)*dy
if (istret /= 0) y=yp(j)
if (iPressureGradient.eq.1.or.imassconserve.eq.1) then
bxx1(j,k)=ustar/k_roughness*log((y+z_zero)/z_zero)
else
bxx1(j,k)=UG(1)
endif
bxy1(j,k)=UG(2)
bxz1(j,k)=UG(3)
enddo
enddo
! Add boundary to noisy velocities
do k=1,xsize(3)
do j=1,xsize(2)
do i=1,xsize(1)
ux1(i,j,k)=bxx1(j,k)*(one+ux1(i,j,k))
uy1(i,j,k)=uy1(i,j,k)
uz1(i,j,k)=uz1(i,j,k)
enddo
enddo
enddo
! Initialize temperature profiles
if (iscalar == 1) then
do j=1,xsize(2)
if (istret == 0) y=real(j + xstart(2)-1-1,mytype)*dy
if (istret /= 0) y=yp(j+xstart(2)-1)
if (ibuoyancy == 1) then
Tstat(j,1)=T_wall + (T_top-T_wall)*y/yly
else
Tstat(j,1)=zero
endif
! Initialize GABLS-1 case
if (istrat==0) then
if (y>onehundred) then
phi1(:,j,:,1)=T_wall-Tstat(j,1) + (y-onehundred)*one/onehundred
else
phi1(:,j,:,1)=T_wall-Tstat(j,1)
endif
! Initialize case from Gadde et al. (2020)
else if (istrat==1) then
if (y>1062._mytype) then
phi1(:,j,:,1)=T_wall-Tstat(j,1) + eight + (y-1062._mytype)*three/onethousand
else if (y>937._mytype) then
phi1(:,j,:,1)=T_wall-Tstat(j,1) + (y-937._mytype)*eight/125._mytype
else
phi1(:,j,:,1)=T_wall-Tstat(j,1)
endif
endif
enddo
! Add random noise
do j=1,xsize(2)
if (istret==0) y=real(j + xstart(2)-1-1,mytype)*dy
if (istret/=0) y=yp(j+xstart(2)-1)
!if (y.lt.50) then
! do k=1,xsize(3)
! do i=1,xsize(1)
! call random_number(phinoise)
! phinoise=0.1*(phinoise*2.-1.)
! phi1(i,j,k,1)=phi1(i,j,k,1)+phinoise
! enddo
! enddo
!endif
enddo
endif
return
end subroutine init_abl
!*******************************************************************************
!
subroutine boundary_conditions_abl(ux,uy,uz,phi)
!
!*******************************************************************************
USE param
USE variables
implicit none
real(mytype),dimension(xsize(1),xsize(2),xsize(3)) :: ux,uy,uz
real(mytype),dimension(ysize(1),ysize(2),ysize(3)) :: gx
real(mytype),dimension(xsize(1),xsize(2),xsize(3),numscalar) :: phi
if (imassconserve==1) then
call transpose_x_to_y(ux,gx)
call forceabl(gx)
call transpose_y_to_x(gx,ux)
endif
if ((iconcprec.eq.1).or.(ishiftedper.eq.1)) then
call fringe_region(ux,uy,uz)
endif
if (nclx1.eq.2) then
if (iscalar.eq.0.or.(iscalar.eq.1.and.nclxS1.eq.2)) then
call inflow(ux,uy,uz,phi)
endif
endif
if (nclxn.eq.2) then
if (iscalar.eq.0.or.(iscalar.eq.1.and.nclxSn.eq.2)) then
call outflow(ux,uy,uz,phi)
endif
endif
return
end subroutine boundary_conditions_abl
!*******************************************************************************
!
subroutine inflow (ux,uy,uz,phi)
!
!*******************************************************************************
USE param
USE variables
USE MPI
USE var, only: ux_inflow, uy_inflow, uz_inflow
implicit none
real(mytype),dimension(xsize(1),xsize(2),xsize(3)) :: ux,uy,uz
real(mytype),dimension(xsize(1),xsize(2),xsize(3),numscalar) :: phi
real(mytype) :: um
integer :: i,j,k,itime_input
um=0.5*(u1+u2)
do k=1,xsize(3)
do j=1,xsize(2)
bxx1(j,k)=um
bxy1(j,k)=zero
bxz1(j,k)=zero
enddo
enddo
if (iin.eq.1.or.iin.eq.2) then
call random_number(bxo)
call random_number(byo)
call random_number(bzo)
do k=1,xsize(3)
do j=1,xsize(2)
bxx1(j,k)=bxx1(j,k)+(two*bxo(j,k)-one)*inflow_noise*um
bxy1(j,k)=bxy1(j,k)+(two*byo(j,k)-one)*inflow_noise*um
bxz1(j,k)=bxz1(j,k)+(two*bzo(j,k)-one)*inflow_noise*um
if (iscalar.eq.1) then
phi(1,j,k,:)=one
endif
enddo
enddo
else if (iin.eq.3) then
! Reading from files (when precursor simulations exist)
itime_input=mod(itime,ntimesteps)
if (itime_input==0) itime_input=ntimesteps
if (mod(itime,ilist)==0.and.nrank==0) print *,'Reading inflow from a file, time step: ', itime_input
do k=1,xsize(3)
do j=1,xsize(2)
! Case 1: Inflow is turbulence added to mean flow profile
!bxx1(j,k)=bxx1(j,k)+ux_inflow(itime_input,j,k)
!bxy1(j,k)=bxy1(j,k)+uy_inflow(itime_input,j,k)
!bxz1(j,k)=bxz1(j,k)+uz_inflow(itime_input,j,k)
! Case 2: Inflow is full velocity field
bxx1(j,k)=ux_inflow(itime_input,j,k)
bxy1(j,k)=uy_inflow(itime_input,j,k)
bxz1(j,k)=uz_inflow(itime_input,j,k)
enddo
enddo
endif
return
end subroutine inflow
!*******************************************************************************
!
subroutine outflow (ux,uy,uz,phi)
!
!*******************************************************************************
USE param
USE variables
USE MPI
implicit none
integer :: j,k,code
real(mytype),dimension(xsize(1),xsize(2),xsize(3)) :: ux,uy,uz
real(mytype),dimension(xsize(1),xsize(2),xsize(3),numscalar) :: phi
real(mytype) :: udx,udy,udz,uddx,uddy,uddz,cx,uxmin,uxmax,uxmin1,uxmax1
udx=one/dx; udy=one/dy; udz=one/dz; uddx=half/dx; uddy=half/dy; uddz=half/dz
uxmax=-1609.
uxmin=1609.
do k=1,xsize(3)
do j=1,xsize(2)
if (ux(nx-1,j,k).gt.uxmax) uxmax=ux(nx-1,j,k)
if (ux(nx-1,j,k).lt.uxmin) uxmin=ux(nx-1,j,k)
enddo
enddo
call MPI_ALLREDUCE(uxmax,uxmax1,1,real_type,MPI_MAX,MPI_COMM_WORLD,code)
call MPI_ALLREDUCE(uxmin,uxmin1,1,real_type,MPI_MIN,MPI_COMM_WORLD,code)
cx=0.5*(uxmax1+uxmin1)*gdt(itr)*udx
do k=1,xsize(3)
do j=1,xsize(2)
bxxn(j,k)=ux(nx,j,k)-cx*(ux(nx,j,k)-ux(nx-1,j,k))
bxyn(j,k)=uy(nx,j,k)-cx*(uy(nx,j,k)-uy(nx-1,j,k))
bxzn(j,k)=uz(nx,j,k)-cx*(uz(nx,j,k)-uz(nx-1,j,k))
if (iscalar.eq.1) then
phi(nx,j,k,:)=phi(nx,j,k,:)-cx*(phi(nx,j,k,:)-phi(nx-1,j,k,:))
endif
enddo
enddo
return
end subroutine outflow
!*******************************************************************************
!
subroutine momentum_forcing_abl(dux1,duy1,duz1,ux1,uy1,uz1,phi1)
!
!*******************************************************************************
USE param
USE variables
implicit none
real(mytype),dimension(xsize(1),xsize(2),xsize(3), ntime) :: dux1, duy1, duz1
real(mytype),dimension(xsize(1),xsize(2),xsize(3)) :: ux1, uy1, uz1
real(mytype),dimension(xsize(1),xsize(2),xsize(3), numscalar) :: phi1
integer :: i
! BL Forcing (Pressure gradient or geostrophic wind)
if (iPressureGradient==1) then
dux1(:,:,:,1)=dux1(:,:,:,1)+ustar**2./dBL
if (iconcprec.eq.1) then
do i=1,xsize(1)
if (real(i-1,mytype)*dx >= pdl) then
dux1(i,:,:,1)=dux1(i,:,:,1)-ustar**2./dBL
endif
enddo
endif
else if (iCoriolis==1 .and. iPressureGradient==0) then
dux1(:,:,:,1)=dux1(:,:,:,1)+CoriolisFreq*(-UG(3))
duz1(:,:,:,1)=duz1(:,:,:,1)-CoriolisFreq*(-UG(1))
endif
! Coriolis terms
if (iCoriolis==1) then
dux1(:,:,:,1)=dux1(:,:,:,1)+CoriolisFreq*uz1(:,:,:)
duz1(:,:,:,1)=duz1(:,:,:,1)-CoriolisFreq*ux1(:,:,:)
endif
! Damping zone
if (idamping==1) then
call damping_zone(dux1,duy1,duz1,ux1,uy1,uz1)
endif
! Buoyancy terms
if (iscalar==1.and.ibuoyancy==1) then
duy1(:,:,:,1)=duy1(:,:,:,1)+gravv*phi1(:,:,:,1)/Tref
endif
return
end subroutine momentum_forcing_abl
!*******************************************************************************
!
subroutine scalar_forcing_abl(uy1,dphi1,phi1)
!
!*******************************************************************************
USE param
USE variables
implicit none
real(mytype),dimension(xsize(1),xsize(2),xsize(3), ntime) :: dphi1
real(mytype),dimension(xsize(1),xsize(2),xsize(3)) :: uy1, phi1
! Damping zone
if (idamping==1) then
call damping_zone_scalar(dphi1,phi1)
endif
! Terms from decomposition
if (ibuoyancy==1) then
dphi1(:,:,:,1) = dphi1(:,:,:,1) + (T_wall-T_top)*uy1(:,:,:)/yly
endif
return
end subroutine scalar_forcing_abl
!*******************************************************************************
!
subroutine wall_sgs_slip(ux,uy,uz,phi,nut1,wallfluxx,wallfluxy,wallfluxz)
!
! Outputs fluxes, only compatible with iconserv=0
!
!*******************************************************************************
use MPI
use param
use variables
use var, only: uxf1, uzf1, phif1, uxf3, uzf3, phif3
use var, only: di1, di3
use var, only: sxy1, syz1, heatflux, ta2, tb2, ta3, tb3
use ibm_param, only : ubcx, ubcz
implicit none
real(mytype),dimension(xsize(1),xsize(2),xsize(3)),intent(in) :: ux,uy,uz, nut1
real(mytype),dimension(xsize(1),xsize(2),xsize(3),numscalar),intent(in) :: phi
real(mytype),dimension(xsize(1),xsize(2),xsize(3)),intent(out) :: wallfluxx,wallfluxy,wallfluxz
real(mytype),dimension(xsize(1),xsize(3)) :: tauwallxy, tauwallzy
real(mytype),dimension(xsize(1),xsize(3)) :: Obukhov, zeta
integer :: i,j,k,ii,code
integer :: nxc, nyc, nzc, xsize1, xsize2, xsize3
real(mytype) :: delta
real(mytype) :: ux_HAve_local, uz_HAve_local, Phi_HAve_local
real(mytype) :: ux_HAve, uz_HAve,S_HAve,Phi_HAve,ux12,uz12,S12,Phi12,Tstat12
real(mytype) :: PsiM_HAve_local, PsiM_HAve, PsiH_HAve_local, PsiH_HAve
real(mytype) :: L_HAve_local, L_HAve, Q_HAve_local, Q_HAve, zL, zeta_HAve
real(mytype) :: Lold, OL_diff
! Filter the velocity with twice the grid scale according to Bou-Zeid et al. (2005)
if (nclx1==1.and.xend(1)==nx) then
xsize1=xsize(1)-1
else
xsize1=xsize(1)
endif
if (ncly1==1.and.xend(2)==ny) then
xsize2=xsize(2)-1
else
xsize2=xsize(2)
endif
if (nclz1==1.and.xend(3)==nz) then
xsize3=xsize(3)-1
else
xsize3=xsize(3)
endif
if (nclx1==1) then
nxc=nxm
else
nxc=nx
endif
if (ncly1==1) then
nyc=nym
else
nyc=ny
endif
if (nclz1==1) then
nzc=nzm
else
nzc=nz
endif
call filter(zero)
call filx(uxf1,ux,di1,fisx,fiffx,fifsx,fifwx,xsize(1),xsize(2),xsize(3),0,ubcx)
call filx(uzf1,uz,di1,fisx,fiffxp,fifsxp,fifwxp,xsize(1),xsize(2),xsize(3),1,ubcz)
call transpose_x_to_y(uxf1,ta2)
call transpose_x_to_y(uzf1,tb2)
call transpose_y_to_z(ta2,ta3)
call transpose_y_to_z(tb2,tb3)
call filz(uxf3,ta3,di3,fisz,fiffzp,fifszp,fifwzp,zsize(1),zsize(2),zsize(3),1,ubcx)
call filz(uzf3,tb3,di3,fisz,fiffz,fifsz,fifwz,zsize(1),zsize(2),zsize(3),0,ubcz)
call transpose_z_to_y(uxf3,ta2)
call transpose_z_to_y(uzf3,tb2)
call transpose_y_to_x(ta2,uxf1)
call transpose_y_to_x(tb2,uzf1)
if (iscalar==1) then
call filx(phif1,phi(:,:,:,1),di1,fisx,fiffx,fifsx,fifwx,xsize(1),xsize(2),xsize(3),0,zero)
call transpose_x_to_y(phif1,ta2)
call transpose_y_to_z(ta2,ta3)
call filz(phif3,ta3,di3,fisz,fiffz,fifsz,fifwz,zsize(1),zsize(2),zsize(3),0,zero)
call transpose_z_to_y(phif3,ta2)
call transpose_y_to_x(ta2,phif1)
endif
! Reset average values
ux_HAve_local = zero
uz_HAve_local = zero
Phi_HAve_local = zero
! dy to y=1/2
if (istret/=0) delta=half*(yp(2)-yp(1))
if (istret==0) delta=half*dy
! Find horizontally averaged velocities at j=1.5
if (xstart(2)==1) then
do k=1,xsize(3)
do i=1,xsize(1)
ux_HAve_local=ux_HAve_local+half*(uxf1(i,1,k)+uxf1(i,2,k))
uz_HAve_local=uz_HAve_local+half*(uzf1(i,1,k)+uzf1(i,2,k))
if (iscalar==1) Phi_HAve_local=Phi_HAve_local+half*(phif1(i,1,k)+phif1(i,2,k))
enddo
enddo
ux_HAve_local=ux_HAve_local
uz_HAve_local=uz_HAve_local
Phi_HAve_local=Phi_HAve_local
endif
call MPI_ALLREDUCE(ux_HAve_local,ux_HAve,1,real_type,MPI_SUM,MPI_COMM_WORLD,code)
call MPI_ALLREDUCE(uz_HAve_local,uz_HAve,1,real_type,MPI_SUM,MPI_COMM_WORLD,code)
if (iscalar==1) call MPI_ALLREDUCE(Phi_HAve_local,Phi_HAve,1,real_type,MPI_SUM,MPI_COMM_WORLD,code)
ux_HAve=ux_HAve/(nxc*nzc)
uz_HAve=uz_HAve/(nxc*nzc)
S_HAve=sqrt(ux_HAve**2.+uz_HAve**2.)
if (iscalar==1) then
Phi_HAve=Phi_HAve/(nxc*nzc)
if (ibuoyancy==1) then
Tstat12 =T_wall + (T_top-T_wall)*delta/yly
else
Tstat12 =zero
endif
Phi_HAve=Phi_HAve + Tstat12
endif
! Reset wall flux values
wallfluxx=zero
wallfluxy=zero
wallfluxz=zero
! Initialize stratification variables
if (iscalar==1.and.ibuoyancy == 1.and.xstart(2)==1) then
PsiM_HAve= zero
PsiH_HAve= zero
ii = 0
OL_diff = one
Lold = one
do while (OL_diff > 1.0e-14_mytype)
if (itherm==0) then
Q_HAve = TempFlux
else if (itherm==1) then
Q_HAve =-k_roughness**two*S_HAve*(Phi_HAve-(T_wall+TempRate*t))/((log(delta/z_zero)-PsiM_HAve)*(log(delta/z_zero)-PsiH_HAve))
endif
L_HAve=-(k_roughness*S_HAve/(log(delta/z_zero)-PsiM_HAve))**three*Phi_HAve/(k_roughness*gravv*Q_HAve)
if (istrat==0) then
PsiM_HAve=-4.8_mytype*delta/L_HAve
PsiH_HAve=-7.8_mytype*delta/L_HAve
else if (istrat==1) then
zeta_HAve=(one-sixteen*delta/L_HAve)**zptwofive
PsiM_HAve=two*log(half*(one+zeta_HAve))+log(zpfive*(one+zeta_HAve**two))-two*atan(zeta_HAve)+pi/two
PsiH_HAve=two*log(half*(one+zeta_HAve**two))
endif
ii = ii + 1
OL_diff = abs((L_HAve - Lold)/Lold)
Lold = L_HAve
if (ii==50) exit
enddo
heatflux=Q_Have
Obukhov=L_HAve
PsiM=PsiM_HAve
PsiH=PsiH_HAve
if (istrat==1) zeta=zeta_HAve
else
heatflux =zero
Obukhov =zero
PsiM =zero
PsiH =zero
PsiM_HAve=zero
PsiH_HAve=zero
endif
! Apply BCs locally
if (xstart(2)==1) then
do k=1,xsize(3)
do i=1,xsize(1)
! Horizontally-averaged formulation
if(iwallmodel==1) then
tauwallxy(i,k)=-(k_roughness/(log(delta/z_zero)-PsiM_HAve))**two*ux_HAve*S_HAve
tauwallzy(i,k)=-(k_roughness/(log(delta/z_zero)-PsiM_HAve))**two*uz_HAve*S_HAve
! Local formulation
else
ux12=half*(uxf1(i,1,k)+uxf1(i,2,k))
uz12=half*(uzf1(i,1,k)+uzf1(i,2,k))
S12=sqrt(ux12**2.+uz12**2.)
if (iscalar==1) then
Phi12= half*(phif1(i,1,k)+ phif1(i,2,k)) + Tstat12
do ii=1,10
if (itherm==1) heatflux(i,k)=-k_roughness**two*S12*(Phi12-(T_wall+TempRate*t))/((log(delta/z_zero)-PsiM(i,k))*(log(delta/z_zero)-PsiH(i,k)))
Obukhov(i,k)=-(k_roughness*S12/(log(delta/z_zero)-PsiM(i,k)))**three*Phi12/(k_roughness*gravv*heatflux(i,k))
if (istrat==0) then
PsiM(i,k)=-4.8_mytype*delta/Obukhov(i,k)
PsiH(i,k)=-7.8_mytype*delta/Obukhov(i,k)
else if (istrat==1) then
zeta(i,k)=(one-sixteen*delta/Obukhov(i,k))**zptwofive
PsiM(i,k)=two*log(half*(one+zeta(i,k)))+log(zpfive*(one+zeta(i,k)**2.))-two*atan(zeta(i,k))+pi/two
PsiH(i,k)=two*log(half*(one+zeta(i,k)**two))
endif
enddo
endif
tauwallxy(i,k)=-(k_roughness/(log(delta/z_zero)-PsiM(i,k)))**two*ux12*S12
tauwallzy(i,k)=-(k_roughness/(log(delta/z_zero)-PsiM(i,k)))**two*uz12*S12
endif
! Apply second-order upwind scheme for the near wall
! Below should change for non-uniform grids, same for wall_sgs_slip_scalar
wallfluxx(i,1,k) = -(-half*(-two*nut1(i,3,k)*sxy1(i,3,k))+&
two*(-two*nut1(i,2,k)*sxy1(i,2,k))-three/two*tauwallxy(i,k))/(two*delta)
wallfluxy(i,1,k) = zero
wallfluxz(i,1,k) = -(-half*(-two*nut1(i,3,k)*syz1(i,3,k))+&
two*(-two*nut1(i,2,k)*syz1(i,2,k))-three/two*tauwallzy(i,k))/(two*delta)
enddo
enddo
endif
! Reset average values
PsiM_HAve_local=zero
PsiH_HAve_local=zero
L_HAve_local =zero
Q_HAve_local =zero
! Find horizontally averaged values
if (iscalar==1) then
do k=1,xsize(3)
do i=1,xsize(1)
PsiM_HAve_local=PsiM_HAve_local+PsiM(i,k)
PsiH_HAve_local=PsiH_HAve_local+PsiH(i,k)
L_HAve_local=L_HAve_local+Obukhov(i,k)
Q_HAve_local=Q_HAve_local+heatflux(i,k)
enddo
enddo
PsiM_HAve_local=PsiM_HAve_local
PsiH_HAve_local=PsiH_HAve_local
L_HAve_local=L_HAve_local
Q_HAve_local=Q_HAve_local
call MPI_ALLREDUCE(PsiM_HAve_local,PsiM_HAve,1,real_type,MPI_SUM,MPI_COMM_WORLD,code)
call MPI_ALLREDUCE(PsiH_HAve_local,PsiH_HAve,1,real_type,MPI_SUM,MPI_COMM_WORLD,code)
call MPI_ALLREDUCE(L_HAve_local,L_HAve,1,real_type,MPI_SUM,MPI_COMM_WORLD,code)
call MPI_ALLREDUCE(Q_HAve_local,Q_HAve,1,real_type,MPI_SUM,MPI_COMM_WORLD,code)
PsiM_HAve=PsiM_HAve/(nxc*nzc)
PsiH_HAve=PsiH_HAve/(nxc*nzc)
L_HAve=L_HAve/(nxc*nzc)
Q_HAve=Q_HAve/(nxc*nzc)
endif
! Compute friction velocity u_shear and boundary layer height
u_shear=k_roughness*S_HAve/(log(delta/z_zero)-PsiM_HAve)
if (iheight==1) call boundary_height(ux,uy,uz,dBL)
if (iscalar==1) zL=dBL/L_HAve
if (mod(itime,ilist)==0.and.nrank==0) then
write(*,*) ' '
write(*,*) ' ABL:'
write(*,*) ' Horizontally-averaged velocity at y=1/2: ', ux_HAve,uz_Have
write(*,*) ' BL height: ', dBL
write(*,*) ' Friction velocity: ', u_shear
if (iscalar==1) then
write(*,*) ' Temperature: ', Phi_HAve
write(*,*) ' PsiM: ', PsiM_HAve
write(*,*) ' PsiH: ', PsiH_HAve
write(*,*) ' Obukhov L: ', L_HAve
write(*,*) ' Heatflux: ', Q_HAve
write(*,*) ' z/L: ', zL
endif
write(*,*) 'Maximum wall shear stress for x and z', maxval(tauwallxy), maxval(tauwallzy)
write(*,*) 'Minimum wall shear stress for x and z', minval(tauwallxy), minval(tauwallzy)
write(*,*) 'Max flux x and z ', maxval(wallfluxx), maxval(wallfluxz)
write(*,*) 'Min flux x and z ', minval(wallfluxx), minval(wallfluxz)
endif
return
end subroutine wall_sgs_slip
!*******************************************************************************
!
subroutine wall_sgs_slip_scalar(sgsphi1,nut1,dphidy1)
!
!*******************************************************************************
use param
use var, only: heatflux
use variables
implicit none
real(mytype),dimension(xsize(1),xsize(2),xsize(3)),intent(in) :: nut1, dphidy1
real(mytype),dimension(xsize(1),xsize(2),xsize(3)),intent(inout) :: sgsphi1
real(mytype) :: delta, Pr
integer :: i,k
Pr=Sc(1)
if (xstart(2)==1) then
if (istret/=0) delta=(yp(2)-yp(1))/two
if (istret==0) delta=dy/two
do k=1,xsize(3)
do i=1,xsize(1)
sgsphi1(i,1,k) =-(-half*(-nut1(i,3,k)*dphidy1(i,3,k))/Pr+&
two*(-nut1(i,2,k)*dphidy1(i,2,k))/Pr-three/two*heatflux(i,k))/(two*delta)
enddo
enddo
endif
end subroutine wall_sgs_slip_scalar
!*******************************************************************************
!
subroutine wall_sgs_noslip(ux1,uy1,uz1,nut1,wallsgsx1,wallsgsy1,wallsgsz1)
!
! Outputs stresses if iconserv=1 and fluxes if iconserv=0 (wallsgsx,wallsgsy,wallsgsz)
!
!*******************************************************************************
use MPI
use param
use variables
use var, only: di1, di2, di3
use var, only: sxy1, syz1, tb1, ta2, tb2
use ibm_param, only : ubcx, ubcy, ubcz
implicit none
real(mytype),dimension(xsize(1),xsize(2),xsize(3)),intent(in) :: ux1,uy1,uz1,nut1
real(mytype),dimension(xsize(1),xsize(2),xsize(3)),intent(out) :: wallsgsx1,wallsgsy1,wallsgsz1
real(mytype),dimension(ysize(1),ysize(3)) :: tauwallxy2, tauwallzy2
integer :: i,j,k,code,j0
integer :: nxc, nyc, nzc, xsize1, xsize2, xsize3
real(mytype) :: delta
real(mytype) :: ux_HAve_local, uz_HAve_local
real(mytype) :: ux_HAve, uz_HAve, S_HAve, ux_delta, uz_delta, S_delta
real(mytype),dimension(xsize(1),xsize(2),xsize(3)) :: txy1,tyz1,dtwxydx
real(mytype),dimension(ysize(1),ysize(2),ysize(3)) :: txy2,tyz2,wallsgsx2,wallsgsz2
real(mytype),dimension(zsize(1),zsize(2),zsize(3)) :: tyz3,dtwyzdz
real(mytype) :: y_sampling
! Reset wall flux/stresses values
wallsgsx1 = zero
wallsgsy1 = zero
wallsgsz1 = zero
! Set sampling distance for the wall model
delta=dsampling*dy
if(iconserv==0) then
! Construct Smag SGS stress tensor
txy1 = -2.0*nut1*sxy1
tyz1 = -2.0*nut1*syz1
call transpose_x_to_y(txy1,txy2)
call transpose_x_to_y(tyz1,tyz2)
endif
! Work on Y-pencil
call transpose_x_to_y(ux1,ta2)
call transpose_x_to_y(uz1,tb2)
! Apply BCs locally
do k=1,ysize(3)
do i=1,ysize(1)
!sampling at dsampling*dy from wall
j0=floor(delta/dy)
y_sampling=delta-real(j0,mytype)*dy
ux_delta=(1-y_sampling/dy)*ta2(i,j0+1,k)+(y_sampling/dy)*ta2(i,j0+2,k)
uz_delta=(1-y_sampling/dy)*tb2(i,j0+1,k)+(y_sampling/dy)*tb2(i,j0+2,k)
S_delta=sqrt(ux_delta**2.+uz_delta**2.)
tauwallxy2(i,k)=-(k_roughness/(log(delta/z_zero)))**two*ux_delta*S_delta
tauwallzy2(i,k)=-(k_roughness/(log(delta/z_zero)))**two*uz_delta*S_delta
txy2(i,2,k) = tauwallxy2(i,k)
tyz2(i,2,k) = tauwallzy2(i,k)
enddo
enddo
if (iconserv==0) then
! Derivative of wallmodel-corrected SGS stress tensor
call dery_22(wallsgsx2,txy2,di2,sy,ffy,fsy,fwy,ppy,ysize(1),ysize(2),ysize(3),1,ubcy)
call dery_22(wallsgsz2,tyz2,di2,sy,ffy,fsy,fwy,ppy,ysize(1),ysize(2),ysize(3),1,ubcy)
call transpose_y_to_x(wallsgsx2,wallsgsx1)
call transpose_y_to_x(wallsgsz2,wallsgsz1)
call derx(dtwxydx,txy1,di1,sx,ffx,fsx,fwx,xsize(1),xsize(2),xsize(3),0,ubcx)
call transpose_y_to_z(tyz2,tyz3)
call derz(dtwyzdz,tyz3,di3,sz,ffz,fsz,fwz,zsize(1),zsize(2),zsize(3),0,ubcz)
call transpose_z_to_y(dtwyzdz,tb2)
call transpose_y_to_x(tb2,tb1)
wallsgsy1 = dtwxydx + tb1
elseif (iconserv==1) then
call transpose_y_to_x(txy2,wallsgsx1)
call transpose_y_to_x(tyz2,wallsgsz1)
endif
! Print information at y=5*dy
ux_HAve_local =zero
uz_HAve_local =zero
if (nclx1==1.and.xend(1)==nx) then
xsize1=xsize(1)-1
else
xsize1=xsize(1)
endif
if (ncly1==1.and.xend(2)==ny) then
xsize2=xsize(2)-1
else
xsize2=xsize(2)
endif
if (nclz1==1.and.xend(3)==nz) then
xsize3=xsize(3)-1
else
xsize3=xsize(3)
endif
if (nclx1==1) then
nxc=nxm
else
nxc=nx
endif
if (ncly1==1) then
nyc=nym
else
nyc=ny
endif
if (nclz1==1) then
nzc=nzm
else
nzc=nz
endif
do k=1,ysize(3)
do i=1,ysize(1)
ux_HAve_local=ux_HAve_local+ta2(i,6,k)
uz_HAve_local=uz_HAve_local+tb2(i,6,k)
enddo
enddo
ux_HAve_local=ux_HAve_local
uz_HAve_local=uz_HAve_local
call MPI_ALLREDUCE(ux_HAve_local,ux_HAve,1,real_type,MPI_SUM,MPI_COMM_WORLD,code)
call MPI_ALLREDUCE(uz_HAve_local,uz_HAve,1,real_type,MPI_SUM,MPI_COMM_WORLD,code)
ux_HAve=ux_HAve/(nxc*nzc)
uz_HAve=uz_HAve/(nxc*nzc)
S_HAve=sqrt(ux_HAve**2.+uz_HAve**2.)
u_shear=k_roughness*S_HAve/log(5*dy/z_zero)
if (mod(itime,ilist)==0.and.nrank==0) then
! Write u_shear in file
write(42,'(20e20.12)') t,u_shear
flush(42)
! Print in terminal
write(*,*) ' ABL:'
write(*,*) ' Horizontally-averaged velocity at 5*dy: ', ux_HAve,uz_HAve
write(*,*) ' Friction velocity at 5*dy: ', u_shear
endif
return
end subroutine wall_sgs_noslip
!*******************************************************************************
!
subroutine forceabl (ux) ! Routine to force constant flow rate
!
!*******************************************************************************
use decomp_2d_poisson
use param
use var
use MPI
implicit none
real(mytype),dimension(ysize(1),ysize(2),ysize(3)) :: ux
integer :: j,i,k,code
real(mytype) :: can,ut3,ut,ut4,xloc
ut3=zero
do k=1,ysize(3)
do i=1,ysize(1)
xloc=(i+ystart(1)-1-1)*dx
if (iconcprec.eq.1.and.xloc>=pdl) then
continue
else
ut=zero
do j=1,ny-1
if (istret/=0) ut=ut+(yp(j+1)-yp(j))*(ux(i,j+1,k)-half*(ux(i,j+1,k)-ux(i,j,k)))
if (istret==0) ut=ut+(yly/real(ny-1,mytype))*(ux(i,j+1,k)-half*(ux(i,j+1,k)-ux(i,j,k)))
enddo
ut3=ut3+ut
endif
enddo
enddo
ut3=ut3/ysize(1)/ysize(3)
call MPI_ALLREDUCE(ut3,ut4,1,real_type,MPI_SUM,MPI_COMM_WORLD,code)
ut4=ut4/nproc
if (iconcprec.eq.1) ut4=ut4*(xlx/pdl)
! Flow rate for a logarithmic profile
!can=-(ustar/k_roughness*yly*(log(yly/z_zero)-1.)-ut4)
can=-(ustar/k_roughness*(yly*log(dBL/z_zero)-dBL)-ut4)
if (nrank==0.and.mod(itime,ilist)==0) write(*,*) '# Rank ',nrank,'correction to ensure constant flow rate',ut4,can
do k=1,ysize(3)
do i=1,ysize(1)
xloc=real(i+ystart(1)-1-1,mytype)*dx
if (iconcprec.eq.1.and.xloc>=pdl) then
continue
else
do j=1,ny
ux(i,j,k)=ux(i,j,k)-can/yly
enddo
endif
enddo
enddo
return
end subroutine forceabl
!*******************************************************************************
!
subroutine fringe_region (ux,uy,uz)
!
!*******************************************************************************
USE param
USE var
implicit none
real(mytype),dimension(xsize(1),xsize(2),xsize(3)) :: ux,uy,uz
real(mytype),dimension(xsize(1),xsize(2),xsize(3)) :: ux_s,uy_s,uz_s
real(mytype),dimension(zsize(1),zsize(2),zsize(3)) :: ux3_s,uy3_s,uz3_s
integer :: i, j, k, nshift, npe, nfe
real(mytype) :: dshift, x, edl, frl, fre, frs, frd, lambda
if (ishiftedper==1) then
! Shifting distance
dshift = zlz/8 ! could be yly/4 etc..
nshift = int(dshift/dz)
! Compute spanwise-shifted velocity field
call transpose_x_to_y(ux,td2)
call transpose_x_to_y(uy,te2)
call transpose_x_to_y(uz,tf2)
call transpose_y_to_z(td2,td3)
call transpose_y_to_z(te2,te3)
call transpose_y_to_z(tf2,tf3)
do k=1,nz-nshift
ux3_s(:,:,k+nshift) = td3(:,:,k)
uy3_s(:,:,k+nshift) = te3(:,:,k)
uz3_s(:,:,k+nshift) = tf3(:,:,k)
enddo
do k=1,nshift
ux3_s(:,:,k) = td3(:,:,nz-nshift+k)
uy3_s(:,:,k) = te3(:,:,nz-nshift+k)
uz3_s(:,:,k) = tf3(:,:,nz-nshift+k)
enddo
call transpose_z_to_y(ux3_s,td2)
call transpose_z_to_y(uy3_s,te2)
call transpose_z_to_y(uz3_s,tf2)
call transpose_y_to_x(td2,ux_s)
call transpose_y_to_x(te2,uy_s)
call transpose_y_to_x(tf2,uz_s)
else
ux_s=ux
uy_s=uy
uz_s=uz
endif
! Fringe region(s) parameters
edl = twothird
frl = 1._mytype/6._mytype
if (ishiftedper==1.and.iconcprec==0) then
fre = xlx*edl
npe = nx
elseif (ishiftedper==1.and.iconcprec==1) then
fre = pdl*edl
npe = int(nx*pdl/xlx)
elseif (ishiftedper==0.and.iconcprec==1) then
fre = pdl
endif
frs = fre-fre*frl
frd = fre-frs
nfe = int(nx*fre/xlx)
! Apply fringe region(s)
do k=1,xsize(3)
do j=1,xsize(2)
do i=1,nfe
x=real(i-1,mytype)*dx
if (x<frs) then
lambda=zero
elseif ( (x>=frs) .and. (x<(fre-frd/four)) ) then
lambda=half*(1.-cos(four*pi/three*(x-frs)/frd))
elseif ( (x>=(fre-frd/four)) .and. (x<fre) ) then
lambda=one
else
lambda=zero
endif
if (ishiftedper==1) then
ux(i+npe-nfe,j,k)=lambda*ux_s(i,j,k)+(one-lambda)*ux(i+npe-nfe,j,k)
uy(i+npe-nfe,j,k)=lambda*uy_s(i,j,k)+(one-lambda)*uy(i+npe-nfe,j,k)
uz(i+npe-nfe,j,k)=lambda*uz_s(i,j,k)+(one-lambda)*uz(i+npe-nfe,j,k)
endif
if (iconcprec==1) then
ux(i+nx-nfe,j,k)=lambda*ux_s(i,j,k)+(one-lambda)*ux(i+nx-nfe,j,k)
uy(i+nx-nfe,j,k)=lambda*uy_s(i,j,k)+(one-lambda)*uy(i+nx-nfe,j,k)
uz(i+nx-nfe,j,k)=lambda*uz_s(i,j,k)+(one-lambda)*uz(i+nx-nfe,j,k)
endif
enddo
enddo
enddo
return
end subroutine fringe_region
!*******************************************************************************
!
subroutine damping_zone (dux1,duy1,duz1,ux1,uy1,uz1) ! Damping zone for ABL
!
!*******************************************************************************
use param
use var, only: yp
implicit none
real(mytype),dimension(xsize(1),xsize(2),xsize(3)),intent(in) :: ux1,uy1,uz1
real(mytype),dimension(xsize(1),xsize(2),xsize(3),ntime),intent(inout) :: dux1, duy1, duz1
integer :: i,j,k