|
V3FIT
|
Go to the documentation of this file.
70 & siesta_file_name, flags, num_p, &
72 USE read_wout_mod,
Only: read_wout_file, extcur
79 CHARACTER (len=*),
INTENT(in) :: mgrid_file_name
80 CHARACTER (len=*),
INTENT(in) :: wout_file_name
81 CHARACTER (len=*),
INTENT(in) :: siesta_file_name
82 INTEGER,
INTENT(in) :: flags
83 INTEGER,
INTENT(inout) :: num_p
85 INTEGER,
INTENT(in) :: io_unit
88 REAL (rprec) :: start_time
92 start_time = profiler_get_start_time()
96 CALL read_wout_file(wout_file_name, status)
97 IF (status .ne. 0)
THEN
98 IF (parallel%offset .eq. 0)
THEN
99 WRITE (io_unit,1000) trim(wout_file_name)
103 IF (.not.
ALLOCATED(extcur))
THEN
104 IF (parallel%offset .eq. 0)
THEN
105 WRITE (io_unit,1001) trim(wout_file_name)
119 & flags, siesta_file_name, parallel,
122 CALL profiler_set_stop_time(
'bmw_context_construct', start_time)
124 1000
FORMAT(a,
' is an invalid wout file.')
125 1001
FORMAT(a,
' is not a free boundary wout file.')
144 TYPE (bmw_context_class),
POINTER :: this
147 IF (
ASSOCIATED(this%m_grid))
THEN
149 this%m_grid => null()
152 IF (
ASSOCIATED(this%p_grid))
THEN
154 this%p_grid => null()
157 IF (
ASSOCIATED(this%up_grid))
THEN
159 this%up_grid => null()
188 TYPE (bmw_context_class),
INTENT(inout) :: this
189 INTEGER,
INTENT(in) :: p_start
190 INTEGER,
INTENT(in) :: p_end
191 TYPE (bmw_parallel_context_class),
INTENT(in) :: parallel
192 INTEGER,
INTENT(in) :: io_unit
195 REAL (rprec) :: start_time
198 start_time = profiler_get_start_time()
201 & p_start, p_end, parallel,
204 CALL profiler_set_stop_time(
'bmw_context_set_up_grid_m',
229 TYPE (bmw_context_class),
INTENT(inout) :: this
230 REAL (rprec),
DIMENSION(:,:,:),
INTENT(in) :: r_grid
231 REAL (rprec),
DIMENSION(:,:,:),
INTENT(in) :: z_grid
232 REAL (rprec),
INTENT(in) :: dphi
233 TYPE (bmw_parallel_context_class),
INTENT(in) :: parallel
234 INTEGER,
INTENT(in) :: io_unit
237 REAL (rprec) :: start_time
240 start_time = profiler_get_start_time()
243 & r_grid, z_grid, dphi,
246 CALL profiler_set_stop_time(
'bmw_context_set_up_grid_a',
299 TYPE (bmw_context_class),
INTENT(in) :: this
300 CHARACTER (len=*),
INTENT(in) :: result_file_name
301 TYPE (bmw_parallel_context_class),
INTENT(in) :: parallel
304 REAL (rprec) :: start_time
324 TYPE (bmw_context_class),
INTENT(in) :: this
325 CHARACTER (len=*),
INTENT(in) :: result_file_name
326 TYPE (bmw_parallel_context_class),
INTENT(in) :: parallel
329 REAL (rprec) :: start_time
331 INTEGER :: result_iou
334 CHARACTER (len=*),
DIMENSION(3),
PARAMETER ::
336 CHARACTER (len=*),
DIMENSION(3),
PARAMETER ::
340 start_time = profiler_get_start_time()
342 IF (parallel%offset .eq. 0)
THEN
343 CALL cdf_open(result_iou, trim(result_file_name),
'w', status)
345 CALL cdf_define(result_iou,
'series',
series)
347 CALL cdf_define(result_iou,
'nfp', this%m_grid%nfp)
349 CALL cdf_define(result_iou,
'rmin', this%m_grid%rmin)
350 CALL cdf_define(result_iou,
'rmax', this%m_grid%rmax)
351 CALL cdf_define(result_iou,
'zmin', this%m_grid%zmin)
352 CALL cdf_define(result_iou,
'zmax', this%m_grid%zmax)
354 CALL cdf_define(result_iou,
'ar_grid', this%up_grid%a_r,
356 CALL cdf_define(result_iou,
'ap_grid', this%up_grid%a_p,
358 CALL cdf_define(result_iou,
'az_grid', this%up_grid%a_z,
361 CALL cdf_define(result_iou,
'br_grid', this%up_grid%b_r,
363 CALL cdf_define(result_iou,
'bp_grid', this%up_grid%b_p,
365 CALL cdf_define(result_iou,
'bz_grid', this%up_grid%b_z,
368 CALL cdf_define(result_iou,
'px_grid', this%p_grid%x,
370 CALL cdf_define(result_iou,
'py_grid', this%p_grid%y,
372 CALL cdf_define(result_iou,
'pz_grid', this%p_grid%z,
375 CALL cdf_define(result_iou,
'jx_grid', this%p_grid%j_x,
377 CALL cdf_define(result_iou,
'jy_grid', this%p_grid%j_y,
379 CALL cdf_define(result_iou,
'jz_grid', this%p_grid%j_z,
382 CALL cdf_write(result_iou,
'series',
series)
384 CALL cdf_write(result_iou,
'nfp', this%m_grid%nfp)
386 CALL cdf_write(result_iou,
'rmin', this%m_grid%rmin)
387 CALL cdf_write(result_iou,
'rmax', this%m_grid%rmax)
388 CALL cdf_write(result_iou,
'zmin', this%m_grid%zmin)
389 CALL cdf_write(result_iou,
'zmax', this%m_grid%zmax)
391 CALL cdf_write(result_iou,
'ar_grid', this%up_grid%a_r)
392 CALL cdf_write(result_iou,
'ap_grid', this%up_grid%a_p)
393 CALL cdf_write(result_iou,
'az_grid', this%up_grid%a_z)
395 CALL cdf_write(result_iou,
'br_grid', this%up_grid%b_r)
396 CALL cdf_write(result_iou,
'bp_grid', this%up_grid%b_p)
397 CALL cdf_write(result_iou,
'bz_grid', this%up_grid%b_z)
399 CALL cdf_write(result_iou,
'px_grid', this%p_grid%x)
400 CALL cdf_write(result_iou,
'py_grid', this%p_grid%y)
401 CALL cdf_write(result_iou,
'pz_grid', this%p_grid%z)
403 CALL cdf_write(result_iou,
'jx_grid', this%p_grid%j_x)
404 CALL cdf_write(result_iou,
'jy_grid', this%p_grid%j_y)
405 CALL cdf_write(result_iou,
'jz_grid', this%p_grid%j_z)
407 CALL cdf_close(result_iou)
410 CALL profiler_set_stop_time(
'bmw_context_write', start_time)
Base class representing a primed grid. This is grid the volume integral will be summed over.
subroutine bmw_context_set_up_grid_a(this, r_grid, z_grid, dphi, parallel, io_unit)
Set the unprimed grid.
subroutine bmw_context_write(this, result_file_name, parallel)
Write NetCDF based result file.
subroutine bmw_context_destruct(this)
Deconstruct a bmw_context_class object.
Contains parameters defining the bit positions for flags that mark different options.
Defines the base class of the type m_grid_class. This contains the state variables to define the vacu...
integer, parameter series
Version number.
type(m_grid_class) function, pointer m_grid_construct(mgrid_file_name, parallel, io_unit)
Construct a m_grid_class object.
type(primed_grid_class) function, pointer primed_grid_construct(num_v, flags, siesta_file, parallel, io_unit)
Construct a primed_grid_class object.
subroutine primed_grid_destruct(this)
Deconstruct a primed_grid_class object.
Defines the base class of the type bmw_parallel_context_class. This contains the state variables need...
Defines the base class of the type unprimed_grid_class. This contains the state variables to define t...
Defines the base class of the type bmw_context_class. This contains the state variables needed by BMW...
subroutine bmw_context_set_up_grid_m(this, p_start, p_end, parallel, io_unit)
Set the unprimed grid.
subroutine bmw_parallel_context_abort(status)
Abort the entire program.
subroutine m_grid_destruct(this)
Deconstruct a m_grid_class object.
Base class representing a unprimed grid. This is grid the volume integral will be summed over.
Base class representing a bmw context. This contains all memory needed to operate bmw.
integer, parameter bmw_state_flags_mgrid
Bit position for mgrid specified number of phi planes.
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.
subroutine unprimed_grid_destruct(this)
Deconstruct a unprimed_grid_class object.
Base class representing a m grid. This is grid contains information about the vacuum fields.
Base class representing a bmw parallel context. This contains all memory needed parameters needed to ...
Interface to constructors.
Interface to set the unprimed grid.
Defines the base class of the type primed_grid_class. This contains the state variables to define the...
subroutine bmw_context_init_nc(this, result_file_name, parallel)