diff --git a/benchmark_cgdrag/benchmarker_cgdrag_forpy.f90 b/benchmark_cgdrag/benchmarker_cgdrag_forpy.f90
index fd15206..0f030fe 100644
--- a/benchmark_cgdrag/benchmarker_cgdrag_forpy.f90
+++ b/benchmark_cgdrag/benchmarker_cgdrag_forpy.f90
@@ -24,8 +24,8 @@ subroutine main()
integer :: i, j, n
real(dp) :: start_time, end_time, start_loop_time, end_loop_time
- real(dp), dimension(:), allocatable :: module_load_durations, module_delete_durations, loop_durations, inference_durations
- real(dp), dimension(:), allocatable :: allocation_durations, deallocation_durations, tensor_creation_durations, tensor_deletion_durations
+ real(dp), dimension(:), allocatable :: loop_durations, inference_durations, allocation_durations
+ real(dp), dimension(:), allocatable :: deallocation_durations, tensor_creation_durations, tensor_deletion_durations
real(dp), dimension(:,:), allocatable :: all_durations
character(len=20), dimension(:), allocatable :: messages
@@ -47,6 +47,8 @@ subroutine main()
character(len=:), allocatable :: model_dir, model_name
character(len=128) :: msg1, msg2, msg3, msg4, msg5, msg6
integer :: ntimes
+ character(len=10) :: input_device
+ logical :: use_cuda = .false.
type(ndarray) :: uuu_nd, vvv_nd, gwfcng_x_nd, gwfcng_y_nd, lat_nd, psfc_nd
@@ -56,16 +58,22 @@ subroutine main()
print *, "====== FORPY ======"
- call setup(model_dir, model_name, ntimes, n, alloc_in_loop)
+ call setup(model_dir, model_name, ntimes, n, alloc_in_loop, use_cuda=use_cuda)
if (ntimes .lt. 2) then
write(*,*) "Error: ntimes must be at least 2"
return
end if
+ if (use_cuda) then
+ input_device = "cuda"
+ else
+ input_device = "cpu"
+ end if
+
! Allocate arrays shared with FTorch implementation and read in data
call init_common_arrays(ntimes, I_MAX, J_MAX, K_MAX, uuu, vvv, gwfcng_x, gwfcng_y, gwfcng_x_ref, gwfcng_y_ref, lat, psfc, &
- module_load_durations, module_delete_durations, loop_durations, allocation_durations, deallocation_durations, &
- tensor_creation_durations, tensor_deletion_durations, inference_durations, all_durations, messages, &
+ loop_durations, allocation_durations, deallocation_durations, tensor_creation_durations, &
+ tensor_deletion_durations, inference_durations, all_durations, messages, &
start_loop_time, end_loop_time, start_time, end_time)
! Reshape arrays, if not done for every loop
@@ -80,7 +88,7 @@ subroutine main()
#else
print *, "generate model in python runtime"
#endif
- call load_module(model_dir, model_name, run_emulator, model)
+ call load_module(model_dir, model_name, run_emulator, model, use_cuda)
do i = 1, ntimes
@@ -108,13 +116,14 @@ subroutine main()
ie = ndarray_create_nocopy(gwfcng_y_nd, gwfcng_y_flattened)
! create model input args as tuple
- ie = tuple_create(args,6)
+ ie = tuple_create(args, 7)
ie = args%setitem(0, model)
ie = args%setitem(1, uuu_nd)
ie = args%setitem(2, lat_nd)
ie = args%setitem(3, psfc_nd)
ie = args%setitem(4, gwfcng_x_nd)
ie = args%setitem(5, J_MAX)
+ ie = args%setitem(6, trim(input_device))
end_time = omp_get_wtime()
tensor_creation_durations(i) = end_time - start_time
! ------------------------------ End tensor creation timer ------------------------------
@@ -210,25 +219,23 @@ subroutine main()
end do
- call time_module(ntimes, model_dir, model_name, module_load_durations, module_delete_durations, run_emulator, model)
+ call forpy_finalize
! Call individual print for loop, to avoid adding to combined mean
call print_time_stats(loop_durations, "full loop")
- all_durations(:, 1) = module_load_durations
- all_durations(:, 2) = module_delete_durations
- all_durations(:, 3) = allocation_durations
- all_durations(:, 4) = deallocation_durations
- all_durations(:, 5) = tensor_creation_durations
- all_durations(:, 6) = tensor_deletion_durations
- all_durations(:, 7) = inference_durations
- messages = [character(len=20) :: "module creation", "module deletion", "array allocation", "array deallocation", &
+ all_durations(:, 1) = allocation_durations
+ all_durations(:, 2) = deallocation_durations
+ all_durations(:, 3) = tensor_creation_durations
+ all_durations(:, 4) = tensor_deletion_durations
+ all_durations(:, 5) = inference_durations
+ messages = [character(len=20) :: "array allocation", "array deallocation", &
"tensor creation", "tensor deletion", "forward pass"]
call print_all_time_stats(all_durations, messages)
- call deallocate_common_arrays(uuu, vvv, gwfcng_x, gwfcng_y, gwfcng_x_ref, gwfcng_y_ref, lat, psfc, module_load_durations, &
- module_delete_durations, loop_durations, allocation_durations, deallocation_durations, &
- tensor_creation_durations, tensor_deletion_durations, inference_durations, all_durations, messages)
+ call deallocate_common_arrays(uuu, vvv, gwfcng_x, gwfcng_y, gwfcng_x_ref, gwfcng_y_ref, lat, psfc, &
+ loop_durations, allocation_durations, deallocation_durations, tensor_creation_durations, &
+ tensor_deletion_durations, inference_durations, all_durations, messages)
if (.not. alloc_in_loop) then
call deallocate_reshaped_arrays(uuu_flattened, vvv_flattened, lat_reshaped, psfc_reshaped, gwfcng_x_flattened, gwfcng_y_flattened)
@@ -236,45 +243,12 @@ subroutine main()
end subroutine main
- subroutine time_module(ntimes, model_dir, model_name, module_load_durations, module_delete_durations, run_emulator, model)
-
- implicit none
-
- integer, intent(in) :: ntimes
- character(len=*), intent(in) :: model_dir, model_name
- real(dp), dimension(:), intent(inout) :: module_load_durations, module_delete_durations
- type(module_py), intent(out) :: run_emulator
- type(object), intent(out) :: model
-
- integer :: i
- real(dp) :: start_time, end_time
-
- do i = 1, ntimes
- ! ------------------------------ Start module load timer ------------------------------
- start_time = omp_get_wtime()
- call load_module(model_dir, model_name, run_emulator, model)
- end_time = omp_get_wtime()
- module_load_durations(i) = end_time - start_time
- ! ------------------------------ End module load timer ------------------------------
-
- ! ------------------------------ Start module deletion timer ------------------------------
- ! We can only call forpy_finalize once
- if (i == ntimes) then
- start_time = omp_get_wtime()
- call forpy_finalize
- end_time = omp_get_wtime()
- module_delete_durations(:) = (end_time - start_time) / (ntimes + 1)
- end if
- ! ------------------------------ End module deletion timer ------------------------------
- end do
-
- end subroutine time_module
-
- subroutine load_module(model_dir, model_name, run_emulator, model)
+ subroutine load_module(model_dir, model_name, run_emulator, model, use_cuda)
implicit none
character(len=*), intent(in) :: model_dir, model_name
+ logical, intent(in) :: use_cuda
type(module_py), intent(out) :: run_emulator
type(object), intent(out) :: model
@@ -301,7 +275,11 @@ subroutine load_module(model_dir, model_name, run_emulator, model)
#ifdef USETS
! load torchscript saved model
ie = tuple_create(args,1)
- ie = str_create(filename, trim(model_dir//"/"//"saved_cgdrag_model_cpu.pt"))
+ if (use_cuda) then
+ ie = str_create(filename, trim(model_dir//"/"//"saved_cgdrag_model_gpu.pt"))
+ else
+ ie = str_create(filename, trim(model_dir//"/"//"saved_cgdrag_model_cpu.pt"))
+ end if
ie = args%setitem(0, filename)
ie = call_py(model, run_emulator, "initialize_ts", args)
call args%destroy
@@ -318,8 +296,8 @@ subroutine load_module(model_dir, model_name, run_emulator, model)
end subroutine load_module
subroutine init_common_arrays(ntimes, I_MAX, J_MAX, K_MAX, uuu, vvv, gwfcng_x, gwfcng_y, gwfcng_x_ref, gwfcng_y_ref, lat, psfc, &
- module_load_durations, module_delete_durations, loop_durations, allocation_durations, &
- deallocation_durations, tensor_creation_durations, tensor_deletion_durations, inference_durations, &
+ loop_durations, allocation_durations, deallocation_durations, &
+ tensor_creation_durations, tensor_deletion_durations, inference_durations, &
all_durations, messages, start_loop_time, end_loop_time, start_time, end_time)
implicit none
@@ -330,8 +308,8 @@ subroutine init_common_arrays(ntimes, I_MAX, J_MAX, K_MAX, uuu, vvv, gwfcng_x, g
real(wp), intent(out), dimension(:,:,:), allocatable :: gwfcng_x_ref, gwfcng_y_ref
real(wp), intent(out), dimension(:,:), allocatable :: lat, psfc
- real(dp), intent(out), dimension(:), allocatable :: module_load_durations, module_delete_durations, loop_durations, inference_durations
- real(dp), intent(out), dimension(:), allocatable :: allocation_durations, deallocation_durations, tensor_creation_durations, tensor_deletion_durations
+ real(dp), intent(out), dimension(:), allocatable :: loop_durations, inference_durations, allocation_durations
+ real(dp), intent(out), dimension(:), allocatable :: deallocation_durations, tensor_creation_durations, tensor_deletion_durations
real(dp), intent(out), dimension(:,:), allocatable :: all_durations
character(len=20), intent(out), dimension(:), allocatable :: messages
@@ -385,20 +363,16 @@ subroutine init_common_arrays(ntimes, I_MAX, J_MAX, K_MAX, uuu, vvv, gwfcng_x, g
close(15)
! Allocate arrays for timings
- allocate(module_load_durations(ntimes))
- allocate(module_delete_durations(ntimes))
allocate(loop_durations(ntimes))
allocate(allocation_durations(ntimes))
allocate(deallocation_durations(ntimes))
allocate(tensor_creation_durations(ntimes))
allocate(tensor_deletion_durations(ntimes))
allocate(inference_durations(ntimes))
- allocate(all_durations(ntimes, 7))
- allocate(messages(7))
+ allocate(all_durations(ntimes, 5))
+ allocate(messages(5))
! Initialise timings with arbitrary large values
- module_load_durations(:) = 100.
- module_delete_durations(:) = 100.
loop_durations(:) = 100.
allocation_durations(:) = 100.
deallocation_durations(:) = 100.
@@ -445,14 +419,14 @@ subroutine init_reshaped_arrays(I_MAX, J_MAX, K_MAX, uuu, vvv, lat, psfc, uuu_fl
end subroutine init_reshaped_arrays
- subroutine deallocate_common_arrays(uuu, vvv, gwfcng_x, gwfcng_y, gwfcng_x_ref, gwfcng_y_ref, lat, psfc, module_load_durations, &
- module_delete_durations, loop_durations, allocation_durations, deallocation_durations, &
- tensor_creation_durations, tensor_deletion_durations, inference_durations, all_durations, messages)
+ subroutine deallocate_common_arrays(uuu, vvv, gwfcng_x, gwfcng_y, gwfcng_x_ref, gwfcng_y_ref, lat, psfc, &
+ loop_durations, allocation_durations, deallocation_durations, tensor_creation_durations, &
+ tensor_deletion_durations, inference_durations, all_durations, messages)
implicit none
- real(dp), intent(inout), dimension(:), allocatable :: module_load_durations, module_delete_durations, loop_durations, inference_durations
- real(dp), intent(inout), dimension(:), allocatable :: allocation_durations, deallocation_durations, tensor_creation_durations, tensor_deletion_durations
+ real(dp), intent(inout), dimension(:), allocatable :: loop_durations, inference_durations, allocation_durations
+ real(dp), intent(inout), dimension(:), allocatable :: deallocation_durations, tensor_creation_durations, tensor_deletion_durations
real(dp), intent(inout), dimension(:,:), allocatable :: all_durations
character(len=20), intent(inout), dimension(:), allocatable :: messages
@@ -460,8 +434,6 @@ subroutine deallocate_common_arrays(uuu, vvv, gwfcng_x, gwfcng_y, gwfcng_x_ref,
real(wp), intent(inout), dimension(:,:,:), allocatable :: gwfcng_x_ref, gwfcng_y_ref
real(wp), intent(inout), dimension(:,:), allocatable :: lat, psfc
- deallocate(module_load_durations)
- deallocate(module_delete_durations)
deallocate(loop_durations)
deallocate(allocation_durations)
deallocate(deallocation_durations)
diff --git a/benchmark_cgdrag/benchmarker_cgdrag_torch.f90 b/benchmark_cgdrag/benchmarker_cgdrag_torch.f90
index c985ebc..9fbd2b2 100644
--- a/benchmark_cgdrag/benchmarker_cgdrag_torch.f90
+++ b/benchmark_cgdrag/benchmarker_cgdrag_torch.f90
@@ -1,6 +1,6 @@
program benchmark_cgdrag_test
- use, intrinsic :: iso_c_binding
+ use, intrinsic :: iso_c_binding, only : c_loc, c_int, c_int64_t
use :: omp_lib, only : omp_get_wtime
use :: utils, only : assert, setup, print_time_stats, print_all_time_stats
use :: ftorch
@@ -22,8 +22,8 @@ subroutine main()
integer :: i, j, n, ii
real(dp) :: start_time, end_time, start_loop_time, end_loop_time
- real(dp), dimension(:), allocatable :: module_load_durations, module_delete_durations, loop_durations, inference_durations
- real(dp), dimension(:), allocatable :: allocation_durations, deallocation_durations, tensor_creation_durations, tensor_deletion_durations
+ real(dp), dimension(:), allocatable :: loop_durations, inference_durations, allocation_durations
+ real(dp), dimension(:), allocatable :: deallocation_durations, tensor_creation_durations, tensor_deletion_durations
real(dp), dimension(:,:), allocatable :: all_durations
character(len=20), dimension(:), allocatable :: messages
@@ -37,17 +37,17 @@ subroutine main()
real(wp), dimension(:,:), allocatable, target :: lat_reshaped, psfc_reshaped
real(wp), dimension(:,:), allocatable, target :: gwfcng_x_flattened, gwfcng_y_flattened
- integer(c_int), parameter :: n_inputs = 3
+ integer, parameter :: n_inputs = 3
- integer(c_int), parameter :: dims_1D = 2
- integer(c_int), parameter :: dims_2D = 2
- integer(c_int), parameter :: dims_out = 2
- integer(c_int64_t) :: shape_2D(dims_2D) = [I_MAX * J_MAX, K_MAX]
- integer(c_int) :: stride_2D(dims_2D) = [1, 2]
- integer(c_int64_t) :: shape_1D(dims_1D) = [I_MAX * J_MAX, 1]
- integer(c_int) :: stride_1D(dims_1D) = [1, 2]
- integer(c_int64_t) :: shape_out(dims_out) = [I_MAX * J_MAX, K_MAX]
- integer(c_int) :: stride_out(dims_out) = [1, 2]
+ integer, parameter :: dims_1D = 2
+ integer, parameter :: dims_2D = 2
+ integer, parameter :: dims_out = 2
+ integer :: shape_2D(dims_2D) = [I_MAX * J_MAX, K_MAX]
+ integer :: stride_2D(dims_2D) = [1, 2]
+ integer :: shape_1D(dims_1D) = [I_MAX * J_MAX, 1]
+ integer :: stride_1D(dims_1D) = [1, 2]
+ integer :: shape_out(dims_out) = [I_MAX * J_MAX, K_MAX]
+ integer :: stride_out(dims_out) = [1, 2]
character(len=:), allocatable :: model_dir, model_name
character(len=128) :: msg1, msg2, msg3, msg4, msg5, msg6
@@ -83,8 +83,8 @@ subroutine main()
! Allocate arrays shared with FTorch implementation and read in data
call init_common_arrays(ntimes, I_MAX, J_MAX, K_MAX, uuu, vvv, gwfcng_x, gwfcng_y, gwfcng_x_ref, gwfcng_y_ref, lat, psfc, &
- module_load_durations, module_delete_durations, loop_durations, allocation_durations, deallocation_durations, &
- tensor_creation_durations, tensor_deletion_durations, inference_durations, all_durations, messages, &
+ loop_durations, allocation_durations, deallocation_durations, tensor_creation_durations, &
+ tensor_deletion_durations, inference_durations, all_durations, messages, &
start_loop_time, end_loop_time, start_time, end_time)
! Allocate arrays and flatten inputs and outputs if --explicit_reshape is set, but --alloc_in_loop is not
@@ -94,7 +94,7 @@ subroutine main()
lat_reshaped, psfc_reshaped, gwfcng_x_flattened, gwfcng_y_flattened)
end if
- ! Load model (creation/deletion timed at end)
+ ! Load model
model = torch_module_load(model_dir//"/"//model_name)
do i = 1, ntimes
@@ -117,20 +117,20 @@ subroutine main()
! ------------------------------ Start tensor creation timer ------------------------------
start_time = omp_get_wtime()
if (explicit_reshape) then
- in_tensors(3) = torch_tensor_from_blob(c_loc(lat_reshaped), dims_1D, shape_1D, torch_wp, input_device, stride_1D)
- in_tensors(2) = torch_tensor_from_blob(c_loc(psfc_reshaped), dims_1D, shape_1D, torch_wp, input_device, stride_1D)
+ in_tensors(3) = torch_tensor_from_array(lat_reshaped, stride_1D, input_device)
+ in_tensors(2) = torch_tensor_from_array(psfc_reshaped, stride_1D, input_device)
else
- in_tensors(3) = torch_tensor_from_blob(c_loc(lat), dims_1D, shape_1D, torch_wp, input_device, stride_1D)
- in_tensors(2) = torch_tensor_from_blob(c_loc(psfc), dims_1D, shape_1D, torch_wp, input_device, stride_1D)
+ in_tensors(3) = torch_tensor_from_blob(c_loc(lat), int(dims_1D, c_int), int(shape_1D, c_int64_t), int(stride_1D, c_int), torch_wp, input_device)
+ in_tensors(2) = torch_tensor_from_blob(c_loc(psfc), int(dims_1D, c_int), int(shape_1D, c_int64_t), int(stride_1D, c_int), torch_wp, input_device)
end if
! Zonal
if (explicit_reshape) then
- in_tensors(1) = torch_tensor_from_blob(c_loc(uuu_flattened), dims_2D, shape_2D, torch_wp, input_device, stride_2D)
- gwfcng_x_tensor = torch_tensor_from_blob(c_loc(gwfcng_x_flattened), dims_out, shape_out, torch_wp, torch_kCPU, stride_out)
+ in_tensors(1) = torch_tensor_from_array(uuu_flattened, stride_2D, input_device)
+ gwfcng_x_tensor = torch_tensor_from_array(gwfcng_x_flattened, stride_out, torch_kCPU)
else
- in_tensors(1) = torch_tensor_from_blob(c_loc(uuu), dims_2D, shape_2D, torch_wp, input_device, stride_2D)
- gwfcng_x_tensor = torch_tensor_from_blob(c_loc(gwfcng_x), dims_out, shape_out, torch_wp, torch_kCPU, stride_out)
+ in_tensors(1) = torch_tensor_from_blob(c_loc(uuu), int(dims_2D, c_int), int(shape_2D, c_int64_t), int(stride_2D, c_int), torch_wp, input_device)
+ gwfcng_x_tensor = torch_tensor_from_blob(c_loc(gwfcng_x), int(dims_out, c_int), int(shape_out, c_int64_t), int(stride_out, c_int), torch_wp, torch_kCPU)
end if
end_time = omp_get_wtime()
tensor_creation_durations(i) = end_time - start_time
@@ -144,15 +144,18 @@ subroutine main()
inference_durations(i) = end_time - start_time
! ------------------------------ End inference timer ------------------------------
+ ! Clean up here before this points to a new tensor.
+ call torch_tensor_delete(in_tensors(1))
+
! Meridional
! ------------------------------ Start tensor creation timer ------------------------------
start_time = omp_get_wtime()
if (explicit_reshape) then
- in_tensors(1) = torch_tensor_from_blob(c_loc(vvv_flattened), dims_2D, shape_2D, torch_wp, input_device, stride_2D)
- gwfcng_y_tensor = torch_tensor_from_blob(c_loc(gwfcng_y_flattened), dims_out, shape_out, torch_wp, torch_kCPU, stride_out)
+ in_tensors(1) = torch_tensor_from_array(vvv_flattened, stride_2D, input_device)
+ gwfcng_y_tensor = torch_tensor_from_array(gwfcng_y_flattened, stride_out, torch_kCPU)
else
- in_tensors(1) = torch_tensor_from_blob(c_loc(vvv), dims_2D, shape_2D, torch_wp, input_device, stride_2D)
- gwfcng_y_tensor = torch_tensor_from_blob(c_loc(gwfcng_y), dims_out, shape_out, torch_wp, torch_kCPU, stride_out)
+ in_tensors(1) = torch_tensor_from_blob(c_loc(vvv), int(dims_2D, c_int), int(shape_2D, c_int64_t), int(stride_2D, c_int), torch_wp, input_device)
+ gwfcng_y_tensor = torch_tensor_from_blob(c_loc(gwfcng_y), int(dims_out, c_int), int(shape_out, c_int64_t), int(stride_out, c_int), torch_wp, torch_kCPU)
end if
end_time = omp_get_wtime()
tensor_creation_durations(i) = tensor_creation_durations(i) + (end_time - start_time)
@@ -225,25 +228,24 @@ subroutine main()
end do
- call time_module(ntimes, model_dir, model_name, module_load_durations, module_delete_durations)
+ ! Delete model
+ call torch_module_delete(model)
! Call individual print for loop, to avoid adding to combined mean
call print_time_stats(loop_durations, "full loop")
- all_durations(:, 1) = module_load_durations
- all_durations(:, 2) = module_delete_durations
- all_durations(:, 3) = allocation_durations
- all_durations(:, 4) = deallocation_durations
- all_durations(:, 5) = tensor_creation_durations
- all_durations(:, 6) = tensor_deletion_durations
- all_durations(:, 7) = inference_durations
- messages = [character(len=20) :: "module creation", "module deletion", "array allocation", "array deallocation", &
+ all_durations(:, 1) = allocation_durations
+ all_durations(:, 2) = deallocation_durations
+ all_durations(:, 3) = tensor_creation_durations
+ all_durations(:, 4) = tensor_deletion_durations
+ all_durations(:, 5) = inference_durations
+ messages = [character(len=20) :: "array allocation", "array deallocation", &
"tensor creation", "tensor deletion", "forward pass"]
call print_all_time_stats(all_durations, messages)
- call deallocate_common_arrays(uuu, vvv, gwfcng_x, gwfcng_y, gwfcng_x_ref, gwfcng_y_ref, lat, psfc, module_load_durations, &
- module_delete_durations, loop_durations, allocation_durations, deallocation_durations, &
- tensor_creation_durations, tensor_deletion_durations, inference_durations, all_durations, messages)
+ call deallocate_common_arrays(uuu, vvv, gwfcng_x, gwfcng_y, gwfcng_x_ref, gwfcng_y_ref, lat, psfc, loop_durations, &
+ allocation_durations, deallocation_durations, tensor_creation_durations, tensor_deletion_durations, &
+ inference_durations, all_durations, messages)
! Deallocate arrays for flattened inputs and outputs if --explicit_reshape is set, but --alloc_in_loop is not
! if --explicit_reshape and --alloc_in_loop are both set, this is done within each loop instead
@@ -253,39 +255,10 @@ subroutine main()
end subroutine main
- subroutine time_module(ntimes, model_dir, model_name, module_load_durations, module_delete_durations)
-
- implicit none
-
- integer, intent(in) :: ntimes
- real(dp), dimension(:), intent(inout) :: module_load_durations, module_delete_durations
- integer :: i
- real(dp) :: start_time, end_time
- character(len=*), intent(in) :: model_dir, model_name
- type(torch_module) :: model
-
- do i = 1, ntimes
- ! ------------------------------ Start module load timer ------------------------------
- start_time = omp_get_wtime()
- model = torch_module_load(model_dir//"/"//model_name)
- end_time = omp_get_wtime()
- module_load_durations(i) = end_time - start_time
- ! ------------------------------ End module load timer ------------------------------
-
- ! ------------------------------ Start module deletion timer ------------------------------
- start_time = omp_get_wtime()
- call torch_module_delete(model)
- end_time = omp_get_wtime()
- module_delete_durations(i) = end_time - start_time
- ! ------------------------------ End module deletion timer ------------------------------
- end do
-
- end subroutine time_module
-
subroutine init_common_arrays(ntimes, I_MAX, J_MAX, K_MAX, uuu, vvv, gwfcng_x, gwfcng_y, gwfcng_x_ref, gwfcng_y_ref, lat, psfc, &
- module_load_durations, module_delete_durations, loop_durations, allocation_durations, &
- deallocation_durations, tensor_creation_durations, tensor_deletion_durations, inference_durations, &
- all_durations, messages, start_loop_time, end_loop_time, start_time, end_time)
+ loop_durations, allocation_durations, deallocation_durations, tensor_creation_durations, &
+ tensor_deletion_durations, inference_durations, all_durations, messages, &
+ start_loop_time, end_loop_time, start_time, end_time)
implicit none
@@ -295,8 +268,8 @@ subroutine init_common_arrays(ntimes, I_MAX, J_MAX, K_MAX, uuu, vvv, gwfcng_x, g
real(wp), intent(out), dimension(:,:,:), allocatable :: gwfcng_x_ref, gwfcng_y_ref
real(wp), intent(out), dimension(:,:), allocatable :: lat, psfc
- real(dp), intent(out), dimension(:), allocatable :: module_load_durations, module_delete_durations, loop_durations, inference_durations
- real(dp), intent(out), dimension(:), allocatable :: allocation_durations, deallocation_durations, tensor_creation_durations, tensor_deletion_durations
+ real(dp), intent(out), dimension(:), allocatable :: loop_durations, inference_durations, allocation_durations
+ real(dp), intent(out), dimension(:), allocatable :: deallocation_durations, tensor_creation_durations, tensor_deletion_durations
real(dp), intent(out), dimension(:,:), allocatable :: all_durations
character(len=20), intent(out), dimension(:), allocatable :: messages
@@ -350,20 +323,16 @@ subroutine init_common_arrays(ntimes, I_MAX, J_MAX, K_MAX, uuu, vvv, gwfcng_x, g
close(15)
! Allocate arrays for timings
- allocate(module_load_durations(ntimes))
- allocate(module_delete_durations(ntimes))
allocate(loop_durations(ntimes))
allocate(allocation_durations(ntimes))
allocate(deallocation_durations(ntimes))
allocate(tensor_creation_durations(ntimes))
allocate(tensor_deletion_durations(ntimes))
allocate(inference_durations(ntimes))
- allocate(all_durations(ntimes, 7))
- allocate(messages(7))
+ allocate(all_durations(ntimes, 5))
+ allocate(messages(5))
! Initialise timings with arbitrary large values
- module_load_durations(:) = 100.
- module_delete_durations(:) = 100.
loop_durations(:) = 100.
allocation_durations(:) = 100.
deallocation_durations(:) = 100.
@@ -410,14 +379,14 @@ subroutine init_reshaped_arrays(I_MAX, J_MAX, K_MAX, uuu, vvv, lat, psfc, uuu_fl
end subroutine init_reshaped_arrays
- subroutine deallocate_common_arrays(uuu, vvv, gwfcng_x, gwfcng_y, gwfcng_x_ref, gwfcng_y_ref, lat, psfc, module_load_durations, &
- module_delete_durations, loop_durations, allocation_durations, deallocation_durations, &
- tensor_creation_durations, tensor_deletion_durations, inference_durations, all_durations, messages)
+ subroutine deallocate_common_arrays(uuu, vvv, gwfcng_x, gwfcng_y, gwfcng_x_ref, gwfcng_y_ref, lat, psfc, loop_durations, &
+ allocation_durations, deallocation_durations, tensor_creation_durations, &
+ tensor_deletion_durations, inference_durations, all_durations, messages)
implicit none
- real(dp), intent(inout), dimension(:), allocatable :: module_load_durations, module_delete_durations, loop_durations, inference_durations
- real(dp), intent(inout), dimension(:), allocatable :: allocation_durations, deallocation_durations, tensor_creation_durations, tensor_deletion_durations
+ real(dp), intent(inout), dimension(:), allocatable :: loop_durations, inference_durations, allocation_durations
+ real(dp), intent(inout), dimension(:), allocatable :: deallocation_durations, tensor_creation_durations, tensor_deletion_durations
real(dp), intent(inout), dimension(:,:), allocatable :: all_durations
character(len=20), intent(inout), dimension(:), allocatable :: messages
@@ -425,8 +394,6 @@ subroutine deallocate_common_arrays(uuu, vvv, gwfcng_x, gwfcng_y, gwfcng_x_ref,
real(wp), intent(inout), dimension(:,:,:), allocatable :: gwfcng_x_ref, gwfcng_y_ref
real(wp), intent(inout), dimension(:,:), allocatable :: lat, psfc
- deallocate(module_load_durations)
- deallocate(module_delete_durations)
deallocate(loop_durations)
deallocate(allocation_durations)
deallocate(deallocation_durations)
diff --git a/benchmark_large_stride/benchmarker_large_stride_torch.f90 b/benchmark_large_stride/benchmarker_large_stride_torch.f90
index 17ffb9e..fa9001c 100644
--- a/benchmark_large_stride/benchmarker_large_stride_torch.f90
+++ b/benchmark_large_stride/benchmarker_large_stride_torch.f90
@@ -95,8 +95,8 @@ subroutine main()
! Create input and output tensors for the model.
! ------------------------------ Start tensor creation timer ------------------------------
start_time = omp_get_wtime()
- input_array(1) = torch_tensor_from_blob(c_loc(big_array), 2, shape_2d, torch_wp, input_device, stride_2d)
- result_tensor = torch_tensor_from_blob(c_loc(big_result), 2, shape_2d, torch_wp, torch_kCPU, stride_2d)
+ input_array(1) = torch_tensor_from_blob(c_loc(big_array), 2, shape_2d, stride_2d, torch_wp, input_device)
+ result_tensor = torch_tensor_from_blob(c_loc(big_result), 2, shape_2d, stride_2d, torch_wp, torch_kCPU)
end_time = omp_get_wtime()
tensor_creation_durations(i) = end_time - start_time
! ------------------------------ End tensor creation timer ------------------------------
diff --git a/benchmark_mima/cg_drag_torch_mod.f90 b/benchmark_mima/cg_drag_torch_mod.f90
index 4bd8748..79d01aa 100644
--- a/benchmark_mima/cg_drag_torch_mod.f90
+++ b/benchmark_mima/cg_drag_torch_mod.f90
@@ -169,18 +169,21 @@ subroutine cg_drag_ML(uuu, vvv, psfc, lat, gwfcng_x, gwfcng_y)
lat = lat*RADIAN
! Create input/output tensors from the above arrays
- model_input_arr(3) = torch_tensor_from_blob(c_loc(lat), dims_1D, shape_1D, torch_wp, torch_kCPU, stride_1D)
- model_input_arr(2) = torch_tensor_from_blob(c_loc(psfc), dims_1D, shape_1D, torch_wp, torch_kCPU, stride_1D)
+ model_input_arr(3) = torch_tensor_from_blob(c_loc(lat), dims_1D, shape_1D, stride_1D, torch_wp, torch_kCPU)
+ model_input_arr(2) = torch_tensor_from_blob(c_loc(psfc), dims_1D, shape_1D, stride_1D, torch_wp, torch_kCPU)
! Zonal
- model_input_arr(1) = torch_tensor_from_blob(c_loc(uuu), dims_2D, shape_2D, torch_wp, torch_kCPU, stride_2D)
- gwfcng_x_tensor = torch_tensor_from_blob(c_loc(gwfcng_x), dims_out, shape_out, torch_wp, torch_kCPU, stride_out)
+ model_input_arr(1) = torch_tensor_from_blob(c_loc(uuu), dims_2D, shape_2D, stride_2D, torch_wp, torch_kCPU)
+ gwfcng_x_tensor = torch_tensor_from_blob(c_loc(gwfcng_x), dims_out, shape_out, stride_out, torch_wp, torch_kCPU)
! Run model and Infer
call torch_module_forward(model, model_input_arr, n_inputs, gwfcng_x_tensor)
+ ! Clean up here before this points to a new tensor
+ call torch_tensor_delete(model_input_arr(1))
+
! Meridional
- model_input_arr(1) = torch_tensor_from_blob(c_loc(vvv), dims_2D, shape_2D, torch_wp, torch_kCPU, stride_2D)
- gwfcng_y_tensor = torch_tensor_from_blob(c_loc(gwfcng_y), dims_out, shape_out, torch_wp, torch_kCPU, stride_out)
+ model_input_arr(1) = torch_tensor_from_blob(c_loc(vvv), dims_2D, shape_2D, stride_2D, torch_wp, torch_kCPU)
+ gwfcng_y_tensor = torch_tensor_from_blob(c_loc(gwfcng_y), dims_out, shape_out, stride_out, torch_wp, torch_kCPU)
! Run model and Infer
call torch_module_forward(model, model_input_arr, n_inputs, gwfcng_y_tensor)
diff --git a/benchmark_resnet/benchmarker_resnet_forpy.f90 b/benchmark_resnet/benchmarker_resnet_forpy.f90
index 2212fcb..541424f 100644
--- a/benchmark_resnet/benchmarker_resnet_forpy.f90
+++ b/benchmark_resnet/benchmarker_resnet_forpy.f90
@@ -24,8 +24,8 @@ subroutine main()
real(wp), dimension(:,:), allocatable, asynchronous :: out_data
real(dp) :: start_time, end_time, start_loop_time, end_loop_time
- real(dp), dimension(:), allocatable :: module_load_durations, module_delete_durations, loop_durations
- real(dp), dimension(:), allocatable :: inference_durations, tensor_creation_durations, tensor_deletion_durations
+ real(dp), dimension(:), allocatable :: loop_durations, inference_durations
+ real(dp), dimension(:), allocatable :: tensor_creation_durations, tensor_deletion_durations
real(dp), dimension(:,:), allocatable :: all_durations
character(len=20), dimension(:), allocatable :: messages
@@ -37,6 +37,8 @@ subroutine main()
character(len=:), allocatable :: model_dir, model_name
character(len=128) :: msg1, msg2, msg3, msg4
integer :: ntimes
+ character(len=10) :: input_device
+ logical :: use_cuda = .false.
type(ndarray) :: out_data_nd, in_data_nd
@@ -54,23 +56,25 @@ subroutine main()
print *, "====== FORPY ======"
- call setup(model_dir, model_name, ntimes, n)
+ call setup(model_dir, model_name, ntimes, n, use_cuda=use_cuda)
+
+ if (use_cuda) then
+ input_device = "cuda"
+ else
+ input_device = "cpu"
+ end if
allocate(in_data(1, 3, 224, 224))
allocate(out_data(1, 1000))
allocate(probabilities(1, 1000))
- allocate(module_load_durations(ntimes))
- allocate(module_delete_durations(ntimes))
allocate(loop_durations(ntimes))
allocate(tensor_creation_durations(ntimes))
allocate(tensor_deletion_durations(ntimes))
allocate(inference_durations(ntimes))
- allocate(all_durations(ntimes, 5))
- allocate(messages(5))
+ allocate(all_durations(ntimes, 3))
+ allocate(messages(3))
! Initialise timings with arbitrary large values
- module_load_durations(:) = 100.
- module_delete_durations(:) = 100.
loop_durations(:) = 100.
tensor_creation_durations(:) = 100.
tensor_deletion_durations(ntimes) = 100.
@@ -92,7 +96,7 @@ subroutine main()
#else
print *, "generate model in python runtime"
#endif
- call load_module(model_dir, model_name, run_emulator, model)
+ call load_module(model_dir, model_name, run_emulator, model, use_cuda)
call load_data(data_file, tensor_length, in_data)
@@ -108,10 +112,11 @@ subroutine main()
ie = ndarray_create_nocopy(out_data_nd, out_data)
! create model input args as tuple
- ie = tuple_create(args,3)
+ ie = tuple_create(args, 4)
ie = args%setitem(0, model)
ie = args%setitem(1, in_data_nd)
- ie = args%setitem(2, out_data_nd)
+ ie = args%setitem(2, trim(input_device))
+ ie = args%setitem(3, out_data_nd)
end_time = omp_get_wtime()
tensor_creation_durations(i) = end_time - start_time
! ------------------------------ End tensor creation timer ------------------------------
@@ -148,7 +153,7 @@ subroutine main()
probability = maxval(probabilities)
! Check top probability matches expected value
- call assert(probability, expected_prob, test_name="Check probability", rtol_opt=1.0e-5_wp)
+ call assert(probability, expected_prob, test_name="Check probability", rtol_opt=1.0e-2_wp)
write(msg1, '(A, I10, A, F10.6, A)') "check iteration create tensors", i, " (", tensor_creation_durations(i), " s)"
write(msg2, '(A, I15, A, F10.6, A)') "check iteration inference", i, " (", inference_durations(i), " s)"
@@ -161,23 +166,19 @@ subroutine main()
end do
- call time_module(ntimes, model_dir, model_name, module_load_durations, module_delete_durations, run_emulator, model)
+ call forpy_finalize
! Call individual print for loop, to avoid adding to combined mean
call print_time_stats(loop_durations, "full loop")
- all_durations(:, 1) = module_load_durations
- all_durations(:, 2) = module_delete_durations
- all_durations(:, 3) = tensor_creation_durations
- all_durations(:, 4) = tensor_deletion_durations
- all_durations(:, 5) = inference_durations
- messages = [character(len=20) :: "module creation", "module deletion", "tensor creation", "tensor deletion", "forward pass"]
+ all_durations(:, 1) = tensor_creation_durations
+ all_durations(:, 2) = tensor_deletion_durations
+ all_durations(:, 3) = inference_durations
+ messages = [character(len=20) :: "tensor creation", "tensor deletion", "forward pass"]
call print_all_time_stats(all_durations, messages)
deallocate(in_data)
deallocate(out_data)
- deallocate(module_load_durations)
- deallocate(module_delete_durations)
deallocate(loop_durations)
deallocate(tensor_creation_durations)
deallocate(tensor_deletion_durations)
@@ -236,45 +237,12 @@ subroutine calc_probs(out_data, probabilities)
end subroutine calc_probs
- subroutine time_module(ntimes, model_dir, model_name, module_load_durations, module_delete_durations, run_emulator, model)
-
- implicit none
-
- integer, intent(in) :: ntimes
- character(len=*), intent(in) :: model_dir, model_name
- real(dp), dimension(:), intent(inout) :: module_load_durations, module_delete_durations
- type(module_py), intent(out) :: run_emulator
- type(object), intent(out) :: model
-
- integer :: i
- real(dp) :: start_time, end_time
-
- do i = 1, ntimes
- ! ------------------------------ Start module load timer ------------------------------
- start_time = omp_get_wtime()
- call load_module(model_dir, model_name, run_emulator, model)
- end_time = omp_get_wtime()
- module_load_durations(i) = end_time - start_time
- ! ------------------------------ End module load timer ------------------------------
-
- ! ------------------------------ Start module deletion timer ------------------------------
- ! We can only call forpy_finalize once
- if (i == ntimes) then
- start_time = omp_get_wtime()
- call forpy_finalize
- end_time = omp_get_wtime()
- module_delete_durations(:) = (end_time - start_time) / (ntimes + 1)
- end if
- ! ------------------------------ End module deletion timer ------------------------------
- end do
-
- end subroutine time_module
-
- subroutine load_module(model_dir, model_name, run_emulator, model)
+ subroutine load_module(model_dir, model_name, run_emulator, model, use_cuda)
implicit none
character(len=*), intent(in) :: model_dir, model_name
+ logical, intent(in) :: use_cuda
type(module_py), intent(out) :: run_emulator
type(object), intent(out) :: model
@@ -301,7 +269,11 @@ subroutine load_module(model_dir, model_name, run_emulator, model)
#ifdef USETS
! load torchscript saved model
ie = tuple_create(args,1)
- ie = str_create(filename, trim(model_dir//"/"//"saved_resnet18_model_cpu.pt"))
+ if (use_cuda) then
+ ie = str_create(filename, trim(model_dir//"/"//"saved_resnet18_model_gpu.pt"))
+ else
+ ie = str_create(filename, trim(model_dir//"/"//"saved_resnet18_model_cpu.pt"))
+ end if
ie = args%setitem(0, filename)
ie = call_py(model, run_emulator, "initialize_ts", args)
call args%destroy
diff --git a/benchmark_resnet/benchmarker_resnet_torch.f90 b/benchmark_resnet/benchmarker_resnet_torch.f90
index 836b95b..193b0e0 100644
--- a/benchmark_resnet/benchmarker_resnet_torch.f90
+++ b/benchmark_resnet/benchmarker_resnet_torch.f90
@@ -1,18 +1,15 @@
program benchmark_resnet_test
- use, intrinsic :: iso_c_binding, only: c_int64_t, c_loc
use :: omp_lib, only : omp_get_wtime
use :: utils, only : assert, setup, print_time_stats, print_all_time_stats
! Import our library for interfacing with PyTorch
use :: ftorch
! Define working precision for C primitives and Fortran reals
! Precision must match `wp` in resnet18.py and `wp_torch` in pt2ts.py
- use :: precision, only: c_wp, wp, dp
+ use :: precision, only: wp, dp
implicit none
- integer, parameter :: torch_wp = torch_kFloat32
-
call main()
contains
@@ -23,21 +20,21 @@ subroutine main()
integer :: i, ii, n
real(dp) :: start_time, end_time, start_loop_time, end_loop_time
- real(dp), dimension(:), allocatable :: module_load_durations, module_delete_durations, loop_durations
- real(dp), dimension(:), allocatable :: inference_durations, tensor_creation_durations, tensor_deletion_durations
+ real(dp), dimension(:), allocatable :: loop_durations, inference_durations
+ real(dp), dimension(:), allocatable :: tensor_creation_durations, tensor_deletion_durations
real(dp), dimension(:,:), allocatable :: all_durations
character(len=20), dimension(:), allocatable :: messages
- real(c_wp), dimension(:,:,:,:), allocatable, target :: in_data
- integer(c_int), parameter :: n_inputs = 1
- real(c_wp), dimension(:,:), allocatable, target :: out_data
+ real(wp), dimension(:,:,:,:), allocatable, target :: in_data
+ real(wp), dimension(:,:), allocatable, target :: out_data
+ integer, parameter :: n_inputs = 1
- integer(c_int), parameter :: in_dims = 4
- integer(c_int64_t) :: in_shape(in_dims) = [1, 3, 224, 224]
- integer(c_int) :: in_layout(in_dims) = [1,2,3,4]
- integer(c_int), parameter :: out_dims = 2
- integer(c_int64_t) :: out_shape(out_dims) = [1, 1000]
- integer(c_int) :: out_layout(out_dims) = [1,2]
+ integer, parameter :: in_dims = 4
+ integer :: in_shape(in_dims) = [1, 3, 224, 224]
+ integer :: in_layout(in_dims) = [1, 2, 3, 4]
+ integer, parameter :: out_dims = 2
+ integer :: out_shape(out_dims) = [1, 1000]
+ integer :: out_layout(out_dims) = [1, 2]
character(len=:), allocatable :: model_dir, model_name
character(len=128) :: msg1, msg2, msg3, msg4
@@ -74,18 +71,14 @@ subroutine main()
allocate(out_data(out_shape(1), out_shape(2)))
allocate(probabilities(out_shape(1), out_shape(2)))
- allocate(module_load_durations(ntimes))
- allocate(module_delete_durations(ntimes))
allocate(loop_durations(ntimes))
allocate(tensor_creation_durations(ntimes))
allocate(tensor_deletion_durations(ntimes))
allocate(inference_durations(ntimes))
- allocate(all_durations(ntimes, 5))
- allocate(messages(5))
+ allocate(all_durations(ntimes, 3))
+ allocate(messages(3))
! Initialise timings with arbitrary large values
- module_load_durations(:) = 100.
- module_delete_durations(:) = 100.
loop_durations(:) = 100.
tensor_creation_durations(:) = 100.
tensor_deletion_durations(ntimes) = 100.
@@ -101,7 +94,7 @@ subroutine main()
return
end if
- ! Load model (creation/deletion timed at end)
+ ! Load model
model = torch_module_load(model_dir//"/"//model_name)
! Initialise data - previously in loop, but not modified?
@@ -115,8 +108,8 @@ subroutine main()
! Create input and output tensors for the model.
! ------------------------------ Start tensor creation timer ------------------------------
start_time = omp_get_wtime()
- in_tensor(1) = torch_tensor_from_blob(c_loc(in_data), in_dims, in_shape, torch_wp, input_device, in_layout)
- out_tensor = torch_tensor_from_blob(c_loc(out_data), out_dims, out_shape, torch_wp, torch_kCPU, out_layout)
+ in_tensor(1) = torch_tensor_from_array(in_data, in_layout, input_device)
+ out_tensor = torch_tensor_from_array(out_data, out_layout, torch_kCPU)
end_time = omp_get_wtime()
tensor_creation_durations(i) = end_time - start_time
! ------------------------------ End tensor creation timer ------------------------------
@@ -162,26 +155,20 @@ subroutine main()
end do
- ! Delete model (creation/deletion timed at end)
+ ! Delete model
call torch_module_delete(model)
- call time_module(ntimes, model_dir, model_name, module_load_durations, module_delete_durations)
-
! Call individual print for loop, to avoid adding to combined mean
call print_time_stats(loop_durations, "full loop")
- all_durations(:, 1) = module_load_durations
- all_durations(:, 2) = module_delete_durations
- all_durations(:, 3) = tensor_creation_durations
- all_durations(:, 4) = tensor_deletion_durations
- all_durations(:, 5) = inference_durations
- messages = [character(len=20) :: "module creation", "module deletion", "tensor creation", "tensor deletion", "forward pass"]
+ all_durations(:, 1) = tensor_creation_durations
+ all_durations(:, 2) = tensor_deletion_durations
+ all_durations(:, 3) = inference_durations
+ messages = [character(len=20) :: "tensor creation", "tensor deletion", "forward pass"]
call print_all_time_stats(all_durations, messages)
deallocate(in_data)
deallocate(out_data)
- deallocate(module_load_durations)
- deallocate(module_delete_durations)
deallocate(loop_durations)
deallocate(tensor_creation_durations)
deallocate(tensor_deletion_durations)
@@ -198,9 +185,9 @@ subroutine load_data(filename, tensor_length, in_data)
character(len=*), intent(in) :: filename
integer, intent(in) :: tensor_length
- real(c_wp), dimension(:,:,:,:), intent(out) :: in_data
+ real(wp), dimension(:,:,:,:), intent(out) :: in_data
- real(c_wp) :: flat_data(tensor_length)
+ real(wp) :: flat_data(tensor_length)
integer :: ios
character(len=100) :: ioerrmsg
@@ -229,7 +216,7 @@ subroutine calc_probs(out_data, probabilities)
implicit none
- real(c_wp), dimension(:,:), intent(in) :: out_data
+ real(wp), dimension(:,:), intent(in) :: out_data
real(wp), dimension(:,:), intent(out) :: probabilities
real(wp) :: prob_sum
@@ -240,33 +227,4 @@ subroutine calc_probs(out_data, probabilities)
end subroutine calc_probs
- subroutine time_module(ntimes, model_dir, model_name, module_load_durations, module_delete_durations)
-
- implicit none
-
- integer, intent(in) :: ntimes
- real(dp), dimension(:), intent(out) :: module_load_durations, module_delete_durations
- integer :: i
- real(dp) :: start_time, end_time
- character(len=*), intent(in) :: model_dir, model_name
- type(torch_module) :: model
-
- do i = 1, ntimes
- ! ------------------------------ Start module load timer ------------------------------
- start_time = omp_get_wtime()
- model = torch_module_load(model_dir//"/"//model_name)
- end_time = omp_get_wtime()
- module_load_durations(i) = end_time - start_time
- ! ------------------------------ End module load timer ------------------------------
-
- ! ------------------------------ Start module deletion timer ------------------------------
- start_time = omp_get_wtime()
- call torch_module_delete(model)
- end_time = omp_get_wtime()
- module_delete_durations(i) = end_time - start_time
- ! ------------------------------ End module deletion timer ------------------------------
- end do
-
- end subroutine time_module
-
end program benchmark_resnet_test
diff --git a/cgdrag_model/run_emulator_davenet.py b/cgdrag_model/run_emulator_davenet.py
index fb92b18..b4b3994 100644
--- a/cgdrag_model/run_emulator_davenet.py
+++ b/cgdrag_model/run_emulator_davenet.py
@@ -4,7 +4,7 @@
It needs in the same directory as `arch_DaveNet.py` which describes the
model architecture, and `network_wst.pkl` which contains the model weights.
"""
-from torch import load, device, no_grad, tensor, float64, jit
+from torch import load, device, no_grad, tensor, float64, jit, device
import arch_davenet as m
@@ -69,22 +69,26 @@ def compute_reshape_drag(*args):
output prellocated in MiMA (128, num_col, 40)
num_col :
# of latitudes on this proc
+ device : str
+ Device type ("cpu", "cuda" or "mps"), and optional device ordinal for
+ the device type, to move input_batch to. Must match device of model.
Returns
-------
Y_out :
Results to be returned to MiMA
"""
- model, wind, lat, p_surf, Y_out, num_col = args
+ model, wind, lat, p_surf, Y_out, num_col, input_device = args
+ input_device = device(input_device)
# Reshape and put all input variables together [wind, lat, p_surf]
- wind_T = tensor(wind)
+ wind_T = tensor(wind).to(input_device)
# lat_T = zeros((imax * num_col, 1), dtype=float64)
- lat_T = tensor(lat)
+ lat_T = tensor(lat).to(input_device)
# pressure_T = zeros((imax * num_col, 1), dtype=float64)
- pressure_T = tensor(p_surf)
+ pressure_T = tensor(p_surf).to(input_device)
# Apply model.
with no_grad():
@@ -94,7 +98,7 @@ def compute_reshape_drag(*args):
temp = model(wind_T, pressure_T, lat_T)
# Place in output array for MiMA.
- Y_out[:, :] = temp
+ Y_out[:, :] = temp.cpu()
del temp
return Y_out
diff --git a/resnet_model/resnet18.py b/resnet_model/resnet18.py
index db8d246..75c0efa 100644
--- a/resnet_model/resnet18.py
+++ b/resnet_model/resnet18.py
@@ -144,15 +144,19 @@ def compute(*args):
ResNet model ready to be deployed.
input_batch : torch.Tensor
Input batch to operate on
+ device : str
+ Device type ("cpu", "cuda" or "mps"), and optional device ordinal for
+ the device type, to move input_batch to. Must match device of model.
Returns
-------
output :
Results from ResNet model
"""
- model, input_batch, result = args
+ model, input_batch, device, result = args
+ device = torch.device(device)
- input_batch = torch.from_numpy(input_batch)
+ input_batch = torch.from_numpy(input_batch).to(device)
# Apply model.
with torch.no_grad():
@@ -160,7 +164,7 @@ def compute(*args):
assert model.training is False
output = model(input_batch)
- result[:, :] = output
+ result[:, :] = output.cpu()
return result
diff --git a/run_benchmarks.sh b/run_benchmarks.sh
index e46f71f..56e7fc2 100755
--- a/run_benchmarks.sh
+++ b/run_benchmarks.sh
@@ -1,19 +1,16 @@
#!/usr/bin/env bash
nrun=1000
-NDIM=256
for n in {1,4,8};
do
export OMP_NUM_THREADS=$n
- ./benchmarker_cgdrag_forpy ../cgdrag_model run_emulator_davenet $nrun 10 --alloc_in_loop | tee cgdrag_forpy_$n.out
- ./benchmarker_cgdrag_torch ../cgdrag_model saved_cgdrag_model_cpu.pt $nrun 10 --alloc_in_loop --explicit_reshape | tee cgdrag_torch_explicit_$n.out
- ./benchmarker_cgdrag_torch ../cgdrag_model saved_cgdrag_model_cpu.pt $nrun 10 | tee cgdrag_torch_implicit_$n.out
+ date;/usr/bin/time -v ./benchmarker_cgdrag_forpy ../cgdrag_model run_emulator_davenet $nrun 10 | tee cgdrag_forpy_$n.out;date
+ date;/usr/bin/time -v ./benchmarker_cgdrag_torch ../cgdrag_model saved_cgdrag_model_cpu.pt $nrun 10 --explicit_reshape | tee cgdrag_torch_explicit_$n.out;date
+ date;/usr/bin/time -v ./benchmarker_cgdrag_torch ../cgdrag_model saved_cgdrag_model_cpu.pt $nrun 10 | tee cgdrag_torch_implicit_$n.out;date
- ./benchmarker_resnet_forpy ../resnet_model resnet18 $nrun 10 | tee resnet_forpy_$n.out
- ./benchmarker_resnet_torch ../resnet_model saved_resnet18_model_cpu.pt $nrun 10 | tee resnet_torch_$n.out
+ date;/usr/bin/time -v ./benchmarker_resnet_forpy ../resnet_model resnet18 $nrun 10 | tee resnet_forpy_$n.out;date
+ date;/usr/bin/time -v ./benchmarker_resnet_torch ../resnet_model saved_resnet18_model_cpu.pt $nrun 10 | tee resnet_torch_$n.out;date
- ./benchmarker_large_stride_forpy ../large_stride_model run_emulator_stride $nrun $NDIM | tee ls_forpy_$n.out
- ./benchmarker_large_stride_torch ../large_stride_model saved_large_stride_model_cpu.pt $nrun $NDIM | tee ls_torch_$n.out
done
diff --git a/run_benchmarks_gpu.sh b/run_benchmarks_gpu.sh
index 4874d1e..79dbafe 100644
--- a/run_benchmarks_gpu.sh
+++ b/run_benchmarks_gpu.sh
@@ -1,19 +1,16 @@
#!/usr/bin/env bash
-nrun=1000
-NDIM=256
+nrun=10000
-for n in {1,4,8};
+for n in {1,8};
do
export OMP_NUM_THREADS=$n
- ./benchmarker_cgdrag_forpy ../cgdrag_model run_emulator_davenet $nrun 10 | tee cgdrag_forpy_$n.out
- ./benchmarker_cgdrag_torch ../cgdrag_model saved_cgdrag_model_gpu.pt $nrun 10 --alloc_in_loop --explicit_reshape --use_cuda | tee cgdrag_torch_explicit_gpu_$n.out
- ./benchmarker_cgdrag_torch ../cgdrag_model saved_cgdrag_model_gpu.pt $nrun 10 --use_cuda | tee cgdrag_torch_implicit_gpu_$n.out
+ date;/usr/bin/time -v ./benchmarker_cgdrag_forpy ../cgdrag_model run_emulator_davenet $nrun 10 --use_cuda | tee cgdrag_forpy_gpu_$n.out;date
+ date;/usr/bin/time -v ./benchmarker_cgdrag_torch ../cgdrag_model saved_cgdrag_model_gpu.pt $nrun 10 --explicit_reshape --use_cuda | tee cgdrag_torch_explicit_gpu_$n.out;date
+ date;/usr/bin/time -v ./benchmarker_cgdrag_torch ../cgdrag_model saved_cgdrag_model_gpu.pt $nrun 10 --use_cuda | tee cgdrag_torch_implicit_gpu_$n.out;date
- ./benchmarker_resnet_forpy ../resnet_model resnet18 $nrun 10 | tee resnet_forpy_$n.out
- ./benchmarker_resnet_torch ../resnet_model saved_resnet18_model_gpu.pt $nrun 10 --use_cuda | tee resnet_torch_gpu_$n.out
+ date;/usr/bin/time -v ./benchmarker_resnet_forpy ../resnet_model resnet18 $nrun 10 --use_cuda | tee resnet_forpy_gpu_$n.out;date
+ date;/usr/bin/time -v ./benchmarker_resnet_torch ../resnet_model saved_resnet18_model_gpu.pt $nrun 10 --use_cuda | tee resnet_torch_gpu_$n.out;date
- ./benchmarker_large_stride_forpy ../large_stride_model run_emulator_stride $nrun $NDIM | tee ls_forpy_$n.out
- ./benchmarker_large_stride_torch ../large_stride_model saved_large_stride_model_gpu.pt $nrun $NDIM --use_cuda | tee ls_torch_gpu_$n.out
done
diff --git a/utils/read_benchmarks.py b/utils/read_benchmarks.py
index 7eb8b6c..843c28e 100644
--- a/utils/read_benchmarks.py
+++ b/utils/read_benchmarks.py
@@ -1,25 +1,26 @@
"""Helper functions to read and plot benchmarking data."""
+from typing import Union
import numpy as np
import matplotlib.pyplot as plt
import pandas as pd
def read_iteration_data(directory: str, filename: str, labels: list) -> pd.DataFrame:
- """Read benchmarking data from each loop iteration
+ """Read benchmarking data from each loop iteration.
Parameters
----------
- directory: str
+ directory : str
Directory of file containing benchmarking data to be read.
- filename: str
- Path to file containing benchmarking data to be read.
- labels: list
+ filename : str
+ Name of file containing benchmarking data to be read.
+ labels : list
List of labels in output file to read.
List does not need to be complete, but must be given in order of output.
Returns
-------
- df: pd.DataFrame
+ df : pd.DataFrame
Dataframe of durations, with columns corresponding to each input label.
"""
df = pd.DataFrame(columns=labels)
@@ -63,16 +64,16 @@ def read_summary_data(directory: str, filename: str, labels: list) -> dict:
Parameters
----------
- directory: str
+ directory : str
Directory of file containing benchmarking data to be read.
- filename: str
+ filename : str
Path to file containing benchmarking data to be read.
- labels: list
+ labels : list
List of labels to read summary information for.
Returns
-------
- results: dict
+ results : dict
Nested dictionary with keys for each label passed, and nested keys for
the mean, min, max and stddev for each label.
"""
@@ -118,13 +119,13 @@ def read_summary_data(directory: str, filename: str, labels: list) -> dict:
def plot_df(df: pd.DataFrame, labels: list) -> None:
- """Plot scatter plots for each column in input dataframe
+ """Plot scatter plots for each column in input dataframe.
Parameters
----------
- df: pd.DataFrame)
+ df : pd.DataFrame)
Dataframe containing data to be plotted.
- labels: list
+ labels : list
List of columns in dataframe to plot.
"""
# Create separate plots for each label.
@@ -138,14 +139,13 @@ def plot_df(df: pd.DataFrame, labels: list) -> None:
def plot_summary_means(data: dict, labels: list) -> None:
- """Plot a bar chart for each labelled duration comparing the files
- specified by keys of the input data.
+ """Plot bar chart comparing durations for specified files and keys.
Parameters
----------
- data: dict
+ data : dict
Dictionary of summary data in the form data[file][label][mean].
- labels: list
+ labels : list
List of summary labels to plot bar charts for.
"""
alpha = 0.9
@@ -174,13 +174,13 @@ def plot_summary_means(data: dict, labels: list) -> None:
def plot_summary_with_stddev(data: dict, labels: list) -> None:
- """Plot scatter plot with error bars of summary data from benchmarking output files
+ """Plot scatter plot with error bars of summary data from benchmarking output files.
Parameters
----------
- data: dict
+ data : dict
Dictionary of summary data in the form data[file][label][mean, stddev].
- labels: list
+ labels : list
List of summary labels to plot on the same graph.
"""
# Loop over each file
@@ -224,3 +224,203 @@ def plot_summary_with_stddev(data: dict, labels: list) -> None:
fontsize=7.5,
)
plt.show()
+
+
+def read_slurm_walltime(filepath: str, labels: list) -> dict:
+ """Read benchmarking data from each loop iteration.
+
+ Parameters
+ ----------
+ filepath : str
+ Path to file containing benchmarking data to be read.
+ labels : list
+ List of all benchmarks run, matching the run order.
+ Typically of the form [model]_[forpy/torch]_[cpu/gpu].
+
+ Returns
+ -------
+ benchmarks : dict
+ Dictionary of times, with keys corresponding to each input label.
+ """
+ print(f"Reading: {filepath}")
+
+ current_label = ""
+ i = 0
+ benchmarks = {}
+
+ with open(filepath) as f:
+ lines = f.readlines()
+ for line in lines:
+ if "Command being timed" in line:
+ # Cut from 'Command being timed: "./benchmarker_cgdrag_forpy...'
+ # to 'cgdrag_forpy'
+ current_label = line.split()[3][15:]
+ if "Elapsed (wall clock) time" in line:
+ if current_label in labels[i]:
+ benchmarks[labels[i]] = convert_to_seconds(line.split()[7])
+ i += 1
+
+ return benchmarks
+
+
+def convert_to_seconds(time_str: str):
+ """
+ Convert wall time string from /usr/bin/time to time in seconds.
+
+ Parameters
+ ----------
+ time_str : str
+ Time in the format h:mm:ss or m:ss.
+
+ Returns
+ -------
+ time : float
+ Time in seconds.
+ """
+ time = time_str.split(":")
+ if len(time) == 3:
+ return float(time[0]) * 3600 + float(time[1]) * 60 + float(time[2])
+ elif len(time) == 2:
+ return float(time[0]) * 60 + float(time[1])
+ else:
+ raise ValueError("Time format not supported. Expected format: h:mm:ss or m:ss")
+
+
+def plot_walltimes(
+ benchmarks: dict,
+ labels: list,
+ normalise: bool = False,
+ title: Union[str, None] = None,
+ ylabel: Union[str, None] = None,
+ xlabel: Union[str, None] = None,
+ alpha: float = 0.9,
+ bar_width: float = 1.0,
+ yscale: str = "linear",
+ ylim: Union[float, tuple] = 0.0,
+ legend_labels: dict = {},
+ xticklabels: Union[list, None] = None,
+ save_path: Union[str, None] = None,
+):
+ """Plot bar charts comparing walltimes for all labels given.
+
+ Parameters
+ ----------
+ benchmarks : dict
+ Dictionary of times, with keys corresponding to each input label.
+ labels : list
+ List containing subset of benchmark keys to plot.
+ normalise : bool
+ Whether to normalise data, so the maximum value is 1.
+ title : Union[str, None]
+ Title for plot.
+ ylabel : Union[str, None]
+ Y-axis label for plot.
+ xlabel : Union[str, None]
+ X-axis label for plot.
+ alpha : float
+ Opaqu
+ bar_width : float
+ Width(s) of bars.
+ yscale : str
+ Y-axis scale type.
+ ylim : Union[float, tuple]
+ Y-axis value range.
+ legend_labels : dict
+ Dictionary of legend labels for each benchmark. Each key should
+ be present in an item in `labels`, while values specify the legend
+ labels plotted.
+ xticklabels : Union[list, None]
+ List of x-axis tick labels.
+ save_path : Union[str, None]
+ File path to save plot.
+ """
+ if len(benchmarks) == 0:
+ raise ValueError("No data passed in `benchmarks`.")
+
+ # If legend_labels unspecified, create bar for every label
+ num_legend_labels = len(legend_labels)
+ if num_legend_labels == 0:
+ num_x_groups = len(labels)
+ # If legend_labels is specified, check legend labels match benchmark labels
+ # or repeat tje list to match the correct length.
+ elif len(labels) % num_legend_labels != 0:
+ raise ValueError(
+ "The number labels specified in `legend_labels` equal or be a factor"
+ " of the number of labels specified in `labels`"
+ )
+ # Calculate number of groups of bars, each with own xtick
+ else:
+ num_x_groups = len(labels) // num_legend_labels
+
+ # Set up list at each xtick value for each legend key
+ group_data = {} # type: dict
+ for key in legend_labels:
+ group_data[key] = []
+
+ # Central xtick coordinates
+ x = np.arange(num_x_groups)
+
+ # Normalise data if requested
+ benchmarks_copy = benchmarks.copy()
+ if normalise:
+ max_time = 0.0
+ for benchmark, value in benchmarks_copy.items():
+ if benchmark in labels and value > max_time:
+ max_time = value
+ for benchmark, value in benchmarks_copy.items():
+ benchmarks_copy[benchmark] = value / max_time
+
+ # Use legend_labels dictionary to extract data for each legend entry
+ if num_legend_labels > 0:
+ for i, label in enumerate(labels):
+ for key in legend_labels:
+ if key in label:
+ group_data[key].append(benchmarks_copy[label])
+
+ # Plot data for each legend entry
+ for i, key in enumerate(legend_labels):
+ # Bars equal on each side of xtick
+ if num_legend_labels % 2 == 0:
+ xticks = np.linspace(
+ -bar_width / num_legend_labels,
+ bar_width / num_legend_labels,
+ num_legend_labels,
+ )
+ # Middle bar centred on xtick
+ else:
+ xticks = np.linspace(-bar_width, bar_width, num_legend_labels)
+ plt.bar(
+ x + xticks[i],
+ group_data[key],
+ alpha=alpha,
+ width=bar_width,
+ label=legend_labels[key],
+ )
+ else:
+ # Plot bar for each label
+ data = []
+ for label in labels:
+ data.append(benchmarks_copy[label])
+ plt.bar(
+ x,
+ data,
+ alpha=alpha,
+ width=bar_width,
+ )
+
+ plt.xticks(ticks=x, labels=xticklabels)
+ plt.yscale(yscale)
+ plt.ylim(ylim)
+ if ylabel is not None:
+ plt.ylabel(ylabel)
+ else:
+ plt.ylabel("Time / s")
+ if xlabel is not None:
+ plt.xlabel(xlabel)
+ if title is not None:
+ plt.title(title)
+ if legend_labels is not None:
+ plt.legend()
+ if save_path is not None:
+ plt.savefig(save_path, dpi=300)
+ plt.show()
diff --git a/utils/visualise.ipynb b/utils/visualise.ipynb
index e2682fd..4d5b8c1 100644
--- a/utils/visualise.ipynb
+++ b/utils/visualise.ipynb
@@ -15,12 +15,81 @@
"metadata": {},
"outputs": [],
"source": [
- "directory = \"../build/\"\n",
- "files = [\n",
- " \"cgdrag_forpy_1.out\",\n",
- " \"cgdrag_torch_1_explicit.out\",\n",
- " \"cgdrag_torch_1_implicit.out\",\n",
- "]"
+ "directory = \"../../results/\"\n",
+ "\n",
+ "# Icelake CPU results with NoGradMode set in torch_jit_module_forward\n",
+ "filepath_nograd_fix_1k = directory + \"icelake_nograd/output_1000_fix/slurm-34050567.out\"\n",
+ "filepath_nograd_fix_10k = directory + \"icelake_nograd/output_10000_fix/slurm-34051232.out\"\n",
+ "\n",
+ "# ampere (A100 GPU) results with NoGradMode set in torch_jit_module_forward\n",
+ "filepath_nograd_fix_gpu_10k = directory + \"ampere_nograd/output_10000_fix/slurm-34050397.out\"\n",
+ "filepath_nograd_fix_gpu_100k = directory + \"ampere_nograd/output_100000_fix/slurm-34051212.out\"\n",
+ "\n",
+ "# Comparison between gradients enabled, NoGradMode, and NoGradMode with a frozen model, on Sapphire Rapids CPUs\n",
+ "filepath_options_1k = directory + \"sapphire_options_grad/output_1k/slurm-37212483.out\"\n",
+ "filepath_options_10k = directory + \"sapphire_options_grad/output_10k/slurm-37224854.out\"\n",
+ "\n",
+ "# Comparison between gradient enabled, NoGradMode, and NoGradMode with a frozen model, on ampere (A100 GPU)\n",
+ "filepath_options_gpu_10k = directory + \"ampere_options_grad/output_10k/slurm-37429435.out\"\n",
+ "filepath_options_gpu_100k = directory + \"ampere_options_grad/output_100k/slurm-37431441.out\"\n",
+ "\n",
+ "# Comparison between InferenceMode and NoGradMode (both with a frozen model) on Sapphire Rapids CPUs\n",
+ "filepath_infer_1k = directory + \"sapphire_infer/output_1k/slurm-37447583.out\"\n",
+ "filepath_infer_10k = directory + \"sapphire_infer/output_10k/slurm-37449094.out\"\n",
+ "\n",
+ "# Comparison between InferenceMode and NoGradMode (both with a frozen model) on ampere (A100 GPU)\n",
+ "filepath_infer_gpu_10k = directory + \"ampere_infer/output_10k/slurm-37521108.out\"\n",
+ "filepath_infer_gpu_100k = directory + \"ampere_infer/output_100k/slurm-37521956.out\""
+ ]
+ },
+ {
+ "cell_type": "markdown",
+ "metadata": {},
+ "source": [
+ "# FTorch and Forpy on Sapphire Rapids CPUs"
+ ]
+ },
+ {
+ "cell_type": "markdown",
+ "metadata": {},
+ "source": [
+ "Output files here use a significantly modified version of run_benchmarks.sh to allow comparisons between not only Forpy and FTorch, but also switching off gradients and freezing the model, e.g.:\n",
+ "\n",
+ "```bash\n",
+ "nrun=1000\n",
+ "\n",
+ "# Run with gradients on\n",
+ "for n in {1,4,8};\n",
+ "do\n",
+ " export OMP_NUM_THREADS=$n\n",
+ " date;/usr/bin/time -v ./benchmarker_cgdrag_forpy ../cgdrag_model run_emulator_davenet $nrun 10 | tee cgdrag_forpy_$n.out;date\n",
+ " date;/usr/bin/time -v ./benchmarker_cgdrag_torch ../cgdrag_model saved_cgdrag_model_cpu.pt $nrun 10 --explicit_reshape | tee cgdrag_torch_explicit_$n.out;date\n",
+ " date;/usr/bin/time -v ./benchmarker_cgdrag_torch ../cgdrag_model saved_cgdrag_model_cpu.pt $nrun 10 | tee cgdrag_torch_implicit_$n.out;date\n",
+ "\n",
+ " date;/usr/bin/time -v ./benchmarker_resnet_forpy ../resnet_model resnet18 $nrun 10 | tee resnet_forpy_$n.out;date\n",
+ " date;/usr/bin/time -v ./benchmarker_resnet_torch ../resnet_model saved_resnet18_model_cpu.pt $nrun 10 | tee resnet_torch_$n.out;date\n",
+ "done\n",
+ "\n",
+ "cd ../build_sapphire_options_nograd\n",
+ "\n",
+ "# Run with gradients off\n",
+ "for n in {1,4,8};\n",
+ "do\n",
+ " export OMP_NUM_THREADS=$n\n",
+ " date;/usr/bin/time -v ./benchmarker_cgdrag_torch ../cgdrag_model saved_cgdrag_model_cpu.pt $nrun 10 --explicit_reshape | tee cgdrag_torch_explicit_$n.out;date\n",
+ " date;/usr/bin/time -v ./benchmarker_cgdrag_torch ../cgdrag_model saved_cgdrag_model_cpu.pt $nrun 10 | tee cgdrag_torch_implicit_$n.out;date\n",
+ " date;/usr/bin/time -v ./benchmarker_resnet_torch ../resnet_model saved_resnet18_model_cpu.pt $nrun 10 | tee resnet_torch_$n.out;date\n",
+ "done\n",
+ "\n",
+ "# Run with gradients off and use frozen models\n",
+ "for n in {1,4,8};\n",
+ "do\n",
+ " export OMP_NUM_THREADS=$n\n",
+ " date;/usr/bin/time -v ./benchmarker_cgdrag_torch ../cgdrag_model saved_cgdrag_model_freeze_cpu.pt $nrun 10 --explicit_reshape | tee cgdrag_torch_explicit_freeze_$n.out;date\n",
+ " date;/usr/bin/time -v ./benchmarker_cgdrag_torch ../cgdrag_model saved_cgdrag_model_freeze_cpu.pt $nrun 10 | tee cgdrag_torch_implicit_freeze_$n.out;date\n",
+ " date;/usr/bin/time -v ./benchmarker_resnet_torch ../resnet_model saved_resnet18_model_freeze_cpu.pt $nrun 10 | tee resnet_torch_freeze_$n.out;date\n",
+ "done\n",
+ "```"
]
},
{
@@ -29,15 +98,40 @@
"metadata": {},
"outputs": [],
"source": [
- "# Labels can be skipped, but those present must be in order of output \"check iteration [label]\"\n",
- "iteration_labels = [\n",
- " \"inference\",\n",
- " \"create tensors\",\n",
- " \"delete tensors\",\n",
- " \"allocate arrays\",\n",
- " \"deallocate arrays\",\n",
- " \"full loop\",\n",
- "]"
+ "# Create labels matching the order of tests in run_benchmarks.sh\n",
+ "\n",
+ "cpu_options_labels = []\n",
+ "\n",
+ "cpu_tests_grad = [\n",
+ " \"cgdrag_forpy\",\n",
+ " \"cgdrag_torch_explicit\",\n",
+ " \"cgdrag_torch_implicit\",\n",
+ " \"resnet_forpy\",\n",
+ " \"resnet_torch\",\n",
+ "]\n",
+ "\n",
+ "cpu_tests_nograd = [\n",
+ " \"cgdrag_torch_explicit\",\n",
+ " \"cgdrag_torch_implicit\",\n",
+ " \"resnet_torch\",\n",
+ "]\n",
+ "\n",
+ "cpu_tests_nograd_freeze = [\n",
+ " \"cgdrag_torch_explicit\",\n",
+ " \"cgdrag_torch_implicit\",\n",
+ " \"resnet_torch\",\n",
+ "]\n",
+ "cpu_n_threads = [\"1\", \"4\", \"8\"]\n",
+ "\n",
+ "for threads in cpu_n_threads:\n",
+ " for test in cpu_tests_grad:\n",
+ " cpu_options_labels.append(f\"{test}_{threads}_grad\")\n",
+ "for threads in cpu_n_threads:\n",
+ " for test in cpu_tests_nograd:\n",
+ " cpu_options_labels.append(f\"{test}_{threads}_nograd\")\n",
+ "for threads in cpu_n_threads:\n",
+ " for test in cpu_tests_nograd_freeze:\n",
+ " cpu_options_labels.append(f\"{test}_{threads}_freeze\")"
]
},
{
@@ -49,20 +143,22 @@
"name": "stdout",
"output_type": "stream",
"text": [
- "Reading: ../build/cgdrag_forpy_1.out\n",
- "Number of runs: 500\n",
- "Reading: ../build/cgdrag_torch_1_explicit.out\n",
- "Number of runs: 500\n",
- "Reading: ../build/cgdrag_torch_1_implicit.out\n",
- "Number of runs: 500\n"
+ "Reading: ../../results/sapphire_options_grad/output_1k/slurm-37212483.out\n",
+ "Reading: ../../results/sapphire_options_grad/output_10k/slurm-37224854.out\n"
]
}
],
"source": [
- "dataframes = {}\n",
+ "benchmarks_options_1k = rb.read_slurm_walltime(filepath_options_1k, cpu_options_labels)\n",
+ "benchmarks_options_10k = rb.read_slurm_walltime(filepath_options_10k, cpu_options_labels)\n",
+ "\n",
+ "\n",
+ "# Scale by number of iterations\n",
+ "for key, value in benchmarks_options_1k.items():\n",
+ " benchmarks_options_1k[key] = value / 1000\n",
"\n",
- "for file in files:\n",
- " dataframes[file] = rb.read_iteration_data(directory, file, iteration_labels)"
+ "for key, value in benchmarks_options_10k.items():\n",
+ " benchmarks_options_10k[key] = value / 10000"
]
},
{
@@ -72,175 +168,37 @@
"outputs": [
{
"data": {
- "text/html": [
- "
\n",
- "\n",
- "
\n",
- " \n",
- " \n",
- " | \n",
- " inference | \n",
- " create tensors | \n",
- " delete tensors | \n",
- " allocate arrays | \n",
- " deallocate arrays | \n",
- " full loop | \n",
- "
\n",
- " \n",
- " \n",
- " \n",
- " 0 | \n",
- " 0.3735 | \n",
- " 0.0 | \n",
- " 0.0 | \n",
- " 0.0002 | \n",
- " 0.0002 | \n",
- " 0.3766 | \n",
- "
\n",
- " \n",
- " 1 | \n",
- " 0.3501 | \n",
- " 0.0 | \n",
- " 0.0 | \n",
- " 0.0000 | \n",
- " 0.0000 | \n",
- " 0.3521 | \n",
- "
\n",
- " \n",
- " 2 | \n",
- " 0.3442 | \n",
- " 0.0 | \n",
- " 0.0 | \n",
- " 0.0000 | \n",
- " 0.0000 | \n",
- " 0.3463 | \n",
- "
\n",
- " \n",
- " 3 | \n",
- " 0.3540 | \n",
- " 0.0 | \n",
- " 0.0 | \n",
- " 0.0000 | \n",
- " 0.0000 | \n",
- " 0.3560 | \n",
- "
\n",
- " \n",
- " 4 | \n",
- " 0.3402 | \n",
- " 0.0 | \n",
- " 0.0 | \n",
- " 0.0000 | \n",
- " 0.0000 | \n",
- " 0.3424 | \n",
- "
\n",
- " \n",
- " ... | \n",
- " ... | \n",
- " ... | \n",
- " ... | \n",
- " ... | \n",
- " ... | \n",
- " ... | \n",
- "
\n",
- " \n",
- " 495 | \n",
- " 0.4860 | \n",
- " 0.0 | \n",
- " 0.0 | \n",
- " 0.0000 | \n",
- " 0.0000 | \n",
- " 0.4881 | \n",
- "
\n",
- " \n",
- " 496 | \n",
- " 0.4618 | \n",
- " 0.0 | \n",
- " 0.0 | \n",
- " 0.0000 | \n",
- " 0.0000 | \n",
- " 0.4654 | \n",
- "
\n",
- " \n",
- " 497 | \n",
- " 0.4590 | \n",
- " 0.0 | \n",
- " 0.0 | \n",
- " 0.0000 | \n",
- " 0.0000 | \n",
- " 0.4613 | \n",
- "
\n",
- " \n",
- " 498 | \n",
- " 0.4457 | \n",
- " 0.0 | \n",
- " 0.0 | \n",
- " 0.0000 | \n",
- " 0.0000 | \n",
- " 0.4479 | \n",
- "
\n",
- " \n",
- " 499 | \n",
- " 0.4261 | \n",
- " 0.0 | \n",
- " 0.0 | \n",
- " 0.0000 | \n",
- " 0.0000 | \n",
- " 0.4282 | \n",
- "
\n",
- " \n",
- "
\n",
- "
500 rows × 6 columns
\n",
- "
"
- ],
- "text/plain": [
- " inference create tensors delete tensors allocate arrays \\\n",
- "0 0.3735 0.0 0.0 0.0002 \n",
- "1 0.3501 0.0 0.0 0.0000 \n",
- "2 0.3442 0.0 0.0 0.0000 \n",
- "3 0.3540 0.0 0.0 0.0000 \n",
- "4 0.3402 0.0 0.0 0.0000 \n",
- ".. ... ... ... ... \n",
- "495 0.4860 0.0 0.0 0.0000 \n",
- "496 0.4618 0.0 0.0 0.0000 \n",
- "497 0.4590 0.0 0.0 0.0000 \n",
- "498 0.4457 0.0 0.0 0.0000 \n",
- "499 0.4261 0.0 0.0 0.0000 \n",
- "\n",
- " deallocate arrays full loop \n",
- "0 0.0002 0.3766 \n",
- "1 0.0000 0.3521 \n",
- "2 0.0000 0.3463 \n",
- "3 0.0000 0.3560 \n",
- "4 0.0000 0.3424 \n",
- ".. ... ... \n",
- "495 0.0000 0.4881 \n",
- "496 0.0000 0.4654 \n",
- "497 0.0000 0.4613 \n",
- "498 0.0000 0.4479 \n",
- "499 0.0000 0.4282 \n",
- "\n",
- "[500 rows x 6 columns]"
- ]
- },
- "execution_count": 5,
- "metadata": {},
- "output_type": "execute_result"
- }
- ],
- "source": [
- "dataframes['cgdrag_forpy_1.out']"
+ "image/png": "iVBORw0KGgoAAAANSUhEUgAAAkAAAAHHCAYAAABXx+fLAAAAOXRFWHRTb2Z0d2FyZQBNYXRwbG90bGliIHZlcnNpb24zLjcuMywgaHR0cHM6Ly9tYXRwbG90bGliLm9yZy/OQEPoAAAACXBIWXMAAA9hAAAPYQGoP6dpAABGOklEQVR4nO3deXwO5/7/8fedkF2CiEQIsbX2xFJOlNpiSdVSpahTEcWvtZSqFtUGRbWqjmos1SrqVG1tVR0nSg49LVp71U5LrRFrUltCMr8/+nUfd5OQO+7bjXk9H4/7cXJfc801n7lz9+Rt5poZi2EYhgAAAEzEzdUFAAAA3G0EIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIMAFwsPD1aNHD1eXkaO+ffuqefPmri7DtNauXSuLxaK1a9e6upQ8mzNnjiwWiw4fPuzSOmbMmKHSpUsrPT3dpXXg/kAAAmB16NAhffzxx3rttdeyLUtLS9Po0aMVEREhPz8/eXt7q1q1aho6dKhOnDhh7dejRw9ZLBbry9/fXxEREXrvvfds/jD16NFDfn5+udbi5+eX75C4b98+vfTSS6pfv768vLxu+8d52bJlqlWrlry8vFS6dGmNHDlS169fz9bvwoUL6tOnj4KCguTr66smTZpo69atdzRmXsyfP1+TJ0/O17qO9NZbb2np0qWuLiNXPXr0UEZGhj788ENXl4L7gQHgritTpowRGxvr6jKyGThwoPHQQw9la//111+NsmXLGu7u7kaXLl2MhIQEY+bMmUb//v2NwMBAo2LFita+sbGxhqenpzFv3jxj3rx5xgcffGA0btzYkGR07tzZpp+vr2+utfj6+ub7M5o9e7bh5uZmVKtWzYiMjDQkGYcOHcqx74oVKwyLxWI0adLEmDlzpjFgwADDzc3NeP755236ZWZmGvXr1zd8fX2NUaNGGQkJCUaVKlWMQoUKGfv378/XmDnJzMw0rly5YmRmZlrbWrdubZQpU8buz8HRcvudXL9+3bhy5YqRlZV194v6i1dffdUoU6bMPVEL7m0EIMAF8hKALl68eHeK+T8ZGRlGsWLFjNdff92m/dq1a0ZERITh4+NjfP/999nWS01NNV577TXr+5yCTWZmplGnTh1DknH8+PFc+93sTgLQ2bNnjbS0NMMwDOPdd9+9ZQCqUqWKERERYVy7ds3aNmLECMNisRh79uyxti1cuNCQZCxevNjalpKSYhQuXNjo2rVrvsbMK2cEoBtByx538ju5WzZv3mxIMpKSklxdCu5xnAID/uL48eN67rnnFBoaKk9PT5UtW1YvvPCCMjIyrH127NihRo0aydvbW6VKldLYsWM1e/bsbKdaDMPQ2LFjVapUKfn4+KhJkybatWtXtm3emEPx3XffqW/fvipevLhKlSolSfr999/Vt29fPfzww/L29lZgYKA6deqU4ymdvNaVkx9++EFnzpxRdHS0TfsXX3yhn3/+WSNGjFCDBg2yrefv769x48bdcmw3Nzc1btxYku7KPJGiRYuqUKFCt+23e/du7d69W3369FGBAgWs7X379pVhGFqyZIm1bcmSJQoODlaHDh2sbUFBQXr66af19ddfW0/v2TNmTv46B6hx48b617/+pd9//916WjE8PNzaPz09XSNHjlSFChXk6empsLAwvfrqq9nmwVgsFvXv31+fffaZqlatKk9PTyUmJkqSJk6cqPr16yswMFDe3t6qXbt2tjotFosuXbqkuXPnWuu4cYoytzlA06ZNs24rNDRU/fr104ULF2z6NG7cWNWqVdPu3bvVpEkT+fj4qGTJkpowYUK2z+aDDz5Q1apV5ePjoyJFiqhOnTqaP3++TZ/atWuraNGi+vrrr2/5OQMFbt8FMI8TJ06obt261rkelSpV0vHjx7VkyRJdvnxZHh4eOn78uJo0aSKLxaLhw4fL19dXH3/8sTw9PbONFx8fr7Fjx+rxxx/X448/rq1bt6pFixY2Yepmffv2VVBQkOLj43Xp0iVJ0qZNm7R+/Xp16dJFpUqV0uHDhzV9+nQ1btxYu3fvlo+PjyTZVVdO1q9fL4vFopo1a9q0L1u2TJL07LPP5vlzzMmvv/4qSQoMDLyjcRxp27ZtkqQ6derYtIeGhqpUqVLW5Tf61qpVS25utv9urFu3rmbOnKn9+/erevXqdo2ZFyNGjFBqaqqOHTumf/zjH5JknTuVlZWltm3b6ocfflCfPn1UuXJl/fLLL/rHP/6h/fv3Z5uv85///EeLFi1S//79VaxYMWuQev/999W2bVt169ZNGRkZWrBggTp16qTly5erdevWkqR58+apV69eqlu3rvr06SNJKl++fK51jxo1SqNHj1Z0dLReeOEF7du3T9OnT9emTZu0bt06FSxY0Nr3/PnzatWqlTp06KCnn35aS5Ys0dChQ1W9enXFxMRIkj766CO9+OKL6tixowYOHKirV69qx44d+umnn/TMM8/YbLtWrVpat26dXZ8zTMjFR6CAe0r37t0NNzc3Y9OmTdmW3ZhTMGDAAMNisRjbtm2zLjt79qxRtGhRm1MtKSkphoeHh9G6dWub+QivvfaaIcnmVMLs2bMNSUaDBg2M69ev22z38uXL2WrZsGGDIcn49NNPrW15rSs3f//7343AwMBs7TVr1jQCAgJuue7NbpzaOn36tHH69Gnj4MGDxltvvWVYLBajRo0a2frlxlGnW251CuzGsiNHjmRb9sgjjxh/+9vfbOrp2bNntn7/+te/DElGYmKi3WPmZM2aNYYkY82aNda23E6BzZs3z3Bzc8t2anLGjBmGJGPdunXWNkmGm5ubsWvXrmzj/PU7lpGRYVSrVs1o2rSpTXtuv5Mb39+/fvdbtGhhM5cpISHBkGR88skn1rZGjRpl+y6np6cbISEhxlNPPWVta9eunVG1atVs285Jnz59DG9v7zz1hXlxCgz4P1lZWVq6dKnatGmT7V/v0p+nACQpMTFRUVFRioyMtC4rWrSounXrZtN/9erVysjI0IABA6zrStKgQYNyraF3795yd3e3afP29rb+fO3aNZ09e1YVKlRQ4cKFba5AymtduTl79qyKFCmSrT0tLS1Pp5NudunSJQUFBSkoKEgVKlTQa6+9pqioKH311Vd2jeNsV65ckaQcj5J5eXlZl9/om1u/m8eyZ8w7tXjxYlWuXFmVKlXSmTNnrK+mTZtKktasWWPTv1GjRqpSpUq2cW7+jp0/f16pqalq2LBhrle43c6N7/6gQYNsjpj17t1b/v7++te//mXT38/PT3//+9+t7z08PFS3bl399ttv1rbChQvr2LFj2rRp0223X6RIEV25ckWXL1/OV/0wB06BAf/n9OnTSktLU7Vq1W7Z7/fff1dUVFS29goVKmTrJ0kVK1a0aQ8KCsoxaEhS2bJls7VduXJF48eP1+zZs3X8+HEZhmFdlpqaanddt3Lz2Df4+/vb/CHKCy8vL33zzTeSZJ1HdWNOkz1uDo7OcOMPf073jbl69apNMPD29s61381j2TPmnTpw4ID27NmjoKCgHJenpKTYvM/p+yVJy5cv19ixY7V9+3abuvP7+d/47j/88MM27R4eHipXrpx1+Q2lSpXKtq0iRYpox44d1vdDhw7V6tWrVbduXVWoUEEtWrTQM888o0cffTTb9m98j539/cH9jQAE3ENy+uM4YMAAzZ49W4MGDVJUVJQCAgJksVjUpUsXZWVlOWzbgYGBOn/+fLb2SpUqadu2bTp69KjCwsLyNJa7u3u2ydR/5eXlpfT0dBmGke0PlWEYunr1qvXoirOUKFFCknTy5Mls+3by5EnVrVvXpu/JkyezjXGjLTQ01O4x71RWVpaqV6+uSZMm5bj8r9vP6fv1/fffq23btnrsscc0bdo0lShRQgULFtTs2bOzTTB2lr8e9bzh5kBeuXJl7du3T8uXL1diYqK++OILTZs2TfHx8Ro9erTNeufPn5ePj49DwyYePJwCA/5PUFCQ/P39tXPnzlv2K1OmjA4ePJit/a9tZcqUkfTnv9Jvdvr06RyDRm6WLFmi2NhYvffee+rYsaOaN2+uBg0aZLuaJq915aZSpUrW0x83a9OmjSTpn//8Z55rzosyZcro+vXr1snRNzt48KAyMzOtn6Gz3DhduHnzZpv2EydO6NixYzanEyMjI7V169ZsofOnn36Sj4+PHnroIbvHzKvcjmSUL19e586dU7NmzRQdHZ3t9dcjMDn54osv5OXlpZUrV6pnz56KiYnJNbzm9YjKjd/bvn37bNozMjJ06NChfP9efX191blzZ82ePVtHjhxR69atNW7cOOtRuBsOHTqkypUr52sbMA8CEPB/3Nzc1L59e33zzTfZ/nhJ//vXaMuWLbVhwwZt377duuzcuXP67LPPbPpHR0erYMGC+uCDD2z+JWvvHX3d3d2znZr64IMPlJmZadOW17pyExUVJcMwtGXLFpv2jh07qnr16ho3bpw2bNiQbb0//vhDI0aMyOPe/M+Nq3sSEhKyLZs6dapNH2epWrWqKlWqpJkzZ9p8ntOnT5fFYlHHjh2tbR07dtSpU6f05ZdfWtvOnDmjxYsXq02bNtY5P/aMmVe+vr7ZgqkkPf300zp+/Lg++uijbMuuXLlivZLwVtzd3WWxWGxqPXz4cI53fPb19c0WvHMSHR0tDw8PTZkyxea7O2vWLKWmplqvLLPH2bNnbd57eHioSpUqMgxD165ds1m2detW1a9f3+5twFw4BQbc5K233tK3336rRo0aWS8rPnnypBYvXqwffvhBhQsX1quvvqp//vOfat68uQYMGGC93Lx06dI6d+6c9V/JQUFBGjJkiMaPH68nnnhCjz/+uLZt26Z///vfKlasWJ5reuKJJzRv3jwFBASoSpUq2rBhg1avXp3tcvK81pWbBg0aKDAwUKtXr7ZOopWkggUL6ssvv1R0dLQee+wxPf3003r00UdVsGBB7dq1S/Pnz1eRIkVuey+gv4qMjFSvXr30/vvv68CBA9bnj61atUorVqxQr169FBERYbPOjcu2b3cvodTUVH3wwQeSZL0cOiEhQYULF1bhwoXVv39/a993331Xbdu2VYsWLdSlSxft3LlTCQkJ6tWrl81RhI4dO+pvf/ub4uLitHv3bhUrVkzTpk1TZmZmtlMweR0zr2rXrq2FCxdq8ODBeuSRR+Tn56c2bdro2Wef1aJFi/T8889rzZo1evTRR5WZmam9e/dq0aJFWrlyZY4T+m/WunVrTZo0Sa1atdIzzzyjlJQUTZ06VRUqVLCZg3OjjtWrV2vSpEkKDQ1V2bJlVa9evWxjBgUFafjw4Ro9erRatWqltm3bat++fZo2bZoeeeQRmwnPedWiRQuFhITo0UcfVXBwsPbs2aOEhAS1bt3aZpL+li1bdO7cObVr187ubcBkXHPxGXDv+v33343u3bsbQUFBhqenp1GuXDmjX79+Rnp6urXPtm3bjIYNGxqenp5GqVKljPHjxxtTpkwxJBnJycnWfpmZmcbo0aONEiVKGN7e3kbjxo2NnTt3ZrsT9I3LiHO6/P78+fNGXFycUaxYMcPPz89o2bKlsXfv3hzvJp3XunLz4osvGhUqVMhx2fnz5434+HijevXqho+Pj+Hl5WVUq1bNGD58uHHy5Elrv9td3n6zzMxM4/333zciIiIMLy8vw8vLy4iIiDCmTJlic/n0DcWKFbvtZeSGYRiHDh0yJOX4yuly8q+++sqIjIy0fm6vv/66kZGRka3fuXPnjOeee84IDAw0fHx8jEaNGuX4O7NnzL/K6TL4ixcvGs8884xRuHDhbPuQkZFhvPPOO0bVqlUNT09Po0iRIkbt2rWN0aNHG6mpqdZ+kox+/frluM1Zs2YZFStWNDw9PY1KlSoZs2fPNkaOHGn89U/E3r17jccee8zw9va2uZXDXy+DvyEhIcGoVKmSUbBgQSM4ONh44YUXjPPnz9v0adSoUY6Xt8fGxtrs54cffmg89thjRmBgoOHp6WmUL1/eeOWVV2z20TAMY+jQoUbp0qV5FAZuy2IYOVz2AcBugwYN0ocffqiLFy/mOqnTFeyp67ffflOlSpX073//W82aNbtLFebN7t27VbVqVZub8wE3S09PV3h4uIYNG6aBAwe6uhzc45gDBOTDX+/lcvbsWc2bN08NGjRwafi507rKlSun5557Tm+//bazSsy3NWvWKCoqivCDXM2ePVsFCxbU888/7+pScB/gCBCQD5GRkWrcuLEqV66sU6dOadasWTpx4oSSkpL02GOPURcA3OOYBA3kw+OPP64lS5Zo5syZslgsqlWrlmbNmuXykHGv1gUA9xqOAAEAANNhDhAAADAdAhAAADAd5gDlICsrSydOnFChQoV4mB4AAPcJwzD0xx9/KDQ0VG5utz7GQwDKwYkTJ/L80EcAAHBvOXr0qEqVKnXLPgSgHNy4rfrRo0fl7+/v4moAAEBepKWlKSwszObxKLkhAOXgxmkvf39/AhAAAPeZvExfYRI0AAAwHQIQAAAwHQIQAAAwHeYAAQBwhzIzM3Xt2jVXl/HAK1iwoMMeOE0AAgAgnwzDUHJysi5cuODqUkyjcOHCCgkJueP79BGAAADIpxvhp3jx4vLx8eHmuU5kGIYuX76slJQUSVKJEiXuaDwCEAAA+ZCZmWkNP4GBga4uxxS8vb0lSSkpKSpevPgdnQ5jEjQAAPlwY86Pj4+Piysxlxuf953OuSIAAQBwBzjtdXc56vMmAAEAANMhAAEAANNhEjQAAA5Ud9zqu7q9jSOi7V6nR48emjt3brb2AwcOqEKFCo4o655HAAIAwIRatWql2bNn27QFBQXZPU5GRoY8PDwcVdZdwykwAABMyNPTUyEhITYvd3d3fffdd6pbt648PT1VokQJDRs2TNevX7eu17hxY/Xv31+DBg1SsWLF1LJlS0l/Tk6ePn26YmJi5O3trXLlymnJkiXW9Zo2bar+/fvb1HD69Gl5eHgoKSnp7uz0TQhAAABAknT8+HE9/vjjeuSRR/Tzzz9r+vTpmjVrlsaOHWvTb+7cufLw8NC6des0Y8YMa/sbb7yhp556Sj///LO6deumLl26aM+ePZKkXr16af78+UpPT7f2/+c//6mSJUuqadOmd2cHb8IpMBe42+eHnS0/558BAK61fPly+fn5Wd/HxMTooYceUlhYmBISEmSxWFSpUiWdOHFCQ4cOVXx8vNzc/jxuUrFiRU2YMCHbmJ06dVKvXr0kSWPGjNGqVav0wQcfaNq0aerQoYP69++vr7/+Wk8//bQkac6cOerRo4dLbiXAESAAAEyoSZMm2r59u/U1ZcoU7dmzR1FRUTaB5NFHH9XFixd17Ngxa1vt2rVzHDMqKirb+xtHgLy8vPTss8/qk08+kSRt3bpVO3fuVI8ePRy8Z3nDESAAAEzI19c331d8+fr65mu9Xr16KTIyUseOHdPs2bPVtGlTlSlTJl9j3SmOAAEAAElS5cqVtWHDBhmGYW1bt26dChUqpFKlSt12/R9//DHb+8qVK1vfV69eXXXq1NFHH32k+fPnq2fPno4r3k4EIAAAIEnq27evjh49qgEDBmjv3r36+uuvNXLkSA0ePNg6/+dWFi9erE8++UT79+/XyJEjtXHjxmxXfvXq1Utvv/22DMPQk08+6axduS0CEAAAkCSVLFlSK1as0MaNGxUREaHnn39ezz33nF5//fU8rT969GgtWLBANWrU0KeffqrPP/9cVapUsenTtWtXFShQQF27dpWXl5czdiNPmAMEAIAD3Q9Xxs6ZMyfXZY0aNdLGjRtzXb527dpcl4WGhurbb7+95bbPnDmjq1ev6rnnnrtdmU5FAAIAAE537do1nT17Vq+//rr+9re/qVatWi6th1NgAADA6datW6cSJUpo06ZNNjdPdBWOAAEAgDt285VjOWncuPFt+9xNHAECAACmQwACAACmQwACAACmQwACAACmQwACAACmQwACAACmQwACAAAusXbtWlksFl24cOGub5v7AAEA4EgTH7672xuyz+5VevTooblz59q93po1a9S4cWO717sXEYAAADChVq1aafbs2db3GRkZcnd3l7u7uyRp4MCBSktLs+lTtGjRPI+fmZkpi8WSp6fIu8K9WRUAAHAqT09PhYSEWF+lS5dWyZIlre+9vb1t+nh6eqpXr14qUqSIfHx8FBMTowMHDljHmzNnjgoXLqxly5apSpUq8vT01JEjR5Senq6hQ4cqLCxMnp6eqlChgmbNmmVTy5YtW1SnTh35+Piofv362rfP/qNa9iIAAQCA2+rRo4c2b96sZcuWacOGDTIMQ48//riuXbtm7XP58mW98847+vjjj7Vr1y4VL15c3bt31+eff64pU6Zoz549+vDDD+Xn52cz9ogRI/Tee+9p8+bNKlCggHr27On0/eEUGO7c3T7f7Wz5OJ8OAPeb5cuX2wSRmJgYLV68OMe+Bw4c0LJly7Ru3TrVr19fkvTZZ58pLCxMS5cuVadOnST9+cT3adOmKSIiQpK0f/9+LVq0SKtWrVJ0dLQkqVy5ctnGHzdunBo1aiRJGjZsmFq3bq2rV6/Ky8vLcTv8FwQgAABMqEmTJpo+fbr1va+vb6599+zZowIFCqhevXrWtsDAQD388MPas2ePtc3Dw0M1atSwvt++fbvc3d2t4SY3N69TokQJSVJKSopKly6d9x2yEwEIAAAT8vX1VYUKFRw6pre3tywWi837vChYsKD15xvrZ2VlObS2v2IOEAAAuKXKlSvr+vXr+umnn6xtZ8+e1b59+1SlSpVc16tevbqysrL03Xff3Y0y7UIAAgAAt1SxYkW1a9dOvXv31g8//KCff/5Zf//731WyZEm1a9cu1/XCw8MVGxurnj17aunSpTp06JDWrl2rRYsW3cXqc0YAAgAAtzV79mzVrl1bTzzxhKKiomQYhlasWGFz+ion06dPV8eOHdW3b19VqlRJvXv31qVLl+5S1bmzGIZhuLqIe01aWpoCAgKUmpoqf39/h49fd9xqh4/pShs9+7m6BMfiKjAAeXD16lUdOnRIZcuWderVSrB1q8/dnr/fHAECAACmQwACAACmQwACAACmQwACAACmQwACAOAOcC3R3eWoz5sABABAPty4/Pvy5csursRcbnzet7v8/nZ4FAYAAPng7u6uwoULKyUlRZLk4+Nj8xgIOJZhGLp8+bJSUlJUuHBhubu739F4BCAAAPIpJCREkqwhCM5XuHBh6+d+JwhAAADkk8ViUYkSJVS8eHFdu3bN1eU88AoWLHjHR35uIAABAHCH3N3dHfaHGXcHk6ABAIDp3BMBaOrUqQoPD5eXl5fq1aunjRs35tr3o48+UsOGDVWkSBEVKVJE0dHR2fobhqH4+HiVKFFC3t7eio6O1oEDB5y9GwAA4D7h8gC0cOFCDR48WCNHjtTWrVsVERGhli1b5jqhbO3ateratavWrFmjDRs2KCwsTC1atNDx48etfSZMmKApU6ZoxowZ+umnn+Tr66uWLVvq6tWrd2u3AADAPczlT4OvV6+eHnnkESUkJEiSsrKyFBYWpgEDBmjYsGG3XT8zM1NFihRRQkKCunfvLsMwFBoaqpdffllDhgyRJKWmpio4OFhz5sxRly5dbjsmT4O3D0+DBwDcC+6bp8FnZGRoy5Ytio6Otra5ubkpOjpaGzZsyNMYly9f1rVr11S0aFFJ0qFDh5ScnGwzZkBAgOrVq5frmOnp6UpLS7N5AQCAB5dLA9CZM2eUmZmp4OBgm/bg4GAlJyfnaYyhQ4cqNDTUGnhurGfPmOPHj1dAQID1FRYWZu+uAACA+4jL5wDdibffflsLFizQV199JS8vr3yPM3z4cKWmplpfR48edWCVAADgXuPS+wAVK1ZM7u7uOnXqlE37qVOnbnuXx4kTJ+rtt9/W6tWrVaNGDWv7jfVOnTqlEiVK2IwZGRmZ41ienp7y9PTM514AAID7jUuPAHl4eKh27dpKSkqytmVlZSkpKUlRUVG5rjdhwgSNGTNGiYmJqlOnjs2ysmXLKiQkxGbMtLQ0/fTTT7ccEwAAmIfL7wQ9ePBgxcbGqk6dOqpbt64mT56sS5cuKS4uTpLUvXt3lSxZUuPHj5ckvfPOO4qPj9f8+fMVHh5undfj5+cnPz8/WSwWDRo0SGPHjlXFihVVtmxZvfHGGwoNDVX79u1dtZsAAOAe4vIA1LlzZ50+fVrx8fFKTk5WZGSkEhMTrZOYjxw5Ije3/x2omj59ujIyMtSxY0ebcUaOHKlRo0ZJkl599VVdunRJffr00YULF9SgQQMlJibe0TwhAADw4HD5fYDuRdwHyD7cBwgAcC+4b+4DBAAA4AoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDoEIAAAYDp2B6CjR4/q2LFj1vcbN27UoEGDNHPmTIcWBgAA4Cx2B6BnnnlGa9askSQlJyerefPm2rhxo0aMGKE333zT4QUCAAA4mt0BaOfOnapbt64kadGiRapWrZrWr1+vzz77THPmzHF0fQAAAA5ndwC6du2aPD09JUmrV69W27ZtJUmVKlXSyZMnHVsdAACAE9gdgKpWraoZM2bo+++/16pVq9SqVStJ0okTJxQYGOjwAgEAABzN7gD0zjvv6MMPP1Tjxo3VtWtXRURESJKWLVtmPTUGAABwLytg7wqNGzfWmTNnlJaWpiJFiljb+/TpIx8fH4cWBwAA4Ax2ByBJcnd3twk/khQeHu6IegAAAJyOGyECAADTIQABAADTIQABAADTyXMA6t69u7744gtdvHjRmfUAAAA4XZ4DUIUKFfTWW28pKChIMTExmj59uo4fP+7M2gAAAJwizwEoPj5eW7Zs0YEDB9SmTRstXbpU5cuXV+3atfXmm29q+/btTiwTAADAceyeA1SqVCn17dtXK1eu1OnTpzV06FDt27dPTZs2VZkyZdS/f3/t2rXLGbUCAAA4xB1Ngi5UqJCefvppffbZZzp9+rQ++eQTubu7a8OGDY6qDwAAwOHydSPEnLi7u6tZs2Zq1qyZo4YEAABwCi6DBwAApkMAAgAApkMAAgAApuPyADR16lSFh4fLy8tL9erV08aNG3Ptu2vXLj311FMKDw+XxWLR5MmTs/UZNWqULBaLzatSpUpO3AMAAHC/ydck6KSkJCUlJSklJUVZWVk2yz755JM8j7Nw4UINHjxYM2bMUL169TR58mS1bNlS+/btU/HixbP1v3z5ssqVK6dOnTrppZdeynXcqlWravXq1db3BQo4bK43AAB4ANh9BGj06NFq0aKFkpKSdObMGZ0/f97mZY9Jkyapd+/eiouLU5UqVTRjxgz5+PjkGqIeeeQRvfvuu+rSpYs8PT1zHbdAgQIKCQmxvooVK2ZXXQAA4MFm96GRGTNmaM6cOXr22WfvaMMZGRnasmWLhg8fbm1zc3NTdHT0Hd9H6MCBAwoNDZWXl5eioqI0fvx4lS5dOtf+6enpSk9Pt75PS0u7o+0DAIB7m91HgDIyMlS/fv073vCZM2eUmZmp4OBgm/bg4GAlJyfne9x69eppzpw5SkxM1PTp03Xo0CE1bNhQf/zxR67rjB8/XgEBAdZXWFhYvrcPAADufXYHoF69emn+/PnOqMUhYmJi1KlTJ9WoUUMtW7bUihUrdOHCBS1atCjXdYYPH67U1FTr6+jRo3exYgAAcLfZfQrs6tWrmjlzplavXq0aNWqoYMGCNssnTZqUp3GKFSsmd3d3nTp1yqb91KlTCgkJsbesXBUuXFgPPfSQDh48mGsfT0/PW84pAgAADxa7jwDt2LFDkZGRcnNz086dO7Vt2zbry54nwnt4eKh27dpKSkqytmVlZSkpKUlRUVH2lpWrixcv6tdff1WJEiUcNiYAALi/2X0EaM2aNQ7b+ODBgxUbG6s6deqobt26mjx5si5duqS4uDhJUvfu3VWyZEmNHz9e0p/zj3bv3m39+fjx49q+fbv8/PxUoUIFSdKQIUPUpk0blSlTRidOnNDIkSPl7u6url27OqxuAABwf7ujG+QcO3ZMklSqVKl8rd+5c2edPn1a8fHxSk5OVmRkpBITE60To48cOSI3t/8dpDpx4oRq1qxpfT9x4kRNnDhRjRo10tq1a601de3aVWfPnlVQUJAaNGigH3/8UUFBQfncSwAA8KCxGIZh2LNCVlaWxo4dq/fee08XL16UJBUqVEgvv/yyRowYYRNY7ldpaWkKCAhQamqq/P39HT5+3XGrb9/pPrLRs5+rS3CsIftcXQEAIB/s+ftt9xGgESNGaNasWXr77bf16KOPSpJ++OEHjRo1SlevXtW4cePyVzUAAMBdYncAmjt3rj7++GO1bdvW2lajRg2VLFlSffv2JQABAIB7nt3nq86dO5fjw0UrVaqkc+fOOaQoAAAAZ7I7AEVERCghISFbe0JCgiIiIhxSFAAAgDPZfQpswoQJat26tVavXm29X8+GDRt09OhRrVixwuEFAgAAOJrdR4AaNWqk/fv368knn9SFCxd04cIFdejQQfv27VPDhg2dUSMAAIBD5es+QKGhoUx2BgAA9608BaAdO3aoWrVqcnNz044dO27Zt0aNGg4pDAAAwFnyFIAiIyOVnJys4sWLKzIyUhaLRTndP9FisSgzM9PhRQIAADhSngLQoUOHrI+SOHTokFMLAgAAcLY8BaAyZcpYf/79999Vv359FShgu+r169e1fv16m74AAAD3IruvAmvSpEmONzxMTU1VkyZNHFIUAACAM9kdgAzDkMViydZ+9uxZ+fr6OqQoAAAAZ8rzZfAdOnSQ9OdE5x49esjT09O6LDMzUzt27FD9+vUdXyEAAICD5TkABQQESPrzCFChQoXk7e1tXebh4aG//e1v6t27t+MrBAAAcLA8B6DZs2dLksLDwzVkyBBOdwEAgPuW3XeCHjlypDPqAAAAuGvy9SiMJUuWaNGiRTpy5IgyMjJslm3dutUhhQEAADiL3VeBTZkyRXFxcQoODta2bdtUt25dBQYG6rffflNMTIwzagQAAHAouwPQtGnTNHPmTH3wwQfy8PDQq6++qlWrVunFF19UamqqM2oEAABwKLsD0JEjR6yXu3t7e+uPP/6QJD377LP6/PPPHVsdAACAE9gdgEJCQqx3gi5durR+/PFHSX8+IyynB6QCAADca+wOQE2bNtWyZcskSXFxcXrppZfUvHlzde7cWU8++aTDCwQAAHA0u68CmzlzprKysiRJ/fr1U2BgoNavX6+2bdvq//2//+fwAgEAABzNrgB0/fp1vfXWW+rZs6dKlSolSerSpYu6dOnilOIAAACcwa5TYAUKFNCECRN0/fp1Z9UDAADgdHbPAWrWrJm+++47Z9QCAABwV9g9BygmJkbDhg3TL7/8otq1a2d7Jljbtm0dVhwAAIAz2B2A+vbtK0maNGlStmUWi0WZmZl3XhUAAIAT2R2AblwBBgAAcL+yew7Qza5eveqoOgAAAO4auwNQZmamxowZo5IlS8rPz0+//fabJOmNN97QrFmzHF4gAACAo9kdgMaNG6c5c+ZowoQJ8vDwsLZXq1ZNH3/8sUOLAwAAcAa7A9Cnn36qmTNnqlu3bnJ3d7e2R0REaO/evQ4tDgAAwBnsDkDHjx9XhQoVsrVnZWXp2rVrDikKAADAmewOQFWqVNH333+frX3JkiWqWbOmQ4oCAABwJrsvg4+Pj1dsbKyOHz+urKwsffnll9q3b58+/fRTLV++3Bk1AgAAOJTdR4DatWunb775RqtXr5avr6/i4+O1Z88effPNN2revLkzagQAAHAou48ASVLDhg21atUqR9cCAABwV9h9BKhcuXI6e/ZstvYLFy6oXLlyDikKAADAmewOQIcPH87xeV/p6ek6fvy4Q4oCAABwpjyfAlu2bJn155UrVyogIMD6PjMzU0lJSQoPD3docQAAAM6Q5wDUvn17SX8+8T02NtZmWcGCBRUeHq733nvPocUBAAA4Q54D0I2nwJctW1abNm1SsWLFnFYUAACAM9l9FdihQ4ecUQcAAMBdk6cANGXKFPXp00deXl6aMmXKLfu++OKLDikMAADAWfIUgP7xj3+oW7du8vLy0j/+8Y9c+1ksFgIQAAC45+UpAN182otTYAAA4H5n932AAAAA7ncEIAAAYDoEIAAAYDoEIAAAYDp2BaDr16/rzTff1LFjx5xVDwAAgNPZFYAKFCigd999V9evX3dWPQAAAE5n9ymwpk2b6rvvvnNGLQAAAHeF3Y/CiImJ0bBhw/TLL7+odu3a8vX1tVnetm1bhxUHAADgDHYHoL59+0qSJk2alG2ZxWJRZmbmnVcFAADgRHYHoBtPhQcAALhf3dFl8FevXnVUHQAAAHeN3QEoMzNTY8aMUcmSJeXn56fffvtNkvTGG29o1qxZDi8QAADA0ewOQOPGjdOcOXM0YcIEeXh4WNurVaumjz/+2KHFAQAAOIPdAejTTz/VzJkz1a1bN7m7u1vbIyIitHfvXocWBwAA4Ax2B6Djx4+rQoUK2dqzsrJ07do1hxQFAADgTHYHoCpVquj777/P1r5kyRLVrFnTIUUBAAA4k92XwcfHxys2NlbHjx9XVlaWvvzyS+3bt0+ffvqpli9f7owaAQAAHMruI0Dt2rXTN998o9WrV8vX11fx8fHas2ePvvnmGzVv3twZNQIAADhUvu4D1LBhQ61atUopKSm6fPmyfvjhB7Vo0SJfBUydOlXh4eHy8vJSvXr1tHHjxlz77tq1S0899ZTCw8NlsVg0efLkOx4TAACYT75vhLh582bNmzdP8+bN05YtW/I1xsKFCzV48GCNHDlSW7duVUREhFq2bKmUlJQc+1++fFnlypXT22+/rZCQEIeMCQAAzMdiGIZhzwrHjh1T165dtW7dOhUuXFiSdOHCBdWvX18LFixQqVKl8jxWvXr19MgjjyghIUHSn1eShYWFacCAARo2bNgt1w0PD9egQYM0aNAgh415Q1pamgICApSamip/f/88709e1R232uFjutJGz36uLsGxhuxzdQUAgHyw5++33UeAevXqpWvXrmnPnj06d+6czp07pz179igrK0u9evXK8zgZGRnasmWLoqOj/1eMm5uio6O1YcMGe8u6ozHT09OVlpZm8wIAAA8uuwPQd999p+nTp+vhhx+2tj388MP64IMP9N///jfP45w5c0aZmZkKDg62aQ8ODlZycrK9Zd3RmOPHj1dAQID1FRYWlq/tAwCA+4PdASgsLCzHGx5mZmYqNDTUIUXdbcOHD1dqaqr1dfToUVeXBAAAnMjuAPTuu+9qwIAB2rx5s7Vt8+bNGjhwoCZOnJjncYoVKyZ3d3edOnXKpv3UqVO5TnB21pienp7y9/e3eQEAgAeX3QGoR48e2r59u+rVqydPT095enqqXr162rp1q3r27KmiRYtaX7fi4eGh2rVrKykpydqWlZWlpKQkRUVF2b8nThoTAAA8eOy+E3Ru997Jj8GDBys2NlZ16tRR3bp1NXnyZF26dElxcXGSpO7du6tkyZIaP368pD8nOe/evdv68/Hjx7V9+3b5+flZn092uzEBAADsDkCxsbEO23jnzp11+vRpxcfHKzk5WZGRkUpMTLROYj5y5Ijc3P53kOrEiRM2zxubOHGiJk6cqEaNGmnt2rV5GhMAAMDu+wCZAfcBsg/3AQIA3Auceh8gAACA+x0BCAAAmA4BCAAAmE6+A9DBgwe1cuVKXblyRZLEVCIAAHC/sDsAnT17VtHR0XrooYf0+OOP6+TJk5Kk5557Ti+//LLDCwQAAHA0uwPQSy+9pAIFCujIkSPy8fGxtnfu3FmJiYkOLQ4AAMAZ7L4P0LfffquVK1eqVKlSNu0VK1bU77//7rDCAAAAnMXuI0CXLl2yOfJzw7lz5+Tp6emQogAAAJzJ7gDUsGFDffrpp9b3FotFWVlZmjBhgpo0aeLQ4gAAAJzB7lNgEyZMULNmzbR582ZlZGTo1Vdf1a5du3Tu3DmtW7fOGTUCAAA4lN1HgKpVq6b9+/erQYMGateunS5duqQOHTpo27ZtKl++vDNqBAAAcCi7jwBJUkBAgEaMGOHoWgAAAO6KfAWgq1evaseOHUpJSVFWVpbNsrZt2zqkMAAAAGexOwAlJiaqe/fuOnPmTLZlFotFmZmZDikMAADAWeyeAzRgwAB16tRJJ0+eVFZWls2L8AMAAO4HdgegU6dOafDgwQoODnZGPQAAAE5ndwDq2LGj1q5d64RSAAAA7g675wAlJCSoU6dO+v7771W9enUVLFjQZvmLL77osOIAAACcwe4A9Pnnn+vbb7+Vl5eX1q5dK4vFYl1msVgIQAAA4J5ndwAaMWKERo8erWHDhsnNze4zaAAAAC5nd4LJyMhQ586dCT8AAOC+ZXeKiY2N1cKFC51RCwAAwF1h9ymwzMxMTZgwQStXrlSNGjWyTYKeNGmSw4oDAABwBrsD0C+//KKaNWtKknbu3Gmz7OYJ0QAAAPcquwPQmjVrnFEHAADAXcNMZgAAYDp5OgLUoUMHzZkzR/7+/urQocMt+3755ZcOKQwAAMBZ8hSAAgICrPN7AgICnFoQAACAs+UpAM2ePVtvvvmmhgwZotmzZzu7JgAAAKfK8xyg0aNH6+LFi86sBQAA4K7IcwAyDMOZdQAAANw1dl0Fxn1+AADAg8Cu+wA99NBDtw1B586du6OCAAAAnM2uADR69GiuAgMAAPc9uwJQly5dVLx4cWfVAgAAcFfkeQ4Q838AAMCDgqvAAACA6eT5FFhWVpYz6wAAALhreBgqAAAwHbsmQQMwp7rjVru6BIfaOCLa1SUAcDGOAAEAANMhAAEAANMhAAEAANMhAAEAANMhAAEAANMhAAEAANMhAAEAANMhAAEAANMhAAEAANMhAAEAANMhAAEAANMhAAEAANMhAAEAANMhAAEAANMhAAEAANMhAAEAANMhAAEAANMhAAEAANMhAAEAANMhAAEAANMp4OoCAOCum/iwqytwrCH7XF0BcN/hCBAAADAdAhAAADAdAhAAADAdAhAAADAdAhAAADCdeyIATZ06VeHh4fLy8lK9evW0cePGW/ZfvHixKlWqJC8vL1WvXl0rVqywWd6jRw9ZLBabV6tWrZy5CwAA4D7i8gC0cOFCDR48WCNHjtTWrVsVERGhli1bKiUlJcf+69evV9euXfXcc89p27Ztat++vdq3b6+dO3fa9GvVqpVOnjxpfX3++ed3Y3cAAMB9wOUBaNKkSerdu7fi4uJUpUoVzZgxQz4+Pvrkk09y7P/++++rVatWeuWVV1S5cmWNGTNGtWrVUkJCgk0/T09PhYSEWF9FihS5G7sDAADuAy4NQBkZGdqyZYuio6OtbW5uboqOjtaGDRtyXGfDhg02/SWpZcuW2fqvXbtWxYsX18MPP6wXXnhBZ8+edfwOAACA+5JL7wR95swZZWZmKjg42KY9ODhYe/fuzXGd5OTkHPsnJydb37dq1UodOnRQ2bJl9euvv+q1115TTEyMNmzYIHd392xjpqenKz093fo+LS3tTnYLAADc4x7IR2F06dLF+nP16tVVo0YNlS9fXmvXrlWzZs2y9R8/frxGjx59N0sEAAAu5NJTYMWKFZO7u7tOnTpl037q1CmFhITkuE5ISIhd/SWpXLlyKlasmA4ePJjj8uHDhys1NdX6Onr0qJ17AgAA7icuDUAeHh6qXbu2kpKSrG1ZWVlKSkpSVFRUjutERUXZ9JekVatW5dpfko4dO6azZ8+qRIkSOS739PSUv7+/zQsAADy4XH4V2ODBg/XRRx9p7ty52rNnj1544QVdunRJcXFxkqTu3btr+PDh1v4DBw5UYmKi3nvvPe3du1ejRo3S5s2b1b9/f0nSxYsX9corr+jHH3/U4cOHlZSUpHbt2qlChQpq2bKlS/YRAADcW1w+B6hz5846ffq04uPjlZycrMjISCUmJlonOh85ckRubv/LafXr19f8+fP1+uuv67XXXlPFihW1dOlSVatWTZLk7u6uHTt2aO7cubpw4YJCQ0PVokULjRkzRp6eni7ZRwAAcG+xGIZhuLqIe01aWpoCAgKUmprqlNNhdcetdviYrrTRs5+rS3CsIftcXcE9h+/sPY7vLCDJvr/fLj8FBgAAcLcRgAAAgOkQgAAAgOkQgAAAgOkQgAAAgOkQgAAAgOkQgAAAgOkQgAAAgOkQgAAAgOkQgAAAgOm4/FlgAAA42gP3+JYR0a4u4YHDESAAAGA6BCAAAGA6BCAAAGA6BCAAAGA6BCAAAGA6BCAAAGA6BCAAAGA6BCAAAGA6BCAAAGA63AkaAIB73cSHXV2BYw3Z5+oKOAIEAADMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABMhwAEAABM554IQFOnTlV4eLi8vLxUr149bdy48Zb9Fy9erEqVKsnLy0vVq1fXihUrbJYbhqH4+HiVKFFC3t7eio6O1oEDB5y5CwAA4D7i8gC0cOFCDR48WCNHjtTWrVsVERGhli1bKiUlJcf+69evV9euXfXcc89p27Ztat++vdq3b6+dO3da+0yYMEFTpkzRjBkz9NNPP8nX11ctW7bU1atX79ZuAQCAe5jLA9CkSZPUu3dvxcXFqUqVKpoxY4Z8fHz0ySef5Nj//fffV6tWrfTKK6+ocuXKGjNmjGrVqqWEhARJfx79mTx5sl5//XW1a9dONWrU0KeffqoTJ05o6dKld3HPAADAvcqlASgjI0NbtmxRdHS0tc3NzU3R0dHasGFDjuts2LDBpr8ktWzZ0tr/0KFDSk5OtukTEBCgevXq5TomAAAwlwKu3PiZM2eUmZmp4OBgm/bg4GDt3bs3x3WSk5Nz7J+cnGxdfqMttz5/lZ6ervT0dOv71NRUSVJaWpode5N3mVcvOWVcV0kzMl1dgmM56fd+P+M7e4/jO5sN39l7nJO+szf+bhuGcdu+Lg1A94rx48dr9OjR2drDwsJcUM39J8DVBTjaGw/cHuEvHrjfMN/ZB94D9xt28nf2jz/+UEDArbfh0gBUrFgxubu769SpUzbtp06dUkhISI7rhISE3LL/jf89deqUSpQoYdMnMjIyxzGHDx+uwYMHW99nZWXp3LlzCgwMlMVisXu/zCQtLU1hYWE6evSo/P39XV0OcFt8Z3G/4Tubd4Zh6I8//lBoaOht+7o0AHl4eKh27dpKSkpS+/btJf0ZPpKSktS/f/8c14mKilJSUpIGDRpkbVu1apWioqIkSWXLllVISIiSkpKsgSctLU0//fSTXnjhhRzH9PT0lKenp01b4cKF72jfzMbf35//MHFf4TuL+w3f2by53ZGfG1x+Cmzw4MGKjY1VnTp1VLduXU2ePFmXLl1SXFycJKl79+4qWbKkxo8fL0kaOHCgGjVqpPfee0+tW7fWggULtHnzZs2cOVOSZLFYNGjQII0dO1YVK1ZU2bJl9cYbbyg0NNQasgAAgLm5PAB17txZp0+fVnx8vJKTkxUZGanExETrJOYjR47Ize1/F6vVr19f8+fP1+uvv67XXntNFStW1NKlS1WtWjVrn1dffVWXLl1Snz59dOHCBTVo0ECJiYny8vK66/sHAADuPRYjL1OlgVykp6dr/PjxGj58eLbTiMC9iO8s7jd8Z52DAAQAAEzH5XeCBgAAuNsIQAAAwHQIQAAAwHQIQAAAwHQIQMiX//73v2rTpo1CQ0NlsVi0dOlSV5cE5Nnbb79tvWcYcK/KzMzUG2+8obJly8rb21vly5fXmDFj8vScK9yey+8DhPvTpUuXFBERoZ49e6pDhw6uLgfIs02bNunDDz9UjRo1XF0KcEvvvPOOpk+frrlz56pq1aravHmz4uLiFBAQoBdffNHV5d33CEDIl5iYGMXExLi6DMAuFy9eVLdu3fTRRx9p7Nixri4HuKX169erXbt2at26tSQpPDxcn3/+uTZu3Ojiyh4MnAIDYBr9+vVT69atFR0d7epSgNuqX7++kpKStH//fknSzz//rB9++IF/fDoIR4AAmMKCBQu0detWbdq0ydWlAHkybNgwpaWlqVKlSnJ3d1dmZqbGjRunbt26ubq0BwIBCMAD7+jRoxo4cKBWrVrFMwFx31i0aJE+++wzzZ8/X1WrVtX27ds1aNAghYaGKjY21tXl3fd4FAbumMVi0VdffaX27du7uhQgR0uXLtWTTz4pd3d3a1tmZqYsFovc3NyUnp5uswy4F4SFhWnYsGHq16+ftW3s2LH65z//qb1797qwsgcDR4AAPPCaNWumX375xaYtLi5OlSpV0tChQwk/uCddvnxZbm62U3Xd3d2VlZXloooeLAQg5MvFixd18OBB6/tDhw5p+/btKlq0qEqXLu3CyoDsChUqpGrVqtm0+fr6KjAwMFs7cK9o06aNxo0bp9KlS6tq1aratm2bJk2apJ49e7q6tAcCp8CQL2vXrlWTJk2ytcfGxmrOnDl3vyDATo0bN1ZkZKQmT57s6lKAHP3xxx9644039NVXXyklJUWhoaHq2rWr4uPj5eHh4ery7nsEIAAAYDrcBwgAAJgOAQgAAJgOAQgAAJgOAQgAAJgOAQgAAJgOAQgAAJgOAQgAAJgOAQgAbmHUqFGKjIx0dRlWhw8flsVi0fbt211dCnBfIwAByNHRo0fVs2dPhYaGysPDQ2XKlNHAgQN19uxZl9TTo0cPWSwWPf/889mW9evXTxaLRT169MjW32KxyMPDQxUqVNCbb76p69ev57oNi8WipUuXOqF6APcaAhCAbH777TfVqVNHBw4c0Oeff66DBw9qxowZSkpKUlRUlM6dO+eSusLCwrRgwQJduXLF2nb16lXNnz8/x2fQtWrVSidPntSBAwf08ssva9SoUXr33XedXmdGRobTtwHgzhCAAGTTr18/eXh46Ntvv1WjRo1UunRpxcTEaPXq1Tp+/LhGjBhh7RseHq4xY8aoa9eu8vX1VcmSJTV16lSb8S5cuKBevXopKChI/v7+atq0qX7++Wfr8hunmebNm6fw8HAFBASoS5cu+uOPP2zGqVWrlsLCwvTll19a27788kuVLl1aNWvWzLYfnp6eCgkJUZkyZfTCCy8oOjpay5Yty3Gfw8PDJUlPPvmkLBaL9f0Nt6qtcePG6t+/vwYNGqRixYqpZcuWkqSdO3cqJiZGfn5+Cg4O1rPPPqszZ85Y10tMTFSDBg1UuHBhBQYG6oknntCvv/5qs92NGzeqZs2a8vLyUp06dbRt2zab5efPn1e3bt0UFBQkb29vVaxYUbNnz85xHwH8DwEIgI1z585p5cqV6tu3r7y9vW2WhYSEqFu3blq4cKFufozgu+++q4iICG3btk3Dhg3TwIEDtWrVKuvyTp06KSUlRf/+97+1ZcsW1apVS82aNbM5kvTrr79q6dKlWr58uZYvX67vvvtOb7/9drb6evbsafMH/pNPPlFcXFye9s3b2zvXozObNm2SJM2ePVsnT560vs9rbXPnzpWHh4fWrVunGTNm6MKFC2ratKlq1qypzZs3KzExUadOndLTTz9tXefSpUsaPHiwNm/erKSkJLm5uenJJ59UVlaWJOnixYt64oknVKVKFW3ZskWjRo3SkCFDbLb7xhtvaPfu3fr3v/+tPXv2aPr06SpWrFiePg/A1AwAuMmPP/5oSDK++uqrHJdPmjTJkGScOnXKMAzDKFOmjNGqVSubPp07dzZiYmIMwzCM77//3vD39zeuXr1q06d8+fLGhx9+aBiGYYwcOdLw8fEx0tLSrMtfeeUVo169etb3sbGxRrt27YyUlBTD09PTOHz4sHH48GHDy8vLOH36tNGuXTsjNjY2W3/DMIysrCxj1apVhqenpzFkyJBc9z2n/c5LbY0aNTJq1qxps96YMWOMFi1a2LQdPXrUkGTs27cvx+2fPn3akGT88ssvhmEYxocffmgEBgYaV65csfaZPn26IcnYtm2bYRiG0aZNGyMuLi7XfQKQswKuDF8A7l3GTUd4bicqKirb+8mTJ0uSfv75Z128eFGBgYE2fa5cuWJzuic8PFyFChWyvi9RooRSUlKybSsoKEitW7fWnDlzZBiGWrdunesRj+XLl8vPz0/Xrl1TVlaWnnnmGY0aNSrP+2VPbbVr17Z5//PPP2vNmjXy8/PLNt6vv/6qhx56SAcOHFB8fLx++uknnTlzxnrk58iRI6pWrZr27NmjGjVqyMvLy7ruXz/rF154QU899ZS2bt2qFi1aqH379qpfv77d+wiYDQEIgI0KFSrIYrFoz549evLJJ7Mt37Nnj4oUKaKgoKA8jXfx4kWVKFFCa9euzbascOHC1p8LFixos8xisVgDwV/17NlT/fv3l6Rs841u1qRJE02fPl0eHh4KDQ1VgQL5+7+8vNTm6+tr8/7ixYtq06aN3nnnnWzjlShRQpLUpk0blSlTRh999JFCQ0OVlZWlatWq2TWJOiYmRr///rtWrFihVatWqVmzZurXr58mTpyY5zEAMyIAAbARGBio5s2ba9q0aXrppZds5gElJyfrs88+U/fu3WWxWKztP/74o80YP/74oypXrizpz4nLycnJKlCgQLaJxfnVqlUrZWRkyGKxWCcc58TX11cVKlTI87gFCxZUZmamI0pUrVq19MUXXyg8PDzH4HX27Fnt27dPH330kRo2bChJ+uGHH2z6VK5cWfPmzdPVq1etR4H++llLfx4Vi42NVWxsrBo2bKhXXnmFAATcBpOgAWSTkJCg9PR0tWzZUv/973919OhRJSYmqnnz5ipZsqTGjRtn03/dunWaMGGC9u/fr6lTp2rx4sUaOHCgJCk6OlpRUVFq3769vv32Wx0+fFjr16/XiBEjtHnz5nzV5+7urj179mj37t1yd3e/4/29ITw8XElJSUpOTtb58+fvaKx+/frp3Llz6tq1qzZt2qRff/1VK1euVFxcnDIzM1WkSBEFBgZq5syZOnjwoP7zn/9o8ODBNmM888wzslgs6t27t3bv3q0VK1ZkCzbx8fH6+uuvdfDgQe3atUvLly+3hk8AuSMAAcimYsWK2rx5s8qVK6enn35a5cuXV58+fdSkSRNt2LBBRYsWten/8ssva/PmzapZs6bGjh2rSZMmWY/MWCwWrVixQo899pji4uL00EMPqUuXLvr9998VHByc7xr9/f3l7+9/R/v5V++9955WrVqlsLCwHC+rt0doaKjWrVunzMxMtWjRQtWrV9egQYNUuHBhubm5yc3NTQsWLNCWLVtUrVo1vfTSS9nuUeTn56dvvvlGv/zyi2rWrKkRI0ZkO6Xm4eGh4cOHq0aNGnrsscfk7u6uBQsW3FHtgBlYDHtmOgLAX4SHh2vQoEEaNGiQq0sBgDzjCBAAADAdAhAAADAdToEBAADT4QgQAAAwHQIQAAAwHQIQAAAwHQIQAAAwHQIQAAAwHQIQAAAwHQIQAAAwHQIQAAAwHQIQAAAwnf8PgrXsqBZ9BwQAAAAASUVORK5CYII=",
+ "text/plain": [
+ "