New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 14975 – NEMO

Changeset 14975


Ignore:
Timestamp:
2021-06-11T11:05:32+02:00 (3 years ago)
Author:
jchanut
Message:

#2638, merge new AGRIF library into trunk

Location:
vendors/AGRIF/dev
Files:
13 edited

Legend:

Unmodified
Added
Removed
  • vendors/AGRIF/dev/AGRIF_FILES/modarrays.F90

    r14107 r14975  
    195195 
    196196    if (present(pvariable)) then 
     197      lower=-1 
     198      upper=-1 
    197199     if (variable%root_var%interptab(index) == 'N') then 
    198200        lower = pvariable%lb(index) 
    199201        upper = pvariable%ub(index) 
     202      else 
     203       lower = variable % lb(index) 
     204       upper = variable % ub(index) 
    200205      endif 
    201206    else 
     
    703708    integer, dimension(6), intent(out)          :: lb_child     !< Lower bound on the child grid 
    704709    integer, dimension(6), intent(out)          :: lb_parent    !< Lower bound on the parent grid 
    705     real, dimension(6),    intent(out)          :: s_child      !< Child  grid position (s_root = 0) 
    706     real, dimension(6),    intent(out)          :: s_parent     !< Parent grid position (s_root = 0) 
    707     real, dimension(6),    intent(out)          :: ds_child     !< Child  grid dx (ds_root = 1) 
    708     real, dimension(6),    intent(out)          :: ds_parent    !< Parent grid dx (ds_root = 1) 
     710    real(kind=8), dimension(6),    intent(out)  :: s_child      !< Child  grid position (s_root = 0) 
     711    real(kind=8), dimension(6),    intent(out)  :: s_parent     !< Parent grid position (s_root = 0) 
     712    real(kind=8), dimension(6),    intent(out)  :: ds_child     !< Child  grid dx (ds_root = 1) 
     713    real(kind=8), dimension(6),    intent(out)  :: ds_parent    !< Parent grid dx (ds_root = 1) 
    709714    integer,               intent(out)          :: nbdim        !< Number of dimensions 
    710715    logical,               intent(in)           :: interp       !< .true. if preprocess for interpolation, \n 
     
    739744            ds_parent(n) = Agrif_Parent_Gr % Agrif_dx(1) 
    740745            ! Take into account potential difference of first points 
    741             s_parent(n) = s_parent(n) + (lb_parent(n)-lb_child(n))*ds_parent(n) 
     746           ! s_parent(n) = s_parent(n) + (lb_parent(n)-lb_child(n))*ds_parent(n) 
    742747! 
    743748            if ( root_var % posvar(n) == 1 ) then 
     
    745750            else 
    746751                ub_child(n) = lb_child(n) + Agrif_Child_Gr % nb(1) - 1 
    747                 s_child(n)  = s_child(n)  + 0.5*ds_child(n) 
    748                 s_parent(n) = s_parent(n) + 0.5*ds_parent(n) 
     752                s_child(n)  = s_child(n)  + 0.5d0*ds_child(n) 
     753                s_parent(n) = s_parent(n) + 0.5d0*ds_parent(n) 
    749754            endif 
    750755! 
     
    759764            ds_parent(n) = Agrif_Parent_Gr % Agrif_dx(2) 
    760765            ! Take into account potential difference of first points 
    761             s_parent(n) = s_parent(n) + (lb_parent(n)-lb_child(n))*ds_parent(n) 
     766           ! s_parent(n) = s_parent(n) + (lb_parent(n)-lb_child(n))*ds_parent(n) 
    762767! 
    763768            if (root_var % posvar(n)==1) then 
     
    765770            else 
    766771                ub_child(n) = lb_child(n) + Agrif_Child_Gr % nb(2) - 1 
    767                 s_child(n)  = s_child(n)  + 0.5*ds_child(n) 
    768                 s_parent(n) = s_parent(n) + 0.5*ds_parent(n) 
     772                s_child(n)  = s_child(n)  + 0.5d0*ds_child(n) 
     773                s_parent(n) = s_parent(n) + 0.5d0*ds_parent(n) 
    769774            endif 
    770775! 
     
    779784            ds_parent(n) = Agrif_Parent_Gr % Agrif_dx(3) 
    780785            ! Take into account potential difference of first points 
    781             s_parent(n) = s_parent(n) + (lb_parent(n)-lb_child(n))*ds_parent(n) 
     786           ! s_parent(n) = s_parent(n) + (lb_parent(n)-lb_child(n))*ds_parent(n) 
    782787! 
    783788            if (root_var % posvar(n)==1) then 
     
    805810!           No interpolation but only a copy of the values of the grid variable 
    806811            lb_parent(n) = lb_child(n) 
    807             s_child(n)   = 0. 
    808             s_parent(n)  = 0. 
    809             ds_child(n)  = 1. 
    810             ds_parent(n) = 1. 
     812            s_child(n)   = 0.d0 
     813            s_parent(n)  = 0.d0 
     814            ds_child(n)  = 1.d0 
     815            ds_parent(n) = 1.d0 
    811816! 
    812817        end select 
  • vendors/AGRIF/dev/AGRIF_FILES/modbc.F90

    r14107 r14975  
    6161    integer, dimension(6)  :: loctab_child      ! Indicates if the child grid has a common border 
    6262                                                !    with the root grid 
    63     real, dimension(6)     :: s_child, s_parent   ! Positions of the parent and child grids 
    64     real, dimension(6)     :: ds_child, ds_parent ! Space steps of the parent and child grids 
     63    real(kind=8), dimension(6)     :: s_child, s_parent   ! Positions of the parent and child grids 
     64    real(kind=8), dimension(6)     :: ds_child, ds_parent ! Space steps of the parent and child grids 
    6565! 
    6666    call PreProcessToInterpOrUpdate( parent,   child,       & 
     
    145145    INTEGER, DIMENSION(nbdim)   :: posvartab_Child      !< Position of the grid variable (1 or 2) 
    146146    INTEGER, DIMENSION(nbdim)   :: loctab_Child         !< Indicates if the child grid has a common border with the root grid 
    147     REAL   , DIMENSION(nbdim)   :: s_Child,  s_Parent   !< Positions of the parent and child grids 
    148     REAL   , DIMENSION(nbdim)   :: ds_Child, ds_Parent  !< Space steps of the parent and child grids 
     147    REAL(kind=8)   , DIMENSION(nbdim)   :: s_Child,  s_Parent   !< Positions of the parent and child grids 
     148    REAL(kind=8)   , DIMENSION(nbdim)   :: ds_Child, ds_Parent  !< Space steps of the parent and child grids 
    149149    INTEGER                             :: nbdim        !< Number of dimensions of the grid variable 
    150150    procedure()                         :: procname     !< Data recovery procedure 
  • vendors/AGRIF/dev/AGRIF_FILES/modbcfunction.F90

    r14107 r14975  
    3030    use Agrif_Update 
    3131    use Agrif_Save 
     32    use Agrif_Arrays 
    3233! 
    3334    implicit none 
     
    431432end subroutine Agrif_Bc_variable 
    432433!=================================================================================================== 
     434!=================================================================================================== 
     435!  subroutine Agrif_Find_Nearest : find nearest point on the parent grid 
     436!--------------------------------------------------------------------------------------------------- 
     437subroutine Agrif_Find_Nearest ( tabvarsindic, fineloc, parentloc ) 
     438!--------------------------------------------------------------------------------------------------- 
     439    integer,        intent(in) :: tabvarsindic     !< indice of the variable in tabvars 
     440    integer,dimension(:), intent(in)    :: fineloc 
     441    integer,dimension(:,:), intent(out) :: parentloc 
     442 
     443! 
     444 
     445    integer :: indic 
     446 
     447    type(Agrif_Variable), pointer :: parent_var 
     448    type(Agrif_Variable), pointer :: child_var 
     449    integer :: i 
     450    integer, dimension(6)           :: nb_child     !< Number of cells on the child grid 
     451    integer, dimension(6)           :: ub_child     !< Upper bound on the child grid 
     452    integer, dimension(6)           :: lb_child     !< Lower bound on the child grid 
     453    integer, dimension(6)           :: lb_parent    !< Lower bound on the parent grid 
     454    real, dimension(6)              :: s_child      !< Child  grid position (s_root = 0) 
     455    real, dimension(6)              :: s_parent     !< Parent grid position (s_root = 0) 
     456    real, dimension(6)              :: ds_child     !< Child  grid dx (ds_root = 1) 
     457    real, dimension(6)              :: ds_parent    !< Parent grid dx (ds_root = 1) 
     458    integer                         :: nbdim        !< Number of dimensions 
     459    real, dimension(6) :: xfineloc 
     460! 
     461    if ( Agrif_Curgrid%level <= 0 ) return 
     462! 
     463! 
     464! 
     465        child_var  => Agrif_Search_Variable(Agrif_Curgrid,tabvarsindic) 
     466        parent_var => child_var % parent_var 
     467! 
     468 
     469    call PreProcessToInterpOrUpdate( parent_var,   child_var,       & 
     470                                     nb_child, ub_child,    & 
     471                                     lb_child, lb_parent,   & 
     472                                      s_child,  s_parent,   & 
     473                                     ds_child, ds_parent, nbdim, interp=.true.) 
     474 
     475    do i=1,nbdim 
     476      xfineloc(i) = s_Child(i) + (fineloc(i) - lb_Child(i)) * ds_Child(i) 
     477 
     478      parentloc(1,i) = lb_parent(i) + agrif_int((xfineloc(i)-s_Parent(i))/ds_Parent(i)) 
     479      parentloc(2,i) = lb_parent(i) + agrif_ceiling((xfineloc(i)-s_Parent(i))/ds_Parent(i)) 
     480    enddo  
     481! 
     482!--------------------------------------------------------------------------------------------------- 
     483end subroutine Agrif_Find_Nearest 
     484!=================================================================================================== 
    433485! 
    434486!=================================================================================================== 
  • vendors/AGRIF/dev/AGRIF_FILES/modcluster.F90

    r5656 r14975  
    5454    TYPE(Agrif_LRectangle), pointer  :: parcours 
    5555    TYPE(Agrif_Grid)      , pointer  :: newgrid 
    56     REAL                             :: g_eps 
     56    REAL(kind=8)                     :: g_eps 
    5757    INTEGER                          :: i 
    5858! 
     
    131131    TYPE(Agrif_PGrid), pointer  :: parcours 
    132132! 
    133     REAL                  :: g_eps, newgrid_eps, eps 
    134     REAL   , DIMENSION(3) :: newmin, newmax 
    135     REAL   , DIMENSION(3) :: gmin, gmax 
    136     REAL   , DIMENSION(3) :: xmin 
     133    REAL(kind=8)                  :: g_eps, newgrid_eps, eps 
     134    REAL(kind=8)   , DIMENSION(3) :: newmin, newmax 
     135    REAL(kind=8)   , DIMENSION(3) :: gmin, gmax 
     136    REAL(kind=8)   , DIMENSION(3) :: xmin 
    137137    INTEGER, DIMENSION(3) :: igmin, inewmin 
    138138    INTEGER, DIMENSION(3) :: inewmax 
  • vendors/AGRIF/dev/AGRIF_FILES/modgrids.F90

    r14107 r14975  
    4444    type(Agrif_Variable_i), dimension(:), allocatable :: tabvars_i  !< List of integer   grid variables 
    4545! 
    46     real   , dimension(3)              :: Agrif_x   !< global x, y and z position 
    47     real   , dimension(3)              :: Agrif_dx  !< global space step in the x, y and z direction 
     46    real(kind=8), dimension(3)         :: Agrif_x   !< global x, y and z position 
     47    real(kind=8)   , dimension(3)      :: Agrif_dx  !< global space step in the x, y and z direction 
    4848    real   , dimension(3)              :: Agrif_dt  !< global time  step in the x, y and z direction 
    4949    integer, dimension(3)              :: nb = 1    !< number of cells in the x, y and z direction 
  • vendors/AGRIF/dev/AGRIF_FILES/modinterp.F90

    r14107 r14975  
    6666    integer, dimension(6) :: ub_child 
    6767    integer, dimension(6) :: lb_parent 
    68     real   , dimension(6) :: s_child,   s_parent 
    69     real   , dimension(6) :: ds_child, ds_parent 
     68    real(kind=8)   , dimension(6) :: s_child,   s_parent 
     69    real(kind=8)   , dimension(6) :: ds_child, ds_parent 
    7070    integer, dimension(child % root_var % nbdim,2,2) :: childarray 
    7171! 
     
    115115    INTEGER, DIMENSION(nbdim), INTENT(in)   :: pttab_Parent !< Index of the first point inside the domain 
    116116                                                            !<    for the parent grid variable 
    117     REAL,    DIMENSION(nbdim), INTENT(in)   :: s_Child,s_Parent   !< Positions of the parent and child grids 
    118     REAL,    DIMENSION(nbdim), INTENT(in)   :: ds_Child,ds_Parent !< Space steps of the parent and child grids 
     117    REAL(kind=8),    DIMENSION(nbdim), INTENT(in)   :: s_Child,s_Parent   !< Positions of the parent and child grids 
     118    REAL(kind=8),    DIMENSION(nbdim), INTENT(in)   :: ds_Child,ds_Parent !< Space steps of the parent and child grids 
    119119    TYPE(Agrif_Variable),      pointer      :: restore            !< Indicates points where interpolation 
    120120    LOGICAL,                   INTENT(in)   :: torestore          !< Indicates if the array restore is used 
     
    139139#endif 
    140140    LOGICAL, DIMENSION(nbdim)     :: noraftab 
    141     REAL   , DIMENSION(nbdim)     :: s_Child_temp,s_Parent_temp 
     141    REAL(kind=8)   , DIMENSION(nbdim)     :: s_Child_temp,s_Parent_temp 
    142142    INTEGER, DIMENSION(nbdim)     :: lowerbound, upperbound, coords 
    143143    INTEGER, DIMENSION(nbdim,2,2), INTENT(OUT) :: childarray 
     
    608608    Agrif_CurChildgrid=>Agrif_Curgrid 
    609609    call Agrif_ChildGrid_to_ParentGrid() 
     610 
     611 
    610612    do i=1,nb_chunks 
    611613    if (agrif_debug_interp) then 
    612614    print *,'PROCNAME POUR CHUCNK ',i 
    613615    endif 
    614  
     616     
    615617    if (member_chuncks(i)) then 
    616618        select case (nbdim) 
     
    13031305    INTEGER,                   intent(in)  :: nbdim 
    13041306    INTEGER, DIMENSION(nbdim), intent(out) :: indmin, indmax 
    1305     REAL,    DIMENSION(nbdim), intent(out) :: s_Parent_temp, s_child_temp 
    1306     REAL,    DIMENSION(nbdim), intent(in)  :: s_Child, ds_child 
    1307     REAL,    DIMENSION(nbdim), intent(in)  :: s_Parent,ds_Parent 
     1307    REAL(kind=8),    DIMENSION(nbdim), intent(out) :: s_Parent_temp, s_child_temp 
     1308    REAL(kind=8),    DIMENSION(nbdim), intent(in)  :: s_Child, ds_child 
     1309    REAL(kind=8),    DIMENSION(nbdim), intent(in)  :: s_Parent,ds_Parent 
    13081310    INTEGER, DIMENSION(nbdim), intent(in)  :: pttruetab, cetruetab 
    13091311    INTEGER, DIMENSION(nbdim), intent(in)  :: pttab_Child, pttab_Parent 
     
    13121314! 
    13131315    INTEGER :: i 
    1314     REAL,DIMENSION(nbdim) :: dim_newmin, dim_newmax 
     1316    REAL(kind=8),DIMENSION(nbdim) :: dim_newmin, dim_newmax 
    13151317! 
    13161318    dim_newmin = s_Child + (pttruetab - pttab_Child) * ds_Child 
     
    13801382    integer,            intent(in)  :: indmin, indmax 
    13811383    integer,            intent(in)  :: pttab_child, petab_child 
    1382     real,               intent(in)  :: s_child, s_parent 
    1383     real,               intent(in)  :: ds_child, ds_parent 
     1384    real(kind=8),               intent(in)  :: s_child, s_parent 
     1385    real(kind=8),               intent(in)  :: ds_child, ds_parent 
    13841386    real, dimension(            & 
    13851387        indmin:indmax           & 
     
    14151417    integer, dimension(2),              intent(in)  :: indmin, indmax 
    14161418    integer, dimension(2),              intent(in)  :: pttab_child, petab_child 
    1417     real,    dimension(2),              intent(in)  :: s_child, s_parent 
    1418     real,    dimension(2),              intent(in)  :: ds_child, ds_parent 
     1419    real(kind=8),    dimension(2),              intent(in)  :: s_child, s_parent 
     1420    real(kind=8),    dimension(2),              intent(in)  :: ds_child, ds_parent 
    14191421    real,    dimension(                 & 
    14201422        indmin(1):indmax(1),            & 
     
    15341536    integer, dimension(3),              intent(in)  :: indmin, indmax 
    15351537    integer, dimension(3),              intent(in)  :: pttab_child, petab_child 
    1536     real,    dimension(3),              intent(in)  :: s_child, s_parent 
    1537     real,    dimension(3),              intent(in)  :: ds_child, ds_parent 
     1538    real(kind=8),    dimension(3),              intent(in)  :: s_child, s_parent 
     1539    real(kind=8),    dimension(3),              intent(in)  :: ds_child, ds_parent 
    15381540    real,    dimension(                 & 
    15391541        indmin(1):indmax(1),            & 
     
    16411643    integer, dimension(4),              intent(in)  :: indmin, indmax 
    16421644    integer, dimension(4),              intent(in)  :: pttab_child, petab_child 
    1643     real,    dimension(4),              intent(in)  :: s_child, s_parent 
    1644     real,    dimension(4),              intent(in)  :: ds_child, ds_parent 
     1645    real(kind=8),    dimension(4),              intent(in)  :: s_child, s_parent 
     1646    real(kind=8),    dimension(4),              intent(in)  :: ds_child, ds_parent 
    16451647    real,    dimension(                 & 
    16461648        indmin(1):indmax(1),            & 
     
    17071709    integer, dimension(5),              intent(in)  :: indmin, indmax 
    17081710    integer, dimension(5),              intent(in)  :: pttab_child, petab_child 
    1709     real,    dimension(5),              intent(in)  :: s_child, s_parent 
    1710     real,    dimension(5),              intent(in)  :: ds_child, ds_parent 
     1711    real(kind=8),    dimension(5),              intent(in)  :: s_child, s_parent 
     1712    real(kind=8),    dimension(5),              intent(in)  :: ds_child, ds_parent 
    17111713    real,    dimension(                 & 
    17121714        indmin(1):indmax(1),            & 
     
    17801782    integer, dimension(6),                  intent(in)  :: indmin, indmax 
    17811783    integer, dimension(6),                  intent(in)  :: pttab_child, petab_child 
    1782     real,    dimension(6),                  intent(in)  :: s_child, s_parent 
    1783     real,    dimension(6),                  intent(in)  :: ds_child, ds_parent 
     1784    real(kind=8),    dimension(6),                  intent(in)  :: s_child, s_parent 
     1785    real(kind=8),    dimension(6),                  intent(in)  :: ds_child, ds_parent 
    17841786    real,    dimension(                 & 
    17851787        indmin(1):indmax(1),            & 
     
    18591861    REAL, DIMENSION(indmin:indmax),           INTENT(IN)    :: parenttab 
    18601862    REAL, DIMENSION(pttab_child:petab_child), INTENT(OUT)   :: childtab 
    1861     REAL                                                    :: s_parent, s_child 
    1862     REAL                                                    :: ds_parent,ds_child 
     1863    REAL(kind=8)                                            :: s_parent, s_child 
     1864    REAL(kind=8)                                            :: ds_parent,ds_child 
    18631865! 
    18641866    if ( (indmin == indmax) .and. (pttab_child == petab_child) ) then 
  • vendors/AGRIF/dev/AGRIF_FILES/modsauv.F90

    r12420 r14975  
    251251! 
    252252    type(Agrif_PGrid), pointer  :: parcours ! Pointer for the recursive procedure 
    253     real    :: g_eps, eps, oldgrid_eps 
     253    real(kind=8)    :: g_eps, eps, oldgrid_eps 
    254254    integer :: out 
    255255    integer :: iii 
     
    332332! 
    333333    type(Agrif_PGrid), pointer  :: parcours ! Pointer for the recursive procedure 
    334     real    :: g_eps,eps,oldgrid_eps 
     334    real(kind=8)    :: g_eps,eps,oldgrid_eps 
    335335    integer :: out 
    336336    integer :: iii 
     
    416416    integer, dimension(6) :: nbtabold  ! Number of cells in each direction 
    417417    integer, dimension(6) :: nbtabnew  ! Number of cells in each direction 
    418     real,    dimension(6) :: snew,sold 
    419     real,    dimension(6) :: dsnew,dsold 
    420     real    :: eps 
     418    real(kind=8),    dimension(6) :: snew,sold 
     419    real(kind=8),    dimension(6) :: dsnew,dsold 
     420    real(kind=8)    :: eps 
    421421    integer :: n 
    422422! 
     
    532532    integer, dimension(nbdim),     intent(in)    :: pttabold 
    533533    integer, dimension(nbdim),     intent(in)    :: petabold 
    534     real,    dimension(nbdim),     intent(in)    :: snew, sold 
    535     real,    dimension(nbdim),     intent(in)    :: dsnew,dsold 
     534    real(kind=8),    dimension(nbdim),     intent(in)    :: snew, sold 
     535    real(kind=8),    dimension(nbdim),     intent(in)    :: dsnew,dsold 
    536536    integer,                       intent(in)    :: nbdim 
    537537! 
    538538    integer :: i,j,k,l,m,n,i0,j0,k0,l0,m0,n0 
    539539! 
    540     real,    dimension(nbdim) :: dim_gmin,   dim_gmax 
    541     real,    dimension(nbdim) :: dim_newmin, dim_newmax 
    542     real,    dimension(nbdim) :: dim_min 
     540    real(kind=8),    dimension(nbdim) :: dim_gmin,   dim_gmax 
     541    real(kind=8),    dimension(nbdim) :: dim_newmin, dim_newmax 
     542    real(kind=8),    dimension(nbdim) :: dim_min 
    543543    integer, dimension(nbdim) :: ind_gmin,ind_newmin, ind_newmax 
    544544! 
  • vendors/AGRIF/dev/AGRIF_FILES/modtypes.F90

    r14107 r14975  
    380380    real                  :: Agrif_Efficiency = 0.7 
    381381    integer               :: MaxSearch = 5 
    382     real, dimension(3)    :: Agrif_mind 
     382    real(kind=8), dimension(3)    :: Agrif_mind 
    383383!> @} 
    384384!> \name parameters for the interpolation of the child grids 
     
    467467integer function Agrif_Ceiling ( x ) 
    468468!--------------------------------------------------------------------------------------------------- 
    469     real,   intent(in) :: x 
     469    real(kind=8),intent(in) :: x 
    470470! 
    471471    integer   :: i 
     
    487487    integer function Agrif_Int(x) 
    488488!--------------------------------------------------------------------------------------------------- 
    489     real,   intent(in) :: x 
     489    real(kind=8),intent(in) :: x 
    490490! 
    491491    integer :: i 
  • vendors/AGRIF/dev/AGRIF_FILES/modupdate.F90

    r14107 r14975  
    5858    integer, dimension(6) :: ub_child 
    5959    integer, dimension(6) :: lb_parent 
    60     real   , dimension(6) ::  s_child           ! Child  grid position (s_root = 0) 
    61     real   , dimension(6) ::  s_parent          ! Parent grid position (s_root = 0) 
    62     real   , dimension(6) :: ds_child           ! Child  grid dx (ds_root = 1) 
    63     real   , dimension(6) :: ds_parent          ! Parent grid dx (ds_root = 1) 
     60    real(kind=8)   , dimension(6) ::  s_child           ! Child  grid position (s_root = 0) 
     61    real(kind=8)   , dimension(6) ::  s_parent          ! Parent grid position (s_root = 0) 
     62    real(kind=8)   , dimension(6) :: ds_child           ! Child  grid dx (ds_root = 1) 
     63    real(kind=8)   , dimension(6) :: ds_parent          ! Parent grid dx (ds_root = 1) 
    6464    logical, dimension(6) :: do_update          ! Indicates if we perform update for each dimension 
    6565    integer, dimension(6) :: posvar             ! Position of the variable on the cell (1 or 2) 
     
    160160    integer, dimension(nbdim), intent(in) :: posvar         !< Position of the variable on the cell (1 or 2) 
    161161    logical, dimension(nbdim), intent(in) :: do_update      !< Indicates if we update for each dimension 
    162     real,    dimension(nbdim), intent(in) :: s_child        !< Positions of the child grid 
    163     real,    dimension(nbdim), intent(in) :: s_parent       !< Positions of the parent grid 
    164     real,    dimension(nbdim), intent(in) :: ds_child       !< Space steps of the child grid 
    165     real,    dimension(nbdim), intent(in) :: ds_parent      !< Space steps of the parent grid 
     162    real(kind=8),    dimension(nbdim), intent(in) :: s_child        !< Positions of the child grid 
     163    real(kind=8),    dimension(nbdim), intent(in) :: s_parent       !< Positions of the parent grid 
     164    real(kind=8),    dimension(nbdim), intent(in) :: ds_child       !< Space steps of the child grid 
     165    real(kind=8),    dimension(nbdim), intent(in) :: ds_parent      !< Space steps of the parent grid 
    166166    procedure()                           :: procname       !< Data recovery procedure 
    167167! 
     
    274274    integer, dimension(nbdim), intent(in)   :: posvar       !< Position of the variable on the cell (1 or 2) 
    275275    logical, dimension(nbdim), intent(in)   :: do_update    !< Indicates if we update for each dimension 
    276     real,    dimension(nbdim), intent(in)   :: s_child      !< Positions of the child grid 
    277     real,    dimension(nbdim), intent(in)   :: s_parent     !< Positions of the parent grid 
    278     real,    dimension(nbdim), intent(in)   :: ds_child     !< Space steps of the child grid 
    279     real,    dimension(nbdim), intent(in)   :: ds_parent    !< Space steps of the parent grid 
     276    real(kind=8),    dimension(nbdim), intent(in)   :: s_child      !< Positions of the child grid 
     277    real(kind=8),    dimension(nbdim), intent(in)   :: s_parent     !< Positions of the parent grid 
     278    real(kind=8),    dimension(nbdim), intent(in)   :: ds_child     !< Space steps of the child grid 
     279    real(kind=8),    dimension(nbdim), intent(in)   :: ds_parent    !< Space steps of the parent grid 
    280280    procedure()                             :: procname     !< Data recovery procedure 
    281281    integer, dimension(6)  :: loctab_child      ! Indicates if the child grid has a common border 
     
    444444    integer, dimension(nbdim), intent(in)   :: lb_parent !< Index of the first point inside the domain for the parent 
    445445                                                            !!    grid variable 
    446     real,    dimension(nbdim), intent(in)   :: s_child      !< Positions of the child grid 
    447     real,    dimension(nbdim), intent(in)   :: s_parent     !< Positions of the parent grid 
    448     real,    dimension(nbdim), intent(in)   :: ds_child     !< Space steps of the child grid 
    449     real,    dimension(nbdim), intent(in)   :: ds_parent    !< Space steps of the parent grid 
     446    real(kind=8),    dimension(nbdim), intent(in)   :: s_child      !< Positions of the child grid 
     447    real(kind=8),    dimension(nbdim), intent(in)   :: s_parent     !< Positions of the parent grid 
     448    real(kind=8),    dimension(nbdim), intent(in)   :: ds_child     !< Space steps of the child grid 
     449    real(kind=8),    dimension(nbdim), intent(in)   :: ds_parent    !< Space steps of the parent grid 
    450450    procedure()                             :: procname     !< Data recovery procedure 
    451451    integer, optional,         intent(in)   :: nb, ndir 
     
    459459    integer, dimension(nbdim)       :: indmin, indmax 
    460460    integer, dimension(nbdim)       :: indminglob, indmaxglob 
    461     real   , dimension(nbdim)       :: s_Child_temp, s_Parent_temp 
     461    real(kind=8)   , dimension(nbdim)       :: s_Child_temp, s_Parent_temp 
    462462    integer, dimension(nbdim)       :: lowerbound,upperbound 
    463463    integer, dimension(nbdim)       :: pttruetabwhole, cetruetabwhole 
     
    17961796    integer,                   intent(in)   :: nbdim 
    17971797    integer, dimension(nbdim), intent(out)  :: indmin, indmax 
    1798     real,    dimension(nbdim), intent(out)  :: s_Parent_temp, s_Child_temp 
    1799     real,    dimension(nbdim), intent(in)   :: s_child,  ds_child 
    1800     real,    dimension(nbdim), intent(in)   :: s_parent, ds_parent 
     1798    real(kind=8),    dimension(nbdim), intent(out)  :: s_Parent_temp, s_Child_temp 
     1799    real(kind=8),    dimension(nbdim), intent(in)   :: s_child,  ds_child 
     1800    real(kind=8),    dimension(nbdim), intent(in)   :: s_parent, ds_parent 
    18011801    integer, dimension(nbdim), intent(in)   :: pttruetab, cetruetab 
    18021802    integer, dimension(nbdim), intent(in)   :: lb_child, lb_parent 
     
    18081808#endif 
    18091809! 
    1810     real,dimension(nbdim) :: dim_newmin,dim_newmax 
     1810    real(kind=8),dimension(nbdim) :: dim_newmin,dim_newmax 
    18111811    integer :: i 
    18121812#if defined AGRIF_MPI 
    1813     real    :: positionmin, positionmax 
     1813    real(kind=8)    :: positionmin, positionmax 
    18141814    integer :: imin, imax 
    18151815    integer :: coeffraf 
     
    19051905    integer,                            intent(in)  :: indmin, indmax 
    19061906    integer,                            intent(in)  :: lb_child, ub_child 
    1907     real,                               intent(in)  ::  s_child,  s_parent 
    1908     real,                               intent(in)  :: ds_child, ds_parent 
     1907    real(kind=8),                               intent(in)  ::  s_child,  s_parent 
     1908    real(kind=8),                               intent(in)  :: ds_child, ds_parent 
    19091909    real, dimension(indmin:indmax),     intent(out) :: tempP 
    19101910    real, dimension(lb_child:ub_child), intent(in)  :: tempC 
     
    19371937    integer, dimension(2),          intent(in)  :: indmin, indmax 
    19381938    integer, dimension(2),          intent(in)  :: lb_child, ub_child 
    1939     real,    dimension(2),          intent(in)  ::  s_child,  s_parent 
    1940     real,    dimension(2),          intent(in)  :: ds_child, ds_parent 
     1939    real(kind=8),    dimension(2),          intent(in)  ::  s_child,  s_parent 
     1940    real(kind=8),    dimension(2),          intent(in)  :: ds_child, ds_parent 
    19411941    real,    dimension(          & 
    19421942        indmin(1):indmax(1),     & 
  • vendors/AGRIF/dev/AGRIF_FILES/modupdatebasic.F90

    r14107 r14975  
    4949    integer,             intent(in)     :: np           !< Length of parent array 
    5050    integer,             intent(in)     :: nc           !< Length of child  array 
    51     real,                intent(in)     :: s_parent     !< Parent grid position (s_root = 0) 
    52     real,                intent(in)     :: s_child      !< Child  grid position (s_root = 0) 
    53     real,                intent(in)     :: ds_parent    !< Parent grid dx (ds_root = 1) 
    54     real,                intent(in)     :: ds_child     !< Child  grid dx (ds_root = 1) 
     51    real(kind=8),        intent(in)     :: s_parent     !< Parent grid position (s_root = 0) 
     52    real(kind=8),        intent(in)     :: s_child      !< Child  grid position (s_root = 0) 
     53    real(kind=8),        intent(in)     :: ds_parent    !< Parent grid dx (ds_root = 1) 
     54    real(kind=8),        intent(in)     :: ds_child     !< Child  grid dx (ds_root = 1) 
    5555!--------------------------------------------------------------------------------------------------- 
    5656    integer :: i, locind_child_left, coeffraf 
     
    8484    integer,             intent(in)     :: np           !< Length of parent array 
    8585    integer,             intent(in)     :: nc           !< Length of child  array 
    86     real,                intent(in)     :: s_parent     !< Parent grid position (s_root = 0) 
    87     real,                intent(in)     :: s_child      !< Child  grid position (s_root = 0) 
    88     real,                intent(in)     :: ds_parent    !< Parent grid dx (ds_root = 1) 
    89     real,                intent(in)     :: ds_child     !< Child  grid dx (ds_root = 1) 
     86    real(kind=8),        intent(in)     :: s_parent     !< Parent grid position (s_root = 0) 
     87    real(kind=8),        intent(in)     :: s_child      !< Child  grid position (s_root = 0) 
     88    real(kind=8),        intent(in)     :: ds_parent    !< Parent grid dx (ds_root = 1) 
     89    real(kind=8),        intent(in)     :: ds_child     !< Child  grid dx (ds_root = 1) 
    9090    integer,             intent(in)     :: dir          !< Direction 
    9191!--------------------------------------------------------------------------------------------------- 
     
    157157    REAL, DIMENSION(nc), intent(in)     :: y 
    158158    INTEGER,             intent(in)     :: np,nc 
    159     REAL,                intent(in)     :: s_parent,  s_child 
    160     REAL,                intent(in)     :: ds_parent, ds_child 
     159    REAL(kind=8),        intent(in)     :: s_parent,  s_child 
     160    REAL(kind=8),        intent(in)     :: ds_parent, ds_child 
    161161! 
    162162    INTEGER :: i, ii, locind_child_left, coeffraf 
    163     REAL    :: xpos, invcoeffraf 
     163    REAL(kind=8)    :: xpos 
     164    REAL ::  invcoeffraf 
    164165    INTEGER :: nbnonnuls 
    165166    INTEGER :: diffmod 
     
    294295!--------------------------------------------------------------------------------------------------- 
    295296    INTEGER, intent(in) :: nc2, np, nc 
    296     REAL,    intent(in) :: s_parent,  s_child 
    297     REAL,    intent(in) :: ds_parent, ds_child 
     297    REAL(kind=8),    intent(in) :: s_parent,  s_child 
     298    REAL(kind=8),    intent(in) :: ds_parent, ds_child 
    298299    INTEGER, intent(in) :: dir 
    299300! 
    300301    INTEGER, DIMENSION(:,:), ALLOCATABLE :: indchildaverage_tmp 
    301302    INTEGER :: i, locind_child_left, coeffraf 
    302     REAL    :: xpos 
     303    REAL(kind=8)    :: xpos 
    303304    INTEGER :: diffmod 
    304305! 
     
    346347    REAL, DIMENSION(nc), intent(in)     :: y 
    347348    INTEGER,             intent(in)     :: np, nc 
    348     REAL,                intent(in)     :: s_parent,  s_child 
    349     REAL,                intent(in)     :: ds_parent, ds_child 
     349    REAL(kind=8),                intent(in)     :: s_parent,  s_child 
     350    REAL(kind=8),                intent(in)     :: ds_parent, ds_child 
    350351    INTEGER,             intent(in)     :: dir 
    351352! 
     
    403404    real, dimension(nc), intent(in)     :: y 
    404405    integer,             intent(in)     :: np, nc 
    405     real,                intent(in)     :: s_parent,  s_child 
    406     real,                intent(in)     :: ds_parent, ds_child 
    407 !--------------------------------------------------------------------------------------------------- 
    408     REAL    :: xpos, xposfin 
     406    real(kind=8),                intent(in)     :: s_parent,  s_child 
     407    real(kind=8),                intent(in)     :: ds_parent, ds_child 
     408!--------------------------------------------------------------------------------------------------- 
     409    REAL(kind=8)    :: xpos, xposfin 
    409410    INTEGER :: i, ii, diffmod 
    410411    INTEGER :: it1, it2 
  • vendors/AGRIF/dev/LEX/fortran.y

    r14431 r14975  
    37203720      | TOK_FILE file-name-expr 
    37213721      | TOK_FORM scalar-default-char-expr 
     3722      | TOK_IOMSG iomsg-variable 
    37223723      | TOK_IOSTAT scalar-int-variable 
    37233724      | TOK_POSITION scalar-default-char-expr 
     
    37463747close-spec: file-unit-number 
    37473748       | TOK_UNIT file-unit-number 
     3749       | TOK_IOMSG iomsg-variable 
    37483750       | TOK_IOSTAT scalar-int-variable 
    37493751       | TOK_ERR label 
     
    38003802         | TOK_EOR label 
    38013803         | TOK_ERR label 
     3804         | TOK_IOMSG iomsg-variable 
    38023805         | TOK_IOSTAT scalar-int-variable 
    38033806         | TOK_REC '=' scalar-int-expr 
     
    39133916     | TOK_ERR label 
    39143917     | TOK_EXIST scalar-logical-variable 
     3918     | TOK_IOMSG iomsg-variable 
    39153919     | TOK_IOSTAT scalar-int-variable 
    39163920     | TOK_NAME_EQ '=' scalar-default-char-variable 
  • vendors/AGRIF/dev/LIB/fortran.c

    r14431 r14975  
    1 /* A Bison parser, made by GNU Bison 3.0.4.  */ 
     1/* A Bison parser, made by GNU Bison 3.5.1.  */ 
    22 
    33/* Bison implementation for Yacc-like parsers in C 
    44 
    5    Copyright (C) 1984, 1989-1990, 2000-2015 Free Software Foundation, Inc. 
     5   Copyright (C) 1984, 1989-1990, 2000-2015, 2018-2020 Free Software Foundation, 
     6   Inc. 
    67 
    78   This program is free software: you can redistribute it and/or modify 
     
    4142   USER NAME SPACE" below.  */ 
    4243 
     44/* Undocumented macros, especially those whose name start with YY_, 
     45   are private implementation details.  Do not rely on them.  */ 
     46 
    4347/* Identify Bison output.  */ 
    4448#define YYBISON 1 
    4549 
    4650/* Bison version.  */ 
    47 #define YYBISON_VERSION "3.0.4" 
     51#define YYBISON_VERSION "3.5.1" 
    4852 
    4953/* Skeleton name.  */ 
     
    6670#define yydebug         fortran_debug 
    6771#define yynerrs         fortran_nerrs 
    68  
    6972#define yylval          fortran_lval 
    7073#define yychar          fortran_char 
    7174 
    72 /* Copy the first part of user declarations.  */ 
    73 #line 36 "fortran.y" /* yacc.c:339  */ 
     75/* First part of user prologue.  */ 
     76#line 36 "fortran.y" 
    7477 
    7578#define YYMAXDEPTH 1000 
     
    126129 
    127130 
    128 #line 129 "fortran.tab.c" /* yacc.c:339  */ 
    129  
     131#line 132 "fortran.tab.c" 
     132 
     133# ifndef YY_CAST 
     134#  ifdef __cplusplus 
     135#   define YY_CAST(Type, Val) static_cast<Type> (Val) 
     136#   define YY_REINTERPRET_CAST(Type, Val) reinterpret_cast<Type> (Val) 
     137#  else 
     138#   define YY_CAST(Type, Val) ((Type) (Val)) 
     139#   define YY_REINTERPRET_CAST(Type, Val) ((Type) (Val)) 
     140#  endif 
     141# endif 
    130142# ifndef YY_NULLPTR 
    131 #  if defined __cplusplus && 201103L <= __cplusplus 
    132 #   define YY_NULLPTR nullptr 
     143#  if defined __cplusplus 
     144#   if 201103L <= __cplusplus 
     145#    define YY_NULLPTR nullptr 
     146#   else 
     147#    define YY_NULLPTR 0 
     148#   endif 
    133149#  else 
    134 #   define YY_NULLPTR 0 
     150#   define YY_NULLPTR ((void*)0) 
    135151#  endif 
    136152# endif 
     
    348364/* Value type.  */ 
    349365#if ! defined YYSTYPE && ! defined YYSTYPE_IS_DECLARED 
    350  
    351366union YYSTYPE 
    352367{ 
    353 #line 91 "fortran.y" /* yacc.c:355  */ 
     368#line 91 "fortran.y" 
    354369 
    355370    char        na[LONG_M]; 
     
    361376    variable    *v; 
    362377 
    363 #line 364 "fortran.tab.c" /* yacc.c:355  */ 
     378#line 379 "fortran.tab.c" 
     379 
    364380}; 
    365  
    366381typedef union YYSTYPE YYSTYPE; 
    367382# define YYSTYPE_IS_TRIVIAL 1 
     
    376391 
    377392 
    378 /* Copy the second part of user declarations.  */ 
    379  
    380 #line 381 "fortran.tab.c" /* yacc.c:358  */ 
     393 
    381394 
    382395#ifdef short 
     
    384397#endif 
    385398 
    386 #ifdef YYTYPE_UINT8 
    387 typedef YYTYPE_UINT8 yytype_uint8; 
    388 #else 
    389 typedef unsigned char yytype_uint8; 
     399/* On compilers that do not define __PTRDIFF_MAX__ etc., make sure 
     400   <limits.h> and (if available) <stdint.h> are included 
     401   so that the code can choose integer types of a good width.  */ 
     402 
     403#ifndef __PTRDIFF_MAX__ 
     404# include <limits.h> /* INFRINGES ON USER NAME SPACE */ 
     405# if defined __STDC_VERSION__ && 199901 <= __STDC_VERSION__ 
     406#  include <stdint.h> /* INFRINGES ON USER NAME SPACE */ 
     407#  define YY_STDINT_H 
     408# endif 
    390409#endif 
    391410 
    392 #ifdef YYTYPE_INT8 
    393 typedef YYTYPE_INT8 yytype_int8; 
     411/* Narrow types that promote to a signed type and that can represent a 
     412   signed or unsigned integer of at least N bits.  In tables they can 
     413   save space and decrease cache pressure.  Promoting to a signed type 
     414   helps avoid bugs in integer arithmetic.  */ 
     415 
     416#ifdef __INT_LEAST8_MAX__ 
     417typedef __INT_LEAST8_TYPE__ yytype_int8; 
     418#elif defined YY_STDINT_H 
     419typedef int_least8_t yytype_int8; 
    394420#else 
    395421typedef signed char yytype_int8; 
    396422#endif 
    397423 
    398 #ifdef YYTYPE_UINT16 
    399 typedef YYTYPE_UINT16 yytype_uint16; 
     424#ifdef __INT_LEAST16_MAX__ 
     425typedef __INT_LEAST16_TYPE__ yytype_int16; 
     426#elif defined YY_STDINT_H 
     427typedef int_least16_t yytype_int16; 
    400428#else 
    401 typedef unsigned short int yytype_uint16; 
     429typedef short yytype_int16; 
    402430#endif 
    403431 
    404 #ifdef YYTYPE_INT16 
    405 typedef YYTYPE_INT16 yytype_int16; 
     432#if defined __UINT_LEAST8_MAX__ && __UINT_LEAST8_MAX__ <= __INT_MAX__ 
     433typedef __UINT_LEAST8_TYPE__ yytype_uint8; 
     434#elif (!defined __UINT_LEAST8_MAX__ && defined YY_STDINT_H \ 
     435       && UINT_LEAST8_MAX <= INT_MAX) 
     436typedef uint_least8_t yytype_uint8; 
     437#elif !defined __UINT_LEAST8_MAX__ && UCHAR_MAX <= INT_MAX 
     438typedef unsigned char yytype_uint8; 
    406439#else 
    407 typedef short int yytype_int16; 
     440typedef short yytype_uint8; 
     441#endif 
     442 
     443#if defined __UINT_LEAST16_MAX__ && __UINT_LEAST16_MAX__ <= __INT_MAX__ 
     444typedef __UINT_LEAST16_TYPE__ yytype_uint16; 
     445#elif (!defined __UINT_LEAST16_MAX__ && defined YY_STDINT_H \ 
     446       && UINT_LEAST16_MAX <= INT_MAX) 
     447typedef uint_least16_t yytype_uint16; 
     448#elif !defined __UINT_LEAST16_MAX__ && USHRT_MAX <= INT_MAX 
     449typedef unsigned short yytype_uint16; 
     450#else 
     451typedef int yytype_uint16; 
     452#endif 
     453 
     454#ifndef YYPTRDIFF_T 
     455# if defined __PTRDIFF_TYPE__ && defined __PTRDIFF_MAX__ 
     456#  define YYPTRDIFF_T __PTRDIFF_TYPE__ 
     457#  define YYPTRDIFF_MAXIMUM __PTRDIFF_MAX__ 
     458# elif defined PTRDIFF_MAX 
     459#  ifndef ptrdiff_t 
     460#   include <stddef.h> /* INFRINGES ON USER NAME SPACE */ 
     461#  endif 
     462#  define YYPTRDIFF_T ptrdiff_t 
     463#  define YYPTRDIFF_MAXIMUM PTRDIFF_MAX 
     464# else 
     465#  define YYPTRDIFF_T long 
     466#  define YYPTRDIFF_MAXIMUM LONG_MAX 
     467# endif 
    408468#endif 
    409469 
     
    413473# elif defined size_t 
    414474#  define YYSIZE_T size_t 
    415 # elif ! defined YYSIZE_T 
     475# elif defined __STDC_VERSION__ && 199901 <= __STDC_VERSION__ 
    416476#  include <stddef.h> /* INFRINGES ON USER NAME SPACE */ 
    417477#  define YYSIZE_T size_t 
    418478# else 
    419 #  define YYSIZE_T unsigned int 
     479#  define YYSIZE_T unsigned 
    420480# endif 
    421481#endif 
    422482 
    423 #define YYSIZE_MAXIMUM ((YYSIZE_T) -1) 
     483#define YYSIZE_MAXIMUM                                  \ 
     484  YY_CAST (YYPTRDIFF_T,                                 \ 
     485           (YYPTRDIFF_MAXIMUM < YY_CAST (YYSIZE_T, -1)  \ 
     486            ? YYPTRDIFF_MAXIMUM                         \ 
     487            : YY_CAST (YYSIZE_T, -1))) 
     488 
     489#define YYSIZEOF(X) YY_CAST (YYPTRDIFF_T, sizeof (X)) 
     490 
     491/* Stored state numbers (used for stacks). */ 
     492typedef yytype_int16 yy_state_t; 
     493 
     494/* State numbers in computations.  */ 
     495typedef int yy_state_fast_t; 
    424496 
    425497#ifndef YY_ 
     
    435507#endif 
    436508 
    437 #ifndef YY_ATTRIBUTE 
    438 # if (defined __GNUC__                                               \ 
    439       && (2 < __GNUC__ || (__GNUC__ == 2 && 96 <= __GNUC_MINOR__)))  \ 
    440      || defined __SUNPRO_C && 0x5110 <= __SUNPRO_C 
    441 #  define YY_ATTRIBUTE(Spec) __attribute__(Spec) 
     509#ifndef YY_ATTRIBUTE_PURE 
     510# if defined __GNUC__ && 2 < __GNUC__ + (96 <= __GNUC_MINOR__) 
     511#  define YY_ATTRIBUTE_PURE __attribute__ ((__pure__)) 
    442512# else 
    443 #  define YY_ATTRIBUTE(Spec) /* empty */ 
     513#  define YY_ATTRIBUTE_PURE 
    444514# endif 
    445515#endif 
    446516 
    447 #ifndef YY_ATTRIBUTE_PURE 
    448 # define YY_ATTRIBUTE_PURE   YY_ATTRIBUTE ((__pure__)) 
    449 #endif 
    450  
    451517#ifndef YY_ATTRIBUTE_UNUSED 
    452 # define YY_ATTRIBUTE_UNUSED YY_ATTRIBUTE ((__unused__)) 
    453 #endif 
    454  
    455 #if !defined _Noreturn \ 
    456      && (!defined __STDC_VERSION__ || __STDC_VERSION__ < 201112) 
    457 # if defined _MSC_VER && 1200 <= _MSC_VER 
    458 #  define _Noreturn __declspec (noreturn) 
     518# if defined __GNUC__ && 2 < __GNUC__ + (7 <= __GNUC_MINOR__) 
     519#  define YY_ATTRIBUTE_UNUSED __attribute__ ((__unused__)) 
    459520# else 
    460 #  define _Noreturn YY_ATTRIBUTE ((__noreturn__)) 
     521#  define YY_ATTRIBUTE_UNUSED 
    461522# endif 
    462523#endif 
     
    469530#endif 
    470531 
    471 #if defined __GNUC__ && 407 <= __GNUC__ * 100 + __GNUC_MINOR__ 
     532#if defined __GNUC__ && ! defined __ICC && 407 <= __GNUC__ * 100 + __GNUC_MINOR__ 
    472533/* Suppress an incorrect diagnostic about yylval being uninitialized.  */ 
    473 # define YY_IGNORE_MAYBE_UNINITIALIZED_BEGIN \ 
    474     _Pragma ("GCC diagnostic push") \ 
    475     _Pragma ("GCC diagnostic ignored \"-Wuninitialized\"")\ 
     534# define YY_IGNORE_MAYBE_UNINITIALIZED_BEGIN                            \ 
     535    _Pragma ("GCC diagnostic push")                                     \ 
     536    _Pragma ("GCC diagnostic ignored \"-Wuninitialized\"")              \ 
    476537    _Pragma ("GCC diagnostic ignored \"-Wmaybe-uninitialized\"") 
    477 # define YY_IGNORE_MAYBE_UNINITIALIZED_END \ 
     538# define YY_IGNORE_MAYBE_UNINITIALIZED_END      \ 
    478539    _Pragma ("GCC diagnostic pop") 
    479540#else 
     
    488549#endif 
    489550 
     551#if defined __cplusplus && defined __GNUC__ && ! defined __ICC && 6 <= __GNUC__ 
     552# define YY_IGNORE_USELESS_CAST_BEGIN                          \ 
     553    _Pragma ("GCC diagnostic push")                            \ 
     554    _Pragma ("GCC diagnostic ignored \"-Wuseless-cast\"") 
     555# define YY_IGNORE_USELESS_CAST_END            \ 
     556    _Pragma ("GCC diagnostic pop") 
     557#endif 
     558#ifndef YY_IGNORE_USELESS_CAST_BEGIN 
     559# define YY_IGNORE_USELESS_CAST_BEGIN 
     560# define YY_IGNORE_USELESS_CAST_END 
     561#endif 
     562 
     563 
     564#define YY_ASSERT(E) ((void) (0 && (E))) 
    490565 
    491566#if ! defined yyoverflow || YYERROR_VERBOSE 
     
    564639union yyalloc 
    565640{ 
    566   yytype_int16 yyss_alloc; 
     641  yy_state_t yyss_alloc; 
    567642  YYSTYPE yyvs_alloc; 
    568643}; 
    569644 
    570645/* The size of the maximum gap between one aligned stack and the next.  */ 
    571 # define YYSTACK_GAP_MAXIMUM (sizeof (union yyalloc) - 1) 
     646# define YYSTACK_GAP_MAXIMUM (YYSIZEOF (union yyalloc) - 1) 
    572647 
    573648/* The size of an array large to enough to hold all stacks, each with 
    574649   N elements.  */ 
    575650# define YYSTACK_BYTES(N) \ 
    576      ((N) * (sizeof (yytype_int16) + sizeof (YYSTYPE)) \ 
     651     ((N) * (YYSIZEOF (yy_state_t) + YYSIZEOF (YYSTYPE)) \ 
    577652      + YYSTACK_GAP_MAXIMUM) 
    578653 
     
    587662    do                                                                  \ 
    588663      {                                                                 \ 
    589         YYSIZE_T yynewbytes;                                            \ 
     664        YYPTRDIFF_T yynewbytes;                                         \ 
    590665        YYCOPY (&yyptr->Stack_alloc, Stack, yysize);                    \ 
    591666        Stack = &yyptr->Stack_alloc;                                    \ 
    592         yynewbytes = yystacksize * sizeof (*Stack) + YYSTACK_GAP_MAXIMUM; \ 
    593         yyptr += yynewbytes / sizeof (*yyptr);                          \ 
     667        yynewbytes = yystacksize * YYSIZEOF (*Stack) + YYSTACK_GAP_MAXIMUM; \ 
     668        yyptr += yynewbytes / YYSIZEOF (*yyptr);                        \ 
    594669      }                                                                 \ 
    595670    while (0) 
     
    603678#  if defined __GNUC__ && 1 < __GNUC__ 
    604679#   define YYCOPY(Dst, Src, Count) \ 
    605       __builtin_memcpy (Dst, Src, (Count) * sizeof (*(Src))) 
     680      __builtin_memcpy (Dst, Src, YY_CAST (YYSIZE_T, (Count)) * sizeof (*(Src))) 
    606681#  else 
    607682#   define YYCOPY(Dst, Src, Count)              \ 
    608683      do                                        \ 
    609684        {                                       \ 
    610           YYSIZE_T yyi;                         \ 
     685          YYPTRDIFF_T yyi;                      \ 
    611686          for (yyi = 0; yyi < (Count); yyi++)   \ 
    612687            (Dst)[yyi] = (Src)[yyi];            \ 
     
    620695#define YYFINAL  2 
    621696/* YYLAST -- Last index in YYTABLE.  */ 
    622 #define YYLAST   4675 
     697#define YYLAST   4842 
    623698 
    624699/* YYNTOKENS -- Number of terminals.  */ 
     
    627702#define YYNNTS  524 
    628703/* YYNRULES -- Number of rules.  */ 
    629 #define YYNRULES  1072 
     704#define YYNRULES  1076 
    630705/* YYNSTATES -- Number of states.  */ 
    631 #define YYNSTATES  1736 
    632  
    633 /* YYTRANSLATE[YYX] -- Symbol number corresponding to YYX as returned 
    634    by yylex, with out-of-bounds checking.  */ 
     706#define YYNSTATES  1744 
     707 
    635708#define YYUNDEFTOK  2 
    636709#define YYMAXUTOK   442 
    637710 
     711 
     712/* YYTRANSLATE(TOKEN-NUM) -- Symbol number corresponding to TOKEN-NUM 
     713   as returned by yylex, with out-of-bounds checking.  */ 
    638714#define YYTRANSLATE(YYX)                                                \ 
    639   ((unsigned int) (YYX) <= YYMAXUTOK ? yytranslate[YYX] : YYUNDEFTOK) 
     715  (0 <= (YYX) && (YYX) <= YYMAXUTOK ? yytranslate[YYX] : YYUNDEFTOK) 
    640716 
    641717/* YYTRANSLATE[TOKEN-NUM] -- Symbol number corresponding to TOKEN-NUM 
    642    as returned by yylex, without out-of-bounds checking.  */ 
     718   as returned by yylex.  */ 
    643719static const yytype_uint8 yytranslate[] = 
    644720{ 
     
    692768#if YYDEBUG 
    693769  /* YYRLINE[YYN] -- Source line where rule number YYN was defined.  */ 
    694 static const yytype_uint16 yyrline[] = 
     770static const yytype_int16 yyrline[] = 
    695771{ 
    696772       0,   515,   515,   516,   518,   519,   520,   522,   524,   525, 
     
    778854    3689,  3693,  3694,  3695,  3699,  3703,  3707,  3707,  3707,  3710, 
    779855    3711,  3715,  3716,  3717,  3718,  3719,  3720,  3721,  3722,  3723, 
    780     3724,  3725,  3729,  3733,  3737,  3737,  3741,  3742,  3746,  3747, 
    781     3748,  3749,  3750,  3755,  3754,  3760,  3759,  3764,  3765,  3770, 
    782     3769,  3775,  3774,  3782,  3783,  3785,  3786,  3789,  3793,  3794, 
    783     3795,  3796,  3797,  3798,  3799,  3800,  3801,  3802,  3803,  3807, 
    784     3808,  3809,  3812,  3813,  3816,  3817,  3821,  3822,  3826,  3827, 
    785     3831,  3834,  3835,  3845,  3849,  3850,  3854,  3855,  3859,  3860, 
    786     3864,  3865,  3866,  3867,  3868,  3872,  3873,  3877,  3878,  3882, 
    787     3883,  3884,  3885,  3886,  3892,  3891,  3895,  3894,  3899,  3903, 
    788     3904,  3908,  3909,  3910,  3911,  3912,  3913,  3914,  3915,  3916, 
    789     3917,  3918,  3922,  3926,  3926,  3929,  3930,  3935,  3934,  3955, 
    790     3954,  3979,  3980,  3983,  3984,  3987,  3990,  3991,  3994,  3995, 
    791     3998,  3999,  4002,  4003,  4007,  4012,  4011,  4050,  4049,  4101, 
    792     4102,  4103,  4107,  4108,  4113,  4116,  4117,  4120,  4121,  4126, 
    793     4125,  4139,  4140,  4139,  4151,  4152,  4154,  4155,  4158,  4162, 
    794     4165,  4171,  4175,  4184,  4194,  4196,  4205,  4213,  4221,  4229, 
    795     4233,  4237,  4238,  4241,  4242,  4245,  4249,  4253,  4254,  4257, 
    796     4261,  4262,  4262,  4269,  4268,  4282,  4281,  4294,  4295,  4294, 
    797     4309,  4309,  4333,  4334,  4335,  4339,  4340,  4345,  4353,  4364, 
    798     4365,  4375,  4378,  4379,  4383,  4384,  4388,  4390,  4392,  4397, 
    799     4402,  4403,  4401,  4427,  4452,  4457,  4458,  4462,  4479,  4478, 
    800     4483,  4484,  4488,  4493,  4492,  4507,  4524,  4529,  4573,  4574, 
    801     4578,  4579,  4579,  4584,  4585,  4590,  4602,  4616,  4618,  4623, 
    802     4624,  4629,  4628,  4664,  4665,  4772,  4773,  4774,  4775,  4776, 
    803     4793,  4886,  4887 
     856    3724,  3725,  3726,  3730,  3734,  3738,  3738,  3742,  3743,  3747, 
     857    3748,  3749,  3750,  3751,  3752,  3757,  3756,  3762,  3761,  3766, 
     858    3767,  3772,  3771,  3777,  3776,  3784,  3785,  3787,  3788,  3791, 
     859    3795,  3796,  3797,  3798,  3799,  3800,  3801,  3802,  3803,  3804, 
     860    3805,  3806,  3810,  3811,  3812,  3815,  3816,  3819,  3820,  3824, 
     861    3825,  3829,  3830,  3834,  3837,  3838,  3848,  3852,  3853,  3857, 
     862    3858,  3862,  3863,  3867,  3868,  3869,  3870,  3871,  3875,  3876, 
     863    3880,  3881,  3885,  3886,  3887,  3888,  3889,  3895,  3894,  3898, 
     864    3897,  3902,  3906,  3907,  3911,  3912,  3913,  3914,  3915,  3916, 
     865    3917,  3918,  3919,  3920,  3921,  3922,  3926,  3930,  3930,  3933, 
     866    3934,  3939,  3938,  3959,  3958,  3983,  3984,  3987,  3988,  3991, 
     867    3994,  3995,  3998,  3999,  4002,  4003,  4006,  4007,  4011,  4016, 
     868    4015,  4054,  4053,  4105,  4106,  4107,  4111,  4112,  4117,  4120, 
     869    4121,  4124,  4125,  4130,  4129,  4143,  4144,  4143,  4155,  4156, 
     870    4158,  4159,  4162,  4166,  4169,  4175,  4179,  4188,  4198,  4200, 
     871    4209,  4217,  4225,  4233,  4237,  4241,  4242,  4245,  4246,  4249, 
     872    4253,  4257,  4258,  4261,  4265,  4266,  4266,  4273,  4272,  4286, 
     873    4285,  4298,  4299,  4298,  4313,  4313,  4337,  4338,  4339,  4343, 
     874    4344,  4349,  4357,  4368,  4369,  4379,  4382,  4383,  4387,  4388, 
     875    4392,  4394,  4396,  4401,  4406,  4407,  4405,  4431,  4456,  4461, 
     876    4462,  4466,  4483,  4482,  4487,  4488,  4492,  4497,  4496,  4511, 
     877    4528,  4533,  4577,  4578,  4582,  4583,  4583,  4588,  4589,  4594, 
     878    4606,  4620,  4622,  4627,  4628,  4633,  4632,  4668,  4669,  4776, 
     879    4777,  4778,  4779,  4780,  4797,  4890,  4891 
    804880}; 
    805881#endif 
     
    10041080/* YYTOKNUM[NUM] -- (External) token number corresponding to the 
    10051081   (internal) symbol number NUM (which must be that of a token).  */ 
    1006 static const yytype_uint16 yytoknum[] = 
     1082static const yytype_int16 yytoknum[] = 
    10071083{ 
    10081084       0,   256,   257,    44,    58,    61,   258,   259,   260,   261, 
     
    10301106# endif 
    10311107 
    1032 #define YYPACT_NINF -1428 
    1033  
    1034 #define yypact_value_is_default(Yystate) \ 
    1035   (!!((Yystate) == (-1428))) 
    1036  
    1037 #define YYTABLE_NINF -1024 
    1038  
    1039 #define yytable_value_is_error(Yytable_value) \ 
     1108#define YYPACT_NINF (-1417) 
     1109 
     1110#define yypact_value_is_default(Yyn) \ 
     1111  ((Yyn) == YYPACT_NINF) 
     1112 
     1113#define YYTABLE_NINF (-1028) 
     1114 
     1115#define yytable_value_is_error(Yyn) \ 
    10401116  0 
    10411117 
     
    10441120static const yytype_int16 yypact[] = 
    10451121{ 
    1046    -1428,  1573, -1428, -1428, -1428,   -56,   -39, -1428, -1428, -1428, 
    1047      -12,   631, -1428, -1428,   119,   199, -1428, -1428, -1428, -1428, 
    1048      751, -1428,    88, -1428,    88,   540,   660, -1428, -1428,    88, 
    1049    -1428,    88, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, 
    1050    -1428, -1428, -1428,   140,   152,   183, -1428, -1428, -1428,   877, 
    1051    -1428, -1428,  4069,   157,    88, -1428,   456,  4369,   233,   315, 
    1052    -1428, -1428,  4369,  4369, -1428,   128,   128,    78,    78,    78, 
    1053       78,    82,    78,  1610, -1428, -1428, -1428, -1428, -1428, -1428, 
    1054      128,   195, -1428, -1428,   107,   236,   362,   400, -1428, -1428, 
    1055      107,   111, -1428, -1428,   869, -1428,   600, -1428,   423, -1428, 
    1056     4069, -1428, -1428,   618,   899,   428, -1428, -1428, -1428,   495, 
    1057      320, -1428, -1428, -1428,   545, -1428, -1428,   573,   577, -1428, 
    1058    -1428, -1428, -1428,   240,   683, -1428,   534, -1428, -1428, -1428, 
    1059    -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, 
    1060    -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, 
    1061      628, -1428, -1428, -1428,   621,   561,   578,  3546,   405,   248, 
    1062      332,   602,   604, -1428,  3799,  3846,   606,   623,  3595,   760, 
    1063      706, -1428,  4256, -1428,   926, -1428, -1428, -1428, -1428, -1428, 
    1064    -1428, -1428, -1428, -1428, -1428, -1428, -1428,   780, -1428, -1428, 
    1065    -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, 
    1066    -1428, -1428,   636, -1428, -1428,   638, -1428,   647,   706,   706, 
    1067      119,   119,   651,  3661, -1428, -1428, -1428, -1428, -1428,   367, 
    1068     1394, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, 
    1069    -1428,  3870, -1428, -1428, -1428,   645,   654,  3903, -1428,    81, 
    1070      859, -1428, -1428, -1428,   700, -1428, -1428,   428, -1428,    91, 
    1071    -1428, -1428,  3870, -1428, -1428,   857, -1428,   613,   234,  1187, 
    1072      570, -1428, -1428,   878,   882,   724,   914, -1428, -1428, -1428, 
    1073    -1428,   703,   707,   119, -1428,   109, -1428, -1428,   119,   349, 
    1074      128,   725, -1428,   118, -1428, -1428,   726,   729,   243,   119, 
    1075      128,   644,   732,   364,   485,   121,   596, -1428, -1428, -1428, 
    1076    -1428,   462, -1428, -1428,  3595,  3628,  3903,   128,   912,   927, 
    1077     3903,   617,   115, -1428,   746,   362,   362,   369,  3940,  3903, 
    1078      795,  3903,  3903,   743, -1428,  4171,   424,   775,   840,   221, 
    1079    -1428, -1428, -1428,   664, -1428, -1428, -1428,  3903,  3903,   238, 
    1080      423, -1428, -1428,   128,   128,   119,   128, -1428, -1428, -1428, 
    1081    -1428, -1428,   754,  3476, -1428,   128,  3516,   128, -1428,   763, 
    1082      119, -1428, -1428, -1428, -1428, -1428, -1428, -1428,   128,   439, 
    1083      128, -1428, -1428, -1428,  4284, -1428, -1428, -1428,  3903,   764, 
    1084     3174,  3174,  3628, -1428,   643,    90,   224, -1428, -1428,   762, 
    1085      128, -1428, -1428, -1428, -1428, -1428, -1428,   954,   767,  1610, 
    1086    -1428, -1428,   960,   961,   102,  3870,   817,   972, -1428, -1428, 
    1087    -1428,   610,   610,   450,   801, -1428,   804,   806,  1187,   787, 
    1088     1610,  1610, -1428,   788, -1428,  1187, -1428, -1428,  1187, -1428, 
    1089    -1428,  1187,   808,   613, -1428, -1428, -1428, -1428, -1428, -1428, 
    1090    -1428, -1428, -1428, -1428, -1428, -1428, -1428,   914,   914, -1428, 
    1091     3903, -1428,  3903, -1428, -1428,  3903, -1428,   793,   798,   937, 
    1092      195,   119,   799, -1428, -1428,   989,   119,   118,   725,   119, 
    1093    -1428,   122, -1428,   981, -1428,   815,   816, -1428,   119,  1007, 
    1094    -1428, -1428,   128, -1428,   818, -1428,  1014, -1428, -1428, -1428, 
    1095    -1428, -1428, -1428, -1428,   123,   869,   869,   592,  3903,   107, 
    1096      107,  1107,   119,   128, -1428,   108, -1428, -1428, -1428,   124, 
    1097      824,   119,   909,  3903,   831,  1026, -1428,   225,   858,   665, 
    1098    -1428, -1428,  2259,   841,   881,  1039,   128, -1428,  1042, -1428, 
    1099    -1428,   854,   222, -1428,   864,   125, -1428, -1428,    99,   848, 
    1100    -1428, -1428, -1428, -1428,   128,  1055, -1428,   103,   106, -1428, 
    1101    -1428,   937,   128,   867,   763, -1428, -1428,   107,  1064,   955, 
    1102     1029, -1428, -1428, -1428, -1428,   -32, -1428,   267, -1428,   876, 
    1103      755, -1428, -1428,   938, -1428,   885,   128,   900, -1428, -1428, 
    1104    -1428,   891,   893,   119,   119,   119,   763,  3247,  3062,  3903, 
    1105      248,   937,   937,   787, -1428,   138, -1428,   119,  3903,   248, 
    1106      937,   937, -1428,   141, -1428,   119,   763, -1428,   148,   119, 
    1107      898,   567, -1428,   915, -1428,   902, -1428, -1428,  1090,  3706, 
    1108     3628,   913,   248,   248,   248,   937, -1428, -1428, -1428, -1428, 
    1109    -1428, -1428,   159, -1428, -1428, -1428,   160,   131,   312,   937, 
    1110    -1428, -1428, -1428,  1062, -1428, -1428, -1428, -1428,   444,   917, 
    1111    -1428, -1428, -1428, -1428,  3903,   119,   208,   128,   208,   930, 
    1112    -1428,   931, -1428,  3903, -1428,   922,  1610,  3903,  3903, -1428, 
    1113     1116,   787, -1428,  3870, -1428, -1428, -1428, -1428,   228,   957, 
    1114    -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428,   613,   234, 
    1115     1112, -1428,   878,   882, -1428,  3903,  1131,   162, -1428,   438, 
    1116     1136, -1428, -1428,   946, -1428, -1428,  3903, -1428,  3903,   119, 
    1117    -1428,   726,   119,   763,  1125,   951,  1147, -1428,   644,   119, 
    1118      963,   485,   128,   869, -1428, -1428,   959, -1428,  1135, -1428, 
    1119    -1428,    86, -1428,   966, -1428, -1428,   634, -1428,  1135, -1428, 
    1120     1140,   327, -1428,   973,   119,   128,   119,   128,  1634,   248, 
    1121     3903,    95,   174, -1428, -1428,   170, -1428,   119,  3986,   119, 
    1122     1065,  3903,   128, -1428,  3903,   792, -1428,   763,   474, -1428, 
    1123    -1428, -1428, -1428, -1428,   976, -1428,   980, -1428, -1428, -1428, 
    1124    -1428, -1428, -1428, -1428, -1428,  1172, -1428,   984, -1428,  2259, 
    1125      119,   746,   985,  1177, -1428, -1428, -1428,  1183, -1428, -1428, 
    1126    -1428,   128,   995,   495,   119,   999,   119,  3903,  3903, -1428, 
    1127     3903,  1045, -1428,   128,   119, -1428, -1428,   119,   128,  1023, 
    1128      482,  1000,  3997,  1001,  1206,   937, -1428, -1428, -1428, -1428, 
    1129    -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, 
    1130    -1428, -1428, -1428,   775, -1428, -1428,  1063,  3903,   513, -1428, 
    1131      591, -1428, -1428, -1428, -1428,  1050,  1203,   119,  1093,   472, 
    1132    -1428, -1428, -1428, -1428,  1207, -1428,  1015,  3903,  3903,  3903, 
    1133     3903,  3903,  1208,  3903,   248,  3903,   937, -1428,   175, -1428, 
    1134     3903,  1215,   937,   937,   937,   937,  3903,   937,   248,   937, 
    1135      937, -1428,   176, -1428, -1428, -1428, -1428, -1428, -1428, -1428, 
    1136    -1428, -1428, -1428,  3476,   128, -1428, -1428, -1428, -1428,  3516, 
    1137      128, -1428,  1209,   763, -1428,  3903, -1428,   852, -1428, -1428, 
    1138    -1428,  1193,  4397,  2649,  3903, -1428, -1428, -1428, -1428, -1428, 
    1139    -1428, -1428, -1428, -1428,  3174,  3986,   979,   979,   119, -1428, 
    1140    -1428,  3903,   827, -1428,  1736,   128,   119, -1428,   128,   128, 
    1141       81,  1219, -1428, -1428,   187, -1428, -1428, -1428, -1428, -1428, 
    1142     1032,  1226, -1428,   119,  1035,  1204,  1210,  1041, -1428,   191, 
    1143      197,  1046,  3870, -1428, -1428, -1428, -1428, -1428,  1048,   198, 
    1144     3903,   798, -1428,   937,  3903,  1052,  1234, -1428, -1428,  1248, 
    1145    -1428, -1428, -1428, -1428,   816,   701, -1428, -1428,   200, -1428, 
    1146      205, -1428,  1247, -1428,   119, -1428,  1610,   996, -1428, -1428, 
    1147     3717,   592, -1428, -1428, -1428, -1428,  1149,   119,   119,  3903, 
    1148     1252, -1428, -1428,  3754,  1107, -1428,  1868,  3903, -1428,  3986, 
    1149    -1428,   132, -1428, -1428,   128,  1071,   119, -1428, -1428, -1428, 
    1150     1066, -1428,   260, -1428, -1428,  1075,   133, -1428,   128,   119, 
    1151    -1428, -1428,   841,   128, -1428,  1237, -1428, -1428, -1428,  1067, 
    1152      128,   128,   222,   119,  1250,   202, -1428, -1428, -1428, -1428, 
    1153    -1428, -1428,  1267, -1428,  1268, -1428,   937,   119,   119,   107, 
    1154      128,   119,  3903,  2979,  2873,  3336, -1428,   763,  3903,  4482, 
    1155    -1428,   775,  1080,   128,   119,   515, -1428, -1428, -1428, -1428, 
    1156       77, -1428, -1428,  1085,   119, -1428,   128,   231,  1084,  3903, 
    1157    -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428,  3903, -1428, 
    1158    -1428, -1428, -1428,  3247, -1428, -1428,   937,  1087, -1428, -1428, 
    1159    -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428,  3401, -1428, 
    1160    -1428,   119, -1428,   119,   386,  1089, -1428,  1091, -1428, -1428, 
    1161     1088, -1428,  1123,   173,  1282,  3903,   248,   937, -1428,   206, 
    1162    -1428, -1428, -1428,   128,  1285,  3986, -1428,   128,  1287, -1428, 
    1163    -1428,   134,  1099,   584,   595, -1428, -1428,   643,  3903, -1428, 
    1164      210, -1428,  1293,   119,   128,   119,   119,  3903,  3903, -1428, 
    1165    -1428,   208,  1272, -1428,  1085, -1428,  1085, -1428,  1211, -1428, 
    1166     1231, -1428, -1428,   205,  1113,  1305, -1428, -1428, -1428, -1428, 
    1167    -1428, -1428,   128,   211, -1428,  1118, -1428,  3903,   763,   151, 
    1168     1930, -1428,   128,   243,   963,   128,  3903,   228,   469, -1428, 
    1169    -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, 
    1170    -1428,  1310,   214, -1428, -1428,  1120, -1428, -1428, -1428, -1428, 
    1171      128, -1428,  3903,   248, -1428, -1428,  3903,  1314, -1428,   787, 
    1172    -1428,  1318, -1428,  3986,   119,   119,  1218, -1428,   792, -1428, 
    1173     2006,  1237,   763,   119,   119,  1930,   603, -1428,   119,  1930, 
    1174      367,   112,  1930,  1129,   119,   119, -1428,  1133,   995, -1428, 
    1175    -1428,  3903,   128,   119,   128,   119,  1141,  3903, -1428, -1428, 
    1176    -1428, -1428, -1428,   353,   410,   768,   785,   836,   508,   547, 
    1177     1145,  3903,  1126, -1428,   937,  1134,   451,  1138,   949,  2894, 
    1178      216,  1150, -1428,  1227,   119,   128,   119,  1331,  1195,  1341, 
    1179    -1428,   128, -1428, -1428,   119,   937,  1343,  1346, -1428, -1428, 
    1180    -1428,   217, -1428,  3903,  1348, -1428, -1428,   128, -1428,  3986, 
    1181    -1428,   128,   937,  1351, -1428,  1347, -1428, -1428, -1428, -1428, 
    1182    -1428,  3903,   248,  3903, -1428, -1428, -1428,  2649,   128,   119, 
    1183      128,   119,   979,   128,   119,   597,   128,   119,   128,   119, 
    1184      643, -1428,  1736, -1428,  3903,   119,   423, -1428, -1428,   128, 
    1185    -1428,  1163, -1428, -1428, -1428, -1428,  1353,  1354, -1428,  3903, 
    1186      119,   937, -1428, -1428,  1357, -1428,   119,  1342, -1428,  1170, 
    1187     1363, -1428,  1366, -1428,  1364, -1428,  1368, -1428, -1428,  3903, 
    1188     1356,  1371, -1428, -1428,  1374,   119, -1428, -1428,   119,  1380, 
    1189    -1428, -1428,  3940,  3940, -1428,   119, -1428, -1428, -1428,  3903, 
    1190     3986, -1428,   128,  2006, -1428, -1428,  1190,  1383,  1387,  1368, 
    1191      220, -1428,  1192, -1428, -1428, -1428,  1198,  1199, -1428,  3903, 
    1192      530, -1428, -1428,  1200, -1428, -1428, -1428,   119,   119,   727, 
    1193    -1428, -1428, -1428, -1428, -1428, -1428,   946, -1428,   230, -1428, 
    1194    -1428,  1202, -1428, -1428,  2456,  3903,  3903,  3903,  3903,  3903, 
    1195     3903,  3903,  3903,  3903,  3903,  3903,  3903,  3903,  3903,  2363, 
    1196     3903,  2578,  2615, -1428, -1428,  4482,   607,   119,  1212,  1217, 
    1197     1220,   119,   128, -1428, -1428,   937,   307,   128,  3903, -1428, 
    1198    -1428, -1428,   119,  1285,   119, -1428,   937,   336,   128,   128, 
    1199      128,  1205,  1396, -1428, -1428,   119,   119, -1428,   119,   128, 
    1200      119,   119,   119, -1428, -1428,   119,  1224,   128, -1428,   128, 
    1201     3903,  1610,  1407, -1428,  3903,  1225, -1428,  3903,  3788,  2140, 
    1202     1414,  1422,  1390, -1428, -1428,  3903,   816,  3903, -1428, -1428, 
    1203    -1428,  1423, -1428,  1236,   119,  1238, -1428,  3903,  3903,  3903, 
    1204      530, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, 
    1205    -1428,  1930,   145, -1428, -1428, -1428,  3903, -1428, -1428, -1428, 
    1206    -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, 
    1207    -1428, -1428, -1428,  3903,  3903, -1428, -1428, -1428,  3903, -1428, 
    1208     3903, -1428,   128,   119,  1195, -1428, -1428,  1429, -1428, -1428, 
    1209    -1428, -1428, -1428,   119, -1428, -1428, -1428,   119, -1428,   128, 
    1210    -1428, -1428,   119,   119,   119,  4482,   248,   119,  1239,   119, 
    1211      128,   119,  1240,  1242,  3903, -1428,  1416, -1428, -1428, -1428, 
    1212    -1428,  1436, -1428, -1428, -1428, -1428, -1428,  1147,   218,  3903, 
    1213    -1428, -1428, -1428, -1428, -1428,  1246,  1126,  1254,  2220,  1249, 
    1214     1251,  1255, -1428, -1428, -1428, -1428, -1428,   119,   128,  1212, 
    1215      119,   128, -1428,   119, -1428, -1428,  1439,   763, -1428,  3903, 
    1216    -1428,  1448, -1428, -1428,  2298,  1449, -1428, -1428,  1450, -1428, 
    1217      937, -1428,   119, -1428,   119,  3903, -1428,  1258,  3903,  3903, 
    1218     1451,  2220,  3903, -1428, -1428, -1428,  1454, -1428,  3903, -1428, 
    1219     1455,  3903, -1428,  3903, -1428, -1428 
     1122   -1417,  1551, -1417, -1417, -1417,   -21,    26, -1417, -1417, -1417, 
     1123      36,   734, -1417, -1417,    81,   230, -1417, -1417, -1417, -1417, 
     1124     801, -1417,   252, -1417,   252,   338,   602, -1417, -1417,   252, 
     1125   -1417,   252, -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, 
     1126   -1417, -1417, -1417,   231,   263,   294, -1417, -1417, -1417,   810, 
     1127   -1417, -1417,  4236,   373,   252, -1417,   523,  4536,   385,   401, 
     1128   -1417, -1417,  4536,  4536, -1417,   188,   188,    80,    80,    80, 
     1129      80,   147,    80,  1612, -1417, -1417, -1417, -1417, -1417, -1417, 
     1130     188,   412, -1417, -1417,    94,   316,   481,   619, -1417, -1417, 
     1131      94,   112, -1417, -1417,   910, -1417,   645, -1417,   460, -1417, 
     1132    4236, -1417, -1417,   515,   922,   490, -1417, -1417, -1417,   526, 
     1133     360, -1417, -1417, -1417,   587, -1417, -1417,   604,   615, -1417, 
     1134   -1417, -1417, -1417,   370,   763, -1417,   612, -1417, -1417, -1417, 
     1135   -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, 
     1136   -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, 
     1137     685, -1417, -1417, -1417,   873,   616,   633,  3106,   222,   494, 
     1138     -44,   660,   662, -1417,  3951,  3996,   674,   678,  3732,   800, 
     1139     700, -1417,  4423, -1417,  1168, -1417, -1417, -1417, -1417, -1417, 
     1140   -1417, -1417, -1417, -1417, -1417, -1417, -1417,   830, -1417, -1417, 
     1141   -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, 
     1142   -1417, -1417,   691, -1417, -1417,   693, -1417,   694,   700,   700, 
     1143      81,    81,   686,  3806, -1417, -1417, -1417, -1417, -1417,   319, 
     1144    1072, -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, 
     1145   -1417,  4007, -1417, -1417, -1417,   688,   705,  4062, -1417,    93, 
     1146     896, -1417, -1417, -1417,   732, -1417, -1417,   490, -1417,   105, 
     1147   -1417, -1417,  4007, -1417, -1417,   885, -1417,   598,   240,  1001, 
     1148     878, -1417, -1417,   905,   908,   701,   472, -1417, -1417, -1417, 
     1149   -1417,   728,   737,    81, -1417,   103, -1417, -1417,    81,   450, 
     1150     188,   747, -1417,   117, -1417, -1417,   751,   752,   664,    81, 
     1151     188,   625,   753,   480,   394,   121,   525, -1417, -1417, -1417, 
     1152   -1417,   323, -1417, -1417,  3732,  3772,  4062,   188,   944,   945, 
     1153    4062,   560,   221, -1417,   759,   481,   481,   224,  4086,  4062, 
     1154     805,  4062,  4062,   754, -1417,  4338,   238,   787,   852,   262, 
     1155   -1417, -1417, -1417,   911, -1417, -1417, -1417,  4062,  4062,   313, 
     1156     460, -1417, -1417,   188,   188,    81,   188, -1417, -1417, -1417, 
     1157   -1417, -1417,   765,  3006, -1417,   188,  3682,   188, -1417,   774, 
     1158      81, -1417, -1417, -1417, -1417, -1417, -1417, -1417,   188,   411, 
     1159     188, -1417, -1417, -1417,  4451, -1417, -1417, -1417,  4062,   779, 
     1160    3400,  3400,  3772, -1417,   804,     5,    89, -1417, -1417,   775, 
     1161     188, -1417, -1417, -1417, -1417, -1417, -1417,   970,   786,  1612, 
     1162   -1417, -1417,   979,   982,   109,  4007,   842,   991, -1417, -1417, 
     1163   -1417,   586,   586,   518,   826, -1417,   832,   835,  1001,   817, 
     1164    1612,  1612, -1417,   802, -1417,  1001, -1417, -1417,  1001, -1417, 
     1165   -1417,  1001,   840,   598, -1417, -1417, -1417, -1417, -1417, -1417, 
     1166   -1417, -1417, -1417, -1417, -1417, -1417, -1417,   472,   472, -1417, 
     1167    4062, -1417,  4062, -1417, -1417,  4062, -1417,   824,   838,   927, 
     1168     412,    81,   833, -1417, -1417,  1028,    81,   117,   747,    81, 
     1169   -1417,   122, -1417,  1012, -1417,   844,   845, -1417,    81,  1035, 
     1170   -1417, -1417,   188, -1417,   851, -1417,  1044, -1417, -1417, -1417, 
     1171   -1417, -1417, -1417, -1417,   125,   910,   910,   584,  4062,    94, 
     1172      94,  1581,    81,   188, -1417,   111, -1417, -1417, -1417,   131, 
     1173     854,    81,   939,  4062,   868,  1061, -1417,   266,   892,   609, 
     1174   -1417, -1417,  1222,   880,   915,  1070,   188, -1417,  1074, -1417, 
     1175   -1417,   887,   244, -1417,   891,   159, -1417, -1417,   107,   881, 
     1176   -1417, -1417, -1417, -1417,   188,  1082, -1417,   123,   127, -1417, 
     1177   -1417,   927,   188,   893,   774, -1417, -1417,    94,  1083,   985, 
     1178    1850, -1417, -1417, -1417, -1417,   -10, -1417,   432, -1417,   909, 
     1179     716, -1417, -1417,   974, -1417,   913,   188,   934, -1417, -1417, 
     1180   -1417,   929,   930,    81,    81,    81,   774,  3542,  3095,  4062, 
     1181     494,   927,   927,   817, -1417,   129, -1417,    81,  4062,   494, 
     1182     927,   927, -1417,   130, -1417,    81,   774, -1417,   136,    81, 
     1183     936,   563, -1417,   949, -1417,   946, -1417, -1417,  1137,  3843, 
     1184    3772,   954,   494,   494,   494,   927,   927, -1417, -1417, -1417, 
     1185   -1417, -1417, -1417,   137, -1417, -1417, -1417,   141,   167,   382, 
     1186     927, -1417, -1417, -1417,  1110, -1417, -1417, -1417, -1417,   363, 
     1187     962, -1417, -1417, -1417, -1417,  4062,    81,   223,   188,   223, 
     1188     972, -1417,   981, -1417,  4062, -1417,   975,  1612,  4062,  4062, 
     1189   -1417,  1162,   817, -1417,  4007, -1417, -1417, -1417, -1417,    84, 
     1190     994, -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417,   598, 
     1191     240,  1153, -1417,   905,   908, -1417,  4062,  1167,   144, -1417, 
     1192     452,  1171, -1417, -1417,   984, -1417, -1417,  4062, -1417,  4062, 
     1193      81, -1417,   751,    81,   774,  1158,   988,  1185, -1417,   625, 
     1194      81,   999,   394,   188,   910, -1417, -1417,   998, -1417,  1175, 
     1195   -1417, -1417,   215, -1417,  1004, -1417, -1417,   692, -1417,  1175, 
     1196   -1417,  1178,   542, -1417,  1005,    81,   188,    81,   188,  1741, 
     1197     494,  4062,   116,   154, -1417, -1417,   115, -1417,    81,  4115, 
     1198      81,  1097,  4062,   188, -1417,  4062,   958, -1417,   774,   404, 
     1199   -1417, -1417, -1417, -1417, -1417,  1008, -1417,  1010, -1417, -1417, 
     1200   -1417, -1417, -1417, -1417, -1417, -1417,  1202, -1417,  1013, -1417, 
     1201    1222,    81,   759,  1015,  1203, -1417, -1417, -1417,  1207, -1417, 
     1202   -1417, -1417,   188,  1019,   526,    81,  1020,    81,  4062,  4062, 
     1203   -1417,  4062,  1068, -1417,   188,    81, -1417, -1417,    81,   188, 
     1204    1046,   418,  1024,  4145,  1027,  1036,   927, -1417, -1417, -1417, 
     1205   -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, 
     1206   -1417, -1417, -1417, -1417,   787, -1417, -1417,  1084,  4062,   442, 
     1207   -1417,   649, -1417, -1417, -1417, -1417,  1071,  1224,    81,  1113, 
     1208     603, -1417, -1417, -1417, -1417,  1227, -1417,  1031,  4062,  4062, 
     1209    4062,  4062,  4062,  1226,  4062,   494,  4062,   927,   927, -1417, 
     1210     166, -1417,  4062,  1228,   927,   927,   927,   927,  4062,   927, 
     1211     494,   927,   927,   927, -1417,   169, -1417, -1417, -1417, -1417, 
     1212   -1417, -1417, -1417, -1417, -1417, -1417,  3006,   188, -1417, -1417, 
     1213   -1417, -1417,  3682,   188, -1417,  1229,   774, -1417,  4062, -1417, 
     1214     938, -1417, -1417, -1417,  1204,  4564,  2184,  4062, -1417, -1417, 
     1215   -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417,  3400,  4115, 
     1216     943,   943,    81, -1417, -1417,  4062,   783, -1417,  1827,   188, 
     1217      81, -1417,   188,   188,    93,  1230, -1417, -1417,   171, -1417, 
     1218   -1417, -1417, -1417, -1417,  1041,  1234, -1417,    81,  1045,  1211, 
     1219    1214,  1049, -1417,   175,   176,  1050,  4007, -1417, -1417, -1417, 
     1220   -1417, -1417,  1051,   189,  4062,   838, -1417,   927,  4062,  1055, 
     1221    1248, -1417, -1417,  1249, -1417, -1417, -1417, -1417,   845,   670, 
     1222   -1417, -1417,   195, -1417,   132, -1417,  1250, -1417,    81, -1417, 
     1223    1612,   534, -1417, -1417,  3502,   584, -1417, -1417, -1417, -1417, 
     1224    1152,    81,    81,  4062,  1255, -1417, -1417,  3872,  1581, -1417, 
     1225    1873,  4062, -1417,  4115, -1417,   185, -1417, -1417,   188,  1075, 
     1226      81, -1417, -1417, -1417,  1073, -1417,   269, -1417, -1417,  1078, 
     1227     187, -1417,   188,    81, -1417, -1417,   880,   188, -1417,  1252, 
     1228   -1417, -1417, -1417,  1077,   188,   188,   244,    81,  1258,   198, 
     1229   -1417, -1417, -1417, -1417, -1417, -1417,  1271, -1417,  1279, -1417, 
     1230     927,    81,    81,    94,   188,    81,  4062,  3336,  3039,  3645, 
     1231   -1417,   774,  4062,  4649, -1417,   787,  1090,   188,    81,   445, 
     1232   -1417, -1417, -1417, -1417,    96, -1417, -1417,  1094,    81, -1417, 
     1233     188,   350,  1098,  4062, -1417, -1417, -1417, -1417, -1417, -1417, 
     1234   -1417, -1417,  4062, -1417, -1417, -1417, -1417, -1417,  3542, -1417, 
     1235   -1417,   927,  1101, -1417, -1417, -1417, -1417, -1417, -1417, -1417, 
     1236   -1417, -1417, -1417, -1417,  3592, -1417, -1417,    81, -1417,    81, 
     1237     419,  1102, -1417,  1103, -1417, -1417,  1100, -1417,  1365,   258, 
     1238    1285,  4062,   494,   927,   927, -1417,   201, -1417, -1417, -1417, 
     1239     188,  1296,  4115, -1417,   188,  1297, -1417, -1417,   191,  1107, 
     1240     471,   506, -1417, -1417,   804,  4062, -1417,   203, -1417,  1299, 
     1241      81,   188,    81,    81,  4062,  4062, -1417, -1417,   223,  1278, 
     1242   -1417,  1094, -1417,  1094, -1417,  1212, -1417,  1232, -1417, -1417, 
     1243     132,  1112,  1304, -1417, -1417, -1417, -1417, -1417, -1417,   188, 
     1244     205, -1417,  1116, -1417,  4062,   774,   193,  2068, -1417,   188, 
     1245     664,   999,   188,  4062,    84,   521, -1417, -1417, -1417, -1417, 
     1246   -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417,  1307,   207, 
     1247   -1417, -1417,  1115, -1417, -1417, -1417, -1417,   188, -1417,  4062, 
     1248     494, -1417, -1417,  4062,  1312, -1417,   817, -1417,  1317, -1417, 
     1249    4115,    81,    81,  1223, -1417,   958, -1417,  2169,  1252,   774, 
     1250      81,    81,  2068,   634, -1417,    81,  2068,   319,   124,  2068, 
     1251    1132,    81,    81, -1417,  1136,  1019, -1417, -1417,  4062,   188, 
     1252      81,   188,    81,  1135,  4062, -1417, -1417, -1417, -1417, -1417, 
     1253     558,   571,   776,   828,   876,   537,   610,  1138,  4062,  1134, 
     1254   -1417,   927,  1141,   476,  1140,   948,  1676,   210,  1142, -1417, 
     1255    1236,    81,   188,    81,  1332,  1194,  1340, -1417,   188, -1417, 
     1256   -1417,    81,   927,  1341,  1342, -1417, -1417, -1417,   211, -1417, 
     1257    4062,  1345, -1417, -1417,   188, -1417,  4115, -1417,   188,   927, 
     1258    1346, -1417,  1347, -1417, -1417, -1417, -1417, -1417,  4062,   494, 
     1259    4062, -1417, -1417, -1417, -1417,  2184,   188,    81,   188,    81, 
     1260     943,   188,    81,   545,   188,    81,   188,    81,   804, -1417, 
     1261    1827, -1417,  4062,    81,   460, -1417, -1417,   188, -1417,  1165, 
     1262   -1417, -1417, -1417, -1417,  1357,  1360, -1417,  4062,    81,   927, 
     1263   -1417, -1417,  1349, -1417,    81,  1344, -1417,  1172,  1369, -1417, 
     1264    1370, -1417,  1373, -1417,  1376, -1417, -1417,  4062,  1352,  1377, 
     1265   -1417, -1417,  1379,    81, -1417, -1417,    81,  1378, -1417, -1417, 
     1266    4086,  4086, -1417,    81, -1417, -1417, -1417,  4062,  4115, -1417, 
     1267     188,  2169, -1417, -1417,  1189,  1383,  1384,  1376,   228, -1417, 
     1268    1192, -1417, -1417, -1417,  1195,  1196, -1417,  4062,   640, -1417, 
     1269   -1417,  1198, -1417, -1417, -1417,    81,    81,   735, -1417, -1417, 
     1270   -1417, -1417, -1417, -1417,   984, -1417,   261, -1417, -1417,  1200, 
     1271   -1417, -1417,  2694,  4062,  4062,  4062,  4062,  4062,  4062,  4062, 
     1272    4062,  4062,  4062,  4062,  4062,  4062,  4062,  2635,  4062,  2760, 
     1273    2919, -1417, -1417,  4649,   589,    81,  1197,  1208,  1209,    81, 
     1274     188, -1417, -1417,   927,    19,   188,  4062, -1417, -1417, -1417, 
     1275      81,  1296,    81, -1417,   927,    25,   188,   188,   188,  1201, 
     1276    1392, -1417, -1417,    81,    81, -1417,    81,   188,    81,    81, 
     1277      81, -1417, -1417,    81,  1213,   188, -1417,   188,  4062,  1612, 
     1278    1400, -1417,  4062,  1215, -1417,  4062,  3922,  2318,  1402,  1404, 
     1279    1389, -1417, -1417,  4062,   845,  4062, -1417, -1417, -1417,  1399, 
     1280   -1417,  1216,    81,  1217, -1417,  4062,  4062,  4062,   640, -1417, 
     1281   -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417,  2068, 
     1282      28, -1417, -1417, -1417,  4062, -1417, -1417, -1417, -1417, -1417, 
     1283   -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, 
     1284   -1417,  4062,  4062, -1417, -1417, -1417,  4062, -1417,  4062, -1417, 
     1285     188,    81,  1194, -1417, -1417,  1410, -1417, -1417, -1417, -1417, 
     1286   -1417,    81, -1417, -1417, -1417,    81, -1417,   188, -1417, -1417, 
     1287      81,    81,    81,  4649,   494,    81,  1219,    81,   188,    81, 
     1288    1220,  1221,  4062, -1417,  1395, -1417, -1417, -1417, -1417,  1414, 
     1289   -1417, -1417, -1417, -1417, -1417,  1185,   216,  4062, -1417, -1417, 
     1290   -1417, -1417, -1417,  1233,  1134,  1235,  2355,  1237,  1238,  1239, 
     1291   -1417, -1417, -1417, -1417, -1417,    81,   188,  1197,    81,   188, 
     1292   -1417,    81, -1417, -1417,  1416,   774, -1417,  4062, -1417,  1417, 
     1293   -1417, -1417,  2410,  1418, -1417, -1417,  1419, -1417,   927, -1417, 
     1294      81, -1417,    81,  4062, -1417,  1240,  4062,  4062,  1420,  2355, 
     1295    4062, -1417, -1417, -1417,  1437, -1417,  4062, -1417,  1438,  4062, 
     1296   -1417,  4062, -1417, -1417 
    12201297}; 
    12211298 
     
    12231300     Performed when YYTABLE does not specify something else to do.  Zero 
    12241301     means the default is an error.  */ 
    1225 static const yytype_uint16 yydefact[] = 
     1302static const yytype_int16 yydefact[] = 
    12261303{ 
    1227        2,     0,     1,     6,     8,     0,     0,    17,     9,  1028, 
    1228     1027,     0,    18,     3,     4,     5,    12,    15,    20,  1026, 
    1229        0,    21,   106,    19,   106,     0,   202,  1024,    22,   106, 
    1230       23,   106,    24,    18,   969,   937,   208,   206,   216,   210, 
     1304       2,     0,     1,     6,     8,     0,     0,    17,     9,  1032, 
     1305    1031,     0,    18,     3,     4,     5,    12,    15,    20,  1030, 
     1306       0,    21,   106,    19,   106,     0,   202,  1028,    22,   106, 
     1307      23,   106,    24,    18,   973,   941,   208,   206,   216,   210, 
    12311308     214,   212,    88,   306,     0,     0,     7,    11,    18,   202, 
    1232      203,   966,   108,     0,   107,   952,   192,   192,     0,     0, 
    1233     1027,  1025,   192,   192,    16,     0,     0,   218,   218,   218, 
     1309     203,   970,   108,     0,   107,   956,   192,   192,     0,     0, 
     1310    1031,  1029,   192,   192,    16,     0,     0,   218,   218,   218, 
    12341311     218,   242,   218,     0,   204,   205,    10,    13,    14,   457, 
    12351312       0,     0,   368,   369,    25,     0,   466,     0,   503,   194, 
     
    12391316     150,   147,   144,   525,     0,   523,   534,   539,   522,   520, 
    12401317     521,   118,   119,   120,   711,   709,   709,   712,   738,   739, 
    1241      121,   709,   122,   124,   114,   148,   149,   123,   954,   953, 
    1242        0,   193,   933,   936,   202,     0,     0,   103,     0,     0, 
    1243        0,     0,     0,   918,     0,     0,     0,     0,     0,    88, 
     1318     121,   709,   122,   124,   114,   148,   149,   123,   958,   957, 
     1319       0,   193,   937,   940,   202,     0,     0,   103,     0,     0, 
     1320       0,     0,     0,   921,     0,     0,     0,     0,     0,    88, 
    12441321     134,   126,   192,   152,     0,   157,   163,   158,   173,   179, 
    12451322     156,   689,   153,   162,   155,   170,   154,   788,   165,   164, 
    12461323     181,   161,   178,   172,   160,   175,   180,   174,   177,   166, 
    1247      171,   159,  1003,   176,  1045,  1050,  1033,     0,   134,   134, 
    1248      970,   938,     0,     0,   209,   219,   207,   217,   211,     0, 
     1324     171,   159,  1007,   176,  1049,  1054,  1037,     0,   134,   134, 
     1325     974,   942,     0,     0,   209,   219,   207,   217,   211,     0, 
    12491326       0,   215,   243,   244,   213,   201,   650,   623,   624,   200, 
    1250     1013,     0,   258,   259,  1014,   231,   225,     0,   324,   541, 
     1327    1017,     0,   258,   259,  1018,   231,   225,     0,   324,   541, 
    12511328       0,   606,   310,   618,   186,   187,   189,   190,   188,     0, 
    12521329     308,   607,     0,   605,   610,   611,   613,   615,   625,     0, 
    12531330     628,   642,   644,   646,   648,   655,     0,   658,   661,   199, 
    1254      608,     0,     0,   932,   496,     0,   494,    26,   725,     0, 
    1255        0,     0,   995,     0,   993,   467,     0,     0,   506,   717, 
     1331     608,     0,     0,   936,   496,     0,   494,    26,   725,     0, 
     1332       0,     0,   999,     0,   997,   467,     0,     0,   506,   717, 
    12561333       0,     0,     0,     0,     0,   510,     0,   417,   422,   525, 
    12571334     421,     0,   542,   111,     0,     0,     0,     0,    88,     0, 
    12581335     659,   202,   337,   402,     0,   466,   466,   202,     0,     0, 
    1259        0,     0,   659,   538,   733,   192,   196,   196,   769,   959, 
    1260     1061,   476,   945,   202,   948,   950,   951,     0,     0,    88, 
    1261      541,   167,   104,     0,     0,   812,     0,  1064,  1063,   169, 
     1336       0,     0,   659,   538,   733,   192,   196,   196,   769,   963, 
     1337    1065,   476,   949,   202,   952,   954,   955,     0,     0,    88, 
     1338     541,   167,   104,     0,     0,   812,     0,  1068,  1067,   169, 
    12621339     569,   826,     0,     0,   824,     0,     0,     0,   594,     0, 
    12631340     817,   657,   665,   667,   819,   664,   820,   666,     0,     0, 
    1264        0,   971,   135,   127,   192,   130,   132,   133,     0,     0, 
    1265        0,     0,     0,  1010,   691,     0,     0,   789,   709,  1007, 
    1266        0,  1051,  1043,  1030,   476,   476,   222,     0,     0,     0, 
     1341       0,   975,   135,   127,   192,   130,   132,   133,     0,     0, 
     1342       0,     0,     0,  1014,   691,     0,     0,   789,   709,  1011, 
     1343       0,  1055,  1047,  1034,   476,   476,   222,     0,     0,     0, 
    12671344     254,   251,     0,     0,     0,     0,     0,   323,   326,   329, 
    12681345     328,     0,     0,   541,   618,   235,   187,     0,     0,     0, 
     
    12701347     223,     0,   186,   616,   632,   634,   633,   635,   630,   631, 
    12711348     627,   636,   637,   639,   641,   638,   640,     0,     0,   651, 
    1272        0,   652,     0,   653,   654,     0,   643,  1001,     0,     0, 
    1273        0,   493,     0,   707,   732,     0,   727,     0,     0,   991, 
    1274      999,     0,   997,     0,   508,     0,     0,   507,   719,   267, 
     1349       0,   652,     0,   653,   654,     0,   643,  1005,     0,     0, 
     1350       0,   493,     0,   707,   732,     0,   727,     0,     0,   995, 
     1351    1003,     0,  1001,     0,   508,     0,     0,   507,   719,   267, 
    12751352     268,   270,     0,   265,     0,   429,     0,   425,   545,   428, 
    12761353     544,   427,   511,   410,   510,     0,     0,     0,     0,    25, 
    1277       25,   549,  1059,     0,   881,   225,   880,   657,   879,     0, 
     1354      25,   549,  1063,     0,   884,   225,   883,   657,   882,     0, 
    12781355       0,   816,     0,     0,     0,     0,   660,   282,     0,   202, 
    12791356     278,   280,     0,     0,     0,   340,     0,   408,   405,   406, 
     
    12821359     677,     0,     0,     0,     0,   710,   198,    25,     0,     0, 
    12831360     192,   709,   714,   734,   740,     0,   760,   192,   715,     0, 
    1284      773,   770,   709,     0,   960,     0,     0,     0,   934,   949, 
     1361     773,   770,   709,     0,   964,     0,     0,     0,   938,   953, 
    12851362     700,     0,     0,   767,   813,   814,     0,     0,     0,     0, 
    1286        0,     0,     0,   658,   909,     0,   907,   905,     0,     0, 
    1287        0,     0,   900,     0,   898,   896,     0,  1071,     0,   818, 
    1288        0,   202,   964,     0,   131,     0,   844,   822,     0,     0, 
    1289        0,     0,     0,     0,     0,     0,    88,   529,   825,   868, 
    1290      821,   823,     0,   871,   865,   870,     0,     0,     0,     0, 
    1291      699,   697,   698,   693,   690,   696,   804,   802,     0,   798, 
    1292      790,   787,   791,  1005,     0,  1004,  1053,     0,  1053,     0, 
    1293     1029,     0,  1042,     0,   220,     0,     0,     0,     0,   249, 
    1294        0,   328,   321,     0,   228,   227,   232,   226,     0,   187, 
    1295      609,   311,   309,   325,   322,   186,   612,   614,   617,   626, 
    1296      629,   645,   647,   649,  1000,     0,     0,     0,   460,   526, 
    1297        0,   500,   502,   534,   501,   495,     0,   731,     0,   992, 
    1298      994,     0,   996,     0,     0,   517,   512,   515,     0,   262, 
    1299        0,     0,     0,     0,   414,   418,   541,   434,   223,   435, 
    1300      229,   439,   437,     0,   438,   436,     0,   419,   439,   448, 
    1301      305,     0,   367,     0,   724,     0,   716,     0,   553,     0, 
    1302        0,   541,     0,   550,   558,   567,   568,  1060,     0,   863, 
    1303        0,     0,     0,   536,   659,     0,   283,     0,     0,   261, 
    1304      279,   353,   344,   345,     0,   348,     0,   351,   352,   354, 
    1305      355,   356,   341,   343,   361,   335,   357,   370,   338,     0, 
    1306      403,     0,     0,   451,   360,   472,   464,   469,   470,   473, 
    1307      474,     0,     0,   202,   477,     0,   672,   679,     0,   674, 
    1308        0,     0,   681,     0,   668,   535,   540,   721,     0,     0, 
    1309        0,     0,     0,     0,     0,   193,   742,   746,   743,   757, 
    1310      741,   751,   748,   735,   753,   745,   755,   758,   754,   756, 
    1311      747,   752,   744,   761,   709,   759,     0,     0,     0,   771, 
    1312        0,   774,   709,   772,   978,     0,   979,  1062,   941,     0, 
    1313      794,   583,   545,   584,   572,   580,   585,     0,     0,     0, 
    1314        0,     0,     0,     0,     0,     0,     0,   831,     0,   829, 
    1315        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1316        0,   921,     0,   919,   910,   913,   533,   911,   532,   531, 
    1317      843,   530,   912,     0,     0,   901,   904,   903,   902,     0, 
    1318        0,   597,   599,     0,   168,     0,   136,   202,   139,   141, 
    1319      142,   974,   192,     0,     0,   822,   869,   873,   867,   872, 
    1320      874,   875,   876,   877,     0,   859,   853,     0,   857,  1012, 
    1321     1011,     0,     0,   689,     0,     0,   796,   800,     0,     0, 
    1322      541,     0,  1020,  1019,     0,  1015,  1017,  1058,  1034,  1057, 
    1323        0,  1054,  1055,  1044,     0,  1040,  1048,     0,   253,     0, 
    1324        0,     0,     0,   327,   191,   239,   237,   238,     0,     0, 
    1325        0,     0,   458,     0,   659,     0,     0,   998,   526,   488, 
    1326      490,   492,   509,   518,     0,   504,   269,   273,     0,   271, 
    1327      541,   426,     0,   430,   411,   415,   542,     0,   432,   433, 
    1328        0,     0,   416,   431,   224,   230,     0,   726,   718,     0, 
    1329      554,   561,   557,     0,     0,   543,   562,     0,   552,     0, 
    1330      888,     0,   886,   889,     0,     0,   669,   537,   288,   289, 
    1331        0,   292,     0,   285,   287,   296,     0,   293,     0,   274, 
    1332      346,   349,     0,     0,   371,   240,   342,   407,   453,     0, 
    1333        0,     0,     0,   479,   485,     0,   483,   481,   682,   683, 
    1334      680,   593,     0,   676,     0,   678,     0,   670,   723,    25, 
    1335        0,   736,     0,  1069,  1067,     0,   749,     0,     0,   192, 
    1336      763,   762,     0,     0,   782,     0,   775,   768,   776,   961, 
    1337        0,   955,   942,   943,   695,   687,     0,     0,     0,     0, 
    1338      582,   842,   656,   836,   833,   834,   837,   840,     0,   832, 
    1339      835,   839,   838,     0,   827,   923,     0,     0,   924,   925, 
    1340      931,   922,   528,   930,   527,   926,   928,   927,     0,   914, 
    1341      908,   906,   899,   897,     0,     0,  1072,     0,   140,   975, 
    1342      976,   786,     0,   193,     0,     0,     0,     0,   848,     0, 
    1343      846,   878,   866,     0,   861,     0,   884,     0,   855,   882, 
    1344      885,     0,     0,     0,     0,   689,   688,   692,     0,   811, 
    1345        0,   805,   807,   797,     0,   799,  1006,     0,     0,  1008, 
    1346     1052,     0,  1035,  1041,   943,  1049,   943,   221,     0,   250, 
    1347        0,   247,   246,   541,     0,     0,   333,   233,  1002,   663, 
    1348      462,   461,     0,     0,   498,     0,   730,     0,     0,   510, 
    1349      392,   516,     0,     0,     0,     0,     0,     0,   191,   441, 
    1350      183,   184,   185,   443,   444,   446,   447,   445,   440,   442, 
    1351      312,     0,     0,   314,   316,   681,   318,   319,   320,   420, 
    1352        0,   555,     0,     0,   559,   551,     0,   563,   566,   888, 
    1353      893,     0,   891,     0,   864,   779,     0,   290,     0,   284, 
    1354        0,   240,     0,   281,   275,   392,     0,   358,   336,   392, 
    1355        0,   362,   392,     0,   452,   465,   471,     0,     0,   482, 
    1356      679,     0,     0,   720,     0,   737,     0,     0,    32,    33, 
    1357       91,    71,    94,   258,   259,   255,   257,   256,   231,   225, 
    1358        0,     0,    27,    63,    65,    62,   541,    28,   101,   658, 
    1359        0,     0,   764,     0,   783,     0,   784,     0,     0,   980, 
    1360      981,     0,   944,   939,   795,     0,     0,   573,   574,   581, 
    1361      570,     0,   587,     0,     0,   841,   830,     0,   929,     0, 
    1362      920,     0,     0,     0,   598,   600,   601,   595,   792,   977, 
    1363      972,     0,     0,     0,   849,   851,   850,     0,     0,   860, 
    1364        0,   854,     0,     0,   858,     0,     0,   703,     0,   705, 
    1365      694,   809,     0,   803,   808,   801,   541,  1018,  1016,     0, 
    1366     1056,     0,  1031,  1036,  1047,  1047,     0,     0,   330,     0, 
    1367      459,     0,   497,   535,   728,   491,   487,     0,   386,     0, 
    1368      373,   378,     0,   381,   374,   384,   375,   388,   376,   394, 
    1369        0,   377,   396,   662,   383,   505,   513,   272,   263,     0, 
    1370      236,   234,     0,     0,   313,   777,   556,   560,   564,     0, 
    1371        0,   887,     0,     0,   286,   390,     0,   298,     0,   299, 
    1372      300,   294,     0,   400,   401,   399,     0,     0,   241,     0, 
    1373        0,   359,   363,     0,   455,   486,   484,   671,   722,     0, 
    1374       31,  1066,  1068,    30,  1070,    66,   534,    67,    72,  1065, 
    1375       95,    98,    96,   102,     0,     0,     0,     0,     0,     0, 
    1376        0,     0,     0,     0,     0,     0,     0,     0,     0,    55, 
    1377        0,     0,     0,    29,   750,   192,     0,   785,   962,     0, 
    1378        0,   956,     0,   579,   576,     0,     0,     0,     0,   586, 
    1379      589,   591,   828,   916,   915,   603,     0,     0,     0,     0, 
    1380        0,     0,     0,   852,   847,   845,   862,   883,   856,     0, 
    1381      701,   704,   706,   806,   810,  1009,     0,     0,  1038,     0, 
    1382        0,     0,     0,   499,     0,     0,   519,   393,   387,     0, 
    1383        0,     0,     0,   382,   398,   394,     0,     0,   317,   315, 
    1384      565,     0,   892,     0,   778,     0,   297,     0,     0,     0, 
    1385        0,   295,   301,   347,   350,   372,   364,   366,   365,   305, 
    1386      454,   392,     0,    64,    64,    64,     0,    54,    60,    39, 
    1387       49,    51,    50,    52,    45,    40,    47,    46,    38,    48, 
    1388       34,    35,    36,     0,     0,    53,    56,    37,     0,    42, 
    1389        0,    41,     0,   780,   989,   957,   988,   963,   984,   987, 
    1390      986,   983,   982,   940,   578,   577,   575,   571,   588,     0, 
    1391      604,   602,   596,   793,   973,   192,     0,   702,     0,  1032, 
    1392        0,  1046,     0,     0,     0,   729,     0,   379,   380,   383, 
    1393      386,     0,   385,   389,   395,   391,   397,   514,     0,     0, 
    1394      890,   291,   302,   304,   303,     0,    74,    61,    75,     0, 
    1395        0,     0,    59,    57,    58,    44,    43,   781,     0,     0, 
    1396      917,     0,  1037,  1039,   245,   248,   331,     0,   387,     0, 
    1397      423,     0,   456,    72,    87,    76,    77,    80,    79,    68, 
    1398        0,    73,   958,   985,   815,     0,   489,     0,     0,     0, 
    1399       85,     0,    86,    70,   332,   424,   894,    84,     0,    78, 
    1400       81,     0,    83,     0,   895,    82 
     1363       0,     0,     0,   658,   912,     0,   910,   908,     0,     0, 
     1364       0,     0,   903,     0,   901,   899,     0,  1075,     0,   818, 
     1365       0,   202,   968,     0,   131,     0,   845,   822,     0,     0, 
     1366       0,     0,     0,     0,     0,     0,     0,    88,   529,   825, 
     1367     870,   821,   823,     0,   873,   867,   872,     0,     0,     0, 
     1368       0,   699,   697,   698,   693,   690,   696,   804,   802,     0, 
     1369     798,   790,   787,   791,  1009,     0,  1008,  1057,     0,  1057, 
     1370       0,  1033,     0,  1046,     0,   220,     0,     0,     0,     0, 
     1371     249,     0,   328,   321,     0,   228,   227,   232,   226,     0, 
     1372     187,   609,   311,   309,   325,   322,   186,   612,   614,   617, 
     1373     626,   629,   645,   647,   649,  1004,     0,     0,     0,   460, 
     1374     526,     0,   500,   502,   534,   501,   495,     0,   731,     0, 
     1375     996,   998,     0,  1000,     0,     0,   517,   512,   515,     0, 
     1376     262,     0,     0,     0,     0,   414,   418,   541,   434,   223, 
     1377     435,   229,   439,   437,     0,   438,   436,     0,   419,   439, 
     1378     448,   305,     0,   367,     0,   724,     0,   716,     0,   553, 
     1379       0,     0,   541,     0,   550,   558,   567,   568,  1064,     0, 
     1380     865,     0,     0,     0,   536,   659,     0,   283,     0,     0, 
     1381     261,   279,   353,   344,   345,     0,   348,     0,   351,   352, 
     1382     354,   355,   356,   341,   343,   361,   335,   357,   370,   338, 
     1383       0,   403,     0,     0,   451,   360,   472,   464,   469,   470, 
     1384     473,   474,     0,     0,   202,   477,     0,   672,   679,     0, 
     1385     674,     0,     0,   681,     0,   668,   535,   540,   721,     0, 
     1386       0,     0,     0,     0,     0,     0,   193,   742,   746,   743, 
     1387     757,   741,   751,   748,   735,   753,   745,   755,   758,   754, 
     1388     756,   747,   752,   744,   761,   709,   759,     0,     0,     0, 
     1389     771,     0,   774,   709,   772,   982,     0,   983,  1066,   945, 
     1390       0,   794,   583,   545,   584,   572,   580,   585,     0,     0, 
     1391       0,     0,     0,     0,     0,     0,     0,     0,     0,   831, 
     1392       0,   829,     0,     0,     0,     0,     0,     0,     0,     0, 
     1393       0,     0,     0,     0,   924,     0,   922,   913,   916,   533, 
     1394     914,   532,   531,   844,   530,   915,     0,     0,   904,   907, 
     1395     906,   905,     0,     0,   597,   599,     0,   168,     0,   136, 
     1396     202,   139,   141,   142,   978,   192,     0,     0,   822,   871, 
     1397     875,   869,   874,   876,   877,   878,   880,   879,     0,   861, 
     1398     855,     0,   859,  1016,  1015,     0,     0,   689,     0,     0, 
     1399     796,   800,     0,     0,   541,     0,  1024,  1023,     0,  1019, 
     1400    1021,  1062,  1038,  1061,     0,  1058,  1059,  1048,     0,  1044, 
     1401    1052,     0,   253,     0,     0,     0,     0,   327,   191,   239, 
     1402     237,   238,     0,     0,     0,     0,   458,     0,   659,     0, 
     1403       0,  1002,   526,   488,   490,   492,   509,   518,     0,   504, 
     1404     269,   273,     0,   271,   541,   426,     0,   430,   411,   415, 
     1405     542,     0,   432,   433,     0,     0,   416,   431,   224,   230, 
     1406       0,   726,   718,     0,   554,   561,   557,     0,     0,   543, 
     1407     562,     0,   552,     0,   891,     0,   889,   892,     0,     0, 
     1408     669,   537,   288,   289,     0,   292,     0,   285,   287,   296, 
     1409       0,   293,     0,   274,   346,   349,     0,     0,   371,   240, 
     1410     342,   407,   453,     0,     0,     0,     0,   479,   485,     0, 
     1411     483,   481,   682,   683,   680,   593,     0,   676,     0,   678, 
     1412       0,   670,   723,    25,     0,   736,     0,  1073,  1071,     0, 
     1413     749,     0,     0,   192,   763,   762,     0,     0,   782,     0, 
     1414     775,   768,   776,   965,     0,   959,   946,   947,   695,   687, 
     1415       0,     0,     0,     0,   582,   843,   656,   836,   833,   834, 
     1416     837,   841,     0,   832,   835,   840,   839,   838,     0,   827, 
     1417     926,     0,     0,   927,   928,   935,   925,   528,   934,   527, 
     1418     929,   932,   931,   930,     0,   917,   911,   909,   902,   900, 
     1419       0,     0,  1076,     0,   140,   979,   980,   786,     0,   193, 
     1420       0,     0,     0,     0,     0,   849,     0,   847,   881,   868, 
     1421       0,   863,     0,   887,     0,   857,   885,   888,     0,     0, 
     1422       0,     0,   689,   688,   692,     0,   811,     0,   805,   807, 
     1423     797,     0,   799,  1010,     0,     0,  1012,  1056,     0,  1039, 
     1424    1045,   947,  1053,   947,   221,     0,   250,     0,   247,   246, 
     1425     541,     0,     0,   333,   233,  1006,   663,   462,   461,     0, 
     1426       0,   498,     0,   730,     0,     0,   510,   392,   516,     0, 
     1427       0,     0,     0,     0,     0,   191,   441,   183,   184,   185, 
     1428     443,   444,   446,   447,   445,   440,   442,   312,     0,     0, 
     1429     314,   316,   681,   318,   319,   320,   420,     0,   555,     0, 
     1430       0,   559,   551,     0,   563,   566,   891,   896,     0,   894, 
     1431       0,   866,   779,     0,   290,     0,   284,     0,   240,     0, 
     1432     281,   275,   392,     0,   358,   336,   392,     0,   362,   392, 
     1433       0,   452,   465,   471,     0,     0,   482,   679,     0,     0, 
     1434     720,     0,   737,     0,     0,    32,    33,    91,    71,    94, 
     1435     258,   259,   255,   257,   256,   231,   225,     0,     0,    27, 
     1436      63,    65,    62,   541,    28,   101,   658,     0,     0,   764, 
     1437       0,   783,     0,   784,     0,     0,   984,   985,     0,   948, 
     1438     943,   795,     0,     0,   573,   574,   581,   570,     0,   587, 
     1439       0,     0,   842,   830,     0,   933,     0,   923,     0,     0, 
     1440       0,   598,   600,   601,   595,   792,   981,   976,     0,     0, 
     1441       0,   850,   853,   852,   851,     0,     0,   862,     0,   856, 
     1442       0,     0,   860,     0,     0,   703,     0,   705,   694,   809, 
     1443       0,   803,   808,   801,   541,  1022,  1020,     0,  1060,     0, 
     1444    1035,  1040,  1051,  1051,     0,     0,   330,     0,   459,     0, 
     1445     497,   535,   728,   491,   487,     0,   386,     0,   373,   378, 
     1446       0,   381,   374,   384,   375,   388,   376,   394,     0,   377, 
     1447     396,   662,   383,   505,   513,   272,   263,     0,   236,   234, 
     1448       0,     0,   313,   777,   556,   560,   564,     0,     0,   890, 
     1449       0,     0,   286,   390,     0,   298,     0,   299,   300,   294, 
     1450       0,   400,   401,   399,     0,     0,   241,     0,     0,   359, 
     1451     363,     0,   455,   486,   484,   671,   722,     0,    31,  1070, 
     1452    1072,    30,  1074,    66,   534,    67,    72,  1069,    95,    98, 
     1453      96,   102,     0,     0,     0,     0,     0,     0,     0,     0, 
     1454       0,     0,     0,     0,     0,     0,     0,    55,     0,     0, 
     1455       0,    29,   750,   192,     0,   785,   966,     0,     0,   960, 
     1456       0,   579,   576,     0,     0,     0,     0,   586,   589,   591, 
     1457     828,   919,   918,   603,     0,     0,     0,     0,     0,     0, 
     1458       0,   854,   848,   846,   864,   886,   858,     0,   701,   704, 
     1459     706,   806,   810,  1013,     0,     0,  1042,     0,     0,     0, 
     1460       0,   499,     0,     0,   519,   393,   387,     0,     0,     0, 
     1461       0,   382,   398,   394,     0,     0,   317,   315,   565,     0, 
     1462     895,     0,   778,     0,   297,     0,     0,     0,     0,   295, 
     1463     301,   347,   350,   372,   364,   366,   365,   305,   454,   392, 
     1464       0,    64,    64,    64,     0,    54,    60,    39,    49,    51, 
     1465      50,    52,    45,    40,    47,    46,    38,    48,    34,    35, 
     1466      36,     0,     0,    53,    56,    37,     0,    42,     0,    41, 
     1467       0,   780,   993,   961,   992,   967,   988,   991,   990,   987, 
     1468     986,   944,   578,   577,   575,   571,   588,     0,   604,   602, 
     1469     596,   793,   977,   192,     0,   702,     0,  1036,     0,  1050, 
     1470       0,     0,     0,   729,     0,   379,   380,   383,   386,     0, 
     1471     385,   389,   395,   391,   397,   514,     0,     0,   893,   291, 
     1472     302,   304,   303,     0,    74,    61,    75,     0,     0,     0, 
     1473      59,    57,    58,    44,    43,   781,     0,     0,   920,     0, 
     1474    1041,  1043,   245,   248,   331,     0,   387,     0,   423,     0, 
     1475     456,    72,    87,    76,    77,    80,    79,    68,     0,    73, 
     1476     962,   989,   815,     0,   489,     0,     0,     0,    85,     0, 
     1477      86,    70,   332,   424,   897,    84,     0,    78,    81,     0, 
     1478      83,     0,   898,    82 
    14011479}; 
    14021480 
     
    14041482static const yytype_int16 yypgoto[] = 
    14051483{ 
    1406    -1428, -1428, -1428,   921, -1428,  1412,   477, -1428, -1428, -1428, 
    1407    -1428, -1428, -1428, -1428, -1428, -1428,  -130, -1428, -1428, -1428, 
    1408    -1428, -1428, -1428, -1428,  -725, -1428,  -258, -1428,   -11, -1428, 
    1409    -1428, -1428, -1428, -1428, -1428, -1428, -1428,  1369,   823, -1428, 
    1410    -1428, -1428,   -95,   691, -1428, -1428, -1428,   549, -1428,   -84, 
    1411     -896,  -636, -1428, -1428,   457,   461,   -45,    63, -1428,   583, 
    1412     -208,   -65, -1428,  1456, -1428, -1428, -1428, -1428, -1428, -1428, 
    1413     1130, -1428,  -189,  -186,  1058,  -441,  -187, -1428, -1428, -1428, 
    1414      203, -1428, -1428, -1428,   204,   -33, -1428, -1428, -1428, -1428, 
    1415    -1428, -1428, -1428,   753, -1428,   251, -1428, -1428, -1428,   958, 
    1416    -1428, -1428, -1428,   212, -1428, -1428,   207, -1428,    40, -1428, 
    1417    -1428,  -967,  1474, -1428,  1068,   479, -1428,    57,    59, -1428, 
    1418     1243, -1428, -1428,  1094,  -608, -1428, -1428, -1428, -1428, -1428, 
    1419    -1428, -1428, -1428, -1428,   709, -1428, -1428, -1428,   440, -1428, 
    1420    -1428, -1428, -1428,  -965,  -266, -1428, -1428, -1184, -1150, -1427, 
    1421    -1169, -1320, -1428,   -63, -1130,   -60, -1428, -1428,    83, -1428, 
    1422      -64, -1428, -1428, -1428, -1428, -1428,   712, -1428, -1428, -1428, 
    1423    -1428,  -427, -1428, -1428,  1009,  -251, -1428,   786, -1428,   497, 
    1424     -281, -1428,   499, -1428, -1428, -1428, -1428, -1428, -1428, -1428, 
    1425    -1428, -1428, -1428, -1428,   528, -1428, -1428, -1428,   -28, -1428, 
    1426    -1428,   448, -1428,     8, -1428, -1428, -1428,   708, -1428,   235, 
    1427    -1428, -1428,  -185,   295, -1428, -1428,  1056, -1428, -1428,  -930, 
    1428    -1428, -1428, -1428, -1428,  -274,  -466, -1428, -1428,   -48,   531, 
    1429    -1428,  1345, -1428,  2073,  -449,   637, -1428, -1428,  -826, -1428, 
    1430     -510, -1428,  -455,  -287,  -291, -1428,   970, -1428, -1428,  -262, 
    1431     -289, -1428, -1428,   502, -1428, -1428,   969, -1428, -1428, -1428, 
    1432    -1428,    14,     5,   182, -1428,   429,  -568, -1428, -1428,    17, 
    1433    -1428,  -245,   194,   978, -1428, -1428, -1428, -1428, -1428,    12, 
    1434    -1428, -1428,   250,   -78,  1095, -1428, -1428,  -145,  1097, -1428, 
    1435     1277, -1428,  1096,  1098,  1100, -1428, -1428, -1428, -1428, -1428, 
    1436     1667,  -791,  -146,  -166,   784,   -37,  -958, -1336, -1428, -1428, 
    1437     -212, -1428,   -46,   298, -1428, -1428, -1428,   741,   742,  -514, 
    1438      748, -1428,  1233,  -376,  -371,  -863, -1428, -1428, -1428, -1428, 
    1439     -828,  -825, -1428, -1428, -1428, -1428,  -107, -1428,   372, -1428, 
    1440    -1428,   991, -1428,   -81,  -694,  -119,  1230, -1428, -1428, -1428, 
    1441    -1428, -1428, -1428, -1428,   994, -1428, -1428, -1428,   379, -1428, 
    1442     -504, -1428, -1428, -1428, -1428, -1428, -1428,  1002, -1428, -1428, 
    1443     1178, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1428, 
    1444    -1428,   181, -1093, -1428,  1005, -1428,    -3, -1428, -1428,   947, 
    1445     -149, -1428,  1011, -1428, -1428, -1428,   449,   687,   974,  1016, 
    1446    -1428, -1428,   223,  1017, -1428, -1428,  1024, -1428, -1428,   -13, 
    1447     1213,   964,   655,  -260,   656,   219,  -871,  -959,  -861, -1428, 
    1448      155, -1428,  1038, -1428,   690,  1047, -1428,   689,  1049, -1428, 
    1449    -1428, -1428, -1428,   467,   394, -1428, -1428, -1428, -1428, -1428, 
    1450    -1428, -1428, -1428,  -495, -1428, -1428, -1428,  1273, -1428, -1428, 
    1451     1554, -1428, -1428, -1428, -1428, -1428,   728, -1428, -1428, -1428, 
    1452    -1428, -1428, -1428, -1428, -1428, -1428, -1428, -1037, -1428,   -76, 
    1453    -1428, -1412, -1428,  1330,  1148, -1428, -1428,   904,  -476, -1428, 
    1454     1059, -1428, -1428, -1428, -1428, -1428, -1428,   982,   923,   434, 
    1455      436, -1428, -1428,  1598,  -134, -1428, -1428, -1428, -1428, -1428, 
    1456    -1428, -1428, -1428, -1428, -1428,  -131, -1428, -1428, -1428, -1428, 
    1457      232, -1428, -1428, -1428,   967, -1428,   435,   453, -1428, -1428, 
    1458    -1428, -1428, -1428,   541 
     1484   -1417, -1417, -1417,  1095, -1417,  1394,   642, -1417, -1417, -1417, 
     1485   -1417, -1417, -1417, -1417, -1417, -1417,  -178, -1417, -1417, -1417, 
     1486   -1417, -1417, -1417, -1417,  -769, -1417,  -285, -1417,   -11, -1417, 
     1487   -1417, -1417, -1417, -1417, -1417, -1417, -1417,  1348,   798, -1417, 
     1488   -1417, -1417,   152,   655, -1417, -1417, -1417,   527, -1417,   -85, 
     1489    -906,  -632, -1417, -1417,   435,   438,   -42,    57, -1417,   544, 
     1490    -215,   -74, -1417,  1431, -1417, -1417, -1417, -1417, -1417, -1417, 
     1491     866, -1417,  -203,  -186,  1042,  -432,  -180, -1417, -1417, -1417, 
     1492     177, -1417, -1417, -1417,   172,   -41, -1417, -1417, -1417, -1417, 
     1493   -1417, -1417, -1417,   739, -1417,   225, -1417, -1417, -1417,   941, 
     1494   -1417, -1417, -1417,   178, -1417, -1417,   182, -1417,    11, -1417, 
     1495   -1417,  -980,  1453, -1417,  1048,   456, -1417,    29,    34, -1417, 
     1496    1231, -1417, -1417,  1076,  -626, -1417, -1417, -1417, -1417, -1417, 
     1497   -1417, -1417, -1417, -1417,   687, -1417, -1417, -1417,   422, -1417, 
     1498   -1417, -1417, -1417,  -967,  -266, -1417, -1417, -1187, -1166, -1186, 
     1499   -1193, -1135, -1417,   -92, -1160,   -89, -1417, -1417,    53, -1417, 
     1500     -86, -1417, -1417, -1417, -1417, -1417,   697, -1417, -1417, -1417, 
     1501   -1417,  -416, -1417, -1417,  1003,  -249, -1417,   762, -1417,   479, 
     1502    -576, -1417,   484, -1417, -1417, -1417, -1417, -1417, -1417, -1417, 
     1503   -1417, -1417, -1417, -1417,   516, -1417, -1417, -1417,   -20, -1417, 
     1504   -1417,   434, -1417,     9, -1417, -1417, -1417,   702, -1417,   212, 
     1505   -1417, -1417,  -197,   284, -1417, -1417,  1053, -1417, -1417,  -931, 
     1506   -1417, -1417, -1417, -1417,  -281,  -467, -1417, -1417,   -63,   517, 
     1507   -1417,  1225, -1417,  2143,  -451,   621, -1417, -1417,  -815, -1417, 
     1508    -531, -1417,  -456,  -286,  -293, -1417,   964, -1417, -1417,  -252, 
     1509    -282, -1417, -1417,   491, -1417, -1417,   960, -1417, -1417, -1417, 
     1510   -1417,    -3,    -9,   163, -1417,   413,  -577, -1417, -1417,     0, 
     1511   -1417,  -270,   179,   967, -1417, -1417, -1417, -1417, -1417,    -7, 
     1512   -1417, -1417,   339,   -30,  1085, -1417, -1417,   -78,  1087, -1417, 
     1513    1265, -1417,  1086,  1081,  1089, -1417, -1417, -1417, -1417, -1417, 
     1514    1819,  -794,   -83,  -166,   772,   -69,  -995, -1108, -1417, -1417, 
     1515    -204, -1417,   -46,   100, -1417, -1417, -1417,   729,   731,  -514, 
     1516     733, -1417,  1241,  -367,  -364,  -861, -1417, -1417, -1417, -1417, 
     1517    -832,  -838, -1417, -1417, -1417, -1417,   -98, -1417,   295, -1417, 
     1518   -1417,   980, -1417,   -77,  -696,  -104,  1242, -1417, -1417, -1417, 
     1519   -1417, -1417, -1417, -1417,   983, -1417, -1417, -1417,   326, -1417, 
     1520    -496, -1417, -1417, -1417, -1417, -1417, -1417,   986, -1417, -1417, 
     1521    1154, -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1417, 
     1522   -1417,   164, -1089, -1417,   989, -1417,   -22, -1417, -1417,   937, 
     1523    -126, -1417,   993, -1417, -1417, -1417,   427,   675,  -534,  1000, 
     1524   -1417, -1417,   183,  1007, -1417, -1417,  1011, -1417, -1417,   -12, 
     1525    1180,   942,   626,  -239,   624,   192,  -889,  -965,  -860, -1417, 
     1526     120, -1417,  1014, -1417,   661,  1016, -1417,   672,  1023, -1417, 
     1527   -1417, -1417, -1417,   440,   397, -1417, -1417, -1417, -1417, -1417, 
     1528   -1417, -1417, -1417,  -404, -1417, -1417, -1417,  1253, -1417, -1417, 
     1529    1533, -1417, -1417, -1417, -1417, -1417,   720, -1417, -1417, -1417, 
     1530   -1417, -1417, -1417, -1417, -1417, -1417, -1417, -1013, -1417,  -107, 
     1531   -1417, -1416, -1417,  1310,  1128, -1417, -1417,   895,  -482, -1417, 
     1532    1037, -1417, -1417, -1417, -1417, -1417, -1417,   971,   907,   423, 
     1533     420, -1417, -1417,  1587,  -136, -1417, -1417, -1417, -1417, -1417, 
     1534   -1417, -1417, -1417, -1417, -1417,  -130, -1417, -1417, -1417, -1417, 
     1535     214, -1417, -1417, -1417,   961, -1417,   421,   505, -1417, -1417, 
     1536   -1417, -1417, -1417,   531 
    14591537}; 
    14601538 
     
    14631541{ 
    14641542      -1,     1,    13,    14,    15,    16,    46,    17,    18,    33, 
    1465      279,  1310,  1311,  1503,  1615,  1597,  1312,  1678,  1313,  1593, 
    1466     1594,  1314,  1595,  1315,  1679,  1705,  1706,  1707,   340,  1317, 
    1467     1318,  1482,   341,    51,    52,    99,   100,   101,   170,   171, 
    1468      373,   374,   375,   371,   372,   916,   917,   918,   102,   172, 
    1469      173,   240,  1229,  1230,   241,   975,   174,   104,   559,  1089, 
     1543     279,  1317,  1318,  1511,  1623,  1605,  1319,  1686,  1320,  1601, 
     1544    1602,  1321,  1603,  1322,  1687,  1713,  1714,  1715,   340,  1324, 
     1545    1325,  1490,   341,    51,    52,    99,   100,   101,   170,   171, 
     1546     373,   374,   375,   371,   372,   919,   920,   921,   102,   172, 
     1547     173,   240,  1236,  1237,   241,   979,   174,   104,   559,  1093, 
    14701548     242,    19,    20,    44,    68,    67,    70,    72,    71,    69, 
    1471      214,   215,   243,   244,   676,   415,   245,   246,   417,   978, 
    1472     1281,   221,   222,   223,   401,   247,   248,   106,   311,   107, 
    1473      292,   293,   479,   480,   998,   999,   769,   518,   519,   520, 
    1474      521,   767,  1042,  1043,  1443,  1046,  1047,  1271,  1446,  1581, 
    1475     1582,   732,   733,   249,   250,   734,  1242,  1243,  1244,   251, 
    1476      406,   252,   684,   407,   408,   409,  1204,  1205,   108,   109, 
    1477     1053,   523,   524,   525,   782,  1275,  1276,   785,   786,   795, 
    1478      787,  1461,  1462,   735,   110,  1055,  1279,  1409,  1410,  1411, 
    1479     1412,  1413,  1414,  1415,  1416,  1417,  1418,  1419,  1420,  1421, 
    1480     1422,  1456,   111,   526,   313,   528,   529,   112,   722,   493, 
    1481      494,   295,   296,   736,   297,   298,   486,   487,  1002,   737, 
    1482     1008,  1238,   738,   739,   113,   114,  1060,   793,  1282,  1591, 
    1483      115,   272,  1212,   697,   698,   116,   117,  1061,   286,   796, 
    1484      797,   798,   799,    53,   119,   801,   535,   536,  1065,  1066, 
    1485      120,  1219,   989,   990,   121,   275,   276,   459,  1213,   700, 
    1486      122,   288,  1222,   476,   800,   495,   995,  1566,   716,   717, 
    1487     1220,   253,   539,   124,   861,  1133,  1134,   628,   900,   901, 
    1488     1634,   898,   125,   514,   126,   323,   127,   501,   489,   128, 
    1489      129,   130,   752,   753,  1028,   754,   175,   586,  1517,  1108, 
    1490     1337,  1338,  1635,  1514,   864,   865,   866,  1110,  1341,  1342, 
    1491     1343,  1344,  1070,   176,   606,  1528,   912,  1145,  1355,  1356, 
     1549     214,   215,   243,   244,   677,   415,   245,   246,   417,   982, 
     1550    1288,   221,   222,   223,   401,   247,   248,   106,   311,   107, 
     1551     292,   293,   479,   480,  1002,  1003,   770,   518,   519,   520, 
     1552     521,   768,  1046,  1047,  1451,  1050,  1051,  1278,  1454,  1589, 
     1553    1590,   733,   734,   249,   250,   735,  1249,  1250,  1251,   251, 
     1554     406,   252,   685,   407,   408,   409,  1211,  1212,   108,   109, 
     1555    1057,   523,   524,   525,   783,  1282,  1283,   786,   787,   796, 
     1556     788,  1469,  1470,   736,   110,  1059,  1286,  1417,  1418,  1419, 
     1557    1420,  1421,  1422,  1423,  1424,  1425,  1426,  1427,  1428,  1429, 
     1558    1430,  1464,   111,   526,   313,   528,   529,   112,   723,   493, 
     1559     494,   295,   296,   737,   297,   298,   486,   487,  1006,   738, 
     1560    1012,  1245,   739,   740,   113,   114,  1064,   794,  1289,  1599, 
     1561     115,   272,  1219,   698,   699,   116,   117,  1065,   286,   797, 
     1562     798,   799,   800,    53,   119,   802,   535,   536,  1069,  1070, 
     1563     120,  1226,   993,   994,   121,   275,   276,   459,  1220,   701, 
     1564     122,   288,  1229,   476,   801,   495,   999,  1574,   717,   718, 
     1565    1227,   253,   539,   124,   862,  1138,  1139,   629,   903,   904, 
     1566    1642,   901,   125,   514,   126,   323,   127,   501,   489,   128, 
     1567     129,   130,   753,   754,  1032,   755,   175,   586,  1525,  1112, 
     1568    1344,  1345,  1643,  1522,   865,   866,   867,  1114,  1348,  1349, 
     1569    1350,  1351,  1074,   176,   606,  1536,   915,  1151,  1362,  1363, 
    14921570     254,   255,   256,   257,   258,   425,   428,   259,   260,   447, 
    14931571     261,   448,   262,   263,   264,   265,   266,   450,   452,   455, 
    1494      267,  1111,  1112,   268,   515,   354,  1424,  1210,   364,   365, 
    1495      366,   367,   177,   178,   320,   547,   548,   549,   550,  1247, 
    1496      542,   543,  1248,   179,   180,   384,   643,   942,   181,   644, 
    1497      645,   581,   943,  1175,  1176,   707,   324,   325,   182,   134, 
     1572     267,  1115,  1116,   268,   515,   354,  1432,  1217,   364,   365, 
     1573     366,   367,   177,   178,   320,   547,   548,   549,   550,  1254, 
     1574     542,   543,  1255,   179,   180,   384,   644,   946,   181,   645, 
     1575     646,   581,   947,  1182,  1183,   708,   324,   325,   182,   134, 
    14981576     135,   561,   136,   280,   465,   326,   562,   563,   137,   138, 
    1499      564,   830,   139,   565,   566,  1090,   343,   183,   184,   570, 
    1500      571,   850,   851,   141,   572,   852,  1097,   185,   186,   386, 
    1501      387,   187,  1529,  1106,   388,   651,   948,  1184,   648,   944, 
    1502     1180,  1181,  1182,   188,   189,   190,   191,   192,   368,   629, 
    1503      630,   631,   193,   587,  1347,   878,   879,  1113,   902,   194, 
    1504      923,  1159,  1160,   195,  1167,  1373,   196,  1163,  1370,   197, 
    1505      632,   633,   634,   635,  1168,  1169,  1031,  1032,  1033,  1261, 
    1506     1262,  1573,   198,   603,   604,   199,   595,   596,   200,  1351, 
    1507     1639,   352,   892,   893,   377,    21,   331,   152,    22,    66, 
    1508      578,  1512,  1103,  1333,   153,   332,   333,   334,    54,   329, 
    1509       55,  1331,  1688,   575,  1625,    23,    56,    24,    65,   612, 
    1510      613,  1530,  1150,  1360,   855,  1101,  1329,  1626,  1627,  1628, 
    1511     1629,   530,   145,   283,   284,   146,   471,   472,   270,   695, 
    1512      201,   390,   949,   654,  1389,   202,   638,   271,   954,   955, 
    1513      956,    25,    26,    27,    28,    29,   658,  1547,   207,   959, 
    1514     1392,  1393,   660,  1650,  1194,    30,    31,   657,   205,   662, 
    1515     1548,  1196,   392,   656,   960,   961,   962,   203,   154,   576, 
    1516      349,  1086,  1592,   608 
     1577     564,   831,   139,   565,   566,  1094,   343,   183,   184,   570, 
     1578     571,   851,   852,   141,   572,   853,  1101,   185,   186,   386, 
     1579     387,   187,  1537,  1110,   388,   652,   952,  1191,   649,   948, 
     1580    1187,  1188,  1189,   188,   189,   190,   191,   192,   368,   630, 
     1581     631,   632,   193,   587,  1354,   880,   881,  1117,   905,   194, 
     1582     926,  1166,  1167,   195,  1174,  1381,   196,  1170,  1378,   197, 
     1583     633,   634,   635,   636,  1175,  1176,  1035,  1036,  1037,  1268, 
     1584    1269,  1581,   198,   603,   604,   199,   595,   596,   200,  1358, 
     1585    1647,   352,   895,   896,   377,    21,   331,   152,    22,    66, 
     1586     578,  1520,  1107,  1340,   153,   332,   333,   334,    54,   329, 
     1587      55,  1338,  1696,   575,  1633,    23,    56,    24,    65,   612, 
     1588     613,  1538,  1156,  1367,   856,  1105,  1336,  1634,  1635,  1636, 
     1589    1637,   530,   145,   283,   284,   146,   471,   472,   270,   696, 
     1590     201,   390,   953,   655,  1397,   202,   639,   271,   958,   959, 
     1591     960,    25,    26,    27,    28,    29,   659,  1555,   207,   963, 
     1592    1400,  1401,   661,  1658,  1201,    30,    31,   658,   205,   663, 
     1593    1556,  1203,   392,   657,   964,   965,   966,   203,   154,   576, 
     1594     349,  1090,  1600,   608 
    15171595}; 
    15181596 
     
    15221600static const yytype_int16 yytable[] = 
    15231601{ 
    1524       43,   398,   363,   488,   702,   491,   131,   103,   641,   290, 
    1525      701,   150,   404,   642,   477,   355,   357,   327,   951,   105, 
    1526      335,   742,   362,   336,   105,   481,  1151,  1003,   723,   105, 
    1527      105,  1105,   490,   400,   328,   553,   269,   813,   911,   143, 
    1528     1235,    98,  1237,   485,   312,   509,    98,   363,   414,   142, 
    1529      416,    98,    98,  1214,   131,   103,   729,  1128,  1129,   951, 
    1530      118,   105,   239,  1330,  1164,   973,   849,   105,   724,   429, 
    1531     1260,   105,   430,   432,   545,  1170,  1170,  1114,  1115,  1116, 
    1532     1177,   897,   314,    98,  1121,  1381,  -182,   143,   376,    98, 
    1533      907,  1452,   418,    98,   421,  1457,  1630,   142,  1463,   212, 
    1534     1023,  1448,  -525,   219,  1327,   668,   808,  1007,   118,   810, 
    1535      277,  -195,   460,   431,   291,   933,  1172,  1459,   522,   151, 
    1536     1447,   468,   637,  1586,   492,   711,   492,   758,   803,    32, 
    1537     1657,     4,  -195,     4,   937,  1263,  1272,  1372,   557,   105, 
    1538     1449,   903,     4,    47,   909,  -412,     4,  -413,     4,     4, 
    1539     1657,   913,     4,    34,   492,     4,     4,     4,     4,   508, 
    1540      558,    98,   934,   934,   414,   981,   416,   414,   703,   416, 
    1541      704,     8,  -195,     8,  1026,     4,  1362,  1024,  1123,  1138, 
    1542       35,   433,     8,   269,   829,  -412,     8,  -413,     8,     8, 
    1543     1188,   665,     8,  1322,  1198,     8,     8,     8,     8,   335, 
    1544     1200,  1188,   336,  1224,   594,  1288,  1260,   602,   418,  1367, 
    1545     -732,   418,   681,  1382,  1401,     8,   414,  1433,   416,   913, 
    1546     1518,  1699,   346,    49,   573,  1579,   413,   646,   765,   957, 
    1547      555,   679,   432,  -542,   508,   508,   508,   977,  1658,   685, 
    1548      474,   376,   685,  1672,   475,   432,   517,   227,   228,  -476, 
    1549     1561,  -542,   534,   227,   228,  1301,   783,  1296,  1658,  1460, 
    1550      418,   474,  -766,  1268,   991,   475,  -266,   503,   464,  1328, 
    1551     -339,   385,   213,   516,  1448,   302,   220,  1630,  1206,   614, 
    1552      310,   652,   546,    98,   647,   516,   422,   531,   532,   302, 
    1553      376,  1544,   105,  1447,  -525,   862,  1005,   669,   809,  -525, 
    1554     1348,   811,  -766,  -195,  1441,    12,  -195,    12,   727,   412, 
    1555      730,   728,  1380,  1449,    98,   862,    12,    48,   148,  -412, 
    1556       12,  -413,    12,    12,   863,  1027,    12,  1345,  1335,    12, 
    1557       12,    12,    12,   904,    73,   756,   910,    42,   640,   577, 
    1558      433,   105,   413,   914,   863,   413,  1096,    74,   607,    12, 
    1559      132,   105,   741,   688,   935,   936,   649,   982,    92,    93, 
    1560      927,    95,   269,    98,   973,    42,  1122,  1580,   506,  1025, 
    1561     1124,  1139,  1127,    98,  1241,  1130,   574,  1336,    75,  1136, 
    1562      766,  -197,  1189,   269,   269,  -542,  1199,   318,  1448,   274, 
    1563     1661,   281,  1201,  1208,   413,  1225,  1561,  1289,   132,   302, 
    1564      958,  1368,   659,   661,  1335,  1383,  1402,  1675,  1448,  1434, 
    1565      239,  1504,  1519,  1700,    42,  1269,    89,   235,   745,   747, 
    1566       42,   236,   287,    42,   133,   204,   105,   236,   282,     4, 
    1567      488,   140,   491,  1352,   319,    89,  -766,   230,   877,   891, 
    1568      894,    97,   843,   506,   506,   506,   144,   639,   699,   905, 
    1569     1009,   967,   481,  1336,   517,   970,   971,  1013,   969,   490, 
    1570       97,  1563,   105,   105,   731,   853,   462,   463,     4,     8, 
    1571      485,  1553,   133,  1632,   508,   285,   818,   919,  1523,   140, 
    1572      920,  1260,  1353,  1352,    98,    98,   726,   610,   234,   976, 
    1573      751,   730,   430,  1587,   144,  1588,     4,   363,     4,  1044, 
    1574      429,   363,   363,   430,    42,   147,     4,   206,     8,  1513, 
    1575       64,  1170,  -466,   533,   828,   824,   235,   285,   105,   483, 
    1576      236,   794,   846,   783,   347,    76,  1513,   105,   702,  1223, 
    1577      348,   742,  1353,   741,   701,   742,     8,     4,     8,     4, 
    1578       98,    42,    11,    98,   431,   -89,     8,   838,   -89,    98, 
    1579      498,   499,   951,   147,  1015,  1014,   484,   833,   105,   105, 
    1580      236,   399,  1292,  1072,   833,  1074,  1234,   105,   105,    58, 
    1581      729,    59,  1533,   498,   499,   699,  1354,     8,    42,     8, 
    1582       98,    98,   434,   435,   436,   437,   438,   439,   440,    98, 
    1583       98,    47,   105,   556,   557,   699, -1022,   344, -1022,   496, 
    1584     1659,  1563,   -90,    12,   301,   -90,   105,  1563,     4,  1151, 
    1585      500,   227,   228,  1673,    98,  1674,   558,   302,   497,     4, 
    1586     1659,     4,   310,   825,    89,  -236,  -236,   939,    98,   269, 
    1587      151,     4,   302,   500,   426,   427,   945,  1011,  -541,  -935, 
    1588       89,  1105,    12,   950,   302,  1478,  1479,  1366,     8,    97, 
    1589    -1022,   -61, -1022,   895,     9,   230,  1012,    92,    93,     8, 
    1590       95,     8,   906,  1006,    42,    97,  1048,   974,    11,  -541, 
    1591       12,     8,    12,   357,  1080,   686,   315,    42,   687,   294, 
    1592       12,   155,    60,   506,   950,   930,   931,   932,   321, -1023, 
    1593      105, -1023,   703, -1022,   704, -1022,   569,  1215,  1095,  1394, 
    1594      -93,  1395,   988,   -93,   492,  1093,   234,  1325,     9,   411, 
    1595     1000,    12,    98,    12,   316,    92,    93,   230,    95,  -510, 
    1596      317,   304,    42,  -510,  1119,  1091,   305,   516,   322,   306, 
    1597      453,   454,   441,   442,   443,   444,    60,  1131,   534,   -92, 
    1598       11,   330,  1471,    82,    83,  1098,  1571,     9,   412,  1151, 
    1599     -137,     9,    57,  1407,   594,   337,  1045,    62,   307,    63, 
    1600      602,  1453,  1454,  1455,   369,    48,   445,   446,   234,   991, 
    1601     1071,   546,   338,   546,  1158,    60,  1376,    92,    93,    60, 
    1602       95,   235,    12,   919,    42,   236,   920,  1378,   508,  1539, 
    1603       11,  -276,   105,    12,    11,    12,   350,  1241,   351,  1622, 
    1604      358,   641,   674,   675,  -946,    12,   642,    36,    37,    38, 
    1605       39,    89,  1021,   640,    98,    40,   862,   359,  1233,   370, 
    1606      416,    41,   727,    42,   730,   728,   105,   385,    92,    93, 
    1607      389,    95,   391,    11,  1117,    42,    97,    11,    11,  -277, 
    1608      414,   393,   416,   105,   396,   863,   411,  -947,    98,   105, 
    1609      105,   105,   105,   862,   105,   412,   105,   105,   756,  1475, 
    1610      569,   848,   741,  1483,   420,    98,   741,  1173,  1174,  1680, 
    1611     1681,    98,    98,    98,    98,  -223,    98,  1152,    98,    98, 
    1612      424, -1022,   863, -1022,   418,   208,   209,  1161,   449,   105, 
    1613      451,    82,    83,  1038,  1039,    89,   414,   457,   416,   394, 
    1614      395,   458,  1146,   105,   105,     5, -1022,     6, -1022,   560, 
    1615      567,    98,    92,    93,     7,    95,   512,   282,   470,    42, 
    1616       97,   473,   639,  1040,   482,    98,    98,    36,    37,    38, 
    1617       39,  1041,   513,   227,   228,    40,   602,  1120,   527,     9, 
    1618      418,    41,   551,   554,   556,   569,   702,   516,   588,  1426, 
    1619      105,  1135,   701,   -97,   -97,    42,   -97,   653,   616,   663, 
    1620      -97,  1203,   664,   -97,     9,   666,   667,    60,   672,   269, 
    1621     -100,  -100,   699,  -100,   877,   673,  -234,  -100,   731,  -229, 
    1622     -100,   678,   680,  -224,   742,  1153,   210,   211,   694,   891, 
    1623      696,   683,    10,   706,   708,   239,  1228,   506,  1294,   239, 
    1624      726,   273,  1044,   713,   641,   278,  1364,   714,   715,   642, 
    1625      718,   289,   720,   751,  1429,   227,   228,   721,   413,   760, 
    1626      761,   -99,   -99,  1476,   -99,    11,   763,  1476,   -99,   304, 
    1627      764,   -99,   768,   784,   305,  -138,   788,   378,  1431,   230, 
    1628      730,   430,   789,   105,  1152,   791,   792,   379,   805,   380, 
    1629       11,   794,   381,   382,    92,    93,   105,    95,   802,   807, 
    1630      363,    42,   815,   294,   231,    98,   307,   821,   819,   820, 
    1631      847,   383,   546,   854,  1316,    77,   607,   856,    98,   345, 
    1632      232,   233,   741,   858,    92,    93,   859,    95,   860,   360, 
    1633      234,   308,   915,   105,   400,   924,   699,   922,   921,    92, 
    1634       93,   941,    95,   235,   742,   928,    42,   236,   237,   947, 
    1635      703,   748,   704,   965,   966,    98,   238,   968,   226,   972, 
    1636      105,   230,    92,    93,   105,    95,   227,   228,   749,    42, 
    1637      440,   640,  -230,   699,  1481,    93,   980,    95,   159,   983, 
    1638      984,    42,    98,  -197,   105,   993,    98,   992,   161,   162, 
    1639      994,   163,   825,  1006,   164,   997,  1007,   822,   166,   823, 
    1640     1010,  -449,   232,   233,    92,    93,    98,    95,  1016,  1034, 
    1641     1050,    42,   234,  1165,  1051,  1052,  1386,   950,  1054,  1058, 
    1642     1059,    92,    93,  1423,    95,   235,  1062,  1064,    42,   236, 
    1643     1227,  1068,  1076,  1079,  1082,  1087,   461,    89,   216,   217, 
    1644      218,   466,   224,   307,   469,  1099,  1100,   988,  1102,  1109, 
    1645     1107,   478,  1144,  1118,    92,    93,  1430,    95,  1158,  1365, 
    1646     1126,    42,    97,  1149,  1187,   502,   304,  1190,   511,  1191, 
    1647     1192,   305,   230,  1423,  1361,  1193,  1197,  1217,  1423,  1195, 
    1648      639,  1202,  1423,  1207,   379,  1423,   380,  1216,   991,   381, 
    1649      382,  1218,  1226,  1250,  1071,  1723,  1252,   231,  1280,  1283, 
    1650     1267,  1045,   750,   307,   583,   584,  1266,   585,   383,  1270, 
    1651     1287,  1290,  1291,   232,   233,  1323,   597,  1332,   605,  1340, 
    1652     1359,   105,  1349,   234,  1357,   105,  1358,  1363,  1263,   609, 
    1653     1372,   611,    92,    93,  1375,    95,   235,  1384,  1391,    42, 
    1654      236,   237,   105,    98,  1397,  1396,  1071,    98,  1398,   238, 
    1655     1399,   655,   230,  1403,   305,  1432,  1437,  1088,  1439,   105, 
    1656     -524,  1440,  1442,  1464,    98,  1465,  1474,   379,  1477,   380, 
    1657     1480,  1506,   381,   382,   640,  1508,  1469,   231,  1652,   105, 
    1658     1472,    98,  1509,  1653,  1510,  1505,   307,   105,  1515,  1516, 
    1659     1527,   383,  1521,   232,   233,  1668,  1526,  1546,  1550,  1551, 
    1660     1554,    98,  1552,   234,  1555,  1556,  1557,  1559,   105,    98, 
    1661     1558,  1560,    92,    93,  1565,    95,   235,  1564,  -382,    42, 
    1662      236,   237,  1423,  1567,   363,  1576,  1577,  1583,   709,   238, 
    1663      699,  1578,   712,  1584,  1585,  1590,  -255,   123,   225,  1646, 
    1664     1645,   363,   123,   719,  1624,   226,  1423,   123,   123,  1631, 
    1665     1654,  1665,  1328,   227,   228,   229,  1648,  1656,  1445,  1476, 
    1666      744,   746,   239,   640,   757,  1532,  1664,   105,  1669,  1203, 
    1667      759,  1670,  1689,  1671,  1692,  1694,   105,  1695,  1697,   299, 
    1668     1698,  1702,  1715,   639,  1709,   123,  1710,   790,  1703,   299, 
    1669     1711,  1718,  1721,  1725,  1722,  1728,   804,  1731,    98,  1733, 
    1670     1152,    78,  1676,  1729,  1231,   806,  1148,   402,  1232,   303, 
    1671      677,   996,   105,   814,  1450,  1427,    50,   770,   817,  1451, 
    1672     1444,   546,   105,  1575,  1458,    45,  1236,  1717,   403,   682, 
    1673     1569,  1568,  1277,   105,    98,   423,  1662,   857,  1056,   670, 
    1674     1663,  1666,  1562,  1057,    98,   725,  1239,  1001,  1249,  1211, 
    1675     1286,  1067,  1716,  1405,   269,    98,   705,   123,  1667,   230, 
    1676     1423,  1423,  1423,  1466,   816,  1221,  1255,  1137,  1423,   826, 
    1677     1636,  1640,   639,   363,  1525,  1638,  1339,  1520,   827,  1641, 
    1678     1423,  1423,   689,   456,   231,   690,   691,   105,  1037,  1073, 
    1679      692,   544,  1075,  1069,  1423,   693,   844,   568,   938,   845, 
    1680      232,   233,   831,  1543,   650,   832,   926,  1125,   825,   946, 
    1681      234,   834,  1346,     2,     3,   908,   835,   836,   963,    92, 
    1682       93,  1677,    95,   235,   837,   929,    42,   236,   237,  1162, 
    1683     1534,  1537,  1140,  1171,   636,  1572,   238,     4,   839,  1142, 
    1684     1152,     5, -1022,     6, -1022,  1350,   579,   840,   149,   841, 
    1685        7,   467,   105,  1713,   225,   987,   710,  1696,   979,   842, 
    1686      940,   226,  1388,  1387,    61,   964,  1390,  1549,  1320,   227, 
    1687      228,   229,  1701,     0,    98,     0,     0,     8,  1019,     0, 
    1688        0,     0,     0,  1004,     0,   226,     0,     0,     0,     0, 
     1602      43,   488,   363,   703,   269,   404,   131,   477,   702,   398, 
     1603     103,   105,   491,   290,   150,   743,   105,   642,   335,  1157, 
     1604     643,   105,   105,   955,   336,   481,  1007,   724,  1109,   914, 
     1605     142,  1242,   327,   400,   414,   312,   553,   814,   355,   357, 
     1606     143,    98,   490,   328,  1244,   485,    98,   363,   977,   545, 
     1607    1171,    98,    98,   105,   131,   429,  1221,   416,   103,   105, 
     1608     900,   118,   239,   105,   955,   730,   509,   911,  1267,   910, 
     1609    1133,  1134,   430,   432,   850,  1118,  1119,  1120,   142,   725, 
     1610    1177,  1177,  1125,    98,  1456,   362,  1184,   376,   143,    98, 
     1611     314,  1337,   937,    98,   936,  1460,  1389,   277,  -182,  1465, 
     1612    1638,   212,  1471,   227,   228,    47,   460,  1179,   421,   118, 
     1613    -525,  1455,   669,   151,  -195,   291,  1342,  1457,     4,  1030, 
     1614     468,  1027,  1359,  1334,   492,   712,   809,     4,   492,  1467, 
     1615     811,   105,   906,   912,   759,  -195,   385,  -732,  1308,   916, 
     1616     938,     4,   647,   638,   938,  -412,     4,   985,   347,  -413, 
     1617     414,   269,   132,   414,   348,     4,  1013,  1028,     8,   418, 
     1618     557,    98,   804,  1017,    32,  1343,   704,     8,   219,  1128, 
     1619     941,  1360,  1144,   416,  1195,  -195,   416,   705,  1205,  1207, 
     1620     431,     8,   558,     4,   666,  -412,     8,  1329,  1270,  -413, 
     1621    1279,     4,  1195,   830,  1380,     8,   492,   335,  1231,   648, 
     1622     132,  1295,   414,   336,  1375,   682,  1390,  1267,  1409,     4, 
     1623    1441,     4,     4,   916,  1526,     4,   346,     4,    34,  1707, 
     1624      42,   650,   508,     8,   522,   416,   413,   594,    35,   433, 
     1625     602,     8,   432,  1587,  1569,   503,  1011,   517,   680,   686, 
     1626     376,   516,   686,   534,   961,   432,     4,   981,  1303,     8, 
     1627     546,     8,     8,   516,    49,     8,   784,     8,  1456,   227, 
     1628     228,  1369,   474,   995,  -542,   573,   475,  -266,   464,   766, 
     1629    1031,  1468,  1275,   235,   213,   418,    42,   236,   418,    48, 
     1630    1213,  1638,  -542,    98,   105,  1455,     8,   302,  1335,   376, 
     1631     653,  1457,    12,   863,   728,   531,   532,   508,   508,   508, 
     1632     422,    12,  -525,  1552,   670,  1449,  -195,  -525,  1009,  -195, 
     1633     302,   729,   412,   863,    98,    12,  1355,   731,   810,  -412, 
     1634      12,  1388,   812,  -413,   907,   913,   302,   418,  1352,    12, 
     1635     269,   917,   939,   105,   864,   757,   940,  -766,   641,   986, 
     1636     577,   220,   413,   105,  1127,   413,  1126,   133,   607,  1029, 
     1637     977,   269,   269,  1132,   864,  1100,  1135,    12,  1142,  1594, 
     1638    1141,  1129,   506,    98,  1145,    12,  1196,    58,   533,    59, 
     1639    1206,  1208,  1456,    98,  1669,  1588,  -339,  -766,   140,  1665, 
     1640    1569,   930,  1248,    12,  1215,    12,    12,     4,   433,    12, 
     1641    1232,    12,  1456,  1296,   413,   133,  1376,    11,  1391,  1665, 
     1642    1410,   689,  1442,   660,   662,  1512,  1527,   556,   557,   310, 
     1643     239,  1708,  1683,  -476,   344,   962,  -542,   574,   105,   742, 
     1644      12,   767,   746,   748,  1276,    73,   140,     8,     4,   488, 
     1645     558,  1666,  1571,   236,   498,   499,    42,   506,   506,   506, 
     1646     491,   640,     4,    92,    93,   517,    95,  1342,   700,   144, 
     1647      42,  1666,   973,   481,   105,   105,   732,   844,    74,   610, 
     1648     971,   879,   894,   897,   974,   975,     4,  1531,     8,     4, 
     1649     490,   281,   908,   485,   854,   922,   980,   555,  1561,  1680, 
     1650     819,   923,     8,  1267,    98,    98,   727,   429,  1595,    75, 
     1651     752,   227,   228,   430,   500,     4,  1343,   144,   363,   731, 
     1652    1048,  1596,   363,   363,   430,  1640,     8,   230,   282,     8, 
     1653     105,  -766,   236,   399,   829,   285,  1359,   318,   825,   105, 
     1654    1177,   795,   498,   499,   784,   847,   614,  1521,   496,   743, 
     1655       4,   703,  1230,   743,   148,     8,   702,   508,   834,  1076, 
     1656      98,  1078,    42,    98,  1521,   834,  -197,   497,   839,    98, 
     1657     105,   105,  -466,   227,   228,   949,  1018,   147,   234,   105, 
     1658     105,    12,  1019,   955,   319,  1360,  1299,   462,   463,     4, 
     1659       8,  1667,  1571,  1361,    42,   700,  1541,   204,  1571,  1241, 
     1660      98,    98,   500,   730,   105,   105,    42,    47,   294,    98, 
     1661      98,  1667, -1026,   206, -1026,   700,  1052,   230,   269,   105, 
     1662      89,   742,    12,   227,   228,   147,   274,  1157,  1681,     8, 
     1663    1084,    42,   431,     4,    98,    98,    12,   826,   304,   426, 
     1664     427,  1682,   231,   305,   151,    97,   306,     4,   943,    98, 
     1665    1374, -1027,  1373, -1027,  1097,   483,   285,  1332,   232,   233, 
     1666      12,   287,    42,    12,   954,  1109,   302,   898,   234,   301, 
     1667       9,  -236,  -541,     8,   302,   307,   909,    92,    93,   230, 
     1668      95,   235,    89,  1384,    42,   236,   237,     8,   978,    12, 
     1669    1486,  1487,   484,   492,   238,    64,   -61,   506,    60,   933, 
     1670     934,   935,   474,   105,   310,   954,   475,    97,  -510,     9, 
     1671      76,    89,  -510,  -236,   704,  1015,   516,   357,  1386,    11, 
     1672     232,   233,  1222,   992,    12,   705,  -939,   453,   454,   230, 
     1673     234,  1004,   302,    98,  1016,  1010,    97,    60,   315,    92, 
     1674      93,  -541,    95,   235,    82,    83,    42,   236,  1234,   -93, 
     1675     534,   235,   -93,    11,  -276,   236,    11,  1547,   411,  1075, 
     1676     546,  1095,   546,    12,    57,   316,  -137,  1157,  1123,    62, 
     1677     -89,    63,  1579,   -89,   569,  1102,  1099,  1049,   317,  1415, 
     1678     234,    48,  1136,   -90,   687,   230,   -90,   688,   321,    92, 
     1679      93,    89,    95,   235,   995,    11,    42,   236,   675,   676, 
     1680     594,  1630,    11,  -277,   922,   105,   602,    12,    92,    93, 
     1681     923,    95,  1461,  1462,  1463,    42,    97,  1402,   330,  1403, 
     1682    1165,    12,   -92,  1121,   369,  1479,   322,  1025,  1240,  1248, 
     1683     337,   412,   728,   370,   641,    98,   234,   642,   863,   105, 
     1684     643,   569,   849,  1180,  1181,    92,    93,   338,    95,   729, 
     1685     414,   416,    42,  1688,  1689,   731,   105,   105,     5, -1026, 
     1686       6, -1026,   155,   105,   105,   105,   105,     7,   105,    98, 
     1687     105,   105,   105,   416,   350,   508,   351,   863,  1168,   864, 
     1688     208,   209,   757,   394,   395,  1483,    98,    98,   358,  1491, 
     1689     560,   567,   359,    98,    98,    98,    98,   385,    98,   396, 
     1690      98,    98,    98,  1158,   105,   389,   414,   391,   393,   411, 
     1691     434,   435,   436,   437,   438,   439,   440,     9,   864,   105, 
     1692     105,   420, -1026,    89, -1026,  1152,   412,  -223,   424,   416, 
     1693      36,    37,    38,    39,    98,   449,   451,   640,    40,   516, 
     1694      92,    93,   457,    95,    41,    10,    42,    42,    97,    98, 
     1695      98,   458,  1124,   742,   216,   217,   218,   742,   224,   282, 
     1696   -1026,   269, -1026,   470,   473,   482,   105,  1140,   512,  1434, 
     1697     513,   527,   551,   703,   554,   418,   556,   569,   702,   588, 
     1698       9,   -97,   -97,   602,   -97,  1210,    42, -1026,   -97, -1026, 
     1699     654,   -97,    89,   616,   732,   664,   700,    36,    37,    38, 
     1700      39,   665,  1159,    11,   667,    40,   743,   668,    60,    92, 
     1701      93,    41,    95,   673,   674,   506,    42,    97,     9,   239, 
     1702    1235,  -234,   879,   239,   727,   684,  1301,  -229,    77,  1048, 
     1703     679,   418,   681,  -100,  -100,  -224,  -100,   752,   894,   695, 
     1704    -100,   642,   413,  -100,   643,     9,    60,   707,  1484,  1437, 
     1705     697,  1439,  1484,   709,   714,  1371,   715,   716,   719,   105, 
     1706     441,   442,   443,   444,   546,   721,    11,   722,   430,   761, 
     1707     762,  1158,   105,    60,   731,   795,  -950,    82,    83,  1042, 
     1708    1043,   -99,   -99,   764,   -99,   765,   769,   363,   -99,    98, 
     1709     789,   -99,   785,   790,   445,   446,   225,   792,  1323,   793, 
     1710     607,   806,    98,   226,    11,   803,   808,   820,   816,  1044, 
     1711     105,   227,   228,   229,  -951,    92,    93,  1045,    95,   821, 
     1712     700,   400,    42,   848,   294,   857,   743,    92,    93,   855, 
     1713      95,    11,    92,    93,   308,    95,   704,   859,   105,    42, 
     1714      98,  -138,   105,   105,   860,   861,   230,   705,    92,    93, 
     1715     918,    95,   924,  1489,    93,    42,    95,  1172,   641,   700, 
     1716      42,   925,   927,   105,   305,   402,   931,  1092,    98,   945, 
     1717     826,   231,    98,    98,   951,   969,   742,   379,  1431,   380, 
     1718     210,   211,   381,   382,   970,   976,   403,   232,   233,  -230, 
     1719     972,   440,   984,    98,   987,   273,   307,   234,   988,   278, 
     1720     996,   383,   997,  1394,   954,   289,    92,    93,   998,    95, 
     1721     235,  1001,  1010,    42,   236,   237,  1011,   230,  1014,  -449, 
     1722    1020,  1038,  1054,   238,  1055,  1056,  1063,  1058,  1431,  1062, 
     1723    1066,  1068,  1072,  1431,   992,  1080,  1083,  1431,  1086,  1372, 
     1724    1431,  1091,   231,  1438,   307,  1113,  1103,  1104,  1106,  1075, 
     1725    1111,  1122,  1150,  1131,  1155,  1194,  1197,  1198,   232,   233, 
     1726    1199,   640,  1200,  1202,  1204,  1209,  1214,   772,   234,  1165, 
     1727    1223,  1224,  1225,   345,   995,  1233,  1257,    92,    93,  1259, 
     1728      95,   235,  1731,   360,    42,   236,   237,  1274,  1049,  1290, 
     1729    1273,   304,  1277,  1287,   238,  1297,   305,   123,  1294,   378, 
     1730     105,  1075,   123,  1298,   105,  1330,  1339,   123,   123,   379, 
     1731    1370,   380,  1366,  1347,   381,   382,  1356,  1364,  1365,  1270, 
     1732    1380,   105,  1383,  1392,  1399,  1405,  1404,  1406,   307,  1407, 
     1733      98,  1411,  1440,   383,    98,  -524,  1447,  1445,   105,   299, 
     1734    1448,    82,    83,   773,   774,   123,  1472,  1450,  1473,   299, 
     1735    1477,    98,  1488,  1480,  1482,  1485,  1516,  1513,  1560,   105, 
     1736    1514,  1517,   641,  1518,  1661,  1524,  1523,   105,    98,  1529, 
     1737    1535,  1534,  1562,   775,  1660,   776,   777,   778,  1431,  1554, 
     1738     779,   780,  1558,   781,   782,  1559,  1563,  1564,   105,    98, 
     1739     461,  1676,  1565,  1572,  1566,   466,  1567,    98,   469,  1568, 
     1740    1573,  1575,  1431,  -382,  1584,   478,  1585,  1591,  1586,  1632, 
     1741    1592,  1593,   363,  1598,  -255,  1654,  1653,   123,   700,   502, 
     1742    1639,  1335,   511,  1662,  1677,  1656,  1453,  1664,  1672,   363, 
     1743    1673,  1678,  1679,  1697,  1700,  1702,  1703,  1705,  1706,  1723, 
     1744    1726,  1729,  1684,  1730,  1736,  1484,  1540,   105,  1710,  1711, 
     1745     239,   641,  1717,  1718,  1719,  1733,   105,  1210,   583,   584, 
     1746    1739,   585,  1741,    78,  1737,   640,  1238,  1154,   303,  1239, 
     1747     597,    50,   605,  1452,   678,  1458,  1435,   546,  1000,  1466, 
     1748     771,  1459,  1583,   609,    45,   611,    98,  1243,   304,   683, 
     1749    1577,  1158,   105,   305,  1576,  1670,  1368,  1060,  1284,  1671, 
     1750    1570,   671,   105,   423,  1005,   656,   379,  1674,   380,  1061, 
     1751     269,   381,   382,   105,  1256,  1246,  1431,  1431,  1431,   726, 
     1752    1293,  1218,    98,  1725,  1431,   307,  1071,  1474,  1724,  1413, 
     1753     383,  1675,    98,   706,  1143,  1228,  1431,  1431,   817,  1262, 
     1754     827,  1644,  1533,    98,  1346,  1648,  1646,   828,  1649,  1528, 
     1755    1431,   456,   690,   693,   640,   691,   692,  1041,  1077,  1073, 
     1756     651,   363,  1079,   538,   694,   845,   832,   105,   846,   833, 
     1757     123,     2,     3,   835,  1551,  1353,   929,  1130,  1542,   544, 
     1758     836,   637,   710,   932,  1169,  1178,   713,   837,  1580,   568, 
     1759     826,   838,  1545,  1148,   840,     4,   841,   720,  1146,     5, 
     1760   -1026,     6, -1026,   842,  1357,   749,   579,   149,     7,  1685, 
     1761    1721,   467,   226,  1704,   745,   747,   711,   843,   758,   123, 
     1762     227,   228,   750,   983,   760,   538,   538,   991,  1709,   299, 
     1763     944,  1158,   105,    61,  1395,     8,   225,  1557,  1396,  1398, 
     1764     968,   791,  1327,   226,     0,     0,     0,     0,     0,     0, 
     1765     805,   227,   228,   229,     0,     0,     0,     0,     9,   807, 
     1766       0,     0,    98,     0,     0,     0,     0,   815,     0,     0, 
     1767       0,     0,   818,     0,  1732,     0,     0,  1734,     0,     0, 
     1768       0,     0,     0,     0,     0,     0,    10,     0,     0,     0, 
     1769    1742,   858,     0,     0,     0,     0,     0,   105,     0,     0, 
     1770       0,  1492,  1493,  1494,  1495,  1496,  1497,     0,  1498,  1499, 
     1771    1500,  1501,  1502,  1503,   992,  1504,  1505,  1506,  1507,  1508, 
     1772       0,     0,     0,     0,     0,     0,   230,    98,     0,     0, 
     1773    1159,  1699,     0,     0,     0,     0,     0,     0,     0,     0, 
     1774     299,   299,   741,     0,    11,     0,     0,  -202,  -202,  -202, 
     1775    -202,   231,     0,   942,     0,  -202,   751,   230,     0,     0, 
     1776       0,  -202,     0,     0,   950,  1023,     0,   232,   233,    12, 
     1777       0,     0,   226,   967,     0,     0,     0,   234,     0,     0, 
     1778     227,   228,   231,     0,     0,     0,    92,    93,     0,    95, 
     1779     235,     0,     0,    42,   236,   237,   299,     0,   232,   233, 
     1780       0,     0,     0,   238,     0,   299,     0,     0,   234,     0, 
     1781       0,     0,     0,     0,     0,     0,     0,    92,    93,     0, 
     1782      95,   235,     0,     0,    42,   236,   237,     0,     0,     0, 
     1783       0,     0,     0,     0,   238,     0,   299,   299,  1008,     0, 
     1784       0,     0,     0,     0,     0,   299,   299,     0,     0,     0, 
     1785       0,  1185,     0,     0,     0,     0,     0,     0,   226,     0, 
     1786       0,  1021,     0,  1022,   538,     0,   227,   228,     0,     0, 
     1787     299,   299,     0,     0,     0,     0,     0,     0,  1040,     0, 
     1788       0,     0,     0,     0,  1053,   299,   230,     0,     0,     0, 
     1789       0,   681,  1509,  1510,     0,     0,     0,  1263,     0,     0, 
     1790     538,     0,     0,     0,   226,     0,     0,     0,   822,     0, 
     1791       0,   231,   227,   228,     0,     0,     0,  1067,     0,     0, 
     1792       0,     0,     0,     0,     0,     0,     0,   232,   233,  1081, 
     1793       0,     0,     0,     0,  1082,     0,  1085,   234,     0,     0, 
     1794       0,   538,     0,     0,     0,     0,    92,    93,     0,    95, 
     1795     235,     0,     0,    42,   236,   237,     0,     0,     0,     0, 
     1796       0,     0,     0,   238,  1098,     0,     0,     0,     0,   299, 
     1797       0,     0,   230,     0,     0,  1108,     0,     0,     0,   159, 
     1798       0,     0,     0,     0,  -197,     0,     0,     0,     0,   161, 
     1799     162,     0,   163,     0,     0,   164,   342,   231,   823,   166, 
     1800     824,     0,     0,     0,     0,     0,     0,   361,     0,     0, 
     1801       0,     0,     0,   232,   233,     0,     0,     0,   230,     0, 
     1802       0,     0,  1147,   234,     0,     0,     0,     0,  1149,     0, 
     1803       0,     0,    92,    93,     0,    95,   235,     0,    89,    42, 
     1804     236,   237,     0,   231,     0,     0,     0,     0,     0,   238, 
     1805       0,     0,     0,     0,     0,    92,    93,     0,    95,   232, 
     1806     233,     0,    42,    97,  1190,     0,     0,  1192,  1193,   234, 
     1807     410,   299,     0,     0,     0,     0,   419,     0,    92,    93, 
     1808       0,    95,   235,     0,     0,    42,   236,   237,     0,     0, 
     1809       0,   410,  1416,     0,     0,   238,     0,     0,     0,   226, 
     1810       0,     0,     0,     0,     0,   299,     0,   227,   228,     0, 
     1811       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
     1812       0,     0,   299,   299,     0,     0,     0,     0,     0,   299, 
     1813     299,   299,   299,     0,   299,     0,   299,   299,   299,     0, 
     1814       0,     0,     0,     0,   507,   510,     0,     0,     0,     0, 
     1815    1271,     0,     0,  1272,     0,     0,     0,   541,     0,     0, 
     1816     552,     0,     0,     0,     0,  1280,     0,  1281,     0,     0, 
     1817     123,     0,  1285,     0,     0,     0,   580,   582,     0,  1291, 
     1818    1292,     0,     0,   538,     0,   299,   299,     0,     0,     0, 
     1819       0,     0,   593,  1453,     0,   593,     0,     0,  1300,  1302, 
     1820     226,     0,     0,     0,     0,     0,     0,     0,   227,   228, 
     1821       0,     0,  1331,   230,  1333,   226,     0,   615,     0,   361, 
     1822     361,   507,     0,   227,   228,  1341,     0,     0,     0,     0, 
     1823       0,     0,     0,     0,     0,     0,     0,     0,   231,     0, 
     1824       0,     0,     0,     0,   672,     0,     0,     0,     0,     0, 
     1825       0,     0,     0,     0,   232,   233,   741,   300,     0,   538, 
     1826     741,  1160,  1161,     0,   234,     0,     0,   309,     0,  1162, 
     1827       0,  1163,  1164,    92,    93,     0,    95,   235,     0,     0, 
     1828      42,   236,   237,     0,     0,  1377,     0,     0,     0,  1379, 
     1829     238,     0,     0,  1382,     0,  1385,  1387,     0,     0,     0, 
     1830       0,     0,     0,     0,     0,     0,  1393,     0,     0,     0, 
     1831       0,     0,     0,     0,   230,     0,     0,     0,     0,     0, 
     1832       0,     0,     0,     0,     0,   299,     0,     0,     0,   230, 
     1833       0,     0,     0,     0,  1408,     0,     0,   744,   123,   231, 
     1834     756,  1414,  1668,     0,  1433,     0,     0,  1436,     0,   226, 
     1835       0,     0,   763,     0,   231,   232,   233,   227,   228,     0, 
     1836       0,     0,     0,     0,     0,   234,     0,     0,     0,     0, 
     1837     232,   233,  1443,     0,    92,    93,   299,    95,   235,  1712, 
     1838     234,    42,   236,   237,     0,     0,   226,     0,     0,    92, 
     1839      93,   238,    95,   235,   227,   228,    42,   236,   237,     0, 
     1840       0,     0,     0,     0,   299,     0,   238,     0,   299,   299, 
     1841       0,     0,     0,     0,  1475,     0,  1476,     0,     0,     0, 
     1842       0,     0,     0,     0,     0,     0,     0,     0,     0,   299, 
     1843       0,     0,     0,     0,  1727,     0,     0,     0,     0,   538, 
     1844     538,   226,     0,     0,     0,     0,     0,  1515,     0,   227, 
     1845     228,     0,     0,  1519,     0,     0,     0,     0,     0,   507, 
     1846       0,     0,     0,   230,     0,     0,     0,     0,     0,  1530, 
     1847       0,     0,     0,  1532,     0,     0,     0,     0,     0,     0, 
     1848       0,   540,     0,     0,     0,     0,     0,     0,   231,     0, 
     1849       0,  1543,     0,  1544,   957,     0,  1546,     0,  1548,  1549, 
     1850     230,  1550,     0,     0,   232,   233,     0,     0,     0,     0, 
     1851       0,     0,  1553,   410,   234,     0,     0,     0,     0,     0, 
     1852       0,     0,     0,    92,    93,   231,    95,   235,     0,     0, 
     1853      42,   236,   237,     0,     0,   957,     0,     0,     0,     0, 
     1854     238,   232,   233,   628,   628,     0,   989,     0,   990,     0, 
     1855       0,   234,     0,     0,     0,   230,     0,     0,     0,     0, 
     1856      92,    93,     0,    95,   235,  1582,     0,    42,   236,   237, 
     1857       0,     0,     0,     0,     0,     0,     0,   238,     0,     0, 
     1858     231,     0,     0,     0,     0,     0,     0,   299,  1024,     0, 
     1859    1026,     0,     0,     0,     0,     0,   232,   233,  1034,     0, 
     1860       0,  1039,     0,     0,   299,     0,   234,     0,     0,     0, 
     1861       0,     0,     0,     0,     0,    92,    93,     0,    95,   235, 
     1862       0,     0,    42,   236,   237,   299,     0,     0,     0,  1631, 
     1863       0,     0,   238,   299,     0,  1641,     0,     0,     0,     0, 
     1864    1645,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
     1865       0,  1650,  1651,  1652,     0,     0,     0,     0,   300,   300, 
     1866    1621,     0,  1655,     0,     0,     0,   226,     0,     0,     0, 
     1867    1657,     0,  1659,     0,   227,   228,     0,  1622,     0,     0, 
     1868       0,     0,     0,     0,     0,   538,   538,  1096,     0,     0, 
     1869       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
     1870       0,     0,     0,     0,     0,     0,     0,   507,   507,   507, 
     1871     507,     0,     0,  1597,   813,   507,     0,     0,     0,  1604, 
     1872       0,   507,   299,     0,     0,   226,     0,     0,     0,     0, 
    16891873       0,     0,     0,   227,   228,     0,     0,     0,     0,     0, 
    1690        9,     0,     0,   538,     0,     0,  1017,     0,  1018,     0, 
    1691      123,     0,     0,     0,     0,     0,     0,   105,  1724,     0, 
    1692        0,  1726,     0,  1036,     0,     0,   988,     0,    10,  1049, 
    1693        0,     0,     0,     0,  1734,     0,     0,     0,     0,    98, 
    1694        0,     0,     0,     0,     0,     0,     0,     0,  1153,  1691, 
    1695        0,     0,     0,     0,     0,     0,     0,     0,     0,   123, 
    1696        0,     0,  1063,     0,     0,   538,   538,     0,     0,   299, 
    1697        0,     0,     0,     0,  1077,   230,     0,     0,     0,  1078, 
    1698     1178,  1081,     0,     0,     0,     0,    11,   226,     0,  -202, 
    1699     -202,  -202,  -202,     0,     0,   227,   228,  -202,     0,   230, 
    1700      231,     0,     0,  -202,     0,     0,     0,     0,     0,  1094, 
    1701        0,    12,     0,     0,     0,     0,   232,   233,     0,     0, 
    1702     1104,     0,     0,     0,   231,     0,   234,     0,     0,     0, 
    1703        0,     0,     0,     0,     0,    92,    93,     0,    95,   235, 
    1704      232,   233,    42,   236,   237,     0,     0,     0,     0,     0, 
    1705      234,     0,   238,     0,     0,     0,     0,     0,     0,    92, 
    1706       93,     0,    95,   235,   342,  1141,    42,   236,   237,     0, 
    1707        0,  1143,     0,     0,     0,   361,   238,     0,     0,     0, 
    1708      299,   299,   740,     0,     0,     0,     0,     0,     0,     0, 
     1874       0,     0,     0,     0,     0,  1695,     0,     0,     0,     0, 
     1875       0,     0,     0,     0,   899,   902,     0,  1153,   123,     0, 
     1876       0,     0,  1698,   899,   902,     0,     0,     0,   299,     0, 
     1877       0,     0,     0,  1701,     0,     0,     0,   361,  1034,   299, 
     1878     230,     0,   628,     0,   580,  1626,     0,  1186,   899,   902, 
     1879       0,   226,     0,     0,     0,     0,     0,     0,     0,   227, 
     1880     228,     0,     0,   309,     0,   231,     0,     0,     0,     0, 
     1881       0,  1720,     0,     0,  1722,   410,     0,     0,   956,     0, 
     1882       0,   232,   233,  1216,     0,     0,     0,     0,     0,     0, 
     1883       0,   234,     0,  1597,     0,     0,     0,     0,     0,   230, 
     1884      92,    93,     0,    95,   235,     0,     0,    42,   236,   237, 
     1885       0,     0,     0,  1253,     0,     0,     0,   238,     0,   956, 
     1886       0,     0,  1258,     0,   231,     0,  1261,   756,     0,  1264, 
     1887    1265,     0,  1266,     0,     0,     0,     0,     0,     0,     0, 
     1888     232,   233,     0,     0,     0,     0,     0,   300,     0,     0, 
     1889     234,     0,     0,     0,     0,     0,     0,     0,   123,    92, 
     1890      93,     0,    95,   235,     0,   230,    42,   236,   237,     0, 
     1891       0,     0,     0,     0,     0,     0,   238,     0,     0,     0, 
     1892       0,     0,     0,     0,     0,   580,     0,     0,  1326,     0, 
     1893     231,  1328,     0,     0,     0,     0,     0,     0,     0,     0, 
     1894       0,     0,     0,     0,  1628,     0,   232,   233,     0,     0, 
     1895     226,     0,     0,     0,     0,     0,   234,     0,   227,   228, 
     1896       0,   507,     0,     0,     0,    92,    93,     0,    95,   235, 
     1897       0,     0,    42,   236,   237,     0,     0,     0,     0,     0, 
     1898       0,     0,   238,     0,     0,     0,     0,     0,     0,   309, 
    17091899       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1710        0,   230,     0,     0,     0,     0,  1183,     0,     0,  1185, 
    1711     1186,     0,  1256,     0,     0,     0,     0,     0,     0,   226, 
    1712        0,     0,     0,     0,     0,     0,   231,   227,   228,     0, 
    1713        0,     0,     0,     0,     0,     0,   299,     0,   410,     0, 
    1714        0,     0,   232,   233,   419,   299,     0,     0,     0,     0, 
    1715        0,     0,   234,     0,     0,     0,     0,     0,     0,   410, 
     1900       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
     1901       0,  1034,     0,     0,     0,     0,     0,     0,     0,     0, 
     1902       0,     0,     0,     0,  1186,     0,     0,     0,     0,     0, 
     1903       0,     0,     0,   957,   957,     0,     0,   226,     0,     0, 
     1904     899,   902,     0,     0,     0,   227,   228,   899,   902,   902, 
     1905     899,     0,  1137,     0,   899,   902,  1137,     0,     0,     0, 
     1906       0,     0,     0,  1412,   230,  -225,  -225,  -225,     0,  -225, 
     1907       0,  -225,  -225,  -225,  -225,  -225,  -225,  -225,  -225,  -225, 
     1908    -225,  -225,  -225,  -225,   589,     0,     0,     0,     0,   231, 
     1909       0,   590,     0,   591,   592,     0,     0,     0,  1444,     0, 
     1910       0,   628,  1446,  1173,  1173,   232,   233,     0,     0,  1034, 
     1911       0,     0,     0,     0,     0,   234,     0,     0,     0,     0, 
     1912       0,     0,     0,  -225,    92,    93,   226,    95,   235,     0, 
     1913       0,    42,   236,   237,   227,   228,     0,   226,     0,     0, 
     1914       0,   238,     0,  1478,     0,   227,   228,     0,     0,     0, 
     1915    -765,   230,     0,     0,     0,     0,     0,  1481,     0,     0, 
     1916       0,     0,     0,     0,   882,     0,   883,   884,   885,   886, 
     1917       0,   887,     0,   888,   889,     0,   231,  1252,     0,     0, 
     1918     890,     0,   891,   892,   893,     0,     0,     0,     0,     0, 
     1919    -765,     0,   232,   233,     0,  1034,     0,     0,     0,     0, 
     1920       0,     0,   234,     0,     0,     0,     0,  1539,     0,   507, 
    17161921       0,    92,    93,     0,    95,   235,     0,     0,    42,   236, 
    1717      237,     0,     0,     0,  1408,     0,   299,   299,   238,     0, 
    1718        0,   226,     0,     0,     0,   299,   299,     0,     0,   227, 
    1719      228,     0,  1264,     0,     0,  1265,     0,     0,     0,     0, 
    1720        0,     0,     0,     0,   538,     0,     0,  1273,     0,  1274, 
    1721      299,     0,   507,   510,  1278,     0,     0,     0,     0,     0, 
    1722        0,  1284,  1285,     0,   299,   541,     0,     0,   552,     0, 
    1723        0,     0,     0,   230,     0,     0,     0,     0,     0,   538, 
    1724     1293,  1295,     0,     0,   580,   582,     0,     0,     0,     0, 
    1725     1445,     0,     0,     0,  1324,     0,  1326,   226,   231,     0, 
    1726      593,     0,     0,   593,     0,   227,   228,  1334,     0,     0, 
    1727        0,     0,     0,     0,   232,   233,     0,     0,     0,     0, 
    1728      538,     0,     0,     0,   234,   615,     0,   361,   361,   507, 
    1729        0,     0,     0,    92,    93,   230,    95,   235,     0,     0, 
    1730       42,   236,   237,     0,     0,     0,     0,     0,   299,     0, 
    1731      238,     0,   671,     0,     0,     0,     0,     0,     0,     0, 
    1732      231,     0,     0,     0,  1369,     0,     0,     0,  1371,     0, 
    1733        0,     0,  1374,     0,  1377,  1379,   232,   233,     0,     0, 
    1734        0,     0,     0,     0,     0,  1385,   234,     0,     0,     0, 
    1735        0,     0,     0,     0,     0,    92,    93,     0,    95,   235, 
    1736        0,     0,    42,   236,   237,     0,     0,     0,     0,     0, 
    1737        0,   230,   238,  1400,     0,     0,     0,     0,     0,     0, 
    1738     1406,     0,     0,  1425,  1660,     0,  1428,     0,     0,     0, 
    1739        0,   226,     0,     0,     0,     0,   231,     0,     0,   227, 
    1740      228,     0,     0,     0,     0,   743,     0,   300,   755,     0, 
    1741      299,  1435,   232,   233,     0,     0,     0,   309,     0,     0, 
    1742      762,     0,   234,     0,     0,     0,     0,     0,     0,     0, 
    1743        0,    92,    93,     0,    95,   235,     0,     0,    42,   236, 
    1744      237,     0,     0,     0,   299,     0,     0,     0,   238,     0, 
    1745        0,     0,     0,  1467,     0,  1468,     0,     0,     0,     0, 
    1746        0,   299,     0,     0,  1704,     0,     0,   299,   299,   299, 
    1747      299,   226,   299,     0,   299,   299,     0,     0,     0,   227, 
    1748      228,     0,     0,     0,     0,     0,  1507,     0,     0,     0, 
    1749        0,     0,  1511,     0,     0,     0,     0,     0,     0,     0, 
    1750        0,     0,     0,     0,     0,   230,     0,   123,  1522,     0, 
    1751        0,     0,  1524,     0,     0,     0,     0,     0,     0,   538, 
    1752        0,   299,   299,     0,   771,     0,     0,   507,     0,  1535, 
    1753      231,  1536,     0,     0,  1538,     0,  1540,  1541,     0,  1542, 
    1754        0,     0,  1719,     0,     0,     0,   232,   233,     0,   226, 
    1755     1545,     0,     0,     0,     0,     0,   234,   227,   228,     0, 
    1756        0,   953,     0,     0,     0,    92,    93,     0,    95,   235, 
    1757        0,     0,    42,   236,   237,     0,     0,     0,     0,     0, 
    1758      410,     0,   238,     0,     0,   230,     0,     0,     0,     0, 
    1759        0,     0,   740,     0,     0,   538,   740,     0,    82,    83, 
    1760      772,   773,   953,  1574,     0,     0,     0,     0,  1613,     0, 
    1761      231,     0,     0,   985,   226,   986,     0,     0,     0,     0, 
    1762        0,     0,   227,   228,     0,  1614,   232,   233,     0,     0, 
    1763      774,   540,   775,   776,   777,     0,   234,   778,   779,     0, 
    1764      780,   781,     0,     0,     0,    92,    93,     0,    95,   235, 
    1765        0,     0,    42,   236,   237,  1020,     0,  1022,     0,     0, 
    1766        0,   299,   238,   230,     0,  1030,     0,  1623,  1035,     0, 
    1767        0,     0,     0,  1633,   123,     0,     0,     0,  1637,     0, 
    1768        0,     0,     0,     0,     0,     0,     0,     0,   231,  1642, 
    1769     1643,  1644,     0,   627,   627,     0,     0,     0,     0,     0, 
    1770     1647,  1596,     0,     0,   232,   233,     0,   226,  1649,     0, 
    1771     1651,   299,     0,     0,   234,   227,   228,     0,     0,     0, 
    1772        0,     0,     0,    92,    93,     0,    95,   235,   230,     0, 
    1773       42,   236,   237,     0,     0,     0,     0,     0,   299,     0, 
    1774      238,     0,   299,     0,     0,     0,     0,     0,     0,     0, 
    1775        0,     0,     0,   231,  1092,     0,     0,     0,     0,     0, 
    1776        0,     0,   299,     0,     0,     0,     0,     0,     0,   232, 
    1777      233,     0,   538,   538,   507,   507,   507,   507,     0,   234, 
    1778        0,     0,   507,  1687,     0,     0,     0,   507,    92,    93, 
    1779        0,    95,   235,     0,     0,    42,   236,   237,     0,     0, 
    1780     1690,     0,     0,     0,     0,   238,     0,     0,   300,   300, 
    1781        0,  1693,     0,     0,     0,     0,     0,     0,     0,     0, 
    1782        0,   230,  1147,  1618,     0,     0,     0,     0,     0,   226, 
    1783        0,     0,     0,     0,     0,     0,     0,   227,   228,     0, 
    1784        0,   361,  1030,     0,     0,     0,   231,     0,   580,  1712, 
    1785        0,  1179,  1714,     0,     0,     0,     0,     0,     0,     0, 
    1786     1620,     0,   232,   233,   812,     0,   226,     0,     0,     0, 
    1787        0,     0,   234,     0,   227,   228,     0,     0,     0,   410, 
    1788        0,    92,    93,     0,    95,   235,     0,  1209,    42,   236, 
    1789      237,     0,     0,     0,     0,     0,     0,     0,   238,     0, 
    1790      226,     0,     0,     0,   896,   899,     0,     0,   227,   228, 
    1791        0,     0,     0,   896,   899,     0,     0,  1246,     0,     0, 
    1792      299,     0,     0,     0,     0,     0,  1251,     0,     0,     0, 
    1793     1254,   755,   627,  1257,  1258,     0,  1259,   299,   896,     0, 
    1794        0,     0,     0,   230,     0,     0,  1154,  1155,     0,     0, 
    1795        0,     0,   309,     0,  1156,     0,  1157,   299,     0,     0, 
    1796        0,     0,     0,     0,     0,   299,     0,   952,   231,     0, 
     1922     237,  -225,  -225,  -225,  -225,     0,     0,     0,   238,  1186, 
     1923       0,  1186,     0,     0,     0,     0,     0,     0,     0,     0, 
     1924     230,     0,     0,   813,     0,     0,     0,     0,     0,     0, 
     1925       0,   230,  -225,     0,     0,  -225,  -225,  -225,     0,     0, 
     1926     412,     0,     0,     0,     0,   231,     0,     0,     0,     0, 
     1927       0,     0,     0,     0,     0,     0,   231,     0,     0,  1253, 
     1928    1253,   232,   233,     0,     0,     0,  1578,  1034,     0,     0, 
     1929       0,   234,   232,   233,   902,     0,     0,     0,     0,     0, 
     1930      92,    93,   234,    95,   235,     0,  1216,    42,   236,   237, 
     1931       0,    92,    93,     0,    95,   235,     0,   238,   339,   236, 
     1932     237,     0,   309,     0,  -765,     0,   899,   902,   238,     0, 
     1933       0,  1606,  1607,  1608,  1609,  1610,  1611,  1612,  1613,  1614, 
     1934    1615,  1616,  1617,  1618,  1619,  1620,  1624,  1625,  1627,  1629, 
     1935       0,     0,     0,     0,     0,     0,     0,   956,   956,     0, 
     1936       0,     0,   -88,   -88,   -88,     0,   -88,     0,   -88,   -88, 
     1937     -88,   -88,   -88,   -88,   -88,   -88,   -88,   -88,   -88,   -88, 
     1938     -88,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    17971939       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1798      230,     0,     0,     0,   232,   233,     0,     0,     0,   580, 
    1799        0,     0,  1319,     0,   234,  1321,     0,     0,     0,     0, 
    1800        0,     0,     0,    92,    93,   231,    95,   235,   952,     0, 
    1801       42,   236,   237,     0,   230,     0,     0,   538,   538,     0, 
    1802      238,   232,   233,     0,     0,   507,     0,     0,     0,     0, 
    1803        0,   234,     0,     0,     0,     0,   300,     0,     0,   231, 
    1804       92,    93,     0,    95,   235,  1589,     0,    42,   236,   237, 
    1805        0,     0,     0,     0,   299,   232,   233,   238,     0,     0, 
    1806        0,     0,     0,     0,     0,   234,     0,     0,     0,     0, 
    1807        0,     0,  1030,     0,    92,    93,     0,    95,   235,     0, 
    1808        0,    42,   236,   237,     0,  1179,     0,     0,     0,     0, 
    1809      123,   238,     0,     0,   953,   953,     0,     0,     0,     0, 
    1810      299,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1811        0,   299,     0,     0,     0,     0,     0,     0,     0,  -225, 
    1812     -225,  -225,     0,  -225,  1404,  -225,  -225,  -225,  -225,  -225, 
    1813     -225,  -225,  -225,  -225,  -225,  -225,  -225,  -225,   309,  1484, 
    1814     1485,  1486,  1487,  1488,  1489,     0,  1490,  1491,  1492,  1493, 
    1815     1494,  1495,     0,  1496,  1497,  1498,  1499,  1500,     0,  1436, 
    1816        0,     0,     0,  1438,     0,  1589,     0,     0,     0,     0, 
    1817     1030,     0,     0,     0,     0,     0,     0,  -225,     0,     0, 
    1818        0,     0,     0,     0,     0,     0,     0,     0,     0,   896, 
    1819        0,     0,     0,     0,     0,   896,   899,   899,   896,     0, 
    1820     1132,     0,   896,  1132,  1470,     0,     0,     0,     0,     0, 
    1821        0,     0,     0,     0,     0,     0,     0,     0,  1473,     0, 
    1822        0,     0,     0,     0,     0,   -88,   -88,   -88,     0,   -88, 
    1823      123,   -88,   -88,   -88,   -88,   -88,   -88,   -88,   -88,   -88, 
    1824      -88,   -88,   -88,   -88,     0,     0,     0,   627,     0,  1166, 
    1825     1166,     0,     0,     0,     0,     0,  1030,     0,     0,     0, 
    1826        0,     0,     0,     0,     0,     0,     0,     0,  1531,     0, 
    1827      507,     0,     0,     0,     0,  -225,  -225,  -225,  -225,     0, 
    1828        0,     0,     0,   -88,     0,     0,     0,     0,     0,  1179, 
    1829        0,  1179,     0,     0,     0,     0,     0,     0,     0,     0, 
    1830        0,     0,     0,     0,     0,     0,  -225,     0,     0,  -225, 
    1831     -225,  -225,     0,   226,   412,     0,     0,     0,     0,     0, 
    1832        0,   227,   228,  1245,     0,     0,     0,     0,     0,   680, 
    1833     1501,  1502,     0,     0,     0,     0,     0,     0,     0,  1246, 
    1834     1246,     0,     0,     0,     0,     0,  1570,  1030,     0,     0, 
    1835        0,   880,     0,   881,   882,   883,   884,     0,   885,     0, 
    1836      886,   887,     0,     0,     0,     0,  1209,   888,     0,   889, 
    1837        0,   890,     0,     0,     0,     0,     0,     0,     0,     0, 
    1838        0,   -88,   -88,   -88,   -88,     0,     0,     0,     0,   812, 
    1839        0,  1598,  1599,  1600,  1601,  1602,  1603,  1604,  1605,  1606, 
    1840     1607,  1608,  1609,  1610,  1611,  1612,  1616,  1617,  1619,  1621, 
    1841        0,     0,   -88,   -88,     0,   -88,   -88,   -88,     0,   -88, 
    1842        0,     0,     0,     0,     0,   226,     0,   230,     0,     0, 
    1843        0,     0,     0,   227,   228,   617,     0,     0,     0,   899, 
     1940       0,  1663,     0,     0,     0,     0,     0,     0,     0,     0, 
    18441941       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1845        0,     0,   231,     0,     0,     0,     0,     0,     0,     0, 
    1846        0,  1655,     0,     0,   618,     0,   309,     0,   232,   233, 
    1847      896,     0,   619,     0,   620,   621,   622,   623,   234,   624, 
    1848        0,   625,     0,     0,     0,     0,  1209,    92,    93,     0, 
    1849       95,   235,     0,     0,    42,   236,   237,     0,   226,     0, 
    1850      952,   952,     0,  1682,   238,     0,   227,   228,     0,     0, 
     1942     -88,     0,     0,     0,     0,     0,  1216,     0,     0,     0, 
     1943       0,   226,     0,     0,     0,     0,     0,     0,     0,   227, 
     1944     228,   617,     0,  1690,     0,     0,     0,     0,     0,     0, 
    18511945       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1852     1683,  1684,     0,     0,     0,  1685,     0,  1686,     0,     0, 
    1853        0,     0,     0,     0,     0,     0,   867,     0,     0,   230, 
    1854      868,   869,   870,   871,   872,   873,     0,     0,     0,     0, 
    1855        0,     0,   874,   875,   876,     0,     0,     0,     0,     0, 
    1856        0,     0,     0,     0,   231,     0,     0,     0,     0,     0, 
     1946    1691,  1692,     0,     0,     0,  1693,     0,  1694,     0,     0, 
     1947     618,     0,     0,     0,     0,     0,     0,     0,   619,     0, 
     1948     620,   621,   622,   623,     0,   624,     0,   625,   626,     0, 
    18571949       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1858      232,   233,    89,     0,     0,  1708,     0,  1297,     0,     0, 
    1859      234,     0,     0,     0,     0,  1298,  1299,     0,     0,    92, 
    1860       93,     0,    95,   235,     0,     0,   626,   505,   237,     0, 
    1861        0,  1720,   230,     0,     0,     0,   238,     0,     0,     0, 
    1862     1300,     0,     0,     0,     0,     0,  1727,     0,  1708,  1730, 
    1863        0,     0,     0,     0,   598,  1732,     0,   231,     0,     0, 
    1864     1735,   599,     0,   600,   601,     0,     0,     0,   899,     0, 
    1865        0,     0,   226,   232,   233,     0,     0,     0,     0,     0, 
    1866      227,   228,     0,   234,     0,   899,     0,     0,     0,     0, 
    1867        0,     0,    92,    93,     0,    95,   235,     0,     0,    42, 
    1868      236,   237,     0,     0,     0,  1166,  1301,     0,     0,   238, 
    1869      880,     0,   881,     0,   883,   884,     0,   885,     0,   886, 
    1870      887,   230,     0,     0,     0,     0,   888,     0,   889,     0, 
    1871      890,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1872        0,     0,     0,     0,     0,     0,   231,   226,     0,     0, 
    1873        0,     0,  1302,     0,     0,   227,   228,     0,     0,     0, 
    1874        0,     0,  1303,  1304,     0,  1245,  1245,     0,     0,     0, 
     1950       0,     0,     0,     0,     0,   902,     0,     0,     0,     0, 
     1951       0,     0,     0,     0,     0,     0,     0,     0,   -88,   -88, 
     1952     -88,   -88,   902,     0,     0,  1716,     0,     0,     0,     0, 
     1953       0,     0,     0,   226,     0,     0,     0,     0,     0,     0, 
     1954       0,   227,   228,  1173,     0,   230,     0,     0,     0,   -88, 
     1955     -88,  1728,   -88,   -88,   -88,     0,   -88,     0,     0,     0, 
     1956       0,     0,     0,     0,     0,     0,  1735,     0,  1716,  1738, 
     1957     231,     0,     0,   226,     0,  1740,     0,     0,     0,     0, 
     1958    1743,   227,   228,     0,     0,     0,   232,   233,    89,     0, 
     1959       0,     0,     0,     0,     0,     0,   234,     0,     0,     0, 
     1960       0,     0,     0,  1252,  1252,    92,    93,     0,    95,   235, 
     1961       0,   868,   627,   505,   237,   869,   870,   871,   872,   873, 
     1962     874,     0,   238,   226,     0,     0,     0,   875,   876,   877, 
     1963     878,   227,   228,     0,     0,     0,     0,     0,     0,     0, 
     1964       0,     0,     0,     0,     0,     0,     0,   230,     0,     0, 
     1965       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
     1966       0,   882,     0,   883,     0,   885,   886,     0,   887,     0, 
     1967     888,   889,   231,     0,     0,     0,  1304,   890,     0,   891, 
     1968     892,   893,     0,     0,  1305,  1306,   899,   230,   232,   233, 
     1969       0,     0,     0,     0,     0,     0,     0,   899,   234,     0, 
     1970       0,     0,     0,     0,     0,     0,     0,    92,    93,  1307, 
     1971      95,   235,   231,   226,   537,   236,   237,  1247,     0,     0, 
     1972       0,   227,   228,   598,   238,     0,     0,     0,   232,   233, 
     1973     599,     0,   600,   601,     0,     0,     0,   230,   234,     0, 
     1974       0,     0,     0,     0,     0,     0,     0,    92,    93,     0, 
     1975      95,   235,     0,     0,    42,   236,   237,     0,     0,     0, 
     1976     598,     0,   231,   226,   238,     0,     0,   599,     0,   600, 
     1977     601,   227,   228,     0,     0,  1308,     4,     0,   232,   233, 
     1978       0,     0,     0,     0,     0,     0,     0,     0,   234,     0, 
     1979     230,     0,     0,     0,     0,     0,     0,    92,    93,     0, 
     1980      95,   235,     0,   226,    42,   236,   237,     0,     0,     0, 
     1981       0,   227,   228,   504,   238,   231,     8,     0,     0,     0, 
     1982       0,  1309,     0,     0,     0,     0,     0,   230,     0,     0, 
     1983       0,  1310,  1311,     0,     0,     0,     0,   226,     0,     0, 
     1984       0,   234,     0,     0,     0,   227,   228,     0,     0,     0, 
     1985    1312,  1313,   231,  1314,  1315,     0,     0,    42,  1316,   237, 
     1986       0,     0,     0,     0,     0,     0,     0,   238,   232,   233, 
     1987       0,     0,     0,     0,   226,     0,     0,   230,   234,     0, 
     1988       0,     0,   227,   228,   928,     0,     0,    92,    93,     0, 
     1989      95,   235,     0,     0,    42,   236,   237,     0,     0,     0, 
     1990       0,     0,   231,   226,   238,     0,     0,     0,     0,     0, 
     1991       0,   227,   228,  1260,     0,     0,     0,   230,   232,   233, 
     1992     397,     0,     0,     0,     0,     0,     0,     0,   234,     0, 
     1993       0,     0,     0,     0,     0,     0,     0,    92,    93,     0, 
     1994      95,   235,   231,     0,    42,   236,   237,     0,     0,     0, 
     1995      12,   230,     0,   226,   238,     0,     0,     0,   232,   233, 
     1996      89,   227,   228,  -395,     0,     0,     0,     0,   234,     0, 
     1997       0,     0,     0,     0,     0,     0,   231,    92,    93,     0, 
     1998      95,   235,   226,     0,    42,   505,   237,     0,   230,     0, 
     1999     227,   228,   232,   233,   238,     0,     0,     0,     0,     0, 
    18752000       0,     0,   234,     0,     0,     0,     0,     0,     0,     0, 
    1876        0,  1305,  1306,     0,  1307,  1308,   230,   226,    42,  1309, 
    1877      237,     0,     0,     0,   589,   227,   228,     0,   238,     0, 
    1878        0,   590,     0,   591,   592,     0,     0,     0,     0,     0, 
    1879        0,   231,     0,     0,     0,     0,     0,   226,     0,     0, 
    1880        0,     0,     0,     0,     0,   227,   228,   232,   233,     0, 
    1881     -765,     0,     0,     0,   598,     0,     0,   234,     0,     0, 
    1882        0,   599,     0,   600,   601,     0,    92,    93,   896,    95, 
    1883      235,     0,     0,    42,   236,   237,     0,     0,     0,   896, 
    1884        0,   230,     0,   238,     0,     0,   226,     0,     0,     0, 
    1885     -765,     0,     0,     0,   227,   228,     0,     0,     0,     4, 
    1886        0,     0,     0,     0,     0,     0,   231,     0,     0,     0, 
    1887        0,     0,     0,     0,     0,     0,     0,     0,     0,   226, 
    1888        0,   230,   232,   233,     0,     0,     0,   227,   228,   504, 
    1889        0,     0,   234,     0,     0,     0,     0,     0,     0,     8, 
    1890        0,    92,    93,     0,    95,   235,   231,     0,    42,   236, 
    1891      237,   230,   226,     0,     0,     0,     0,     0,   238,     0, 
    1892      227,   228,   232,   233,     0,     0,     0,     0,     0,     0, 
    1893        0,     0,   234,     0,     0,     0,   231,     0,     0,     0, 
    1894        0,    92,    93,     0,    95,   235,     0,     0,    42,   236, 
    1895      237,     0,   232,   233,     0,     0,     0,   226,   238,     0, 
    1896      230,     0,   234,     0,     0,   227,   228,   925,   226,     0, 
    1897        0,    92,    93,     0,    95,   235,   227,   228,   339,   236, 
    1898      237,     0,     0,     0,  -765,   231,     0,     0,   238,     0, 
    1899        0,     0,     0,   230,     0,   397,     0,     0,     0,     0, 
    1900        0,   232,   233,     0,     0,   226,     0,     0,     0,     0, 
    1901        0,   234,     0,   227,   228,  1253,     0,     0,   231,     0, 
    1902       92,    93,     0,    95,   235,     0,   230,    42,   236,   237, 
    1903        0,     0,     0,    12,   232,   233,    89,   238,     0,   226, 
    1904        0,     0,     0,     0,   234,     0,     0,   227,   228,  -395, 
    1905      226,   231,     0,    92,    93,     0,    95,   235,   227,   228, 
    1906       42,   505,   237,     0,     0,     0,     0,   232,   233,     0, 
    1907      238,   230,     0,     0,     0,     0,     0,   234,     0,     0, 
    1908        0,     0,   230,     0,     0,     0,    92,    93,     0,    95, 
    1909      235,     0,     0,    42,   236,   237,   231,   226,     0,     0, 
    1910        0,     0,     0,   238,     0,   227,   228,   231,     0,     0, 
    1911        0,     0,   232,   233,     0,     0,     0,     0,     0,   230, 
    1912        0,   226,   234,   232,   233,     0,     0,     0,     0,   227, 
    1913      228,    92,    93,   234,    95,   235,     0,     0,    42,   236, 
    1914      237,     0,    92,    93,   231,    95,   235,     0,   238,   537, 
    1915      236,   237,  1240,   230,   226,     0,     0,     0,     0,   238, 
    1916      232,   233,   227,   228,   230,     0,     0,     0,     0,     0, 
    1917      234,     0,     0,     0,     0,     0,     0,     0,   231,    92, 
    1918       93,     0,    95,   235,     0,     0,    42,   236,   237,   231, 
    1919        0,   226,     0,     0,   232,   233,   238,     0,     0,   227, 
    1920      228,     0,     0,     0,   234,   232,   233,     0,     0,     0, 
    1921        0,   230,     0,    92,    93,   234,    95,   235,     0,     0, 
    1922       42,   236,   237,     0,    92,    93,     0,    95,   235,     0, 
    1923      238,    42,   236,   353,     0,   230,   231,   226,     0,     0, 
    1924        0,   238,     0,     0,     0,   227,   228,     0,   226,     0, 
    1925        0,     0,   232,   233,     0,     0,   227,   228,     0,     0, 
    1926      231,     0,   234,     0,     0,     0,     0,     0,   230,     0, 
    1927        0,    92,    93,     0,    95,   235,   232,   233,    42,   236, 
    1928      356,     0,     0,     0,     0,     0,   234,     0,   238,     0, 
    1929        0,     0,     0,   231,     0,    92,    93,     0,    95,   235, 
    1930        0,     0,    42,   236,   405,   230,     0,     0,     0,   232, 
    1931      233,     0,   238,     0,     0,     0,     0,     0,     0,   234, 
    1932        0,     0,     0,     0,     0,     0,     0,     0,    92,    93, 
    1933      231,    95,   235,     0,    79,    42,   236,   237,     0,     0, 
    1934        0,    80,     0,     0,     0,   238,   232,   233,     0,     0, 
    1935        0,   230,     0,     0,     0,     0,   234,     0,     0,     0, 
    1936        0,     0,   230,     0,     0,    92,    93,     0,    95,   235, 
    1937        0,     0,   537,   236,   237,     0,   231,     0,     0,     0, 
    1938        0,     0,   238,     0,     0,     0,     0,   231,     0,     0, 
    1939        0,    81,   232,   233,     0,     0,     0,     0,     0,     0, 
    1940        0,     0,   234,   232,   233,     0,     0,     0,    82,    83, 
    1941        0,    92,    93,   234,    95,   235,     0,     0,    42,   236, 
    1942     1029,    84,    92,    93,     0,    95,   235,     0,   238,  1083, 
    1943     1084,  1085,     0,     0,     0,     0,     0,     0,     0,   238, 
    1944     -450,     0,    85,    80,    86,    87,     0,     0,     0,   155, 
    1945     -463,     0,  -476,     0,     0,     0,     0,    88,  -708,   156, 
     2001       0,    92,    93,   231,    95,   235,     0,   230,    42,   236, 
     2002     237,     0,     0,     0,     0,     0,     0,   226,   238,   232, 
     2003     233,     0,     0,     0,     0,   227,   228,     0,   226,   234, 
     2004       0,     0,   231,     0,     0,     0,   227,   228,    92,    93, 
     2005       0,    95,   235,     0,     0,    42,   236,   237,   232,   233, 
     2006       0,     0,     0,     0,     0,   238,     0,   230,   234,     0, 
     2007       0,     0,     0,     0,     0,     0,     0,    92,    93,     0, 
     2008      95,   235,     0,     0,    42,   236,   237,     0,     0,     0, 
     2009       0,     0,   231,   226,   238,     0,   230,     0,     0,     0, 
     2010       0,   227,   228,     0,     0,     0,     0,     0,   232,   233, 
     2011       0,     0,     0,     0,     0,     0,     0,   226,   234,     0, 
     2012       0,   231,     0,     0,     0,   227,   228,    92,    93,     0, 
     2013      95,   235,     0,     0,    42,   236,   237,   232,   233,     0, 
     2014       0,   230,     0,     0,   238,     0,   226,   234,     0,     0, 
     2015       0,     0,   230,     0,   227,   228,    92,    93,     0,    95, 
     2016     235,     0,     0,    42,   236,   353,   231,     0,     0,     0, 
     2017       0,     0,     0,   238,     0,     0,   226,   231,     0,     0, 
     2018       0,     0,   232,   233,   227,   228,     0,     0,     0,     0, 
     2019       0,     0,   234,   232,   233,     0,     0,     0,     0,     0, 
     2020       0,    92,    93,   234,    95,   235,     0,   230,    42,   236, 
     2021     356,     0,    92,    93,     0,    95,   235,     0,   238,    42, 
     2022     236,   405,     0,     0,     0,     0,     0,     0,     0,   238, 
     2023       0,   230,   231,     0,     0,     0,     0,     0,     0,     0, 
     2024       0,     0,     0,     0,     0,     0,     0,     0,   232,   233, 
     2025       0,     0,     0,     0,     0,     0,   231,     0,   234,     0, 
     2026     230,     0,     0,     0,     0,     0,     0,    92,    93,     0, 
     2027      95,   235,   232,   233,    42,   236,   237,     0,     0,     0, 
     2028       0,    79,   234,     0,   238,   231,     0,     0,    80,     0, 
     2029     230,    92,    93,     0,    95,   235,     0,     0,   537,   236, 
     2030     237,   232,   233,     0,     0,     0,     0,     0,   238,     0, 
     2031       0,   234,     0,     0,     0,   231,     0,     0,     0,     0, 
     2032      92,    93,     0,    95,   235,     0,     0,    42,   236,  1033, 
     2033       0,   232,   233,     0,     0,     0,     0,   238,    81,     0, 
     2034       0,   234,     0,     0,     0,     0,     0,     0,     0,     0, 
     2035      92,    93,     0,    95,   235,    82,    83,  1087,  1088,  1089, 
     2036       0,     0,     0,     0,     0,     0,     0,   238,    84,     0, 
    19462037       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
     2038       0,     0,     0,     0,     0,     0,     0,  -450,     0,    85, 
     2039      80,    86,    87,     0,     0,     0,   155,  -463,     0,  -476, 
     2040       0,     0,     0,     0,    88,  -708,   156,     0,     0,     0, 
     2041       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
     2042       0,     0,     0,     0,    89,     0,     0,    90,    91,  -334, 
     2043       0,     0,  -334,  -334,  -334,  -334,   157,     0,     0,     0, 
     2044    -334,    92,    93,    94,    95,     0,  -334,     0,    96,    97, 
     2045       0,   158,     0,     0,     0,     0,     0,     0,     0,     0, 
     2046       0,     0,     0,  -708,  -708,  -708,     0,   159,     0,     0, 
     2047      84,     0,  -708,     0,   160,    80,     0,   161,   162,     0, 
     2048     163,   155,     0,   164,     0,     0,   165,   166,   167,     0, 
     2049    -708,   156,     0,     0,     0,     0,     0,     0,     0,     0, 
     2050       0,     0,     0,    80,     0,     0,     0,     0,     0,   155, 
     2051       0,     0,   168,     0,     0,     0,     0,     0,     0,   156, 
     2052       0,   157,     0,     0,     0,     0,    89,  -708,  -708,    90, 
     2053       0,     0,     0,     0,     0,     0,   158,     0,     0,     0, 
     2054       0,     0,     0,    92,    93,     0,    95,     0,     0,   157, 
     2055     169,    97,   159,     0,     0,    84,  -128,     0,     0,   160, 
     2056       0,     0,   161,   162,   158,   163,     0,     0,   164,     0, 
     2057       0,   165,   166,   167,     0,     0,     0,     0,     0,     0, 
     2058     159,     0,     0,    84,  -129,     0,     0,   160,     0,     0, 
     2059     161,   162,     0,   163,   155,     0,   164,   168,     0,   165, 
     2060     166,   167,     0,     0,   156,     0,     0,     0,     0,     0, 
     2061       0,    89,     0,     0,    90,     0,     0,     0,     0,     0, 
     2062       0,     0,   822,     0,     0,   168,  -128,     0,    92,    93, 
     2063       0,    95,     0,     0,   157,   169,    97,     0,     0,    89, 
     2064       0,     0,    90,     0,     0,     0,     0,     0,     0,   158, 
     2065       0,     0,     0,     0,  -129,     0,    92,    93,     0,    95, 
     2066       0,     0,   157,   169,    97,   159,     0,     0,    84,  -125, 
     2067       0,     0,   160,     0,     0,   161,   162,   158,   163,     0, 
     2068       0,   164,     0,     0,   165,   166,   167,     0,  1038,     0, 
     2069       0,     0,     0,   159,     0,     0,     0,     0,     0,     0, 
     2070     160,     0,     0,   161,   162,     0,   163,   822,     0,   164, 
     2071     168,     0,   165,   166,   167,     0,     0,     0,     0,     0, 
     2072       0,     0,     0,     0,    89,     0,     0,    90,     0,     0, 
     2073       0,     0,     0,     0,     0,     0,     0,     0,   168,  -125, 
     2074       0,    92,    93,     0,    95,     0,     0,   157,   169,    97, 
     2075       0,     0,    89,     0,     0,     0,     0,     0,     0,     0, 
     2076       0,     0,   158,     0,     0,     0,     0,     0,     0,    92, 
     2077      93,     0,    95,     0,     0,     0,    42,    97,   159,     0, 
     2078       0,     0,     0,     0,     0,   160,     0,     0,   161,   162, 
     2079       0,   163,     0,     0,   164,     0,     0,   165,   166,   167, 
     2080       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
     2081       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
     2082       0,     0,     0,   168,     0,     0,     0,     0,     0,     0, 
    19472083       0,     0,     0,     0,     0,     0,     0,    89,     0,     0, 
    1948       90,    91,  -334,     0,     0,  -334,  -334,  -334,  -334,   157, 
    1949        0,     0,     0,  -334,    92,    93,    94,    95,     0,  -334, 
    1950        0,    96,    97,     0,   158,     0,     0,     0,     0,     0, 
    1951        0,     0,     0,     0,     0,     0,  -708,  -708,  -708,     0, 
    1952      159,     0,     0,    84,     0,  -708,     0,   160,    80,     0, 
    1953      161,   162,     0,   163,   155,     0,   164,     0,     0,   165, 
    1954      166,   167,     0,  -708,   156,     0,     0,     0,     0,     0, 
    1955        0,     0,     0,     0,     0,     0,    80,     0,     0,     0, 
    1956        0,     0,   155,     0,     0,   168,     0,     0,     0,     0, 
    1957        0,     0,   156,     0,   157,     0,     0,     0,     0,    89, 
    1958     -708,  -708,    90,     0,     0,     0,     0,     0,     0,   158, 
    1959        0,     0,     0,     0,     0,     0,    92,    93,     0,    95, 
    1960        0,     0,   157,   169,    97,   159,     0,     0,    84,  -128, 
    1961        0,     0,   160,     0,     0,   161,   162,   158,   163,     0, 
    1962        0,   164,     0,     0,   165,   166,   167,     0,     0,     0, 
    1963        0,     0,     0,   159,     0,     0,    84,  -129,     0,     0, 
    1964      160,     0,     0,   161,   162,     0,   163,   155,     0,   164, 
    1965      168,     0,   165,   166,   167,     0,     0,   156,     0,     0, 
    1966        0,     0,     0,     0,    89,     0,     0,    90,     0,     0, 
    1967        0,     0,     0,     0,     0,   821,     0,     0,   168,  -128, 
    1968        0,    92,    93,     0,    95,     0,     0,   157,   169,    97, 
    1969        0,     0,    89,     0,     0,    90,     0,     0,     0,     0, 
    1970        0,     0,   158,     0,     0,     0,     0,  -129,     0,    92, 
    1971       93,     0,    95,     0,     0,   157,   169,    97,   159,     0, 
    1972        0,    84,  -125,     0,     0,   160,     0,     0,   161,   162, 
    1973      158,   163,     0,     0,   164,     0,     0,   165,   166,   167, 
    1974        0,  1034,     0,     0,     0,     0,   159,     0,     0,     0, 
    1975        0,     0,     0,   160,     0,     0,   161,   162,     0,   163, 
    1976      821,     0,   164,   168,     0,   165,   166,   167,     0,     0, 
    1977        0,     0,     0,     0,     0,     0,     0,    89,     0,     0, 
    1978       90,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1979        0,   168,  -125,     0,    92,    93,     0,    95,     0,     0, 
    1980      157,   169,    97,     0,     0,    89,     0,     0,     0,     0, 
    1981        0,     0,     0,     0,     0,   158,     0,     0,     0,     0, 
    1982        0,     0,    92,    93,     0,    95,     0,     0,     0,    42, 
    1983       97,   159,     0,     0,     0,     0,     0,     0,   160,     0, 
    1984        0,   161,   162,     0,   163,     0,     0,   164,     0,     0, 
    1985      165,   166,   167,     0,     0,     0,     0,     0,     0,     0, 
    19862084       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1987        0,     0,     0,     0,     0,     0,   168,     0,     0,     0, 
    1988        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1989       89,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1990        0,     0,     0,     0,     0,     0,     0,    92,    93,     0, 
    1991       95,     0,     0,     0,    42,    97 
     2085       0,     0,     0,     0,    92,    93,     0,    95,     0,     0, 
     2086       0,    42,    97 
    19922087}; 
    19932088 
    19942089static const yytype_int16 yycheck[] = 
    19952090{ 
    1996       11,   213,   168,   294,   459,   294,    52,    52,   384,    90, 
    1997      459,    56,   220,   384,   288,   164,   165,   136,   654,    52, 
    1998      154,   497,   168,   154,    57,   291,   922,   721,   494,    62, 
    1999       63,   859,   294,   219,   141,   322,    73,   551,   606,    52, 
    2000     1007,    52,  1007,   294,   109,   305,    57,   213,   237,    52, 
    2001      237,    62,    63,   983,   100,   100,   497,   883,   884,   695, 
    2002       52,    94,    73,  1100,   935,   673,   570,   100,   495,   258, 
    2003     1029,   104,   258,   259,   319,   936,   937,   868,   869,   870, 
    2004      943,   591,   110,    94,   875,  1178,     5,   100,   172,   100, 
    2005      600,  1275,   237,   104,     3,  1279,  1508,   100,  1282,    21, 
    2006        5,  1270,     3,    21,    27,     3,     3,    21,   100,     3, 
    2007        3,     3,     3,   258,     3,   625,   941,     5,     3,    56, 
    2008     1270,     3,   382,  1459,     3,     3,     3,     3,     3,   185, 
    2009     1557,    24,    24,    24,     3,     3,     3,     3,   170,   172, 
    2010     1270,     3,    24,    24,     3,    24,    24,    24,    24,    24, 
    2011     1577,     3,    24,   192,     3,    24,    24,    24,    24,   305, 
    2012      192,   172,     3,     3,   353,     3,   353,   356,   459,   356, 
    2013      459,    64,    64,    64,     4,    24,     3,     3,     3,     3, 
    2014      192,   259,    64,   220,   560,    64,    64,    64,    64,    64, 
    2015        3,   399,    64,  1089,     3,    64,    64,    64,    64,   333, 
    2016        3,     3,   333,     3,   353,     3,  1165,   356,   353,     3, 
    2017        5,   356,   420,     3,     3,    64,   405,     3,   405,     3, 
    2018        3,     3,   159,    24,     3,     5,   237,   137,     3,    21, 
    2019      325,   418,   418,     3,   380,   381,   382,   678,  1558,   425, 
    2020       18,   325,   428,  1579,    22,   431,   311,    19,    20,   161, 
    2021     1419,    21,   317,    19,    20,   110,   522,  1082,  1578,   147, 
    2022      405,    18,    24,     3,   713,    22,   155,   304,   279,   192, 
    2023      155,    47,   194,   310,  1443,   194,   194,  1689,   972,   374, 
    2024      194,   388,   319,   294,   194,   322,   195,   315,   316,   194, 
    2025      374,  1384,   325,  1443,   195,   586,   723,   195,   195,   200, 
    2026     1126,   195,    64,   195,  1263,   198,   198,   198,   497,   201, 
    2027      497,   497,  1175,  1443,   325,   606,   198,   198,   161,   198, 
    2028      198,   198,   198,   198,   586,   155,   198,  1118,    97,   198, 
    2029      198,   198,   198,   195,   194,   501,   195,   192,   384,   331, 
    2030      418,   374,   353,   195,   606,   356,   850,   195,   359,   198, 
    2031       52,   384,   497,   431,   195,   195,   132,   195,   185,   186, 
    2032      620,   188,   399,   374,   972,   192,   876,   147,   305,   195, 
    2033      195,   195,   882,   384,  1010,   885,   155,   146,   195,   889, 
    2034      155,   114,   195,   420,   421,   155,   195,   147,  1557,   194, 
    2035     1559,   155,   195,   195,   405,   195,  1565,   195,   100,   194, 
    2036      192,   195,   394,   395,    97,   195,   195,  1591,  1577,   195, 
    2037      421,   195,   195,   195,   192,   155,   168,   189,   499,   500, 
    2038      192,   193,    22,   192,    52,   192,   459,   193,   192,    24, 
    2039      721,    52,   721,    97,   194,   168,   198,   125,   587,   588, 
    2040      589,   193,   561,   380,   381,   382,    52,   384,   459,   598, 
    2041      731,   663,   718,   146,   519,   667,   668,   738,   666,   721, 
    2042      193,  1419,   495,   496,   497,   572,   117,   118,    24,    64, 
    2043      721,  1401,   100,  1510,   620,   155,   557,   611,  1349,   100, 
    2044      611,  1440,   146,    97,   495,   496,   497,    48,   176,   678, 
    2045      501,   678,   678,  1460,   100,  1460,    24,   663,    24,   765, 
    2046      689,   667,   668,   689,   192,    52,    24,   192,    64,  1335, 
    2047       33,  1372,   192,   144,   560,   560,   189,   155,   551,   155, 
    2048      193,   532,   567,   789,   192,    48,  1352,   560,   983,   995, 
    2049      198,  1007,   146,   678,   983,  1011,    64,    24,    64,    24, 
    2050      551,   192,   173,   554,   689,   192,    64,   560,   195,   560, 
    2051      111,   112,  1188,   100,   741,   741,   192,   560,   591,   592, 
    2052      193,   194,  1076,   808,   567,   810,  1007,   600,   601,    29, 
    2053     1011,    31,  1363,   111,   112,   586,  1144,    64,   192,    64, 
    2054      591,   592,    12,    13,    14,    15,    16,    17,    18,   600, 
    2055      601,    24,   625,   169,   170,   606,    29,   192,    31,     3, 
    2056     1558,  1559,   192,   198,     4,   195,   639,  1565,    24,  1505, 
    2057      171,    19,    20,  1580,   625,  1580,   192,   194,    22,    24, 
    2058     1578,    24,   194,   560,   168,   175,   175,   638,   639,   666, 
    2059      567,    24,   194,   171,    21,    22,   192,     3,   200,   183, 
    2060      168,  1469,   198,   654,   194,   194,   195,  1157,    64,   193, 
    2061       29,   200,    31,   590,    87,   125,    22,   185,   186,    64, 
    2062      188,    64,   599,   194,   192,   193,   192,   678,   173,   200, 
    2063      198,    64,   198,   822,   192,   425,   131,   192,   428,   194, 
    2064      198,    38,   115,   620,   695,   622,   623,   624,     5,    29, 
    2065      723,    31,   983,    29,   983,    31,   105,   984,   107,  1194, 
    2066      192,  1196,   713,   195,     3,   192,   176,   192,    87,   201, 
    2067      721,   198,   723,   198,   141,   185,   186,   125,   188,    18, 
    2068      143,   103,   192,    22,   873,   844,   108,   764,   194,   111, 
    2069        6,     7,   162,   163,   164,   165,   115,   886,   803,   192, 
    2070      173,   113,   195,    99,   100,   852,  1440,    87,   201,  1645, 
    2071      183,    87,    24,  1219,   903,   194,   767,    29,   140,    31, 
    2072      909,   158,   159,   160,     4,   198,   196,   197,   176,  1218, 
    2073      807,   808,   194,   810,   923,   115,   192,   185,   186,   115, 
    2074      188,   189,   198,   917,   192,   193,   917,   192,   934,   192, 
    2075      173,   174,   825,   198,   173,   198,   194,  1433,   194,   192, 
    2076      194,  1177,   192,   193,   183,   198,  1177,   176,   177,   178, 
    2077      179,   168,   749,   859,   825,   184,  1107,   194,  1007,   113, 
    2078     1007,   190,  1011,   192,  1011,  1011,   859,    47,   185,   186, 
    2079      194,   188,   194,   173,   871,   192,   193,   173,   173,   174, 
    2080     1029,   194,  1029,   876,   193,  1107,   201,   183,   859,   882, 
    2081      883,   884,   885,  1144,   887,   201,   889,   890,  1024,  1314, 
    2082      105,   106,  1007,  1318,     5,   876,  1011,    40,    41,  1594, 
    2083     1595,   882,   883,   884,   885,   175,   887,   922,   889,   890, 
    2084       23,    29,  1144,    31,  1029,    62,    63,   924,    10,   922, 
    2085        8,    99,   100,   101,   102,   168,  1085,   194,  1085,   208, 
    2086      209,   194,   913,   936,   937,    28,    29,    30,    31,   326, 
    2087      327,   922,   185,   186,    37,   188,     4,   192,   192,   192, 
    2088      193,   192,   859,   131,   192,   936,   937,   176,   177,   178, 
    2089      179,   139,     5,    19,    20,   184,  1085,   874,   192,    87, 
    2090     1085,   190,   147,   200,   169,   105,  1401,   984,   194,  1223, 
    2091      983,   888,  1401,   185,   186,   192,   188,   195,   194,     5, 
    2092      192,   972,   195,   195,    87,     5,     5,   115,   151,  1006, 
    2093      185,   186,   983,   188,  1123,     3,   175,   192,  1011,   175, 
    2094      195,   175,   195,   175,  1460,   922,    65,    66,   195,  1138, 
    2095      192,   203,   115,   194,     5,  1006,  1007,   934,  1079,  1010, 
    2096     1011,    80,  1268,    22,  1380,    84,  1155,   192,   192,  1380, 
    2097        3,    90,   194,  1024,  1226,    19,    20,     3,  1029,   195, 
    2098      111,   185,   186,  1314,   188,   173,   195,  1318,   192,   103, 
    2099        4,   195,   174,   192,   108,   183,   155,   111,  1227,   125, 
    2100     1227,  1227,     3,  1076,  1089,     3,   192,   121,   200,   123, 
    2101      173,  1062,   126,   127,   185,   186,  1089,   188,   194,     4, 
    2102     1226,   192,   195,   194,   150,  1076,   140,    38,     4,   114, 
    2103      194,   145,  1109,   135,  1085,   198,  1087,   192,  1089,   158, 
    2104      166,   167,  1227,   183,   185,   186,   195,   188,   195,   168, 
    2105      176,   192,   194,  1126,  1280,     5,  1107,   195,   183,   185, 
    2106      186,    39,   188,   189,  1580,   192,   192,   193,   194,   192, 
    2107     1401,     4,  1401,   183,   183,  1126,   202,   195,    11,     3, 
    2108     1153,   125,   185,   186,  1157,   188,    19,    20,    21,   192, 
    2109       18,  1177,   175,  1144,   185,   186,     5,   188,   109,     3, 
    2110      194,   192,  1153,   114,  1177,   194,  1157,    22,   119,   120, 
    2111        3,   122,  1089,   194,   125,   192,    21,   128,   129,   130, 
    2112      194,    21,   166,   167,   185,   186,  1177,   188,   195,   104, 
    2113      194,   192,   176,   194,   194,     3,  1187,  1188,   194,   194, 
    2114        3,   185,   186,  1220,   188,   189,     3,   192,   192,   193, 
    2115      194,   192,   147,   170,   194,   194,   275,   168,    68,    69, 
    2116       70,   280,    72,   140,   283,   155,     3,  1218,   115,   194, 
    2117        3,   290,     3,     5,   185,   186,  1227,   188,  1367,  1156, 
    2118        5,   192,   193,    30,     5,   304,   103,   195,   307,     3, 
    2119      195,   108,   125,  1270,   111,    31,   195,     3,  1275,    29, 
    2120     1177,   195,  1279,   195,   121,  1282,   123,   195,  1697,   126, 
    2121      127,     3,     5,   104,  1291,  1710,     4,   150,    21,   192, 
    2122      194,  1272,   155,   140,   343,   344,   195,   346,   145,   194, 
    2123       20,     4,     4,   166,   167,   195,   355,   192,   357,   195, 
    2124      192,  1314,   195,   176,   195,  1318,   195,     5,     3,   368, 
    2125        3,   370,   185,   186,   195,   188,   189,     4,    26,   192, 
    2126      193,   194,  1335,  1314,    73,    94,  1343,  1318,   195,   202, 
    2127        5,   390,   125,   195,   108,     5,  1253,   111,     4,  1352, 
    2128      200,     3,   104,   194,  1335,   192,   200,   121,   194,   123, 
    2129      192,   104,   126,   127,  1380,     4,   195,   150,  1550,  1372, 
    2130      195,  1352,   147,  1551,     3,   195,   140,  1380,     5,     3, 
    2131        3,   145,     4,   166,   167,  1567,     5,   194,     5,     5, 
    2132        3,  1372,  1399,   176,    22,   195,     3,     3,  1401,  1380, 
    2133        4,     3,   185,   186,     3,   188,   189,    21,     4,   192, 
    2134      193,   194,  1419,     3,  1550,   195,     3,   195,   467,   202, 
    2135     1401,     4,   471,   195,   195,   195,   194,    52,     4,     3, 
    2136      195,  1567,    57,   482,   192,    11,  1443,    62,    63,   192, 
    2137        3,    21,   192,    19,    20,    21,   192,   192,     4,  1710, 
    2138      499,   500,  1433,  1469,   503,  1362,     4,  1460,     5,  1440, 
    2139      509,   195,     3,   195,   195,   195,  1469,   195,    22,    94, 
    2140        4,   195,     3,  1380,   195,   100,   195,   526,   194,   104, 
    2141      195,     3,     3,   195,     4,     4,   535,     3,  1469,     4, 
    2142     1505,    49,  1592,  1721,  1007,   544,   917,    73,  1007,   100, 
    2143      412,   718,  1505,   552,  1271,  1224,    20,   519,   557,  1272, 
    2144     1268,  1518,  1515,  1443,  1280,    11,  1007,  1699,    94,   421, 
    2145     1433,  1432,  1052,  1526,  1505,   252,  1559,   576,   789,   405, 
    2146     1560,  1565,  1419,   791,  1515,   496,  1007,   721,  1011,   981, 
    2147     1062,   803,  1697,  1218,  1551,  1526,   460,   172,  1566,   125, 
    2148     1557,  1558,  1559,  1288,   554,   994,  1024,   890,  1565,   560, 
    2149     1516,  1526,  1469,  1699,  1352,  1518,  1107,  1343,   560,  1527, 
    2150     1577,  1578,   447,   266,   150,   448,   450,  1580,   764,   808, 
    2151      452,   318,   810,   805,  1591,   455,   565,   327,   637,   565, 
    2152      166,   167,   560,  1382,   386,   560,   619,   880,  1505,   648, 
    2153      176,   560,  1123,     0,     1,   601,   560,   560,   657,   185, 
    2154      186,  1592,   188,   189,   560,   621,   192,   193,   194,   934, 
    2155     1367,  1372,   903,   937,   381,  1440,   202,    24,   560,   909, 
    2156     1645,    28,    29,    30,    31,  1138,   333,   560,    54,   560, 
    2157       37,   281,  1645,  1689,     4,   711,   468,  1654,   695,   560, 
    2158      638,    11,  1188,  1187,    26,   658,  1191,  1395,  1087,    19, 
    2159       20,    21,  1669,    -1,  1645,    -1,    -1,    64,     4,    -1, 
    2160       -1,    -1,    -1,   722,    -1,    11,    -1,    -1,    -1,    -1, 
     2091      11,   294,   168,   459,    73,   220,    52,   288,   459,   213, 
     2092      52,    52,   294,    90,    56,   497,    57,   384,   154,   925, 
     2093     384,    62,    63,   655,   154,   291,   722,   494,   860,   606, 
     2094      52,  1011,   136,   219,   237,   109,   322,   551,   164,   165, 
     2095      52,    52,   294,   141,  1011,   294,    57,   213,   674,   319, 
     2096     939,    62,    63,    94,   100,   258,   987,   237,   100,   100, 
     2097     591,    52,    73,   104,   696,   497,   305,   601,  1033,   600, 
     2098     885,   886,   258,   259,   570,   869,   870,   871,   100,   495, 
     2099     940,   941,   876,    94,  1277,   168,   947,   172,   100,   100, 
     2100     110,  1104,   626,   104,   625,  1282,  1185,     3,     5,  1286, 
     2101    1516,    21,  1289,    19,    20,    24,     3,   945,     3,   100, 
     2102       3,  1277,     3,    56,     3,     3,    97,  1277,    24,     4, 
     2103       3,     5,    97,    27,     3,     3,     3,    24,     3,     5, 
     2104       3,   172,     3,     3,     3,    24,    47,     5,   110,     3, 
     2105       3,    24,   137,   382,     3,    24,    24,     3,   192,    24, 
     2106     353,   220,    52,   356,   198,    24,   732,     3,    64,   237, 
     2107     170,   172,     3,   739,   185,   146,   459,    64,    21,     3, 
     2108       3,   146,     3,   353,     3,    64,   356,   459,     3,     3, 
     2109     258,    64,   192,    24,   399,    64,    64,  1093,     3,    64, 
     2110       3,    24,     3,   560,     3,    64,     3,   333,     3,   194, 
     2111     100,     3,   405,   333,     3,   420,     3,  1172,     3,    24, 
     2112       3,    24,    24,     3,     3,    24,   159,    24,   192,     3, 
     2113     192,   132,   305,    64,     3,   405,   237,   353,   192,   259, 
     2114     356,    64,   418,     5,  1427,   304,    21,   311,   418,   425, 
     2115     325,   310,   428,   317,    21,   431,    24,   679,  1086,    64, 
     2116     319,    64,    64,   322,    24,    64,   522,    64,  1451,    19, 
     2117      20,     3,    18,   714,     3,     3,    22,   155,   279,     3, 
     2118     155,   147,     3,   189,   194,   353,   192,   193,   356,   198, 
     2119     976,  1697,    21,   294,   325,  1451,    64,   194,   192,   374, 
     2120     388,  1451,   198,   586,   497,   315,   316,   380,   381,   382, 
     2121     195,   198,   195,  1392,   195,  1270,   195,   200,   724,   198, 
     2122     194,   497,   201,   606,   325,   198,  1131,   497,   195,   198, 
     2123     198,  1182,   195,   198,   195,   195,   194,   405,  1122,   198, 
     2124     399,   195,   195,   374,   586,   501,   195,    24,   384,   195, 
     2125     331,   194,   353,   384,   878,   356,   877,    52,   359,   195, 
     2126     976,   420,   421,   884,   606,   851,   887,   198,   892,  1467, 
     2127     891,   195,   305,   374,   195,   198,   195,    29,   144,    31, 
     2128     195,   195,  1565,   384,  1567,   147,   155,    64,    52,  1565, 
     2129    1573,   620,  1014,   198,   195,   198,   198,    24,   418,   198, 
     2130     195,   198,  1585,   195,   405,   100,   195,   173,   195,  1585, 
     2131     195,   431,   195,   394,   395,   195,   195,   169,   170,   194, 
     2132     421,   195,  1599,   161,   192,   192,   155,   155,   459,   497, 
     2133     198,   155,   499,   500,   155,   194,   100,    64,    24,   722, 
     2134     192,  1566,  1427,   193,   111,   112,   192,   380,   381,   382, 
     2135     722,   384,    24,   185,   186,   519,   188,    97,   459,    52, 
     2136     192,  1586,   667,   719,   495,   496,   497,   561,   195,    48, 
     2137     664,   587,   588,   589,   668,   669,    24,  1356,    64,    24, 
     2138     722,   155,   598,   722,   572,   611,   679,   325,  1409,  1587, 
     2139     557,   611,    64,  1448,   495,   496,   497,   690,  1468,   195, 
     2140     501,    19,    20,   679,   171,    24,   146,   100,   664,   679, 
     2141     766,  1468,   668,   669,   690,  1518,    64,   125,   192,    64, 
     2142     551,   198,   193,   194,   560,   155,    97,   147,   560,   560, 
     2143    1380,   532,   111,   112,   790,   567,   374,  1342,     3,  1011, 
     2144      24,   987,   999,  1015,   161,    64,   987,   620,   560,   809, 
     2145     551,   811,   192,   554,  1359,   567,   114,    22,   560,   560, 
     2146     591,   592,   192,    19,    20,   192,   742,    52,   176,   600, 
     2147     601,   198,   742,  1195,   194,   146,  1080,   117,   118,    24, 
     2148      64,  1566,  1567,  1150,   192,   586,  1370,   192,  1573,  1011, 
     2149     591,   592,   171,  1015,   625,   626,   192,    24,   194,   600, 
     2150     601,  1586,    29,   192,    31,   606,   192,   125,   667,   640, 
     2151     168,   679,   198,    19,    20,   100,   194,  1513,  1588,    64, 
     2152     192,   192,   690,    24,   625,   626,   198,   560,   103,    21, 
     2153      22,  1588,   150,   108,   567,   193,   111,    24,   639,   640, 
     2154    1164,    29,  1163,    31,   192,   155,   155,   192,   166,   167, 
     2155     198,    22,   192,   198,   655,  1477,   194,   590,   176,     4, 
     2156      87,   175,   200,    64,   194,   140,   599,   185,   186,   125, 
     2157     188,   189,   168,   192,   192,   193,   194,    64,   679,   198, 
     2158     194,   195,   192,     3,   202,    33,   200,   620,   115,   622, 
     2159     623,   624,    18,   724,   194,   696,    22,   193,    18,    87, 
     2160      48,   168,    22,   175,   987,     3,   765,   823,   192,   173, 
     2161     166,   167,   988,   714,   198,   987,   183,     6,     7,   125, 
     2162     176,   722,   194,   724,    22,   194,   193,   115,   131,   185, 
     2163     186,   200,   188,   189,    99,   100,   192,   193,   194,   192, 
     2164     804,   189,   195,   173,   174,   193,   173,   192,   201,   808, 
     2165     809,   845,   811,   198,    24,   141,   183,  1653,   874,    29, 
     2166     192,    31,  1448,   195,   105,   853,   107,   768,   143,  1226, 
     2167     176,   198,   888,   192,   425,   125,   195,   428,     5,   185, 
     2168     186,   168,   188,   189,  1225,   173,   192,   193,   192,   193, 
     2169     906,   192,   173,   174,   920,   826,   912,   198,   185,   186, 
     2170     920,   188,   158,   159,   160,   192,   193,  1201,   113,  1203, 
     2171     926,   198,   192,   872,     4,   195,   194,   750,  1011,  1441, 
     2172     194,   201,  1015,   113,   860,   826,   176,  1184,  1111,   860, 
     2173    1184,   105,   106,    40,    41,   185,   186,   194,   188,  1015, 
     2174    1033,  1011,   192,  1602,  1603,  1015,   877,   878,    28,    29, 
     2175      30,    31,    38,   884,   885,   886,   887,    37,   889,   860, 
     2176     891,   892,   893,  1033,   194,   938,   194,  1150,   927,  1111, 
     2177      62,    63,  1028,   208,   209,  1321,   877,   878,   194,  1325, 
     2178     326,   327,   194,   884,   885,   886,   887,    47,   889,   193, 
     2179     891,   892,   893,   925,   925,   194,  1089,   194,   194,   201, 
     2180      12,    13,    14,    15,    16,    17,    18,    87,  1150,   940, 
     2181     941,     5,    29,   168,    31,   916,   201,   175,    23,  1089, 
     2182     176,   177,   178,   179,   925,    10,     8,   860,   184,   988, 
     2183     185,   186,   194,   188,   190,   115,   192,   192,   193,   940, 
     2184     941,   194,   875,  1011,    68,    69,    70,  1015,    72,   192, 
     2185      29,  1010,    31,   192,   192,   192,   987,   890,     4,  1230, 
     2186       5,   192,   147,  1409,   200,  1033,   169,   105,  1409,   194, 
     2187      87,   185,   186,  1089,   188,   976,   192,    29,   192,    31, 
     2188     195,   195,   168,   194,  1015,     5,   987,   176,   177,   178, 
     2189     179,   195,   925,   173,     5,   184,  1468,     5,   115,   185, 
     2190     186,   190,   188,   151,     3,   938,   192,   193,    87,  1010, 
     2191    1011,   175,  1128,  1014,  1015,   203,  1083,   175,   198,  1275, 
     2192     175,  1089,   195,   185,   186,   175,   188,  1028,  1144,   195, 
     2193     192,  1388,  1033,   195,  1388,    87,   115,   194,  1321,  1233, 
     2194     192,  1234,  1325,     5,    22,  1161,   192,   192,     3,  1080, 
     2195     162,   163,   164,   165,  1113,   194,   173,     3,  1234,   195, 
     2196     111,  1093,  1093,   115,  1234,  1066,   183,    99,   100,   101, 
     2197     102,   185,   186,   195,   188,     4,   174,  1233,   192,  1080, 
     2198     155,   195,   192,     3,   196,   197,     4,     3,  1089,   192, 
     2199    1091,   200,  1093,    11,   173,   194,     4,     4,   195,   131, 
     2200    1131,    19,    20,    21,   183,   185,   186,   139,   188,   114, 
     2201    1111,  1287,   192,   194,   194,   192,  1588,   185,   186,   135, 
     2202     188,   173,   185,   186,   192,   188,  1409,   183,  1159,   192, 
     2203    1131,   183,  1163,  1164,   195,   195,   125,  1409,   185,   186, 
     2204     194,   188,   183,   185,   186,   192,   188,   194,  1184,  1150, 
     2205     192,   195,     5,  1184,   108,    73,   192,   111,  1159,    39, 
     2206    1093,   150,  1163,  1164,   192,   183,  1234,   121,  1227,   123, 
     2207      65,    66,   126,   127,   183,     3,    94,   166,   167,   175, 
     2208     195,    18,     5,  1184,     3,    80,   140,   176,   194,    84, 
     2209      22,   145,   194,  1194,  1195,    90,   185,   186,     3,   188, 
     2210     189,   192,   194,   192,   193,   194,    21,   125,   194,    21, 
     2211     195,   104,   194,   202,   194,     3,     3,   194,  1277,   194, 
     2212       3,   192,   192,  1282,  1225,   147,   170,  1286,   194,  1162, 
     2213    1289,   194,   150,  1234,   140,   194,   155,     3,   115,  1298, 
     2214       3,     5,     3,     5,    30,     5,   195,     3,   166,   167, 
     2215     195,  1184,    31,    29,   195,   195,   195,    25,   176,  1375, 
     2216     195,     3,     3,   158,  1705,     5,   104,   185,   186,     4, 
     2217     188,   189,  1718,   168,   192,   193,   194,   194,  1279,   192, 
     2218     195,   103,   194,    21,   202,     4,   108,    52,    20,   111, 
     2219    1321,  1350,    57,     4,  1325,   195,   192,    62,    63,   121, 
     2220       5,   123,   192,   195,   126,   127,   195,   195,   195,     3, 
     2221       3,  1342,   195,     4,    26,    73,    94,   195,   140,     5, 
     2222    1321,   195,     5,   145,  1325,   200,     4,  1260,  1359,    94, 
     2223       3,    99,   100,   101,   102,   100,   194,   104,   192,   104, 
     2224     195,  1342,   192,   195,   200,   194,     4,   195,  1407,  1380, 
     2225     104,   147,  1388,     3,  1559,     3,     5,  1388,  1359,     4, 
     2226       3,     5,     3,   131,  1558,   133,   134,   135,  1427,   194, 
     2227     138,   139,     5,   141,   142,     5,    22,   195,  1409,  1380, 
     2228     275,  1575,     3,    21,     4,   280,     3,  1388,   283,     3, 
     2229       3,     3,  1451,     4,   195,   290,     3,   195,     4,   192, 
     2230     195,   195,  1558,   195,   194,     3,   195,   172,  1409,   304, 
     2231     192,   192,   307,     3,     5,   192,     4,   192,     4,  1575, 
     2232      21,   195,   195,     3,   195,   195,   195,    22,     4,     3, 
     2233       3,     3,  1600,     4,     4,  1718,  1369,  1468,   195,   194, 
     2234    1441,  1477,   195,   195,   195,   195,  1477,  1448,   343,   344, 
     2235       3,   346,     4,    49,  1729,  1388,  1011,   920,   100,  1011, 
     2236     355,    20,   357,  1275,   412,  1278,  1231,  1526,   719,  1287, 
     2237     519,  1279,  1451,   368,    11,   370,  1477,  1011,   103,   421, 
     2238    1441,  1513,  1513,   108,  1440,  1567,   111,   790,  1056,  1568, 
     2239    1427,   405,  1523,   252,   722,   390,   121,  1573,   123,   792, 
     2240    1559,   126,   127,  1534,  1015,  1011,  1565,  1566,  1567,   496, 
     2241    1066,   985,  1513,  1707,  1573,   140,   804,  1295,  1705,  1225, 
     2242     145,  1574,  1523,   460,   893,   998,  1585,  1586,   554,  1028, 
     2243     560,  1524,  1359,  1534,  1111,  1534,  1526,   560,  1535,  1350, 
     2244    1599,   266,   447,   452,  1477,   448,   450,   765,   809,   806, 
     2245     386,  1707,   811,   318,   455,   565,   560,  1588,   565,   560, 
     2246     325,     0,     1,   560,  1390,  1128,   619,   882,  1375,   318, 
     2247     560,   381,   467,   621,   938,   941,   471,   560,  1448,   327, 
     2248    1513,   560,  1380,   912,   560,    24,   560,   482,   906,    28, 
     2249      29,    30,    31,   560,  1144,     4,   333,    54,    37,  1600, 
     2250    1697,   281,    11,  1662,   499,   500,   468,   560,   503,   374, 
     2251      19,    20,    21,   696,   509,   380,   381,   712,  1677,   384, 
     2252     639,  1653,  1653,    26,  1194,    64,     4,  1403,  1195,  1198, 
     2253     659,   526,  1091,    11,    -1,    -1,    -1,    -1,    -1,    -1, 
     2254     535,    19,    20,    21,    -1,    -1,    -1,    -1,    87,   544, 
     2255      -1,    -1,  1653,    -1,    -1,    -1,    -1,   552,    -1,    -1, 
     2256      -1,    -1,   557,    -1,  1723,    -1,    -1,  1726,    -1,    -1, 
     2257      -1,    -1,    -1,    -1,    -1,    -1,   115,    -1,    -1,    -1, 
     2258    1739,   576,    -1,    -1,    -1,    -1,    -1,  1718,    -1,    -1, 
     2259      -1,     5,     6,     7,     8,     9,    10,    -1,    12,    13, 
     2260      14,    15,    16,    17,  1705,    19,    20,    21,    22,    23, 
     2261      -1,    -1,    -1,    -1,    -1,    -1,   125,  1718,    -1,    -1, 
     2262    1653,  1654,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2263     495,   496,   497,    -1,   173,    -1,    -1,   176,   177,   178, 
     2264     179,   150,    -1,   638,    -1,   184,   155,   125,    -1,    -1, 
     2265      -1,   190,    -1,    -1,   649,     4,    -1,   166,   167,   198, 
     2266      -1,    -1,    11,   658,    -1,    -1,    -1,   176,    -1,    -1, 
     2267      19,    20,   150,    -1,    -1,    -1,   185,   186,    -1,   188, 
     2268     189,    -1,    -1,   192,   193,   194,   551,    -1,   166,   167, 
     2269      -1,    -1,    -1,   202,    -1,   560,    -1,    -1,   176,    -1, 
     2270      -1,    -1,    -1,    -1,    -1,    -1,    -1,   185,   186,    -1, 
     2271     188,   189,    -1,    -1,   192,   193,   194,    -1,    -1,    -1, 
     2272      -1,    -1,    -1,    -1,   202,    -1,   591,   592,   723,    -1, 
     2273      -1,    -1,    -1,    -1,    -1,   600,   601,    -1,    -1,    -1, 
     2274      -1,     4,    -1,    -1,    -1,    -1,    -1,    -1,    11,    -1, 
     2275      -1,   746,    -1,   748,   619,    -1,    19,    20,    -1,    -1, 
     2276     625,   626,    -1,    -1,    -1,    -1,    -1,    -1,   763,    -1, 
     2277      -1,    -1,    -1,    -1,   769,   640,   125,    -1,    -1,    -1, 
     2278      -1,   195,   196,   197,    -1,    -1,    -1,     4,    -1,    -1, 
     2279     655,    -1,    -1,    -1,    11,    -1,    -1,    -1,    38,    -1, 
     2280      -1,   150,    19,    20,    -1,    -1,    -1,   802,    -1,    -1, 
     2281      -1,    -1,    -1,    -1,    -1,    -1,    -1,   166,   167,   814, 
     2282      -1,    -1,    -1,    -1,   819,    -1,   821,   176,    -1,    -1, 
     2283      -1,   696,    -1,    -1,    -1,    -1,   185,   186,    -1,   188, 
     2284     189,    -1,    -1,   192,   193,   194,    -1,    -1,    -1,    -1, 
     2285      -1,    -1,    -1,   202,   849,    -1,    -1,    -1,    -1,   724, 
     2286      -1,    -1,   125,    -1,    -1,   860,    -1,    -1,    -1,   109, 
     2287      -1,    -1,    -1,    -1,   114,    -1,    -1,    -1,    -1,   119, 
     2288     120,    -1,   122,    -1,    -1,   125,   157,   150,   128,   129, 
     2289     130,    -1,    -1,    -1,    -1,    -1,    -1,   168,    -1,    -1, 
     2290      -1,    -1,    -1,   166,   167,    -1,    -1,    -1,   125,    -1, 
     2291      -1,    -1,   907,   176,    -1,    -1,    -1,    -1,   913,    -1, 
     2292      -1,    -1,   185,   186,    -1,   188,   189,    -1,   168,   192, 
     2293     193,   194,    -1,   150,    -1,    -1,    -1,    -1,    -1,   202, 
     2294      -1,    -1,    -1,    -1,    -1,   185,   186,    -1,   188,   166, 
     2295     167,    -1,   192,   193,   949,    -1,    -1,   952,   953,   176, 
     2296     231,   826,    -1,    -1,    -1,    -1,   237,    -1,   185,   186, 
     2297      -1,   188,   189,    -1,    -1,   192,   193,   194,    -1,    -1, 
     2298      -1,   252,     4,    -1,    -1,   202,    -1,    -1,    -1,    11, 
     2299      -1,    -1,    -1,    -1,    -1,   860,    -1,    19,    20,    -1, 
     2300      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2301      -1,    -1,   877,   878,    -1,    -1,    -1,    -1,    -1,   884, 
     2302     885,   886,   887,    -1,   889,    -1,   891,   892,   893,    -1, 
     2303      -1,    -1,    -1,    -1,   305,   306,    -1,    -1,    -1,    -1, 
     2304    1035,    -1,    -1,  1038,    -1,    -1,    -1,   318,    -1,    -1, 
     2305     321,    -1,    -1,    -1,    -1,  1050,    -1,  1052,    -1,    -1, 
     2306     925,    -1,  1057,    -1,    -1,    -1,   337,   338,    -1,  1064, 
     2307    1065,    -1,    -1,   938,    -1,   940,   941,    -1,    -1,    -1, 
     2308      -1,    -1,   353,     4,    -1,   356,    -1,    -1,  1083,  1084, 
     2309      11,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    19,    20, 
     2310      -1,    -1,  1097,   125,  1099,    11,    -1,   378,    -1,   380, 
     2311     381,   382,    -1,    19,    20,  1110,    -1,    -1,    -1,    -1, 
     2312      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   150,    -1, 
     2313      -1,    -1,    -1,    -1,   405,    -1,    -1,    -1,    -1,    -1, 
     2314      -1,    -1,    -1,    -1,   166,   167,  1011,    94,    -1,  1014, 
     2315    1015,    57,    58,    -1,   176,    -1,    -1,   104,    -1,    65, 
     2316      -1,    67,    68,   185,   186,    -1,   188,   189,    -1,    -1, 
     2317     192,   193,   194,    -1,    -1,  1170,    -1,    -1,    -1,  1174, 
     2318     202,    -1,    -1,  1178,    -1,  1180,  1181,    -1,    -1,    -1, 
     2319      -1,    -1,    -1,    -1,    -1,    -1,  1191,    -1,    -1,    -1, 
     2320      -1,    -1,    -1,    -1,   125,    -1,    -1,    -1,    -1,    -1, 
     2321      -1,    -1,    -1,    -1,    -1,  1080,    -1,    -1,    -1,   125, 
     2322      -1,    -1,    -1,    -1,  1219,    -1,    -1,   498,  1093,   150, 
     2323     501,  1226,     4,    -1,  1229,    -1,    -1,  1232,    -1,    11, 
     2324      -1,    -1,   513,    -1,   150,   166,   167,    19,    20,    -1, 
     2325      -1,    -1,    -1,    -1,    -1,   176,    -1,    -1,    -1,    -1, 
     2326     166,   167,  1257,    -1,   185,   186,  1131,   188,   189,     4, 
     2327     176,   192,   193,   194,    -1,    -1,    11,    -1,    -1,   185, 
     2328     186,   202,   188,   189,    19,    20,   192,   193,   194,    -1, 
     2329      -1,    -1,    -1,    -1,  1159,    -1,   202,    -1,  1163,  1164, 
     2330      -1,    -1,    -1,    -1,  1299,    -1,  1301,    -1,    -1,    -1, 
     2331      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,  1184, 
     2332      -1,    -1,    -1,    -1,     4,    -1,    -1,    -1,    -1,  1194, 
     2333    1195,    11,    -1,    -1,    -1,    -1,    -1,  1332,    -1,    19, 
     2334      20,    -1,    -1,  1338,    -1,    -1,    -1,    -1,    -1,   620, 
     2335      -1,    -1,    -1,   125,    -1,    -1,    -1,    -1,    -1,  1354, 
     2336      -1,    -1,    -1,  1358,    -1,    -1,    -1,    -1,    -1,    -1, 
     2337      -1,   318,    -1,    -1,    -1,    -1,    -1,    -1,   150,    -1, 
     2338      -1,  1376,    -1,  1378,   655,    -1,  1381,    -1,  1383,  1384, 
     2339     125,  1386,    -1,    -1,   166,   167,    -1,    -1,    -1,    -1, 
     2340      -1,    -1,  1397,   674,   176,    -1,    -1,    -1,    -1,    -1, 
     2341      -1,    -1,    -1,   185,   186,   150,   188,   189,    -1,    -1, 
     2342     192,   193,   194,    -1,    -1,   696,    -1,    -1,    -1,    -1, 
     2343     202,   166,   167,   380,   381,    -1,   707,    -1,   709,    -1, 
     2344      -1,   176,    -1,    -1,    -1,   125,    -1,    -1,    -1,    -1, 
     2345     185,   186,    -1,   188,   189,  1450,    -1,   192,   193,   194, 
     2346      -1,    -1,    -1,    -1,    -1,    -1,    -1,   202,    -1,    -1, 
     2347     150,    -1,    -1,    -1,    -1,    -1,    -1,  1342,   749,    -1, 
     2348     751,    -1,    -1,    -1,    -1,    -1,   166,   167,   759,    -1, 
     2349      -1,   762,    -1,    -1,  1359,    -1,   176,    -1,    -1,    -1, 
     2350      -1,    -1,    -1,    -1,    -1,   185,   186,    -1,   188,   189, 
     2351      -1,    -1,   192,   193,   194,  1380,    -1,    -1,    -1,  1514, 
     2352      -1,    -1,   202,  1388,    -1,  1520,    -1,    -1,    -1,    -1, 
     2353    1525,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2354      -1,  1536,  1537,  1538,    -1,    -1,    -1,    -1,   495,   496, 
     2355       5,    -1,  1547,    -1,    -1,    -1,    11,    -1,    -1,    -1, 
     2356    1555,    -1,  1557,    -1,    19,    20,    -1,    22,    -1,    -1, 
     2357      -1,    -1,    -1,    -1,    -1,  1440,  1441,   848,    -1,    -1, 
     2358      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2359      -1,    -1,    -1,    -1,    -1,    -1,    -1,   868,   869,   870, 
     2360     871,    -1,    -1,  1468,   551,   876,    -1,    -1,    -1,     5, 
     2361      -1,   882,  1477,    -1,    -1,    11,    -1,    -1,    -1,    -1, 
    21612362      -1,    -1,    -1,    19,    20,    -1,    -1,    -1,    -1,    -1, 
    2162       87,    -1,    -1,   318,    -1,    -1,   745,    -1,   747,    -1, 
    2163      325,    -1,    -1,    -1,    -1,    -1,    -1,  1710,  1715,    -1, 
    2164       -1,  1718,    -1,   762,    -1,    -1,  1697,    -1,   115,   768, 
    2165       -1,    -1,    -1,    -1,  1731,    -1,    -1,    -1,    -1,  1710, 
    2166       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,  1645,  1646, 
    2167       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   374, 
    2168       -1,    -1,   801,    -1,    -1,   380,   381,    -1,    -1,   384, 
    2169       -1,    -1,    -1,    -1,   813,   125,    -1,    -1,    -1,   818, 
    2170        4,   820,    -1,    -1,    -1,    -1,   173,    11,    -1,   176, 
    2171      177,   178,   179,    -1,    -1,    19,    20,   184,    -1,   125, 
    2172      150,    -1,    -1,   190,    -1,    -1,    -1,    -1,    -1,   848, 
    2173       -1,   198,    -1,    -1,    -1,    -1,   166,   167,    -1,    -1, 
    2174      859,    -1,    -1,    -1,   150,    -1,   176,    -1,    -1,    -1, 
    2175       -1,    -1,    -1,    -1,    -1,   185,   186,    -1,   188,   189, 
    2176      166,   167,   192,   193,   194,    -1,    -1,    -1,    -1,    -1, 
    2177      176,    -1,   202,    -1,    -1,    -1,    -1,    -1,    -1,   185, 
    2178      186,    -1,   188,   189,   157,   904,   192,   193,   194,    -1, 
    2179       -1,   910,    -1,    -1,    -1,   168,   202,    -1,    -1,    -1, 
    2180      495,   496,   497,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2363      -1,    -1,    -1,    -1,    -1,  1630,    -1,    -1,    -1,    -1, 
     2364      -1,    -1,    -1,    -1,   591,   592,    -1,   918,  1513,    -1, 
     2365      -1,    -1,  1647,   600,   601,    -1,    -1,    -1,  1523,    -1, 
     2366      -1,    -1,    -1,  1658,    -1,    -1,    -1,   938,   939,  1534, 
     2367     125,    -1,   619,    -1,   945,     5,    -1,   948,   625,   626, 
     2368      -1,    11,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    19, 
     2369      20,    -1,    -1,   640,    -1,   150,    -1,    -1,    -1,    -1, 
     2370      -1,  1696,    -1,    -1,  1699,   976,    -1,    -1,   655,    -1, 
     2371      -1,   166,   167,   984,    -1,    -1,    -1,    -1,    -1,    -1, 
     2372      -1,   176,    -1,  1588,    -1,    -1,    -1,    -1,    -1,   125, 
     2373     185,   186,    -1,   188,   189,    -1,    -1,   192,   193,   194, 
     2374      -1,    -1,    -1,  1014,    -1,    -1,    -1,   202,    -1,   696, 
     2375      -1,    -1,  1023,    -1,   150,    -1,  1027,  1028,    -1,  1030, 
     2376    1031,    -1,  1033,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2377     166,   167,    -1,    -1,    -1,    -1,    -1,   724,    -1,    -1, 
     2378     176,    -1,    -1,    -1,    -1,    -1,    -1,    -1,  1653,   185, 
     2379     186,    -1,   188,   189,    -1,   125,   192,   193,   194,    -1, 
     2380      -1,    -1,    -1,    -1,    -1,    -1,   202,    -1,    -1,    -1, 
     2381      -1,    -1,    -1,    -1,    -1,  1086,    -1,    -1,  1089,    -1, 
     2382     150,  1092,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2383      -1,    -1,    -1,    -1,     5,    -1,   166,   167,    -1,    -1, 
     2384      11,    -1,    -1,    -1,    -1,    -1,   176,    -1,    19,    20, 
     2385      -1,  1122,    -1,    -1,    -1,   185,   186,    -1,   188,   189, 
     2386      -1,    -1,   192,   193,   194,    -1,    -1,    -1,    -1,    -1, 
     2387      -1,    -1,   202,    -1,    -1,    -1,    -1,    -1,    -1,   826, 
    21812388      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2182       -1,   125,    -1,    -1,    -1,    -1,   945,    -1,    -1,   948, 
    2183      949,    -1,     4,    -1,    -1,    -1,    -1,    -1,    -1,    11, 
    2184       -1,    -1,    -1,    -1,    -1,    -1,   150,    19,    20,    -1, 
    2185       -1,    -1,    -1,    -1,    -1,    -1,   551,    -1,   231,    -1, 
    2186       -1,    -1,   166,   167,   237,   560,    -1,    -1,    -1,    -1, 
    2187       -1,    -1,   176,    -1,    -1,    -1,    -1,    -1,    -1,   252, 
     2389      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2390      -1,  1172,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2391      -1,    -1,    -1,    -1,  1185,    -1,    -1,    -1,    -1,    -1, 
     2392      -1,    -1,    -1,  1194,  1195,    -1,    -1,    11,    -1,    -1, 
     2393     877,   878,    -1,    -1,    -1,    19,    20,   884,   885,   886, 
     2394     887,    -1,   889,    -1,   891,   892,   893,    -1,    -1,    -1, 
     2395      -1,    -1,    -1,  1224,   125,     6,     7,     8,    -1,    10, 
     2396      -1,    12,    13,    14,    15,    16,    17,    18,    19,    20, 
     2397      21,    22,    23,    24,    58,    -1,    -1,    -1,    -1,   150, 
     2398      -1,    65,    -1,    67,    68,    -1,    -1,    -1,  1259,    -1, 
     2399      -1,   938,  1263,   940,   941,   166,   167,    -1,    -1,  1270, 
     2400      -1,    -1,    -1,    -1,    -1,   176,    -1,    -1,    -1,    -1, 
     2401      -1,    -1,    -1,    64,   185,   186,    11,   188,   189,    -1, 
     2402      -1,   192,   193,   194,    19,    20,    -1,    11,    -1,    -1, 
     2403      -1,   202,    -1,  1304,    -1,    19,    20,    -1,    -1,    -1, 
     2404      24,   125,    -1,    -1,    -1,    -1,    -1,  1318,    -1,    -1, 
     2405      -1,    -1,    -1,    -1,    49,    -1,    51,    52,    53,    54, 
     2406      -1,    56,    -1,    58,    59,    -1,   150,  1014,    -1,    -1, 
     2407      65,    -1,    67,    68,    69,    -1,    -1,    -1,    -1,    -1, 
     2408      64,    -1,   166,   167,    -1,  1356,    -1,    -1,    -1,    -1, 
     2409      -1,    -1,   176,    -1,    -1,    -1,    -1,  1368,    -1,  1370, 
    21882410      -1,   185,   186,    -1,   188,   189,    -1,    -1,   192,   193, 
    2189      194,    -1,    -1,    -1,     4,    -1,   591,   592,   202,    -1, 
    2190       -1,    11,    -1,    -1,    -1,   600,   601,    -1,    -1,    19, 
    2191       20,    -1,  1031,    -1,    -1,  1034,    -1,    -1,    -1,    -1, 
    2192       -1,    -1,    -1,    -1,   619,    -1,    -1,  1046,    -1,  1048, 
    2193      625,    -1,   305,   306,  1053,    -1,    -1,    -1,    -1,    -1, 
    2194       -1,  1060,  1061,    -1,   639,   318,    -1,    -1,   321,    -1, 
    2195       -1,    -1,    -1,   125,    -1,    -1,    -1,    -1,    -1,   654, 
    2196     1079,  1080,    -1,    -1,   337,   338,    -1,    -1,    -1,    -1, 
    2197        4,    -1,    -1,    -1,  1093,    -1,  1095,    11,   150,    -1, 
    2198      353,    -1,    -1,   356,    -1,    19,    20,  1106,    -1,    -1, 
    2199       -1,    -1,    -1,    -1,   166,   167,    -1,    -1,    -1,    -1, 
    2200      695,    -1,    -1,    -1,   176,   378,    -1,   380,   381,   382, 
    2201       -1,    -1,    -1,   185,   186,   125,   188,   189,    -1,    -1, 
    2202      192,   193,   194,    -1,    -1,    -1,    -1,    -1,   723,    -1, 
    2203      202,    -1,   405,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2204      150,    -1,    -1,    -1,  1163,    -1,    -1,    -1,  1167,    -1, 
    2205       -1,    -1,  1171,    -1,  1173,  1174,   166,   167,    -1,    -1, 
    2206       -1,    -1,    -1,    -1,    -1,  1184,   176,    -1,    -1,    -1, 
    2207       -1,    -1,    -1,    -1,    -1,   185,   186,    -1,   188,   189, 
    2208       -1,    -1,   192,   193,   194,    -1,    -1,    -1,    -1,    -1, 
    2209       -1,   125,   202,  1212,    -1,    -1,    -1,    -1,    -1,    -1, 
    2210     1219,    -1,    -1,  1222,     4,    -1,  1225,    -1,    -1,    -1, 
    2211       -1,    11,    -1,    -1,    -1,    -1,   150,    -1,    -1,    19, 
    2212       20,    -1,    -1,    -1,    -1,   498,    -1,    94,   501,    -1, 
    2213      825,  1250,   166,   167,    -1,    -1,    -1,   104,    -1,    -1, 
    2214      513,    -1,   176,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2215       -1,   185,   186,    -1,   188,   189,    -1,    -1,   192,   193, 
    2216      194,    -1,    -1,    -1,   859,    -1,    -1,    -1,   202,    -1, 
    2217       -1,    -1,    -1,  1292,    -1,  1294,    -1,    -1,    -1,    -1, 
    2218       -1,   876,    -1,    -1,     4,    -1,    -1,   882,   883,   884, 
    2219      885,    11,   887,    -1,   889,   890,    -1,    -1,    -1,    19, 
    2220       20,    -1,    -1,    -1,    -1,    -1,  1325,    -1,    -1,    -1, 
    2221       -1,    -1,  1331,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2222       -1,    -1,    -1,    -1,    -1,   125,    -1,   922,  1347,    -1, 
    2223       -1,    -1,  1351,    -1,    -1,    -1,    -1,    -1,    -1,   934, 
    2224       -1,   936,   937,    -1,    25,    -1,    -1,   620,    -1,  1368, 
    2225      150,  1370,    -1,    -1,  1373,    -1,  1375,  1376,    -1,  1378, 
    2226       -1,    -1,     4,    -1,    -1,    -1,   166,   167,    -1,    11, 
    2227     1389,    -1,    -1,    -1,    -1,    -1,   176,    19,    20,    -1, 
    2228       -1,   654,    -1,    -1,    -1,   185,   186,    -1,   188,   189, 
    2229       -1,    -1,   192,   193,   194,    -1,    -1,    -1,    -1,    -1, 
    2230      673,    -1,   202,    -1,    -1,   125,    -1,    -1,    -1,    -1, 
    2231       -1,    -1,  1007,    -1,    -1,  1010,  1011,    -1,    99,   100, 
    2232      101,   102,   695,  1442,    -1,    -1,    -1,    -1,     5,    -1, 
    2233      150,    -1,    -1,   706,    11,   708,    -1,    -1,    -1,    -1, 
    2234       -1,    -1,    19,    20,    -1,    22,   166,   167,    -1,    -1, 
    2235      131,   318,   133,   134,   135,    -1,   176,   138,   139,    -1, 
    2236      141,   142,    -1,    -1,    -1,   185,   186,    -1,   188,   189, 
    2237       -1,    -1,   192,   193,   194,   748,    -1,   750,    -1,    -1, 
    2238       -1,  1076,   202,   125,    -1,   758,    -1,  1506,   761,    -1, 
    2239       -1,    -1,    -1,  1512,  1089,    -1,    -1,    -1,  1517,    -1, 
    2240       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   150,  1528, 
    2241     1529,  1530,    -1,   380,   381,    -1,    -1,    -1,    -1,    -1, 
    2242     1539,     5,    -1,    -1,   166,   167,    -1,    11,  1547,    -1, 
    2243     1549,  1126,    -1,    -1,   176,    19,    20,    -1,    -1,    -1, 
    2244       -1,    -1,    -1,   185,   186,    -1,   188,   189,   125,    -1, 
    2245      192,   193,   194,    -1,    -1,    -1,    -1,    -1,  1153,    -1, 
    2246      202,    -1,  1157,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2247       -1,    -1,    -1,   150,   847,    -1,    -1,    -1,    -1,    -1, 
    2248       -1,    -1,  1177,    -1,    -1,    -1,    -1,    -1,    -1,   166, 
    2249      167,    -1,  1187,  1188,   867,   868,   869,   870,    -1,   176, 
    2250       -1,    -1,   875,  1622,    -1,    -1,    -1,   880,   185,   186, 
    2251       -1,   188,   189,    -1,    -1,   192,   193,   194,    -1,    -1, 
    2252     1639,    -1,    -1,    -1,    -1,   202,    -1,    -1,   495,   496, 
    2253       -1,  1650,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2254       -1,   125,   915,     5,    -1,    -1,    -1,    -1,    -1,    11, 
    2255       -1,    -1,    -1,    -1,    -1,    -1,    -1,    19,    20,    -1, 
    2256       -1,   934,   935,    -1,    -1,    -1,   150,    -1,   941,  1688, 
    2257       -1,   944,  1691,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2258        5,    -1,   166,   167,   551,    -1,    11,    -1,    -1,    -1, 
    2259       -1,    -1,   176,    -1,    19,    20,    -1,    -1,    -1,   972, 
    2260       -1,   185,   186,    -1,   188,   189,    -1,   980,   192,   193, 
    2261      194,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   202,    -1, 
    2262       11,    -1,    -1,    -1,   591,   592,    -1,    -1,    19,    20, 
    2263       -1,    -1,    -1,   600,   601,    -1,    -1,  1010,    -1,    -1, 
    2264     1335,    -1,    -1,    -1,    -1,    -1,  1019,    -1,    -1,    -1, 
    2265     1023,  1024,   619,  1026,  1027,    -1,  1029,  1352,   625,    -1, 
    2266       -1,    -1,    -1,   125,    -1,    -1,    57,    58,    -1,    -1, 
    2267       -1,    -1,   639,    -1,    65,    -1,    67,  1372,    -1,    -1, 
    2268       -1,    -1,    -1,    -1,    -1,  1380,    -1,   654,   150,    -1, 
     2411     194,   162,   163,   164,   165,    -1,    -1,    -1,   202,  1390, 
     2412      -1,  1392,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2413     125,    -1,    -1,  1080,    -1,    -1,    -1,    -1,    -1,    -1, 
     2414      -1,   125,   193,    -1,    -1,   196,   197,   198,    -1,    -1, 
     2415     201,    -1,    -1,    -1,    -1,   150,    -1,    -1,    -1,    -1, 
     2416      -1,    -1,    -1,    -1,    -1,    -1,   150,    -1,    -1,  1440, 
     2417    1441,   166,   167,    -1,    -1,    -1,  1447,  1448,    -1,    -1, 
     2418      -1,   176,   166,   167,  1131,    -1,    -1,    -1,    -1,    -1, 
     2419     185,   186,   176,   188,   189,    -1,  1467,   192,   193,   194, 
     2420      -1,   185,   186,    -1,   188,   189,    -1,   202,   192,   193, 
     2421     194,    -1,  1159,    -1,   198,    -1,  1163,  1164,   202,    -1, 
     2422      -1,  1492,  1493,  1494,  1495,  1496,  1497,  1498,  1499,  1500, 
     2423    1501,  1502,  1503,  1504,  1505,  1506,  1507,  1508,  1509,  1510, 
     2424      -1,    -1,    -1,    -1,    -1,    -1,    -1,  1194,  1195,    -1, 
     2425      -1,    -1,     6,     7,     8,    -1,    10,    -1,    12,    13, 
     2426      14,    15,    16,    17,    18,    19,    20,    21,    22,    23, 
     2427      24,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    22692428      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2270      125,    -1,    -1,    -1,   166,   167,    -1,    -1,    -1,  1082, 
    2271       -1,    -1,  1085,    -1,   176,  1088,    -1,    -1,    -1,    -1, 
    2272       -1,    -1,    -1,   185,   186,   150,   188,   189,   695,    -1, 
    2273      192,   193,   194,    -1,   125,    -1,    -1,  1432,  1433,    -1, 
    2274      202,   166,   167,    -1,    -1,  1118,    -1,    -1,    -1,    -1, 
    2275       -1,   176,    -1,    -1,    -1,    -1,   723,    -1,    -1,   150, 
    2276      185,   186,    -1,   188,   189,  1460,    -1,   192,   193,   194, 
    2277       -1,    -1,    -1,    -1,  1469,   166,   167,   202,    -1,    -1, 
    2278       -1,    -1,    -1,    -1,    -1,   176,    -1,    -1,    -1,    -1, 
    2279       -1,    -1,  1165,    -1,   185,   186,    -1,   188,   189,    -1, 
    2280       -1,   192,   193,   194,    -1,  1178,    -1,    -1,    -1,    -1, 
    2281     1505,   202,    -1,    -1,  1187,  1188,    -1,    -1,    -1,    -1, 
    2282     1515,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2283       -1,  1526,    -1,    -1,    -1,    -1,    -1,    -1,    -1,     6, 
    2284        7,     8,    -1,    10,  1217,    12,    13,    14,    15,    16, 
    2285       17,    18,    19,    20,    21,    22,    23,    24,   825,     5, 
    2286        6,     7,     8,     9,    10,    -1,    12,    13,    14,    15, 
    2287       16,    17,    -1,    19,    20,    21,    22,    23,    -1,  1252, 
    2288       -1,    -1,    -1,  1256,    -1,  1580,    -1,    -1,    -1,    -1, 
    2289     1263,    -1,    -1,    -1,    -1,    -1,    -1,    64,    -1,    -1, 
    2290       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   876, 
    2291       -1,    -1,    -1,    -1,    -1,   882,   883,   884,   885,    -1, 
    2292      887,    -1,   889,   890,  1297,    -1,    -1,    -1,    -1,    -1, 
    2293       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,  1311,    -1, 
    2294       -1,    -1,    -1,    -1,    -1,     6,     7,     8,    -1,    10, 
    2295     1645,    12,    13,    14,    15,    16,    17,    18,    19,    20, 
    2296       21,    22,    23,    24,    -1,    -1,    -1,   934,    -1,   936, 
    2297      937,    -1,    -1,    -1,    -1,    -1,  1349,    -1,    -1,    -1, 
    2298       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,  1361,    -1, 
    2299     1363,    -1,    -1,    -1,    -1,   162,   163,   164,   165,    -1, 
    2300       -1,    -1,    -1,    64,    -1,    -1,    -1,    -1,    -1,  1382, 
    2301       -1,  1384,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2302       -1,    -1,    -1,    -1,    -1,    -1,   193,    -1,    -1,   196, 
    2303      197,   198,    -1,    11,   201,    -1,    -1,    -1,    -1,    -1, 
    2304       -1,    19,    20,  1010,    -1,    -1,    -1,    -1,    -1,   195, 
    2305      196,   197,    -1,    -1,    -1,    -1,    -1,    -1,    -1,  1432, 
    2306     1433,    -1,    -1,    -1,    -1,    -1,  1439,  1440,    -1,    -1, 
    2307       -1,    49,    -1,    51,    52,    53,    54,    -1,    56,    -1, 
    2308       58,    59,    -1,    -1,    -1,    -1,  1459,    65,    -1,    67, 
    2309       -1,    69,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2310       -1,   162,   163,   164,   165,    -1,    -1,    -1,    -1,  1076, 
    2311       -1,  1484,  1485,  1486,  1487,  1488,  1489,  1490,  1491,  1492, 
    2312     1493,  1494,  1495,  1496,  1497,  1498,  1499,  1500,  1501,  1502, 
    2313       -1,    -1,   193,   194,    -1,   196,   197,   198,    -1,   200, 
    2314       -1,    -1,    -1,    -1,    -1,    11,    -1,   125,    -1,    -1, 
    2315       -1,    -1,    -1,    19,    20,    21,    -1,    -1,    -1,  1126, 
     2429      -1,  1562,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    23162430      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2317       -1,    -1,   150,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2318       -1,  1554,    -1,    -1,    50,    -1,  1153,    -1,   166,   167, 
    2319     1157,    -1,    58,    -1,    60,    61,    62,    63,   176,    65, 
    2320       -1,    67,    -1,    -1,    -1,    -1,  1579,   185,   186,    -1, 
    2321      188,   189,    -1,    -1,   192,   193,   194,    -1,    11,    -1, 
    2322     1187,  1188,    -1,  1596,   202,    -1,    19,    20,    -1,    -1, 
     2431      64,    -1,    -1,    -1,    -1,    -1,  1587,    -1,    -1,    -1, 
     2432      -1,    11,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    19, 
     2433      20,    21,    -1,  1604,    -1,    -1,    -1,    -1,    -1,    -1, 
    23232434      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2324     1613,  1614,    -1,    -1,    -1,  1618,    -1,  1620,    -1,    -1, 
    2325       -1,    -1,    -1,    -1,    -1,    -1,    49,    -1,    -1,   125, 
    2326       53,    54,    55,    56,    57,    58,    -1,    -1,    -1,    -1, 
    2327       -1,    -1,    65,    66,    67,    -1,    -1,    -1,    -1,    -1, 
    2328       -1,    -1,    -1,    -1,   150,    -1,    -1,    -1,    -1,    -1, 
     2435    1621,  1622,    -1,    -1,    -1,  1626,    -1,  1628,    -1,    -1, 
     2436      50,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    58,    -1, 
     2437      60,    61,    62,    63,    -1,    65,    -1,    67,    68,    -1, 
    23292438      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2330      166,   167,   168,    -1,    -1,  1678,    -1,    11,    -1,    -1, 
    2331      176,    -1,    -1,    -1,    -1,    19,    20,    -1,    -1,   185, 
    2332      186,    -1,   188,   189,    -1,    -1,   192,   193,   194,    -1, 
    2333       -1,  1704,   125,    -1,    -1,    -1,   202,    -1,    -1,    -1, 
    2334       44,    -1,    -1,    -1,    -1,    -1,  1719,    -1,  1721,  1722, 
    2335       -1,    -1,    -1,    -1,    58,  1728,    -1,   150,    -1,    -1, 
    2336     1733,    65,    -1,    67,    68,    -1,    -1,    -1,  1335,    -1, 
    2337       -1,    -1,    11,   166,   167,    -1,    -1,    -1,    -1,    -1, 
    2338       19,    20,    -1,   176,    -1,  1352,    -1,    -1,    -1,    -1, 
    2339       -1,    -1,   185,   186,    -1,   188,   189,    -1,    -1,   192, 
    2340      193,   194,    -1,    -1,    -1,  1372,   110,    -1,    -1,   202, 
    2341       49,    -1,    51,    -1,    53,    54,    -1,    56,    -1,    58, 
    2342       59,   125,    -1,    -1,    -1,    -1,    65,    -1,    67,    -1, 
    2343       69,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2344       -1,    -1,    -1,    -1,    -1,    -1,   150,    11,    -1,    -1, 
    2345       -1,    -1,   156,    -1,    -1,    19,    20,    -1,    -1,    -1, 
    2346       -1,    -1,   166,   167,    -1,  1432,  1433,    -1,    -1,    -1, 
     2439      -1,    -1,    -1,    -1,    -1,  1342,    -1,    -1,    -1,    -1, 
     2440      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   162,   163, 
     2441     164,   165,  1359,    -1,    -1,  1686,    -1,    -1,    -1,    -1, 
     2442      -1,    -1,    -1,    11,    -1,    -1,    -1,    -1,    -1,    -1, 
     2443      -1,    19,    20,  1380,    -1,   125,    -1,    -1,    -1,   193, 
     2444     194,  1712,   196,   197,   198,    -1,   200,    -1,    -1,    -1, 
     2445      -1,    -1,    -1,    -1,    -1,    -1,  1727,    -1,  1729,  1730, 
     2446     150,    -1,    -1,    11,    -1,  1736,    -1,    -1,    -1,    -1, 
     2447    1741,    19,    20,    -1,    -1,    -1,   166,   167,   168,    -1, 
     2448      -1,    -1,    -1,    -1,    -1,    -1,   176,    -1,    -1,    -1, 
     2449      -1,    -1,    -1,  1440,  1441,   185,   186,    -1,   188,   189, 
     2450      -1,    49,   192,   193,   194,    53,    54,    55,    56,    57, 
     2451      58,    -1,   202,    11,    -1,    -1,    -1,    65,    66,    67, 
     2452      68,    19,    20,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2453      -1,    -1,    -1,    -1,    -1,    -1,    -1,   125,    -1,    -1, 
     2454      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2455      -1,    49,    -1,    51,    -1,    53,    54,    -1,    56,    -1, 
     2456      58,    59,   150,    -1,    -1,    -1,    11,    65,    -1,    67, 
     2457      68,    69,    -1,    -1,    19,    20,  1523,   125,   166,   167, 
     2458      -1,    -1,    -1,    -1,    -1,    -1,    -1,  1534,   176,    -1, 
     2459      -1,    -1,    -1,    -1,    -1,    -1,    -1,   185,   186,    44, 
     2460     188,   189,   150,    11,   192,   193,   194,   195,    -1,    -1, 
     2461      -1,    19,    20,    58,   202,    -1,    -1,    -1,   166,   167, 
     2462      65,    -1,    67,    68,    -1,    -1,    -1,   125,   176,    -1, 
     2463      -1,    -1,    -1,    -1,    -1,    -1,    -1,   185,   186,    -1, 
     2464     188,   189,    -1,    -1,   192,   193,   194,    -1,    -1,    -1, 
     2465      58,    -1,   150,    11,   202,    -1,    -1,    65,    -1,    67, 
     2466      68,    19,    20,    -1,    -1,   110,    24,    -1,   166,   167, 
     2467      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   176,    -1, 
     2468     125,    -1,    -1,    -1,    -1,    -1,    -1,   185,   186,    -1, 
     2469     188,   189,    -1,    11,   192,   193,   194,    -1,    -1,    -1, 
     2470      -1,    19,    20,    21,   202,   150,    64,    -1,    -1,    -1, 
     2471      -1,   156,    -1,    -1,    -1,    -1,    -1,   125,    -1,    -1, 
     2472      -1,   166,   167,    -1,    -1,    -1,    -1,    11,    -1,    -1, 
     2473      -1,   176,    -1,    -1,    -1,    19,    20,    -1,    -1,    -1, 
     2474     185,   186,   150,   188,   189,    -1,    -1,   192,   193,   194, 
     2475      -1,    -1,    -1,    -1,    -1,    -1,    -1,   202,   166,   167, 
     2476      -1,    -1,    -1,    -1,    11,    -1,    -1,   125,   176,    -1, 
     2477      -1,    -1,    19,    20,    21,    -1,    -1,   185,   186,    -1, 
     2478     188,   189,    -1,    -1,   192,   193,   194,    -1,    -1,    -1, 
     2479      -1,    -1,   150,    11,   202,    -1,    -1,    -1,    -1,    -1, 
     2480      -1,    19,    20,    21,    -1,    -1,    -1,   125,   166,   167, 
     2481      94,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   176,    -1, 
     2482      -1,    -1,    -1,    -1,    -1,    -1,    -1,   185,   186,    -1, 
     2483     188,   189,   150,    -1,   192,   193,   194,    -1,    -1,    -1, 
     2484     198,   125,    -1,    11,   202,    -1,    -1,    -1,   166,   167, 
     2485     168,    19,    20,    21,    -1,    -1,    -1,    -1,   176,    -1, 
     2486      -1,    -1,    -1,    -1,    -1,    -1,   150,   185,   186,    -1, 
     2487     188,   189,    11,    -1,   192,   193,   194,    -1,   125,    -1, 
     2488      19,    20,   166,   167,   202,    -1,    -1,    -1,    -1,    -1, 
    23472489      -1,    -1,   176,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2348       -1,   185,   186,    -1,   188,   189,   125,    11,   192,   193, 
    2349      194,    -1,    -1,    -1,    58,    19,    20,    -1,   202,    -1, 
    2350       -1,    65,    -1,    67,    68,    -1,    -1,    -1,    -1,    -1, 
    2351       -1,   150,    -1,    -1,    -1,    -1,    -1,    11,    -1,    -1, 
    2352       -1,    -1,    -1,    -1,    -1,    19,    20,   166,   167,    -1, 
    2353       24,    -1,    -1,    -1,    58,    -1,    -1,   176,    -1,    -1, 
    2354       -1,    65,    -1,    67,    68,    -1,   185,   186,  1515,   188, 
    2355      189,    -1,    -1,   192,   193,   194,    -1,    -1,    -1,  1526, 
    2356       -1,   125,    -1,   202,    -1,    -1,    11,    -1,    -1,    -1, 
    2357       64,    -1,    -1,    -1,    19,    20,    -1,    -1,    -1,    24, 
    2358       -1,    -1,    -1,    -1,    -1,    -1,   150,    -1,    -1,    -1, 
    2359       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    11, 
    2360       -1,   125,   166,   167,    -1,    -1,    -1,    19,    20,    21, 
    2361       -1,    -1,   176,    -1,    -1,    -1,    -1,    -1,    -1,    64, 
    2362       -1,   185,   186,    -1,   188,   189,   150,    -1,   192,   193, 
    2363      194,   125,    11,    -1,    -1,    -1,    -1,    -1,   202,    -1, 
    2364       19,    20,   166,   167,    -1,    -1,    -1,    -1,    -1,    -1, 
    2365       -1,    -1,   176,    -1,    -1,    -1,   150,    -1,    -1,    -1, 
    2366       -1,   185,   186,    -1,   188,   189,    -1,    -1,   192,   193, 
    2367      194,    -1,   166,   167,    -1,    -1,    -1,    11,   202,    -1, 
    2368      125,    -1,   176,    -1,    -1,    19,    20,    21,    11,    -1, 
    2369       -1,   185,   186,    -1,   188,   189,    19,    20,   192,   193, 
    2370      194,    -1,    -1,    -1,   198,   150,    -1,    -1,   202,    -1, 
    2371       -1,    -1,    -1,   125,    -1,    94,    -1,    -1,    -1,    -1, 
    2372       -1,   166,   167,    -1,    -1,    11,    -1,    -1,    -1,    -1, 
    2373       -1,   176,    -1,    19,    20,    21,    -1,    -1,   150,    -1, 
    2374      185,   186,    -1,   188,   189,    -1,   125,   192,   193,   194, 
    2375       -1,    -1,    -1,   198,   166,   167,   168,   202,    -1,    11, 
    2376       -1,    -1,    -1,    -1,   176,    -1,    -1,    19,    20,    21, 
    2377       11,   150,    -1,   185,   186,    -1,   188,   189,    19,    20, 
    2378      192,   193,   194,    -1,    -1,    -1,    -1,   166,   167,    -1, 
    2379      202,   125,    -1,    -1,    -1,    -1,    -1,   176,    -1,    -1, 
    2380       -1,    -1,   125,    -1,    -1,    -1,   185,   186,    -1,   188, 
    2381      189,    -1,    -1,   192,   193,   194,   150,    11,    -1,    -1, 
    2382       -1,    -1,    -1,   202,    -1,    19,    20,   150,    -1,    -1, 
    2383       -1,    -1,   166,   167,    -1,    -1,    -1,    -1,    -1,   125, 
    2384       -1,    11,   176,   166,   167,    -1,    -1,    -1,    -1,    19, 
    2385       20,   185,   186,   176,   188,   189,    -1,    -1,   192,   193, 
    2386      194,    -1,   185,   186,   150,   188,   189,    -1,   202,   192, 
    2387      193,   194,   195,   125,    11,    -1,    -1,    -1,    -1,   202, 
    2388      166,   167,    19,    20,   125,    -1,    -1,    -1,    -1,    -1, 
    2389      176,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   150,   185, 
    2390      186,    -1,   188,   189,    -1,    -1,   192,   193,   194,   150, 
    2391       -1,    11,    -1,    -1,   166,   167,   202,    -1,    -1,    19, 
    2392       20,    -1,    -1,    -1,   176,   166,   167,    -1,    -1,    -1, 
    2393       -1,   125,    -1,   185,   186,   176,   188,   189,    -1,    -1, 
    2394      192,   193,   194,    -1,   185,   186,    -1,   188,   189,    -1, 
    2395      202,   192,   193,   194,    -1,   125,   150,    11,    -1,    -1, 
    2396       -1,   202,    -1,    -1,    -1,    19,    20,    -1,    11,    -1, 
    2397       -1,    -1,   166,   167,    -1,    -1,    19,    20,    -1,    -1, 
    2398      150,    -1,   176,    -1,    -1,    -1,    -1,    -1,   125,    -1, 
    2399       -1,   185,   186,    -1,   188,   189,   166,   167,   192,   193, 
    2400      194,    -1,    -1,    -1,    -1,    -1,   176,    -1,   202,    -1, 
    2401       -1,    -1,    -1,   150,    -1,   185,   186,    -1,   188,   189, 
    2402       -1,    -1,   192,   193,   194,   125,    -1,    -1,    -1,   166, 
    2403      167,    -1,   202,    -1,    -1,    -1,    -1,    -1,    -1,   176, 
    2404       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   185,   186, 
    2405      150,   188,   189,    -1,    25,   192,   193,   194,    -1,    -1, 
    2406       -1,    32,    -1,    -1,    -1,   202,   166,   167,    -1,    -1, 
    2407       -1,   125,    -1,    -1,    -1,    -1,   176,    -1,    -1,    -1, 
    2408       -1,    -1,   125,    -1,    -1,   185,   186,    -1,   188,   189, 
    2409       -1,    -1,   192,   193,   194,    -1,   150,    -1,    -1,    -1, 
    2410       -1,    -1,   202,    -1,    -1,    -1,    -1,   150,    -1,    -1, 
    2411       -1,    82,   166,   167,    -1,    -1,    -1,    -1,    -1,    -1, 
    2412       -1,    -1,   176,   166,   167,    -1,    -1,    -1,    99,   100, 
    2413       -1,   185,   186,   176,   188,   189,    -1,    -1,   192,   193, 
    2414      194,   112,   185,   186,    -1,   188,   189,    -1,   202,   192, 
     2490      -1,   185,   186,   150,   188,   189,    -1,   125,   192,   193, 
     2491     194,    -1,    -1,    -1,    -1,    -1,    -1,    11,   202,   166, 
     2492     167,    -1,    -1,    -1,    -1,    19,    20,    -1,    11,   176, 
     2493      -1,    -1,   150,    -1,    -1,    -1,    19,    20,   185,   186, 
     2494      -1,   188,   189,    -1,    -1,   192,   193,   194,   166,   167, 
     2495      -1,    -1,    -1,    -1,    -1,   202,    -1,   125,   176,    -1, 
     2496      -1,    -1,    -1,    -1,    -1,    -1,    -1,   185,   186,    -1, 
     2497     188,   189,    -1,    -1,   192,   193,   194,    -1,    -1,    -1, 
     2498      -1,    -1,   150,    11,   202,    -1,   125,    -1,    -1,    -1, 
     2499      -1,    19,    20,    -1,    -1,    -1,    -1,    -1,   166,   167, 
     2500      -1,    -1,    -1,    -1,    -1,    -1,    -1,    11,   176,    -1, 
     2501      -1,   150,    -1,    -1,    -1,    19,    20,   185,   186,    -1, 
     2502     188,   189,    -1,    -1,   192,   193,   194,   166,   167,    -1, 
     2503      -1,   125,    -1,    -1,   202,    -1,    11,   176,    -1,    -1, 
     2504      -1,    -1,   125,    -1,    19,    20,   185,   186,    -1,   188, 
     2505     189,    -1,    -1,   192,   193,   194,   150,    -1,    -1,    -1, 
     2506      -1,    -1,    -1,   202,    -1,    -1,    11,   150,    -1,    -1, 
     2507      -1,    -1,   166,   167,    19,    20,    -1,    -1,    -1,    -1, 
     2508      -1,    -1,   176,   166,   167,    -1,    -1,    -1,    -1,    -1, 
     2509      -1,   185,   186,   176,   188,   189,    -1,   125,   192,   193, 
     2510     194,    -1,   185,   186,    -1,   188,   189,    -1,   202,   192, 
    24152511     193,   194,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   202, 
    2416      131,    -1,   133,    32,   135,   136,    -1,    -1,    -1,    38, 
    2417      141,    -1,   143,    -1,    -1,    -1,    -1,   148,    47,    48, 
     2512      -1,   125,   150,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2513      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   166,   167, 
     2514      -1,    -1,    -1,    -1,    -1,    -1,   150,    -1,   176,    -1, 
     2515     125,    -1,    -1,    -1,    -1,    -1,    -1,   185,   186,    -1, 
     2516     188,   189,   166,   167,   192,   193,   194,    -1,    -1,    -1, 
     2517      -1,    25,   176,    -1,   202,   150,    -1,    -1,    32,    -1, 
     2518     125,   185,   186,    -1,   188,   189,    -1,    -1,   192,   193, 
     2519     194,   166,   167,    -1,    -1,    -1,    -1,    -1,   202,    -1, 
     2520      -1,   176,    -1,    -1,    -1,   150,    -1,    -1,    -1,    -1, 
     2521     185,   186,    -1,   188,   189,    -1,    -1,   192,   193,   194, 
     2522      -1,   166,   167,    -1,    -1,    -1,    -1,   202,    82,    -1, 
     2523      -1,   176,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2524     185,   186,    -1,   188,   189,    99,   100,   192,   193,   194, 
     2525      -1,    -1,    -1,    -1,    -1,    -1,    -1,   202,   112,    -1, 
    24182526      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2419       -1,    -1,    -1,    -1,    -1,    -1,    -1,   168,    -1,    -1, 
    2420      171,   172,   173,    -1,    -1,   176,   177,   178,   179,    78, 
    2421       -1,    -1,    -1,   184,   185,   186,   187,   188,    -1,   190, 
    2422       -1,   192,   193,    -1,    93,    -1,    -1,    -1,    -1,    -1, 
    2423       -1,    -1,    -1,    -1,    -1,    -1,   105,   106,   107,    -1, 
    2424      109,    -1,    -1,   112,    -1,   114,    -1,   116,    32,    -1, 
    2425      119,   120,    -1,   122,    38,    -1,   125,    -1,    -1,   128, 
    2426      129,   130,    -1,   132,    48,    -1,    -1,    -1,    -1,    -1, 
    2427       -1,    -1,    -1,    -1,    -1,    -1,    32,    -1,    -1,    -1, 
    2428       -1,    -1,    38,    -1,    -1,   154,    -1,    -1,    -1,    -1, 
    2429       -1,    -1,    48,    -1,    78,    -1,    -1,    -1,    -1,   168, 
    2430      169,   170,   171,    -1,    -1,    -1,    -1,    -1,    -1,    93, 
    2431       -1,    -1,    -1,    -1,    -1,    -1,   185,   186,    -1,   188, 
     2527      -1,    -1,    -1,    -1,    -1,    -1,    -1,   131,    -1,   133, 
     2528      32,   135,   136,    -1,    -1,    -1,    38,   141,    -1,   143, 
     2529      -1,    -1,    -1,    -1,   148,    47,    48,    -1,    -1,    -1, 
     2530      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2531      -1,    -1,    -1,    -1,   168,    -1,    -1,   171,   172,   173, 
     2532      -1,    -1,   176,   177,   178,   179,    78,    -1,    -1,    -1, 
     2533     184,   185,   186,   187,   188,    -1,   190,    -1,   192,   193, 
     2534      -1,    93,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2535      -1,    -1,    -1,   105,   106,   107,    -1,   109,    -1,    -1, 
     2536     112,    -1,   114,    -1,   116,    32,    -1,   119,   120,    -1, 
     2537     122,    38,    -1,   125,    -1,    -1,   128,   129,   130,    -1, 
     2538     132,    48,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2539      -1,    -1,    -1,    32,    -1,    -1,    -1,    -1,    -1,    38, 
     2540      -1,    -1,   154,    -1,    -1,    -1,    -1,    -1,    -1,    48, 
     2541      -1,    78,    -1,    -1,    -1,    -1,   168,   169,   170,   171, 
     2542      -1,    -1,    -1,    -1,    -1,    -1,    93,    -1,    -1,    -1, 
     2543      -1,    -1,    -1,   185,   186,    -1,   188,    -1,    -1,    78, 
     2544     192,   193,   109,    -1,    -1,   112,   113,    -1,    -1,   116, 
     2545      -1,    -1,   119,   120,    93,   122,    -1,    -1,   125,    -1, 
     2546      -1,   128,   129,   130,    -1,    -1,    -1,    -1,    -1,    -1, 
     2547     109,    -1,    -1,   112,   113,    -1,    -1,   116,    -1,    -1, 
     2548     119,   120,    -1,   122,    38,    -1,   125,   154,    -1,   128, 
     2549     129,   130,    -1,    -1,    48,    -1,    -1,    -1,    -1,    -1, 
     2550      -1,   168,    -1,    -1,   171,    -1,    -1,    -1,    -1,    -1, 
     2551      -1,    -1,    38,    -1,    -1,   154,   183,    -1,   185,   186, 
     2552      -1,   188,    -1,    -1,    78,   192,   193,    -1,    -1,   168, 
     2553      -1,    -1,   171,    -1,    -1,    -1,    -1,    -1,    -1,    93, 
     2554      -1,    -1,    -1,    -1,   183,    -1,   185,   186,    -1,   188, 
    24322555      -1,    -1,    78,   192,   193,   109,    -1,    -1,   112,   113, 
    24332556      -1,    -1,   116,    -1,    -1,   119,   120,    93,   122,    -1, 
    2434       -1,   125,    -1,    -1,   128,   129,   130,    -1,    -1,    -1, 
    2435       -1,    -1,    -1,   109,    -1,    -1,   112,   113,    -1,    -1, 
     2557      -1,   125,    -1,    -1,   128,   129,   130,    -1,   104,    -1, 
     2558      -1,    -1,    -1,   109,    -1,    -1,    -1,    -1,    -1,    -1, 
    24362559     116,    -1,    -1,   119,   120,    -1,   122,    38,    -1,   125, 
    2437      154,    -1,   128,   129,   130,    -1,    -1,    48,    -1,    -1, 
     2560     154,    -1,   128,   129,   130,    -1,    -1,    -1,    -1,    -1, 
    24382561      -1,    -1,    -1,    -1,   168,    -1,    -1,   171,    -1,    -1, 
    2439       -1,    -1,    -1,    -1,    -1,    38,    -1,    -1,   154,   183, 
     2562      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   154,   183, 
    24402563      -1,   185,   186,    -1,   188,    -1,    -1,    78,   192,   193, 
    2441       -1,    -1,   168,    -1,    -1,