File: RELATIVE:/../../../mfix.git/model/dmp_modules/dbg_util_mod.f

1     !       Debug printout utilities written by Aytekin Gel from Aeolus Research Inc.
2     !       following the convention in ORNL's mpi_utility template
3     
4         module dbg_util
5     
6         use compar
7         use geometry
8         use parallel_mpi
9         use indices
10     
11         implicit none
12     
13     !       Object-oriented approach to direct to the correct procedure
14     !       depending on the argument type. i stands for integer, r for real
15     !       and d for double precision. 0 for scalar, 1 for vector, 2 for
16     !       2-D array and similarly 3.
17     
18           interface dbgprn
19             module  procedure  dbgprn_0i,dbgprn_1i, &
20                                dbgprn_0r,dbgprn_1r
21     !               , , dbgprn_2i, dbgprn_3i, &
22     !                          dbgprn_0r, dbgprn_1r, dbgprn_2r, dbgprn_3r, &
23     !                          bcast_0d, bcast_1d, bcast_2d, bcast_3d
24           end interface
25     
26           interface prnfield
27              module  procedure prnfield_1d,prnfield_1r,prnfield_2d
28           end interface
29     
30           contains
31     
32           subroutine dbgprn_0i( buffer, ncount, myid )
33           integer, intent(inout) :: buffer
34           integer, intent(in) :: ncount
35           integer, optional, intent(in) :: myid
36           integer :: dbgout = 75
37     
38           open(convert='big_endian',unit=dbgout, FILE='dbg'//fbname//'.dat', STATUS='UNKNOWN')
39           write(dbgout,"('(PE ',I3,') :')") myPE
40           write(dbgout,"(10X,'buffer = ',I6)") buffer
41           close(dbgout)
42           return
43           end subroutine dbgprn_0i
44     
45           subroutine dbgprn_1i( buffer, ncount, myid )
46           integer, intent(inout), dimension(:) :: buffer
47           integer, intent(in) :: ncount
48           integer, optional, intent(in) :: myid
49           integer :: dbgout = 75
50           integer :: i
51     
52           open(convert='big_endian',unit=dbgout, FILE='dbg'//fbname//'.dat', STATUS='UNKNOWN')
53           write(dbgout,"('(PE ',I3,') :')") myPE
54           do i=1,ncount
55             write(dbgout,"(10X,'buf(',I3,')= ',I6)") i,buffer(i)
56           end do
57           close(dbgout)
58           return
59           end subroutine dbgprn_1i
60     
61           subroutine dbgprn_0r( buffer, ncount, myid )
62           real, intent(inout) :: buffer
63           integer, intent(in) :: ncount
64           integer, optional, intent(in) :: myid
65           integer :: dbgout = 75
66     
67           open(convert='big_endian',unit=dbgout, FILE='dbg'//fbname//'.dat', STATUS='UNKNOWN')
68           write(dbgout,"('(PE ',I3,') :')") myPE
69           write(dbgout,"(10X,'buffer = ',E14.6)") buffer
70           close(dbgout)
71           return
72           end subroutine dbgprn_0r
73     
74           subroutine dbgprn_1r( buffer, ncount, myid )
75           real, intent(inout), dimension(:) :: buffer
76           integer, intent(in) :: ncount
77           integer, optional, intent(in) :: myid
78           integer :: dbgout = 75
79           integer :: i
80     
81           open(convert='big_endian',unit=dbgout, FILE='dbg'//fbname//'.dat', STATUS='UNKNOWN')
82           write(dbgout,"('(PE ',I3,') :')") myPE
83           do i=1,ncount
84             write(dbgout,"(10X,'buf(',I3,')= ',E14.6)") i,buffer(i)
85           end do
86           close(dbgout)
87           return
88           end subroutine dbgprn_1r
89     
90           subroutine prnfield_1d (gbuf,varname,flagl)
91     
92           use functions
93           implicit none
94     
95           double precision, intent(in), dimension(:) :: gbuf
96           character(len=3), intent(in)   :: flagl
97           character(len=*), intent(in)   :: varname
98           integer :: ldbg = 35
99           integer :: i,j,k
100     !      integer, optional, intent(in) :: mroot, idebug
101     
102            OPEN(CONVERT='BIG_ENDIAN',unit=ldbg,file=flagl//fbname//'.LOG',status='UNKNOWN')
103            write(ldbg,"('Dumping variable : ',A10)") varname
104            DO K = kstart3, kend3                               !//AIKEPARDBG
105              write(ldbg,"('K = ',I5)") K                !//AIKEPARDBG
106              write(ldbg,"(12X,14(I3,11X))") (I,i=Istart3,Iend3)  !//AIKEPARDBG
107               DO J = jstart3, Jend3                            !//AIKEPARDBG
108                 write(ldbg,"(I3,')')",ADVANCE="NO") J               !//AIKEPARDBG
109                 DO I = istart3, Iend3                          !//AIKEPARDBG
110                   write(ldbg,"(2X,E12.4)",ADVANCE="NO") gbuf(FUNIJK(I,J,K)) !//AIKEPARDBG
111                 END DO                                       !//AIKEPARDBG
112                 write(ldbg,"(/)")                        !//AIKEPARDBG
113               END DO                                         !//AIKEPARDBG
114            END DO                                            !//AIKEPARDBG
115            close(35)
116           end subroutine prnfield_1d
117     
118     
119           subroutine prnfield_1r (gbuf,varname,flagl)
120     
121           use functions
122           implicit none
123     
124           real, intent(in), dimension(:) :: gbuf
125           character(len=3), intent(in)   :: flagl
126           character(len=*), intent(in)   :: varname
127           integer :: ldbg = 35
128           integer :: i,j,k
129     !      integer, optional, intent(in) :: mroot, idebug
130     
131            OPEN(CONVERT='BIG_ENDIAN',unit=ldbg,file=flagl//fbname//'.LOG',status='UNKNOWN')
132            write(ldbg,"('Dumping variable : ',A10)") varname
133            DO K = kstart3, kend3                               !//AIKEPARDBG
134              write(ldbg,"('K = ',I5)") K                !//AIKEPARDBG
135              write(ldbg,"(12X,14(I3,11X))") (I,i=Istart3,Iend3)  !//AIKEPARDBG
136               DO J = jstart3, Jend3                            !//AIKEPARDBG
137                 write(ldbg,"(I3,')')",ADVANCE="NO") J               !//AIKEPARDBG
138                 DO I = istart3, Iend3                          !//AIKEPARDBG
139                   write(ldbg,"(2X,E12.4)",ADVANCE="NO") gbuf(FUNIJK(I,J,K)) !//AIKEPARDBG
140                 END DO                                       !//AIKEPARDBG
141                 write(ldbg,"(/)")                        !//AIKEPARDBG
142               END DO                                         !//AIKEPARDBG
143            END DO                                            !//AIKEPARDBG
144            close(35)
145           end subroutine prnfield_1r
146     
147           subroutine prnfield_2d (gbuf,varname,flagl)
148     
149           use functions
150           implicit none
151     
152           double precision, intent(in), dimension(:,:) :: gbuf
153           character(len=3), intent(in)   :: flagl
154           character(len=*), intent(in)   :: varname
155           integer :: ldbg = 35
156           integer :: i,j,k
157     !      integer, optional, intent(in) :: mroot, idebug
158     
159            OPEN(CONVERT='BIG_ENDIAN',unit=ldbg,file=flagl//fbname//'.LOG',status='UNKNOWN')
160            write(ldbg,"('Dumping variable : ',A10)") varname
161            DO K = kstart3, kend3                               !//AIKEPARDBG
162              write(ldbg,"('K = ',I5)") K                !//AIKEPARDBG
163              write(ldbg,"(12X,14(I3,11X))") (I,i=Istart3,Iend3)  !//AIKEPARDBG
164               DO J = jstart3, Jend3                            !//AIKEPARDBG
165                 write(ldbg,"(I3,')')",ADVANCE="NO") J               !//AIKEPARDBG
166                 DO I = istart3, Iend3                          !//AIKEPARDBG
167                   write(ldbg,"(2X,E12.4)",ADVANCE="NO") gbuf(FUNIJK(I,J,K),1) !//AIKEPARDBG
168                 END DO                                       !//AIKEPARDBG
169                 write(ldbg,"(/)")                        !//AIKEPARDBG
170               END DO                                         !//AIKEPARDBG
171            END DO                                            !//AIKEPARDBG
172            close(35)
173           end subroutine prnfield_2d
174     
175         end module dbg_util
176