-
Notifications
You must be signed in to change notification settings - Fork 1
/
visit.f90
127 lines (107 loc) · 4.14 KB
/
visit.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
!Crown Copyright 2014 AWE.
!
! This file is part of TeaLeaf.
!
! TeaLeaf is free software: you can redistribute it and/or modify it under
! the terms of the GNU General Public License as published by the
! Free Software Foundation, either version 3 of the License, or (at your option)
! any later version.
!
! TeaLeaf is distributed in the hope that it will be useful, but
! WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
! FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more
! details.
!
! You should have received a copy of the GNU General Public License along with
! TeaLeaf. If not, see http://www.gnu.org/licenses/.
!> @brief Generates graphics output files.
!> @author David Beckingsale, Wayne Gaudin
!> @details The field data over all mesh chunks is written to a .vtk files and
!> the .visit file is written that defines the time for each set of vtk files.
SUBROUTINE visit
USE tea_module
USE update_halo_module
IMPLICIT NONE
INTEGER :: j,k,c,err,get_unit,u,dummy
INTEGER :: nxc,nyc,nxv,nyv,nblocks
REAL(KIND=8) :: temp_var
CHARACTER(len=80) :: name
CHARACTER(len=10) :: chunk_name,step_name
CHARACTER(len=90) :: filename
LOGICAL, SAVE :: first_call=.TRUE.
INTEGER :: fields(NUM_FIELDS)
REAL(KIND=8) :: kernel_time,timer
name = 'tea'
IF(first_call) THEN
IF ( parallel%boss ) THEN
nblocks=number_of_chunks
filename = "tea.visit"
u=get_unit(dummy)
OPEN(UNIT=u,FILE=filename,STATUS='UNKNOWN',IOSTAT=err)
WRITE(u,'(a,i5)')'!NBLOCKS ',nblocks
CLOSE(u)
ENDIF
first_call=.FALSE.
ENDIF
IF ( parallel%boss ) THEN
filename = "tea.visit"
u=get_unit(dummy)
OPEN(UNIT=u,FILE=filename,STATUS='UNKNOWN',POSITION='APPEND',IOSTAT=err)
DO c = 1, number_of_chunks
WRITE(chunk_name, '(i6)') c+100000
chunk_name(1:1) = "."
WRITE(step_name, '(i6)') step+100000
step_name(1:1) = "."
filename = trim(trim(name) //trim(chunk_name)//trim(step_name))//".vtk"
WRITE(u,'(a)')TRIM(filename)
ENDDO
CLOSE(u)
ENDIF
IF(profiler_on) kernel_time=timer()
DO c = 1, chunks_per_task
IF(chunks(c)%task.EQ.parallel%task) THEN
nxc=chunks(c)%field%x_max-chunks(c)%field%x_min+1
nyc=chunks(c)%field%y_max-chunks(c)%field%y_min+1
nxv=nxc+1
nyv=nyc+1
WRITE(chunk_name, '(i6)') parallel%task+100001
chunk_name(1:1) = "."
WRITE(step_name, '(i6)') step+100000
step_name(1:1) = "."
filename = trim(trim(name) //trim(chunk_name)//trim(step_name))//".vtk"
u=get_unit(dummy)
OPEN(UNIT=u,FILE=filename,STATUS='UNKNOWN',IOSTAT=err)
WRITE(u,'(a)')'# vtk DataFile Version 3.0'
WRITE(u,'(a)')'vtk output'
WRITE(u,'(a)')'ASCII'
WRITE(u,'(a)')'DATASET RECTILINEAR_GRID'
WRITE(u,'(a,2i12,a)')'DIMENSIONS',nxv,nyv,' 1'
WRITE(u,'(a,i5,a)')'X_COORDINATES ',nxv,' double'
DO j=chunks(c)%field%x_min,chunks(c)%field%x_max+1
WRITE(u,'(e12.4)')chunks(c)%field%vertexx(j)
ENDDO
WRITE(u,'(a,i5,a)')'Y_COORDINATES ',nyv,' double'
DO k=chunks(c)%field%y_min,chunks(c)%field%y_max+1
WRITE(u,'(e12.4)')chunks(c)%field%vertexy(k)
ENDDO
WRITE(u,'(a)')'Z_COORDINATES 1 double'
WRITE(u,'(a)')'0'
WRITE(u,'(a,i20)')'CELL_DATA ',nxc*nyc
WRITE(u,'(a)')'FIELD FieldData 3'
WRITE(u,'(a,i20,a)')'density 1 ',nxc*nyc,' double'
DO k=chunks(c)%field%y_min,chunks(c)%field%y_max
WRITE(u,'(e12.4)')(chunks(c)%field%density(j,k),j=chunks(c)%field%x_min,chunks(c)%field%x_max)
ENDDO
WRITE(u,'(a,i20,a)')'energy 1 ',nxc*nyc,' double'
DO k=chunks(c)%field%y_min,chunks(c)%field%y_max
WRITE(u,'(e12.4)')(chunks(c)%field%energy0(j,k),j=chunks(c)%field%x_min,chunks(c)%field%x_max)
ENDDO
WRITE(u,'(a,i20,a)')'temperature 1 ',nxc*nyc,' double'
DO k=chunks(c)%field%y_min,chunks(c)%field%y_max
WRITE(u,'(e12.4)')(chunks(c)%field%u(j,k),j=chunks(c)%field%x_min,chunks(c)%field%x_max)
ENDDO
CLOSE(u)
ENDIF
ENDDO
IF(profiler_on) profiler%visit=profiler%visit+(timer()-kernel_time)
END SUBROUTINE visit