Skip to content

Commit

Permalink
Alternative approach for case support.
Browse files Browse the repository at this point in the history
  • Loading branch information
semi-h committed Oct 9, 2024
1 parent 6e9f344 commit dc5f923
Show file tree
Hide file tree
Showing 4 changed files with 70 additions and 2 deletions.
1 change: 1 addition & 0 deletions src/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ set(SRC
tdsops.f90
time_integrator.f90
vector_calculus.f90
case/tgv.f90
omp/backend.f90
omp/common.f90
omp/kernels/distributed.f90
Expand Down
51 changes: 51 additions & 0 deletions src/case/tgv.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,51 @@
module m_case_tgv
use iso_fortran_env, only: stderr => error_unit
use mpi

use m_allocator, only: allocator_t, field_t
use m_base_backend, only: base_backend_t
use m_common, only: dp
use m_mesh, only: mesh_t
use m_solver, only: solver_t, init
use m_tdsops, only: tdsops_t, dirps_t
use m_time_integrator, only: time_intg_t
use m_vector_calculus, only: vector_calculus_t

implicit none

type, extends(solver_t) :: case_tgv_t
contains
procedure :: post_transeq => post_transeq_tgv
end type case_tgv_t

interface case_tgv_t
module procedure case_tgv_init
end interface case_tgv_t

contains


function case_tgv_init(backend, mesh, host_allocator) result(solver)
implicit none

class(base_backend_t), target, intent(inout) :: backend
type(mesh_t), target, intent(inout) :: mesh
type(allocator_t), target, intent(inout) :: host_allocator
type(case_tgv_t) :: solver

solver%solver_t = init(backend, mesh, host_allocator)
end function case_tgv_init

subroutine post_transeq_tgv(self, du, dv, dw)
implicit none

class(case_tgv_t) :: self
class(field_t), intent(inout) :: du, dv, dw

! first call the parent class
call self%solver_t%post_transeq(du, dv, dw)

print *, 'post_transeq for the tgv case'
end subroutine post_transeq_tgv

end module m_case_tgv
13 changes: 13 additions & 0 deletions src/solver.f90
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,7 @@ module m_solver
procedure(poisson_solver), pointer :: poisson => null()
contains
procedure :: transeq
procedure :: post_transeq
procedure :: pressure_correction
procedure :: divergence_v2p
procedure :: gradient_p2v
Expand Down Expand Up @@ -318,6 +319,16 @@ subroutine transeq(self, du, dv, dw, u, v, w)

end subroutine transeq

subroutine post_transeq(self, du, dv, dw)
implicit none

class(solver_t) :: self
class(field_t), intent(inout) :: du, dv, dw

print*, 'base post_transeq'

end subroutine post_transeq

subroutine divergence_v2p(self, div_u, u, v, w)
!! Wrapper for divergence_v2p
implicit none
Expand Down Expand Up @@ -518,6 +529,8 @@ subroutine run(self)

call self%transeq(du, dv, dw, self%u, self%v, self%w)

call self%post_transeq(du, dv, dw)

! time integration
call self%time_integrator%step(self%u, self%v, self%w, &
du, dv, dw, self%dt)
Expand Down
7 changes: 5 additions & 2 deletions src/xcompact.f90
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ program xcompact
use m_solver, only: solver_t
use m_tdsops, only: tdsops_t
use m_mesh
use m_case_tgv, only: case_tgv_t

#ifdef CUDA
use m_cuda_allocator
Expand All @@ -24,7 +25,7 @@ program xcompact
class(allocator_t), pointer :: allocator
type(mesh_t) :: mesh
type(allocator_t), pointer :: host_allocator
type(solver_t) :: solver
class(solver_t), allocatable :: solver

#ifdef CUDA
type(cuda_backend_t), target :: cuda_backend
Expand Down Expand Up @@ -99,7 +100,9 @@ program xcompact
if (nrank == 0) print *, 'OpenMP backend instantiated'
#endif

solver = solver_t(backend, mesh, host_allocator)
!solver = solver_t(backend, mesh, host_allocator)
!allocate(solver :: case_tgv_t)
solver = case_tgv_t(backend, mesh, host_allocator)
if (nrank == 0) print *, 'solver instantiated'

call cpu_time(t_start)
Expand Down

0 comments on commit dc5f923

Please sign in to comment.