V3FIT
bmw_run.f
1 !*******************************************************************************
5 !
6 ! Note separating the Doxygen comment block here so detailed decription is
7 ! found in the Module not the file.
8 !
26 !*******************************************************************************
27  MODULE bmw_run
28  USE bmw_context
30  use, INTRINSIC :: iso_fortran_env, only : output_unit
31  USE bmw_state_flags
32 
33  IMPLICIT NONE
34 
35  CONTAINS
36 
37 !-------------------------------------------------------------------------------
55 !-------------------------------------------------------------------------------
56  SUBROUTINE bmw_exec(mgrid_file_name, wout_file_name, &
57  & r_grid, z_grid, dphi, surf_num, &
58  & A_r, A_p, A_z)
59  USE read_wout_mod, ONLY: nfp_vmec=>nfp
60  USE island_params, ONLY: nfp_i
61 
62 ! dummy variables
63  CHARACTER (len=*), INTENT(in) :: mgrid_file_name
64  CHARACTER (len=*), INTENT(in) :: wout_file_name
65  REAL (rprec), DIMENSION(:,:,:), INTENT(in) :: r_grid
66  REAL (rprec), DIMENSION(:,:,:), INTENT(in) :: z_grid
67  REAL (rprec), INTENT(in) :: dphi
68  INTEGER, INTENT(in) :: surf_num
69  REAL (rprec), DIMENSION(:,:,:), INTENT(out) :: A_r
70  REAL (rprec), DIMENSION(:,:,:), INTENT(out) :: A_p
71  REAL (rprec), DIMENSION(:,:,:), INTENT(out) :: A_z
72 
73 ! local variables
74  TYPE (bmw_parallel_context_class), POINTER :: parallel => null()
75  TYPE (bmw_context_class), POINTER :: context => null()
76  TYPE (bmw_commandline_parser_class), POINTER :: &
77  & cl_parser => null()
78  INTEGER :: flags
79  INTEGER :: num_p
80  INTEGER :: status
81  INTEGER :: i
82 
83 ! Start of executable code
84  CALL profiler_construct
85 
86  parallel => bmw_parallel_context_construct(mpi_comm_world)
87  flags = bmw_state_flags_off
88 
89  CALL bmw_parallel_context_set_threads(parallel, -1)
90  CALL bmw_parallel_context_report(parallel, output_unit)
91 
92 ! BMW uses num_p to set the number of grid points in for the primed grid. In
93 ! doing so, it mutliplies by the number of field periods in the mgrid file. If
94 ! using a user defined number of field periods that is less than the amount in
95 ! in mgrid, we need to scale num_p.
96  num_p = SIZE(a_r, 2)*2/(nfp_vmec/nfp_i)
97  context => bmw_context_construct(mgrid_file_name, &
98  & wout_file_name, '', flags, &
99  & num_p, parallel, output_unit)
100 
101  CALL bmw_context_set_up_grid(context, &
102  & r_grid(:,:,surf_num:surf_num), &
103  & z_grid(:,:,surf_num:surf_num), &
104  & dphi, parallel, output_unit)
105 
106  a_r = context%up_grid%a_r
107  a_p = context%up_grid%a_p
108  a_z = context%up_grid%a_z
109 
110  CALL bmw_context_destruct(context)
111  CALL profiler_destruct
112 
113  CALL bmw_parallel_context_destruct(parallel &
114 #if defined (MPI_OPT)
115  & ,.false. &
116 #endif
117  & )
118 
119 1000 FORMAT('BMW ',i4,' Series.')
120 
121  END SUBROUTINE
122 
123  END MODULE
bmw_context::bmw_context_destruct
subroutine bmw_context_destruct(this)
Deconstruct a bmw_context_class object.
Definition: bmw_context.f:140
bmw_run
BMW is a code for extending fields belond the VMEC domain in a manner that ensures divergence free fi...
Definition: bmw_run.f:27
bmw_state_flags
Contains parameters defining the bit positions for flags that mark different options.
Definition: bmw_state_flags.f:11
bmw_commandline_parser
Defines the base class of the type bmw_commandline_parser_class.
Definition: bmw_commandline_parser.f:57
island_params
This file contains fix parameters related to the computational grids.
Definition: island_params.f90:10
bmw_state_flags::bmw_state_flags_off
integer, parameter bmw_state_flags_off
Clear all flags.
Definition: bmw_state_flags.f:26
bmw_context
Defines the base class of the type bmw_context_class. This contains the state variables needed by BMW...
Definition: bmw_context.f:11
bmw_context::bmw_context_construct
type(bmw_context_class) function, pointer bmw_context_construct(mgrid_file_name, wout_file_name, siesta_file_name, flags, num_p, parallel, io_unit)
Construct a bmw_context_class object.
Definition: bmw_context.f:72
bmw_context::bmw_context_set_up_grid
Interface to set the unprimed grid.
Definition: bmw_context.f:46