-
Notifications
You must be signed in to change notification settings - Fork 0
/
papero.f90
executable file
·171 lines (138 loc) · 4.28 KB
/
papero.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
program papero
use mpih
use mpi_param
use param
use local_arrays, only: vy,vz,pr,vx
use mls_param
implicit none
character(len=4) :: dummy
integer :: n,ns,nt,errorcode
integer :: ntstf
real :: dmax,minwtdt
real :: ti(2), tin(3)
call InitializeMPI
tin(1) = mpi_wtime()
tin(2) = mpi_wtime()
!RO Calculate number of OpenMP Threads
nt = 0
nt = nt + 1
if (ismaster) then
write(6,*) 'MPI tasks=', numtasks
write(6,*) 'OMP threads per task=', nt
write(6,*) 'No. of processors=', nt*numtasks
end if
open(unit=15,file='bou.in',status='old')
read(15,301) dummy
read(15,*) n1m,n2m,n3m
read(15,301) dummy
read(15,*) xlen,ylen,zlen
read(15,301) dummy
read(15,*) nread, pread
read(15,301) dummy
read(15,*) ntst,nsst,tframe,tpin,ireset
read(15,301) dummy
read(15,*) idtv, dt, dtmax, cflfix
read(15,301) dummy
read(15,*) ren,prandtl,betagz
read(15,301) dummy
read(15,*) Tmelt , Tliq, Tsol, latHeat, cpliquid, temp_restart
read(15,301) dummy
read(15,*) forcing
close(15)
open(unit=15,file='HITForcing.in',status='old')
read(15,301) dummy
read(15,*) which_hit
read(15,301) dummy
read(15,*) tl, epsstar, kf_on_kmin
read(15,301) dummy
read(15,*) C_HIT
close(15)
open(unit=15,file='part.in',status='old')
read(15,301) dummy
read(15,*) imlsfor, imlsstr, imelt
read(15,301) dummy
read(15,*) dens_ratio
read(15,301) dummy
read(15,*) gtsfx, rad_p
read(15,301) dummy
read(15,*) iremesh, PERC_Ethresh, V_ON_VE_PERC
!read(15,*) iremesh, PERC_Athresh, skew_thresh, V_ON_VE_PERC
close(15)
301 format(a4)
! KZ Verify correctness of bou.in, part.in
! Can only melt if MLS forcing is enabled
if (imelt.eq.1) then
if(imlsfor.ne.1) then
write(*,*) "Rank", myid, "Melting enabled but MLS forcing disabled, exiting"
call MPI_ABORT(MPI_COMM_WORLD,ierr)
endif
endif
! Can only do FSI if MLS forcing is enabled
if (imlsstr.eq.1) then
if(imlsfor.ne.1) then
write(*,*) "Rank", myid, "FSI enabled but MLS forcing disabled, exiting"
call MPI_ABORT(MPI_COMM_WORLD,ierr)
endif
endif
gtsfx = "gts/" // trim(gtsfx)
starea = 0 ! KZ: fix to zero, not using stat.f90
pec = ren * prandtl
n1=n1m+1
n2=n2m+1
n3=n3m+1
n1mh = n1m/2 + 1
n2mh = n2m/2 + 1
nsst=3
if(nsst.eq.3)then
gam(1)=8.d0/15.d0
gam(2)=5.d0/12.d0
gam(3)=3.d0/4.d0
rom(1)=0.d0
rom(2)=-17.d0/60.d0
rom(3)=-5.d0/12.d0
endif
if(nsst.eq.1)then
gam(1)=3./2.
gam(2)=0.d0
gam(3)=0.d0
rom(1)=-1./2.
rom(2)=0.d0
rom(3)=0.d0
endif
do ns=1,nsst
alm(ns)=(gam(ns)+rom(ns))
end do
call MpiBarrier
pi=2.d0*dasin(1.d0)
if(ismaster) then
!m====================================================
write(6,112)xlen/zlen,ylen/zlen
112 format(//,20x,'H I T',//,10x, &
'3D Cube with aspect-ratio: L1/L3 = ',f5.2,' L2/L3 = ',f5.2)
write(6,120)nsst
120 format(/,5x, &
'nsst', i7,/)
write(6,202) ren, prandtl
202 format(/,5x,'Parameters: ',' Re=',e10.3,' Prandtl = ',f5.2)
if(idtv.eq.1) then
write(6,204) cflfix
204 format(/,5x,'Variable dt and fixed cfl= ', &
e11.4,/ )
else
write(6,205) dtmax,cfllim
205 format(/,5x,'Fixed dt= ',e11.4,' and maximum cfl=', &
e11.4,/ )
endif
!m====================================================
endif
!m======================================================
#ifdef TIMED
timeflag = .true.
#endif
#ifdef SPEC
specflag = .true.
#endif
call gcurv
errorcode = 1
call QuitRoutine(tin,.true.,errorcode)
end