diff --git a/CMakeLists.txt b/CMakeLists.txt index 2404159d..12b21ec7 100755 --- a/CMakeLists.txt +++ b/CMakeLists.txt @@ -116,6 +116,8 @@ if (SEMBA_FDTD_MAIN_LIB) "src_main_pub/timestepping.F90" "src_main_pub/observation.F90" "src_main_pub/vtk.F90" + "src_main_pub/xdmf.F90" + "src_main_pub/xdmf_h5.F90" "src_wires_pub/wires.F90" "src_wires_pub/wires_mtln.F90" ) @@ -140,13 +142,6 @@ add_definitions( -DCompileWithInt2 -DCompileWithReal4 -DCompileWithOpenMP --DCompileWithAnisotropic --DCompileWithEDispersives --DCompileWithNF2FF --DCompileWithNodalSources --DCompileWithDMMA --DCompileWithSGBC --DCompileWithWires ) diff --git a/doc/smbjson.md b/doc/smbjson.md index 07847c68..54f8e103 100644 --- a/doc/smbjson.md +++ b/doc/smbjson.md @@ -634,7 +634,7 @@ If not `magnitudeFile` is specified and only one `source` is defined, the `magni Probes of type `movie` record a vector field in a volume region indicated by `elementIds`. `[field]` can be `electric`, `magnetic`, or `currentDensity`; defaults to `electric`. `currentDensity` will store only the surface density currents on `pec` or lossy surfaces. -The stored values can be selected using `[components]`, which stores an array of the following labels `x`, `y`, `z`, or `magnitude`; if no components are specified, defaults to `magnitude`. +The stored values can be selected using the `[component]` entry, which stores one of the following labels `x`, `y`, `z`, or `magnitude`; if no component is specified, defaults to `magnitude`. An example follows: ```json @@ -642,7 +642,7 @@ An example follows: "name": "electric_field_movie", "type": "movie", "field": "electric", - "components": ["x"], + "component": "x", "elementIds": [4] } ``` diff --git a/src_json_parser/CMakeLists.txt b/src_json_parser/CMakeLists.txt index c0803869..2d69d2a2 100755 --- a/src_json_parser/CMakeLists.txt +++ b/src_json_parser/CMakeLists.txt @@ -13,7 +13,7 @@ add_library (jsonfortran ) add_library(smbjson - "labels_mod.F90" + "smbjson_labels.F90" "cells.F90" "smbjson.F90" "idchildtable.F90" diff --git a/src_json_parser/idchildtable.F90 b/src_json_parser/idchildtable.F90 index 0ddf43f1..3372e88f 100644 --- a/src_json_parser/idchildtable.F90 +++ b/src_json_parser/idchildtable.F90 @@ -2,8 +2,8 @@ module idchildtable_mod #ifdef CompileWithSMBJSON use json_module + use smbjson_labels_mod, only: J_ID use fhash, only: fhash_tbl_t, key=>fhash_key - use labels_mod use parser_tools_mod, only: json_value_ptr type :: IdChildTable_t @@ -29,10 +29,13 @@ function ctor(core, root, path) result(res) integer :: id integer :: i logical :: found + integer :: numberOfEntries call core%get(root, path, jentries, found) if (.not. found) return - do i = 1, core%count(jentries) + numberOfEntries = core%count(jentries) + call res%idToChilds%allocate(10*numberOfEntries) + do i = 1, numberOfEntries call core%get_child(jentries, i, jentry) call core%get(jentry, J_ID, id) call res%idToChilds%set(key(id), json_value_ptr(jentry)) diff --git a/src_json_parser/mesh.F90 b/src_json_parser/mesh.F90 index 2374f53c..ca22073a 100644 --- a/src_json_parser/mesh.F90 +++ b/src_json_parser/mesh.F90 @@ -40,10 +40,10 @@ module mesh_mod procedure :: checkId => mesh_checkId procedure :: addElement => mesh_addElement + procedure :: addCellRegion => mesh_addCellRegion + procedure :: getNode => mesh_getNode procedure :: getPolyline => mesh_getPolyline - - procedure :: addCellRegion => mesh_addCellRegion procedure :: getCellRegion => mesh_getCellRegion procedure :: getCellRegions => mesh_getCellRegions @@ -54,6 +54,7 @@ module mesh_mod procedure :: printCoordHashInfo => mesh_printCoordHashInfo procedure :: allocateCoordinates => mesh_allocateCoordinates + procedure :: allocateElements => mesh_allocateElements end type @@ -65,6 +66,13 @@ subroutine mesh_allocateCoordinates(this, buck) integer :: buck call this%coordinates%allocate(buck) end subroutine + + subroutine mesh_allocateElements(this, buck) + class(mesh_t) :: this + integer :: buck + call this%elements%allocate(buck) + end subroutine + subroutine mesh_printCoordHashInfo(this) class(mesh_t) :: this @@ -193,12 +201,26 @@ function mesh_getCellRegions(this, ids) result (res) integer, dimension(:), intent(in) :: ids type(cell_region_t) :: cR logical :: found - integer :: i + integer :: i, j + integer :: numberOfCellRegions - allocate(res(0)) + ! Precounts + numberOfCellRegions = 0 do i = 1, size(ids) cR = this%getCellRegion(ids(i), found) - if (found) res = [res, cR] + if (found) then + numberOfCellRegions = numberOfCellRegions + 1 + end if + end do + + allocate(res(numberOfCellRegions)) + j = 1 + do i = 1, size(ids) + cR = this%getCellRegion(ids(i), found) + if (found) then + res(j) = cR + j = j + 1 + end if end do end function diff --git a/src_json_parser/parser_tools.F90 b/src_json_parser/parser_tools.F90 index 7427db78..07709aa6 100644 --- a/src_json_parser/parser_tools.F90 +++ b/src_json_parser/parser_tools.F90 @@ -1,7 +1,6 @@ module parser_tools_mod #ifdef CompileWithSMBJSON - use labels_mod use mesh_mod use cells_mod use json_module diff --git a/src_json_parser/smbjson.F90 b/src_json_parser/smbjson.F90 index 3fac4244..a9020438 100644 --- a/src_json_parser/smbjson.F90 +++ b/src_json_parser/smbjson.F90 @@ -4,7 +4,7 @@ module smbjson use NFDETypes use NFDETypes_extension - use labels_mod + use smbjson_labels_mod use mesh_mod use parser_tools_mod use idchildtable_mod @@ -30,7 +30,6 @@ module smbjson contains procedure :: readProblemDescription - procedure :: initializeJson ! private procedure :: readGeneral @@ -93,112 +92,96 @@ function parser_ctor(filename) result(res) type(parser_t) :: res character(len=*), intent(in) :: filename res%filename = filename - end function - - subroutine initializeJson(this) - class(parser_t) :: this - integer :: stat - - allocate(this%jsonfile) - call this%jsonfile%initialize() - if (this%jsonfile%failed()) then - call this%jsonfile%print_error_message(error_unit) + + allocate(res%jsonfile) + call res%jsonfile%initialize() + if (res%jsonfile%failed()) then + call res%jsonfile%print_error_message(error_unit) return end if - call this%jsonfile%load(filename = this%filename) - if (this%jsonfile%failed()) then - call this%jsonfile%print_error_message(error_unit) + call res%jsonfile%load(filename = res%filename) + if (res%jsonfile%failed()) then + call res%jsonfile%print_error_message(error_unit) return end if - allocate(this%core) - call this%jsonfile%get_core(this%core) - call this%jsonfile%get('.', this%root) - end subroutine + allocate(res%core) + call res%jsonfile%get_core(res%core) + call res%jsonfile%get('.', res%root) + end function function readProblemDescription(this) result (res) class(parser_t) :: this type(Parseador) :: res integer :: stat - allocate(this%jsonfile) - call this%jsonfile%initialize() - if (this%jsonfile%failed()) then - call this%jsonfile%print_error_message(error_unit) - return - end if - - call this%jsonfile%load(filename = this%filename) - if (this%jsonfile%failed()) then - call this%jsonfile%print_error_message(error_unit) - return - end if - - allocate(this%core) - call this%jsonfile%get_core(this%core) - call this%jsonfile%get('.', this%root) - this%mesh = this%readMesh() this%matTable = IdChildTable_t(this%core, this%root, J_MATERIALS) - + call initializeProblemDescription(res) - + ! Basics res%general = this%readGeneral() res%matriz = this%readMediaMatrix() res%despl = this%readGrid() res%front = this%readBoundary() - + ! Materials res%pecRegs = this%readPECRegions() res%pmcRegs = this%readPMCRegions() - + ! Sources res%plnSrc = this%readPlanewaves() res%nodSrc = this%readNodalSources() - + ! Probes res%oldSonda = this%readProbes() res%sonda = this%readMoreProbes() res%BloquePrb = this%readBlockProbes() res%VolPrb = this%readVolumicProbes() - + ! Thin elements res%tWires = this%readThinWires() res%mtln = this%readMTLN(res%despl) - ! Cleanup - call this%core%destroy() - call this%jsonfile%destroy() - nullify(this%root) + !! Cleanup + !call this%core%destroy() + !call this%jsonfile%destroy() + !nullify(this%root) end function function readMesh(this) result(res) class(parser_t) :: this type(Mesh_t) :: res - type(json_value), pointer :: jcs, jc - integer :: id, i - real, dimension(:), allocatable :: pos - type(coordinate_t) :: c - integer :: stat - logical :: found - - call this%core%get(this%root, J_MESH//'.'//J_COORDINATES, jcs, found=found) - if (found) then - call res%allocateCoordinates(10*this%core%count(jcs)) - do i = 1, this%core%count(jcs) - call this%core%get_child(jcs, i, jc) - call this%core%get(jc, J_ID, id) - call this%core%get(jc, J_COORDINATE_POS, pos) - c%position = pos - call res%addCoordinate(id, c) - end do - end if + call addCoordinates(res) call addElements(res) contains + subroutine addCoordinates(mesh) + type(mesh_t), intent(inout) :: mesh + type(json_value), pointer :: jcs, jc + integer :: id, i + real, dimension(:), allocatable :: pos + type(coordinate_t) :: c + integer :: numberOfCoordinates + logical :: found + + call this%core%get(this%root, J_MESH//'.'//J_COORDINATES, jcs, found=found) + if (found) then + numberOfCoordinates = this%core%count(jcs) + call res%allocateCoordinates(10*numberOfCoordinates) + do i = 1, numberOfCoordinates + call this%core%get_child(jcs, i, jc) + call this%core%get(jc, J_ID, id) + call this%core%get(jc, J_COORDINATE_POS, pos) + c%position = pos + call mesh%addCoordinate(id, c) + end do + end if + end subroutine + subroutine addElements(mesh) type(mesh_t), intent(inout) :: mesh character (len=:), allocatable :: elementType @@ -207,10 +190,15 @@ subroutine addElements(mesh) type(node_t) :: node type(polyline_t) :: polyline integer, dimension(:), allocatable :: coordIds + integer :: numberOfElements logical :: found + call this%core%get(this%root, J_MESH//'.'//J_ELEMENTS, jes, found=found) + numberOfElements = this%core%count(jes) + call res%allocateElements(10*numberOfElements) + if (found) then - do i = 1, this%core%count(jes) + do i = 1, numberOfElements call this%core%get_child(jes, i, je) call this%core%get(je, J_ID, id) call this%core%get(je, J_TYPE, elementType) @@ -985,19 +973,13 @@ function readVolProbe(p) result(res) cs = cellIntervalsToCoords(cRs(1)%intervals) fieldType = this%getStrAt(p, J_FIELD, default=J_FIELD_ELECTRIC) - call this%core%get(p, J_PR_MOVIE_COMPONENTS, compsPtr, found=componentsFound) + call this%core%get(p, J_PR_MOVIE_COMPONENT, compsPtr, found=componentsFound) + allocate(res%cordinates(1)) if (componentsFound) then - numberOfComponents = this%core%count(compsPtr) - allocate(res%cordinates(numberOfComponents)) - do i = 1, numberOfComponents - call this%core%get_child(compsPtr, i, compPtr) - call this%core%get(compPtr, component) - res%cordinates(i) = cs(1) - res%cordinates(i)%Or = buildVolProbeType(fieldType, component) - end do - else - allocate(res%cordinates(1)) + call this%core%get(compsPtr, component) res%cordinates(1) = cs(1) + res%cordinates(1)%Or = buildVolProbeType(fieldType, component) + else component = J_DIR_M res%cordinates(1)%Or = buildVolProbeType(fieldType, component) endif diff --git a/src_json_parser/labels_mod.F90 b/src_json_parser/smbjson_labels.F90 similarity index 98% rename from src_json_parser/labels_mod.F90 rename to src_json_parser/smbjson_labels.F90 index 34f92975..c56001ac 100644 --- a/src_json_parser/labels_mod.F90 +++ b/src_json_parser/smbjson_labels.F90 @@ -1,4 +1,4 @@ -module labels_mod +module smbjson_labels_mod #ifdef CompileWithSMBJSON ! LABELS @@ -155,7 +155,7 @@ module labels_mod character (len=*), parameter :: J_PR_POINT_DIRECTIONS = "directions" - character (len=*), parameter :: J_PR_MOVIE_COMPONENTS = "components" + character (len=*), parameter :: J_PR_MOVIE_COMPONENT = "component" character (len=*), parameter :: J_PR_FAR_FIELD_THETA = "theta" character (len=*), parameter :: J_PR_FAR_FIELD_PHI = "phi" diff --git a/src_main_pub/anisotropic.F90 b/src_main_pub/anisotropic.F90 index 788e45e2..cd980a45 100755 --- a/src_main_pub/anisotropic.F90 +++ b/src_main_pub/anisotropic.F90 @@ -32,9 +32,6 @@ !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! module Anisotropic - -#ifdef CompileWithAnisotropic - use fdetypes implicit none private @@ -1581,6 +1578,4 @@ Subroutine CalculateCoeff(epr,mur,sigma,sigmam,dt,coeff) end subroutine -#endif - end module Anisotropic diff --git a/src_main_pub/dmma_thin_slot.F90 b/src_main_pub/dmma_thin_slot.F90 index e16ab35c..7e32b73c 100755 --- a/src_main_pub/dmma_thin_slot.F90 +++ b/src_main_pub/dmma_thin_slot.F90 @@ -23,10 +23,6 @@ !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! MODULE DMMA - - -#ifdef CompileWithDMMA - USE FDETYPES IMPLICIT NONE PRIVATE @@ -162,6 +158,4 @@ END SUBROUTINE dmma_thin_Slot ! ! -#endif - END MODULE diff --git a/src_main_pub/electricdispersive.F90 b/src_main_pub/electricdispersive.F90 index 9ce7885b..5b6a907d 100755 --- a/src_main_pub/electricdispersive.F90 +++ b/src_main_pub/electricdispersive.F90 @@ -33,7 +33,6 @@ module EDispersives -#ifdef CompileWithEDispersives use fdetypes USE REPORT @@ -442,6 +441,4 @@ subroutine DestroyEDispersives(sgg) end subroutine -#endif - end module EDispersives diff --git a/src_main_pub/errorreport.F90 b/src_main_pub/errorreport.F90 index ab0f7d86..1f053128 100755 --- a/src_main_pub/errorreport.F90 +++ b/src_main_pub/errorreport.F90 @@ -25,9 +25,7 @@ Module Report use FDETYPES -#ifdef CompileWithXDMF use snapxdmf -#endif implicit none private @@ -299,32 +297,7 @@ subroutine ReportExistence(sgg,layoutnumber,size,thereare,mur_second,MurAfterPML call print11(layoutnumber,SEPARADOR//sEPARADOR//SEPARADOR) !!! - if ((thereare%NodalE).or.(thereare%NodalH)) then -#ifdef CompileWithNodalSources - continue -#else - buff=trim(adjustl(whoami))//' Nodal sources unsupported. Recompile' - call stoponerror(layoutnumber,size,buff) -#endif - endif ! - IF (thereare%FarFields) then -#ifdef CompileWithNF2FF - continue -#else - buff=trim(adjustl(whoami))//' NF2FF unsupported. Recompile' - call stoponerror(layoutnumber,size,buff) -#endif - endif - ! - IF (thereare%SGBCs) then -#ifdef CompileWithSGBC - continue -#else - buff=trim(adjustl(whoami))//' SGBC unsupported. Recompile' - call stoponerror(layoutnumber,size,buff) -#endif - endif IF ((thereare%Multiports).or.(thereare%AnisMultiports)) then #ifdef CompileWithNIBC continue @@ -333,52 +306,6 @@ subroutine ReportExistence(sgg,layoutnumber,size,thereare,mur_second,MurAfterPML call stoponerror(layoutnumber,size,buff) #endif endif - ! - ! - IF (thereare%Anisotropic) then -#ifdef CompileWithAnisotropic - continue -#else - buff=trim(adjustl(whoami))//' Anisotropic unsupported. Recompile' - call stoponerror(layoutnumber,size,buff) -#endif - endif - ! - IF (thereare%ThinSlot) then -#ifdef CompileWithDMMA - continue -#else - buff=trim(adjustl(whoami))//' Thin slots unsupported. Recompile' - call stoponerror(layoutnumber,size,buff) -#endif - endif - ! - IF (thereare%EDispersives.or.thereare%MDispersives) then -#ifdef CompileWithEDispersives - continue -#else - buff=trim(adjustl(whoami))//' Dispersive materials unsupported. Recompile' - call stoponerror(layoutnumber,size,buff) -#endif - endif - ! - If (thereare%Wires) then -#ifdef CompileWithWires - continue -#else -#ifdef CompileWithBerengerWires - continue -#else -#ifdef CompileWithSlantedWires - continue -#else - buff=trim(adjustl(whoami))//' WIREs unsupported. Recompile' - call stoponerror(layoutnumber,size,buff) -#endif -#endif -#endif - endif - ! !!!!!!!!!!!!! if (thereAre%MagneticMedia) then buff=' has special H-media' @@ -416,20 +343,15 @@ subroutine ReportExistence(sgg,layoutnumber,size,thereare,mur_second,MurAfterPML buff= ' has Thin metal Materials' call warnerrreport(buff) endif -#ifdef CompileWithAnisotropic IF ((thereare%Anisotropic).and.(.not.thereare%ThinSlot)) then buff= ' has pure anisotropic media' call warnerrreport(buff) endif -#ifdef CompileWithDMMA IF (thereare%ThinSlot) then buff= ' has Thin Slots' call warnerrreport(buff) endif -#endif -#endif ! -#ifdef CompileWithEDispersives IF (thereare%EDispersives) then buff= ' has electric dispersives' call warnerrreport(buff) @@ -438,13 +360,10 @@ subroutine ReportExistence(sgg,layoutnumber,size,thereare,mur_second,MurAfterPML buff= ' has magnetic dispersives' call warnerrreport(buff) endif -#endif -#ifdef CompileWithWires If (thereare%Wires) then buff= ' has Holland WIREs' call warnerrreport(buff) endif -#endif #ifdef CompileWithBerengerWires If (thereare%Wires) then buff= ' has Multi-WIREs' @@ -1168,7 +1087,6 @@ subroutine Timing(sgg, b, n, n_info, layoutnumber, size, maxCPUtime,flushseconds call MPI_Barrier(MPI_COMM_WORLD,ierr) #endif -#ifdef CompileWithXDMF if ((mustsnap.and.(lmaxval (layoutnumber+1)> snapLevel)).or.(countersnap > 0)) then countersnap=countersnap + 1 ! @@ -1272,7 +1190,6 @@ subroutine Timing(sgg, b, n, n_info, layoutnumber, size, maxCPUtime,flushseconds countersnap=0 endif endif -#endif #ifdef CompileWithMPI call MPI_Barrier(MPI_COMM_WORLD,ierr) !TODOS STOCH O NO 060619 diff --git a/src_main_pub/farfield.F90 b/src_main_pub/farfield.F90 index ad041658..9c4c9422 100755 --- a/src_main_pub/farfield.F90 +++ b/src_main_pub/farfield.F90 @@ -29,9 +29,6 @@ !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! module farfield_m - -#ifdef CompileWithNF2FF - use fdetypes USE REPORT @@ -3576,5 +3573,4 @@ function average (pasadas,z1,z2) result (z) RETURN END FUNCTION -#endif END MODULE farfield_m diff --git a/src_main_pub/interpreta_switches.F90 b/src_main_pub/interpreta_switches.F90 index 8c567eb2..b3a5a542 100755 --- a/src_main_pub/interpreta_switches.F90 +++ b/src_main_pub/interpreta_switches.F90 @@ -5,9 +5,7 @@ module interpreta_switches_m use EpsMuTimeScale_m use Report use version -! #ifdef CompilePrivateVersion -! use ParseadorClass -! #endif + IMPLICIT NONE PRIVATE ! @@ -456,13 +454,12 @@ subroutine interpreta(l,statuse) END IF l%opcionespararesumeo = trim (adjustl(l%opcionespararesumeo)) // ' ' // trim (adjustl(l%chain)) // ' ' // trim (adjustl(f)) ! -#ifdef CompileWithDMMA CASE ('-dmma') l%run_with_dmma = .TRUE. l%run_with_abrezanjas = .FALSE. l%opcionespararesumeo = trim (adjustl(l%opcionespararesumeo)) // ' ' // trim (adjustl(l%chain)) !! i = i + 1; -#endif + #ifdef CompileWithConformal CASE ('-abrezanjas') !Provisional FEB-2018 @@ -697,7 +694,6 @@ subroutine interpreta(l,statuse) l%opcionespararesumeo = trim (adjustl(l%opcionespararesumeo)) // ' ' // trim (adjustl(l%chain)) CASE ('-saveall') l%saveall = .TRUE. -#ifdef CompileWithWires CASE ('-attw') i = i + 1 CALL getcommandargument (l%chaininput, i, f, l%length, statuse) @@ -840,14 +836,12 @@ subroutine interpreta(l,statuse) endif end select #endif -#ifdef CompileWithWires select case (trim(adjustl(l%wiresflavor))) case ('berenger','slanted','experimental','transition') if (l%wirethickness/=1) then CALL stoponerror (l%layoutnumber, l%size, 'Thickness>1 unsupported for this wireflavor',.true.); statuse=-1; !goto 668 endif end select -#endif #ifndef CompileWithBerengerWires select case (trim(adjustl(l%wiresflavor))) case ('berenger') @@ -887,7 +881,6 @@ subroutine interpreta(l,statuse) GO TO 180 179 CALL stoponerror (l%layoutnumber, l%size, 'Invalid inductance order',.true.); statuse=-1; !goto 668 180 l%opcionespararesumeo = trim (adjustl(l%opcionespararesumeo)) // ' ' // trim (adjustl(l%chain)) // ' ' // trim (adjustl(f)) -#endif CASE ('-prefix') i = i + 1 CALL getcommandargument (l%chaininput, i, f, l%length, statuse) @@ -1021,12 +1014,6 @@ subroutine interpreta(l,statuse) END IF #endif -#ifdef CompileWithDMMA -#ifndef CompileWithAnisotropic - CALL stoponerror (l%layoutnumber, l%size, 'ERROR: DMMA without Anisotropic support. Recompile!') -#endif -#endif - IF (l%connectendings .AND. l%strictOLD) THEN CALL stoponerror (l%layoutnumber, l%size, 'l%strictOLD option not compatible with -l%connectendings',.true.); statuse=-1; !goto 668 END IF @@ -1541,7 +1528,6 @@ subroutine print_help(l) #endif CALL print11 (l%layoutnumber, '-prioritizeCOMPOoverPEC: Uses Composites instead of PEC in conflicts. ') CALL print11 (l%layoutnumber, '-prioritizeISOTROPICBODYoverall: Uses ISOTROPIC BODY FOR conflicts (JUST FOR SIVA). ') -#ifdef CompileWithSGBC CALL print11 (l%layoutnumber, '-sgbc : Enables the defaults sgbc model for composites. Default sgbc:') CALL print11 (l%layoutnumber, '-nosgbc : Disables the defaults sgbc model for composites. Default sgbc:') CALL print11 (l%layoutnumber, '& -sgbfreq 3e9 -sgbresol 1 -sgbcrank ') @@ -1551,7 +1537,7 @@ subroutine print_help(l) CALL print11 (l%layoutnumber, '-sgbccrank : Uses sgbc Crank-Nicolson (default) ') CALL print11 (l%layoutnumber, '-sgbcdepth number : Overrides automatic calculation of number of cells ') CALL print11 (l%layoutnumber, '& within sgbc ') -#endif + CALL print11 (l%layoutnumber, '-pmlalpha factor order : CPML Alpha factor (>=0, <1 sug.) & polyn. grading.') CALL print11 (l%layoutnumber, '& alpha=factor * maximum_PML_sigma , order=polynom. ') write(buff,'(a,2e10.2e3)') '& Default= ',l%alphamaxpar,l%alphaOrden @@ -1562,16 +1548,13 @@ subroutine print_help(l) CALL print11 (l%layoutnumber, '& sigma=factor * maximum_PML_sigma, depth= # layers ') CALL print11 (l%layoutnumber, '-mur1 : Supplement PMLs with 1st order Mur ABCs ') CALL print11 (l%layoutnumber, '-mur2 : Supplement PMLs with 2nd order Mur ABCs ') -#ifdef CompileWithWires CALL print11 (l%layoutnumber, '-wiresflavor {holland.or.old} : model for the wires ') -#endif #ifdef CompileWithBerengerWires CALL print11 (l%layoutnumber, '-wiresflavor {berenger} : model for the wires ') #endif #ifdef CompileWithSlantedWires CALL print11 (l%layoutnumber, '-wiresflavor {new/Slanted.or.experimental.or.slanted/transition/semistructured l%precision} : model for the wires ') #endif -#ifdef CompileWithWires CALL print11 (l%layoutnumber, '& (default '//trim(adjustl(l%wiresflavor))//') ') CALL print11 (l%layoutnumber, '-mtlnwires : Use mtln solver to advance wires currents ') CALL print11 (l%layoutnumber, '-notaparrabos : Do not remove extra double tails at the end of the wires ') @@ -1609,13 +1592,10 @@ subroutine print_help(l) CALL print11 (l%layoutnumber, '-maxwireradius number : Bounds globally the wire radius ') CALL print11 (l%layoutnumber, '-clip : Permits to clip a bigger problem truncating wires.') CALL print11 (l%layoutnumber, '-wirecrank : Uses Crank-Nicolson for wires (development) ') -#endif -#ifdef CompileWithNF2FF CALL print11 (l%layoutnumber, '-noNF2FF string : Supress a NF2FF plane for calculation ') CALL print11 (l%layoutnumber, '& String can be: up, down, left, right, back , front') CALL print11 (l%layoutnumber, '-NF2FFDecim : Uses decimation in NF2FF calculation (faster). ') CALL print11 (l%layoutnumber, '& WARNING: High-freq aliasing may occur ') -#endif CALL print11 (l%layoutnumber, '-vtkindex : Output index instead of real point in 3D slices. ') CALL print11 (l%layoutnumber, '-ignoreerrors : Run even if errors reported in *Warnings.txt file.') CALL print11 (l%layoutnumber, '___________________________________________________________________________') @@ -1633,9 +1613,7 @@ subroutine print_help(l) CALL print11 (l%layoutnumber, '-conf file : conformal file ') CALL print11 (l%layoutnumber, '-abrezanjas : Thin-gaps treated in conformal manner ') #endif -#ifdef CompileWithDMMA CALL print11 (l%layoutnumber, '-dmma : Thin-gaps treated in DMMA manner ') -#endif #ifdef CompileWithMPI CALL print11 (l%layoutnumber, '-mpidir {x,y,z} : Rotate model to force MPI along z be the largest ') CALL print11 (l%layoutnumber, '-force cutplane : Force a MPI layout to begin at cutplane (debug!) ') @@ -1697,47 +1675,18 @@ subroutine print_help(l) #else !CALL print11 (l%layoutnumber, 'UNSUPPORTED: Conformal algorithm') #endif -#ifdef CompileWithNF2FF CALL print11 (l%layoutnumber, 'SUPPORTED: Near-to-Far field probes') -#else - !CALL print11 (l%layoutnumber, 'UNSUPPORTED: Near-to-Far field probes') -#endif -#ifdef CompileWithAnisotropic CALL print11 (l%layoutnumber, 'SUPPORTED: Lossy anistropic materials, both electric and magnetic') -#else - !CALL print11 (l%layoutnumber, 'UNSUPPORTED: Lossy anistropic materials, both electric and magnetic') -#endif -#ifdef CompileWithDMMA CALL print11 (l%layoutnumber, 'SUPPORTED: Thin Slots ') -#else - !CALL print11 (l%layoutnumber, 'UNSUPPORTED: Thin Slots ') -#endif -#ifdef CompileWithEDispersives CALL print11 (l%layoutnumber, 'SUPPORTED: Electric and Magnetic Dispersive materials ') -#else - !CALL print11 (l%layoutnumber, 'UNSUPPORTED: Electric and Magnetic Dispersive materials ') -#endif -#ifdef CompileWithSGBC CALL print11 (l%layoutnumber, 'SUPPORTED: Isotropic Multilayer Skin-depth Materials (sgbc)') -#else - !CALL print11 (l%layoutnumber, 'UNSUPPORTED: Isotropic Multilayer Skin-depth Materials (sgbc)') -#endif #ifdef CompileWithNIBC CALL print11 (l%layoutnumber, 'SUPPORTED: Isotropic Multilayer Skin-depth Materials (l%mibc)') #else !CALL print11 (l%layoutnumber, 'UNSUPPORTED: Isotropic Multilayer Skin-depth Materials (l%mibc)') #endif - -#ifdef CompileWithWires CALL print11 (l%layoutnumber, 'SUPPORTED: Loaded and grounded thin-wires with juntions') -#else - !CALL print11 (l%layoutnumber, 'UNSUPPORTED: Loaded and grounded thin-wires with juntions') -#endif -#ifdef CompileWithNodalSources CALL print11 (l%layoutnumber, 'SUPPORTED: Nodal hard/soft electric and magnetic sources') -#else - !CALL print11 (l%layoutnumber, 'UNSUPPORTED: Nodal hard/soft electric and magnetic sources') -#endif #ifdef CompileWithHDF CALL print11 (l%layoutnumber, 'SUPPORTED: .xdmf+.h5 probes ') #else @@ -1758,11 +1707,7 @@ subroutine print_help(l) #else !CALL print11 (l%layoutnumber, 'UNSUPPORTED: Permittivity scaling accelerations') #endif -#ifdef CompileWithWires CALL print11 (l%layoutnumber, 'SUPPORTED: Holland Wires') -#else - !CALL print11 (l%layoutnumber, 'UNSUPPORTED: Holland Wires') -#endif #ifdef CompileWithBerengerWires CALL print11 (l%layoutnumber, 'SUPPORTED: Multi-Wires') #else @@ -2201,12 +2146,7 @@ subroutine default_flags(l) l%relaunching=.false. l%forcestop=.false. l%input_conformal_flag = .false. -!thin gaps -#ifdef CompileWithDMMA l%run_with_dmma = .true. -#else - l%run_with_dmma = .false. -#endif #ifdef CompileWithConformal l%run_with_dmma = .false. ! todo esto para el abrezanjas. se precisa tambien el l%input_conformal_flag diff --git a/src_main_pub/magneticdispersive.F90 b/src_main_pub/magneticdispersive.F90 index 21756df7..cdb3a0fd 100755 --- a/src_main_pub/magneticdispersive.F90 +++ b/src_main_pub/magneticdispersive.F90 @@ -33,7 +33,6 @@ module Mdispersives -#ifdef CompileWithEDispersives !mismo switch electrico y magnetico use fdetypes @@ -441,6 +440,4 @@ subroutine DestroyMdispersives(sgg) end subroutine -#endif - end module Mdispersives diff --git a/src_main_pub/maloney_nostoch.F90 b/src_main_pub/maloney_nostoch.F90 index fae1044d..38f50865 100755 --- a/src_main_pub/maloney_nostoch.F90 +++ b/src_main_pub/maloney_nostoch.F90 @@ -38,8 +38,6 @@ module SGBC_nostoch - -#ifdef CompileWithSGBC #ifndef CompileWithStochastic use Report @@ -1717,7 +1715,6 @@ subroutine solve_tridiag_iguales(aa,bb,cc,a1,b1,c1,an,bn,cn,d,x,n) end subroutine solve_tridiag_iguales #endif -#endif end module SGBC_nostoch diff --git a/src_main_pub/mpicomm.F90 b/src_main_pub/mpicomm.F90 index 035aab2f..f749c4fb 100755 --- a/src_main_pub/mpicomm.F90 +++ b/src_main_pub/mpicomm.F90 @@ -32,17 +32,13 @@ module MPIcomm Use Report use fdetypes -#ifdef CompileWithWires use wiresHolland_constants use HollandWires -#endif implicit none private -#ifdef CompileWithWires type(Thinwires_t), pointer :: HwiresMPI -#endif Type buffer_t @@ -68,10 +64,8 @@ module MPIcomm public FlushMPI_E,FlushMPI_H,InitMPI,MPIupdateMin, InitGeneralMPI,MPIdivide public MPIupdateBloques, MPIinitSubcomm -#ifdef CompileWithWires !public InitWiresMPI public newInitWiresMPI,NewFlushWiresMPI -#endif public InitExtraFlushMPI @@ -649,7 +643,7 @@ subroutine FlushMPI_E(sggalloc,layoutnumber,size, Ex,Ey,Ez) ! -#ifdef CompileWithWires + !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! new routine: works without the MediaMatrix Info ! supports multiwires @@ -1219,10 +1213,6 @@ subroutine FlushWiresMPIorigindexInfo(layoutnumber,size) !!! return !!!end subroutine newFlushWiresMPIindexmedInfo -#endif - !del compilewithwires - - subroutine InitExtraFlushMPI (layoutnumber,sggsweep,sggalloc,med,nummed,sggmiez,sggMiHz) type (XYZlimit_t), dimension(1:6) :: sggalloc,sggsweep integer (kind=4) :: layoutnumber diff --git a/src_main_pub/nodalsources.F90 b/src_main_pub/nodalsources.F90 index 984c8251..ed729f9d 100755 --- a/src_main_pub/nodalsources.F90 +++ b/src_main_pub/nodalsources.F90 @@ -29,8 +29,6 @@ module nodalsources -#ifdef CompileWithNodalSources - use fdetypes USE REPORT @@ -772,7 +770,5 @@ subroutine InitHopf(sgg,NumNodalSources,sggNodalSource,sggSweep,ficherohopf) return end subroutine InitHopf -#endif - END MODULE nodalsources \ No newline at end of file diff --git a/src_main_pub/observation.F90 b/src_main_pub/observation.F90 index 8f35f23a..002ad58e 100755 --- a/src_main_pub/observation.F90 +++ b/src_main_pub/observation.F90 @@ -33,14 +33,13 @@ module Observa use MPIcomm #endif -#ifdef CompileWithWires use wiresHolland_constants use HollandWires + #ifdef CompileWithMTLN use Wire_bundles_mtln_mod use mtln_solver_mod , mtln_solver_t => mtln_t #endif -#endif #ifdef CompileWithBerengerWires use WiresBerenger #endif @@ -50,13 +49,8 @@ module Observa use WiresSlanted_Constants #endif use report - -#ifdef CompileWithNF2FF use farfield_m -#endif -#ifdef CompileWithNodalSources use nodalsources -#endif ! IMPLICIT NONE private @@ -71,9 +65,9 @@ module Observa complex( kind = CKIND), dimension( :,:), allocatable :: valorComplex_Hx,valorComplex_Hy,valorComplex_Hz end type Serialized_t type item_t -#ifdef CompileWithWires - type (CurrentSegments), pointer :: segmento !segmento de hilo que se observa si lo hubiere -#endif + + type (CurrentSegments), pointer :: segmento !segmento de hilo que se observa si lo hubiere + #ifdef CompileWithBerengerWires type (TSegment) , pointer :: segmento_Berenger !segmento de hilo que se observa si lo hubiere #endif @@ -110,11 +104,7 @@ module Observa complex( kind = CKIND), dimension( :), allocatable :: auxExp_E,auxExp_H,dftEntrada !para sondas freqdomain end type output_t - - -#ifdef CompileWithWires type(Thinwires_t), pointer :: Hwireslocal -#endif #ifdef CompileWithBerengerWires type(TWires) , pointer :: Hwireslocal_Berenger #endif @@ -430,7 +420,6 @@ subroutine InitObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,s endif #endif case (FarField) -#ifdef CompileWithNF2FF if ( (sgg%observation(ii)%P(1)%ZI > sgg%SINPMLSweep(IHz)%ZE).or. & !MPI NO DUPLICAR CALCULOS (sgg%observation(ii)%P(1)%ZE < sgg%SINPMLSweep(iHz)%ZI)) then @@ -452,9 +441,6 @@ subroutine InitObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,s endif #endif ! -#else - call stoponerror(layoutnumber,size,'Current version does not support Near to Far field. Recompile') -#endif end select end do end do @@ -486,12 +472,10 @@ subroutine InitObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,s 9138 if(my_iostat /= 0) write(*,fmt='(a)',advance='no') '.' !!if(my_iostat /= 0) print '(i5,a1,i4,2x,a)',9138,'.',layoutnumber,trim(adjustl(nEntradaRoot))//'_Outputrequests_'//trim(adjustl(whoamishort))//'.txt' open (19,file=trim(adjustl(nEntradaRoot))//'_Outputrequests_'//trim(adjustl(whoamishort))//'.txt',err=9138,iostat=my_iostat,status='new',action='write') -#ifdef CompileWithWires if ((trim(adjustl(wiresflavor))=='holland') .or. & (trim(adjustl(wiresflavor))=='transition')) then if (Therearewires) Hwireslocal => GetHwires() endif -#endif #ifdef CompileWithBerengerWires if (trim(adjustl(wiresflavor))=='berenger') then if (Therearewires) Hwireslocal_Berenger => GetHwires_Berenger() @@ -763,7 +747,7 @@ subroutine InitObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,s endif allocate (output(ii)%item(i)%valor(0 : BuffObse)) output(ii)%item(i)%valor(0 : BuffObse)=0.0_RKIND -#ifdef CompileWithWires + if ((trim(adjustl(wiresflavor))=='holland') .or. & (trim(adjustl(wiresflavor))=='transition')) then found=.false. @@ -828,7 +812,7 @@ subroutine InitObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,s CALL WarnErrReport (buff,.true.) endif endif -#endif + #ifdef CompileWithBerengerWires if (trim(adjustl(wiresflavor))=='berenger') then found=.false. @@ -1310,14 +1294,10 @@ subroutine InitObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,s if (field==mapvtk) then INIT=.TRUE.; geom=.false. ; asigna=.false.; magnetic=.false. ; electric=.true. -#ifdef CompileWithNodalSources call nodalvtk(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,sggMtag, & init,geom,asigna,electric,magnetic,conta,i,ii,output,Ntimeforvolumic) -#endif -#ifdef CompileWithWires call wirebundlesvtk(sgg,init,geom,asigna,conta,i,ii,output,Ntimeforvolumic,wiresflavor,sggMtag) -#endif endif !!! do kkk=sgg%Observation(ii)%P(i)%ZI, sgg%Observation(ii)%P(i)%ZE @@ -1375,10 +1355,9 @@ subroutine InitObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,s !!! if (field==mapvtk) then INIT=.false.; geom=.false. ; asigna=.false.; magnetic=.true. ; electric=.false. -#ifdef CompileWithNodalSources call nodalvtk(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,sggMtag, & init,geom,asigna,electric,magnetic,conta,i,ii,output,Ntimeforvolumic) -#endif + endif !!! output(ii)%item(i)%columnas=conta @@ -1623,13 +1602,9 @@ subroutine InitObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,s !!! if (field==mapvtk) then INIT=.false.; geom=.true. ; asigna=.false.; magnetic=.false. ; electric=.true. -#ifdef CompileWithNodalSources call nodalvtk(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,sggMtag,& init,geom,asigna,electric,magnetic,conta,i,ii,output,Ntimeforvolumic) -#endif -#ifdef CompileWithWires call wirebundlesvtk(sgg,init,geom,asigna,conta,i,ii,output,Ntimeforvolumic,wiresflavor,sggMtag) -#endif endif !!! do kkk=sgg%Observation(ii)%P(i)%ZI, sgg%Observation(ii)%P(i)%ZE @@ -1733,10 +1708,9 @@ subroutine InitObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,s !!! if (field==mapvtk) then INIT=.false.; geom=.true. ; asigna=.false.; magnetic=.true. ; electric=.false. -#ifdef CompileWithNodalSources call nodalvtk(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,sggMtag,& init,geom,asigna,electric,magnetic,conta,i,ii,output,Ntimeforvolumic) -#endif + endif !!! my_iostat=0 @@ -2094,8 +2068,8 @@ subroutine InitObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,s endif endif endif -#ifdef CompileWithNF2FF - case (farfield) + + case (farfield) ThereAreFarFields=.true. ! write(chari ,'(i7)') sgg%observation(ii)%P(1)%XI @@ -2161,7 +2135,6 @@ subroutine InitObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,s ,output(ii)%item(i)%MPISubComm,output(ii)%item(i)%MPIRoot & #endif ,eps0,mu0) -#endif !no es necesario hacer wipe out pq en DF se van machacando end select end do loop_ob @@ -2687,9 +2660,8 @@ subroutine UpdateObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz real (kind = RKIND) :: jx,jy,jz integer(kind=4) :: conta !para realmente dar tangenciales de campos en los medios superficiales character(len=*), INTENT(in) :: wiresflavor -#ifdef CompileWithWires + type( CurrentSegments), pointer :: segmDumm !segmento de hilo que se observa si lo hubiere -#endif ! #ifdef CompileWithBerengerWires type(TSegment) , pointer :: segmDumm_Berenger !segmento de hilo que se observa si lo hubiere @@ -2892,8 +2864,8 @@ subroutine UpdateObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz output( ii)%item( i)%valor(nTime-nInit) + & (Ey( i1_m, JJJ_m, k1_m) - Ey( i2_m+1, JJJ_m, k1_m)) * dye( JJJ_m ) enddo + case( iJx, iJy, iJz) -#ifdef CompileWithWires if ((trim(adjustl(wiresflavor))=='holland') .or. & (trim(adjustl(wiresflavor))=='transition')) then output( ii)%item( i)%valor(nTime-nInit) = 0.0_RKIND !wipe value @@ -2924,7 +2896,7 @@ subroutine UpdateObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz endif !!!!!!!!!!!!!!!!!! endif -#endif + #ifdef CompileWithBerengerWires if (trim(adjustl(wiresflavor))=='berenger') then SegmDumm_Berenger => output( ii)%item( i)%Segmento_Berenger @@ -3466,13 +3438,10 @@ subroutine UpdateObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz !!! if (field==mapvtk) then INIT=.false.; geom=.false. ; asigna=.true.; magnetic=.false. ; electric=.true. -#ifdef CompileWithNodalSources call nodalvtk(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,sggMtag,& init,geom,asigna,electric,magnetic,conta,i,ii,output,Ntimeforvolumic) -#endif -#ifdef CompileWithWires + call wirebundlesvtk(sgg,init,geom,asigna,conta,i,ii,output,Ntimeforvolumic,wiresflavor,sggMtag) -#endif endif !!! do KKK = k1, k2 @@ -3488,9 +3457,9 @@ subroutine UpdateObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz (dzh(KKK ) * Hz( III , JJJ , KKK ) + dzh(KKK +1) *Hz( III , JJJ , KKK +1) )/1.0_RKIND + & dxh(III )*( Hx( III , JJJ , KKK +1) - Hx( III , JJJ , KKK -1) )/1.0_RKIND !el Hx al promediarlo con el suyo (i,j,k) a ambos lados pierde su componente y solo quedan las adyacentes - !a pesar de ser lógico tengo dudas de esa division por 2 caso tiras guada 0824 !?!? + !a pesar de ser l�gico tengo dudas de esa division por 2 caso tiras guada 0824 !?!? !he quitado la division por 2 porque el lazo debe tragarse los lados de la celda - !otro tema sería la resta de la corriente de desplazamiento ahora que tambien calculamos campo electrico es posible 020824 + !otro tema ser�a la resta de la corriente de desplazamiento ahora que tambien calculamos campo electrico es posible 020824 Jz=(dyh(JJJ ) * Hy( III , JJJ , KKK ) + dyh(JJJ +1) *Hy( III , JJJ +1, KKK ) )/1.0_RKIND - & (dyh(JJJ ) * Hy( III -1, JJJ , KKK ) + dyh(JJJ +1) *Hy( III -1, JJJ +1, KKK ) )/1.0_RKIND + & dxh(III )*( Hx( III , JJJ -1, KKK ) - Hx( III , JJJ +1, KKK ) )/1.0_RKIND @@ -3669,17 +3638,14 @@ subroutine UpdateObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz !!! if (field==mapvtk) then INIT=.false.; geom=.false. ; asigna=.true.; magnetic=.true. ; electric=.false. -#ifdef CompileWithNodalSources call nodalvtk(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,sggMtag, & init,geom,asigna,electric,magnetic,conta,i,ii,output,Ntimeforvolumic) -#endif endif !!! !!!!!!!!!!!!esto dara problemas en los angulos y aristas donde porque ahi sacara la Bloque current en Hx!!!! 19/2/14 endif endif !!!!!!!!fin sondas corriente -#ifdef CompileWithNF2FF case( FarField) if (planewavecorr) then Excor=Ex-Exvac; Eycor=Ey-Eyvac; Ezcor=Ez-Ezvac; @@ -3688,8 +3654,6 @@ subroutine UpdateObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz else call UpdateFarField(ntime, b, Ex, Ey, Ez,Hx,Hy,Hz) endif - -#endif endselect !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!FREQMAIN !!!!!!!!!!!!!!!!!!!! @@ -4136,8 +4100,6 @@ subroutine FlushObservationFiles(sgg,nInit,FinalInstant,layoutnumber,size, dxe,d endif endif ! - -#ifdef CompileWithWires case(iJx,iJy,iJz) if (singlefilewrite) then unidad=output(ii)%item(i)%unitmaster @@ -4155,7 +4117,6 @@ subroutine FlushObservationFiles(sgg,nInit,FinalInstant,layoutnumber,size, dxe,d output(ii)%item(i)%valor4(n-nInit) , & ! Vminus output(ii)%item(i)%valor5(n-nInit) ! vplus-vminus endif -#endif end select endif endif @@ -4223,11 +4184,10 @@ subroutine FlushObservationFiles(sgg,nInit,FinalInstant,layoutnumber,size, dxe,d #ifdef CompileWithMPI endif #endif -#ifdef CompileWithNF2FF - CASe (FarField) !no emplear tiempo calculando rcs por el camino solo al final + + case (FarField) !no emplear tiempo calculando rcs por el camino solo al final at=sgg%tiempo(FinalInstant) if (flushFF) call FlushFarfield(layoutnumber,size, b, dxe, dye, dze, dxh, dyh, dzh,facesNF2FF,at) -#endif case (iMHC,iHxC,iHyC,iHzC,iMEC,iExC,iEyC,iEzC,icur,iCurX,iCurY,iCurZ,mapvtk) DO N=nInit,FinalInstant at=sgg%tiempo(N) @@ -4455,10 +4415,8 @@ subroutine DestroyObservation(sgg) field=sgg%observation(ii)%P(i)%what select case(field) case (iJx,iJy,iJz) -#ifdef CompileWithWires deallocate (output(ii)%item(i)%valor) deallocate (output(ii)%item(i)%valor2,output(ii)%item(i)%valor3,output(ii)%item(i)%valor4,output(ii)%item(i)%valor5) !en caso de hilos se necesitan -#endif case (iBloqueJx,iBloqueJy,iBloqueMx,iBloqueMy) deallocate (output(ii)%item(i)%valor) #ifdef CompileWithMPI @@ -4497,14 +4455,12 @@ subroutine DestroyObservation(sgg) case (iBloqueMz,iBloqueJz,iEx,iEy,iEz,iHx,iHy,iHz) deallocate (output(ii)%item(i)%valor) -#ifdef CompileWithNF2FF case (farfield) call DestroyFarField #ifdef CompileWithMPI if (output(ii)%item(i)%MPISubComm /= -1) then call MPI_Group_free(output(ii)%item(i)%MPIgroupindex,ierr) endif -#endif #endif end select end do @@ -4588,10 +4544,8 @@ function prefix(campo) result(ext) ext='BCY_' case (iCurZ) ext='BCZ_' -#ifdef CompileWithNF2FF case (farfield) ext='FF_' -#endif end select return @@ -4815,10 +4769,6 @@ subroutine contabordes(sgg,imed,imed1,imed2,imed3,imed4,EsBorde,SINPML_fullsize, return end subroutine contabordes - - - -#ifdef CompileWithNodalSources subroutine nodalvtk(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,sggMtag, & init,geom,asigna,electric,magnetic,conta,i,ii,output,Ntimeforvolumic) type (SGGFDTDINFO), intent(IN) :: sgg @@ -5184,11 +5134,6 @@ subroutine nodalvtk(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,sggMtag, return end subroutine -#endif -!del CompileWithNodalSources - - -#ifdef CompileWithWires subroutine wirebundlesvtk(sgg,init,geom,asigna,conta,i,ii,output,Ntimeforvolumic,wiresflavor,sggMtag) type (SGGFDTDINFO), intent(IN) :: sgg @@ -5214,12 +5159,10 @@ subroutine wirebundlesvtk(sgg,init,geom,asigna,conta,i,ii,output,Ntimeforvolumic !print *,'----antes wires init,geom,asigna,conta,i,ii',init,geom,asigna,conta,i,ii if (init) then -#ifdef CompileWithWires if ((trim(adjustl(wiresflavor))=='holland') .or. & (trim(adjustl(wiresflavor))=='transition')) then Hwireslocal => GetHwires() endif -#endif #ifdef CompileWithBerengerWires if (trim(adjustl(wiresflavor))=='berenger') then Hwireslocal_Berenger => GetHwires_Berenger() @@ -5274,7 +5217,6 @@ subroutine wirebundlesvtk(sgg,init,geom,asigna,conta,i,ii,output,Ntimeforvolumic endif endif #endif -#ifdef CompileWithWires if ((trim(adjustl(wiresflavor))=='holland') .or. & (trim(adjustl(wiresflavor))=='transition')) then if (geom) then @@ -5318,7 +5260,6 @@ subroutine wirebundlesvtk(sgg,init,geom,asigna,conta,i,ii,output,Ntimeforvolumic end do endif endif -#endif #ifdef CompileWithSlantedWires if ((trim(adjustl(wiresflavor))=='slanted').or.(trim(adjustl(wiresflavor))=='semistructured')) then !parsea los hilos @@ -5368,9 +5309,6 @@ subroutine wirebundlesvtk(sgg,init,geom,asigna,conta,i,ii,output,Ntimeforvolumic return end subroutine -#endif - - !!!!!!!!!!!!!!!!!!!!!!!!!!!! !Function to publish the private output data (used in postprocess) !!!!!!!!!!!!!!!!!!!!!!!!!!!! diff --git a/src_main_pub/preprocess_geom.F90 b/src_main_pub/preprocess_geom.F90 index 339e107f..2a1d96ee 100644 --- a/src_main_pub/preprocess_geom.F90 +++ b/src_main_pub/preprocess_geom.F90 @@ -38,9 +38,7 @@ MODULE Preprocess_m USE CreateMatrices !typos que leo desde mi FDE USE FDEtypes -#ifdef CompileWithDMMA USE DMMA -#endif #ifdef CompileWithConformal USE CONFORMAL_INI_CLASS USE CONFORMAL_TOOLS @@ -113,14 +111,12 @@ SUBROUTINE read_geomData (sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sg character (LEN=BUFSIZE) :: chari,charj,chark,chari2,charj2,chark2 ! logical :: paraerrhilo,groundwires,islossy,DENTRO -#ifdef CompileWithDMMA REAL (KIND=RKIND) :: width, dir (1:3), epr1, mur1 LOGICAL :: oriX, oriY, oriZ, oriX2, oriY2, oriZ2, oriX3, oriY3, oriZ3, iguales LOGICAL :: oriX4, oriY4, oriZ4 REAL (KIND=RKIND), DIMENSION (3, 3) :: EprSlot, MurSlot INTEGER (KIND=4) :: indicemedio INTEGER (KIND=4) :: i11, j11 -#endif ! type (tagtype_t) :: tagtype TYPE (FreqDepenMaterial), POINTER :: fdgeom @@ -195,13 +191,12 @@ SUBROUTINE read_geomData (sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sg !echo por demas, habria que precontar pero es complicado porque depende del procesamiento !thin Slots -#ifdef CompileWithDMMA if (run_with_dmma) then DO j = 1, this%tSlots%n_tg contamedia = contamedia + this%tSlots%Tg(j)%N_tgc END DO endif -#endif + !end thin Slots !PARA LA CAPA EXTRA 2013 if (medioextra%exists) then @@ -2567,9 +2562,6 @@ SUBROUTINE read_geomData (sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sg ENDIF !FIN WIRES - !!?!?!? - ! -#ifdef CompileWithDMMA if (run_with_dmma) then !always at the end since the orientation is found from the PEC one !thin Slots @@ -2834,7 +2826,7 @@ SUBROUTINE read_geomData (sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sg END DO ! endif !del run_with_dmma -#endif + !debe ir al final para respetar el tipo de medio que haya SI SE TRATASE COMO A UN MEDIO !nodalsource !precounting diff --git a/src_main_pub/resuming.F90 b/src_main_pub/resuming.F90 index 08c39da4..db831128 100755 --- a/src_main_pub/resuming.F90 +++ b/src_main_pub/resuming.F90 @@ -31,39 +31,20 @@ module resuming Use Report use fdetypes - - - - !Thin metals - -#ifdef CompileWithSGBC #ifdef CompileWithStochastic use SGBC_stoch #else use SGBC_NOstoch #endif -#endif use PMLbodies - use Lumped #ifdef CompileWithNIBC use Multiports #endif - - !EDispersives -#ifdef CompileWithEDispersives use EDispersives use MDispersives -#endif - -#ifdef CompileWithNF2FF use farfield_m -#endif - - !Wires Thin Module -#ifdef CompileWithWires use HollandWires -#endif #ifdef CompileWithBerengerWires use WiresBerenger #ifdef CompileWithMPI @@ -293,7 +274,6 @@ subroutine flush_and_save_resume(sgg, b, layoutnumber, size, nentradaroot, nresu #ifdef CompileWithMPI !do an update of the currents to later read the currents OK if (size>1) then -#ifdef CompileWithWires if ((trim(adjustl(wiresflavor))=='holland') .or. & (trim(adjustl(wiresflavor))=='transition')) then if ((size>1).and.(thereare%wires)) then @@ -305,7 +285,6 @@ subroutine flush_and_save_resume(sgg, b, layoutnumber, size, nentradaroot, nresu endif #endif endif -#endif #ifdef CompileWithBerengerWires if (trim(adjustl(wiresflavor))=='berenger') then call FlushWiresMPI_Berenger(layoutnumber,size) @@ -316,12 +295,10 @@ subroutine flush_and_save_resume(sgg, b, layoutnumber, size, nentradaroot, nresu #endif if( Thereare%Wires) then -#ifdef CompileWithWires if ((trim(adjustl(wiresflavor))=='holland') .or. & (trim(adjustl(wiresflavor))=='transition')) then call StoreFieldsWires endif -#endif #ifdef CompileWithBerengerWires if (trim(adjustl(wiresflavor))=='berenger') then call StoreFieldsWires_Berenger @@ -344,7 +321,6 @@ subroutine flush_and_save_resume(sgg, b, layoutnumber, size, nentradaroot, nresu #endif if (ThereAre%Lumpeds) call StoreFieldsLumpeds(stochastic) -#ifdef CompileWithSGBC #ifdef CompileWithMPI #ifdef CompileWithStochastic if (stochastic) then @@ -354,21 +330,14 @@ subroutine flush_and_save_resume(sgg, b, layoutnumber, size, nentradaroot, nresu #endif if( Thereare%SGBCs) then call StoreFieldsSGBCs(stochastic) - endif - -#endif + endif #ifdef CompileWithNIBC if( Thereare%Multiports) call StoreFieldsMultiports #endif - -#ifdef CompileWithEDispersives if( Thereare%EDispersives) call StoreFieldsEDispersives if( Thereare%MDispersives) call StoreFieldsMDispersives -#endif if( Thereare%PlaneWaveBoxes) call StorePlaneWaves(sgg) -#ifdef CompileWithNF2FF if( Thereare%FarFields) call StoreFarFields(b) !called at initobservation -#endif #ifdef CompileWithMPI call MPI_Barrier(SUBCOMM_MPI,ierr) #endif diff --git a/src_main_pub/semba_fdtd.F90 b/src_main_pub/semba_fdtd.F90 index b8b9f25b..b6bcaa0e 100755 --- a/src_main_pub/semba_fdtd.F90 +++ b/src_main_pub/semba_fdtd.F90 @@ -55,10 +55,7 @@ PROGRAM SEMBA_FDTD_launcher USE Preprocess_m USE storeData - -#ifdef CompileWithXDMF USE xdmf_h5 -#endif ! #ifdef CompileWithMPI USE MPIcomm @@ -394,7 +391,6 @@ PROGRAM SEMBA_FDTD_launcher end if #endif -#ifdef CompileWithXDMF #ifdef CompileWithHDF !!!!tunel a lo bestia para crear el .h5 a 021219 if (l%createh5filefromsinglebin) then @@ -418,7 +414,6 @@ PROGRAM SEMBA_FDTD_launcher #endif stop endif -#endif #endif IF (status /= 0) then @@ -621,9 +616,6 @@ PROGRAM SEMBA_FDTD_launcher !check that simulation can actually be done for the kind of media requested DO i = 1, sgg%nummedia IF (sgg%Med(i)%Is%ThinWire) THEN -#ifndef CompileWithWires - CALL stoponerror (l%layoutnumber, l%size, 'Wires without wire support. Recompile!') -#endif #ifndef CompileWithBerengerWires if ((l%wiresflavor=='berenger')) then CALL stoponerror (l%layoutnumber, l%size, 'Berenger Wires without support. Recompile!') @@ -633,37 +625,6 @@ PROGRAM SEMBA_FDTD_launcher if ((l%wiresflavor=='slanted').or.(l%wiresflavor=='semistructured')) then CALL stoponerror (l%layoutnumber, l%size, 'slanted Wires without support. Recompile!') endif -#endif - CONTINUE - END IF - ! - IF (sgg%Med(i)%Is%EDispersive) THEN -#ifndef CompileWithEDispersives - CALL stoponerror (l%layoutnumber, l%size, 'Edispersives without Edispersives support. Recompile!') -#endif - CONTINUE - END IF - ! - IF (sgg%Med(i)%Is%MDispersive) THEN -#ifndef CompileWithEDispersives - CALL stoponerror (l%layoutnumber, l%size, 'Mdispersives without Edispersives support. Recompile!') -#endif - CONTINUE - END IF - ! - IF (sgg%Med(i)%Is%ThinSlot) THEN -#ifndef CompileWithDMMA - CALL stoponerror (l%layoutnumber, l%size, 'Slots without Slots support. Recompile!') -#endif -#ifndef CompileWithAnisotropic - CALL stoponerror (l%layoutnumber, l%size, 'Slots without Anisotropic support. Recompile!') -#endif - CONTINUE - END IF - ! - IF (sgg%Med(i)%Is%Anisotropic) THEN -#ifndef CompileWithAnisotropic - CALL stoponerror (l%layoutnumber, l%size, 'Anisotropics without Anisotropic support. Recompile!') #endif CONTINUE END IF @@ -672,10 +633,7 @@ PROGRAM SEMBA_FDTD_launcher #ifndef CompileWithNIBC if (l%mibc) CALL stoponerror (l%layoutnumber, l%size, 'l%mibc Multiports without support. Recompile!') #endif - -#ifndef CompileWithSGBC if (l%sgbc) CALL stoponerror (l%layoutnumber, l%size, 'sgbc thin metals without support. Recompile!') -#endif if (.not.(l%mibc.or.l%sgbc)) & CALL stoponerror (l%layoutnumber, l%size, 'Choose some treatment for multiports (-l%mibc,-sgbc)') CONTINUE diff --git a/src_main_pub/timestepping.F90 b/src_main_pub/timestepping.F90 index 89cf6396..93fd51c4 100755 --- a/src_main_pub/timestepping.F90 +++ b/src_main_pub/timestepping.F90 @@ -50,15 +50,10 @@ module Solver use Borders_CPML use Borders_MUR use Resuming - -#ifdef CompileWithNodalSources use nodalsources -#endif use Lumped use PMLbodies -#ifdef CompileWithXDMF use xdmf -#endif use vtk #ifdef CompileWithMPI use MPIcomm @@ -70,29 +65,19 @@ module Solver use Multiports #endif -#ifdef CompileWithSGBC #ifdef CompileWithStochastic use sgbc_stoch #else use sgbc_NOstoch #endif -#endif - -#ifdef CompileWithEDispersives use EDispersives use MDispersives -#endif -#ifdef CompileWithAnisotropic use Anisotropic -#endif -#ifdef CompileWithWires use HollandWires -#endif -#ifdef CompileWithWires + #ifdef CompileWithMTLN use Wire_bundles_mtln_mod #endif -#endif #ifdef CompileWithBerengerWires use WiresBerenger @@ -100,6 +85,7 @@ module Solver use WiresBerenger_MPI #endif #endif + #ifdef CompileWithSlantedWires use WiresSlanted use estructura_slanted_m @@ -741,7 +727,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx ! one more MM for right adjancencies dtcritico=sgg%dt -#ifdef CompileWithWires if ((trim(adjustl(wiresflavor))=='holland') .or. & (trim(adjustl(wiresflavor))=='transition')) then #ifdef CompileWithMPI @@ -764,7 +749,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx endif endif -#endif #ifdef CompileWithBerengerWires if (trim(adjustl(wiresflavor))=='berenger') then @@ -855,8 +839,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx call MPI_Barrier(SUBCOMM_MPI,ierr) #endif - -#ifdef CompileWithWires if (use_mtln_wires) then #ifdef CompileWithMTLN call InitWires_mtln(sgg,Ex,Ey,Ez,eps0, mu0, mtln_parsed,thereAre%MTLNbundles) @@ -864,11 +846,7 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx write(buff,'(a)') 'WIR_ERROR: Executable was not compiled with MTLN modules.' #endif endif -#endif - - -#ifdef CompileWithAnisotropic !Anisotropic #ifdef CompileWithMPI call MPI_Barrier(SUBCOMM_MPI,ierr) @@ -881,14 +859,12 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx call MPI_Barrier(SUBCOMM_MPI,ierr) call MPI_AllReduce( l_auxinput, l_auxoutput, 1_4, MPI_LOGICAL, MPI_LOR, MPI_COMM_WORLD, ierr) #endif - if (l_auxoutput) then - write (dubuf,*) '----> there are Structured anisotropic elements'; call print11(layoutnumber,dubuf) - else - write(dubuf,*) '----> no Structured anisotropic elements found'; call print11(layoutnumber,dubuf) - endif -#endif + if (l_auxoutput) then + write (dubuf,*) '----> there are Structured anisotropic elements'; call print11(layoutnumber,dubuf) + else + write(dubuf,*) '----> no Structured anisotropic elements found'; call print11(layoutnumber,dubuf) + endif -#ifdef CompileWithSGBC IF (sgbc) then #ifdef CompileWithMPI call MPI_Barrier(SUBCOMM_MPI,ierr) @@ -908,7 +884,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx write(dubuf,*) '----> no Structured sgbc elements found'; call print11(layoutnumber,dubuf) endif endif -#endif !!!! #ifdef CompileWithNIBC @@ -971,7 +946,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx endif #endif -#ifdef CompileWithEDispersives #ifdef CompileWithMPI call MPI_Barrier(SUBCOMM_MPI,ierr) #endif @@ -1004,7 +978,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx else write(dubuf,*) '----> no Structured Magnetic dispersive elements found'; call print11(layoutnumber,dubuf) endif -#endif #ifdef CompileWithMPI call MPI_Barrier(SUBCOMM_MPI,ierr) @@ -1024,8 +997,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx write(dubuf,*) '----> no Plane waves are found'; call print11(layoutnumber,dubuf) endif -#ifdef CompileWithNodalSources - !debe venir antes para que observation las use en mapvtk #ifdef CompileWithMPI call MPI_Barrier(SUBCOMM_MPI,ierr) #endif @@ -1050,8 +1021,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx write(dubuf,*) '----> no Structured Nodal sources are found'; call print11(layoutnumber,dubuf) endif -#endif - !!!!!!!sgg 121020 !rellena la matriz Mtag con los slots de una celda call fillMtag(sgg, sggMiEx, sggMiEy, sggMiEz, sggMiHx, sggMiHy, sggMiHz,sggMtag, b) !!!!!!!fin @@ -1117,7 +1086,7 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx Ex,Ey,Ez,Hx,Hy,Hz) call MPI_Barrier(SUBCOMM_MPI,ierr) write(dubuf,*) '[OK]'; call print11(layoutnumber,dubuf) -#ifdef CompileWithWires + !this modifies the initwires stuff and must be called after initwires (typically at the end) !llamalo siempre aunque no HAYA WIRES!!! para que no se quede colgado en hilos terminales if ((trim(adjustl(wiresflavor))=='holland') .or. & @@ -1127,7 +1096,7 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx call MPI_Barrier(SUBCOMM_MPI,ierr) write(dubuf,*) '[OK]'; call print11(layoutnumber,dubuf) endif -#endif + #ifdef CompileWithBerengerWires if (trim(adjustl(wiresflavor))=='berenger') then write(dubuf,*) 'Init MPI Multi-Wires...'; call print11(layoutnumber,dubuf) @@ -1147,12 +1116,11 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx !must be called now in case the MPI has changed the connectivity info -#ifdef CompileWithWires if ((trim(adjustl(wiresflavor))=='holland') .or. & (trim(adjustl(wiresflavor))=='transition')) then call ReportWireJunctions(layoutnumber,size,thereare%wires,sgg%Sweep(iHz)%ZI, sgg%Sweep(iHz)%ZE,groundwires,strictOLD,verbose) endif -#endif + #ifdef CompileWithBerengerWires if (trim(adjustl(wiresflavor))=='berenger') then call ReportWireJunctionsBerenger(layoutnumber,size,thereare%wires,sgg%Sweep(iHz)%ZI, sgg%Sweep(iHz)%ZE,groundwires,strictOLD,verbose) @@ -1209,7 +1177,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx call MPI_Barrier(SUBCOMM_MPI,ierr) call FlushMPI_H_Cray endif -#ifdef CompileWithWires if ((trim(adjustl(wiresflavor))=='holland') .or. & (trim(adjustl(wiresflavor))=='transition')) then if ((size>1).and.(thereare%wires)) then @@ -1221,7 +1188,7 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx endif #endif endif -#endif + #ifdef CompileWithBerengerWires if (trim(adjustl(wiresflavor))=='berenger') then if ((size>1).and.(thereare%wires)) call FlushWiresMPI_Berenger(layoutnumber,size) @@ -1229,7 +1196,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx #endif #endif !!!no se si el orden wires - sgbcs del sync importa 150519 -#ifdef CompileWithSGBC #ifdef CompileWithMPI #ifdef CompileWithStochastic if (stochastic) then @@ -1237,7 +1203,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx endif #endif #endif -#endif #ifdef CompileWithMPI #ifdef CompileWithStochastic @@ -1337,12 +1302,11 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx if (thereareplanewave) call print11(layoutnumber,dubuf) endif endif -#ifdef CompileWithAnisotropic + !Anisotropic !Must be previous to the main stepping since the main stepping overrides the past components with the last and the !lossy part of the anisotropic STILL requires the past info on adjacent components IF (Thereare%Anisotropic) call AdvanceAnisotropicE(sgg%alloc,ex,ey,ez,hx,hy,hz,Idxe,Idye,Idze,Idxh,Idyh,Idzh) -#endif !!electric Fields Maxwell AND CPML Zone !!for tuning @@ -1413,7 +1377,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx !******************************************************************************* !******************************************************************************* !!!lamo aqui los hilos por coherencia con las PML que deben absorber los campos creados por los hilos -#ifdef CompileWithWires !Wires (only updated here. No need to update in the H-field part) if (( (trim(adjustl(wiresflavor))=='holland') .or. & (trim(adjustl(wiresflavor))=='transition')) .and. .not. use_mtln_wires) then @@ -1431,7 +1394,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx endif endif endif -#endif #ifdef CompileWithBerengerWires if (trim(adjustl(wiresflavor))=='berenger') then IF (Thereare%Wires) call AdvanceWiresE_Berenger(sgg,n) @@ -1444,7 +1406,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx call AdvanceWiresE_Slanted(sgg,n) endif #endif -#ifdef CompileWithWires if (use_mtln_wires) then #ifdef CompileWithMTLN call AdvanceWiresE_mtln(sgg,Idxh,Idyh,Idzh,eps0,mu0) @@ -1452,7 +1413,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx write(buff,'(a)') 'WIR_ERROR: Executable was not compiled with MTLN modules.' #endif end if -#endif If (Thereare%PMLbodies) then !waveport absorbers call AdvancePMLbodyE endif @@ -1485,20 +1445,15 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx IF (Thereare%Multiports.and.(mibc)) call AdvanceMultiportE(sgg%alloc,Ex, Ey, Ez) #endif - -#ifdef CompileWithSGBC !MultiportS H-field advancing IF (Thereare%sgbcs.and.(sgbc)) then call AdvancesgbcE(real(sgg%dt,RKIND),sgbcDispersive,simu_devia,stochastic) endif -#endif !!! if (ThereAre%Lumpeds) call AdvanceLumpedE(sgg,n,simu_devia,stochastic) !!! -#ifdef CompileWithEDispersives !EDispersives (only updated here. No need to update in the H-field part) IF (Thereare%Edispersives) call AdvanceEDispersiveE(sgg) -#endif !PMC are only called in the H-field part (image theory method) @@ -1518,16 +1473,13 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx endif endif - -#ifdef CompileWithNodalSources - !NOdal sources E-field advancing + !Nodal sources E-field advancing If (Thereare%NodalE) then - ! if (.not.simu_devia) then !bug! debe entrar en nodal y si son hard simplemente ponerlas a cero !mdrc 290323 - call AdvanceNodalE(sgg,sggMiEx,sggMiEy,sggMiEz,sgg%NumMedia,n, b,G2,Idxh,Idyh,Idzh,Ex,Ey,Ez,simu_devia) - ! endif + ! if (.not.simu_devia) then !bug! debe entrar en nodal y si son hard simplemente ponerlas a cero !mdrc 290323 + call AdvanceNodalE(sgg,sggMiEx,sggMiEy,sggMiEz,sgg%NumMedia,n, b,G2,Idxh,Idyh,Idzh,Ex,Ey,Ez,simu_devia) + ! endif endif -#endif !!!!!!!!!!!!!!!!!! @@ -1546,12 +1498,10 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx ! !Magnetic Fields Maxwell AND CPML Zone -#ifdef CompileWithAnisotropic !Anisotropic !Must be previous to the main stepping since the main stepping overrides the past components with the last and the !lossy part of the anisotropic STILL requires the past info on adjacent components IF (Thereare%Anisotropic) call AdvanceAnisotropicH(sgg%alloc,ex,ey,ez,hx,hy,hz,Idxe,Idye,Idze,Idxh,Idyh,Idzh) -#endif !************************************************************************************************** !***[conformal] ******************************************************************* @@ -1659,18 +1609,13 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx call CloneMagneticPeriodic(sgg%alloc,sgg%Border,Hx,Hy,Hz,sgg%sweep,layoutnumber,size) endif ! - -#ifdef CompileWithSGBC !MultiportS H-field advancing IF (Thereare%sgbcs.and.(sgbc)) then call AdvancesgbcH endif -#endif -#ifdef CompileWithEDispersives !MDispersives (only updated here. No need to update in the E-field part) IF (Thereare%Mdispersives) call AdvanceMDispersiveH(sgg) -#endif #ifdef CompileWithNIBC !Multiports H-field advancing @@ -1693,20 +1638,15 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx endif - -#ifdef CompileWithNodalSources - !NOdal sources E-field advancing + !Nodal sources E-field advancing If (Thereare%NodalH) then !! if (.not.simu_devia) then !bug! debe entrar en nodal y si son hard simplemente ponerlas a cero !mdrc 290323 call AdvanceNodalH(sgg,sggMiHx,sggMiHy,sggMiHz,sgg%NumMedia,n, b ,GM2,Idxe,Idye,Idze,Hx,Hy,Hz,simu_devia) !! endif endif -#endif - !Must be called here again at the end to enforce any of the previous changes !Posible Wire for thickwires advancing in the H-field part -#ifdef CompileWithWires !Wires (only updated here. No need to update in the H-field part) if ((trim(adjustl(wiresflavor))=='holland') .or. & (trim(adjustl(wiresflavor))=='transition')) then @@ -1718,7 +1658,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx endif endif endif -#endif !PMC BORDERS H-field advancing (duplicates the H-fields at the interface changing their sign) If (Thereare%PMCBorders) call MinusCloneMagneticPMC(sgg%alloc,sgg%Border,Hx,Hy,Hz,sgg%sweep,layoutnumber,size) !Periodic BORDERS H-field mirroring @@ -1753,7 +1692,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx call MPI_Barrier(SUBCOMM_MPI,ierr) call FlushMPI_H_Cray endif -#ifdef CompileWithWires if ((trim(adjustl(wiresflavor))=='holland') .or. & (trim(adjustl(wiresflavor))=='transition')) then if ((size>1).and.(thereare%wires)) then @@ -1765,7 +1703,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx endif #endif endif -#endif #ifdef CompileWithBerengerWires if (trim(adjustl(wiresflavor))=='berenger') then if ((size>1).and.(thereare%wires)) call FlushWiresMPI_Berenger(layoutnumber,size) @@ -1774,14 +1711,12 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx #endif !!!no se si el orden wires - sgbcs del sync importa 150519 -#ifdef CompileWithSGBC #ifdef CompileWithMPI #ifdef CompileWithStochastic if (stochastic) then call syncstoch_mpi_sgbcs(simu_devia,layoutnumber,size) endif #endif -#endif #endif #ifdef CompileWithMPI @@ -1971,10 +1906,10 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx call print11(layoutnumber,dubuf) call print11(layoutnumber,SEPARADOR//separador//separador) somethingdone=.false. -#ifdef CompileWithXDMF + if (Thereare%Observation) call createxdmfOnTheFly(sgg,layoutnumber,size,vtkindex,createh5bin,somethingdone,mpidir) if (createh5bin) call createh5bintxt(sgg,layoutnumber,size) !lo deben llamar todos haya on on thereare%observation -#endif + #ifdef CompileWithMPI call MPI_Barrier(SUBCOMM_MPI,ierr) call MPI_AllReduce( somethingdone, newsomethingdone, 1_4, MPI_LOGICAL, MPI_LOR, SUBCOMM_MPI, ierr) @@ -2191,11 +2126,9 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx write(dubuf,*) SEPARADOR//separador//separador call print11(layoutnumber,dubuf) somethingdone=.false. -#ifdef CompileWithXDMF if (Thereare%Observation) call createxdmf(sgg,layoutnumber,size,vtkindex,createh5bin,somethingdone,mpidir) if (createh5bin) call createh5bintxt(sgg,layoutnumber,size) !lo deben llamar todos haya o no thereare%observation ! call create_interpreted_mesh(sgg) -#endif #ifdef CompileWithMPI call MPI_Barrier(SUBCOMM_MPI,ierr) call MPI_AllReduce( somethingdone, newsomethingdone, 1_4, MPI_LOGICAL, MPI_LOR, SUBCOMM_MPI, ierr) @@ -3272,28 +3205,20 @@ subroutine Destroy_All_exceptSGGMxx(sgg,Ex, Ey, Ez, Hx, Hy, Hz,G1,G2,GM1,GM2,dxe REAL (KIND=RKIND), intent(INOUT) , pointer, dimension ( : ) :: G1,G2,GM1,GM2,dxe ,dye ,dze ,Idxe ,Idye ,Idze ,dxh ,dyh ,dzh ,Idxh ,Idyh ,Idzh call DestroyObservation(sgg) -#ifdef CompileWithNodalSources Call DestroyNodal(sgg) -#endif call DestroyIlumina(sgg) #ifdef CompileWithNIBC call DestroyMultiports(sgg) #endif -#ifdef CompileWithSGBC call destroysgbcs(sgg) !!todos deben destruir pq alocatean en funcion de sgg no de si contienen estos materiales que lo controla therearesgbcs. Lo que habia era IF ((Thereare%sgbcs).and.(sgbc)) -#endif call destroyLumped(sgg) -#ifdef CompileWithEDispersives call DestroyEDispersives(sgg) call DestroyMDispersives(sgg) -#endif -#ifdef CompileWithWires if ((trim(adjustl(wiresflavor))=='holland') .or. & (trim(adjustl(wiresflavor))=='transition')) then call DestroyWires(sgg) endif -#endif #ifdef CompileWithBerengerWires if (trim(adjustl(wiresflavor))=='berenger') then call DestroyWires_Berenger(sgg) diff --git a/src_main_pub/xdmf.F90 b/src_main_pub/xdmf.F90 new file mode 100644 index 00000000..31633e79 --- /dev/null +++ b/src_main_pub/xdmf.F90 @@ -0,0 +1,579 @@ +MODULE xdmf + ! + USE fdetypes + USE Observa + use report + use xdmf_h5 + ! + ! + ! + ! + IMPLICIT NONE + ! + PRIVATE + PUBLIC createxdmf,createxdmfOnTheFly,createh5bintxt + !!! public create_interpreted_mesh +CONTAINS + ! ================================================================================================= + ! ====>>>> SALVADOR's CODE <<<<==== + ! ================================================================================================= + ! + !Subrutine to parse the volumic probes to create .xdmf and .h5 files + ! + SUBROUTINE createxdmf (sgg,layoutnumber, size,vtkindex,createh5bin,somethingdone,mpidir) + logical, save :: firsttimeenteringcreatexdmf=.true. + integer (KIND=4) :: mpidir + logical :: vtkindex,createh5bin + !------------------------> + CHARACTER (LEN=BUFSIZE) :: filename ! File name + ! + type (SGGFDTDINFO), intent(IN) :: sgg + INTEGER (KIND=4), INTENT (IN) :: layoutnumber, size + INTEGER (KIND=4) :: ierr, sizeofvalores,COMPO + complex( kind = CKIND), dimension( :, :, :, :,: ), allocatable :: valor3DComplex !freqdomain probes + ! + TYPE (output_t), POINTER, DIMENSION (:) :: output + INTEGER (KIND=4) :: iroot + integer (KIND=4) :: myunit + ! +#ifdef CompileWithMPI + REAL (KIND=RKIND), ALLOCATABLE, DIMENSION (:, :, :, :) :: newvalor3d !para sondas Volumic +#endif + + + REAL (KIND=RKIND), ALLOCATABLE, DIMENSION (:, :, :, :) :: valor3d !para sondas Volumic + real ( KINd=RKIND_TIEMPO), ALLOCATABLE, DIMENSION (:) :: att + + + INTEGER (KIND=4) :: indi,fieldob + ! + INTEGER (KIND=4) :: ii, i1, j1, k1, finalstep + INTEGER (KIND=4) :: minx, maxx, miny, maxy, minz, maxz,pasadas,pasadastotales + LOGICAL :: lexis,somethingdone + character (LEN=BUFSIZE) :: dubuf + INTEGER (KIND=4) :: minXabs, maxXabs, minYabs, maxYabs, minZabs, maxZabs + INTEGER (KIND=4) :: minXabs_primero,minYabs_primero,minZabs_primero,imdice + CHARACTER (LEN=BUFSIZE) :: pathroot + character (LEN=BUFSIZE) :: chari,charj,chark,chari2,charj2,chark2 + character (LEN=BUFSIZE) :: extpoint + character(len=BUFSIZE) :: buff + REAL (KIND=RKIND) :: linez_minZabs_primero,liney_minYabs_primero,linex_minXabs_primero, & + dz_minZabs,dy_minYabs,dx_minXabs + ! + CHARACTER (LEN=BUFSIZE) :: whoami, whoamishort + REAL (KIND=RKIND) :: rdum + integer :: my_iostat + + WRITE (whoamishort, '(i5)') layoutnumber + 1 + WRITE (whoami, '(a,i5,a,i5,a)') '(', layoutnumber + 1, '/', size, ') ' + ! + output => GetOutput ()!get the output private info from observation + + somethingdone=.false. + barridoprobes: DO ii = 1, sgg%NumberRequest + + IF (sgg%observation(ii)%Volumic) then + if (sgg%observation(ii)%nP == 1) then + if ((sgg%observation(ii)%P(1)%What /= nothing).AND.(sgg%observation(ii)%P(1)%What /= iCur).AND.(sgg%observation(ii)%P(1)%What /= mapvtk).AND. & + (sgg%observation(ii)%P(1)%What /= iCurX).AND.(sgg%observation(ii)%P(1)%What /= iCurY).AND.(sgg%observation(ii)%P(1)%What /= iCurZ)) THEN + if (sgg%Observation(ii)%done.and.(sgg%Observation(ii)%flushed)) then + cycle barridoprobes + elseif (sgg%Observation(ii)%done) then + sgg%Observation(ii)%flushed=.true. !ultima que se flushea + continue + elseif ((.not.(sgg%Observation(ii)%done)).and.(sgg%Observation(ii)%Begun)) then + continue + elseif (.not.(sgg%Observation(ii)%begun)) then + cycle barridoprobes + else !creo que tengo toda la casuistica, por si se me escapa algo continuo, y ya debajo se manejara + continue + endif + else + cycle barridoprobes + endif + endif + endif + ! + !sondas Volumic traducelas a xdfm + IF (sgg%observation(ii)%Volumic) then + if (sgg%observation(ii)%nP == 1) then + if ((sgg%observation(ii)%P(1)%What /= nothing).AND.(sgg%observation(ii)%P(1)%What /= iCur).AND.(sgg%observation(ii)%P(1)%What /= mapvtk).AND. & + (sgg%observation(ii)%P(1)%What /= iCurX).AND.(sgg%observation(ii)%P(1)%What /= iCurY).AND.(sgg%observation(ii)%P(1)%What /= iCurZ)) THEN + INQUIRE (FILE=trim(adjustl(output(ii)%item(1)%path)), EXIST=lexis) + if ((lexis).and.(output(ii)%TimesWritten/=0)) then + fieldob=sgg%observation(ii)%P(1)%what +!inicializaciones varias + ! + minXabs = sgg%observation(ii)%P(1)%XI + maxXabs = sgg%observation(ii)%P(1)%XE + minYabs = sgg%observation(ii)%P(1)%YI + maxYabs = sgg%observation(ii)%P(1)%YE +#ifdef CompileWithMPI + minZabs = output(ii)%item(1)%ZIorig + maxZabs = output(ii)%item(1)%ZEorig +#else + minZabs = sgg%observation(ii)%P(1)%zI + maxZabs = sgg%observation(ii)%P(1)%zE +#endif + write(chari ,'(i7)') minXabs + write(charj ,'(i7)') minYabs + write(chark ,'(i7)') minZabs + write(chari2,'(i7)') maxXabs + write(charj2,'(i7)') maxYabs + write(chark2,'(i7)') maxZabs + !mpidir 190319 !desrotacion para que los nombres sean correctos + if (mpidir==3) then + extpoint=trim(adjustl(chari)) //'_'//trim(adjustl(charj)) //'_'//trim(adjustl(chark))//'__'// & + trim(adjustl(chari2))//'_'//trim(adjustl(charj2))//'_'//trim(adjustl(chark2)) + elseif (mpidir==2) then + extpoint=trim(adjustl(charj)) //'_'//trim(adjustl(chark)) //'_'//trim(adjustl(chari))//'__'// & + trim(adjustl(charj2))//'_'//trim(adjustl(chark2))//'_'//trim(adjustl(chari2)) + elseif (mpidir==1) then + extpoint=trim(adjustl(chark)) //'_'//trim(adjustl(chari)) //'_'//trim(adjustl(charj))//'__'// & + trim(adjustl(chark2))//'_'//trim(adjustl(chari2))//'_'//trim(adjustl(charj2)) + else + call stoponerror(layoutnumber,size,'Buggy error in mpidir. ') + endif + !fin mpidir + + !! CORREGIDO PARA TRANCOS AHORA DESPUES DE HABER PUESTO BIEN EXTPOINT +!guarda el original + minXabs_primero = minXabs + minYabs_primero = minYabs + minZabs_primero = minZabs + im1: do imdice=minXabs,maxXabs + if (mod(imdice,output(ii)%item(1)%Xtrancos)==0) then + minXabs_primero=imdice + exit im1 + endif + end do im1 + im2: do imdice=minYabs,maxYabs + if (mod(imdice,output(ii)%item(1)%Ytrancos)==0) then + minYabs_primero=imdice + exit im2 + endif + end do im2 + im3: do imdice=minZabs,maxZabs + if (mod(imdice,output(ii)%item(1)%Ztrancos)==0) then + minZabs_primero=imdice + exit im3 + endif + end do im3 +!pufff hay mucha reduncancia minxabs = minx, etc. 021219 limpiar algun dia + minXabs = int(sgg%Observation(ii)%P(1)%XI/output(ii)%item(1)%Xtrancos) + if (mod(sgg%Observation(ii)%P(1)%XI,output(ii)%item(1)%Xtrancos) /= 0) minXabs=minXabs+1 + maxXabs = int(sgg%Observation(ii)%P(1)%XE/output(ii)%item(1)%Xtrancos) + minYabs = int(sgg%observation(ii)%P(1)%YI/output(ii)%item(1)%Ytrancos) + if (mod(sgg%Observation(ii)%P(1)%YI,output(ii)%item(1)%Ytrancos) /= 0) minYabs=minYabs+1 + maxYabs = int(sgg%observation(ii)%P(1)%YE/output(ii)%item(1)%Ytrancos) + +#ifdef CompileWithMPI + minZabs = int(output(ii)%item(1)%ZIorig/output(ii)%item(1)%Ztrancos) + if (mod(output(ii)%item(1)%ZIorig,output(ii)%item(1)%Ztrancos) /= 0) minZabs=minZabs+1 + maxZabs = int(output(ii)%item(1)%ZEorig/output(ii)%item(1)%Ztrancos) +#else + minZabs = int(sgg%observation(ii)%P(1)%zI/output(ii)%item(1)%Ztrancos) + if (mod(sgg%Observation(ii)%P(1)%ZI,output(ii)%item(1)%Ztrancos) /= 0) minZabs=minZabs+1 + maxZabs = int(sgg%observation(ii)%P(1)%zE/output(ii)%item(1)%Ztrancos) +#endif + + + !fin trancos + + iroot=index(output(ii)%item(1)%path,'__',.true.) + pathroot=trim(adjustl(output(ii)%item(1)%path(1:iroot-1))) + iroot = index (pathroot, '_',.true.) + pathroot = trim (adjustl(pathroot(1:iroot-1))) + iroot = index (pathroot, '_',.true.) + pathroot = trim (adjustl(pathroot(1:iroot-1))) + iroot = index (pathroot, '_',.true.) + pathroot = trim(adjustl(pathroot(1:iroot-1)))//'_'//trim(adjustl(extpoint)) + + + linez_minZabs_primero = sgg%linez(minZabs_primero) + liney_minYabs_primero = sgg%liney(minYabs_primero) + linex_minXabs_primero = sgg%linex(minXabs_primero) + dz_minZabs = sgg%dz(minZabs)*output(ii)%item(1)%Ztrancos + dy_minYabs = sgg%dy(minYabs)*output(ii)%item(1)%Ytrancos + dx_minXabs = sgg%dx(minXabs)*output(ii)%item(1)%Xtrancos + + OPEN (output(ii)%item(1)%UNIT, FILE=trim(adjustl(output(ii)%item(1)%path)), FORM='unformatted') +!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! + READ (output(ii)%item(1)%UNIT) minx, maxx , miny, maxy, minz, maxz !ya deben venir bien escritos incluyendo correccion de TRANCOS +!!!allocate space + if (SGG%Observation(ii)%TimeDomain) then + finalstep=output(ii)%TimesWritten + allocate (att(1:finalstep)) + att = 0.0_RKIND !aquiiiii + pasadastotales=1 + ALLOCATE (valor3d(minXabs:maxXabs, minYabs:maxYabs, minZabs:maxZabs, 1)) + elseif (SGG%Observation(ii)%FreqDomain) then + !este read solo se precisa para la frecuencial y es dummy + read(output(ii)%item(1)%unit) rdum !instante en el que se ha escrito la info frequencial + finalstep= output(ii)%NumFreqs + allocate (att(1:finalstep)) + att = 0.0_RKIND !aquiiiii + pasadastotales=2 + ALLOCATE (valor3d(minXabs:maxXabs, minYabs:maxYabs, minZabs:maxZabs, 1)) + ALLOCATE (valor3dCOMPLEX(1,1:3,minXabs:maxXabs, minYabs:maxYabs, minZabs:maxZabs)) + endif + +#ifdef CompileWithMPI + ALLOCATE (newvalor3d(minXabs:maxXabs, minYabs:maxYabs, minZabs:maxZabs, 1)) +#endif + +#ifdef CompileWithMPI + IF (layoutnumber == output(ii)%item(1)%MPIRoot) THEN +#else + IF (layoutnumber == 0) THEN +#endif + if (createh5bin) then + if (firsttimeenteringcreatexdmf) then + open(newunit=myunit,file=trim(adjustl(sgg%nEntradaRoot))//'_'//trim(adjustl(whoamishort))//'_h5bin.txt',form='formatted') !lista de todos los .h5bin + WRITE (myunit, '(a)') '!END' + close(myunit,status='delete') + firsttimeenteringcreatexdmf=.false. + endif + my_iostat=0 +9138 if(my_iostat /= 0) write(*,fmt='(a)',advance='no'), '.' !!if(my_iostat /= 0) print '(i5,a1,i4,2x,a)',9138,'.',layoutnumber,trim(adjustl(sgg%nEntradaRoot))//'_'//trim(adjustl(whoamishort))//'_h5bin.txt' + open(newunit=myunit,file=trim(adjustl(sgg%nEntradaRoot))//'_'//trim(adjustl(whoamishort))//'_h5bin.txt',form='formatted',position='append',err=9138,iostat=my_iostat,status='new',action='write') !lista de todos los .h5bin + ! !lista de todos los .h5bin + write (myunit,'(a)') trim(adjustl(pathroot))//'.h5bin' + close(myunit) + ! + open(newunit=myunit,file=trim(adjustl(pathroot))//'.h5bin',form='unformatted') + write (myunit) finalstep,minXabs, maxXabs, minYabs, maxYabs, minZabs, maxZabs,fieldob,SGG%Observation(ii)%TimeDomain,pasadastotales + endif + endif !del layoutnumber + +#ifdef CompileWithMPI + call MPI_Barrier(output(ii)%item(1)%MPISubComm,ierr) +#endif + buclepasadas: do pasadas=1,pasadastotales +!!!inicializa a cero en cada pasada + if (SGG%Observation(ii)%TimeDomain) then + valor3d = 0.0_RKIND + elseif (SGG%Observation(ii)%FreqDomain) then + valor3d = 0.0_RKIND + valor3dCOMPLEX = 0.0_RKIND + endif + +#ifdef CompileWithMPI + newvalor3d = 0.0_RKIND +#endif +!!!!abre fiecho escritura .h5 + +!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! + if (SGG%Observation(ii)%TimeDomain) then + if (pasadas==1) then + filename = trim (adjustl(pathroot))//'_time' + else + print *,'Buggy error in valor3d. ' + stop + endif + continue !ya se ha leido valor3d + else + if (pasadas==1) then + filename = trim (adjustl(pathroot))//'_mod' + elseif (pasadas==2) then + filename = trim (adjustl(pathroot))//'_phase' + else + print *,'Buggy error in valor3d. ' + stop + endif + endif +#ifdef CompileWithHDF +#ifdef CompileWithMPI + IF (layoutnumber == output(ii)%item(1)%MPIRoot) THEN +#else + IF (layoutnumber == 0) THEN +#endif + + if (.not.(((fieldob == iMEC).or.(fieldob ==iMHC)).and.(pasadas ==2))) then ! no tiene sentido esccribir la fase del modulo + call openh5file(filename,finalstep,minXabs,maxXabs, minYabs,maxYabs, minZabs,maxZabs) + endif + endif +#endif + + bucleindi: DO indi = 1, finalstep + if (pasadas == 1) then !solo es preciso leer los datos una vez + READ (output(ii)%item(1)%UNIT) att(indi) + write(dubuf,*) ' ----> .xdmf file ',att(indi),'(',indi,'/',finalstep,')' + call print11(layoutnumber,dubuf) + + if (SGG%Observation(ii)%TimeDomain) then + DO k1 = minz, maxz + DO j1 = miny, maxy + READ (output(ii)%item(1)%UNIT) (valor3d(i1, j1, k1, 1), i1=minx, maxx) + END DO + END DO + ! + elseif (SGG%Observation(ii)%FreqDomain) then + DO COMPO=1,3 + DO k1 = minz, maxz + DO j1 = miny, maxy + READ (output(ii)%item(1)%UNIT) (valor3dCOMPLEX(1,COMPO,i1, j1, k1), i1=minx, maxx) + END DO + END DO + END DO + endif + endif !del if (pasadas==1 +!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! + if (SGG%Observation(ii)%TimeDomain) then + continue !ya se ha leido valor3d + else !freqdomain construir valor3d + select case (fieldob) + case(iMEC,iMHC) + !modulo + DO k1 = minz, maxz + DO j1 = miny, maxy + DO i1=minx, maxx + if (pasadas==1) then !modulo + valor3d(i1, j1, k1, 1)=SQRT( ABS(valor3dCOMPLEX(1,1,i1, j1, k1))**2. + & + ABS(valor3dCOMPLEX(1,2,i1, j1, k1))**2. + & + ABS(valor3dCOMPLEX(1,3,i1, j1, k1))**2. ) !sgg 301119 faltaba este cuadrado creo + else !phase + valor3d=0.0_RKIND !LA fase no tiene sentido para el modulo del vector + endif + END DO + END DO + END DO + case(iExC,iHxC) + DO k1 = minz, maxz + DO j1 = miny, maxy + DO i1=minx, maxx + if (pasadas==1) then !modulo + valor3d(i1, j1, k1, 1)= ABS(valor3dCOMPLEX(1,1,i1, j1, k1)) + else !phase + valor3d(i1, j1, k1, 1)= ATAN2(AIMAG(valor3dCOMPLEX(1,1,i1, j1, k1)),REAL(valor3dCOMPLEX(1,1,i1, j1, k1))) + endif + END DO + END DO + END DO + case(iEyC,iHyC) + DO k1 = minz, maxz + DO j1 = miny, maxy + DO i1=minx, maxx + if (pasadas==1) then !modulo + valor3d(i1, j1, k1, 1)=ABS(valor3dCOMPLEX(1,2,i1, j1, k1)) + else !phase + valor3d(i1, j1, k1, 1)= ATAN2(AIMAG(valor3dCOMPLEX(1,2,i1, j1, k1)),REAL(valor3dCOMPLEX(1,2,i1, j1, k1))) + endif + END DO + END DO + END DO + case(iEzC,iHzC) + DO k1 = minz, maxz + DO j1 = miny, maxy + DO i1=minx, maxx + if (pasadas==1) then !modulo + valor3d(i1, j1, k1, 1)=ABS(valor3dCOMPLEX(1,3,i1, j1, k1)) + else !phase + valor3d(i1, j1, k1, 1)= ATAN2(AIMAG(valor3dCOMPLEX(1,3,i1, j1, k1)),REAL(valor3dCOMPLEX(1,3,i1, j1, k1))) + endif + END DO + END DO + END DO + case default + print *,'Buggy error in valor3d. Not processing continuing. ' + continue + end select + endif !del time domain +!!!!!!!!!!!!!!!!sincroniza valor3d y aunalos en el root +#ifdef CompileWithMPI + if (size>1) then + if (output(ii)%item(1)%MPISubComm /= -1) then + sizeofvalores = (maxXabs-minXabs+1) * (maxYabs-minYabs+1) * (maxZabs-minZabs+1) + call MPI_Barrier(output(ii)%item(1)%MPISubComm,ierr) + CALL MPI_AllReduce (valor3d, newvalor3d, sizeofvalores, REALSIZE, MPI_SUM, & + & output(ii)%item(1)%MPISubComm, ierr) + endif + valor3d = newvalor3d + endif +#endif + +!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! +!escribe los ficheros de salida + +#ifdef CompileWithMPI + IF (layoutnumber == output(ii)%item(1)%MPIRoot) THEN +#else + IF (layoutnumber == 0) THEN +#endif +#ifdef CompileWithHDF + if (.not.(((fieldob == iMEC).or.(fieldob ==iMHC)).and.(pasadas ==2))) then ! no tiene sentido esccribir la fase del modulo + call writeh5file(filename,valor3d,indi,att(indi),minXabs,maxXabs, minYabs,maxYabs, minZabs,maxZabs, & + linez_minZabs_primero,liney_minYabs_primero,linex_minXabs_primero, & + dz_minZabs,dy_minYabs,dx_minXabs,& + minZabs_primero,minYabs_primero,minXabs_primero,finalstep,vtkindex) + endif +#endif + if (createh5bin) then + write (myunit) (minZabs_primero),(minYabs_primero), (minXabs_primero) + write (myunit) linez_minZabs_primero,liney_minYabs_primero,linex_minXabs_primero + write (myunit) dz_minZabs,dy_minYabs,dx_minXabs + WRITE (myunit) att(indi) + DO k1 = minzabs, maxzabs + DO j1 = minyabs, maxyabs + WRITE (myunit) (valor3d(i1, j1, k1, 1), i1=minxabs, maxxabs) + END DO + END DO + endif + endif + + END DO bucleindi + +#ifdef CompileWithHDF +#ifdef CompileWithMPI + IF (layoutnumber == output(ii)%item(1)%MPIRoot) THEN +#else + IF (layoutnumber == 0) THEN +#endif + + if (.not.(((fieldob == iMEC).or.(fieldob ==iMHC)).and.(pasadas ==2))) then ! no tiene sentido esccribir la fase del modulo + call closeh5file(finalstep,att) + CALL print11 (layoutnumber, trim(adjustl(whoami))//' Written into '//trim(adjustl(filename))//'.h5', .TRUE.) !enforces print + endif + endif +#endif + end do buclepasadas + ! +#ifdef CompileWithMPI + IF (layoutnumber == output(ii)%item(1)%MPIRoot) THEN +#else + IF (layoutnumber == 0) THEN +#endif + if (createh5bin) then + close(myunit) + CALL print11 (layoutnumber, trim(adjustl(whoami))//' Written into '//trim(adjustl(sgg%nEntradaRoot))//'.h5bin', .TRUE.) + endif + endif + + DEALLOCATE (valor3d) + if (SGG%Observation(ii)%FreqDomain) then + DEALLOCATE (valor3dCOMPLEX) + ENDIF +#ifdef CompileWithMPI + DEALLOCATE (newvalor3d) +#endif + DEALLOCATE (ATT) +!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! + CLOSE (output(ii)%item(1)%UNIT) + else !del lexis + buff='NOT PROCESSING: Ignoring: Inexistent or void file '//trim(adjustl(output(ii)%item(1)%path)) + CALL print11(layoutnumber, buff) + ENDIF !DEL LEXIS + somethingdone=.true. + ENDIF + ENDIF + ENDIF + END DO barridoprobes !barrido puntos de observacion + + RETURN + END SUBROUTINE createxdmf + + + SUBROUTINE createh5bintxt(sgg,layoutnumber,size) + type (SGGFDTDINFO), intent(IN) :: sgg + INTEGER (KIND=4), INTENT (IN) :: layoutnumber, size + logical :: lexis,algoescrito + INTEGER (KIND=4) :: ii,ierr + integer (KIND=4) :: myunit,myunit2 + CHARACTER (LEN=BUFSIZE) :: whoamishort + CHARACTER (LEN=BUFSIZE) :: pathroot + integer :: my_iostat +#ifdef CompileWithMPI + call MPI_Barrier(SUBCOMM_MPI,ierr) +#endif + if (layoutnumber == 0) then !solo el root + open(newunit=myunit,file=trim(adjustl(sgg%nEntradaRoot))//'_h5bin.txt',form='formatted') !lista de todos los .h5bin + write (myunit,'(a)') '!END' + close(myunit,status='delete') + my_iostat=0 +9138 if(my_iostat /= 0) write(*,fmt='(a)',advance='no'), '.' !!if(my_iostat /= 0) print '(i5,a1,i4,2x,a)',9138,'.',layoutnumber,trim(adjustl(sgg%nEntradaRoot))//'_h5bin.txt' + open(newunit=myunit,file=trim(adjustl(sgg%nEntradaRoot))//'_h5bin.txt',form='formatted',err=9138,iostat=my_iostat,status='new',action='write') !lista de todos los .h5bin + algoescrito=.false. + do ii=0,size-1 !auna todos los _h5bin.txt + WRITE (whoamishort, '(i5)') ii + 1 + INQUIRE (FILE=trim(adjustl(trim(adjustl(sgg%nEntradaRoot))//'_'//trim(adjustl(whoamishort))//'_h5bin.txt')), EXIST=lexis) + if (lexis) then + open(newunit=myunit2,file=trim(adjustl(sgg%nEntradaRoot))//'_'//trim(adjustl(whoamishort))//'_h5bin.txt',form='formatted') + do + read (myunit2, '(a)',end=9874) pathroot + write (myunit,'(a)') trim(adjustl(pathroot)) + algoescrito=.true. + end do +9874 close (myunit2,status='delete') + endif + end do + if (algoescrito) then + close(myunit) + else + close(myunit,status='delete') + endif + endif +#ifdef CompileWithMPI + call MPI_Barrier(SUBCOMM_MPI,ierr) +#endif + end SUBROUTINE createh5bintxt + + SUBROUTINE createxdmfOnTheFly (sgg,layoutnumber,size,vtkindex,createh5bin,somethingdone,mpidir) + integer (KIND=4) :: mpidir + logical :: vtkindex,createh5bin + !------------------------> + + type (SGGFDTDINFO), intent(IN) :: sgg + INTEGER (KIND=4), INTENT (IN) :: layoutnumber, size + TYPE (output_t), POINTER, DIMENSION (:) :: output + INTEGER (KIND=4) :: ii + logical :: lexis,somethingdone + character(len=BUFSIZE) :: buff + ! + output => GetOutput ()!get the output private info from observation + ! + + DO ii = 1, sgg%NumberRequest + !sondas Volumic traducelas a xdfm + IF (sgg%observation(ii)%Volumic) then + if (sgg%observation(ii)%nP == 1) then + if ((sgg%observation(ii)%P(1)%What /= nothing).AND.(sgg%observation(ii)%P(1)%What /= iCur).AND.(sgg%observation(ii)%P(1)%What /= iCurX).AND.(sgg%observation(ii)%P(1)%What /= iCurY).AND.(sgg%observation(ii)%P(1)%What /= iCurZ)) THEN + ! + INQUIRE (FILE=trim(adjustl(output(ii)%item(1)%path)), EXIST=lexis) + if (.not.lexis) then + buff='NOT PROCESSING: Inexistent file '//trim(adjustl(output(ii)%item(1)%path)) + CALL print11(layoutnumber, buff) + return + ELSE + close (output(ii)%item(1)%unit) + ENDIF !DEL LEXIS + ENDIF + ENDIF + ENDIF + + END DO !barrido puntos de observacion + call createxdmf (sgg,layoutnumber, size,vtkindex,createh5bin,somethingdone,mpidir) + DO ii = 1, sgg%NumberRequest + !sondas Volumic traducelas a xdfm + IF (sgg%observation(ii)%Volumic) then + if (sgg%observation(ii)%nP == 1) then + if ((sgg%observation(ii)%P(1)%What /= nothing).AND.(sgg%observation(ii)%P(1)%What /= iCur).AND.(sgg%observation(ii)%P(1)%What /= iCurX).AND.(sgg%observation(ii)%P(1)%What /= iCurY).AND.(sgg%observation(ii)%P(1)%What /= iCurZ)) THEN + ! + INQUIRE (FILE=trim(adjustl(output(ii)%item(1)%path)), EXIST=lexis) + if (.not.lexis) then + buff='NOT PROCESSING: Inexistent file '//trim(adjustl(output(ii)%item(1)%path)) + CALL print11(layoutnumber, buff) + return + ELSE + open (output(ii)%item(1)%unit,file=trim(adjustl(output(ii)%item(1)%path)),FORM='unformatted',position='append') + ENDIF !DEL LEXIS + ENDIF + ENDIF + ENDIF + + END DO !barrido puntos de observacion + + RETURN + END SUBROUTINE createxdmfOnTheFly +END MODULE xdmf +! +! diff --git a/src_main_pub/xdmf_h5.F90 b/src_main_pub/xdmf_h5.F90 new file mode 100644 index 00000000..445a429a --- /dev/null +++ b/src_main_pub/xdmf_h5.F90 @@ -0,0 +1,283 @@ +MODULE xdmf_h5 +#ifdef CompileWithHDF + + USE fdetypes + USE HDF5 + IMPLICIT NONE + + INTEGER (HID_T) :: file_id ! File identifier + INTEGER (HID_T) :: dset_id ! Dataset identifier + INTEGER (HID_T) :: dspace_id, slice2D_id ! Dataspace identifier + INTEGER (HSIZE_T), ALLOCATABLE, DIMENSION (:) :: DATA_dims ! Dataset dimensions + INTEGER (HSIZE_T), ALLOCATABLE, DIMENSION (:) :: offset + INTEGER (HSIZE_T), ALLOCATABLE, DIMENSION (:) :: valor3d_dims ! slice dimensions + + ! + PRIVATE + PUBLIC openh5file,writeh5file,closeh5file,createh5filefromsinglebin + +CONTAINS + +!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! + + subroutine openh5file(filename,finalstep,minXabs,maxXabs, minYabs,maxYabs, minZabs,maxZabs) + + INTEGER :: error ! Error flag + CHARACTER (LEN=BUFSIZE) :: filename ! File name + CHARACTER (LEN=BUFSIZE) :: dsetname ! Dataset name + ! + INTEGER (KIND=4) :: minXabs, maxXabs, minYabs, maxYabs, minZabs, maxZabs,finalstep + + INTEGER :: rank ! Dataset rank + ! + rank = 4 + ALLOCATE(DATA_dims(1:RANK),valor3d_dims(1:RANK),offset(1:RANK)) + ! + DATA_dims (1) = maxXabs - minXabs + 1 + DATA_dims (2) = maxYabs - minYabs + 1 + DATA_dims (3) = maxZabs - minZabs + 1 + DATA_dims (4) = finalstep + ! + valor3d_dims (1) = DATA_dims (1) + valor3d_dims (2) = DATA_dims (2) + valor3d_dims (3) = DATA_dims (3) + valor3d_dims (4) = 1 + + dsetname = 'data' + CALL h5open_f (error) + CALL h5fcreate_f (trim(adjustl(filename))//'.h5', H5F_ACC_TRUNC_F, file_id, error) + CALL h5screate_simple_f (rank, DATA_dims, dspace_id, error) + CALL h5screate_simple_f (rank, valor3d_dims, slice2D_id, error) +#ifdef CompileWithReal8 + CALL h5dcreate_f (file_id, trim(adjustl(dsetname)), H5T_NATIVE_DOUBLE, dspace_id, dset_id, error) +#else + CALL h5dcreate_f (file_id, trim(adjustl(dsetname)), H5T_NATIVE_REAL , dspace_id, dset_id, error) +#endif + +!xdmf part + OPEN (18, FILE=trim(adjustl(filename))//'.xdmf', FORM='formatted') + WRITE (18,*) '' + WRITE (18,*) '' + WRITE (18,*) '' + + + end subroutine openh5file + + subroutine writeh5file(filename,valor3d,indi,attindi,minXabs,maxXabs, minYabs,maxYabs, minZabs,maxZabs, & + linez_minZabs_primero,liney_minYabs_primero,linex_minXabs_primero, & + dz_minZabs,dy_minYabs,dx_minXabs,& + minZabs_primero,minYabs_primero,minXabs_primero,finalstep,vtkindex) + real ( KINd=RKIND_tiempo) :: attindi + CHARACTER (LEN=BUFSIZE) :: filename + logical :: vtkindex + ! + CHARACTER (LEN=BUFSIZE) :: dsetname ! Dataset name + INTEGER (KIND=4) :: indi + REAL (KIND=RKIND), DIMENSION (:, :, :, :) :: valor3d + INTEGER :: error ! Error flag + CHARACTER (LEN=BUFSIZE) :: charc + INTEGER (KIND=4) :: minXabs, maxXabs, minYabs, maxYabs, minZabs, maxZabs, & + minZabs_primero,minYabs_primero,minXabs_primero,finalstep + REAL (KIND=RKIND) :: linez_minZabs_primero,liney_minYabs_primero,linex_minXabs_primero, & + dz_minZabs,dy_minYabs,dx_minXabs + + + offset (1) = 0 + offset (2) = 0 + offset (3) = 0 + offset (4) = indi - 1 + ! + CALL h5sselect_hyperslab_f (dspace_id, H5S_SELECT_SET_F, offset, valor3d_dims, error) +#ifdef CompileWithReal8 + CALL h5dwrite_f (dset_id, H5T_NATIVE_DOUBLE, valor3d, valor3d_dims, error, slice2D_id, & + & dspace_id) +#elif CompileWithReal16 + !miguel-2018: compila pero no testeado + CALL h5dwrite_f (dset_id, H5T_NATIVE_LDOUBLE, valor3d, valor3d_dims, error, slice2D_id, & + & dspace_id) +#else + CALL h5dwrite_f (dset_id, H5T_NATIVE_REAL, valor3d, valor3d_dims, error, slice2D_id, & + & dspace_id) +#endif + + !el .xdmf como usualmente + !HDF5 transposes matrices + WRITE (charc,'(e19.9e3)') attindi !'(i9)') indi ! + dsetname = 'data' + DATA_dims(1) = maxXabs - minXabs + 1 + DATA_dims(2) = maxYabs - minYabs + 1 + DATA_dims(3) = maxZabs - minZabs + 1 + WRITE (18, '(a)') '>' + WRITE (18, '(a)') '' + + + end subroutine writeh5file + + + subroutine closeh5file(finalstep,att) + ! + INTEGER :: rank ! Dataset rank + real ( KINd=RKIND_tiempo), DIMENSION (:) :: att + INTEGER :: error ! Error flag + INTEGER (KIND=4) :: finalstep + CHARACTER (LEN=BUFSIZE) :: dsetname ! Dataset name + + + DEALLOCATE(DATA_dims,valor3d_dims,offset) + + !timedata + CALL h5dclose_f (dset_id, error) + + dsetname='Time' + rank = 1 + ALLOCATE(DATA_dims(rank)) + data_dims(1) = finalstep + + CALL h5screate_simple_f (rank, DATA_dims, dspace_id, error) +#ifdef CompileWithReal8 + CALL h5dcreate_f (file_id, trim(adjustl(dsetname)), H5T_NATIVE_DOUBLE, dspace_id, dset_id, error) + CALL h5dwrite_f (dset_id, H5T_NATIVE_DOUBLE, att, DATA_dims, error) +#elif CompileWithReal16 + !miguel-2018: compila pero no testeado + CALL h5dcreate_f (file_id, trim(adjustl(dsetname)), H5T_NATIVE_LDOUBLE, dspace_id, dset_id, error) + CALL h5dwrite_f (dset_id, H5T_NATIVE_REAL, att, DATA_dims, error) +#else + CALL h5dcreate_f (file_id, trim(adjustl(dsetname)), H5T_NATIVE_REAL, dspace_id, dset_id, error) + CALL h5dwrite_f (dset_id, H5T_NATIVE_REAL, att, DATA_dims, error) +#endif + cALL h5dclose_f (dset_id, error) + + CALL h5sclose_f (slice2D_id, error) + CALL h5sclose_f (dspace_id, error) + + + + CALL h5fclose_f (file_id, error) + CALL h5close_f (error) + ! + ! + WRITE (18, '(a)') '' + WRITE (18, '(a)') '' + WRITE (18, '(a)') '' + CLOSE (18) + ! + DEALLOCATE(DATA_dims) + + + end subroutine closeh5file + + subroutine createh5filefromsinglebin(filename,vtkindex) + integer (KIND=4) :: myunit,fieldob,pasadas,pasadastotales + CHARACTER (LEN=BUFSIZE) :: filename,fichin ! File name + real ( KINd=RKIND_tiempo), ALLOCATABLE, DIMENSION (:) :: att + REAL (KIND=RKIND), ALLOCATABLE, DIMENSION (:, :, :, :) :: valor3d !para sondas Volumic + logical :: vtkindex,SGGObservationiiTimeDomain + INTEGER (KIND=4) :: minXabs, maxXabs, minYabs, maxYabs, minZabs, maxZabs, & + minZabs_primero,minYabs_primero,minXabs_primero,finalstep,indi,i1,j1,k1 + REAL (KIND=RKIND) :: linez_minZabs_primero,liney_minYabs_primero,linex_minXabs_primero, & + dz_minZabs,dy_minYabs,dx_minXabs + character (LEN=BUFSIZE) :: dubuf + + filename=filename(1:index(filename,'.h5bin')-1); filename=trim(adjustl(filename)) + + open(newunit=myunit,file=trim(adjustl(filename))//'.h5bin',form='unformatted') + read (myunit) finalstep,minXabs, maxXabs, minYabs, maxYabs, minZabs, maxZabs,fieldob, & + SGGObservationiiTimeDomain,pasadastotales + + ALLOCATE (valor3d(minXabs:maxXabs, minYabs:maxYabs, minZabs:maxZabs, 1)) + allocate (att(1:finalstep)) + + buclepasadas: do pasadas=1,pasadastotales + if (SGGObservationiiTimeDomain) then + if (pasadas==1) then + fichin = trim (adjustl(filename))//'_time' + else + print *,'Buggy error in valor3d. ' + stop + endif + else + if (pasadas==1) then + fichin = trim (adjustl(filename))//'_mod' + elseif (pasadas==2) then + fichin = trim (adjustl(filename))//'_phase' + else + print *,'Buggy error in valor3d. ' + stop + endif + endif + + + if (.not.(((fieldob == iMEC).or.(fieldob ==iMHC)).and.(pasadas ==2))) then ! no tiene sentido esccribir la fase + call openh5file(fichin,finalstep,minXabs,maxXabs, minYabs,maxYabs, minZabs,maxZabs) + endif + + valor3d = 0.0_RKIND + att=0.0_RKIND + DO indi = 1, finalstep + read(myunit) minZabs_primero,minYabs_primero,minXabs_primero + read(myunit) linez_minZabs_primero,liney_minYabs_primero,linex_minXabs_primero + read(myunit) dz_minZabs,dy_minYabs,dx_minXabs + read (myunit) att(indi) + write(dubuf,*) ' ----> .xdmf file ',att(indi),'(',indi,'/',finalstep,')' + print *,trim(adjustl(dubuf)) + DO k1 = minzabs, maxzabs + DO j1 = minyabs, maxyabs + read (myunit) (valor3d(i1, j1, k1, 1), i1=minxabs, maxxabs) + END DO + END DO + + if (.not.(((fieldob == iMEC).or.(fieldob ==iMHC)).and.(pasadas ==2))) then ! no tiene sentido esccribir la fase + call writeh5file(fichin,valor3d,indi,att(indi),minXabs,maxXabs, minYabs,maxYabs, minZabs,maxZabs, & + linez_minZabs_primero,liney_minYabs_primero,linex_minXabs_primero, & + dz_minZabs,dy_minYabs,dx_minXabs,& + minZabs_primero,minYabs_primero,minXabs_primero,finalstep,vtkindex) + endif + end do + + if (.not.(((fieldob == iMEC).or.(fieldob ==iMHC)).and.(pasadas ==2))) then ! no tiene sentido esccribir la fase + call closeh5file(finalstep,att) + endif + end do buclepasadas + + close(myunit) + + DEALLOCATE (valor3d) + DEALLOCATE (ATT) + + + end subroutine createh5filefromsinglebin + + +#endif + +END MODULE xdmf_h5 \ No newline at end of file diff --git a/src_pyWrapper/pyWrapper.py b/src_pyWrapper/pyWrapper.py index b54566de..8fd1f75c 100644 --- a/src_pyWrapper/pyWrapper.py +++ b/src_pyWrapper/pyWrapper.py @@ -13,17 +13,11 @@ class Probe(): def __init__(self, probe_filename): self.filename = probe_filename - - # with open(probe_filename, 'r') as file: - # data = file.read() - # data = data.replace('/', '-') - # with open(probe_filename, 'w') as file: - # file.write(data) mtln_probe_tags = ['_V_','_I_'] current_probe_tags = ['_Wx_', '_Wy_', '_Wz_'] far_field_tag = ['_FF_'] - movie_tags = ['_ExC_', '_EyC_', '_EzC_', '_HxC_', '_HyC_', '_HzC_'] + movie_tags = ['_ExC_', '_EyC_', '_EzC_', '_HxC_', '_HyC_', '_HzC_', '_ME_', '_MH_'] all_tags = current_probe_tags + far_field_tag + movie_tags + mtln_probe_tags @@ -48,14 +42,14 @@ def __init__(self, probe_filename): elif tag in far_field_tag: self.type = 'farField' self.name, positions_str = basename_with_no_case_name.split(tag) - init_str, end_str = pos = positions_str.split('__') + init_str, end_str = positions_str.split('__') self.cell_init = positionStrToCell(init_str) self.cell_end = positionStrToCell(end_str) self.df = pd.read_csv(self.filename, sep='\s+') elif tag in movie_tags: self.type = 'movie' self.name, positions_str = basename_with_no_case_name.split(tag) - init_str, end_str = pos = positions_str.split('__') + init_str, end_str = positions_str.split('__') self.cell_init = positionStrToCell(init_str) self.cell_end = positionStrToCell(end_str) elif tag in mtln_probe_tags: @@ -101,7 +95,7 @@ def getSolvedProbeFilenames(self, probe_name): if not "probes" in input_json: raise ValueError('Solver does not contain probes.') - file_extensions = ('*.dat', '*.bin') + file_extensions = ('*.dat', '*.xdmf', '*.bin', '*.h5') probeFiles = [] for ext in file_extensions: newProbes = [x for x in glob.glob(ext) if re.match(self.case + '_' + probe_name, x)] diff --git a/src_wires_pub/wires.F90 b/src_wires_pub/wires.F90 index bbd48c93..aa41b5d6 100755 --- a/src_wires_pub/wires.F90 +++ b/src_wires_pub/wires.F90 @@ -28,7 +28,6 @@ module HollandWires ! -#ifdef CompileWithWires use report use fdetypes @@ -7031,7 +7030,5 @@ subroutine wiresconstantes(fieldtotl,dummy,G2,sgg) end subroutine wiresconstantes -#endif - !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! end module HollandWires diff --git a/test/pyWrapper/test_full_system.py b/test/pyWrapper/test_full_system.py index ebeef72d..d51acdc9 100644 --- a/test/pyWrapper/test_full_system.py +++ b/test/pyWrapper/test_full_system.py @@ -91,27 +91,33 @@ def test_towelHanger(tmp_path): for i in range(3): p_solved = Probe(probe_files[i]) assert np.allclose(p_expected[i].df.to_numpy()[:,0:3], p_solved.df.to_numpy()[:,0:3], rtol = 5e-2, atol=5e-2) - - def test_sphere(tmp_path): case = 'sphere' input_json = getCase(case) - input_json['general']['numberOfSteps'] = 200 - input_json['probes'][0]['domain']['numberOfFrequencies'] = 100 + input_json['general']['numberOfSteps'] = 20 + input_json['probes'][0]['domain']['initialFrequency'] = 1e8 + input_json['probes'][0]['domain']['finalFrequency'] = 1e9 fn = tmp_path._str + '/' + case + '.fdtd.json' - with open(fn, 'w') as modified_json: - json.dump(input_json, modified_json) + with open(fn, 'w') as modified_json_file: + json.dump(input_json, modified_json_file) makeCopy(tmp_path, EXCITATIONS_FOLDER+'gauss.exc') solver = FDTD(input_filename = fn, path_to_exe=SEMBA_EXE) solver.run() - probe_files = solver.getSolvedProbeFilenames("Far") # semba-fdtd seems to always use the name Far for "far field" probes. + assert solver.hasFinishedSuccessfully() + far_field_probe_files = solver.getSolvedProbeFilenames("Far") # semba-fdtd seems to always use the name Far for "far field" probes. assert solver.hasFinishedSuccessfully() == True - assert len(probe_files) == 1 - - p = Probe(probe_files[0]) - assert p.type == 'farField' \ No newline at end of file + assert len(far_field_probe_files) == 1 + p = Probe(far_field_probe_files[0]) + assert p.type == 'farField' + + electric_field_movie_files = solver.getSolvedProbeFilenames("electric_field_movie") + assert solver.hasFinishedSuccessfully() == True + assert len(electric_field_movie_files) == 3 + p = Probe(electric_field_movie_files[0]) + assert p.type == 'movie' + \ No newline at end of file diff --git a/test/pyWrapper/utils.py b/test/pyWrapper/utils.py index dc0f93b3..f40f920f 100644 --- a/test/pyWrapper/utils.py +++ b/test/pyWrapper/utils.py @@ -30,7 +30,14 @@ def copyInputFiles(temp_dir, input, excitation, executable): makeCopy(temp_dir, executable) def getProbeFile(prefix, probe_name): - return ([x for x in glob.glob('*dat') if re.match(prefix + '_' + probe_name + '.*dat',x)])[0] + extensions = ["dat", "xdmf", "h5", "bin"] + + probeFiles = [] + for ext in extensions: + newFiles = ([x for x in glob.glob('*'+ext) if re.match(prefix + '_' + probe_name + '.*'+ext, x)])[0] + probeFiles.append(newFiles) + + return probeFiles def countLinesInFile(probe_fn): with open(probe_fn, 'r') as f: diff --git a/test/smbjson/CMakeLists.txt b/test/smbjson/CMakeLists.txt index 13313e45..8b045393 100644 --- a/test/smbjson/CMakeLists.txt +++ b/test/smbjson/CMakeLists.txt @@ -17,6 +17,7 @@ add_library (smbjson_test_fortran "test_read_mtln.F90" "test_read_sphere.F90" "test_read_airplane.F90" + "test_read_large_airplane_mtln.F90" ) target_link_libraries(smbjson_test_fortran smbjson diff --git a/test/smbjson/smbjson_tests.h b/test/smbjson/smbjson_tests.h index a239ba79..ae1ad59a 100644 --- a/test/smbjson/smbjson_tests.h +++ b/test/smbjson/smbjson_tests.h @@ -21,24 +21,26 @@ extern "C" int test_read_shieldedpair(); extern "C" int test_read_mtln(); extern "C" int test_read_sphere(); extern "C" int test_read_airplane(); +extern "C" int test_read_large_airplane_mtln(); TEST(smbjson, idchildtable_fhash) {EXPECT_EQ(0, test_idchildtable_fhash()); } TEST(smbjson, idchildtable_add_get) {EXPECT_EQ(0, test_idchildtable()); } -TEST(smbjson, mesh_cells) { EXPECT_EQ(0, test_cells()); } -TEST(smbjson, mesh_add_get) { EXPECT_EQ(0, test_mesh_add_get()); } -TEST(smbjson, mesh_add_get_long_list) { EXPECT_EQ(0, test_mesh_add_get_long_list()); } -TEST(smbjson, mesh_node_to_pixel) { EXPECT_EQ(0, test_mesh_node_to_pixel()); } -TEST(smbjson, mesh_polyline_to_linel) { EXPECT_EQ(0, test_mesh_polyline_to_linel()); } - -TEST(smbjson, parser_ctor) { EXPECT_EQ(0, test_parser_ctor()); } -TEST(smbjson, parser_read_mesh) { EXPECT_EQ(0, test_parser_read_mesh()); } -TEST(smbjson, read_planewave) { EXPECT_EQ(0, test_read_planewave()); } -TEST(smbjson, read_holland1981) { EXPECT_EQ(0, test_read_holland1981()); } -TEST(smbjson, read_towelhanger) { EXPECT_EQ(0, test_read_towelhanger()); } -TEST(smbjson, read_connectedwires) { EXPECT_EQ(0, test_read_connectedwires()); } -TEST(smbjson, read_currentinjection) { EXPECT_EQ(0, test_read_currentinjection()); } -// TEST(smbjson, read_shieldedpair) { EXPECT_EQ(0, test_read_shieldedpair()); } -TEST(smbjson, read_mtln) { EXPECT_EQ(0, test_read_mtln()); } -TEST(smbjson, read_sphere) { EXPECT_EQ(0, test_read_sphere()); } -TEST(smbjson, read_airplane) { EXPECT_EQ(0, test_read_airplane()); } \ No newline at end of file +TEST(smbjson, mesh_cells) { EXPECT_EQ(0, test_cells()); } +TEST(smbjson, mesh_add_get) { EXPECT_EQ(0, test_mesh_add_get()); } +TEST(smbjson, mesh_add_get_long_list) { EXPECT_EQ(0, test_mesh_add_get_long_list()); } +TEST(smbjson, mesh_node_to_pixel) { EXPECT_EQ(0, test_mesh_node_to_pixel()); } +TEST(smbjson, mesh_polyline_to_linel) { EXPECT_EQ(0, test_mesh_polyline_to_linel()); } + +TEST(smbjson, parser_ctor) { EXPECT_EQ(0, test_parser_ctor()); } +TEST(smbjson, parser_read_mesh) { EXPECT_EQ(0, test_parser_read_mesh()); } +TEST(smbjson, read_planewave) { EXPECT_EQ(0, test_read_planewave()); } +TEST(smbjson, read_holland1981) { EXPECT_EQ(0, test_read_holland1981()); } +TEST(smbjson, read_towelhanger) { EXPECT_EQ(0, test_read_towelhanger()); } +TEST(smbjson, read_connectedwires) { EXPECT_EQ(0, test_read_connectedwires()); } +TEST(smbjson, read_currentinjection) { EXPECT_EQ(0, test_read_currentinjection()); } +// TEST(smbjson, read_shieldedpair) { EXPECT_EQ(0, test_read_shieldedpair()); } +TEST(smbjson, read_mtln) { EXPECT_EQ(0, test_read_mtln()); } +TEST(smbjson, read_sphere) { EXPECT_EQ(0, test_read_sphere()); } +TEST(smbjson, read_airplane) { EXPECT_EQ(0, test_read_airplane()); } +TEST(smbjson, read_large_airplane_mtln) { EXPECT_EQ(0, test_read_large_airplane_mtln()); } \ No newline at end of file diff --git a/test/smbjson/test_idchildtable.F90 b/test/smbjson/test_idchildtable.F90 index c2f20702..9e1f2008 100644 --- a/test/smbjson/test_idchildtable.F90 +++ b/test/smbjson/test_idchildtable.F90 @@ -22,6 +22,7 @@ integer function test_idchildtable_fhash() bind(C) result(error_cnt) integer function test_idchildtable() bind(C) result(err) use idchildtable_mod + use smbjson_labels_mod use parser_tools_mod, only: json_value_ptr use smbjson_testingTools use json_module diff --git a/test/smbjson/test_parser.F90 b/test/smbjson/test_parser.F90 index 146dc85c..1f95a1b1 100644 --- a/test/smbjson/test_parser.F90 +++ b/test/smbjson/test_parser.F90 @@ -82,8 +82,8 @@ integer function test_parser_read_mesh() bind(C) result(err) err = 0 parser = parser_t(filename) - call parser%initializeJson() mesh = parser%readMesh() + call mesh%printCoordHashInfo() expected%position = [10,2,1] diff --git a/test/smbjson/test_read_large_airplane_mtln.F90 b/test/smbjson/test_read_large_airplane_mtln.F90 new file mode 100644 index 00000000..2f53343a --- /dev/null +++ b/test/smbjson/test_read_large_airplane_mtln.F90 @@ -0,0 +1,18 @@ +integer function test_read_large_airplane_mtln() bind (C) result(err) + use smbjson + use smbjson_testingTools + + character(len=*),parameter :: filename = PATH_TO_TEST_DATA//'cases/large_airplane_mtln.fdtd.json' + type(Parseador) :: pr + type(parser_t) :: parser + + err = 0 + + parser = parser_t(filename) + + pr = parser%readProblemDescription() + +contains + +end function + diff --git a/testData/cases/large_airplane_mtln.fdtd.json b/testData/cases/large_airplane_mtln.fdtd.json new file mode 100644 index 00000000..976f841d --- /dev/null +++ b/testData/cases/large_airplane_mtln.fdtd.json @@ -0,0 +1,47210 @@ +{ + "_format": "FDTD Input file", + "general": { + "timeStep": 2.311e-10, + "numberOfSteps": 86 + }, + "boundary": { + "all": { + "type": "pml", + "layers": 10, + "order": 2, + "reflection": 0.001 + } + }, + "mesh": { + "grid": { + "numberOfCells": [ + 200, + 80, + 80 + ], + "steps": { + "x": [ + 0.08 + ], + "y": [ + 0.075 + ], + "z": [ + 0.225 + ] + } + }, + "coordinates": [ + { + "id": 1, + "relativePosition": [ + 40.0, + 29.0, + 41.0 + ] + }, + { + "id": 2, + "relativePosition": [ + 71.0, + 17.0, + 46.0 + ] + }, + { + "id": 3, + "relativePosition": [ + 81.0, + 17.0, + 40.0 + ] + }, + { + "id": 4, + "relativePosition": [ + 75.0, + 37.0, + 42.0 + ] + }, + { + "id": 5, + "relativePosition": [ + 21.0, + 20.0, + 42.0 + ] + }, + { + "id": 6, + "relativePosition": [ + 72.0, + 17.0, + 43.0 + ] + }, + { + "id": 7, + "relativePosition": [ + 72.0, + 17.0, + 42.0 + ] + }, + { + "id": 8, + "relativePosition": [ + 75.0, + 17.0, + 42.0 + ] + }, + { + "id": 9, + "relativePosition": [ + 75.0, + 17.0, + 41.0 + ] + }, + { + "id": 10, + "relativePosition": [ + 77.0, + 17.0, + 41.0 + ] + }, + { + "id": 11, + "relativePosition": [ + 77.0, + 17.0, + 40.0 + ] + }, + { + "id": 12, + "relativePosition": [ + 72.0, + 17.0, + 43.0 + ] + }, + { + "id": 13, + "relativePosition": [ + 72.0, + 16.0, + 43.0 + ] + }, + { + "id": 14, + "relativePosition": [ + 72.0, + 16.0, + 44.0 + ] + }, + { + "id": 15, + "relativePosition": [ + 71.0, + 16.0, + 44.0 + ] + }, + { + "id": 16, + "relativePosition": [ + 71.0, + 17.0, + 44.0 + ] + }, + { + "id": 17, + "relativePosition": [ + 71.0, + 17.0, + 45.0 + ] + }, + { + "id": 18, + "relativePosition": [ + 71.0, + 18.0, + 45.0 + ] + }, + { + "id": 19, + "relativePosition": [ + 71.0, + 17.0, + 45.0 + ] + }, + { + "id": 20, + "relativePosition": [ + 52.0, + 20.0, + 43.0 + ] + }, + { + "id": 21, + "relativePosition": [ + 55.0, + 20.0, + 43.0 + ] + }, + { + "id": 22, + "relativePosition": [ + 21.0, + 21.0, + 42.0 + ] + }, + { + "id": 23, + "relativePosition": [ + 22.0, + 21.0, + 42.0 + ] + }, + { + "id": 24, + "relativePosition": [ + 22.0, + 21.0, + 41.0 + ] + }, + { + "id": 25, + "relativePosition": [ + 33.0, + 21.0, + 41.0 + ] + }, + { + "id": 26, + "relativePosition": [ + 33.0, + 20.0, + 41.0 + ] + }, + { + "id": 27, + "relativePosition": [ + 34.0, + 20.0, + 41.0 + ] + }, + { + "id": 28, + "relativePosition": [ + 34.0, + 20.0, + 42.0 + ] + }, + { + "id": 29, + "relativePosition": [ + 38.0, + 20.0, + 42.0 + ] + }, + { + "id": 30, + "relativePosition": [ + 38.0, + 20.0, + 43.0 + ] + }, + { + "id": 31, + "relativePosition": [ + 40.0, + 20.0, + 43.0 + ] + }, + { + "id": 32, + "relativePosition": [ + 40.0, + 20.0, + 43.0 + ] + }, + { + "id": 33, + "relativePosition": [ + 39.0, + 20.0, + 43.0 + ] + }, + { + "id": 34, + "relativePosition": [ + 39.0, + 23.0, + 43.0 + ] + }, + { + "id": 35, + "relativePosition": [ + 38.0, + 23.0, + 43.0 + ] + }, + { + "id": 36, + "relativePosition": [ + 38.0, + 24.0, + 43.0 + ] + }, + { + "id": 37, + "relativePosition": [ + 37.0, + 24.0, + 43.0 + ] + }, + { + "id": 38, + "relativePosition": [ + 37.0, + 27.0, + 43.0 + ] + }, + { + "id": 39, + "relativePosition": [ + 37.0, + 27.0, + 43.0 + ] + }, + { + "id": 40, + "relativePosition": [ + 37.0, + 27.0, + 42.0 + ] + }, + { + "id": 41, + "relativePosition": [ + 37.0, + 28.0, + 42.0 + ] + }, + { + "id": 42, + "relativePosition": [ + 37.0, + 28.0, + 41.0 + ] + }, + { + "id": 43, + "relativePosition": [ + 38.0, + 28.0, + 41.0 + ] + }, + { + "id": 44, + "relativePosition": [ + 38.0, + 29.0, + 41.0 + ] + }, + { + "id": 45, + "relativePosition": [ + 40.0, + 20.0, + 43.0 + ] + }, + { + "id": 46, + "relativePosition": [ + 40.0, + 18.0, + 43.0 + ] + }, + { + "id": 47, + "relativePosition": [ + 52.0, + 18.0, + 43.0 + ] + }, + { + "id": 48, + "relativePosition": [ + 52.0, + 20.0, + 43.0 + ] + }, + { + "id": 49, + "relativePosition": [ + 55.0, + 20.0, + 43.0 + ] + }, + { + "id": 50, + "relativePosition": [ + 55.0, + 35.0, + 43.0 + ] + }, + { + "id": 51, + "relativePosition": [ + 56.0, + 35.0, + 43.0 + ] + }, + { + "id": 52, + "relativePosition": [ + 56.0, + 35.0, + 42.0 + ] + }, + { + "id": 53, + "relativePosition": [ + 57.0, + 35.0, + 42.0 + ] + }, + { + "id": 54, + "relativePosition": [ + 57.0, + 37.0, + 42.0 + ] + }, + { + "id": 55, + "relativePosition": [ + 58.0, + 37.0, + 42.0 + ] + }, + { + "id": 56, + "relativePosition": [ + 58.0, + 38.0, + 42.0 + ] + }, + { + "id": 57, + "relativePosition": [ + 59.0, + 38.0, + 42.0 + ] + }, + { + "id": 58, + "relativePosition": [ + 59.0, + 38.0, + 42.0 + ] + }, + { + "id": 59, + "relativePosition": [ + 59.0, + 38.0, + 41.0 + ] + }, + { + "id": 60, + "relativePosition": [ + 63.0, + 38.0, + 41.0 + ] + }, + { + "id": 61, + "relativePosition": [ + 63.0, + 37.0, + 41.0 + ] + }, + { + "id": 62, + "relativePosition": [ + 66.0, + 37.0, + 41.0 + ] + }, + { + "id": 63, + "relativePosition": [ + 66.0, + 37.0, + 42.0 + ] + }, + { + "id": 64, + "relativePosition": [ + 55.0, + 20.0, + 43.0 + ] + }, + { + "id": 65, + "relativePosition": [ + 68.0, + 20.0, + 43.0 + ] + }, + { + "id": 66, + "relativePosition": [ + 68.0, + 19.0, + 43.0 + ] + }, + { + "id": 67, + "relativePosition": [ + 70.0, + 19.0, + 43.0 + ] + }, + { + "id": 68, + "relativePosition": [ + 70.0, + 19.0, + 43.0 + ] + }, + { + "id": 69, + "relativePosition": [ + 71.0, + 19.0, + 43.0 + ] + }, + { + "id": 70, + "relativePosition": [ + 71.0, + 18.0, + 43.0 + ] + }, + { + "id": 71, + "relativePosition": [ + 72.0, + 18.0, + 43.0 + ] + }, + { + "id": 72, + "relativePosition": [ + 72.0, + 17.0, + 43.0 + ] + }, + { + "id": 73, + "relativePosition": [ + 70.0, + 19.0, + 43.0 + ] + }, + { + "id": 74, + "relativePosition": [ + 71.0, + 19.0, + 43.0 + ] + }, + { + "id": 75, + "relativePosition": [ + 71.0, + 18.0, + 43.0 + ] + }, + { + "id": 76, + "relativePosition": [ + 72.0, + 18.0, + 43.0 + ] + }, + { + "id": 77, + "relativePosition": [ + 72.0, + 17.0, + 43.0 + ] + }, + { + "id": 78, + "relativePosition": [ + 70.0, + 19.0, + 43.0 + ] + }, + { + "id": 79, + "relativePosition": [ + 71.0, + 19.0, + 43.0 + ] + }, + { + "id": 80, + "relativePosition": [ + 71.0, + 18.0, + 43.0 + ] + }, + { + "id": 81, + "relativePosition": [ + 72.0, + 18.0, + 43.0 + ] + }, + { + "id": 82, + "relativePosition": [ + 72.0, + 17.0, + 43.0 + ] + }, + { + "id": 83, + "relativePosition": [ + 55.0, + 20.0, + 43.0 + ] + }, + { + "id": 84, + "relativePosition": [ + 68.0, + 20.0, + 43.0 + ] + }, + { + "id": 85, + "relativePosition": [ + 68.0, + 19.0, + 43.0 + ] + }, + { + "id": 86, + "relativePosition": [ + 70.0, + 19.0, + 43.0 + ] + }, + { + "id": 87, + "relativePosition": [ + 55.0, + 20.0, + 43.0 + ] + }, + { + "id": 88, + "relativePosition": [ + 68.0, + 20.0, + 43.0 + ] + }, + { + "id": 89, + "relativePosition": [ + 68.0, + 19.0, + 43.0 + ] + }, + { + "id": 90, + "relativePosition": [ + 70.0, + 19.0, + 43.0 + ] + }, + { + "id": 91, + "relativePosition": [ + 59.0, + 38.0, + 42.0 + ] + }, + { + "id": 92, + "relativePosition": [ + 59.0, + 38.0, + 41.0 + ] + }, + { + "id": 93, + "relativePosition": [ + 63.0, + 38.0, + 41.0 + ] + }, + { + "id": 94, + "relativePosition": [ + 63.0, + 37.0, + 41.0 + ] + }, + { + "id": 95, + "relativePosition": [ + 66.0, + 37.0, + 41.0 + ] + }, + { + "id": 96, + "relativePosition": [ + 66.0, + 37.0, + 42.0 + ] + }, + { + "id": 97, + "relativePosition": [ + 75.0, + 37.0, + 42.0 + ] + }, + { + "id": 98, + "relativePosition": [ + 59.0, + 38.0, + 42.0 + ] + }, + { + "id": 99, + "relativePosition": [ + 59.0, + 38.0, + 41.0 + ] + }, + { + "id": 100, + "relativePosition": [ + 63.0, + 38.0, + 41.0 + ] + }, + { + "id": 101, + "relativePosition": [ + 63.0, + 37.0, + 41.0 + ] + }, + { + "id": 102, + "relativePosition": [ + 66.0, + 37.0, + 41.0 + ] + }, + { + "id": 103, + "relativePosition": [ + 66.0, + 37.0, + 42.0 + ] + }, + { + "id": 104, + "relativePosition": [ + 75.0, + 37.0, + 42.0 + ] + }, + { + "id": 105, + "relativePosition": [ + 55.0, + 20.0, + 43.0 + ] + }, + { + "id": 106, + "relativePosition": [ + 55.0, + 35.0, + 43.0 + ] + }, + { + "id": 107, + "relativePosition": [ + 56.0, + 35.0, + 43.0 + ] + }, + { + "id": 108, + "relativePosition": [ + 56.0, + 35.0, + 42.0 + ] + }, + { + "id": 109, + "relativePosition": [ + 57.0, + 35.0, + 42.0 + ] + }, + { + "id": 110, + "relativePosition": [ + 57.0, + 37.0, + 42.0 + ] + }, + { + "id": 111, + "relativePosition": [ + 58.0, + 37.0, + 42.0 + ] + }, + { + "id": 112, + "relativePosition": [ + 58.0, + 38.0, + 42.0 + ] + }, + { + "id": 113, + "relativePosition": [ + 59.0, + 38.0, + 42.0 + ] + }, + { + "id": 114, + "relativePosition": [ + 55.0, + 20.0, + 43.0 + ] + }, + { + "id": 115, + "relativePosition": [ + 55.0, + 35.0, + 43.0 + ] + }, + { + "id": 116, + "relativePosition": [ + 56.0, + 35.0, + 43.0 + ] + }, + { + "id": 117, + "relativePosition": [ + 56.0, + 35.0, + 42.0 + ] + }, + { + "id": 118, + "relativePosition": [ + 57.0, + 35.0, + 42.0 + ] + }, + { + "id": 119, + "relativePosition": [ + 57.0, + 37.0, + 42.0 + ] + }, + { + "id": 120, + "relativePosition": [ + 58.0, + 37.0, + 42.0 + ] + }, + { + "id": 121, + "relativePosition": [ + 58.0, + 38.0, + 42.0 + ] + }, + { + "id": 122, + "relativePosition": [ + 59.0, + 38.0, + 42.0 + ] + }, + { + "id": 123, + "relativePosition": [ + 40.0, + 20.0, + 43.0 + ] + }, + { + "id": 124, + "relativePosition": [ + 40.0, + 18.0, + 43.0 + ] + }, + { + "id": 125, + "relativePosition": [ + 52.0, + 18.0, + 43.0 + ] + }, + { + "id": 126, + "relativePosition": [ + 52.0, + 20.0, + 43.0 + ] + }, + { + "id": 127, + "relativePosition": [ + 40.0, + 20.0, + 43.0 + ] + }, + { + "id": 128, + "relativePosition": [ + 40.0, + 18.0, + 43.0 + ] + }, + { + "id": 129, + "relativePosition": [ + 52.0, + 18.0, + 43.0 + ] + }, + { + "id": 130, + "relativePosition": [ + 52.0, + 20.0, + 43.0 + ] + }, + { + "id": 131, + "relativePosition": [ + 37.0, + 27.0, + 43.0 + ] + }, + { + "id": 132, + "relativePosition": [ + 37.0, + 27.0, + 42.0 + ] + }, + { + "id": 133, + "relativePosition": [ + 37.0, + 28.0, + 42.0 + ] + }, + { + "id": 134, + "relativePosition": [ + 37.0, + 28.0, + 41.0 + ] + }, + { + "id": 135, + "relativePosition": [ + 38.0, + 28.0, + 41.0 + ] + }, + { + "id": 136, + "relativePosition": [ + 38.0, + 29.0, + 41.0 + ] + }, + { + "id": 137, + "relativePosition": [ + 40.0, + 29.0, + 41.0 + ] + }, + { + "id": 138, + "relativePosition": [ + 37.0, + 27.0, + 43.0 + ] + }, + { + "id": 139, + "relativePosition": [ + 37.0, + 27.0, + 42.0 + ] + }, + { + "id": 140, + "relativePosition": [ + 37.0, + 28.0, + 42.0 + ] + }, + { + "id": 141, + "relativePosition": [ + 37.0, + 28.0, + 41.0 + ] + }, + { + "id": 142, + "relativePosition": [ + 38.0, + 28.0, + 41.0 + ] + }, + { + "id": 143, + "relativePosition": [ + 38.0, + 29.0, + 41.0 + ] + }, + { + "id": 144, + "relativePosition": [ + 40.0, + 29.0, + 41.0 + ] + }, + { + "id": 145, + "relativePosition": [ + 40.0, + 20.0, + 43.0 + ] + }, + { + "id": 146, + "relativePosition": [ + 39.0, + 20.0, + 43.0 + ] + }, + { + "id": 147, + "relativePosition": [ + 39.0, + 23.0, + 43.0 + ] + }, + { + "id": 148, + "relativePosition": [ + 38.0, + 23.0, + 43.0 + ] + }, + { + "id": 149, + "relativePosition": [ + 38.0, + 24.0, + 43.0 + ] + }, + { + "id": 150, + "relativePosition": [ + 37.0, + 24.0, + 43.0 + ] + }, + { + "id": 151, + "relativePosition": [ + 37.0, + 27.0, + 43.0 + ] + }, + { + "id": 152, + "relativePosition": [ + 40.0, + 20.0, + 43.0 + ] + }, + { + "id": 153, + "relativePosition": [ + 39.0, + 20.0, + 43.0 + ] + }, + { + "id": 154, + "relativePosition": [ + 39.0, + 23.0, + 43.0 + ] + }, + { + "id": 155, + "relativePosition": [ + 38.0, + 23.0, + 43.0 + ] + }, + { + "id": 156, + "relativePosition": [ + 38.0, + 24.0, + 43.0 + ] + }, + { + "id": 157, + "relativePosition": [ + 37.0, + 24.0, + 43.0 + ] + }, + { + "id": 158, + "relativePosition": [ + 37.0, + 27.0, + 43.0 + ] + }, + { + "id": 159, + "relativePosition": [ + 21.0, + 20.0, + 42.0 + ] + }, + { + "id": 160, + "relativePosition": [ + 21.0, + 21.0, + 42.0 + ] + }, + { + "id": 161, + "relativePosition": [ + 22.0, + 21.0, + 42.0 + ] + }, + { + "id": 162, + "relativePosition": [ + 22.0, + 21.0, + 41.0 + ] + }, + { + "id": 163, + "relativePosition": [ + 33.0, + 21.0, + 41.0 + ] + }, + { + "id": 164, + "relativePosition": [ + 33.0, + 20.0, + 41.0 + ] + }, + { + "id": 165, + "relativePosition": [ + 34.0, + 20.0, + 41.0 + ] + }, + { + "id": 166, + "relativePosition": [ + 34.0, + 20.0, + 42.0 + ] + }, + { + "id": 167, + "relativePosition": [ + 38.0, + 20.0, + 42.0 + ] + }, + { + "id": 168, + "relativePosition": [ + 38.0, + 20.0, + 43.0 + ] + }, + { + "id": 169, + "relativePosition": [ + 40.0, + 20.0, + 43.0 + ] + }, + { + "id": 170, + "relativePosition": [ + 21.0, + 20.0, + 42.0 + ] + }, + { + "id": 171, + "relativePosition": [ + 21.0, + 21.0, + 42.0 + ] + }, + { + "id": 172, + "relativePosition": [ + 22.0, + 21.0, + 42.0 + ] + }, + { + "id": 173, + "relativePosition": [ + 22.0, + 21.0, + 41.0 + ] + }, + { + "id": 174, + "relativePosition": [ + 33.0, + 21.0, + 41.0 + ] + }, + { + "id": 175, + "relativePosition": [ + 33.0, + 20.0, + 41.0 + ] + }, + { + "id": 176, + "relativePosition": [ + 34.0, + 20.0, + 41.0 + ] + }, + { + "id": 177, + "relativePosition": [ + 34.0, + 20.0, + 42.0 + ] + }, + { + "id": 178, + "relativePosition": [ + 38.0, + 20.0, + 42.0 + ] + }, + { + "id": 179, + "relativePosition": [ + 38.0, + 20.0, + 43.0 + ] + }, + { + "id": 180, + "relativePosition": [ + 40.0, + 20.0, + 43.0 + ] + }, + { + "id": 181, + "relativePosition": [ + 52.0, + 20.0, + 43.0 + ] + }, + { + "id": 182, + "relativePosition": [ + 55.0, + 20.0, + 43.0 + ] + }, + { + "id": 183, + "relativePosition": [ + 52.0, + 20.0, + 43.0 + ] + }, + { + "id": 184, + "relativePosition": [ + 55.0, + 20.0, + 43.0 + ] + }, + { + "id": 185, + "relativePosition": [ + 72.0, + 17.0, + 43.0 + ] + }, + { + "id": 186, + "relativePosition": [ + 72.0, + 16.0, + 43.0 + ] + }, + { + "id": 187, + "relativePosition": [ + 72.0, + 16.0, + 44.0 + ] + }, + { + "id": 188, + "relativePosition": [ + 71.0, + 16.0, + 44.0 + ] + }, + { + "id": 189, + "relativePosition": [ + 71.0, + 17.0, + 44.0 + ] + }, + { + "id": 190, + "relativePosition": [ + 71.0, + 17.0, + 45.0 + ] + }, + { + "id": 191, + "relativePosition": [ + 71.0, + 18.0, + 45.0 + ] + }, + { + "id": 192, + "relativePosition": [ + 71.0, + 17.0, + 45.0 + ] + }, + { + "id": 193, + "relativePosition": [ + 71.0, + 17.0, + 46.0 + ] + }, + { + "id": 194, + "relativePosition": [ + 72.0, + 17.0, + 43.0 + ] + }, + { + "id": 195, + "relativePosition": [ + 72.0, + 16.0, + 43.0 + ] + }, + { + "id": 196, + "relativePosition": [ + 72.0, + 16.0, + 44.0 + ] + }, + { + "id": 197, + "relativePosition": [ + 71.0, + 16.0, + 44.0 + ] + }, + { + "id": 198, + "relativePosition": [ + 71.0, + 17.0, + 44.0 + ] + }, + { + "id": 199, + "relativePosition": [ + 71.0, + 17.0, + 45.0 + ] + }, + { + "id": 200, + "relativePosition": [ + 71.0, + 18.0, + 45.0 + ] + }, + { + "id": 201, + "relativePosition": [ + 71.0, + 17.0, + 45.0 + ] + }, + { + "id": 202, + "relativePosition": [ + 71.0, + 17.0, + 46.0 + ] + }, + { + "id": 203, + "relativePosition": [ + 72.0, + 17.0, + 43.0 + ] + }, + { + "id": 204, + "relativePosition": [ + 72.0, + 17.0, + 42.0 + ] + }, + { + "id": 205, + "relativePosition": [ + 75.0, + 17.0, + 42.0 + ] + }, + { + "id": 206, + "relativePosition": [ + 75.0, + 17.0, + 41.0 + ] + }, + { + "id": 207, + "relativePosition": [ + 77.0, + 17.0, + 41.0 + ] + }, + { + "id": 208, + "relativePosition": [ + 77.0, + 17.0, + 40.0 + ] + }, + { + "id": 209, + "relativePosition": [ + 81.0, + 17.0, + 40.0 + ] + }, + { + "id": 210, + "relativePosition": [ + 72.0, + 17.0, + 43.0 + ] + }, + { + "id": 211, + "relativePosition": [ + 72.0, + 17.0, + 42.0 + ] + }, + { + "id": 212, + "relativePosition": [ + 75.0, + 17.0, + 42.0 + ] + }, + { + "id": 213, + "relativePosition": [ + 75.0, + 17.0, + 41.0 + ] + }, + { + "id": 214, + "relativePosition": [ + 77.0, + 17.0, + 41.0 + ] + }, + { + "id": 215, + "relativePosition": [ + 77.0, + 17.0, + 40.0 + ] + }, + { + "id": 216, + "relativePosition": [ + 81.0, + 17.0, + 40.0 + ] + } + ], + "elements": [ + { + "id": 1, + "type": "cell", + "intervals": [ + [ + [ + 2, + 2, + 2 + ], + [ + 198, + 78, + 78 + ] + ] + ] + }, + { + "id": 2, + "type": "node", + "coordinateIds": [ + 1 + ] + }, + { + "id": 3, + "type": "node", + "coordinateIds": [ + 2 + ] + }, + { + "id": 4, + "type": "node", + "coordinateIds": [ + 3 + ] + }, + { + "id": 5, + "type": "node", + "coordinateIds": [ + 4 + ] + }, + { + "id": 6, + "type": "node", + "coordinateIds": [ + 5 + ] + }, + { + "id": 7, + "type": "cell", + "intervals": [ + [ + [ + 39, + 27, + 39 + ], + [ + 42, + 27, + 40 + ] + ], + [ + [ + 42, + 27, + 40 + ], + [ + 43, + 27, + 41 + ] + ], + [ + [ + 39, + 29, + 39 + ], + [ + 40, + 29, + 40 + ] + ], + [ + [ + 41, + 30, + 40 + ], + [ + 42, + 30, + 41 + ] + ], + [ + [ + 41, + 30, + 39 + ], + [ + 42, + 30, + 40 + ] + ], + [ + [ + 40, + 31, + 39 + ], + [ + 41, + 31, + 40 + ] + ], + [ + [ + 41, + 32, + 40 + ], + [ + 43, + 32, + 41 + ] + ], + [ + [ + 39, + 27, + 39 + ], + [ + 39, + 29, + 40 + ] + ], + [ + [ + 39, + 27, + 39 + ], + [ + 42, + 29, + 39 + ] + ], + [ + [ + 40, + 29, + 39 + ], + [ + 42, + 30, + 39 + ] + ], + [ + [ + 40, + 30, + 39 + ], + [ + 41, + 31, + 39 + ] + ], + [ + [ + 40, + 29, + 39 + ], + [ + 40, + 31, + 40 + ] + ], + [ + [ + 39, + 26, + 40 + ], + [ + 42, + 27, + 40 + ] + ], + [ + [ + 41, + 25, + 40 + ], + [ + 42, + 26, + 40 + ] + ], + [ + [ + 41, + 30, + 40 + ], + [ + 43, + 32, + 40 + ] + ], + [ + [ + 42, + 21, + 40 + ], + [ + 43, + 30, + 40 + ] + ], + [ + [ + 43, + 19, + 40 + ], + [ + 44, + 26, + 40 + ] + ], + [ + [ + 39, + 28, + 40 + ], + [ + 43, + 29, + 40 + ] + ], + [ + [ + 40, + 29, + 40 + ], + [ + 43, + 31, + 40 + ] + ], + [ + [ + 42, + 21, + 40 + ], + [ + 44, + 22, + 40 + ] + ], + [ + [ + 43, + 19, + 40 + ], + [ + 44, + 21, + 40 + ] + ], + [ + [ + 39, + 26, + 40 + ], + [ + 41, + 29, + 40 + ] + ], + [ + [ + 40, + 29, + 40 + ], + [ + 41, + 31, + 40 + ] + ], + [ + [ + 41, + 25, + 40 + ], + [ + 42, + 30, + 40 + ] + ], + [ + [ + 42, + 21, + 40 + ], + [ + 43, + 27, + 40 + ] + ], + [ + [ + 43, + 19, + 40 + ], + [ + 44, + 26, + 40 + ] + ], + [ + [ + 39, + 28, + 40 + ], + [ + 43, + 29, + 40 + ] + ], + [ + [ + 40, + 29, + 40 + ], + [ + 43, + 31, + 40 + ] + ], + [ + [ + 42, + 21, + 40 + ], + [ + 44, + 22, + 40 + ] + ], + [ + [ + 43, + 19, + 40 + ], + [ + 44, + 21, + 40 + ] + ], + [ + [ + 41, + 30, + 40 + ], + [ + 41, + 32, + 41 + ] + ], + [ + [ + 41, + 31, + 39 + ], + [ + 41, + 32, + 40 + ] + ], + [ + [ + 41, + 30, + 39 + ], + [ + 41, + 32, + 40 + ] + ], + [ + [ + 41, + 30, + 41 + ], + [ + 43, + 32, + 41 + ] + ], + [ + [ + 42, + 27, + 41 + ], + [ + 43, + 30, + 41 + ] + ], + [ + [ + 42, + 27, + 40 + ], + [ + 42, + 30, + 41 + ] + ], + [ + [ + 42, + 27, + 39 + ], + [ + 42, + 30, + 40 + ] + ], + [ + [ + 43, + 27, + 40 + ], + [ + 43, + 32, + 41 + ] + ] + ] + }, + { + "id": 8, + "type": "cell", + "intervals": [ + [ + [ + 54, + 20, + 43 + ], + [ + 53, + 20, + 43 + ] + ], + [ + [ + 59, + 20, + 43 + ], + [ + 63, + 20, + 43 + ] + ], + [ + [ + 21, + 21, + 42 + ], + [ + 20, + 21, + 42 + ] + ], + [ + [ + 40, + 30, + 41 + ], + [ + 42, + 30, + 41 + ] + ], + [ + [ + 41, + 31, + 41 + ], + [ + 41, + 30, + 41 + ] + ], + [ + [ + 71, + 15, + 43 + ], + [ + 72, + 15, + 44 + ] + ], + [ + [ + 76, + 16, + 40 + ], + [ + 77, + 16, + 41 + ] + ], + [ + [ + 72, + 16, + 42 + ], + [ + 73, + 16, + 43 + ] + ], + [ + [ + 74, + 16, + 41 + ], + [ + 75, + 16, + 42 + ] + ], + [ + [ + 71, + 16, + 43 + ], + [ + 72, + 16, + 44 + ] + ], + [ + [ + 70, + 17, + 45 + ], + [ + 71, + 17, + 46 + ] + ], + [ + [ + 40, + 17, + 42 + ], + [ + 52, + 17, + 43 + ] + ], + [ + [ + 39, + 17, + 42 + ], + [ + 40, + 17, + 43 + ] + ], + [ + [ + 76, + 17, + 40 + ], + [ + 77, + 17, + 41 + ] + ], + [ + [ + 74, + 17, + 41 + ], + [ + 75, + 17, + 42 + ] + ], + [ + [ + 72, + 17, + 42 + ], + [ + 73, + 17, + 43 + ] + ], + [ + [ + 70, + 18, + 45 + ], + [ + 71, + 18, + 46 + ] + ], + [ + [ + 40, + 18, + 42 + ], + [ + 52, + 18, + 43 + ] + ], + [ + [ + 37, + 19, + 42 + ], + [ + 38, + 19, + 43 + ] + ], + [ + [ + 38, + 19, + 42 + ], + [ + 39, + 19, + 43 + ] + ], + [ + [ + 52, + 19, + 42 + ], + [ + 53, + 19, + 43 + ] + ], + [ + [ + 39, + 19, + 42 + ], + [ + 40, + 19, + 43 + ] + ], + [ + [ + 34, + 20, + 41 + ], + [ + 36, + 20, + 42 + ] + ], + [ + [ + 33, + 20, + 41 + ], + [ + 34, + 20, + 42 + ] + ], + [ + [ + 21, + 20, + 41 + ], + [ + 22, + 20, + 42 + ] + ], + [ + [ + 52, + 20, + 42 + ], + [ + 53, + 20, + 43 + ] + ], + [ + [ + 38, + 20, + 42 + ], + [ + 39, + 20, + 43 + ] + ], + [ + [ + 37, + 20, + 42 + ], + [ + 38, + 20, + 43 + ] + ], + [ + [ + 21, + 20, + 41 + ], + [ + 21, + 21, + 42 + ] + ], + [ + [ + 21, + 21, + 41 + ], + [ + 22, + 21, + 42 + ] + ], + [ + [ + 33, + 21, + 41 + ], + [ + 34, + 21, + 42 + ] + ], + [ + [ + 34, + 21, + 41 + ], + [ + 35, + 21, + 42 + ] + ], + [ + [ + 35, + 21, + 41 + ], + [ + 36, + 21, + 42 + ] + ], + [ + [ + 22, + 20, + 41 + ], + [ + 22, + 21, + 42 + ] + ], + [ + [ + 39, + 22, + 42 + ], + [ + 40, + 22, + 43 + ] + ], + [ + [ + 37, + 27, + 42 + ], + [ + 38, + 27, + 43 + ] + ], + [ + [ + 37, + 28, + 42 + ], + [ + 38, + 28, + 43 + ] + ], + [ + [ + 33, + 20, + 41 + ], + [ + 33, + 21, + 42 + ] + ], + [ + [ + 35, + 20, + 41 + ], + [ + 35, + 21, + 42 + ] + ], + [ + [ + 36, + 20, + 41 + ], + [ + 36, + 21, + 42 + ] + ], + [ + [ + 37, + 28, + 41 + ], + [ + 37, + 29, + 42 + ] + ], + [ + [ + 37, + 27, + 42 + ], + [ + 37, + 28, + 43 + ] + ], + [ + [ + 37, + 19, + 42 + ], + [ + 37, + 20, + 43 + ] + ], + [ + [ + 58, + 37, + 41 + ], + [ + 59, + 37, + 42 + ] + ], + [ + [ + 64, + 37, + 41 + ], + [ + 68, + 37, + 42 + ] + ], + [ + [ + 60, + 37, + 41 + ], + [ + 64, + 37, + 42 + ] + ], + [ + [ + 37, + 28, + 41 + ], + [ + 37, + 29, + 42 + ] + ], + [ + [ + 38, + 27, + 42 + ], + [ + 38, + 28, + 43 + ] + ], + [ + [ + 58, + 38, + 41 + ], + [ + 59, + 38, + 42 + ] + ], + [ + [ + 64, + 38, + 41 + ], + [ + 68, + 38, + 42 + ] + ], + [ + [ + 60, + 38, + 41 + ], + [ + 64, + 38, + 42 + ] + ], + [ + [ + 39, + 17, + 42 + ], + [ + 39, + 19, + 43 + ] + ], + [ + [ + 39, + 20, + 42 + ], + [ + 39, + 22, + 43 + ] + ], + [ + [ + 77, + 16, + 40 + ], + [ + 81, + 17, + 40 + ] + ], + [ + [ + 80, + 15, + 40 + ], + [ + 81, + 16, + 40 + ] + ], + [ + [ + 76, + 16, + 40 + ], + [ + 77, + 17, + 40 + ] + ], + [ + [ + 40, + 20, + 42 + ], + [ + 40, + 21, + 43 + ] + ], + [ + [ + 40, + 21, + 42 + ], + [ + 40, + 22, + 43 + ] + ], + [ + [ + 40, + 18, + 42 + ], + [ + 40, + 19, + 43 + ] + ], + [ + [ + 40, + 19, + 42 + ], + [ + 40, + 20, + 43 + ] + ], + [ + [ + 79, + 16, + 40 + ], + [ + 81, + 17, + 40 + ] + ], + [ + [ + 80, + 15, + 40 + ], + [ + 81, + 16, + 40 + ] + ], + [ + [ + 77, + 16, + 40 + ], + [ + 78, + 17, + 40 + ] + ], + [ + [ + 78, + 16, + 40 + ], + [ + 79, + 17, + 40 + ] + ], + [ + [ + 74, + 16, + 41 + ], + [ + 76, + 17, + 41 + ] + ], + [ + [ + 59, + 37, + 41 + ], + [ + 68, + 38, + 41 + ] + ], + [ + [ + 58, + 37, + 41 + ], + [ + 59, + 38, + 41 + ] + ], + [ + [ + 21, + 20, + 41 + ], + [ + 34, + 21, + 41 + ] + ], + [ + [ + 34, + 20, + 41 + ], + [ + 35, + 21, + 41 + ] + ], + [ + [ + 35, + 20, + 41 + ], + [ + 36, + 21, + 41 + ] + ], + [ + [ + 39, + 28, + 41 + ], + [ + 42, + 29, + 41 + ] + ], + [ + [ + 37, + 28, + 41 + ], + [ + 39, + 29, + 41 + ] + ], + [ + [ + 39, + 29, + 41 + ], + [ + 40, + 30, + 41 + ] + ], + [ + [ + 75, + 16, + 41 + ], + [ + 77, + 17, + 41 + ] + ], + [ + [ + 59, + 37, + 41 + ], + [ + 60, + 38, + 41 + ] + ], + [ + [ + 22, + 20, + 41 + ], + [ + 33, + 21, + 41 + ] + ], + [ + [ + 37, + 28, + 41 + ], + [ + 40, + 29, + 41 + ] + ], + [ + [ + 39, + 29, + 41 + ], + [ + 40, + 30, + 41 + ] + ], + [ + [ + 40, + 28, + 41 + ], + [ + 42, + 29, + 41 + ] + ], + [ + [ + 68, + 37, + 42 + ], + [ + 75, + 38, + 42 + ] + ], + [ + [ + 72, + 36, + 42 + ], + [ + 73, + 37, + 42 + ] + ], + [ + [ + 74, + 36, + 42 + ], + [ + 75, + 37, + 42 + ] + ], + [ + [ + 56, + 35, + 42 + ], + [ + 57, + 37, + 42 + ] + ], + [ + [ + 57, + 37, + 42 + ], + [ + 58, + 38, + 42 + ] + ], + [ + [ + 36, + 19, + 42 + ], + [ + 39, + 20, + 42 + ] + ], + [ + [ + 40, + 17, + 42 + ], + [ + 52, + 18, + 42 + ] + ], + [ + [ + 39, + 17, + 42 + ], + [ + 40, + 18, + 42 + ] + ], + [ + [ + 39, + 20, + 42 + ], + [ + 40, + 21, + 42 + ] + ], + [ + [ + 39, + 21, + 42 + ], + [ + 40, + 22, + 42 + ] + ], + [ + [ + 37, + 27, + 42 + ], + [ + 38, + 28, + 42 + ] + ], + [ + [ + 52, + 19, + 42 + ], + [ + 53, + 20, + 42 + ] + ], + [ + [ + 39, + 18, + 42 + ], + [ + 40, + 19, + 42 + ] + ], + [ + [ + 39, + 19, + 42 + ], + [ + 40, + 20, + 42 + ] + ], + [ + [ + 72, + 16, + 42 + ], + [ + 74, + 17, + 42 + ] + ], + [ + [ + 73, + 37, + 42 + ], + [ + 75, + 38, + 42 + ] + ], + [ + [ + 74, + 36, + 42 + ], + [ + 75, + 37, + 42 + ] + ], + [ + [ + 72, + 36, + 42 + ], + [ + 73, + 37, + 42 + ] + ], + [ + [ + 60, + 37, + 42 + ], + [ + 72, + 38, + 42 + ] + ], + [ + [ + 56, + 35, + 42 + ], + [ + 57, + 37, + 42 + ] + ], + [ + [ + 57, + 37, + 42 + ], + [ + 59, + 38, + 42 + ] + ], + [ + [ + 21, + 20, + 42 + ], + [ + 22, + 21, + 42 + ] + ], + [ + [ + 33, + 20, + 42 + ], + [ + 36, + 21, + 42 + ] + ], + [ + [ + 72, + 37, + 42 + ], + [ + 73, + 38, + 42 + ] + ], + [ + [ + 36, + 19, + 42 + ], + [ + 37, + 20, + 42 + ] + ], + [ + [ + 73, + 16, + 42 + ], + [ + 75, + 17, + 42 + ] + ], + [ + [ + 71, + 15, + 43 + ], + [ + 72, + 17, + 43 + ] + ], + [ + [ + 71, + 17, + 43 + ], + [ + 72, + 19, + 43 + ] + ], + [ + [ + 63, + 19, + 43 + ], + [ + 71, + 20, + 43 + ] + ], + [ + [ + 54, + 20, + 43 + ], + [ + 59, + 21, + 43 + ] + ], + [ + [ + 55, + 35, + 43 + ], + [ + 56, + 36, + 43 + ] + ], + [ + [ + 54, + 34, + 43 + ], + [ + 55, + 35, + 43 + ] + ], + [ + [ + 54, + 21, + 43 + ], + [ + 55, + 34, + 43 + ] + ], + [ + [ + 37, + 23, + 43 + ], + [ + 38, + 24, + 43 + ] + ], + [ + [ + 38, + 22, + 43 + ], + [ + 39, + 23, + 43 + ] + ], + [ + [ + 37, + 24, + 43 + ], + [ + 38, + 27, + 43 + ] + ], + [ + [ + 63, + 19, + 43 + ], + [ + 71, + 20, + 43 + ] + ], + [ + [ + 54, + 20, + 43 + ], + [ + 59, + 21, + 43 + ] + ], + [ + [ + 71, + 17, + 43 + ], + [ + 72, + 19, + 43 + ] + ], + [ + [ + 55, + 35, + 43 + ], + [ + 56, + 36, + 43 + ] + ], + [ + [ + 54, + 34, + 43 + ], + [ + 55, + 35, + 43 + ] + ], + [ + [ + 54, + 21, + 43 + ], + [ + 55, + 34, + 43 + ] + ], + [ + [ + 52, + 19, + 43 + ], + [ + 53, + 20, + 43 + ] + ], + [ + [ + 37, + 19, + 43 + ], + [ + 39, + 20, + 43 + ] + ], + [ + [ + 39, + 17, + 43 + ], + [ + 52, + 18, + 43 + ] + ], + [ + [ + 39, + 18, + 43 + ], + [ + 40, + 20, + 43 + ] + ], + [ + [ + 39, + 20, + 43 + ], + [ + 40, + 21, + 43 + ] + ], + [ + [ + 37, + 24, + 43 + ], + [ + 38, + 28, + 43 + ] + ], + [ + [ + 39, + 21, + 43 + ], + [ + 40, + 22, + 43 + ] + ], + [ + [ + 37, + 23, + 43 + ], + [ + 38, + 24, + 43 + ] + ], + [ + [ + 38, + 22, + 43 + ], + [ + 39, + 23, + 43 + ] + ], + [ + [ + 71, + 16, + 43 + ], + [ + 73, + 17, + 43 + ] + ], + [ + [ + 71, + 16, + 44 + ], + [ + 72, + 17, + 44 + ] + ], + [ + [ + 71, + 15, + 44 + ], + [ + 72, + 16, + 44 + ] + ], + [ + [ + 71, + 16, + 44 + ], + [ + 72, + 17, + 44 + ] + ], + [ + [ + 70, + 17, + 45 + ], + [ + 71, + 18, + 45 + ] + ], + [ + [ + 70, + 17, + 46 + ], + [ + 71, + 18, + 46 + ] + ], + [ + [ + 52, + 18, + 42 + ], + [ + 52, + 20, + 43 + ] + ], + [ + [ + 52, + 17, + 42 + ], + [ + 52, + 19, + 43 + ] + ], + [ + [ + 53, + 19, + 42 + ], + [ + 53, + 20, + 43 + ] + ], + [ + [ + 56, + 35, + 42 + ], + [ + 56, + 36, + 43 + ] + ], + [ + [ + 56, + 35, + 42 + ], + [ + 56, + 36, + 43 + ] + ], + [ + [ + 58, + 37, + 41 + ], + [ + 58, + 38, + 42 + ] + ], + [ + [ + 59, + 37, + 41 + ], + [ + 59, + 38, + 42 + ] + ], + [ + [ + 60, + 37, + 41 + ], + [ + 60, + 38, + 42 + ] + ], + [ + [ + 68, + 37, + 41 + ], + [ + 68, + 38, + 42 + ] + ], + [ + [ + 70, + 17, + 45 + ], + [ + 70, + 18, + 46 + ] + ], + [ + [ + 71, + 16, + 44 + ], + [ + 71, + 17, + 45 + ] + ], + [ + [ + 71, + 15, + 43 + ], + [ + 71, + 16, + 44 + ] + ], + [ + [ + 71, + 36, + 42 + ], + [ + 71, + 37, + 43 + ] + ], + [ + [ + 71, + 17, + 45 + ], + [ + 71, + 18, + 46 + ] + ], + [ + [ + 71, + 16, + 44 + ], + [ + 71, + 17, + 45 + ] + ], + [ + [ + 71, + 36, + 42 + ], + [ + 71, + 37, + 43 + ] + ], + [ + [ + 72, + 16, + 42 + ], + [ + 72, + 17, + 43 + ] + ], + [ + [ + 72, + 15, + 43 + ], + [ + 72, + 16, + 44 + ] + ], + [ + [ + 73, + 36, + 42 + ], + [ + 73, + 37, + 43 + ] + ], + [ + [ + 73, + 36, + 42 + ], + [ + 73, + 37, + 43 + ] + ], + [ + [ + 73, + 16, + 42 + ], + [ + 73, + 17, + 43 + ] + ], + [ + [ + 74, + 16, + 41 + ], + [ + 74, + 17, + 42 + ] + ], + [ + [ + 75, + 16, + 41 + ], + [ + 75, + 17, + 42 + ] + ], + [ + [ + 76, + 16, + 40 + ], + [ + 76, + 17, + 41 + ] + ], + [ + [ + 77, + 16, + 40 + ], + [ + 77, + 17, + 41 + ] + ] + ] + }, + { + "id": 9, + "type": "cell", + "intervals": [ + [ + [ + 46, + 36, + 40 + ], + [ + 45, + 36, + 40 + ] + ], + [ + [ + 45, + 36, + 40 + ], + [ + 45, + 35, + 40 + ] + ], + [ + [ + 45, + 35, + 40 + ], + [ + 43, + 35, + 40 + ] + ], + [ + [ + 43, + 35, + 40 + ], + [ + 43, + 34, + 40 + ] + ], + [ + [ + 43, + 34, + 40 + ], + [ + 41, + 34, + 40 + ] + ], + [ + [ + 41, + 34, + 40 + ], + [ + 41, + 33, + 40 + ] + ], + [ + [ + 41, + 33, + 40 + ], + [ + 39, + 33, + 40 + ] + ], + [ + [ + 39, + 33, + 40 + ], + [ + 39, + 32, + 40 + ] + ], + [ + [ + 39, + 32, + 40 + ], + [ + 37, + 32, + 40 + ] + ], + [ + [ + 37, + 32, + 40 + ], + [ + 37, + 31, + 40 + ] + ], + [ + [ + 192, + 72, + 40 + ], + [ + 193, + 72, + 40 + ] + ], + [ + [ + 79, + 41, + 4 + ], + [ + 80, + 42, + 4 + ] + ], + [ + [ + 79, + 42, + 4 + ], + [ + 93, + 43, + 4 + ] + ], + [ + [ + 80, + 41, + 4 + ], + [ + 89, + 42, + 4 + ] + ], + [ + [ + 92, + 42, + 5 + ], + [ + 93, + 43, + 5 + ] + ], + [ + [ + 89, + 41, + 5 + ], + [ + 90, + 42, + 5 + ] + ], + [ + [ + 90, + 41, + 6 + ], + [ + 91, + 42, + 6 + ] + ], + [ + [ + 91, + 41, + 7 + ], + [ + 92, + 42, + 7 + ] + ], + [ + [ + 91, + 42, + 8 + ], + [ + 92, + 43, + 8 + ] + ], + [ + [ + 78, + 41, + 8 + ], + [ + 79, + 43, + 8 + ] + ], + [ + [ + 81, + 40, + 8 + ], + [ + 84, + 41, + 8 + ] + ], + [ + [ + 92, + 41, + 9 + ], + [ + 93, + 42, + 9 + ] + ], + [ + [ + 79, + 40, + 9 + ], + [ + 81, + 41, + 9 + ] + ], + [ + [ + 84, + 40, + 9 + ], + [ + 86, + 41, + 9 + ] + ], + [ + [ + 93, + 41, + 10 + ], + [ + 94, + 42, + 10 + ] + ], + [ + [ + 86, + 40, + 10 + ], + [ + 87, + 41, + 10 + ] + ], + [ + [ + 77, + 41, + 11 + ], + [ + 78, + 42, + 11 + ] + ], + [ + [ + 78, + 40, + 11 + ], + [ + 79, + 41, + 11 + ] + ], + [ + [ + 87, + 40, + 11 + ], + [ + 89, + 41, + 11 + ] + ], + [ + [ + 90, + 42, + 12 + ], + [ + 91, + 43, + 12 + ] + ], + [ + [ + 89, + 40, + 12 + ], + [ + 90, + 41, + 12 + ] + ], + [ + [ + 78, + 13, + 41 + ], + [ + 94, + 13, + 42 + ] + ], + [ + [ + 71, + 13, + 42 + ], + [ + 95, + 13, + 43 + ] + ], + [ + [ + 72, + 13, + 43 + ], + [ + 75, + 13, + 44 + ] + ], + [ + [ + 76, + 13, + 43 + ], + [ + 94, + 13, + 44 + ] + ], + [ + [ + 72, + 13, + 36 + ], + [ + 75, + 13, + 37 + ] + ], + [ + [ + 76, + 13, + 36 + ], + [ + 96, + 13, + 39 + ] + ], + [ + [ + 71, + 13, + 37 + ], + [ + 73, + 13, + 38 + ] + ], + [ + [ + 73, + 13, + 37 + ], + [ + 76, + 13, + 39 + ] + ], + [ + [ + 77, + 40, + 13 + ], + [ + 78, + 41, + 13 + ] + ], + [ + [ + 77, + 42, + 13 + ], + [ + 78, + 43, + 13 + ] + ], + [ + [ + 90, + 40, + 13 + ], + [ + 91, + 41, + 13 + ] + ], + [ + [ + 71, + 14, + 40 + ], + [ + 98, + 14, + 41 + ] + ], + [ + [ + 68, + 14, + 41 + ], + [ + 71, + 14, + 43 + ] + ], + [ + [ + 71, + 14, + 41 + ], + [ + 78, + 14, + 42 + ] + ], + [ + [ + 94, + 14, + 41 + ], + [ + 95, + 14, + 42 + ] + ], + [ + [ + 95, + 14, + 41 + ], + [ + 97, + 14, + 44 + ] + ], + [ + [ + 70, + 14, + 43 + ], + [ + 72, + 14, + 44 + ] + ], + [ + [ + 94, + 14, + 43 + ], + [ + 95, + 14, + 44 + ] + ], + [ + [ + 76, + 14, + 44 + ], + [ + 95, + 14, + 45 + ] + ], + [ + [ + 75, + 14, + 43 + ], + [ + 76, + 14, + 45 + ] + ], + [ + [ + 72, + 14, + 44 + ], + [ + 75, + 14, + 45 + ] + ], + [ + [ + 93, + 41, + 14 + ], + [ + 94, + 42, + 14 + ] + ], + [ + [ + 76, + 14, + 35 + ], + [ + 96, + 14, + 36 + ] + ], + [ + [ + 69, + 14, + 36 + ], + [ + 72, + 14, + 37 + ] + ], + [ + [ + 96, + 14, + 36 + ], + [ + 98, + 14, + 39 + ] + ], + [ + [ + 67, + 14, + 37 + ], + [ + 71, + 14, + 38 + ] + ], + [ + [ + 98, + 14, + 37 + ], + [ + 99, + 14, + 39 + ] + ], + [ + [ + 99, + 14, + 37 + ], + [ + 100, + 14, + 38 + ] + ], + [ + [ + 68, + 14, + 38 + ], + [ + 73, + 14, + 39 + ] + ], + [ + [ + 70, + 14, + 39 + ], + [ + 98, + 14, + 40 + ] + ], + [ + [ + 72, + 14, + 35 + ], + [ + 75, + 14, + 36 + ] + ], + [ + [ + 75, + 14, + 35 + ], + [ + 76, + 14, + 37 + ] + ], + [ + [ + 91, + 40, + 14 + ], + [ + 92, + 41, + 14 + ] + ], + [ + [ + 15, + 18, + 40 + ], + [ + 15, + 20, + 41 + ] + ], + [ + [ + 49, + 15, + 40 + ], + [ + 52, + 15, + 42 + ] + ], + [ + [ + 52, + 15, + 40 + ], + [ + 53, + 15, + 43 + ] + ], + [ + [ + 50, + 15, + 42 + ], + [ + 51, + 15, + 43 + ] + ], + [ + [ + 53, + 15, + 40 + ], + [ + 54, + 15, + 43 + ] + ], + [ + [ + 54, + 15, + 40 + ], + [ + 55, + 15, + 42 + ] + ], + [ + [ + 101, + 15, + 40 + ], + [ + 102, + 15, + 41 + ] + ], + [ + [ + 102, + 15, + 40 + ], + [ + 110, + 15, + 42 + ] + ], + [ + [ + 26, + 15, + 40 + ], + [ + 43, + 15, + 41 + ] + ], + [ + [ + 43, + 15, + 40 + ], + [ + 49, + 15, + 42 + ] + ], + [ + [ + 34, + 15, + 41 + ], + [ + 41, + 15, + 42 + ] + ], + [ + [ + 98, + 15, + 40 + ], + [ + 101, + 15, + 41 + ] + ], + [ + [ + 97, + 15, + 41 + ], + [ + 100, + 15, + 44 + ] + ], + [ + [ + 100, + 15, + 41 + ], + [ + 101, + 15, + 43 + ] + ], + [ + [ + 101, + 15, + 41 + ], + [ + 102, + 15, + 42 + ] + ], + [ + [ + 95, + 15, + 44 + ], + [ + 98, + 15, + 45 + ] + ], + [ + [ + 76, + 15, + 45 + ], + [ + 93, + 15, + 46 + ] + ], + [ + [ + 66, + 15, + 40 + ], + [ + 71, + 15, + 41 + ] + ], + [ + [ + 65, + 15, + 41 + ], + [ + 68, + 15, + 43 + ] + ], + [ + [ + 67, + 15, + 43 + ], + [ + 70, + 15, + 44 + ] + ], + [ + [ + 69, + 15, + 44 + ], + [ + 72, + 15, + 45 + ] + ], + [ + [ + 75, + 15, + 45 + ], + [ + 76, + 15, + 46 + ] + ], + [ + [ + 110, + 15, + 40 + ], + [ + 114, + 15, + 42 + ] + ], + [ + [ + 114, + 15, + 40 + ], + [ + 117, + 15, + 41 + ] + ], + [ + [ + 55, + 15, + 40 + ], + [ + 65, + 15, + 42 + ] + ], + [ + [ + 65, + 15, + 40 + ], + [ + 66, + 15, + 41 + ] + ], + [ + [ + 15, + 18, + 39 + ], + [ + 15, + 20, + 40 + ] + ], + [ + [ + 49, + 15, + 37 + ], + [ + 53, + 15, + 40 + ] + ], + [ + [ + 53, + 15, + 37 + ], + [ + 54, + 15, + 40 + ] + ], + [ + [ + 54, + 15, + 38 + ], + [ + 55, + 15, + 40 + ] + ], + [ + [ + 110, + 15, + 38 + ], + [ + 114, + 15, + 40 + ] + ], + [ + [ + 114, + 15, + 39 + ], + [ + 117, + 15, + 40 + ] + ], + [ + [ + 102, + 15, + 38 + ], + [ + 110, + 15, + 40 + ] + ], + [ + [ + 101, + 15, + 39 + ], + [ + 102, + 15, + 40 + ] + ], + [ + [ + 96, + 15, + 35 + ], + [ + 98, + 15, + 36 + ] + ], + [ + [ + 76, + 15, + 34 + ], + [ + 93, + 15, + 35 + ] + ], + [ + [ + 100, + 15, + 37 + ], + [ + 101, + 15, + 38 + ] + ], + [ + [ + 99, + 15, + 38 + ], + [ + 102, + 15, + 39 + ] + ], + [ + [ + 98, + 15, + 39 + ], + [ + 101, + 15, + 40 + ] + ], + [ + [ + 98, + 15, + 36 + ], + [ + 100, + 15, + 37 + ] + ], + [ + [ + 69, + 15, + 35 + ], + [ + 72, + 15, + 36 + ] + ], + [ + [ + 65, + 15, + 37 + ], + [ + 67, + 15, + 39 + ] + ], + [ + [ + 67, + 15, + 38 + ], + [ + 68, + 15, + 39 + ] + ], + [ + [ + 66, + 15, + 39 + ], + [ + 70, + 15, + 40 + ] + ], + [ + [ + 67, + 15, + 36 + ], + [ + 69, + 15, + 37 + ] + ], + [ + [ + 74, + 15, + 34 + ], + [ + 76, + 15, + 35 + ] + ], + [ + [ + 34, + 15, + 38 + ], + [ + 41, + 15, + 39 + ] + ], + [ + [ + 43, + 15, + 38 + ], + [ + 49, + 15, + 40 + ] + ], + [ + [ + 27, + 15, + 39 + ], + [ + 43, + 15, + 40 + ] + ], + [ + [ + 55, + 15, + 38 + ], + [ + 65, + 15, + 40 + ] + ], + [ + [ + 65, + 15, + 39 + ], + [ + 66, + 15, + 40 + ] + ], + [ + [ + 76, + 41, + 15 + ], + [ + 77, + 42, + 15 + ] + ], + [ + [ + 92, + 40, + 15 + ], + [ + 93, + 41, + 15 + ] + ], + [ + [ + 16, + 20, + 40 + ], + [ + 16, + 21, + 41 + ] + ], + [ + [ + 16, + 17, + 40 + ], + [ + 16, + 18, + 41 + ] + ], + [ + [ + 51, + 16, + 42 + ], + [ + 52, + 16, + 43 + ] + ], + [ + [ + 49, + 16, + 42 + ], + [ + 50, + 16, + 43 + ] + ], + [ + [ + 54, + 16, + 42 + ], + [ + 55, + 16, + 43 + ] + ], + [ + [ + 101, + 16, + 42 + ], + [ + 110, + 16, + 43 + ] + ], + [ + [ + 21, + 16, + 40 + ], + [ + 26, + 16, + 41 + ] + ], + [ + [ + 24, + 16, + 41 + ], + [ + 34, + 16, + 42 + ] + ], + [ + [ + 32, + 16, + 42 + ], + [ + 35, + 16, + 43 + ] + ], + [ + [ + 93, + 16, + 45 + ], + [ + 95, + 16, + 46 + ] + ], + [ + [ + 70, + 16, + 45 + ], + [ + 75, + 16, + 46 + ] + ], + [ + [ + 64, + 16, + 42 + ], + [ + 65, + 16, + 44 + ] + ], + [ + [ + 65, + 16, + 43 + ], + [ + 67, + 16, + 44 + ] + ], + [ + [ + 67, + 16, + 44 + ], + [ + 69, + 16, + 45 + ] + ], + [ + [ + 117, + 16, + 40 + ], + [ + 123, + 16, + 41 + ] + ], + [ + [ + 114, + 16, + 41 + ], + [ + 121, + 16, + 42 + ] + ], + [ + [ + 110, + 16, + 42 + ], + [ + 117, + 16, + 43 + ] + ], + [ + [ + 41, + 16, + 41 + ], + [ + 43, + 16, + 42 + ] + ], + [ + [ + 35, + 16, + 42 + ], + [ + 49, + 16, + 43 + ] + ], + [ + [ + 55, + 16, + 42 + ], + [ + 64, + 16, + 43 + ] + ], + [ + [ + 16, + 20, + 39 + ], + [ + 16, + 21, + 40 + ] + ], + [ + [ + 16, + 17, + 39 + ], + [ + 16, + 18, + 40 + ] + ], + [ + [ + 54, + 16, + 37 + ], + [ + 55, + 16, + 38 + ] + ], + [ + [ + 110, + 16, + 37 + ], + [ + 117, + 16, + 38 + ] + ], + [ + [ + 114, + 16, + 38 + ], + [ + 121, + 16, + 39 + ] + ], + [ + [ + 117, + 16, + 39 + ], + [ + 123, + 16, + 40 + ] + ], + [ + [ + 101, + 16, + 37 + ], + [ + 110, + 16, + 38 + ] + ], + [ + [ + 93, + 16, + 34 + ], + [ + 95, + 16, + 35 + ] + ], + [ + [ + 70, + 16, + 34 + ], + [ + 74, + 16, + 35 + ] + ], + [ + [ + 64, + 16, + 36 + ], + [ + 65, + 16, + 38 + ] + ], + [ + [ + 65, + 16, + 36 + ], + [ + 67, + 16, + 37 + ] + ], + [ + [ + 67, + 16, + 35 + ], + [ + 69, + 16, + 36 + ] + ], + [ + [ + 32, + 16, + 37 + ], + [ + 35, + 16, + 38 + ] + ], + [ + [ + 24, + 16, + 38 + ], + [ + 34, + 16, + 39 + ] + ], + [ + [ + 21, + 16, + 39 + ], + [ + 27, + 16, + 40 + ] + ], + [ + [ + 35, + 16, + 37 + ], + [ + 49, + 16, + 38 + ] + ], + [ + [ + 41, + 16, + 38 + ], + [ + 43, + 16, + 39 + ] + ], + [ + [ + 55, + 16, + 37 + ], + [ + 64, + 16, + 38 + ] + ], + [ + [ + 76, + 40, + 16 + ], + [ + 77, + 41, + 16 + ] + ], + [ + [ + 93, + 40, + 16 + ], + [ + 94, + 41, + 16 + ] + ], + [ + [ + 80, + 39, + 16 + ], + [ + 85, + 40, + 16 + ] + ], + [ + [ + 17, + 21, + 40 + ], + [ + 17, + 22, + 41 + ] + ], + [ + [ + 99, + 17, + 36 + ], + [ + 100, + 17, + 37 + ] + ], + [ + [ + 97, + 17, + 35 + ], + [ + 98, + 17, + 36 + ] + ], + [ + [ + 16, + 17, + 40 + ], + [ + 17, + 17, + 41 + ] + ], + [ + [ + 21, + 17, + 41 + ], + [ + 24, + 17, + 42 + ] + ], + [ + [ + 28, + 17, + 42 + ], + [ + 32, + 17, + 43 + ] + ], + [ + [ + 17, + 17, + 40 + ], + [ + 21, + 17, + 41 + ] + ], + [ + [ + 69, + 17, + 45 + ], + [ + 70, + 17, + 46 + ] + ], + [ + [ + 66, + 17, + 44 + ], + [ + 67, + 17, + 45 + ] + ], + [ + [ + 63, + 17, + 43 + ], + [ + 64, + 17, + 44 + ] + ], + [ + [ + 117, + 17, + 42 + ], + [ + 121, + 17, + 43 + ] + ], + [ + [ + 123, + 17, + 40 + ], + [ + 127, + 17, + 41 + ] + ], + [ + [ + 121, + 17, + 41 + ], + [ + 125, + 17, + 42 + ] + ], + [ + [ + 89, + 42, + 17 + ], + [ + 90, + 43, + 17 + ] + ], + [ + [ + 17, + 21, + 39 + ], + [ + 17, + 22, + 40 + ] + ], + [ + [ + 121, + 17, + 38 + ], + [ + 125, + 17, + 39 + ] + ], + [ + [ + 123, + 17, + 39 + ], + [ + 128, + 17, + 40 + ] + ], + [ + [ + 117, + 17, + 37 + ], + [ + 121, + 17, + 38 + ] + ], + [ + [ + 69, + 17, + 34 + ], + [ + 70, + 17, + 35 + ] + ], + [ + [ + 65, + 17, + 35 + ], + [ + 67, + 17, + 36 + ] + ], + [ + [ + 63, + 17, + 36 + ], + [ + 64, + 17, + 37 + ] + ], + [ + [ + 16, + 17, + 39 + ], + [ + 17, + 17, + 40 + ] + ], + [ + [ + 17, + 17, + 39 + ], + [ + 21, + 17, + 40 + ] + ], + [ + [ + 21, + 17, + 38 + ], + [ + 24, + 17, + 39 + ] + ], + [ + [ + 28, + 17, + 37 + ], + [ + 32, + 17, + 38 + ] + ], + [ + [ + 99, + 17, + 43 + ], + [ + 100, + 17, + 44 + ] + ], + [ + [ + 97, + 17, + 44 + ], + [ + 98, + 17, + 45 + ] + ], + [ + [ + 94, + 40, + 17 + ], + [ + 95, + 41, + 17 + ] + ], + [ + [ + 85, + 39, + 17 + ], + [ + 87, + 40, + 17 + ] + ], + [ + [ + 78, + 39, + 17 + ], + [ + 80, + 40, + 17 + ] + ], + [ + [ + 98, + 18, + 36 + ], + [ + 99, + 18, + 37 + ] + ], + [ + [ + 96, + 18, + 35 + ], + [ + 97, + 18, + 36 + ] + ], + [ + [ + 93, + 18, + 34 + ], + [ + 95, + 18, + 35 + ] + ], + [ + [ + 65, + 18, + 35 + ], + [ + 66, + 18, + 36 + ] + ], + [ + [ + 68, + 18, + 34 + ], + [ + 69, + 18, + 35 + ] + ], + [ + [ + 50, + 18, + 43 + ], + [ + 53, + 18, + 44 + ] + ], + [ + [ + 53, + 18, + 43 + ], + [ + 55, + 18, + 44 + ] + ], + [ + [ + 98, + 18, + 43 + ], + [ + 110, + 18, + 44 + ] + ], + [ + [ + 15, + 18, + 40 + ], + [ + 16, + 18, + 41 + ] + ], + [ + [ + 19, + 18, + 41 + ], + [ + 21, + 18, + 42 + ] + ], + [ + [ + 26, + 18, + 42 + ], + [ + 28, + 18, + 43 + ] + ], + [ + [ + 68, + 18, + 45 + ], + [ + 69, + 18, + 46 + ] + ], + [ + [ + 65, + 18, + 44 + ], + [ + 66, + 18, + 45 + ] + ], + [ + [ + 127, + 18, + 40 + ], + [ + 128, + 18, + 41 + ] + ], + [ + [ + 125, + 18, + 41 + ], + [ + 126, + 18, + 42 + ] + ], + [ + [ + 121, + 18, + 42 + ], + [ + 122, + 18, + 43 + ] + ], + [ + [ + 110, + 18, + 43 + ], + [ + 111, + 18, + 44 + ] + ], + [ + [ + 130, + 18, + 40 + ], + [ + 131, + 18, + 41 + ] + ], + [ + [ + 55, + 18, + 43 + ], + [ + 63, + 18, + 44 + ] + ], + [ + [ + 128, + 18, + 40 + ], + [ + 130, + 18, + 41 + ] + ], + [ + [ + 126, + 18, + 41 + ], + [ + 129, + 18, + 42 + ] + ], + [ + [ + 122, + 18, + 42 + ], + [ + 124, + 18, + 43 + ] + ], + [ + [ + 18, + 22, + 39 + ], + [ + 18, + 23, + 40 + ] + ], + [ + [ + 49, + 18, + 36 + ], + [ + 53, + 18, + 37 + ] + ], + [ + [ + 53, + 18, + 36 + ], + [ + 55, + 18, + 37 + ] + ], + [ + [ + 125, + 18, + 38 + ], + [ + 126, + 18, + 39 + ] + ], + [ + [ + 121, + 18, + 37 + ], + [ + 122, + 18, + 38 + ] + ], + [ + [ + 98, + 18, + 36 + ], + [ + 110, + 18, + 37 + ] + ], + [ + [ + 68, + 18, + 34 + ], + [ + 69, + 18, + 35 + ] + ], + [ + [ + 110, + 18, + 36 + ], + [ + 111, + 18, + 37 + ] + ], + [ + [ + 130, + 18, + 39 + ], + [ + 131, + 18, + 40 + ] + ], + [ + [ + 15, + 18, + 39 + ], + [ + 16, + 18, + 40 + ] + ], + [ + [ + 19, + 18, + 38 + ], + [ + 21, + 18, + 39 + ] + ], + [ + [ + 26, + 18, + 37 + ], + [ + 28, + 18, + 38 + ] + ], + [ + [ + 55, + 18, + 36 + ], + [ + 63, + 18, + 37 + ] + ], + [ + [ + 65, + 18, + 44 + ], + [ + 66, + 18, + 45 + ] + ], + [ + [ + 98, + 18, + 43 + ], + [ + 99, + 18, + 44 + ] + ], + [ + [ + 96, + 18, + 44 + ], + [ + 97, + 18, + 45 + ] + ], + [ + [ + 93, + 18, + 45 + ], + [ + 95, + 18, + 46 + ] + ], + [ + [ + 126, + 18, + 38 + ], + [ + 129, + 18, + 39 + ] + ], + [ + [ + 128, + 18, + 39 + ], + [ + 130, + 18, + 40 + ] + ], + [ + [ + 122, + 18, + 37 + ], + [ + 124, + 18, + 38 + ] + ], + [ + [ + 77, + 39, + 18 + ], + [ + 78, + 40, + 18 + ] + ], + [ + [ + 87, + 39, + 18 + ], + [ + 88, + 40, + 18 + ] + ], + [ + [ + 19, + 18, + 41 + ], + [ + 19, + 21, + 42 + ] + ], + [ + [ + 19, + 22, + 40 + ], + [ + 19, + 23, + 41 + ] + ], + [ + [ + 90, + 19, + 34 + ], + [ + 93, + 19, + 35 + ] + ], + [ + [ + 92, + 19, + 35 + ], + [ + 96, + 19, + 36 + ] + ], + [ + [ + 69, + 19, + 34 + ], + [ + 70, + 19, + 35 + ] + ], + [ + [ + 49, + 19, + 43 + ], + [ + 50, + 19, + 44 + ] + ], + [ + [ + 25, + 19, + 42 + ], + [ + 26, + 19, + 43 + ] + ], + [ + [ + 111, + 19, + 43 + ], + [ + 112, + 19, + 44 + ] + ], + [ + [ + 131, + 19, + 40 + ], + [ + 134, + 19, + 41 + ] + ], + [ + [ + 130, + 19, + 41 + ], + [ + 132, + 19, + 42 + ] + ], + [ + [ + 45, + 19, + 43 + ], + [ + 49, + 19, + 44 + ] + ], + [ + [ + 129, + 19, + 41 + ], + [ + 130, + 19, + 42 + ] + ], + [ + [ + 124, + 19, + 42 + ], + [ + 126, + 19, + 43 + ] + ], + [ + [ + 92, + 41, + 19 + ], + [ + 93, + 42, + 19 + ] + ], + [ + [ + 19, + 18, + 38 + ], + [ + 19, + 21, + 39 + ] + ], + [ + [ + 111, + 19, + 36 + ], + [ + 112, + 19, + 37 + ] + ], + [ + [ + 130, + 19, + 38 + ], + [ + 132, + 19, + 39 + ] + ], + [ + [ + 131, + 19, + 39 + ], + [ + 134, + 19, + 40 + ] + ], + [ + [ + 25, + 19, + 37 + ], + [ + 26, + 19, + 38 + ] + ], + [ + [ + 48, + 19, + 36 + ], + [ + 49, + 19, + 37 + ] + ], + [ + [ + 45, + 19, + 36 + ], + [ + 48, + 19, + 37 + ] + ], + [ + [ + 69, + 19, + 45 + ], + [ + 70, + 19, + 46 + ] + ], + [ + [ + 92, + 19, + 44 + ], + [ + 96, + 19, + 45 + ] + ], + [ + [ + 90, + 19, + 45 + ], + [ + 93, + 19, + 46 + ] + ], + [ + [ + 129, + 19, + 38 + ], + [ + 130, + 19, + 39 + ] + ], + [ + [ + 124, + 19, + 37 + ], + [ + 126, + 19, + 38 + ] + ], + [ + [ + 75, + 40, + 19 + ], + [ + 76, + 42, + 19 + ] + ], + [ + [ + 76, + 42, + 19 + ], + [ + 77, + 43, + 19 + ] + ], + [ + [ + 88, + 39, + 19 + ], + [ + 90, + 40, + 19 + ] + ], + [ + [ + 20, + 23, + 40 + ], + [ + 20, + 24, + 41 + ] + ], + [ + [ + 20, + 21, + 41 + ], + [ + 20, + 22, + 42 + ] + ], + [ + [ + 70, + 20, + 34 + ], + [ + 90, + 20, + 35 + ] + ], + [ + [ + 87, + 20, + 35 + ], + [ + 92, + 20, + 36 + ] + ], + [ + [ + 66, + 20, + 35 + ], + [ + 70, + 20, + 36 + ] + ], + [ + [ + 15, + 20, + 39 + ], + [ + 16, + 20, + 40 + ] + ], + [ + [ + 112, + 20, + 43 + ], + [ + 113, + 20, + 44 + ] + ], + [ + [ + 134, + 20, + 40 + ], + [ + 137, + 20, + 41 + ] + ], + [ + [ + 132, + 20, + 41 + ], + [ + 135, + 20, + 42 + ] + ], + [ + [ + 44, + 20, + 43 + ], + [ + 45, + 20, + 44 + ] + ], + [ + [ + 126, + 20, + 42 + ], + [ + 128, + 20, + 43 + ] + ], + [ + [ + 20, + 23, + 39 + ], + [ + 20, + 24, + 40 + ] + ], + [ + [ + 20, + 21, + 38 + ], + [ + 20, + 22, + 39 + ] + ], + [ + [ + 112, + 20, + 36 + ], + [ + 113, + 20, + 37 + ] + ], + [ + [ + 132, + 20, + 38 + ], + [ + 135, + 20, + 39 + ] + ], + [ + [ + 134, + 20, + 39 + ], + [ + 137, + 20, + 40 + ] + ], + [ + [ + 15, + 20, + 40 + ], + [ + 16, + 20, + 41 + ] + ], + [ + [ + 44, + 20, + 36 + ], + [ + 45, + 20, + 37 + ] + ], + [ + [ + 87, + 20, + 44 + ], + [ + 92, + 20, + 45 + ] + ], + [ + [ + 70, + 20, + 45 + ], + [ + 90, + 20, + 46 + ] + ], + [ + [ + 66, + 20, + 44 + ], + [ + 70, + 20, + 45 + ] + ], + [ + [ + 126, + 20, + 37 + ], + [ + 128, + 20, + 38 + ] + ], + [ + [ + 76, + 39, + 20 + ], + [ + 77, + 40, + 20 + ] + ], + [ + [ + 90, + 39, + 20 + ], + [ + 91, + 40, + 20 + ] + ], + [ + [ + 21, + 17, + 41 + ], + [ + 21, + 18, + 42 + ] + ], + [ + [ + 21, + 16, + 40 + ], + [ + 21, + 17, + 41 + ] + ], + [ + [ + 21, + 22, + 41 + ], + [ + 21, + 23, + 42 + ] + ], + [ + [ + 78, + 21, + 35 + ], + [ + 87, + 21, + 36 + ] + ], + [ + [ + 75, + 21, + 35 + ], + [ + 79, + 21, + 36 + ] + ], + [ + [ + 72, + 21, + 35 + ], + [ + 76, + 21, + 36 + ] + ], + [ + [ + 70, + 21, + 35 + ], + [ + 73, + 21, + 36 + ] + ], + [ + [ + 16, + 21, + 39 + ], + [ + 17, + 21, + 40 + ] + ], + [ + [ + 19, + 21, + 38 + ], + [ + 20, + 21, + 39 + ] + ], + [ + [ + 81, + 21, + 44 + ], + [ + 82, + 21, + 45 + ] + ], + [ + [ + 78, + 21, + 44 + ], + [ + 79, + 21, + 45 + ] + ], + [ + [ + 75, + 21, + 44 + ], + [ + 76, + 21, + 45 + ] + ], + [ + [ + 72, + 21, + 44 + ], + [ + 73, + 21, + 45 + ] + ], + [ + [ + 128, + 21, + 42 + ], + [ + 129, + 21, + 43 + ] + ], + [ + [ + 113, + 21, + 43 + ], + [ + 116, + 21, + 44 + ] + ], + [ + [ + 137, + 21, + 40 + ], + [ + 141, + 21, + 41 + ] + ], + [ + [ + 135, + 21, + 41 + ], + [ + 138, + 21, + 42 + ] + ], + [ + [ + 42, + 21, + 43 + ], + [ + 44, + 21, + 44 + ] + ], + [ + [ + 94, + 40, + 21 + ], + [ + 95, + 41, + 21 + ] + ], + [ + [ + 21, + 22, + 38 + ], + [ + 21, + 23, + 39 + ] + ], + [ + [ + 21, + 17, + 38 + ], + [ + 21, + 18, + 39 + ] + ], + [ + [ + 21, + 16, + 39 + ], + [ + 21, + 17, + 40 + ] + ], + [ + [ + 78, + 21, + 35 + ], + [ + 79, + 21, + 36 + ] + ], + [ + [ + 75, + 21, + 35 + ], + [ + 76, + 21, + 36 + ] + ], + [ + [ + 72, + 21, + 35 + ], + [ + 73, + 21, + 36 + ] + ], + [ + [ + 128, + 21, + 37 + ], + [ + 129, + 21, + 38 + ] + ], + [ + [ + 113, + 21, + 36 + ], + [ + 116, + 21, + 37 + ] + ], + [ + [ + 135, + 21, + 38 + ], + [ + 138, + 21, + 39 + ] + ], + [ + [ + 137, + 21, + 39 + ], + [ + 141, + 21, + 40 + ] + ], + [ + [ + 16, + 21, + 40 + ], + [ + 17, + 21, + 41 + ] + ], + [ + [ + 19, + 21, + 41 + ], + [ + 20, + 21, + 42 + ] + ], + [ + [ + 42, + 21, + 36 + ], + [ + 44, + 21, + 37 + ] + ], + [ + [ + 81, + 21, + 44 + ], + [ + 87, + 21, + 45 + ] + ], + [ + [ + 78, + 21, + 44 + ], + [ + 82, + 21, + 45 + ] + ], + [ + [ + 75, + 21, + 44 + ], + [ + 79, + 21, + 45 + ] + ], + [ + [ + 72, + 21, + 44 + ], + [ + 76, + 21, + 45 + ] + ], + [ + [ + 70, + 21, + 44 + ], + [ + 73, + 21, + 45 + ] + ], + [ + [ + 91, + 39, + 21 + ], + [ + 93, + 40, + 21 + ] + ], + [ + [ + 22, + 24, + 40 + ], + [ + 22, + 25, + 41 + ] + ], + [ + [ + 22, + 23, + 41 + ], + [ + 22, + 24, + 42 + ] + ], + [ + [ + 17, + 22, + 39 + ], + [ + 18, + 22, + 40 + ] + ], + [ + [ + 20, + 22, + 38 + ], + [ + 21, + 22, + 39 + ] + ], + [ + [ + 130, + 22, + 42 + ], + [ + 131, + 22, + 43 + ] + ], + [ + [ + 129, + 22, + 42 + ], + [ + 130, + 22, + 43 + ] + ], + [ + [ + 116, + 22, + 43 + ], + [ + 117, + 22, + 44 + ] + ], + [ + [ + 141, + 22, + 40 + ], + [ + 144, + 22, + 41 + ] + ], + [ + [ + 138, + 22, + 41 + ], + [ + 141, + 22, + 42 + ] + ], + [ + [ + 39, + 22, + 43 + ], + [ + 42, + 22, + 44 + ] + ], + [ + [ + 88, + 42, + 22 + ], + [ + 89, + 43, + 22 + ] + ], + [ + [ + 22, + 24, + 39 + ], + [ + 22, + 25, + 40 + ] + ], + [ + [ + 22, + 23, + 38 + ], + [ + 22, + 24, + 39 + ] + ], + [ + [ + 130, + 22, + 37 + ], + [ + 131, + 22, + 38 + ] + ], + [ + [ + 129, + 22, + 37 + ], + [ + 130, + 22, + 38 + ] + ], + [ + [ + 116, + 22, + 36 + ], + [ + 117, + 22, + 37 + ] + ], + [ + [ + 141, + 22, + 39 + ], + [ + 144, + 22, + 40 + ] + ], + [ + [ + 138, + 22, + 38 + ], + [ + 141, + 22, + 39 + ] + ], + [ + [ + 17, + 22, + 40 + ], + [ + 19, + 22, + 41 + ] + ], + [ + [ + 20, + 22, + 41 + ], + [ + 21, + 22, + 42 + ] + ], + [ + [ + 39, + 22, + 36 + ], + [ + 42, + 22, + 37 + ] + ], + [ + [ + 75, + 39, + 22 + ], + [ + 76, + 40, + 22 + ] + ], + [ + [ + 93, + 39, + 22 + ], + [ + 94, + 40, + 22 + ] + ], + [ + [ + 18, + 23, + 39 + ], + [ + 20, + 23, + 40 + ] + ], + [ + [ + 21, + 23, + 38 + ], + [ + 22, + 23, + 39 + ] + ], + [ + [ + 25, + 23, + 37 + ], + [ + 26, + 23, + 38 + ] + ], + [ + [ + 131, + 23, + 42 + ], + [ + 132, + 23, + 43 + ] + ], + [ + [ + 117, + 23, + 43 + ], + [ + 118, + 23, + 44 + ] + ], + [ + [ + 144, + 23, + 40 + ], + [ + 147, + 23, + 41 + ] + ], + [ + [ + 141, + 23, + 41 + ], + [ + 143, + 23, + 42 + ] + ], + [ + [ + 37, + 23, + 43 + ], + [ + 39, + 23, + 44 + ] + ], + [ + [ + 131, + 23, + 37 + ], + [ + 132, + 23, + 38 + ] + ], + [ + [ + 117, + 23, + 36 + ], + [ + 118, + 23, + 37 + ] + ], + [ + [ + 144, + 23, + 39 + ], + [ + 147, + 23, + 40 + ] + ], + [ + [ + 141, + 23, + 38 + ], + [ + 143, + 23, + 39 + ] + ], + [ + [ + 19, + 23, + 40 + ], + [ + 20, + 23, + 41 + ] + ], + [ + [ + 21, + 23, + 41 + ], + [ + 22, + 23, + 42 + ] + ], + [ + [ + 25, + 23, + 42 + ], + [ + 26, + 23, + 43 + ] + ], + [ + [ + 37, + 23, + 36 + ], + [ + 39, + 23, + 37 + ] + ], + [ + [ + 74, + 40, + 23 + ], + [ + 75, + 41, + 23 + ] + ], + [ + [ + 94, + 39, + 23 + ], + [ + 95, + 40, + 23 + ] + ], + [ + [ + 80, + 38, + 23 + ], + [ + 84, + 39, + 23 + ] + ], + [ + [ + 24, + 16, + 41 + ], + [ + 24, + 17, + 42 + ] + ], + [ + [ + 24, + 25, + 40 + ], + [ + 24, + 26, + 41 + ] + ], + [ + [ + 24, + 24, + 41 + ], + [ + 24, + 25, + 42 + ] + ], + [ + [ + 20, + 24, + 39 + ], + [ + 22, + 24, + 40 + ] + ], + [ + [ + 22, + 24, + 38 + ], + [ + 24, + 24, + 39 + ] + ], + [ + [ + 26, + 24, + 37 + ], + [ + 27, + 24, + 38 + ] + ], + [ + [ + 132, + 24, + 42 + ], + [ + 133, + 24, + 43 + ] + ], + [ + [ + 118, + 24, + 43 + ], + [ + 119, + 24, + 44 + ] + ], + [ + [ + 147, + 24, + 40 + ], + [ + 150, + 24, + 41 + ] + ], + [ + [ + 143, + 24, + 41 + ], + [ + 145, + 24, + 42 + ] + ], + [ + [ + 36, + 24, + 43 + ], + [ + 37, + 24, + 44 + ] + ], + [ + [ + 24, + 25, + 39 + ], + [ + 24, + 26, + 40 + ] + ], + [ + [ + 24, + 24, + 38 + ], + [ + 24, + 25, + 39 + ] + ], + [ + [ + 24, + 16, + 38 + ], + [ + 24, + 17, + 39 + ] + ], + [ + [ + 132, + 24, + 37 + ], + [ + 133, + 24, + 38 + ] + ], + [ + [ + 118, + 24, + 36 + ], + [ + 119, + 24, + 37 + ] + ], + [ + [ + 147, + 24, + 39 + ], + [ + 150, + 24, + 40 + ] + ], + [ + [ + 143, + 24, + 38 + ], + [ + 145, + 24, + 39 + ] + ], + [ + [ + 26, + 24, + 42 + ], + [ + 27, + 24, + 43 + ] + ], + [ + [ + 20, + 24, + 40 + ], + [ + 22, + 24, + 41 + ] + ], + [ + [ + 22, + 24, + 41 + ], + [ + 24, + 24, + 42 + ] + ], + [ + [ + 36, + 24, + 36 + ], + [ + 37, + 24, + 37 + ] + ], + [ + [ + 74, + 41, + 24 + ], + [ + 75, + 42, + 24 + ] + ], + [ + [ + 74, + 39, + 24 + ], + [ + 75, + 40, + 24 + ] + ], + [ + [ + 84, + 38, + 24 + ], + [ + 86, + 39, + 24 + ] + ], + [ + [ + 95, + 39, + 24 + ], + [ + 96, + 40, + 24 + ] + ], + [ + [ + 78, + 38, + 24 + ], + [ + 80, + 39, + 24 + ] + ], + [ + [ + 25, + 19, + 42 + ], + [ + 25, + 23, + 43 + ] + ], + [ + [ + 25, + 26, + 40 + ], + [ + 25, + 27, + 41 + ] + ], + [ + [ + 25, + 25, + 41 + ], + [ + 25, + 26, + 42 + ] + ], + [ + [ + 22, + 25, + 39 + ], + [ + 24, + 25, + 40 + ] + ], + [ + [ + 24, + 25, + 38 + ], + [ + 25, + 25, + 39 + ] + ], + [ + [ + 27, + 25, + 37 + ], + [ + 29, + 25, + 38 + ] + ], + [ + [ + 36, + 25, + 36 + ], + [ + 37, + 25, + 37 + ] + ], + [ + [ + 146, + 25, + 41 + ], + [ + 147, + 25, + 42 + ] + ], + [ + [ + 133, + 25, + 42 + ], + [ + 134, + 25, + 43 + ] + ], + [ + [ + 150, + 25, + 40 + ], + [ + 154, + 25, + 41 + ] + ], + [ + [ + 145, + 25, + 41 + ], + [ + 146, + 25, + 42 + ] + ], + [ + [ + 25, + 26, + 39 + ], + [ + 25, + 27, + 40 + ] + ], + [ + [ + 25, + 25, + 38 + ], + [ + 25, + 26, + 39 + ] + ], + [ + [ + 25, + 19, + 37 + ], + [ + 25, + 23, + 38 + ] + ], + [ + [ + 146, + 25, + 38 + ], + [ + 147, + 25, + 39 + ] + ], + [ + [ + 133, + 25, + 37 + ], + [ + 134, + 25, + 38 + ] + ], + [ + [ + 119, + 25, + 36 + ], + [ + 120, + 25, + 37 + ] + ], + [ + [ + 150, + 25, + 39 + ], + [ + 154, + 25, + 40 + ] + ], + [ + [ + 145, + 25, + 38 + ], + [ + 146, + 25, + 39 + ] + ], + [ + [ + 36, + 25, + 43 + ], + [ + 37, + 25, + 44 + ] + ], + [ + [ + 27, + 25, + 42 + ], + [ + 30, + 25, + 43 + ] + ], + [ + [ + 22, + 25, + 40 + ], + [ + 24, + 25, + 41 + ] + ], + [ + [ + 24, + 25, + 41 + ], + [ + 25, + 25, + 42 + ] + ], + [ + [ + 86, + 38, + 25 + ], + [ + 88, + 39, + 25 + ] + ], + [ + [ + 77, + 38, + 25 + ], + [ + 78, + 39, + 25 + ] + ], + [ + [ + 26, + 18, + 42 + ], + [ + 26, + 19, + 43 + ] + ], + [ + [ + 26, + 15, + 40 + ], + [ + 26, + 16, + 41 + ] + ], + [ + [ + 26, + 23, + 42 + ], + [ + 26, + 24, + 43 + ] + ], + [ + [ + 24, + 26, + 39 + ], + [ + 25, + 26, + 40 + ] + ], + [ + [ + 25, + 26, + 38 + ], + [ + 27, + 26, + 39 + ] + ], + [ + [ + 29, + 26, + 37 + ], + [ + 31, + 26, + 38 + ] + ], + [ + [ + 37, + 26, + 36 + ], + [ + 38, + 26, + 37 + ] + ], + [ + [ + 147, + 26, + 41 + ], + [ + 149, + 26, + 42 + ] + ], + [ + [ + 119, + 26, + 43 + ], + [ + 120, + 26, + 44 + ] + ], + [ + [ + 154, + 26, + 40 + ], + [ + 157, + 26, + 41 + ] + ], + [ + [ + 76, + 42, + 26 + ], + [ + 77, + 43, + 26 + ] + ], + [ + [ + 87, + 42, + 26 + ], + [ + 88, + 43, + 26 + ] + ], + [ + [ + 91, + 41, + 26 + ], + [ + 92, + 42, + 26 + ] + ], + [ + [ + 26, + 23, + 37 + ], + [ + 26, + 24, + 38 + ] + ], + [ + [ + 26, + 18, + 37 + ], + [ + 26, + 19, + 38 + ] + ], + [ + [ + 147, + 26, + 38 + ], + [ + 149, + 26, + 39 + ] + ], + [ + [ + 154, + 26, + 39 + ], + [ + 157, + 26, + 40 + ] + ], + [ + [ + 37, + 26, + 43 + ], + [ + 38, + 26, + 44 + ] + ], + [ + [ + 24, + 26, + 40 + ], + [ + 25, + 26, + 41 + ] + ], + [ + [ + 25, + 26, + 41 + ], + [ + 27, + 26, + 42 + ] + ], + [ + [ + 30, + 26, + 42 + ], + [ + 32, + 26, + 43 + ] + ], + [ + [ + 119, + 26, + 43 + ], + [ + 120, + 26, + 44 + ] + ], + [ + [ + 88, + 38, + 26 + ], + [ + 89, + 39, + 26 + ] + ], + [ + [ + 76, + 38, + 26 + ], + [ + 77, + 39, + 26 + ] + ], + [ + [ + 27, + 24, + 42 + ], + [ + 27, + 25, + 43 + ] + ], + [ + [ + 27, + 27, + 40 + ], + [ + 27, + 28, + 41 + ] + ], + [ + [ + 27, + 26, + 41 + ], + [ + 27, + 27, + 42 + ] + ], + [ + [ + 119, + 27, + 36 + ], + [ + 120, + 27, + 37 + ] + ], + [ + [ + 25, + 27, + 39 + ], + [ + 27, + 27, + 40 + ] + ], + [ + [ + 27, + 27, + 38 + ], + [ + 29, + 27, + 39 + ] + ], + [ + [ + 31, + 27, + 37 + ], + [ + 33, + 27, + 38 + ] + ], + [ + [ + 38, + 27, + 36 + ], + [ + 39, + 27, + 37 + ] + ], + [ + [ + 149, + 27, + 41 + ], + [ + 150, + 27, + 42 + ] + ], + [ + [ + 134, + 27, + 42 + ], + [ + 135, + 27, + 43 + ] + ], + [ + [ + 157, + 27, + 40 + ], + [ + 161, + 27, + 41 + ] + ], + [ + [ + 27, + 27, + 39 + ], + [ + 27, + 28, + 40 + ] + ], + [ + [ + 27, + 26, + 38 + ], + [ + 27, + 27, + 39 + ] + ], + [ + [ + 27, + 24, + 37 + ], + [ + 27, + 25, + 38 + ] + ], + [ + [ + 27, + 15, + 39 + ], + [ + 27, + 16, + 40 + ] + ], + [ + [ + 149, + 27, + 38 + ], + [ + 150, + 27, + 39 + ] + ], + [ + [ + 134, + 27, + 37 + ], + [ + 135, + 27, + 38 + ] + ], + [ + [ + 157, + 27, + 39 + ], + [ + 161, + 27, + 40 + ] + ], + [ + [ + 38, + 27, + 43 + ], + [ + 39, + 27, + 44 + ] + ], + [ + [ + 25, + 27, + 40 + ], + [ + 27, + 27, + 41 + ] + ], + [ + [ + 27, + 27, + 41 + ], + [ + 32, + 27, + 42 + ] + ], + [ + [ + 32, + 27, + 42 + ], + [ + 34, + 27, + 43 + ] + ], + [ + [ + 73, + 39, + 27 + ], + [ + 74, + 41, + 27 + ] + ], + [ + [ + 89, + 38, + 27 + ], + [ + 91, + 39, + 27 + ] + ], + [ + [ + 75, + 38, + 27 + ], + [ + 76, + 39, + 27 + ] + ], + [ + [ + 28, + 17, + 42 + ], + [ + 28, + 18, + 43 + ] + ], + [ + [ + 29, + 28, + 38 + ], + [ + 32, + 28, + 39 + ] + ], + [ + [ + 27, + 28, + 39 + ], + [ + 30, + 28, + 40 + ] + ], + [ + [ + 33, + 28, + 37 + ], + [ + 35, + 28, + 38 + ] + ], + [ + [ + 70, + 28, + 50 + ], + [ + 75, + 28, + 51 + ] + ], + [ + [ + 161, + 28, + 40 + ], + [ + 164, + 28, + 41 + ] + ], + [ + [ + 95, + 39, + 28 + ], + [ + 96, + 40, + 28 + ] + ], + [ + [ + 28, + 17, + 37 + ], + [ + 28, + 18, + 38 + ] + ], + [ + [ + 161, + 28, + 39 + ], + [ + 164, + 28, + 40 + ] + ], + [ + [ + 70, + 28, + 29 + ], + [ + 75, + 28, + 30 + ] + ], + [ + [ + 32, + 28, + 41 + ], + [ + 34, + 28, + 42 + ] + ], + [ + [ + 34, + 28, + 42 + ], + [ + 35, + 28, + 43 + ] + ], + [ + [ + 27, + 28, + 40 + ], + [ + 31, + 28, + 41 + ] + ], + [ + [ + 74, + 38, + 28 + ], + [ + 75, + 39, + 28 + ] + ], + [ + [ + 73, + 41, + 28 + ], + [ + 74, + 42, + 28 + ] + ], + [ + [ + 91, + 38, + 28 + ], + [ + 93, + 39, + 28 + ] + ], + [ + [ + 61, + 34, + 28 + ], + [ + 79, + 35, + 28 + ] + ], + [ + [ + 63, + 33, + 28 + ], + [ + 78, + 34, + 28 + ] + ], + [ + [ + 63, + 35, + 28 + ], + [ + 80, + 36, + 28 + ] + ], + [ + [ + 65, + 32, + 28 + ], + [ + 77, + 33, + 28 + ] + ], + [ + [ + 68, + 31, + 28 + ], + [ + 76, + 32, + 28 + ] + ], + [ + [ + 72, + 30, + 28 + ], + [ + 74, + 31, + 28 + ] + ], + [ + [ + 63, + 36, + 28 + ], + [ + 79, + 37, + 28 + ] + ], + [ + [ + 68, + 37, + 28 + ], + [ + 77, + 38, + 28 + ] + ], + [ + [ + 73, + 38, + 28 + ], + [ + 74, + 39, + 28 + ] + ], + [ + [ + 60, + 35, + 28 + ], + [ + 63, + 36, + 28 + ] + ], + [ + [ + 118, + 29, + 36 + ], + [ + 119, + 29, + 37 + ] + ], + [ + [ + 32, + 29, + 38 + ], + [ + 34, + 29, + 39 + ] + ], + [ + [ + 30, + 29, + 39 + ], + [ + 33, + 29, + 40 + ] + ], + [ + [ + 35, + 29, + 37 + ], + [ + 37, + 29, + 38 + ] + ], + [ + [ + 61, + 29, + 49 + ], + [ + 79, + 29, + 50 + ] + ], + [ + [ + 75, + 29, + 50 + ], + [ + 80, + 29, + 51 + ] + ], + [ + [ + 58, + 29, + 50 + ], + [ + 70, + 29, + 51 + ] + ], + [ + [ + 165, + 29, + 40 + ], + [ + 166, + 29, + 41 + ] + ], + [ + [ + 150, + 29, + 41 + ], + [ + 151, + 29, + 42 + ] + ], + [ + [ + 164, + 29, + 40 + ], + [ + 165, + 29, + 41 + ] + ], + [ + [ + 177, + 66, + 29 + ], + [ + 178, + 67, + 29 + ] + ], + [ + [ + 178, + 65, + 29 + ], + [ + 179, + 66, + 29 + ] + ], + [ + [ + 29, + 27, + 38 + ], + [ + 29, + 28, + 39 + ] + ], + [ + [ + 29, + 25, + 37 + ], + [ + 29, + 26, + 38 + ] + ], + [ + [ + 150, + 29, + 38 + ], + [ + 151, + 29, + 39 + ] + ], + [ + [ + 165, + 29, + 39 + ], + [ + 166, + 29, + 40 + ] + ], + [ + [ + 164, + 29, + 39 + ], + [ + 165, + 29, + 40 + ] + ], + [ + [ + 61, + 29, + 30 + ], + [ + 79, + 29, + 31 + ] + ], + [ + [ + 75, + 29, + 29 + ], + [ + 80, + 29, + 30 + ] + ], + [ + [ + 58, + 29, + 29 + ], + [ + 70, + 29, + 30 + ] + ], + [ + [ + 35, + 29, + 42 + ], + [ + 37, + 29, + 43 + ] + ], + [ + [ + 34, + 29, + 41 + ], + [ + 35, + 29, + 42 + ] + ], + [ + [ + 31, + 29, + 40 + ], + [ + 33, + 29, + 41 + ] + ], + [ + [ + 118, + 29, + 43 + ], + [ + 119, + 29, + 44 + ] + ], + [ + [ + 93, + 38, + 29 + ], + [ + 94, + 39, + 29 + ] + ], + [ + [ + 174, + 66, + 29 + ], + [ + 175, + 67, + 29 + ] + ], + [ + [ + 178, + 65, + 29 + ], + [ + 181, + 66, + 29 + ] + ], + [ + [ + 173, + 65, + 29 + ], + [ + 179, + 66, + 29 + ] + ], + [ + [ + 175, + 66, + 29 + ], + [ + 178, + 67, + 29 + ] + ], + [ + [ + 58, + 38, + 29 + ], + [ + 62, + 39, + 29 + ] + ], + [ + [ + 61, + 39, + 29 + ], + [ + 70, + 40, + 29 + ] + ], + [ + [ + 67, + 40, + 29 + ], + [ + 73, + 41, + 29 + ] + ], + [ + [ + 76, + 31, + 29 + ], + [ + 82, + 32, + 29 + ] + ], + [ + [ + 77, + 32, + 29 + ], + [ + 85, + 33, + 29 + ] + ], + [ + [ + 78, + 33, + 29 + ], + [ + 87, + 34, + 29 + ] + ], + [ + [ + 79, + 34, + 29 + ], + [ + 89, + 35, + 29 + ] + ], + [ + [ + 80, + 35, + 29 + ], + [ + 90, + 36, + 29 + ] + ], + [ + [ + 85, + 36, + 29 + ], + [ + 91, + 37, + 29 + ] + ], + [ + [ + 89, + 37, + 29 + ], + [ + 93, + 38, + 29 + ] + ], + [ + [ + 74, + 30, + 29 + ], + [ + 76, + 31, + 29 + ] + ], + [ + [ + 58, + 31, + 29 + ], + [ + 68, + 32, + 29 + ] + ], + [ + [ + 58, + 32, + 29 + ], + [ + 65, + 33, + 29 + ] + ], + [ + [ + 58, + 33, + 29 + ], + [ + 63, + 34, + 29 + ] + ], + [ + [ + 58, + 34, + 29 + ], + [ + 61, + 35, + 29 + ] + ], + [ + [ + 67, + 30, + 29 + ], + [ + 72, + 31, + 29 + ] + ], + [ + [ + 56, + 31, + 29 + ], + [ + 58, + 36, + 29 + ] + ], + [ + [ + 57, + 30, + 29 + ], + [ + 67, + 31, + 29 + ] + ], + [ + [ + 57, + 36, + 29 + ], + [ + 58, + 37, + 29 + ] + ], + [ + [ + 59, + 29, + 29 + ], + [ + 80, + 30, + 29 + ] + ], + [ + [ + 71, + 28, + 29 + ], + [ + 74, + 29, + 29 + ] + ], + [ + [ + 76, + 30, + 29 + ], + [ + 83, + 31, + 29 + ] + ], + [ + [ + 82, + 31, + 29 + ], + [ + 85, + 32, + 29 + ] + ], + [ + [ + 56, + 36, + 29 + ], + [ + 57, + 37, + 29 + ] + ], + [ + [ + 57, + 37, + 29 + ], + [ + 58, + 38, + 29 + ] + ], + [ + [ + 56, + 30, + 29 + ], + [ + 57, + 31, + 29 + ] + ], + [ + [ + 91, + 36, + 29 + ], + [ + 92, + 37, + 29 + ] + ], + [ + [ + 90, + 35, + 29 + ], + [ + 91, + 36, + 29 + ] + ], + [ + [ + 87, + 33, + 29 + ], + [ + 88, + 34, + 29 + ] + ], + [ + [ + 85, + 32, + 29 + ], + [ + 87, + 33, + 29 + ] + ], + [ + [ + 74, + 28, + 29 + ], + [ + 75, + 29, + 29 + ] + ], + [ + [ + 58, + 29, + 29 + ], + [ + 59, + 30, + 29 + ] + ], + [ + [ + 70, + 28, + 29 + ], + [ + 71, + 29, + 29 + ] + ], + [ + [ + 77, + 37, + 29 + ], + [ + 89, + 38, + 29 + ] + ], + [ + [ + 79, + 36, + 29 + ], + [ + 85, + 37, + 29 + ] + ], + [ + [ + 58, + 35, + 29 + ], + [ + 60, + 36, + 29 + ] + ], + [ + [ + 58, + 36, + 29 + ], + [ + 63, + 37, + 29 + ] + ], + [ + [ + 58, + 37, + 29 + ], + [ + 68, + 38, + 29 + ] + ], + [ + [ + 62, + 38, + 29 + ], + [ + 73, + 39, + 29 + ] + ], + [ + [ + 70, + 39, + 29 + ], + [ + 73, + 40, + 29 + ] + ], + [ + [ + 30, + 25, + 42 + ], + [ + 30, + 26, + 43 + ] + ], + [ + [ + 34, + 30, + 38 + ], + [ + 35, + 30, + 40 + ] + ], + [ + [ + 33, + 30, + 39 + ], + [ + 34, + 30, + 40 + ] + ], + [ + [ + 36, + 30, + 38 + ], + [ + 37, + 30, + 39 + ] + ], + [ + [ + 35, + 30, + 38 + ], + [ + 36, + 30, + 40 + ] + ], + [ + [ + 57, + 30, + 49 + ], + [ + 61, + 30, + 50 + ] + ], + [ + [ + 56, + 30, + 50 + ], + [ + 58, + 30, + 51 + ] + ], + [ + [ + 79, + 30, + 49 + ], + [ + 82, + 30, + 50 + ] + ], + [ + [ + 80, + 30, + 50 + ], + [ + 83, + 30, + 51 + ] + ], + [ + [ + 166, + 30, + 40 + ], + [ + 167, + 30, + 41 + ] + ], + [ + [ + 176, + 66, + 30 + ], + [ + 177, + 67, + 30 + ] + ], + [ + [ + 56, + 30, + 30 + ], + [ + 57, + 31, + 30 + ] + ], + [ + [ + 56, + 37, + 30 + ], + [ + 57, + 38, + 30 + ] + ], + [ + [ + 88, + 34, + 30 + ], + [ + 89, + 36, + 30 + ] + ], + [ + [ + 89, + 35, + 30 + ], + [ + 90, + 36, + 30 + ] + ], + [ + [ + 89, + 36, + 30 + ], + [ + 91, + 37, + 30 + ] + ], + [ + [ + 89, + 37, + 30 + ], + [ + 93, + 38, + 30 + ] + ], + [ + [ + 91, + 36, + 30 + ], + [ + 92, + 37, + 30 + ] + ], + [ + [ + 90, + 35, + 30 + ], + [ + 91, + 36, + 30 + ] + ], + [ + [ + 87, + 33, + 30 + ], + [ + 88, + 34, + 30 + ] + ], + [ + [ + 86, + 32, + 30 + ], + [ + 87, + 33, + 30 + ] + ], + [ + [ + 84, + 31, + 30 + ], + [ + 85, + 32, + 30 + ] + ], + [ + [ + 82, + 30, + 30 + ], + [ + 83, + 31, + 30 + ] + ], + [ + [ + 79, + 29, + 30 + ], + [ + 80, + 30, + 30 + ] + ], + [ + [ + 71, + 28, + 30 + ], + [ + 74, + 29, + 30 + ] + ], + [ + [ + 59, + 29, + 30 + ], + [ + 61, + 30, + 30 + ] + ], + [ + [ + 74, + 28, + 30 + ], + [ + 75, + 29, + 30 + ] + ], + [ + [ + 58, + 29, + 30 + ], + [ + 59, + 30, + 30 + ] + ], + [ + [ + 69, + 28, + 30 + ], + [ + 71, + 29, + 30 + ] + ], + [ + [ + 61, + 39, + 30 + ], + [ + 64, + 40, + 30 + ] + ], + [ + [ + 66, + 40, + 30 + ], + [ + 71, + 41, + 30 + ] + ], + [ + [ + 58, + 38, + 30 + ], + [ + 60, + 39, + 30 + ] + ], + [ + [ + 93, + 40, + 30 + ], + [ + 94, + 41, + 30 + ] + ], + [ + [ + 77, + 42, + 30 + ], + [ + 78, + 43, + 30 + ] + ], + [ + [ + 86, + 42, + 30 + ], + [ + 87, + 43, + 30 + ] + ], + [ + [ + 180, + 65, + 30 + ], + [ + 181, + 66, + 30 + ] + ], + [ + [ + 30, + 28, + 39 + ], + [ + 30, + 29, + 40 + ] + ], + [ + [ + 166, + 30, + 39 + ], + [ + 167, + 30, + 40 + ] + ], + [ + [ + 72, + 30, + 28 + ], + [ + 74, + 30, + 29 + ] + ], + [ + [ + 56, + 30, + 29 + ], + [ + 58, + 30, + 30 + ] + ], + [ + [ + 57, + 30, + 30 + ], + [ + 61, + 30, + 31 + ] + ], + [ + [ + 79, + 30, + 30 + ], + [ + 82, + 30, + 31 + ] + ], + [ + [ + 80, + 30, + 29 + ], + [ + 83, + 30, + 30 + ] + ], + [ + [ + 36, + 30, + 41 + ], + [ + 37, + 30, + 42 + ] + ], + [ + [ + 35, + 30, + 40 + ], + [ + 36, + 30, + 42 + ] + ], + [ + [ + 33, + 30, + 40 + ], + [ + 35, + 30, + 41 + ] + ], + [ + [ + 73, + 38, + 30 + ], + [ + 74, + 39, + 30 + ] + ], + [ + [ + 72, + 40, + 30 + ], + [ + 73, + 41, + 30 + ] + ], + [ + [ + 94, + 38, + 30 + ], + [ + 96, + 39, + 30 + ] + ], + [ + [ + 66, + 40, + 30 + ], + [ + 67, + 41, + 30 + ] + ], + [ + [ + 56, + 37, + 30 + ], + [ + 57, + 38, + 30 + ] + ], + [ + [ + 69, + 28, + 30 + ], + [ + 70, + 29, + 30 + ] + ], + [ + [ + 172, + 65, + 30 + ], + [ + 173, + 66, + 30 + ] + ], + [ + [ + 31, + 28, + 40 + ], + [ + 31, + 29, + 41 + ] + ], + [ + [ + 31, + 28, + 40 + ], + [ + 31, + 29, + 41 + ] + ], + [ + [ + 150, + 31, + 38 + ], + [ + 151, + 31, + 39 + ] + ], + [ + [ + 134, + 31, + 37 + ], + [ + 135, + 31, + 38 + ] + ], + [ + [ + 117, + 31, + 36 + ], + [ + 118, + 31, + 37 + ] + ], + [ + [ + 36, + 31, + 39 + ], + [ + 37, + 31, + 40 + ] + ], + [ + [ + 45, + 31, + 36 + ], + [ + 46, + 31, + 37 + ] + ], + [ + [ + 69, + 31, + 51 + ], + [ + 76, + 31, + 52 + ] + ], + [ + [ + 56, + 31, + 49 + ], + [ + 57, + 31, + 50 + ] + ], + [ + [ + 82, + 31, + 49 + ], + [ + 84, + 31, + 50 + ] + ], + [ + [ + 83, + 31, + 50 + ], + [ + 85, + 31, + 51 + ] + ], + [ + [ + 175, + 66, + 31 + ], + [ + 176, + 67, + 31 + ] + ], + [ + [ + 58, + 35, + 31 + ], + [ + 63, + 36, + 31 + ] + ], + [ + [ + 58, + 36, + 31 + ], + [ + 85, + 37, + 31 + ] + ], + [ + [ + 58, + 37, + 31 + ], + [ + 79, + 38, + 31 + ] + ], + [ + [ + 61, + 38, + 31 + ], + [ + 73, + 39, + 31 + ] + ], + [ + [ + 68, + 39, + 31 + ], + [ + 72, + 40, + 31 + ] + ], + [ + [ + 83, + 37, + 31 + ], + [ + 89, + 38, + 31 + ] + ], + [ + [ + 56, + 36, + 31 + ], + [ + 57, + 37, + 31 + ] + ], + [ + [ + 58, + 31, + 31 + ], + [ + 82, + 32, + 31 + ] + ], + [ + [ + 58, + 32, + 31 + ], + [ + 85, + 33, + 31 + ] + ], + [ + [ + 58, + 33, + 31 + ], + [ + 87, + 34, + 31 + ] + ], + [ + [ + 58, + 34, + 31 + ], + [ + 88, + 35, + 31 + ] + ], + [ + [ + 63, + 35, + 31 + ], + [ + 88, + 36, + 31 + ] + ], + [ + [ + 67, + 30, + 31 + ], + [ + 76, + 31, + 31 + ] + ], + [ + [ + 85, + 36, + 31 + ], + [ + 89, + 37, + 31 + ] + ], + [ + [ + 85, + 32, + 31 + ], + [ + 86, + 33, + 31 + ] + ], + [ + [ + 82, + 31, + 31 + ], + [ + 84, + 32, + 31 + ] + ], + [ + [ + 56, + 31, + 31 + ], + [ + 58, + 36, + 31 + ] + ], + [ + [ + 57, + 30, + 31 + ], + [ + 67, + 31, + 31 + ] + ], + [ + [ + 57, + 36, + 31 + ], + [ + 58, + 38, + 31 + ] + ], + [ + [ + 61, + 29, + 31 + ], + [ + 79, + 30, + 31 + ] + ], + [ + [ + 76, + 30, + 31 + ], + [ + 82, + 31, + 31 + ] + ], + [ + [ + 71, + 40, + 31 + ], + [ + 72, + 41, + 31 + ] + ], + [ + [ + 64, + 39, + 31 + ], + [ + 68, + 40, + 31 + ] + ], + [ + [ + 60, + 38, + 31 + ], + [ + 61, + 39, + 31 + ] + ], + [ + [ + 31, + 26, + 37 + ], + [ + 31, + 27, + 38 + ] + ], + [ + [ + 31, + 28, + 40 + ], + [ + 31, + 29, + 41 + ] + ], + [ + [ + 74, + 31, + 28 + ], + [ + 76, + 31, + 29 + ] + ], + [ + [ + 68, + 31, + 28 + ], + [ + 72, + 31, + 29 + ] + ], + [ + [ + 56, + 31, + 30 + ], + [ + 57, + 31, + 31 + ] + ], + [ + [ + 82, + 31, + 30 + ], + [ + 84, + 31, + 31 + ] + ], + [ + [ + 83, + 31, + 29 + ], + [ + 85, + 31, + 30 + ] + ], + [ + [ + 36, + 31, + 40 + ], + [ + 37, + 31, + 41 + ] + ], + [ + [ + 45, + 31, + 43 + ], + [ + 47, + 31, + 44 + ] + ], + [ + [ + 150, + 31, + 41 + ], + [ + 151, + 31, + 42 + ] + ], + [ + [ + 134, + 31, + 42 + ], + [ + 135, + 31, + 43 + ] + ], + [ + [ + 117, + 31, + 43 + ], + [ + 118, + 31, + 44 + ] + ], + [ + [ + 72, + 39, + 31 + ], + [ + 73, + 40, + 31 + ] + ], + [ + [ + 83, + 37, + 31 + ], + [ + 85, + 38, + 31 + ] + ], + [ + [ + 78, + 37, + 31 + ], + [ + 79, + 38, + 31 + ] + ], + [ + [ + 96, + 38, + 31 + ], + [ + 97, + 39, + 31 + ] + ], + [ + [ + 173, + 66, + 31 + ], + [ + 174, + 67, + 31 + ] + ], + [ + [ + 79, + 37, + 31 + ], + [ + 83, + 38, + 31 + ] + ], + [ + [ + 180, + 65, + 31 + ], + [ + 181, + 66, + 31 + ] + ], + [ + [ + 32, + 16, + 42 + ], + [ + 32, + 17, + 43 + ] + ], + [ + [ + 32, + 26, + 42 + ], + [ + 32, + 27, + 43 + ] + ], + [ + [ + 32, + 27, + 41 + ], + [ + 32, + 28, + 42 + ] + ], + [ + [ + 166, + 32, + 39 + ], + [ + 167, + 32, + 40 + ] + ], + [ + [ + 148, + 32, + 38 + ], + [ + 150, + 32, + 39 + ] + ], + [ + [ + 132, + 32, + 37 + ], + [ + 134, + 32, + 38 + ] + ], + [ + [ + 114, + 32, + 36 + ], + [ + 117, + 32, + 37 + ] + ], + [ + [ + 46, + 32, + 36 + ], + [ + 49, + 32, + 37 + ] + ], + [ + [ + 76, + 32, + 51 + ], + [ + 77, + 32, + 52 + ] + ], + [ + [ + 66, + 32, + 51 + ], + [ + 69, + 32, + 52 + ] + ], + [ + [ + 84, + 32, + 49 + ], + [ + 86, + 32, + 50 + ] + ], + [ + [ + 85, + 32, + 50 + ], + [ + 87, + 32, + 51 + ] + ], + [ + [ + 173, + 66, + 32 + ], + [ + 175, + 67, + 32 + ] + ], + [ + [ + 78, + 42, + 32 + ], + [ + 79, + 43, + 32 + ] + ], + [ + [ + 32, + 16, + 37 + ], + [ + 32, + 17, + 38 + ] + ], + [ + [ + 32, + 28, + 38 + ], + [ + 32, + 29, + 39 + ] + ], + [ + [ + 76, + 32, + 28 + ], + [ + 77, + 32, + 29 + ] + ], + [ + [ + 65, + 32, + 28 + ], + [ + 68, + 32, + 29 + ] + ], + [ + [ + 84, + 32, + 30 + ], + [ + 86, + 32, + 31 + ] + ], + [ + [ + 85, + 32, + 29 + ], + [ + 87, + 32, + 30 + ] + ], + [ + [ + 47, + 32, + 43 + ], + [ + 49, + 32, + 44 + ] + ], + [ + [ + 166, + 32, + 40 + ], + [ + 167, + 32, + 41 + ] + ], + [ + [ + 148, + 32, + 41 + ], + [ + 150, + 32, + 42 + ] + ], + [ + [ + 132, + 32, + 42 + ], + [ + 134, + 32, + 43 + ] + ], + [ + [ + 114, + 32, + 43 + ], + [ + 117, + 32, + 44 + ] + ], + [ + [ + 72, + 41, + 32 + ], + [ + 73, + 42, + 32 + ] + ], + [ + [ + 85, + 37, + 32 + ], + [ + 87, + 38, + 32 + ] + ], + [ + [ + 76, + 37, + 32 + ], + [ + 78, + 38, + 32 + ] + ], + [ + [ + 175, + 66, + 32 + ], + [ + 178, + 67, + 32 + ] + ], + [ + [ + 171, + 65, + 32 + ], + [ + 172, + 66, + 32 + ] + ], + [ + [ + 181, + 65, + 32 + ], + [ + 182, + 66, + 32 + ] + ], + [ + [ + 33, + 29, + 40 + ], + [ + 33, + 30, + 41 + ] + ], + [ + [ + 145, + 33, + 38 + ], + [ + 148, + 33, + 39 + ] + ], + [ + [ + 130, + 33, + 37 + ], + [ + 132, + 33, + 38 + ] + ], + [ + [ + 111, + 33, + 36 + ], + [ + 114, + 33, + 37 + ] + ], + [ + [ + 49, + 33, + 36 + ], + [ + 52, + 33, + 37 + ] + ], + [ + [ + 166, + 33, + 40 + ], + [ + 167, + 33, + 41 + ] + ], + [ + [ + 77, + 33, + 51 + ], + [ + 78, + 33, + 52 + ] + ], + [ + [ + 63, + 33, + 51 + ], + [ + 66, + 33, + 52 + ] + ], + [ + [ + 86, + 33, + 49 + ], + [ + 87, + 33, + 50 + ] + ], + [ + [ + 87, + 33, + 50 + ], + [ + 88, + 33, + 51 + ] + ], + [ + [ + 175, + 66, + 33 + ], + [ + 179, + 67, + 33 + ] + ], + [ + [ + 85, + 42, + 33 + ], + [ + 86, + 43, + 33 + ] + ], + [ + [ + 33, + 29, + 39 + ], + [ + 33, + 30, + 40 + ] + ], + [ + [ + 33, + 27, + 37 + ], + [ + 33, + 28, + 38 + ] + ], + [ + [ + 77, + 33, + 28 + ], + [ + 78, + 33, + 29 + ] + ], + [ + [ + 63, + 33, + 28 + ], + [ + 65, + 33, + 29 + ] + ], + [ + [ + 86, + 33, + 30 + ], + [ + 87, + 33, + 31 + ] + ], + [ + [ + 87, + 33, + 29 + ], + [ + 88, + 33, + 30 + ] + ], + [ + [ + 49, + 33, + 43 + ], + [ + 52, + 33, + 44 + ] + ], + [ + [ + 166, + 33, + 39 + ], + [ + 167, + 33, + 40 + ] + ], + [ + [ + 145, + 33, + 41 + ], + [ + 148, + 33, + 42 + ] + ], + [ + [ + 130, + 33, + 42 + ], + [ + 132, + 33, + 43 + ] + ], + [ + [ + 112, + 33, + 43 + ], + [ + 114, + 33, + 44 + ] + ], + [ + [ + 72, + 38, + 33 + ], + [ + 73, + 39, + 33 + ] + ], + [ + [ + 87, + 37, + 33 + ], + [ + 89, + 38, + 33 + ] + ], + [ + [ + 75, + 37, + 33 + ], + [ + 76, + 38, + 33 + ] + ], + [ + [ + 178, + 66, + 33 + ], + [ + 180, + 67, + 33 + ] + ], + [ + [ + 34, + 28, + 41 + ], + [ + 34, + 29, + 42 + ] + ], + [ + [ + 34, + 27, + 42 + ], + [ + 34, + 28, + 43 + ] + ], + [ + [ + 34, + 15, + 41 + ], + [ + 34, + 16, + 42 + ] + ], + [ + [ + 140, + 34, + 38 + ], + [ + 145, + 34, + 39 + ] + ], + [ + [ + 55, + 34, + 36 + ], + [ + 110, + 34, + 37 + ] + ], + [ + [ + 125, + 34, + 37 + ], + [ + 130, + 34, + 38 + ] + ], + [ + [ + 110, + 34, + 36 + ], + [ + 111, + 34, + 37 + ] + ], + [ + [ + 52, + 34, + 36 + ], + [ + 53, + 34, + 37 + ] + ], + [ + [ + 53, + 34, + 36 + ], + [ + 55, + 34, + 37 + ] + ], + [ + [ + 78, + 34, + 51 + ], + [ + 79, + 34, + 52 + ] + ], + [ + [ + 61, + 34, + 51 + ], + [ + 63, + 34, + 52 + ] + ], + [ + [ + 87, + 34, + 49 + ], + [ + 88, + 34, + 50 + ] + ], + [ + [ + 88, + 34, + 50 + ], + [ + 89, + 34, + 51 + ] + ], + [ + [ + 180, + 66, + 34 + ], + [ + 181, + 67, + 34 + ] + ], + [ + [ + 179, + 66, + 34 + ], + [ + 180, + 67, + 34 + ] + ], + [ + [ + 90, + 41, + 34 + ], + [ + 91, + 42, + 34 + ] + ], + [ + [ + 96, + 38, + 34 + ], + [ + 97, + 39, + 34 + ] + ], + [ + [ + 34, + 15, + 38 + ], + [ + 34, + 16, + 39 + ] + ], + [ + [ + 34, + 29, + 38 + ], + [ + 34, + 30, + 39 + ] + ], + [ + [ + 78, + 34, + 28 + ], + [ + 79, + 34, + 29 + ] + ], + [ + [ + 61, + 34, + 28 + ], + [ + 63, + 34, + 29 + ] + ], + [ + [ + 87, + 34, + 30 + ], + [ + 88, + 34, + 31 + ] + ], + [ + [ + 88, + 34, + 29 + ], + [ + 89, + 34, + 30 + ] + ], + [ + [ + 55, + 34, + 43 + ], + [ + 110, + 34, + 44 + ] + ], + [ + [ + 52, + 34, + 43 + ], + [ + 53, + 34, + 44 + ] + ], + [ + [ + 53, + 34, + 43 + ], + [ + 55, + 34, + 44 + ] + ], + [ + [ + 140, + 34, + 41 + ], + [ + 145, + 34, + 42 + ] + ], + [ + [ + 125, + 34, + 42 + ], + [ + 130, + 34, + 43 + ] + ], + [ + [ + 110, + 34, + 43 + ], + [ + 112, + 34, + 44 + ] + ], + [ + [ + 71, + 39, + 34 + ], + [ + 72, + 40, + 34 + ] + ], + [ + [ + 89, + 37, + 34 + ], + [ + 91, + 38, + 34 + ] + ], + [ + [ + 74, + 37, + 34 + ], + [ + 75, + 38, + 34 + ] + ], + [ + [ + 69, + 18, + 34 + ], + [ + 93, + 19, + 34 + ] + ], + [ + [ + 70, + 19, + 34 + ], + [ + 90, + 20, + 34 + ] + ], + [ + [ + 90, + 17, + 34 + ], + [ + 95, + 18, + 34 + ] + ], + [ + [ + 69, + 17, + 34 + ], + [ + 90, + 18, + 34 + ] + ], + [ + [ + 70, + 16, + 34 + ], + [ + 95, + 17, + 34 + ] + ], + [ + [ + 74, + 15, + 34 + ], + [ + 93, + 16, + 34 + ] + ], + [ + [ + 180, + 66, + 34 + ], + [ + 181, + 67, + 34 + ] + ], + [ + [ + 177, + 66, + 34 + ], + [ + 180, + 67, + 34 + ] + ], + [ + [ + 170, + 65, + 34 + ], + [ + 171, + 66, + 34 + ] + ], + [ + [ + 35, + 29, + 41 + ], + [ + 35, + 30, + 42 + ] + ], + [ + [ + 35, + 28, + 42 + ], + [ + 35, + 29, + 43 + ] + ], + [ + [ + 134, + 35, + 38 + ], + [ + 140, + 35, + 39 + ] + ], + [ + [ + 139, + 35, + 39 + ], + [ + 145, + 35, + 40 + ] + ], + [ + [ + 121, + 35, + 37 + ], + [ + 125, + 35, + 38 + ] + ], + [ + [ + 167, + 35, + 40 + ], + [ + 168, + 35, + 41 + ] + ], + [ + [ + 79, + 35, + 51 + ], + [ + 80, + 35, + 52 + ] + ], + [ + [ + 60, + 35, + 51 + ], + [ + 61, + 35, + 52 + ] + ], + [ + [ + 89, + 35, + 50 + ], + [ + 91, + 35, + 51 + ] + ], + [ + [ + 177, + 66, + 35 + ], + [ + 180, + 67, + 35 + ] + ], + [ + [ + 79, + 42, + 35 + ], + [ + 80, + 43, + 35 + ] + ], + [ + [ + 84, + 42, + 35 + ], + [ + 85, + 43, + 35 + ] + ], + [ + [ + 35, + 28, + 37 + ], + [ + 35, + 29, + 38 + ] + ], + [ + [ + 79, + 35, + 28 + ], + [ + 80, + 35, + 29 + ] + ], + [ + [ + 60, + 35, + 28 + ], + [ + 61, + 35, + 29 + ] + ], + [ + [ + 89, + 35, + 29 + ], + [ + 91, + 35, + 30 + ] + ], + [ + [ + 167, + 35, + 39 + ], + [ + 168, + 35, + 40 + ] + ], + [ + [ + 139, + 35, + 40 + ], + [ + 145, + 35, + 41 + ] + ], + [ + [ + 134, + 35, + 41 + ], + [ + 140, + 35, + 42 + ] + ], + [ + [ + 121, + 35, + 42 + ], + [ + 125, + 35, + 43 + ] + ], + [ + [ + 71, + 40, + 35 + ], + [ + 72, + 41, + 35 + ] + ], + [ + [ + 91, + 37, + 35 + ], + [ + 93, + 38, + 35 + ] + ], + [ + [ + 73, + 37, + 35 + ], + [ + 74, + 38, + 35 + ] + ], + [ + [ + 97, + 16, + 35 + ], + [ + 98, + 17, + 35 + ] + ], + [ + [ + 93, + 18, + 35 + ], + [ + 96, + 19, + 35 + ] + ], + [ + [ + 95, + 17, + 35 + ], + [ + 97, + 18, + 35 + ] + ], + [ + [ + 90, + 19, + 35 + ], + [ + 92, + 20, + 35 + ] + ], + [ + [ + 70, + 20, + 35 + ], + [ + 87, + 21, + 35 + ] + ], + [ + [ + 66, + 18, + 35 + ], + [ + 69, + 19, + 35 + ] + ], + [ + [ + 66, + 19, + 35 + ], + [ + 70, + 20, + 35 + ] + ], + [ + [ + 76, + 14, + 35 + ], + [ + 96, + 15, + 35 + ] + ], + [ + [ + 93, + 15, + 35 + ], + [ + 98, + 16, + 35 + ] + ], + [ + [ + 95, + 16, + 35 + ], + [ + 97, + 17, + 35 + ] + ], + [ + [ + 65, + 17, + 35 + ], + [ + 69, + 18, + 35 + ] + ], + [ + [ + 67, + 16, + 35 + ], + [ + 70, + 17, + 35 + ] + ], + [ + [ + 69, + 15, + 35 + ], + [ + 74, + 16, + 35 + ] + ], + [ + [ + 72, + 14, + 35 + ], + [ + 76, + 15, + 35 + ] + ], + [ + [ + 173, + 66, + 35 + ], + [ + 177, + 67, + 35 + ] + ], + [ + [ + 36, + 30, + 40 + ], + [ + 36, + 31, + 41 + ] + ], + [ + [ + 36, + 24, + 43 + ], + [ + 36, + 25, + 44 + ] + ], + [ + [ + 130, + 36, + 38 + ], + [ + 134, + 36, + 39 + ] + ], + [ + [ + 131, + 36, + 39 + ], + [ + 139, + 36, + 40 + ] + ], + [ + [ + 126, + 36, + 38 + ], + [ + 130, + 36, + 39 + ] + ], + [ + [ + 114, + 36, + 37 + ], + [ + 121, + 36, + 38 + ] + ], + [ + [ + 79, + 36, + 28 + ], + [ + 80, + 36, + 29 + ] + ], + [ + [ + 60, + 36, + 28 + ], + [ + 63, + 36, + 29 + ] + ], + [ + [ + 48, + 36, + 37 + ], + [ + 52, + 36, + 38 + ] + ], + [ + [ + 47, + 36, + 38 + ], + [ + 49, + 36, + 39 + ] + ], + [ + [ + 46, + 36, + 39 + ], + [ + 48, + 36, + 40 + ] + ], + [ + [ + 145, + 36, + 39 + ], + [ + 146, + 36, + 40 + ] + ], + [ + [ + 88, + 36, + 49 + ], + [ + 89, + 36, + 50 + ] + ], + [ + [ + 91, + 36, + 50 + ], + [ + 92, + 36, + 51 + ] + ], + [ + [ + 174, + 66, + 36 + ], + [ + 177, + 67, + 36 + ] + ], + [ + [ + 36, + 30, + 39 + ], + [ + 36, + 31, + 40 + ] + ], + [ + [ + 36, + 24, + 36 + ], + [ + 36, + 25, + 37 + ] + ], + [ + [ + 88, + 36, + 30 + ], + [ + 89, + 36, + 31 + ] + ], + [ + [ + 91, + 36, + 29 + ], + [ + 92, + 36, + 30 + ] + ], + [ + [ + 46, + 36, + 40 + ], + [ + 48, + 36, + 41 + ] + ], + [ + [ + 47, + 36, + 41 + ], + [ + 49, + 36, + 42 + ] + ], + [ + [ + 48, + 36, + 42 + ], + [ + 52, + 36, + 43 + ] + ], + [ + [ + 145, + 36, + 40 + ], + [ + 146, + 36, + 41 + ] + ], + [ + [ + 78, + 36, + 51 + ], + [ + 80, + 36, + 52 + ] + ], + [ + [ + 60, + 36, + 51 + ], + [ + 64, + 36, + 52 + ] + ], + [ + [ + 131, + 36, + 40 + ], + [ + 139, + 36, + 41 + ] + ], + [ + [ + 130, + 36, + 41 + ], + [ + 134, + 36, + 42 + ] + ], + [ + [ + 126, + 36, + 41 + ], + [ + 130, + 36, + 42 + ] + ], + [ + [ + 114, + 36, + 42 + ], + [ + 121, + 36, + 43 + ] + ], + [ + [ + 49, + 19, + 36 + ], + [ + 65, + 20, + 36 + ] + ], + [ + [ + 49, + 20, + 36 + ], + [ + 53, + 26, + 36 + ] + ], + [ + [ + 50, + 26, + 36 + ], + [ + 53, + 27, + 36 + ] + ], + [ + [ + 55, + 18, + 36 + ], + [ + 64, + 19, + 36 + ] + ], + [ + [ + 55, + 20, + 36 + ], + [ + 67, + 21, + 36 + ] + ], + [ + [ + 55, + 21, + 36 + ], + [ + 110, + 34, + 36 + ] + ], + [ + [ + 88, + 20, + 36 + ], + [ + 110, + 21, + 36 + ] + ], + [ + [ + 94, + 19, + 36 + ], + [ + 110, + 20, + 36 + ] + ], + [ + [ + 97, + 18, + 36 + ], + [ + 110, + 19, + 36 + ] + ], + [ + [ + 49, + 18, + 36 + ], + [ + 53, + 19, + 36 + ] + ], + [ + [ + 53, + 18, + 36 + ], + [ + 55, + 19, + 36 + ] + ], + [ + [ + 72, + 37, + 36 + ], + [ + 73, + 38, + 36 + ] + ], + [ + [ + 71, + 38, + 36 + ], + [ + 72, + 39, + 36 + ] + ], + [ + [ + 93, + 37, + 36 + ], + [ + 95, + 38, + 36 + ] + ], + [ + [ + 97, + 17, + 36 + ], + [ + 99, + 18, + 36 + ] + ], + [ + [ + 98, + 16, + 36 + ], + [ + 100, + 17, + 36 + ] + ], + [ + [ + 96, + 18, + 36 + ], + [ + 97, + 19, + 36 + ] + ], + [ + [ + 92, + 19, + 36 + ], + [ + 94, + 20, + 36 + ] + ], + [ + [ + 87, + 20, + 36 + ], + [ + 88, + 21, + 36 + ] + ], + [ + [ + 67, + 20, + 36 + ], + [ + 70, + 21, + 36 + ] + ], + [ + [ + 64, + 18, + 36 + ], + [ + 66, + 19, + 36 + ] + ], + [ + [ + 65, + 19, + 36 + ], + [ + 66, + 20, + 36 + ] + ], + [ + [ + 98, + 15, + 36 + ], + [ + 100, + 16, + 36 + ] + ], + [ + [ + 63, + 17, + 36 + ], + [ + 65, + 18, + 36 + ] + ], + [ + [ + 64, + 16, + 36 + ], + [ + 67, + 17, + 36 + ] + ], + [ + [ + 96, + 14, + 36 + ], + [ + 98, + 15, + 36 + ] + ], + [ + [ + 76, + 13, + 36 + ], + [ + 96, + 14, + 36 + ] + ], + [ + [ + 72, + 13, + 36 + ], + [ + 75, + 14, + 36 + ] + ], + [ + [ + 69, + 14, + 36 + ], + [ + 72, + 15, + 36 + ] + ], + [ + [ + 67, + 15, + 36 + ], + [ + 69, + 16, + 36 + ] + ], + [ + [ + 110, + 18, + 36 + ], + [ + 111, + 34, + 36 + ] + ], + [ + [ + 111, + 19, + 36 + ], + [ + 112, + 20, + 36 + ] + ], + [ + [ + 111, + 20, + 36 + ], + [ + 113, + 21, + 36 + ] + ], + [ + [ + 111, + 21, + 36 + ], + [ + 116, + 22, + 36 + ] + ], + [ + [ + 111, + 22, + 36 + ], + [ + 117, + 32, + 36 + ] + ], + [ + [ + 111, + 32, + 36 + ], + [ + 114, + 33, + 36 + ] + ], + [ + [ + 117, + 23, + 36 + ], + [ + 118, + 31, + 36 + ] + ], + [ + [ + 118, + 24, + 36 + ], + [ + 119, + 29, + 36 + ] + ], + [ + [ + 119, + 25, + 36 + ], + [ + 120, + 27, + 36 + ] + ], + [ + [ + 171, + 66, + 36 + ], + [ + 173, + 67, + 36 + ] + ], + [ + [ + 38, + 25, + 36 + ], + [ + 41, + 26, + 36 + ] + ], + [ + [ + 38, + 26, + 36 + ], + [ + 50, + 27, + 36 + ] + ], + [ + [ + 43, + 27, + 36 + ], + [ + 53, + 29, + 36 + ] + ], + [ + [ + 44, + 29, + 36 + ], + [ + 53, + 30, + 36 + ] + ], + [ + [ + 45, + 30, + 36 + ], + [ + 53, + 31, + 36 + ] + ], + [ + [ + 46, + 31, + 36 + ], + [ + 53, + 32, + 36 + ] + ], + [ + [ + 49, + 32, + 36 + ], + [ + 53, + 33, + 36 + ] + ], + [ + [ + 52, + 33, + 36 + ], + [ + 53, + 34, + 36 + ] + ], + [ + [ + 37, + 25, + 36 + ], + [ + 38, + 26, + 36 + ] + ], + [ + [ + 53, + 20, + 36 + ], + [ + 55, + 34, + 36 + ] + ], + [ + [ + 36, + 24, + 36 + ], + [ + 49, + 25, + 36 + ] + ], + [ + [ + 37, + 23, + 36 + ], + [ + 49, + 24, + 36 + ] + ], + [ + [ + 39, + 22, + 36 + ], + [ + 49, + 23, + 36 + ] + ], + [ + [ + 41, + 25, + 36 + ], + [ + 49, + 26, + 36 + ] + ], + [ + [ + 42, + 21, + 36 + ], + [ + 49, + 22, + 36 + ] + ], + [ + [ + 44, + 20, + 36 + ], + [ + 49, + 21, + 36 + ] + ], + [ + [ + 45, + 19, + 36 + ], + [ + 49, + 20, + 36 + ] + ], + [ + [ + 169, + 65, + 36 + ], + [ + 170, + 66, + 36 + ] + ], + [ + [ + 176, + 64, + 36 + ], + [ + 177, + 65, + 36 + ] + ], + [ + [ + 37, + 30, + 41 + ], + [ + 37, + 31, + 42 + ] + ], + [ + [ + 37, + 29, + 42 + ], + [ + 37, + 30, + 43 + ] + ], + [ + [ + 37, + 25, + 43 + ], + [ + 37, + 26, + 44 + ] + ], + [ + [ + 37, + 23, + 43 + ], + [ + 37, + 24, + 44 + ] + ], + [ + [ + 130, + 37, + 39 + ], + [ + 131, + 37, + 40 + ] + ], + [ + [ + 106, + 37, + 37 + ], + [ + 110, + 37, + 38 + ] + ], + [ + [ + 116, + 37, + 38 + ], + [ + 126, + 37, + 39 + ] + ], + [ + [ + 120, + 37, + 39 + ], + [ + 130, + 37, + 40 + ] + ], + [ + [ + 110, + 37, + 37 + ], + [ + 114, + 37, + 38 + ] + ], + [ + [ + 56, + 37, + 29 + ], + [ + 57, + 37, + 30 + ] + ], + [ + [ + 56, + 37, + 30 + ], + [ + 57, + 37, + 31 + ] + ], + [ + [ + 77, + 37, + 28 + ], + [ + 79, + 37, + 29 + ] + ], + [ + [ + 63, + 37, + 28 + ], + [ + 68, + 37, + 29 + ] + ], + [ + [ + 55, + 37, + 37 + ], + [ + 56, + 37, + 38 + ] + ], + [ + [ + 49, + 37, + 38 + ], + [ + 52, + 37, + 39 + ] + ], + [ + [ + 48, + 37, + 39 + ], + [ + 51, + 37, + 40 + ] + ], + [ + [ + 52, + 37, + 37 + ], + [ + 53, + 37, + 38 + ] + ], + [ + [ + 53, + 37, + 37 + ], + [ + 55, + 37, + 38 + ] + ], + [ + [ + 146, + 37, + 39 + ], + [ + 147, + 37, + 40 + ] + ], + [ + [ + 168, + 37, + 40 + ], + [ + 169, + 37, + 41 + ] + ], + [ + [ + 72, + 37, + 43 + ], + [ + 73, + 37, + 44 + ] + ], + [ + [ + 73, + 37, + 43 + ], + [ + 93, + 37, + 45 + ] + ], + [ + [ + 93, + 37, + 43 + ], + [ + 95, + 37, + 44 + ] + ], + [ + [ + 74, + 37, + 45 + ], + [ + 91, + 37, + 46 + ] + ], + [ + [ + 75, + 37, + 46 + ], + [ + 89, + 37, + 47 + ] + ], + [ + [ + 76, + 37, + 47 + ], + [ + 87, + 37, + 48 + ] + ], + [ + [ + 78, + 37, + 48 + ], + [ + 85, + 37, + 49 + ] + ], + [ + [ + 89, + 37, + 49 + ], + [ + 90, + 37, + 50 + ] + ], + [ + [ + 92, + 37, + 50 + ], + [ + 93, + 37, + 51 + ] + ], + [ + [ + 81, + 42, + 37 + ], + [ + 82, + 43, + 37 + ] + ], + [ + [ + 83, + 42, + 37 + ], + [ + 84, + 43, + 37 + ] + ], + [ + [ + 100, + 35, + 37 + ], + [ + 101, + 36, + 37 + ] + ], + [ + [ + 96, + 13, + 37 + ], + [ + 97, + 14, + 37 + ] + ], + [ + [ + 88, + 12, + 37 + ], + [ + 90, + 13, + 37 + ] + ], + [ + [ + 80, + 42, + 37 + ], + [ + 81, + 43, + 37 + ] + ], + [ + [ + 63, + 16, + 37 + ], + [ + 64, + 17, + 37 + ] + ], + [ + [ + 37, + 30, + 38 + ], + [ + 37, + 31, + 39 + ] + ], + [ + [ + 37, + 29, + 37 + ], + [ + 37, + 30, + 38 + ] + ], + [ + [ + 37, + 25, + 36 + ], + [ + 37, + 26, + 37 + ] + ], + [ + [ + 37, + 23, + 36 + ], + [ + 37, + 24, + 37 + ] + ], + [ + [ + 72, + 37, + 36 + ], + [ + 73, + 37, + 37 + ] + ], + [ + [ + 78, + 37, + 31 + ], + [ + 85, + 37, + 32 + ] + ], + [ + [ + 76, + 37, + 32 + ], + [ + 87, + 37, + 33 + ] + ], + [ + [ + 75, + 37, + 33 + ], + [ + 89, + 37, + 34 + ] + ], + [ + [ + 74, + 37, + 34 + ], + [ + 91, + 37, + 35 + ] + ], + [ + [ + 73, + 37, + 35 + ], + [ + 93, + 37, + 37 + ] + ], + [ + [ + 93, + 37, + 36 + ], + [ + 95, + 37, + 37 + ] + ], + [ + [ + 92, + 37, + 29 + ], + [ + 93, + 37, + 30 + ] + ], + [ + [ + 107, + 37, + 42 + ], + [ + 110, + 37, + 43 + ] + ], + [ + [ + 55, + 37, + 42 + ], + [ + 56, + 37, + 43 + ] + ], + [ + [ + 48, + 37, + 40 + ], + [ + 51, + 37, + 41 + ] + ], + [ + [ + 49, + 37, + 41 + ], + [ + 52, + 37, + 42 + ] + ], + [ + [ + 52, + 37, + 42 + ], + [ + 53, + 37, + 43 + ] + ], + [ + [ + 53, + 37, + 42 + ], + [ + 55, + 37, + 43 + ] + ], + [ + [ + 168, + 37, + 39 + ], + [ + 169, + 37, + 40 + ] + ], + [ + [ + 146, + 37, + 40 + ], + [ + 147, + 37, + 41 + ] + ], + [ + [ + 56, + 37, + 50 + ], + [ + 57, + 37, + 51 + ] + ], + [ + [ + 56, + 37, + 49 + ], + [ + 57, + 37, + 50 + ] + ], + [ + [ + 77, + 37, + 51 + ], + [ + 78, + 37, + 52 + ] + ], + [ + [ + 64, + 37, + 51 + ], + [ + 68, + 37, + 52 + ] + ], + [ + [ + 130, + 37, + 40 + ], + [ + 131, + 37, + 41 + ] + ], + [ + [ + 120, + 37, + 40 + ], + [ + 130, + 37, + 41 + ] + ], + [ + [ + 116, + 37, + 41 + ], + [ + 126, + 37, + 42 + ] + ], + [ + [ + 110, + 37, + 42 + ], + [ + 114, + 37, + 43 + ] + ], + [ + [ + 49, + 15, + 37 + ], + [ + 53, + 18, + 37 + ] + ], + [ + [ + 53, + 15, + 37 + ], + [ + 54, + 16, + 37 + ] + ], + [ + [ + 53, + 16, + 37 + ], + [ + 55, + 18, + 37 + ] + ], + [ + [ + 110, + 16, + 37 + ], + [ + 117, + 17, + 37 + ] + ], + [ + [ + 110, + 17, + 37 + ], + [ + 121, + 18, + 37 + ] + ], + [ + [ + 110, + 34, + 37 + ], + [ + 125, + 35, + 37 + ] + ], + [ + [ + 110, + 35, + 37 + ], + [ + 121, + 36, + 37 + ] + ], + [ + [ + 110, + 36, + 37 + ], + [ + 114, + 37, + 37 + ] + ], + [ + [ + 111, + 18, + 37 + ], + [ + 118, + 19, + 37 + ] + ], + [ + [ + 111, + 33, + 37 + ], + [ + 130, + 34, + 37 + ] + ], + [ + [ + 112, + 19, + 37 + ], + [ + 123, + 20, + 37 + ] + ], + [ + [ + 113, + 20, + 37 + ], + [ + 127, + 21, + 37 + ] + ], + [ + [ + 114, + 32, + 37 + ], + [ + 130, + 33, + 37 + ] + ], + [ + [ + 116, + 21, + 37 + ], + [ + 129, + 22, + 37 + ] + ], + [ + [ + 117, + 22, + 37 + ], + [ + 130, + 23, + 37 + ] + ], + [ + [ + 117, + 31, + 37 + ], + [ + 130, + 32, + 37 + ] + ], + [ + [ + 118, + 23, + 37 + ], + [ + 130, + 24, + 37 + ] + ], + [ + [ + 118, + 29, + 37 + ], + [ + 130, + 31, + 37 + ] + ], + [ + [ + 119, + 24, + 37 + ], + [ + 130, + 25, + 37 + ] + ], + [ + [ + 119, + 27, + 37 + ], + [ + 130, + 29, + 37 + ] + ], + [ + [ + 120, + 25, + 37 + ], + [ + 130, + 27, + 37 + ] + ], + [ + [ + 99, + 17, + 37 + ], + [ + 110, + 18, + 37 + ] + ], + [ + [ + 101, + 16, + 37 + ], + [ + 110, + 17, + 37 + ] + ], + [ + [ + 130, + 22, + 37 + ], + [ + 131, + 23, + 37 + ] + ], + [ + [ + 130, + 23, + 37 + ], + [ + 132, + 33, + 37 + ] + ], + [ + [ + 132, + 24, + 37 + ], + [ + 133, + 25, + 37 + ] + ], + [ + [ + 132, + 25, + 37 + ], + [ + 134, + 32, + 37 + ] + ], + [ + [ + 134, + 27, + 37 + ], + [ + 135, + 31, + 37 + ] + ], + [ + [ + 73, + 35, + 37 + ], + [ + 102, + 36, + 37 + ] + ], + [ + [ + 73, + 36, + 37 + ], + [ + 110, + 37, + 37 + ] + ], + [ + [ + 103, + 37, + 37 + ], + [ + 106, + 38, + 37 + ] + ], + [ + [ + 95, + 37, + 37 + ], + [ + 97, + 38, + 37 + ] + ], + [ + [ + 55, + 34, + 37 + ], + [ + 110, + 35, + 37 + ] + ], + [ + [ + 55, + 35, + 37 + ], + [ + 72, + 36, + 37 + ] + ], + [ + [ + 55, + 36, + 37 + ], + [ + 67, + 37, + 37 + ] + ], + [ + [ + 56, + 37, + 37 + ], + [ + 67, + 38, + 37 + ] + ], + [ + [ + 62, + 38, + 37 + ], + [ + 67, + 39, + 37 + ] + ], + [ + [ + 102, + 35, + 37 + ], + [ + 110, + 36, + 37 + ] + ], + [ + [ + 67, + 36, + 37 + ], + [ + 72, + 38, + 37 + ] + ], + [ + [ + 67, + 38, + 37 + ], + [ + 71, + 39, + 37 + ] + ], + [ + [ + 72, + 35, + 37 + ], + [ + 73, + 37, + 37 + ] + ], + [ + [ + 100, + 16, + 37 + ], + [ + 101, + 17, + 37 + ] + ], + [ + [ + 100, + 15, + 37 + ], + [ + 101, + 16, + 37 + ] + ], + [ + [ + 63, + 16, + 37 + ], + [ + 64, + 17, + 37 + ] + ], + [ + [ + 96, + 13, + 37 + ], + [ + 97, + 14, + 37 + ] + ], + [ + [ + 98, + 14, + 37 + ], + [ + 100, + 15, + 37 + ] + ], + [ + [ + 88, + 12, + 37 + ], + [ + 90, + 13, + 37 + ] + ], + [ + [ + 75, + 13, + 37 + ], + [ + 76, + 14, + 37 + ] + ], + [ + [ + 71, + 13, + 37 + ], + [ + 72, + 14, + 37 + ] + ], + [ + [ + 65, + 15, + 37 + ], + [ + 67, + 16, + 37 + ] + ], + [ + [ + 67, + 14, + 37 + ], + [ + 69, + 15, + 37 + ] + ], + [ + [ + 174, + 66, + 37 + ], + [ + 176, + 67, + 37 + ] + ], + [ + [ + 25, + 19, + 37 + ], + [ + 26, + 23, + 37 + ] + ], + [ + [ + 26, + 18, + 37 + ], + [ + 35, + 24, + 37 + ] + ], + [ + [ + 27, + 24, + 37 + ], + [ + 35, + 25, + 37 + ] + ], + [ + [ + 28, + 17, + 37 + ], + [ + 35, + 18, + 37 + ] + ], + [ + [ + 29, + 25, + 37 + ], + [ + 35, + 26, + 37 + ] + ], + [ + [ + 31, + 26, + 37 + ], + [ + 35, + 27, + 37 + ] + ], + [ + [ + 32, + 16, + 37 + ], + [ + 35, + 17, + 37 + ] + ], + [ + [ + 33, + 27, + 37 + ], + [ + 35, + 28, + 37 + ] + ], + [ + [ + 37, + 26, + 37 + ], + [ + 38, + 28, + 37 + ] + ], + [ + [ + 46, + 32, + 37 + ], + [ + 49, + 33, + 37 + ] + ], + [ + [ + 47, + 33, + 37 + ], + [ + 52, + 35, + 37 + ] + ], + [ + [ + 48, + 35, + 37 + ], + [ + 52, + 36, + 37 + ] + ], + [ + [ + 52, + 34, + 37 + ], + [ + 53, + 37, + 37 + ] + ], + [ + [ + 45, + 31, + 37 + ], + [ + 46, + 32, + 37 + ] + ], + [ + [ + 35, + 24, + 37 + ], + [ + 36, + 25, + 37 + ] + ], + [ + [ + 35, + 25, + 37 + ], + [ + 37, + 29, + 37 + ] + ], + [ + [ + 53, + 34, + 37 + ], + [ + 55, + 37, + 37 + ] + ], + [ + [ + 35, + 16, + 37 + ], + [ + 49, + 19, + 37 + ] + ], + [ + [ + 35, + 19, + 37 + ], + [ + 45, + 20, + 37 + ] + ], + [ + [ + 35, + 20, + 37 + ], + [ + 44, + 21, + 37 + ] + ], + [ + [ + 35, + 21, + 37 + ], + [ + 42, + 22, + 37 + ] + ], + [ + [ + 35, + 22, + 37 + ], + [ + 39, + 23, + 37 + ] + ], + [ + [ + 35, + 23, + 37 + ], + [ + 37, + 24, + 37 + ] + ], + [ + [ + 55, + 16, + 37 + ], + [ + 64, + 17, + 37 + ] + ], + [ + [ + 55, + 17, + 37 + ], + [ + 63, + 18, + 37 + ] + ], + [ + [ + 102, + 37, + 37 + ], + [ + 103, + 38, + 37 + ] + ], + [ + [ + 97, + 37, + 37 + ], + [ + 102, + 38, + 37 + ] + ], + [ + [ + 118, + 18, + 37 + ], + [ + 124, + 19, + 37 + ] + ], + [ + [ + 123, + 19, + 37 + ], + [ + 126, + 20, + 37 + ] + ], + [ + [ + 127, + 20, + 37 + ], + [ + 128, + 21, + 37 + ] + ], + [ + [ + 173, + 64, + 37 + ], + [ + 176, + 65, + 37 + ] + ], + [ + [ + 38, + 26, + 43 + ], + [ + 38, + 27, + 44 + ] + ], + [ + [ + 106, + 38, + 38 + ], + [ + 109, + 38, + 39 + ] + ], + [ + [ + 109, + 38, + 38 + ], + [ + 110, + 38, + 40 + ] + ], + [ + [ + 103, + 38, + 37 + ], + [ + 106, + 38, + 38 + ] + ], + [ + [ + 96, + 38, + 37 + ], + [ + 97, + 38, + 38 + ] + ], + [ + [ + 110, + 38, + 38 + ], + [ + 116, + 38, + 40 + ] + ], + [ + [ + 116, + 38, + 39 + ], + [ + 120, + 38, + 40 + ] + ], + [ + [ + 57, + 38, + 29 + ], + [ + 58, + 38, + 31 + ] + ], + [ + [ + 58, + 38, + 30 + ], + [ + 60, + 38, + 31 + ] + ], + [ + [ + 68, + 38, + 28 + ], + [ + 73, + 38, + 29 + ] + ], + [ + [ + 96, + 38, + 34 + ], + [ + 97, + 38, + 37 + ] + ], + [ + [ + 56, + 38, + 37 + ], + [ + 62, + 38, + 38 + ] + ], + [ + [ + 52, + 38, + 38 + ], + [ + 53, + 38, + 40 + ] + ], + [ + [ + 51, + 38, + 39 + ], + [ + 52, + 38, + 40 + ] + ], + [ + [ + 53, + 38, + 38 + ], + [ + 54, + 38, + 40 + ] + ], + [ + [ + 54, + 38, + 38 + ], + [ + 55, + 38, + 39 + ] + ], + [ + [ + 101, + 38, + 37 + ], + [ + 103, + 38, + 38 + ] + ], + [ + [ + 97, + 38, + 37 + ], + [ + 101, + 38, + 38 + ] + ], + [ + [ + 147, + 38, + 39 + ], + [ + 148, + 38, + 40 + ] + ], + [ + [ + 73, + 38, + 47 + ], + [ + 74, + 38, + 49 + ] + ], + [ + [ + 71, + 38, + 43 + ], + [ + 72, + 38, + 44 + ] + ], + [ + [ + 72, + 38, + 44 + ], + [ + 73, + 38, + 47 + ] + ], + [ + [ + 95, + 38, + 43 + ], + [ + 97, + 38, + 49 + ] + ], + [ + [ + 93, + 38, + 44 + ], + [ + 95, + 38, + 49 + ] + ], + [ + [ + 91, + 38, + 45 + ], + [ + 93, + 38, + 49 + ] + ], + [ + [ + 89, + 38, + 46 + ], + [ + 91, + 38, + 49 + ] + ], + [ + [ + 87, + 38, + 47 + ], + [ + 89, + 38, + 49 + ] + ], + [ + [ + 85, + 38, + 48 + ], + [ + 87, + 38, + 49 + ] + ], + [ + [ + 90, + 38, + 49 + ], + [ + 96, + 38, + 50 + ] + ], + [ + [ + 77, + 38, + 51 + ], + [ + 93, + 38, + 52 + ] + ], + [ + [ + 75, + 38, + 52 + ], + [ + 91, + 38, + 53 + ] + ], + [ + [ + 76, + 38, + 53 + ], + [ + 89, + 38, + 54 + ] + ], + [ + [ + 77, + 38, + 54 + ], + [ + 88, + 38, + 55 + ] + ], + [ + [ + 78, + 38, + 55 + ], + [ + 86, + 38, + 56 + ] + ], + [ + [ + 80, + 38, + 56 + ], + [ + 84, + 38, + 57 + ] + ], + [ + [ + 73, + 38, + 45 + ], + [ + 74, + 38, + 47 + ] + ], + [ + [ + 74, + 38, + 46 + ], + [ + 75, + 38, + 47 + ] + ], + [ + [ + 74, + 38, + 47 + ], + [ + 76, + 38, + 49 + ] + ], + [ + [ + 76, + 38, + 48 + ], + [ + 78, + 38, + 49 + ] + ], + [ + [ + 93, + 38, + 50 + ], + [ + 94, + 38, + 51 + ] + ], + [ + [ + 82, + 42, + 38 + ], + [ + 83, + 43, + 38 + ] + ], + [ + [ + 94, + 39, + 38 + ], + [ + 95, + 40, + 38 + ] + ], + [ + [ + 92, + 40, + 38 + ], + [ + 93, + 41, + 38 + ] + ], + [ + [ + 99, + 14, + 38 + ], + [ + 100, + 15, + 38 + ] + ], + [ + [ + 71, + 13, + 38 + ], + [ + 73, + 14, + 38 + ] + ], + [ + [ + 67, + 14, + 38 + ], + [ + 68, + 15, + 38 + ] + ], + [ + [ + 64, + 15, + 38 + ], + [ + 65, + 16, + 38 + ] + ], + [ + [ + 176, + 64, + 38 + ], + [ + 177, + 65, + 38 + ] + ], + [ + [ + 38, + 26, + 36 + ], + [ + 38, + 27, + 37 + ] + ], + [ + [ + 73, + 38, + 31 + ], + [ + 74, + 38, + 33 + ] + ], + [ + [ + 71, + 38, + 36 + ], + [ + 72, + 38, + 37 + ] + ], + [ + [ + 72, + 38, + 33 + ], + [ + 73, + 38, + 36 + ] + ], + [ + [ + 74, + 38, + 28 + ], + [ + 77, + 38, + 30 + ] + ], + [ + [ + 77, + 38, + 29 + ], + [ + 94, + 38, + 30 + ] + ], + [ + [ + 73, + 38, + 30 + ], + [ + 90, + 38, + 31 + ] + ], + [ + [ + 90, + 38, + 30 + ], + [ + 96, + 38, + 31 + ] + ], + [ + [ + 85, + 38, + 31 + ], + [ + 87, + 38, + 32 + ] + ], + [ + [ + 87, + 38, + 31 + ], + [ + 89, + 38, + 33 + ] + ], + [ + [ + 89, + 38, + 31 + ], + [ + 91, + 38, + 34 + ] + ], + [ + [ + 91, + 38, + 31 + ], + [ + 93, + 38, + 35 + ] + ], + [ + [ + 93, + 38, + 31 + ], + [ + 95, + 38, + 36 + ] + ], + [ + [ + 95, + 38, + 31 + ], + [ + 97, + 38, + 37 + ] + ], + [ + [ + 80, + 38, + 23 + ], + [ + 84, + 38, + 24 + ] + ], + [ + [ + 78, + 38, + 24 + ], + [ + 86, + 38, + 25 + ] + ], + [ + [ + 77, + 38, + 25 + ], + [ + 88, + 38, + 26 + ] + ], + [ + [ + 76, + 38, + 26 + ], + [ + 89, + 38, + 27 + ] + ], + [ + [ + 75, + 38, + 27 + ], + [ + 91, + 38, + 28 + ] + ], + [ + [ + 77, + 38, + 28 + ], + [ + 93, + 38, + 29 + ] + ], + [ + [ + 74, + 38, + 31 + ], + [ + 76, + 38, + 33 + ] + ], + [ + [ + 76, + 38, + 31 + ], + [ + 78, + 38, + 32 + ] + ], + [ + [ + 73, + 38, + 33 + ], + [ + 74, + 38, + 35 + ] + ], + [ + [ + 74, + 38, + 33 + ], + [ + 75, + 38, + 34 + ] + ], + [ + [ + 89, + 38, + 30 + ], + [ + 90, + 38, + 31 + ] + ], + [ + [ + 109, + 38, + 40 + ], + [ + 110, + 38, + 42 + ] + ], + [ + [ + 106, + 38, + 41 + ], + [ + 109, + 38, + 42 + ] + ], + [ + [ + 103, + 38, + 42 + ], + [ + 107, + 38, + 43 + ] + ], + [ + [ + 56, + 38, + 42 + ], + [ + 62, + 38, + 43 + ] + ], + [ + [ + 55, + 38, + 41 + ], + [ + 56, + 38, + 42 + ] + ], + [ + [ + 51, + 38, + 40 + ], + [ + 52, + 38, + 41 + ] + ], + [ + [ + 52, + 38, + 40 + ], + [ + 53, + 38, + 42 + ] + ], + [ + [ + 53, + 38, + 40 + ], + [ + 54, + 38, + 42 + ] + ], + [ + [ + 54, + 38, + 41 + ], + [ + 55, + 38, + 42 + ] + ], + [ + [ + 147, + 38, + 40 + ], + [ + 148, + 38, + 41 + ] + ], + [ + [ + 73, + 38, + 49 + ], + [ + 90, + 38, + 50 + ] + ], + [ + [ + 74, + 38, + 50 + ], + [ + 77, + 38, + 52 + ] + ], + [ + [ + 77, + 38, + 50 + ], + [ + 94, + 38, + 51 + ] + ], + [ + [ + 96, + 38, + 42 + ], + [ + 97, + 38, + 43 + ] + ], + [ + [ + 57, + 38, + 49 + ], + [ + 58, + 38, + 51 + ] + ], + [ + [ + 58, + 38, + 49 + ], + [ + 60, + 38, + 50 + ] + ], + [ + [ + 68, + 38, + 51 + ], + [ + 73, + 38, + 52 + ] + ], + [ + [ + 96, + 38, + 43 + ], + [ + 97, + 38, + 46 + ] + ], + [ + [ + 101, + 38, + 42 + ], + [ + 103, + 38, + 43 + ] + ], + [ + [ + 97, + 38, + 42 + ], + [ + 101, + 38, + 43 + ] + ], + [ + [ + 110, + 38, + 40 + ], + [ + 116, + 38, + 42 + ] + ], + [ + [ + 116, + 38, + 40 + ], + [ + 120, + 38, + 41 + ] + ], + [ + [ + 54, + 15, + 38 + ], + [ + 55, + 16, + 38 + ] + ], + [ + [ + 117, + 16, + 38 + ], + [ + 121, + 17, + 38 + ] + ], + [ + [ + 121, + 17, + 38 + ], + [ + 125, + 18, + 38 + ] + ], + [ + [ + 110, + 15, + 38 + ], + [ + 114, + 16, + 38 + ] + ], + [ + [ + 101, + 15, + 38 + ], + [ + 110, + 16, + 38 + ] + ], + [ + [ + 130, + 33, + 38 + ], + [ + 145, + 34, + 38 + ] + ], + [ + [ + 130, + 34, + 38 + ], + [ + 140, + 35, + 38 + ] + ], + [ + [ + 130, + 35, + 38 + ], + [ + 134, + 36, + 38 + ] + ], + [ + [ + 131, + 22, + 38 + ], + [ + 135, + 23, + 38 + ] + ], + [ + [ + 132, + 23, + 38 + ], + [ + 140, + 24, + 38 + ] + ], + [ + [ + 132, + 32, + 38 + ], + [ + 148, + 33, + 38 + ] + ], + [ + [ + 133, + 24, + 38 + ], + [ + 144, + 25, + 38 + ] + ], + [ + [ + 134, + 25, + 38 + ], + [ + 147, + 26, + 38 + ] + ], + [ + [ + 134, + 26, + 38 + ], + [ + 149, + 27, + 38 + ] + ], + [ + [ + 134, + 31, + 38 + ], + [ + 150, + 32, + 38 + ] + ], + [ + [ + 135, + 27, + 38 + ], + [ + 150, + 29, + 38 + ] + ], + [ + [ + 135, + 29, + 38 + ], + [ + 151, + 31, + 38 + ] + ], + [ + [ + 130, + 21, + 38 + ], + [ + 131, + 22, + 38 + ] + ], + [ + [ + 106, + 37, + 38 + ], + [ + 110, + 38, + 38 + ] + ], + [ + [ + 103, + 38, + 38 + ], + [ + 106, + 39, + 38 + ] + ], + [ + [ + 94, + 39, + 38 + ], + [ + 95, + 40, + 38 + ] + ], + [ + [ + 67, + 39, + 38 + ], + [ + 71, + 41, + 38 + ] + ], + [ + [ + 64, + 15, + 38 + ], + [ + 65, + 16, + 38 + ] + ], + [ + [ + 129, + 21, + 38 + ], + [ + 130, + 22, + 38 + ] + ], + [ + [ + 110, + 37, + 38 + ], + [ + 116, + 38, + 38 + ] + ], + [ + [ + 114, + 36, + 38 + ], + [ + 126, + 37, + 38 + ] + ], + [ + [ + 121, + 35, + 38 + ], + [ + 130, + 36, + 38 + ] + ], + [ + [ + 125, + 34, + 38 + ], + [ + 130, + 35, + 38 + ] + ], + [ + [ + 130, + 19, + 38 + ], + [ + 132, + 20, + 38 + ] + ], + [ + [ + 130, + 20, + 38 + ], + [ + 135, + 21, + 38 + ] + ], + [ + [ + 131, + 21, + 38 + ], + [ + 138, + 22, + 38 + ] + ], + [ + [ + 135, + 22, + 38 + ], + [ + 141, + 23, + 38 + ] + ], + [ + [ + 140, + 23, + 38 + ], + [ + 143, + 24, + 38 + ] + ], + [ + [ + 144, + 24, + 38 + ], + [ + 145, + 25, + 38 + ] + ], + [ + [ + 170, + 66, + 38 + ], + [ + 171, + 67, + 38 + ] + ], + [ + [ + 176, + 66, + 38 + ], + [ + 180, + 67, + 38 + ] + ], + [ + [ + 34, + 15, + 38 + ], + [ + 35, + 16, + 38 + ] + ], + [ + [ + 19, + 18, + 38 + ], + [ + 26, + 19, + 38 + ] + ], + [ + [ + 19, + 19, + 38 + ], + [ + 25, + 21, + 38 + ] + ], + [ + [ + 20, + 21, + 38 + ], + [ + 25, + 22, + 38 + ] + ], + [ + [ + 21, + 17, + 38 + ], + [ + 28, + 18, + 38 + ] + ], + [ + [ + 21, + 22, + 38 + ], + [ + 25, + 23, + 38 + ] + ], + [ + [ + 22, + 23, + 38 + ], + [ + 26, + 24, + 38 + ] + ], + [ + [ + 24, + 16, + 38 + ], + [ + 32, + 17, + 38 + ] + ], + [ + [ + 24, + 24, + 38 + ], + [ + 27, + 25, + 38 + ] + ], + [ + [ + 25, + 25, + 38 + ], + [ + 29, + 26, + 38 + ] + ], + [ + [ + 27, + 26, + 38 + ], + [ + 31, + 27, + 38 + ] + ], + [ + [ + 29, + 27, + 38 + ], + [ + 33, + 28, + 38 + ] + ], + [ + [ + 32, + 28, + 38 + ], + [ + 35, + 29, + 38 + ] + ], + [ + [ + 34, + 29, + 38 + ], + [ + 35, + 30, + 38 + ] + ], + [ + [ + 55, + 37, + 38 + ], + [ + 56, + 38, + 38 + ] + ], + [ + [ + 55, + 38, + 38 + ], + [ + 62, + 39, + 38 + ] + ], + [ + [ + 60, + 39, + 38 + ], + [ + 67, + 40, + 38 + ] + ], + [ + [ + 66, + 40, + 38 + ], + [ + 67, + 41, + 38 + ] + ], + [ + [ + 52, + 37, + 38 + ], + [ + 53, + 38, + 38 + ] + ], + [ + [ + 49, + 36, + 38 + ], + [ + 52, + 37, + 38 + ] + ], + [ + [ + 35, + 29, + 38 + ], + [ + 37, + 30, + 38 + ] + ], + [ + [ + 53, + 37, + 38 + ], + [ + 55, + 38, + 38 + ] + ], + [ + [ + 43, + 15, + 38 + ], + [ + 49, + 16, + 38 + ] + ], + [ + [ + 35, + 15, + 38 + ], + [ + 41, + 16, + 38 + ] + ], + [ + [ + 55, + 15, + 38 + ], + [ + 65, + 16, + 38 + ] + ], + [ + [ + 98, + 38, + 38 + ], + [ + 103, + 39, + 38 + ] + ], + [ + [ + 96, + 38, + 38 + ], + [ + 97, + 39, + 38 + ] + ], + [ + [ + 97, + 38, + 38 + ], + [ + 98, + 39, + 38 + ] + ], + [ + [ + 124, + 18, + 38 + ], + [ + 129, + 19, + 38 + ] + ], + [ + [ + 126, + 19, + 38 + ], + [ + 130, + 20, + 38 + ] + ], + [ + [ + 128, + 20, + 38 + ], + [ + 130, + 21, + 38 + ] + ], + [ + [ + 168, + 65, + 38 + ], + [ + 169, + 66, + 38 + ] + ], + [ + [ + 182, + 65, + 38 + ], + [ + 183, + 66, + 38 + ] + ], + [ + [ + 176, + 64, + 38 + ], + [ + 177, + 65, + 38 + ] + ], + [ + [ + 171, + 64, + 38 + ], + [ + 173, + 65, + 38 + ] + ], + [ + [ + 39, + 22, + 43 + ], + [ + 39, + 23, + 44 + ] + ], + [ + [ + 103, + 39, + 38 + ], + [ + 106, + 39, + 40 + ] + ], + [ + [ + 106, + 39, + 39 + ], + [ + 109, + 39, + 40 + ] + ], + [ + [ + 95, + 39, + 37 + ], + [ + 96, + 39, + 38 + ] + ], + [ + [ + 67, + 39, + 37 + ], + [ + 71, + 39, + 38 + ] + ], + [ + [ + 58, + 39, + 29 + ], + [ + 61, + 39, + 30 + ] + ], + [ + [ + 60, + 39, + 30 + ], + [ + 64, + 39, + 31 + ] + ], + [ + [ + 95, + 39, + 28 + ], + [ + 96, + 39, + 37 + ] + ], + [ + [ + 96, + 39, + 29 + ], + [ + 97, + 39, + 34 + ] + ], + [ + [ + 55, + 39, + 38 + ], + [ + 59, + 39, + 40 + ] + ], + [ + [ + 59, + 39, + 38 + ], + [ + 60, + 39, + 39 + ] + ], + [ + [ + 62, + 39, + 37 + ], + [ + 67, + 39, + 38 + ] + ], + [ + [ + 54, + 39, + 39 + ], + [ + 55, + 39, + 40 + ] + ], + [ + [ + 96, + 39, + 38 + ], + [ + 98, + 39, + 39 + ] + ], + [ + [ + 98, + 39, + 38 + ], + [ + 103, + 39, + 40 + ] + ], + [ + [ + 95, + 39, + 38 + ], + [ + 96, + 39, + 39 + ] + ], + [ + [ + 169, + 39, + 40 + ], + [ + 170, + 39, + 41 + ] + ], + [ + [ + 76, + 39, + 59 + ], + [ + 77, + 39, + 60 + ] + ], + [ + [ + 73, + 39, + 52 + ], + [ + 74, + 39, + 53 + ] + ], + [ + [ + 74, + 39, + 52 + ], + [ + 75, + 39, + 56 + ] + ], + [ + [ + 75, + 39, + 55 + ], + [ + 76, + 39, + 58 + ] + ], + [ + [ + 72, + 39, + 47 + ], + [ + 73, + 39, + 49 + ] + ], + [ + [ + 71, + 39, + 44 + ], + [ + 72, + 39, + 46 + ] + ], + [ + [ + 96, + 39, + 49 + ], + [ + 97, + 39, + 51 + ] + ], + [ + [ + 94, + 39, + 50 + ], + [ + 95, + 39, + 57 + ] + ], + [ + [ + 95, + 39, + 50 + ], + [ + 96, + 39, + 56 + ] + ], + [ + [ + 93, + 39, + 51 + ], + [ + 94, + 39, + 58 + ] + ], + [ + [ + 91, + 39, + 52 + ], + [ + 93, + 39, + 59 + ] + ], + [ + [ + 75, + 39, + 53 + ], + [ + 76, + 39, + 55 + ] + ], + [ + [ + 89, + 39, + 53 + ], + [ + 90, + 39, + 61 + ] + ], + [ + [ + 90, + 39, + 53 + ], + [ + 91, + 39, + 60 + ] + ], + [ + [ + 76, + 39, + 54 + ], + [ + 77, + 39, + 59 + ] + ], + [ + [ + 88, + 39, + 54 + ], + [ + 89, + 39, + 61 + ] + ], + [ + [ + 77, + 39, + 55 + ], + [ + 78, + 39, + 62 + ] + ], + [ + [ + 86, + 39, + 55 + ], + [ + 87, + 39, + 63 + ] + ], + [ + [ + 87, + 39, + 55 + ], + [ + 88, + 39, + 62 + ] + ], + [ + [ + 78, + 39, + 56 + ], + [ + 80, + 39, + 63 + ] + ], + [ + [ + 84, + 39, + 56 + ], + [ + 85, + 39, + 64 + ] + ], + [ + [ + 85, + 39, + 56 + ], + [ + 86, + 39, + 63 + ] + ], + [ + [ + 80, + 39, + 57 + ], + [ + 84, + 39, + 64 + ] + ], + [ + [ + 98, + 14, + 39 + ], + [ + 99, + 15, + 39 + ] + ], + [ + [ + 73, + 13, + 39 + ], + [ + 96, + 14, + 39 + ] + ], + [ + [ + 68, + 14, + 39 + ], + [ + 70, + 15, + 39 + ] + ], + [ + [ + 39, + 22, + 36 + ], + [ + 39, + 23, + 37 + ] + ], + [ + [ + 76, + 39, + 20 + ], + [ + 77, + 39, + 21 + ] + ], + [ + [ + 75, + 39, + 22 + ], + [ + 76, + 39, + 25 + ] + ], + [ + [ + 74, + 39, + 24 + ], + [ + 75, + 39, + 28 + ] + ], + [ + [ + 73, + 39, + 27 + ], + [ + 74, + 39, + 28 + ] + ], + [ + [ + 72, + 39, + 31 + ], + [ + 73, + 39, + 33 + ] + ], + [ + [ + 71, + 39, + 34 + ], + [ + 72, + 39, + 36 + ] + ], + [ + [ + 73, + 39, + 28 + ], + [ + 74, + 39, + 30 + ] + ], + [ + [ + 80, + 39, + 16 + ], + [ + 84, + 39, + 23 + ] + ], + [ + [ + 84, + 39, + 16 + ], + [ + 85, + 39, + 24 + ] + ], + [ + [ + 78, + 39, + 17 + ], + [ + 80, + 39, + 24 + ] + ], + [ + [ + 85, + 39, + 17 + ], + [ + 86, + 39, + 24 + ] + ], + [ + [ + 86, + 39, + 17 + ], + [ + 87, + 39, + 25 + ] + ], + [ + [ + 77, + 39, + 18 + ], + [ + 78, + 39, + 25 + ] + ], + [ + [ + 87, + 39, + 18 + ], + [ + 88, + 39, + 25 + ] + ], + [ + [ + 88, + 39, + 19 + ], + [ + 89, + 39, + 26 + ] + ], + [ + [ + 89, + 39, + 19 + ], + [ + 90, + 39, + 27 + ] + ], + [ + [ + 90, + 39, + 20 + ], + [ + 91, + 39, + 27 + ] + ], + [ + [ + 76, + 39, + 21 + ], + [ + 77, + 39, + 26 + ] + ], + [ + [ + 91, + 39, + 21 + ], + [ + 93, + 39, + 28 + ] + ], + [ + [ + 93, + 39, + 22 + ], + [ + 94, + 39, + 29 + ] + ], + [ + [ + 94, + 39, + 23 + ], + [ + 95, + 39, + 30 + ] + ], + [ + [ + 95, + 39, + 24 + ], + [ + 96, + 39, + 30 + ] + ], + [ + [ + 75, + 39, + 25 + ], + [ + 76, + 39, + 27 + ] + ], + [ + [ + 96, + 39, + 29 + ], + [ + 97, + 39, + 31 + ] + ], + [ + [ + 103, + 39, + 40 + ], + [ + 106, + 39, + 42 + ] + ], + [ + [ + 106, + 39, + 40 + ], + [ + 109, + 39, + 41 + ] + ], + [ + [ + 62, + 39, + 42 + ], + [ + 67, + 39, + 43 + ] + ], + [ + [ + 55, + 39, + 40 + ], + [ + 59, + 39, + 41 + ] + ], + [ + [ + 56, + 39, + 41 + ], + [ + 61, + 39, + 42 + ] + ], + [ + [ + 54, + 39, + 40 + ], + [ + 55, + 39, + 41 + ] + ], + [ + [ + 73, + 39, + 50 + ], + [ + 74, + 39, + 52 + ] + ], + [ + [ + 72, + 39, + 49 + ], + [ + 73, + 39, + 50 + ] + ], + [ + [ + 95, + 39, + 42 + ], + [ + 96, + 39, + 43 + ] + ], + [ + [ + 67, + 39, + 42 + ], + [ + 71, + 39, + 43 + ] + ], + [ + [ + 58, + 39, + 50 + ], + [ + 61, + 39, + 51 + ] + ], + [ + [ + 60, + 39, + 49 + ], + [ + 64, + 39, + 50 + ] + ], + [ + [ + 95, + 39, + 43 + ], + [ + 96, + 39, + 52 + ] + ], + [ + [ + 96, + 39, + 46 + ], + [ + 97, + 39, + 51 + ] + ], + [ + [ + 98, + 39, + 40 + ], + [ + 103, + 39, + 42 + ] + ], + [ + [ + 96, + 39, + 41 + ], + [ + 98, + 39, + 42 + ] + ], + [ + [ + 95, + 39, + 41 + ], + [ + 96, + 39, + 42 + ] + ], + [ + [ + 125, + 17, + 39 + ], + [ + 128, + 18, + 39 + ] + ], + [ + [ + 121, + 16, + 39 + ], + [ + 123, + 17, + 39 + ] + ], + [ + [ + 114, + 15, + 39 + ], + [ + 117, + 16, + 39 + ] + ], + [ + [ + 140, + 34, + 39 + ], + [ + 147, + 35, + 39 + ] + ], + [ + [ + 145, + 33, + 39 + ], + [ + 152, + 34, + 39 + ] + ], + [ + [ + 148, + 32, + 39 + ], + [ + 157, + 33, + 39 + ] + ], + [ + [ + 149, + 26, + 39 + ], + [ + 154, + 27, + 39 + ] + ], + [ + [ + 150, + 27, + 39 + ], + [ + 158, + 28, + 39 + ] + ], + [ + [ + 150, + 28, + 39 + ], + [ + 163, + 29, + 39 + ] + ], + [ + [ + 150, + 31, + 39 + ], + [ + 167, + 32, + 39 + ] + ], + [ + [ + 151, + 29, + 39 + ], + [ + 166, + 30, + 39 + ] + ], + [ + [ + 151, + 30, + 39 + ], + [ + 167, + 31, + 39 + ] + ], + [ + [ + 130, + 36, + 39 + ], + [ + 131, + 37, + 39 + ] + ], + [ + [ + 134, + 35, + 39 + ], + [ + 139, + 36, + 39 + ] + ], + [ + [ + 147, + 25, + 39 + ], + [ + 149, + 26, + 39 + ] + ], + [ + [ + 106, + 38, + 39 + ], + [ + 109, + 39, + 39 + ] + ], + [ + [ + 92, + 40, + 39 + ], + [ + 93, + 41, + 39 + ] + ], + [ + [ + 126, + 36, + 39 + ], + [ + 130, + 37, + 39 + ] + ], + [ + [ + 116, + 37, + 39 + ], + [ + 120, + 38, + 39 + ] + ], + [ + [ + 154, + 26, + 39 + ], + [ + 157, + 27, + 39 + ] + ], + [ + [ + 141, + 22, + 39 + ], + [ + 144, + 23, + 39 + ] + ], + [ + [ + 143, + 23, + 39 + ], + [ + 147, + 24, + 39 + ] + ], + [ + [ + 145, + 24, + 39 + ], + [ + 150, + 25, + 39 + ] + ], + [ + [ + 149, + 25, + 39 + ], + [ + 154, + 26, + 39 + ] + ], + [ + [ + 135, + 20, + 39 + ], + [ + 137, + 21, + 39 + ] + ], + [ + [ + 132, + 19, + 39 + ], + [ + 134, + 20, + 39 + ] + ], + [ + [ + 130, + 18, + 39 + ], + [ + 131, + 19, + 39 + ] + ], + [ + [ + 163, + 28, + 39 + ], + [ + 164, + 29, + 39 + ] + ], + [ + [ + 158, + 27, + 39 + ], + [ + 161, + 28, + 39 + ] + ], + [ + [ + 138, + 21, + 39 + ], + [ + 141, + 22, + 39 + ] + ], + [ + [ + 180, + 66, + 39 + ], + [ + 183, + 67, + 39 + ] + ], + [ + [ + 15, + 18, + 39 + ], + [ + 16, + 20, + 39 + ] + ], + [ + [ + 16, + 17, + 39 + ], + [ + 17, + 21, + 39 + ] + ], + [ + [ + 27, + 15, + 39 + ], + [ + 34, + 16, + 39 + ] + ], + [ + [ + 25, + 26, + 39 + ], + [ + 27, + 27, + 39 + ] + ], + [ + [ + 24, + 25, + 39 + ], + [ + 25, + 26, + 39 + ] + ], + [ + [ + 22, + 24, + 39 + ], + [ + 24, + 25, + 39 + ] + ], + [ + [ + 17, + 17, + 39 + ], + [ + 21, + 18, + 39 + ] + ], + [ + [ + 17, + 18, + 39 + ], + [ + 19, + 21, + 39 + ] + ], + [ + [ + 17, + 21, + 39 + ], + [ + 20, + 22, + 39 + ] + ], + [ + [ + 18, + 22, + 39 + ], + [ + 21, + 23, + 39 + ] + ], + [ + [ + 20, + 23, + 39 + ], + [ + 22, + 24, + 39 + ] + ], + [ + [ + 27, + 27, + 39 + ], + [ + 29, + 28, + 39 + ] + ], + [ + [ + 21, + 16, + 39 + ], + [ + 24, + 17, + 39 + ] + ], + [ + [ + 30, + 28, + 39 + ], + [ + 32, + 29, + 39 + ] + ], + [ + [ + 33, + 29, + 39 + ], + [ + 34, + 30, + 39 + ] + ], + [ + [ + 64, + 40, + 39 + ], + [ + 66, + 41, + 39 + ] + ], + [ + [ + 59, + 39, + 39 + ], + [ + 60, + 40, + 39 + ] + ], + [ + [ + 36, + 30, + 39 + ], + [ + 37, + 31, + 39 + ] + ], + [ + [ + 51, + 37, + 39 + ], + [ + 52, + 38, + 39 + ] + ], + [ + [ + 48, + 36, + 39 + ], + [ + 49, + 37, + 39 + ] + ], + [ + [ + 54, + 38, + 39 + ], + [ + 55, + 39, + 39 + ] + ], + [ + [ + 41, + 15, + 39 + ], + [ + 43, + 16, + 39 + ] + ], + [ + [ + 95, + 39, + 39 + ], + [ + 98, + 40, + 39 + ] + ], + [ + [ + 145, + 35, + 39 + ], + [ + 147, + 36, + 39 + ] + ], + [ + [ + 146, + 36, + 39 + ], + [ + 147, + 37, + 39 + ] + ], + [ + [ + 147, + 34, + 39 + ], + [ + 152, + 38, + 39 + ] + ], + [ + [ + 148, + 38, + 39 + ], + [ + 152, + 40, + 39 + ] + ], + [ + [ + 149, + 40, + 39 + ], + [ + 152, + 41, + 39 + ] + ], + [ + [ + 150, + 41, + 39 + ], + [ + 152, + 42, + 39 + ] + ], + [ + [ + 151, + 42, + 39 + ], + [ + 152, + 43, + 39 + ] + ], + [ + [ + 152, + 33, + 39 + ], + [ + 157, + 45, + 39 + ] + ], + [ + [ + 153, + 45, + 39 + ], + [ + 157, + 46, + 39 + ] + ], + [ + [ + 154, + 46, + 39 + ], + [ + 157, + 47, + 39 + ] + ], + [ + [ + 155, + 47, + 39 + ], + [ + 157, + 48, + 39 + ] + ], + [ + [ + 156, + 48, + 39 + ], + [ + 157, + 50, + 39 + ] + ], + [ + [ + 157, + 32, + 39 + ], + [ + 166, + 51, + 39 + ] + ], + [ + [ + 158, + 51, + 39 + ], + [ + 166, + 52, + 39 + ] + ], + [ + [ + 159, + 52, + 39 + ], + [ + 166, + 53, + 39 + ] + ], + [ + [ + 160, + 53, + 39 + ], + [ + 166, + 54, + 39 + ] + ], + [ + [ + 161, + 54, + 39 + ], + [ + 166, + 56, + 39 + ] + ], + [ + [ + 162, + 56, + 39 + ], + [ + 166, + 57, + 39 + ] + ], + [ + [ + 163, + 57, + 39 + ], + [ + 166, + 58, + 39 + ] + ], + [ + [ + 164, + 58, + 39 + ], + [ + 166, + 59, + 39 + ] + ], + [ + [ + 165, + 59, + 39 + ], + [ + 166, + 60, + 39 + ] + ], + [ + [ + 166, + 33, + 39 + ], + [ + 167, + 62, + 39 + ] + ], + [ + [ + 167, + 35, + 39 + ], + [ + 168, + 63, + 39 + ] + ], + [ + [ + 168, + 37, + 39 + ], + [ + 169, + 64, + 39 + ] + ], + [ + [ + 169, + 40, + 39 + ], + [ + 170, + 65, + 39 + ] + ], + [ + [ + 170, + 42, + 39 + ], + [ + 171, + 67, + 39 + ] + ], + [ + [ + 171, + 44, + 39 + ], + [ + 172, + 68, + 39 + ] + ], + [ + [ + 172, + 46, + 39 + ], + [ + 173, + 69, + 39 + ] + ], + [ + [ + 173, + 49, + 39 + ], + [ + 174, + 70, + 39 + ] + ], + [ + [ + 174, + 52, + 39 + ], + [ + 175, + 55, + 39 + ] + ], + [ + [ + 174, + 55, + 39 + ], + [ + 176, + 58, + 39 + ] + ], + [ + [ + 174, + 58, + 39 + ], + [ + 177, + 61, + 39 + ] + ], + [ + [ + 174, + 61, + 39 + ], + [ + 178, + 63, + 39 + ] + ], + [ + [ + 174, + 63, + 39 + ], + [ + 179, + 66, + 39 + ] + ], + [ + [ + 174, + 66, + 39 + ], + [ + 180, + 68, + 39 + ] + ], + [ + [ + 174, + 68, + 39 + ], + [ + 181, + 70, + 39 + ] + ], + [ + [ + 174, + 70, + 39 + ], + [ + 182, + 72, + 39 + ] + ], + [ + [ + 129, + 18, + 39 + ], + [ + 130, + 19, + 39 + ] + ], + [ + [ + 177, + 64, + 39 + ], + [ + 179, + 65, + 39 + ] + ], + [ + [ + 169, + 64, + 39 + ], + [ + 171, + 65, + 39 + ] + ], + [ + [ + 71, + 40, + 34 + ], + [ + 72, + 40, + 35 + ] + ], + [ + [ + 93, + 40, + 37 + ], + [ + 95, + 40, + 39 + ] + ], + [ + [ + 92, + 40, + 38 + ], + [ + 93, + 40, + 39 + ] + ], + [ + [ + 93, + 40, + 39 + ], + [ + 94, + 40, + 40 + ] + ], + [ + [ + 61, + 40, + 29 + ], + [ + 67, + 40, + 30 + ] + ], + [ + [ + 64, + 40, + 30 + ], + [ + 71, + 40, + 31 + ] + ], + [ + [ + 94, + 40, + 21 + ], + [ + 95, + 40, + 37 + ] + ], + [ + [ + 95, + 40, + 21 + ], + [ + 96, + 40, + 28 + ] + ], + [ + [ + 93, + 40, + 30 + ], + [ + 94, + 40, + 37 + ] + ], + [ + [ + 60, + 40, + 38 + ], + [ + 66, + 40, + 39 + ] + ], + [ + [ + 59, + 40, + 39 + ], + [ + 64, + 40, + 40 + ] + ], + [ + [ + 94, + 40, + 39 + ], + [ + 98, + 40, + 40 + ] + ], + [ + [ + 148, + 40, + 39 + ], + [ + 149, + 40, + 40 + ] + ], + [ + [ + 75, + 40, + 58 + ], + [ + 76, + 40, + 61 + ] + ], + [ + [ + 76, + 40, + 60 + ], + [ + 77, + 40, + 64 + ] + ], + [ + [ + 77, + 40, + 63 + ], + [ + 78, + 40, + 67 + ] + ], + [ + [ + 78, + 40, + 67 + ], + [ + 79, + 40, + 69 + ] + ], + [ + [ + 74, + 40, + 56 + ], + [ + 75, + 40, + 57 + ] + ], + [ + [ + 95, + 40, + 56 + ], + [ + 96, + 40, + 59 + ] + ], + [ + [ + 94, + 40, + 57 + ], + [ + 95, + 40, + 63 + ] + ], + [ + [ + 93, + 40, + 58 + ], + [ + 94, + 40, + 64 + ] + ], + [ + [ + 91, + 40, + 59 + ], + [ + 92, + 40, + 66 + ] + ], + [ + [ + 92, + 40, + 59 + ], + [ + 93, + 40, + 65 + ] + ], + [ + [ + 90, + 40, + 60 + ], + [ + 91, + 40, + 67 + ] + ], + [ + [ + 88, + 40, + 61 + ], + [ + 89, + 40, + 69 + ] + ], + [ + [ + 89, + 40, + 61 + ], + [ + 90, + 40, + 68 + ] + ], + [ + [ + 87, + 40, + 62 + ], + [ + 88, + 40, + 69 + ] + ], + [ + [ + 78, + 40, + 63 + ], + [ + 79, + 40, + 67 + ] + ], + [ + [ + 79, + 40, + 63 + ], + [ + 80, + 40, + 71 + ] + ], + [ + [ + 85, + 40, + 63 + ], + [ + 86, + 40, + 71 + ] + ], + [ + [ + 86, + 40, + 63 + ], + [ + 87, + 40, + 70 + ] + ], + [ + [ + 80, + 40, + 64 + ], + [ + 81, + 40, + 71 + ] + ], + [ + [ + 81, + 40, + 64 + ], + [ + 84, + 40, + 72 + ] + ], + [ + [ + 84, + 40, + 64 + ], + [ + 85, + 40, + 71 + ] + ], + [ + [ + 77, + 40, + 62 + ], + [ + 78, + 40, + 63 + ] + ], + [ + [ + 95, + 14, + 40 + ], + [ + 98, + 15, + 40 + ] + ], + [ + [ + 70, + 14, + 40 + ], + [ + 75, + 15, + 40 + ] + ], + [ + [ + 77, + 40, + 13 + ], + [ + 78, + 40, + 17 + ] + ], + [ + [ + 76, + 40, + 16 + ], + [ + 77, + 40, + 20 + ] + ], + [ + [ + 75, + 40, + 19 + ], + [ + 76, + 40, + 22 + ] + ], + [ + [ + 78, + 40, + 11 + ], + [ + 79, + 40, + 13 + ] + ], + [ + [ + 74, + 40, + 23 + ], + [ + 75, + 40, + 24 + ] + ], + [ + [ + 72, + 40, + 30 + ], + [ + 73, + 40, + 31 + ] + ], + [ + [ + 81, + 40, + 8 + ], + [ + 84, + 40, + 16 + ] + ], + [ + [ + 79, + 40, + 9 + ], + [ + 80, + 40, + 17 + ] + ], + [ + [ + 80, + 40, + 9 + ], + [ + 81, + 40, + 16 + ] + ], + [ + [ + 84, + 40, + 9 + ], + [ + 85, + 40, + 16 + ] + ], + [ + [ + 85, + 40, + 9 + ], + [ + 86, + 40, + 17 + ] + ], + [ + [ + 86, + 40, + 10 + ], + [ + 87, + 40, + 17 + ] + ], + [ + [ + 87, + 40, + 11 + ], + [ + 88, + 40, + 18 + ] + ], + [ + [ + 88, + 40, + 11 + ], + [ + 89, + 40, + 19 + ] + ], + [ + [ + 89, + 40, + 12 + ], + [ + 90, + 40, + 19 + ] + ], + [ + [ + 78, + 40, + 13 + ], + [ + 79, + 40, + 17 + ] + ], + [ + [ + 90, + 40, + 13 + ], + [ + 91, + 40, + 20 + ] + ], + [ + [ + 91, + 40, + 14 + ], + [ + 92, + 40, + 21 + ] + ], + [ + [ + 92, + 40, + 15 + ], + [ + 93, + 40, + 21 + ] + ], + [ + [ + 93, + 40, + 16 + ], + [ + 94, + 40, + 22 + ] + ], + [ + [ + 94, + 40, + 17 + ], + [ + 95, + 40, + 23 + ] + ], + [ + [ + 95, + 40, + 21 + ], + [ + 96, + 40, + 24 + ] + ], + [ + [ + 77, + 40, + 17 + ], + [ + 78, + 40, + 18 + ] + ], + [ + [ + 59, + 40, + 40 + ], + [ + 64, + 40, + 41 + ] + ], + [ + [ + 61, + 40, + 41 + ], + [ + 66, + 40, + 42 + ] + ], + [ + [ + 169, + 40, + 39 + ], + [ + 170, + 40, + 40 + ] + ], + [ + [ + 148, + 40, + 40 + ], + [ + 149, + 40, + 41 + ] + ], + [ + [ + 71, + 40, + 45 + ], + [ + 72, + 40, + 46 + ] + ], + [ + [ + 93, + 40, + 40 + ], + [ + 94, + 40, + 41 + ] + ], + [ + [ + 92, + 40, + 41 + ], + [ + 93, + 40, + 42 + ] + ], + [ + [ + 93, + 40, + 41 + ], + [ + 95, + 40, + 43 + ] + ], + [ + [ + 61, + 40, + 50 + ], + [ + 67, + 40, + 51 + ] + ], + [ + [ + 64, + 40, + 49 + ], + [ + 71, + 40, + 50 + ] + ], + [ + [ + 93, + 40, + 43 + ], + [ + 94, + 40, + 50 + ] + ], + [ + [ + 94, + 40, + 43 + ], + [ + 95, + 40, + 59 + ] + ], + [ + [ + 95, + 40, + 52 + ], + [ + 96, + 40, + 59 + ] + ], + [ + [ + 94, + 40, + 40 + ], + [ + 98, + 40, + 41 + ] + ], + [ + [ + 123, + 16, + 40 + ], + [ + 124, + 17, + 40 + ] + ], + [ + [ + 117, + 15, + 40 + ], + [ + 118, + 16, + 40 + ] + ], + [ + [ + 166, + 29, + 40 + ], + [ + 168, + 30, + 40 + ] + ], + [ + [ + 166, + 32, + 40 + ], + [ + 167, + 33, + 40 + ] + ], + [ + [ + 167, + 30, + 40 + ], + [ + 168, + 35, + 40 + ] + ], + [ + [ + 168, + 30, + 40 + ], + [ + 172, + 32, + 40 + ] + ], + [ + [ + 168, + 32, + 40 + ], + [ + 171, + 37, + 40 + ] + ], + [ + [ + 169, + 37, + 40 + ], + [ + 171, + 40, + 40 + ] + ], + [ + [ + 170, + 40, + 40 + ], + [ + 171, + 42, + 40 + ] + ], + [ + [ + 171, + 33, + 40 + ], + [ + 172, + 44, + 40 + ] + ], + [ + [ + 172, + 35, + 40 + ], + [ + 173, + 46, + 40 + ] + ], + [ + [ + 173, + 37, + 40 + ], + [ + 174, + 49, + 40 + ] + ], + [ + [ + 174, + 39, + 40 + ], + [ + 175, + 52, + 40 + ] + ], + [ + [ + 175, + 41, + 40 + ], + [ + 176, + 55, + 40 + ] + ], + [ + [ + 176, + 42, + 40 + ], + [ + 177, + 58, + 40 + ] + ], + [ + [ + 177, + 44, + 40 + ], + [ + 178, + 61, + 40 + ] + ], + [ + [ + 178, + 46, + 40 + ], + [ + 179, + 63, + 40 + ] + ], + [ + [ + 179, + 48, + 40 + ], + [ + 180, + 66, + 40 + ] + ], + [ + [ + 180, + 50, + 40 + ], + [ + 181, + 68, + 40 + ] + ], + [ + [ + 181, + 51, + 40 + ], + [ + 182, + 70, + 40 + ] + ], + [ + [ + 182, + 53, + 40 + ], + [ + 183, + 55, + 40 + ] + ], + [ + [ + 182, + 55, + 40 + ], + [ + 184, + 57, + 40 + ] + ], + [ + [ + 182, + 57, + 40 + ], + [ + 185, + 59, + 40 + ] + ], + [ + [ + 182, + 59, + 40 + ], + [ + 186, + 61, + 40 + ] + ], + [ + [ + 182, + 61, + 40 + ], + [ + 187, + 62, + 40 + ] + ], + [ + [ + 182, + 62, + 40 + ], + [ + 188, + 64, + 40 + ] + ], + [ + [ + 182, + 64, + 40 + ], + [ + 189, + 66, + 40 + ] + ], + [ + [ + 182, + 66, + 40 + ], + [ + 190, + 68, + 40 + ] + ], + [ + [ + 182, + 68, + 40 + ], + [ + 191, + 70, + 40 + ] + ], + [ + [ + 182, + 70, + 40 + ], + [ + 192, + 72, + 40 + ] + ], + [ + [ + 139, + 35, + 40 + ], + [ + 140, + 36, + 40 + ] + ], + [ + [ + 120, + 37, + 40 + ], + [ + 122, + 38, + 40 + ] + ], + [ + [ + 161, + 27, + 40 + ], + [ + 162, + 28, + 40 + ] + ], + [ + [ + 157, + 26, + 40 + ], + [ + 158, + 27, + 40 + ] + ], + [ + [ + 154, + 25, + 40 + ], + [ + 155, + 26, + 40 + ] + ], + [ + [ + 150, + 24, + 40 + ], + [ + 151, + 25, + 40 + ] + ], + [ + [ + 147, + 23, + 40 + ], + [ + 148, + 24, + 40 + ] + ], + [ + [ + 134, + 19, + 40 + ], + [ + 135, + 20, + 40 + ] + ], + [ + [ + 131, + 18, + 40 + ], + [ + 132, + 19, + 40 + ] + ], + [ + [ + 168, + 29, + 40 + ], + [ + 169, + 30, + 40 + ] + ], + [ + [ + 164, + 28, + 40 + ], + [ + 165, + 29, + 40 + ] + ], + [ + [ + 144, + 22, + 40 + ], + [ + 145, + 23, + 40 + ] + ], + [ + [ + 137, + 20, + 40 + ], + [ + 138, + 21, + 40 + ] + ], + [ + [ + 19, + 16, + 40 + ], + [ + 21, + 17, + 40 + ] + ], + [ + [ + 23, + 25, + 40 + ], + [ + 24, + 26, + 40 + ] + ], + [ + [ + 21, + 24, + 40 + ], + [ + 22, + 25, + 40 + ] + ], + [ + [ + 25, + 15, + 40 + ], + [ + 27, + 16, + 40 + ] + ], + [ + [ + 32, + 29, + 40 + ], + [ + 33, + 30, + 40 + ] + ], + [ + [ + 58, + 39, + 40 + ], + [ + 59, + 40, + 40 + ] + ], + [ + [ + 47, + 36, + 40 + ], + [ + 48, + 37, + 40 + ] + ], + [ + [ + 50, + 37, + 40 + ], + [ + 51, + 38, + 40 + ] + ], + [ + [ + 18, + 22, + 40 + ], + [ + 19, + 23, + 40 + ] + ], + [ + [ + 30, + 28, + 40 + ], + [ + 31, + 29, + 40 + ] + ], + [ + [ + 152, + 45, + 40 + ], + [ + 153, + 47, + 40 + ] + ], + [ + [ + 153, + 46, + 40 + ], + [ + 154, + 48, + 40 + ] + ], + [ + [ + 154, + 47, + 40 + ], + [ + 155, + 49, + 40 + ] + ], + [ + [ + 155, + 48, + 40 + ], + [ + 156, + 51, + 40 + ] + ], + [ + [ + 156, + 50, + 40 + ], + [ + 157, + 52, + 40 + ] + ], + [ + [ + 157, + 51, + 40 + ], + [ + 158, + 53, + 40 + ] + ], + [ + [ + 158, + 52, + 40 + ], + [ + 159, + 54, + 40 + ] + ], + [ + [ + 159, + 53, + 40 + ], + [ + 160, + 56, + 40 + ] + ], + [ + [ + 160, + 54, + 40 + ], + [ + 161, + 57, + 40 + ] + ], + [ + [ + 161, + 56, + 40 + ], + [ + 162, + 58, + 40 + ] + ], + [ + [ + 162, + 57, + 40 + ], + [ + 163, + 60, + 40 + ] + ], + [ + [ + 163, + 58, + 40 + ], + [ + 164, + 61, + 40 + ] + ], + [ + [ + 164, + 59, + 40 + ], + [ + 165, + 62, + 40 + ] + ], + [ + [ + 165, + 60, + 40 + ], + [ + 166, + 64, + 40 + ] + ], + [ + [ + 166, + 62, + 40 + ], + [ + 167, + 65, + 40 + ] + ], + [ + [ + 167, + 63, + 40 + ], + [ + 168, + 66, + 40 + ] + ], + [ + [ + 168, + 64, + 40 + ], + [ + 169, + 68, + 40 + ] + ], + [ + [ + 169, + 65, + 40 + ], + [ + 170, + 69, + 40 + ] + ], + [ + [ + 170, + 67, + 40 + ], + [ + 171, + 70, + 40 + ] + ], + [ + [ + 171, + 68, + 40 + ], + [ + 172, + 69, + 40 + ] + ], + [ + [ + 171, + 69, + 40 + ], + [ + 173, + 70, + 40 + ] + ], + [ + [ + 171, + 70, + 40 + ], + [ + 174, + 72, + 40 + ] + ], + [ + [ + 146, + 37, + 40 + ], + [ + 147, + 39, + 40 + ] + ], + [ + [ + 147, + 38, + 40 + ], + [ + 148, + 40, + 40 + ] + ], + [ + [ + 144, + 35, + 40 + ], + [ + 145, + 36, + 40 + ] + ], + [ + [ + 145, + 36, + 40 + ], + [ + 146, + 37, + 40 + ] + ], + [ + [ + 148, + 40, + 40 + ], + [ + 149, + 41, + 40 + ] + ], + [ + [ + 149, + 41, + 40 + ], + [ + 150, + 43, + 40 + ] + ], + [ + [ + 150, + 42, + 40 + ], + [ + 151, + 44, + 40 + ] + ], + [ + [ + 151, + 43, + 40 + ], + [ + 152, + 45, + 40 + ] + ], + [ + [ + 127, + 17, + 40 + ], + [ + 128, + 18, + 40 + ] + ], + [ + [ + 167, + 65, + 40 + ], + [ + 168, + 66, + 40 + ] + ], + [ + [ + 183, + 65, + 40 + ], + [ + 184, + 66, + 40 + ] + ], + [ + [ + 167, + 65, + 40 + ], + [ + 168, + 66, + 40 + ] + ], + [ + [ + 183, + 65, + 40 + ], + [ + 184, + 66, + 40 + ] + ], + [ + [ + 41, + 15, + 38 + ], + [ + 41, + 16, + 39 + ] + ], + [ + [ + 72, + 41, + 30 + ], + [ + 73, + 41, + 32 + ] + ], + [ + [ + 73, + 41, + 27 + ], + [ + 74, + 41, + 28 + ] + ], + [ + [ + 71, + 41, + 35 + ], + [ + 72, + 41, + 37 + ] + ], + [ + [ + 74, + 41, + 23 + ], + [ + 75, + 41, + 24 + ] + ], + [ + [ + 90, + 41, + 37 + ], + [ + 92, + 41, + 40 + ] + ], + [ + [ + 92, + 41, + 37 + ], + [ + 93, + 41, + 38 + ] + ], + [ + [ + 92, + 41, + 39 + ], + [ + 93, + 41, + 40 + ] + ], + [ + [ + 67, + 41, + 38 + ], + [ + 71, + 41, + 40 + ] + ], + [ + [ + 71, + 41, + 37 + ], + [ + 72, + 41, + 40 + ] + ], + [ + [ + 67, + 41, + 29 + ], + [ + 73, + 41, + 30 + ] + ], + [ + [ + 71, + 41, + 30 + ], + [ + 72, + 41, + 31 + ] + ], + [ + [ + 94, + 41, + 12 + ], + [ + 95, + 41, + 21 + ] + ], + [ + [ + 93, + 41, + 14 + ], + [ + 94, + 41, + 30 + ] + ], + [ + [ + 92, + 41, + 19 + ], + [ + 93, + 41, + 37 + ] + ], + [ + [ + 91, + 41, + 26 + ], + [ + 92, + 41, + 37 + ] + ], + [ + [ + 90, + 41, + 34 + ], + [ + 91, + 41, + 37 + ] + ], + [ + [ + 66, + 41, + 38 + ], + [ + 67, + 41, + 40 + ] + ], + [ + [ + 64, + 41, + 39 + ], + [ + 66, + 41, + 40 + ] + ], + [ + [ + 149, + 41, + 39 + ], + [ + 150, + 41, + 40 + ] + ], + [ + [ + 170, + 41, + 40 + ], + [ + 171, + 41, + 41 + ] + ], + [ + [ + 78, + 41, + 69 + ], + [ + 79, + 41, + 72 + ] + ], + [ + [ + 79, + 41, + 71 + ], + [ + 80, + 41, + 76 + ] + ], + [ + [ + 80, + 41, + 75 + ], + [ + 81, + 41, + 76 + ] + ], + [ + [ + 76, + 41, + 64 + ], + [ + 77, + 41, + 65 + ] + ], + [ + [ + 77, + 41, + 67 + ], + [ + 78, + 41, + 69 + ] + ], + [ + [ + 94, + 41, + 63 + ], + [ + 95, + 41, + 67 + ] + ], + [ + [ + 93, + 41, + 64 + ], + [ + 94, + 41, + 70 + ] + ], + [ + [ + 92, + 41, + 65 + ], + [ + 93, + 41, + 71 + ] + ], + [ + [ + 91, + 41, + 66 + ], + [ + 92, + 41, + 73 + ] + ], + [ + [ + 90, + 41, + 67 + ], + [ + 91, + 41, + 74 + ] + ], + [ + [ + 89, + 41, + 68 + ], + [ + 90, + 41, + 75 + ] + ], + [ + [ + 87, + 41, + 69 + ], + [ + 89, + 41, + 76 + ] + ], + [ + [ + 86, + 41, + 70 + ], + [ + 87, + 41, + 76 + ] + ], + [ + [ + 80, + 41, + 71 + ], + [ + 81, + 41, + 75 + ] + ], + [ + [ + 84, + 41, + 71 + ], + [ + 86, + 41, + 76 + ] + ], + [ + [ + 81, + 41, + 72 + ], + [ + 84, + 41, + 76 + ] + ], + [ + [ + 78, + 13, + 41 + ], + [ + 94, + 14, + 41 + ] + ], + [ + [ + 68, + 14, + 41 + ], + [ + 71, + 15, + 41 + ] + ], + [ + [ + 41, + 15, + 41 + ], + [ + 41, + 16, + 42 + ] + ], + [ + [ + 79, + 41, + 4 + ], + [ + 80, + 41, + 9 + ] + ], + [ + [ + 80, + 41, + 4 + ], + [ + 81, + 41, + 5 + ] + ], + [ + [ + 78, + 41, + 8 + ], + [ + 79, + 41, + 11 + ] + ], + [ + [ + 76, + 41, + 15 + ], + [ + 77, + 41, + 16 + ] + ], + [ + [ + 77, + 41, + 11 + ], + [ + 78, + 41, + 13 + ] + ], + [ + [ + 81, + 41, + 4 + ], + [ + 84, + 41, + 8 + ] + ], + [ + [ + 84, + 41, + 4 + ], + [ + 86, + 41, + 9 + ] + ], + [ + [ + 86, + 41, + 4 + ], + [ + 87, + 41, + 10 + ] + ], + [ + [ + 87, + 41, + 4 + ], + [ + 89, + 41, + 11 + ] + ], + [ + [ + 80, + 41, + 5 + ], + [ + 81, + 41, + 9 + ] + ], + [ + [ + 89, + 41, + 5 + ], + [ + 90, + 41, + 12 + ] + ], + [ + [ + 90, + 41, + 6 + ], + [ + 91, + 41, + 13 + ] + ], + [ + [ + 91, + 41, + 7 + ], + [ + 92, + 41, + 14 + ] + ], + [ + [ + 92, + 41, + 9 + ], + [ + 93, + 41, + 15 + ] + ], + [ + [ + 93, + 41, + 10 + ], + [ + 94, + 41, + 16 + ] + ], + [ + [ + 94, + 41, + 12 + ], + [ + 95, + 41, + 17 + ] + ], + [ + [ + 64, + 41, + 40 + ], + [ + 66, + 41, + 41 + ] + ], + [ + [ + 66, + 41, + 40 + ], + [ + 67, + 41, + 42 + ] + ], + [ + [ + 149, + 41, + 40 + ], + [ + 150, + 41, + 41 + ] + ], + [ + [ + 72, + 41, + 48 + ], + [ + 73, + 41, + 50 + ] + ], + [ + [ + 73, + 41, + 52 + ], + [ + 74, + 41, + 53 + ] + ], + [ + [ + 71, + 41, + 43 + ], + [ + 72, + 41, + 45 + ] + ], + [ + [ + 74, + 41, + 56 + ], + [ + 75, + 41, + 57 + ] + ], + [ + [ + 90, + 41, + 40 + ], + [ + 92, + 41, + 43 + ] + ], + [ + [ + 92, + 41, + 40 + ], + [ + 93, + 41, + 41 + ] + ], + [ + [ + 92, + 41, + 42 + ], + [ + 93, + 41, + 43 + ] + ], + [ + [ + 67, + 41, + 40 + ], + [ + 71, + 41, + 42 + ] + ], + [ + [ + 71, + 41, + 40 + ], + [ + 72, + 41, + 43 + ] + ], + [ + [ + 67, + 41, + 50 + ], + [ + 73, + 41, + 51 + ] + ], + [ + [ + 71, + 41, + 49 + ], + [ + 72, + 41, + 50 + ] + ], + [ + [ + 90, + 41, + 43 + ], + [ + 91, + 41, + 46 + ] + ], + [ + [ + 91, + 41, + 43 + ], + [ + 92, + 41, + 54 + ] + ], + [ + [ + 92, + 41, + 43 + ], + [ + 93, + 41, + 61 + ] + ], + [ + [ + 93, + 41, + 50 + ], + [ + 94, + 41, + 67 + ] + ], + [ + [ + 94, + 41, + 59 + ], + [ + 95, + 41, + 67 + ] + ], + [ + [ + 106, + 38, + 41 + ], + [ + 109, + 39, + 41 + ] + ], + [ + [ + 180, + 66, + 41 + ], + [ + 183, + 67, + 41 + ] + ], + [ + [ + 15, + 18, + 41 + ], + [ + 16, + 20, + 41 + ] + ], + [ + [ + 16, + 17, + 41 + ], + [ + 17, + 21, + 41 + ] + ], + [ + [ + 64, + 40, + 41 + ], + [ + 66, + 41, + 41 + ] + ], + [ + [ + 59, + 39, + 41 + ], + [ + 61, + 40, + 41 + ] + ], + [ + [ + 55, + 38, + 41 + ], + [ + 56, + 39, + 41 + ] + ], + [ + [ + 36, + 30, + 41 + ], + [ + 37, + 31, + 41 + ] + ], + [ + [ + 51, + 37, + 41 + ], + [ + 52, + 38, + 41 + ] + ], + [ + [ + 48, + 36, + 41 + ], + [ + 49, + 37, + 41 + ] + ], + [ + [ + 54, + 38, + 41 + ], + [ + 55, + 39, + 41 + ] + ], + [ + [ + 17, + 17, + 41 + ], + [ + 21, + 18, + 41 + ] + ], + [ + [ + 17, + 18, + 41 + ], + [ + 19, + 22, + 41 + ] + ], + [ + [ + 19, + 21, + 41 + ], + [ + 20, + 23, + 41 + ] + ], + [ + [ + 20, + 22, + 41 + ], + [ + 21, + 23, + 41 + ] + ], + [ + [ + 20, + 23, + 41 + ], + [ + 22, + 24, + 41 + ] + ], + [ + [ + 21, + 16, + 41 + ], + [ + 24, + 17, + 41 + ] + ], + [ + [ + 26, + 15, + 41 + ], + [ + 34, + 16, + 41 + ] + ], + [ + [ + 27, + 27, + 41 + ], + [ + 32, + 28, + 41 + ] + ], + [ + [ + 31, + 28, + 41 + ], + [ + 34, + 29, + 41 + ] + ], + [ + [ + 33, + 29, + 41 + ], + [ + 35, + 30, + 41 + ] + ], + [ + [ + 25, + 26, + 41 + ], + [ + 27, + 27, + 41 + ] + ], + [ + [ + 24, + 25, + 41 + ], + [ + 25, + 26, + 41 + ] + ], + [ + [ + 22, + 24, + 41 + ], + [ + 24, + 25, + 41 + ] + ], + [ + [ + 145, + 35, + 41 + ], + [ + 168, + 36, + 41 + ] + ], + [ + [ + 146, + 36, + 41 + ], + [ + 168, + 37, + 41 + ] + ], + [ + [ + 147, + 34, + 41 + ], + [ + 167, + 35, + 41 + ] + ], + [ + [ + 147, + 37, + 41 + ], + [ + 169, + 38, + 41 + ] + ], + [ + [ + 148, + 38, + 41 + ], + [ + 169, + 39, + 41 + ] + ], + [ + [ + 148, + 39, + 41 + ], + [ + 170, + 40, + 41 + ] + ], + [ + [ + 149, + 40, + 41 + ], + [ + 170, + 41, + 41 + ] + ], + [ + [ + 150, + 41, + 41 + ], + [ + 171, + 42, + 41 + ] + ], + [ + [ + 151, + 42, + 41 + ], + [ + 171, + 43, + 41 + ] + ], + [ + [ + 152, + 33, + 41 + ], + [ + 167, + 34, + 41 + ] + ], + [ + [ + 152, + 43, + 41 + ], + [ + 171, + 44, + 41 + ] + ], + [ + [ + 152, + 44, + 41 + ], + [ + 172, + 45, + 41 + ] + ], + [ + [ + 153, + 45, + 41 + ], + [ + 172, + 46, + 41 + ] + ], + [ + [ + 154, + 46, + 41 + ], + [ + 173, + 47, + 41 + ] + ], + [ + [ + 155, + 47, + 41 + ], + [ + 173, + 48, + 41 + ] + ], + [ + [ + 156, + 48, + 41 + ], + [ + 173, + 49, + 41 + ] + ], + [ + [ + 156, + 49, + 41 + ], + [ + 174, + 50, + 41 + ] + ], + [ + [ + 157, + 32, + 41 + ], + [ + 166, + 33, + 41 + ] + ], + [ + [ + 157, + 50, + 41 + ], + [ + 174, + 51, + 41 + ] + ], + [ + [ + 158, + 51, + 41 + ], + [ + 175, + 52, + 41 + ] + ], + [ + [ + 159, + 52, + 41 + ], + [ + 175, + 53, + 41 + ] + ], + [ + [ + 160, + 53, + 41 + ], + [ + 175, + 54, + 41 + ] + ], + [ + [ + 161, + 54, + 41 + ], + [ + 176, + 56, + 41 + ] + ], + [ + [ + 162, + 56, + 41 + ], + [ + 176, + 57, + 41 + ] + ], + [ + [ + 163, + 57, + 41 + ], + [ + 177, + 58, + 41 + ] + ], + [ + [ + 164, + 58, + 41 + ], + [ + 177, + 59, + 41 + ] + ], + [ + [ + 165, + 59, + 41 + ], + [ + 177, + 60, + 41 + ] + ], + [ + [ + 166, + 60, + 41 + ], + [ + 178, + 62, + 41 + ] + ], + [ + [ + 167, + 62, + 41 + ], + [ + 178, + 63, + 41 + ] + ], + [ + [ + 168, + 63, + 41 + ], + [ + 179, + 64, + 41 + ] + ], + [ + [ + 169, + 64, + 41 + ], + [ + 179, + 65, + 41 + ] + ], + [ + [ + 170, + 65, + 41 + ], + [ + 180, + 67, + 41 + ] + ], + [ + [ + 171, + 67, + 41 + ], + [ + 180, + 68, + 41 + ] + ], + [ + [ + 172, + 68, + 41 + ], + [ + 181, + 69, + 41 + ] + ], + [ + [ + 173, + 69, + 41 + ], + [ + 181, + 70, + 41 + ] + ], + [ + [ + 174, + 70, + 41 + ], + [ + 182, + 72, + 41 + ] + ], + [ + [ + 97, + 14, + 41 + ], + [ + 98, + 15, + 41 + ] + ], + [ + [ + 92, + 40, + 41 + ], + [ + 93, + 41, + 41 + ] + ], + [ + [ + 95, + 39, + 41 + ], + [ + 98, + 40, + 41 + ] + ], + [ + [ + 125, + 17, + 41 + ], + [ + 127, + 18, + 41 + ] + ], + [ + [ + 121, + 16, + 41 + ], + [ + 123, + 17, + 41 + ] + ], + [ + [ + 114, + 15, + 41 + ], + [ + 117, + 16, + 41 + ] + ], + [ + [ + 140, + 34, + 41 + ], + [ + 147, + 35, + 41 + ] + ], + [ + [ + 145, + 33, + 41 + ], + [ + 152, + 34, + 41 + ] + ], + [ + [ + 148, + 32, + 41 + ], + [ + 157, + 33, + 41 + ] + ], + [ + [ + 149, + 26, + 41 + ], + [ + 154, + 27, + 41 + ] + ], + [ + [ + 150, + 27, + 41 + ], + [ + 158, + 28, + 41 + ] + ], + [ + [ + 150, + 28, + 41 + ], + [ + 163, + 29, + 41 + ] + ], + [ + [ + 150, + 31, + 41 + ], + [ + 167, + 32, + 41 + ] + ], + [ + [ + 151, + 29, + 41 + ], + [ + 166, + 30, + 41 + ] + ], + [ + [ + 151, + 30, + 41 + ], + [ + 167, + 31, + 41 + ] + ], + [ + [ + 130, + 36, + 41 + ], + [ + 131, + 37, + 41 + ] + ], + [ + [ + 134, + 35, + 41 + ], + [ + 139, + 36, + 41 + ] + ], + [ + [ + 147, + 25, + 41 + ], + [ + 149, + 26, + 41 + ] + ], + [ + [ + 126, + 36, + 41 + ], + [ + 130, + 37, + 41 + ] + ], + [ + [ + 116, + 37, + 41 + ], + [ + 120, + 38, + 41 + ] + ], + [ + [ + 154, + 26, + 41 + ], + [ + 157, + 27, + 41 + ] + ], + [ + [ + 141, + 22, + 41 + ], + [ + 144, + 23, + 41 + ] + ], + [ + [ + 143, + 23, + 41 + ], + [ + 147, + 24, + 41 + ] + ], + [ + [ + 145, + 24, + 41 + ], + [ + 150, + 25, + 41 + ] + ], + [ + [ + 149, + 25, + 41 + ], + [ + 154, + 26, + 41 + ] + ], + [ + [ + 135, + 20, + 41 + ], + [ + 137, + 21, + 41 + ] + ], + [ + [ + 132, + 19, + 41 + ], + [ + 134, + 20, + 41 + ] + ], + [ + [ + 130, + 18, + 41 + ], + [ + 131, + 19, + 41 + ] + ], + [ + [ + 163, + 28, + 41 + ], + [ + 164, + 29, + 41 + ] + ], + [ + [ + 158, + 27, + 41 + ], + [ + 161, + 28, + 41 + ] + ], + [ + [ + 138, + 21, + 41 + ], + [ + 141, + 22, + 41 + ] + ], + [ + [ + 41, + 15, + 41 + ], + [ + 43, + 16, + 41 + ] + ], + [ + [ + 129, + 18, + 41 + ], + [ + 130, + 19, + 41 + ] + ], + [ + [ + 177, + 64, + 41 + ], + [ + 179, + 65, + 41 + ] + ], + [ + [ + 169, + 64, + 41 + ], + [ + 171, + 65, + 41 + ] + ], + [ + [ + 42, + 21, + 43 + ], + [ + 42, + 22, + 44 + ] + ], + [ + [ + 75, + 42, + 19 + ], + [ + 76, + 42, + 25 + ] + ], + [ + [ + 74, + 42, + 24 + ], + [ + 75, + 42, + 29 + ] + ], + [ + [ + 73, + 42, + 28 + ], + [ + 74, + 42, + 34 + ] + ], + [ + [ + 72, + 42, + 32 + ], + [ + 73, + 42, + 40 + ] + ], + [ + [ + 76, + 42, + 15 + ], + [ + 77, + 42, + 19 + ] + ], + [ + [ + 77, + 42, + 11 + ], + [ + 78, + 42, + 13 + ] + ], + [ + [ + 73, + 42, + 37 + ], + [ + 82, + 42, + 40 + ] + ], + [ + [ + 83, + 42, + 37 + ], + [ + 90, + 42, + 40 + ] + ], + [ + [ + 82, + 42, + 38 + ], + [ + 83, + 42, + 40 + ] + ], + [ + [ + 93, + 42, + 4 + ], + [ + 94, + 42, + 14 + ] + ], + [ + [ + 92, + 42, + 5 + ], + [ + 93, + 42, + 19 + ] + ], + [ + [ + 91, + 42, + 8 + ], + [ + 92, + 42, + 26 + ] + ], + [ + [ + 90, + 42, + 12 + ], + [ + 91, + 42, + 34 + ] + ], + [ + [ + 89, + 42, + 17 + ], + [ + 90, + 42, + 37 + ] + ], + [ + [ + 88, + 42, + 22 + ], + [ + 89, + 42, + 37 + ] + ], + [ + [ + 87, + 42, + 26 + ], + [ + 88, + 42, + 37 + ] + ], + [ + [ + 86, + 42, + 30 + ], + [ + 87, + 42, + 37 + ] + ], + [ + [ + 85, + 42, + 33 + ], + [ + 86, + 42, + 37 + ] + ], + [ + [ + 84, + 42, + 35 + ], + [ + 85, + 42, + 37 + ] + ], + [ + [ + 75, + 42, + 25 + ], + [ + 76, + 42, + 37 + ] + ], + [ + [ + 76, + 42, + 26 + ], + [ + 77, + 42, + 37 + ] + ], + [ + [ + 74, + 42, + 29 + ], + [ + 75, + 42, + 37 + ] + ], + [ + [ + 77, + 42, + 30 + ], + [ + 78, + 42, + 37 + ] + ], + [ + [ + 78, + 42, + 32 + ], + [ + 79, + 42, + 37 + ] + ], + [ + [ + 73, + 42, + 34 + ], + [ + 74, + 42, + 37 + ] + ], + [ + [ + 79, + 42, + 35 + ], + [ + 80, + 42, + 37 + ] + ], + [ + [ + 150, + 42, + 39 + ], + [ + 151, + 42, + 40 + ] + ], + [ + [ + 78, + 42, + 72 + ], + [ + 79, + 42, + 73 + ] + ], + [ + [ + 93, + 42, + 70 + ], + [ + 94, + 42, + 76 + ] + ], + [ + [ + 92, + 42, + 71 + ], + [ + 93, + 42, + 76 + ] + ], + [ + [ + 91, + 42, + 73 + ], + [ + 92, + 42, + 76 + ] + ], + [ + [ + 90, + 42, + 74 + ], + [ + 91, + 42, + 76 + ] + ], + [ + [ + 89, + 42, + 75 + ], + [ + 90, + 42, + 76 + ] + ], + [ + [ + 94, + 13, + 42 + ], + [ + 96, + 14, + 42 + ] + ], + [ + [ + 71, + 13, + 42 + ], + [ + 78, + 14, + 42 + ] + ], + [ + [ + 67, + 14, + 42 + ], + [ + 68, + 15, + 42 + ] + ], + [ + [ + 82, + 42, + 42 + ], + [ + 83, + 43, + 42 + ] + ], + [ + [ + 94, + 39, + 42 + ], + [ + 95, + 40, + 42 + ] + ], + [ + [ + 92, + 40, + 42 + ], + [ + 93, + 41, + 42 + ] + ], + [ + [ + 64, + 15, + 42 + ], + [ + 65, + 16, + 42 + ] + ], + [ + [ + 42, + 21, + 36 + ], + [ + 42, + 22, + 37 + ] + ], + [ + [ + 89, + 42, + 4 + ], + [ + 90, + 42, + 5 + ] + ], + [ + [ + 90, + 42, + 4 + ], + [ + 91, + 42, + 6 + ] + ], + [ + [ + 91, + 42, + 4 + ], + [ + 92, + 42, + 7 + ] + ], + [ + [ + 92, + 42, + 4 + ], + [ + 93, + 42, + 9 + ] + ], + [ + [ + 93, + 42, + 4 + ], + [ + 94, + 42, + 10 + ] + ], + [ + [ + 170, + 42, + 39 + ], + [ + 171, + 42, + 40 + ] + ], + [ + [ + 150, + 42, + 40 + ], + [ + 151, + 42, + 41 + ] + ], + [ + [ + 72, + 42, + 40 + ], + [ + 73, + 42, + 48 + ] + ], + [ + [ + 73, + 42, + 46 + ], + [ + 74, + 42, + 52 + ] + ], + [ + [ + 74, + 42, + 51 + ], + [ + 75, + 42, + 56 + ] + ], + [ + [ + 75, + 42, + 55 + ], + [ + 76, + 42, + 61 + ] + ], + [ + [ + 76, + 42, + 61 + ], + [ + 77, + 42, + 65 + ] + ], + [ + [ + 77, + 42, + 67 + ], + [ + 78, + 42, + 69 + ] + ], + [ + [ + 78, + 42, + 72 + ], + [ + 79, + 42, + 73 + ] + ], + [ + [ + 73, + 42, + 40 + ], + [ + 82, + 42, + 43 + ] + ], + [ + [ + 82, + 42, + 40 + ], + [ + 83, + 42, + 42 + ] + ], + [ + [ + 83, + 42, + 40 + ], + [ + 90, + 42, + 43 + ] + ], + [ + [ + 84, + 42, + 43 + ], + [ + 85, + 42, + 45 + ] + ], + [ + [ + 85, + 42, + 43 + ], + [ + 86, + 42, + 47 + ] + ], + [ + [ + 86, + 42, + 43 + ], + [ + 87, + 42, + 50 + ] + ], + [ + [ + 87, + 42, + 43 + ], + [ + 88, + 42, + 54 + ] + ], + [ + [ + 88, + 42, + 43 + ], + [ + 89, + 42, + 59 + ] + ], + [ + [ + 89, + 42, + 43 + ], + [ + 90, + 42, + 63 + ] + ], + [ + [ + 90, + 42, + 46 + ], + [ + 91, + 42, + 68 + ] + ], + [ + [ + 91, + 42, + 54 + ], + [ + 92, + 42, + 72 + ] + ], + [ + [ + 92, + 42, + 61 + ], + [ + 93, + 42, + 75 + ] + ], + [ + [ + 93, + 42, + 67 + ], + [ + 94, + 42, + 76 + ] + ], + [ + [ + 73, + 42, + 43 + ], + [ + 74, + 42, + 46 + ] + ], + [ + [ + 74, + 42, + 43 + ], + [ + 78, + 42, + 51 + ] + ], + [ + [ + 78, + 42, + 43 + ], + [ + 79, + 42, + 48 + ] + ], + [ + [ + 79, + 42, + 43 + ], + [ + 80, + 42, + 45 + ] + ], + [ + [ + 75, + 42, + 51 + ], + [ + 76, + 42, + 55 + ] + ], + [ + [ + 76, + 42, + 51 + ], + [ + 77, + 42, + 54 + ] + ], + [ + [ + 51, + 15, + 42 + ], + [ + 52, + 16, + 42 + ] + ], + [ + [ + 49, + 15, + 42 + ], + [ + 50, + 16, + 42 + ] + ], + [ + [ + 54, + 15, + 42 + ], + [ + 55, + 16, + 42 + ] + ], + [ + [ + 101, + 15, + 42 + ], + [ + 110, + 16, + 42 + ] + ], + [ + [ + 107, + 37, + 42 + ], + [ + 110, + 38, + 42 + ] + ], + [ + [ + 103, + 38, + 42 + ], + [ + 106, + 39, + 42 + ] + ], + [ + [ + 170, + 66, + 42 + ], + [ + 171, + 67, + 42 + ] + ], + [ + [ + 176, + 66, + 42 + ], + [ + 180, + 67, + 42 + ] + ], + [ + [ + 56, + 38, + 42 + ], + [ + 62, + 39, + 42 + ] + ], + [ + [ + 61, + 39, + 42 + ], + [ + 67, + 40, + 42 + ] + ], + [ + [ + 66, + 40, + 42 + ], + [ + 67, + 41, + 42 + ] + ], + [ + [ + 55, + 37, + 42 + ], + [ + 56, + 38, + 42 + ] + ], + [ + [ + 52, + 37, + 42 + ], + [ + 53, + 38, + 42 + ] + ], + [ + [ + 49, + 36, + 42 + ], + [ + 52, + 37, + 42 + ] + ], + [ + [ + 35, + 29, + 42 + ], + [ + 37, + 30, + 42 + ] + ], + [ + [ + 53, + 37, + 42 + ], + [ + 55, + 38, + 42 + ] + ], + [ + [ + 19, + 18, + 42 + ], + [ + 26, + 19, + 42 + ] + ], + [ + [ + 19, + 19, + 42 + ], + [ + 25, + 21, + 42 + ] + ], + [ + [ + 20, + 21, + 42 + ], + [ + 25, + 22, + 42 + ] + ], + [ + [ + 21, + 17, + 42 + ], + [ + 28, + 18, + 42 + ] + ], + [ + [ + 21, + 22, + 42 + ], + [ + 25, + 23, + 42 + ] + ], + [ + [ + 22, + 23, + 42 + ], + [ + 26, + 24, + 42 + ] + ], + [ + [ + 24, + 16, + 42 + ], + [ + 32, + 17, + 42 + ] + ], + [ + [ + 24, + 24, + 42 + ], + [ + 27, + 25, + 42 + ] + ], + [ + [ + 25, + 25, + 42 + ], + [ + 30, + 26, + 42 + ] + ], + [ + [ + 27, + 26, + 42 + ], + [ + 32, + 27, + 42 + ] + ], + [ + [ + 34, + 28, + 42 + ], + [ + 35, + 29, + 42 + ] + ], + [ + [ + 34, + 15, + 42 + ], + [ + 35, + 16, + 42 + ] + ], + [ + [ + 32, + 27, + 42 + ], + [ + 34, + 28, + 42 + ] + ], + [ + [ + 64, + 15, + 42 + ], + [ + 65, + 16, + 42 + ] + ], + [ + [ + 95, + 13, + 42 + ], + [ + 96, + 14, + 42 + ] + ], + [ + [ + 67, + 14, + 42 + ], + [ + 68, + 15, + 42 + ] + ], + [ + [ + 94, + 39, + 42 + ], + [ + 95, + 40, + 42 + ] + ], + [ + [ + 67, + 39, + 42 + ], + [ + 71, + 41, + 42 + ] + ], + [ + [ + 98, + 38, + 42 + ], + [ + 103, + 39, + 42 + ] + ], + [ + [ + 96, + 38, + 42 + ], + [ + 97, + 39, + 42 + ] + ], + [ + [ + 97, + 38, + 42 + ], + [ + 98, + 39, + 42 + ] + ], + [ + [ + 121, + 17, + 42 + ], + [ + 125, + 18, + 42 + ] + ], + [ + [ + 117, + 16, + 42 + ], + [ + 121, + 17, + 42 + ] + ], + [ + [ + 110, + 15, + 42 + ], + [ + 114, + 16, + 42 + ] + ], + [ + [ + 130, + 21, + 42 + ], + [ + 131, + 22, + 42 + ] + ], + [ + [ + 130, + 33, + 42 + ], + [ + 145, + 34, + 42 + ] + ], + [ + [ + 130, + 34, + 42 + ], + [ + 140, + 35, + 42 + ] + ], + [ + [ + 130, + 35, + 42 + ], + [ + 134, + 36, + 42 + ] + ], + [ + [ + 131, + 22, + 42 + ], + [ + 135, + 23, + 42 + ] + ], + [ + [ + 132, + 23, + 42 + ], + [ + 140, + 24, + 42 + ] + ], + [ + [ + 132, + 32, + 42 + ], + [ + 148, + 33, + 42 + ] + ], + [ + [ + 133, + 24, + 42 + ], + [ + 144, + 25, + 42 + ] + ], + [ + [ + 134, + 25, + 42 + ], + [ + 147, + 26, + 42 + ] + ], + [ + [ + 134, + 26, + 42 + ], + [ + 149, + 27, + 42 + ] + ], + [ + [ + 134, + 31, + 42 + ], + [ + 150, + 32, + 42 + ] + ], + [ + [ + 135, + 27, + 42 + ], + [ + 150, + 29, + 42 + ] + ], + [ + [ + 135, + 29, + 42 + ], + [ + 151, + 31, + 42 + ] + ], + [ + [ + 129, + 21, + 42 + ], + [ + 130, + 22, + 42 + ] + ], + [ + [ + 110, + 37, + 42 + ], + [ + 116, + 38, + 42 + ] + ], + [ + [ + 114, + 36, + 42 + ], + [ + 126, + 37, + 42 + ] + ], + [ + [ + 121, + 35, + 42 + ], + [ + 130, + 36, + 42 + ] + ], + [ + [ + 125, + 34, + 42 + ], + [ + 130, + 35, + 42 + ] + ], + [ + [ + 130, + 19, + 42 + ], + [ + 132, + 20, + 42 + ] + ], + [ + [ + 130, + 20, + 42 + ], + [ + 135, + 21, + 42 + ] + ], + [ + [ + 131, + 21, + 42 + ], + [ + 138, + 22, + 42 + ] + ], + [ + [ + 135, + 22, + 42 + ], + [ + 141, + 23, + 42 + ] + ], + [ + [ + 140, + 23, + 42 + ], + [ + 143, + 24, + 42 + ] + ], + [ + [ + 144, + 24, + 42 + ], + [ + 145, + 25, + 42 + ] + ], + [ + [ + 43, + 15, + 42 + ], + [ + 49, + 16, + 42 + ] + ], + [ + [ + 35, + 15, + 42 + ], + [ + 41, + 16, + 42 + ] + ], + [ + [ + 55, + 15, + 42 + ], + [ + 65, + 16, + 42 + ] + ], + [ + [ + 124, + 18, + 42 + ], + [ + 129, + 19, + 42 + ] + ], + [ + [ + 126, + 19, + 42 + ], + [ + 130, + 20, + 42 + ] + ], + [ + [ + 128, + 20, + 42 + ], + [ + 130, + 21, + 42 + ] + ], + [ + [ + 168, + 65, + 42 + ], + [ + 169, + 66, + 42 + ] + ], + [ + [ + 182, + 65, + 42 + ], + [ + 183, + 66, + 42 + ] + ], + [ + [ + 171, + 64, + 42 + ], + [ + 174, + 65, + 42 + ] + ], + [ + [ + 43, + 15, + 41 + ], + [ + 43, + 16, + 42 + ] + ], + [ + [ + 76, + 43, + 19 + ], + [ + 77, + 43, + 21 + ] + ], + [ + [ + 78, + 43, + 8 + ], + [ + 79, + 43, + 12 + ] + ], + [ + [ + 79, + 43, + 4 + ], + [ + 80, + 43, + 8 + ] + ], + [ + [ + 77, + 43, + 13 + ], + [ + 78, + 43, + 16 + ] + ], + [ + [ + 82, + 43, + 37 + ], + [ + 83, + 43, + 38 + ] + ], + [ + [ + 80, + 43, + 4 + ], + [ + 92, + 43, + 8 + ] + ], + [ + [ + 92, + 43, + 4 + ], + [ + 93, + 43, + 5 + ] + ], + [ + [ + 79, + 43, + 8 + ], + [ + 91, + 43, + 12 + ] + ], + [ + [ + 78, + 43, + 12 + ], + [ + 88, + 43, + 26 + ] + ], + [ + [ + 88, + 43, + 12 + ], + [ + 89, + 43, + 22 + ] + ], + [ + [ + 89, + 43, + 12 + ], + [ + 90, + 43, + 17 + ] + ], + [ + [ + 77, + 43, + 16 + ], + [ + 78, + 43, + 26 + ] + ], + [ + [ + 76, + 43, + 21 + ], + [ + 77, + 43, + 26 + ] + ], + [ + [ + 77, + 43, + 26 + ], + [ + 87, + 43, + 30 + ] + ], + [ + [ + 78, + 43, + 30 + ], + [ + 79, + 43, + 32 + ] + ], + [ + [ + 79, + 43, + 30 + ], + [ + 85, + 43, + 35 + ] + ], + [ + [ + 85, + 43, + 30 + ], + [ + 86, + 43, + 33 + ] + ], + [ + [ + 80, + 43, + 35 + ], + [ + 84, + 43, + 37 + ] + ], + [ + [ + 151, + 43, + 39 + ], + [ + 152, + 43, + 40 + ] + ], + [ + [ + 88, + 12, + 43 + ], + [ + 90, + 13, + 43 + ] + ], + [ + [ + 81, + 42, + 43 + ], + [ + 82, + 43, + 43 + ] + ], + [ + [ + 83, + 42, + 43 + ], + [ + 84, + 43, + 43 + ] + ], + [ + [ + 80, + 42, + 43 + ], + [ + 81, + 43, + 43 + ] + ], + [ + [ + 63, + 16, + 43 + ], + [ + 64, + 17, + 43 + ] + ], + [ + [ + 43, + 15, + 38 + ], + [ + 43, + 16, + 39 + ] + ], + [ + [ + 151, + 43, + 40 + ], + [ + 152, + 43, + 41 + ] + ], + [ + [ + 76, + 43, + 59 + ], + [ + 77, + 43, + 61 + ] + ], + [ + [ + 78, + 43, + 68 + ], + [ + 79, + 43, + 72 + ] + ], + [ + [ + 79, + 43, + 72 + ], + [ + 80, + 43, + 76 + ] + ], + [ + [ + 77, + 43, + 64 + ], + [ + 78, + 43, + 67 + ] + ], + [ + [ + 82, + 43, + 42 + ], + [ + 83, + 43, + 43 + ] + ], + [ + [ + 80, + 43, + 43 + ], + [ + 84, + 43, + 45 + ] + ], + [ + [ + 79, + 43, + 45 + ], + [ + 85, + 43, + 54 + ] + ], + [ + [ + 85, + 43, + 47 + ], + [ + 86, + 43, + 54 + ] + ], + [ + [ + 78, + 43, + 48 + ], + [ + 79, + 43, + 54 + ] + ], + [ + [ + 86, + 43, + 50 + ], + [ + 87, + 43, + 54 + ] + ], + [ + [ + 77, + 43, + 51 + ], + [ + 78, + 43, + 54 + ] + ], + [ + [ + 76, + 43, + 54 + ], + [ + 88, + 43, + 59 + ] + ], + [ + [ + 77, + 43, + 59 + ], + [ + 78, + 43, + 64 + ] + ], + [ + [ + 78, + 43, + 59 + ], + [ + 89, + 43, + 68 + ] + ], + [ + [ + 89, + 43, + 63 + ], + [ + 90, + 43, + 68 + ] + ], + [ + [ + 79, + 43, + 68 + ], + [ + 91, + 43, + 72 + ] + ], + [ + [ + 80, + 43, + 72 + ], + [ + 92, + 43, + 76 + ] + ], + [ + [ + 92, + 43, + 75 + ], + [ + 93, + 43, + 76 + ] + ], + [ + [ + 49, + 16, + 43 + ], + [ + 50, + 19, + 43 + ] + ], + [ + [ + 50, + 15, + 43 + ], + [ + 51, + 16, + 43 + ] + ], + [ + [ + 50, + 16, + 43 + ], + [ + 53, + 18, + 43 + ] + ], + [ + [ + 52, + 15, + 43 + ], + [ + 53, + 16, + 43 + ] + ], + [ + [ + 53, + 15, + 43 + ], + [ + 54, + 16, + 43 + ] + ], + [ + [ + 53, + 16, + 43 + ], + [ + 55, + 18, + 43 + ] + ], + [ + [ + 99, + 17, + 43 + ], + [ + 110, + 18, + 43 + ] + ], + [ + [ + 101, + 16, + 43 + ], + [ + 110, + 17, + 43 + ] + ], + [ + [ + 73, + 35, + 43 + ], + [ + 102, + 36, + 43 + ] + ], + [ + [ + 73, + 36, + 43 + ], + [ + 110, + 37, + 43 + ] + ], + [ + [ + 103, + 37, + 43 + ], + [ + 107, + 38, + 43 + ] + ], + [ + [ + 55, + 34, + 43 + ], + [ + 110, + 35, + 43 + ] + ], + [ + [ + 55, + 35, + 43 + ], + [ + 72, + 36, + 43 + ] + ], + [ + [ + 55, + 36, + 43 + ], + [ + 67, + 37, + 43 + ] + ], + [ + [ + 56, + 37, + 43 + ], + [ + 67, + 38, + 43 + ] + ], + [ + [ + 62, + 38, + 43 + ], + [ + 67, + 39, + 43 + ] + ], + [ + [ + 102, + 35, + 43 + ], + [ + 110, + 36, + 43 + ] + ], + [ + [ + 174, + 66, + 43 + ], + [ + 176, + 67, + 43 + ] + ], + [ + [ + 37, + 26, + 43 + ], + [ + 38, + 28, + 43 + ] + ], + [ + [ + 45, + 31, + 43 + ], + [ + 47, + 32, + 43 + ] + ], + [ + [ + 46, + 32, + 43 + ], + [ + 47, + 33, + 43 + ] + ], + [ + [ + 47, + 32, + 43 + ], + [ + 49, + 33, + 43 + ] + ], + [ + [ + 47, + 33, + 43 + ], + [ + 52, + 35, + 43 + ] + ], + [ + [ + 48, + 35, + 43 + ], + [ + 52, + 36, + 43 + ] + ], + [ + [ + 52, + 34, + 43 + ], + [ + 53, + 37, + 43 + ] + ], + [ + [ + 35, + 24, + 43 + ], + [ + 36, + 25, + 43 + ] + ], + [ + [ + 35, + 25, + 43 + ], + [ + 37, + 29, + 43 + ] + ], + [ + [ + 53, + 34, + 43 + ], + [ + 55, + 37, + 43 + ] + ], + [ + [ + 25, + 19, + 43 + ], + [ + 26, + 23, + 43 + ] + ], + [ + [ + 26, + 18, + 43 + ], + [ + 32, + 24, + 43 + ] + ], + [ + [ + 27, + 24, + 43 + ], + [ + 32, + 25, + 43 + ] + ], + [ + [ + 28, + 17, + 43 + ], + [ + 32, + 18, + 43 + ] + ], + [ + [ + 30, + 25, + 43 + ], + [ + 32, + 26, + 43 + ] + ], + [ + [ + 32, + 16, + 43 + ], + [ + 35, + 27, + 43 + ] + ], + [ + [ + 34, + 27, + 43 + ], + [ + 35, + 28, + 43 + ] + ], + [ + [ + 100, + 16, + 43 + ], + [ + 101, + 17, + 43 + ] + ], + [ + [ + 100, + 15, + 43 + ], + [ + 101, + 16, + 43 + ] + ], + [ + [ + 63, + 16, + 43 + ], + [ + 64, + 17, + 43 + ] + ], + [ + [ + 94, + 13, + 43 + ], + [ + 95, + 14, + 43 + ] + ], + [ + [ + 88, + 12, + 43 + ], + [ + 90, + 13, + 43 + ] + ], + [ + [ + 75, + 13, + 43 + ], + [ + 76, + 14, + 43 + ] + ], + [ + [ + 65, + 15, + 43 + ], + [ + 67, + 16, + 43 + ] + ], + [ + [ + 68, + 14, + 43 + ], + [ + 70, + 15, + 43 + ] + ], + [ + [ + 71, + 13, + 43 + ], + [ + 72, + 14, + 43 + ] + ], + [ + [ + 95, + 37, + 43 + ], + [ + 97, + 38, + 43 + ] + ], + [ + [ + 67, + 36, + 43 + ], + [ + 72, + 38, + 43 + ] + ], + [ + [ + 67, + 38, + 43 + ], + [ + 71, + 39, + 43 + ] + ], + [ + [ + 72, + 35, + 43 + ], + [ + 73, + 37, + 43 + ] + ], + [ + [ + 102, + 37, + 43 + ], + [ + 103, + 38, + 43 + ] + ], + [ + [ + 97, + 37, + 43 + ], + [ + 102, + 38, + 43 + ] + ], + [ + [ + 110, + 16, + 43 + ], + [ + 117, + 17, + 43 + ] + ], + [ + [ + 110, + 17, + 43 + ], + [ + 121, + 18, + 43 + ] + ], + [ + [ + 110, + 34, + 43 + ], + [ + 125, + 35, + 43 + ] + ], + [ + [ + 110, + 35, + 43 + ], + [ + 121, + 36, + 43 + ] + ], + [ + [ + 110, + 36, + 43 + ], + [ + 114, + 37, + 43 + ] + ], + [ + [ + 111, + 18, + 43 + ], + [ + 118, + 19, + 43 + ] + ], + [ + [ + 112, + 19, + 43 + ], + [ + 123, + 20, + 43 + ] + ], + [ + [ + 112, + 33, + 43 + ], + [ + 130, + 34, + 43 + ] + ], + [ + [ + 113, + 20, + 43 + ], + [ + 127, + 21, + 43 + ] + ], + [ + [ + 114, + 32, + 43 + ], + [ + 130, + 33, + 43 + ] + ], + [ + [ + 116, + 21, + 43 + ], + [ + 129, + 22, + 43 + ] + ], + [ + [ + 117, + 22, + 43 + ], + [ + 130, + 23, + 43 + ] + ], + [ + [ + 117, + 31, + 43 + ], + [ + 130, + 32, + 43 + ] + ], + [ + [ + 118, + 23, + 43 + ], + [ + 130, + 24, + 43 + ] + ], + [ + [ + 118, + 29, + 43 + ], + [ + 130, + 31, + 43 + ] + ], + [ + [ + 119, + 24, + 43 + ], + [ + 130, + 29, + 43 + ] + ], + [ + [ + 130, + 22, + 43 + ], + [ + 131, + 23, + 43 + ] + ], + [ + [ + 130, + 23, + 43 + ], + [ + 132, + 33, + 43 + ] + ], + [ + [ + 132, + 24, + 43 + ], + [ + 133, + 25, + 43 + ] + ], + [ + [ + 132, + 25, + 43 + ], + [ + 134, + 32, + 43 + ] + ], + [ + [ + 134, + 27, + 43 + ], + [ + 135, + 31, + 43 + ] + ], + [ + [ + 35, + 16, + 43 + ], + [ + 49, + 19, + 43 + ] + ], + [ + [ + 35, + 19, + 43 + ], + [ + 45, + 20, + 43 + ] + ], + [ + [ + 35, + 20, + 43 + ], + [ + 44, + 21, + 43 + ] + ], + [ + [ + 35, + 21, + 43 + ], + [ + 42, + 22, + 43 + ] + ], + [ + [ + 35, + 22, + 43 + ], + [ + 39, + 23, + 43 + ] + ], + [ + [ + 35, + 23, + 43 + ], + [ + 37, + 24, + 43 + ] + ], + [ + [ + 55, + 16, + 43 + ], + [ + 64, + 17, + 43 + ] + ], + [ + [ + 55, + 17, + 43 + ], + [ + 63, + 18, + 43 + ] + ], + [ + [ + 118, + 18, + 43 + ], + [ + 124, + 19, + 43 + ] + ], + [ + [ + 123, + 19, + 43 + ], + [ + 126, + 20, + 43 + ] + ], + [ + [ + 127, + 20, + 43 + ], + [ + 128, + 21, + 43 + ] + ], + [ + [ + 174, + 64, + 43 + ], + [ + 176, + 65, + 43 + ] + ], + [ + [ + 44, + 20, + 43 + ], + [ + 44, + 21, + 44 + ] + ], + [ + [ + 171, + 44, + 40 + ], + [ + 172, + 44, + 41 + ] + ], + [ + [ + 174, + 66, + 44 + ], + [ + 177, + 67, + 44 + ] + ], + [ + [ + 44, + 20, + 36 + ], + [ + 44, + 21, + 37 + ] + ], + [ + [ + 171, + 44, + 39 + ], + [ + 172, + 44, + 40 + ] + ], + [ + [ + 49, + 19, + 44 + ], + [ + 65, + 20, + 44 + ] + ], + [ + [ + 49, + 20, + 44 + ], + [ + 67, + 21, + 44 + ] + ], + [ + [ + 49, + 21, + 44 + ], + [ + 110, + 26, + 44 + ] + ], + [ + [ + 50, + 26, + 44 + ], + [ + 110, + 27, + 44 + ] + ], + [ + [ + 53, + 27, + 44 + ], + [ + 110, + 34, + 44 + ] + ], + [ + [ + 55, + 18, + 44 + ], + [ + 64, + 19, + 44 + ] + ], + [ + [ + 88, + 20, + 44 + ], + [ + 110, + 21, + 44 + ] + ], + [ + [ + 94, + 19, + 44 + ], + [ + 110, + 20, + 44 + ] + ], + [ + [ + 97, + 18, + 44 + ], + [ + 110, + 19, + 44 + ] + ], + [ + [ + 50, + 18, + 44 + ], + [ + 53, + 19, + 44 + ] + ], + [ + [ + 53, + 18, + 44 + ], + [ + 55, + 19, + 44 + ] + ], + [ + [ + 171, + 66, + 44 + ], + [ + 173, + 67, + 44 + ] + ], + [ + [ + 38, + 25, + 44 + ], + [ + 41, + 26, + 44 + ] + ], + [ + [ + 38, + 26, + 44 + ], + [ + 50, + 27, + 44 + ] + ], + [ + [ + 43, + 27, + 44 + ], + [ + 53, + 29, + 44 + ] + ], + [ + [ + 44, + 29, + 44 + ], + [ + 53, + 30, + 44 + ] + ], + [ + [ + 45, + 30, + 44 + ], + [ + 53, + 31, + 44 + ] + ], + [ + [ + 47, + 31, + 44 + ], + [ + 53, + 32, + 44 + ] + ], + [ + [ + 49, + 32, + 44 + ], + [ + 53, + 33, + 44 + ] + ], + [ + [ + 52, + 33, + 44 + ], + [ + 53, + 34, + 44 + ] + ], + [ + [ + 37, + 25, + 44 + ], + [ + 38, + 26, + 44 + ] + ], + [ + [ + 64, + 18, + 44 + ], + [ + 66, + 19, + 44 + ] + ], + [ + [ + 65, + 19, + 44 + ], + [ + 66, + 20, + 44 + ] + ], + [ + [ + 97, + 17, + 44 + ], + [ + 99, + 18, + 44 + ] + ], + [ + [ + 98, + 16, + 44 + ], + [ + 100, + 17, + 44 + ] + ], + [ + [ + 96, + 18, + 44 + ], + [ + 97, + 19, + 44 + ] + ], + [ + [ + 92, + 19, + 44 + ], + [ + 94, + 20, + 44 + ] + ], + [ + [ + 87, + 20, + 44 + ], + [ + 88, + 21, + 44 + ] + ], + [ + [ + 67, + 20, + 44 + ], + [ + 70, + 21, + 44 + ] + ], + [ + [ + 98, + 15, + 44 + ], + [ + 100, + 16, + 44 + ] + ], + [ + [ + 63, + 17, + 44 + ], + [ + 66, + 18, + 44 + ] + ], + [ + [ + 64, + 16, + 44 + ], + [ + 67, + 17, + 44 + ] + ], + [ + [ + 76, + 13, + 44 + ], + [ + 94, + 14, + 44 + ] + ], + [ + [ + 95, + 14, + 44 + ], + [ + 97, + 15, + 44 + ] + ], + [ + [ + 72, + 13, + 44 + ], + [ + 75, + 14, + 44 + ] + ], + [ + [ + 67, + 15, + 44 + ], + [ + 69, + 16, + 44 + ] + ], + [ + [ + 70, + 14, + 44 + ], + [ + 72, + 15, + 44 + ] + ], + [ + [ + 72, + 37, + 44 + ], + [ + 73, + 38, + 44 + ] + ], + [ + [ + 71, + 38, + 44 + ], + [ + 72, + 39, + 44 + ] + ], + [ + [ + 93, + 37, + 44 + ], + [ + 95, + 38, + 44 + ] + ], + [ + [ + 110, + 18, + 44 + ], + [ + 111, + 19, + 44 + ] + ], + [ + [ + 110, + 19, + 44 + ], + [ + 112, + 34, + 44 + ] + ], + [ + [ + 112, + 20, + 44 + ], + [ + 113, + 21, + 44 + ] + ], + [ + [ + 112, + 21, + 44 + ], + [ + 116, + 22, + 44 + ] + ], + [ + [ + 112, + 22, + 44 + ], + [ + 117, + 32, + 44 + ] + ], + [ + [ + 112, + 32, + 44 + ], + [ + 114, + 33, + 44 + ] + ], + [ + [ + 117, + 23, + 44 + ], + [ + 118, + 31, + 44 + ] + ], + [ + [ + 118, + 24, + 44 + ], + [ + 119, + 29, + 44 + ] + ], + [ + [ + 36, + 24, + 44 + ], + [ + 49, + 25, + 44 + ] + ], + [ + [ + 37, + 23, + 44 + ], + [ + 49, + 24, + 44 + ] + ], + [ + [ + 39, + 22, + 44 + ], + [ + 49, + 23, + 44 + ] + ], + [ + [ + 41, + 25, + 44 + ], + [ + 49, + 26, + 44 + ] + ], + [ + [ + 42, + 21, + 44 + ], + [ + 49, + 22, + 44 + ] + ], + [ + [ + 44, + 20, + 44 + ], + [ + 49, + 21, + 44 + ] + ], + [ + [ + 45, + 19, + 44 + ], + [ + 49, + 20, + 44 + ] + ], + [ + [ + 169, + 65, + 44 + ], + [ + 170, + 66, + 44 + ] + ], + [ + [ + 176, + 64, + 44 + ], + [ + 177, + 65, + 44 + ] + ], + [ + [ + 45, + 19, + 43 + ], + [ + 45, + 20, + 44 + ] + ], + [ + [ + 152, + 45, + 39 + ], + [ + 153, + 45, + 40 + ] + ], + [ + [ + 177, + 66, + 45 + ], + [ + 180, + 67, + 45 + ] + ], + [ + [ + 79, + 42, + 45 + ], + [ + 80, + 43, + 45 + ] + ], + [ + [ + 84, + 42, + 45 + ], + [ + 85, + 43, + 45 + ] + ], + [ + [ + 45, + 19, + 36 + ], + [ + 45, + 20, + 37 + ] + ], + [ + [ + 152, + 45, + 40 + ], + [ + 153, + 45, + 41 + ] + ], + [ + [ + 173, + 66, + 45 + ], + [ + 177, + 67, + 45 + ] + ], + [ + [ + 66, + 18, + 45 + ], + [ + 69, + 19, + 45 + ] + ], + [ + [ + 66, + 19, + 45 + ], + [ + 70, + 20, + 45 + ] + ], + [ + [ + 97, + 16, + 45 + ], + [ + 98, + 17, + 45 + ] + ], + [ + [ + 93, + 18, + 45 + ], + [ + 96, + 19, + 45 + ] + ], + [ + [ + 95, + 17, + 45 + ], + [ + 97, + 18, + 45 + ] + ], + [ + [ + 90, + 19, + 45 + ], + [ + 92, + 20, + 45 + ] + ], + [ + [ + 70, + 20, + 45 + ], + [ + 87, + 21, + 45 + ] + ], + [ + [ + 76, + 14, + 45 + ], + [ + 95, + 15, + 45 + ] + ], + [ + [ + 93, + 15, + 45 + ], + [ + 98, + 16, + 45 + ] + ], + [ + [ + 95, + 16, + 45 + ], + [ + 97, + 17, + 45 + ] + ], + [ + [ + 66, + 17, + 45 + ], + [ + 69, + 18, + 45 + ] + ], + [ + [ + 67, + 16, + 45 + ], + [ + 70, + 17, + 45 + ] + ], + [ + [ + 69, + 15, + 45 + ], + [ + 75, + 16, + 45 + ] + ], + [ + [ + 72, + 14, + 45 + ], + [ + 76, + 15, + 45 + ] + ], + [ + [ + 71, + 40, + 45 + ], + [ + 72, + 41, + 45 + ] + ], + [ + [ + 91, + 37, + 45 + ], + [ + 93, + 38, + 45 + ] + ], + [ + [ + 73, + 37, + 45 + ], + [ + 74, + 38, + 45 + ] + ], + [ + [ + 153, + 46, + 39 + ], + [ + 154, + 46, + 40 + ] + ], + [ + [ + 172, + 46, + 40 + ], + [ + 173, + 46, + 41 + ] + ], + [ + [ + 180, + 66, + 46 + ], + [ + 181, + 67, + 46 + ] + ], + [ + [ + 179, + 66, + 46 + ], + [ + 180, + 67, + 46 + ] + ], + [ + [ + 90, + 41, + 46 + ], + [ + 91, + 42, + 46 + ] + ], + [ + [ + 96, + 38, + 46 + ], + [ + 97, + 39, + 46 + ] + ], + [ + [ + 46, + 31, + 36 + ], + [ + 46, + 32, + 37 + ] + ], + [ + [ + 172, + 46, + 39 + ], + [ + 173, + 46, + 40 + ] + ], + [ + [ + 153, + 46, + 40 + ], + [ + 154, + 46, + 41 + ] + ], + [ + [ + 180, + 66, + 46 + ], + [ + 181, + 67, + 46 + ] + ], + [ + [ + 177, + 66, + 46 + ], + [ + 180, + 67, + 46 + ] + ], + [ + [ + 69, + 18, + 46 + ], + [ + 93, + 19, + 46 + ] + ], + [ + [ + 70, + 19, + 46 + ], + [ + 90, + 20, + 46 + ] + ], + [ + [ + 90, + 17, + 46 + ], + [ + 95, + 18, + 46 + ] + ], + [ + [ + 69, + 17, + 46 + ], + [ + 90, + 18, + 46 + ] + ], + [ + [ + 70, + 16, + 46 + ], + [ + 95, + 17, + 46 + ] + ], + [ + [ + 75, + 15, + 46 + ], + [ + 93, + 16, + 46 + ] + ], + [ + [ + 71, + 39, + 46 + ], + [ + 72, + 40, + 46 + ] + ], + [ + [ + 89, + 37, + 46 + ], + [ + 91, + 38, + 46 + ] + ], + [ + [ + 74, + 37, + 46 + ], + [ + 75, + 38, + 46 + ] + ], + [ + [ + 170, + 65, + 46 + ], + [ + 171, + 66, + 46 + ] + ], + [ + [ + 47, + 31, + 43 + ], + [ + 47, + 32, + 44 + ] + ], + [ + [ + 154, + 47, + 39 + ], + [ + 155, + 47, + 40 + ] + ], + [ + [ + 175, + 66, + 47 + ], + [ + 179, + 67, + 47 + ] + ], + [ + [ + 85, + 42, + 47 + ], + [ + 86, + 43, + 47 + ] + ], + [ + [ + 154, + 47, + 40 + ], + [ + 155, + 47, + 41 + ] + ], + [ + [ + 178, + 66, + 47 + ], + [ + 180, + 67, + 47 + ] + ], + [ + [ + 72, + 38, + 47 + ], + [ + 73, + 39, + 47 + ] + ], + [ + [ + 87, + 37, + 47 + ], + [ + 89, + 38, + 47 + ] + ], + [ + [ + 75, + 37, + 47 + ], + [ + 76, + 38, + 47 + ] + ], + [ + [ + 48, + 36, + 40 + ], + [ + 48, + 37, + 41 + ] + ], + [ + [ + 155, + 48, + 39 + ], + [ + 156, + 48, + 40 + ] + ], + [ + [ + 173, + 66, + 48 + ], + [ + 175, + 67, + 48 + ] + ], + [ + [ + 78, + 42, + 48 + ], + [ + 79, + 43, + 48 + ] + ], + [ + [ + 48, + 36, + 39 + ], + [ + 48, + 37, + 40 + ] + ], + [ + [ + 155, + 48, + 40 + ], + [ + 156, + 48, + 41 + ] + ], + [ + [ + 175, + 66, + 48 + ], + [ + 178, + 67, + 48 + ] + ], + [ + [ + 72, + 41, + 48 + ], + [ + 73, + 42, + 48 + ] + ], + [ + [ + 85, + 37, + 48 + ], + [ + 87, + 38, + 48 + ] + ], + [ + [ + 76, + 37, + 48 + ], + [ + 78, + 38, + 48 + ] + ], + [ + [ + 171, + 65, + 48 + ], + [ + 172, + 66, + 48 + ] + ], + [ + [ + 181, + 65, + 48 + ], + [ + 182, + 66, + 48 + ] + ], + [ + [ + 49, + 36, + 41 + ], + [ + 49, + 37, + 42 + ] + ], + [ + [ + 49, + 32, + 43 + ], + [ + 49, + 33, + 44 + ] + ], + [ + [ + 173, + 49, + 40 + ], + [ + 174, + 49, + 41 + ] + ], + [ + [ + 175, + 66, + 49 + ], + [ + 176, + 67, + 49 + ] + ], + [ + [ + 58, + 35, + 49 + ], + [ + 63, + 36, + 49 + ] + ], + [ + [ + 58, + 36, + 49 + ], + [ + 85, + 37, + 49 + ] + ], + [ + [ + 58, + 37, + 49 + ], + [ + 79, + 38, + 49 + ] + ], + [ + [ + 61, + 38, + 49 + ], + [ + 73, + 39, + 49 + ] + ], + [ + [ + 68, + 39, + 49 + ], + [ + 72, + 40, + 49 + ] + ], + [ + [ + 83, + 37, + 49 + ], + [ + 89, + 38, + 49 + ] + ], + [ + [ + 56, + 36, + 49 + ], + [ + 57, + 37, + 49 + ] + ], + [ + [ + 58, + 31, + 49 + ], + [ + 82, + 32, + 49 + ] + ], + [ + [ + 58, + 32, + 49 + ], + [ + 85, + 33, + 49 + ] + ], + [ + [ + 58, + 33, + 49 + ], + [ + 87, + 34, + 49 + ] + ], + [ + [ + 58, + 34, + 49 + ], + [ + 88, + 35, + 49 + ] + ], + [ + [ + 63, + 35, + 49 + ], + [ + 88, + 36, + 49 + ] + ], + [ + [ + 67, + 30, + 49 + ], + [ + 76, + 31, + 49 + ] + ], + [ + [ + 85, + 36, + 49 + ], + [ + 89, + 37, + 49 + ] + ], + [ + [ + 89, + 37, + 49 + ], + [ + 90, + 38, + 49 + ] + ], + [ + [ + 85, + 32, + 49 + ], + [ + 86, + 33, + 49 + ] + ], + [ + [ + 82, + 31, + 49 + ], + [ + 84, + 32, + 49 + ] + ], + [ + [ + 56, + 31, + 49 + ], + [ + 58, + 36, + 49 + ] + ], + [ + [ + 57, + 30, + 49 + ], + [ + 67, + 31, + 49 + ] + ], + [ + [ + 57, + 36, + 49 + ], + [ + 58, + 38, + 49 + ] + ], + [ + [ + 61, + 29, + 49 + ], + [ + 79, + 30, + 49 + ] + ], + [ + [ + 76, + 30, + 49 + ], + [ + 82, + 31, + 49 + ] + ], + [ + [ + 71, + 40, + 49 + ], + [ + 72, + 41, + 49 + ] + ], + [ + [ + 64, + 39, + 49 + ], + [ + 68, + 40, + 49 + ] + ], + [ + [ + 60, + 38, + 49 + ], + [ + 61, + 39, + 49 + ] + ], + [ + [ + 79, + 37, + 49 + ], + [ + 83, + 38, + 49 + ] + ], + [ + [ + 49, + 36, + 38 + ], + [ + 49, + 37, + 39 + ] + ], + [ + [ + 49, + 32, + 36 + ], + [ + 49, + 33, + 37 + ] + ], + [ + [ + 49, + 18, + 36 + ], + [ + 49, + 19, + 37 + ] + ], + [ + [ + 49, + 15, + 37 + ], + [ + 49, + 16, + 38 + ] + ], + [ + [ + 173, + 49, + 39 + ], + [ + 174, + 49, + 40 + ] + ], + [ + [ + 173, + 66, + 49 + ], + [ + 174, + 67, + 49 + ] + ], + [ + [ + 83, + 37, + 49 + ], + [ + 85, + 38, + 49 + ] + ], + [ + [ + 78, + 37, + 49 + ], + [ + 79, + 38, + 49 + ] + ], + [ + [ + 96, + 38, + 49 + ], + [ + 97, + 39, + 49 + ] + ], + [ + [ + 180, + 65, + 49 + ], + [ + 181, + 66, + 49 + ] + ], + [ + [ + 50, + 18, + 43 + ], + [ + 50, + 19, + 44 + ] + ], + [ + [ + 50, + 15, + 42 + ], + [ + 50, + 16, + 43 + ] + ], + [ + [ + 156, + 50, + 39 + ], + [ + 157, + 50, + 40 + ] + ], + [ + [ + 176, + 66, + 50 + ], + [ + 177, + 67, + 50 + ] + ], + [ + [ + 73, + 38, + 50 + ], + [ + 74, + 39, + 50 + ] + ], + [ + [ + 72, + 39, + 50 + ], + [ + 73, + 41, + 50 + ] + ], + [ + [ + 56, + 30, + 50 + ], + [ + 57, + 31, + 50 + ] + ], + [ + [ + 56, + 37, + 50 + ], + [ + 57, + 38, + 50 + ] + ], + [ + [ + 88, + 34, + 50 + ], + [ + 89, + 36, + 50 + ] + ], + [ + [ + 89, + 35, + 50 + ], + [ + 90, + 37, + 50 + ] + ], + [ + [ + 90, + 36, + 50 + ], + [ + 91, + 37, + 50 + ] + ], + [ + [ + 90, + 37, + 50 + ], + [ + 93, + 38, + 50 + ] + ], + [ + [ + 91, + 36, + 50 + ], + [ + 92, + 37, + 50 + ] + ], + [ + [ + 90, + 35, + 50 + ], + [ + 91, + 36, + 50 + ] + ], + [ + [ + 87, + 33, + 50 + ], + [ + 88, + 34, + 50 + ] + ], + [ + [ + 86, + 32, + 50 + ], + [ + 87, + 33, + 50 + ] + ], + [ + [ + 84, + 31, + 50 + ], + [ + 85, + 32, + 50 + ] + ], + [ + [ + 82, + 30, + 50 + ], + [ + 83, + 31, + 50 + ] + ], + [ + [ + 79, + 29, + 50 + ], + [ + 80, + 30, + 50 + ] + ], + [ + [ + 71, + 28, + 50 + ], + [ + 74, + 29, + 50 + ] + ], + [ + [ + 59, + 29, + 50 + ], + [ + 61, + 30, + 50 + ] + ], + [ + [ + 74, + 28, + 50 + ], + [ + 75, + 29, + 50 + ] + ], + [ + [ + 58, + 29, + 50 + ], + [ + 59, + 30, + 50 + ] + ], + [ + [ + 69, + 28, + 50 + ], + [ + 71, + 29, + 50 + ] + ], + [ + [ + 61, + 39, + 50 + ], + [ + 64, + 40, + 50 + ] + ], + [ + [ + 66, + 40, + 50 + ], + [ + 71, + 41, + 50 + ] + ], + [ + [ + 58, + 38, + 50 + ], + [ + 60, + 39, + 50 + ] + ], + [ + [ + 93, + 40, + 50 + ], + [ + 94, + 41, + 50 + ] + ], + [ + [ + 86, + 42, + 50 + ], + [ + 87, + 43, + 50 + ] + ], + [ + [ + 180, + 65, + 50 + ], + [ + 181, + 66, + 50 + ] + ], + [ + [ + 180, + 65, + 50 + ], + [ + 181, + 66, + 50 + ] + ], + [ + [ + 156, + 50, + 40 + ], + [ + 157, + 50, + 41 + ] + ], + [ + [ + 94, + 38, + 50 + ], + [ + 96, + 39, + 50 + ] + ], + [ + [ + 66, + 40, + 50 + ], + [ + 67, + 41, + 50 + ] + ], + [ + [ + 56, + 37, + 50 + ], + [ + 57, + 38, + 50 + ] + ], + [ + [ + 69, + 28, + 50 + ], + [ + 70, + 29, + 50 + ] + ], + [ + [ + 180, + 65, + 50 + ], + [ + 181, + 66, + 50 + ] + ], + [ + [ + 51, + 37, + 40 + ], + [ + 51, + 38, + 41 + ] + ], + [ + [ + 157, + 51, + 39 + ], + [ + 158, + 51, + 40 + ] + ], + [ + [ + 174, + 51, + 40 + ], + [ + 175, + 51, + 41 + ] + ], + [ + [ + 177, + 66, + 51 + ], + [ + 178, + 67, + 51 + ] + ], + [ + [ + 179, + 65, + 51 + ], + [ + 180, + 66, + 51 + ] + ], + [ + [ + 178, + 65, + 51 + ], + [ + 179, + 66, + 51 + ] + ], + [ + [ + 178, + 65, + 51 + ], + [ + 179, + 66, + 51 + ] + ], + [ + [ + 174, + 65, + 51 + ], + [ + 175, + 66, + 51 + ] + ], + [ + [ + 77, + 42, + 51 + ], + [ + 78, + 43, + 51 + ] + ], + [ + [ + 51, + 37, + 39 + ], + [ + 51, + 38, + 40 + ] + ], + [ + [ + 51, + 15, + 42 + ], + [ + 51, + 16, + 43 + ] + ], + [ + [ + 157, + 51, + 40 + ], + [ + 158, + 51, + 41 + ] + ], + [ + [ + 174, + 66, + 51 + ], + [ + 175, + 67, + 51 + ] + ], + [ + [ + 179, + 65, + 51 + ], + [ + 181, + 66, + 51 + ] + ], + [ + [ + 172, + 65, + 51 + ], + [ + 180, + 66, + 51 + ] + ], + [ + [ + 175, + 66, + 51 + ], + [ + 178, + 67, + 51 + ] + ], + [ + [ + 178, + 65, + 51 + ], + [ + 179, + 66, + 51 + ] + ], + [ + [ + 93, + 38, + 51 + ], + [ + 94, + 39, + 51 + ] + ], + [ + [ + 58, + 38, + 51 + ], + [ + 62, + 39, + 51 + ] + ], + [ + [ + 61, + 39, + 51 + ], + [ + 70, + 40, + 51 + ] + ], + [ + [ + 67, + 40, + 51 + ], + [ + 73, + 41, + 51 + ] + ], + [ + [ + 76, + 31, + 51 + ], + [ + 82, + 32, + 51 + ] + ], + [ + [ + 77, + 32, + 51 + ], + [ + 85, + 33, + 51 + ] + ], + [ + [ + 78, + 33, + 51 + ], + [ + 87, + 34, + 51 + ] + ], + [ + [ + 79, + 34, + 51 + ], + [ + 89, + 35, + 51 + ] + ], + [ + [ + 80, + 35, + 51 + ], + [ + 90, + 36, + 51 + ] + ], + [ + [ + 85, + 36, + 51 + ], + [ + 91, + 37, + 51 + ] + ], + [ + [ + 89, + 37, + 51 + ], + [ + 93, + 38, + 51 + ] + ], + [ + [ + 58, + 31, + 51 + ], + [ + 69, + 32, + 51 + ] + ], + [ + [ + 58, + 32, + 51 + ], + [ + 66, + 33, + 51 + ] + ], + [ + [ + 58, + 33, + 51 + ], + [ + 63, + 34, + 51 + ] + ], + [ + [ + 58, + 34, + 51 + ], + [ + 61, + 35, + 51 + ] + ], + [ + [ + 67, + 30, + 51 + ], + [ + 76, + 31, + 51 + ] + ], + [ + [ + 56, + 31, + 51 + ], + [ + 58, + 36, + 51 + ] + ], + [ + [ + 57, + 30, + 51 + ], + [ + 67, + 31, + 51 + ] + ], + [ + [ + 57, + 36, + 51 + ], + [ + 58, + 37, + 51 + ] + ], + [ + [ + 59, + 29, + 51 + ], + [ + 80, + 30, + 51 + ] + ], + [ + [ + 71, + 28, + 51 + ], + [ + 74, + 29, + 51 + ] + ], + [ + [ + 76, + 30, + 51 + ], + [ + 83, + 31, + 51 + ] + ], + [ + [ + 82, + 31, + 51 + ], + [ + 85, + 32, + 51 + ] + ], + [ + [ + 56, + 36, + 51 + ], + [ + 57, + 37, + 51 + ] + ], + [ + [ + 57, + 37, + 51 + ], + [ + 58, + 38, + 51 + ] + ], + [ + [ + 56, + 30, + 51 + ], + [ + 57, + 31, + 51 + ] + ], + [ + [ + 91, + 36, + 51 + ], + [ + 92, + 37, + 51 + ] + ], + [ + [ + 90, + 35, + 51 + ], + [ + 91, + 36, + 51 + ] + ], + [ + [ + 87, + 33, + 51 + ], + [ + 88, + 34, + 51 + ] + ], + [ + [ + 85, + 32, + 51 + ], + [ + 87, + 33, + 51 + ] + ], + [ + [ + 74, + 28, + 51 + ], + [ + 75, + 29, + 51 + ] + ], + [ + [ + 58, + 29, + 51 + ], + [ + 59, + 30, + 51 + ] + ], + [ + [ + 70, + 28, + 51 + ], + [ + 71, + 29, + 51 + ] + ], + [ + [ + 77, + 37, + 51 + ], + [ + 89, + 38, + 51 + ] + ], + [ + [ + 78, + 36, + 51 + ], + [ + 85, + 37, + 51 + ] + ], + [ + [ + 58, + 35, + 51 + ], + [ + 60, + 36, + 51 + ] + ], + [ + [ + 58, + 36, + 51 + ], + [ + 64, + 37, + 51 + ] + ], + [ + [ + 58, + 37, + 51 + ], + [ + 68, + 38, + 51 + ] + ], + [ + [ + 62, + 38, + 51 + ], + [ + 73, + 39, + 51 + ] + ], + [ + [ + 70, + 39, + 51 + ], + [ + 73, + 40, + 51 + ] + ], + [ + [ + 52, + 15, + 42 + ], + [ + 52, + 16, + 43 + ] + ], + [ + [ + 52, + 37, + 41 + ], + [ + 52, + 38, + 42 + ] + ], + [ + [ + 52, + 36, + 42 + ], + [ + 52, + 37, + 43 + ] + ], + [ + [ + 52, + 33, + 43 + ], + [ + 52, + 34, + 44 + ] + ], + [ + [ + 158, + 52, + 39 + ], + [ + 159, + 52, + 40 + ] + ], + [ + [ + 95, + 39, + 52 + ], + [ + 96, + 40, + 52 + ] + ], + [ + [ + 52, + 37, + 38 + ], + [ + 52, + 38, + 39 + ] + ], + [ + [ + 52, + 36, + 37 + ], + [ + 52, + 37, + 38 + ] + ], + [ + [ + 52, + 33, + 36 + ], + [ + 52, + 34, + 37 + ] + ], + [ + [ + 174, + 52, + 39 + ], + [ + 175, + 52, + 40 + ] + ], + [ + [ + 158, + 52, + 40 + ], + [ + 159, + 52, + 41 + ] + ], + [ + [ + 74, + 38, + 52 + ], + [ + 75, + 39, + 52 + ] + ], + [ + [ + 73, + 41, + 52 + ], + [ + 74, + 42, + 52 + ] + ], + [ + [ + 91, + 38, + 52 + ], + [ + 93, + 39, + 52 + ] + ], + [ + [ + 61, + 34, + 52 + ], + [ + 79, + 35, + 52 + ] + ], + [ + [ + 63, + 33, + 52 + ], + [ + 78, + 34, + 52 + ] + ], + [ + [ + 63, + 35, + 52 + ], + [ + 80, + 36, + 52 + ] + ], + [ + [ + 66, + 32, + 52 + ], + [ + 77, + 33, + 52 + ] + ], + [ + [ + 69, + 31, + 52 + ], + [ + 76, + 32, + 52 + ] + ], + [ + [ + 64, + 36, + 52 + ], + [ + 78, + 37, + 52 + ] + ], + [ + [ + 68, + 37, + 52 + ], + [ + 77, + 38, + 52 + ] + ], + [ + [ + 73, + 38, + 52 + ], + [ + 74, + 39, + 52 + ] + ], + [ + [ + 60, + 35, + 52 + ], + [ + 63, + 36, + 52 + ] + ], + [ + [ + 159, + 53, + 39 + ], + [ + 160, + 53, + 40 + ] + ], + [ + [ + 159, + 53, + 40 + ], + [ + 160, + 53, + 41 + ] + ], + [ + [ + 73, + 39, + 53 + ], + [ + 74, + 41, + 53 + ] + ], + [ + [ + 89, + 38, + 53 + ], + [ + 91, + 39, + 53 + ] + ], + [ + [ + 75, + 38, + 53 + ], + [ + 76, + 39, + 53 + ] + ], + [ + [ + 54, + 15, + 37 + ], + [ + 54, + 16, + 38 + ] + ], + [ + [ + 54, + 38, + 40 + ], + [ + 54, + 39, + 41 + ] + ], + [ + [ + 160, + 54, + 39 + ], + [ + 161, + 54, + 40 + ] + ], + [ + [ + 175, + 54, + 40 + ], + [ + 176, + 54, + 41 + ] + ], + [ + [ + 76, + 42, + 54 + ], + [ + 77, + 43, + 54 + ] + ], + [ + [ + 87, + 42, + 54 + ], + [ + 88, + 43, + 54 + ] + ], + [ + [ + 91, + 41, + 54 + ], + [ + 92, + 42, + 54 + ] + ], + [ + [ + 54, + 38, + 39 + ], + [ + 54, + 39, + 40 + ] + ], + [ + [ + 54, + 15, + 42 + ], + [ + 54, + 16, + 43 + ] + ], + [ + [ + 160, + 54, + 40 + ], + [ + 161, + 54, + 41 + ] + ], + [ + [ + 88, + 38, + 54 + ], + [ + 89, + 39, + 54 + ] + ], + [ + [ + 76, + 38, + 54 + ], + [ + 77, + 39, + 54 + ] + ], + [ + [ + 55, + 38, + 38 + ], + [ + 55, + 39, + 39 + ] + ], + [ + [ + 175, + 55, + 39 + ], + [ + 176, + 55, + 40 + ] + ], + [ + [ + 86, + 38, + 55 + ], + [ + 88, + 39, + 55 + ] + ], + [ + [ + 77, + 38, + 55 + ], + [ + 78, + 39, + 55 + ] + ], + [ + [ + 56, + 38, + 41 + ], + [ + 56, + 39, + 42 + ] + ], + [ + [ + 56, + 37, + 42 + ], + [ + 56, + 38, + 43 + ] + ], + [ + [ + 56, + 30, + 50 + ], + [ + 56, + 37, + 51 + ] + ], + [ + [ + 56, + 31, + 49 + ], + [ + 56, + 37, + 50 + ] + ], + [ + [ + 161, + 56, + 39 + ], + [ + 162, + 56, + 40 + ] + ], + [ + [ + 56, + 30, + 29 + ], + [ + 56, + 37, + 30 + ] + ], + [ + [ + 56, + 31, + 30 + ], + [ + 56, + 37, + 31 + ] + ], + [ + [ + 56, + 37, + 37 + ], + [ + 56, + 38, + 38 + ] + ], + [ + [ + 161, + 56, + 40 + ], + [ + 162, + 56, + 41 + ] + ], + [ + [ + 74, + 41, + 56 + ], + [ + 75, + 42, + 56 + ] + ], + [ + [ + 74, + 39, + 56 + ], + [ + 75, + 40, + 56 + ] + ], + [ + [ + 84, + 38, + 56 + ], + [ + 86, + 39, + 56 + ] + ], + [ + [ + 95, + 39, + 56 + ], + [ + 96, + 40, + 56 + ] + ], + [ + [ + 78, + 38, + 56 + ], + [ + 80, + 39, + 56 + ] + ], + [ + [ + 57, + 30, + 49 + ], + [ + 57, + 31, + 50 + ] + ], + [ + [ + 57, + 37, + 50 + ], + [ + 57, + 38, + 51 + ] + ], + [ + [ + 57, + 37, + 49 + ], + [ + 57, + 38, + 50 + ] + ], + [ + [ + 162, + 57, + 39 + ], + [ + 163, + 57, + 40 + ] + ], + [ + [ + 176, + 57, + 40 + ], + [ + 177, + 57, + 41 + ] + ], + [ + [ + 57, + 30, + 30 + ], + [ + 57, + 31, + 31 + ] + ], + [ + [ + 57, + 37, + 29 + ], + [ + 57, + 38, + 30 + ] + ], + [ + [ + 57, + 37, + 30 + ], + [ + 57, + 38, + 31 + ] + ], + [ + [ + 162, + 57, + 40 + ], + [ + 163, + 57, + 41 + ] + ], + [ + [ + 74, + 40, + 57 + ], + [ + 75, + 41, + 57 + ] + ], + [ + [ + 94, + 39, + 57 + ], + [ + 95, + 40, + 57 + ] + ], + [ + [ + 80, + 38, + 57 + ], + [ + 84, + 39, + 57 + ] + ], + [ + [ + 58, + 38, + 50 + ], + [ + 58, + 39, + 51 + ] + ], + [ + [ + 58, + 29, + 50 + ], + [ + 58, + 30, + 51 + ] + ], + [ + [ + 163, + 58, + 39 + ], + [ + 164, + 58, + 40 + ] + ], + [ + [ + 58, + 38, + 29 + ], + [ + 58, + 39, + 30 + ] + ], + [ + [ + 58, + 29, + 29 + ], + [ + 58, + 30, + 30 + ] + ], + [ + [ + 176, + 58, + 39 + ], + [ + 177, + 58, + 40 + ] + ], + [ + [ + 163, + 58, + 40 + ], + [ + 164, + 58, + 41 + ] + ], + [ + [ + 75, + 39, + 58 + ], + [ + 76, + 40, + 58 + ] + ], + [ + [ + 93, + 39, + 58 + ], + [ + 94, + 40, + 58 + ] + ], + [ + [ + 59, + 39, + 40 + ], + [ + 59, + 40, + 41 + ] + ], + [ + [ + 164, + 59, + 39 + ], + [ + 165, + 59, + 40 + ] + ], + [ + [ + 88, + 42, + 59 + ], + [ + 89, + 43, + 59 + ] + ], + [ + [ + 94, + 40, + 59 + ], + [ + 95, + 41, + 59 + ] + ], + [ + [ + 59, + 39, + 39 + ], + [ + 59, + 40, + 40 + ] + ], + [ + [ + 164, + 59, + 40 + ], + [ + 165, + 59, + 41 + ] + ], + [ + [ + 91, + 39, + 59 + ], + [ + 93, + 40, + 59 + ] + ], + [ + [ + 60, + 38, + 49 + ], + [ + 60, + 39, + 50 + ] + ], + [ + [ + 60, + 35, + 51 + ], + [ + 60, + 36, + 52 + ] + ], + [ + [ + 165, + 60, + 39 + ], + [ + 166, + 60, + 40 + ] + ], + [ + [ + 177, + 60, + 40 + ], + [ + 178, + 60, + 41 + ] + ], + [ + [ + 60, + 38, + 30 + ], + [ + 60, + 39, + 31 + ] + ], + [ + [ + 60, + 35, + 28 + ], + [ + 60, + 36, + 29 + ] + ], + [ + [ + 60, + 39, + 38 + ], + [ + 60, + 40, + 39 + ] + ], + [ + [ + 165, + 60, + 40 + ], + [ + 166, + 60, + 41 + ] + ], + [ + [ + 76, + 39, + 60 + ], + [ + 77, + 40, + 60 + ] + ], + [ + [ + 90, + 39, + 60 + ], + [ + 91, + 40, + 60 + ] + ], + [ + [ + 61, + 39, + 41 + ], + [ + 61, + 40, + 42 + ] + ], + [ + [ + 61, + 39, + 50 + ], + [ + 61, + 40, + 51 + ] + ], + [ + [ + 61, + 34, + 51 + ], + [ + 61, + 35, + 52 + ] + ], + [ + [ + 61, + 29, + 49 + ], + [ + 61, + 30, + 50 + ] + ], + [ + [ + 92, + 41, + 61 + ], + [ + 93, + 42, + 61 + ] + ], + [ + [ + 61, + 39, + 29 + ], + [ + 61, + 40, + 30 + ] + ], + [ + [ + 61, + 34, + 28 + ], + [ + 61, + 35, + 29 + ] + ], + [ + [ + 61, + 29, + 30 + ], + [ + 61, + 30, + 31 + ] + ], + [ + [ + 177, + 61, + 39 + ], + [ + 178, + 61, + 40 + ] + ], + [ + [ + 75, + 40, + 61 + ], + [ + 76, + 42, + 61 + ] + ], + [ + [ + 76, + 42, + 61 + ], + [ + 77, + 43, + 61 + ] + ], + [ + [ + 88, + 39, + 61 + ], + [ + 90, + 40, + 61 + ] + ], + [ + [ + 62, + 38, + 42 + ], + [ + 62, + 39, + 43 + ] + ], + [ + [ + 166, + 62, + 39 + ], + [ + 167, + 62, + 40 + ] + ], + [ + [ + 62, + 38, + 37 + ], + [ + 62, + 39, + 38 + ] + ], + [ + [ + 166, + 62, + 40 + ], + [ + 167, + 62, + 41 + ] + ], + [ + [ + 77, + 39, + 62 + ], + [ + 78, + 40, + 62 + ] + ], + [ + [ + 87, + 39, + 62 + ], + [ + 88, + 40, + 62 + ] + ], + [ + [ + 63, + 17, + 43 + ], + [ + 63, + 18, + 44 + ] + ], + [ + [ + 63, + 33, + 51 + ], + [ + 63, + 34, + 52 + ] + ], + [ + [ + 167, + 63, + 39 + ], + [ + 168, + 63, + 40 + ] + ], + [ + [ + 178, + 63, + 40 + ], + [ + 179, + 63, + 41 + ] + ], + [ + [ + 89, + 42, + 63 + ], + [ + 90, + 43, + 63 + ] + ], + [ + [ + 63, + 17, + 36 + ], + [ + 63, + 18, + 37 + ] + ], + [ + [ + 63, + 33, + 28 + ], + [ + 63, + 34, + 29 + ] + ], + [ + [ + 63, + 36, + 28 + ], + [ + 63, + 37, + 29 + ] + ], + [ + [ + 178, + 63, + 39 + ], + [ + 179, + 63, + 40 + ] + ], + [ + [ + 167, + 63, + 40 + ], + [ + 168, + 63, + 41 + ] + ], + [ + [ + 94, + 40, + 63 + ], + [ + 95, + 41, + 63 + ] + ], + [ + [ + 85, + 39, + 63 + ], + [ + 87, + 40, + 63 + ] + ], + [ + [ + 78, + 39, + 63 + ], + [ + 80, + 40, + 63 + ] + ], + [ + [ + 64, + 40, + 40 + ], + [ + 64, + 41, + 41 + ] + ], + [ + [ + 64, + 16, + 43 + ], + [ + 64, + 17, + 44 + ] + ], + [ + [ + 64, + 39, + 49 + ], + [ + 64, + 40, + 50 + ] + ], + [ + [ + 64, + 36, + 51 + ], + [ + 64, + 37, + 52 + ] + ], + [ + [ + 168, + 64, + 39 + ], + [ + 169, + 64, + 40 + ] + ], + [ + [ + 171, + 64, + 41 + ], + [ + 174, + 64, + 42 + ] + ], + [ + [ + 174, + 64, + 41 + ], + [ + 176, + 64, + 43 + ] + ], + [ + [ + 176, + 64, + 41 + ], + [ + 177, + 64, + 44 + ] + ], + [ + [ + 64, + 16, + 36 + ], + [ + 64, + 17, + 37 + ] + ], + [ + [ + 64, + 39, + 30 + ], + [ + 64, + 40, + 31 + ] + ], + [ + [ + 64, + 40, + 39 + ], + [ + 64, + 41, + 40 + ] + ], + [ + [ + 168, + 64, + 40 + ], + [ + 169, + 64, + 41 + ] + ], + [ + [ + 176, + 64, + 36 + ], + [ + 177, + 64, + 39 + ] + ], + [ + [ + 173, + 64, + 37 + ], + [ + 176, + 64, + 39 + ] + ], + [ + [ + 171, + 64, + 38 + ], + [ + 173, + 64, + 39 + ] + ], + [ + [ + 76, + 40, + 64 + ], + [ + 77, + 41, + 64 + ] + ], + [ + [ + 93, + 40, + 64 + ], + [ + 94, + 41, + 64 + ] + ], + [ + [ + 80, + 39, + 64 + ], + [ + 85, + 40, + 64 + ] + ], + [ + [ + 65, + 15, + 42 + ], + [ + 65, + 16, + 43 + ] + ], + [ + [ + 169, + 65, + 39 + ], + [ + 170, + 65, + 40 + ] + ], + [ + [ + 179, + 65, + 40 + ], + [ + 180, + 65, + 41 + ] + ], + [ + [ + 172, + 65, + 50 + ], + [ + 173, + 65, + 51 + ] + ], + [ + [ + 168, + 65, + 40 + ], + [ + 169, + 65, + 42 + ] + ], + [ + [ + 180, + 65, + 40 + ], + [ + 182, + 65, + 48 + ] + ], + [ + [ + 182, + 65, + 40 + ], + [ + 183, + 65, + 42 + ] + ], + [ + [ + 169, + 65, + 41 + ], + [ + 171, + 65, + 42 + ] + ], + [ + [ + 177, + 65, + 41 + ], + [ + 180, + 65, + 48 + ] + ], + [ + [ + 169, + 65, + 42 + ], + [ + 174, + 65, + 44 + ] + ], + [ + [ + 174, + 65, + 43 + ], + [ + 176, + 65, + 44 + ] + ], + [ + [ + 170, + 65, + 44 + ], + [ + 171, + 65, + 46 + ] + ], + [ + [ + 171, + 65, + 44 + ], + [ + 177, + 65, + 48 + ] + ], + [ + [ + 172, + 65, + 48 + ], + [ + 180, + 65, + 50 + ] + ], + [ + [ + 180, + 65, + 48 + ], + [ + 181, + 65, + 49 + ] + ], + [ + [ + 173, + 65, + 50 + ], + [ + 181, + 65, + 51 + ] + ], + [ + [ + 65, + 15, + 37 + ], + [ + 65, + 16, + 38 + ] + ], + [ + [ + 65, + 17, + 35 + ], + [ + 65, + 18, + 36 + ] + ], + [ + [ + 65, + 32, + 28 + ], + [ + 65, + 33, + 29 + ] + ], + [ + [ + 169, + 65, + 40 + ], + [ + 170, + 65, + 41 + ] + ], + [ + [ + 173, + 65, + 29 + ], + [ + 181, + 65, + 30 + ] + ], + [ + [ + 172, + 65, + 30 + ], + [ + 180, + 65, + 32 + ] + ], + [ + [ + 180, + 65, + 31 + ], + [ + 181, + 65, + 32 + ] + ], + [ + [ + 171, + 65, + 32 + ], + [ + 177, + 65, + 36 + ] + ], + [ + [ + 177, + 65, + 32 + ], + [ + 180, + 65, + 39 + ] + ], + [ + [ + 180, + 65, + 32 + ], + [ + 182, + 65, + 40 + ] + ], + [ + [ + 170, + 65, + 34 + ], + [ + 171, + 65, + 36 + ] + ], + [ + [ + 169, + 65, + 36 + ], + [ + 173, + 65, + 38 + ] + ], + [ + [ + 173, + 65, + 36 + ], + [ + 176, + 65, + 37 + ] + ], + [ + [ + 168, + 65, + 38 + ], + [ + 169, + 65, + 40 + ] + ], + [ + [ + 169, + 65, + 38 + ], + [ + 171, + 65, + 39 + ] + ], + [ + [ + 182, + 65, + 38 + ], + [ + 183, + 65, + 40 + ] + ], + [ + [ + 76, + 41, + 65 + ], + [ + 77, + 42, + 65 + ] + ], + [ + [ + 92, + 40, + 65 + ], + [ + 93, + 41, + 65 + ] + ], + [ + [ + 66, + 40, + 41 + ], + [ + 66, + 41, + 42 + ] + ], + [ + [ + 66, + 18, + 44 + ], + [ + 66, + 20, + 45 + ] + ], + [ + [ + 66, + 17, + 44 + ], + [ + 66, + 18, + 45 + ] + ], + [ + [ + 66, + 32, + 51 + ], + [ + 66, + 33, + 52 + ] + ], + [ + [ + 177, + 66, + 29 + ], + [ + 182, + 66, + 31 + ] + ], + [ + [ + 176, + 66, + 30 + ], + [ + 177, + 66, + 31 + ] + ], + [ + [ + 175, + 66, + 31 + ], + [ + 178, + 66, + 32 + ] + ], + [ + [ + 178, + 66, + 31 + ], + [ + 180, + 66, + 33 + ] + ], + [ + [ + 180, + 66, + 31 + ], + [ + 183, + 66, + 38 + ] + ], + [ + [ + 183, + 66, + 34 + ], + [ + 184, + 66, + 38 + ] + ], + [ + [ + 177, + 66, + 35 + ], + [ + 180, + 66, + 38 + ] + ], + [ + [ + 174, + 66, + 36 + ], + [ + 176, + 66, + 37 + ] + ], + [ + [ + 176, + 66, + 36 + ], + [ + 177, + 66, + 38 + ] + ], + [ + [ + 180, + 66, + 38 + ], + [ + 183, + 66, + 39 + ] + ], + [ + [ + 183, + 66, + 38 + ], + [ + 185, + 66, + 40 + ] + ], + [ + [ + 172, + 66, + 29 + ], + [ + 173, + 66, + 32 + ] + ], + [ + [ + 173, + 66, + 29 + ], + [ + 174, + 66, + 31 + ] + ], + [ + [ + 171, + 66, + 32 + ], + [ + 175, + 66, + 34 + ] + ], + [ + [ + 175, + 66, + 33 + ], + [ + 179, + 66, + 34 + ] + ], + [ + [ + 170, + 66, + 34 + ], + [ + 173, + 66, + 36 + ] + ], + [ + [ + 173, + 66, + 34 + ], + [ + 177, + 66, + 35 + ] + ], + [ + [ + 169, + 66, + 36 + ], + [ + 171, + 66, + 38 + ] + ], + [ + [ + 168, + 66, + 38 + ], + [ + 170, + 66, + 40 + ] + ], + [ + [ + 183, + 66, + 40 + ], + [ + 184, + 66, + 46 + ] + ], + [ + [ + 184, + 66, + 40 + ], + [ + 185, + 66, + 42 + ] + ], + [ + [ + 182, + 66, + 42 + ], + [ + 183, + 66, + 49 + ] + ], + [ + [ + 181, + 66, + 48 + ], + [ + 182, + 66, + 51 + ] + ], + [ + [ + 180, + 66, + 49 + ], + [ + 181, + 66, + 50 + ] + ], + [ + [ + 66, + 18, + 35 + ], + [ + 66, + 20, + 36 + ] + ], + [ + [ + 66, + 40, + 38 + ], + [ + 66, + 41, + 39 + ] + ], + [ + [ + 183, + 66, + 40 + ], + [ + 185, + 66, + 42 + ] + ], + [ + [ + 180, + 66, + 41 + ], + [ + 183, + 66, + 42 + ] + ], + [ + [ + 176, + 66, + 42 + ], + [ + 177, + 66, + 44 + ] + ], + [ + [ + 177, + 66, + 42 + ], + [ + 180, + 66, + 45 + ] + ], + [ + [ + 180, + 66, + 42 + ], + [ + 183, + 66, + 49 + ] + ], + [ + [ + 183, + 66, + 42 + ], + [ + 184, + 66, + 46 + ] + ], + [ + [ + 174, + 66, + 43 + ], + [ + 176, + 66, + 44 + ] + ], + [ + [ + 178, + 66, + 47 + ], + [ + 180, + 66, + 49 + ] + ], + [ + [ + 175, + 66, + 48 + ], + [ + 178, + 66, + 49 + ] + ], + [ + [ + 176, + 66, + 49 + ], + [ + 177, + 66, + 50 + ] + ], + [ + [ + 177, + 66, + 49 + ], + [ + 182, + 66, + 51 + ] + ], + [ + [ + 168, + 66, + 40 + ], + [ + 170, + 66, + 42 + ] + ], + [ + [ + 169, + 66, + 42 + ], + [ + 171, + 66, + 44 + ] + ], + [ + [ + 170, + 66, + 44 + ], + [ + 173, + 66, + 46 + ] + ], + [ + [ + 173, + 66, + 45 + ], + [ + 177, + 66, + 46 + ] + ], + [ + [ + 171, + 66, + 46 + ], + [ + 175, + 66, + 48 + ] + ], + [ + [ + 175, + 66, + 46 + ], + [ + 179, + 66, + 47 + ] + ], + [ + [ + 172, + 66, + 48 + ], + [ + 173, + 66, + 51 + ] + ], + [ + [ + 173, + 66, + 49 + ], + [ + 174, + 66, + 51 + ] + ], + [ + [ + 179, + 66, + 39 + ], + [ + 180, + 66, + 40 + ] + ], + [ + [ + 172, + 66, + 29 + ], + [ + 173, + 66, + 30 + ] + ], + [ + [ + 181, + 66, + 29 + ], + [ + 182, + 66, + 32 + ] + ], + [ + [ + 180, + 66, + 30 + ], + [ + 181, + 66, + 31 + ] + ], + [ + [ + 182, + 66, + 31 + ], + [ + 183, + 66, + 38 + ] + ], + [ + [ + 183, + 66, + 34 + ], + [ + 184, + 66, + 40 + ] + ], + [ + [ + 184, + 66, + 38 + ], + [ + 185, + 66, + 40 + ] + ], + [ + [ + 91, + 40, + 66 + ], + [ + 92, + 41, + 66 + ] + ], + [ + [ + 67, + 16, + 44 + ], + [ + 67, + 17, + 45 + ] + ], + [ + [ + 67, + 15, + 43 + ], + [ + 67, + 16, + 44 + ] + ], + [ + [ + 67, + 40, + 50 + ], + [ + 67, + 41, + 51 + ] + ], + [ + [ + 181, + 67, + 39 + ], + [ + 183, + 67, + 40 + ] + ], + [ + [ + 173, + 67, + 35 + ], + [ + 177, + 67, + 36 + ] + ], + [ + [ + 171, + 67, + 36 + ], + [ + 174, + 67, + 38 + ] + ], + [ + [ + 174, + 67, + 37 + ], + [ + 176, + 67, + 38 + ] + ], + [ + [ + 170, + 67, + 38 + ], + [ + 180, + 67, + 39 + ] + ], + [ + [ + 177, + 67, + 34 + ], + [ + 180, + 67, + 35 + ] + ], + [ + [ + 174, + 67, + 29 + ], + [ + 176, + 67, + 31 + ] + ], + [ + [ + 176, + 67, + 29 + ], + [ + 177, + 67, + 30 + ] + ], + [ + [ + 173, + 67, + 31 + ], + [ + 175, + 67, + 32 + ] + ], + [ + [ + 175, + 67, + 32 + ], + [ + 178, + 67, + 33 + ] + ], + [ + [ + 179, + 67, + 33 + ], + [ + 180, + 67, + 34 + ] + ], + [ + [ + 170, + 67, + 39 + ], + [ + 171, + 67, + 40 + ] + ], + [ + [ + 93, + 41, + 67 + ], + [ + 94, + 42, + 67 + ] + ], + [ + [ + 67, + 16, + 35 + ], + [ + 67, + 17, + 36 + ] + ], + [ + [ + 67, + 14, + 37 + ], + [ + 67, + 15, + 38 + ] + ], + [ + [ + 67, + 15, + 36 + ], + [ + 67, + 16, + 37 + ] + ], + [ + [ + 67, + 40, + 29 + ], + [ + 67, + 41, + 30 + ] + ], + [ + [ + 181, + 67, + 40 + ], + [ + 183, + 67, + 41 + ] + ], + [ + [ + 170, + 67, + 41 + ], + [ + 180, + 67, + 42 + ] + ], + [ + [ + 171, + 67, + 42 + ], + [ + 174, + 67, + 44 + ] + ], + [ + [ + 174, + 67, + 42 + ], + [ + 176, + 67, + 43 + ] + ], + [ + [ + 173, + 67, + 44 + ], + [ + 177, + 67, + 45 + ] + ], + [ + [ + 177, + 67, + 45 + ], + [ + 180, + 67, + 46 + ] + ], + [ + [ + 173, + 67, + 48 + ], + [ + 175, + 67, + 49 + ] + ], + [ + [ + 174, + 67, + 49 + ], + [ + 176, + 67, + 51 + ] + ], + [ + [ + 176, + 67, + 50 + ], + [ + 177, + 67, + 51 + ] + ], + [ + [ + 175, + 67, + 47 + ], + [ + 178, + 67, + 48 + ] + ], + [ + [ + 179, + 67, + 46 + ], + [ + 180, + 67, + 47 + ] + ], + [ + [ + 170, + 67, + 40 + ], + [ + 171, + 67, + 41 + ] + ], + [ + [ + 77, + 40, + 67 + ], + [ + 78, + 41, + 67 + ] + ], + [ + [ + 77, + 42, + 67 + ], + [ + 78, + 43, + 67 + ] + ], + [ + [ + 90, + 40, + 67 + ], + [ + 91, + 41, + 67 + ] + ], + [ + [ + 68, + 14, + 42 + ], + [ + 68, + 15, + 43 + ] + ], + [ + [ + 68, + 14, + 41 + ], + [ + 68, + 15, + 42 + ] + ], + [ + [ + 68, + 37, + 51 + ], + [ + 68, + 38, + 52 + ] + ], + [ + [ + 171, + 68, + 39 + ], + [ + 172, + 68, + 40 + ] + ], + [ + [ + 180, + 68, + 40 + ], + [ + 181, + 68, + 41 + ] + ], + [ + [ + 90, + 42, + 68 + ], + [ + 91, + 43, + 68 + ] + ], + [ + [ + 68, + 14, + 38 + ], + [ + 68, + 15, + 39 + ] + ], + [ + [ + 68, + 31, + 28 + ], + [ + 68, + 32, + 29 + ] + ], + [ + [ + 68, + 37, + 28 + ], + [ + 68, + 38, + 29 + ] + ], + [ + [ + 180, + 68, + 39 + ], + [ + 181, + 68, + 40 + ] + ], + [ + [ + 171, + 68, + 40 + ], + [ + 172, + 68, + 41 + ] + ], + [ + [ + 89, + 40, + 68 + ], + [ + 90, + 41, + 68 + ] + ], + [ + [ + 69, + 18, + 45 + ], + [ + 69, + 19, + 46 + ] + ], + [ + [ + 69, + 17, + 45 + ], + [ + 69, + 18, + 46 + ] + ], + [ + [ + 69, + 15, + 44 + ], + [ + 69, + 16, + 45 + ] + ], + [ + [ + 69, + 31, + 51 + ], + [ + 69, + 32, + 52 + ] + ], + [ + [ + 172, + 69, + 39 + ], + [ + 173, + 69, + 40 + ] + ], + [ + [ + 69, + 18, + 34 + ], + [ + 69, + 19, + 35 + ] + ], + [ + [ + 69, + 17, + 34 + ], + [ + 69, + 18, + 35 + ] + ], + [ + [ + 69, + 14, + 36 + ], + [ + 69, + 15, + 37 + ] + ], + [ + [ + 69, + 15, + 35 + ], + [ + 69, + 16, + 36 + ] + ], + [ + [ + 172, + 69, + 40 + ], + [ + 173, + 69, + 41 + ] + ], + [ + [ + 77, + 41, + 69 + ], + [ + 78, + 42, + 69 + ] + ], + [ + [ + 78, + 40, + 69 + ], + [ + 79, + 41, + 69 + ] + ], + [ + [ + 87, + 40, + 69 + ], + [ + 89, + 41, + 69 + ] + ], + [ + [ + 70, + 19, + 45 + ], + [ + 70, + 20, + 46 + ] + ], + [ + [ + 70, + 20, + 44 + ], + [ + 70, + 21, + 45 + ] + ], + [ + [ + 70, + 16, + 45 + ], + [ + 70, + 17, + 46 + ] + ], + [ + [ + 70, + 14, + 43 + ], + [ + 70, + 15, + 44 + ] + ], + [ + [ + 70, + 28, + 50 + ], + [ + 70, + 29, + 51 + ] + ], + [ + [ + 173, + 70, + 39 + ], + [ + 174, + 70, + 40 + ] + ], + [ + [ + 181, + 70, + 40 + ], + [ + 182, + 70, + 41 + ] + ], + [ + [ + 70, + 20, + 35 + ], + [ + 70, + 21, + 36 + ] + ], + [ + [ + 70, + 19, + 34 + ], + [ + 70, + 20, + 35 + ] + ], + [ + [ + 70, + 16, + 34 + ], + [ + 70, + 17, + 35 + ] + ], + [ + [ + 70, + 14, + 39 + ], + [ + 70, + 15, + 40 + ] + ], + [ + [ + 70, + 28, + 29 + ], + [ + 70, + 29, + 30 + ] + ], + [ + [ + 181, + 70, + 39 + ], + [ + 182, + 70, + 40 + ] + ], + [ + [ + 173, + 70, + 40 + ], + [ + 174, + 70, + 41 + ] + ], + [ + [ + 93, + 41, + 70 + ], + [ + 94, + 42, + 70 + ] + ], + [ + [ + 86, + 40, + 70 + ], + [ + 87, + 41, + 70 + ] + ], + [ + [ + 71, + 13, + 42 + ], + [ + 71, + 14, + 43 + ] + ], + [ + [ + 71, + 14, + 40 + ], + [ + 71, + 15, + 41 + ] + ], + [ + [ + 71, + 38, + 43 + ], + [ + 71, + 41, + 44 + ] + ], + [ + [ + 71, + 39, + 44 + ], + [ + 71, + 41, + 45 + ] + ], + [ + [ + 71, + 39, + 45 + ], + [ + 71, + 40, + 46 + ] + ], + [ + [ + 71, + 39, + 42 + ], + [ + 71, + 41, + 43 + ] + ], + [ + [ + 71, + 40, + 49 + ], + [ + 71, + 41, + 50 + ] + ], + [ + [ + 71, + 38, + 36 + ], + [ + 71, + 41, + 37 + ] + ], + [ + [ + 71, + 39, + 34 + ], + [ + 71, + 40, + 35 + ] + ], + [ + [ + 71, + 39, + 35 + ], + [ + 71, + 41, + 36 + ] + ], + [ + [ + 71, + 39, + 37 + ], + [ + 71, + 40, + 38 + ] + ], + [ + [ + 71, + 40, + 37 + ], + [ + 71, + 41, + 38 + ] + ], + [ + [ + 71, + 13, + 37 + ], + [ + 71, + 14, + 38 + ] + ], + [ + [ + 71, + 40, + 30 + ], + [ + 71, + 41, + 31 + ] + ], + [ + [ + 92, + 41, + 71 + ], + [ + 93, + 42, + 71 + ] + ], + [ + [ + 79, + 40, + 71 + ], + [ + 81, + 41, + 71 + ] + ], + [ + [ + 84, + 40, + 71 + ], + [ + 86, + 41, + 71 + ] + ], + [ + [ + 72, + 13, + 43 + ], + [ + 72, + 14, + 44 + ] + ], + [ + [ + 72, + 14, + 44 + ], + [ + 72, + 15, + 45 + ] + ], + [ + [ + 72, + 37, + 43 + ], + [ + 72, + 38, + 44 + ] + ], + [ + [ + 72, + 38, + 44 + ], + [ + 72, + 39, + 47 + ] + ], + [ + [ + 72, + 39, + 46 + ], + [ + 72, + 41, + 49 + ] + ], + [ + [ + 72, + 40, + 45 + ], + [ + 72, + 41, + 46 + ] + ], + [ + [ + 72, + 41, + 43 + ], + [ + 72, + 42, + 48 + ] + ], + [ + [ + 72, + 41, + 40 + ], + [ + 72, + 42, + 43 + ] + ], + [ + [ + 174, + 72, + 39 + ], + [ + 182, + 72, + 40 + ] + ], + [ + [ + 91, + 42, + 72 + ], + [ + 92, + 43, + 72 + ] + ], + [ + [ + 72, + 37, + 36 + ], + [ + 72, + 38, + 37 + ] + ], + [ + [ + 72, + 38, + 33 + ], + [ + 72, + 39, + 36 + ] + ], + [ + [ + 72, + 39, + 31 + ], + [ + 72, + 41, + 34 + ] + ], + [ + [ + 72, + 40, + 34 + ], + [ + 72, + 41, + 35 + ] + ], + [ + [ + 72, + 41, + 32 + ], + [ + 72, + 42, + 37 + ] + ], + [ + [ + 72, + 40, + 30 + ], + [ + 72, + 41, + 31 + ] + ], + [ + [ + 72, + 41, + 37 + ], + [ + 72, + 42, + 40 + ] + ], + [ + [ + 72, + 13, + 36 + ], + [ + 72, + 14, + 37 + ] + ], + [ + [ + 72, + 14, + 35 + ], + [ + 72, + 15, + 36 + ] + ], + [ + [ + 72, + 30, + 28 + ], + [ + 72, + 31, + 29 + ] + ], + [ + [ + 72, + 39, + 49 + ], + [ + 72, + 41, + 50 + ] + ], + [ + [ + 174, + 72, + 40 + ], + [ + 182, + 72, + 41 + ] + ], + [ + [ + 78, + 42, + 72 + ], + [ + 79, + 43, + 72 + ] + ], + [ + [ + 78, + 41, + 72 + ], + [ + 79, + 42, + 72 + ] + ], + [ + [ + 81, + 40, + 72 + ], + [ + 84, + 41, + 72 + ] + ], + [ + [ + 73, + 39, + 51 + ], + [ + 73, + 41, + 53 + ] + ], + [ + [ + 73, + 41, + 48 + ], + [ + 73, + 42, + 52 + ] + ], + [ + [ + 73, + 38, + 47 + ], + [ + 73, + 39, + 49 + ] + ], + [ + [ + 73, + 37, + 44 + ], + [ + 73, + 38, + 45 + ] + ], + [ + [ + 73, + 38, + 51 + ], + [ + 73, + 39, + 52 + ] + ], + [ + [ + 73, + 39, + 27 + ], + [ + 73, + 41, + 29 + ] + ], + [ + [ + 73, + 41, + 28 + ], + [ + 73, + 42, + 32 + ] + ], + [ + [ + 73, + 38, + 31 + ], + [ + 73, + 39, + 33 + ] + ], + [ + [ + 73, + 37, + 35 + ], + [ + 73, + 38, + 36 + ] + ], + [ + [ + 73, + 38, + 30 + ], + [ + 73, + 40, + 31 + ] + ], + [ + [ + 73, + 39, + 29 + ], + [ + 73, + 41, + 30 + ] + ], + [ + [ + 73, + 13, + 38 + ], + [ + 73, + 14, + 39 + ] + ], + [ + [ + 73, + 38, + 28 + ], + [ + 73, + 39, + 29 + ] + ], + [ + [ + 73, + 38, + 49 + ], + [ + 73, + 39, + 50 + ] + ], + [ + [ + 73, + 39, + 50 + ], + [ + 73, + 41, + 51 + ] + ], + [ + [ + 91, + 41, + 73 + ], + [ + 92, + 42, + 73 + ] + ], + [ + [ + 74, + 30, + 28 + ], + [ + 74, + 31, + 29 + ] + ], + [ + [ + 74, + 39, + 53 + ], + [ + 74, + 41, + 56 + ] + ], + [ + [ + 74, + 40, + 56 + ], + [ + 74, + 41, + 57 + ] + ], + [ + [ + 74, + 41, + 52 + ], + [ + 74, + 42, + 56 + ] + ], + [ + [ + 74, + 37, + 45 + ], + [ + 74, + 38, + 46 + ] + ], + [ + [ + 74, + 39, + 24 + ], + [ + 74, + 41, + 27 + ] + ], + [ + [ + 74, + 40, + 23 + ], + [ + 74, + 41, + 24 + ] + ], + [ + [ + 74, + 41, + 24 + ], + [ + 74, + 42, + 28 + ] + ], + [ + [ + 74, + 38, + 28 + ], + [ + 74, + 39, + 30 + ] + ], + [ + [ + 74, + 37, + 34 + ], + [ + 74, + 38, + 35 + ] + ], + [ + [ + 74, + 15, + 34 + ], + [ + 74, + 16, + 35 + ] + ], + [ + [ + 74, + 38, + 50 + ], + [ + 74, + 39, + 52 + ] + ], + [ + [ + 90, + 41, + 74 + ], + [ + 91, + 42, + 74 + ] + ], + [ + [ + 75, + 13, + 36 + ], + [ + 75, + 14, + 37 + ] + ], + [ + [ + 75, + 28, + 29 + ], + [ + 75, + 29, + 30 + ] + ], + [ + [ + 75, + 15, + 45 + ], + [ + 75, + 16, + 46 + ] + ], + [ + [ + 75, + 39, + 56 + ], + [ + 75, + 40, + 58 + ] + ], + [ + [ + 75, + 40, + 57 + ], + [ + 75, + 42, + 61 + ] + ], + [ + [ + 75, + 41, + 56 + ], + [ + 75, + 42, + 57 + ] + ], + [ + [ + 75, + 38, + 52 + ], + [ + 75, + 39, + 53 + ] + ], + [ + [ + 75, + 37, + 46 + ], + [ + 75, + 38, + 47 + ] + ], + [ + [ + 92, + 42, + 75 + ], + [ + 93, + 43, + 75 + ] + ], + [ + [ + 75, + 39, + 22 + ], + [ + 75, + 40, + 24 + ] + ], + [ + [ + 75, + 40, + 19 + ], + [ + 75, + 42, + 23 + ] + ], + [ + [ + 75, + 41, + 23 + ], + [ + 75, + 42, + 24 + ] + ], + [ + [ + 75, + 38, + 27 + ], + [ + 75, + 39, + 28 + ] + ], + [ + [ + 75, + 37, + 33 + ], + [ + 75, + 38, + 34 + ] + ], + [ + [ + 75, + 13, + 43 + ], + [ + 75, + 14, + 44 + ] + ], + [ + [ + 75, + 28, + 50 + ], + [ + 75, + 29, + 51 + ] + ], + [ + [ + 89, + 41, + 75 + ], + [ + 90, + 42, + 75 + ] + ], + [ + [ + 76, + 14, + 35 + ], + [ + 76, + 15, + 36 + ] + ], + [ + [ + 76, + 15, + 34 + ], + [ + 76, + 16, + 35 + ] + ], + [ + [ + 76, + 31, + 28 + ], + [ + 76, + 32, + 29 + ] + ], + [ + [ + 76, + 13, + 43 + ], + [ + 76, + 14, + 44 + ] + ], + [ + [ + 76, + 14, + 44 + ], + [ + 76, + 15, + 45 + ] + ], + [ + [ + 76, + 15, + 45 + ], + [ + 76, + 16, + 46 + ] + ], + [ + [ + 76, + 39, + 58 + ], + [ + 76, + 40, + 60 + ] + ], + [ + [ + 76, + 40, + 61 + ], + [ + 76, + 42, + 64 + ] + ], + [ + [ + 76, + 41, + 64 + ], + [ + 76, + 42, + 65 + ] + ], + [ + [ + 76, + 42, + 57 + ], + [ + 76, + 43, + 61 + ] + ], + [ + [ + 76, + 37, + 47 + ], + [ + 76, + 38, + 48 + ] + ], + [ + [ + 76, + 38, + 53 + ], + [ + 76, + 39, + 54 + ] + ], + [ + [ + 76, + 42, + 54 + ], + [ + 76, + 43, + 57 + ] + ], + [ + [ + 76, + 39, + 20 + ], + [ + 76, + 40, + 22 + ] + ], + [ + [ + 76, + 40, + 16 + ], + [ + 76, + 42, + 19 + ] + ], + [ + [ + 76, + 41, + 15 + ], + [ + 76, + 42, + 16 + ] + ], + [ + [ + 76, + 42, + 19 + ], + [ + 76, + 43, + 23 + ] + ], + [ + [ + 76, + 37, + 32 + ], + [ + 76, + 38, + 33 + ] + ], + [ + [ + 76, + 38, + 26 + ], + [ + 76, + 39, + 27 + ] + ], + [ + [ + 76, + 13, + 36 + ], + [ + 76, + 14, + 37 + ] + ], + [ + [ + 76, + 14, + 35 + ], + [ + 76, + 15, + 36 + ] + ], + [ + [ + 76, + 15, + 34 + ], + [ + 76, + 16, + 35 + ] + ], + [ + [ + 76, + 42, + 23 + ], + [ + 76, + 43, + 26 + ] + ], + [ + [ + 76, + 14, + 44 + ], + [ + 76, + 15, + 45 + ] + ], + [ + [ + 76, + 15, + 45 + ], + [ + 76, + 16, + 46 + ] + ], + [ + [ + 76, + 31, + 51 + ], + [ + 76, + 32, + 52 + ] + ], + [ + [ + 79, + 41, + 76 + ], + [ + 89, + 42, + 76 + ] + ], + [ + [ + 79, + 42, + 76 + ], + [ + 93, + 43, + 76 + ] + ], + [ + [ + 77, + 32, + 28 + ], + [ + 77, + 33, + 29 + ] + ], + [ + [ + 77, + 37, + 28 + ], + [ + 77, + 38, + 29 + ] + ], + [ + [ + 77, + 39, + 60 + ], + [ + 77, + 40, + 62 + ] + ], + [ + [ + 77, + 40, + 64 + ], + [ + 77, + 41, + 67 + ] + ], + [ + [ + 77, + 41, + 65 + ], + [ + 77, + 42, + 69 + ] + ], + [ + [ + 77, + 42, + 61 + ], + [ + 77, + 43, + 67 + ] + ], + [ + [ + 77, + 38, + 54 + ], + [ + 77, + 39, + 55 + ] + ], + [ + [ + 77, + 42, + 51 + ], + [ + 77, + 43, + 54 + ] + ], + [ + [ + 77, + 39, + 18 + ], + [ + 77, + 40, + 20 + ] + ], + [ + [ + 77, + 40, + 13 + ], + [ + 77, + 41, + 16 + ] + ], + [ + [ + 77, + 41, + 11 + ], + [ + 77, + 42, + 15 + ] + ], + [ + [ + 77, + 42, + 13 + ], + [ + 77, + 43, + 19 + ] + ], + [ + [ + 77, + 38, + 25 + ], + [ + 77, + 39, + 26 + ] + ], + [ + [ + 77, + 42, + 26 + ], + [ + 77, + 43, + 30 + ] + ], + [ + [ + 77, + 32, + 51 + ], + [ + 77, + 33, + 52 + ] + ], + [ + [ + 77, + 37, + 51 + ], + [ + 77, + 38, + 52 + ] + ], + [ + [ + 78, + 33, + 28 + ], + [ + 78, + 34, + 29 + ] + ], + [ + [ + 78, + 13, + 41 + ], + [ + 78, + 14, + 42 + ] + ], + [ + [ + 78, + 41, + 69 + ], + [ + 78, + 43, + 72 + ] + ], + [ + [ + 78, + 42, + 67 + ], + [ + 78, + 43, + 69 + ] + ], + [ + [ + 78, + 40, + 67 + ], + [ + 78, + 41, + 69 + ] + ], + [ + [ + 78, + 37, + 48 + ], + [ + 78, + 38, + 49 + ] + ], + [ + [ + 78, + 38, + 55 + ], + [ + 78, + 39, + 56 + ] + ], + [ + [ + 78, + 39, + 62 + ], + [ + 78, + 40, + 63 + ] + ], + [ + [ + 78, + 42, + 48 + ], + [ + 78, + 43, + 51 + ] + ], + [ + [ + 78, + 41, + 8 + ], + [ + 78, + 43, + 11 + ] + ], + [ + [ + 78, + 42, + 11 + ], + [ + 78, + 43, + 13 + ] + ], + [ + [ + 78, + 40, + 11 + ], + [ + 78, + 41, + 13 + ] + ], + [ + [ + 78, + 37, + 31 + ], + [ + 78, + 38, + 32 + ] + ], + [ + [ + 78, + 38, + 24 + ], + [ + 78, + 39, + 25 + ] + ], + [ + [ + 78, + 39, + 17 + ], + [ + 78, + 40, + 18 + ] + ], + [ + [ + 78, + 42, + 30 + ], + [ + 78, + 43, + 32 + ] + ], + [ + [ + 78, + 33, + 51 + ], + [ + 78, + 34, + 52 + ] + ], + [ + [ + 78, + 36, + 51 + ], + [ + 78, + 37, + 52 + ] + ], + [ + [ + 79, + 34, + 28 + ], + [ + 79, + 35, + 29 + ] + ], + [ + [ + 79, + 29, + 30 + ], + [ + 79, + 30, + 31 + ] + ], + [ + [ + 79, + 36, + 28 + ], + [ + 79, + 37, + 29 + ] + ], + [ + [ + 79, + 41, + 72 + ], + [ + 79, + 43, + 76 + ] + ], + [ + [ + 79, + 40, + 69 + ], + [ + 79, + 41, + 71 + ] + ], + [ + [ + 79, + 42, + 45 + ], + [ + 79, + 43, + 48 + ] + ], + [ + [ + 79, + 41, + 4 + ], + [ + 79, + 43, + 8 + ] + ], + [ + [ + 79, + 40, + 9 + ], + [ + 79, + 41, + 11 + ] + ], + [ + [ + 79, + 42, + 32 + ], + [ + 79, + 43, + 35 + ] + ], + [ + [ + 79, + 34, + 51 + ], + [ + 79, + 35, + 52 + ] + ], + [ + [ + 79, + 29, + 49 + ], + [ + 79, + 30, + 50 + ] + ], + [ + [ + 80, + 35, + 28 + ], + [ + 80, + 36, + 29 + ] + ], + [ + [ + 80, + 29, + 29 + ], + [ + 80, + 30, + 30 + ] + ], + [ + [ + 80, + 38, + 56 + ], + [ + 80, + 39, + 57 + ] + ], + [ + [ + 80, + 39, + 63 + ], + [ + 80, + 40, + 64 + ] + ], + [ + [ + 80, + 42, + 43 + ], + [ + 80, + 43, + 45 + ] + ], + [ + [ + 80, + 38, + 23 + ], + [ + 80, + 39, + 24 + ] + ], + [ + [ + 80, + 39, + 16 + ], + [ + 80, + 40, + 17 + ] + ], + [ + [ + 80, + 42, + 35 + ], + [ + 80, + 43, + 37 + ] + ], + [ + [ + 80, + 35, + 51 + ], + [ + 80, + 36, + 52 + ] + ], + [ + [ + 80, + 29, + 50 + ], + [ + 80, + 30, + 51 + ] + ], + [ + [ + 81, + 40, + 71 + ], + [ + 81, + 41, + 72 + ] + ], + [ + [ + 81, + 40, + 8 + ], + [ + 81, + 41, + 9 + ] + ], + [ + [ + 82, + 30, + 30 + ], + [ + 82, + 31, + 31 + ] + ], + [ + [ + 82, + 42, + 42 + ], + [ + 82, + 43, + 43 + ] + ], + [ + [ + 82, + 42, + 37 + ], + [ + 82, + 43, + 38 + ] + ], + [ + [ + 82, + 30, + 49 + ], + [ + 82, + 31, + 50 + ] + ], + [ + [ + 83, + 42, + 37 + ], + [ + 83, + 43, + 38 + ] + ], + [ + [ + 83, + 30, + 29 + ], + [ + 83, + 31, + 30 + ] + ], + [ + [ + 83, + 42, + 42 + ], + [ + 83, + 43, + 43 + ] + ], + [ + [ + 83, + 30, + 50 + ], + [ + 83, + 31, + 51 + ] + ], + [ + [ + 84, + 38, + 23 + ], + [ + 84, + 39, + 24 + ] + ], + [ + [ + 84, + 40, + 8 + ], + [ + 84, + 41, + 9 + ] + ], + [ + [ + 84, + 31, + 30 + ], + [ + 84, + 32, + 31 + ] + ], + [ + [ + 84, + 42, + 35 + ], + [ + 84, + 43, + 37 + ] + ], + [ + [ + 84, + 38, + 56 + ], + [ + 84, + 39, + 57 + ] + ], + [ + [ + 84, + 40, + 71 + ], + [ + 84, + 41, + 72 + ] + ], + [ + [ + 84, + 31, + 49 + ], + [ + 84, + 32, + 50 + ] + ], + [ + [ + 84, + 42, + 43 + ], + [ + 84, + 43, + 45 + ] + ], + [ + [ + 85, + 37, + 31 + ], + [ + 85, + 38, + 32 + ] + ], + [ + [ + 85, + 39, + 16 + ], + [ + 85, + 40, + 17 + ] + ], + [ + [ + 85, + 31, + 29 + ], + [ + 85, + 32, + 30 + ] + ], + [ + [ + 85, + 42, + 33 + ], + [ + 85, + 43, + 35 + ] + ], + [ + [ + 85, + 37, + 48 + ], + [ + 85, + 38, + 49 + ] + ], + [ + [ + 85, + 39, + 63 + ], + [ + 85, + 40, + 64 + ] + ], + [ + [ + 85, + 31, + 50 + ], + [ + 85, + 32, + 51 + ] + ], + [ + [ + 85, + 42, + 45 + ], + [ + 85, + 43, + 47 + ] + ], + [ + [ + 86, + 38, + 24 + ], + [ + 86, + 39, + 25 + ] + ], + [ + [ + 86, + 40, + 9 + ], + [ + 86, + 41, + 10 + ] + ], + [ + [ + 86, + 32, + 30 + ], + [ + 86, + 33, + 31 + ] + ], + [ + [ + 86, + 42, + 30 + ], + [ + 86, + 43, + 33 + ] + ], + [ + [ + 86, + 38, + 55 + ], + [ + 86, + 39, + 56 + ] + ], + [ + [ + 86, + 40, + 70 + ], + [ + 86, + 41, + 71 + ] + ], + [ + [ + 86, + 32, + 49 + ], + [ + 86, + 33, + 50 + ] + ], + [ + [ + 86, + 42, + 47 + ], + [ + 86, + 43, + 50 + ] + ], + [ + [ + 87, + 37, + 32 + ], + [ + 87, + 38, + 33 + ] + ], + [ + [ + 87, + 39, + 17 + ], + [ + 87, + 40, + 18 + ] + ], + [ + [ + 87, + 40, + 10 + ], + [ + 87, + 41, + 11 + ] + ], + [ + [ + 87, + 20, + 35 + ], + [ + 87, + 21, + 36 + ] + ], + [ + [ + 87, + 33, + 30 + ], + [ + 87, + 34, + 31 + ] + ], + [ + [ + 87, + 32, + 29 + ], + [ + 87, + 33, + 30 + ] + ], + [ + [ + 87, + 42, + 26 + ], + [ + 87, + 43, + 30 + ] + ], + [ + [ + 87, + 20, + 44 + ], + [ + 87, + 21, + 45 + ] + ], + [ + [ + 87, + 37, + 47 + ], + [ + 87, + 38, + 48 + ] + ], + [ + [ + 87, + 39, + 62 + ], + [ + 87, + 40, + 63 + ] + ], + [ + [ + 87, + 40, + 69 + ], + [ + 87, + 41, + 70 + ] + ], + [ + [ + 87, + 33, + 49 + ], + [ + 87, + 34, + 50 + ] + ], + [ + [ + 87, + 32, + 50 + ], + [ + 87, + 33, + 51 + ] + ], + [ + [ + 87, + 42, + 50 + ], + [ + 87, + 43, + 54 + ] + ], + [ + [ + 88, + 38, + 25 + ], + [ + 88, + 39, + 26 + ] + ], + [ + [ + 88, + 39, + 18 + ], + [ + 88, + 40, + 19 + ] + ], + [ + [ + 88, + 34, + 30 + ], + [ + 88, + 36, + 31 + ] + ], + [ + [ + 88, + 33, + 29 + ], + [ + 88, + 34, + 30 + ] + ], + [ + [ + 88, + 42, + 22 + ], + [ + 88, + 43, + 26 + ] + ], + [ + [ + 88, + 38, + 54 + ], + [ + 88, + 39, + 55 + ] + ], + [ + [ + 88, + 39, + 61 + ], + [ + 88, + 40, + 62 + ] + ], + [ + [ + 88, + 34, + 49 + ], + [ + 88, + 36, + 50 + ] + ], + [ + [ + 88, + 33, + 50 + ], + [ + 88, + 34, + 51 + ] + ], + [ + [ + 88, + 42, + 54 + ], + [ + 88, + 43, + 59 + ] + ], + [ + [ + 89, + 37, + 33 + ], + [ + 89, + 38, + 34 + ] + ], + [ + [ + 89, + 38, + 26 + ], + [ + 89, + 39, + 27 + ] + ], + [ + [ + 89, + 41, + 4 + ], + [ + 89, + 42, + 5 + ] + ], + [ + [ + 89, + 40, + 11 + ], + [ + 89, + 41, + 12 + ] + ], + [ + [ + 89, + 36, + 30 + ], + [ + 89, + 38, + 31 + ] + ], + [ + [ + 89, + 34, + 29 + ], + [ + 89, + 35, + 30 + ] + ], + [ + [ + 89, + 42, + 17 + ], + [ + 89, + 43, + 22 + ] + ], + [ + [ + 89, + 37, + 46 + ], + [ + 89, + 38, + 47 + ] + ], + [ + [ + 89, + 38, + 53 + ], + [ + 89, + 39, + 54 + ] + ], + [ + [ + 89, + 41, + 75 + ], + [ + 89, + 42, + 76 + ] + ], + [ + [ + 89, + 40, + 68 + ], + [ + 89, + 41, + 69 + ] + ], + [ + [ + 89, + 36, + 49 + ], + [ + 89, + 37, + 50 + ] + ], + [ + [ + 89, + 34, + 50 + ], + [ + 89, + 35, + 51 + ] + ], + [ + [ + 89, + 42, + 59 + ], + [ + 89, + 43, + 63 + ] + ], + [ + [ + 90, + 39, + 19 + ], + [ + 90, + 40, + 20 + ] + ], + [ + [ + 90, + 40, + 12 + ], + [ + 90, + 41, + 13 + ] + ], + [ + [ + 90, + 41, + 5 + ], + [ + 90, + 42, + 6 + ] + ], + [ + [ + 90, + 41, + 37 + ], + [ + 90, + 42, + 40 + ] + ], + [ + [ + 90, + 19, + 34 + ], + [ + 90, + 20, + 35 + ] + ], + [ + [ + 90, + 41, + 34 + ], + [ + 90, + 42, + 37 + ] + ], + [ + [ + 90, + 42, + 12 + ], + [ + 90, + 43, + 17 + ] + ], + [ + [ + 90, + 19, + 45 + ], + [ + 90, + 20, + 46 + ] + ], + [ + [ + 90, + 39, + 60 + ], + [ + 90, + 40, + 61 + ] + ], + [ + [ + 90, + 40, + 67 + ], + [ + 90, + 41, + 68 + ] + ], + [ + [ + 90, + 41, + 74 + ], + [ + 90, + 42, + 75 + ] + ], + [ + [ + 90, + 41, + 40 + ], + [ + 90, + 42, + 43 + ] + ], + [ + [ + 90, + 37, + 49 + ], + [ + 90, + 38, + 50 + ] + ], + [ + [ + 90, + 41, + 43 + ], + [ + 90, + 42, + 46 + ] + ], + [ + [ + 90, + 42, + 63 + ], + [ + 90, + 43, + 68 + ] + ], + [ + [ + 91, + 37, + 34 + ], + [ + 91, + 38, + 35 + ] + ], + [ + [ + 91, + 38, + 27 + ], + [ + 91, + 39, + 28 + ] + ], + [ + [ + 91, + 39, + 20 + ], + [ + 91, + 40, + 21 + ] + ], + [ + [ + 91, + 40, + 13 + ], + [ + 91, + 41, + 14 + ] + ], + [ + [ + 91, + 41, + 6 + ], + [ + 91, + 42, + 7 + ] + ], + [ + [ + 91, + 35, + 29 + ], + [ + 91, + 36, + 30 + ] + ], + [ + [ + 91, + 42, + 8 + ], + [ + 91, + 43, + 12 + ] + ], + [ + [ + 91, + 41, + 26 + ], + [ + 91, + 42, + 34 + ] + ], + [ + [ + 91, + 37, + 45 + ], + [ + 91, + 38, + 46 + ] + ], + [ + [ + 91, + 38, + 52 + ], + [ + 91, + 39, + 53 + ] + ], + [ + [ + 91, + 39, + 59 + ], + [ + 91, + 40, + 60 + ] + ], + [ + [ + 91, + 40, + 66 + ], + [ + 91, + 41, + 67 + ] + ], + [ + [ + 91, + 41, + 73 + ], + [ + 91, + 42, + 74 + ] + ], + [ + [ + 91, + 35, + 50 + ], + [ + 91, + 36, + 51 + ] + ], + [ + [ + 91, + 42, + 68 + ], + [ + 91, + 43, + 72 + ] + ], + [ + [ + 91, + 41, + 46 + ], + [ + 91, + 42, + 54 + ] + ], + [ + [ + 92, + 40, + 14 + ], + [ + 92, + 41, + 15 + ] + ], + [ + [ + 92, + 41, + 7 + ], + [ + 92, + 42, + 9 + ] + ], + [ + [ + 92, + 40, + 38 + ], + [ + 92, + 41, + 39 + ] + ], + [ + [ + 92, + 19, + 35 + ], + [ + 92, + 20, + 36 + ] + ], + [ + [ + 92, + 36, + 29 + ], + [ + 92, + 37, + 30 + ] + ], + [ + [ + 92, + 42, + 5 + ], + [ + 92, + 43, + 8 + ] + ], + [ + [ + 92, + 41, + 19 + ], + [ + 92, + 42, + 26 + ] + ], + [ + [ + 92, + 19, + 44 + ], + [ + 92, + 20, + 45 + ] + ], + [ + [ + 92, + 40, + 65 + ], + [ + 92, + 41, + 66 + ] + ], + [ + [ + 92, + 41, + 71 + ], + [ + 92, + 42, + 73 + ] + ], + [ + [ + 92, + 40, + 41 + ], + [ + 92, + 41, + 42 + ] + ], + [ + [ + 92, + 36, + 50 + ], + [ + 92, + 37, + 51 + ] + ], + [ + [ + 92, + 42, + 72 + ], + [ + 92, + 43, + 75 + ] + ], + [ + [ + 92, + 41, + 54 + ], + [ + 92, + 42, + 61 + ] + ], + [ + [ + 93, + 37, + 35 + ], + [ + 93, + 38, + 36 + ] + ], + [ + [ + 93, + 38, + 28 + ], + [ + 93, + 39, + 29 + ] + ], + [ + [ + 93, + 39, + 21 + ], + [ + 93, + 40, + 22 + ] + ], + [ + [ + 93, + 40, + 15 + ], + [ + 93, + 41, + 16 + ] + ], + [ + [ + 93, + 41, + 9 + ], + [ + 93, + 42, + 10 + ] + ], + [ + [ + 93, + 40, + 39 + ], + [ + 93, + 41, + 40 + ] + ], + [ + [ + 93, + 40, + 37 + ], + [ + 93, + 41, + 38 + ] + ], + [ + [ + 93, + 18, + 34 + ], + [ + 93, + 19, + 35 + ] + ], + [ + [ + 93, + 15, + 34 + ], + [ + 93, + 16, + 35 + ] + ], + [ + [ + 93, + 37, + 29 + ], + [ + 93, + 38, + 30 + ] + ], + [ + [ + 93, + 40, + 30 + ], + [ + 93, + 41, + 37 + ] + ], + [ + [ + 93, + 41, + 14 + ], + [ + 93, + 42, + 19 + ] + ], + [ + [ + 93, + 42, + 4 + ], + [ + 93, + 43, + 5 + ] + ], + [ + [ + 93, + 18, + 45 + ], + [ + 93, + 19, + 46 + ] + ], + [ + [ + 93, + 15, + 45 + ], + [ + 93, + 16, + 46 + ] + ], + [ + [ + 93, + 37, + 44 + ], + [ + 93, + 38, + 45 + ] + ], + [ + [ + 93, + 38, + 51 + ], + [ + 93, + 39, + 52 + ] + ], + [ + [ + 93, + 39, + 58 + ], + [ + 93, + 40, + 59 + ] + ], + [ + [ + 93, + 40, + 64 + ], + [ + 93, + 41, + 65 + ] + ], + [ + [ + 93, + 41, + 70 + ], + [ + 93, + 42, + 71 + ] + ], + [ + [ + 93, + 40, + 40 + ], + [ + 93, + 41, + 41 + ] + ], + [ + [ + 93, + 40, + 42 + ], + [ + 93, + 41, + 43 + ] + ], + [ + [ + 93, + 37, + 50 + ], + [ + 93, + 38, + 51 + ] + ], + [ + [ + 93, + 40, + 43 + ], + [ + 93, + 41, + 50 + ] + ], + [ + [ + 93, + 41, + 61 + ], + [ + 93, + 42, + 67 + ] + ], + [ + [ + 93, + 42, + 75 + ], + [ + 93, + 43, + 76 + ] + ], + [ + [ + 94, + 38, + 29 + ], + [ + 94, + 39, + 30 + ] + ], + [ + [ + 94, + 40, + 16 + ], + [ + 94, + 41, + 17 + ] + ], + [ + [ + 94, + 41, + 10 + ], + [ + 94, + 42, + 14 + ] + ], + [ + [ + 94, + 39, + 22 + ], + [ + 94, + 40, + 23 + ] + ], + [ + [ + 94, + 40, + 21 + ], + [ + 94, + 41, + 30 + ] + ], + [ + [ + 94, + 13, + 43 + ], + [ + 94, + 14, + 44 + ] + ], + [ + [ + 94, + 13, + 41 + ], + [ + 94, + 14, + 42 + ] + ], + [ + [ + 94, + 38, + 50 + ], + [ + 94, + 39, + 51 + ] + ], + [ + [ + 94, + 40, + 63 + ], + [ + 94, + 41, + 64 + ] + ], + [ + [ + 94, + 39, + 57 + ], + [ + 94, + 40, + 58 + ] + ], + [ + [ + 94, + 41, + 67 + ], + [ + 94, + 42, + 70 + ] + ], + [ + [ + 94, + 40, + 50 + ], + [ + 94, + 41, + 59 + ] + ], + [ + [ + 95, + 37, + 36 + ], + [ + 95, + 38, + 37 + ] + ], + [ + [ + 95, + 39, + 23 + ], + [ + 95, + 40, + 24 + ] + ], + [ + [ + 95, + 39, + 38 + ], + [ + 95, + 40, + 39 + ] + ], + [ + [ + 95, + 39, + 37 + ], + [ + 95, + 40, + 38 + ] + ], + [ + [ + 95, + 17, + 34 + ], + [ + 95, + 18, + 35 + ] + ], + [ + [ + 95, + 16, + 34 + ], + [ + 95, + 17, + 35 + ] + ], + [ + [ + 95, + 39, + 28 + ], + [ + 95, + 40, + 37 + ] + ], + [ + [ + 95, + 40, + 17 + ], + [ + 95, + 41, + 21 + ] + ], + [ + [ + 95, + 17, + 45 + ], + [ + 95, + 18, + 46 + ] + ], + [ + [ + 95, + 16, + 45 + ], + [ + 95, + 17, + 46 + ] + ], + [ + [ + 95, + 13, + 42 + ], + [ + 95, + 14, + 43 + ] + ], + [ + [ + 95, + 14, + 44 + ], + [ + 95, + 15, + 45 + ] + ], + [ + [ + 95, + 37, + 43 + ], + [ + 95, + 38, + 44 + ] + ], + [ + [ + 95, + 39, + 56 + ], + [ + 95, + 40, + 57 + ] + ], + [ + [ + 95, + 39, + 41 + ], + [ + 95, + 40, + 42 + ] + ], + [ + [ + 95, + 39, + 42 + ], + [ + 95, + 40, + 43 + ] + ], + [ + [ + 95, + 39, + 43 + ], + [ + 95, + 40, + 52 + ] + ], + [ + [ + 95, + 40, + 59 + ], + [ + 95, + 41, + 63 + ] + ], + [ + [ + 96, + 38, + 30 + ], + [ + 96, + 39, + 31 + ] + ], + [ + [ + 96, + 38, + 37 + ], + [ + 96, + 39, + 38 + ] + ], + [ + [ + 96, + 18, + 35 + ], + [ + 96, + 19, + 36 + ] + ], + [ + [ + 96, + 14, + 35 + ], + [ + 96, + 15, + 36 + ] + ], + [ + [ + 96, + 13, + 36 + ], + [ + 96, + 14, + 37 + ] + ], + [ + [ + 96, + 13, + 37 + ], + [ + 96, + 14, + 39 + ] + ], + [ + [ + 96, + 38, + 34 + ], + [ + 96, + 39, + 37 + ] + ], + [ + [ + 96, + 39, + 24 + ], + [ + 96, + 40, + 28 + ] + ], + [ + [ + 96, + 18, + 44 + ], + [ + 96, + 19, + 45 + ] + ], + [ + [ + 96, + 38, + 49 + ], + [ + 96, + 39, + 50 + ] + ], + [ + [ + 96, + 38, + 42 + ], + [ + 96, + 39, + 43 + ] + ], + [ + [ + 96, + 38, + 43 + ], + [ + 96, + 39, + 46 + ] + ], + [ + [ + 96, + 39, + 52 + ], + [ + 96, + 40, + 56 + ] + ], + [ + [ + 97, + 17, + 35 + ], + [ + 97, + 18, + 36 + ] + ], + [ + [ + 97, + 38, + 31 + ], + [ + 97, + 39, + 34 + ] + ], + [ + [ + 97, + 17, + 44 + ], + [ + 97, + 18, + 45 + ] + ], + [ + [ + 97, + 14, + 41 + ], + [ + 97, + 15, + 44 + ] + ], + [ + [ + 97, + 38, + 46 + ], + [ + 97, + 39, + 49 + ] + ], + [ + [ + 98, + 16, + 35 + ], + [ + 98, + 17, + 36 + ] + ], + [ + [ + 98, + 15, + 35 + ], + [ + 98, + 16, + 36 + ] + ], + [ + [ + 98, + 14, + 36 + ], + [ + 98, + 15, + 37 + ] + ], + [ + [ + 98, + 14, + 39 + ], + [ + 98, + 15, + 40 + ] + ], + [ + [ + 98, + 39, + 39 + ], + [ + 98, + 40, + 40 + ] + ], + [ + [ + 98, + 16, + 44 + ], + [ + 98, + 17, + 45 + ] + ], + [ + [ + 98, + 15, + 44 + ], + [ + 98, + 16, + 45 + ] + ], + [ + [ + 98, + 14, + 40 + ], + [ + 98, + 15, + 41 + ] + ], + [ + [ + 98, + 39, + 40 + ], + [ + 98, + 40, + 41 + ] + ], + [ + [ + 99, + 17, + 36 + ], + [ + 99, + 18, + 37 + ] + ], + [ + [ + 99, + 14, + 38 + ], + [ + 99, + 15, + 39 + ] + ], + [ + [ + 99, + 17, + 43 + ], + [ + 99, + 18, + 44 + ] + ], + [ + [ + 100, + 16, + 36 + ], + [ + 100, + 17, + 37 + ] + ], + [ + [ + 100, + 15, + 36 + ], + [ + 100, + 16, + 37 + ] + ], + [ + [ + 100, + 14, + 37 + ], + [ + 100, + 15, + 38 + ] + ], + [ + [ + 100, + 16, + 43 + ], + [ + 100, + 17, + 44 + ] + ], + [ + [ + 100, + 15, + 43 + ], + [ + 100, + 16, + 44 + ] + ], + [ + [ + 101, + 15, + 37 + ], + [ + 101, + 16, + 38 + ] + ], + [ + [ + 101, + 15, + 42 + ], + [ + 101, + 16, + 43 + ] + ], + [ + [ + 106, + 38, + 38 + ], + [ + 106, + 39, + 39 + ] + ], + [ + [ + 106, + 37, + 37 + ], + [ + 106, + 38, + 38 + ] + ], + [ + [ + 106, + 38, + 41 + ], + [ + 106, + 39, + 42 + ] + ], + [ + [ + 107, + 37, + 42 + ], + [ + 107, + 38, + 43 + ] + ], + [ + [ + 109, + 38, + 39 + ], + [ + 109, + 39, + 40 + ] + ], + [ + [ + 109, + 38, + 40 + ], + [ + 109, + 39, + 41 + ] + ], + [ + [ + 111, + 18, + 36 + ], + [ + 111, + 19, + 37 + ] + ], + [ + [ + 111, + 33, + 36 + ], + [ + 111, + 34, + 37 + ] + ], + [ + [ + 111, + 18, + 43 + ], + [ + 111, + 19, + 44 + ] + ], + [ + [ + 112, + 19, + 36 + ], + [ + 112, + 20, + 37 + ] + ], + [ + [ + 112, + 19, + 43 + ], + [ + 112, + 20, + 44 + ] + ], + [ + [ + 112, + 33, + 43 + ], + [ + 112, + 34, + 44 + ] + ], + [ + [ + 113, + 20, + 36 + ], + [ + 113, + 21, + 37 + ] + ], + [ + [ + 113, + 20, + 43 + ], + [ + 113, + 21, + 44 + ] + ], + [ + [ + 114, + 15, + 38 + ], + [ + 114, + 16, + 39 + ] + ], + [ + [ + 114, + 36, + 37 + ], + [ + 114, + 37, + 38 + ] + ], + [ + [ + 114, + 32, + 36 + ], + [ + 114, + 33, + 37 + ] + ], + [ + [ + 114, + 15, + 41 + ], + [ + 114, + 16, + 42 + ] + ], + [ + [ + 114, + 36, + 42 + ], + [ + 114, + 37, + 43 + ] + ], + [ + [ + 114, + 32, + 43 + ], + [ + 114, + 33, + 44 + ] + ], + [ + [ + 116, + 37, + 38 + ], + [ + 116, + 38, + 39 + ] + ], + [ + [ + 116, + 21, + 36 + ], + [ + 116, + 22, + 37 + ] + ], + [ + [ + 116, + 37, + 41 + ], + [ + 116, + 38, + 42 + ] + ], + [ + [ + 116, + 21, + 43 + ], + [ + 116, + 22, + 44 + ] + ], + [ + [ + 117, + 15, + 39 + ], + [ + 117, + 16, + 40 + ] + ], + [ + [ + 117, + 16, + 37 + ], + [ + 117, + 17, + 38 + ] + ], + [ + [ + 117, + 22, + 36 + ], + [ + 117, + 23, + 37 + ] + ], + [ + [ + 117, + 31, + 36 + ], + [ + 117, + 32, + 37 + ] + ], + [ + [ + 117, + 16, + 42 + ], + [ + 117, + 17, + 43 + ] + ], + [ + [ + 117, + 15, + 40 + ], + [ + 117, + 16, + 41 + ] + ], + [ + [ + 117, + 22, + 43 + ], + [ + 117, + 23, + 44 + ] + ], + [ + [ + 117, + 31, + 43 + ], + [ + 117, + 32, + 44 + ] + ], + [ + [ + 118, + 23, + 36 + ], + [ + 118, + 24, + 37 + ] + ], + [ + [ + 118, + 29, + 36 + ], + [ + 118, + 31, + 37 + ] + ], + [ + [ + 118, + 23, + 43 + ], + [ + 118, + 24, + 44 + ] + ], + [ + [ + 118, + 29, + 43 + ], + [ + 118, + 31, + 44 + ] + ], + [ + [ + 119, + 24, + 36 + ], + [ + 119, + 25, + 37 + ] + ], + [ + [ + 119, + 27, + 36 + ], + [ + 119, + 29, + 37 + ] + ], + [ + [ + 119, + 24, + 43 + ], + [ + 119, + 26, + 44 + ] + ], + [ + [ + 119, + 26, + 43 + ], + [ + 119, + 29, + 44 + ] + ], + [ + [ + 120, + 37, + 39 + ], + [ + 120, + 38, + 40 + ] + ], + [ + [ + 120, + 25, + 36 + ], + [ + 120, + 27, + 37 + ] + ], + [ + [ + 120, + 37, + 40 + ], + [ + 120, + 38, + 41 + ] + ], + [ + [ + 121, + 16, + 38 + ], + [ + 121, + 17, + 39 + ] + ], + [ + [ + 121, + 17, + 37 + ], + [ + 121, + 18, + 38 + ] + ], + [ + [ + 121, + 35, + 37 + ], + [ + 121, + 36, + 38 + ] + ], + [ + [ + 121, + 16, + 41 + ], + [ + 121, + 17, + 42 + ] + ], + [ + [ + 121, + 17, + 42 + ], + [ + 121, + 18, + 43 + ] + ], + [ + [ + 121, + 35, + 42 + ], + [ + 121, + 36, + 43 + ] + ], + [ + [ + 123, + 16, + 39 + ], + [ + 123, + 17, + 40 + ] + ], + [ + [ + 123, + 16, + 40 + ], + [ + 123, + 17, + 41 + ] + ], + [ + [ + 124, + 18, + 37 + ], + [ + 124, + 19, + 38 + ] + ], + [ + [ + 124, + 18, + 42 + ], + [ + 124, + 19, + 43 + ] + ], + [ + [ + 125, + 17, + 38 + ], + [ + 125, + 18, + 39 + ] + ], + [ + [ + 125, + 34, + 37 + ], + [ + 125, + 35, + 38 + ] + ], + [ + [ + 125, + 17, + 41 + ], + [ + 125, + 18, + 42 + ] + ], + [ + [ + 125, + 34, + 42 + ], + [ + 125, + 35, + 43 + ] + ], + [ + [ + 126, + 36, + 38 + ], + [ + 126, + 37, + 39 + ] + ], + [ + [ + 126, + 19, + 37 + ], + [ + 126, + 20, + 38 + ] + ], + [ + [ + 126, + 36, + 41 + ], + [ + 126, + 37, + 42 + ] + ], + [ + [ + 126, + 19, + 42 + ], + [ + 126, + 20, + 43 + ] + ], + [ + [ + 127, + 17, + 40 + ], + [ + 127, + 18, + 41 + ] + ], + [ + [ + 128, + 17, + 39 + ], + [ + 128, + 18, + 40 + ] + ], + [ + [ + 128, + 20, + 37 + ], + [ + 128, + 21, + 38 + ] + ], + [ + [ + 128, + 20, + 42 + ], + [ + 128, + 21, + 43 + ] + ], + [ + [ + 129, + 21, + 37 + ], + [ + 129, + 22, + 38 + ] + ], + [ + [ + 129, + 18, + 38 + ], + [ + 129, + 19, + 39 + ] + ], + [ + [ + 129, + 21, + 42 + ], + [ + 129, + 22, + 43 + ] + ], + [ + [ + 129, + 18, + 41 + ], + [ + 129, + 19, + 42 + ] + ], + [ + [ + 130, + 33, + 37 + ], + [ + 130, + 34, + 38 + ] + ], + [ + [ + 130, + 33, + 42 + ], + [ + 130, + 34, + 43 + ] + ], + [ + [ + 131, + 36, + 39 + ], + [ + 131, + 37, + 40 + ] + ], + [ + [ + 131, + 22, + 37 + ], + [ + 131, + 23, + 38 + ] + ], + [ + [ + 131, + 18, + 39 + ], + [ + 131, + 19, + 40 + ] + ], + [ + [ + 131, + 36, + 40 + ], + [ + 131, + 37, + 41 + ] + ], + [ + [ + 131, + 22, + 42 + ], + [ + 131, + 23, + 43 + ] + ], + [ + [ + 131, + 18, + 40 + ], + [ + 131, + 19, + 41 + ] + ], + [ + [ + 132, + 23, + 37 + ], + [ + 132, + 24, + 38 + ] + ], + [ + [ + 132, + 32, + 37 + ], + [ + 132, + 33, + 38 + ] + ], + [ + [ + 132, + 19, + 38 + ], + [ + 132, + 20, + 39 + ] + ], + [ + [ + 132, + 23, + 42 + ], + [ + 132, + 24, + 43 + ] + ], + [ + [ + 132, + 32, + 42 + ], + [ + 132, + 33, + 43 + ] + ], + [ + [ + 132, + 19, + 41 + ], + [ + 132, + 20, + 42 + ] + ], + [ + [ + 133, + 24, + 37 + ], + [ + 133, + 25, + 38 + ] + ], + [ + [ + 133, + 24, + 42 + ], + [ + 133, + 25, + 43 + ] + ], + [ + [ + 134, + 35, + 38 + ], + [ + 134, + 36, + 39 + ] + ], + [ + [ + 134, + 25, + 37 + ], + [ + 134, + 27, + 38 + ] + ], + [ + [ + 134, + 31, + 37 + ], + [ + 134, + 32, + 38 + ] + ], + [ + [ + 134, + 19, + 39 + ], + [ + 134, + 20, + 40 + ] + ], + [ + [ + 134, + 35, + 41 + ], + [ + 134, + 36, + 42 + ] + ], + [ + [ + 134, + 25, + 42 + ], + [ + 134, + 27, + 43 + ] + ], + [ + [ + 134, + 31, + 42 + ], + [ + 134, + 32, + 43 + ] + ], + [ + [ + 134, + 19, + 40 + ], + [ + 134, + 20, + 41 + ] + ], + [ + [ + 135, + 27, + 37 + ], + [ + 135, + 31, + 38 + ] + ], + [ + [ + 135, + 20, + 38 + ], + [ + 135, + 21, + 39 + ] + ], + [ + [ + 135, + 27, + 42 + ], + [ + 135, + 31, + 43 + ] + ], + [ + [ + 135, + 20, + 41 + ], + [ + 135, + 21, + 42 + ] + ], + [ + [ + 137, + 20, + 39 + ], + [ + 137, + 21, + 40 + ] + ], + [ + [ + 137, + 20, + 40 + ], + [ + 137, + 21, + 41 + ] + ], + [ + [ + 138, + 21, + 38 + ], + [ + 138, + 22, + 39 + ] + ], + [ + [ + 138, + 21, + 41 + ], + [ + 138, + 22, + 42 + ] + ], + [ + [ + 139, + 35, + 39 + ], + [ + 139, + 36, + 40 + ] + ], + [ + [ + 139, + 35, + 40 + ], + [ + 139, + 36, + 41 + ] + ], + [ + [ + 140, + 34, + 38 + ], + [ + 140, + 35, + 39 + ] + ], + [ + [ + 140, + 34, + 41 + ], + [ + 140, + 35, + 42 + ] + ], + [ + [ + 141, + 21, + 39 + ], + [ + 141, + 22, + 40 + ] + ], + [ + [ + 141, + 22, + 38 + ], + [ + 141, + 23, + 39 + ] + ], + [ + [ + 141, + 21, + 40 + ], + [ + 141, + 22, + 41 + ] + ], + [ + [ + 141, + 22, + 41 + ], + [ + 141, + 23, + 42 + ] + ], + [ + [ + 143, + 23, + 38 + ], + [ + 143, + 24, + 39 + ] + ], + [ + [ + 143, + 23, + 41 + ], + [ + 143, + 24, + 42 + ] + ], + [ + [ + 144, + 22, + 39 + ], + [ + 144, + 23, + 40 + ] + ], + [ + [ + 144, + 22, + 40 + ], + [ + 144, + 23, + 41 + ] + ], + [ + [ + 145, + 33, + 38 + ], + [ + 145, + 34, + 39 + ] + ], + [ + [ + 145, + 24, + 38 + ], + [ + 145, + 25, + 39 + ] + ], + [ + [ + 145, + 35, + 40 + ], + [ + 145, + 36, + 41 + ] + ], + [ + [ + 145, + 35, + 39 + ], + [ + 145, + 36, + 40 + ] + ], + [ + [ + 145, + 33, + 41 + ], + [ + 145, + 34, + 42 + ] + ], + [ + [ + 145, + 24, + 41 + ], + [ + 145, + 25, + 42 + ] + ], + [ + [ + 146, + 36, + 40 + ], + [ + 146, + 37, + 41 + ] + ], + [ + [ + 146, + 36, + 39 + ], + [ + 146, + 37, + 40 + ] + ], + [ + [ + 147, + 25, + 38 + ], + [ + 147, + 26, + 39 + ] + ], + [ + [ + 147, + 23, + 39 + ], + [ + 147, + 24, + 40 + ] + ], + [ + [ + 147, + 37, + 40 + ], + [ + 147, + 38, + 41 + ] + ], + [ + [ + 147, + 37, + 39 + ], + [ + 147, + 38, + 40 + ] + ], + [ + [ + 147, + 25, + 41 + ], + [ + 147, + 26, + 42 + ] + ], + [ + [ + 147, + 23, + 40 + ], + [ + 147, + 24, + 41 + ] + ], + [ + [ + 148, + 32, + 38 + ], + [ + 148, + 33, + 39 + ] + ], + [ + [ + 148, + 38, + 40 + ], + [ + 148, + 40, + 41 + ] + ], + [ + [ + 148, + 38, + 39 + ], + [ + 148, + 40, + 40 + ] + ], + [ + [ + 148, + 32, + 41 + ], + [ + 148, + 33, + 42 + ] + ], + [ + [ + 149, + 26, + 38 + ], + [ + 149, + 27, + 39 + ] + ], + [ + [ + 149, + 40, + 40 + ], + [ + 149, + 41, + 41 + ] + ], + [ + [ + 149, + 40, + 39 + ], + [ + 149, + 41, + 40 + ] + ], + [ + [ + 149, + 26, + 41 + ], + [ + 149, + 27, + 42 + ] + ], + [ + [ + 150, + 27, + 38 + ], + [ + 150, + 29, + 39 + ] + ], + [ + [ + 150, + 31, + 38 + ], + [ + 150, + 32, + 39 + ] + ], + [ + [ + 150, + 24, + 39 + ], + [ + 150, + 25, + 40 + ] + ], + [ + [ + 150, + 41, + 40 + ], + [ + 150, + 42, + 41 + ] + ], + [ + [ + 150, + 41, + 39 + ], + [ + 150, + 42, + 40 + ] + ], + [ + [ + 150, + 31, + 41 + ], + [ + 150, + 32, + 42 + ] + ], + [ + [ + 150, + 27, + 41 + ], + [ + 150, + 29, + 42 + ] + ], + [ + [ + 150, + 24, + 40 + ], + [ + 150, + 25, + 41 + ] + ], + [ + [ + 151, + 29, + 38 + ], + [ + 151, + 31, + 39 + ] + ], + [ + [ + 151, + 42, + 40 + ], + [ + 151, + 43, + 41 + ] + ], + [ + [ + 151, + 42, + 39 + ], + [ + 151, + 43, + 40 + ] + ], + [ + [ + 151, + 29, + 41 + ], + [ + 151, + 31, + 42 + ] + ], + [ + [ + 152, + 43, + 40 + ], + [ + 152, + 45, + 41 + ] + ], + [ + [ + 152, + 43, + 39 + ], + [ + 152, + 45, + 40 + ] + ], + [ + [ + 153, + 45, + 40 + ], + [ + 153, + 46, + 41 + ] + ], + [ + [ + 153, + 45, + 39 + ], + [ + 153, + 46, + 40 + ] + ], + [ + [ + 154, + 25, + 39 + ], + [ + 154, + 26, + 40 + ] + ], + [ + [ + 154, + 46, + 40 + ], + [ + 154, + 47, + 41 + ] + ], + [ + [ + 154, + 46, + 39 + ], + [ + 154, + 47, + 40 + ] + ], + [ + [ + 154, + 25, + 40 + ], + [ + 154, + 26, + 41 + ] + ], + [ + [ + 155, + 47, + 40 + ], + [ + 155, + 48, + 41 + ] + ], + [ + [ + 155, + 47, + 39 + ], + [ + 155, + 48, + 40 + ] + ], + [ + [ + 156, + 48, + 40 + ], + [ + 156, + 50, + 41 + ] + ], + [ + [ + 156, + 48, + 39 + ], + [ + 156, + 50, + 40 + ] + ], + [ + [ + 157, + 26, + 39 + ], + [ + 157, + 27, + 40 + ] + ], + [ + [ + 157, + 50, + 40 + ], + [ + 157, + 51, + 41 + ] + ], + [ + [ + 157, + 50, + 39 + ], + [ + 157, + 51, + 40 + ] + ], + [ + [ + 157, + 26, + 40 + ], + [ + 157, + 27, + 41 + ] + ], + [ + [ + 158, + 51, + 40 + ], + [ + 158, + 52, + 41 + ] + ], + [ + [ + 158, + 51, + 39 + ], + [ + 158, + 52, + 40 + ] + ], + [ + [ + 159, + 52, + 40 + ], + [ + 159, + 53, + 41 + ] + ], + [ + [ + 159, + 52, + 39 + ], + [ + 159, + 53, + 40 + ] + ], + [ + [ + 160, + 53, + 40 + ], + [ + 160, + 54, + 41 + ] + ], + [ + [ + 160, + 53, + 39 + ], + [ + 160, + 54, + 40 + ] + ], + [ + [ + 161, + 27, + 39 + ], + [ + 161, + 28, + 40 + ] + ], + [ + [ + 161, + 54, + 40 + ], + [ + 161, + 56, + 41 + ] + ], + [ + [ + 161, + 54, + 39 + ], + [ + 161, + 56, + 40 + ] + ], + [ + [ + 161, + 27, + 40 + ], + [ + 161, + 28, + 41 + ] + ], + [ + [ + 162, + 56, + 40 + ], + [ + 162, + 57, + 41 + ] + ], + [ + [ + 162, + 56, + 39 + ], + [ + 162, + 57, + 40 + ] + ], + [ + [ + 163, + 57, + 40 + ], + [ + 163, + 58, + 41 + ] + ], + [ + [ + 163, + 57, + 39 + ], + [ + 163, + 58, + 40 + ] + ], + [ + [ + 164, + 28, + 39 + ], + [ + 164, + 29, + 40 + ] + ], + [ + [ + 164, + 58, + 40 + ], + [ + 164, + 59, + 41 + ] + ], + [ + [ + 164, + 58, + 39 + ], + [ + 164, + 59, + 40 + ] + ], + [ + [ + 164, + 28, + 40 + ], + [ + 164, + 29, + 41 + ] + ], + [ + [ + 165, + 59, + 40 + ], + [ + 165, + 60, + 41 + ] + ], + [ + [ + 165, + 59, + 39 + ], + [ + 165, + 60, + 40 + ] + ], + [ + [ + 166, + 29, + 39 + ], + [ + 166, + 30, + 40 + ] + ], + [ + [ + 166, + 32, + 39 + ], + [ + 166, + 33, + 40 + ] + ], + [ + [ + 166, + 60, + 40 + ], + [ + 166, + 62, + 41 + ] + ], + [ + [ + 166, + 60, + 39 + ], + [ + 166, + 62, + 40 + ] + ], + [ + [ + 166, + 32, + 40 + ], + [ + 166, + 33, + 41 + ] + ], + [ + [ + 166, + 29, + 40 + ], + [ + 166, + 30, + 41 + ] + ], + [ + [ + 167, + 30, + 39 + ], + [ + 167, + 32, + 40 + ] + ], + [ + [ + 167, + 33, + 39 + ], + [ + 167, + 35, + 40 + ] + ], + [ + [ + 167, + 62, + 40 + ], + [ + 167, + 63, + 41 + ] + ], + [ + [ + 167, + 62, + 39 + ], + [ + 167, + 63, + 40 + ] + ], + [ + [ + 167, + 33, + 40 + ], + [ + 167, + 35, + 41 + ] + ], + [ + [ + 167, + 30, + 40 + ], + [ + 167, + 32, + 41 + ] + ], + [ + [ + 168, + 35, + 39 + ], + [ + 168, + 37, + 40 + ] + ], + [ + [ + 168, + 63, + 40 + ], + [ + 168, + 64, + 41 + ] + ], + [ + [ + 168, + 65, + 40 + ], + [ + 168, + 66, + 42 + ] + ], + [ + [ + 168, + 63, + 39 + ], + [ + 168, + 64, + 40 + ] + ], + [ + [ + 168, + 35, + 40 + ], + [ + 168, + 37, + 41 + ] + ], + [ + [ + 168, + 65, + 38 + ], + [ + 168, + 66, + 40 + ] + ], + [ + [ + 169, + 37, + 39 + ], + [ + 169, + 40, + 40 + ] + ], + [ + [ + 169, + 64, + 40 + ], + [ + 169, + 65, + 41 + ] + ], + [ + [ + 169, + 65, + 42 + ], + [ + 169, + 66, + 44 + ] + ], + [ + [ + 169, + 64, + 40 + ], + [ + 169, + 65, + 41 + ] + ], + [ + [ + 169, + 64, + 39 + ], + [ + 169, + 65, + 40 + ] + ], + [ + [ + 169, + 37, + 40 + ], + [ + 169, + 39, + 41 + ] + ], + [ + [ + 169, + 65, + 36 + ], + [ + 169, + 66, + 38 + ] + ], + [ + [ + 169, + 64, + 39 + ], + [ + 169, + 65, + 40 + ] + ], + [ + [ + 170, + 66, + 40 + ], + [ + 170, + 67, + 42 + ] + ], + [ + [ + 170, + 40, + 39 + ], + [ + 170, + 42, + 40 + ] + ], + [ + [ + 170, + 65, + 40 + ], + [ + 170, + 67, + 41 + ] + ], + [ + [ + 170, + 65, + 44 + ], + [ + 170, + 66, + 46 + ] + ], + [ + [ + 170, + 66, + 38 + ], + [ + 170, + 67, + 40 + ] + ], + [ + [ + 170, + 65, + 39 + ], + [ + 170, + 67, + 40 + ] + ], + [ + [ + 170, + 39, + 40 + ], + [ + 170, + 41, + 41 + ] + ], + [ + [ + 170, + 65, + 34 + ], + [ + 170, + 66, + 36 + ] + ], + [ + [ + 171, + 66, + 42 + ], + [ + 171, + 67, + 44 + ] + ], + [ + [ + 171, + 42, + 39 + ], + [ + 171, + 44, + 40 + ] + ], + [ + [ + 171, + 67, + 40 + ], + [ + 171, + 68, + 41 + ] + ], + [ + [ + 171, + 65, + 46 + ], + [ + 171, + 66, + 48 + ] + ], + [ + [ + 171, + 64, + 41 + ], + [ + 171, + 65, + 42 + ] + ], + [ + [ + 171, + 66, + 36 + ], + [ + 171, + 67, + 38 + ] + ], + [ + [ + 171, + 67, + 39 + ], + [ + 171, + 68, + 40 + ] + ], + [ + [ + 171, + 41, + 40 + ], + [ + 171, + 44, + 41 + ] + ], + [ + [ + 171, + 65, + 32 + ], + [ + 171, + 66, + 34 + ] + ], + [ + [ + 171, + 64, + 38 + ], + [ + 171, + 65, + 39 + ] + ], + [ + [ + 172, + 44, + 39 + ], + [ + 172, + 46, + 40 + ] + ], + [ + [ + 172, + 68, + 40 + ], + [ + 172, + 69, + 41 + ] + ], + [ + [ + 172, + 65, + 48 + ], + [ + 172, + 66, + 51 + ] + ], + [ + [ + 172, + 68, + 39 + ], + [ + 172, + 69, + 40 + ] + ], + [ + [ + 172, + 44, + 40 + ], + [ + 172, + 46, + 41 + ] + ], + [ + [ + 172, + 65, + 30 + ], + [ + 172, + 66, + 32 + ] + ], + [ + [ + 173, + 66, + 44 + ], + [ + 173, + 67, + 45 + ] + ], + [ + [ + 173, + 66, + 48 + ], + [ + 173, + 67, + 49 + ] + ], + [ + [ + 173, + 46, + 39 + ], + [ + 173, + 49, + 40 + ] + ], + [ + [ + 173, + 69, + 40 + ], + [ + 173, + 70, + 41 + ] + ], + [ + [ + 173, + 66, + 35 + ], + [ + 173, + 67, + 36 + ] + ], + [ + [ + 173, + 66, + 31 + ], + [ + 173, + 67, + 32 + ] + ], + [ + [ + 173, + 69, + 39 + ], + [ + 173, + 70, + 40 + ] + ], + [ + [ + 173, + 46, + 40 + ], + [ + 173, + 49, + 41 + ] + ], + [ + [ + 173, + 65, + 29 + ], + [ + 173, + 66, + 30 + ] + ], + [ + [ + 173, + 64, + 37 + ], + [ + 173, + 65, + 38 + ] + ], + [ + [ + 174, + 66, + 36 + ], + [ + 174, + 67, + 37 + ] + ], + [ + [ + 174, + 66, + 49 + ], + [ + 174, + 67, + 51 + ] + ], + [ + [ + 174, + 49, + 39 + ], + [ + 174, + 52, + 40 + ] + ], + [ + [ + 174, + 70, + 40 + ], + [ + 174, + 72, + 41 + ] + ], + [ + [ + 174, + 64, + 42 + ], + [ + 174, + 65, + 43 + ] + ], + [ + [ + 174, + 66, + 29 + ], + [ + 174, + 67, + 31 + ] + ], + [ + [ + 174, + 66, + 43 + ], + [ + 174, + 67, + 44 + ] + ], + [ + [ + 174, + 70, + 39 + ], + [ + 174, + 72, + 40 + ] + ], + [ + [ + 174, + 49, + 40 + ], + [ + 174, + 51, + 41 + ] + ], + [ + [ + 175, + 66, + 31 + ], + [ + 175, + 67, + 32 + ] + ], + [ + [ + 175, + 66, + 47 + ], + [ + 175, + 67, + 48 + ] + ], + [ + [ + 175, + 52, + 39 + ], + [ + 175, + 55, + 40 + ] + ], + [ + [ + 175, + 66, + 32 + ], + [ + 175, + 67, + 33 + ] + ], + [ + [ + 175, + 66, + 48 + ], + [ + 175, + 67, + 49 + ] + ], + [ + [ + 175, + 51, + 40 + ], + [ + 175, + 54, + 41 + ] + ], + [ + [ + 176, + 66, + 37 + ], + [ + 176, + 67, + 38 + ] + ], + [ + [ + 176, + 66, + 30 + ], + [ + 176, + 67, + 31 + ] + ], + [ + [ + 176, + 55, + 39 + ], + [ + 176, + 58, + 40 + ] + ], + [ + [ + 176, + 64, + 43 + ], + [ + 176, + 65, + 44 + ] + ], + [ + [ + 176, + 66, + 42 + ], + [ + 176, + 67, + 43 + ] + ], + [ + [ + 176, + 66, + 49 + ], + [ + 176, + 67, + 50 + ] + ], + [ + [ + 176, + 54, + 40 + ], + [ + 176, + 57, + 41 + ] + ], + [ + [ + 176, + 64, + 36 + ], + [ + 176, + 65, + 37 + ] + ], + [ + [ + 177, + 66, + 35 + ], + [ + 177, + 67, + 36 + ] + ], + [ + [ + 177, + 66, + 29 + ], + [ + 177, + 67, + 30 + ] + ], + [ + [ + 177, + 66, + 45 + ], + [ + 177, + 67, + 46 + ] + ], + [ + [ + 177, + 58, + 39 + ], + [ + 177, + 61, + 40 + ] + ], + [ + [ + 177, + 64, + 38 + ], + [ + 177, + 65, + 39 + ] + ], + [ + [ + 177, + 64, + 36 + ], + [ + 177, + 65, + 38 + ] + ], + [ + [ + 177, + 66, + 34 + ], + [ + 177, + 67, + 35 + ] + ], + [ + [ + 177, + 66, + 44 + ], + [ + 177, + 67, + 45 + ] + ], + [ + [ + 177, + 66, + 50 + ], + [ + 177, + 67, + 51 + ] + ], + [ + [ + 177, + 57, + 40 + ], + [ + 177, + 60, + 41 + ] + ], + [ + [ + 177, + 64, + 41 + ], + [ + 177, + 65, + 44 + ] + ], + [ + [ + 178, + 66, + 32 + ], + [ + 178, + 67, + 33 + ] + ], + [ + [ + 178, + 61, + 39 + ], + [ + 178, + 63, + 40 + ] + ], + [ + [ + 178, + 66, + 47 + ], + [ + 178, + 67, + 48 + ] + ], + [ + [ + 178, + 60, + 40 + ], + [ + 178, + 63, + 41 + ] + ], + [ + [ + 179, + 66, + 46 + ], + [ + 179, + 67, + 47 + ] + ], + [ + [ + 179, + 63, + 39 + ], + [ + 179, + 66, + 40 + ] + ], + [ + [ + 179, + 66, + 33 + ], + [ + 179, + 67, + 34 + ] + ], + [ + [ + 179, + 63, + 40 + ], + [ + 179, + 65, + 41 + ] + ], + [ + [ + 180, + 66, + 34 + ], + [ + 180, + 67, + 35 + ] + ], + [ + [ + 180, + 66, + 38 + ], + [ + 180, + 67, + 39 + ] + ], + [ + [ + 180, + 66, + 33 + ], + [ + 180, + 67, + 34 + ] + ], + [ + [ + 180, + 66, + 39 + ], + [ + 180, + 68, + 40 + ] + ], + [ + [ + 180, + 65, + 30 + ], + [ + 180, + 66, + 31 + ] + ], + [ + [ + 180, + 66, + 45 + ], + [ + 180, + 67, + 46 + ] + ], + [ + [ + 180, + 66, + 41 + ], + [ + 180, + 67, + 42 + ] + ], + [ + [ + 180, + 66, + 46 + ], + [ + 180, + 67, + 47 + ] + ], + [ + [ + 180, + 65, + 40 + ], + [ + 180, + 68, + 41 + ] + ], + [ + [ + 180, + 65, + 49 + ], + [ + 180, + 66, + 50 + ] + ], + [ + [ + 181, + 68, + 39 + ], + [ + 181, + 70, + 40 + ] + ], + [ + [ + 181, + 65, + 29 + ], + [ + 181, + 66, + 30 + ] + ], + [ + [ + 181, + 65, + 31 + ], + [ + 181, + 66, + 32 + ] + ], + [ + [ + 181, + 68, + 40 + ], + [ + 181, + 70, + 41 + ] + ], + [ + [ + 181, + 65, + 50 + ], + [ + 181, + 66, + 51 + ] + ], + [ + [ + 181, + 65, + 48 + ], + [ + 181, + 66, + 49 + ] + ], + [ + [ + 182, + 70, + 39 + ], + [ + 182, + 72, + 40 + ] + ], + [ + [ + 182, + 65, + 32 + ], + [ + 182, + 66, + 38 + ] + ], + [ + [ + 182, + 70, + 40 + ], + [ + 182, + 72, + 41 + ] + ], + [ + [ + 182, + 65, + 42 + ], + [ + 182, + 66, + 48 + ] + ], + [ + [ + 183, + 66, + 39 + ], + [ + 183, + 67, + 40 + ] + ], + [ + [ + 183, + 65, + 38 + ], + [ + 183, + 66, + 40 + ] + ], + [ + [ + 183, + 66, + 40 + ], + [ + 183, + 67, + 41 + ] + ], + [ + [ + 183, + 65, + 40 + ], + [ + 183, + 66, + 42 + ] + ] + ] + }, + { + "id": 10, + "type": "cell", + "intervals": [ + [ + [ + 128, + 18, + 40 + ], + [ + 129, + 18, + 40 + ] + ], + [ + [ + 65, + 15, + 38 + ], + [ + 102, + 15, + 39 + ] + ], + [ + [ + 66, + 15, + 39 + ], + [ + 101, + 15, + 41 + ] + ], + [ + [ + 65, + 15, + 41 + ], + [ + 102, + 15, + 42 + ] + ], + [ + [ + 64, + 16, + 37 + ], + [ + 101, + 16, + 38 + ] + ], + [ + [ + 64, + 16, + 42 + ], + [ + 101, + 16, + 43 + ] + ], + [ + [ + 55, + 18, + 37 + ], + [ + 122, + 18, + 43 + ] + ], + [ + [ + 122, + 18, + 38 + ], + [ + 126, + 18, + 42 + ] + ], + [ + [ + 126, + 18, + 39 + ], + [ + 128, + 18, + 41 + ] + ], + [ + [ + 63, + 18, + 36 + ], + [ + 98, + 18, + 37 + ] + ], + [ + [ + 81, + 18, + 43 + ], + [ + 98, + 18, + 44 + ] + ], + [ + [ + 63, + 18, + 43 + ], + [ + 81, + 18, + 44 + ] + ], + [ + [ + 35, + 19, + 38 + ], + [ + 49, + 19, + 43 + ] + ], + [ + [ + 49, + 19, + 38 + ], + [ + 55, + 19, + 44 + ] + ], + [ + [ + 49, + 19, + 36 + ], + [ + 55, + 19, + 38 + ] + ], + [ + [ + 35, + 15, + 39 + ], + [ + 35, + 19, + 41 + ] + ], + [ + [ + 35, + 19, + 37 + ], + [ + 35, + 29, + 41 + ] + ], + [ + [ + 35, + 19, + 41 + ], + [ + 35, + 20, + 42 + ] + ], + [ + [ + 35, + 19, + 42 + ], + [ + 35, + 29, + 43 + ] + ], + [ + [ + 35, + 21, + 41 + ], + [ + 35, + 29, + 42 + ] + ], + [ + [ + 35, + 29, + 38 + ], + [ + 35, + 30, + 42 + ] + ], + [ + [ + 55, + 36, + 37 + ], + [ + 110, + 36, + 43 + ] + ], + [ + [ + 64, + 18, + 36 + ], + [ + 97, + 19, + 36 + ] + ], + [ + [ + 65, + 19, + 36 + ], + [ + 94, + 20, + 36 + ] + ], + [ + [ + 67, + 20, + 36 + ], + [ + 88, + 21, + 36 + ] + ], + [ + [ + 71, + 35, + 37 + ], + [ + 72, + 36, + 37 + ] + ], + [ + [ + 71, + 35, + 37 + ], + [ + 102, + 36, + 37 + ] + ], + [ + [ + 63, + 16, + 37 + ], + [ + 101, + 17, + 37 + ] + ], + [ + [ + 63, + 17, + 37 + ], + [ + 99, + 18, + 37 + ] + ], + [ + [ + 64, + 15, + 38 + ], + [ + 101, + 16, + 38 + ] + ], + [ + [ + 64, + 15, + 42 + ], + [ + 101, + 16, + 42 + ] + ], + [ + [ + 72, + 35, + 43 + ], + [ + 102, + 36, + 43 + ] + ], + [ + [ + 63, + 16, + 43 + ], + [ + 71, + 17, + 43 + ] + ], + [ + [ + 63, + 17, + 43 + ], + [ + 99, + 18, + 43 + ] + ], + [ + [ + 72, + 16, + 43 + ], + [ + 101, + 17, + 43 + ] + ], + [ + [ + 64, + 18, + 44 + ], + [ + 97, + 19, + 44 + ] + ], + [ + [ + 65, + 19, + 44 + ], + [ + 94, + 20, + 44 + ] + ], + [ + [ + 67, + 20, + 44 + ], + [ + 88, + 21, + 44 + ] + ], + [ + [ + 55, + 18, + 36 + ], + [ + 55, + 19, + 44 + ] + ], + [ + [ + 81, + 18, + 43 + ], + [ + 81, + 19, + 44 + ] + ], + [ + [ + 81, + 18, + 43 + ], + [ + 81, + 19, + 44 + ] + ], + [ + [ + 110, + 36, + 37 + ], + [ + 110, + 37, + 43 + ] + ], + [ + [ + 110, + 37, + 38 + ], + [ + 110, + 38, + 42 + ] + ], + [ + [ + 130, + 18, + 39 + ], + [ + 130, + 19, + 41 + ] + ], + [ + [ + 130, + 19, + 38 + ], + [ + 130, + 22, + 42 + ] + ], + [ + [ + 130, + 22, + 37 + ], + [ + 130, + 34, + 43 + ] + ], + [ + [ + 130, + 34, + 38 + ], + [ + 130, + 36, + 42 + ] + ], + [ + [ + 130, + 36, + 39 + ], + [ + 130, + 37, + 41 + ] + ] + ] + }, + { + "id": 11, + "type": "cell", + "intervals": [ + [ + [ + 40, + 20, + 43 + ], + [ + 40, + 20, + 43 + ] + ], + [ + [ + 40, + 20, + 43 + ], + [ + 40, + 20, + 43 + ] + ] + ] + }, + { + "id": 12, + "type": "cell", + "intervals": [ + [ + [ + 40, + 20, + 43 + ], + [ + 40, + 20, + 43 + ] + ], + [ + [ + 37, + 27, + 43 + ], + [ + 37, + 27, + 43 + ] + ], + [ + [ + 40, + 20, + 43 + ], + [ + 40, + 20, + 43 + ] + ], + [ + [ + 37, + 27, + 43 + ], + [ + 37, + 27, + 43 + ] + ] + ] + }, + { + "id": 13, + "type": "cell", + "intervals": [ + [ + [ + 37, + 27, + 43 + ], + [ + 37, + 27, + 43 + ] + ], + [ + [ + 37, + 27, + 43 + ], + [ + 37, + 27, + 43 + ] + ] + ] + }, + { + "id": 14, + "type": "cell", + "intervals": [ + [ + [ + 40, + 20, + 43 + ], + [ + 40, + 20, + 43 + ] + ], + [ + [ + 52, + 20, + 43 + ], + [ + 52, + 20, + 43 + ] + ], + [ + [ + 40, + 20, + 43 + ], + [ + 40, + 20, + 43 + ] + ], + [ + [ + 52, + 20, + 43 + ], + [ + 52, + 20, + 43 + ] + ] + ] + }, + { + "id": 15, + "type": "cell", + "intervals": [ + [ + [ + 52, + 20, + 43 + ], + [ + 52, + 20, + 43 + ] + ], + [ + [ + 55, + 20, + 43 + ], + [ + 55, + 20, + 43 + ] + ], + [ + [ + 52, + 20, + 43 + ], + [ + 52, + 20, + 43 + ] + ], + [ + [ + 55, + 20, + 43 + ], + [ + 55, + 20, + 43 + ] + ] + ] + }, + { + "id": 16, + "type": "cell", + "intervals": [ + [ + [ + 55, + 20, + 43 + ], + [ + 55, + 20, + 43 + ] + ], + [ + [ + 59, + 38, + 42 + ], + [ + 59, + 38, + 42 + ] + ], + [ + [ + 55, + 20, + 43 + ], + [ + 55, + 20, + 43 + ] + ], + [ + [ + 59, + 38, + 42 + ], + [ + 59, + 38, + 42 + ] + ] + ] + }, + { + "id": 17, + "type": "cell", + "intervals": [ + [ + [ + 59, + 38, + 42 + ], + [ + 59, + 38, + 42 + ] + ], + [ + [ + 59, + 38, + 42 + ], + [ + 59, + 38, + 42 + ] + ] + ] + }, + { + "id": 18, + "type": "cell", + "intervals": [ + [ + [ + 55, + 20, + 43 + ], + [ + 55, + 20, + 43 + ] + ], + [ + [ + 70, + 19, + 43 + ], + [ + 70, + 19, + 43 + ] + ], + [ + [ + 55, + 20, + 43 + ], + [ + 55, + 20, + 43 + ] + ], + [ + [ + 70, + 19, + 43 + ], + [ + 70, + 19, + 43 + ] + ] + ] + }, + { + "id": 19, + "type": "cell", + "intervals": [ + [ + [ + 70, + 19, + 43 + ], + [ + 70, + 19, + 43 + ] + ], + [ + [ + 72, + 17, + 43 + ], + [ + 72, + 17, + 43 + ] + ], + [ + [ + 70, + 19, + 43 + ], + [ + 70, + 19, + 43 + ] + ], + [ + [ + 72, + 17, + 43 + ], + [ + 72, + 17, + 43 + ] + ] + ] + }, + { + "id": 20, + "type": "cell", + "intervals": [ + [ + [ + 72, + 17, + 43 + ], + [ + 72, + 17, + 43 + ] + ], + [ + [ + 72, + 17, + 43 + ], + [ + 72, + 17, + 43 + ] + ] + ] + }, + { + "id": 21, + "type": "cell", + "intervals": [ + [ + [ + 72, + 17, + 43 + ], + [ + 72, + 17, + 43 + ] + ], + [ + [ + 72, + 17, + 43 + ], + [ + 72, + 17, + 43 + ] + ] + ] + }, + { + "id": 22, + "type": "cell", + "intervals": [ + [ + [ + 21, + 20, + 42 + ], + [ + 21, + 20, + 42 + ] + ], + [ + [ + 21, + 20, + 42 + ], + [ + 21, + 20, + 42 + ] + ] + ] + }, + { + "id": 23, + "type": "cell", + "intervals": [ + [ + [ + 40, + 29, + 41 + ], + [ + 40, + 29, + 41 + ] + ], + [ + [ + 40, + 29, + 41 + ], + [ + 40, + 29, + 41 + ] + ] + ] + }, + { + "id": 24, + "type": "cell", + "intervals": [ + [ + [ + 75, + 37, + 42 + ], + [ + 75, + 37, + 42 + ] + ], + [ + [ + 75, + 37, + 42 + ], + [ + 75, + 37, + 42 + ] + ] + ] + }, + { + "id": 25, + "type": "cell", + "intervals": [ + [ + [ + 81, + 17, + 40 + ], + [ + 81, + 17, + 40 + ] + ], + [ + [ + 81, + 17, + 40 + ], + [ + 81, + 17, + 40 + ] + ] + ] + }, + { + "id": 26, + "type": "cell", + "intervals": [ + [ + [ + 71, + 17, + 46 + ], + [ + 71, + 17, + 46 + ] + ], + [ + [ + 71, + 17, + 46 + ], + [ + 71, + 17, + 46 + ] + ] + ] + }, + { + "id": 27, + "type": "cell", + "intervals": [ + [ + [ + 72, + 17, + 42 + ], + [ + 72, + 17, + 43 + ] + ], + [ + [ + 75, + 17, + 41 + ], + [ + 75, + 17, + 42 + ] + ], + [ + [ + 77, + 17, + 40 + ], + [ + 77, + 17, + 41 + ] + ], + [ + [ + 72, + 17, + 42 + ], + [ + 72, + 17, + 42 + ] + ], + [ + [ + 72, + 17, + 43 + ], + [ + 72, + 17, + 43 + ] + ], + [ + [ + 75, + 17, + 41 + ], + [ + 75, + 17, + 41 + ] + ], + [ + [ + 75, + 17, + 42 + ], + [ + 75, + 17, + 42 + ] + ], + [ + [ + 77, + 17, + 40 + ], + [ + 77, + 17, + 40 + ] + ], + [ + [ + 77, + 17, + 41 + ], + [ + 77, + 17, + 41 + ] + ] + ] + }, + { + "id": 28, + "type": "cell", + "intervals": [ + [ + [ + 71, + 16, + 44 + ], + [ + 72, + 16, + 44 + ] + ], + [ + [ + 71, + 16, + 44 + ], + [ + 71, + 17, + 44 + ] + ], + [ + [ + 71, + 17, + 44 + ], + [ + 71, + 17, + 45 + ] + ], + [ + [ + 71, + 17, + 45 + ], + [ + 71, + 18, + 45 + ] + ], + [ + [ + 71, + 17, + 45 + ], + [ + 71, + 17, + 46 + ] + ], + [ + [ + 72, + 16, + 43 + ], + [ + 72, + 17, + 43 + ] + ], + [ + [ + 72, + 16, + 43 + ], + [ + 72, + 16, + 44 + ] + ], + [ + [ + 71, + 16, + 44 + ], + [ + 71, + 16, + 44 + ] + ], + [ + [ + 71, + 17, + 44 + ], + [ + 71, + 17, + 44 + ] + ], + [ + [ + 71, + 17, + 45 + ], + [ + 71, + 17, + 45 + ] + ], + [ + [ + 71, + 17, + 46 + ], + [ + 71, + 17, + 46 + ] + ], + [ + [ + 71, + 18, + 45 + ], + [ + 71, + 18, + 45 + ] + ], + [ + [ + 72, + 16, + 43 + ], + [ + 72, + 16, + 43 + ] + ], + [ + [ + 72, + 16, + 44 + ], + [ + 72, + 16, + 44 + ] + ], + [ + [ + 72, + 17, + 43 + ], + [ + 72, + 17, + 43 + ] + ] + ] + }, + { + "id": 29, + "type": "cell", + "intervals": [ + [ + [ + 21, + 20, + 42 + ], + [ + 21, + 21, + 42 + ] + ], + [ + [ + 21, + 21, + 42 + ], + [ + 22, + 21, + 42 + ] + ], + [ + [ + 22, + 21, + 41 + ], + [ + 22, + 21, + 42 + ] + ], + [ + [ + 33, + 20, + 41 + ], + [ + 34, + 20, + 41 + ] + ], + [ + [ + 33, + 20, + 41 + ], + [ + 33, + 21, + 41 + ] + ], + [ + [ + 34, + 20, + 41 + ], + [ + 34, + 20, + 42 + ] + ], + [ + [ + 38, + 20, + 42 + ], + [ + 38, + 20, + 43 + ] + ], + [ + [ + 21, + 20, + 42 + ], + [ + 21, + 20, + 42 + ] + ], + [ + [ + 21, + 21, + 42 + ], + [ + 21, + 21, + 42 + ] + ], + [ + [ + 22, + 21, + 41 + ], + [ + 22, + 21, + 41 + ] + ], + [ + [ + 22, + 21, + 42 + ], + [ + 22, + 21, + 42 + ] + ], + [ + [ + 33, + 20, + 41 + ], + [ + 33, + 20, + 41 + ] + ], + [ + [ + 33, + 21, + 41 + ], + [ + 33, + 21, + 41 + ] + ], + [ + [ + 34, + 20, + 41 + ], + [ + 34, + 20, + 41 + ] + ], + [ + [ + 34, + 20, + 42 + ], + [ + 34, + 20, + 42 + ] + ], + [ + [ + 38, + 20, + 42 + ], + [ + 38, + 20, + 42 + ] + ], + [ + [ + 38, + 20, + 43 + ], + [ + 38, + 20, + 43 + ] + ] + ] + }, + { + "id": 30, + "type": "cell", + "intervals": [ + [ + [ + 37, + 24, + 43 + ], + [ + 38, + 24, + 43 + ] + ], + [ + [ + 38, + 23, + 43 + ], + [ + 39, + 23, + 43 + ] + ], + [ + [ + 38, + 23, + 43 + ], + [ + 38, + 24, + 43 + ] + ], + [ + [ + 39, + 20, + 43 + ], + [ + 40, + 20, + 43 + ] + ], + [ + [ + 37, + 24, + 43 + ], + [ + 37, + 24, + 43 + ] + ], + [ + [ + 38, + 23, + 43 + ], + [ + 38, + 23, + 43 + ] + ], + [ + [ + 38, + 24, + 43 + ], + [ + 38, + 24, + 43 + ] + ], + [ + [ + 39, + 20, + 43 + ], + [ + 39, + 20, + 43 + ] + ], + [ + [ + 39, + 23, + 43 + ], + [ + 39, + 23, + 43 + ] + ], + [ + [ + 40, + 20, + 43 + ], + [ + 40, + 20, + 43 + ] + ] + ] + }, + { + "id": 31, + "type": "cell", + "intervals": [ + [ + [ + 37, + 27, + 42 + ], + [ + 37, + 28, + 42 + ] + ], + [ + [ + 37, + 27, + 42 + ], + [ + 37, + 27, + 43 + ] + ], + [ + [ + 37, + 28, + 41 + ], + [ + 38, + 28, + 41 + ] + ], + [ + [ + 37, + 28, + 41 + ], + [ + 37, + 28, + 42 + ] + ], + [ + [ + 38, + 28, + 41 + ], + [ + 38, + 29, + 41 + ] + ], + [ + [ + 37, + 27, + 42 + ], + [ + 37, + 27, + 42 + ] + ], + [ + [ + 37, + 27, + 43 + ], + [ + 37, + 27, + 43 + ] + ], + [ + [ + 37, + 28, + 41 + ], + [ + 37, + 28, + 41 + ] + ], + [ + [ + 37, + 28, + 42 + ], + [ + 37, + 28, + 42 + ] + ], + [ + [ + 38, + 28, + 41 + ], + [ + 38, + 28, + 41 + ] + ], + [ + [ + 38, + 29, + 41 + ], + [ + 38, + 29, + 41 + ] + ] + ] + }, + { + "id": 32, + "type": "cell", + "intervals": [ + [ + [ + 55, + 35, + 43 + ], + [ + 56, + 35, + 43 + ] + ], + [ + [ + 56, + 35, + 42 + ], + [ + 57, + 35, + 42 + ] + ], + [ + [ + 56, + 35, + 42 + ], + [ + 56, + 35, + 43 + ] + ], + [ + [ + 57, + 37, + 42 + ], + [ + 58, + 37, + 42 + ] + ], + [ + [ + 58, + 37, + 42 + ], + [ + 58, + 38, + 42 + ] + ], + [ + [ + 58, + 38, + 42 + ], + [ + 59, + 38, + 42 + ] + ], + [ + [ + 55, + 35, + 43 + ], + [ + 55, + 35, + 43 + ] + ], + [ + [ + 56, + 35, + 42 + ], + [ + 56, + 35, + 42 + ] + ], + [ + [ + 56, + 35, + 43 + ], + [ + 56, + 35, + 43 + ] + ], + [ + [ + 57, + 35, + 42 + ], + [ + 57, + 35, + 42 + ] + ], + [ + [ + 57, + 37, + 42 + ], + [ + 57, + 37, + 42 + ] + ], + [ + [ + 58, + 37, + 42 + ], + [ + 58, + 37, + 42 + ] + ], + [ + [ + 58, + 38, + 42 + ], + [ + 58, + 38, + 42 + ] + ], + [ + [ + 59, + 38, + 42 + ], + [ + 59, + 38, + 42 + ] + ] + ] + }, + { + "id": 33, + "type": "cell", + "intervals": [ + [ + [ + 59, + 38, + 41 + ], + [ + 59, + 38, + 42 + ] + ], + [ + [ + 63, + 37, + 41 + ], + [ + 63, + 38, + 41 + ] + ], + [ + [ + 66, + 37, + 41 + ], + [ + 66, + 37, + 42 + ] + ], + [ + [ + 59, + 38, + 41 + ], + [ + 59, + 38, + 41 + ] + ], + [ + [ + 59, + 38, + 42 + ], + [ + 59, + 38, + 42 + ] + ], + [ + [ + 63, + 37, + 41 + ], + [ + 63, + 37, + 41 + ] + ], + [ + [ + 63, + 38, + 41 + ], + [ + 63, + 38, + 41 + ] + ], + [ + [ + 66, + 37, + 41 + ], + [ + 66, + 37, + 41 + ] + ], + [ + [ + 66, + 37, + 42 + ], + [ + 66, + 37, + 42 + ] + ] + ] + }, + { + "id": 34, + "type": "cell", + "intervals": [ + [ + [ + 68, + 19, + 43 + ], + [ + 68, + 20, + 43 + ] + ], + [ + [ + 68, + 19, + 43 + ], + [ + 68, + 19, + 43 + ] + ], + [ + [ + 68, + 20, + 43 + ], + [ + 68, + 20, + 43 + ] + ] + ] + }, + { + "id": 35, + "type": "cell", + "intervals": [ + [ + [ + 70, + 19, + 43 + ], + [ + 71, + 19, + 43 + ] + ], + [ + [ + 71, + 18, + 43 + ], + [ + 72, + 18, + 43 + ] + ], + [ + [ + 71, + 18, + 43 + ], + [ + 71, + 19, + 43 + ] + ], + [ + [ + 72, + 17, + 43 + ], + [ + 72, + 18, + 43 + ] + ], + [ + [ + 70, + 19, + 43 + ], + [ + 70, + 19, + 43 + ] + ], + [ + [ + 71, + 18, + 43 + ], + [ + 71, + 18, + 43 + ] + ], + [ + [ + 71, + 19, + 43 + ], + [ + 71, + 19, + 43 + ] + ], + [ + [ + 72, + 17, + 43 + ], + [ + 72, + 17, + 43 + ] + ], + [ + [ + 72, + 18, + 43 + ], + [ + 72, + 18, + 43 + ] + ] + ] + }, + { + "id": 36, + "type": "polyline", + "coordinateIds": [ + 6, + 7, + 8, + 9, + 10, + 11, + 3 + ] + }, + { + "id": 37, + "type": "polyline", + "coordinateIds": [ + 12, + 13, + 14, + 15, + 16, + 19, + 18, + 19, + 2 + ] + }, + { + "id": 38, + "type": "polyline", + "coordinateIds": [ + 20, + 21 + ] + }, + { + "id": 39, + "type": "polyline", + "coordinateIds": [ + 5, + 22, + 23, + 24, + 25, + 26, + 27, + 28, + 29, + 30, + 31 + ] + }, + { + "id": 40, + "type": "polyline", + "coordinateIds": [ + 32, + 33, + 34, + 35, + 36, + 37, + 38 + ] + }, + { + "id": 41, + "type": "polyline", + "coordinateIds": [ + 39, + 40, + 41, + 42, + 43, + 44, + 1 + ] + }, + { + "id": 42, + "type": "polyline", + "coordinateIds": [ + 45, + 46, + 47, + 48 + ] + }, + { + "id": 43, + "type": "polyline", + "coordinateIds": [ + 49, + 50, + 51, + 52, + 53, + 54, + 55, + 56, + 57 + ] + }, + { + "id": 44, + "type": "polyline", + "coordinateIds": [ + 58, + 59, + 60, + 61, + 62, + 63, + 4 + ] + }, + { + "id": 45, + "type": "polyline", + "coordinateIds": [ + 64, + 65, + 66, + 67 + ] + }, + { + "id": 46, + "type": "polyline", + "coordinateIds": [ + 68, + 69, + 70, + 71, + 72 + ] + }, + { + "id": 47, + "type": "polyline", + "coordinateIds": [ + 73, + 74, + 75, + 76, + 77 + ] + }, + { + "id": 48, + "type": "polyline", + "coordinateIds": [ + 78, + 79, + 80, + 81, + 82 + ] + }, + { + "id": 49, + "type": "polyline", + "coordinateIds": [ + 83, + 84, + 85, + 86 + ] + }, + { + "id": 50, + "type": "polyline", + "coordinateIds": [ + 87, + 88, + 89, + 90 + ] + }, + { + "id": 51, + "type": "polyline", + "coordinateIds": [ + 91, + 92, + 93, + 94, + 95, + 96, + 97 + ] + }, + { + "id": 52, + "type": "polyline", + "coordinateIds": [ + 98, + 99, + 100, + 101, + 102, + 103, + 104 + ] + }, + { + "id": 53, + "type": "polyline", + "coordinateIds": [ + 105, + 106, + 107, + 108, + 109, + 110, + 111, + 112, + 113 + ] + }, + { + "id": 54, + "type": "polyline", + "coordinateIds": [ + 114, + 115, + 116, + 117, + 118, + 119, + 120, + 121, + 122 + ] + }, + { + "id": 55, + "type": "polyline", + "coordinateIds": [ + 123, + 124, + 125, + 126 + ] + }, + { + "id": 56, + "type": "polyline", + "coordinateIds": [ + 127, + 128, + 129, + 130 + ] + }, + { + "id": 57, + "type": "polyline", + "coordinateIds": [ + 131, + 132, + 133, + 134, + 135, + 136, + 137 + ] + }, + { + "id": 58, + "type": "polyline", + "coordinateIds": [ + 138, + 139, + 140, + 141, + 142, + 143, + 144 + ] + }, + { + "id": 59, + "type": "polyline", + "coordinateIds": [ + 145, + 146, + 147, + 148, + 149, + 150, + 151 + ] + }, + { + "id": 60, + "type": "polyline", + "coordinateIds": [ + 152, + 153, + 154, + 155, + 156, + 157, + 158 + ] + }, + { + "id": 61, + "type": "polyline", + "coordinateIds": [ + 159, + 160, + 161, + 162, + 163, + 164, + 165, + 166, + 167, + 168, + 169 + ] + }, + { + "id": 62, + "type": "polyline", + "coordinateIds": [ + 170, + 171, + 172, + 173, + 174, + 175, + 176, + 177, + 178, + 179, + 180 + ] + }, + { + "id": 63, + "type": "polyline", + "coordinateIds": [ + 181, + 182 + ] + }, + { + "id": 64, + "type": "polyline", + "coordinateIds": [ + 183, + 184 + ] + }, + { + "id": 65, + "type": "polyline", + "coordinateIds": [ + 185, + 186, + 187, + 188, + 189, + 190, + 191, + 192, + 193 + ] + }, + { + "id": 66, + "type": "polyline", + "coordinateIds": [ + 194, + 195, + 196, + 197, + 198, + 199, + 200, + 201, + 202 + ] + }, + { + "id": 67, + "type": "polyline", + "coordinateIds": [ + 203, + 204, + 205, + 206, + 207, + 208, + 209 + ] + }, + { + "id": 68, + "type": "polyline", + "coordinateIds": [ + 210, + 211, + 212, + 213, + 214, + 215, + 216 + ] + } + ] + }, + "materials": [ + { + "id": 1, + "type": "pec" + }, + { + "name": "Wirematerial", + "id": 2, + "type": "wire", + "radius": 0.001, + "resistancePerMeter": 1.68e-09, + "inductancePerMeter": 0.0 + }, + { + "name": "Terminal50Ohm", + "id": 3, + "type": "terminal", + "terminations": [ + { + "type": "series", + "resistance": 50.0, + "capacitance": 1e+22 + } + ] + }, + { + "name": "InnerMaterial_Cable000", + "id": 4, + "type": "multiwire", + "resistancePerMeter": [ + 0.0, + 0.0 + ], + "inductancePerMeter": [ + [ + 5.861760574253059e-07, + 4.438734999842879e-08 + ], + [ + 4.438496530147375e-08, + 5.861718267026432e-07 + ] + ], + "capacitancePerMeter": [ + [ + 1.9090963183548857e-11, + -1.4456465255283824e-12 + ], + [ + -1.445568858605991e-12, + 1.909110097347139e-11 + ] + ], + "conductancePerMeter": [ + 0.0, + 0.0 + ] + }, + { + "name": "InnerStartTerminal_Cable000", + "id": 5, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerEndTerminal_Cable000", + "id": 6, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerMaterial_Cable001", + "id": 7, + "type": "multiwire", + "resistancePerMeter": [ + 0.0, + 0.0 + ], + "inductancePerMeter": [ + [ + 5.861760574253059e-07, + 4.438734999842879e-08 + ], + [ + 4.438496530147375e-08, + 5.861718267026432e-07 + ] + ], + "capacitancePerMeter": [ + [ + 1.9090963183548857e-11, + -1.4456465255283824e-12 + ], + [ + -1.445568858605991e-12, + 1.909110097347139e-11 + ] + ], + "conductancePerMeter": [ + 0.0, + 0.0 + ] + }, + { + "name": "InnerStartTerminal_Cable001", + "id": 8, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerEndTerminal_Cable001", + "id": 9, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerMaterial_Cable002", + "id": 10, + "type": "multiwire", + "resistancePerMeter": [ + 0.0, + 0.0 + ], + "inductancePerMeter": [ + [ + 5.861760574253059e-07, + 4.438734999842879e-08 + ], + [ + 4.438496530147375e-08, + 5.861718267026432e-07 + ] + ], + "capacitancePerMeter": [ + [ + 1.9090963183548857e-11, + -1.4456465255283824e-12 + ], + [ + -1.445568858605991e-12, + 1.909110097347139e-11 + ] + ], + "conductancePerMeter": [ + 0.0, + 0.0 + ] + }, + { + "name": "InnerStartTerminal_Cable002", + "id": 11, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerEndTerminal_Cable002", + "id": 12, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerMaterial_Cable003", + "id": 13, + "type": "multiwire", + "resistancePerMeter": [ + 0.0, + 0.0 + ], + "inductancePerMeter": [ + [ + 5.861760574253059e-07, + 4.438734999842879e-08 + ], + [ + 4.438496530147375e-08, + 5.861718267026432e-07 + ] + ], + "capacitancePerMeter": [ + [ + 1.9090963183548857e-11, + -1.4456465255283824e-12 + ], + [ + -1.445568858605991e-12, + 1.909110097347139e-11 + ] + ], + "conductancePerMeter": [ + 0.0, + 0.0 + ] + }, + { + "name": "InnerStartTerminal_Cable003", + "id": 14, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerEndTerminal_Cable003", + "id": 15, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerMaterial_Cable004", + "id": 16, + "type": "multiwire", + "resistancePerMeter": [ + 0.0, + 0.0 + ], + "inductancePerMeter": [ + [ + 5.861760574253059e-07, + 4.438734999842879e-08 + ], + [ + 4.438496530147375e-08, + 5.861718267026432e-07 + ] + ], + "capacitancePerMeter": [ + [ + 1.9090963183548857e-11, + -1.4456465255283824e-12 + ], + [ + -1.445568858605991e-12, + 1.909110097347139e-11 + ] + ], + "conductancePerMeter": [ + 0.0, + 0.0 + ] + }, + { + "name": "InnerStartTerminal_Cable004", + "id": 17, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerEndTerminal_Cable004", + "id": 18, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerMaterial_Cable005", + "id": 19, + "type": "multiwire", + "resistancePerMeter": [ + 0.0, + 0.0 + ], + "inductancePerMeter": [ + [ + 5.861760574253059e-07, + 4.438734999842879e-08 + ], + [ + 4.438496530147375e-08, + 5.861718267026432e-07 + ] + ], + "capacitancePerMeter": [ + [ + 1.9090963183548857e-11, + -1.4456465255283824e-12 + ], + [ + -1.445568858605991e-12, + 1.909110097347139e-11 + ] + ], + "conductancePerMeter": [ + 0.0, + 0.0 + ] + }, + { + "name": "InnerStartTerminal_Cable005", + "id": 20, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerEndTerminal_Cable005", + "id": 21, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerMaterial_Cable006", + "id": 22, + "type": "multiwire", + "resistancePerMeter": [ + 0.0, + 0.0 + ], + "inductancePerMeter": [ + [ + 5.861760574253059e-07, + 4.438734999842879e-08 + ], + [ + 4.438496530147375e-08, + 5.861718267026432e-07 + ] + ], + "capacitancePerMeter": [ + [ + 1.9090963183548857e-11, + -1.4456465255283824e-12 + ], + [ + -1.445568858605991e-12, + 1.909110097347139e-11 + ] + ], + "conductancePerMeter": [ + 0.0, + 0.0 + ] + }, + { + "name": "InnerStartTerminal_Cable006", + "id": 23, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerEndTerminal_Cable006", + "id": 24, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerMaterial_Cable007", + "id": 25, + "type": "multiwire", + "resistancePerMeter": [ + 0.0, + 0.0 + ], + "inductancePerMeter": [ + [ + 5.861760574253059e-07, + 4.438734999842879e-08 + ], + [ + 4.438496530147375e-08, + 5.861718267026432e-07 + ] + ], + "capacitancePerMeter": [ + [ + 1.9090963183548857e-11, + -1.4456465255283824e-12 + ], + [ + -1.445568858605991e-12, + 1.909110097347139e-11 + ] + ], + "conductancePerMeter": [ + 0.0, + 0.0 + ] + }, + { + "name": "InnerStartTerminal_Cable007", + "id": 26, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerEndTerminal_Cable007", + "id": 27, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerMaterial_Cable008", + "id": 28, + "type": "multiwire", + "resistancePerMeter": [ + 0.0, + 0.0 + ], + "inductancePerMeter": [ + [ + 5.861760574253059e-07, + 4.438734999842879e-08 + ], + [ + 4.438496530147375e-08, + 5.861718267026432e-07 + ] + ], + "capacitancePerMeter": [ + [ + 1.9090963183548857e-11, + -1.4456465255283824e-12 + ], + [ + -1.445568858605991e-12, + 1.909110097347139e-11 + ] + ], + "conductancePerMeter": [ + 0.0, + 0.0 + ] + }, + { + "name": "InnerStartTerminal_Cable008", + "id": 29, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerEndTerminal_Cable008", + "id": 30, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerMaterial_Cable009", + "id": 31, + "type": "multiwire", + "resistancePerMeter": [ + 0.0, + 0.0 + ], + "inductancePerMeter": [ + [ + 5.861760574253059e-07, + 4.438734999842879e-08 + ], + [ + 4.438496530147375e-08, + 5.861718267026432e-07 + ] + ], + "capacitancePerMeter": [ + [ + 1.9090963183548857e-11, + -1.4456465255283824e-12 + ], + [ + -1.445568858605991e-12, + 1.909110097347139e-11 + ] + ], + "conductancePerMeter": [ + 0.0, + 0.0 + ] + }, + { + "name": "InnerStartTerminal_Cable009", + "id": 32, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerEndTerminal_Cable009", + "id": 33, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerMaterial_Cable010", + "id": 34, + "type": "multiwire", + "resistancePerMeter": [ + 0.0, + 0.0 + ], + "inductancePerMeter": [ + [ + 5.861760574253059e-07, + 4.438734999842879e-08 + ], + [ + 4.438496530147375e-08, + 5.861718267026432e-07 + ] + ], + "capacitancePerMeter": [ + [ + 1.9090963183548857e-11, + -1.4456465255283824e-12 + ], + [ + -1.445568858605991e-12, + 1.909110097347139e-11 + ] + ], + "conductancePerMeter": [ + 0.0, + 0.0 + ] + }, + { + "name": "InnerStartTerminal_Cable010", + "id": 35, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "InnerEndTerminal_Cable010", + "id": 36, + "type": "terminal", + "terminations": [ + { + "type": "short" + }, + { + "type": "short" + } + ] + }, + { + "name": "Short", + "id": 37, + "type": "terminal", + "terminations": [ + { + "type": "short" + } + ] + } + ], + "materialAssociations": [ + { + "type": "surface", + "materialId": 1, + "elementIds": [ + 7, + 8, + 9, + 10 + ] + }, + { + "name": "Cable000", + "type": "cable", + "elementIds": [ + 36 + ], + "materialId": 2, + "initialTerminalId": 3, + "endTerminalId": 37 + }, + { + "name": "Cable001", + "type": "cable", + "elementIds": [ + 37 + ], + "materialId": 2, + "initialTerminalId": 37, + "endTerminalId": 37 + }, + { + "name": "Cable002", + "type": "cable", + "elementIds": [ + 38 + ], + "materialId": 2, + "initialTerminalId": 37, + "endTerminalId": 3 + }, + { + "name": "Cable003", + "type": "cable", + "elementIds": [ + 39 + ], + "materialId": 2, + "initialTerminalId": 37, + "endTerminalId": 37 + }, + { + "name": "Cable004", + "type": "cable", + "elementIds": [ + 40 + ], + "materialId": 2, + "initialTerminalId": 37, + "endTerminalId": 37 + }, + { + "name": "Cable005", + "type": "cable", + "elementIds": [ + 41 + ], + "materialId": 2, + "initialTerminalId": 37, + "endTerminalId": 37 + }, + { + "name": "Cable006", + "type": "cable", + "elementIds": [ + 42 + ], + "materialId": 2, + "initialTerminalId": 37, + "endTerminalId": 3 + }, + { + "name": "Cable007", + "type": "cable", + "elementIds": [ + 43 + ], + "materialId": 2, + "initialTerminalId": 37, + "endTerminalId": 37 + }, + { + "name": "Cable008", + "type": "cable", + "elementIds": [ + 44 + ], + "materialId": 2, + "initialTerminalId": 37, + "endTerminalId": 37 + }, + { + "name": "Cable009", + "type": "cable", + "elementIds": [ + 45 + ], + "materialId": 2, + "initialTerminalId": 37, + "endTerminalId": 3 + }, + { + "name": "Cable010", + "type": "cable", + "elementIds": [ + 46 + ], + "materialId": 2, + "initialTerminalId": 37, + "endTerminalId": 3 + }, + { + "name": "InnerBundle_Cable010", + "type": "cable", + "elementIds": [ + 47, + 48 + ], + "materialId": 34, + "initialTerminalId": 35, + "endTerminalId": 36, + "containedWithinElementId": 46 + }, + { + "name": "InnerBundle_Cable009", + "type": "cable", + "elementIds": [ + 49, + 50 + ], + "materialId": 31, + "initialTerminalId": 32, + "endTerminalId": 33, + "containedWithinElementId": 45 + }, + { + "name": "InnerBundle_Cable008", + "type": "cable", + "elementIds": [ + 51, + 52 + ], + "materialId": 28, + "initialTerminalId": 29, + "endTerminalId": 30, + "containedWithinElementId": 44 + }, + { + "name": "InnerBundle_Cable007", + "type": "cable", + "elementIds": [ + 53, + 54 + ], + "materialId": 25, + "initialTerminalId": 26, + "endTerminalId": 27, + "containedWithinElementId": 43 + }, + { + "name": "InnerBundle_Cable006", + "type": "cable", + "elementIds": [ + 55, + 56 + ], + "materialId": 22, + "initialTerminalId": 23, + "endTerminalId": 24, + "containedWithinElementId": 42 + }, + { + "name": "InnerBundle_Cable005", + "type": "cable", + "elementIds": [ + 57, + 58 + ], + "materialId": 19, + "initialTerminalId": 20, + "endTerminalId": 21, + "containedWithinElementId": 41 + }, + { + "name": "InnerBundle_Cable004", + "type": "cable", + "elementIds": [ + 59, + 60 + ], + "materialId": 16, + "initialTerminalId": 17, + "endTerminalId": 18, + "containedWithinElementId": 40 + }, + { + "name": "InnerBundle_Cable003", + "type": "cable", + "elementIds": [ + 61, + 62 + ], + "materialId": 13, + "initialTerminalId": 14, + "endTerminalId": 15, + "containedWithinElementId": 39 + }, + { + "name": "InnerBundle_Cable002", + "type": "cable", + "elementIds": [ + 63, + 64 + ], + "materialId": 10, + "initialTerminalId": 11, + "endTerminalId": 12, + "containedWithinElementId": 38 + }, + { + "name": "InnerBundle_Cable001", + "type": "cable", + "elementIds": [ + 65, + 66 + ], + "materialId": 7, + "initialTerminalId": 8, + "endTerminalId": 9, + "containedWithinElementId": 37 + }, + { + "name": "InnerBundle_Cable000", + "type": "cable", + "elementIds": [ + 67, + 68 + ], + "materialId": 4, + "initialTerminalId": 5, + "endTerminalId": 6, + "containedWithinElementId": 36 + } + ], + "sources": [ + { + "type": "planewave", + "magnitudeFile": "predefinedExcitation.1.exc", + "elementIds": [ + 1 + ], + "direction": { + "theta": 0.7853981634, + "phi": 1.5707963268 + }, + "polarization": { + "theta": 1.5707963268, + "phi": 0.0 + } + } + ], + "probes": [ + { + "name": "Nose Probe", + "type": "point", + "field": "electric", + "elementIds": [ + 6 + ], + "directions": [ + "x", + "y", + "z" + ], + "domain": { + "type": "time" + } + }, + { + "name": "Board Probe", + "type": "point", + "field": "electric", + "elementIds": [ + 2 + ], + "directions": [ + "x", + "y", + "z" + ], + "domain": { + "type": "time" + } + }, + { + "name": "Light Probe", + "type": "point", + "field": "electric", + "elementIds": [ + 5 + ], + "directions": [ + "x", + "y", + "z" + ], + "domain": { + "type": "time" + } + }, + { + "name": "Float Probe", + "type": "point", + "field": "electric", + "elementIds": [ + 3 + ], + "directions": [ + "x", + "y", + "z" + ], + "domain": { + "type": "time" + } + }, + { + "name": "Floor Probe", + "type": "point", + "field": "electric", + "elementIds": [ + 4 + ], + "directions": [ + "x", + "y", + "z" + ], + "domain": { + "type": "time" + } + } + ] +} \ No newline at end of file diff --git a/testData/cases/sphere.fdtd.json b/testData/cases/sphere.fdtd.json index 72172030..3f306146 100644 --- a/testData/cases/sphere.fdtd.json +++ b/testData/cases/sphere.fdtd.json @@ -40956,7 +40956,7 @@ "name": "electric_field_movie", "type": "movie", "field": "electric", - "components": ["x"], + "component": "x", "elementIds": [2], "domain": { "type": "time",