source: trunk/00FlowSolve_PL/PROJECTS/NEW_SRC/cfd.f90

Last change on this file was 11, checked in by xlvlod, 18 years ago

Import initial

File size: 3.0 KB
Line 
1program cfd                                 ! XZ version
2
3#define DEBUG_LEVEL 1
4! Module definitions in cfd_modules.F90
5use  grid_info
6use  mpi_parameters
7use  dimensional_scales
8use  boundary_information
9use  pde_parameters
10use  dependent_variables
11use  intermediate_variables
12use  counters_flags_etc
13use  immersed_boundary
14use  user_parameters
15use  mpi_times
16
17implicit none
18
19include 'mpif.h'
20include '../input/problem_size.h'
21
22!%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% ONLY EXECUTABLE STATEMENTS BELOW HERE  %%%%%%%%%%%%%%%%%%%
23
24 include 'start_MPI.h'
25
26 call MPI_Time(0)
27
28!!! LAPACK_FLAG='double'
29 LAPACK_FLAG='single'
30 call initialize_grids(0)              ! initialize spatial grids at all discretization levels
31 call initialize_cfd                   ! basic setup, read input parameters etc.
32 call initialize_user                  ! e.g. user can set nontrivial initial conditions
33
34
35 print*,'loop...'
36 
37 do istep=istart,iend                ! MAIN TIME STEPPING LOOP
38  t = t_start + (istep-istart)*dt    ! dimensionless time
39
40  call save                          ! write restart files {i_restart}
41!  print*,'...  call save ...'
42!  call maxim
43
44  call write3d_netcdf                ! output 3d fields {i_full_fields}
45!  if ( prob_eos == 'yes' ) then 
46!   print*,'...  call write3d_netcdf ...'
47!   call maxim
48!   print*,' ARRET IMPOSE ! '
49!   call mpi_barrier(comm,ierr)
50!   call MPI_Time(1)
51!   call mpi_finalize(ierr)
52!   STOP
53!  endif
54
55  call rhs                           ! compute rhs for U,v,W & pd neglecting
56  !print*,'...  call rhs ...'
57  !call maxim
58    ! only pressure gradients
59
60  call time_step                     ! time step w/o pressure gradient => u_star
61  !print*,'...  call time_step ...'
62  !call maxim
63 
64  call divergence                    ! compute "divergence" of u_star -> div_u
65  !print*,'...  call divergence ...'
66  !call maxim
67 
68  call set_rhs_for_pressure          ! set the rhs for pressure equation L[p]=b
69  !print*,'...  call set_rhs_for_pressure ...'
70  !call maxim
71
72  call psolve_xy_periodic            ! solve pressure using xyfft & direct solve in z
73  !print*,'...  call psolve_xy_periodic ...'
74  !call maxim
75
76   
77  call gradient                      ! compute pressure "gradient"
78  !print*,'...  call gradient ...'
79  !call maxim
80 
81  call project                       ! project u_star onto div-free subspace =>[U,v,W]
82  !print*,'...  call project ...'
83  !call maxim
84 
85  call filter                        ! compact spatial filtering(i_filter,alpha)
86  !print*,'...  call filter ...'
87  !call maxim
88 
89  call set_BC_values                 ! compute u boundary values for faces 1:6
90  !print*,'...  call set_BC_values ...'
91  !call maxim
92
93  call apply_BCs                     ! impose exact satisfaction of BCs
94  !print*,'...  call apply_BCs ...'
95  !call maxim
96
97  call user_BCs                      ! impose user-defined
98  !print*,'...  call user_BCs ...'
99  !call maxim
100
101  include 'toggle.h'                 ! toggle counters, indices etc
102  !print*,'...  call toggle.h'
103
104  call maxim
105
106enddo
107
108 call mpi_barrier(comm,ierr)
109
110 call MPI_Time(1)
111
112 call mpi_finalize(ierr)
113
114end program cfd
Note: See TracBrowser for help on using the repository browser.