Skip to content

Commit

Permalink
Rearrange code line
Browse files Browse the repository at this point in the history
  • Loading branch information
blackcata committed Jan 20, 2017
1 parent 4b21286 commit 4b77ac2
Show file tree
Hide file tree
Showing 9 changed files with 99 additions and 96 deletions.
22 changes: 11 additions & 11 deletions LES_Filtering_eig33.f90
Original file line number Diff line number Diff line change
@@ -1,11 +1,11 @@
!------------------------------------------------------------------------------!
!
! PROGRAM : LES_Filtering_eig33.f90
!
! PURPOSE : Getting eigenvalue of 3 X 3 matrix
!
! 2016.12.17 K.Noh
!
! !
! PROGRAM : LES_Filtering_eig33.f90 !
! !
! PURPOSE : Getting eigenvalue of 3 X 3 matrix !
! !
! 2016.12.17 K.Noh !
! !
!------------------------------------------------------------------------------!

SUBROUTINE EIG33(A,eig)
Expand Down Expand Up @@ -40,8 +40,8 @@ FUNCTION det(A)
REAL(KIND=8) :: det
REAL(KIND=8) :: A(3,3)

det = A(1,1)*A(2,2)*A(3,3) + A(1,2)*A(2,3)*A(3,1) &
+ A(1,3)*A(2,1)*A(3,2) - A(1,3)*A(2,2)*A(3,1) &
det = A(1,1)*A(2,2)*A(3,3) + A(1,2)*A(2,3)*A(3,1) &
+ A(1,3)*A(2,1)*A(3,2) - A(1,3)*A(2,2)*A(3,1) &
- A(1,2)*A(2,1)*A(3,3) - A(1,1)*A(2,3)*A(3,2)

END FUNCTION det
Expand Down Expand Up @@ -94,11 +94,11 @@ SUBROUTINE CUBIC(a,b,c,d,x)
- 1./(3.*a)*((Q - sqrt(Q**2. - 4.*R**3.))/2.)**(1.0d0/3.0d0)

x(2) = - b/(3.*a) &
+ (1.-i*sqrt(3.))/(6.*a)*((Q + sqrt(Q**2. - 4.*R**3.))/2.)**(1.0d0/3.0d0) &
+ (1.-i*sqrt(3.))/(6.*a)*((Q + sqrt(Q**2. - 4.*R**3.))/2.)**(1.0d0/3.0d0) &
+ (1.+i*sqrt(3.))/(6.*a)*((Q - sqrt(Q**2. - 4.*R**3.))/2.)**(1.0d0/3.0d0)

x(3) = - b/(3.*a) &
+ (1.+i*sqrt(3.))/(6.*a)*((Q + sqrt(Q**2. - 4.*R**3.))/2.)**(1.0d0/3.0d0) &
+ (1.+i*sqrt(3.))/(6.*a)*((Q + sqrt(Q**2. - 4.*R**3.))/2.)**(1.0d0/3.0d0) &
+ (1.-i*sqrt(3.))/(6.*a)*((Q - sqrt(Q**2. - 4.*R**3.))/2.)**(1.0d0/3.0d0)

END SUBROUTINE CUBIC
Expand Down
16 changes: 8 additions & 8 deletions LES_Filtering_filter.f90
Original file line number Diff line number Diff line change
@@ -1,12 +1,12 @@
!------------------------------------------------------------------------------!
!
! PROGRAM : LES_Filtering_filter.f90
!
! PURPOSE : Filter datas from the DNS data for turbulent channel flow
! using Gaussian filter.
!
! 2016.12.07 K.Noh
!
! !
! PROGRAM : LES_Filtering_filter.f90 !
! !
! PURPOSE : Filter datas from the DNS data for turbulent channel flow !
! using Gaussian filter. !
! !
! 2016.12.07 K.Noh !
! !
!------------------------------------------------------------------------------!

SUBROUTINE FILTER
Expand Down
23 changes: 12 additions & 11 deletions LES_Filtering_main.f90
Original file line number Diff line number Diff line change
@@ -1,18 +1,19 @@
!------------------------------------------------------------------------------!
!
! PROGRAM : LES_Filtering_main.f90
!
! PURPOSE : To LES-filter the DNS data for turbulent channel flow.
! (a) : obtain a filtered velocity field by applying Gaussian filter
! (b) : obtain the residual-stress tensor
! (c) : obtain the residual viscosity
! (d) : obtain averaged Smagorinsky coefficient
!
! 2016.12.07 K.Noh
!
! !
! PROGRAM : LES_Filtering_main.f90 !
! !
! PURPOSE : To LES-filter the DNS data for turbulent channel flow. !
! (a) : obtain a filtered velocity by applying Gaussian filter !
! (b) : obtain the residual-stress tensor !
! (c) : obtain the residual viscosity !
! (d) : obtain averaged Smagorinsky coefficient !
! !
! 2016.12.07 K.Noh !
! !
!------------------------------------------------------------------------------!

PROGRAM LES_FILTERING

USE LES_FILTERING_module, &
ONLY : FILTER_OX, VS_ONLY

Expand Down
18 changes: 9 additions & 9 deletions LES_Filtering_module.f90
Original file line number Diff line number Diff line change
@@ -1,18 +1,18 @@
!------------------------------------------------------------------------------!
!
! PROGRAM : LES_Filtering_module.f90
!
! PURPOSE : Module for LES-filter the DNS data for turbulent channel flow.
!
! 2016.12.07 K.Noh
!
! !
! PROGRAM : LES_Filtering_module.f90 !
! !
! PURPOSE : Module for LES-filter the DNS data for turbulent channel flow. !
! !
! 2016.12.07 K.Noh !
! !
!------------------------------------------------------------------------------!

MODULE LES_FILTERING_module

IMPLICIT NONE
INTEGER :: N, Nx, Ny, Nz, Nx_fil, Nz_fil, VS_CASE, FILTER_OX, VS_ONLY,&
Y_ORDER
INTEGER :: N, Nx, Ny, Nz, Nx_fil, Nz_fil, &
VS_CASE, FILTER_OX, VS_ONLY, Y_ORDER
REAL(KIND=8) :: Del,dx,dz,FW,pi,tol
CHARACTER(LEN=65) :: file_name, dir_name, path_name

Expand Down
37 changes: 19 additions & 18 deletions LES_Filtering_output.f90
Original file line number Diff line number Diff line change
@@ -1,13 +1,14 @@
!------------------------------------------------------------------------------!
!
! PROGRAM : LES_Filtering_output.f90
!
! PURPOSE : Write each variables in the RESULT folder.
!
! 2016.12.07 K.Noh
!
! !
! PROGRAM : LES_Filtering_output.f90 !
! !
! PURPOSE : Write each variables in the RESULT folder. !
! !
! 2016.12.07 K.Noh !
! !
!------------------------------------------------------------------------------!
SUBROUTINE OUTPUT

USE LES_FILTERING_module, &
ONLY : J_det

Expand Down Expand Up @@ -166,10 +167,10 @@ SUBROUTINE OUTPUT
WRITE(file_name,"(I3.3,A)")INT(YP(it)),'.S_T_slice.plt'
path_name = TRIM(dir_name)//'/'//TRIM(file_name)
OPEN(100,FILE=path_name,FORM='FORMATTED',POSITION='APPEND')
WRITE(100,*)'VARIABLES = X,Z,S_11,S_12,S_13,S_21,S_22,S_23' &
//',S_31,S_32,S_33,S_Fil_11,S_Fil_12' &
//',S_Fil_13,S_Fil_21,S_Fil_22,S_Fil_23'&
//',S_Fil_31,S_Fil_32,S_Fil_33,S'
WRITE(100,*)'VARIABLES = X,Z,S_11,S_12,S_13,S_21,S_22,S_23' &
//',S_31,S_32,S_33,S_Fil_11,S_Fil_12' &
//',S_Fil_13,S_Fil_21,S_Fil_22,S_Fil_23'&
//',S_Fil_31,S_Fil_32,S_Fil_33,S'
WRITE(100,"(2(A,I3,2X))")' ZONE I = ',Nx,' K = ', Nz

J_loc = J_det(YP(it))
Expand All @@ -190,9 +191,9 @@ SUBROUTINE OUTPUT
file_name = '/S_T_averaged_profile.plt'
path_name = TRIM(dir_name)//TRIM(file_name)
OPEN(100,FILE=path_name,FORM='FORMATTED',POSITION='APPEND')
WRITE(100,*)'VARIABLES = Y,S_11,S_12,S_13,S_21,S_22,S_23' &
//',S_31,S_32,S_33,S_Fil_11,S_Fil_12' &
//',S_Fil_13,S_Fil_21,S_Fil_22,S_Fil_23'&
WRITE(100,*)'VARIABLES = Y,S_11,S_12,S_13,S_21,S_22,S_23' &
//',S_31,S_32,S_33,S_Fil_11,S_Fil_12' &
//',S_Fil_13,S_Fil_21,S_Fil_22,S_Fil_23' &
//',S_Fil_31,S_Fil_32,S_Fil_33,S'

DO j = 2,Ny-1
Expand Down Expand Up @@ -230,10 +231,10 @@ SUBROUTINE OUTPUT
WRITE(file_name,"(I3.3,A)")INT(YP(it)),'.O_T_slice.plt'
path_name = TRIM(dir_name)//'/'//TRIM(file_name)
OPEN(100,FILE=path_name,FORM='FORMATTED',POSITION='APPEND')
WRITE(100,*)'VARIABLES = X,Z,O_11,O_12,O_13,O_21,O_22,O_23' &
//',O_31,O_32,O_33,O_Fil_11,O_Fil_12' &
//',O_Fil_13,O_Fil_21,O_Fil_22,O_Fil_23'&
//',O_Fil_31,O_Fil_32,O_Fil_33,O'
WRITE(100,*)'VARIABLES = X,Z,O_11,O_12,O_13,O_21,O_22,O_23' &
//',O_31,O_32,O_33,O_Fil_11,O_Fil_12' &
//',O_Fil_13,O_Fil_21,O_Fil_22,O_Fil_23'&
//',O_Fil_31,O_Fil_32,O_Fil_33,O'
WRITE(100,"(2(A,I3,2X))")' ZONE I = ',Nx,' K = ', Nz

J_loc = J_det(YP(it))
Expand Down
14 changes: 7 additions & 7 deletions LES_Filtering_read.f90
Original file line number Diff line number Diff line change
@@ -1,11 +1,11 @@
!------------------------------------------------------------------------------!
!
! PROGRAM : LES_Filtering_read.f90
!
! PURPOSE : Reading datas from the DNS data for turbulent channel flow.
!
! 2016.12.07 K.Noh
!
! !
! PROGRAM : LES_Filtering_read.f90 !
! !
! PURPOSE : Reading datas from the DNS data for turbulent channel flow. !
! !
! 2016.12.07 K.Noh !
! !
!------------------------------------------------------------------------------!

SUBROUTINE READ_DNS
Expand Down
17 changes: 9 additions & 8 deletions LES_Filtering_second_filter.f90
Original file line number Diff line number Diff line change
@@ -1,15 +1,16 @@
!------------------------------------------------------------------------------!
!
! PROGRAM : LES_Filtering_filter.f90
!
! PURPOSE : Filter datas from the DNS data for turbulent channel flow
! using Gaussian filter.
!
! 2016.12.07 K.Noh
!
! !
! PROGRAM : LES_Filtering_filter.f90 !
! !
! PURPOSE : Filter datas from the DNS data for turbulent channel flow !
! using Gaussian filter. !
! !
! 2016.12.07 K.Noh !
! !
!------------------------------------------------------------------------------!

SUBROUTINE SECOND_FILTER

USE LES_FILTERING_module, &
ONLY : G, FIND_U_Fil, FIND_U_Fil_2, FIND_dU_Fil_2, FIND_dx

Expand Down
28 changes: 14 additions & 14 deletions LES_Filtering_setup.f90
Original file line number Diff line number Diff line change
@@ -1,11 +1,11 @@
!------------------------------------------------------------------------------!
!
! PROGRAM : LES_Filtering_setup.f90
!
! PURPOSE : Setup for LES-filter the DNS data for turbulent channel flow.
!
! 2016.12.07 K.Noh
!
! !
! PROGRAM : LES_Filtering_setup.f90 !
! !
! PURPOSE : Setup for LES-filter the DNS data for turbulent channel flow. !
! !
! 2016.12.07 K.Noh !
! !
!------------------------------------------------------------------------------!

SUBROUTINE SETUP
Expand All @@ -28,8 +28,8 @@ SUBROUTINE SETUP
!------------------------------------------------------------------!
! Make & Initialize Result folder !
!------------------------------------------------------------------!
file_name = 'instantaneous_velocity_field_re644.plt'
! file_name = 'INSU_XYZ.plt'
! file_name = 'instantaneous_velocity_field_re644.plt'
file_name = 'INSU_XYZ.plt'
dir_name = 'RESULT'

CALL SYSTEM('mkdir '//TRIM(dir_name))
Expand Down Expand Up @@ -61,7 +61,7 @@ SUBROUTINE SETUP
! (c) Only Vortical Structure : 2 !
! !
!------------------------------------------------------------------!
VS_ONLY = 1
VS_ONLY = 2

!------------------------------------------------------------------!
! Vortical Structure methods !
Expand Down Expand Up @@ -90,7 +90,7 @@ SUBROUTINE SETUP
! (b) Descending Order : 1 !
! !
!------------------------------------------------------------------!
Y_ORDER = 1
Y_ORDER = 0

!------------------------------------------------------------------!
! Statistic Slice Point !
Expand All @@ -106,9 +106,9 @@ SUBROUTINE SETUP
!------------------------------------------------------------------!
! Constants for LES filtering !
!------------------------------------------------------------------!
Nx = 288
Ny = 257
Nz = 288
Nx = 128
Ny = 191
Nz = 159

FW = 4 ! Filter width constant
tol = 1e-8 ! Tolerance for the number of nodes in x,z directions
Expand Down
20 changes: 10 additions & 10 deletions Vortical_Structure.f90
Original file line number Diff line number Diff line change
@@ -1,14 +1,14 @@
!------------------------------------------------------------------------------!
!
! PROGRAM : Vortical_Structure.f90
!
! PURPOSE : Make the vortircal structures by using 3 methods
! (a) Q criteria
! (b) Lambda_2 criteria
! (c) Lambda_ci criteria
!
! 2016.12.17 K.Noh
!
! !
! PROGRAM : Vortical_Structure.f90 !
! !
! PURPOSE : Make the vortircal structures by using 3 methods !
! (a) Q criteria !
! (b) Lambda_2 criteria !
! (c) Lambda_ci criteria !
! !
! 2016.12.17 K.Noh !
! !
!------------------------------------------------------------------------------!

SUBROUTINE VORTICAL_STRUCTURE
Expand Down

0 comments on commit 4b77ac2

Please sign in to comment.