-
Notifications
You must be signed in to change notification settings - Fork 1
/
Copy pathreadGridPLOT3D.f90
151 lines (121 loc) · 4.66 KB
/
readGridPLOT3D.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
! ******************************************************************************
!
! $Id: readGridPLOT3D.f90,v 1.1 2005/03/05 17:25:53 haselbac Exp $
!
! Filename: readGridPLOT3D.F90
!
! Purpose: Read 2d grid file in PLOT3D format.
!
! Description: None.
!
! Input: None.
!
! Output: None.
!
! Notes: None.
!
! Author: Andreas Haselbacher
!
! Copyright: (c) 2004 by the University of Illinois
!
! RCS Revision history:
!
! $Log: readGridPLOT3D.f90,v $
! Revision 1.1 2005/03/05 17:25:53 haselbac
! Initial revision
!
! Revision 1.2 2005/02/18 20:38:46 haselbac
! Added reading of proper PLOT3D grids
!
! Revision 1.1 2004/12/27 15:35:05 haselbac
! Initial revision
!
! Revision 1.1 2004/12/27 15:05:24 haselbac
! Initial revision
!
! ******************************************************************************
SUBROUTINE readGridPLOT3D
USE modError
USE modGlobals
USE modGrid
IMPLICIT NONE
! ******************************************************************************
! Declarations and definitions
! ******************************************************************************
! ==============================================================================
! Local variables
! ==============================================================================
INTEGER :: dummyInteger,i,iFile,ix,iy,iz,nx,ny,nz
CHARACTER :: choice
CHARACTER*(MAX_STRING_LEN) :: iFileName
! ******************************************************************************
! Start
! ******************************************************************************
WRITE(STDOUT,'(/,1X,A)') 'Enter file name:'
READ(STDIN,'(A)') iFileName
WRITE(STDOUT,'(/)')
iFile = FILE_UNIT_GRID_INPUT
OPEN(iFile,FILE=iFileName,FORM="FORMATTED",STATUS="OLD",IOSTAT=errorFlag)
IF ( errorFlag /= NO_ERROR ) THEN
CALL errorHandling(FILE_OPEN_ERROR,iFileName,errorFlag)
END IF ! errorFlag
WRITE(STDOUT,'(1X,A)') 'Reading grid file in PLOT3D format...'
! ******************************************************************************
! Read grid file
! ******************************************************************************
! For AGARD 445.6 wing file from Lee-Rausch
! READ(iFile,*) dummyInteger
! READ(iFile,*) gridPLOT3D%nx
! READ(iFile,*) gridPLOT3D%ny
! READ(iFile,*) gridPLOT3D%nz
READ(iFile,*) gridPLOT3D%nx,gridPLOT3D%ny,gridPLOT3D%nz
WRITE(STDOUT,'(3X,A,3(1X,I3))') 'Dimensions:',gridPLOT3D%nx, &
gridPLOT3D%ny, &
gridPLOT3D%nz
IF ( gridPLOT3D%nx == 1 .OR. gridPLOT3D%ny == 1 .OR. gridPLOT3D%nz == 1 ) THEN
gridPLOT3D%nCells = MAX(gridPLOT3D%nx-1,1)* &
MAX(gridPLOT3D%ny-1,1)* &
MAX(gridPLOT3D%nz-1,1)
is2d = .TRUE.
ELSE
gridPLOT3D%nCells = (gridPLOT3D%nx-1)*(gridPLOT3D%ny-1)*(gridPLOT3D%nz-1)
is2d = .FALSE.
END IF ! gridPLOT3D%nx
gridPLOT3D%nVert = gridPLOT3D%nx*gridPLOT3D%ny*gridPLOT3D%nz
WRITE(STDOUT,'(3X,A,1X,I6)') 'Number of vertices:',gridPLOT3D%nVert
WRITE(STDOUT,'(3X,A,1X,I6)') 'Number of cells:',gridPLOT3D%nCells
! ==============================================================================
! Read coordinates
! ==============================================================================
ALLOCATE(gridPLOT3D%xyz(3,gridPLOT3D%nx,gridPLOT3D%ny,gridPLOT3D%nz), &
STAT=errorFlag)
IF ( errorFlag /= NO_ERROR ) THEN
CALL errorHandling(ALLOCATE_ERROR,'gridPLOT3D%xyz',errorFlag)
END IF ! errorFlag
WRITE(STDOUT,'(3X,A)') 'Coordinates...'
! For AGARD 445.6 wing file from Lee-Rausch
! DO i = 1,3
! DO iz = 1,gridPLOT3D%nz
! DO iy = 1,gridPLOT3D%ny
! DO ix = 1,gridPLOT3D%nx
! READ(iFile,*) gridPLOT3D%xyz(i,ix,iy,iz)
! END DO ! ix
! END DO ! iy
! END DO ! iz
! END DO ! i
READ(iFile,*) ((((gridPLOT3D%xyz(i,ix,iy,iz),ix=1,gridPLOT3D%nx), &
iy=1,gridPLOT3D%ny), &
iz=1,gridPLOT3D%nz), &
i=1,3)
! ******************************************************************************
! End
! ******************************************************************************
CLOSE(iFile,IOSTAT=errorFlag)
IF ( errorFlag /= NO_ERROR ) THEN
CALL errorHandling(FILE_CLOSE_ERROR,iFileName,errorFlag)
END IF ! errorFlag
WRITE(STDOUT,'(1X,A,/)') 'Grid file read successfully.'
! ******************************************************************************
! End
! ******************************************************************************
END SUBROUTINE readGridPLOT3D