CFD Online Logo CFD Online URL
www.cfd-online.com
[Sponsors]
Home > Wiki > Geom 1.f90

Geom 1.f90

From CFD-Wiki

(Difference between revisions)
Jump to: navigation, search
 
(3 intermediate revisions not shown)
Line 1: Line 1:
 +
<pre>
 +
 +
!Sample program for solving Smith-Hutton Test using different schemes
 +
!of covective terms approximation -  Geometry computing modul
 +
!Copyright (C) 2005  Michail Kirichkov
 +
 +
!This program 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 2
 +
!of the License, or (at your option) any later version.
 +
 +
!This program 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 this program; if not, write to the Free Software
 +
!Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301, USA.
 +
 +
!**********************************************************************
Subroutine Geom
Subroutine Geom
Line 4: Line 25:
! calculation Xp,Yp
! calculation Xp,Yp
-
 
! ------------------------------------------------------------------------
! ------------------------------------------------------------------------
-
do  2 I=2,NXmax
+
    do  2 I=2,NXmax
-
 
+
     do  2 J=2,NYmax
     do  2 J=2,NYmax
  Xp(I,J)=( X(i-1,j-1) + X(i-1,j  ) + &
  Xp(I,J)=( X(i-1,j-1) + X(i-1,j  ) + &
-
            X(i  ,j  ) + X(i  ,j-1)      ) * 0.25  
+
                  X(i  ,j  ) + X(i  ,j-1)      ) * 0.25  
    Yp(I,J)=(  Y(i-1,j-1) + Y(i-1,j  ) + &
    Yp(I,J)=(  Y(i-1,j-1) + Y(i-1,j  ) + &
-
              Y(i  ,j  ) + Y(i  ,j-1)    ) * 0.25  
+
                Y(i  ,j  ) + Y(i  ,j-1)    ) * 0.25  
2 continue
2 continue
-
 
! ------------------------------------------------------------------------
! ------------------------------------------------------------------------
 +
do 4 I=2,NXmax
do 4 I=2,NXmax
Xp(i,1      ) = ( X(i  ,1    ) + X(i-1,1    ) ) * 0.5
Xp(i,1      ) = ( X(i  ,1    ) + X(i-1,1    ) ) * 0.5
-
 
Xp(i,NYmax+1) = ( X(i  ,NYmax) + X(i-1,NYmax) ) * 0.5
Xp(i,NYmax+1) = ( X(i  ,NYmax) + X(i-1,NYmax) ) * 0.5
-
 
Yp(i,1      ) = ( Y(i  ,1    ) + Y(i-1,1    ) ) * 0.5
Yp(i,1      ) = ( Y(i  ,1    ) + Y(i-1,1    ) ) * 0.5
-
 
Yp(i,NYmax+1) = ( Y(i  ,NYmax) + Y(i-1,NYmax) ) * 0.5
Yp(i,NYmax+1) = ( Y(i  ,NYmax) + Y(i-1,NYmax) ) * 0.5
4 continue  
4 continue  
-
 
  ! ------------------------------------------------------------------------
  ! ------------------------------------------------------------------------
-
 
Xp(1      ,      1) = X(    1,    1)
Xp(1      ,      1) = X(    1,    1)
-
 
Xp(NXmax+1,      1) = X(NXmax,    1)
Xp(NXmax+1,      1) = X(NXmax,    1)
-
 
Xp(      1,NYmax+1) = X(    1,NYmax)
Xp(      1,NYmax+1) = X(    1,NYmax)
-
 
Xp(NXmax+1,NYmax+1) = X(NXmax,NYmax)
Xp(NXmax+1,NYmax+1) = X(NXmax,NYmax)
Yp(1      ,      1) = Y(    1,    1)
Yp(1      ,      1) = Y(    1,    1)
-
 
+
        Yp(NXmax+1,      1) = Y(NXmax,    1)
-
Yp(NXmax+1,      1) = Y(NXmax,    1)
+
-
 
+
Yp(      1,NYmax+1) = Y(    1,NYmax)
Yp(      1,NYmax+1) = Y(    1,NYmax)
-
 
Yp(NXmax+1,NYmax+1) = Y(NXmax,NYmax)
Yp(NXmax+1,NYmax+1) = Y(NXmax,NYmax)
-
 
!--------------------------------------------------------------------------
!--------------------------------------------------------------------------
! ------------------------------------------------------------------------
! ------------------------------------------------------------------------
Line 58: Line 65:
Yp(1      ,j ) = ( Y(1    ,j) + Y(1    ,j-1) ) * 0.5
Yp(1      ,j ) = ( Y(1    ,j) + Y(1    ,j-1) ) * 0.5
-
 
Yp(NXmax+1,j ) = ( Y(NXmax ,j) + Y(NXmax,j-1) ) * 0.5
Yp(NXmax+1,j ) = ( Y(NXmax ,j) + Y(NXmax,j-1) ) * 0.5
-
 
Xp(1      ,j ) = ( X(1    ,j) + X(1    ,j-1) ) * 0.5
Xp(1      ,j ) = ( X(1    ,j) + X(1    ,j-1) ) * 0.5
-
 
Xp(NXmax+1,j ) = ( X(NXmax ,j) + X(NXmax,j-1) ) * 0.5
Xp(NXmax+1,j ) = ( X(NXmax ,j) + X(NXmax,j-1) ) * 0.5
5 continue  
5 continue  
-
 
!--------------------------------------------------------------------------
!--------------------------------------------------------------------------
 +
! ------------------------------------------------------------------------
-
! ------------------------------------------------------------------------
 
! Xi (vertical)  
! Xi (vertical)  
Do 101 I=1,NXmax   
Do 101 I=1,NXmax   
-
 
Do 101 J=1,NYmax-1
Do 101 J=1,NYmax-1
X_xi(I,J) = X(i  ,j+1) - X(i  ,j  )
X_xi(I,J) = X(i  ,j+1) - X(i  ,j  )
-
 
Y_xi(I,J) = Y(i  ,j+1) - Y(i  ,j  )  
Y_xi(I,J) = Y(i  ,j+1) - Y(i  ,j  )  
Line 85: Line 86:
Do 102 I=1,NXmax-1
Do 102 I=1,NXmax-1
-
 
Do 102 J=1,NYmax   
Do 102 J=1,NYmax   
X_et(I,J) = X(i+1,j  ) - X(i  ,j  )
X_et(I,J) = X(i+1,j  ) - X(i  ,j  )
-
 
Y_et(I,J) = Y(i+1,j  ) - Y(i  ,j  )
Y_et(I,J) = Y(i+1,j  ) - Y(i  ,j  )
Line 95: Line 94:
!--------------------------------------------------------------------------
!--------------------------------------------------------------------------
-
 
! ------------------------------------------------------------------------
! ------------------------------------------------------------------------
Line 101: Line 99:
Do 201 I=1,NXmaxP  
Do 201 I=1,NXmaxP  
-
 
Do 201 J=1,NYmax
Do 201 J=1,NYmax
Del_X_xi(i  ,j  ) =  Xp(i  ,j+1) - Xp(i  ,j  )
Del_X_xi(i  ,j  ) =  Xp(i  ,j+1) - Xp(i  ,j  )
-
 
Del_Y_xi(i  ,j  ) =  Yp(i  ,j+1) - Yp(i  ,j  )  
Del_Y_xi(i  ,j  ) =  Yp(i  ,j+1) - Yp(i  ,j  )  
201 continue
201 continue
-
 
! Eta (horisontal)  
! Eta (horisontal)  
Do 202 I=1,NXmax  
Do 202 I=1,NXmax  
-
 
Do 202 J=1,NYmaxP
Do 202 J=1,NYmaxP
 
 
Del_X_et(i  ,j  ) =  Xp(i+1,j  ) - Xp(i  ,j  )  
Del_X_et(i  ,j  ) =  Xp(i+1,j  ) - Xp(i  ,j  )  
-
 
Del_Y_et(i  ,j  ) =  Yp(i+1,j  ) - Yp(i  ,j  )  
Del_Y_et(i  ,j  ) =  Yp(i+1,j  ) - Yp(i  ,j  )  
Line 124: Line 117:
!--------------------------------------------------------------------------
!--------------------------------------------------------------------------
-
 
! ------------------------------------------------------------------------
! ------------------------------------------------------------------------
Return
Return
-
 
+
End</pre>
-
End
+

Latest revision as of 15:12, 21 September 2005


!Sample program for solving Smith-Hutton Test using different schemes 
!of covective terms approximation -  Geometry computing modul
!Copyright (C) 2005  Michail Kirichkov

!This program 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 2
!of the License, or (at your option) any later version.

!This program 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 this program; if not, write to the Free Software
!Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301, USA.

!**********************************************************************
Subroutine Geom

include 'icomm_1.f90'

! calculation Xp,Yp
! ------------------------------------------------------------------------ 	
	
    do  2 I=2,NXmax
    do  2 J=2,NYmax

	  	Xp(I,J)=( X(i-1,j-1) + X(i-1,j  ) + &

      	  	          X(i  ,j  ) + X(i  ,j-1)      ) * 0.25 

	    Yp(I,J)=(  Y(i-1,j-1) + Y(i-1,j  ) + &

         	        Y(i  ,j  ) + Y(i  ,j-1)     ) * 0.25 

	2 continue
! ------------------------------------------------------------------------ 	

	do 4 I=2,NXmax

		Xp(i,1      ) = ( X(i  ,1    ) + X(i-1,1    ) ) * 0.5
		Xp(i,NYmax+1) = ( X(i  ,NYmax) + X(i-1,NYmax) ) * 0.5

		Yp(i,1      ) = ( Y(i  ,1    ) + Y(i-1,1    ) ) * 0.5
		Yp(i,NYmax+1) = ( Y(i  ,NYmax) + Y(i-1,NYmax) ) * 0.5

	4 continue 
 ! ------------------------------------------------------------------------ 	
	Xp(1      ,      1) = X(    1,    1)
	Xp(NXmax+1,      1) = X(NXmax,    1)
	Xp(      1,NYmax+1) = X(    1,NYmax)
	Xp(NXmax+1,NYmax+1) = X(NXmax,NYmax)

	Yp(1      ,      1) = Y(    1,    1)
        Yp(NXmax+1,      1) = Y(NXmax,    1)
	Yp(      1,NYmax+1) = Y(    1,NYmax)
	Yp(NXmax+1,NYmax+1) = Y(NXmax,NYmax)
!--------------------------------------------------------------------------
! ------------------------------------------------------------------------ 	
	do 5 J=2,NYmax

		Yp(1      ,j ) = ( Y(1     ,j) + Y(1    ,j-1) ) * 0.5
		Yp(NXmax+1,j ) = ( Y(NXmax ,j) + Y(NXmax,j-1) ) * 0.5
		Xp(1      ,j ) = ( X(1     ,j) + X(1    ,j-1) ) * 0.5
		Xp(NXmax+1,j ) = ( X(NXmax ,j) + X(NXmax,j-1) ) * 0.5

	5 continue 
!--------------------------------------------------------------------------
! ------------------------------------------------------------------------ 	

! Xi (vertical) 
	
	Do 101 I=1,NXmax  
	Do 101 J=1,NYmax-1

		X_xi(I,J) = X(i  ,j+1) - X(i  ,j  )
		Y_xi(I,J) = Y(i  ,j+1) - Y(i  ,j  ) 

	101 continue 

! Eta (horisontal) 

	Do 102 I=1,NXmax-1
	Do 102 J=1,NYmax  

		X_et(I,J) = X(i+1,j  ) - X(i  ,j  )
		Y_et(I,J) = Y(i+1,j  ) - Y(i  ,j  )

	102 continue

!--------------------------------------------------------------------------
! ------------------------------------------------------------------------ 	

! Xi (vertical) 

	Do 201 I=1,NXmaxP 
	Do 201 J=1,NYmax

		Del_X_xi(i  ,j  ) =  Xp(i  ,j+1) - Xp(i  ,j  )
		Del_Y_xi(i  ,j  ) =  Yp(i  ,j+1) - Yp(i  ,j  ) 

	201 continue

! Eta (horisontal) 
	
	Do 202 I=1,NXmax 
	Do 202 J=1,NYmaxP
		 
		Del_X_et(i  ,j  ) =  Xp(i+1,j  ) - Xp(i  ,j  ) 
		Del_Y_et(i  ,j  ) =  Yp(i+1,j  ) - Yp(i  ,j  ) 

	202 continue

!--------------------------------------------------------------------------
! ------------------------------------------------------------------------ 	

Return
End
My wiki