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 6258 for branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp – NEMO

Ignore:
Timestamp:
2016-01-15T13:11:56+01:00 (8 years ago)
Author:
timgraham
Message:

First inclusion of Laurent Debreu's modified code for vertical refinement.
Still a lot of outstanding issues:
1) conv preprocessor fails for limrhg.F90 at the moment (for now I've run without ice model)
2) conv preprocessor fails for STO code - removed this code from testing for now
3) conv preprocessor fails for cpl_oasis.F90 - can work round this by modifying code but the preprocessor should be fixed to deal with this.

After that code compiles and can be run for horizontal grid refinement. Not yet working for vertical refinement.

Location:
branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM
Files:
46 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modarrays.F90

    r5819 r6258  
    11! 
    2 ! $Id$ 
     2! $Id: modarrays.F 662 2007-05-25 15:58:52Z opalod $ 
    33! 
    44!     AGRIF (Adaptive Grid Refinement In Fortran) 
     
    5555                               proc_id,         & 
    5656                               coords,          & 
    57                                lb_tab_true, ub_tab_true, memberin ) 
     57                               lb_tab_true, ub_tab_true, memberin,  & 
     58                               indminglob3,indmaxglob3) 
    5859!--------------------------------------------------------------------------------------------------- 
    5960    integer,                   intent(in)  :: nbdim         !< Number of dimensions 
     
    6162    integer, dimension(nbdim), intent(in)  :: ub_var        !< Local upper boundary on the current processor 
    6263    integer, dimension(nbdim), intent(in)  :: lb_tab        !< Global lower boundary of the variable 
     64    integer, dimension(nbdim),OPTIONAL     :: indminglob3,indmaxglob3 !< True bounds for MPI USE 
    6365    integer, dimension(nbdim), intent(in)  :: ub_tab        !< Global upper boundary of the variable 
    6466    integer,                   intent(in)  :: proc_id       !< Current processor 
     
    7880        call Agrif_InvLoc( lb_var(i), proc_id, coord_i, lb_glob_index ) 
    7981        call Agrif_InvLoc( ub_var(i), proc_id, coord_i, ub_glob_index ) 
     82        if (present(indminglob3)) then 
     83          indminglob3(i)=lb_glob_index 
     84          indmaxglob3(i)=ub_glob_index 
     85        endif 
    8086#else 
    8187        lb_glob_index = lb_var(i) 
     
    8490        lb_tab_true(i) = max(lb_tab(i), lb_glob_index) 
    8591        ub_tab_true(i) = min(ub_tab(i), ub_glob_index) 
     92 
    8693    enddo 
    8794! 
     
    123130! 
    124131    iminmaxg(1:nbdim,2) = - iminmaxg(1:nbdim,2) 
    125     call MPI_ALLREDUCE(iminmaxg, lubglob, 2*nbdim, MPI_INTEGER, MPI_MIN, Agrif_mpi_comm, code) 
     132    call MPI_ALLREDUCE(iminmaxg, lubglob, 2*nbdim, MPI_INTEGER, MPI_MIN, & 
     133                       Agrif_mpi_comm, code) 
    126134    lubglob(1:nbdim,2)  = - lubglob(1:nbdim,2) 
    127135#endif 
     
    803811    do i = 1,nbdim 
    804812! 
     813     if (coords(i) == 0) then 
     814       nbloc(i) = 1 
     815       locbounds(i,1,1) = lb_glob(i) 
     816       locbounds(i,2,1) = ub_glob(i) 
     817       locbounds(i,1,2) = lb_glob(i) 
     818       locbounds(i,2,2) = ub_glob(i) 
     819     else 
    805820        call Agrif_InvLoc(lb_var(i), rank, coords(i), i1) 
    806821! 
     
    816831            endif 
    817832        enddo 
     833     endif 
    818834    enddo 
    819835 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modbc.F90

    r5819 r6258  
    11! 
    2 ! $Id$ 
     2! $Id: modbc.F 779 2007-12-22 17:04:17Z rblod $ 
    33! 
    44!     AGRIF (Adaptive Grid Refinement In Fortran) 
     
    148148    REAL   , DIMENSION(nbdim)   :: ds_Child, ds_Parent  !< Space steps of the parent and child grids 
    149149    INTEGER                             :: nbdim        !< Number of dimensions of the grid variable 
    150     procedure()                         :: procname     !< Data recovery procedure 
     150    procedure()                           :: procname     !< Data recovery procedure 
    151151! 
    152152    INTEGER,DIMENSION(6)                :: type_interp     ! Type of interpolation (linear, spline,...) 
     
    171171#endif 
    172172! 
     173 
    173174    type_interp_bc = child % root_var % type_interp_bc 
    174175    coords         = child % root_var % coords 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modbcfunction.F90

    r5819 r6258  
    11! 
    2 ! $Id$ 
     2! $Id: modbcfunction.F 779 2007-12-22 17:04:17Z rblod $ 
    33! 
    44!     AGRIF (Adaptive Grid Refinement In Fortran) 
     
    5353!> To set the TYPE of the variable 
    5454!--------------------------------------------------------------------------------------------------- 
    55 subroutine Agrif_Set_parent_int(tabvarsindic,value) 
    56 !--------------------------------------------------------------------------------------------------- 
    57     integer, intent(in)     :: tabvarsindic !< indice of the variable in tabvars 
     55subroutine Agrif_Set_parent_int(integer_variable,value) 
     56!--------------------------------------------------------------------------------------------------- 
     57    integer, intent(in)     :: integer_variable !< indice of the variable in tabvars 
    5858    integer, intent(in)     :: value        !< input value 
    5959! 
    60     Agrif_Curgrid % parent % tabvars_i(tabvarsindic) % iarray0 = value 
     60 
     61integer :: i 
     62logical :: i_found 
     63 
     64i_found = .FALSE. 
     65 
     66do i=1,Agrif_NbVariables(4) 
     67  if (LOC(integer_variable) == LOC(agrif_curgrid%tabvars_i(i)%iarray0)) then 
     68     agrif_curgrid%tabvars_i(i)%parent_var%iarray0 = value 
     69     i_found = .TRUE. 
     70     EXIT 
     71  endif 
     72enddo 
     73 
     74if (.NOT.i_found) STOP 'Agrif_Set_Integer : Variable not found' 
     75 
    6176!--------------------------------------------------------------------------------------------------- 
    6277end subroutine Agrif_Set_parent_int 
     
    6681!  subroutine Agrif_Set_parent_real4 
    6782!--------------------------------------------------------------------------------------------------- 
    68 !> To set the TYPE of the variable 
    69 !--------------------------------------------------------------------------------------------------- 
    70 subroutine Agrif_Set_parent_real4 ( tabvarsindic, value ) 
    71 !--------------------------------------------------------------------------------------------------- 
    72     integer, intent(in)     :: tabvarsindic !< indice of the variable in tabvars 
    73     real(kind=4),intent(in) :: value        !< input value 
    74 ! 
    75     Agrif_Curgrid % parent % tabvars_r(tabvarsindic) % array0 = value 
    76     Agrif_Curgrid % parent % tabvars_r(tabvarsindic) % sarray0 = value 
     83!> To set the parent value of a real variable 
     84!--------------------------------------------------------------------------------------------------- 
     85subroutine Agrif_Set_parent_real4 ( real_variable, value ) 
     86!--------------------------------------------------------------------------------------------------- 
     87    real(kind=4), intent(in)     :: real_variable !< input variable 
     88    real(kind=4),intent(in) :: value        !< input value for the parent grid 
     89 
     90integer :: i 
     91logical :: i_found 
     92 
     93i_found = .FALSE. 
     94 
     95do i=1,Agrif_NbVariables(2) 
     96  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%array0)) then 
     97     agrif_curgrid%tabvars_r(i)%parent_var%array0 = value 
     98     agrif_curgrid%tabvars_r(i)%parent_var%sarray0 = value 
     99     i_found = .TRUE. 
     100     EXIT 
     101  endif 
     102enddo 
     103 
     104IF (.NOT.i_found) THEN 
     105do i=1,Agrif_NbVariables(2) 
     106  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%sarray0)) then 
     107     agrif_curgrid%tabvars_r(i)%parent_var%array0 = value 
     108     agrif_curgrid%tabvars_r(i)%parent_var%sarray0 = value 
     109     i_found = .TRUE. 
     110     EXIT 
     111  endif 
     112enddo 
     113ENDIF 
     114 
     115if (.NOT.i_found) STOP 'Agrif_Set_parent_real4 : Variable not found' 
    77116!--------------------------------------------------------------------------------------------------- 
    78117end subroutine Agrif_Set_parent_real4 
     
    82121!  subroutine Agrif_Set_parent_real8 
    83122!--------------------------------------------------------------------------------------------------- 
    84 !> To set the TYPE of the variable 
    85 !--------------------------------------------------------------------------------------------------- 
    86 subroutine Agrif_Set_parent_real8 ( tabvarsindic, value ) 
    87 !--------------------------------------------------------------------------------------------------- 
    88     integer, intent(in)     :: tabvarsindic !< indice of the variable in tabvars 
    89     real(kind=8),intent(in) :: value        !< input value 
    90 ! 
    91     Agrif_Curgrid % parent % tabvars_r(tabvarsindic) % darray0 = value 
     123!> To set the parent value of a real variable 
     124!--------------------------------------------------------------------------------------------------- 
     125subroutine Agrif_Set_parent_real8 ( real_variable, value ) 
     126!--------------------------------------------------------------------------------------------------- 
     127    real(kind=8), intent(in)     :: real_variable !< input variable 
     128    real(kind=8),intent(in) :: value        !< input value for the parent grid 
     129 
     130integer :: i 
     131logical :: i_found 
     132 
     133i_found = .FALSE. 
     134 
     135do i=1,Agrif_NbVariables(2) 
     136  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%array0)) then 
     137     agrif_curgrid%tabvars_r(i)%parent_var%darray0 = value 
     138     agrif_curgrid%tabvars_r(i)%parent_var%array0 = value 
     139     i_found = .TRUE. 
     140     EXIT 
     141  endif 
     142enddo 
     143 
     144IF (.NOT.i_found) THEN 
     145do i=1,Agrif_NbVariables(2) 
     146  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%darray0)) then 
     147     agrif_curgrid%tabvars_r(i)%parent_var%darray0 = value 
     148     agrif_curgrid%tabvars_r(i)%parent_var%array0 = value 
     149     i_found = .TRUE. 
     150     EXIT 
     151  endif 
     152enddo 
     153ENDIF 
     154 
     155if (.NOT.i_found) STOP 'Agrif_Set_parent_real8 : Variable not found' 
     156 
    92157!--------------------------------------------------------------------------------------------------- 
    93158end subroutine Agrif_Set_parent_real8 
     
    106171    type(Agrif_Variable),  pointer  :: var 
    107172! 
    108     indic = Agrif_Curgrid % tabvars_i(tabvarsindic) % iarray0 
    109 ! 
    110     if (indic <= 0) then 
    111         var => Agrif_Search_Variable(Agrif_Curgrid,-indic) 
    112     else 
    113         print*,"Agrif_Set_bc : warning indic >= 0 !!!" 
    114         var => Agrif_Curgrid % tabvars(indic) 
    115     endif 
    116  
     173    var => Agrif_Search_Variable(Agrif_Curgrid,tabvarsindic) 
    117174    if (.not.associated(var)) return ! Grand mother grid case 
    118175! 
     
    145202    type(Agrif_Variable), pointer   :: var 
    146203! 
    147     indic = Agrif_Curgrid % tabvars_i(tabvarsindic) % iarray0 
    148 ! 
    149     if (indic <= 0) then 
    150         var => Agrif_Search_Variable(Agrif_Mygrid,-indic) 
    151     else 
    152         print*,"Agrif_Set_interp : warning indic >= 0 !!!" 
    153         var => Agrif_Mygrid % tabvars(indic) 
    154     endif 
     204    var => Agrif_Search_Variable(Agrif_Curgrid,tabvarsindic) 
     205    if (.not.associated(var)) return ! Grand mother grid case 
    155206! 
    156207    var % type_interp = Agrif_Constant 
     
    178229    TYPE(Agrif_Variable), pointer   :: var 
    179230! 
    180     indic = Agrif_Curgrid%tabvars_i(tabvarsindic)%iarray0 
    181 ! 
    182     if (indic <= 0) then 
    183         var => Agrif_Search_Variable(Agrif_Mygrid,-indic) 
    184     else 
    185         print*,"Agrif_Set_bcinterp : warning indic >= 0 !!!" 
    186         var => Agrif_Mygrid % tabvars(indic) 
    187     endif 
     231    var => Agrif_Search_Variable(Agrif_Curgrid,tabvarsindic) 
    188232! 
    189233    var % type_interp_bc = Agrif_Constant 
     
    214258    type(Agrif_Variable),  pointer  :: root_var 
    215259! 
    216     indic = Agrif_Curgrid%tabvars_i(tabvarsindic)%iarray0 
    217 ! 
    218     if (indic <= 0) then 
    219         root_var => Agrif_Search_Variable(Agrif_Mygrid,-indic) 
    220     else 
    221         print*,"Agrif_Set_UpdateType : warning indic >= 0 !!!" 
    222         root_var => Agrif_Mygrid % tabvars(indic) 
    223     endif 
     260 
     261        root_var => Agrif_Search_Variable(Agrif_Mygrid,tabvarsindic) 
     262 
    224263! 
    225264    root_var % type_update = Agrif_Update_Copy 
     
    243282    INTEGER :: indic  !  indice of the variable in tabvars 
    244283! 
     284print *,'CURRENTLY BROKEN' 
     285STOP 
     286 
    245287    indic = Agrif_Curgrid%tabvars_i(tabvarsindic)%iarray0 
    246288! 
     
    283325    type(Agrif_Variable), pointer :: child_var 
    284326    type(Agrif_Variable), pointer :: child_tmp      ! Temporary variable on the child grid 
     327    integer :: i 
     328    integer,dimension(7) :: lb, ub 
    285329! 
    286330    if ( Agrif_Curgrid%level <= 0 ) return 
    287331! 
    288     indic = Agrif_Curgrid%tabvars_i(tabvarsindic)%iarray0 
    289332! 
    290333    if ( present(calledweight) ) then 
     
    296339    endif 
    297340! 
    298     if (indic <= 0) then 
    299         child_var  => Agrif_Search_Variable(Agrif_Curgrid,-indic) 
     341        child_var  => Agrif_Search_Variable(Agrif_Curgrid,tabvarsindic) 
    300342        parent_var => child_var % parent_var 
    301343        root_var   => child_var % root_var 
    302     else 
    303         print*,"Agrif_Bc_variable : warning indic >= 0 !!!" 
    304         child_var  => Agrif_Curgrid % tabvars(indic) 
    305         parent_var => Agrif_Curgrid % parent % tabvars(indic) 
    306         root_var   => Agrif_Mygrid % tabvars(indic) 
    307     endif 
    308344! 
    309345    nbdim = root_var % nbdim 
    310346! 
     347    do i=1,nbdim 
     348      if (root_var%coords(i) == 0) then 
     349        lb(i) = parent_var%lb(i) 
     350        ub(i) = parent_var%ub(i) 
     351      else 
     352        lb(i) = child_var%lb(i) 
     353        ub(i) = child_var%ub(i) 
     354      endif 
     355    enddo 
     356 
    311357    select case( nbdim ) 
    312358    case(1) 
    313         allocate(parray1(child_var%lb(1):child_var%ub(1))) 
     359        allocate(parray1(lb(1):ub(1))) 
    314360    case(2) 
    315         allocate(parray2(child_var%lb(1):child_var%ub(1), & 
    316                          child_var%lb(2):child_var%ub(2) )) 
     361        allocate(parray2(lb(1):ub(1), & 
     362                         lb(2):ub(2) )) 
    317363    case(3) 
    318         allocate(parray3(child_var%lb(1):child_var%ub(1), & 
    319                          child_var%lb(2):child_var%ub(2), & 
    320                          child_var%lb(3):child_var%ub(3) )) 
     364        allocate(parray3(lb(1):ub(1), & 
     365                         lb(2):ub(2), & 
     366                         lb(3):ub(3) )) 
    321367    case(4) 
    322         allocate(parray4(child_var%lb(1):child_var%ub(1), & 
    323                          child_var%lb(2):child_var%ub(2), & 
    324                          child_var%lb(3):child_var%ub(3), & 
    325                          child_var%lb(4):child_var%ub(4) )) 
     368        allocate(parray4(lb(1):ub(1), & 
     369                         lb(2):ub(2), & 
     370                         lb(3):ub(3), & 
     371                         lb(4):ub(4) )) 
    326372    case(5) 
    327         allocate(parray5(child_var%lb(1):child_var%ub(1), & 
    328                          child_var%lb(2):child_var%ub(2), & 
    329                          child_var%lb(3):child_var%ub(3), & 
    330                          child_var%lb(4):child_var%ub(4), & 
    331                          child_var%lb(5):child_var%ub(5) )) 
     373        allocate(parray5(lb(1):ub(1), & 
     374                         lb(2):ub(2), & 
     375                         lb(3):ub(3), & 
     376                         lb(4):ub(4), & 
     377                         lb(5):ub(5) )) 
    332378    case(6) 
    333         allocate(parray6(child_var%lb(1):child_var%ub(1), & 
    334                          child_var%lb(2):child_var%ub(2), & 
    335                          child_var%lb(3):child_var%ub(3), & 
    336                          child_var%lb(4):child_var%ub(4), & 
    337                          child_var%lb(5):child_var%ub(5), & 
    338                          child_var%lb(6):child_var%ub(6) )) 
     379        allocate(parray6(lb(1):ub(1), & 
     380                         lb(2):ub(2), & 
     381                         lb(3):ub(3), & 
     382                         lb(4):ub(4), & 
     383                         lb(5):ub(5), & 
     384                         lb(6):ub(6) )) 
    339385    end select 
    340386! 
     
    402448    if ( Agrif_Curgrid%level <= 0 ) return 
    403449! 
    404     indic = Agrif_Curgrid%tabvars_i(tabvarsindic)%iarray0 
    405 ! 
    406     if (indic <= 0) then 
    407         child_var  => Agrif_Search_Variable(Agrif_Curgrid,-indic) 
     450 
     451        child_var  => Agrif_Search_Variable(Agrif_Curgrid,tabvarsindic) 
    408452        parent_var => child_var % parent_var 
    409453        root_var   => child_var % root_var 
    410     else 
    411         print*,"Agrif_Interp_variable : warning indic >= 0 !!!" 
    412         child_var  => Agrif_Curgrid % tabvars(indic) 
    413         parent_var => Agrif_Curgrid % parent % tabvars(indic) 
    414         root_var   => Agrif_Mygrid % tabvars(indic) 
    415     endif 
     454 
    416455! 
    417456    nbdim     = root_var % nbdim 
     
    486525    if (agrif_curgrid%grand_mother_grid) return 
    487526! 
    488     indic = Agrif_Curgrid%tabvars_i(tabvarsindic)%iarray0 
    489 ! 
    490     if (indic <= 0) then 
    491         child_var  => Agrif_Search_Variable(Agrif_Curgrid, -indic) 
     527 
     528        child_var  => Agrif_Search_Variable(Agrif_Curgrid, tabvarsindic) 
    492529        parent_var => child_var % parent_var 
    493530 
    494531        if (.not.associated(parent_var)) then 
    495532          ! can occur during the first update of Agrif_Coarsegrid (if any) 
    496           parent_var => Agrif_Search_Variable(Agrif_Curgrid % parent, -indic) 
     533          parent_var => Agrif_Search_Variable(Agrif_Curgrid % parent, tabvarsindic) 
    497534          child_var % parent_var => parent_var 
    498535        endif 
    499536 
    500537        root_var   => child_var % root_var 
    501     else 
    502         print*,"Agrif_Update_Variable : warning indic >= 0 !!!" 
    503         root_var   => Agrif_Mygrid  % tabvars(indic) 
    504         child_var  => Agrif_Curgrid % tabvars(indic) 
    505         parent_var => Agrif_Curgrid % parent % tabvars(indic) 
    506     endif 
     538 
    507539! 
    508540    nbdim = root_var % nbdim 
     
    551583    integer :: nbdim 
    552584! 
     585print *,'CURRENTLY BROKEN' 
     586STOP 
    553587    root_var => Agrif_Mygrid % tabvars(tabvarsindic0) 
    554588    save_var => Agrif_Curgrid % tabvars(tabvarsindic0) 
     
    575609    integer                         :: indic 
    576610! 
     611print *,'CURRENTLY BROKEN' 
     612STOP 
    577613    indic = tabvarsindic 
    578614    if (tabvarsindic >= 0) then 
     
    612648    integer                         :: indic 
    613649! 
     650print *,'CURRENTLY BROKEN' 
     651STOP 
     652 
    614653    indic = tabvarsindic 
    615654    if (tabvarsindic >= 0) then 
     
    650689    integer                         :: indic 
    651690! 
     691print *,'CURRENTLY BROKEN' 
     692STOP 
    652693    indic = tabvarsindic 
    653694    if (tabvarsindic >= 0) then 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modcluster.F90

    r5819 r6258  
    11! 
    2 ! $Id$ 
     2! $Id: modcluster.F 662 2007-05-25 15:58:52Z opalod $ 
    33! 
    44!     AGRIF (Adaptive Grid Refinement In Fortran) 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modcurgridfunctions.F90

    r5819 r6258  
    11! 
    2 ! $Id$ 
     2! $Id: modcurgridfunctions.F 774 2007-12-18 16:45:53Z rblod $ 
    33! 
    44!     AGRIF (Adaptive Grid Refinement In Fortran) 
     
    2929    implicit none 
    3030! 
     31 
     32    interface Agrif_Parent 
     33        module procedure Agrif_Parent_Real_4,   & 
     34                         Agrif_Parent_Real_8,   & 
     35                         Agrif_Parent_Integer, & 
     36                         Agrif_Parent_Character, & 
     37                         Agrif_Parent_Logical 
     38    end interface 
     39     
    3140contains 
    3241! 
     
    763772!=================================================================================================== 
    764773! 
     774 
     775function Agrif_Parent_Real_4(real_variable) result(real_variable_parent) 
     776real(KIND=4) :: real_variable 
     777real(KIND=4) :: real_variable_parent 
     778 
     779integer :: i 
     780logical :: i_found 
     781 
     782i_found = .FALSE. 
     783 
     784do i=1,Agrif_NbVariables(2) 
     785  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%array0)) then 
     786     real_variable_parent = agrif_curgrid%tabvars_r(i)%parent_var%array0 
     787     i_found = .TRUE. 
     788     EXIT 
     789  endif 
     790enddo 
     791 
     792IF (.NOT.i_found) THEN 
     793do i=1,Agrif_NbVariables(2) 
     794  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%sarray0)) then 
     795     real_variable_parent = agrif_curgrid%tabvars_r(i)%parent_var%sarray0 
     796     i_found = .TRUE. 
     797     EXIT 
     798  endif 
     799enddo 
     800ENDIF 
     801 
     802if (.NOT.i_found) STOP 'Agrif_Parent_Real_4 : Variable not found' 
     803 
     804end function Agrif_Parent_Real_4 
     805 
     806function Agrif_Parent_Real_8(real_variable) result(real_variable_parent) 
     807real(KIND=8) :: real_variable 
     808real(KIND=8) :: real_variable_parent 
     809 
     810integer :: i 
     811logical :: i_found 
     812 
     813i_found = .FALSE. 
     814 
     815do i=1,Agrif_NbVariables(2) 
     816  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%array0)) then 
     817     real_variable_parent = agrif_curgrid%tabvars_r(i)%parent_var%array0 
     818     i_found = .TRUE. 
     819     EXIT 
     820  endif 
     821enddo 
     822 
     823IF (.NOT.i_found) THEN 
     824do i=1,Agrif_NbVariables(2) 
     825  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%darray0)) then 
     826     real_variable_parent = agrif_curgrid%tabvars_r(i)%parent_var%darray0 
     827     i_found = .TRUE. 
     828     EXIT 
     829  endif 
     830enddo 
     831ENDIF 
     832 
     833if (.NOT.i_found) STOP 'Agrif_Parent_Real_8 : Variable not found' 
     834 
     835end function Agrif_Parent_Real_8 
     836 
     837function Agrif_Parent_Integer(integer_variable) result(integer_variable_parent) 
     838integer :: integer_variable 
     839integer :: integer_variable_parent 
     840 
     841integer :: i 
     842logical :: i_found 
     843 
     844i_found = .FALSE. 
     845 
     846do i=1,Agrif_NbVariables(4) 
     847  if (LOC(integer_variable) == LOC(agrif_curgrid%tabvars_i(i)%iarray0)) then 
     848     integer_variable_parent = agrif_curgrid%tabvars_i(i)%parent_var%iarray0 
     849     i_found = .TRUE. 
     850     EXIT 
     851  endif 
     852enddo 
     853 
     854if (.NOT.i_found) STOP 'Agrif_Parent : Variable not found' 
     855 
     856end function Agrif_Parent_Integer 
     857 
     858function Agrif_Parent_Character(character_variable) result(character_variable_parent) 
     859character(*) :: character_variable 
     860character(len(character_variable)) :: character_variable_parent 
     861 
     862integer :: i 
     863logical :: i_found 
     864 
     865i_found = .FALSE. 
     866 
     867do i=1,Agrif_NbVariables(1) 
     868  if (LOC(character_variable) == LOC(agrif_curgrid%tabvars_c(i)%carray0)) then 
     869     character_variable_parent = agrif_curgrid%tabvars_c(i)%parent_var%carray0 
     870     i_found = .TRUE. 
     871     EXIT 
     872  endif 
     873enddo 
     874 
     875if (.NOT.i_found) STOP 'Agrif_Parent : Variable not found' 
     876 
     877end function Agrif_Parent_Character 
     878 
     879function Agrif_Parent_Logical(logical_variable) result(logical_variable_parent) 
     880logical :: logical_variable 
     881logical :: logical_variable_parent 
     882 
     883integer :: i 
     884logical :: i_found 
     885 
     886i_found = .FALSE. 
     887 
     888do i=1,Agrif_NbVariables(3) 
     889  if (LOC(logical_variable) == LOC(agrif_curgrid%tabvars_l(i)%larray0)) then 
     890     logical_variable_parent = agrif_curgrid%tabvars_l(i)%parent_var%larray0 
     891     i_found = .TRUE. 
     892     EXIT 
     893  endif 
     894enddo 
     895 
     896if (.NOT.i_found) STOP 'Agrif_Parent : Variable not found' 
     897 
     898end function Agrif_Parent_Logical 
     899 
     900function Agrif_Irhox() result(i_val) 
     901integer :: i_val 
     902i_val = agrif_curgrid%spaceref(1) 
     903end function Agrif_Irhox 
     904 
     905function Agrif_Irhoy() result(i_val) 
     906integer :: i_val 
     907i_val = agrif_curgrid%spaceref(2) 
     908end function Agrif_Irhoy 
     909 
     910function Agrif_Irhoz() result(i_val) 
     911integer :: i_val 
     912i_val = agrif_curgrid%spaceref(3) 
     913end function Agrif_Irhoz 
     914 
     915function Agrif_NearCommonBorderX() result(l_val) 
     916logical :: l_val 
     917l_val = agrif_curgrid%nearRootBorder(1) 
     918end function Agrif_NearCommonBorderX 
     919 
     920function Agrif_NearCommonBorderY() result(l_val) 
     921logical :: l_val 
     922l_val = agrif_curgrid%nearRootBorder(2) 
     923end function Agrif_NearCommonBorderY 
     924 
     925function Agrif_NearCommonBorderZ() result(l_val) 
     926logical :: l_val 
     927l_val = agrif_curgrid%nearRootBorder(3) 
     928end function Agrif_NearCommonBorderZ 
     929 
     930function Agrif_DistantCommonBorderX() result(l_val) 
     931logical :: l_val 
     932l_val = agrif_curgrid%DistantRootBorder(1) 
     933end function Agrif_DistantCommonBorderX 
     934 
     935function Agrif_DistantCommonBorderY() result(l_val) 
     936logical :: l_val 
     937l_val = agrif_curgrid%DistantRootBorder(2) 
     938end function Agrif_DistantCommonBorderY 
     939 
     940function Agrif_DistantCommonBorderZ() result(l_val) 
     941logical :: l_val 
     942l_val = agrif_curgrid%DistantRootBorder(3) 
     943end function Agrif_DistantCommonBorderZ 
     944 
     945function Agrif_Ix() result(i_val) 
     946integer :: i_val 
     947i_val = agrif_curgrid%ix(1) 
     948end function Agrif_Ix 
     949 
     950function Agrif_Iy() result(i_val) 
     951integer :: i_val 
     952i_val = agrif_curgrid%ix(2) 
     953end function Agrif_Iy 
     954 
     955function Agrif_Iz() result(i_val) 
     956integer :: i_val 
     957i_val = agrif_curgrid%ix(3) 
     958end function Agrif_Iz 
     959 
     960function Agrif_Get_grid_id() result(i_val) 
     961integer :: i_val 
     962i_val = agrif_curgrid % grid_id 
     963end function Agrif_Get_grid_id 
     964 
     965function Agrif_Get_parent_id() result(i_val) 
     966integer :: i_val 
     967i_val = agrif_curgrid % parent % grid_id 
     968end function Agrif_Get_parent_id 
     969 
     970function Agrif_rhox() result(r_val) 
     971real :: r_val 
     972r_val = real(agrif_curgrid%spaceref(1)) 
     973end function Agrif_rhox 
     974 
     975function Agrif_rhoy() result(r_val) 
     976real :: r_val 
     977r_val = real(agrif_curgrid%spaceref(2)) 
     978end function Agrif_rhoy 
     979 
     980function Agrif_rhoz() result(r_val) 
     981real :: r_val 
     982r_val = real(agrif_curgrid%spaceref(3)) 
     983end function Agrif_rhoz 
     984 
     985function Agrif_Nb_Step() result(i_val) 
     986integer :: i_val 
     987i_val = agrif_curgrid%ngridstep 
     988end function Agrif_Nb_Step 
     989 
     990function Agrif_Nb_Fine_Grids() result(i_val) 
     991integer :: i_val 
     992i_val = Agrif_nbfixedgrids 
     993end function Agrif_Nb_Fine_Grids 
     994 
    765995end module Agrif_CurgridFunctions 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modinitvars.F90

    r5819 r6258  
    11! 
    2 ! $Id$ 
     2! $Id: modinitvars.F 662 2007-05-25 15:58:52Z opalod $ 
    33! 
    44!     Agrif (Adaptive Grid Refinement In Fortran) 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modinterp.F90

    r5819 r6258  
    11! 
    2 ! $Id$ 
     2! $Id: modinterp.F 779 2007-12-22 17:04:17Z rblod $ 
    33! 
    44!     AGRIF (Adaptive Grid Refinement In Fortran) 
     
    132132#if defined AGRIF_MPI 
    133133    INTEGER, DIMENSION(nbdim)     :: indminglob2,indmaxglob2 
     134    INTEGER, DIMENSION(nbdim)     :: indminglob3,indmaxglob3 
    134135#endif 
    135136    LOGICAL, DIMENSION(nbdim)     :: noraftab 
     
    148149    INTEGER, DIMENSION(nbdim,4,0:Agrif_Nbprocs-1)   :: tab4 
    149150    INTEGER, DIMENSION(nbdim,0:Agrif_Nbprocs-1,8)   :: tab4t 
     151    INTEGER,DIMENSION(nbdim,2) :: tab5 
     152    INTEGER,DIMENSION(nbdim,2,0:Agrif_Nbprocs-1) :: tab6 
     153    INTEGER,DIMENSION(nbdim,0:Agrif_Nbprocs-1,2) :: tab5t 
    150154    LOGICAL, DIMENSION(0:Agrif_Nbprocs-1)           :: memberinall 
    151155    LOGICAL, DIMENSION(0:Agrif_Nbprocs-1)           :: sendtoproc1, recvfromproc1 
     
    205209        call Agrif_Childbounds(nbdim,lowerbound,upperbound,                 & 
    206210                               indminglob,indmaxglob, local_proc, coords,   & 
    207                                indminglob2,indmaxglob2,member) 
     211                               indminglob2,indmaxglob2,member,              & 
     212                               indminglob3,indmaxglob3) 
    208213! 
    209214        if (member) then 
     
    224229        member = .TRUE. 
    225230#endif 
     231!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 
     232! Correct for non refined directions 
     233!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 
     234        do i=1,nbdim 
     235          if (coords(i) == 0) then 
     236             indmin(i) = indminglob(i) 
     237             indmax(i) = indmaxglob(i) 
     238             pttruetab(i) = indminglob(i) 
     239             cetruetab(i) = indmaxglob(i) 
     240          endif 
     241        enddo 
    226242 
    227243    else 
     
    298314        tab3(:,3) = indmin(:) 
    299315        tab3(:,4) = indmax(:) 
     316        tab5(:,1) = indminglob3(:) 
     317        tab5(:,2) = indmaxglob3(:) 
    300318! 
    301319        call MPI_ALLGATHER(tab3,4*nbdim,MPI_INTEGER,tab4,4*nbdim,MPI_INTEGER,Agrif_mpi_comm,code) 
    302  
     320        call MPI_ALLGATHER(tab5,2*nbdim,MPI_INTEGER,tab6,2*nbdim,MPI_INTEGER,Agrif_mpi_comm,code) 
    303321        if (.not.associated(tempPextend))   allocate(tempPextend) 
    304322 
     
    311329        enddo 
    312330 
     331        do k=0,Agrif_Nbprocs-1 
     332          do j=1,2 
     333            do i=1,nbdim 
     334               tab5t(i,k,j) = tab6(i,j,k) 
     335            enddo 
     336          enddo 
     337        enddo 
     338       
    313339        memberin1(1) = memberin 
    314340        call MPI_ALLGATHER(memberin1,1,MPI_LOGICAL,memberinall,1,MPI_LOGICAL,Agrif_mpi_comm,code) 
     
    319345                                     sendtoproc1,recvfromproc1,         & 
    320346                                     tab4t(:,:,5),tab4t(:,:,6),         & 
    321                                      tab4t(:,:,7),tab4t(:,:,8) ) 
     347                                     tab4t(:,:,7),tab4t(:,:,8),         & 
     348                                     tab5t(:,:,1),tab5t(:,:,2)) 
    322349    endif 
    323350 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modinterpbasic.F90

    r5819 r6258  
    11! 
    2 ! $Id$ 
     2! $Id: modinterpbasic.F 779 2007-12-22 17:04:17Z rblod $ 
    33! 
    44!     AGRIF (Adaptive Grid Refinement In Fortran) 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modlinktomodel.F90

    r5819 r6258  
    8080!                    Agrif_Curgrid % spaceref(1) 
    8181!=================================================================================================== 
    82 !  function Agrif_Parent_Irhox 
    83 !        modify by conv. To use : var = Agrif_Parent_IRhox() 
    84 !                    Agrif_Curgrid % parent % spaceref(1) 
    85 !=================================================================================================== 
    8682!  function Agrif_Rhoy 
    8783!        modify by conv. To use : var = Agrif_Rhoy() 
     
    9692!                    Agrif_Curgrid % spaceref(2) 
    9793!=================================================================================================== 
    98 !  function Agrif_Parent_Irhoy 
    99 !        modify by conv. To use : var = Agrif_Parent_IRhoy() 
    100 !                    Agrif_Curgrid % parent % spaceref(2) 
     94 
     95 
    10196!=================================================================================================== 
    10297!  function Agrif_Rhoz 
     
    111106!        modify by conv. To use : var = Agrif_Parent_IRhoz() 
    112107!                    Agrif_Curgrid % spaceref(3) 
    113 !=================================================================================================== 
    114 !  function Agrif_Parent_Irhoz 
    115 !        modify by conv. To use : var = Agrif_Parent_IRhoz() 
    116 !                    Agrif_Curgrid % parent % spaceref(3) 
     108 
    117109!=================================================================================================== 
    118110!  function Agrif_NearCommonBorderX 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modmask.F90

    r5819 r6258  
    11! 
    2 ! $Id$ 
     2! $Id: modmask.F 779 2007-12-22 17:04:17Z rblod $ 
    33! 
    44!     AGRIF (Adaptive Grid Refinement In Fortran) 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modmpp.F90

    r5819 r6258  
    11! 
    2 ! $Id$ 
     2! $Id: modmpp.F 779 2007-12-22 17:04:17Z rblod $ 
    33! 
    44!     AGRIF (Adaptive Grid Refinement In Fortran) 
     
    166166subroutine Get_External_Data_first ( pttruetab, cetruetab, pttruetabwhole, cetruetabwhole,  & 
    167167                                     nbdim, memberoutall, coords, sendtoproc, recvfromproc, & 
    168                                      imin, imax, imin_recv, imax_recv ) 
     168                                     imin, imax, imin_recv, imax_recv, bornesmin, bornesmax ) 
    169169!--------------------------------------------------------------------------------------------------- 
    170170    include 'mpif.h' 
     
    179179    integer, dimension(nbdim,0:Agrif_NbProcs-1), intent(out) :: imin,imax 
    180180    integer, dimension(nbdim,0:Agrif_NbProcs-1), intent(out) :: imin_recv,imax_recv 
     181    integer, dimension(nbdim,0:Agrif_NbProcs-1), intent(in) :: bornesmin, bornesmax 
    181182! 
    182183    integer :: imintmp, imaxtmp, i, j, k, i1 
     
    211212            IF (cetruetab(i,Agrif_Procrank) > cetruetab(i,k)) THEN 
    212213                DO j=imin1,imax1 
    213                     IF ((cetruetab(i,k)-j) > (j-pttruetab(i,Agrif_Procrank))) THEN 
     214                    IF ((bornesmax(i,k)-j) > (j-bornesmin(i,Agrif_Procrank))) THEN 
    214215                        imintmp = j+1 
    215216                        tochange = .TRUE. 
     
    228229            IF (pttruetab(i,Agrif_Procrank) < pttruetab(i,k)) THEN 
    229230                DO j=imax1,imin1,-1 
    230                     IF ((j-pttruetab(i,k)) > (cetruetab(i,Agrif_Procrank)-j)) THEN 
     231                    IF ((j-bornesmin(i,k)) > (bornesmax(i,Agrif_Procrank)-j)) THEN 
    231232                        imaxtmp = j-1 
    232233                        tochange = .TRUE. 
     
    248249        sendtoproc(k) = .true. 
    249250! 
     251        IF ( .not. memberoutall(k) ) THEN 
     252            sendtoproc(k) = .false. 
     253        ELSE 
    250254!CDIR SHORTLOOP 
    251255        do i = 1,nbdim 
     
    257261            endif 
    258262        enddo 
    259         IF ( .not. memberoutall(k) ) THEN 
    260             sendtoproc(k) = .false. 
    261263        ENDIF 
    262264    enddo 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modsauv.F90

    r5819 r6258  
    11! 
    2 ! $Id$ 
     2! $Id: modsauv.F 662 2007-05-25 15:58:52Z opalod $ 
    33! 
    44!     AGRIF (Adaptive Grid Refinement In Fortran) 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modtypes.F90

    r5819 r6258  
    109109    real(4), dimension(:,:,:,:,:,:), allocatable :: sarray6 
    110110!> @} 
     111!> \name Arrays containing the values of the grid variables (real) 
     112!> @{ 
     113    real,    dimension(:)          , pointer :: parray1 
     114    real,    dimension(:,:)        , pointer :: parray2 
     115    real,    dimension(:,:,:)      , pointer :: parray3 
     116    real,    dimension(:,:,:,:)    , pointer :: parray4 
     117    real,    dimension(:,:,:,:,:)  , pointer :: parray5 
     118    real,    dimension(:,:,:,:,:,:), pointer :: parray6 
     119!> @} 
     120!> \name Arrays containing the values of the grid variables (real*8) 
     121!> @{ 
     122    real(8), dimension(:)          , pointer :: pdarray1 
     123    real(8), dimension(:,:)        , pointer :: pdarray2 
     124    real(8), dimension(:,:,:)      , pointer :: pdarray3 
     125    real(8), dimension(:,:,:,:)    , pointer :: pdarray4 
     126    real(8), dimension(:,:,:,:,:)  , pointer :: pdarray5 
     127    real(8), dimension(:,:,:,:,:,:), pointer :: pdarray6 
     128!> @} 
     129!> \name Arrays containing the values of the grid variables (real*4) 
     130!> @{ 
     131    real(4), dimension(:)          , pointer :: psarray1 
     132    real(4), dimension(:,:)        , pointer :: psarray2 
     133    real(4), dimension(:,:,:)      , pointer :: psarray3 
     134    real(4), dimension(:,:,:,:)    , pointer :: psarray4 
     135    real(4), dimension(:,:,:,:,:)  , pointer :: psarray5 
     136    real(4), dimension(:,:,:,:,:,:), pointer :: psarray6 
     137!> @} 
    111138!> \name Arrays used to restore the values 
    112139!> @{ 
     
    153180!> \name Arrays containing the values of the grid variables (character) 
    154181!> @{ 
    155     character(2400)                             :: carray0 
    156     character(200), dimension(:)  , allocatable :: carray1 
    157     character(200), dimension(:,:), allocatable :: carray2 
     182    character(4000)                             :: carray0 
     183    character(400), dimension(:)  , allocatable :: carray1 
     184    character(400), dimension(:,:), allocatable :: carray2 
    158185!> @} 
    159186!--------------------------------------------------------------------------------------------------- 
     
    218245!> \name Arrays containing the values of the grid variables (logical) 
    219246!> @{ 
    220     logical                                      :: larray0 
     247    logical                                      :: larray0 = .FALSE. 
    221248    logical, dimension(:)          , allocatable :: larray1 
    222249    logical, dimension(:,:)        , allocatable :: larray2 
     
    242269!> \name Arrays containing the values of the grid variables (integer) 
    243270!> @{ 
    244     integer                                      :: iarray0 
     271    integer                                      :: iarray0 = 0 
    245272    integer, dimension(:)          , allocatable :: iarray1 
    246273    integer, dimension(:,:)        , allocatable :: iarray2 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modupdate.F90

    r5819 r6258  
    11! 
    2 ! $Id$ 
     2! $Id: modupdate.F 779 2007-12-22 17:04:17Z rblod $ 
    33! 
    44!     AGRIF (Adaptive Grid Refinement In Fortran) 
     
    390390#endif 
    391391! 
    392     integer, dimension(6),     intent(in)   :: type_update  !< Type of update (copy or average) 
    393392    type(Agrif_Variable), pointer           :: parent       !< Variable of the parent grid 
    394393    type(Agrif_Variable), pointer           :: child        !< Variable of the child grid 
    395394    integer,                   intent(in)   :: nbdim 
     395    integer, dimension(nbdim), intent(in)   :: type_update  !< Type of update (copy or average) 
    396396    integer, dimension(nbdim), intent(in)   :: pttab        !< Index of the first point inside the domain 
    397397    integer, dimension(nbdim), intent(in)   :: petab        !< Index of the first point inside the domain 
     
    582582                                     nbdim, memberinall, coords,                            & 
    583583                                     sendtoproc1,recvfromproc1,                             & 
    584                                      tab4t(:,:,5),tab4t(:,:,6),tab4t(:,:,7),tab4t(:,:,8)) 
     584                                     tab4t(:,:,5),tab4t(:,:,6),tab4t(:,:,7),tab4t(:,:,8),   & 
     585                                     tab4t(:,:,1),tab4t(:,:,2)) 
    585586    endif 
    586587 
     
    11541155                                     nbdim, memberinall2, coords,                           & 
    11551156                                     sendtoproc2, recvfromproc2,                            & 
    1156                                      tab5t(:,:,5),tab5t(:,:,6),tab5t(:,:,7),tab5t(:,:,8)) 
     1157                                     tab5t(:,:,5),tab5t(:,:,6),tab5t(:,:,7),tab5t(:,:,8),   & 
     1158                                     tab5t(:,:,1),tab5t(:,:,2)) 
    11571159 
    11581160        call Agrif_Addto_list_update(child%list_update,pttab,petab,lb_child,lb_parent,      & 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modupdatebasic.F90

    r5819 r6258  
    11! 
    2 ! $Id$ 
     2! $Id: modupdatebasic.F 779 2007-12-22 17:04:17Z rblod $ 
    33! 
    44!     AGRIF (Adaptive Grid Refinement In Fortran) 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modutil.F90

    r5819 r6258  
    11! 
    2 ! $Id$ 
     2! $Id: modutil.F 662 2007-05-25 15:58:52Z opalod $ 
    33! 
    44!     Agrif (Adaptive Grid Refinement In Fortran) 
     
    108108!--------------------------------------------------------------------------------------------------- 
    109109end subroutine Agrif_Step_Child 
     110!=================================================================================================== 
     111! 
     112!=================================================================================================== 
     113!  subroutine Agrif_Step_Childs 
     114! 
     115!> Apply 'procname' to each child grids of the current grid 
     116!--------------------------------------------------------------------------------------------------- 
     117!     ************************************************************************** 
     118!!!   Subroutine Agrif_Step_Childs 
     119!     ************************************************************************** 
     120! 
     121      Subroutine Agrif_Step_Childs(procname) 
     122! 
     123    procedure(step_proc)    :: procname     !< subroutine to call on each grid 
     124!     Pointer argument 
     125      Type(Agrif_Grid),pointer   :: g        ! Pointer on the current grid 
     126! 
     127 
     128! 
     129!     Local pointer 
     130      Type(Agrif_pgrid),pointer  :: parcours ! Pointer for the recursive 
     131                                             ! procedure 
     132! 
     133      g => Agrif_Curgrid 
     134       
     135      parcours => g % child_list % first 
     136! 
     137!     Recursive procedure for the time integration of the grid hierarchy       
     138      Do while (associated(parcours)) 
     139! 
     140!       Instanciation of the variables of the current grid 
     141        Call Agrif_Instance(parcours % gr) 
     142 
     143!     One step on the current grid 
     144 
     145         Call procname () 
     146        parcours => parcours % next 
     147      enddo 
     148    
     149      If (associated(g % child_list % first)) Call Agrif_Instance (g) 
     150      Return 
     151      End Subroutine Agrif_Step_Childs 
    110152!=================================================================================================== 
    111153! 
     
    538580!=================================================================================================== 
    539581! 
     582!=================================================================================================== 
     583! 
    540584! 
    541585!=================================================================================================== 
     
    587631#ifdef AGRIF_MPI 
    588632    else 
    589 #endif     
    590633! Continue only if the grid has defined sequences of child integrations. 
    591634    if ( .not. associated(save_grid % child_seq) ) return 
     
    610653! 
    611654    enddo 
    612 #ifdef AGRIF_MPI 
    613655    endif 
    614656#endif  
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modvariables.F90

    r5819 r6258  
    9999    Agrif_Curgrid % Nbvariables = Agrif_Curgrid % Nbvariables + 1 
    100100 
    101     varid = -Agrif_Curgrid % Nbvariables 
     101    varid = Agrif_Curgrid % Nbvariables 
    102102 
    103103    var % parent_var => Agrif_Search_Variable(Agrif_Curgrid % parent, Agrif_Curgrid % nbvariables) 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/LIB/DiversListe.c

    r5819 r6258  
    479479        strcpy(newvar->var->v_nomvar,name); 
    480480        strcpy(newvar->var->v_modulename,curmodulename); 
     481        if (strcasecmp(curmodulename,"")) 
     482        { 
     483        newvar->var->v_module=1; 
     484        } 
    481485        strcpy(newvar->var->v_subroutinename,subroutinename); 
    482486        strcpy(newvar->var->v_commoninfile,cur_filename); 
     
    522526 
    523527            Init_Variable(newvar->var); 
    524  
    525528            newvar->var->v_save = 1; 
    526529            strcpy(newvar->var->v_nomvar,parcours->var->v_nomvar); 
     530            strcpy(newvar->var->v_dimchar,parcours->var->v_dimchar); 
    527531            strcpy(newvar->var->v_modulename,curmodulename); 
    528532            strcpy(newvar->var->v_subroutinename,subroutinename); 
     
    531535 
    532536            newvar->var->v_nbdim = parcours->var->v_nbdim; 
     537            strcpy(newvar->var->v_typevar,parcours->var->v_typevar); 
     538            strcpy(newvar->var->v_precision,parcours->var->v_precision); 
    533539            newvar->var->v_catvar = parcours->var->v_catvar; 
    534540            newvar->var->v_dimension = parcours->var->v_dimension; 
    535541            newvar->var->v_dimensiongiven=parcours->var->v_dimensiongiven; 
     542            newvar->var->v_allocatable = parcours->var->v_allocatable; 
     543            newvar->var->v_initialvalue = parcours->var->v_initialvalue; 
     544            newvar->var->v_initialvalue_array = parcours->var->v_initialvalue_array; 
    536545            newvar->suiv = List_Save_Var; 
    537546            List_Save_Var = newvar; 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/LIB/Makefile

    r5819 r6258  
    6262 
    6363clean: 
    64 #  $(MAKE) -f Makefile.lex clean 
    6564   $(RM) *.o conv 
    6665    
     66clean-all: clean 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/LIB/SubLoopCreation.c

    r5819 r6258  
    5858      if ( todebug == 1 ) printf("> enter in WriteBeginof_SubLoop : IsTabvarsUseInArgument_0() == 1\n"); 
    5959      /* we should add the use agrif_uti l if it is necessary                 */ 
     60      if (todebug == 1) fprintf(fortran_out,"\n      !DEBUG: Avant WriteHeadofSubroutineLoop\n"); 
    6061      WriteHeadofSubroutineLoop(); 
     62      if (todebug == 1) fprintf(fortran_out,"      !DEBUG: Apres WriteHeadofSubroutineLoop\n"); 
     63      fflush(fortran_out); 
     64      if (todebug == 1) { 
     65      fprintf(fortran_out,"      !DEBUG: Avant WriteUsemoduleDeclaration\n"); 
     66      } 
     67       
    6168      WriteUsemoduleDeclaration(subroutinename); 
    6269      if ( ImplicitNoneInSubroutine() == 1 ) fprintf(fortran_out, "      implicit none\n"); 
    6370      WriteIncludeDeclaration(fortran_out); 
     71      if (todebug == 1) fprintf(fortran_out,"      !DEBUG: Avant WriteIncludeDeclaration\n"); 
    6472      /*                                                                      */ 
    6573      /* We should write once the declaration of tables (extract              */ 
     
    7785      AddUseAgrifUtil_0(fortran_out); 
    7886      WriteUsemoduleDeclaration(subroutinename); 
     87      if ( ImplicitNoneInSubroutine() == 1 ) fprintf(fortran_out, "      implicit none\n"); 
    7988      WriteIncludeDeclaration(fortran_out); 
    80       if ( ImplicitNoneInSubroutine() == 1 ) fprintf(fortran_out, "      implicit none\n"); 
    8189      WriteLocalParamDeclaration(fortran_out); 
    8290      WriteArgumentDeclaration_beforecall(); 
     91      if (todebug == 1) fprintf(fortran_out,"      !DEBUG: Avant WriteFunctionDeclaration\n"); 
    8392      if ( functiondeclarationisdone == 0 ) WriteFunctionDeclaration(fortran_out, 1); 
    8493/*    writesub_loopdeclaration_scalar(List_SubroutineArgument_Var,fortran_out); 
     
    102111/*                                                                            */ 
    103112/******************************************************************************/ 
    104 void WriteVariablelist_subloop(char *ligne) 
     113void WriteVariablelist_subloop(char **ligne, size_t *line_length) 
    105114{ 
    106115   listvar *parcours; 
     
    117126      if ( !strcasecmp(parcours->var->v_subroutinename,subroutinename) ) 
    118127      { 
    119          if ( didvariableadded == 1 )   strcat(ligne,","); 
    120          strcat(ligne,parcours->var->v_nomvar); 
     128         if ( didvariableadded == 1 )   strcat(*ligne,","); 
     129         if ( (strlen(*ligne)+strlen(parcours->var->v_nomvar)+100) > *line_length ) 
     130         { 
     131            *line_length += LONG_M; 
     132            *ligne = realloc( *ligne, *line_length*sizeof(char) ); 
     133         } 
     134         strcat(*ligne,parcours->var->v_nomvar); 
    121135         didvariableadded = 1; 
    122136      } 
     
    128142      if ( !strcasecmp(parcours->var->v_subroutinename,subroutinename) ) 
    129143      { 
    130          if ( didvariableadded == 1 )   strcat(ligne,","); 
    131          strcat(ligne,parcours->var->v_nomvar); 
     144         if ( didvariableadded == 1 )   strcat(*ligne,","); 
     145         if ( (strlen(*ligne)+strlen(parcours->var->v_nomvar)+100) > *line_length ) 
     146         { 
     147            *line_length += LONG_M; 
     148            *ligne = realloc( *ligne, *line_length*sizeof(char) ); 
     149         } 
     150         strcat(*ligne,parcours->var->v_nomvar); 
    132151         didvariableadded = 1; 
    133152      } 
     
    152171/*                                                                            */ 
    153172/******************************************************************************/ 
    154 void WriteVariablelist_subloop_Call(char **ligne, size_t line_length) 
     173void WriteVariablelist_subloop_Call(char **ligne, size_t *line_length) 
    155174{ 
    156175   listvar *parcours; 
    157176   char ligne2[LONG_M]; 
    158177   int i; 
    159    size_t cur_length; 
    160  
    161    cur_length = line_length; 
    162178 
    163179   if ( todebug == 1 ) printf("> enter in WriteVariablelist_subloop_Call\n"); 
     
    170186      /*    in the output file                                                */ 
    171187      if ( !strcasecmp(parcours->var->v_subroutinename,subroutinename)  && 
    172            (parcours->var->v_pointerdeclare == 0 || !strcasecmp(parcours->var->v_typevar,"type")) 
     188           (parcours->var->v_pointerdeclare >= 0 || !strcasecmp(parcours->var->v_typevar,"type")) 
    173189         ) 
    174190      { 
    175191         if ( didvariableadded == 1 )   strcat(*ligne,","); 
    176192         const char *vres = vargridcurgridtabvars(parcours->var, 0); 
    177          if ( (strlen(*ligne)+strlen(vres)+100) > cur_length ) 
     193         if ( (strlen(*ligne)+strlen(parcours->var->v_nomvar)+100) > *line_length ) 
    178194         { 
    179             cur_length += LONG_M; 
    180             *ligne = realloc( *ligne, cur_length*sizeof(char) ); 
     195            *line_length += LONG_M; 
     196            *ligne = realloc( *ligne, *line_length*sizeof(char) ); 
    181197         } 
    182198         strcat(*ligne, vres); 
     
    186202         if (  SubloopScalar != 0 && 
    187203               ( 
    188                (parcours->var->v_pointerdeclare == 0 || !strcasecmp(parcours->var->v_typevar,"type"))) && 
     204               (parcours->var->v_pointerdeclare >= 0 || !strcasecmp(parcours->var->v_typevar,"type"))) && 
    189205               parcours->var->v_nbdim != 0 ) 
    190206         { 
     
    231247/*                                                                            */ 
    232248/******************************************************************************/ 
    233 void WriteVariablelist_subloop_Def(char *ligne) 
     249void WriteVariablelist_subloop_Def(char **ligne, size_t *line_length) 
    234250{ 
    235251   listvar *parcours; 
     
    244260      /*    in the output file                                                */ 
    245261      if ( !strcasecmp(parcours->var->v_subroutinename,subroutinename)  && 
    246            (parcours->var->v_pointerdeclare == 0 || !strcasecmp(parcours->var->v_typevar,"type")) ) 
     262           (parcours->var->v_pointerdeclare >= 0 || !strcasecmp(parcours->var->v_typevar,"type")) ) 
    247263      { 
    248          if ( didvariableadded == 1 )   strcat(ligne,","); 
    249          strcat(ligne,parcours->var->v_nomvar); 
     264         if ( didvariableadded == 1 )   strcat(*ligne,","); 
     265         if ( (strlen(*ligne)+strlen(parcours->var->v_nomvar)+100) > *line_length ) 
     266         { 
     267            *line_length += LONG_M; 
     268            *ligne = realloc( *ligne, *line_length*sizeof(char) ); 
     269         } 
     270         strcat(*ligne,parcours->var->v_nomvar); 
    250271         didvariableadded = 1; 
    251272      } 
    252273      parcours = parcours -> suiv; 
    253274   } 
    254    Save_Length(ligne,41); 
     275 
    255276   if ( todebug == 1 ) printf("<   out of WriteVariablelist_subloop_Def\n"); 
    256277} 
     
    272293void WriteHeadofSubroutineLoop() 
    273294{ 
    274    char ligne[LONG_M]; 
     295   char *ligne; 
    275296   FILE * subloop; 
    276  
    277    if ( todebug == 1 ) printf("> enter in WriteHeadofSubroutineLoop\n"); 
     297   size_t line_length; 
     298 
     299   ligne = (char*) calloc(LONG_M, sizeof(char)); 
     300   line_length = LONG_M; 
     301 
     302   if ( todebug == 1 ) printf("> enter in WriteHeadofSubroutineLoop subroutine %s\n",subroutinename); 
    278303   tofich(fortran_out,"\n",1); 
     304 
    279305   /* Open this newfile                                                       */ 
    280306   sprintf(ligne,"Sub_Loop_%s.h",subroutinename); 
     
    283309   if (isrecursive) sprintf(ligne,"recursive subroutine Sub_Loop_%s(",subroutinename); 
    284310   else             sprintf(ligne,"subroutine Sub_Loop_%s(",subroutinename); 
     311 
    285312   /*                                                                         */ 
    286    WriteVariablelist_subloop(ligne); 
    287    WriteVariablelist_subloop_Def(ligne); 
     313   if (todebug == 1) fprintf(subloop,"      !DEBUG: Avant WriteVariablelist_subloop\n"); 
     314   WriteVariablelist_subloop(&ligne,&line_length); 
     315   WriteVariablelist_subloop_Def(&ligne,&line_length); 
    288316   /*                                                                         */ 
    289317   strcat(ligne,")"); 
    290318   tofich(subloop,ligne,1); 
     319 
    291320   /* if USE agrif_Uti l should be add                                        */ 
     321   if (todebug == 1) fprintf(subloop,"      !DEBUG: Avant AddUseAgrifUtil_0\n"); 
    292322   AddUseAgrifUtil_0(subloop); 
     323 
    293324   /*                                                                         */ 
     325   if (todebug == 1) fprintf(subloop,"      !DEBUG: Apres AddUseAgrifUtil_0\n"); 
    294326   oldfortran_out = fortran_out; 
    295327   fortran_out = subloop; 
     328    
    296329   if ( todebug == 1 ) printf("<   out of WriteHeadofSubroutineLoop\n"); 
     330    
     331   free(ligne); 
    297332} 
    298333 
     
    313348{ 
    314349   char *ligne; 
     350   size_t line_length; 
    315351 
    316352   if ( firstpass == 1 )    return; 
     
    318354 
    319355   ligne = (char*) calloc(LONG_M, sizeof(char)); 
     356   line_length = LONG_M; 
    320357 
    321358   if ( IsTabvarsUseInArgument_0() == 1 ) 
     
    331368 
    332369      AddUseAgrifUtilBeforeCall_0(fortran_out); 
     370            
    333371      WriteArgumentDeclaration_beforecall(); 
     372      if (todebug == 1) fprintf(fortran_out,"      !DEBUG: Avant WriteFunctionDeclaration\n"); 
     373 
    334374      if ( functiondeclarationisdone == 0 ) WriteFunctionDeclaration(fortran_out, 0); 
    335375      if ( !strcasecmp(subofagrifinitgrids,subroutinename) ) 
     
    339379      sprintf(ligne,"  call Sub_Loop_%s(",subroutinename); 
    340380      /* Write the list of the local variables used in this new subroutine    */ 
    341       WriteVariablelist_subloop(ligne); 
     381      WriteVariablelist_subloop(&ligne,&line_length); 
    342382      /* Write the list of the global tables used in this new subroutine      */ 
    343383      /*    in doloop                                                         */ 
    344       WriteVariablelist_subloop_Call(&ligne, LONG_M); 
     384      WriteVariablelist_subloop_Call(&ligne, &line_length); 
    345385      /* Close the parenthesis of the new subroutine called                   */ 
    346386      strcat(ligne,")\n"); 
     
    358398    oldfortran_out = (FILE *)NULL; 
    359399    if ( todebug == 1 ) printf("<   out of closeandcallsubloopandincludeit_0\n"); 
     400     
     401    free(ligne); 
    360402} 
    361403 
     
    363405{ 
    364406   char *ligne; 
     407   size_t line_length; 
    365408 
    366409   if ( todebug == 1 ) printf("> enter in closeandcallsubloop_contains_0\n"); 
     
    368411   { 
    369412      ligne = (char*) calloc(LONG_M, sizeof(char)); 
     413      line_length = LONG_M; 
    370414      RemoveWordCUR_0(fortran_out,9);   // Remove word 'contains' 
    371415      tofich(fortran_out,"\n",1); 
     
    376420 
    377421      AddUseAgrifUtilBeforeCall_0(fortran_out); 
    378  
    379422      if ( ImplicitNoneInSubroutine() == 1 ) fprintf(fortran_out, "      implicit none\n"); 
    380423      WriteLocalParamDeclaration(fortran_out); 
     424            printf("ICI3\n"); 
    381425      WriteArgumentDeclaration_beforecall(); 
     426      if (todebug == 1) fprintf(fortran_out,"      !DEBUG: Avant WriteFunctionDeclaration\n"); 
    382427      if ( functiondeclarationisdone == 0 ) WriteFunctionDeclaration(fortran_out, 0); 
    383428/*      WriteSubroutineDeclaration(0);*/ 
     
    388433      sprintf(ligne,"  call Sub_Loop_%s(",subroutinename); 
    389434      /* Write the list of the local variables used in this new subroutine    */ 
    390       WriteVariablelist_subloop(ligne); 
     435      WriteVariablelist_subloop(&ligne,&line_length); 
    391436      /* Write the list of the global tables used in this new subroutine      */ 
    392437      /*    in doloop                                                         */ 
    393       WriteVariablelist_subloop_Call(&ligne, LONG_M); 
     438      WriteVariablelist_subloop_Call(&ligne, &line_length); 
    394439      /* Close the parenthesis of the new subroutine called                   */ 
    395440      strcat(ligne,")\n"); 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/LIB/UtilAgrif.c

    r5819 r6258  
    150150    { 
    151151        // remove the variable 
    152         RemoveWordCUR_0(fortran_out,lengthname); 
     152 //       RemoveWordCUR_0(fortran_out,lengthname); 
    153153        // then write the new name 
    154         if ( inagrifcallargument == 1 && agrif_parentcall == 0 ) 
    155             fprintf(fortran_out,"%d",newvar->var->v_indicetabvars); 
    156         else 
    157         { 
    158             if ( retour77 == 0 ) 
    159                 fprintf(fortran_out,"Agrif_%s & \n      ", tabvarsname(newvar->var)); 
    160             else 
    161             { 
    162                fprintf(fortran_out,"Agrif_%s", tabvarsname(newvar->var)); 
    163                fprintf(fortran_out," \n     & "); 
    164             } 
    165             fprintf(fortran_out,"%s",vargridcurgridtabvarswithoutAgrif_Gr(newvar->var)); 
    166         } 
     154 //        if ( inagrifcallargument == 1 && agrif_parentcall == 0 ) 
     155//             fprintf(fortran_out,"%d",newvar->var->v_indicetabvars); 
     156//         else 
     157//         { 
     158//             if ( retour77 == 0 ) 
     159//                 fprintf(fortran_out,"Agrif_%s & \n      ", tabvarsname(newvar->var)); 
     160//             else 
     161//             { 
     162//                fprintf(fortran_out,"Agrif_%s", tabvarsname(newvar->var)); 
     163//                fprintf(fortran_out," \n     & "); 
     164//             } 
     165//             fprintf(fortran_out,"%s",vargridcurgridtabvarswithoutAgrif_Gr(newvar->var)); 
     166//         } 
    167167    } 
    168168    else 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/LIB/UtilFortran.c

    r5819 r6258  
    423423                                                                  doloopout = 1; 
    424424         else parcours = parcours->suiv; 
     425         
    425426      } 
    426427      if (  doloopout == 0 ) out = 0; 
     
    591592    out = 0; 
    592593 
     594    return (out == 0); 
     595     
    593596    if ( !strcasecmp(ident,"size") || 
    594597         !strcasecmp(ident,"if")   || 
     
    596599         !strcasecmp(ident,"min")  ) 
    597600    { 
     601    printf("ident = %s\n",ident); 
    598602        newvar = List_SubroutineDeclaration_Var; 
    599603        while ( newvar && out == 0 ) 
     
    611615            while ( newvar && out == 0 ) 
    612616            { 
     617            printf("llll = %s\n",newvar->var->v_nomvar); 
    613618                if ( !strcasecmp(ident, newvar->var->v_nomvar) ) out = 1; 
    614619                newvar = newvar -> suiv ; 
     
    617622    } 
    618623    return (out == 0); 
     624} 
     625 
     626/* removenewline */ 
     627/* REMOVE UNWANTED character */ 
     628/* from a NAME{NEWLINE77]NAME flex match */ 
     629 
     630void removenewline(char *nom) 
     631{ 
     632char temp_nom[LONG_VNAME]; 
     633int size_nom,i,j; 
     634 
     635size_nom=strlen(nom); 
     636 
     637j=0; 
     638for (i=0;i<size_nom;) 
     639{ 
     640if (nom[i]=='\n') 
     641{ 
     642/* REMOVE RETURN - blank and column 6 character */ 
     643i=i+7; 
     644} 
     645else if (nom[i]==' ' || nom[i]=='\t') 
     646{ 
     647i=i+1; 
     648} 
     649else 
     650{ 
     651temp_nom[j]=nom[i]; 
     652j++; 
     653i++; 
     654} 
     655} 
     656temp_nom[j]='\0'; 
     657 
     658strcpy(nom,temp_nom); 
    619659} 
    620660 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/LIB/UtilListe.c

    r5819 r6258  
    5252   strcpy(var->v_subroutinename     , ""); 
    5353   strcpy(var->v_precision          , ""); 
    54    strcpy(var->v_initialvalue       , ""); 
     54   var->v_initialvalue = (listname *)NULL; 
     55   var->v_initialvalue_array = (listname *)NULL; 
     56   var->v_do_loop = NULL; 
    5557   strcpy(var->v_IntentSpec         , ""); 
    5658   strcpy(var->v_readedlistdimension, ""); 
     
    103105            newvar->suiv = l; 
    104106        } 
     107        newvar=glob; 
     108        while (newvar) 
     109        { 
     110        newvar=newvar->suiv; 
     111        } 
    105112    } 
    106113    return glob; 
     
    117124void CreateAndFillin_Curvar(const char *type, variable *curvar) 
    118125{ 
     126listname *newvar; 
     127 
    119128    if ( !strcasecmp(type, "character") && strcasecmp(CharacterSize, "") ) 
    120129    { 
     
    150159    if (InitialValueGiven == 1 ) 
    151160    { 
    152         strcpy(curvar->v_initialvalue,InitValue); 
     161    curvar->v_initialvalue=Insertname(curvar->v_initialvalue,InitValue,0); 
     162     
     163//        strcpy(curvar->v_initialvalue,InitValue); 
     164         
    153165        Save_Length(InitValue,14); 
    154166    } 
     
    481493      v = newvar->var; 
    482494      strcpy(v->v_typevar,nom); 
     495       
    483496      v->v_catvar = get_cat_var(v); 
     497 
    484498      newvar = newvar->suiv; 
    485499   } 
     
    502516   { 
    503517      v=newvar->var; 
    504       printf("nom = %s, allocatable = %d dim = %s\n",v->v_nomvar,v->v_allocatable,(v->v_dimension)->dim.last); 
    505518      newvar=newvar->suiv; 
    506519   } 
     
    564577} 
    565578 
     579int testandextractfromlist(listname **lin, char*nom) 
     580{ 
     581listname *newvar; 
     582int val_1, val_2; 
     583int return_stmt; 
     584 
     585printname(*lin); 
     586if (!(*lin)) 
     587 { 
     588  return 0; 
     589 } 
     590else 
     591 { 
     592 sscanf(nom,"%d",&val_1); 
     593 sscanf((*lin)->n_name,"%d",&val_2); 
     594 if (val_1==val_2) 
     595   { 
     596/*   newvar = *lin; 
     597   *lin = (*lin)->suiv; 
     598   free(newvar);*/ 
     599   /* continue to remove while the label stays the same */ 
     600/*   return_stmt=testandextractfromlist(lin,nom);*/ 
     601   return 1; 
     602   } 
     603 else 
     604  { 
     605  return 0; 
     606  } 
     607 } 
     608} 
     609 
     610void removefromlist(listname **lin, char*nom) 
     611{ 
     612listname *newvar,*prev; 
     613int val_1, val_2; 
     614int return_stmt; 
     615int out; 
     616 
     617printname(*lin); 
     618if (*lin) 
     619 { 
     620 sscanf(nom,"%d",&val_1); 
     621 prev=(listname *) calloc(1,sizeof(listname)); 
     622 prev->suiv=*lin; 
     623 *lin=prev; 
     624 newvar=(*lin)->suiv; 
     625 out = 0; 
     626 while (newvar && out == 0) 
     627 { 
     628 sscanf((newvar)->n_name,"%d",&val_2); 
     629 if (val_1==val_2) 
     630   { 
     631   prev->suiv=newvar->suiv; 
     632   free(newvar); 
     633   } 
     634  if (prev->suiv)  
     635    { 
     636    prev=prev->suiv; 
     637    newvar=prev->suiv; 
     638    } 
     639   else 
     640   { 
     641   out = 1; 
     642   } 
     643  } 
     644 prev=*lin; 
     645 *lin=(*lin)->suiv; 
     646 free(prev); 
     647 } 
     648} 
     649 
    566650listname *concat_listname(listname *l1, listname *l2) 
    567651{ 
     
    606690   while (newvar) 
    607691   { 
    608       printf("nom = %s \n",newvar->n_name); 
    609692      newvar=newvar->suiv; 
    610693   } 
     
    694777int get_cat_var(variable *var) 
    695778{ 
     779 
    696780    if (!strcasecmp(var->v_typevar, "CHARACTER")) 
    697781        return 1; 
     
    705789        return 0; 
    706790} 
     791 
     792void Insertdoloop(variable *var,char *do_var,char *do_begin, char *do_end, char *do_step) 
     793{ 
     794listdoloop *new_do_loop; 
     795listdoloop *tmploop; 
     796new_do_loop = (listdoloop *) calloc(1,sizeof(listdoloop)); 
     797 
     798new_do_loop->cur_do_loop = (do_loop *) calloc(1,sizeof(do_loop)); 
     799 
     800strcpy(new_do_loop->cur_do_loop->do_variable,do_var); 
     801strcpy(new_do_loop->cur_do_loop->do_begin,do_begin); 
     802strcpy(new_do_loop->cur_do_loop->do_end,do_end); 
     803strcpy(new_do_loop->cur_do_loop->do_step,do_step); 
     804new_do_loop->suiv = NULL; 
     805 
     806if (!var->v_do_loop) 
     807{ 
     808  var->v_do_loop = new_do_loop; 
     809} 
     810else 
     811{ 
     812  new_do_loop->suiv = var->v_do_loop; 
     813  var->v_do_loop = new_do_loop; 
     814       
     815//   tmploop = var->v_do_loop; 
     816//   while (tmploop->suiv) 
     817//   { 
     818//     tmploop=tmploop->suiv; 
     819//   } 
     820//   tmploop->suiv = new_do_loop ; 
     821//   } 
     822} 
     823} 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/LIB/WorkWithlistdatavariable.c

    r5819 r6258  
    7070        strcpy(ligne,values); 
    7171        
    72      strcpy(newvar->var->v_initialvalue,ligne); 
     72     newvar->var->v_initialvalue=Insertname(newvar->var->v_initialvalue,ligne,0); 
     73      
     74     // strcpy(newvar->var->v_initialvalue,ligne); 
    7375     Save_Length(ligne,14); 
    7476     newvar->suiv = NULL; 
     
    8587} 
    8688 
    87 void Add_Data_Var_Names_01 (listvar **curlist,listname *l1,listname *l2) 
     89void Add_Data_Var_Names_01 (listvar **curlist,listvar *l1,listname *l2) 
    8890{ 
    8991    listvar *newvar; 
    9092    listvar *tmpvar; 
    91     listname *tmpvar1; 
    92     listname *tmpvar2;   
     93    listvar *tmpvar1; 
     94    listname *tmpvar2; 
     95    char tempname[LONG_M]; 
    9396    variable *found_var = NULL; 
     97    int out; 
     98    size_t i = 0; 
     99    char chartmp[2]; 
    94100     
    95101    tmpvar1 = l1; 
     
    98104    while (tmpvar1) 
    99105    { 
    100         newvar = (listvar *) calloc(1,sizeof(listvar)); 
    101         newvar->var = (variable *) calloc(1,sizeof(variable)); 
    102  
    103         Init_Variable(newvar->var); 
    104  
    105         if ( inmoduledeclare == 1 ) newvar->var->v_module=1; 
    106       
    107         found_var = get_variable_in_list_from_name(List_Common_Var, tmpvar1->n_name); 
    108         if ( ! found_var )  found_var = get_variable_in_list_from_name(List_Global_Var,tmpvar1->n_name); 
    109         if ( ! found_var )  found_var = get_variable_in_list_from_name(List_SubroutineDeclaration_Var,tmpvar1->n_name); 
    110          
    111         if ( found_var && found_var->v_nbdim > 0 ) 
     106//    printf("TMPVAR 1 nomvar = %s, initialvaluearra = %s\n",tmpvar1->var->v_nomvar,tmpvar1->var->v_initialvalue_array->n_name); 
     107       strcpy(tempname,tmpvar1->var->v_nomvar); 
     108//        while ( i < strlen(tmpvar1->var->v_nomvar) ) 
     109//        { 
     110//        if (tmpvar1->var->v_nomvar[i]=='(') break; 
     111//          sprintf(chartmp,"%c",tmpvar1->var->v_nomvar[i]); 
     112//          strcat(tempname,chartmp); 
     113//          i++; 
     114//        } 
     115        found_var = get_variable_in_list_from_name(List_Common_Var, tempname); 
     116        if ( ! found_var )  found_var = get_variable_in_list_from_name(List_Global_Var,tempname); 
     117        if ( ! found_var )  found_var = get_variable_in_list_from_name(List_SubroutineDeclaration_Var,tempname); 
     118         
     119        if ( found_var && found_var->v_nbdim > 1000 ) 
    112120        { 
    113121            printf("##############################################################################################################\n"); 
     
    118126        } 
    119127         
    120         strcpy(newvar->var->v_nomvar,tmpvar1->n_name); 
     128        if (tmpvar1->var->v_initialvalue_array) 
     129        { 
     130        if ((firstpass == 1) && strcmp(tmpvar1->var->v_initialvalue_array->n_name,"")) 
     131        { 
     132        DecomposeTheName(tmpvar1->var->v_initialvalue_array->n_name); 
     133        } 
     134        } 
     135         
     136        // Search for existing newvar 
     137         
     138        tmpvar = *curlist; 
     139        out = 0; 
     140        while (tmpvar) 
     141        { 
     142        if (!strcasecmp(tempname,tmpvar->var->v_nomvar) && !strcasecmp(subroutinename,tmpvar->var->v_subroutinename) && !strcasecmp(curmodulename,tmpvar->var->v_modulename) && !strcasecmp(cur_filename,tmpvar->var->v_commoninfile) ) 
     143        { 
     144        out = 1; 
     145        break; 
     146        } 
     147        tmpvar=tmpvar->suiv; 
     148        } 
     149        if (out == 0) 
     150        { 
     151        newvar = (listvar *) calloc(1,sizeof(listvar)); 
     152        newvar->var = (variable *) calloc(1,sizeof(variable)); 
     153 
     154        Init_Variable(newvar->var); 
     155 
     156        if ( inmoduledeclare == 1 ) newvar->var->v_module=1; 
     157         
     158        strcpy(newvar->var->v_nomvar,tempname); 
    121159        strcpy(newvar->var->v_subroutinename,subroutinename); 
    122160        strcpy(newvar->var->v_modulename,curmodulename); 
    123161        strcpy(newvar->var->v_commoninfile,cur_filename); 
    124         strcpy(newvar->var->v_initialvalue,tmpvar2->n_name); 
     162        /*printf("TMPVAR 2 nomvar = %s\n",tmpvar2->n_name);*/ 
     163        newvar->var->v_initialvalue=Insertname(newvar->var->v_initialvalue,tmpvar2->n_name,0); 
     164         
     165        if (tmpvar1->var->v_initialvalue_array) 
     166        { 
     167        if (strcmp(tmpvar1->var->v_initialvalue_array->n_name,"")) 
     168        { 
     169        newvar->var->v_initialvalue_array=Insertname(newvar->var->v_initialvalue_array,tmpvar1->var->v_initialvalue_array->n_name,0); 
     170        } 
     171        } 
     172        newvar->var->v_do_loop=tmpvar1->var->v_do_loop; 
     173//        strcpy(newvar->var->v_initialvalue,tmpvar2->n_name); 
     174//        strcpy(newvar->var->v_initialvalue_array,tmpvar1->var->v_initialvalue_array); 
     175         
     176        newvar->var->v_dimension=tmpvar1->var->v_dimension; 
    125177 
    126178        Save_Length(tmpvar2->n_name,14); 
     
    139191            *curlist  = newvar ; 
    140192        } 
     193        tmpvar=newvar; 
     194        } 
     195        else // out = 1 
     196        { 
     197        tmpvar->var->v_initialvalue=Insertname(tmpvar->var->v_initialvalue,tmpvar2->n_name,0); 
     198        if (strcmp(tmpvar1->var->v_initialvalue_array->n_name,"")) 
     199        { 
     200        tmpvar->var->v_initialvalue_array=Insertname(tmpvar->var->v_initialvalue_array,tmpvar1->var->v_initialvalue_array->n_name,0); 
     201        } 
     202        tmpvar->var->v_do_loop=tmpvar1->var->v_do_loop; 
     203        } 
    141204      
    142205        tmpvar1 = tmpvar1->suiv; 
    143         tmpvar2 = tmpvar2->suiv;   
     206        tmpvar2 = tmpvar2->suiv; 
    144207    } 
     208     
     209    while (tmpvar2) 
     210    { 
     211    strcpy(tempname,tmpvar2->n_name); 
     212    tmpvar->var->v_initialvalue = Insertname(tmpvar->var->v_initialvalue,tempname,1); 
     213    tmpvar2 = tmpvar2->suiv;  
     214    } 
     215     
    145216} 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/LIB/WorkWithlistvarindoloop.c

    r5819 r6258  
    119119  if ( !List_UsedInSubroutine_Var ) 
    120120  { 
     121  printf("LISTE VIDE\n"); 
    121122      newvar=(listvar *)calloc(1,sizeof(listvar)); 
    122123      newvar->var=(variable *)calloc(1,sizeof(variable)); 
     
    161162         } 
    162163      } 
     164       
    163165      if ( out == 2 || out == 0 ) 
    164166      { 
     
    175177 
    176178         /* we should find this new variable to know the tabvars indice       */ 
     179 
    177180         if ( variableisglobal(newvar, List_Global_Var) == 1 ) 
    178181         { 
     
    271274void Merge_Variables(variable *var1, variable *var2) 
    272275{ 
     276 
    273277    if ( !strcasecmp(var1->v_typevar,"") ) 
    274278            strcpy(var1->v_typevar,var2->v_typevar); 
    275     else 
    276       { 
    277       strcpy(var2->v_typevar,var1->v_typevar); 
    278       } 
     279    else    strcpy(var2->v_typevar,var1->v_typevar); 
    279280 
    280281    if ( !strcasecmp(var1->v_oldname,"") ) 
     
    310311    else    strcpy(var2->v_precision,var1->v_precision); 
    311312 
    312     if ( !strcasecmp(var1->v_initialvalue,"") ) 
    313             strcpy(var1->v_initialvalue,var2->v_initialvalue); 
    314     else    strcpy(var2->v_initialvalue,var1->v_initialvalue); 
    315  
     313//     if ( !strcasecmp(var1->v_initialvalue,"") ) 
     314//             strcpy(var1->v_initialvalue,var2->v_initialvalue); 
     315//     else    strcpy(var2->v_initialvalue,var1->v_initialvalue); 
     316 
     317    if ( var1->v_initialvalue ) 
     318            var2->v_initialvalue = var1->v_initialvalue; 
     319    else    var1->v_initialvalue = var2->v_initialvalue; 
     320 
     321    if ( var1->v_initialvalue_array ) 
     322            var2->v_initialvalue_array = var1->v_initialvalue_array; 
     323    else    var1->v_initialvalue_array = var2->v_initialvalue_array; 
     324     
     325    if ( var1->v_do_loop ) 
     326            var2->v_do_loop = var1->v_do_loop; 
     327    else    var1->v_do_loop = var2->v_do_loop; 
     328     
     329//     if ( !strcasecmp(var1->v_initialvalue_array,"") ) 
     330//             strcpy(var1->v_initialvalue_array,var2->v_initialvalue_array); 
     331//     else    strcpy(var2->v_initialvalue_array,var1->v_initialvalue_array); 
     332     
    316333    if ( !strcasecmp(var1->v_IntentSpec,"") ) 
    317334            strcpy(var1->v_IntentSpec,var2->v_IntentSpec); 
     
    490507         /*                                                                   */ 
    491508         newvar->suiv = NULL; 
     509 
    492510         Merge_Variables(parcours->var,newvar->var); 
    493511         strcpy(newvar->var->v_subroutinename,parcours->var->v_subroutinename); 
     
    11551173                newvar->var->v_VariableIsParameter, 
    11561174                newvar->var->v_typevar, 
    1157                 newvar->var->v_initialvalue ); 
     1175                newvar->var->v_initialvalue->n_name ); 
    11581176        newvar = newvar->suiv; 
    11591177    } 
     
    11731191                                        strcpy(parcours->var->v_typevar,"REAL"); 
    11741192         else strcpy(parcours->var->v_typevar,"INTEGER"); 
     1193         parcours->var->v_catvar = get_cat_var(parcours->var); 
    11751194      } 
    11761195      parcours = parcours -> suiv ; 
     
    11851204                                        strcpy(parcours->var->v_typevar,"REAL"); 
    11861205         else strcpy(parcours->var->v_typevar,"INTEGER"); 
     1206         parcours->var->v_catvar = get_cat_var(parcours->var); 
    11871207      } 
    11881208      parcours = parcours -> suiv ; 
     
    11971217                                        strcpy(parcours->var->v_typevar,"REAL"); 
    11981218         else strcpy(parcours->var->v_typevar,"INTEGER"); 
     1219         parcours->var->v_catvar = get_cat_var(parcours->var); 
    11991220      } 
    12001221      parcours = parcours -> suiv ; 
     
    12091230                                        strcpy(parcours->var->v_typevar,"REAL"); 
    12101231         else strcpy(parcours->var->v_typevar,"INTEGER"); 
     1232         parcours->var->v_catvar = get_cat_var(parcours->var); 
     1233      } 
     1234      parcours = parcours -> suiv ; 
     1235   } 
     1236    
     1237   /*                                                                         */ 
     1238   parcours = List_Parameter_Var; 
     1239   while ( parcours ) 
     1240   { 
     1241      if ( !strcasecmp(parcours->var->v_typevar,"") ) 
     1242      { 
     1243         if ( IsVariableReal(parcours->var->v_nomvar) == 1 ) 
     1244                                        strcpy(parcours->var->v_typevar,"REAL"); 
     1245         else strcpy(parcours->var->v_typevar,"INTEGER"); 
     1246         parcours->var->v_catvar = get_cat_var(parcours->var); 
     1247      } 
     1248      parcours = parcours -> suiv ; 
     1249   } 
     1250    
     1251   /*                                                                         */ 
     1252   parcours = List_GlobalParameter_Var; 
     1253   while ( parcours ) 
     1254   { 
     1255      if ( !strcasecmp(parcours->var->v_typevar,"") ) 
     1256      { 
     1257         if ( IsVariableReal(parcours->var->v_nomvar) == 1 ) 
     1258                                        strcpy(parcours->var->v_typevar,"REAL"); 
     1259         else strcpy(parcours->var->v_typevar,"INTEGER"); 
     1260         parcours->var->v_catvar = get_cat_var(parcours->var); 
    12111261      } 
    12121262      parcours = parcours -> suiv ; 
     
    15091559void update_indicemaxtabvars(variable *var,listindice **Listofindices) 
    15101560{ 
    1511  
    1512  
    15131561            if ( Listofindices[var->v_catvar] ) 
    15141562            { 
     
    15471595          ) 
    15481596      { 
     1597            /* The type may has not been given if the variable was only declared with dimension */ 
     1598 
     1599            if ( !strcasecmp(parcours->var->v_typevar,"") ) 
     1600            { 
     1601                  if ( IsVariableReal(parcours->var->v_nomvar) == 1 ) 
     1602                                        strcpy(parcours->var->v_typevar,"REAL"); 
     1603                  else strcpy(parcours->var->v_typevar,"INTEGER"); 
     1604                  parcours->var->v_catvar = get_cat_var(parcours->var); 
     1605             } 
     1606              
    15491607         indicemaxtabvars[parcours->var->v_catvar] = indicemaxtabvars[parcours->var->v_catvar] + 1 ; 
    15501608         parcours->var->v_indicetabvars = indicemaxtabvars[parcours->var->v_catvar]; 
     
    16261684              parcours->var->v_notgrid == 0                              && 
    16271685              ( ( parcours->var->v_nbdim != 0 || !strcasecmp(parcours->var->v_typevar,"type") ) 
    1628               || strcasecmp(parcours->var->v_initialvalue,"") ) 
     1686              || parcours->var->v_initialvalue ) 
    16291687            ) 
    16301688         { 
     
    16581716              !strcasecmp(parcours->var->v_commoninfile,cur_filename)       && 
    16591717              ( ( parcours->var->v_nbdim != 0 || !strcasecmp(parcours->var->v_typevar,"type") ) 
    1660               || strcasecmp(parcours->var->v_initialvalue,"") ) 
     1718              || parcours->var->v_initialvalue ) 
    16611719            ) 
    16621720         { 
     
    18451903      printf("dimensiongiven - %d \n", parcours->var->v_dimensiongiven); 
    18461904      printf("dimsempty      - %d \n", parcours->var->v_dimsempty); 
    1847       printf("initialvalue   - %s \n", parcours->var->v_initialvalue); 
     1905      printf("initialvalue   - %s \n", parcours->var->v_initialvalue->n_name); 
    18481906      printf("readedlistdim  - %s \n", parcours->var->v_readedlistdimension); 
    18491907      printf("-------------------------------------\n"); 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/LIB/WriteInFile.c

    r5819 r6258  
    141141    fseek(filout, position, SEEK_SET); 
    142142    tofich_blanc(filout, sizetoremove); 
    143     fseek(filout, position, SEEK_SET); 
     143 
    144144} 
    145145 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/LIB/Writedeclarations.c

    r5819 r6258  
    6666  /* We should give the precision of the variable if it has been given        */ 
    6767  precision_given = 0; 
     68   
    6869  if ( strcasecmp(v->v_precision,"") ) 
    6970  { 
     
    128129    { 
    129130        strcat(line," = "); 
    130         strcat(line, v->v_initialvalue); 
     131        strcat(line, v->v_initialvalue->n_name); 
    131132    } 
    132133    Save_Length(line, 45); 
     
    173174    { 
    174175        strcat(ligne," = "); 
    175         strcat(ligne,v->v_initialvalue); 
     176        strcat(ligne,v->v_initialvalue->n_name); 
    176177    } 
    177178    Save_Length(ligne,45); 
     
    206207        WriteTableDeclaration(v, ligne, value); 
    207208 
    208      if ( v->v_VariableIsParameter != 1 && strcasecmp(v->v_initialvalue,"") ) 
     209     if ( v->v_VariableIsParameter != 1 && v->v_initialvalue) 
    209210     { 
    210211        strcat(ligne," = "); 
    211         strcat(ligne,v->v_initialvalue); 
     212        strcat(ligne,v->v_initialvalue->n_name); 
    212213     } 
    213214     tofich(filecommon, ligne, 1); 
     
    241242    while ( parcours ) 
    242243    { 
     244    if (!strcmp(parcours->var->v_typevar, "")) 
     245    { 
     246     /* Default type*/ 
     247          if ( IsVariableReal(parcours->var->v_nomvar) == 1 ) 
     248                                         strcpy(parcours->var->v_typevar,"REAL"); 
     249          else strcpy(parcours->var->v_typevar,"INTEGER"); 
     250     } 
    243251        if ( !strcasecmp(parcours->var->v_subroutinename, subroutinename) && 
    244252              strcasecmp(parcours->var->v_typevar, "") ) 
     
    261269        if ( !strcasecmp(v->v_subroutinename, subroutinename)   && 
    262270             (v->v_save == 0)                                   && 
    263              (v->v_pointerdeclare == 0)                         && 
    264271             (v->v_VariableIsParameter == 0)                    && 
    265272             (v->v_common == 0) ) 
     
    285292    listvar *parcours; 
    286293    variable *v; 
    287     char ligne[LONG_M]; 
    288  
     294    char *ligne; 
     295    size_t line_length; 
     296    int res; 
     297    int global_check; 
     298 
     299    ligne = (char*) calloc(LONG_M, sizeof(char)); 
     300    line_length = LONG_M; 
     301     
     302    global_check = 0; 
     303    
     304    
    289305    fprintf(fortran_out,"#include \"Param_BeforeCall_%s.h\"\n",subroutinename); 
    290306 
     
    303319            position++; 
    304320            WriteVarDeclaration(v, fortran_out, 0, 1); 
    305             neededparameter = writedeclarationintoamr(List_Parameter_Var, paramtoamr, 
    306                                     v, v->v_subroutinename, neededparameter, subroutinename); 
     321            res = writedeclarationintoamr(List_Parameter_Var, paramtoamr, 
     322                                    v, v->v_subroutinename, &neededparameter, subroutinename, global_check); 
    307323            parcours = List_SubroutineArgument_Var; 
    308324        } 
    309325        else parcours = parcours -> suiv; 
    310326    } 
    311     Save_Length(ligne,45); 
    312327 
    313328    // Write interface for 'Sub_Loop_machin' in 'Param_BeforeCall_machin.h' when outside a module 
     
    317332        if (isrecursive) sprintf(ligne,"  recursive subroutine Sub_Loop_%s(", subroutinename); 
    318333        else             sprintf(ligne,"  subroutine Sub_Loop_%s(", subroutinename); 
    319         WriteVariablelist_subloop(ligne); 
    320         WriteVariablelist_subloop_Def(ligne); 
     334        WriteVariablelist_subloop(&ligne,&line_length); 
     335        WriteVariablelist_subloop_Def(&ligne,&line_length); 
    321336        strcat(ligne,")"); 
    322         Save_Length(ligne,45); 
     337 
    323338        tofich(paramtoamr,ligne,1); 
    324339 
     
    353368 
    354369    parcours = List_SubroutineArgument_Var; 
     370     
    355371    while ( parcours ) 
    356372    { 
     
    399415/*                                                                            */ 
    400416/******************************************************************************/ 
    401 listnom *writedeclarationintoamr (listvar * deb_common, FILE *fileout, 
     417int writedeclarationintoamr (listvar * deb_common, FILE *fileout, 
    402418                              variable *var , const char *commonname, 
    403                            listnom *neededparameter, const char *name_common) 
     419                           listnom **neededparameter, const char *name_common, int global_check) 
    404420{ 
    405421  listvar *newvar; 
     
    410426  int writeit; 
    411427  listnom *parcours; 
     428  listname *parcours_name_array; 
     429  int res; 
     430   
     431  res = 0; 
    412432 
    413433  /* we should list the needed parameter                                      */ 
     434 
    414435  if ( !strcasecmp(name_common,commonname) ) 
    415      neededparameter = DecomposeTheNameinlistnom(var->v_readedlistdimension,neededparameter); 
     436     { 
     437     *neededparameter = DecomposeTheNameinlistnom(var->v_readedlistdimension,*neededparameter); 
     438     parcours_name_array = var->v_initialvalue_array; 
     439     while (parcours_name_array) 
     440     { 
     441     *neededparameter = DecomposeTheNameinlistnom(parcours_name_array->n_name,*neededparameter); 
     442     parcours_name_array=parcours_name_array->suiv; 
     443     } 
     444     } 
     445 
    416446  /*                                                                          */ 
    417   parcours = neededparameter; 
     447  parcours = *neededparameter; 
     448 
    418449  while (parcours) 
    419450  { 
     
    423454     while ( newvar && out == 0 ) 
    424455     { 
    425  
    426         if ( !strcasecmp(parcours->o_nom,newvar->var->v_nomvar) && !strcasecmp(var->v_subroutinename,newvar->var->v_subroutinename)) 
     456        if ( (global_check == 0) && !strcasecmp(parcours->o_nom,newvar->var->v_nomvar) && !strcasecmp(var->v_subroutinename,newvar->var->v_subroutinename)) 
    427457        { 
    428458           out=1; 
    429459        /* add the name to the list of needed parameter                       */ 
    430            neededparameter = DecomposeTheNameinlistnom( 
    431                  newvar->var->v_initialvalue, 
    432                  neededparameter ); 
     460           *neededparameter = DecomposeTheNameinlistnom( 
     461                 newvar->var->v_initialvalue->n_name, 
     462                 *neededparameter ); 
     463        } 
     464        else if ( (global_check == 1) && !strcasecmp(parcours->o_nom,newvar->var->v_nomvar) && !strcasecmp(var->v_modulename,newvar->var->v_modulename)) 
     465        { 
     466           out=1; 
     467        /* add the name to the list of needed parameter                       */ 
     468           *neededparameter = DecomposeTheNameinlistnom( 
     469                 newvar->var->v_initialvalue->n_name, 
     470                 *neededparameter ); 
    433471        } 
    434472        else newvar=newvar->suiv; 
     
    437475   } 
    438476  /*                                                                          */ 
    439   parcours = neededparameter; 
     477  parcours = *neededparameter; 
     478   
    440479  while (parcours) 
    441480  { 
     
    444483     while ( newvar && out == 0 ) 
    445484     { 
    446         if ( !strcasecmp(parcours->o_nom,newvar->var->v_nomvar) && !strcasecmp(var->v_subroutinename,newvar->var->v_subroutinename)) 
     485        if ( (global_check == 0) && !strcasecmp(parcours->o_nom,newvar->var->v_nomvar) && !strcasecmp(var->v_subroutinename,newvar->var->v_subroutinename)) 
    447486        { 
    448487           out=1; 
    449488        /* add the name to the list of needed parameter                       */ 
    450            neededparameter = DecomposeTheNameinlistnom( 
    451                  newvar->var->v_initialvalue, 
    452                  neededparameter ); 
     489           *neededparameter = DecomposeTheNameinlistnom( 
     490                 newvar->var->v_initialvalue->n_name, 
     491                 *neededparameter ); 
     492        } 
     493        else if ( (global_check == 1) && !strcasecmp(parcours->o_nom,newvar->var->v_nomvar) && !strcasecmp(var->v_modulename,newvar->var->v_modulename)) 
     494        { 
     495           out=1; 
     496        /* add the name to the list of needed parameter                       */ 
     497           *neededparameter = DecomposeTheNameinlistnom( 
     498                 newvar->var->v_initialvalue->n_name, 
     499                 *neededparameter ); 
    453500        } 
    454501        else newvar=newvar->suiv; 
     
    456503     parcours=parcours->suiv; 
    457504   } 
    458   parcours = neededparameter; 
     505  parcours = *neededparameter; 
    459506  while (parcours) 
    460507  { 
     
    463510     while ( newvar && writeit == 0 ) 
    464511     { 
    465         if ( !strcasecmp(parcours->o_nom,newvar->var->v_nomvar) && 
     512        if ( (global_check == 0) && !strcasecmp(parcours->o_nom,newvar->var->v_nomvar) && 
    466513            !strcasecmp(var->v_subroutinename,newvar->var->v_subroutinename) && parcours->o_val == 0 ) 
     514        { 
     515           writeit=1; 
     516           parcours->o_val = 1; 
     517        } 
     518        else if ( (global_check == 1) && !strcasecmp(parcours->o_nom,newvar->var->v_nomvar) && 
     519            !strcasecmp(var->v_modulename,newvar->var->v_modulename) && parcours->o_val == 0 ) 
    467520        { 
    468521           writeit=1; 
     
    490543           v->v_allocatable = 1; 
    491544        } 
     545        res = 1; 
    492546     } 
    493547     else 
     
    503557  } 
    504558  Save_Length(ligne,45); 
    505   return neededparameter; 
     559  return res; 
    506560} 
    507561 
     
    532586     if ( newvar->var->v_nbdim == 0 && 
    533587          !strcasecmp(newvar->var->v_subroutinename,subroutinename)  && 
    534            (newvar->var->v_pointerdeclare == 0 || !strcasecmp(newvar->var->v_typevar,"type")) ) 
     588           (newvar->var->v_pointerdeclare >= 0 || !strcasecmp(newvar->var->v_typevar,"type")) ) 
    535589     { 
    536590        v = newvar->var; 
    537  
    538591        WriteBeginDeclaration(v,ligne,1); 
    539592        WriteScalarDeclaration(v,ligne); 
     
    570623//  printf("newvar = %s %d %s\n",newvar->var->v_nomvar,newvar->var->v_pointerdeclare,newvar->var->v_typevar); 
    571624     if ( (v->v_nbdim != 0)  && !strcasecmp(v->v_subroutinename, subroutinename) && 
    572           (v->v_pointerdeclare == 0 || !strcasecmp(v->v_typevar,"type")) ) 
     625          (v->v_pointerdeclare >= 0 || !strcasecmp(v->v_typevar,"type")) ) 
    573626     { 
    574627        changeval = 0; 
     
    596649     newvar = newvar->suiv; 
    597650  } 
     651 
    598652  Save_Length(ligne,45); 
    599653} 
     
    619673            if (firstpass == 0 && out == 0 && VariableIsParameter == 0 && SaveDeclare == 0) 
    620674            { 
     675             
     676            /* The type may has not been given if the variable was only declared with dimension */ 
     677 
     678            if ( !strcasecmp(v->v_typevar,"") ) 
     679            { 
     680                  if ( IsVariableReal(v->v_nomvar) == 1 ) 
     681                                        strcpy(v->v_typevar,"REAL"); 
     682                  else strcpy(v->v_typevar,"INTEGER"); 
     683                  v->v_catvar = get_cat_var(v); 
     684             } 
     685              
    621686                WriteVarDeclaration(v, fortran_out, 1, 1); 
    622687            } 
     
    639704    char ligne[LONG_M]; 
    640705    char initialvalue[LONG_M]; 
    641  
     706    listname *parcours_name; 
     707     
    642708    if (insubroutinedeclare == 1) 
    643709    { 
     
    651717            if (out)   break; 
    652718 
    653             if (strncasecmp(parcours->var->v_initialvalue,"(/",2)) 
     719            strcpy(initialvalue,""); 
     720            parcours_name = parcours->var->v_initialvalue; 
     721            while (parcours_name) 
    654722            { 
    655                 strcpy(initialvalue,parcours->var->v_initialvalue); 
     723            if (strncasecmp(parcours_name->n_name,"(/",2)) 
     724            { 
     725                strcat(initialvalue,parcours_name->n_name); 
     726                if (parcours_name->suiv) 
     727                { 
     728                strcat(initialvalue,","); 
     729                } 
    656730            } 
    657731            else 
    658732            { 
    659                 strncpy(initialvalue,&parcours->var->v_initialvalue[2],strlen(parcours->var->v_initialvalue)-4); 
    660                 strcpy(&initialvalue[strlen(parcours->var->v_initialvalue)-4],"\0"); 
     733            printf("A TRAITER DANS REWRITEDATA STATEMETN "); 
     734            exit(1); 
     735                strncpy(initialvalue,&parcours_name->n_name[2],strlen(parcours_name->n_name)-4); 
     736                strcpy(&initialvalue[strlen(parcours_name->n_name)-4],"\0"); 
     737            } 
     738            parcours_name=parcours_name->suiv; 
    661739            } 
    662740            sprintf(ligne,"data %s/%s/",parcours->var->v_nomvar,initialvalue); 
    663741            tofich(filout,ligne,1); 
    664  
     742             
    665743            parcours = parcours->suiv; 
    666744        } 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/LIB/decl.h

    r5819 r6258  
    5656} listdim;                 /* list of the dimensions of a variable            */ 
    5757 
     58typedef struct listname 
     59{ 
     60   char n_name[LONG_M]; 
     61   struct  listname* suiv; 
     62} listname ;            /* list of names                                  */ 
     63 
     64typedef struct do_loop 
     65{ 
     66   char do_variable[LONG_VNAME]; 
     67   char do_begin[LONG_VNAME]; 
     68   char do_end[LONG_VNAME]; 
     69   char do_step[LONG_VNAME]; 
     70} do_loop ; 
     71 
     72typedef struct listdoloop 
     73{ 
     74   do_loop *cur_do_loop; 
     75   struct listdoloop* suiv; 
     76} listdoloop; 
     77 
    5878typedef struct variable 
    5979{ 
     
    6888   char v_commoninfile[LONG_FNAME]; 
    6989   char v_subroutinename[LONG_VNAME]; 
     90   listdoloop *v_do_loop; 
    7091   char v_precision[LONG_C]; 
    71    char v_initialvalue[LONG_M]; 
     92   listname *v_initialvalue; 
     93   listname *v_initialvalue_array; 
    7294   char v_IntentSpec[LONG_M]; 
    7395   char v_readedlistdimension[LONG_M]; 
     
    126148} listparameter ;           /* list of names                                  */ 
    127149 
    128 typedef struct listname 
    129 { 
    130    char n_name[LONG_VNAME]; 
    131    struct  listname* suiv; 
    132 } listname ;            /* list of names                                  */ 
    133  
    134150typedef struct listcouple 
    135151{ 
     
    198214 listname *List_Pointer_Var; 
    199215 listname *List_ImplicitNoneSubroutine; 
     216  
     217 listname *List_Do_labels;  
     218 /* A list that contains the do labels if any */ 
    200219 
    201220 listusemodule *List_NameOfModuleUsed; 
     
    321340 char curmodulename[LONG_VNAME]; 
    322341 char subroutinename[LONG_VNAME]; 
     342 char old_subroutinename[LONG_VNAME]; // For internal subprogramm 
    323343 char cur_filename[LONG_FNAME];     // Name of the current parsed Fortran file 
    324344 char config_file[LONG_FNAME];      // Name of conv configuration file (ex: amr.in) 
     
    331351 FILE *fortran_in;           /* Input File                                     */ 
    332352 FILE *oldfortran_out; 
     353 FILE *old_oldfortran_out; // For internal subprogramm 
    333354 FILE *subloop; 
    334355 FILE *module_declar; 
     
    433454/******************************************************************************/ 
    434455extern void WriteBeginof_SubLoop(); 
    435 extern void WriteVariablelist_subloop(char *ligne); 
    436 extern void WriteVariablelist_subloop_Call(char **ligne, size_t line_length); 
    437 extern void WriteVariablelist_subloop_Def(char *ligne); 
     456extern void WriteVariablelist_subloop(char **ligne, size_t *line_length); 
     457extern void WriteVariablelist_subloop_Call(char **ligne, size_t *line_length); 
     458extern void WriteVariablelist_subloop_Def(char **ligne, size_t *line_length); 
    438459extern void WriteHeadofSubroutineLoop(); 
    439460extern void closeandcallsubloopandincludeit_0(int suborfun); 
     
    516537extern int varistyped_0(char *ident); 
    517538extern void dump_var(const variable* var); 
     539extern void removenewline(char *nom); 
    518540/******************************************************************************/ 
    519541/*********** UtilListe.c ******************************************************/ 
     
    532554extern int IsinListe(listvar *lin,char *nom); 
    533555extern listname *Insertname(listname *lin,char *nom,int sens); 
     556extern int testandextractfromlist(listname **lin, char*nom); 
     557extern void removefromlist(listname **lin, char*nom); 
    534558extern listname *concat_listname(listname *l1, listname *l2); 
    535559extern void createstringfromlistname(char *ligne, listname *lin); 
     
    540564extern void  addprecision_derivedfromkind(variable *curvar); 
    541565extern int get_cat_var(variable *var); 
     566extern void Insertdoloop(variable *var,char *do_var, char *do_begin, char *do_end, char *do_step); 
    542567/******************************************************************************/ 
    543568/*********** UtilNotGridDep.c *************************************************/ 
     
    560585/******************************************************************************/ 
    561586extern void Add_Data_Var_1 (listvar **curlist,char *name,char *values); 
    562 extern void Add_Data_Var_Names_01 (listvar **curlist,listname *l1, listname *l2); 
     587extern void Add_Data_Var_Names_01 (listvar **curlist,listvar *l1, listname *l2); 
    563588/******************************************************************************/ 
    564589/*********** WorkWithlistmoduleinfile.c ***************************************/ 
     
    641666extern void WriteArgumentDeclaration_beforecall(); 
    642667extern void WriteArgumentDeclaration_Sort(FILE* tofile); 
    643 extern listnom * writedeclarationintoamr(listvar *deb_common, FILE *fileout, variable *var, 
    644                   const char *commonname, listnom *neededparameter, const char *name_common); 
     668extern int writedeclarationintoamr(listvar *deb_common, FILE *fileout, variable *var, 
     669                  const char *commonname, listnom **neededparameter, const char *name_common, int global_check); 
    645670extern void writesub_loopdeclaration_scalar(listvar *deb_common, FILE *fileout); 
    646671extern void writesub_loopdeclaration_tab(listvar *deb_common, FILE *fileout); 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/LIB/fortran.c

    r5819 r6258  
    4545 
    4646/* Bison version.  */ 
     47#define YYBISON_VERSION "2.7" 
    4748 
    4849/* Skeleton name.  */ 
     
    7980 
    8081extern int line_num_input; 
    81 extern char *fortran_text; 
    8282 
    8383char c_selectorname[LONG_M]; 
     
    8787int c_selectorgiven=0; 
    8888listvar *curlistvar; 
     89int in_select_case_stmt=0; 
    8990typedim c_selectordim; 
    9091listcouple *coupletmp; 
    9192int removeline=0; 
     93int token_since_endofstmt = 0; 
     94int increment_nbtokens = 1; 
     95int in_complex_literal = 0; 
     96int close_or_connect = 0; 
     97long int my_position; 
     98long int my_position_before; 
     99int suborfun = 0; 
     100int indeclaration = 0; 
     101int endoffile = 0; 
     102int in_inquire = 0; 
     103int in_char_selector = 0; 
     104int in_kind_selector =0; 
     105int char_length_toreset = 0; 
     106 
     107typedim my_dim; 
     108 
    92109listvar *test; 
     110 
     111char linebuf1[1024]; 
     112char linebuf2[1024]; 
    93113 
    94114int fortran_error(const char *s) 
    95115{ 
    96     printf("%s line %d, file %s motclef = |%s|\n", s, line_num_input, cur_filename, fortran_text); 
     116  if (endoffile == 1)  
     117  { 
     118  endoffile = 0; 
     119  return 0; 
     120  } 
     121    printf("%s line %d, file %s culprit = |%s|\n", s, line_num_input, cur_filename, strcat(linebuf1, linebuf2)); 
    97122    exit(1); 
    98123} 
     
    100125 
    101126/* Line 371 of yacc.c  */ 
    102 #line 104 "fortran.tab.c" 
     127#line 128 "fortran.tab.c" 
    103128 
    104129# ifndef YY_NULL 
     
    156181     TOK_PROGRAM = 279, 
    157182     TOK_FUNCTION = 280, 
    158      TOK_FORMAT = 281, 
    159      TOK_MAX = 282, 
    160      TOK_TANH = 283, 
    161      TOK_WHERE = 284, 
    162      TOK_ELSEWHEREPAR = 285, 
    163      TOK_ELSEWHERE = 286, 
    164      TOK_ENDWHERE = 287, 
    165      TOK_MAXVAL = 288, 
    166      TOK_TRIM = 289, 
    167      TOK_NULL_PTR = 290, 
    168      TOK_SUM = 291, 
    169      TOK_SQRT = 292, 
    170      TOK_CASE = 293, 
    171      TOK_SELECTCASE = 294, 
    172      TOK_FILE = 295, 
    173      TOK_UNIT = 296, 
    174      TOK_FMT = 297, 
    175      TOK_NML = 298, 
    176      TOK_END = 299, 
    177      TOK_EOR = 300, 
    178      TOK_ERR = 301, 
    179      TOK_EXIST = 302, 
    180      TOK_MIN = 303, 
    181      TOK_FLOAT = 304, 
    182      TOK_EXP = 305, 
    183      TOK_COS = 306, 
    184      TOK_COSH = 307, 
    185      TOK_ACOS = 308, 
    186      TOK_NINT = 309, 
    187      TOK_CYCLE = 310, 
    188      TOK_SIN = 311, 
    189      TOK_SINH = 312, 
    190      TOK_ASIN = 313, 
    191      TOK_EQUIVALENCE = 314, 
    192      TOK_BACKSPACE = 315, 
    193      TOK_LOG = 316, 
    194      TOK_TAN = 317, 
    195      TOK_ATAN = 318, 
    196      TOK_RECURSIVE = 319, 
    197      TOK_ABS = 320, 
    198      TOK_MOD = 321, 
    199      TOK_SIGN = 322, 
    200      TOK_MINLOC = 323, 
    201      TOK_MAXLOC = 324, 
    202      TOK_EXIT = 325, 
    203      TOK_MINVAL = 326, 
    204      TOK_PUBLIC = 327, 
    205      TOK_PRIVATE = 328, 
    206      TOK_ALLOCATABLE = 329, 
    207      TOK_RETURN = 330, 
    208      TOK_THEN = 331, 
    209      TOK_ELSEIF = 332, 
    210      TOK_ELSE = 333, 
    211      TOK_ENDIF = 334, 
    212      TOK_PRINT = 335, 
    213      TOK_PLAINGOTO = 336, 
    214      TOK_LOGICALIF = 337, 
    215      TOK_PLAINDO = 338, 
    216      TOK_CONTAINS = 339, 
    217      TOK_ENDDO = 340, 
    218      TOK_MODULE = 341, 
    219      TOK_ENDMODULE = 342, 
    220      TOK_WHILE = 343, 
    221      TOK_CONCURRENT = 344, 
    222      TOK_ALLOCATE = 345, 
    223      TOK_OPEN = 346, 
    224      TOK_CLOSE = 347, 
    225      TOK_INQUIRE = 348, 
    226      TOK_WRITE = 349, 
    227      TOK_FLUSH = 350, 
    228      TOK_READ = 351, 
    229      TOK_REWIND = 352, 
    230      TOK_DEALLOCATE = 353, 
    231      TOK_NULLIFY = 354, 
    232      TOK_DIMENSION = 355, 
    233      TOK_ENDSELECT = 356, 
    234      TOK_EXTERNAL = 357, 
    235      TOK_INTENT = 358, 
    236      TOK_INTRINSIC = 359, 
    237      TOK_NAMELIST = 360, 
    238      TOK_DEFAULT = 361, 
    239      TOK_OPTIONAL = 362, 
    240      TOK_POINTER = 363, 
    241      TOK_CONTINUE = 364, 
    242      TOK_SAVE = 365, 
    243      TOK_TARGET = 366, 
    244      TOK_IMPLICIT = 367, 
    245      TOK_NONE = 368, 
    246      TOK_CALL = 369, 
    247      TOK_STAT = 370, 
    248      TOK_POINT_TO = 371, 
    249      TOK_COMMON = 372, 
    250      TOK_GLOBAL = 373, 
    251      TOK_LEFTAB = 374, 
    252      TOK_RIGHTAB = 375, 
    253      TOK_PAUSE = 376, 
    254      TOK_PROCEDURE = 377, 
    255      TOK_STOP = 378, 
    256      TOK_REAL8 = 379, 
    257      TOK_FOURDOTS = 380, 
    258      TOK_HEXA = 381, 
    259      TOK_ASSIGNTYPE = 382, 
    260      TOK_OUT = 383, 
    261      TOK_INOUT = 384, 
    262      TOK_IN = 385, 
    263      TOK_USE = 386, 
    264      TOK_TRUE = 387, 
    265      TOK_FALSE = 388, 
    266      TOK_LABEL = 389, 
    267      TOK_TYPE = 390, 
    268      TOK_TYPEPAR = 391, 
    269      TOK_ENDTYPE = 392, 
    270      TOK_REAL = 393, 
    271      TOK_INTEGER = 394, 
    272      TOK_LOGICAL = 395, 
    273      TOK_DOUBLEPRECISION = 396, 
    274      TOK_ENDSUBROUTINE = 397, 
    275      TOK_ENDFUNCTION = 398, 
    276      TOK_ENDPROGRAM = 399, 
    277      TOK_ENDUNIT = 400, 
    278      TOK_CHARACTER = 401, 
    279      TOK_CHAR_CONSTANT = 402, 
    280      TOK_CHAR_CUT = 403, 
    281      TOK_DATA = 404, 
    282      TOK_CHAR_MESSAGE = 405, 
    283      TOK_CSTREAL = 406, 
    284      TOK_COMPLEX = 407, 
    285      TOK_DOUBLECOMPLEX = 408, 
    286      TOK_NAME = 409, 
    287      TOK_CSTINT = 410 
     183     TOK_LABEL_FORMAT = 281, 
     184     TOK_LABEL_CONTINUE = 282, 
     185     TOK_LABEL_END_DO = 283, 
     186     TOK_MAX = 284, 
     187     TOK_TANH = 285, 
     188     TOK_COMMENT = 286, 
     189     TOK_WHERE = 287, 
     190     TOK_ELSEWHEREPAR = 288, 
     191     TOK_ELSEWHERE = 289, 
     192     TOK_ENDWHERE = 290, 
     193     TOK_MAXVAL = 291, 
     194     TOK_TRIM = 292, 
     195     TOK_NULL_PTR = 293, 
     196     TOK_SUM = 294, 
     197     TOK_SQRT = 295, 
     198     TOK_CASE = 296, 
     199     TOK_SELECTCASE = 297, 
     200     TOK_FILE = 298, 
     201     TOK_REC = 299, 
     202     TOK_NAME_EQ = 300, 
     203     TOK_IOLENGTH = 301, 
     204     TOK_ACCESS = 302, 
     205     TOK_ACTION = 303, 
     206     TOK_FORM = 304, 
     207     TOK_RECL = 305, 
     208     TOK_STATUS = 306, 
     209     TOK_UNIT = 307, 
     210     TOK_OPENED = 308, 
     211     TOK_FMT = 309, 
     212     TOK_NML = 310, 
     213     TOK_END = 311, 
     214     TOK_EOR = 312, 
     215     TOK_EOF = 313, 
     216     TOK_ERR = 314, 
     217     TOK_POSITION = 315, 
     218     TOK_IOSTAT = 316, 
     219     TOK_IOMSG = 317, 
     220     TOK_EXIST = 318, 
     221     TOK_MIN = 319, 
     222     TOK_FLOAT = 320, 
     223     TOK_EXP = 321, 
     224     TOK_LEN = 322, 
     225     TOK_COS = 323, 
     226     TOK_COSH = 324, 
     227     TOK_ACOS = 325, 
     228     TOK_NINT = 326, 
     229     TOK_CYCLE = 327, 
     230     TOK_SIN = 328, 
     231     TOK_SINH = 329, 
     232     TOK_ASIN = 330, 
     233     TOK_EQUIVALENCE = 331, 
     234     TOK_BACKSPACE = 332, 
     235     TOK_LOG = 333, 
     236     TOK_TAN = 334, 
     237     TOK_ATAN = 335, 
     238     TOK_RECURSIVE = 336, 
     239     TOK_ABS = 337, 
     240     TOK_MOD = 338, 
     241     TOK_SIGN = 339, 
     242     TOK_MINLOC = 340, 
     243     TOK_MAXLOC = 341, 
     244     TOK_EXIT = 342, 
     245     TOK_KIND = 343, 
     246     TOK_MOLD = 344, 
     247     TOK_SOURCE = 345, 
     248     TOK_ERRMSG = 346, 
     249     TOK_MINVAL = 347, 
     250     TOK_PUBLIC = 348, 
     251     TOK_PRIVATE = 349, 
     252     TOK_ALLOCATABLE = 350, 
     253     TOK_RETURN = 351, 
     254     TOK_THEN = 352, 
     255     TOK_ELSEIF = 353, 
     256     TOK_ELSE = 354, 
     257     TOK_ENDIF = 355, 
     258     TOK_PRINT = 356, 
     259     TOK_PLAINGOTO = 357, 
     260     TOK_LOGICALIF = 358, 
     261     TOK_LOGICALIF_PAR = 359, 
     262     TOK_PLAINDO = 360, 
     263     TOK_CONTAINS = 361, 
     264     TOK_ENDDO = 362, 
     265     TOK_MODULE = 363, 
     266     TOK_ENDMODULE = 364, 
     267     TOK_WHILE = 365, 
     268     TOK_CONCURRENT = 366, 
     269     TOK_ALLOCATE = 367, 
     270     TOK_OPEN = 368, 
     271     TOK_CLOSE = 369, 
     272     TOK_INQUIRE = 370, 
     273     TOK_WRITE_PAR = 371, 
     274     TOK_WRITE = 372, 
     275     TOK_FLUSH = 373, 
     276     TOK_READ_PAR = 374, 
     277     TOK_READ = 375, 
     278     TOK_REWIND = 376, 
     279     TOK_DEALLOCATE = 377, 
     280     TOK_NULLIFY = 378, 
     281     TOK_DIMENSION = 379, 
     282     TOK_ENDSELECT = 380, 
     283     TOK_EXTERNAL = 381, 
     284     TOK_INTENT = 382, 
     285     TOK_INTRINSIC = 383, 
     286     TOK_NAMELIST = 384, 
     287     TOK_DEFAULT = 385, 
     288     TOK_OPTIONAL = 386, 
     289     TOK_POINTER = 387, 
     290     TOK_CONTINUE = 388, 
     291     TOK_SAVE = 389, 
     292     TOK_TARGET = 390, 
     293     TOK_IMPLICIT = 391, 
     294     TOK_NONE = 392, 
     295     TOK_CALL = 393, 
     296     TOK_STAT = 394, 
     297     TOK_POINT_TO = 395, 
     298     TOK_COMMON = 396, 
     299     TOK_GLOBAL = 397, 
     300     TOK_LEFTAB = 398, 
     301     TOK_RIGHTAB = 399, 
     302     TOK_PAUSE = 400, 
     303     TOK_PROCEDURE = 401, 
     304     TOK_STOP = 402, 
     305     TOK_FOURDOTS = 403, 
     306     TOK_HEXA = 404, 
     307     TOK_ASSIGNTYPE = 405, 
     308     TOK_OUT = 406, 
     309     TOK_INOUT = 407, 
     310     TOK_IN = 408, 
     311     TOK_USE = 409, 
     312     TOK_EQUALEQUAL = 410, 
     313     TOK_SLASHEQUAL = 411, 
     314     TOK_INFEQUAL = 412, 
     315     TOK_SUPEQUAL = 413, 
     316     TOK_TRUE = 414, 
     317     TOK_FALSE = 415, 
     318     TOK_LABEL = 416, 
     319     TOK_LABEL_DJVIEW = 417, 
     320     TOK_PLAINDO_LABEL_DJVIEW = 418, 
     321     TOK_PLAINDO_LABEL = 419, 
     322     TOK_TYPE = 420, 
     323     TOK_TYPEPAR = 421, 
     324     TOK_ENDTYPE = 422, 
     325     TOK_COMMACOMPLEX = 423, 
     326     TOK_REAL = 424, 
     327     TOK_INTEGER = 425, 
     328     TOK_LOGICAL = 426, 
     329     TOK_DOUBLEPRECISION = 427, 
     330     TOK_ENDSUBROUTINE = 428, 
     331     TOK_ENDFUNCTION = 429, 
     332     TOK_ENDPROGRAM = 430, 
     333     TOK_ENDUNIT = 431, 
     334     TOK_CHARACTER = 432, 
     335     TOK_CHAR_CONSTANT = 433, 
     336     TOK_CHAR_CUT = 434, 
     337     TOK_DATA = 435, 
     338     TOK_CHAR_MESSAGE = 436, 
     339     TOK_CSTREAL = 437, 
     340     TOK_COMPLEX = 438, 
     341     TOK_DOUBLECOMPLEX = 439, 
     342     TOK_NAME = 440, 
     343     TOK_CSTINT = 441 
    288344   }; 
    289345#endif 
     
    294350{ 
    295351/* Line 387 of yacc.c  */ 
    296 #line 65 "fortran.y" 
     352#line 89 "fortran.y" 
    297353 
    298354    char        na[LONG_M]; 
     
    306362 
    307363/* Line 387 of yacc.c  */ 
    308 #line 310 "fortran.tab.c" 
     364#line 365 "fortran.tab.c" 
    309365} YYSTYPE; 
    310366# define YYSTYPE_IS_TRIVIAL 1 
     
    334390 
    335391/* Line 390 of yacc.c  */ 
    336 #line 338 "fortran.tab.c" 
     392#line 393 "fortran.tab.c" 
    337393 
    338394#ifdef short 
     
    554610#define YYFINAL  2 
    555611/* YYLAST -- Last index in YYTABLE.  */ 
    556 #define YYLAST   6268 
     612#define YYLAST   4537 
    557613 
    558614/* YYNTOKENS -- Number of terminals.  */ 
    559 #define YYNTOKENS  169 
     615#define YYNTOKENS  203 
    560616/* YYNNTS -- Number of nonterminals.  */ 
    561 #define YYNNTS  206 
     617#define YYNNTS  518 
    562618/* YYNRULES -- Number of rules.  */ 
    563 #define YYNRULES  597 
     619#define YYNRULES  1063 
    564620/* YYNRULES -- Number of states.  */ 
    565 #define YYNSTATES  1051 
     621#define YYNSTATES  1719 
    566622 
    567623/* YYTRANSLATE(YYLEX) -- Bison symbol number corresponding to YYLEX.  */ 
    568624#define YYUNDEFTOK  2 
    569 #define YYMAXUTOK   410 
     625#define YYMAXUTOK   441 
    570626 
    571627#define YYTRANSLATE(YYX)                  \ 
     
    576632{ 
    577633       0,     2,     2,     2,     2,     2,     2,     2,     2,     2, 
    578      166,     2,     2,     2,     2,     2,     2,     2,     2,     2, 
     634     197,     2,     2,     2,     2,     2,     2,     2,     2,     2, 
    579635       2,     2,     2,     2,     2,     2,     2,     2,     2,     2, 
    580        2,     2,     2,     2,     2,     2,     2,   168,     2,     2, 
    581      162,   163,    21,    19,     3,    20,     2,   167,     2,     2, 
     636       2,     2,     2,     2,     2,     2,     2,   199,     2,     2, 
     637     193,   194,    21,    19,     3,    20,     2,   198,     2,     2, 
    582638       2,     2,     2,     2,     2,     2,     2,     2,     4,     2, 
    583      164,     5,   165,     2,     2,     2,     2,     2,     2,     2, 
     639     195,     5,   196,     2,     2,     2,     2,     2,     2,     2, 
    584640       2,     2,     2,     2,     2,     2,     2,     2,     2,     2, 
    585641       2,     2,     2,     2,     2,     2,     2,     2,     2,     2, 
    586        2,     2,     2,     2,     2,     2,     2,     2,     2,     2, 
     642       2,   201,     2,   202,     2,   200,     2,     2,     2,     2, 
    587643       2,     2,     2,     2,     2,     2,     2,     2,     2,     2, 
    588644       2,     2,     2,     2,     2,     2,     2,     2,     2,     2, 
     
    616672     141,   142,   143,   144,   145,   146,   147,   148,   149,   150, 
    617673     151,   152,   153,   154,   155,   156,   157,   158,   159,   160, 
    618      161 
     674     161,   162,   163,   164,   165,   166,   167,   168,   169,   170, 
     675     171,   172,   173,   174,   175,   176,   177,   178,   179,   180, 
     676     181,   182,   183,   184,   185,   186,   187,   188,   189,   190, 
     677     191,   192 
    619678}; 
    620679 
     
    624683static const yytype_uint16 yyprhs[] = 
    625684{ 
    626        0,     0,     3,     4,     7,     9,    11,    14,    16,    19, 
    627       21,    25,    28,    31,    33,    37,    41,    44,    47,    51, 
    628       53,    54,    55,    57,    58,    61,    66,    69,    75,    78, 
    629       80,    83,    85,    87,    88,    91,    95,    96,    99,   103, 
    630      105,   109,   111,   113,   116,   121,   124,   127,   132,   135, 
    631      137,   139,   141,   143,   145,   147,   149,   151,   153,   158, 
    632      162,   166,   169,   172,   173,   175,   177,   179,   181,   183, 
    633      185,   187,   189,   191,   193,   195,   197,   199,   201,   203, 
    634      205,   207,   209,   211,   213,   215,   217,   219,   221,   223, 
    635      225,   229,   233,   239,   241,   245,   249,   252,   257,   259, 
    636      263,   264,   266,   269,   273,   275,   277,   280,   282,   286, 
    637      291,   296,   305,   307,   311,   314,   318,   324,   328,   330, 
    638      331,   334,   336,   341,   345,   348,   352,   356,   360,   364, 
    639      365,   367,   370,   374,   380,   384,   386,   392,   398,   401, 
    640      405,   408,   412,   414,   416,   420,   424,   427,   431,   437, 
    641      439,   442,   444,   448,   451,   453,   457,   458,   460,   462, 
    642      466,   470,   473,   475,   479,   482,   485,   491,   498,   499, 
    643      502,   505,   509,   513,   514,   517,   522,   526,   530,   535, 
    644      538,   540,   542,   544,   546,   548,   550,   552,   553,   556, 
    645      558,   562,   563,   566,   570,   572,   576,   579,   583,   585, 
    646      587,   589,   591,   593,   594,   598,   599,   601,   605,   607, 
    647      611,   613,   615,   617,   620,   622,   627,   629,   631,   633, 
    648      635,   637,   639,   641,   643,   645,   647,   648,   652,   654, 
    649      658,   660,   662,   665,   668,   672,   674,   676,   678,   680, 
    650      682,   686,   690,   694,   699,   704,   708,   713,   718,   722, 
    651      727,   732,   737,   742,   747,   752,   757,   762,   767,   772, 
    652      777,   782,   787,   791,   796,   800,   805,   810,   812,   816, 
    653      818,   820,   822,   825,   828,   831,   833,   835,   838,   841, 
    654      844,   847,   850,   853,   856,   859,   862,   866,   870,   873, 
    655      876,   879,   882,   885,   888,   891,   894,   897,   900,   901, 
    656      903,   906,   909,   912,   914,   916,   918,   920,   921,   923, 
    657      926,   931,   937,   942,   947,   951,   953,   956,   958,   962, 
    658      964,   966,   970,   976,   981,   985,   988,   991,   993,   995, 
    659      997,   999,  1001,  1003,  1005,  1007,  1010,  1013,  1015,  1018, 
    660     1020,  1022,  1023,  1025,  1031,  1032,  1034,  1036,  1038,  1039, 
    661     1042,  1045,  1051,  1054,  1059,  1066,  1073,  1075,  1077,  1081, 
    662     1085,  1087,  1091,  1095,  1097,  1099,  1101,  1103,  1105,  1107, 
    663     1109,  1111,  1113,  1116,  1118,  1120,  1123,  1126,  1129,  1133, 
    664     1136,  1142,  1148,  1151,  1154,  1157,  1160,  1162,  1167,  1169, 
    665     1172,  1175,  1178,  1181,  1183,  1185,  1187,  1189,  1195,  1202, 
    666     1203,  1207,  1208,  1213,  1214,  1219,  1224,  1226,  1228,  1230, 
    667     1232,  1234,  1238,  1243,  1245,  1248,  1250,  1253,  1254,  1255, 
    668     1258,  1262,  1264,  1269,  1271,  1273,  1278,  1281,  1287,  1291, 
    669     1295,  1297,  1302,  1305,  1312,  1321,  1327,  1331,  1333,  1335, 
    670     1337,  1339,  1341,  1344,  1351,  1352,  1354,  1357,  1361,  1362, 
    671     1364,  1367,  1371,  1379,  1385,  1391,  1398,  1400,  1403,  1405, 
    672     1408,  1414,  1419,  1420,  1422,  1425,  1429,  1436,  1441,  1444, 
    673     1448,  1450,  1453,  1457,  1459,  1461,  1465,  1467,  1470,  1473, 
    674     1477,  1479,  1481,  1483,  1485,  1487,  1489,  1491,  1493,  1495, 
    675     1496,  1501,  1509,  1511,  1515,  1518,  1521,  1524,  1525,  1529, 
    676     1530,  1532,  1535,  1538,  1540,  1542,  1546,  1548,  1551,  1553, 
    677     1555,  1556,  1558,  1561,  1564,  1565,  1568,  1572,  1576,  1580, 
    678     1582,  1586,  1588,  1590,  1594,  1596,  1598,  1600,  1604,  1610, 
    679     1615,  1618,  1621,  1622,  1624,  1626,  1628,  1630,  1632,  1634, 
    680     1636,  1638,  1640,  1644,  1646,  1648,  1652,  1656,  1660,  1664, 
    681     1667,  1671,  1674,  1677,  1680,  1683,  1686,  1689,  1692,  1696, 
    682     1698,  1700,  1702,  1704,  1708,  1711,  1716,  1719,  1722,  1728, 
    683     1729,  1731,  1734,  1736,  1738,  1740,  1742,  1746,  1750,  1754, 
    684     1758,  1762,  1766,  1772,  1778,  1784,  1790,  1798,  1807,  1810, 
    685     1812,  1816,  1818,  1820,  1824,  1825,  1830,  1832 
     685       0,     0,     3,     4,     7,     9,    11,    13,    16,    18, 
     686      20,    24,    27,    29,    33,    37,    39,    43,    45,    46, 
     687      48,    50,    52,    54,    56,    58,    59,    61,    63,    65, 
     688      68,    71,    74,    76,    78,    81,    84,    87,    90,    93, 
     689      96,    99,   102,   105,   109,   113,   116,   119,   122,   125, 
     690     128,   131,   134,   137,   140,   143,   144,   146,   149,   152, 
     691     155,   157,   159,   161,   163,   164,   166,   169,   170,   176, 
     692     177,   184,   186,   187,   193,   198,   200,   203,   205,   209, 
     693     211,   213,   217,   223,   228,   232,   235,   238,   240,   242, 
     694     244,   246,   248,   250,   252,   254,   257,   260,   262,   265, 
     695     267,   269,   270,   272,   273,   275,   278,   279,   281,   282, 
     696     284,   286,   289,   291,   293,   295,   297,   299,   301,   303, 
     697     305,   307,   309,   311,   313,   314,   316,   319,   320,   322, 
     698     324,   327,   329,   331,   332,   334,   338,   339,   341,   343, 
     699     346,   348,   350,   352,   354,   356,   358,   360,   362,   364, 
     700     366,   368,   370,   372,   374,   376,   378,   380,   382,   384, 
     701     386,   388,   390,   392,   394,   396,   398,   401,   406,   409, 
     702     411,   413,   415,   417,   419,   421,   423,   425,   427,   429, 
     703     431,   433,   435,   437,   439,   441,   443,   445,   447,   449, 
     704     451,   453,   454,   456,   458,   460,   461,   463,   465,   467, 
     705     469,   471,   472,   475,   479,   483,   484,   488,   489,   493, 
     706     494,   498,   499,   503,   504,   508,   509,   513,   514,   516, 
     707     520,   526,   529,   531,   534,   536,   540,   542,   544,   546, 
     708     549,   551,   555,   561,   563,   565,   567,   569,   571,   573, 
     709     574,   577,   578,   580,   582,   592,   598,   604,   614,   618, 
     710     624,   627,   631,   635,   637,   639,   641,   643,   645,   647, 
     711     648,   653,   658,   666,   667,   670,   671,   674,   676,   680, 
     712     682,   684,   688,   690,   693,   697,   698,   700,   702,   705, 
     713     707,   712,   713,   715,   719,   721,   725,   727,   729,   734, 
     714     736,   738,   742,   747,   748,   752,   754,   756,   757,   759, 
     715     762,   765,   768,   770,   772,   777,   779,   783,   785,   789, 
     716     793,   798,   800,   804,   806,   810,   812,   814,   816,   820, 
     717     824,   826,   828,   830,   832,   836,   838,   840,   846,   852, 
     718     860,   862,   863,   864,   871,   872,   875,   876,   878,   881, 
     719     885,   887,   889,   890,   896,   898,   899,   905,   907,   909, 
     720     911,   913,   915,   917,   919,   923,   928,   930,   932,   933, 
     721     935,   938,   941,   944,   946,   948,   950,   951,   952,   957, 
     722     959,   961,   963,   965,   967,   969,   973,   977,   979,   981, 
     723     983,   985,   989,   991,   994,   996,  1000,  1002,  1006,  1007, 
     724    1010,  1011,  1014,  1016,  1020,  1023,  1025,  1027,  1029,  1030, 
     725    1035,  1036,  1039,  1041,  1045,  1047,  1049,  1050,  1056,  1057, 
     726    1059,  1062,  1066,  1071,  1073,  1077,  1079,  1083,  1085,  1087, 
     727    1097,  1109,  1111,  1115,  1117,  1119,  1121,  1123,  1126,  1129, 
     728    1132,  1134,  1136,  1138,  1140,  1142,  1143,  1146,  1148,  1150, 
     729    1152,  1154,  1156,  1158,  1160,  1162,  1164,  1165,  1166,  1173, 
     730    1174,  1180,  1181,  1189,  1190,  1191,  1199,  1201,  1205,  1209, 
     731    1210,  1211,  1218,  1219,  1221,  1222,  1224,  1226,  1230,  1232, 
     732    1234,  1236,  1238,  1239,  1244,  1245,  1251,  1253,  1257,  1262, 
     733    1264,  1268,  1270,  1274,  1282,  1283,  1290,  1292,  1296,  1298, 
     734    1302,  1304,  1308,  1309,  1316,  1318,  1322,  1324,  1326,  1328, 
     735    1329,  1330,  1338,  1339,  1341,  1343,  1347,  1348,  1350,  1351, 
     736    1356,  1358,  1362,  1364,  1365,  1371,  1373,  1375,  1377,  1379, 
     737    1381,  1383,  1385,  1387,  1389,  1391,  1393,  1395,  1397,  1399, 
     738    1401,  1406,  1411,  1415,  1418,  1419,  1423,  1425,  1426,  1432, 
     739    1434,  1436,  1438,  1440,  1445,  1446,  1448,  1452,  1455,  1457, 
     740    1460,  1464,  1469,  1472,  1474,  1478,  1483,  1486,  1488,  1491, 
     741    1495,  1500,  1503,  1504,  1506,  1507,  1508,  1517,  1518,  1521, 
     742    1523,  1527,  1530,  1534,  1536,  1538,  1540,  1544,  1547,  1549, 
     743    1551,  1552,  1556,  1558,  1562,  1565,  1566,  1569,  1571,  1573, 
     744    1574,  1575,  1584,  1586,  1590,  1591,  1594,  1596,  1600,  1603, 
     745    1607,  1609,  1611,  1613,  1615,  1619,  1621,  1623,  1627,  1629, 
     746    1633,  1635,  1638,  1642,  1644,  1647,  1649,  1651,  1653,  1655, 
     747    1657,  1659,  1663,  1665,  1667,  1671,  1673,  1675,  1677,  1679, 
     748    1681,  1683,  1685,  1687,  1689,  1691,  1693,  1695,  1697,  1700, 
     749    1702,  1706,  1708,  1712,  1714,  1718,  1720,  1722,  1724,  1726, 
     750    1728,  1730,  1732,  1734,  1736,  1737,  1739,  1741,  1743,  1745, 
     751    1747,  1749,  1751,  1753,  1758,  1764,  1770,  1778,  1783,  1784, 
     752    1788,  1790,  1794,  1796,  1800,  1803,  1807,  1809,  1811,  1815, 
     753    1817,  1819,  1821,  1827,  1833,  1834,  1837,  1838,  1842,  1843, 
     754    1847,  1853,  1855,  1857,  1859,  1861,  1863,  1868,  1874,  1877, 
     755    1881,  1884,  1888,  1889,  1891,  1892,  1895,  1897,  1899,  1901, 
     756    1905,  1909,  1914,  1917,  1923,  1927,  1932,  1935,  1941,  1945, 
     757    1950,  1953,  1959,  1963,  1970,  1979,  1985,  1989,  1991,  1993, 
     758    1995,  1998,  2002,  2007,  2009,  2011,  2015,  2018,  2020,  2022, 
     759    2024,  2026,  2028,  2030,  2032,  2035,  2040,  2042,  2044,  2046, 
     760    2048,  2050,  2052,  2054,  2056,  2061,  2065,  2068,  2072,  2076, 
     761    2079,  2080,  2082,  2086,  2092,  2093,  2095,  2098,  2101,  2102, 
     762    2104,  2107,  2110,  2119,  2126,  2133,  2141,  2144,  2148,  2151, 
     763    2155,  2161,  2165,  2166,  2168,  2171,  2174,  2175,  2184,  2185, 
     764    2192,  2196,  2201,  2202,  2206,  2207,  2212,  2213,  2218,  2220, 
     765    2222,  2226,  2228,  2231,  2234,  2238,  2240,  2243,  2247,  2251, 
     766    2262,  2266,  2269,  2273,  2275,  2277,  2279,  2281,  2283,  2285, 
     767    2287,  2288,  2289,  2297,  2299,  2303,  2305,  2308,  2311,  2314, 
     768    2317,  2320,  2323,  2326,  2329,  2332,  2336,  2338,  2340,  2341, 
     769    2348,  2350,  2354,  2356,  2359,  2362,  2365,  2369,  2375,  2382, 
     770    2387,  2394,  2400,  2407,  2412,  2419,  2421,  2425,  2427,  2429, 
     771    2432,  2434,  2436,  2439,  2442,  2445,  2448,  2451,  2454,  2457, 
     772    2459,  2461,  2463,  2465,  2469,  2471,  2473,  2475,  2479,  2481, 
     773    2483,  2489,  2491,  2495,  2497,  2499,  2505,  2513,  2517,  2523, 
     774    2525,  2529,  2531,  2534,  2537,  2540,  2543,  2547,  2553,  2555, 
     775    2559,  2561,  2564,  2567,  2570,  2573,  2574,  2582,  2583,  2593, 
     776    2594,  2596,  2600,  2602,  2605,  2608,  2611,  2614,  2617,  2620, 
     777    2623,  2627,  2630,  2633,  2636,  2637,  2643,  2644,  2646,  2647, 
     778    2652,  2653,  2660,  2661,  2663,  2664,  2666,  2669,  2670,  2672, 
     779    2674,  2677,  2679,  2681,  2683,  2686,  2687,  2688,  2697,  2698, 
     780    2710,  2711,  2713,  2717,  2718,  2720,  2726,  2727,  2729,  2730, 
     781    2732,  2733,  2738,  2739,  2740,  2747,  2748,  2750,  2751,  2753, 
     782    2755,  2756,  2759,  2761,  2765,  2769,  2771,  2775,  2777,  2779, 
     783    2781,  2783,  2785,  2789,  2794,  2796,  2800,  2802,  2807,  2809, 
     784    2813,  2815,  2819,  2820,  2826,  2827,  2831,  2832,  2838,  2839, 
     785    2840,  2848,  2849,  2854,  2856,  2858,  2860,  2862,  2866,  2868, 
     786    2872,  2874,  2876,  2878,  2879,  2881,  2883,  2886,  2888,  2890, 
     787    2892,  2898,  2899,  2900,  2911,  2913,  2915,  2916,  2918,  2923, 
     788    2924,  2932,  2933,  2935,  2941,  2942,  2949,  2951,  2958,  2959, 
     789    2960,  2962,  2963,  2964,  2969,  2970,  2972,  2974,  2978,  2980, 
     790    2982,  2986,  2991,  2992,  2997,  2999,  3001,  3005,  3009,  3011, 
     791    3015,  3017,  3018,  3020 
    686792}; 
    687793 
     
    689795static const yytype_int16 yyrhs[] = 
    690796{ 
    691      170,     0,    -1,    -1,   170,   171,    -1,   172,    -1,   173, 
    692       -1,   140,   173,    -1,     1,    -1,   166,   175,    -1,    24, 
    693       -1,   172,   166,   175,    -1,   172,    24,    -1,   172,   140, 
    694       -1,   174,    -1,   173,    24,   166,    -1,   173,    24,   174, 
    695       -1,   178,   175,    -1,   186,   175,    -1,    28,   181,   175, 
    696       -1,   282,    -1,    -1,    -1,    70,    -1,    -1,    26,   183, 
    697       -1,   176,    29,   180,   182,    -1,    30,   180,    -1,   176, 
    698       31,   180,   182,   177,    -1,    92,   160,    -1,   161,    -1, 
    699      179,   161,    -1,   160,    -1,   153,    -1,    -1,   162,   163, 
    700       -1,   162,   184,   163,    -1,    -1,   162,   163,    -1,   162, 
    701      184,   163,    -1,   185,    -1,   184,     3,   185,    -1,   160, 
    702       -1,    21,    -1,   228,   196,    -1,   141,   187,   195,   336, 
    703       -1,   143,   336,    -1,   114,   190,    -1,   198,   162,   221, 
    704      163,    -1,   198,   221,    -1,   215,    -1,   203,    -1,   225, 
    705       -1,   211,    -1,   213,    -1,   212,    -1,   276,    -1,   223, 
    706       -1,   209,    -1,    66,   162,   249,   163,    -1,   108,   195, 
    707      214,    -1,   110,   195,   189,    -1,    65,   191,    -1,   199, 
    708      166,    -1,    -1,   244,    -1,    42,    -1,    34,    -1,    39, 
    709       -1,    54,    -1,    77,    -1,    40,    -1,    43,    -1,    60, 
    710       -1,    55,    -1,    56,    -1,    57,    -1,    58,    -1,    59, 
    711       -1,    62,    -1,    63,    -1,    64,    -1,    67,    -1,    68, 
    712       -1,    69,    -1,    72,    -1,    73,    -1,    74,    -1,    75, 
    713       -1,   160,    -1,   188,    -1,   189,     3,   188,    -1,   162, 
    714      194,   163,    -1,   190,     3,   162,   194,   163,    -1,   192, 
    715       -1,   191,     3,   192,    -1,   162,   193,   163,    -1,   267, 
    716      245,    -1,   193,     3,   267,   245,    -1,   249,    -1,   194, 
    717        3,   249,    -1,    -1,   131,    -1,   226,   227,    -1,   197, 
    718      180,   182,    -1,    31,    -1,    25,    -1,   155,   200,    -1, 
    719      201,    -1,   200,   220,   201,    -1,   160,    22,   202,    22, 
    720       -1,   206,    22,   202,    22,    -1,   162,   257,     3,   368, 
    721      163,    22,   202,    22,    -1,   207,    -1,   207,     3,   202, 
    722       -1,   204,   205,    -1,   204,   219,   205,    -1,   203,   220, 
    723      219,   220,   205,    -1,   203,     3,   205,    -1,   116,    -1, 
    724       -1,   160,   245,    -1,   160,    -1,   160,   162,   249,   163, 
    725       -1,   206,     3,   206,    -1,   208,   268,    -1,   207,    19, 
    726      207,    -1,   207,    20,   207,    -1,   207,    21,   207,    -1, 
    727      207,   167,   207,    -1,    -1,   253,    -1,   111,   267,    -1, 
    728      111,   219,   267,    -1,   209,   220,   219,   220,   267,    -1, 
    729      209,     3,   267,    -1,   106,    -1,   210,   220,   160,   245, 
    730      233,    -1,   211,     3,   160,   245,   233,    -1,    79,   166, 
    731       -1,    79,   195,   214,    -1,    78,   166,    -1,    78,   195, 
    732      214,    -1,   160,    -1,   133,    -1,   214,     3,   160,    -1, 
    733      214,     3,   133,    -1,   216,   217,    -1,   216,   219,   217, 
    734       -1,   215,   220,   219,   220,   217,    -1,   123,    -1,   124, 
    735      123,    -1,   218,    -1,   217,     3,   218,    -1,   160,   245, 
    736       -1,    18,    -1,    22,   160,    22,    -1,    -1,     3,    -1, 
    737      222,    -1,   221,     3,   222,    -1,   160,     5,   249,    -1, 
    738      128,   224,    -1,   160,    -1,   224,     3,   160,    -1,   118, 
    739      119,    -1,   118,   130,    -1,   240,   160,   245,   233,   274, 
    740       -1,   226,     3,   160,   245,   233,   274,    -1,    -1,   232, 
    741      235,    -1,   231,   229,    -1,   232,    21,   161,    -1,   142, 
    742      237,   163,    -1,    -1,    21,   161,    -1,    21,   162,   230, 
    743      163,    -1,   162,   230,   163,    -1,   160,   238,   239,    -1, 
    744      160,     5,   238,   239,    -1,   238,   239,    -1,   152,    -1, 
    745      145,    -1,   146,    -1,   144,    -1,   158,    -1,   159,    -1, 
    746      147,    -1,    -1,    21,   234,    -1,   249,    -1,   162,    21, 
    747      163,    -1,    -1,    21,   236,    -1,   162,   237,   163,    -1, 
    748      249,    -1,   162,    21,   163,    -1,   160,   238,    -1,   160, 
    749        5,   238,    -1,   160,    -1,   161,    -1,   133,    -1,   249, 
    750       -1,    21,    -1,    -1,     3,   160,   238,    -1,    -1,   131, 
    751       -1,     3,   241,   131,    -1,   242,    -1,   241,     3,   242, 
    752       -1,    25,    -1,   244,    -1,    80,    -1,   106,   245,    -1, 
    753      108,    -1,   109,   162,   243,   163,    -1,   110,    -1,   113, 
    754       -1,   114,    -1,   116,    -1,   117,    -1,   136,    -1,   134, 
    755       -1,   135,    -1,    78,    -1,    79,    -1,    -1,   162,   246, 
    756      163,    -1,   247,    -1,   246,     3,   247,    -1,   248,    -1, 
    757        4,    -1,   249,     4,    -1,     4,   249,    -1,   249,     4, 
    758      248,    -1,    21,    -1,   249,    -1,   252,    -1,   275,    -1, 
    759      250,    -1,   162,   249,   163,    -1,    42,   251,   163,    -1, 
    760       33,   251,   163,    -1,    34,   162,   251,   163,    -1,    39, 
    761      162,   251,   163,    -1,    54,   251,   163,    -1,    77,   162, 
    762      251,   163,    -1,    40,   162,   249,   163,    -1,    43,   249, 
    763      163,    -1,   144,   162,   251,   163,    -1,    60,   162,   249, 
    764      163,    -1,    55,   162,   249,   163,    -1,    56,   162,   249, 
    765      163,    -1,    57,   162,   249,   163,    -1,    58,   162,   249, 
    766      163,    -1,    59,   162,   249,   163,    -1,    62,   162,   249, 
    767      163,    -1,    63,   162,   249,   163,    -1,    64,   162,   249, 
    768      163,    -1,    67,   162,   249,   163,    -1,    68,   162,   249, 
    769      163,    -1,    69,   162,   249,   163,    -1,    71,   249,   163, 
    770       -1,    72,   162,   251,   163,    -1,    73,   251,   163,    -1, 
    771       74,   162,   251,   163,    -1,    75,   162,   251,   163,    -1, 
    772      249,    -1,   251,     3,   249,    -1,   257,    -1,   268,    -1, 
    773      262,    -1,   249,   254,    -1,   253,   249,    -1,    11,   249, 
    774       -1,    19,    -1,    20,    -1,    19,   249,    -1,    20,   249, 
    775       -1,    21,   249,    -1,    23,   249,    -1,    13,   249,    -1, 
    776        7,   249,    -1,    16,   249,    -1,   165,   249,    -1,   164, 
    777      249,    -1,   165,     5,   249,    -1,   164,     5,   249,    -1, 
    778       17,   249,    -1,    14,   249,    -1,    15,   249,    -1,    12, 
    779      249,    -1,     6,   249,    -1,     8,   249,    -1,     9,   249, 
    780       -1,    10,   249,    -1,    22,   255,    -1,     5,   256,    -1, 
    781       -1,   249,    -1,     5,   249,    -1,    22,   249,    -1,     5, 
    782      249,    -1,   249,    -1,   267,    -1,   261,    -1,   259,    -1, 
    783       -1,   260,    -1,   260,   271,    -1,   261,   162,   263,   163, 
    784       -1,   261,   162,   263,   163,   271,    -1,   267,   162,   263, 
    785      163,    -1,   257,   168,   356,   257,    -1,   125,   366,   126, 
    786       -1,   258,    -1,   258,   264,    -1,   265,    -1,   264,     3, 
    787      265,    -1,   249,    -1,   266,    -1,   249,     4,   249,    -1, 
    788      249,     4,   249,     4,   249,    -1,     4,   249,     4,   249, 
    789       -1,     4,     4,   249,    -1,     4,   249,    -1,   249,     4, 
    790       -1,     4,    -1,   160,    -1,   138,    -1,   139,    -1,    41, 
    791       -1,   161,    -1,   157,    -1,   132,    -1,   268,   160,    -1, 
    792      269,   270,    -1,   153,    -1,   269,   153,    -1,   156,    -1, 
    793      154,    -1,    -1,   271,    -1,   162,   272,     4,   272,   163, 
    794       -1,    -1,   249,    -1,   166,    -1,   249,    -1,    -1,     5, 
    795      249,    -1,   122,   249,    -1,   162,   252,     3,   252,   163, 
    796       -1,   277,   160,    -1,   277,   160,     3,   278,    -1,   277, 
    797      160,     3,    27,     4,   166,    -1,   277,   160,     3,    27, 
    798        4,   280,    -1,   137,    -1,   279,    -1,   278,     3,   279, 
    799       -1,   160,   122,   160,    -1,   281,    -1,   280,     3,   281, 
    800       -1,   160,   122,   160,    -1,   160,    -1,   283,    -1,   331, 
    801       -1,   284,    -1,   300,    -1,   320,    -1,   310,    -1,   287, 
    802       -1,   115,    -1,   338,   340,    -1,   369,    -1,   341,    -1, 
    803      357,   352,    -1,   359,   350,    -1,   100,   352,    -1,   100, 
    804      352,   366,    -1,   103,   353,    -1,    96,   162,   370,   373, 
    805      163,    -1,   104,   162,   372,   373,   163,    -1,    76,   272, 
    806       -1,    81,   273,    -1,    61,   273,    -1,   348,   273,    -1, 
    807      339,    -1,   105,   162,   374,   163,    -1,   333,    -1,   334, 
    808      336,    -1,   332,   336,    -1,   335,   336,    -1,    93,   336, 
    809       -1,   319,    -1,   286,    -1,    90,    -1,   249,    -1,    35, 
    810      162,   294,   163,   293,    -1,   291,   172,   288,   289,   290, 
    811      297,    -1,    -1,   288,   292,   172,    -1,    -1,   289,   295, 
    812      172,   288,    -1,    -1,   290,   296,   172,   288,    -1,    35, 
    813      162,   294,   163,    -1,   293,    -1,   286,    -1,   287,    -1, 
    814      285,    -1,   249,    -1,    36,   294,   163,    -1,    36,   294, 
    815      163,   160,    -1,    37,    -1,    37,   160,    -1,    38,    -1, 
    816       38,   160,    -1,    -1,    -1,   299,   282,    -1,   299,   282, 
    817      172,    -1,   301,    -1,   302,   172,   307,   308,    -1,   303, 
    818       -1,   304,    -1,   160,     4,    89,   179,    -1,    89,   179, 
    819       -1,   160,     4,    89,   179,   305,    -1,    89,   179,   305, 
    820       -1,   160,     4,    89,    -1,    89,    -1,   160,     4,    89, 
    821      305,    -1,    89,   305,    -1,   220,   306,     5,   249,     3, 
    822      249,    -1,   220,   306,     5,   249,     3,   249,     3,   249, 
    823       -1,   220,    94,   162,   249,   163,    -1,   220,    95,   298, 
    824       -1,   267,    -1,   299,    -1,   309,    -1,   330,    -1,    91, 
    825       -1,    91,   160,    -1,   315,   172,   299,   311,   313,   318, 
    826       -1,    -1,   312,    -1,   311,   312,    -1,   316,   172,   299, 
    827       -1,    -1,   314,    -1,   313,   312,    -1,   317,   172,   299, 
    828       -1,   160,     4,    88,   162,   249,   163,    82,    -1,    88, 
    829      162,   249,   163,    82,    -1,    83,   162,   249,   163,    82, 
    830       -1,    83,   162,   249,   163,    82,   160,    -1,    84,    -1, 
    831       84,   160,    -1,    85,    -1,    85,   160,    -1,    88,   162, 
    832      249,   163,   284,    -1,   323,   172,   321,   325,    -1,    -1, 
    833      322,    -1,   321,   322,    -1,   324,   172,   299,    -1,   160, 
    834        4,    45,   162,   249,   163,    -1,    45,   162,   249,   163, 
    835       -1,    44,   326,    -1,    44,   326,   160,    -1,   107,    -1, 
    836      107,   160,    -1,   162,   327,   163,    -1,   112,    -1,   328, 
    837       -1,   327,     3,   328,    -1,   329,    -1,   329,     4,    -1, 
    838        4,   329,    -1,   329,     4,   329,    -1,   249,    -1,   115, 
    839       -1,    32,    -1,   148,    -1,   151,    -1,   150,    -1,   149, 
    840       -1,   166,    -1,   160,    -1,    -1,   267,   337,   245,   245, 
    841       -1,   338,   168,   356,   267,   337,   245,   245,    -1,   161, 
    842       -1,   339,     3,   161,    -1,     5,   249,    -1,   122,   249, 
    843       -1,   344,   342,    -1,    -1,   162,   343,   163,    -1,    -1, 
    844      346,    -1,   345,   101,    -1,   345,   160,    -1,   120,    -1, 
    845      347,    -1,   346,     3,   347,    -1,   249,    -1,    21,   161, 
    846       -1,   127,    -1,   129,    -1,    -1,   363,    -1,   352,   349, 
    847       -1,   358,   351,    -1,    -1,     3,   363,    -1,   162,   354, 
    848      163,    -1,   162,   267,   163,    -1,   162,   161,   163,    -1, 
    849      161,    -1,   162,   252,   163,    -1,   160,    -1,   355,    -1, 
    850      354,     3,   355,    -1,   360,    -1,    21,    -1,    23,    -1, 
    851      267,   249,   245,    -1,   267,   249,   168,   356,   338,    -1, 
    852      267,   162,   266,   163,    -1,   267,    21,    -1,   267,    23, 
    853       -1,    -1,    97,    -1,    98,    -1,   101,    -1,   361,    -1, 
    854       21,    -1,   102,    -1,    99,    -1,    86,    -1,   361,    -1, 
    855      162,   360,   163,    -1,   257,    -1,   268,    -1,   360,   362, 
    856      360,    -1,   360,    21,   360,    -1,   360,    22,   360,    -1, 
    857      360,    23,   360,    -1,   362,   360,    -1,   360,    18,   360, 
    858       -1,    46,   249,    -1,    47,   249,    -1,    49,   249,    -1, 
    859       48,   249,    -1,    53,   249,    -1,    52,   249,    -1,    50, 
    860      249,    -1,   160,     5,   249,    -1,   250,    -1,    19,    -1, 
    861       20,    -1,   364,    -1,   363,     3,   364,    -1,   257,   365, 
    862       -1,   162,   363,   163,   365,    -1,   250,   365,    -1,   268, 
    863      365,    -1,   162,   363,     3,   368,   163,    -1,    -1,   254, 
    864       -1,   365,   254,    -1,   275,    -1,   250,    -1,   252,    -1, 
    865      367,    -1,   252,     3,   249,    -1,   252,     3,   367,    -1, 
    866      367,     3,   249,    -1,   367,     3,   367,    -1,   366,     3, 
    867      249,    -1,   366,     3,   367,    -1,   162,   252,     3,   368, 
    868      163,    -1,   162,   366,     3,   368,   163,    -1,   162,   367, 
    869        3,   368,   163,    -1,   160,     5,   249,     3,   249,    -1, 
    870      160,     5,   249,     3,   249,     3,   249,    -1,    87,   162, 
    871      249,     3,   249,   163,     3,   249,    -1,    87,   161,    -1, 
    872      371,    -1,   370,     3,   371,    -1,   257,    -1,   371,    -1, 
    873      372,     3,   371,    -1,    -1,     3,   121,     5,   257,    -1, 
    874      267,    -1,   374,     3,   267,    -1 
     797     204,     0,    -1,    -1,   204,   205,    -1,   206,    -1,   207, 
     798      -1,     1,    -1,   197,   209,    -1,    24,    -1,    64,    -1, 
     799     206,   197,   209,    -1,   206,    24,    -1,   208,    -1,   207, 
     800      24,   197,    -1,   207,    24,   208,    -1,   210,    -1,    28, 
     801     212,   209,    -1,    37,    -1,    -1,   652,    -1,   211,    -1, 
     802     632,    -1,   691,    -1,   702,    -1,   184,    -1,    -1,     3, 
     803      -1,   219,    -1,   232,    -1,   501,   216,    -1,   215,   501, 
     804      -1,    11,   501,    -1,    19,    -1,    20,    -1,    19,   501, 
     805      -1,    20,   501,    -1,    21,   501,    -1,    23,   501,    -1, 
     806      13,   501,    -1,     7,   501,    -1,    16,   501,    -1,   196, 
     807     501,    -1,   195,   501,    -1,   196,     5,   501,    -1,   195, 
     808       5,   501,    -1,    17,   501,    -1,    14,   501,    -1,    15, 
     809     501,    -1,    12,   501,    -1,     6,   501,    -1,     8,   501, 
     810      -1,     9,   501,    -1,    10,   501,    -1,    22,   217,    -1, 
     811       5,   218,    -1,    -1,   501,    -1,     5,   501,    -1,    22, 
     812     501,    -1,     5,   501,    -1,   501,    -1,   231,    -1,   226, 
     813      -1,   221,    -1,    -1,   224,    -1,   224,   443,    -1,    -1, 
     814     226,   193,   222,   227,   194,    -1,    -1,   226,   193,   223, 
     815     227,   194,   443,    -1,   109,    -1,    -1,   231,   193,   225, 
     816     227,   194,    -1,   219,   199,   719,   219,    -1,   220,    -1, 
     817     220,   228,    -1,   229,    -1,   228,     3,   229,    -1,   501, 
     818      -1,   230,    -1,   501,     4,   501,    -1,   501,     4,   501, 
     819       4,   501,    -1,     4,   501,     4,   501,    -1,     4,     4, 
     820     501,    -1,     4,   501,    -1,   501,     4,    -1,     4,    -1, 
     821     191,    -1,   165,    -1,   166,    -1,    44,    -1,   192,    -1, 
     822     188,    -1,   155,    -1,   232,   191,    -1,   233,   234,    -1, 
     823     184,    -1,   233,   184,    -1,   187,    -1,   185,    -1,    -1, 
     824     443,    -1,    -1,   501,    -1,   237,   238,    -1,    -1,   645, 
     825      -1,    -1,   239,    -1,   240,    -1,   239,   240,    -1,   290, 
     826      -1,   392,    -1,   631,    -1,   406,    -1,   251,    -1,   330, 
     827      -1,   513,    -1,   514,    -1,   539,    -1,   587,    -1,   714, 
     828      -1,   606,    -1,    -1,   242,    -1,   252,   243,    -1,    -1, 
     829     244,    -1,   245,    -1,   244,   245,    -1,   252,    -1,   631, 
     830      -1,    -1,   247,    -1,   112,   206,   248,    -1,    -1,   249, 
     831      -1,   250,    -1,   249,   250,    -1,   691,    -1,   702,    -1, 
     832     364,    -1,   422,    -1,   369,    -1,   386,    -1,   416,    -1, 
     833     669,    -1,   672,    -1,   412,    -1,   397,    -1,   253,    -1, 
     834     539,    -1,   569,    -1,   559,    -1,   525,    -1,   457,    -1, 
     835     513,    -1,   677,    -1,   600,    -1,   587,    -1,   558,    -1, 
     836     474,    -1,   585,    -1,   584,    -1,   622,    -1,    78,   235, 
     837      -1,   129,   193,   720,   194,    -1,   115,   717,    -1,   568, 
     838      -1,   625,    -1,   593,    -1,   514,    -1,   606,    -1,   604, 
     839      -1,   714,    -1,   619,    -1,   588,    -1,   524,    -1,   605, 
     840      -1,   586,    -1,   231,    -1,   256,    -1,   257,    -1,   258, 
     841      -1,   276,    -1,   279,    -1,   289,    -1,   280,    -1,   288, 
     842      -1,   231,    -1,    -1,   260,    -1,   167,    -1,   192,    -1, 
     843      -1,   262,    -1,   168,    -1,   506,    -1,    21,    -1,     4, 
     844      -1,    -1,   265,   266,    -1,   172,   266,   194,    -1,   172, 
     845     314,   194,    -1,    -1,   176,   267,   273,    -1,    -1,   175, 
     846     268,   273,    -1,    -1,   178,   269,   273,    -1,    -1,   189, 
     847     270,   273,    -1,    -1,   183,   271,   284,    -1,    -1,   177, 
     848     272,   273,    -1,    -1,   274,    -1,   193,   511,   194,    -1, 
     849     193,    94,     5,   511,   194,    -1,    21,   192,    -1,   276, 
     850      -1,   488,   276,    -1,   192,    -1,   192,   200,   277,    -1, 
     851     192,    -1,   191,    -1,   279,    -1,   488,   279,    -1,   188, 
     852      -1,   188,   200,   277,    -1,   193,   281,   174,   282,   194, 
     853      -1,   275,    -1,   278,    -1,   231,    -1,   275,    -1,   278, 
     854      -1,   258,    -1,    -1,    21,   287,    -1,    -1,   285,    -1, 
     855     286,    -1,   193,    73,     5,   263,     3,    94,     5,   511, 
     856     194,    -1,   193,   263,     3,   511,   194,    -1,   193,    94, 
     857       5,   511,   194,    -1,   193,    94,     5,   511,     3,    73, 
     858       5,   263,   194,    -1,   193,   263,   194,    -1,   193,    73, 
     859       5,   263,   194,    -1,    21,   287,    -1,    21,   287,     3, 
     860      -1,   193,   263,   194,    -1,   276,    -1,   184,    -1,   187, 
     861      -1,   185,    -1,   165,    -1,   166,    -1,    -1,   292,   291, 
     862     300,   299,    -1,   171,   293,   191,   206,    -1,   171,   294, 
     863     191,   193,   297,   194,   206,    -1,    -1,   294,   154,    -1, 
     864      -1,     3,   295,    -1,   296,    -1,   295,     3,   296,    -1, 
     865     346,    -1,   298,    -1,   297,     3,   298,    -1,   191,    -1, 
     866     173,   206,    -1,   173,   191,   206,    -1,    -1,   301,    -1, 
     867     302,    -1,   301,   302,    -1,   303,    -1,   264,   304,   307, 
     868     206,    -1,    -1,   154,    -1,     3,   305,   154,    -1,   306, 
     869      -1,   305,     3,   306,    -1,   346,    -1,   101,    -1,   130, 
     870     193,   310,   194,    -1,   138,    -1,   308,    -1,   307,     3, 
     871     308,    -1,   231,   309,   283,   311,    -1,    -1,   193,   310, 
     872     194,    -1,   350,    -1,   356,    -1,    -1,   312,    -1,     5, 
     873     508,    -1,   146,   345,    -1,   146,   313,    -1,   432,    -1, 
     874     231,    -1,   231,   193,   315,   194,    -1,   316,    -1,   315, 
     875       3,   316,    -1,   263,    -1,   254,     5,   263,    -1,   314, 
     876     193,   194,    -1,   314,   193,   318,   194,    -1,   319,    -1, 
     877     318,     3,   319,    -1,   320,    -1,   254,     5,   320,    -1, 
     878     501,    -1,   520,    -1,   523,    -1,   149,   322,   150,    -1, 
     879     323,   322,   324,    -1,   325,    -1,   201,    -1,   202,    -1, 
     880     326,    -1,   325,     3,   326,    -1,   501,    -1,   327,    -1, 
     881     193,   325,     3,   328,   194,    -1,   329,     5,   506,     3, 
     882     506,    -1,   329,     5,   506,     3,   506,     3,   506,    -1, 
     883     545,    -1,    -1,    -1,   331,   264,   333,   339,   332,   206, 
     884      -1,    -1,   334,   154,    -1,    -1,   335,    -1,     3,   336, 
     885      -1,   335,     3,   336,    -1,   346,    -1,   101,    -1,    -1, 
     886     130,   193,   337,   349,   194,    -1,   132,    -1,    -1,   133, 
     887     193,   338,   363,   194,    -1,   134,    -1,   137,    -1,    25, 
     888      -1,   138,    -1,   140,    -1,   141,    -1,   340,    -1,   339, 
     889       3,   340,    -1,   342,   347,   283,   343,    -1,   231,    -1, 
     890     191,    -1,    -1,   344,    -1,     5,   508,    -1,   146,   345, 
     891      -1,   146,   313,    -1,   675,    -1,    99,    -1,   100,    -1, 
     892      -1,    -1,   193,   348,   349,   194,    -1,   350,    -1,   354, 
     893      -1,   356,    -1,   358,    -1,   361,    -1,   351,    -1,   350, 
     894       3,   351,    -1,   352,     4,   353,    -1,   353,    -1,   507, 
     895      -1,   507,    -1,   355,    -1,   354,     3,   355,    -1,     4, 
     896      -1,   352,     4,    -1,   357,    -1,   356,     3,   357,    -1, 
     897       4,    -1,   359,   360,    21,    -1,    -1,   350,     3,    -1, 
     898      -1,   352,     4,    -1,   362,    -1,   361,     3,   362,    -1, 
     899     360,    21,    -1,   159,    -1,   157,    -1,   158,    -1,    -1, 
     900     346,   366,   365,   206,    -1,    -1,   400,   367,    -1,   368, 
     901      -1,   367,     3,   368,    -1,   191,    -1,   668,    -1,    -1, 
     902     186,   373,   371,   370,   206,    -1,    -1,   372,    -1,   427, 
     903     373,    -1,   372,   427,   373,    -1,   374,    22,   375,    22, 
     904      -1,   376,    -1,   374,     3,   376,    -1,   381,    -1,   375, 
     905       3,   381,    -1,   434,    -1,   377,    -1,   193,   378,     3, 
     906     380,     5,   511,     3,   511,   194,    -1,   193,   378,     3, 
     907     380,     5,   511,     3,   511,     3,   511,   194,    -1,   379, 
     908      -1,   378,     3,   379,    -1,   451,    -1,   449,    -1,   377, 
     909      -1,   545,    -1,   384,   382,    -1,   276,   382,    -1,   288, 
     910     382,    -1,   275,    -1,   278,    -1,   345,    -1,   313,    -1, 
     911     317,    -1,    -1,    21,   383,    -1,   255,    -1,   384,    -1, 
     912     275,    -1,   278,    -1,   345,    -1,   313,    -1,   317,    -1, 
     913     385,    -1,   432,    -1,    -1,    -1,   387,   130,   400,   389, 
     914     388,   206,    -1,    -1,   191,   193,   390,   349,   194,    -1, 
     915      -1,   389,     3,   191,   193,   391,   349,   194,    -1,    -1, 
     916      -1,    25,   393,   193,   395,   194,   394,   206,    -1,   396, 
     917      -1,   395,     3,   396,    -1,   191,     5,   508,    -1,    -1, 
     918      -1,   398,   140,   400,   401,   399,   206,    -1,    -1,   154, 
     919      -1,    -1,   402,    -1,   403,    -1,   402,     3,   403,    -1, 
     920     341,    -1,   404,    -1,   426,    -1,   231,    -1,    -1,   405, 
     921     142,   408,   206,    -1,    -1,   405,   142,   143,   407,   206, 
     922      -1,   409,    -1,   408,     3,   409,    -1,   264,   193,   410, 
     923     194,    -1,   411,    -1,   410,     3,   411,    -1,   191,    -1, 
     924     191,    20,   191,    -1,   135,    22,   191,    22,   414,   413, 
     925     206,    -1,    -1,   413,   427,    22,   191,    22,   414,    -1, 
     926     415,    -1,   414,     3,   415,    -1,   435,    -1,    82,   417, 
     927     206,    -1,   418,    -1,   417,     3,   418,    -1,    -1,   193, 
     928     419,   421,     3,   420,   194,    -1,   421,    -1,   420,     3, 
     929     421,    -1,   435,    -1,   451,    -1,   443,    -1,    -1,    -1, 
     930     147,   423,   425,   429,   428,   424,   206,    -1,    -1,   426, 
     931      -1,    18,    -1,    22,   191,    22,    -1,    -1,     3,    -1, 
     932      -1,   428,   427,   426,   429,    -1,   430,    -1,   429,     3, 
     933     430,    -1,   191,    -1,    -1,   191,   193,   431,   349,   194, 
     934      -1,   451,    -1,   452,    -1,   450,    -1,   443,    -1,   434, 
     935      -1,   432,    -1,   231,    -1,   437,    -1,   434,    -1,   434, 
     936      -1,   440,    -1,   434,    -1,   442,    -1,   434,    -1,   445, 
     937      -1,   445,   193,   444,   194,    -1,   288,   193,   444,   194, 
     938      -1,   505,     4,   505,    -1,   447,   446,    -1,    -1,   446, 
     939     199,   447,    -1,   231,    -1,    -1,   231,   193,   448,   453, 
     940     194,    -1,   450,    -1,   445,    -1,   445,    -1,   445,    -1, 
     941     445,   193,   444,   194,    -1,    -1,   454,    -1,   453,     3, 
     942     454,    -1,   501,   455,    -1,     4,    -1,     4,   501,    -1, 
     943       4,     4,   501,    -1,     4,   501,     4,   501,    -1,   154, 
     944     501,    -1,   456,    -1,   231,     5,   501,    -1,   231,     5, 
     945      21,   260,    -1,    21,   260,    -1,     4,    -1,     4,   501, 
     946      -1,     4,     4,   501,    -1,     4,   501,     4,   501,    -1, 
     947     154,   501,    -1,    -1,   504,    -1,    -1,    -1,   118,   193, 
     948     458,   465,   460,   194,   459,   206,    -1,    -1,     3,   461, 
     949      -1,   462,    -1,   461,     3,   462,    -1,    97,   464,    -1, 
     950     145,     5,   463,    -1,   441,    -1,   439,    -1,   466,    -1, 
     951     465,     3,   466,    -1,   467,   468,    -1,   435,    -1,   450, 
     952      -1,    -1,   193,   469,   194,    -1,   470,    -1,   469,     3, 
     953     470,    -1,   471,   473,    -1,    -1,   472,     4,    -1,   506, 
     954      -1,   506,    -1,    -1,    -1,   128,   193,   475,   477,   478, 
     955     194,   476,   206,    -1,   467,    -1,   477,     3,   467,    -1, 
     956      -1,     3,   479,    -1,   480,    -1,   479,     3,   480,    -1, 
     957      97,   464,    -1,   145,     5,   463,    -1,   432,    -1,   257, 
     958      -1,   321,    -1,   675,    -1,   193,   501,   194,    -1,   481, 
     959      -1,   482,    -1,   482,   486,   483,    -1,   483,    -1,   484, 
     960     487,   483,    -1,   484,    -1,   488,   484,    -1,   485,   488, 
     961     484,    -1,   275,    -1,   485,   275,    -1,    23,    -1,    21, 
     962      -1,    22,    -1,    19,    -1,    20,    -1,   485,    -1,   489, 
     963     490,   485,    -1,    18,    -1,   489,    -1,   489,   492,   489, 
     964      -1,    13,    -1,    12,    -1,    17,    -1,    15,    -1,    16, 
     965      -1,    14,    -1,   161,    -1,   162,    -1,   195,    -1,   163, 
     966      -1,   196,    -1,   164,    -1,   491,    -1,   497,   491,    -1, 
     967     493,    -1,   494,   498,   493,    -1,   494,    -1,   495,   499, 
     968     494,    -1,   495,    -1,   496,   500,   495,    -1,    11,    -1, 
     969      10,    -1,     9,    -1,     7,    -1,     6,    -1,   496,    -1, 
     970     503,    -1,   501,    -1,   501,    -1,    -1,   506,    -1,   504, 
     971      -1,   506,    -1,   501,    -1,   510,    -1,   503,    -1,   512, 
     972      -1,   504,    -1,   434,     5,   501,   206,    -1,   260,   434, 
     973       5,   501,   206,    -1,   432,   515,   146,   520,   206,    -1, 
     974     432,   193,   517,   194,   146,   520,   206,    -1,   432,   146, 
     975     523,   206,    -1,    -1,   193,   516,   194,    -1,   518,    -1, 
     976     516,     3,   518,    -1,   519,    -1,   517,     3,   519,    -1, 
     977     472,     4,    -1,   472,     4,   473,    -1,   434,    -1,   191, 
     978      -1,   433,   199,   521,    -1,   501,    -1,   521,    -1,   522, 
     979      -1,    38,   193,   532,   194,   531,    -1,   529,   526,   527, 
     980     528,   535,    -1,    -1,   526,   530,    -1,    -1,   527,   533, 
     981     526,    -1,    -1,   528,   534,   526,    -1,    38,   193,   532, 
     982     194,   206,    -1,   531,    -1,   524,    -1,   525,    -1,   513, 
     983      -1,   501,    -1,    39,   532,   194,   206,    -1,    39,   532, 
     984     194,   191,   206,    -1,    40,   206,    -1,    40,   191,   206, 
     985      -1,    41,   206,    -1,    41,   191,   206,    -1,    -1,   538, 
     986      -1,    -1,   538,   245,    -1,   540,    -1,   549,    -1,   540, 
     987      -1,   541,   546,   547,    -1,   543,   546,   547,    -1,   191, 
     988       4,   170,   206,    -1,   170,   206,    -1,   191,     4,   170, 
     989     544,   206,    -1,   170,   544,   206,    -1,   191,     4,   169, 
     990     206,    -1,   169,   206,    -1,   191,     4,   169,   544,   206, 
     991      -1,   169,   544,   206,    -1,   191,     4,   111,   206,    -1, 
     992     111,   206,    -1,   191,     4,   111,   544,   206,    -1,   111, 
     993     544,   206,    -1,   213,   545,     5,   501,     3,   501,    -1, 
     994     213,   545,     5,   501,     3,   501,     3,   501,    -1,   213, 
     995     116,   193,   501,   194,    -1,   213,   117,   536,    -1,   231, 
     996      -1,   537,    -1,   548,    -1,   262,   587,    -1,   261,   113, 
     997     206,    -1,   261,   113,   191,   206,    -1,   550,    -1,   553, 
     998      -1,   541,   546,   551,    -1,   262,   552,    -1,   457,    -1, 
     999     513,    -1,   677,    -1,   600,    -1,   474,    -1,   622,    -1, 
     1000     585,    -1,   127,   718,    -1,   129,   193,   720,   194,    -1, 
     1001     568,    -1,   625,    -1,   593,    -1,   606,    -1,   604,    -1, 
     1002     619,    -1,   524,    -1,   605,    -1,   541,   546,   554,   555, 
     1003      -1,   541,   546,   555,    -1,   542,   546,    -1,   554,   542, 
     1004     546,    -1,   542,   546,   556,    -1,   262,   253,    -1,    -1, 
     1005     191,    -1,    78,   557,   206,    -1,   564,   537,   560,   562, 
     1006     567,    -1,    -1,   561,    -1,   560,   561,    -1,   565,   537, 
     1007      -1,    -1,   563,    -1,   562,   561,    -1,   566,   537,    -1, 
     1008     259,   191,     4,   110,   501,   194,   103,   206,    -1,   259, 
     1009     110,   501,   194,   103,   206,    -1,   104,   193,   501,   194, 
     1010     103,   206,    -1,   104,   193,   501,   194,   103,   191,   206, 
     1011      -1,   105,   206,    -1,   105,   191,   206,    -1,   106,   206, 
     1012      -1,   106,   191,   206,    -1,   259,   110,   501,   194,   253, 
     1013      -1,   572,   570,   576,    -1,    -1,   571,    -1,   570,   571, 
     1014      -1,   575,   537,    -1,    -1,   191,     4,    48,   193,   501, 
     1015     194,   573,   206,    -1,    -1,    48,   193,   501,   194,   574, 
     1016     206,    -1,    47,   579,   206,    -1,    47,   579,   191,   206, 
     1017      -1,    -1,   131,   577,   206,    -1,    -1,   131,   191,   578, 
     1018     206,    -1,    -1,   193,   580,   581,   194,    -1,   136,    -1, 
     1019     582,    -1,   581,     3,   582,    -1,   583,    -1,   583,     4, 
     1020      -1,     4,   583,    -1,   583,     4,   583,    -1,   501,    -1, 
     1021      93,   206,    -1,    93,   191,   206,    -1,   108,   260,   206, 
     1022      -1,   259,   110,   501,   194,   260,     3,   260,     3,   260, 
     1023     206,    -1,   259,   139,   206,    -1,   153,   206,    -1,   153, 
     1024     589,   206,    -1,   509,    -1,   511,    -1,   591,    -1,    21, 
     1025      -1,   592,    -1,   506,    -1,   438,    -1,    -1,    -1,   119, 
     1026     193,   594,   596,   194,   595,   206,    -1,   597,    -1,   596, 
     1027       3,   597,    -1,   591,    -1,    58,   591,    -1,    53,   502, 
     1028      -1,    54,   502,    -1,    65,   260,    -1,    49,   598,    -1, 
     1029      55,   502,    -1,    67,   441,    -1,    66,   502,    -1,    56, 
     1030     506,    -1,    57,     5,   502,    -1,   502,    -1,   439,    -1, 
     1031      -1,   120,   193,   601,   602,   194,   206,    -1,   603,    -1, 
     1032     602,     3,   603,    -1,   591,    -1,    58,   591,    -1,    67, 
     1033     441,    -1,    65,   260,    -1,    57,     5,   502,    -1,   259, 
     1034     125,   607,   194,   206,    -1,   259,   125,   607,   194,   611, 
     1035     206,    -1,   259,   126,   610,   206,    -1,   259,   126,   610, 
     1036       3,   611,   206,    -1,   259,   122,   607,   194,   206,    -1, 
     1037     259,   122,   607,   194,   613,   206,    -1,   259,   107,   610, 
     1038     206,    -1,   259,   107,   610,     3,   613,   206,    -1,   609, 
     1039      -1,   607,     3,   609,    -1,   191,    -1,   590,    -1,    58, 
     1040     590,    -1,   610,    -1,   608,    -1,    61,   608,    -1,    60, 
     1041     610,    -1,    62,   260,    -1,    63,   260,    -1,    65,   260, 
     1042      -1,    67,   441,    -1,    50,   506,    -1,   503,    -1,   260, 
     1043      -1,    21,    -1,   612,    -1,   611,     3,   612,    -1,   434, 
     1044      -1,   615,    -1,   614,    -1,   613,     3,   614,    -1,   501, 
     1045      -1,   615,    -1,   193,   616,     3,   618,   194,    -1,   617, 
     1046      -1,   616,     3,   617,    -1,   612,    -1,   614,    -1,   545, 
     1047       5,   506,     3,   506,    -1,   545,     5,   506,     3,   506, 
     1048       3,   506,    -1,   127,   591,   206,    -1,   127,   193,   620, 
     1049     194,   206,    -1,   621,    -1,   620,     3,   621,    -1,   591, 
     1050      -1,    58,   591,    -1,    68,   599,    -1,    67,   441,    -1, 
     1051      65,   260,    -1,   124,   591,   206,    -1,   124,   193,   623, 
     1052     194,   206,    -1,   624,    -1,   623,     3,   624,    -1,   591, 
     1053      -1,    58,   591,    -1,    67,   441,    -1,    68,   599,    -1, 
     1054      65,   260,    -1,    -1,   121,   628,   193,   629,   194,   626, 
     1055     206,    -1,    -1,   121,   628,   193,    52,   441,   194,   613, 
     1056     627,   206,    -1,    -1,   630,    -1,   629,     3,   630,    -1, 
     1057     591,    -1,    58,   591,    -1,    49,   598,    -1,    53,   439, 
     1058      -1,    54,   439,    -1,    65,   260,    -1,    69,   436,    -1, 
     1059      67,   441,    -1,    51,     5,   439,    -1,    59,   436,    -1, 
     1060      56,   441,    -1,    32,   206,    -1,    -1,   635,   653,   634, 
     1061     633,   637,    -1,    -1,   641,    -1,    -1,   114,   191,   636, 
     1062     206,    -1,    -1,   405,   182,   639,   640,   638,   206,    -1, 
     1063      -1,   114,    -1,    -1,   191,    -1,   715,   642,    -1,    -1, 
     1064     643,    -1,   644,    -1,   643,   644,    -1,   691,    -1,   702, 
     1065      -1,   647,    -1,   645,   647,    -1,    -1,    -1,   405,   160, 
     1066     646,   650,   191,   662,   648,   206,    -1,    -1,   405,   160, 
     1067     646,   650,   191,     3,    27,     4,   651,   649,   206,    -1, 
     1068      -1,   154,    -1,     3,   661,   154,    -1,    -1,   665,    -1, 
     1069     654,   653,   241,   246,   656,    -1,    -1,   236,    -1,    -1, 
     1070     242,    -1,    -1,    30,   191,   655,   206,    -1,    -1,    -1, 
     1071     657,   182,   659,   660,   658,   206,    -1,    -1,    30,    -1, 
     1072      -1,   191,    -1,   134,    -1,    -1,     3,   663,    -1,   664, 
     1073      -1,   663,     3,   664,    -1,   191,   146,   191,    -1,   666, 
     1074      -1,   665,     3,   666,    -1,   668,    -1,   667,    -1,   664, 
     1075      -1,   191,    -1,   191,    -1,   132,   670,   206,    -1,   132, 
     1076     154,   670,   206,    -1,   671,    -1,   670,     3,   671,    -1, 
     1077     191,    -1,   134,   400,   673,   206,    -1,   674,    -1,   673, 
     1078       3,   674,    -1,   191,    -1,   684,   193,   194,    -1,    -1, 
     1079     684,   193,   676,   685,   194,    -1,    -1,   682,   678,   206, 
     1080      -1,    -1,   682,   193,   194,   679,   206,    -1,    -1,    -1, 
     1081     682,   193,   680,   685,   194,   681,   206,    -1,    -1,   259, 
     1082     144,   683,   684,    -1,   231,    -1,   124,    -1,   175,    -1, 
     1083     686,    -1,   685,     3,   686,    -1,   687,    -1,   254,     5, 
     1084     687,    -1,   501,    -1,   434,    -1,   231,    -1,    -1,   689, 
     1085      -1,   690,    -1,   689,   690,    -1,   264,    -1,   114,    -1, 
     1086      87,    -1,   692,   653,   241,   246,   699,    -1,    -1,    -1, 
     1087     688,    31,   695,   193,   693,   711,   194,   697,   694,   206, 
     1088      -1,   191,    -1,   191,    -1,    -1,   698,    -1,    26,   193, 
     1089     191,   194,    -1,    -1,   405,   182,   701,   640,   707,   700, 
     1090     206,    -1,    -1,    31,    -1,   703,   653,   241,   246,   706, 
     1091      -1,    -1,   688,    29,   705,   709,   704,   206,    -1,   191, 
     1092      -1,   405,   182,   708,   640,   707,   206,    -1,    -1,    -1, 
     1093      29,    -1,    -1,    -1,   193,   710,   711,   194,    -1,    -1, 
     1094     712,    -1,   713,    -1,   712,     3,   713,    -1,   696,    -1, 
     1095      21,    -1,   259,   102,   206,    -1,   259,   102,   506,   206, 
     1096      -1,    -1,   259,   112,   716,   206,    -1,   197,    -1,   191, 
     1097      -1,   193,   231,   194,    -1,   193,   192,   194,    -1,   192, 
     1098      -1,   193,   214,   194,    -1,   191,    -1,    -1,   231,    -1, 
     1099     720,     3,   231,    -1 
    8751100}; 
    8761101 
     
    8781103static const yytype_uint16 yyrline[] = 
    8791104{ 
    880        0,   313,   313,   314,   316,   317,   318,   319,   322,   323, 
    881      324,   325,   326,   329,   330,   331,   334,   335,   336,   344, 
    882      347,   350,   351,   354,   355,   358,   366,   375,   392,   411, 
    883      412,   415,   417,   419,   420,   421,   423,   424,   425,   427, 
    884      439,   451,   452,   454,   455,   456,   457,   458,   475,   492, 
    885      493,   498,   499,   536,   549,   550,   551,   552,   553,   554, 
    886      555,   556,   557,   570,   571,   578,   579,   580,   581,   582, 
    887      583,   584,   585,   586,   587,   588,   589,   590,   591,   592, 
    888      593,   594,   595,   596,   597,   598,   599,   600,   601,   604, 
    889      605,   608,   609,   612,   613,   615,   618,   619,   622,   623, 
    890      625,   626,   629,   695,   710,   712,   716,   719,   720,   723, 
    891      729,   734,   748,   749,   752,   753,   754,   755,   758,   760, 
    892      761,   764,   765,   766,   769,   770,   771,   772,   773,   775, 
    893      776,   779,   780,   781,   782,   785,   792,   802,   814,   815, 
    894      818,   819,   822,   823,   824,   825,   828,   834,   842,   852, 
    895      853,   856,   857,   860,   868,   874,   881,   882,   885,   886, 
    896      889,   905,   908,   909,   912,   921,   923,   945,   970,   972, 
    897      973,   974,   975,   977,   978,   979,   980,   983,   984,   985, 
    898      987,   990,   991,   992,   993,   994,   995,   997,   998,  1001, 
    899     1002,  1004,  1005,  1006,  1008,  1009,  1012,  1013,  1023,  1024, 
    900     1025,  1028,  1029,  1031,  1032,  1034,  1035,  1036,  1038,  1039, 
    901     1042,  1043,  1044,  1045,  1046,  1047,  1049,  1050,  1051,  1052, 
    902     1053,  1056,  1057,  1058,  1061,  1062,  1064,  1065,  1073,  1079, 
    903     1086,  1087,  1088,  1089,  1090,  1093,  1094,  1096,  1097,  1098, 
    904     1099,  1103,  1104,  1105,  1106,  1107,  1108,  1109,  1110,  1111, 
    905     1112,  1113,  1114,  1115,  1116,  1117,  1118,  1119,  1120,  1121, 
    906     1122,  1123,  1124,  1125,  1126,  1127,  1128,  1130,  1131,  1133, 
    907     1134,  1135,  1136,  1137,  1138,  1140,  1141,  1145,  1146,  1147, 
    908     1148,  1149,  1150,  1151,  1152,  1153,  1154,  1155,  1156,  1157, 
    909     1158,  1159,  1160,  1161,  1162,  1163,  1164,  1165,  1167,  1168, 
    910     1169,  1170,  1173,  1174,  1177,  1178,  1179,  1183,  1194,  1195, 
    911     1196,  1197,  1200,  1209,  1216,  1219,  1220,  1223,  1224,  1227, 
    912     1228,  1231,  1232,  1233,  1234,  1235,  1236,  1237,  1239,  1285, 
    913     1286,  1287,  1288,  1289,  1290,  1291,  1293,  1296,  1297,  1298, 
    914     1299,  1301,  1302,  1305,  1307,  1308,  1311,  1312,  1314,  1315, 
    915     1321,  1329,  1332,  1352,  1379,  1399,  1439,  1446,  1450,  1457, 
    916     1467,  1468,  1476,  1486,  1498,  1499,  1504,  1505,  1506,  1507, 
    917     1508,  1513,  1514,  1515,  1516,  1517,  1518,  1519,  1520,  1521, 
    918     1522,  1523,  1524,  1525,  1526,  1527,  1528,  1529,  1530,  1567, 
    919     1576,  1587,  1595,  1617,  1618,  1619,  1657,  1661,  1665,  1668, 
    920     1669,  1672,  1673,  1676,  1677,  1682,  1686,  1687,  1688,  1692, 
    921     1696,  1701,  1702,  1707,  1708,  1713,  1714,  1718,  1722,  1723, 
    922     1724,  1729,  1734,  1739,  1740,  1745,  1746,  1747,  1748,  1753, 
    923     1754,  1755,  1756,  1761,  1762,  1763,  1764,  1768,  1772,  1776, 
    924     1777,  1782,  1783,  1787,  1790,  1791,  1792,  1796,  1799,  1800, 
    925     1801,  1804,  1809,  1810,  1815,  1816,  1821,  1822,  1827,  1828, 
    926     1832,  1836,  1839,  1840,  1841,  1844,  1849,  1850,  1855,  1856, 
    927     1861,  1862,  1867,  1868,  1872,  1873,  1878,  1879,  1880,  1881, 
    928     1885,  1889,  1893,  1897,  1905,  1912,  1919,  1926,  1927,  1930, 
    929     1933,  1944,  1950,  1951,  1954,  1955,  1957,  1970,  1971,  1973, 
    930     1974,  1977,  1978,  2000,  2003,  2004,  2007,  2015,  2018,  2019, 
    931     2022,  2023,  2026,  2027,  2029,  2030,  2032,  2035,  2036,  2037, 
    932     2038,  2039,  2042,  2043,  2046,  2047,  2048,  2049,  2050,  2051, 
    933     2052,  2053,  2056,  2059,  2060,  2061,  2063,  2064,  2067,  2068, 
    934     2069,  2072,  2073,  2076,  2077,  2078,  2079,  2080,  2081,  2082, 
    935     2083,  2084,  2085,  2086,  2087,  2088,  2089,  2090,  2091,  2092, 
    936     2094,  2095,  2097,  2098,  2104,  2105,  2106,  2107,  2108,  2110, 
    937     2111,  2112,  2115,  2116,  2117,  2118,  2119,  2120,  2121,  2122, 
    938     2123,  2124,  2127,  2128,  2129,  2131,  2132,  2134,  2135,  2138, 
    939     2139,  2142,  2145,  2146,  2148,  2149,  2152,  2153 
     1105       0,   512,   512,   513,   515,   516,   517,   519,   521,   522, 
     1106     523,   524,   527,   528,   529,   531,   532,   540,   558,   562, 
     1107     563,   564,   568,   569,   582,   850,   851,  1102,  1103,  1104, 
     1108    1105,  1106,  1108,  1109,  1113,  1114,  1115,  1116,  1117,  1118, 
     1109    1119,  1120,  1121,  1122,  1123,  1124,  1125,  1126,  1127,  1128, 
     1110    1129,  1130,  1131,  1132,  1133,  1135,  1136,  1137,  1138,  1141, 
     1111    1142,  1145,  1146,  1147,  1151,  1162,  1163,  1164,  1164,  1165, 
     1112    1165,  1167,  1168,  1168,  1177,  1189,  1190,  1193,  1194,  1197, 
     1113    1198,  1201,  1202,  1203,  1204,  1205,  1206,  1207,  1209,  1256, 
     1114    1257,  1258,  1259,  1260,  1261,  1262,  1264,  1267,  1268,  1269, 
     1115    1270,  1272,  1273,  1283,  1284,  1336,  1339,  1340,  1365,  1366, 
     1116    1370,  1371,  1384,  1385,  1386,  1387,  1388,  1389,  1390,  1391, 
     1117    1392,  1393,  1394,  1395,  1398,  1399,  1403,  1406,  1407,  1411, 
     1118    1412,  1416,  1417,  1420,  1421,  1425,  1429,  1430,  1433,  1434, 
     1119    1438,  1439,  1443,  1444,  1445,  1446,  1447,  1448,  1449,  1450, 
     1120    1451,  1456,  1457,  1458,  1459,  1460,  1468,  1469,  1470,  1471, 
     1121    1472,  1473,  1474,  1475,  1476,  1477,  1478,  1479,  1480,  1502, 
     1122    1503,  1504,  1505,  1506,  1507,  1508,  1509,  1510,  1511,  1512, 
     1123    1513,  1517,  1520,  1525,  1526,  1530,  1531,  1532,  1533,  1535, 
     1124    1539,  1558,  1559,  1563,  1564,  1568,  1569,  1573,  1577,  1578, 
     1125    1579,  1590,  1590,  1592,  1593,  1598,  1598,  1600,  1600,  1602, 
     1126    1602,  1604,  1604,  1606,  1606,  1608,  1608,  1613,  1614,  1620, 
     1127    1622,  1624,  1631,  1632,  1637,  1638,  1643,  1644,  1660,  1661, 
     1128    1666,  1667,  1674,  1680,  1681,  1682,  1686,  1687,  1688,  1691, 
     1129    1692,  1697,  1698,  1703,  1704,  1705,  1706,  1707,  1711,  1713, 
     1130    1715,  1716,  1720,  1722,  1727,  1728,  1729,  1733,  1734,  1738, 
     1131    1738,  1743,  1744,  1747,  1748,  1751,  1752,  1755,  1756,  1760, 
     1132    1763,  1764,  1767,  1771,  1772,  1775,  1776,  1780,  1781,  1785, 
     1133    1789,  1792,  1793,  1794,  1797,  1798,  1802,  1803,  1804,  1805, 
     1134    1808,  1809,  1813,  1836,  1837,  1841,  1842,  1845,  1846,  1850, 
     1135    1851,  1852,  1856,  1861,  1863,  1866,  1867,  1871,  1872,  1876, 
     1136    1877,  1880,  1881,  1885,  1886,  1890,  1891,  1892,  1896,  1898, 
     1137    1913,  1917,  1921,  1925,  1926,  1931,  1932,  1936,  1941,  1943, 
     1138    1948,  1952,  1953,  1952,  2020,  2021,  2024,  2025,  2029,  2030, 
     1139    2034,  2035,  2037,  2037,  2039,  2041,  2041,  2043,  2044,  2046, 
     1140    2048,  2050,  2052,  2057,  2059,  2064,  2098,  2101,  2104,  2105, 
     1141    2109,  2115,  2121,  2130,  2134,  2136,  2141,  2142,  2142,  2147, 
     1142    2149,  2151,  2153,  2155,  2159,  2165,  2174,  2176,  2181,  2186, 
     1143    2190,  2196,  2205,  2207,  2212,  2218,  2227,  2232,  2255,  2256, 
     1144    2275,  2276,  2280,  2281,  2285,  2289,  2291,  2293,  2299,  2298, 
     1145    2317,  2318,  2322,  2324,  2329,  2330,  2335,  2334,  2349,  2350, 
     1146    2353,  2354,  2358,  2368,  2370,  2376,  2378,  2383,  2384,  2388, 
     1147    2394,  2401,  2403,  2408,  2409,  2413,  2417,  2422,  2424,  2426, 
     1148    2428,  2429,  2430,  2431,  2432,  2436,  2437,  2453,  2454,  2455, 
     1149    2456,  2457,  2458,  2459,  2465,  2473,  2478,  2480,  2478,  2525, 
     1150    2525,  2534,  2534,  2547,  2548,  2547,  2567,  2569,  2574,  2591, 
     1151    2592,  2591,  2599,  2600,  2603,  2604,  2607,  2608,  2612,  2614, 
     1152    2615,  2619,  2623,  2627,  2629,  2628,  2640,  2641,  2645,  2648, 
     1153    2649,  2653,  2654,  2658,  2661,  2662,  2664,  2665,  2669,  2673, 
     1154    2676,  2677,  2681,  2681,  2684,  2685,  2689,  2690,  2691,  2696, 
     1155    2697,  2696,  2706,  2707,  2715,  2721,  2729,  2730,  2733,  2734, 
     1156    2738,  2740,  2748,  2754,  2754,  2763,  2764,  2765,  2766,  2775, 
     1157    2778,  2791,  2794,  2798,  2802,  2805,  2809,  2812,  2815,  2819, 
     1158    2820,  2822,  2837,  2842,  2847,  2848,  2853,  2855,  2855,  2867, 
     1159    2871,  2876,  2881,  2883,  2890,  2891,  2893,  2915,  2917,  2919, 
     1160    2921,  2923,  2925,  2927,  2928,  2930,  2932,  2936,  2938,  2940, 
     1161    2942,  2944,  2947,  2961,  2965,  2966,  2965,  2974,  2975,  2979, 
     1162    2980,  2984,  2985,  2989,  2993,  2997,  2998,  3002,  3006,  3007, 
     1163    3010,  3011,  3015,  3016,  3020,  3023,  3024,  3028,  3032,  3036, 
     1164    3037,  3036,  3042,  3043,  3046,  3047,  3051,  3052,  3056,  3057, 
     1165    3066,  3076,  3077,  3078,  3079,  3084,  3089,  3090,  3094,  3095, 
     1166    3102,  3103,  3105,  3107,  3108,  3113,  3117,  3119,  3123,  3125, 
     1167    3130,  3131,  3136,  3139,  3140,  3145,  3146,  3147,  3148,  3149, 
     1168    3150,  3151,  3152,  3153,  3155,  3156,  3158,  3163,  3164,  3170, 
     1169    3171,  3177,  3178,  3183,  3184,  3189,  3193,  3197,  3201,  3202, 
     1170    3206,  3209,  3213,  3217,  3221,  3222,  3225,  3229,  3236,  3240, 
     1171    3244,  3247,  3251,  3257,  3258,  3270,  3271,  3272,  3280,  3281, 
     1172    3285,  3286,  3290,  3291,  3295,  3299,  3303,  3306,  3315,  3319, 
     1173    3320,  3321,  3325,  3329,  3332,  3333,  3336,  3337,  3340,  3341, 
     1174    3345,  3349,  3350,  3351,  3355,  3359,  3363,  3364,  3368,  3369, 
     1175    3374,  3375,  3379,  3383,  3386,  3387,  3392,  3393,  3397,  3402, 
     1176    3403,  3414,  3415,  3416,  3417,  3420,  3421,  3422,  3423,  3427, 
     1177    3428,  3429,  3430,  3435,  3436,  3437,  3438,  3442,  3446,  3455, 
     1178    3456,  3460,  3461,  3472,  3473,  3479,  3489,  3494,  3495,  3496, 
     1179    3497,  3498,  3499,  3500,  3501,  3502,  3503,  3504,  3505,  3506, 
     1180    3507,  3508,  3509,  3510,  3520,  3521,  3524,  3525,  3536,  3541, 
     1181    3544,  3545,  3549,  3553,  3556,  3557,  3558,  3561,  3564,  3565, 
     1182    3566,  3569,  3573,  3574,  3578,  3579,  3583,  3584,  3588,  3589, 
     1183    3593,  3597,  3600,  3601,  3602,  3605,  3609,  3609,  3610,  3610, 
     1184    3614,  3615,  3619,  3619,  3620,  3620,  3625,  3625,  3626,  3630, 
     1185    3631,  3636,  3637,  3638,  3639,  3643,  3647,  3648,  3652,  3656, 
     1186    3660,  3664,  3665,  3669,  3670,  3674,  3675,  3676,  3680,  3684, 
     1187    3688,  3688,  3688,  3691,  3692,  3696,  3697,  3698,  3699,  3700, 
     1188    3701,  3702,  3703,  3704,  3705,  3706,  3710,  3714,  3718,  3718, 
     1189    3722,  3723,  3727,  3728,  3729,  3730,  3731,  3735,  3736,  3737, 
     1190    3738,  3742,  3743,  3747,  3748,  3750,  3751,  3754,  3758,  3759, 
     1191    3760,  3761,  3762,  3763,  3764,  3765,  3766,  3767,  3768,  3772, 
     1192    3773,  3774,  3777,  3778,  3781,  3782,  3786,  3787,  3791,  3792, 
     1193    3796,  3799,  3800,  3804,  3805,  3809,  3810,  3814,  3815,  3819, 
     1194    3820,  3824,  3825,  3826,  3827,  3828,  3832,  3833,  3837,  3838, 
     1195    3842,  3843,  3844,  3845,  3846,  3852,  3851,  3855,  3854,  3859, 
     1196    3863,  3864,  3868,  3869,  3870,  3871,  3872,  3873,  3874,  3875, 
     1197    3876,  3877,  3878,  3882,  3886,  3886,  3889,  3890,  3895,  3894, 
     1198    3915,  3914,  3939,  3940,  3943,  3944,  3947,  3950,  3951,  3954, 
     1199    3955,  3958,  3959,  3962,  3963,  3967,  3972,  3971,  4010,  4009, 
     1200    4061,  4062,  4063,  4067,  4068,  4073,  4076,  4077,  4080,  4081, 
     1201    4086,  4085,  4099,  4100,  4099,  4111,  4112,  4114,  4115,  4118, 
     1202    4122,  4125,  4131,  4135,  4144,  4154,  4156,  4165,  4173,  4181, 
     1203    4189,  4193,  4197,  4198,  4201,  4202,  4205,  4209,  4213,  4214, 
     1204    4217,  4221,  4222,  4222,  4229,  4228,  4242,  4241,  4254,  4255, 
     1205    4254,  4269,  4269,  4293,  4294,  4295,  4299,  4300,  4305,  4313, 
     1206    4324,  4325,  4335,  4338,  4339,  4343,  4344,  4348,  4350,  4352, 
     1207    4357,  4362,  4363,  4361,  4386,  4411,  4416,  4417,  4421,  4438, 
     1208    4437,  4442,  4443,  4447,  4452,  4451,  4466,  4483,  4488,  4532, 
     1209    4533,  4537,  4538,  4538,  4543,  4544,  4549,  4561,  4575,  4577, 
     1210    4582,  4583,  4588,  4587,  4623,  4624,  4731,  4732,  4733,  4734, 
     1211    4735,  4752,  4845,  4846 
    9401212}; 
    9411213#endif 
     
    9511223  "'*'", "TOK_SLASH", "TOK_DASTER", "TOK_SEMICOLON", "TOK_PARAMETER", 
    9521224  "TOK_RESULT", "TOK_ONLY", "TOK_INCLUDE", "TOK_SUBROUTINE", "TOK_PROGRAM", 
    953   "TOK_FUNCTION", "TOK_FORMAT", "TOK_MAX", "TOK_TANH", "TOK_WHERE", 
     1225  "TOK_FUNCTION", "TOK_LABEL_FORMAT", "TOK_LABEL_CONTINUE", 
     1226  "TOK_LABEL_END_DO", "TOK_MAX", "TOK_TANH", "TOK_COMMENT", "TOK_WHERE", 
    9541227  "TOK_ELSEWHEREPAR", "TOK_ELSEWHERE", "TOK_ENDWHERE", "TOK_MAXVAL", 
    9551228  "TOK_TRIM", "TOK_NULL_PTR", "TOK_SUM", "TOK_SQRT", "TOK_CASE", 
    956   "TOK_SELECTCASE", "TOK_FILE", "TOK_UNIT", "TOK_FMT", "TOK_NML", 
    957   "TOK_END", "TOK_EOR", "TOK_ERR", "TOK_EXIST", "TOK_MIN", "TOK_FLOAT", 
    958   "TOK_EXP", "TOK_COS", "TOK_COSH", "TOK_ACOS", "TOK_NINT", "TOK_CYCLE", 
    959   "TOK_SIN", "TOK_SINH", "TOK_ASIN", "TOK_EQUIVALENCE", "TOK_BACKSPACE", 
    960   "TOK_LOG", "TOK_TAN", "TOK_ATAN", "TOK_RECURSIVE", "TOK_ABS", "TOK_MOD", 
    961   "TOK_SIGN", "TOK_MINLOC", "TOK_MAXLOC", "TOK_EXIT", "TOK_MINVAL", 
    962   "TOK_PUBLIC", "TOK_PRIVATE", "TOK_ALLOCATABLE", "TOK_RETURN", "TOK_THEN", 
    963   "TOK_ELSEIF", "TOK_ELSE", "TOK_ENDIF", "TOK_PRINT", "TOK_PLAINGOTO", 
    964   "TOK_LOGICALIF", "TOK_PLAINDO", "TOK_CONTAINS", "TOK_ENDDO", 
     1229  "TOK_SELECTCASE", "TOK_FILE", "TOK_REC", "TOK_NAME_EQ", "TOK_IOLENGTH", 
     1230  "TOK_ACCESS", "TOK_ACTION", "TOK_FORM", "TOK_RECL", "TOK_STATUS", 
     1231  "TOK_UNIT", "TOK_OPENED", "TOK_FMT", "TOK_NML", "TOK_END", "TOK_EOR", 
     1232  "TOK_EOF", "TOK_ERR", "TOK_POSITION", "TOK_IOSTAT", "TOK_IOMSG", 
     1233  "TOK_EXIST", "TOK_MIN", "TOK_FLOAT", "TOK_EXP", "TOK_LEN", "TOK_COS", 
     1234  "TOK_COSH", "TOK_ACOS", "TOK_NINT", "TOK_CYCLE", "TOK_SIN", "TOK_SINH", 
     1235  "TOK_ASIN", "TOK_EQUIVALENCE", "TOK_BACKSPACE", "TOK_LOG", "TOK_TAN", 
     1236  "TOK_ATAN", "TOK_RECURSIVE", "TOK_ABS", "TOK_MOD", "TOK_SIGN", 
     1237  "TOK_MINLOC", "TOK_MAXLOC", "TOK_EXIT", "TOK_KIND", "TOK_MOLD", 
     1238  "TOK_SOURCE", "TOK_ERRMSG", "TOK_MINVAL", "TOK_PUBLIC", "TOK_PRIVATE", 
     1239  "TOK_ALLOCATABLE", "TOK_RETURN", "TOK_THEN", "TOK_ELSEIF", "TOK_ELSE", 
     1240  "TOK_ENDIF", "TOK_PRINT", "TOK_PLAINGOTO", "TOK_LOGICALIF", 
     1241  "TOK_LOGICALIF_PAR", "TOK_PLAINDO", "TOK_CONTAINS", "TOK_ENDDO", 
    9651242  "TOK_MODULE", "TOK_ENDMODULE", "TOK_WHILE", "TOK_CONCURRENT", 
    966   "TOK_ALLOCATE", "TOK_OPEN", "TOK_CLOSE", "TOK_INQUIRE", "TOK_WRITE", 
    967   "TOK_FLUSH", "TOK_READ", "TOK_REWIND", "TOK_DEALLOCATE", "TOK_NULLIFY", 
    968   "TOK_DIMENSION", "TOK_ENDSELECT", "TOK_EXTERNAL", "TOK_INTENT", 
    969   "TOK_INTRINSIC", "TOK_NAMELIST", "TOK_DEFAULT", "TOK_OPTIONAL", 
    970   "TOK_POINTER", "TOK_CONTINUE", "TOK_SAVE", "TOK_TARGET", "TOK_IMPLICIT", 
    971   "TOK_NONE", "TOK_CALL", "TOK_STAT", "TOK_POINT_TO", "TOK_COMMON", 
    972   "TOK_GLOBAL", "TOK_LEFTAB", "TOK_RIGHTAB", "TOK_PAUSE", "TOK_PROCEDURE", 
    973   "TOK_STOP", "TOK_REAL8", "TOK_FOURDOTS", "TOK_HEXA", "TOK_ASSIGNTYPE", 
    974   "TOK_OUT", "TOK_INOUT", "TOK_IN", "TOK_USE", "TOK_TRUE", "TOK_FALSE", 
    975   "TOK_LABEL", "TOK_TYPE", "TOK_TYPEPAR", "TOK_ENDTYPE", "TOK_REAL", 
     1243  "TOK_ALLOCATE", "TOK_OPEN", "TOK_CLOSE", "TOK_INQUIRE", "TOK_WRITE_PAR", 
     1244  "TOK_WRITE", "TOK_FLUSH", "TOK_READ_PAR", "TOK_READ", "TOK_REWIND", 
     1245  "TOK_DEALLOCATE", "TOK_NULLIFY", "TOK_DIMENSION", "TOK_ENDSELECT", 
     1246  "TOK_EXTERNAL", "TOK_INTENT", "TOK_INTRINSIC", "TOK_NAMELIST", 
     1247  "TOK_DEFAULT", "TOK_OPTIONAL", "TOK_POINTER", "TOK_CONTINUE", "TOK_SAVE", 
     1248  "TOK_TARGET", "TOK_IMPLICIT", "TOK_NONE", "TOK_CALL", "TOK_STAT", 
     1249  "TOK_POINT_TO", "TOK_COMMON", "TOK_GLOBAL", "TOK_LEFTAB", "TOK_RIGHTAB", 
     1250  "TOK_PAUSE", "TOK_PROCEDURE", "TOK_STOP", "TOK_FOURDOTS", "TOK_HEXA", 
     1251  "TOK_ASSIGNTYPE", "TOK_OUT", "TOK_INOUT", "TOK_IN", "TOK_USE", 
     1252  "TOK_EQUALEQUAL", "TOK_SLASHEQUAL", "TOK_INFEQUAL", "TOK_SUPEQUAL", 
     1253  "TOK_TRUE", "TOK_FALSE", "TOK_LABEL", "TOK_LABEL_DJVIEW", 
     1254  "TOK_PLAINDO_LABEL_DJVIEW", "TOK_PLAINDO_LABEL", "TOK_TYPE", 
     1255  "TOK_TYPEPAR", "TOK_ENDTYPE", "TOK_COMMACOMPLEX", "TOK_REAL", 
    9761256  "TOK_INTEGER", "TOK_LOGICAL", "TOK_DOUBLEPRECISION", "TOK_ENDSUBROUTINE", 
    9771257  "TOK_ENDFUNCTION", "TOK_ENDPROGRAM", "TOK_ENDUNIT", "TOK_CHARACTER", 
    9781258  "TOK_CHAR_CONSTANT", "TOK_CHAR_CUT", "TOK_DATA", "TOK_CHAR_MESSAGE", 
    9791259  "TOK_CSTREAL", "TOK_COMPLEX", "TOK_DOUBLECOMPLEX", "TOK_NAME", 
    980   "TOK_CSTINT", "'('", "')'", "'<'", "'>'", "'\\n'", "'/'", "'%'", 
    981   "$accept", "input", "line", "line-break", "suite_line_list", 
    982   "suite_line", "fin_line", "opt_recursive", "opt_result", "entry", 
    983   "label", "name_routine", "filename", "arglist", "arglist_after_result", 
    984   "args", "arg", "spec", "opt_spec", "name_intrinsic", 
    985   "use_intrinsic_list", "list_couple", "list_expr_equi", "expr_equi", 
    986   "list_expr_equi1", "list_expr", "opt_sep", "after_type", 
    987   "before_function", "before_parameter", "data_stmt", "data_stmt_set_list", 
    988   "data_stmt_set", "data_stmt_value_list", "save", "before_save", 
    989   "varsave", "datanamelist", "expr_data", "opt_signe", "namelist", 
    990   "before_dimension", "dimension", "private", "public", "use_name_list", 
    991   "common", "before_common", "var_common_list", "var_common", "comblock", 
    992   "opt_comma", "paramlist", "paramitem", "module_proc_stmt", 
    993   "proc_name_list", "implicit", "dcl", "nodimsgiven", "type", "c_selector", 
    994   "c_attribute", "before_character", "typespec", "lengspec", 
    995   "proper_lengspec", "selector", "proper_selector", "attribute", "clause", 
    996   "opt_clause", "options", "attr_spec_list", "attr_spec", "intent_spec", 
    997   "access_spec", "dims", "dimlist", "dim", "ubound", "expr", 
    998   "predefinedfunction", "minmaxlist", "uexpr", "signe", "operation", 
    999   "after_slash", "after_equal", "lhs", "beforefunctionuse", 
    1000   "array_ele_substring_func_ref", "begin_array", "structure_component", 
    1001   "vec", "funarglist", "funargs", "funarg", "triplet", "ident", 
    1002   "simple_const", "string_constant", "opt_substring", "substring", 
    1003   "optexpr", "opt_expr", "initial_value", "complex_const", "use_stat", 
    1004   "word_use", "rename_list", "rename_name", "only_list", "only_name", 
    1005   "execution-part-construct", "executable-construct", "action-stmt", 
    1006   "assignment-stmt", "where-stmt", "where-construct", 
    1007   "opt-where-body-construct", "opt-masked-elsewhere-construct", 
    1008   "opt-elsewhere-construct", "where-construct-stmt", 
    1009   "where-body-construct", "where-assignment-stmt", "mask-expr", 
    1010   "masked-elsewhere-stmt", "elsewhere-stmt", "end-where-stmt", 
    1011   "forall-header", "block", "do-construct", "block-do-construct", 
    1012   "do-stmt", "label-do-stmt", "nonlabel-do-stmt", "loop-control", 
    1013   "do-variable", "do-block", "end-do", "end-do-stmt", "if-construct", 
     1260  "TOK_CSTINT", "'('", "')'", "'<'", "'>'", "'\\n'", "'/'", "'%'", "'_'", 
     1261  "'['", "']'", "$accept", "input", "line", "line-break", 
     1262  "suite_line_list", "suite_line", "fin_line", "program-unit", 
     1263  "external-subprogram", "filename", "opt_comma", "uexpr", "signe", 
     1264  "operation", "after_slash", "after_equal", "lhs", "beforefunctionuse", 
     1265  "array_ele_substring_func_ref", "$@4", "$@5", "begin_array", "$@6", 
     1266  "structure_component", "funarglist", "funargs", "funarg", "triplet", 
     1267  "ident", "simple_const", "string_constant", "opt_substring", "opt_expr", 
     1268  "specification-part", "opt-use-stmt-list", 
     1269  "opt-declaration-construct-list", "declaration-construct-list", 
     1270  "declaration-construct", "opt-execution-part", "execution-part", 
     1271  "opt-execution-part-construct-list", "execution-part-construct-list", 
     1272  "execution-part-construct", "opt-internal-subprogram-part", 
     1273  "internal-subprogram-part", "opt-internal-subprogram", 
     1274  "internal-subprogram-list", "internal-subprogram", 
     1275  "other-specification-stmt", "executable-construct", "action-stmt", 
     1276  "keyword", "scalar-constant", "constant", "literal-constant", 
     1277  "named-constant", "opt-label", "label", "opt-label-djview", 
     1278  "label-djview", "type-param-value", "declaration-type-spec", "$@7", 
     1279  "intrinsic-type-spec", "$@8", "$@9", "$@10", "$@11", "$@12", "$@13", 
     1280  "opt-kind-selector", "kind-selector", "signed-int-literal-constant", 
     1281  "int-literal-constant", "kind-param", "signed-real-literal-constant", 
     1282  "real-literal-constant", "complex-literal-constant", "real-part", 
     1283  "imag-part", "opt-char_length-star", "opt-char-selector", 
     1284  "char-selector", "length-selector", "char-length", 
     1285  "char-literal-constant", "logical-literal-constant", "derived-type-def", 
     1286  "$@14", "derived-type-stmt", "opt-type-attr-spec-list-comma-fourdots", 
     1287  "opt-type-attr-spec-list-comma", "type-attr-spec-list", "type-attr-spec", 
     1288  "type-param-name-list", "type-param-name", "end-type-stmt", 
     1289  "opt-component-part", "component-part", "component-def-stmt", 
     1290  "data-component-def-stmt", "opt-component-attr-spec-list-comma-2points", 
     1291  "component-attr-spec-list", "component-attr-spec", "component-decl-list", 
     1292  "component-decl", "opt-component-array-spec", "component-array-spec", 
     1293  "opt-component-initialization", "component-initialization", 
     1294  "initial-data-target", "derived-type-spec", "type-param-spec-list", 
     1295  "type-param-spec", "structure-constructor", "component-spec-list", 
     1296  "component-spec", "component-data-source", "array-constructor", 
     1297  "ac-spec", "lbracket", "rbracket", "ac-value-list", "ac-value", 
     1298  "ac-implied-do", "ac-implied-do-control", "ac-do-variable", 
     1299  "type-declaration-stmt", "$@15", "$@16", "opt-attr-spec-construct", 
     1300  "opt-attr-spec-comma-list", "attr-spec-comma-list", "attr-spec", "$@17", 
     1301  "$@18", "entity-decl-list", "entity-decl", "object-name", 
     1302  "object-name-noident", "opt-initialization", "initialization", 
     1303  "null-init", "access-spec", "opt-array-spec-par", "$@19", "array-spec", 
     1304  "explicit-shape-spec-list", "explicit-shape-spec", "lower-bound", 
     1305  "upper-bound", "assumed-shape-spec-list", "assumed-shape-spec", 
     1306  "deferred-shape-spec-list", "deferred-shape-spec", "assumed-size-spec", 
     1307  "opt-explicit-shape-spec-list-comma", "opt-lower-bound-2points", 
     1308  "implied-shape-spec-list", "implied-shape-spec", "intent-spec", 
     1309  "access-stmt", "$@20", "opt-access-id-list", "access-id-list", 
     1310  "access-id", "data-stmt", "$@21", "opt-data-stmt-set-nlist", 
     1311  "data-stmt-set-nlist", "data-stmt-set", "data-stmt-object-list", 
     1312  "data-stmt-value-list", "data-stmt-object", "data-implied-do", 
     1313  "data-i-do-object-list", "data-i-do-object", "data-i-do-variable", 
     1314  "data-stmt-value", "opt-data-stmt-star", "data-stmt-constant", 
     1315  "scalar-constant-subobject", "constant-subobject", "dimension-stmt", 
     1316  "$@22", "$@23", "array-name-spec-list", "$@24", "$@25", "parameter-stmt", 
     1317  "$@26", "$@27", "named-constant-def-list", "named-constant-def", 
     1318  "save-stmt", "$@28", "$@29", "opt-TOK_FOURDOTS", "opt-saved-entity-list", 
     1319  "saved-entity-list", "saved-entity", "proc-pointer-name", 
     1320  "get_my_position", "implicit-stmt", "$@30", "implicit-spec-list", 
     1321  "implicit-spec", "letter-spec-list", "letter-spec", "namelist-stmt", 
     1322  "opt-namelist-other", "namelist-group-object-list", 
     1323  "namelist-group-object", "equivalence-stmt", "equivalence-set-list", 
     1324  "equivalence-set", "$@31", "equivalence-object-list", 
     1325  "equivalence-object", "common-stmt", "$@32", "$@33", 
     1326  "opt-common-block-name", "common-block-name", "opt-comma", 
     1327  "opt-common-block-list", "common-block-object-list", 
     1328  "common-block-object", "$@34", "designator", "scalar-variable", 
     1329  "variable", "variable-name", "scalar-logical-variable", 
     1330  "logical-variable", "char-variable", "scalar-default-char-variable", 
     1331  "default-char-variable", "scalar-int-variable", "int-variable", 
     1332  "substring", "substring-range", "data-ref", "opt-part-ref", "part-ref", 
     1333  "$@35", "scalar-structure-component", "structure-component", 
     1334  "array-element", "array-section", "section-subscript-list", 
     1335  "section-subscript", "section_subscript_ambiguous", "vector-subscript", 
     1336  "allocate-stmt", "$@36", "$@37", "opt-alloc-opt-list-comma", 
     1337  "alloc-opt-list", "alloc-opt", "stat-variable", "errmsg-variable", 
     1338  "allocation-list", "allocation", "allocate-object", 
     1339  "opt-allocate-shape-spec-list-par", "allocate-shape-spec-list", 
     1340  "allocate-shape-spec", "opt-lower-bound-expr", "lower-bound-expr", 
     1341  "upper-bound-expr", "deallocate-stmt", "$@38", "$@39", 
     1342  "allocate-object-list", "opt-dealloc-opt-list-comma", "dealloc-opt-list", 
     1343  "dealloc-opt", "primary", "level-1-expr", "mult-operand", "add-operand", 
     1344  "level-2-expr", "power-op", "mult-op", "add-op", "level-3-expr", 
     1345  "concat-op", "level-4-expr", "rel-op", "and-operand", "or-operand", 
     1346  "equiv-operand", "level-5-expr", "not-op", "and-op", "or-op", "equiv-op", 
     1347  "expr", "scalar-default-char-expr", "default-char-expr", "int-expr", 
     1348  "opt-scalar-int-expr", "scalar-int-expr", "specification-expr", 
     1349  "constant-expr", "scalar-default-char-constant-expr", 
     1350  "default-char-constant-expr", "scalar-int-constant-expr", 
     1351  "int-constant-expr", "assignment-stmt", "pointer-assignment-stmt", 
     1352  "opt-bounds-spec-list-par", "bounds-spec-list", "bounds-remapping-list", 
     1353  "bounds-spec", "bounds-remapping", "data-target", 
     1354  "procedure-component-name", "proc-component-ref", "proc-target", 
     1355  "where-stmt", "where-construct", "opt-where-body-construct", 
     1356  "opt-masked-elsewhere-construct", "opt-elsewhere-construct", 
     1357  "where-construct-stmt", "where-body-construct", "where-assignment-stmt", 
     1358  "mask-expr", "masked-elsewhere-stmt", "elsewhere-stmt", "end-where-stmt", 
     1359  "forall-header", "block", "opt-execution-part-construct", "do-construct", 
     1360  "block-do-construct", "label-do-stmt", "label-do-stmt-djview", 
     1361  "nonlabel-do-stmt", "loop-control", "do-variable", "do-block", "end-do", 
     1362  "end-do-stmt", "nonblock-do-construct", "action-term-do-construct", 
     1363  "do-term-action-stmt", "do-term-action-stmt-special", 
     1364  "outer-shared-do-construct", "label-do-stmt-djview-do-block-list", 
     1365  "inner-shared-do-construct", "do-term-shared-stmt", 
     1366  "opt-do-construct-name", "cycle-stmt", "if-construct", 
    10141367  "opt-else-if-stmt-block", "else-if-stmt-block", "opt-else-stmt-block", 
    10151368  "else-stmt-block", "if-then-stmt", "else-if-stmt", "else-stmt", 
    10161369  "end-if-stmt", "if-stmt", "case-construct", "opt_case-stmt-block", 
    1017   "case-stmt-block", "select-case-stmt", "case-stmt", "end-select-stmt", 
    1018   "case-selector", "case-value-range-list", "case-value-range", 
    1019   "case-value", "continue-stmt", "format-stmt", "word_endsubroutine", 
    1020   "word_endunit", "word_endprogram", "word_endfunction", "opt_name", 
    1021   "before_dims", "ident_dims", "int_list", "after_ident_dims", "call", 
    1022   "opt_call", "opt_callarglist", "keywordcall", "before_call", 
    1023   "callarglist", "callarg", "stop", "option_inlist", "option_read", 
    1024   "opt_inlist", "ioctl", "after_rewind", "ctllist", "ioclause", 
    1025   "declare_after_percent", "iofctl", "infmt", "read", "fexpr", 
    1026   "unpar_fexpr", "addop", "inlist", "inelt", "opt_operation", "outlist", 
    1027   "other", "dospec", "goto", "allocation_list", "allocate_object", 
    1028   "allocate_object_list", "opt_stat_spec", "pointer_name_list", YY_NULL 
     1370  "case-stmt-block", "select-case-stmt", "$@40", "$@41", "case-stmt", 
     1371  "end-select-stmt", "$@42", "$@43", "case-selector", "$@44", 
     1372  "case-value-range-list", "case-value-range", "case-value", "exit-stmt", 
     1373  "goto-stmt", "arithmetic-if-stmt", "continue-stmt", "stop-stmt", 
     1374  "stop-code", "io-unit", "file-unit-number", "internal-file-variable", 
     1375  "open-stmt", "$@45", "$@46", "connect-spec-list", "connect-spec", 
     1376  "file-name-expr", "iomsg-variable", "close-stmt", "$@47", 
     1377  "close-spec-list", "close-spec", "read-stmt", "write-stmt", "print-stmt", 
     1378  "io-control-spec-list", "namelist-group-name", "io-control-spec", 
     1379  "format", "input-item-list", "input-item", "output-item-list", 
     1380  "output-item", "io-implied-do", "io-implied-do-object-list", 
     1381  "io-implied-do-object", "io-implied-do-control", "rewind-stmt", 
     1382  "position-spec-list", "position-spec", "flush-stmt", "flush-spec-list", 
     1383  "flush-spec", "inquire-stmt", "$@48", "$@49", "set_in_inquire", 
     1384  "inquire-spec-list", "inquire-spec", "format-stmt", "module", "$@50", 
     1385  "opt-module-subprogram-part", "module-stmt", "$@51", "end-module-stmt", 
     1386  "$@52", "opt-tok-module", "opt-ident", "module-subprogram-part", 
     1387  "opt-module-subprogram-list", "module-subprogram-list", 
     1388  "module-subprogram", "use-stmt-list", "save_olduse", "use-stmt", "$@53", 
     1389  "$@54", "opt-module-nature-2points", "opt-only-list", "main-program", 
     1390  "opt-specification-part", "program-stmt", "$@55", "end-program-stmt", 
     1391  "$@56", "$@57", "opt-tok-program", "opt-tok-name", "module-nature", 
     1392  "opt-rename-list", "rename-list", "rename", "only-list", "only", 
     1393  "only-use-name", "generic-spec", "external-stmt", "external-name-list", 
     1394  "external-name", "intrinsic-stmt", "intrinsic-procedure-name-list", 
     1395  "intrinsic-procedure-name", "function-reference", "$@58", "call-stmt", 
     1396  "$@59", "$@60", "$@61", "$@62", "before-call-stmt", "$@63", 
     1397  "procedure-designator", "actual-arg-spec-list", "actual-arg-spec", 
     1398  "actual-arg", "opt-prefix", "prefix", "prefix-spec", 
     1399  "function-subprogram", "function-stmt", "$@64", "$@65", "function-name", 
     1400  "dummy-arg-name", "opt-suffix", "suffix", "end-function-stmt", "$@66", 
     1401  "opt-tok-function", "subroutine-subprogram", "subroutine-stmt", "$@67", 
     1402  "subroutine-name", "end-subroutine-stmt", "close_subroutine", 
     1403  "opt-tok-subroutine", "opt-dummy-arg-list-par", "$@68", 
     1404  "opt-dummy-arg-list", "dummy-arg-list", "dummy-arg", "return-stmt", 
     1405  "contains-stmt", "$@69", "opt_name", "after_rewind", 
     1406  "declare_after_percent", "pointer_name_list", YY_NULL 
    10291407}; 
    10301408#endif 
     
    10511429     389,   390,   391,   392,   393,   394,   395,   396,   397,   398, 
    10521430     399,   400,   401,   402,   403,   404,   405,   406,   407,   408, 
    1053      409,   410,    40,    41,    60,    62,    10,    47,    37 
     1431     409,   410,   411,   412,   413,   414,   415,   416,   417,   418, 
     1432     419,   420,   421,   422,   423,   424,   425,   426,   427,   428, 
     1433     429,   430,   431,   432,   433,   434,   435,   436,   437,   438, 
     1434     439,   440,   441,    40,    41,    60,    62,    10,    47,    37, 
     1435      95,    91,    93 
    10541436}; 
    10551437# endif 
     
    10581440static const yytype_uint16 yyr1[] = 
    10591441{ 
    1060        0,   169,   170,   170,   171,   171,   171,   171,   172,   172, 
    1061      172,   172,   172,   173,   173,   173,   174,   174,   174,   174, 
    1062      175,   176,   176,   177,   177,   178,   178,   178,   178,   179, 
    1063      179,   180,   181,   182,   182,   182,   183,   183,   183,   184, 
    1064      184,   185,   185,   186,   186,   186,   186,   186,   186,   186, 
    1065      186,   186,   186,   186,   186,   186,   186,   186,   186,   186, 
    1066      186,   186,   186,   187,   187,   188,   188,   188,   188,   188, 
    1067      188,   188,   188,   188,   188,   188,   188,   188,   188,   188, 
    1068      188,   188,   188,   188,   188,   188,   188,   188,   188,   189, 
    1069      189,   190,   190,   191,   191,   192,   193,   193,   194,   194, 
    1070      195,   195,   196,   196,   197,   198,   199,   200,   200,   201, 
    1071      201,   201,   202,   202,   203,   203,   203,   203,   204,   205, 
    1072      205,   206,   206,   206,   207,   207,   207,   207,   207,   208, 
    1073      208,   209,   209,   209,   209,   210,   211,   211,   212,   212, 
    1074      213,   213,   214,   214,   214,   214,   215,   215,   215,   216, 
    1075      216,   217,   217,   218,   219,   219,   220,   220,   221,   221, 
    1076      222,   223,   224,   224,   225,   225,   226,   226,   227,   228, 
    1077      228,   228,   228,   229,   229,   229,   229,   230,   230,   230, 
    1078      231,   232,   232,   232,   232,   232,   232,   233,   233,   234, 
    1079      234,   235,   235,   235,   236,   236,   237,   237,   237,   237, 
    1080      237,   238,   238,   239,   239,   240,   240,   240,   241,   241, 
    1081      242,   242,   242,   242,   242,   242,   242,   242,   242,   242, 
    1082      242,   243,   243,   243,   244,   244,   245,   245,   246,   246, 
    1083      247,   247,   247,   247,   247,   248,   248,   249,   249,   249, 
    1084      249,   250,   250,   250,   250,   250,   250,   250,   250,   250, 
    1085      250,   250,   250,   250,   250,   250,   250,   250,   250,   250, 
    1086      250,   250,   250,   250,   250,   250,   250,   251,   251,   252, 
    1087      252,   252,   252,   252,   252,   253,   253,   254,   254,   254, 
    1088      254,   254,   254,   254,   254,   254,   254,   254,   254,   254, 
    1089      254,   254,   254,   254,   254,   254,   254,   254,   255,   255, 
    1090      255,   255,   256,   256,   257,   257,   257,   258,   259,   259, 
    1091      259,   259,   260,   261,   262,   263,   263,   264,   264,   265, 
    1092      265,   266,   266,   266,   266,   266,   266,   266,   267,   268, 
    1093      268,   268,   268,   268,   268,   268,   268,   269,   269,   269, 
    1094      269,   270,   270,   271,   272,   272,   273,   273,   274,   274, 
    1095      274,   275,   276,   276,   276,   276,   277,   278,   278,   279, 
    1096      280,   280,   281,   281,   282,   282,   283,   283,   283,   283, 
    1097      283,   284,   284,   284,   284,   284,   284,   284,   284,   284, 
    1098      284,   284,   284,   284,   284,   284,   284,   284,   284,   284, 
    1099      284,   284,   284,   284,   284,   284,   285,   286,   287,   288, 
    1100      288,   289,   289,   290,   290,   291,   292,   292,   292,   293, 
    1101      294,   295,   295,   296,   296,   297,   297,   298,   299,   299, 
    1102      299,   300,   301,   302,   302,   303,   303,   303,   303,   304, 
    1103      304,   304,   304,   305,   305,   305,   305,   306,   307,   308, 
    1104      308,   309,   309,   310,   311,   311,   311,   312,   313,   313, 
    1105      313,   314,   315,   315,   316,   316,   317,   317,   318,   318, 
    1106      319,   320,   321,   321,   321,   322,   323,   323,   324,   324, 
    1107      325,   325,   326,   326,   327,   327,   328,   328,   328,   328, 
    1108      329,   330,   331,   332,   333,   334,   335,   336,   336,   337, 
    1109      338,   338,   339,   339,   340,   340,   341,   342,   342,   343, 
    1110      343,   344,   344,   345,   346,   346,   347,   347,   348,   348, 
    1111      349,   349,   350,   350,   351,   351,   352,   353,   353,   353, 
    1112      353,   353,   354,   354,   355,   355,   355,   355,   355,   355, 
    1113      355,   355,   356,   357,   357,   357,   358,   358,   359,   359, 
    1114      359,   360,   360,   361,   361,   361,   361,   361,   361,   361, 
    1115      361,   361,   361,   361,   361,   361,   361,   361,   361,   361, 
    1116      362,   362,   363,   363,   364,   364,   364,   364,   364,   365, 
    1117      365,   365,   366,   366,   366,   366,   366,   366,   366,   366, 
    1118      366,   366,   367,   367,   367,   368,   368,   369,   369,   370, 
    1119      370,   371,   372,   372,   373,   373,   374,   374 
     1442       0,   203,   204,   204,   205,   205,   205,   206,   206,   206, 
     1443     206,   206,   207,   207,   207,   208,   208,   208,   209,   210, 
     1444     210,   210,   211,   211,   212,   213,   213,   214,   214,   214, 
     1445     214,   214,   215,   215,   216,   216,   216,   216,   216,   216, 
     1446     216,   216,   216,   216,   216,   216,   216,   216,   216,   216, 
     1447     216,   216,   216,   216,   216,   217,   217,   217,   217,   218, 
     1448     218,   219,   219,   219,   220,   221,   221,   222,   221,   223, 
     1449     221,   224,   225,   224,   226,   227,   227,   228,   228,   229, 
     1450     229,   230,   230,   230,   230,   230,   230,   230,   231,   232, 
     1451     232,   232,   232,   232,   232,   232,   232,   233,   233,   233, 
     1452     233,   234,   234,   235,   235,   236,   237,   237,   238,   238, 
     1453     239,   239,   240,   240,   240,   240,   240,   240,   240,   240, 
     1454     240,   240,   240,   240,   241,   241,   242,   243,   243,   244, 
     1455     244,   245,   245,   246,   246,   247,   248,   248,   249,   249, 
     1456     250,   250,   251,   251,   251,   251,   251,   251,   251,   251, 
     1457     251,   252,   252,   252,   252,   252,   253,   253,   253,   253, 
     1458     253,   253,   253,   253,   253,   253,   253,   253,   253,   253, 
     1459     253,   253,   253,   253,   253,   253,   253,   253,   253,   253, 
     1460     253,   254,   255,   256,   256,   257,   257,   257,   257,   257, 
     1461     258,   259,   259,   260,   260,   261,   261,   262,   263,   263, 
     1462     263,   265,   264,   264,   264,   267,   266,   268,   266,   269, 
     1463     266,   270,   266,   271,   266,   272,   266,   273,   273,   274, 
     1464     274,   274,   275,   275,   276,   276,   277,   277,   278,   278, 
     1465     279,   279,   280,   281,   281,   281,   282,   282,   282,   283, 
     1466     283,   284,   284,   285,   285,   285,   285,   285,   286,   286, 
     1467     286,   286,   287,   287,   288,   288,   288,   289,   289,   291, 
     1468     290,   292,   292,   293,   293,   294,   294,   295,   295,   296, 
     1469     297,   297,   298,   299,   299,   300,   300,   301,   301,   302, 
     1470     303,   304,   304,   304,   305,   305,   306,   306,   306,   306, 
     1471     307,   307,   308,   309,   309,   310,   310,   311,   311,   312, 
     1472     312,   312,   313,   314,   314,   315,   315,   316,   316,   317, 
     1473     317,   318,   318,   319,   319,   320,   320,   320,   321,   321, 
     1474     322,   323,   324,   325,   325,   326,   326,   327,   328,   328, 
     1475     329,   331,   332,   330,   333,   333,   334,   334,   335,   335, 
     1476     336,   336,   337,   336,   336,   338,   336,   336,   336,   336, 
     1477     336,   336,   336,   339,   339,   340,   341,   342,   343,   343, 
     1478     344,   344,   344,   345,   346,   346,   347,   348,   347,   349, 
     1479     349,   349,   349,   349,   350,   350,   351,   351,   352,   353, 
     1480     354,   354,   355,   355,   356,   356,   357,   358,   359,   359, 
     1481     360,   360,   361,   361,   362,   363,   363,   363,   365,   364, 
     1482     366,   366,   367,   367,   368,   368,   370,   369,   371,   371, 
     1483     372,   372,   373,   374,   374,   375,   375,   376,   376,   377, 
     1484     377,   378,   378,   379,   379,   379,   380,   381,   381,   381, 
     1485     381,   381,   381,   381,   381,   382,   382,   383,   383,   383, 
     1486     383,   383,   383,   383,   384,   385,   387,   388,   386,   390, 
     1487     389,   391,   389,   393,   394,   392,   395,   395,   396,   398, 
     1488     399,   397,   400,   400,   401,   401,   402,   402,   403,   403, 
     1489     403,   404,   405,   406,   407,   406,   408,   408,   409,   410, 
     1490     410,   411,   411,   412,   413,   413,   414,   414,   415,   416, 
     1491     417,   417,   419,   418,   420,   420,   421,   421,   421,   423, 
     1492     424,   422,   425,   425,   426,   426,   427,   427,   428,   428, 
     1493     429,   429,   430,   431,   430,   432,   432,   432,   432,   433, 
     1494     434,   435,   436,   437,   438,   439,   440,   441,   442,   443, 
     1495     443,   443,   444,   445,   446,   446,   447,   448,   447,   449, 
     1496     450,   451,   452,   452,   453,   453,   453,   454,   454,   454, 
     1497     454,   454,   454,   454,   454,   454,   454,   455,   455,   455, 
     1498     455,   455,   455,   456,   458,   459,   457,   460,   460,   461, 
     1499     461,   462,   462,   463,   464,   465,   465,   466,   467,   467, 
     1500     468,   468,   469,   469,   470,   471,   471,   472,   473,   475, 
     1501     476,   474,   477,   477,   478,   478,   479,   479,   480,   480, 
     1502     481,   481,   481,   481,   481,   482,   483,   483,   484,   484, 
     1503     485,   485,   485,   485,   485,   486,   487,   487,   488,   488, 
     1504     489,   489,   490,   491,   491,   492,   492,   492,   492,   492, 
     1505     492,   492,   492,   492,   492,   492,   492,   493,   493,   494, 
     1506     494,   495,   495,   496,   496,   497,   498,   499,   500,   500, 
     1507     501,   502,   503,   504,   505,   505,   506,   507,   508,   509, 
     1508     510,   511,   512,   513,   513,   514,   514,   514,   515,   515, 
     1509     516,   516,   517,   517,   518,   519,   520,   521,   522,   523, 
     1510     523,   523,   524,   525,   526,   526,   527,   527,   528,   528, 
     1511     529,   530,   530,   530,   531,   532,   533,   533,   534,   534, 
     1512     535,   535,   536,   537,   538,   538,   539,   539,   539,   540, 
     1513     540,   541,   541,   541,   541,   542,   542,   542,   542,   543, 
     1514     543,   543,   543,   544,   544,   544,   544,   545,   546,   547, 
     1515     547,   548,   548,   549,   549,   550,   551,   552,   552,   552, 
     1516     552,   552,   552,   552,   552,   552,   552,   552,   552,   552, 
     1517     552,   552,   552,   552,   553,   553,   554,   554,   555,   556, 
     1518     557,   557,   558,   559,   560,   560,   560,   561,   562,   562, 
     1519     562,   563,   564,   564,   565,   565,   566,   566,   567,   567, 
     1520     568,   569,   570,   570,   570,   571,   573,   572,   574,   572, 
     1521     575,   575,   577,   576,   578,   576,   580,   579,   579,   581, 
     1522     581,   582,   582,   582,   582,   583,   584,   584,   585,   586, 
     1523     587,   588,   588,   589,   589,   590,   590,   590,   591,   592, 
     1524     594,   595,   593,   596,   596,   597,   597,   597,   597,   597, 
     1525     597,   597,   597,   597,   597,   597,   598,   599,   601,   600, 
     1526     602,   602,   603,   603,   603,   603,   603,   604,   604,   604, 
     1527     604,   605,   605,   606,   606,   607,   607,   608,   609,   609, 
     1528     609,   609,   609,   609,   609,   609,   609,   609,   609,   610, 
     1529     610,   610,   611,   611,   612,   612,   613,   613,   614,   614, 
     1530     615,   616,   616,   617,   617,   618,   618,   619,   619,   620, 
     1531     620,   621,   621,   621,   621,   621,   622,   622,   623,   623, 
     1532     624,   624,   624,   624,   624,   626,   625,   627,   625,   628, 
     1533     629,   629,   630,   630,   630,   630,   630,   630,   630,   630, 
     1534     630,   630,   630,   631,   633,   632,   634,   634,   636,   635, 
     1535     638,   637,   639,   639,   640,   640,   641,   642,   642,   643, 
     1536     643,   644,   644,   645,   645,   646,   648,   647,   649,   647, 
     1537     650,   650,   650,   651,   651,   652,   653,   653,   241,   241, 
     1538     655,   654,   657,   658,   656,   659,   659,   660,   660,   661, 
     1539     662,   662,   663,   663,   664,   665,   665,   666,   666,   666, 
     1540     667,   668,   669,   669,   670,   670,   671,   672,   673,   673, 
     1541     674,   675,   676,   675,   678,   677,   679,   677,   680,   681, 
     1542     677,   683,   682,   684,   684,   684,   685,   685,   686,   686, 
     1543     687,   687,   687,   688,   688,   689,   689,   690,   690,   690, 
     1544     691,   693,   694,   692,   695,   696,   697,   697,   698,   700, 
     1545     699,   701,   701,   702,   704,   703,   705,   706,   707,   708, 
     1546     708,   709,   710,   709,   711,   711,   712,   712,   713,   713, 
     1547     714,   714,   716,   715,   717,   717,   718,   718,   718,   718, 
     1548     718,   719,   720,   720 
    11201549}; 
    11211550 
     
    11231552static const yytype_uint8 yyr2[] = 
    11241553{ 
    1125        0,     2,     0,     2,     1,     1,     2,     1,     2,     1, 
    1126        3,     2,     2,     1,     3,     3,     2,     2,     3,     1, 
    1127        0,     0,     1,     0,     2,     4,     2,     5,     2,     1, 
    1128        2,     1,     1,     0,     2,     3,     0,     2,     3,     1, 
    1129        3,     1,     1,     2,     4,     2,     2,     4,     2,     1, 
    1130        1,     1,     1,     1,     1,     1,     1,     1,     4,     3, 
    1131        3,     2,     2,     0,     1,     1,     1,     1,     1,     1, 
     1554       0,     2,     0,     2,     1,     1,     1,     2,     1,     1, 
     1555       3,     2,     1,     3,     3,     1,     3,     1,     0,     1, 
     1556       1,     1,     1,     1,     1,     0,     1,     1,     1,     2, 
     1557       2,     2,     1,     1,     2,     2,     2,     2,     2,     2, 
     1558       2,     2,     2,     3,     3,     2,     2,     2,     2,     2, 
     1559       2,     2,     2,     2,     2,     0,     1,     2,     2,     2, 
     1560       1,     1,     1,     1,     0,     1,     2,     0,     5,     0, 
     1561       6,     1,     0,     5,     4,     1,     2,     1,     3,     1, 
     1562       1,     3,     5,     4,     3,     2,     2,     1,     1,     1, 
     1563       1,     1,     1,     1,     1,     2,     2,     1,     2,     1, 
     1564       1,     0,     1,     0,     1,     2,     0,     1,     0,     1, 
     1565       1,     2,     1,     1,     1,     1,     1,     1,     1,     1, 
     1566       1,     1,     1,     1,     0,     1,     2,     0,     1,     1, 
     1567       2,     1,     1,     0,     1,     3,     0,     1,     1,     2, 
    11321568       1,     1,     1,     1,     1,     1,     1,     1,     1,     1, 
    11331569       1,     1,     1,     1,     1,     1,     1,     1,     1,     1, 
    1134        3,     3,     5,     1,     3,     3,     2,     4,     1,     3, 
    1135        0,     1,     2,     3,     1,     1,     2,     1,     3,     4, 
    1136        4,     8,     1,     3,     2,     3,     5,     3,     1,     0, 
    1137        2,     1,     4,     3,     2,     3,     3,     3,     3,     0, 
    1138        1,     2,     3,     5,     3,     1,     5,     5,     2,     3, 
    1139        2,     3,     1,     1,     3,     3,     2,     3,     5,     1, 
    1140        2,     1,     3,     2,     1,     3,     0,     1,     1,     3, 
    1141        3,     2,     1,     3,     2,     2,     5,     6,     0,     2, 
    1142        2,     3,     3,     0,     2,     4,     3,     3,     4,     2, 
    1143        1,     1,     1,     1,     1,     1,     1,     0,     2,     1, 
    1144        3,     0,     2,     3,     1,     3,     2,     3,     1,     1, 
    1145        1,     1,     1,     0,     3,     0,     1,     3,     1,     3, 
    1146        1,     1,     1,     2,     1,     4,     1,     1,     1,     1, 
    1147        1,     1,     1,     1,     1,     1,     0,     3,     1,     3, 
    1148        1,     1,     2,     2,     3,     1,     1,     1,     1,     1, 
    1149        3,     3,     3,     4,     4,     3,     4,     4,     3,     4, 
    1150        4,     4,     4,     4,     4,     4,     4,     4,     4,     4, 
    1151        4,     4,     3,     4,     3,     4,     4,     1,     3,     1, 
    1152        1,     1,     2,     2,     2,     1,     1,     2,     2,     2, 
    1153        2,     2,     2,     2,     2,     2,     3,     3,     2,     2, 
    1154        2,     2,     2,     2,     2,     2,     2,     2,     0,     1, 
    1155        2,     2,     2,     1,     1,     1,     1,     0,     1,     2, 
    1156        4,     5,     4,     4,     3,     1,     2,     1,     3,     1, 
    1157        1,     3,     5,     4,     3,     2,     2,     1,     1,     1, 
    1158        1,     1,     1,     1,     1,     2,     2,     1,     2,     1, 
    1159        1,     0,     1,     5,     0,     1,     1,     1,     0,     2, 
    1160        2,     5,     2,     4,     6,     6,     1,     1,     3,     3, 
    1161        1,     3,     3,     1,     1,     1,     1,     1,     1,     1, 
    1162        1,     1,     2,     1,     1,     2,     2,     2,     3,     2, 
    1163        5,     5,     2,     2,     2,     2,     1,     4,     1,     2, 
    1164        2,     2,     2,     1,     1,     1,     1,     5,     6,     0, 
    1165        3,     0,     4,     0,     4,     4,     1,     1,     1,     1, 
    1166        1,     3,     4,     1,     2,     1,     2,     0,     0,     2, 
    1167        3,     1,     4,     1,     1,     4,     2,     5,     3,     3, 
    1168        1,     4,     2,     6,     8,     5,     3,     1,     1,     1, 
    1169        1,     1,     2,     6,     0,     1,     2,     3,     0,     1, 
    1170        2,     3,     7,     5,     5,     6,     1,     2,     1,     2, 
    1171        5,     4,     0,     1,     2,     3,     6,     4,     2,     3, 
    1172        1,     2,     3,     1,     1,     3,     1,     2,     2,     3, 
    1173        1,     1,     1,     1,     1,     1,     1,     1,     1,     0, 
    1174        4,     7,     1,     3,     2,     2,     2,     0,     3,     0, 
    1175        1,     2,     2,     1,     1,     3,     1,     2,     1,     1, 
    1176        0,     1,     2,     2,     0,     2,     3,     3,     3,     1, 
    1177        3,     1,     1,     3,     1,     1,     1,     3,     5,     4, 
    1178        2,     2,     0,     1,     1,     1,     1,     1,     1,     1, 
    1179        1,     1,     3,     1,     1,     3,     3,     3,     3,     2, 
    1180        3,     2,     2,     2,     2,     2,     2,     2,     3,     1, 
    1181        1,     1,     1,     3,     2,     4,     2,     2,     5,     0, 
    1182        1,     2,     1,     1,     1,     1,     3,     3,     3,     3, 
    1183        3,     3,     5,     5,     5,     5,     7,     8,     2,     1, 
    1184        3,     1,     1,     3,     0,     4,     1,     3 
     1570       1,     1,     1,     1,     1,     1,     2,     4,     2,     1, 
     1571       1,     1,     1,     1,     1,     1,     1,     1,     1,     1, 
     1572       1,     1,     1,     1,     1,     1,     1,     1,     1,     1, 
     1573       1,     0,     1,     1,     1,     0,     1,     1,     1,     1, 
     1574       1,     0,     2,     3,     3,     0,     3,     0,     3,     0, 
     1575       3,     0,     3,     0,     3,     0,     3,     0,     1,     3, 
     1576       5,     2,     1,     2,     1,     3,     1,     1,     1,     2, 
     1577       1,     3,     5,     1,     1,     1,     1,     1,     1,     0, 
     1578       2,     0,     1,     1,     9,     5,     5,     9,     3,     5, 
     1579       2,     3,     3,     1,     1,     1,     1,     1,     1,     0, 
     1580       4,     4,     7,     0,     2,     0,     2,     1,     3,     1, 
     1581       1,     3,     1,     2,     3,     0,     1,     1,     2,     1, 
     1582       4,     0,     1,     3,     1,     3,     1,     1,     4,     1, 
     1583       1,     3,     4,     0,     3,     1,     1,     0,     1,     2, 
     1584       2,     2,     1,     1,     4,     1,     3,     1,     3,     3, 
     1585       4,     1,     3,     1,     3,     1,     1,     1,     3,     3, 
     1586       1,     1,     1,     1,     3,     1,     1,     5,     5,     7, 
     1587       1,     0,     0,     6,     0,     2,     0,     1,     2,     3, 
     1588       1,     1,     0,     5,     1,     0,     5,     1,     1,     1, 
     1589       1,     1,     1,     1,     3,     4,     1,     1,     0,     1, 
     1590       2,     2,     2,     1,     1,     1,     0,     0,     4,     1, 
     1591       1,     1,     1,     1,     1,     3,     3,     1,     1,     1, 
     1592       1,     3,     1,     2,     1,     3,     1,     3,     0,     2, 
     1593       0,     2,     1,     3,     2,     1,     1,     1,     0,     4, 
     1594       0,     2,     1,     3,     1,     1,     0,     5,     0,     1, 
     1595       2,     3,     4,     1,     3,     1,     3,     1,     1,     9, 
     1596      11,     1,     3,     1,     1,     1,     1,     2,     2,     2, 
     1597       1,     1,     1,     1,     1,     0,     2,     1,     1,     1, 
     1598       1,     1,     1,     1,     1,     1,     0,     0,     6,     0, 
     1599       5,     0,     7,     0,     0,     7,     1,     3,     3,     0, 
     1600       0,     6,     0,     1,     0,     1,     1,     3,     1,     1, 
     1601       1,     1,     0,     4,     0,     5,     1,     3,     4,     1, 
     1602       3,     1,     3,     7,     0,     6,     1,     3,     1,     3, 
     1603       1,     3,     0,     6,     1,     3,     1,     1,     1,     0, 
     1604       0,     7,     0,     1,     1,     3,     0,     1,     0,     4, 
     1605       1,     3,     1,     0,     5,     1,     1,     1,     1,     1, 
     1606       1,     1,     1,     1,     1,     1,     1,     1,     1,     1, 
     1607       4,     4,     3,     2,     0,     3,     1,     0,     5,     1, 
     1608       1,     1,     1,     4,     0,     1,     3,     2,     1,     2, 
     1609       3,     4,     2,     1,     3,     4,     2,     1,     2,     3, 
     1610       4,     2,     0,     1,     0,     0,     8,     0,     2,     1, 
     1611       3,     2,     3,     1,     1,     1,     3,     2,     1,     1, 
     1612       0,     3,     1,     3,     2,     0,     2,     1,     1,     0, 
     1613       0,     8,     1,     3,     0,     2,     1,     3,     2,     3, 
     1614       1,     1,     1,     1,     3,     1,     1,     3,     1,     3, 
     1615       1,     2,     3,     1,     2,     1,     1,     1,     1,     1, 
     1616       1,     3,     1,     1,     3,     1,     1,     1,     1,     1, 
     1617       1,     1,     1,     1,     1,     1,     1,     1,     2,     1, 
     1618       3,     1,     3,     1,     3,     1,     1,     1,     1,     1, 
     1619       1,     1,     1,     1,     0,     1,     1,     1,     1,     1, 
     1620       1,     1,     1,     4,     5,     5,     7,     4,     0,     3, 
     1621       1,     3,     1,     3,     2,     3,     1,     1,     3,     1, 
     1622       1,     1,     5,     5,     0,     2,     0,     3,     0,     3, 
     1623       5,     1,     1,     1,     1,     1,     4,     5,     2,     3, 
     1624       2,     3,     0,     1,     0,     2,     1,     1,     1,     3, 
     1625       3,     4,     2,     5,     3,     4,     2,     5,     3,     4, 
     1626       2,     5,     3,     6,     8,     5,     3,     1,     1,     1, 
     1627       2,     3,     4,     1,     1,     3,     2,     1,     1,     1, 
     1628       1,     1,     1,     1,     2,     4,     1,     1,     1,     1, 
     1629       1,     1,     1,     1,     4,     3,     2,     3,     3,     2, 
     1630       0,     1,     3,     5,     0,     1,     2,     2,     0,     1, 
     1631       2,     2,     8,     6,     6,     7,     2,     3,     2,     3, 
     1632       5,     3,     0,     1,     2,     2,     0,     8,     0,     6, 
     1633       3,     4,     0,     3,     0,     4,     0,     4,     1,     1, 
     1634       3,     1,     2,     2,     3,     1,     2,     3,     3,    10, 
     1635       3,     2,     3,     1,     1,     1,     1,     1,     1,     1, 
     1636       0,     0,     7,     1,     3,     1,     2,     2,     2,     2, 
     1637       2,     2,     2,     2,     2,     3,     1,     1,     0,     6, 
     1638       1,     3,     1,     2,     2,     2,     3,     5,     6,     4, 
     1639       6,     5,     6,     4,     6,     1,     3,     1,     1,     2, 
     1640       1,     1,     2,     2,     2,     2,     2,     2,     2,     1, 
     1641       1,     1,     1,     3,     1,     1,     1,     3,     1,     1, 
     1642       5,     1,     3,     1,     1,     5,     7,     3,     5,     1, 
     1643       3,     1,     2,     2,     2,     2,     3,     5,     1,     3, 
     1644       1,     2,     2,     2,     2,     0,     7,     0,     9,     0, 
     1645       1,     3,     1,     2,     2,     2,     2,     2,     2,     2, 
     1646       3,     2,     2,     2,     0,     5,     0,     1,     0,     4, 
     1647       0,     6,     0,     1,     0,     1,     2,     0,     1,     1, 
     1648       2,     1,     1,     1,     2,     0,     0,     8,     0,    11, 
     1649       0,     1,     3,     0,     1,     5,     0,     1,     0,     1, 
     1650       0,     4,     0,     0,     6,     0,     1,     0,     1,     1, 
     1651       0,     2,     1,     3,     3,     1,     3,     1,     1,     1, 
     1652       1,     1,     3,     4,     1,     3,     1,     4,     1,     3, 
     1653       1,     3,     0,     5,     0,     3,     0,     5,     0,     0, 
     1654       7,     0,     4,     1,     1,     1,     1,     3,     1,     3, 
     1655       1,     1,     1,     0,     1,     1,     2,     1,     1,     1, 
     1656       5,     0,     0,    10,     1,     1,     0,     1,     4,     0, 
     1657       7,     0,     1,     5,     0,     6,     1,     6,     0,     0, 
     1658       1,     0,     0,     4,     0,     1,     1,     3,     1,     1, 
     1659       3,     4,     0,     4,     1,     1,     3,     3,     1,     3, 
     1660       1,     0,     1,     3 
    11851661}; 
    11861662 
     
    11901666static const yytype_uint16 yydefact[] = 
    11911667{ 
    1192        2,     0,     1,     7,     9,   105,     0,     0,   482,     0, 
    1193        0,     0,     0,     0,    22,   344,   100,   100,     0,   540, 
    1194        0,     0,   156,   395,     0,     0,     0,   533,   534,   539, 
    1195        0,   535,   538,     0,     0,     0,   135,   100,   100,     0, 
    1196        0,   371,   118,     0,   503,   149,     0,   508,     0,   509, 
    1197      356,    21,    63,     0,     0,   183,   181,   182,   186,   483, 
    1198      486,   485,   484,   180,     0,   184,   185,   328,   492,    20, 
    1199        3,     4,     5,    13,     0,    20,    20,     0,     0,    50, 
    1200      119,    57,   156,    52,    54,    53,    49,     0,    56,    51, 
    1201      205,   173,   191,   489,    55,     0,    19,   364,   366,   394, 
    1202      370,     0,   367,   421,     0,   423,   424,   369,     0,   393, 
    1203      368,     0,   365,     0,   388,     0,     0,     0,   386,   374, 
    1204      497,     0,     0,     0,     0,   373,    32,    20,    31,    26, 
    1205        0,     0,     0,   275,   276,     0,     0,     0,     0,   331, 
    1206        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1207        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1208        0,     0,   334,   329,   330,     0,   337,   340,   339,   333, 
    1209      328,   332,     0,   346,   347,   239,   237,     0,   269,   306, 
    1210      308,   305,   271,   304,   270,   341,   384,   238,     0,    61, 
    1211       93,     0,   345,   382,   101,   140,     0,   138,     0,   383, 
    1212      588,     0,     0,   157,    29,   156,     0,   432,    28,   488, 
    1213      487,   392,     0,     0,   377,   521,   519,     0,   379,     0, 
    1214        0,     0,     0,   154,     0,     0,   131,     0,    46,   164, 
    1215      165,   150,   162,   161,     6,   224,   225,   100,    64,   200, 
    1216      198,   199,     0,    45,   121,     0,   156,   107,     0,     0, 
    1217        8,    11,    12,    20,    21,     0,     0,    16,    17,     0, 
    1218        0,    48,   158,    62,   119,     0,   226,   114,   119,   157, 
    1219        0,     0,     0,     0,   226,   146,   151,     0,     0,   104, 
    1220      206,    43,     0,   168,     0,     0,     0,   170,     0,     0, 
    1221      169,   226,   352,   399,   418,   418,   462,   390,   389,   391, 
    1222        0,     0,   532,   372,     0,   499,   496,   501,   502,   385, 
    1223      375,   560,   561,   537,     0,     0,     0,     0,     0,     0, 
    1224        0,   328,     0,   559,   543,   544,   376,   510,   514,     0, 
    1225      536,     0,    18,   410,     0,     0,   274,   267,     0,     0, 
    1226        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1227        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1228        0,     0,     0,     0,     0,   573,   574,   572,     0,   575, 
    1229        0,     0,   237,     0,     0,     0,     0,     0,     0,     0, 
    1230        0,     0,     0,     0,     0,     0,     0,     0,   298,     0, 
    1231        0,     0,   272,   273,   532,   344,   309,   307,   307,   335, 
    1232      338,   336,   342,     0,   226,     0,     0,   143,   142,   141, 
    1233      139,     0,     0,    30,   428,     0,   417,   437,     0,   591, 
    1234      594,   589,   525,   526,     0,   304,     0,   522,   524,   541, 
    1235      378,   332,   237,   304,   592,   594,   596,     0,    59,    66, 
    1236       67,    70,    65,    71,    68,    73,    74,    75,    76,    77, 
    1237       72,    78,    79,    80,    81,    82,    83,    84,    85,    86, 
    1238       87,    69,    88,    89,    60,     0,   132,     0,    98,     0, 
    1239        0,     0,     0,   202,   196,   201,   172,   129,     0,     0, 
    1240        0,     0,   129,     0,     0,   156,    10,    14,    15,    33, 
    1241       33,     0,     0,     0,   117,   156,     0,   120,   115,   134, 
    1242      156,   226,   226,   156,   153,     0,   147,   210,   212,   226, 
    1243      214,     0,   216,   217,   218,   219,   220,     0,   208,   211, 
    1244       33,     0,   102,   226,   174,     0,   328,     0,   203,   332, 
    1245        0,   192,   194,     0,   226,     0,   401,   438,     0,   444, 
    1246        0,     0,   463,     0,   494,   495,     0,   493,     0,   506, 
    1247        0,   500,   504,   551,   552,   554,   553,   557,   556,   555, 
    1248        0,   524,     0,   569,   569,   569,   512,   511,   562,     0, 
    1249      513,     0,     0,     0,     0,     0,   549,   405,   467,     0, 
    1250      242,     0,     0,     0,   241,   248,   245,     0,     0,     0, 
    1251        0,     0,     0,     0,     0,     0,     0,     0,     0,   262, 
    1252        0,   264,     0,     0,     0,   237,     0,     0,     0,     0, 
    1253      314,     0,     0,   240,     0,     0,   303,   297,   292,   282, 
    1254      293,   294,   295,   291,   281,   289,   290,   283,   288,   277, 
    1255      278,   279,     0,     0,   299,   296,   280,     0,   285,     0, 
    1256      284,     0,     0,   315,     0,     0,     0,    95,    96,    94, 
    1257       58,     0,     0,     0,     0,   436,     0,     0,     0,     0, 
    1258      530,   531,   307,   226,     0,   516,   518,   520,   517,     0, 
    1259        0,     0,   387,     0,   155,     0,    91,     0,   163,    44, 
    1260      197,     0,   112,     0,   130,     0,     0,   108,   121,   123, 
    1261        0,     0,     0,   156,   431,     0,    25,    23,   160,    47, 
    1262      159,   119,   231,   235,     0,   228,   230,   236,     0,   187, 
    1263      187,     0,   152,   213,     0,     0,   207,   103,   226,   187, 
    1264        0,     0,   203,   176,     0,   179,     0,   193,   490,     0, 
    1265        0,   353,   357,   396,   409,   407,   408,   403,     0,   406, 
    1266      419,   441,   481,   422,   439,   440,     0,   448,   445,     0, 
    1267      473,     0,   468,   470,   464,   461,   418,   489,   507,   498, 
    1268        0,   558,   542,     0,   570,   566,   564,   567,     0,   515, 
    1269      550,   546,   547,   548,   545,   397,   268,   243,   244,   247, 
    1270      251,   252,   253,   254,   255,   250,   256,   257,   258,   259, 
    1271      260,   261,   263,   265,   266,   246,     0,     0,     0,   576, 
    1272      577,   580,   581,   578,   579,   249,   237,   302,   300,   301, 
    1273      287,   286,   313,   344,   327,   319,   316,   317,   320,   310, 
    1274      312,   226,   145,   144,     0,     0,   453,     0,   460,     0, 
    1275        0,     0,   590,   380,     0,     0,   532,   527,   523,   593, 
    1276      381,   597,    90,    99,     0,   109,   129,   129,   129,   129, 
    1277      129,   124,   122,     0,     0,   110,     0,     0,   427,    42, 
    1278       41,    34,     0,    39,    36,    27,   116,   233,     0,   227, 
    1279      232,   133,     0,   136,   137,   148,   222,   223,   221,     0, 
    1280      209,   187,   348,   175,   203,   177,     0,   195,     0,     0, 
    1281        0,     0,     0,     0,   400,   420,   442,     0,   456,   446, 
    1282        0,   449,     0,   418,     0,   480,     0,   474,   476,   469, 
    1283      471,   465,   226,   505,     0,   569,   571,   563,   328,     0, 
    1284        0,     0,   351,     0,     0,   325,   326,     0,   311,    97, 
    1285        0,     0,     0,   435,     0,     0,   529,     0,    92,   113, 
    1286      125,   126,   127,   128,     0,     0,   466,     0,     0,    35, 
    1287        0,    24,   229,   234,   236,     0,   188,   189,   215,   348, 
    1288        0,     0,   166,   178,   204,   363,   354,   355,   360,   359, 
    1289      358,     0,   413,   415,     0,   398,   399,     0,   457,   458, 
    1290      450,   443,   418,   447,   478,     0,   472,   477,   226,     0, 
    1291      565,   582,   583,   584,   343,   324,     0,   321,   318,     0, 
    1292        0,     0,   433,   595,   528,     0,   129,   452,    40,    37, 
    1293        0,     0,   167,   349,   350,     0,     0,   411,   414,   416, 
    1294      399,   402,     0,   459,   451,   475,   479,   491,   568,   323, 
    1295        0,   587,     0,     0,     0,     0,     0,    38,   190,   362, 
    1296      361,   412,   404,   454,   322,   434,   585,   111,   455,     0, 
    1297      586 
     1668       2,     0,     1,     6,     8,     0,     0,    17,     9,  1019, 
     1669    1018,     0,    18,     3,     4,     5,    12,    15,    20,  1017, 
     1670       0,    21,   106,    19,   106,     0,   201,  1015,    22,   106, 
     1671      23,   106,    24,    18,   960,   928,   207,   205,   215,   209, 
     1672     213,   211,    88,   303,     0,     0,     7,    11,    18,   201, 
     1673     202,   957,   108,     0,   107,   943,   191,   191,     0,     0, 
     1674    1018,  1016,   191,   191,    16,     0,     0,   217,   217,   217, 
     1675     217,   241,   217,     0,   203,   204,    10,    13,    14,   453, 
     1676       0,     0,   364,   365,    25,     0,   462,     0,   499,   193, 
     1677      25,   263,   254,   256,     0,   255,    88,   194,   536,   105, 
     1678     109,   110,   116,     0,   192,     0,   112,   259,   117,   201, 
     1679     400,   142,   144,   145,     0,   113,   150,     0,     0,   115, 
     1680     149,   146,   143,   520,     0,   518,   529,   534,   517,   515, 
     1681     516,   118,   119,   120,   706,   704,   704,   707,   733,   734, 
     1682     121,   123,   114,   147,   148,   122,   945,   944,     0,   192, 
     1683     924,   927,   201,     0,     0,   103,     0,     0,     0,     0, 
     1684       0,     0,   909,     0,     0,     0,     0,     0,    88,   133, 
     1685     125,   191,   151,     0,   156,   162,   157,   172,   178,   155, 
     1686     684,   152,   161,   154,   704,   169,   153,   782,   164,   163, 
     1687     180,   160,   177,   171,   159,   174,   179,   173,   176,   165, 
     1688     170,   158,   994,   175,  1036,  1041,  1024,     0,   133,   133, 
     1689     961,   929,     0,     0,   208,   218,   206,   216,   210,     0, 
     1690       0,   214,   242,   243,   212,   200,   645,   618,   619,   199, 
     1691    1004,     0,   257,   258,  1005,   230,   224,     0,   321,   536, 
     1692       0,   601,   307,   613,   185,   186,   188,   189,   187,     0, 
     1693     305,   602,     0,   600,   605,   606,   608,   610,   620,     0, 
     1694     623,   637,   639,   641,   643,   650,     0,   653,   656,   198, 
     1695     603,     0,     0,   923,   492,     0,   490,    26,   720,     0, 
     1696       0,     0,   986,     0,   984,   463,     0,     0,   502,   712, 
     1697       0,     0,     0,     0,     0,   506,     0,   413,   418,   520, 
     1698     417,     0,   537,   111,     0,     0,     0,     0,   654,   201, 
     1699     334,   398,     0,   462,   462,   201,     0,     0,     0,     0, 
     1700     654,   533,   728,   191,   195,   195,   950,  1052,   472,   936, 
     1701     201,   939,   941,   942,     0,     0,    88,   536,   166,   104, 
     1702       0,     0,   806,     0,  1055,  1054,   168,   564,   820,   838, 
     1703       0,     0,   818,     0,     0,     0,   589,     0,   811,   652, 
     1704     660,   662,   813,   659,   814,   661,     0,     0,     0,   962, 
     1705     134,   126,   191,   129,   131,   132,     0,     0,     0,     0, 
     1706    1001,     0,   686,   764,     0,     0,   783,   704,   998,     0, 
     1707    1042,  1034,  1021,   472,   472,   221,     0,     0,     0,   253, 
     1708     250,     0,     0,     0,     0,     0,   320,   323,   326,   325, 
     1709       0,     0,   536,   613,   234,   186,     0,     0,     0,     0, 
     1710       0,   304,     0,   615,     0,   616,   617,     0,   614,   222, 
     1711       0,   185,   611,   626,   625,   630,   628,   629,   627,   622, 
     1712     631,   632,   634,   636,   633,   635,     0,     0,   646,     0, 
     1713     647,     0,   649,   648,     0,   638,   992,     0,     0,     0, 
     1714     489,     0,   702,   727,     0,   722,     0,     0,   982,   990, 
     1715       0,   988,     0,   504,     0,     0,   503,   714,   266,   267, 
     1716     269,     0,   264,     0,   425,     0,   421,   540,   424,   539, 
     1717     423,   507,   406,   506,     0,     0,     0,    25,    25,   544, 
     1718    1050,     0,   871,   224,   870,   652,   869,     0,   810,     0, 
     1719       0,     0,   655,   281,     0,   201,   277,   279,     0,     0, 
     1720       0,   337,     0,   404,   401,   402,   405,     0,   464,   474, 
     1721       0,     0,   476,    88,   600,     0,   519,   679,   680,   681, 
     1722       0,     0,   587,     0,     0,   670,   672,     0,     0,     0, 
     1723       0,   705,   197,    25,     0,     0,   191,   704,   709,   729, 
     1724     735,     0,   755,   191,   710,     0,   951,     0,     0,     0, 
     1725     925,   940,   695,     0,     0,   762,   807,   808,     0,     0, 
     1726       0,     0,     0,     0,     0,     0,   653,   900,     0,   898, 
     1727     896,     0,     0,     0,     0,   891,     0,   889,   887,     0, 
     1728    1062,     0,   812,     0,   201,   955,     0,   130,     0,   816, 
     1729       0,     0,     0,     0,     0,     0,     0,     0,    88,   524, 
     1730     819,   858,   815,   817,     0,   861,   855,   860,     0,     0, 
     1731       0,     0,     0,   694,   692,   693,   688,   685,   691,     0, 
     1732     768,   765,   704,   798,   796,     0,   792,   784,   781,   785, 
     1733     996,     0,   995,  1044,     0,  1044,     0,  1020,     0,  1033, 
     1734       0,   219,     0,     0,     0,     0,   248,     0,   325,   318, 
     1735       0,   227,   226,   231,   225,     0,   186,   604,   308,   306, 
     1736     322,   319,   185,   607,   609,   612,   621,   624,   640,   642, 
     1737     644,   991,     0,     0,     0,   456,   521,     0,   496,   498, 
     1738     529,   497,   491,     0,   726,     0,   983,   985,     0,   987, 
     1739       0,     0,   512,   508,   510,     0,   261,     0,     0,     0, 
     1740       0,   410,   414,   536,   430,   222,   431,   228,   435,   433, 
     1741       0,   434,   432,     0,   415,   435,   444,   302,     0,   363, 
     1742     719,     0,   711,     0,   548,     0,     0,   536,     0,   545, 
     1743     553,   562,   563,  1051,     0,   853,     0,   531,   654,     0, 
     1744     282,     0,     0,   260,   278,   349,   341,     0,   344,     0, 
     1745     347,   348,   350,   351,   352,   338,   340,   357,   332,   353, 
     1746     366,   335,     0,   399,     0,     0,   447,   356,   468,   460, 
     1747     465,   466,   469,   470,     0,     0,   201,   473,     0,   667, 
     1748     674,     0,   669,     0,     0,   676,     0,   663,   530,   535, 
     1749     716,     0,     0,     0,     0,     0,     0,     0,   737,   741, 
     1750     738,   752,   736,   746,   743,   730,   748,   740,   750,   753, 
     1751     749,   751,   742,   747,   739,   756,   704,   754,     0,   969, 
     1752       0,   970,  1053,   932,     0,   788,   578,   540,   579,   567, 
     1753     575,   580,     0,     0,     0,     0,     0,     0,     0,     0, 
     1754       0,     0,   825,     0,   823,     0,     0,     0,     0,   842, 
     1755       0,   840,     0,     0,     0,     0,     0,     0,     0,     0, 
     1756       0,     0,     0,   912,     0,   910,   901,   904,   528,   902, 
     1757     527,   526,   837,   525,   903,     0,     0,   892,   895,   894, 
     1758     893,     0,     0,   592,   594,     0,   167,     0,   135,   201, 
     1759     138,   140,   141,   965,   191,   868,   816,   859,   863,   857, 
     1760     862,   864,   865,   866,   867,     0,     0,     0,     0,   849, 
     1761    1003,  1002,     0,     0,     0,   684,     0,     0,   766,     0, 
     1762     769,   704,   767,     0,     0,   790,   794,     0,     0,   536, 
     1763       0,  1011,  1010,     0,  1006,  1008,  1049,  1025,  1048,     0, 
     1764    1045,  1046,  1035,     0,  1031,  1039,     0,   252,     0,     0, 
     1765       0,     0,   324,   190,   238,   236,   237,     0,     0,     0, 
     1766       0,   454,     0,   654,     0,     0,   989,   521,   484,   486, 
     1767     488,   505,   513,     0,   500,   268,   272,     0,   270,   536, 
     1768     422,     0,   426,   407,   411,   537,     0,   428,   429,     0, 
     1769       0,   412,   427,   223,   229,   721,   713,     0,   549,   556, 
     1770     552,     0,     0,   538,   557,     0,   547,     0,   878,     0, 
     1771     876,   879,   664,   532,   287,     0,   289,     0,   284,   286, 
     1772     293,     0,   290,     0,   273,   342,   345,     0,     0,   367, 
     1773     239,   339,   403,   449,     0,     0,     0,     0,   475,   481, 
     1774       0,   479,   477,   677,   678,   675,   588,     0,   671,     0, 
     1775     673,     0,   665,   718,    25,     0,   731,     0,  1060,  1058, 
     1776       0,   744,     0,     0,   191,   758,   757,   952,     0,   946, 
     1777     933,   934,   690,   682,     0,     0,     0,     0,   577,   836, 
     1778     651,   830,   827,   828,   831,   834,     0,   826,   829,   833, 
     1779     832,     0,   821,     0,   843,   845,   844,     0,     0,   914, 
     1780       0,     0,   915,   916,   922,   913,   523,   921,   522,   917, 
     1781     919,   918,     0,   905,   899,   897,   890,   888,     0,     0, 
     1782    1063,     0,   139,   966,   967,     0,   780,     0,   192,   856, 
     1783     851,     0,     0,   847,   874,     0,   872,   875,     0,     0, 
     1784       0,     0,     0,   684,   683,   687,     0,     0,   776,     0, 
     1785     770,   763,   771,     0,   805,     0,   799,   801,   791,     0, 
     1786     793,   997,     0,     0,   999,  1043,     0,  1026,  1032,   934, 
     1787    1040,   934,   220,     0,   249,     0,   246,   245,   536,     0, 
     1788       0,   330,   232,   993,   658,   458,   457,     0,     0,   494, 
     1789       0,   725,     0,     0,   506,   388,   511,     0,     0,     0, 
     1790       0,     0,     0,   190,   437,   182,   183,   184,   439,   440, 
     1791     442,   443,   441,   436,   438,   309,     0,     0,   311,   313, 
     1792     676,   315,   316,   317,   416,   550,     0,     0,   554,   546, 
     1793       0,   558,   561,   878,   883,   884,   875,     0,   881,     0, 
     1794     854,     0,     0,   283,     0,   239,     0,   280,   274,   388, 
     1795       0,   354,   333,   388,     0,   358,   388,     0,   448,   461, 
     1796     467,     0,     0,   478,   674,     0,     0,   715,     0,   732, 
     1797       0,     0,    32,    33,    91,    71,    94,   257,   258,   254, 
     1798     256,   255,   230,   224,     0,     0,    27,    63,    65,    62, 
     1799     536,    28,   101,   653,     0,     0,   759,     0,     0,   971, 
     1800     972,     0,   935,   930,   789,     0,     0,   568,   569,   576, 
     1801     565,     0,   582,     0,     0,   835,   824,     0,   846,   841, 
     1802     839,   920,     0,   911,     0,     0,     0,   593,   595,   596, 
     1803     590,   786,   968,   963,   773,     0,     0,   852,     0,   848, 
     1804     850,     0,     0,     0,   698,     0,   700,   689,     0,   777, 
     1805       0,   778,   803,     0,   797,   802,   795,   536,  1009,  1007, 
     1806       0,  1047,     0,  1022,  1027,  1038,  1038,     0,     0,   327, 
     1807       0,   455,     0,   493,   530,   723,   487,   483,     0,   382, 
     1808       0,   369,   374,     0,   377,   370,   380,   371,   384,   372, 
     1809     390,     0,   373,   392,   657,   379,   501,     0,   271,   262, 
     1810       0,   235,   233,     0,     0,   310,   551,   555,   559,     0, 
     1811       0,   877,   386,     0,   295,     0,   296,   285,     0,   297, 
     1812     291,     0,   396,   397,   395,     0,     0,   240,     0,     0, 
     1813     355,   359,     0,   451,   482,   480,   666,   717,     0,    31, 
     1814    1057,  1059,    30,  1061,    66,   529,    67,    72,  1056,    95, 
     1815      98,    96,   102,     0,     0,     0,     0,     0,     0,     0, 
     1816       0,     0,     0,     0,     0,     0,     0,     0,    55,     0, 
     1817       0,     0,    29,   745,   191,   953,     0,     0,   947,     0, 
     1818     574,   571,     0,     0,     0,     0,   581,   584,   586,   822, 
     1819     907,   906,   598,     0,     0,     0,     0,     0,     0,     0, 
     1820     873,     0,     0,   696,   699,   701,     0,   779,   800,   804, 
     1821    1000,     0,     0,  1029,     0,     0,     0,     0,   495,     0, 
     1822       0,   514,   389,   383,     0,     0,     0,     0,   378,   394, 
     1823     390,   509,     0,   314,   312,   560,     0,   882,     0,   288, 
     1824       0,     0,   294,     0,     0,   292,   298,   343,   346,   368, 
     1825     360,   362,   361,   302,   450,   388,     0,    64,    64,    64, 
     1826       0,    54,    60,    49,    39,    50,    51,    52,    48,    38, 
     1827      46,    47,    40,    45,    34,    35,    36,     0,     0,    53, 
     1828      56,    37,     0,    42,     0,    41,   980,   948,   979,   954, 
     1829     975,   978,   977,   974,   973,   931,   573,   572,   570,   566, 
     1830     583,     0,   599,   597,   591,   787,   964,   191,     0,   772, 
     1831     697,     0,   774,     0,  1023,     0,  1037,     0,     0,     0, 
     1832     724,     0,   375,   376,   379,   382,     0,   381,   385,   391, 
     1833     387,   393,     0,     0,   880,   299,   301,   300,     0,    74, 
     1834      61,    75,     0,     0,     0,    59,    57,    58,    44,    43, 
     1835       0,     0,   908,     0,   775,  1028,  1030,   244,   247,   328, 
     1836       0,   383,     0,   419,     0,   452,    72,    87,    76,    77, 
     1837      80,    79,    68,     0,    73,   949,   976,   809,     0,   485, 
     1838       0,     0,     0,    85,     0,    86,    70,   329,   420,   885, 
     1839      84,     0,    78,    81,     0,    83,     0,   886,    82 
    12981840}; 
    12991841 
     
    13011843static const yytype_int16 yydefgoto[] = 
    13021844{ 
    1303       -1,     1,    70,    71,    72,    73,   250,    74,   865,    75, 
    1304      205,   129,   127,   696,   951,   862,   863,    76,   237,   463, 
    1305      464,   228,   189,   190,   403,   467,   196,   281,   282,    77, 
    1306       78,   246,   247,   681,    79,    80,   267,   248,   682,   683, 
    1307       81,    82,    83,    84,    85,   409,    86,    87,   275,   276, 
    1308      225,   206,   261,   262,    88,   233,    89,   283,   522,    90, 
    1309      287,   527,    91,    92,   873,   956,   290,   531,   242,   528, 
    1310      725,   284,   517,   518,   879,   519,   497,   704,   705,   706, 
    1311      337,   175,   338,   176,   177,   392,   635,   617,   178,   643, 
    1312      179,   180,   181,   182,   645,   816,   817,   818,   183,   184, 
    1313      185,   401,   396,   193,   186,   962,   187,    94,    95,   731, 
    1314      732,   967,   968,   740,    97,    98,   734,    99,   100,   536, 
    1315      737,   892,   101,   738,   739,   334,   893,   974,   975,   655, 
    1316      537,   102,   103,   104,   105,   106,   207,   418,   538,   743, 
    1317      744,   107,   747,   748,   900,   901,   108,   749,   902,   981, 
    1318      109,   110,   541,   542,   111,   543,   755,   752,   906,   907, 
    1319      908,   745,   112,   113,   114,   115,   116,   211,   291,   117, 
    1320      118,   303,   119,   306,   550,   120,   121,   551,   552,   122, 
    1321      566,   326,   570,   214,   218,   426,   427,   546,   123,   328, 
    1322      124,   428,   429,   331,   567,   568,   765,   368,   369,   854, 
    1323      125,   420,   421,   435,   658,   437 
     1845      -1,     1,    13,    14,    15,    16,    46,    17,    18,    33, 
     1846     279,  1304,  1305,  1492,  1599,  1581,  1306,  1661,  1307,  1577, 
     1847    1578,  1308,  1579,  1309,  1662,  1688,  1689,  1690,   337,  1311, 
     1848    1312,  1471,   338,    51,    52,    99,   100,   101,   169,   170, 
     1849     371,   372,   373,   369,   370,   908,   909,   910,   102,   171, 
     1850     172,   240,  1224,  1225,   241,   974,   173,   104,   555,  1084, 
     1851     242,    19,    20,    44,    68,    67,    70,    72,    71,    69, 
     1852     214,   215,   243,   244,   673,   414,   245,   246,   416,   977, 
     1853    1275,   221,   222,   223,   400,   247,   248,   106,   309,   107, 
     1854     292,   293,   478,   479,   997,   998,   763,   514,   515,   516, 
     1855     517,   761,  1037,  1038,  1041,  1042,  1265,  1433,  1565,  1566, 
     1856     729,   730,   249,   250,   731,  1237,  1238,  1239,   251,   405, 
     1857     252,   681,   406,   407,   408,  1199,  1200,   108,   109,  1048, 
     1858     519,   520,   521,   775,  1269,  1270,   778,   779,   788,   780, 
     1859    1450,  1451,   732,   110,  1050,  1273,  1400,  1401,  1402,  1403, 
     1860    1404,  1405,  1406,  1407,  1408,  1409,  1410,  1411,  1412,  1413, 
     1861    1445,   111,   522,   311,   524,   525,   112,   719,   492,   493, 
     1862     295,   296,   733,   297,   298,   485,   486,  1001,   734,  1007, 
     1863    1233,   735,   736,   113,   114,  1055,   786,  1276,  1575,   115, 
     1864     272,  1207,   694,   695,   116,   117,  1056,   286,   789,   790, 
     1865     791,   792,    53,   119,   794,   531,   532,  1060,  1061,   120, 
     1866    1214,   988,   989,   121,   275,   276,   458,  1208,   697,   122, 
     1867     288,  1217,   475,   793,   494,   994,   713,   714,  1215,   253, 
     1868     535,   124,   846,  1127,  1128,   620,   892,   893,  1616,   890, 
     1869     125,   510,   126,   321,   127,   499,   488,   128,   129,   130, 
     1870     748,   749,  1026,   750,   174,   578,  1504,  1096,  1327,  1328, 
     1871    1617,  1501,   849,   850,   851,  1098,  1331,  1332,  1333,  1334, 
     1872    1065,   175,   599,  1515,   904,  1139,  1348,  1349,   254,   255, 
     1873     256,   257,   258,   424,   427,   259,   260,   446,   261,   447, 
     1874     262,   263,   264,   265,   266,   449,   451,   454,   267,  1099, 
     1875    1100,   268,   511,   352,  1415,  1205,   362,   363,   364,   365, 
     1876     176,   177,   318,   543,   544,   545,   546,  1242,   538,   539, 
     1877    1243,   178,   179,   382,   636,   934,   180,   637,   638,   573, 
     1878     935,  1163,  1164,   704,   322,   323,   181,   134,   135,   557, 
     1879     136,   280,   464,   324,   558,   559,   137,   138,   560,   822, 
     1880     139,   561,   562,  1085,   340,   182,   183,   640,   641,   939, 
     1881     940,   184,   642,   941,  1171,   185,   186,   385,   386,   187, 
     1882    1516,  1094,   387,   648,   947,  1179,   645,   943,  1175,  1176, 
     1883    1177,   188,   189,   190,   191,   192,   366,   621,   622,   623, 
     1884     193,   579,  1337,   863,   864,  1101,   894,   194,   580,   870, 
     1885     871,   195,   196,   197,   624,   625,   626,   627,  1155,  1254, 
     1886    1029,  1030,  1031,  1257,  1258,  1558,   198,   596,   597,   199, 
     1887     588,   589,   200,  1344,  1621,   350,   884,   885,   375,    21, 
     1888     328,   150,    22,    66,   570,  1499,  1091,  1323,   151,   329, 
     1889     330,   331,    54,   326,    55,  1321,  1670,   567,  1607,    23, 
     1890      56,    24,    65,   605,   606,  1517,  1144,  1353,   840,  1089, 
     1891    1319,  1608,  1609,  1610,  1611,   526,   143,   283,   284,   144, 
     1892     470,   471,   270,   692,   201,   389,   948,   651,  1380,   202, 
     1893     630,   271,   953,   954,   955,    25,    26,    27,    28,    29, 
     1894     655,  1532,   207,   958,  1383,  1384,   657,  1635,  1189,    30, 
     1895      31,   654,   205,   659,  1533,  1191,   391,   653,   959,   960, 
     1896     961,   203,   152,   568,   346,  1081,  1576,   601 
    13241897}; 
    13251898 
    13261899/* YYPACT[STATE-NUM] -- Index in YYTABLE of the portion describing 
    13271900   STATE-NUM.  */ 
    1328 #define YYPACT_NINF -845 
     1901#define YYPACT_NINF -1394 
    13291902static const yytype_int16 yypact[] = 
    13301903{ 
    1331     -845,   967,  -845,  -845,  -845,  -845,   -22,    45,  -845,    94, 
    1332      186,  3621,   199,   238,  -845,  4658,    16,    36,  3621,  -845, 
    1333      369,   256,    56,  -845,   299,   280,   268,  -845,  -845,  -845, 
    1334      306,  -845,  -845,   409,   311,   350,  -845,   357,   357,   119, 
    1335      354,  -845,  -845,    53,  -845,  -845,   420,  -845,   386,  -845, 
    1336     -845,  5758,   363,   274,   280,  -845,  -845,  -845,  -845,  -845, 
    1337     -845,  -845,  -845,  -845,   237,  -845,  -845,   549,  -845,  -845, 
    1338     -845,   122,   563,  -845,   440,  -845,  -845,   319,   433,   436, 
    1339      159,   495,   622,   624,  -845,  -845,   523,   329,  -845,  -845, 
    1340      398,   102,   163,  -845,  -845,   471,  -845,  -845,  -845,  -845, 
    1341     -845,   215,  -845,  -845,   215,  -845,  -845,  -845,   215,  -845, 
    1342     -845,   215,  -845,   280,  -845,   280,   280,    20,   630,  -845, 
    1343      472,    44,  3621,   306,  5477,  -845,  -845,  -845,  -845,  -845, 
    1344     4658,  4658,  4658,  -845,  -845,  4658,   473,   474,   477,  -845, 
    1345     4658,  4658,  4658,   478,   484,   486,   487,   488,   494,   496, 
    1346      497,   498,   499,   500,   501,  4658,   505,  4658,   507,   508, 
    1347      511,  4767,  -845,  -845,  -845,   512,  -845,  -845,  -845,  -845, 
    1348     -845,  -845,  4658,  -845,  2490,  -845,  -845,  4658,   470,  -845, 
    1349      513,   515,  -845,   516,   522,   270,  -845,  -845,   524,   654, 
    1350     -845,  4658,  2490,  -845,  -845,  -845,   277,  -845,   277,  -845, 
    1351     -845,  4658,  4658,  -845,  -845,   110,   326,  -845,  -845,  -845, 
    1352     -845,  -845,   524,  5347,  4767,  -845,  -845,  4876,  -845,   524, 
    1353      524,   277,  2573,  -845,   527,   524,  -845,  4658,   665,  -845, 
    1354     -845,  -845,  -845,   680,   563,  -845,  -845,   357,  -845,  -845, 
    1355     2967,  -845,   526,  -845,    88,   524,    32,  -845,   384,    82, 
    1356     -845,  -845,  -845,  -845,  5621,    45,    45,  -845,  -845,   687, 
    1357      533,   691,  -845,  -845,   535,   442,   534,  -845,   535,   524, 
    1358      442,   537,   539,   442,   534,   699,  -845,   545,   847,  -845, 
    1359     -845,  -845,    45,   714,   564,   434,  3874,  -845,  4985,   274, 
    1360     -845,   534,   727,   122,   122,   122,   258,  -845,  -845,  -845, 
    1361     4658,  4658,  -845,  -845,   571,  3983,  -845,  -845,  -845,  -845, 
    1362     -845,  -845,  -845,  -845,  4658,  4658,  4658,  4658,  4658,  4658, 
    1363     4658,   726,  5347,  -845,   470,   522,  -845,  1249,   730,   555, 
    1364      561,  5523,  -845,  2490,   572,  1332,   875,  2490,    38,  4658, 
    1365     4658,  4658,    48,  1353,    61,  4658,  4658,  4658,  4658,  4658, 
    1366     4658,  4658,  4658,  4658,  4658,  4658,  4658,  1514,  4658,    68, 
    1367     4658,  4658,  4658,  4767,  2490,  1533,   753,  1552,   278,   731, 
    1368     4658,  1616,   733,  3294,  4658,  4658,  4658,  4658,  4658,  4658, 
    1369     4658,  4658,  4658,  4658,  4658,  4658,  4658,  4658,  3076,  4658, 
    1370     3403,  3512,  -845,   185,  -845,  4658,  -845,  -845,  -845,  -845, 
    1371     -845,  -845,  -845,    69,   534,   199,  1635,  -845,  -845,   734, 
    1372      734,  1129,  1713,  -845,  -845,   576,  -845,  -845,   736,   470, 
    1373      739,  -845,  -845,  -845,  5523,  3765,    79,  -845,   555,  -845, 
    1374      740,   581,   582,   439,  -845,   743,  -845,   105,   734,  -845, 
    1375     -845,  -845,  -845,  -845,  -845,  -845,  -845,  -845,  -845,  -845, 
    1376     -845,  -845,  -845,  -845,  -845,  -845,  -845,  -845,  -845,  -845, 
    1377     -845,  -845,  -845,  -845,   744,   717,  -845,   106,  2490,   588, 
    1378      591,   280,  4092,  -845,  -845,  2490,  -845,   598,  4658,    31, 
    1379      237,   594,   598,   595,   602,   125,  -845,  -845,  -845,   609, 
    1380      609,  4658,   109,   533,  -845,   622,  2531,  -845,  -845,  -845, 
    1381      622,   534,   534,   622,  -845,   545,   699,  -845,  -845,   534, 
    1382     -845,   615,  -845,  -845,  -845,  -845,  -845,   123,  -845,  -845, 
    1383      609,   618,  -845,   534,  -845,  3874,  3185,   585,   750,    34, 
    1384     4201,  -845,  2490,   592,   534,    80,  4331,  5955,    78,  5879, 
    1385       13,    85,  -845,   215,  2490,  2490,   524,  -845,   619,  2490, 
    1386      616,   778,  -845,  2490,  2490,  2490,  2490,  2490,  2490,  2490, 
    1387     4658,   337,  1249,  2490,   706,  1732,  -845,   779,  -845,  1249, 
    1388     -845,  5523,  5523,  5523,  5523,  5523,   760,  4658,  -845,  4658, 
    1389     -845,   111,   115,  1751,  -845,  -845,  -845,  1796,  1815,  1834, 
    1390     1912,  1931,  1995,  2014,  2033,  2092,  2111,  2130,  2194,  -845, 
    1391      121,  -845,   130,   136,   149,   781,   785,   786,  4767,  4767, 
    1392     -845,  4767,   150,  -845,  4658,  4658,  2490,  -845,   542,   542, 
    1393      806,   806,   875,   887,   887,   887,   887,   887,   887,   164, 
    1394      164,   185,  4658,  4658,  2490,  -845,   185,  4658,   887,  4658, 
    1395      887,   524,   787,  2640,   627,   629,   524,  -845,  -845,  -845, 
    1396     -845,   295,  4658,  6031,  4658,  -845,  4658,    19,   631,   337, 
    1397     -845,  -845,  2640,    83,  5347,  -845,  -845,  -845,  -845,    19, 
    1398      632,   524,  -845,  2573,  -845,  4658,  -845,  4658,  -845,  -845, 
    1399     -845,   771,    42,   547,  -845,  2213,   636,  -845,   637,  -845, 
    1400      776,  4658,  4658,   135,  -845,   242,  -845,   774,  2490,  -845, 
    1401     -845,   535,  4658,  -845,   151,  -845,  -845,  1253,   524,   780, 
    1402      780,   545,  -845,  -845,   476,   847,  -845,  -845,   534,   780, 
    1403      641,  4092,   750,  -845,   645,  -845,   644,  -845,  -845,   804, 
    1404      688,   809,  -845,  2490,  -845,  -845,  -845,   773,   215,  -845, 
    1405      215,   653,  -845,  -845,  -845,  -845,   652,   536,  -845,   215, 
    1406     -845,  2749,   655,   664,  -845,  -845,   122,  -845,  -845,  -845, 
    1407     3983,  2490,  -845,   152,  -845,  2490,  2490,  2490,  1249,   779, 
    1408      570,   760,   760,   760,   593,  -845,  2490,  -845,  -845,  -845, 
    1409     -845,  -845,  -845,  -845,  -845,  -845,  -845,  -845,  -845,  -845, 
    1410     -845,  -845,  -845,  -845,  -845,  -845,  5094,  5094,  5094,  2490, 
    1411     -845,  2490,  -845,  2490,  -845,  -845,   667,   887,   887,   185, 
    1412      887,   887,   470,  4658,  2858,  1415,   828,  -845,  -845,   513, 
    1413     -845,   534,  -845,  -845,  2291,   670,  -845,   671,  -845,  2310, 
    1414     1150,   829,  -845,  -845,  1233,   672,  -845,  -845,  -845,  -845, 
    1415     -845,  -845,  -845,  2490,   153,  -845,   598,   598,   598,   598, 
    1416      598,   522,  -845,   832,   676,  -845,  2329,  2374,  -845,  -845, 
    1417     -845,  -845,   154,  -845,   678,  -845,  -845,  2490,  2531,  -845, 
    1418     4440,  -845,  5203,  -845,  -845,   699,  -845,  -845,  -845,   679, 
    1419     -845,   780,   231,  -845,   750,  -845,  4092,  -845,   291,   681, 
    1420      683,  4658,   586,   215,   122,   122,  -845,  4658,   685,  -845, 
    1421      454,  -845,   215,   122,  4658,  2490,   155,  -845,   842,  -845, 
    1422     -845,  5955,   534,  -845,  1831,  2490,  -845,  -845,   832,   684, 
    1423      686,   689,  -845,   690,  4658,  1435,  4658,  2640,  -845,  -845, 
    1424      845,  4658,  4658,  -845,  4658,   524,  -845,   524,  -845,  -845, 
    1425       66,    66,   693,   143,  4658,   833,  -845,   768,    60,  -845, 
    1426      259,  -845,  -845,  -845,  2490,  4549,  -845,  2490,  -845,   231, 
    1427     4658,  4658,  -845,  -845,  -845,   729,  -845,   851,  -845,  -845, 
    1428     -845,   695,   696,   702,   215,  -845,   122,  2393,  -845,   703, 
    1429     -845,  -845,   122,  5955,  -845,  2749,  -845,  4658,   534,   701, 
    1430     2490,  -845,  -845,  -845,  -845,  2490,  4658,  1455,  -845,  4658, 
    1431      704,  2412,  1171,   470,   697,  1192,   598,  -845,  -845,  -845, 
    1432      157,   705,  -845,  2490,  2490,   709,   713,   716,  -845,  -845, 
    1433      122,  4331,   784,  -845,  5955,  -845,  -845,  -845,  -845,  2490, 
    1434     4658,  2490,  4658,  6107,  4658,  4658,   855,  -845,  -845,  -845, 
    1435     -845,  -845,  4331,   719,  2490,  2490,  1213,  -845,  -845,  4658, 
    1436     2490 
     1904   -1394,  1431, -1394, -1394, -1394,   -49,   -36, -1394, -1394, -1394, 
     1905      39,   837, -1394, -1394,   155,   218, -1394, -1394, -1394, -1394, 
     1906     855, -1394,   194, -1394,   194,   189,   624, -1394, -1394,   194, 
     1907   -1394,   194, -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, 
     1908   -1394, -1394, -1394,   101,   233,   268, -1394, -1394, -1394,   869, 
     1909   -1394, -1394,  4057,   229,   194, -1394,   512,  2546,   303,   355, 
     1910   -1394, -1394,  2546,  2546, -1394,   188,   188,    86,    86,    86, 
     1911      86,    95,    86,   132, -1394, -1394, -1394, -1394, -1394, -1394, 
     1912     188,   361, -1394, -1394,    98,   296,   421,   598, -1394, -1394, 
     1913      98,   109, -1394, -1394,   800, -1394,   658, -1394,   434, -1394, 
     1914    4057, -1394, -1394,   313,   697,   495, -1394, -1394, -1394,   549, 
     1915     422, -1394, -1394, -1394,   604, -1394, -1394,   625,   651, -1394, 
     1916   -1394, -1394, -1394,   -18,   764, -1394,   615, -1394, -1394, -1394, 
     1917   -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, 
     1918   -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394,   691, -1394, 
     1919   -1394, -1394,   892,   667,   669,  1351,   432,   -53,   475,   674, 
     1920     676,   683, -1394,  3782,  3837,   687,   690,  3574,   812,   731, 
     1921   -1394,  4247, -1394,  1042, -1394, -1394, -1394, -1394, -1394, -1394, 
     1922   -1394, -1394, -1394, -1394, -1394, -1394, -1394,   827, -1394, -1394, 
     1923   -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, 
     1924   -1394, -1394,   709, -1394, -1394,   716, -1394,   729,   731,   731, 
     1925     155,   155,   700,  3103, -1394, -1394, -1394, -1394, -1394,   411, 
     1926    1061, -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, 
     1927   -1394,  3867, -1394, -1394, -1394,   727,   730,  3882, -1394,    87, 
     1928     927, -1394, -1394, -1394,   760, -1394, -1394,   495, -1394,    82, 
     1929   -1394, -1394,  3867, -1394, -1394,   932, -1394,   756,   253,  1456, 
     1930     951, -1394, -1394,   947,   949,   781,  2103, -1394, -1394, -1394, 
     1931   -1394,   768,   769,   155, -1394,   103, -1394, -1394,   155,   322, 
     1932     188,   783, -1394,   118, -1394, -1394,   786,   789,   610,   155, 
     1933     188,   699,   790,   433,   487,   130,   608, -1394, -1394, -1394, 
     1934   -1394,    13, -1394, -1394,  3574,  3585,   188,   967,  3882,   657, 
     1935     210, -1394,   795,   421,   421,    14,  3913,  3882,   843,  3882, 
     1936    3882,   798, -1394,  4169,   409,   834,   263, -1394, -1394, -1394, 
     1937     895, -1394, -1394, -1394,  3882,  3882,   336,   434, -1394, -1394, 
     1938     188,   188,   155,   188, -1394, -1394, -1394, -1394, -1394, -1394, 
     1939     811,  3434, -1394,   188,  3464,   188, -1394,   819,   155, -1394, 
     1940   -1394, -1394, -1394, -1394, -1394, -1394,   188,   362,   188, -1394, 
     1941   -1394, -1394,  4270, -1394, -1394, -1394,  3882,  3133,  3133,  3585, 
     1942   -1394,  1014,   556,   918,    -5,    76, -1394, -1394,   841,   188, 
     1943   -1394, -1394, -1394, -1394, -1394, -1394,  1031,   846,   132, -1394, 
     1944   -1394,  1032,  1038,   112,  3867,   898,  1048, -1394, -1394, -1394, 
     1945     644,   644,   482,   871, -1394,   879,   888,  1456,   874,   132, 
     1946     132, -1394,   868, -1394,  1456, -1394, -1394,  1456, -1394, -1394, 
     1947    1456,   901,   756, -1394, -1394, -1394, -1394, -1394, -1394, -1394, 
     1948   -1394, -1394, -1394, -1394, -1394, -1394,  2103,  2103, -1394,  3882, 
     1949   -1394,  3882, -1394, -1394,  3882, -1394,   882,   887,   697,   361, 
     1950     155,   886, -1394, -1394,  1087,   155,   118,   783,   155, -1394, 
     1951     160, -1394,  1073, -1394,   906,   908, -1394,   155,  1101, -1394, 
     1952   -1394,   188, -1394,   913, -1394,  1105, -1394, -1394, -1394, -1394, 
     1953   -1394, -1394, -1394,   169,   800,   800,   762,    98,    98,  1119, 
     1954     155,   188, -1394,   114, -1394, -1394, -1394,   195,   155,  3882, 
     1955     916,  1113, -1394,   341,   952,   723, -1394, -1394,  1850,   933, 
     1956     972,  1126,   188, -1394,  1128, -1394, -1394,   944,   158, -1394, 
     1957     948,   201, -1394, -1394,    93,   946, -1394, -1394, -1394, -1394, 
     1958     188,  1146, -1394,   115,   134, -1394, -1394,   697,   188,   957, 
     1959     819, -1394, -1394,    98,  1149,  1043,  4345, -1394, -1394, -1394, 
     1960   -1394,   -25, -1394,   331, -1394,  1025, -1394,   969,   188,   979, 
     1961   -1394, -1394, -1394,   968,   971,   155,   155,   155,   819,  3218, 
     1962    3519,  2975,  3882,   -53,   697,   697,   874, -1394,   137, -1394, 
     1963     155,  3882,   -53,   697,   697, -1394,   138, -1394,   155,   819, 
     1964   -1394,   147,   155,   970,   555, -1394,   987, -1394,   980, -1394, 
     1965    3882,  3639,  3585,   982,   -53,   -53,   -53,   697, -1394, -1394, 
     1966   -1394, -1394, -1394, -1394,   161, -1394, -1394, -1394,   168,   207, 
     1967     440,  1060,   697, -1394, -1394, -1394,  1137, -1394, -1394,   984, 
     1968     803, -1394, -1394, -1394, -1394,   442,   988, -1394, -1394, -1394, 
     1969   -1394,  3882,   155,    83,   188,    83,   996, -1394,  1000, -1394, 
     1970    3882, -1394,   990,   132,  3882,  3882, -1394,  1187,   874, -1394, 
     1971    3867, -1394, -1394, -1394, -1394,   234,  1017, -1394, -1394, -1394, 
     1972   -1394, -1394, -1394, -1394, -1394,   756,   253,  1175, -1394,   947, 
     1973     949, -1394,  3882,  1189,   171, -1394,   496,  1195, -1394, -1394, 
     1974    1007, -1394, -1394,  3882, -1394,  3882,   155, -1394,   786,   155, 
     1975     819,  1183,  1013,  1204, -1394,   699,   155,  1018,   487,   188, 
     1976     800, -1394, -1394,  1015, -1394,  1191, -1394, -1394,   176, -1394, 
     1977    1021, -1394, -1394,   710, -1394,  1191, -1394,  1194,   534, -1394, 
     1978     155,   188,   155,   188,  1176,   -53,  3882,   125,   174, -1394, 
     1979   -1394,   116, -1394,   155,  3960,   155,   188, -1394,  3882,   659, 
     1980   -1394,   819,   485, -1394, -1394, -1394, -1394,  1023, -1394,  1024, 
     1981   -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394,  1215, -1394, 
     1982    1026, -1394,  1850,   155,   795,  1027,  1218, -1394, -1394, -1394, 
     1983    1219, -1394, -1394, -1394,   188,  1033,   549,   155,  1034,   155, 
     1984    3882,  3882, -1394,  3882,  1077, -1394,   188,   155, -1394, -1394, 
     1985     155,   188,  1062,   501,  1036,  3989,  1039,  1206, -1394, -1394, 
     1986   -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, 
     1987   -1394, -1394, -1394, -1394, -1394,   834, -1394, -1394,  1095, -1394, 
     1988    1084,  1236,   155,  1130,   476, -1394, -1394, -1394, -1394,  1239, 
     1989   -1394,  1054,  3882,  3882,  3882,  3882,  3882,  1245,  3882,   -53, 
     1990    3882,   697, -1394,   193, -1394,  1246,  3882,   -53,   697, -1394, 
     1991     197, -1394,  3882,  1251,   697,   697,   697,   697,  3882,   697, 
     1992     -53,   697,   697, -1394,   200, -1394, -1394, -1394, -1394, -1394, 
     1993   -1394, -1394, -1394, -1394, -1394,  3434,   188, -1394, -1394, -1394, 
     1994   -1394,  3464,   188, -1394,  1254,   819, -1394,  3882, -1394,   976, 
     1995   -1394, -1394, -1394,  1228,  2759, -1394, -1394, -1394, -1394, -1394, 
     1996   -1394, -1394, -1394, -1394, -1394,  3133,  3650,   425,   909,   155, 
     1997   -1394, -1394,  3882,  3882,   864, -1394,  3882,   505, -1394,   645, 
     1998   -1394, -1394, -1394,  1555,   188,   155, -1394,   188,   188,    87, 
     1999    1255, -1394, -1394,   202, -1394, -1394, -1394, -1394, -1394,  1065, 
     2000    1260, -1394,   155,  1071,  1235,  1238,  1075, -1394,   203,   205, 
     2001    1076,  3867, -1394, -1394, -1394, -1394, -1394,  1080,   211,  3882, 
     2002     887, -1394,   697,  3882,  1082,  1274, -1394, -1394,  1276, -1394, 
     2003   -1394, -1394, -1394,   908,   567, -1394, -1394,   212, -1394,   182, 
     2004   -1394,  1278, -1394,   155, -1394,   132,   579, -1394, -1394,  3697, 
     2005     762, -1394, -1394, -1394, -1394,   155,   155,  3882,  1282, -1394, 
     2006   -1394,  3734,  1119, -1394,  1634,  3882, -1394,  3960, -1394,   258, 
     2007   -1394, -1394,   155, -1394, -1394,  1094, -1394,   353, -1394, -1394, 
     2008    1097,   266, -1394,   188,   155, -1394, -1394,   933,   188, -1394, 
     2009    1270, -1394, -1394, -1394,  1102,   188,   188,   158,   155,  1272, 
     2010     214, -1394, -1394, -1394, -1394, -1394, -1394,  1291, -1394,  1292, 
     2011   -1394,   697,   155,   155,    98,   188,   155,  3882,  2901,  2425, 
     2012    3379, -1394,   819,  3882,  1839, -1394,   834, -1394,   143, -1394, 
     2013   -1394,  1107,   155, -1394,   188,   414,  1108,  3882, -1394, -1394, 
     2014   -1394, -1394, -1394, -1394, -1394, -1394,  3882, -1394, -1394, -1394, 
     2015   -1394,  3218, -1394,  3882, -1394, -1394, -1394,  3519,   188, -1394, 
     2016     697,  1111, -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, 
     2017   -1394, -1394,  3294, -1394, -1394,   155, -1394,   155,   445,  1115, 
     2018   -1394,  1121, -1394, -1394,  1133,   188, -1394,  1592,   350, -1394, 
     2019     155,   258,  3960,   155, -1394,   318, -1394, -1394,   318,  1123, 
     2020    1132,   577,   613, -1394, -1394,   556,  1135,   188,   155,   623, 
     2021   -1394, -1394, -1394,  3882, -1394,   220, -1394,  1295,   155,   188, 
     2022     155,   155,  3882,  3882, -1394, -1394,    83,  1301, -1394,  1107, 
     2023   -1394,  1107, -1394,  1242, -1394,  1264, -1394, -1394,   182,  1139, 
     2024    1334, -1394, -1394, -1394, -1394, -1394, -1394,   188,   225, -1394, 
     2025    1150, -1394,  3882,   819,   364,  1681, -1394,   188,   610,  1018, 
     2026     188,  3882,   234,   540, -1394, -1394, -1394, -1394, -1394, -1394, 
     2027   -1394, -1394, -1394, -1394, -1394, -1394,  1335,   240, -1394, -1394, 
     2028    1144, -1394, -1394, -1394, -1394, -1394,  3882,   -53, -1394, -1394, 
     2029    3882,  1342, -1394,   874, -1394, -1394, -1394,  1345, -1394,  3960, 
     2030     155,  1923,   659, -1394,  1923,  1270,   819,   155,   155,  1681, 
     2031     696, -1394,   155,  1681,   411,   105,  1681,  1160,   155,   155, 
     2032   -1394,  1166,  1033, -1394, -1394,  3882,   188,   155,   188,   155, 
     2033    1164,  3882, -1394, -1394, -1394, -1394, -1394,   582,   592,   634, 
     2034     744,   865,   444,   562,  1165,  3882,  1167, -1394,   697,  1181, 
     2035     491,  1188,   870,  1880,   243,  1186, -1394,  1378,  1237,  1381, 
     2036   -1394,   188, -1394, -1394,   155,   697,  1382,  1383, -1394, -1394, 
     2037   -1394,   246, -1394,  3882,  1384, -1394, -1394,   188, -1394, -1394, 
     2038     155, -1394,  3960, -1394,   188,   697,  1387, -1394,  1390, -1394, 
     2039   -1394, -1394, -1394, -1394,   155,  3882,   -53,   155,   909,   155, 
     2040     155,  1293,   650,   188,   155,   188,   155,   556,  1296,   155, 
     2041     188,   155, -1394,  1555, -1394,  3882,   155,   434, -1394, -1394, 
     2042     188, -1394,  1201, -1394, -1394, -1394, -1394,  1393,  1395, -1394, 
     2043    3882,   155,   697, -1394, -1394,  1392, -1394,   155,  1385, -1394, 
     2044    1209,  1402, -1394,  1405, -1394,  1403, -1394,  1407, -1394, -1394, 
     2045    3882,  1396,  1408, -1394, -1394,  1412,   155,   908, -1394,   155, 
     2046    1415, -1394, -1394,  3913,  3913, -1394, -1394, -1394, -1394,  3882, 
     2047    3960, -1394, -1394,  1226,  1419,  1420,  1407, -1394,  1229,   121, 
     2048   -1394,  1231, -1394, -1394, -1394,  1232,  1233, -1394,  3882,   533, 
     2049   -1394, -1394,  1234, -1394, -1394, -1394,   155,   155,   467, -1394, 
     2050   -1394, -1394, -1394, -1394, -1394,  1007, -1394,   108, -1394, -1394, 
     2051    1241, -1394, -1394,  2513,  3882,  3882,  3882,  3882,  3882,  3882, 
     2052    3882,  3882,  3882,  3882,  3882,  3882,  3882,  3882,  2329,  3882, 
     2053    2559,  2599, -1394, -1394,  1839,  1244,  1247,  1248,   155,   188, 
     2054   -1394, -1394,   697,    50,   188,  3882, -1394, -1394, -1394,   155, 
     2055    1427,   155, -1394,   697,   262,   188,   188,   188,  1243,  1433, 
     2056   -1394,   188,   188,   155,   155,   155,   682,   155, -1394, -1394, 
     2057     155,  1249,   188, -1394,   188,  3882,   132,  1439, -1394,  3882, 
     2058    1252, -1394,  3882,  3771,  2016,  1440,  1441,  1428, -1394, -1394, 
     2059    3882,  1204,  3882, -1394, -1394, -1394,  1445, -1394,  1257, -1394, 
     2060    3882,  3882, -1394,  3882,   533, -1394, -1394, -1394, -1394, -1394, 
     2061   -1394, -1394, -1394, -1394, -1394,  1681,    -1, -1394, -1394, -1394, 
     2062    3882, -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, 
     2063   -1394, -1394, -1394, -1394, -1394, -1394, -1394,  3882,  3882, -1394, 
     2064   -1394, -1394,  3882, -1394,  3882, -1394,  1237, -1394, -1394,  1450, 
     2065   -1394, -1394, -1394, -1394, -1394,   155, -1394, -1394, -1394,   155, 
     2066   -1394,   188, -1394, -1394,   155,   155,   155,  1839,   -53,   155, 
     2067     155,   188,   155,  1262,   155,   188,   155,  1269,  1273,  3882, 
     2068   -1394,  1432, -1394, -1394, -1394, -1394,  1454, -1394, -1394, -1394, 
     2069   -1394, -1394,   247,  3882, -1394, -1394, -1394, -1394,  1275,  1167, 
     2070    1280,  2127,  1283,  1286,  1287, -1394, -1394, -1394, -1394, -1394, 
     2071     188,  1244,   155,   188,   155, -1394,   155, -1394, -1394,  1463, 
     2072     819, -1394,  3882, -1394,  1471, -1394, -1394,  2220,  1481, -1394, 
     2073   -1394,  1482, -1394,   697, -1394,   155, -1394,   155,  3882, -1394, 
     2074    1299,  3882,  3882,  1483,  2127,  3882, -1394, -1394, -1394,  1487, 
     2075   -1394,  3882, -1394,  1492,  3882, -1394,  3882, -1394, -1394 
    14372076}; 
    14382077 
     
    14402079static const yytype_int16 yypgoto[] = 
    14412080{ 
    1442     -845,  -845,  -845,   -96,   830,   628,   -26,  -845,  -845,  -845, 
    1443      399,   156,  -845,   -94,  -845,   -67,   -63,  -845,  -845,   232, 
    1444     -845,  -845,  -845,   509,  -845,   234,    30,  -845,  -845,  -845, 
    1445     -845,  -845,   444,  -464,  -845,  -845,  -238,   438,  -242,  -845, 
    1446     -845,  -845,  -845,  -845,  -845,   -47,  -845,  -845,  -263,   417, 
    1447      -27,   -50,   668,   437,  -845,  -845,  -845,  -845,  -845,  -845, 
    1448     -845,   404,  -845,  -845,  -671,  -845,  -845,  -845,   642,  -231, 
    1449     -656,  -845,  -845,   217,  -845,   882,  -236,  -845,    67,    70, 
    1450      -11,   -78,    55,  -144,  -458,  -507,  -845,  -845,   -97,  -845, 
    1451     -845,  -845,  -845,  -845,   540,  -845,     9,   279,     1,   -70, 
    1452     -845,  -845,  -182,  -382,   365,   -20,  -128,  -845,  -845,  -845, 
    1453       52,  -845,   -73,    43,  -845,  -630,  -845,  -515,  -514,  -844, 
    1454     -845,  -845,  -845,  -845,  -566,  -718,  -845,  -845,  -845,  -845, 
    1455     -294,  -845,  -845,  -845,  -845,  -845,  -185,  -845,  -845,  -845, 
    1456     -845,  -845,  -845,  -663,  -845,  -845,  -845,  -845,  -845,  -845, 
    1457     -845,  -845,  -845,   405,  -845,  -845,  -845,  -845,  -845,   -40, 
    1458     -787,  -845,  -845,  -845,  -845,  -845,  -845,   -38,   190,    11, 
    1459     -845,  -845,  -845,  -845,  -845,  -845,  -845,  -845,   191,  -845, 
    1460     -845,  -845,  -845,   506,  -845,  -845,   288,  -384,  -845,  -845, 
    1461     -845,   -39,   834,  -250,  -126,  -699,  -522,  -140,  -287,  -465, 
    1462     -845,  -845,  -213,  -845,   519,  -845 
     2081   -1394, -1394, -1394,   635, -1394,  1436,   548, -1394, -1394, -1394, 
     2082   -1394, -1394, -1394, -1394, -1394, -1394,   -79, -1394, -1394, -1394, 
     2083   -1394, -1394, -1394, -1394,  -666, -1394,  -206, -1394,   -11, -1394, 
     2084   -1394, -1394, -1394, -1394, -1394, -1394, -1394,  1399,   857, -1394, 
     2085   -1394, -1394,   119,   735, -1394, -1394, -1394,   595, -1394,   -68, 
     2086    -892,  -632, -1394, -1394,   499,   500,   -42,    34, -1394,   627, 
     2087    -217,   -80, -1394,  1488, -1394, -1394, -1394, -1394, -1394, -1394, 
     2088    1050, -1394,  -205,  -183,  1096,  -448,  -195, -1394, -1394, -1394, 
     2089     244, -1394, -1394, -1394,   236,   -37, -1394, -1394, -1394, -1394, 
     2090   -1394, -1394, -1394,   796, -1394,   293, -1394, -1394, -1394,   998, 
     2091   -1394, -1394, -1394,   252, -1394,   249, -1394,   256, -1394, -1394, 
     2092    -972,  1510, -1394,  1103,   516, -1394,   100,   102, -1394,  1277, 
     2093   -1394, -1394,  1124,  -598, -1394, -1394, -1394, -1394, -1394, -1394, 
     2094   -1394, -1394, -1394,   748, -1394, -1394, -1394,   486, -1394, -1394, 
     2095   -1394, -1394,  -971,  -254, -1394, -1394, -1189,  -438, -1112, -1170, 
     2096   -1107, -1394,   -10,  -413,   -13, -1394, -1394,   131, -1394,    -4, 
     2097   -1394, -1394, -1394, -1394, -1394,   763, -1394, -1394, -1394, -1394, 
     2098    -415, -1394, -1394,  1045,  -247, -1394,   831, -1394,   541,  -603, 
     2099   -1394,   547, -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, 
     2100   -1394, -1394, -1394,   574, -1394, -1394, -1394,   -29, -1394, -1394, 
     2101     506, -1394,     9, -1394, -1394, -1394,   761, -1394,   276, -1394, 
     2102   -1394,  -116,   356, -1394, -1394,  1109, -1394, -1394,  -939, -1394, 
     2103   -1394, -1394, -1394,  -276,  -472, -1394,   153,   578, -1394,  1178, 
     2104   -1394,  1964,  -452,   694, -1394, -1394,  -821, -1394,  -498, -1394, 
     2105    -456,  -292,  -289, -1394,  1028, -1394, -1394,  -249,  -285, -1394, 
     2106   -1394,   551, -1394, -1394,  1030, -1394, -1394, -1394, -1394,    74, 
     2107      71,   248, -1394,   493,  -566, -1394, -1394,    84, -1394,  -251, 
     2108     259,  1035, -1394, -1394, -1394, -1394, -1394,    80, -1394, -1394, 
     2109     385,     1,  1151, -1394, -1394,  -193,  1148, -1394,  1330, -1394, 
     2110    1152,  1147,  1145, -1394, -1394, -1394, -1394, -1394,  1529,  -755, 
     2111    -140,  -163,   842,   -72,  -936, -1047, -1394, -1394,  -200, -1394, 
     2112     -44,   332, -1394, -1394, -1394,   801,   807,  -508,   806, -1394, 
     2113    1297,  -371,  -375,  -861, -1394, -1394, -1394, -1394,  -813,  -820, 
     2114   -1394, -1394, -1394, -1394,  -166, -1394,   343, -1394, -1394,  1051, 
     2115   -1394,   -74,  -694,  -106,  1290, -1394, -1394, -1394, -1394, -1394, 
     2116   -1394, -1394,  1056, -1394, -1394, -1394, -1394, -1394,  -558, -1394, 
     2117   -1394, -1394, -1394, -1394, -1394,  1055, -1394, -1394,  1240, -1394, 
     2118   -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394,   250, 
     2119   -1100, -1394,  1063, -1394,    -3, -1394, -1394,  1016,   507, -1394, 
     2120    1074, -1394, -1394, -1394,   521,   765,  1040,  1079, -1394, -1394, 
     2121     519,  1090,  1099,   -12,  1281,  1020,   725,  -234,   724,  -850, 
     2122    -856,  -963,  -859, -1394,   221, -1394,  1104, -1394,   757,  1110, 
     2123   -1394,   770,  1112, -1394, -1394, -1394, -1394,   531,   466, -1394, 
     2124   -1394, -1394, -1394, -1394, -1394, -1394, -1394,  -434, -1394, -1394, 
     2125   -1394,  1337, -1394, -1394,  1616, -1394, -1394, -1394, -1394, -1394, 
     2126     681, -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, 
     2127   -1394, -1029, -1394,     0, -1394, -1393, -1394,  1394,  1210, -1394, 
     2128   -1394,   973,  -479, -1394,  1131, -1394, -1394, -1394, -1394, -1394, 
     2129   -1394,  1058,   994,   497,   511, -1394, -1394,  1663,  -129, -1394, 
     2130   -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394, -1394,  -114, 
     2131   -1394, -1394, -1394, -1394,   309, -1394, -1394, -1394,  1052, -1394, 
     2132     517,   468, -1394, -1394, -1394, -1394, -1394,   616 
    14632133}; 
    14642134 
     
    14662136   positive, shift that token.  If negative, reduce the rule which 
    14672137   number is the opposite.  If YYTABLE_NINF, syntax error.  */ 
    1468 #define YYTABLE_NINF -542 
     2138#define YYTABLE_NINF -1015 
    14692139static const yytype_int16 yytable[] = 
    14702140{ 
    1471      174,   539,    93,   402,   192,   293,   434,   174,   294,   474, 
    1472      641,   775,   295,   642,   506,   296,   243,   366,   690,   684, 
    1473      414,   735,   736,   828,   684,   300,   494,   324,   372,   265, 
    1474      498,   270,   271,   367,   686,   203,   273,  -171,   504,   874, 
    1475      226,   579,   766,   767,    96,   846,   323,   198,   882,   257, 
    1476      258,   579,    93,   268,   325,   534,   764,   764,   764,   203, 
    1477      277,   847,   848,   849,   579,  -171,   885,   221,   222,   917, 
    1478      366,   579,   646,   432,   430,   297,   607,   298,   299,   575, 
    1479     -430,   859,   664,   365,   899,   329,   367,   849,   373,   374, 
    1480      375,   376,   377,   378,    96,   379,   380,   381,   382,   383, 
    1481      384,   332,   385,   386,   387,   388,   389,   729,   671,   675, 
    1482      477,   174,   493,   203,   579,   419,   324,   984,   579,   333, 
    1483      335,   336,   419,   285,   579,   750,   715,   483,   203,   540, 
    1484      343,   126,  1021,   579,  -426,   323,   365,   223,   203,   579, 
    1485      831,   224,   301,   325,   357,   307,   251,   194,   479,  -429, 
    1486      364,   410,   579,   579,   868,   914,   675,   948,   985,  -425, 
    1487      948,   371,   847,   848,   849,  -171,   393,   194,   648,   741, 
    1488      484,   485,   229,   971,   438,   751,  1042,   223,   575,   170, 
    1489      406,   224,   195,   230,   288,   387,   388,   389,   302,   404, 
    1490      411,   412,   753,   742,  -171,   342,   480,   344,  -106,   394, 
    1491     1026,   580,   197,   364,   308,   128,   364,   417,   389,   850, 
    1492      959,   584,   359,  1000,   425,   917,   468,   204,   433,   605, 
    1493      860,   436,  -430,   606,   586,   324,   466,   486,   963,   475, 
    1494      564,   601,   647,   850,   324,   367,   960,   980,   495,     4, 
    1495      730,   680,   665,   500,   323,   496,   503,   390,   391,   563, 
    1496      478,   836,   325,   323,   716,    93,   130,   565,   916,   916, 
    1497      916,   325,   252,   859,   286,   709,   710,   471,   672,   676, 
    1498      499,   413,   699,   713,   777,   475,  -426,   532,   778,   170, 
    1499      859,   609,   251,   561,   792,   365,   204,   719,   253,   544, 
    1500      545,  -429,   576,   793,   549,   722,   413,    96,   728,   794, 
    1501      694,  -425,   540,   553,   554,   555,   556,   557,   558,   559, 
    1502      850,   575,   795,   805,   869,   915,   938,   949,   986,   266, 
    1503     1037,   800,   802,   425,   804,   289,   575,   324,   390,   391, 
    1504      583,   919,   920,   921,   587,   588,   589,   590,   591,   592, 
    1505      593,   594,   595,   596,   597,   598,   323,   223,   131,   390, 
    1506      391,   224,   371,   961,   325,   571,   311,   312,   572,   573, 
    1507      574,   188,   616,   618,   619,   620,   621,   622,   623,   624, 
    1508      625,   626,   627,   628,   629,   630,   631,   634,   636,   638, 
    1509      640,    69,   939,   199,   192,   659,   372,   481,   684,   684, 
    1510      684,   684,   684,   990,   581,   582,   697,   244,   252,   245, 
    1511      191,   278,   860,   828,   610,   861,   482,   239,   764,   575, 
    1512      407,   489,   490,   600,   663,   602,   603,   604,   202,   860, 
    1513      415,   416,  1009,   400,   253,   612,   717,   837,   822,   279, 
    1514      212,   923,   395,   679,   240,   241,   763,   408,   520,   264, 
    1515      209,   235,   236,   769,   832,   701,   210,   756,   875,   989, 
    1516      708,   965,   937,   711,  -156,   823,   839,   966,  -156,   208, 
    1517      223,   475,   911,   866,   224,   564,   775,   685,   213,   255, 
    1518      806,   256,   564,   219,   324,   324,   324,   324,   324,   259, 
    1519      698,   260,   881,   916,   563,   707,   170,   309,   194,   274, 
    1520      884,   563,   565,   323,   323,   323,   323,   323,   269,   565, 
    1521      762,   325,   325,   325,   325,   325,   735,   736,   858,   800, 
    1522      802,   804,   220,  -156,   475,   475,   227,  -156,   372,   371, 
    1523      575,   575,   575,   575,   575,   733,   203,   735,   736,   280, 
    1524      200,   201,   770,   771,   772,   773,   774,   746,    93,   979, 
    1525       93,  -156,  1036,   231,   812,  -156,   232,   757,   684,   761, 
    1526      376,   377,   378,   249,   379,   380,   381,   382,   383,   384, 
    1527      419,   385,   386,   387,   388,   389,   733,   324,   776,   215, 
    1528      216,   217,   419,   571,   311,   312,   572,   573,   574,  -541, 
    1529     -541,  -541,  -541,  -541,  -541,   929,   323,   254,   139,   311, 
    1530      312,   572,   573,   574,   325,   524,   525,   799,   801,   263, 
    1531      803,   398,   668,   364,   807,   940,   941,   942,   943,   983, 
    1532      876,   877,   878,   851,   572,   573,   574,   133,   134,   746, 
    1533      898,   808,   809,   972,   973,   203,   810,   272,   811,   310, 
    1534      327,   292,   815,   304,   305,   339,   340,   928,   394,   341, 
    1535      345,   824,   894,   829,   895,   830,   346,   821,   347,   348, 
    1536      349,   834,   806,   903,    93,   964,   350,   405,   351,   352, 
    1537      353,   354,   355,   356,   843,   425,   468,   358,   469,   360, 
    1538      361,   564,   841,   362,   370,   395,   988,   397,   398,   162, 
    1539      856,   857,   399,   470,   170,   163,   164,   465,  1024,   476, 
    1540      563,   867,   491,   259,   493,   266,   496,   501,   565,   502, 
    1541      166,   167,   505,   168,   169,   274,   390,   391,   171,   871, 
    1542      475,   373,   374,   375,   376,   377,   378,   521,   379,   380, 
    1543      381,   382,   383,   384,   523,   385,   386,   387,   388,   389, 
    1544      535,   560,   547,   569,   611,   577,   614,   651,   654,   674, 
    1545      905,   656,   657,   609,   666,   667,   669,   673,   723,   549, 
    1546      677,   678,  1027,   724,   688,   727,   608,   691,  -237,  -237, 
    1547     -237,  -237,  -237,  -237,   692,  -237,  -237,  -237,  -237,  -237, 
    1548     -237,   695,  -237,  -237,  -237,  -237,  -237,   714,   718,   759, 
    1549      758,   760,   768,   574,   796,   799,   801,   803,   797,   798, 
    1550      819,   813,   820,   845,   833,   840,   853,   976,   855,   478, 
    1551      864,   872,   192,   925,   883,   886,   982,   887,   888,   891, 
    1552      889,   372,   890,   896,   897,   909,   378,   564,   379,   380, 
    1553      381,   382,   383,   384,   910,   385,   386,   387,   388,   389, 
    1554      922,   927,   931,   932,   935,   936,   563,   944,  1003,   945, 
    1555      950,   969,   958,   730,   565,   978,   987,   991,   999,   992, 
    1556     1007,  1015,   993,   994,  1016,  1006,  1018,   707,  1017,   954, 
    1557      850,   957,  1019,  1023,  1028,   302,  1043,  1032,  1038,  1039, 
    1558      390,   391,   507,   965,   394,   475,  1041,  1047,  1020,  1048, 
    1559      333,   234,   488,  1010,   693,  1008,   977,   379,   380,   381, 
    1560      382,   383,   384,   905,   385,   386,   387,   388,   389,  -542, 
    1561     -542,  -542,  -542,  -542,  -542,   842,   385,   386,   387,   388, 
    1562      389,   844,    93,   995,   649,   997,   815,  -237,  -237,   689, 
    1563      333,  1001,   712,  1002,   687,   235,   236,   508,   492,   720, 
    1564      700,   533,   880,  1005,   238,   952,   998,   644,    93,  1012, 
    1565      953,   835,   970,  1040,   371,  1025,   754,   912,  1004,  1013, 
    1566     1014,   913,   838,   509,   670,   510,   511,   512,   330,     0, 
    1567      513,   514,     0,   515,   516,     0,     0,     2,     3,     0, 
    1568      390,   391,     0,     0,   905,     0,   905,     0,     0,     0, 
    1569        0,     0,     0,     0,    93,  1029,     0,     0,  1031,     0, 
    1570        0,     4,     5,     0,     0,     6,   -21,     7,   -21,     8, 
    1571        0,     0,     9,     0,     0,     0,     0,     0,     0,     0, 
    1572      733,     0,    10,     0,     0,     0,     0,     0,     0,  1044, 
    1573        0,   733,     0,  1045,  1046,    93,     0,     0,    11,     0, 
    1574        0,   733,    12,    13,    93,     0,     0,    14,  1050,   390, 
    1575      391,     0,     0,    15,     0,    16,    17,     0,    18,     0, 
    1576        0,   390,   391,    19,    20,    21,    22,    23,     0,    24, 
    1577       25,     0,     0,    26,    27,    28,    29,    30,    31,    32, 
    1578       33,    34,    35,    36,     0,    37,     0,    38,    39,     0, 
    1579        0,    40,    41,    42,     0,    43,     0,    44,     0,     0, 
    1580       45,    46,     0,     0,    47,    48,    49,     0,     0,     0, 
    1581        0,     0,     0,     0,    50,     0,     0,    51,    52,    53, 
    1582       54,    55,    56,    57,    58,    59,    60,    61,    62,    63, 
    1583        0,     0,    64,     0,     0,    65,    66,    67,    68,     0, 
    1584        0,     0,   652,    69,   373,   374,   375,   376,   377,   378, 
    1585        0,   379,   380,   381,   382,   383,   384,     0,   385,   386, 
    1586      387,   388,   389,   934,     0,   373,   374,   375,   376,   377, 
    1587      378,     0,   379,   380,   381,   382,   383,   384,     0,   385, 
    1588      386,   387,   388,   389,  1034,     0,   373,   374,   375,   376, 
    1589      377,   378,     0,   379,   380,   381,   382,   383,   384,     0, 
    1590      385,   386,   387,   388,   389,  1035,     0,   373,   374,   375, 
    1591      376,   377,   378,     0,   379,   380,   381,   382,   383,   384, 
    1592        0,   385,   386,   387,   388,   389,  1049,     0,   373,   374, 
    1593      375,   376,   377,   378,     0,   379,   380,   381,   382,   383, 
    1594      384,     0,   385,   386,   387,   388,   389,   926,   373,   374, 
    1595      375,   376,   377,   378,     0,   379,   380,   381,   382,   383, 
    1596      384,     0,   385,   386,   387,   388,   389,   870,   373,   374, 
    1597      375,   376,   377,   378,     0,   379,   380,   381,   382,   383, 
    1598      384,     0,   385,   386,   387,   388,   389,     0,     0,     0, 
    1599        0,     0,   135,   136,     0,     0,     0,     0,   137,   138, 
    1600      139,   140,   141,   390,   391,     0,     0,     0,     0,     0, 
    1601        0,     0,     0,   142,   143,   144,   145,   146,   147,   148, 
    1602        0,   149,   150,   151,   390,   391,   152,   153,   154,     0, 
    1603      155,   156,   157,   158,   159,     0,   160,     0,     0,     0, 
    1604        0,     0,     0,     0,     0,   390,   391,   373,   374,   375, 
    1605      376,   377,   378,     0,   379,   380,   381,   382,   383,   384, 
    1606        0,   385,   386,   387,   388,   389,   390,   391,   373,   374, 
    1607      375,   376,   377,   378,     0,   379,   380,   381,   382,   383, 
    1608      384,     0,   385,   386,   387,   388,   389,   390,   391,     0, 
    1609        0,   162,     0,     0,     0,     0,     0,   163,   164,     0, 
    1610        0,     0,     0,   165,     0,     0,   613,   390,   391,     0, 
    1611        0,     0,   166,   167,     0,   168,   169,     0,     0,   170, 
    1612      171,   562,     0,     0,     0,     0,     0,   390,   391,   926, 
    1613      373,   374,   375,   376,   377,   378,     0,   379,   380,   381, 
    1614      382,   383,   384,     0,   385,   386,   387,   388,   389,   996, 
    1615      373,   374,   375,   376,   377,   378,     0,   379,   380,   381, 
    1616      382,   383,   384,     0,   385,   386,   387,   388,   389,  1030, 
    1617      373,   374,   375,   376,   377,   378,     0,   379,   380,   381, 
    1618      382,   383,   384,     0,   385,   386,   387,   388,   389,     0, 
     2141      43,   269,   699,   403,   361,   487,   698,   635,   131,   490, 
     2142     103,   634,   476,   397,   148,   105,   290,   739,   383,   950, 
     2143     105,   720,  1146,   332,  1002,   105,   105,   360,   549,   310, 
     2144     325,  1093,   413,   903,  1230,  1232,   399,   480,   333,   806, 
     2145     141,    98,   415,  1209,   417,   489,    98,   484,   726,   140, 
     2146     361,    98,    98,   428,  1122,  1123,   131,   105,   103,  1320, 
     2147     950,   118,   239,   105,  1255,   430,   541,   105,  1157,  1157, 
     2148    1151,   507,   972,  1372,  1165,   429,   431,  1156,  1156,   721, 
     2149    1441,   312,   938,    98,  1446,   420,   889,  1452,   141,    98, 
     2150     149,  1435,  -181,    98,  1435,   899,  -520,   140,  1102,  1103, 
     2151    1104,   277,  1612,   374,   956,  1109,   459,   212,  1295,   118, 
     2152    1448,  -537,   291,  1160,    89,   665,   219,  -194,   801,   924, 
     2153    1024,   467,     4,   384,   497,  1008,  1563,     4,   316,  -537, 
     2154    1021,   643,  1012,   491,   105,    32,   225,   803,  -194,    97, 
     2155     895,   901,     4,   226,   553,   629,   413,  1325,   269,   413, 
     2156     905,   227,   228,   229,  -408,    34,   415,   529,   417,   415, 
     2157      98,   417,     8,   708,   925,   506,   554,     8,  1256,   700, 
     2158    1317,   925,   491,   701,   980,   317,   473,  1022,  -194,    47, 
     2159     474,   662,     8,   498,     4,   821,    11,  -727,   644,  1255, 
     2160      42,   343,  1316,  -409,  -408,  1326,  1111,  1006,   754,   413, 
     2161    1117,   332,   678,  1132,   796,  1183,  1193,   646,  1195,   415, 
     2162     928,   417,     4,   518,  1183,  1219,   333,  1282,    58,     4, 
     2163      59,   649,   676,  1373,     8,     4,   412,   976,  1392,   513, 
     2164      35,     4,   501,  -409,   431,   530,   512,   506,   506,   506, 
     2165    1546,   682,    49,  1424,   682,   542,   905,   431,   512,  1505, 
     2166    1682,  1449,     8,   227,   228,   374,   230,  1290,   990,     8, 
     2167     432,  1259,  -537,  -265,   776,     8,   565,  1564,   463,  1266, 
     2168    1025,     8,   227,   228,   957,  1529,   421,  1201,  1612,   213, 
     2169     302,   231,     4,    98,   527,   528,   105,  -520,   220,   847, 
     2170       4,   724,  -520,  1256,    73,    12,  1431,   232,   233,  1341, 
     2171      12,   727,  1367,   738,   374,  1004,   666,   234,  -194,   802, 
     2172     847,  -194,    98,   725,   411,    12,    92,    93,   302,    95, 
     2173     235,  1358,     8,    42,   236,   237,   269,  -408,   804,   848, 
     2174       8,   896,   902,   238,  1318,   105,   752,   569,   633,   504, 
     2175     412,   906,     4,   412,   759,   105,   600,   269,   269,    42, 
     2176     848,  1335,    48,  1356,  -472,   926,  1262,    12,  1338,  1345, 
     2177    -761,    98,   927,  1110,  -336,   981,  -409,   491,  1023,   308, 
     2178    1116,    98,  1435,   972,  1646,   302,  1121,  1236,   918,  1124, 
     2179    1546,  1170,     8,  1130,   132,    12,  1658,  1112,     4,   146, 
     2180    1435,  1118,    12,   412,  1133,   133,  1184,  1194,    12,  1196, 
     2181    -761,  1570,   656,   658,    12,  1203,  1220,  1346,  1283,   239, 
     2182     603,   504,   504,   504,  1374,   304,   632,   566,   432,  1393, 
     2183     305,   105,   235,   741,   743,    42,   236,    74,     8,   487, 
     2184    1642,   685,   132,   490,  1425,   513,  1643,  1493,   461,   462, 
     2185    1506,  1683,   551,   133,  -196,   236,   968,   696,  1642,     4, 
     2186     281,   835,   306,  1538,  1643,    12,     4,   105,   105,   728, 
     2187     966,   480,    75,    12,   969,   970,     4,  1255,  1614,   489, 
     2188     975,   484,   506,   497,  1548,   911,   942,  1571,  1572,   811, 
     2189     727,   428,   738,    98,    98,   723,  1510,   282,   747,     8, 
     2190     912,   607,   429,   430,   204,   760,     8,   361,    89,  1157, 
     2191       4,   361,   361,   429,  1500,  1039,     8,  1263,  1520,     4, 
     2192     105,  1325,   820,    42,   817,    12,  1655,   787,   142,   105, 
     2193     145,   838,  1218,    97,  1500,     4,   699,   739,   776,     4, 
     2194     698,   739,   498,  -761,    92,    93,    98,    95,   915,    98, 
     2195       8,    42,  1345,  1014,   830,    98,   206,   105,   105,     8, 
     2196    1067,   950,  1069,   825,   274,  1013,   105,   105,  1229,  1326, 
     2197     825,    12,   726,  1286,   230,     8,   142,   696,   145,     8, 
     2198     491,  1256,  1347,    98,    98,   285,   285,   552,   553,    47, 
     2199     105,    64,    98,    98, -1013,  -506, -1013,   482,   696,  -506, 
     2200    1346,   269,  1656,  1657,   153,   105,    76,   149,   227,   228, 
     2201     554,     4,  1146,   236,   398,    42,    98,  1644,  1548,    92, 
     2202      93,   495,    95,  -462,  1548,   234,    42,   887,  1152,   930, 
     2203     287,    98,    12,   341,   483,  1644,   898,   302,   473,    12, 
     2204     496,    42,   474,   944,    89,   -93,    42,     4,   -93,    12, 
     2205     949,     8,     9,    89,   410,  1093,   504,     4,   921,   922, 
     2206     923,    92,    93, -1014,    95, -1014,  -235,   230,    42,    97, 
     2207      92,    93,   301,    95,   973,  -235,   344,    42,    97,    60, 
     2208     353,   355,   345,    12,     4,   302,  1043,     8,    42,    89, 
     2209     294,   949,    12,   105,  1467,  1468,   512,     8,   308,   302, 
     2210     -61,  1210,  1075,   700,  -926,  -536,  1167,   701,    12,   987, 
     2211     210,   211,    12,   230,    97,    57,     4,   999,   234,    98, 
     2212      62,     9,    63,  1010,     8,   273,   530,    92,    93,   278, 
     2213      95,    11,   235,    89,    42,   289,   236,    11,  1066,   542, 
     2214    1086,   542,  1011,  1005,   313,  1146,  1556,  -136,    60,  -536, 
     2215      92,    93,  1398,    95,   232,   233,     8,    42,    97,   639, 
     2216    1040,  1169,    48,   -92,   234,  1385,  1460,  1386,    82,    83, 
     2217    1034,   990,   411,    92,    93,   314,    95,   235,  1363,   319, 
     2218      42,   236,  1222,   -89,    12,  1172,   -89,   425,   426,  1019, 
     2219     911,   227,   228,   -90,  1105,   506,   -90,   452,   453,  1035, 
     2220     635,   342,  1236,   315,   634,   912,    11,  1036,    82,    83, 
     2221     633,  1228,   358,   327,  1365,   724,   847,   105,   320,   683, 
     2222      12,   415,   684,   738,  1370,   727,   367,   738,   -97,   -97, 
     2223      12,   -97,   413,  1434,   105,   -97,  1434,   725,   -97,    11, 
     2224    -275,   105,   415,    98,   417,   671,   672,   105,   105,   105, 
     2225     105,  1522,   105,   368,   105,   105,   848,    12,  1436,   847, 
     2226      98,  1436,  1464,  1442,  1443,  1444,  1472,    98,   587,   752, 
     2227     334,   595,   335,    98,    98,    98,    98,   347,    98,   348, 
     2228      98,    98,  1147,  1631,   384,   413,   349,   105,   632,    12, 
     2229     356,    92,    93,   357,    95,   415,   230,   417,    42,   848, 
     2230     105,   105,   395,  1108,  1140,    11,  -276,     5, -1013,     6, 
     2231   -1013,  1115,   388,    98,  1161,  1162,     7,   639,   937,   390, 
     2232     460,   512,  1663,  1664,  1129,   465,    98,    98,   468,   208, 
     2233     209, -1013,   392, -1013, -1013,   477, -1013,   410,  -100,  -100, 
     2234     411,  -100,   419,   269,  -222,  -100,   699,   234,  -100,   500, 
     2235     698,   508,  1417,   393,   394,   105,    92,    93,  1148,    95, 
     2236     235,   556,   563,    42,   236,   423,     9,   448,   450,   504, 
     2237    1198,   456,   457,   433,   434,   435,   436,   437,   438,   439, 
     2238     739,   696,   509,   728,   282,   575,   576,   469,   577,     9, 
     2239     472,   481,     9,    10,    92,    93,   523,    95,   590,   547, 
     2240     598,    42,   635,   294,   239,  1223,   634,   550,   239,   723, 
     2241    1288,   602,   552,   604,   581, -1013,    60, -1013,  1039,    60, 
     2242      42,   747,    36,    37,    38,    39,   412,  1422,   631,  1465, 
     2243      40,  1420,   639,  1465,   652,   542,    41,   727,    42,   738, 
     2244      36,    37,    38,    39,   105,   650,   660,   663,    40,   429, 
     2245     661,    11,  1147,   664,    41,  -233,   787,   105,   669,   -99, 
     2246     -99,   670,   -99,  -228,  1470,    93,   -99,    95,   361,   -99, 
     2247      98,    42,   675,     9,    11,   225,    77,    11,   677,  1310, 
     2248     680,   600,   226,    98,  -937,  -223,   691,  -938,   693,   703, 
     2249     227,   228,   229,   105,   696,   739,   862,   869,   883,   886, 
     2250      60,   399,   705,    92,    93,   710,    95,   711,   897,   712, 
     2251      42,   706,  1152,   700,   715,   709,   717,   701,   718,    98, 
     2252     757,   105,   440,   441,   442,   443,   716,   758,   216,   217, 
     2253     218,   633,   224,   744,   777,   762,   781,   696,   105,   782, 
     2254     226,   784,   740,   742,   401,   785,   753,    98,   227,   228, 
     2255     745,   795,   755,  1414,   304,   798,   444,   445,    11,   305, 
     2256     800,   808,   376,   812,    98,   402,   813,   783,  -137,   839, 
     2257     841,   843,   844,   907,   377,   845,   797,   378,   379,   913, 
     2258     932,  1377,   949,   919,   914,   799,   933,   936,   964,   946, 
     2259    1017,   306,   965,   807,   967,   230,   380,   226,   810,  1414, 
     2260     971,  -229,  1414,   439,   979,   227,   228,  1414,   982,   632, 
     2261     983,  1414,   987,   842,  1414,   991,   992,   993,  1005,   996, 
     2262     231,  1421,  1006,  1066,  1009,  -445,  1045,  1046,  1047,  1049, 
     2263    1053,  1054,  1057,  1071,  1059,  1063,   232,   233,   990,  1077, 
     2264     123,  1074,  1082,   381,   306,   123,   234,  1706,  1087,  1088, 
     2265     123,   123,  1095,   230,  1090,    92,    93,  1097,    95,   235, 
     2266    1106,  1113,    42,   236,   237,  1040,  1120,  1138,  1143,  1185, 
     2267    1182,  1066,   238,  1186,   929,  1187,  1188,  1190,   231,  1192, 
     2268    1197,   105,   299,   746,  1202,   105,  1211,  1212,   123,  1213, 
     2269     945,  1427,   299,  1221,   232,   233,  1246,  1261,   105,   962, 
     2270    1264,  1274,  1281,  1277,   234,  1284,  1285,    98,  1322,  1375, 
     2271     230,    98,  1330,    92,    93,  1342,    95,   235,   105,  1350, 
     2272      42,   236,   237,   305,    98,  1351,  1083,  1361,  1537,  1638, 
     2273     238,   105,   355,   633,  1352,   231,  1362,  1382,   377,  1368, 
     2274     105,   378,   379,  1389,    98,  1637,  1387,  1388,  1414,  1390, 
     2275    1423,   232,   233,  -519,  1394,   306,  1429,    98,  1430,   123, 
     2276     380,   234,  1652,  1453,  1003,   105,    98,  1454,  1458,  1461, 
     2277      92,    93,   226,    95,   235,  1107,  1463,    42,   236,   237, 
     2278     227,   228,   361,  1114,  1466,  -760,  1015,   238,  1016,  1469, 
     2279    1494,   696,  1495,  1496,  1497,  1125,  1503,  1502,  1508,   361, 
     2280    1519,  1032,  1513,  1514,  1531,  1539,  1521,  1044,  1535,  1526, 
     2281    1536,   632,   587,  1541,  1465,  1542,  1544,  1540,   595,  1543, 
     2282    1545,  1550,   105,   239,   633,  -760,  -378,  1549,  1552,  1198, 
     2283    1559,   105,  1560,  1562,  1561,  1567,  1568,  1569,  1574,  1058, 
     2284    1259,     2,     3,   542,  -254,  1606,  1628,  1627,  1613,  1318, 
     2285    1633,  1072,  1639,  1641,  1432,  1649,  1073,    98,  1076,  1650, 
     2286    1653,  1654,  1147,  1671,  1680,     4,  1675,   105,  1681,     5, 
     2287   -1013,     6, -1013,  1677,   269,   105,  1698,  1678,     7,  1685, 
     2288    1414,  1414,  1414,  1686,  1701,   230,   105,  1692,  1414,  1092, 
     2289    1693,  1694,  1700,    98,  1704,    78,  1705,  1711,  1414,  1414, 
     2290    1714,    98,   632,  1708,   534,     8,  1716,  1659,  1712,   303, 
     2291     231,   123,    98,  1414,  1142,  1226,  1227,   674,    50,  1439, 
     2292    1447,   995,  1418,   764,  1437,  1440,   232,   233,     9,   361, 
     2293    1438,    45,  1231,   679,  1554,  1553,   234,   105,   667,   422, 
     2294    1051,  1135,  1648,  1271,  1647,    92,    93,  1137,    95,   235, 
     2295     722,  1547,   336,   236,   237,    10,  1651,  1052,  -760,  1000, 
     2296     123,  1244,   238,  1234,  1206,   534,   534,  1062,  1455,  1173, 
     2297     299,  1150,  1153,  1280,  1699,  1660,   226,  1679,   702,  1396, 
     2298    1551,  1216,  1168,  1249,   227,   228,  1131,  1618,   809,  1178, 
     2299     230,  1684,  1180,  1181,  1622,  1147,   818,   595,  1329,  1620, 
     2300     105,   819,  1507,  1512,  1623,   687,   455,   686,   689,   690, 
     2301    1033,   688,  1068,    11,  1064,   231,  -201,  -201,  -201,  -201, 
     2302    1070,   823,   836,   540,  -201,   564,    98,   837,   862,   824, 
     2303    -201,   232,   233,  1528,   869,   647,  1707,   917,    12,  1709, 
     2304     826,   234,  1336,   920,   900,   827,  1339,  1119,  1250,   883, 
     2305      92,    93,  1717,    95,   235,   226,   828,    42,   236,   237, 
     2306    1149,  1557,  1158,   227,   228,   829,   105,   238,  1136,   628, 
     2307     831,  1148,  1673,  1343,  1260,  1134,   832,   571,   833,   987, 
     2308     147,  1696,   299,   299,   737,   466,  1267,   707,  1268,   230, 
     2309    1379,   986,    98,  1272,   339,  1399,   978,   834,   931,    61, 
     2310    1278,  1279,   226,  1378,   304,  1534,   359,     0,  1314,   305, 
     2311     227,   228,  1355,  1381,   231,     0,     0,   963,     0,  1287, 
     2312    1289,     0,     0,     0,   377,     0,     0,   378,   379,     0, 
     2313     232,   233,     0,     0,     0,   299,     0,     0,     0,  1324, 
     2314     234,   306,     0,     0,   299,     0,   380,     0,     0,    92, 
     2315      93,     0,    95,   235,     0,     0,    42,   236,   237,     0, 
     2316       0,     0,     0,  1340,     0,     0,   238,     0,   230,     0, 
     2317     409,     0,   299,   299,     0,     0,   418,     0,     0,     0, 
     2318       0,   299,   299,     0,     0,     0,     0,     0,     0,     0, 
     2319    1354,   409,     0,   231,     0,     0,  1357,     0,     0,   534, 
     2320    1359,     0,     0,  1360,     0,   299,  1364,  1366,     0,   232, 
     2321     233,     0,  1369,     0,  1371,   230,     0,     0,     0,   234, 
     2322     299,     0,     0,     0,  1376,     0,     0,     0,    92,    93, 
     2323       0,    95,   235,     0,     0,    42,   236,   237,     0,   534, 
     2324     231,     0,     0,     0,   505,   238,     0,     0,     0,     0, 
     2325       0,     0,  1391,     0,     0,   537,   232,   233,   548,  1397, 
     2326       0,     0,  1416,     0,     0,  1419,   234,     0,     0,     0, 
     2327       0,     0,     0,   572,   574,    92,    93,     0,    95,   235, 
     2328     534,     0,    42,   236,   237,   765,     0,   814,     0,     0, 
     2329     586,     0,   238,   586,     0,  1473,  1474,  1475,  1476,  1477, 
     2330    1478,     0,  1479,  1480,  1481,  1482,  1483,  1484,   299,  1485, 
     2331    1486,  1487,  1488,  1489,     0,   608,   359,   359,   505,     0, 
     2332       0,     0,     0,     0,     0,     0,     0,   155,     0,     0, 
     2333       0,  1456,     0,  1457,     0,     0,     0,  1432,     0,     0, 
     2334       0,     0,   156,   668,   226,     0,     0,     0,     0,     0, 
     2335       0,     0,   227,   228,     0,     0,     0,   157,     0,    82, 
     2336      83,   766,     0,     0,   158,     0,  1498,   159,   160,   161, 
     2337     162,     0,     0,   163,     0,     0,   164,   165,   166,     0, 
     2338       0,     0,  1509,     0,     0,     0,     0,     0,     0,  1511, 
     2339     767,     0,   768,   769,   770,     0,     0,   771,   772,     0, 
     2340     773,   774,   167,     0,     0,     0,     0,  1523,  1524,     0, 
     2341    1525,     0,     0,     0,     0,  1527,    89,     0,     0,     0, 
     2342       0,     0,     0,     0,     0,  1530,     0,     0,     0,     0, 
     2343    1645,     0,   299,    92,    93,     0,    95,   226,   751,     0, 
     2344      42,    97,     0,     0,     0,   227,   228,     0,   756,   299, 
     2345       0,     0,     0,     0,     0,     0,   299,   230,     0,     0, 
     2346       0,     0,   299,   299,   299,   299,     0,   299,   300,   299, 
     2347     299,     0,     0,     0,     0,     0,     0,     0,   307,     0, 
     2348       0,     0,   231,     0,   677,  1490,  1491,     0,     0,     0, 
     2349       0,     0,     0,     0,     0,     0,     0,     0,   232,   233, 
     2350       0,     0,   123,     0,     0,     0,     0,     0,   234,     0, 
     2351       0,     0,     0,   534,     0,   299,   299,    92,    93,     0, 
     2352      95,   235,     0,     0,    42,   236,   237,     0,     0,     0, 
     2353       0,     0,   227,   228,   238,     0,     0,     0,     0,     0, 
     2354       0,  1687,     0,     0,  1615,     0,     0,     0,   226,  1619, 
     2355     230,   505,     0,     0,     0,     0,   227,   228,     0,     0, 
     2356    1624,  1625,  1626,     0,     0,     0,  1629,  1630,     0,     0, 
     2357       0,  1632,     0,     0,     0,   231,     0,  1634,     0,  1636, 
    16192358       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1620        0,     0,     0,     0,     0,   578,   390,   391,     0,     0, 
     2359     952,   232,   233,     0,   737,     0,     0,   534,   737,     0, 
     2360       0,   234,     0,     0,     0,     0,     0,     0,     0,   409, 
     2361      92,    93,     0,    95,   235,   534,     0,    42,   236,   237, 
     2362       0,     0,     0,     0,     0,     0,     0,   238,     0,     0, 
     2363       0,   952,     0,     0,  1702,     0,     0,   230,     0,     0, 
     2364       0,   226,   984,     0,   985,     0,     0,     0,     0,   227, 
     2365     228,     0,     0,     0,     0,     0,     0,     0,     0,   299, 
     2366       0,   230,   231,     0,     0,     0,  1672,     0,     0,     0, 
     2367       0,     0,   123,     0,     0,     0,  1674,     0,   232,   233, 
     2368    1676,     0,     0,  1018,     0,  1020,   231,     0,   234,     0, 
     2369     536,     0,     0,  1028,     0,     0,     0,    92,    93,     0, 
     2370      95,   235,   232,   233,    42,   236,   237,     0,   299,     0, 
     2371       0,     0,   234,     0,   238,  1695,     0,     0,  1697,     0, 
     2372       0,    92,    93,     0,    95,   235,     0,     0,    42,   236, 
     2373     237,     0,     0,     0,     0,     0,   299,     0,   238,     0, 
     2374     534,     0,     0,     0,  1597,     0,     0,     0,     0,     0, 
     2375     226,   619,   619,   299,   230,     0,     0,     0,   227,   228, 
     2376       0,  1598,     0,     0,     0,     0,     0,     0,     0,     0, 
     2377     534,   534,     0,     0,     0,     0,     0,     0,     0,   231, 
    16212378       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1622        0,     0,     0,     0,     0,     0,   585,   390,   391,   373, 
    1623      374,   375,   376,   377,   378,     0,   379,   380,   381,   382, 
    1624      383,   384,     0,   385,   386,   387,   388,   389,  -239,  -239, 
    1625     -239,  -239,  -239,  -239,     0,  -239,  -239,  -239,  -239,  -239, 
    1626     -239,     0,  -239,  -239,  -239,  -239,  -239,  -238,  -238,  -238, 
    1627     -238,  -238,  -238,     0,  -238,  -238,  -238,  -238,  -238,  -238, 
    1628        0,  -238,  -238,  -238,  -238,  -238,     0,     0,     0,   390, 
    1629      391,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1630        0,     0,     0,     0,     0,     0,     0,     0,     0,   390, 
    1631      391,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1632        0,     0,     0,     0,     0,     0,     0,     0,     0,   390, 
    1633      391,   373,   374,   375,   376,   377,   378,     0,   379,   380, 
    1634      381,   382,   383,   384,     0,   385,   386,   387,   388,   389, 
    1635      373,   374,   375,   376,   377,   378,     0,   379,   380,   381, 
    1636      382,   383,   384,     0,   385,   386,   387,   388,   389,     0, 
     2379       0,   505,   505,   505,   505,   232,   233,     0,     0,   505, 
     2380       0,     0,     0,     0,     0,   234,     0,     0,     0,     0, 
     2381       0,   505,     0,     0,    92,    93,     0,    95,   235,     0, 
     2382       0,    42,   236,   237,     0,     0,     0,     0,     0,     0, 
     2383       0,   238,     0,     0,     0,     0,     0,     0,     0,     0, 
     2384       0,  -224,  -224,     0,  -224,  -224,  1141,  -224,  -224,  -224, 
     2385    -224,  -224,  -224,  -224,  -224,  -224,  -224,  -224,  -224,  -224, 
     2386       0,     0,     0,   230,   359,  1028,     0,     0,   300,   300, 
     2387       0,  1159,   572,     0,     0,  1166,     0,     0,     0,     0, 
     2388       0,     0,  1174,     0,     0,     0,     0,     0,   231,     0, 
     2389       0,     0,     0,     0,     0,     0,     0,     0,     0,  -224, 
     2390       0,     0,     0,     0,   232,   233,     0,     0,     0,     0, 
     2391     409,     0,     0,   299,   234,     0,     0,     0,  1204,     0, 
     2392       0,   805,     0,    92,    93,     0,    95,   235,  1580,     0, 
     2393      42,   236,   237,   299,   226,     0,     0,     0,     0,     0, 
     2394     238,     0,   227,   228,     0,     0,   299,     0,  1241,     0, 
     2395       0,     0,     0,     0,     0,   299,  1245,     0,   888,   891, 
     2396    1248,   751,     0,  1251,  1252,     0,  1253,   888,   891,     0, 
     2397       0,     0,     0,     0,  1602,     0,     0,     0,     0,     0, 
     2398     226,     0,     0,     0,     0,   619,     0,     0,   227,   228, 
     2399       0,   888,     0,     0,   153,     0,  -224,  -224,  -224,  -224, 
     2400       0,     0,     0,     0,   154,     0,   307,     0,     0,     0, 
     2401       0,   534,   534,     0,  1604,     0,   572,     0,   534,  1313, 
     2402     226,     0,  1315,     0,     0,   951,     0,  -224,   227,   228, 
     2403    -224,  -224,  -224,     0,   155,   411,     0,  1573,     0,     0, 
     2404       0,     0,     0,     0,     0,   505,   299,   230,     0,   156, 
     2405       0,     0,   505,     0,     0,     0,     0,     0,     0,     0, 
     2406       0,     0,     0,     0,   157,     0,   951,    84,  -124,     0, 
     2407       0,   158,   231,     0,   159,   160,   161,   162,     0,     0, 
     2408     163,     0,   123,   164,   165,   166,     0,     0,   232,   233, 
     2409     299,  1028,     0,   230,   300,     0,     0,     0,   234,     0, 
     2410       0,   299,     0,     0,     0,     0,     0,    92,    93,   167, 
     2411      95,   235,  1174,     0,    42,   236,   237,     0,   231,     0, 
     2412       0,   952,   952,    89,   238,     0,    90,     0,     0,     0, 
     2413       0,     0,     0,   230,   232,   233,     0,     0,  -124,     0, 
     2414      92,    93,     0,    95,   234,     0,     0,   168,    97,     0, 
     2415       0,  1395,  1573,    92,    93,     0,    95,   235,   231,     0, 
     2416      42,   236,   237,     0,     0,     0,     0,     0,     0,     0, 
     2417     238,     0,     0,     0,   232,   233,     0,     0,     0,     0, 
     2418       0,     0,     0,     0,   234,  1426,     0,     0,     0,  1428, 
     2419       0,     0,     0,    92,    93,     0,    95,   235,  1028,     0, 
     2420      42,   236,   237,     0,     0,     0,     0,   814,     0,     0, 
     2421     238,     0,     0,     0,     0,   123,     0,     0,     0,     0, 
    16372422       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1638        0,     0,     0,     0,     0,     0,     0,   599,   390,   391, 
     2423    1459,     0,     0,     0,     0,   888,     0,     0,     0,     0, 
     2424       0,     0,   888,     0,  1462,     0,     0,   155,   888,   891, 
     2425     891,   888,     0,  1126,     0,   888,  1126,     0,     0,     0, 
     2426       0,     0,   156,     0,     0,     0,     0,     0,     0,     0, 
     2427       0,     0,  1145,     0,     0,     0,     0,   157,     0,     0, 
     2428       0,  1028,     0,     0,   158,     0,     0,   159,   160,   161, 
     2429     162,     0,     0,   163,  1518,     0,   164,   165,   166,   619, 
     2430       0,  1154,  1154,     0,     0,     0,     0,     0,     0,     0, 
     2431       0,     0,  1174,     0,  1174,     0,     0,   -88,   -88,     0, 
     2432     -88,   -88,   167,   -88,   -88,   -88,   -88,   -88,   -88,   -88, 
     2433     -88,   -88,   -88,   -88,   -88,   -88,    89,     0,     0,     0, 
    16392434       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1640        0,     0,     0,     0,     0,     0,  -239,  -239,  -239,     0, 
     2435       0,     0,     0,    92,    93,     0,    95,     0,     0,     0, 
     2436      42,    97,  1241,  1241,     0,     0,     0,     0,  1555,  1028, 
     2437       0,     0,     0,     0,     0,   -88,     0,     0,     0,     0, 
     2438       0,     0,     0,  1240,     0,     0,     0,  1204,     0,     0, 
     2439       0,     0,     0,     0,     0,     0,   226,     0,     0,     0, 
     2440       0,  1154,     0,     0,   227,   228,     0,     0,     0,     0, 
     2441       0,     0,  1582,  1583,  1584,  1585,  1586,  1587,  1588,  1589, 
     2442    1590,  1591,  1592,  1593,  1594,  1595,  1596,  1600,  1601,  1603, 
     2443    1605,     0,     0,     0,   872,     0,   873,   874,   875,   876, 
     2444       0,   877,     0,   878,   879,   805,     0,     0,     0,     0, 
     2445     880,     0,   881,     0,   882,     0,     0,     0,     0,     0, 
    16412446       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1642        0,     0,     0,     0,     0,  -238,  -238,  -238,   373,   374, 
    1643      375,   376,   377,   378,     0,   379,   380,   381,   382,   383, 
    1644      384,     0,   385,   386,   387,   388,   389,   373,   374,   375, 
    1645      376,   377,   378,     0,   379,   380,   381,   382,   383,   384, 
    1646        0,   385,   386,   387,   388,   389,   373,   374,   375,   376, 
    1647      377,   378,     0,   379,   380,   381,   382,   383,   384,     0, 
    1648      385,   386,   387,   388,   389,     0,     0,     0,     0,   613, 
    1649      390,   391,     0,     0,     0,     0,     0,     0,     0,     0, 
    1650        0,     0,     0,     0,     0,     0,     0,     0,   650,   390, 
    1651      391,   373,   374,   375,   376,   377,   378,     0,   379,   380, 
    1652      381,   382,   383,   384,     0,   385,   386,   387,   388,   389, 
    1653      373,   374,   375,   376,   377,   378,     0,   379,   380,   381, 
    1654      382,   383,   384,     0,   385,   386,   387,   388,   389,   373, 
    1655      374,   375,   376,   377,   378,     0,   379,   380,   381,   382, 
    1656      383,   384,     0,   385,   386,   387,   388,   389,     0,     0, 
    1657        0,     0,     0,     0,   135,   136,     0,     0,     0,     0, 
    1658      137,   138,   139,   140,   141,     0,   653,   390,   391,     0, 
    1659        0,     0,     0,     0,     0,   142,   143,   144,   145,   146, 
    1660      147,   148,   399,   149,   150,   151,   390,   391,   152,   153, 
    1661      154,     0,   155,   156,   157,   158,   159,     0,   160,     0, 
    1662        0,     0,     0,     0,   779,   390,   391,   373,   374,   375, 
    1663      376,   377,   378,     0,   379,   380,   381,   382,   383,   384, 
    1664        0,   385,   386,   387,   388,   389,   373,   374,   375,   376, 
    1665      377,   378,     0,   379,   380,   381,   382,   383,   384,     0, 
    1666      385,   386,   387,   388,   389,     0,     0,     0,     0,   780, 
    1667      390,   391,     0,   162,     0,     0,     0,     0,     0,   163, 
    1668      164,     0,     0,     0,     0,   165,     0,     0,   781,   390, 
    1669      391,     0,     0,     0,   166,   167,     0,   168,   169,     0, 
    1670        0,   918,   171,   562,     0,     0,     0,   782,   390,   391, 
    1671      373,   374,   375,   376,   377,   378,     0,   379,   380,   381, 
    1672      382,   383,   384,     0,   385,   386,   387,   388,   389,   373, 
    1673      374,   375,   376,   377,   378,     0,   379,   380,   381,   382, 
    1674      383,   384,     0,   385,   386,   387,   388,   389,   373,   374, 
    1675      375,   376,   377,   378,     0,   379,   380,   381,   382,   383, 
    1676      384,     0,   385,   386,   387,   388,   389,     0,     0,     0, 
     2447       0,     0,   -88,   -88,   -88,   -88,     0,     0,  1640,     0, 
    16772448       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1678        0,     0,     0,     0,     0,   783,   390,   391,     0,     0, 
     2449       0,     0,     0,     0,   891,     0,     0,     0,     0,     0, 
     2450       0,     0,  1204,   -88,   -88,     0,   -88,   -88,   -88,   230, 
     2451     -88,     0,     0,     0,     0,     0,     0,     0,     0,  1665, 
     2452       0,     0,   307,     0,   226,     0,  1154,     0,     0,     0, 
     2453       0,     0,   227,   228,   231,     0,  1666,  1667,     0,     0, 
     2454       0,  1668,     0,  1669,     0,     0,     0,     0,     0,     0, 
     2455     232,   233,     0,     0,   226,     0,   951,   951,     0,     0, 
     2456     234,     0,   227,   228,   609,     0,     0,     0,     0,    92, 
     2457      93,     0,    95,   235,     0,     0,    42,   236,   237,     0, 
     2458       0,     0,     0,     0,     0,     0,   238,     0,     0,     0, 
     2459       0,     0,     0,   610,     0,     0,     0,     0,     0,     0, 
     2460    1691,   611,     0,   612,   613,   614,   615,   396,   616,     0, 
     2461     617,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
     2462       0,     0,     0,     0,     0,     0,  1703,     0,     0,     0, 
     2463       0,     0,     0,     0,     0,     0,     0,   230,     0,   226, 
     2464       0,  1710,     0,  1691,  1713,     0,     0,   227,   228,     0, 
     2465    1715,     0,     0,     0,     0,  1718,     0,     0,     0,     0, 
     2466       0,     0,   231,     0,     0,     0,     0,   230,     0,     0, 
     2467       0,     0,     0,     0,     0,     0,     0,   852,   232,   233, 
     2468       0,   853,   854,   855,   856,   857,   858,     0,   234,     0, 
     2469       0,     0,   231,   859,   860,   861,     0,    92,    93,   891, 
     2470      95,   235,     0,     0,    42,   236,   237,     0,   232,   233, 
     2471      89,     0,     0,     0,   238,   226,     0,     0,   234,   891, 
     2472       0,     0,     0,   227,   228,     0,     0,    92,    93,     0, 
     2473      95,   235,  1154,     0,   618,   503,   237,     0,     0,     0, 
     2474       0,     0,     0,     0,   238,     0,     0,     0,     0,     0, 
     2475       0,     0,   230,   872,     0,   873,     0,   875,   876,     0, 
     2476     877,     0,   878,   879,     0,     0,     0,     0,     0,   880, 
     2477       0,   881,     0,   882,     0,     0,     0,   231,     0,     0, 
    16792478       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1680        0,     0,     0,     0,   784,   390,   391,   373,   374,   375, 
    1681      376,   377,   378,     0,   379,   380,   381,   382,   383,   384, 
    1682        0,   385,   386,   387,   388,   389,   373,   374,   375,   376, 
    1683      377,   378,     0,   379,   380,   381,   382,   383,   384,     0, 
    1684      385,   386,   387,   388,   389,   373,   374,   375,   376,   377, 
    1685      378,     0,   379,   380,   381,   382,   383,   384,     0,   385, 
    1686      386,   387,   388,   389,     0,     0,     0,     0,   785,   390, 
    1687      391,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1688        0,     0,     0,     0,     0,     0,     0,   786,   390,   391, 
     2479       0,     0,     0,   232,   233,     0,     0,  1240,  1240,     0, 
     2480    1291,     0,     0,   234,  1154,     0,     0,     0,  1292,  1293, 
     2481       0,     0,    92,    93,     0,    95,   235,     0,     0,    42, 
     2482     236,   237,     0,     0,     0,     0,     0,     0,   230,   238, 
     2483       0,     0,     0,  1294,     0,     0,     0,     0,     0,     0, 
     2484       0,     0,     0,     0,     0,     0,     0,   591,     0,     0, 
     2485       0,     0,     0,   231,   592,   226,   593,   594,     0,     0, 
     2486       0,     0,     0,   227,   228,     0,     0,     0,     0,   232, 
     2487     233,     0,     0,     0,     0,     0,   888,     0,     0,   234, 
     2488       0,     0,     0,     0,     0,   226,     0,   888,    92,    93, 
     2489       0,    95,   235,   227,   228,    42,   236,   237,  1295,     0, 
     2490       0,     0,   582,     0,     0,   238,     0,     0,     0,   583, 
     2491       0,   584,   585,   230,     0,     0,     0,     0,     0,     0, 
    16892492       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1690        0,     0,     0,     0,     0,     0,   787,   390,   391,   373, 
    1691      374,   375,   376,   377,   378,     0,   379,   380,   381,   382, 
    1692      383,   384,     0,   385,   386,   387,   388,   389,   373,   374, 
    1693      375,   376,   377,   378,     0,   379,   380,   381,   382,   383, 
    1694      384,     0,   385,   386,   387,   388,   389,     0,     0,     0, 
     2493       0,     0,   591,     0,     0,     0,     0,     0,   231,   592, 
     2494     226,   593,   594,     0,  1296,     0,     0,     0,   227,   228, 
     2495       0,     0,     0,     0,  1297,  1298,     0,     0,     0,     0, 
     2496       0,     0,     0,     0,   234,     0,     0,     0,   230,     0, 
     2497       0,     0,     0,  1299,  1300,     0,  1301,  1302,     0,     0, 
     2498      42,  1303,   237,     0,     0,     0,   865,   866,     0,     0, 
     2499     238,     0,     0,   231,   867,   226,   868,     0,   230,     0, 
     2500       0,     0,     0,   227,   228,     0,   226,     0,     4,   232, 
     2501     233,     0,     0,     0,   227,   228,   502,     0,     0,   234, 
     2502       0,     0,     0,   231,     0,     0,     0,     0,    92,    93, 
     2503       0,    95,   235,     0,     0,    42,   236,   237,     0,   232, 
     2504     233,     0,     0,     0,     0,   238,     0,     0,     8,   234, 
     2505       0,     0,     0,   230,     0,     0,     0,     0,    92,    93, 
     2506     226,    95,   235,     0,     0,    42,   236,   237,   227,   228, 
     2507     916,   226,     0,     0,     0,   238,     0,     0,   231,   227, 
     2508     228,     0,     0,     0,     4,     0,     0,     0,     0,     0, 
     2509       0,     0,     0,     0,   232,   233,     0,     0,     0,     0, 
     2510       0,     0,     0,     0,   234,     0,     0,     0,   230,     0, 
     2511       0,     0,     0,    92,    93,     0,    95,   235,   226,   230, 
     2512      42,   236,   237,     0,     8,     0,   227,   228,     0,     0, 
     2513     238,     0,     0,   231,     0,     0,     0,     0,     0,     0, 
     2514       0,     0,     0,     0,   231,     0,     0,     0,     0,   232, 
     2515     233,     0,     0,     0,     0,   226,     0,     0,     0,   234, 
     2516     232,   233,    89,   227,   228,  1247,     0,     0,    92,    93, 
     2517     234,    95,   235,   230,     0,    42,   236,   237,     0,    92, 
     2518      93,    12,    95,   235,   230,   238,    42,   503,   237,     0, 
     2519       0,     0,   226,     0,     0,     0,   238,     0,   231,     0, 
     2520     227,   228,  -391,   226,     0,     0,     0,     0,     0,   231, 
     2521       0,   227,   228,     0,   232,   233,     0,     0,     0,     0, 
     2522       0,     0,     0,     0,   234,   232,   233,     0,     0,     0, 
     2523       0,   230,     0,    92,    93,   234,    95,   235,     0,     0, 
     2524      42,   236,   237,     0,    92,    93,     0,    95,   235,     0, 
     2525     238,    42,   236,  1027,     0,     0,   231,    12,   226,     0, 
     2526       0,   238,     0,     0,     0,     0,   227,   228,   230,     0, 
     2527       0,     0,   232,   233,     0,     0,     0,     0,     0,     0, 
     2528       0,     0,   234,     0,     0,     0,     0,     0,   226,     0, 
     2529       0,    92,    93,   231,    95,   235,   227,   228,   533,   236, 
     2530     237,  1235,     0,   226,     0,   230,     0,     0,   238,   232, 
     2531     233,   227,   228,     0,     0,     0,   230,     0,     0,   234, 
     2532       0,     0,     0,     0,     0,     0,     0,     0,    92,    93, 
     2533     231,    95,   235,     0,   226,    42,   236,   237,     0,     0, 
     2534       0,   231,   227,   228,     0,   238,   232,   233,     0,     0, 
     2535       0,     0,     0,     0,     0,     0,   234,   232,   233,     0, 
     2536       0,     0,     0,     0,     0,    92,    93,   234,    95,   235, 
     2537       0,   230,    42,   236,   237,     0,    92,    93,     0,    95, 
     2538     235,   226,   238,    42,   236,   351,     0,     0,     0,   227, 
     2539     228,     0,     0,   238,     0,     0,   231,     0,     0,     0, 
     2540       0,   230,     0,     0,     0,     0,     0,     0,     0,     0, 
     2541     226,     0,   232,   233,     0,     0,   230,     0,   227,   228, 
     2542       0,     0,   234,     0,     0,     0,   231,     0,     0,     0, 
     2543       0,    92,    93,     0,    95,   235,     0,     0,    42,   236, 
     2544     354,   231,   232,   233,     0,     0,     0,   230,   238,     0, 
     2545       0,     0,   234,     0,     0,     0,     0,   232,   233,     0, 
     2546       0,    92,    93,     0,    95,   235,     0,   234,    42,   236, 
     2547     404,     0,   231,     0,     0,     0,    92,    93,   238,    95, 
     2548     235,     0,     0,    42,   236,   237,     0,     0,   232,   233, 
     2549       0,     0,    79,   238,   230,     0,     0,     0,   234,    80, 
     2550       0,     0,     0,     0,     0,     0,     0,    92,    93,     0, 
     2551      95,   235,     0,     0,   533,   236,   237,     0,     0,   231, 
     2552       0,     0,     0,   230,   238,     0,     0,     0,     0,     0, 
     2553       0,     0,     0,     0,     0,   232,   233,     0,     0,     0, 
     2554       0,     0,     0,     0,     0,   234,     0,     0,   231,    81, 
     2555       0,     0,     0,     0,    92,    93,     0,    95,   235,     0, 
     2556       0,    42,   236,  1027,   232,   233,    82,    83,     0,     0, 
     2557       0,   238,     0,     0,   234,     0,     0,     0,    84,     0, 
     2558       0,     0,     0,    92,    93,     0,    95,   235,     0,     0, 
     2559    1078,  1079,  1080,     0,     0,     0,     0,  -446,     0,    85, 
     2560     238,    86,    87,     0,     0,     0,     0,  -459,     0,  -472, 
     2561       0,    80,     0,     0,    88,     0,     0,   153,     0,     0, 
     2562       0,     0,     0,     0,     0,     0,  -703,   154,     0,     0, 
     2563       0,     0,     0,     0,    89,     0,     0,    90,    91,  -331, 
     2564       0,     0,  -331,  -331,  -331,  -331,     0,     0,     0,     0, 
     2565    -331,    92,    93,    94,    95,     0,  -331,   155,    96,    97, 
    16952566       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1696        0,     0,     0,     0,     0,   788,   390,   391,     0,     0, 
    1697        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1698        0,     0,     0,     0,   789,   390,   391,     0,     0,     0, 
    1699        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1700        0,     0,     0,   790,   390,   391,   373,   374,   375,   376, 
    1701      377,   378,     0,   379,   380,   381,   382,   383,   384,     0, 
    1702      385,   386,   387,   388,   389,   373,   374,   375,   376,   377, 
    1703      378,     0,   379,   380,   381,   382,   383,   384,     0,   385, 
    1704      386,   387,   388,   389,   373,   374,   375,   376,   377,   378, 
    1705        0,   379,   380,   381,   382,   383,   384,     0,   385,   386, 
    1706      387,   388,   389,     0,     0,     0,     0,   791,   390,   391, 
    1707        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1708        0,     0,     0,     0,     0,     0,   852,   390,   391,   373, 
    1709      374,   375,   376,   377,   378,     0,   379,   380,   381,   382, 
    1710      383,   384,     0,   385,   386,   387,   388,   389,   373,   374, 
    1711      375,   376,   377,   378,     0,   379,   380,   381,   382,   383, 
    1712      384,     0,   385,   386,   387,   388,   389,   373,   374,   375, 
    1713      376,   377,   378,     0,   379,   380,   381,   382,   383,   384, 
    1714        0,   385,   386,   387,   388,   389,     0,     0,     0,     0, 
    1715        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1716        0,     0,     0,     0,   930,   390,   391,     0,     0,     0, 
    1717        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1718        0,     0,     0,   933,   390,   391,     0,     0,     0,     0, 
    1719        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1720        0,     0,   946,   390,   391,   373,   374,   375,   376,   377, 
    1721      378,     0,   379,   380,   381,   382,   383,   384,     0,   385, 
    1722      386,   387,   388,   389,     0,     0,     0,     0,     0,     0, 
    1723        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1724        0,     0,     0,     0,     0,   702,     0,   947,   390,   391, 
    1725        0,     0,   132,     0,     0,     0,     0,     0,     0,     0, 
    1726      133,   134,   703,     0,     0,     0,  1022,   390,   391,     0, 
    1727        0,     0,     0,     0,   135,   136,     0,     0,     0,     0, 
    1728      137,   138,   139,   140,   141,  1033,   390,   391,     0,     0, 
    1729        0,     0,     0,     0,     0,   142,   143,   144,   145,   146, 
    1730      147,   148,     0,   149,   150,   151,     0,     0,   152,   153, 
    1731      154,     0,   155,   156,   157,   158,   159,   439,   160,     0, 
    1732        0,     0,   440,   441,     0,   442,   443,     0,     0,     0, 
    1733        0,     0,     0,     0,     0,     0,     0,   444,   445,   446, 
    1734      447,   448,   449,   450,     0,   451,   452,   453,     0,     0, 
    1735      454,   455,   456,     0,   814,   457,   458,   459,   460,     0, 
    1736      461,   132,     0,     0,   390,   391,   161,     0,     0,   133, 
    1737      134,     0,     0,   162,     0,     0,     0,     0,     0,   163, 
    1738      164,     0,     0,   135,   136,   165,     0,     0,     0,   137, 
    1739      138,   139,   140,   141,   166,   167,     0,   168,   169,     0, 
    1740        0,   170,   171,   172,   142,   143,   144,   145,   146,   147, 
    1741      148,     0,   149,   150,   151,     0,     0,   152,   153,   154, 
    1742        0,   155,   156,   157,   158,   159,     0,   160,     0,     0, 
    1743        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1744        0,     0,     0,   462,     0,     0,     0,     0,     0,     0, 
    1745        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1746        0,     0,     0,   904,     0,     0,     0,     0,     0,     0, 
    1747      132,     0,     0,     0,     0,   161,     0,     0,   133,   134, 
    1748        0,     0,   162,     0,     0,     0,     0,     0,   163,   164, 
    1749        0,     0,   135,   136,   165,     0,     0,     0,   137,   138, 
    1750      139,   140,   141,   166,   167,     0,   168,   169,     0,     0, 
    1751      170,   171,   172,   142,   143,   144,   145,   146,   147,   148, 
    1752        0,   149,   150,   151,     0,     0,   152,   153,   154,     0, 
    1753      155,   156,   157,   158,   159,     0,   160,     0,     0,     0, 
     2567       0,     0,   156,     0,     0,     0,     0,     0,     0,     0, 
     2568       0,     0,     0,  -703,  -703,  -703,     0,   157,     0,    80, 
     2569      84,     0,  -703,     0,   158,   153,     0,   159,   160,   161, 
     2570     162,     0,     0,   163,     0,   154,   164,   165,   166,     0, 
     2571    -703,     0,    80,     0,     0,     0,     0,     0,   153,     0, 
     2572       0,     0,     0,     0,     0,     0,     0,     0,   154,     0, 
     2573       0,     0,   167,     0,     0,   155,     0,     0,     0,     0, 
     2574       0,     0,     0,     0,     0,     0,    89,  -703,  -703,    90, 
     2575     156,     0,     0,     0,     0,     0,     0,     0,   155,     0, 
     2576       0,     0,     0,    92,    93,   157,    95,     0,    84,  -127, 
     2577     168,    97,   158,   156,     0,   159,   160,   161,   162,     0, 
     2578       0,   163,     0,     0,   164,   165,   166,     0,   157,     0, 
     2579       0,    84,  -128,   814,     0,   158,     0,     0,   159,   160, 
     2580     161,   162,     0,     0,   163,     0,     0,   164,   165,   166, 
     2581     167,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
     2582       0,     0,     0,     0,    89,     0,     0,    90,     0,     0, 
     2583       0,     0,     0,   167,     0,     0,     0,     0,     0,  -127, 
     2584       0,    92,    93,     0,    95,     0,     0,    89,   168,    97, 
     2585      90,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
     2586       0,     0,  -128,   157,    92,    93,     0,    95,  -196,     0, 
     2587       0,   168,    97,   159,   160,   161,   162,     0,     0,   163, 
     2588       0,     0,   815,   165,   816,     0,     0,     0,     0,     0, 
    17542589       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    17552590       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    17562591       0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1757        0,     0,   924,     0,     0,     0,     0,     0,     0,   132, 
    1758        0,     0,     0,     0,   161,     0,     0,   133,   134,     0, 
    1759        0,   162,     0,     0,     0,     0,     0,   163,   164,     0, 
    1760        0,   135,   136,   165,     0,     0,     0,   137,   138,   139, 
    1761      140,   141,   166,   167,     0,   168,   169,     0,     0,   170, 
    1762      171,   172,   142,   143,   144,   145,   146,   147,   148,     0, 
    1763      149,   150,   151,     0,     0,   152,   153,   154,     0,   155, 
    1764      156,   157,   158,   159,     0,   160,     0,     0,     0,     0, 
    1765        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1766        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1767        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1768        0,     0,   472,     0,     0,     0,     0,     0,   132,     0, 
    1769        0,     0,     0,   161,     0,     0,   133,   134,   473,     0, 
    1770      162,     0,     0,     0,     0,     0,   163,   164,     0,     0, 
    1771      135,   136,   165,     0,     0,     0,   137,   138,   139,   140, 
    1772      141,   166,   167,     0,   168,   169,     0,     0,   170,   171, 
    1773      172,   142,   143,   144,   145,   146,   147,   148,     0,   149, 
    1774      150,   151,     0,     0,   152,   153,   154,     0,   155,   156, 
    1775      157,   158,   159,     0,   160,     0,     0,     0,     0,     0, 
    1776        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1777        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1778        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1779        0,   632,     0,     0,     0,     0,     0,   132,     0,     0, 
    1780        0,     0,   161,     0,     0,   133,   134,     0,   633,   162, 
    1781        0,     0,     0,     0,     0,   163,   164,     0,     0,   135, 
    1782      136,   165,     0,     0,     0,   137,   138,   139,   140,   141, 
    1783      166,   167,     0,   168,   169,     0,     0,   170,   171,   172, 
    1784      142,   143,   144,   145,   146,   147,   148,     0,   149,   150, 
    1785      151,     0,     0,   152,   153,   154,     0,   155,   156,   157, 
    1786      158,   159,     0,   160,     0,     0,     0,     0,     0,     0, 
    1787        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1788        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1789        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1790      721,     0,     0,     0,     0,     0,   132,     0,     0,     0, 
    1791        0,   161,     0,     0,   133,   134,   473,     0,   162,     0, 
    1792        0,     0,     0,     0,   163,   164,     0,     0,   135,   136, 
    1793      165,     0,     0,     0,   137,   138,   139,   140,   141,   166, 
    1794      167,     0,   168,   169,     0,     0,   170,   171,   172,   142, 
    1795      143,   144,   145,   146,   147,   148,     0,   149,   150,   151, 
    1796        0,     0,   152,   153,   154,     0,   155,   156,   157,   158, 
    1797      159,     0,   160,     0,     0,     0,     0,     0,     0,     0, 
    1798        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1799        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1800        0,     0,     0,     0,     0,     0,     0,     0,     0,   615, 
    1801        0,     0,     0,     0,     0,   132,     0,     0,     0,     0, 
    1802      161,     0,     0,   133,   134,     0,     0,   162,     0,     0, 
    1803        0,     0,     0,   163,   164,     0,     0,   135,   136,   165, 
    1804        0,     0,     0,   137,   138,   139,   140,   141,   166,   167, 
    1805        0,   168,   169,     0,     0,   170,   171,   172,   142,   143, 
    1806      144,   145,   146,   147,   148,     0,   149,   150,   151,     0, 
    1807        0,   152,   153,   154,     0,   155,   156,   157,   158,   159, 
    1808        0,   160,     0,     0,     0,     0,     0,     0,     0,     0, 
    1809        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1810        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1811        0,     0,     0,     0,     0,     0,     0,     0,   637,     0, 
    1812        0,     0,     0,     0,   132,     0,     0,     0,     0,   161, 
    1813        0,     0,   133,   134,     0,     0,   162,     0,     0,     0, 
    1814        0,     0,   163,   164,     0,     0,   135,   136,   165,     0, 
    1815        0,     0,   137,   138,   139,   140,   141,   166,   167,     0, 
    1816      168,   169,     0,     0,   170,   171,   172,   142,   143,   144, 
    1817      145,   146,   147,   148,     0,   149,   150,   151,     0,     0, 
    1818      152,   153,   154,     0,   155,   156,   157,   158,   159,     0, 
    1819      160,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1820        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1821        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1822        0,     0,     0,     0,     0,     0,     0,   639,     0,     0, 
    1823        0,     0,     0,   132,     0,     0,     0,     0,   161,     0, 
    1824        0,   133,   134,     0,     0,   162,     0,     0,     0,     0, 
    1825        0,   163,   164,     0,     0,   135,   136,   165,     0,     0, 
    1826        0,   137,   138,   139,   140,   141,   166,   167,     0,   168, 
    1827      169,     0,     0,   170,   171,   172,   142,   143,   144,   145, 
    1828      146,   147,   148,     0,   149,   150,   151,     0,     0,   152, 
    1829      153,   154,     0,   155,   156,   157,   158,   159,     0,   160, 
    1830        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1831        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1832        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1833        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1834        0,     0,   132,     0,     0,     0,     0,   161,     0,     0, 
    1835      133,   134,     0,     0,   162,     0,     0,     0,     0,     0, 
    1836      163,   164,     0,     0,   135,   136,   165,     0,     0,     0, 
    1837      137,   138,   139,   140,   141,   166,   167,     0,   168,   169, 
    1838        0,     0,   170,   171,   172,   142,   143,   144,   145,   146, 
    1839      147,   148,     0,   149,   150,   151,     0,     0,   152,   153, 
    1840      154,     0,   155,   156,   157,   158,   159,     0,   160,     0, 
    1841        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1842        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1843        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1844        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1845        0,     0,     0,     0,     0,     0,   161,     0,     0,     0, 
    1846        0,     0,     0,   162,     0,     0,     0,     0,     0,   163, 
    1847      164,     0,     0,     0,     0,   165,     0,     0,     0,     0, 
    1848        0,     0,     0,     0,   166,   167,   132,   168,   169,     0, 
    1849        0,   170,   171,   172,   133,   134,   660,   173,   661,     0, 
    1850        0,     0,     0,     0,     0,     0,     0,     0,   135,   136, 
    1851        0,     0,     0,     0,   137,   138,   139,   140,   141,     0, 
    1852        0,     0,     0,     0,     0,     0,     0,     0,     0,   142, 
    1853      143,   144,   145,   146,   147,   148,     0,   149,   150,   151, 
    1854        0,     0,   152,   153,   154,     0,   155,   156,   157,   158, 
    1855      159,     0,   160,     0,     0,     0,     0,     0,     0,     0, 
    1856        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1857        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1858        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1859        0,     0,     0,     0,     0,   132,     0,     0,     0,     0, 
    1860      161,     0,     0,   133,   134,   473,     0,   162,     0,     0, 
    1861        0,     0,     0,   163,   164,     0,     0,   135,   136,   165, 
    1862        0,     0,     0,   137,   138,   139,   140,   141,   166,   167, 
    1863        0,   168,   169,     0,     0,   170,   171,   662,   142,   143, 
    1864      144,   145,   146,   147,   148,     0,   149,   150,   151,     0, 
    1865        0,   152,   153,   154,     0,   155,   156,   157,   158,   159, 
    1866        0,   160,     0,     0,     0,     0,     0,     0,     0,     0, 
    1867        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1868        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1869        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1870        0,     0,     0,     0,   132,     0,     0,     0,     0,   161, 
    1871        0,     0,   133,   134,   548,     0,   162,     0,     0,     0, 
    1872        0,     0,   163,   164,     0,     0,   135,   136,   165,     0, 
    1873        0,     0,   137,   138,   139,   140,   141,   166,   167,     0, 
    1874      168,   169,     0,     0,   526,   171,   172,   142,   143,   144, 
    1875      145,   146,   147,   148,     0,   149,   150,   151,     0,     0, 
    1876      152,   153,   154,     0,   155,   156,   157,   158,   159,     0, 
    1877      160,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1878        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1879        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1880        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1881        0,     0,     0,   132,     0,     0,     0,     0,   161,     0, 
    1882        0,   133,   134,   473,     0,   162,     0,     0,     0,     0, 
    1883        0,   163,   164,     0,     0,   135,   136,   165,     0,     0, 
    1884        0,   137,   138,   139,   140,   141,   166,   167,     0,   168, 
    1885      169,     0,     0,   170,   171,   172,   142,   143,   144,   145, 
    1886      146,   147,   148,     0,   149,   150,   151,     0,     0,   152, 
    1887      153,   154,     0,   155,   156,   157,   158,   159,     0,   160, 
    1888        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1889        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1890        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1891        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1892        0,     0,   132,     0,     0,     0,     0,   161,     0,     0, 
    1893      133,   134,   726,     0,   162,     0,     0,     0,     0,     0, 
    1894      163,   164,     0,     0,   135,   136,   165,     0,     0,     0, 
    1895      137,   138,   139,   140,   141,   166,   167,     0,   168,   169, 
    1896        0,     0,   170,   171,   172,   142,   143,   144,   145,   146, 
    1897      147,   148,     0,   149,   150,   151,     0,     0,   152,   153, 
    1898      154,     0,   155,   156,   157,   158,   159,     0,   160,     0, 
    1899        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1900        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1901        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1902        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1903        0,     0,     0,     0,     0,     0,   161,     0,     0,     0, 
    1904        0,     0,     0,   162,     0,     0,     0,     0,     0,   163, 
    1905      164,     0,   132,     0,     0,   165,     0,     0,     0,     0, 
    1906      133,   134,     0,     0,   166,   167,     0,   168,   169,     0, 
    1907        0,   170,   171,   172,   135,   136,     9,     0,     0,     0, 
    1908      137,   138,   139,   140,   141,     0,     0,     0,     0,     0, 
    1909        0,     0,     0,     0,     0,   142,   143,   144,   145,   146, 
    1910      147,   148,     0,   149,   150,   151,     0,     0,   152,   153, 
    1911      154,     0,   155,   156,   157,   158,   159,     0,   160,     0, 
    1912        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1913        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1914        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1915        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1916        0,   132,     0,     0,     0,     0,   161,     0,     0,   133, 
    1917      134,   703,     0,   162,     0,     0,     0,     0,     0,   163, 
    1918      164,     0,     0,   135,   136,   165,     0,     0,     0,   137, 
    1919      138,   139,   140,   141,   166,   167,     0,   168,   169,     0, 
    1920        0,   170,   171,   172,   142,   143,   144,   145,   146,   147, 
    1921      148,     0,   149,   150,   151,     0,     0,   152,   153,   154, 
    1922        0,   155,   156,   157,   158,   159,     0,   160,     0,     0, 
    1923        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1924        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1925        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1926        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1927      132,     0,     0,     0,     0,   161,     0,     0,   133,   134, 
    1928     1011,     0,   162,     0,     0,     0,     0,     0,   163,   164, 
    1929        0,     0,   135,   136,   165,     0,     0,     0,   137,   138, 
    1930      139,   140,   141,   166,   167,     0,   168,   169,     0,     0, 
    1931      170,   171,   172,   142,   143,   144,   145,   146,   147,   148, 
    1932        0,   149,   150,   151,     0,     0,   152,   153,   154,     0, 
    1933      155,   156,   157,   158,   159,     0,   160,     0,     0,     0, 
    1934        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1935        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1936        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1937        0,     0,     0,     0,     0,     0,     0,     0,     0,   132, 
    1938        0,     0,     0,     0,   161,     0,     0,   133,   134,     0, 
    1939        0,   162,     0,     0,     0,     0,     0,   163,   164,     0, 
    1940        0,   135,   136,   165,     0,     0,     0,   137,   138,   139, 
    1941      140,   141,   166,   167,     0,   168,   169,     0,     0,   170, 
    1942      171,   172,   142,   143,   144,   145,   146,   147,   148,     0, 
    1943      149,   150,   151,     0,     0,   152,   153,   154,     0,   155, 
    1944      156,   157,   158,   159,     0,   160,     0,     0,     0,     0, 
    1945        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1946        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1947        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1948        0,     0,     0,     0,     0,     0,     0,     0,   132,     0, 
    1949        0,     0,     0,   161,     0,     0,   133,   134,     0,     0, 
    1950      162,     0,     0,     0,     0,     0,   163,   164,     0,     0, 
    1951      135,   136,   165,     0,     0,     0,   137,   138,   139,   140, 
    1952      141,   166,   167,     0,   168,   169,     0,     0,   170,   171, 
    1953      172,   142,   143,   144,   145,   146,   147,   148,     0,   149, 
    1954      150,   151,     0,     0,   152,   153,   154,     0,   155,   156, 
    1955      157,   158,   159,     0,   160,     0,     0,     0,     0,     0, 
    1956        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1957        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1958        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1959        0,     0,     0,     0,     0,     0,     0,   132,     0,     0, 
    1960        0,     0,   161,     0,     0,   133,   134,     0,     0,   162, 
    1961        0,     0,     0,     0,     0,   163,   164,     0,     0,   135, 
    1962      136,   165,     0,     0,     0,   137,   138,   139,   140,   141, 
    1963      166,   167,     0,   168,   169,     0,     0,   170,   171,   363, 
    1964      142,   143,   144,   145,   146,   147,   148,     0,   149,   150, 
    1965      151,     0,     0,   152,   153,   154,     0,   155,   156,   157, 
    1966      158,   159,     0,   160,     0,     0,     0,     0,     0,     0, 
    1967        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1968        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1969        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1970        0,     0,     0,     0,     0,     0,   132,     0,     0,     0, 
    1971        0,   161,     0,     0,   133,   134,     0,     0,   162,     0, 
    1972        0,     0,     0,     0,   163,   164,     0,     0,   135,   136, 
    1973      165,     0,     0,     0,   137,   138,   139,   140,   141,   166, 
    1974      167,     0,   168,   169,     0,     0,   170,   431,   172,   142, 
    1975      143,   144,   145,   146,   147,   148,     0,   149,   150,   151, 
    1976        0,     0,   152,   153,   154,     0,   155,   156,   157,   158, 
    1977      159,     0,   160,     0,     0,     0,     0,     0,     0,     0, 
    1978        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1979        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1980        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1981        0,     0,     0,     0,     0,   132,     0,     0,     0,     0, 
    1982      161,     0,     0,   133,   134,     0,     0,   162,     0,     0, 
    1983        0,     0,     0,   163,   164,     0,     0,   135,   136,   165, 
    1984        0,     0,     0,   137,   138,   139,   140,   141,   166,   167, 
    1985        0,   168,   169,     0,     0,   170,   529,   530,   142,   143, 
    1986      144,   145,   146,   147,   148,     0,   149,   150,   151,     0, 
    1987        0,   152,   153,   154,     0,   155,   156,   157,   158,   159, 
    1988        0,   160,     0,     0,     0,     0,     0,     0,     0,     0, 
    1989        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1990        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1991        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    1992        0,     0,     0,     0,   132,     0,     0,     0,     0,   161, 
    1993        0,     0,   133,   134,     0,     0,   162,     0,     0,     0, 
    1994        0,     0,   163,   164,     0,     0,   135,   136,   165,     0, 
    1995        0,     0,   137,   138,   139,   140,   141,   166,   167,     0, 
    1996      168,   169,     0,     0,   918,   171,   363,   142,   143,   144, 
    1997      145,   146,   147,   148,     0,   149,   150,   151,     0,     0, 
    1998      152,   153,   154,     0,   155,   156,   157,   158,   159,     0, 
    1999      160,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    2000        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    2001        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    2002        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    2003        0,     0,     0,     0,     0,     0,     0,     0,   161,     0, 
    2004        0,     0,     0,     0,     0,   162,     0,     0,     0,     0, 
    2005        0,   163,   164,     0,     0,     0,     0,   165,     0,     0, 
    2006        0,     0,     0,     0,     0,     0,   166,   167,     0,   168, 
    2007      169,     0,     0,   170,   171,   955,   311,   312,   422,     0, 
    2008      423,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    2009      135,   136,     0,     0,     0,     0,   137,   138,   139,   140, 
    2010      141,     0,     0,   314,   315,   316,   317,   318,     0,   319, 
    2011      320,   142,   143,   144,   145,   146,   147,   148,     0,   149, 
    2012      150,   151,     0,     0,   152,   153,   154,     0,   155,   156, 
    2013      157,   158,   159,     0,   160,     0,     0,     0,     0,     0, 
    2014        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    2015        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    2016        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    2017        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    2018        0,     0,     0,     0,     0,     0,     0,     0,     0,   162, 
    2019        0,     0,     0,     0,     0,   163,   164,     0,     0,     0, 
    2020        0,   165,     0,     0,     0,     0,   311,   312,   313,     0, 
    2021      166,   167,     0,   168,   169,     0,     0,   321,   171,   424, 
    2022      135,   136,     0,     0,     0,     0,   137,   138,   139,   140, 
    2023      141,     0,     0,   314,   315,   316,   317,   318,     0,   319, 
    2024      320,   142,   143,   144,   145,   146,   147,   148,     0,   149, 
    2025      150,   151,   311,   312,   152,   153,   154,     0,   155,   156, 
    2026      157,   158,   159,     0,   160,     0,   135,   136,     0,     0, 
    2027        0,     0,   137,   138,   139,   140,   141,     0,     0,   314, 
    2028      315,   316,   317,   318,     0,   319,   320,   142,   143,   144, 
    2029      145,   146,   147,   148,     0,   149,   150,   151,     0,     0, 
    2030      152,   153,   154,     0,   155,   156,   157,   158,   159,     0, 
    2031      160,     0,     0,     0,     0,     0,     0,     0,     0,   162, 
    2032        0,     0,     0,     0,     0,   163,   164,     0,     0,     0, 
    2033        0,   165,     0,     0,     0,     0,     0,     0,     0,     0, 
    2034      166,   167,     0,   168,   169,     0,     0,   321,   171,   322, 
    2035        0,     0,     0,     0,     0,     0,     5,     0,     0,     6, 
    2036        0,     7,     0,     8,     0,   162,     9,     0,     0,     0, 
    2037        0,   163,   164,     0,     0,     0,    10,   165,     0,     0, 
    2038        0,     0,     0,     0,     0,     0,   166,   167,     0,   168, 
    2039      169,     0,    11,   321,   171,   424,    12,    13,     0,     0, 
    2040        0,    14,     0,     0,     0,     0,     0,    15,     0,    16, 
    2041       17,     0,    18,     0,     0,     0,     0,    19,    20,    21, 
    2042       22,    23,     0,    24,    25,     0,     0,    26,    27,    28, 
    2043       29,    30,    31,    32,    33,    34,    35,    36,     0,    37, 
    2044        0,    38,    39,     0,     0,    40,    41,    42,     0,    43, 
    2045        0,    44,     0,     0,    45,    46,     0,     0,    47,    48, 
    2046       49,     0,     0,     0,     0,     0,     0,     0,    50,     0, 
    2047        0,     0,    52,    53,    54,    55,    56,    57,    58,    59, 
    2048       60,    61,    62,    63,     0,     0,    64,     0,     0,    65, 
    2049       66,    67,    68,     5,     0,     0,     6,   487,     7,     0, 
    2050        8,     0,     0,     9,     0,     0,     0,     0,     0,     0, 
    2051        0,     0,     0,    10,     0,     0,     0,     0,     0,     0, 
    2052        0,     0,     0,     0,     0,     0,     0,     0,     0,    11, 
    2053        0,     0,     0,    12,    13,     0,     0,     0,    14,     0, 
    2054        0,     0,     0,     0,    15,     0,    16,    17,     0,    18, 
    2055        0,     0,     0,     0,    19,    20,    21,    22,    23,     0, 
    2056       24,    25,     0,     0,    26,    27,    28,    29,    30,    31, 
    2057       32,    33,    34,    35,    36,     0,    37,     0,    38,    39, 
    2058        0,     0,    40,    41,    42,     0,    43,     0,    44,     0, 
    2059        0,    45,    46,     0,     0,    47,    48,    49,     0,     0, 
    2060        0,     0,     0,     0,     0,    50,     0,     0,     0,    52, 
    2061       53,    54,    55,    56,    57,    58,    59,    60,    61,    62, 
    2062       63,     8,     0,    64,     9,     0,    65,    66,    67,    68, 
    2063        0,     0,     0,     0,    10,     0,     0,     0,     0,     0, 
    2064        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    2065       11,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    2066        0,     0,     0,     0,     0,    15,     0,     0,     0,     0, 
    2067       18,     0,   746,     0,     0,    19,    20,    21,    22,    23, 
    2068        0,     0,    25,     0,     0,    26,    27,    28,    29,    30, 
    2069       31,    32,    33,    34,    35,     0,     0,     8,     0,     0, 
    2070        9,     0,     0,     0,    41,     0,     0,     0,     0,    44, 
    2071       10,     0,     0,     0,     0,     0,    47,     0,    49,     0, 
    2072        0,     0,     0,     0,     0,     0,    11,     0,     0,     0, 
    2073        0,     0,     0,     0,     0,     0,     0,    59,    60,    61, 
    2074       62,    15,     0,     0,     0,     0,    18,     0,     0,    67, 
    2075       68,    19,    20,    21,    22,    23,     0,     0,    25,     0, 
    2076        0,    26,    27,    28,    29,    30,    31,    32,    33,    34, 
    2077       35,     0,     0,     0,     0,     0,   825,     0,     0,     0, 
    2078       41,     0,     0,     0,     0,    44,     0,     0,     0,     0, 
    2079        0,     0,    47,     0,    49,     0,     0,     0,     0,     0, 
    2080        0,     0,    11,     0,     0,     0,     0,     0,     0,     0, 
    2081        0,     0,     0,    59,    60,    61,    62,    15,     0,     0, 
    2082        0,     0,    18,   826,     0,    67,    68,    19,    20,   827, 
    2083        0,    23,     0,     0,    25,     0,     0,    26,    27,    28, 
    2084       29,    30,    31,    32,    33,    34,    35,     0,     0,     0, 
    2085        0,     0,   825,     0,     0,     0,    41,     0,     0,     0, 
    2086        0,    44,     0,     0,     0,     0,     0,     0,    47,     0, 
    2087       49,     0,     0,     0,     0,     0,     0,     0,    11,     0, 
    2088        0,     0,     0,     0,     0,     0,     0,     0,     0,    59, 
    2089       60,    61,    62,    15,     0,     0,     0,     0,    18,     0, 
    2090        0,   170,    68,    19,    20,   827,     0,    23,     0,     0, 
    2091       25,     0,     0,    26,    27,    28,    29,    30,    31,    32, 
    2092       33,    34,    35,     0,     0,     0,     0,     0,     0,     0, 
    2093        0,     0,    41,     0,     0,     0,     0,    44,     0,     0, 
    2094        0,     0,     0,     0,    47,     0,    49,     0,     0,     0, 
    2095        0,     0,     0,     0,     0,     0,     0,     0,     0,     0, 
    2096        0,     0,     0,     0,     0,    59,    60,    61,    62,     0, 
    2097        0,     0,     0,     0,     0,     0,     0,   170,    68 
     2592       0,     0,    89,     0,     0,     0,     0,     0,     0,     0, 
     2593       0,     0,     0,     0,     0,     0,     0,     0,     0,    92, 
     2594      93,     0,    95,     0,     0,     0,    42,    97 
    20982595}; 
    20992596 
    21002597#define yypact_value_is_default(Yystate) \ 
    2101   (!!((Yystate) == (-845))) 
     2598  (!!((Yystate) == (-1394))) 
    21022599 
    21032600#define yytable_value_is_error(Yytable_value) \ 
    2104   (!!((Yytable_value) == (-542))) 
     2601  YYID (0) 
    21052602 
    21062603static const yytype_int16 yycheck[] = 
    21072604{ 
    2108       11,   295,     1,   185,    15,   101,   219,    18,   104,   240, 
    2109      394,   577,   108,   395,   277,   111,    54,   161,   482,   477, 
    2110      205,   536,   536,   653,   482,     5,   264,   124,   172,    79, 
    2111      268,    81,    82,   161,     3,     3,    86,     3,   274,   710, 
    2112       39,     3,   564,   565,     1,     3,   124,    17,   719,    75, 
    2113       76,     3,    51,    80,   124,   291,   563,   564,   565,     3, 
    2114       87,    19,    20,    21,     3,    31,   722,    37,    38,   768, 
    2115      214,     3,     3,   217,   214,   113,   363,   115,   116,   329, 
    2116       24,    21,     3,   161,   747,   124,   214,    21,     5,     6, 
    2117        7,     8,     9,    10,    51,    12,    13,    14,    15,    16, 
    2118       17,   127,    19,    20,    21,    22,    23,    27,     3,     3, 
    2119       22,   122,     3,     3,     3,   212,   213,   904,     3,   130, 
    2120      131,   132,   219,    21,     3,   112,     3,    45,     3,    44, 
    2121      141,   153,   976,     3,    24,   213,   214,    18,     3,     3, 
    2122      121,    22,   122,   213,   155,   101,    24,   131,   245,    24, 
    2123      161,   198,     3,     3,     3,     3,     3,     3,     3,    24, 
    2124        3,   172,    19,    20,    21,   131,   177,   131,   404,    91, 
    2125       88,    89,   119,   891,   221,   162,  1020,    18,   428,   160, 
    2126      191,    22,   166,   130,    21,    21,    22,    23,   168,   188, 
    2127      201,   202,   107,   115,   160,   140,   246,   142,   166,   168, 
    2128      987,   163,   166,   214,   160,   160,   217,   206,    23,   167, 
    2129      881,   163,   157,   931,   213,   914,   227,   161,   217,   363, 
    2130      160,   220,   166,   363,   163,   322,   225,   253,   884,   240, 
    2131      327,   163,   163,   167,   331,   363,     5,   900,   265,    24, 
    2132      160,   472,   163,   270,   322,   162,   273,   164,   165,   327, 
    2133      162,   168,   322,   331,   131,   254,   162,   327,   765,   766, 
    2134      767,   331,   140,    21,   162,   501,   502,   237,   163,   163, 
    2135      269,   161,   163,   509,   163,   286,   166,   288,   163,   160, 
    2136       21,     3,    24,   322,   163,   363,   161,   523,   166,   300, 
    2137      301,   166,   331,   163,   305,   526,   161,   254,   534,   163, 
    2138      485,   166,    44,   314,   315,   316,   317,   318,   319,   320, 
    2139      167,   561,   163,   163,   163,   163,   163,   163,   163,   160, 
    2140      163,   608,   609,   322,   611,   162,   576,   424,   164,   165, 
    2141      341,   796,   797,   798,   345,   346,   347,   348,   349,   350, 
    2142      351,   352,   353,   354,   355,   356,   424,    18,   162,   164, 
    2143      165,    22,   363,   122,   424,    18,    19,    20,    21,    22, 
    2144       23,   162,   373,   374,   375,   376,   377,   378,   379,   380, 
    2145      381,   382,   383,   384,   385,   386,   387,   388,   389,   390, 
    2146      391,   166,   846,    18,   395,   424,   530,     3,   846,   847, 
    2147      848,   849,   850,   915,   339,   340,   490,   160,   140,   162, 
    2148      162,     3,   160,  1033,   126,   163,    22,   133,   915,   659, 
    2149      133,   255,   256,   358,   425,   360,   361,   362,   162,   160, 
    2150       94,    95,   163,   153,   166,   370,   520,   663,   133,    31, 
    2151      162,   813,   162,   471,   160,   161,   562,   160,   282,     3, 
    2152      160,    78,    79,   569,   657,   495,   166,   543,   711,   914, 
    2153      500,   160,   836,   503,    18,   160,   669,   166,    22,   160, 
    2154       18,   472,   756,   701,    22,   562,  1032,   478,   162,    29, 
    2155      614,    31,   569,   162,   571,   572,   573,   574,   575,   160, 
    2156      491,   162,   718,   990,   562,   496,   160,   122,   131,   160, 
    2157      721,   569,   562,   571,   572,   573,   574,   575,     3,   569, 
    2158      163,   571,   572,   573,   574,   575,  1021,  1021,   693,   796, 
    2159      797,   798,   162,    18,   525,   526,   162,    22,   662,   530, 
    2160      770,   771,   772,   773,   774,   536,     3,  1042,  1042,   131, 
    2161      161,   162,   571,   572,   573,   574,   575,    83,   537,    85, 
    2162      539,    18,  1006,   123,   641,    22,   160,   546,  1006,   560, 
    2163        8,     9,    10,     4,    12,    13,    14,    15,    16,    17, 
    2164      657,    19,    20,    21,    22,    23,   577,   664,   579,   160, 
    2165      161,   162,   669,    18,    19,    20,    21,    22,    23,    18, 
    2166       19,    20,    21,    22,    23,   821,   664,    24,    41,    19, 
    2167       20,    21,    22,    23,   664,   161,   162,   608,   609,   166, 
    2168      611,   162,   163,   614,   615,   847,   848,   849,   850,   903, 
    2169      134,   135,   136,   683,    21,    22,    23,    19,    20,    83, 
    2170       84,   632,   633,    37,    38,     3,   637,     3,   639,   123, 
    2171      124,   160,   643,     3,   162,   162,   162,   819,   168,   162, 
    2172      162,   652,   738,   654,   740,   656,   162,   646,   162,   162, 
    2173      162,   662,   796,   749,   653,   886,   162,     3,   162,   162, 
    2174      162,   162,   162,   162,   675,   664,   677,   162,     3,   162, 
    2175      162,   768,   671,   162,   162,   162,   912,   162,   162,   132, 
    2176      691,   692,   160,     3,   160,   138,   139,   160,   982,   163, 
    2177      768,   702,     5,   160,     3,   160,   162,   160,   768,   160, 
    2178      153,   154,     3,   156,   157,   160,   164,   165,   161,   708, 
    2179      721,     5,     6,     7,     8,     9,    10,     3,    12,    13, 
    2180       14,    15,    16,    17,   160,    19,    20,    21,    22,    23, 
    2181        3,     5,   161,     3,     3,   163,     3,     3,   162,    22, 
    2182      751,     5,     3,     3,   163,   163,     3,     3,   163,   760, 
    2183      162,   160,   988,     3,   160,   163,     3,   162,     5,     6, 
    2184        7,     8,     9,    10,   162,    12,    13,    14,    15,    16, 
    2185       17,   162,    19,    20,    21,    22,    23,   162,   160,   163, 
    2186      161,     3,     3,    23,     3,   796,   797,   798,     3,     3, 
    2187      163,     4,   163,    22,   163,   163,   160,   893,    22,   162, 
    2188       26,    21,   813,   814,   163,   160,   902,   163,     4,    36, 
    2189      122,   955,     3,   160,   162,   160,    10,   914,    12,    13, 
    2190       14,    15,    16,    17,   160,    19,    20,    21,    22,    23, 
    2191      163,     3,   162,   162,     5,   163,   914,     5,   935,   163, 
    2192      162,   160,   163,   160,   914,   160,     4,   163,     3,   163, 
    2193       82,   122,   163,   163,     3,    22,   160,   868,   163,   870, 
    2194      167,   872,   160,   160,   163,   168,    82,   163,   163,   160, 
    2195      164,   165,    25,   160,   168,   886,   160,    22,   974,   160, 
    2196      891,    51,   254,   950,   485,   948,   897,    12,    13,    14, 
    2197       15,    16,    17,   904,    19,    20,    21,    22,    23,    12, 
    2198       13,    14,    15,    16,    17,   673,    19,    20,    21,    22, 
    2199       23,   677,   911,   924,   405,   926,   927,   164,   165,   481, 
    2200      931,   932,   505,   934,   480,    78,    79,    80,   260,   525, 
    2201      493,   289,   715,   944,    52,   868,   927,   397,   937,   959, 
    2202      870,   662,   890,  1016,   955,   985,   541,   757,   937,   960, 
    2203      961,   760,   664,   106,   435,   108,   109,   110,   124,    -1, 
    2204      113,   114,    -1,   116,   117,    -1,    -1,     0,     1,    -1, 
    2205      164,   165,    -1,    -1,   985,    -1,   987,    -1,    -1,    -1, 
    2206       -1,    -1,    -1,    -1,   983,   996,    -1,    -1,   999,    -1, 
    2207       -1,    24,    25,    -1,    -1,    28,    29,    30,    31,    32, 
    2208       -1,    -1,    35,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2209     1021,    -1,    45,    -1,    -1,    -1,    -1,    -1,    -1,  1030, 
    2210       -1,  1032,    -1,  1034,  1035,  1024,    -1,    -1,    61,    -1, 
    2211       -1,  1042,    65,    66,  1033,    -1,    -1,    70,  1049,   164, 
    2212      165,    -1,    -1,    76,    -1,    78,    79,    -1,    81,    -1, 
    2213       -1,   164,   165,    86,    87,    88,    89,    90,    -1,    92, 
    2214       93,    -1,    -1,    96,    97,    98,    99,   100,   101,   102, 
    2215      103,   104,   105,   106,    -1,   108,    -1,   110,   111,    -1, 
    2216       -1,   114,   115,   116,    -1,   118,    -1,   120,    -1,    -1, 
    2217      123,   124,    -1,    -1,   127,   128,   129,    -1,    -1,    -1, 
    2218       -1,    -1,    -1,    -1,   137,    -1,    -1,   140,   141,   142, 
    2219      143,   144,   145,   146,   147,   148,   149,   150,   151,   152, 
    2220       -1,    -1,   155,    -1,    -1,   158,   159,   160,   161,    -1, 
    2221       -1,    -1,     3,   166,     5,     6,     7,     8,     9,    10, 
    2222       -1,    12,    13,    14,    15,    16,    17,    -1,    19,    20, 
    2223       21,    22,    23,     3,    -1,     5,     6,     7,     8,     9, 
    2224       10,    -1,    12,    13,    14,    15,    16,    17,    -1,    19, 
    2225       20,    21,    22,    23,     3,    -1,     5,     6,     7,     8, 
    2226        9,    10,    -1,    12,    13,    14,    15,    16,    17,    -1, 
    2227       19,    20,    21,    22,    23,     3,    -1,     5,     6,     7, 
    2228        8,     9,    10,    -1,    12,    13,    14,    15,    16,    17, 
    2229       -1,    19,    20,    21,    22,    23,     3,    -1,     5,     6, 
    2230        7,     8,     9,    10,    -1,    12,    13,    14,    15,    16, 
    2231       17,    -1,    19,    20,    21,    22,    23,     4,     5,     6, 
    2232        7,     8,     9,    10,    -1,    12,    13,    14,    15,    16, 
    2233       17,    -1,    19,    20,    21,    22,    23,     4,     5,     6, 
    2234        7,     8,     9,    10,    -1,    12,    13,    14,    15,    16, 
    2235       17,    -1,    19,    20,    21,    22,    23,    -1,    -1,    -1, 
    2236       -1,    -1,    33,    34,    -1,    -1,    -1,    -1,    39,    40, 
    2237       41,    42,    43,   164,   165,    -1,    -1,    -1,    -1,    -1, 
    2238       -1,    -1,    -1,    54,    55,    56,    57,    58,    59,    60, 
    2239       -1,    62,    63,    64,   164,   165,    67,    68,    69,    -1, 
    2240       71,    72,    73,    74,    75,    -1,    77,    -1,    -1,    -1, 
    2241       -1,    -1,    -1,    -1,    -1,   164,   165,     5,     6,     7, 
    2242        8,     9,    10,    -1,    12,    13,    14,    15,    16,    17, 
    2243       -1,    19,    20,    21,    22,    23,   164,   165,     5,     6, 
    2244        7,     8,     9,    10,    -1,    12,    13,    14,    15,    16, 
    2245       17,    -1,    19,    20,    21,    22,    23,   164,   165,    -1, 
    2246       -1,   132,    -1,    -1,    -1,    -1,    -1,   138,   139,    -1, 
    2247       -1,    -1,    -1,   144,    -1,    -1,   163,   164,   165,    -1, 
    2248       -1,    -1,   153,   154,    -1,   156,   157,    -1,    -1,   160, 
    2249      161,   162,    -1,    -1,    -1,    -1,    -1,   164,   165,     4, 
    2250        5,     6,     7,     8,     9,    10,    -1,    12,    13,    14, 
    2251       15,    16,    17,    -1,    19,    20,    21,    22,    23,     4, 
    2252        5,     6,     7,     8,     9,    10,    -1,    12,    13,    14, 
    2253       15,    16,    17,    -1,    19,    20,    21,    22,    23,     4, 
    2254        5,     6,     7,     8,     9,    10,    -1,    12,    13,    14, 
    2255       15,    16,    17,    -1,    19,    20,    21,    22,    23,    -1, 
     2605      11,    73,   458,   220,   167,   294,   458,   382,    52,   294, 
     2606      52,   382,   288,   213,    56,    52,    90,   496,   184,   651, 
     2607      57,   493,   914,   152,   718,    62,    63,   167,   320,   109, 
     2608     136,   844,   237,   599,  1006,  1006,   219,   291,   152,   547, 
     2609      52,    52,   237,   982,   237,   294,    57,   294,   496,    52, 
     2610     213,    62,    63,   258,   875,   876,   100,    94,   100,  1088, 
     2611     692,    52,    73,   100,  1027,   258,   317,   104,   927,   928, 
     2612     926,   305,   670,  1173,   935,   258,   259,   927,   928,   494, 
     2613    1269,   110,   640,    94,  1273,     3,   584,  1276,   100,   100, 
     2614      56,  1261,     5,   104,  1264,   593,     3,   100,   853,   854, 
     2615     855,     3,  1495,   171,    21,   860,     3,    21,   109,   100, 
     2616       5,     3,     3,   933,   167,     3,    21,     3,     3,   617, 
     2617       4,     3,    24,    47,   111,   728,     5,    24,   146,    21, 
     2618       5,   136,   735,     3,   171,   184,     4,     3,    24,   192, 
     2619       3,     3,    24,    11,   169,   379,   351,    97,   220,   354, 
     2620       3,    19,    20,    21,    24,   191,   351,   143,   351,   354, 
     2621     171,   354,    64,     3,     3,   305,   191,    64,  1027,   458, 
     2622      27,     3,     3,   458,     3,   193,    18,     3,    64,    24, 
     2623      22,   398,    64,   170,    24,   556,   172,     5,   193,  1152, 
     2624     191,   157,  1084,    24,    64,   145,     3,    21,     3,   404, 
     2625       3,   330,   419,     3,     3,     3,     3,   131,     3,   404, 
     2626       3,   404,    24,     3,     3,     3,   330,     3,    29,    24, 
     2627      31,   387,   417,     3,    64,    24,   237,   675,     3,   309, 
     2628     191,    24,   304,    64,   417,   315,   308,   377,   378,   379, 
     2629    1410,   424,    24,     3,   427,   317,     3,   430,   320,     3, 
     2630       3,   146,    64,    19,    20,   323,   124,  1077,   710,    64, 
     2631     259,     3,   154,   154,   518,    64,     3,   146,   279,     3, 
     2632     154,    64,    19,    20,   191,  1375,   194,   971,  1671,   193, 
     2633     193,   149,    24,   294,   313,   314,   323,   194,   193,   578, 
     2634      24,   496,   199,  1152,   193,   197,  1259,   165,   166,  1120, 
     2635     197,   496,  1163,   496,   372,   720,   194,   175,   194,   194, 
     2636     599,   197,   323,   496,   200,   197,   184,   185,   193,   187, 
     2637     188,     3,    64,   191,   192,   193,   398,   197,   194,   578, 
     2638      64,   194,   194,   201,   191,   372,   499,   328,   382,   305, 
     2639     351,   194,    24,   354,     3,   382,   357,   419,   420,   191, 
     2640     599,  1106,   197,     3,   160,   194,     3,   197,  1113,    97, 
     2641      24,   372,   194,   861,   154,   194,   197,     3,   194,   193, 
     2642     868,   382,  1542,   971,  1544,   193,   874,  1009,   612,   877, 
     2643    1550,   939,    64,   881,    52,   197,  1575,   194,    24,   160, 
     2644    1560,   194,   197,   404,   194,    52,   194,   194,   197,   194, 
     2645      64,  1448,   393,   394,   197,   194,   194,   145,   194,   420, 
     2646      48,   377,   378,   379,   194,   102,   382,   154,   417,   194, 
     2647     107,   458,   188,   497,   498,   191,   192,   194,    64,   718, 
     2648    1542,   430,   100,   718,   194,   515,  1543,   194,   116,   117, 
     2649     194,   194,   323,   100,   113,   192,   663,   458,  1560,    24, 
     2650     154,   557,   139,  1392,  1561,   197,    24,   494,   495,   496, 
     2651     660,   715,   194,   197,   664,   665,    24,  1430,  1497,   718, 
     2652     675,   718,   612,   111,  1410,   604,   642,  1449,  1449,   553, 
     2653     675,   686,   675,   494,   495,   496,  1342,   191,   499,    64, 
     2654     604,   372,   675,   686,   191,   154,    64,   660,   167,  1358, 
     2655      24,   664,   665,   686,  1325,   759,    64,   154,  1358,    24, 
     2656     547,    97,   556,   191,   556,   197,  1563,   528,    52,   556, 
     2657      52,   563,   994,   192,  1345,    24,   982,  1006,   782,    24, 
     2658     982,  1010,   170,   197,   184,   185,   547,   187,   610,   550, 
     2659      64,   191,    97,   738,   556,   556,   191,   584,   585,    64, 
     2660     801,  1183,   803,   556,   193,   738,   593,   594,  1006,   145, 
     2661     563,   197,  1010,  1071,   124,    64,   100,   578,   100,    64, 
     2662       3,  1430,  1138,   584,   585,   154,   154,   168,   169,    24, 
     2663     617,    33,   593,   594,    29,    18,    31,   154,   599,    22, 
     2664     145,   663,  1564,  1564,    38,   632,    48,   563,    19,    20, 
     2665     191,    24,  1494,   192,   193,   191,   617,  1543,  1544,   184, 
     2666     185,     3,   187,   191,  1550,   175,   191,   583,   193,   630, 
     2667      22,   632,   197,   191,   191,  1561,   592,   193,    18,   197, 
     2668      22,   191,    22,   191,   167,   191,   191,    24,   194,   197, 
     2669     651,    64,    87,   167,   200,  1458,   612,    24,   614,   615, 
     2670     616,   184,   185,    29,   187,    31,   174,   124,   191,   192, 
     2671     184,   185,     4,   187,   675,   174,   191,   191,   192,   114, 
     2672     163,   164,   197,   197,    24,   193,   191,    64,   191,   167, 
     2673     193,   692,   197,   720,   193,   194,   758,    64,   193,   193, 
     2674     199,   983,   191,   982,   182,   199,   191,   982,   197,   710, 
     2675      65,    66,   197,   124,   192,    24,    24,   718,   175,   720, 
     2676      29,    87,    31,     3,    64,    80,   796,   184,   185,    84, 
     2677     187,   172,   188,   167,   191,    90,   192,   172,   800,   801, 
     2678     836,   803,    22,   193,   130,  1627,  1430,   182,   114,   199, 
     2679     184,   185,  1214,   187,   165,   166,    64,   191,   192,   104, 
     2680     761,   106,   197,   191,   175,  1189,   194,  1191,    99,   100, 
     2681     101,  1213,   200,   184,   185,   140,   187,   188,   191,     5, 
     2682     191,   192,   193,   191,   197,   941,   194,    21,    22,   745, 
     2683     909,    19,    20,   191,   856,   925,   194,     6,     7,   130, 
     2684    1165,   156,  1424,   142,  1165,   909,   172,   138,    99,   100, 
     2685     844,  1006,   167,   112,   191,  1010,  1095,   844,   193,   424, 
     2686     197,  1006,   427,  1006,   191,  1010,     4,  1010,   184,   185, 
     2687     197,   187,  1027,  1261,   861,   191,  1264,  1010,   194,   172, 
     2688     173,   868,  1027,   844,  1027,   191,   192,   874,   875,   876, 
     2689     877,   191,   879,   112,   881,   882,  1095,   197,  1261,  1138, 
     2690     861,  1264,  1308,   157,   158,   159,  1312,   868,   351,  1022, 
     2691     193,   354,   193,   874,   875,   876,   877,   193,   879,   193, 
     2692     881,   882,   914,   191,    47,  1080,   193,   914,   844,   197, 
     2693     193,   184,   185,   193,   187,  1080,   124,  1080,   191,  1138, 
     2694     927,   928,   192,   859,   905,   172,   173,    28,    29,    30, 
     2695      31,   867,   193,   914,    40,    41,    37,   104,   105,   193, 
     2696     275,   983,  1578,  1579,   880,   280,   927,   928,   283,    62, 
     2697      63,    29,   193,    31,    29,   290,    31,   200,   184,   185, 
     2698     200,   187,     5,  1005,   174,   191,  1392,   175,   194,   304, 
     2699    1392,   306,  1218,   208,   209,   982,   184,   185,   914,   187, 
     2700     188,   324,   325,   191,   192,    23,    87,    10,     9,   925, 
     2701     971,   193,   193,    12,    13,    14,    15,    16,    17,    18, 
     2702    1449,   982,     5,  1010,   191,   340,   341,   191,   343,    87, 
     2703     191,   191,    87,   114,   184,   185,   191,   187,   353,   146, 
     2704     355,   191,  1367,   193,  1005,  1006,  1367,   199,  1009,  1010, 
     2705    1074,   366,   168,   368,   193,    29,   114,    31,  1262,   114, 
     2706     191,  1022,   175,   176,   177,   178,  1027,  1222,     4,  1308, 
     2707     183,  1221,   104,  1312,   389,  1097,   189,  1222,   191,  1222, 
     2708     175,   176,   177,   178,  1071,   194,     5,     5,   183,  1222, 
     2709     194,   172,  1084,     5,   189,   174,  1057,  1084,   150,   184, 
     2710     185,     3,   187,   174,   184,   185,   191,   187,  1221,   194, 
     2711    1071,   191,   174,    87,   172,     4,   197,   172,   194,  1080, 
     2712     202,  1082,    11,  1084,   182,   174,   194,   182,   191,   193, 
     2713      19,    20,    21,  1120,  1095,  1564,   579,   580,   581,   582, 
     2714     114,  1274,     5,   184,   185,    22,   187,   191,   591,   191, 
     2715     191,   466,   193,  1392,     3,   470,   193,  1392,     3,  1120, 
     2716     194,  1148,   161,   162,   163,   164,   481,     4,    68,    69, 
     2717      70,  1165,    72,     4,   191,   173,   154,  1138,  1165,     3, 
     2718      11,     3,   497,   498,    73,   191,   501,  1148,    19,    20, 
     2719      21,   193,   507,  1215,   102,   199,   195,   196,   172,   107, 
     2720       4,   194,   110,     4,  1165,    94,   113,   522,   182,   134, 
     2721     191,   182,   194,   193,   122,   194,   531,   125,   126,   182, 
     2722     110,  1182,  1183,   191,   194,   540,    39,   193,   182,   191, 
     2723       4,   139,   182,   548,   194,   124,   144,    11,   553,  1261, 
     2724       3,   174,  1264,    18,     5,    19,    20,  1269,     3,  1165, 
     2725     193,  1273,  1213,   568,  1276,    22,   193,     3,   193,   191, 
     2726     149,  1222,    21,  1285,   193,    21,   193,   193,     3,   193, 
     2727     193,     3,     3,   146,   191,   191,   165,   166,  1680,   193, 
     2728      52,   169,   193,   191,   139,    57,   175,  1693,   154,     3, 
     2729      62,    63,     3,   124,   114,   184,   185,   193,   187,   188, 
     2730       5,     5,   191,   192,   193,  1266,     5,     3,    30,   194, 
     2731       5,  1333,   201,     3,   629,   194,    31,    29,   149,   194, 
     2732     194,  1308,    94,   154,   194,  1312,   194,     3,   100,     3, 
     2733     645,  1247,   104,     5,   165,   166,     4,   193,  1325,   654, 
     2734     193,    21,    20,   191,   175,     4,     4,  1308,   191,     4, 
     2735     124,  1312,   194,   184,   185,   194,   187,   188,  1345,   194, 
     2736     191,   192,   193,   107,  1325,   194,   110,   194,  1390,  1536, 
     2737     201,  1358,   815,  1367,   191,   149,   194,    26,   122,   194, 
     2738    1367,   125,   126,   194,  1345,  1535,    94,    73,  1410,     5, 
     2739       5,   165,   166,   199,   194,   139,     4,  1358,     3,   171, 
     2740     144,   175,  1552,   193,   719,  1392,  1367,   191,   194,   194, 
     2741     184,   185,    11,   187,   188,   858,   199,   191,   192,   193, 
     2742      19,    20,  1535,   866,   193,    24,   741,   201,   743,   191, 
     2743     194,  1392,     4,   146,     3,   878,     3,     5,     4,  1552, 
     2744    1356,   756,     5,     3,   193,     3,   103,   762,     5,   103, 
     2745       5,  1367,   895,   194,  1693,     3,     3,    22,   901,     4, 
     2746       3,     3,  1449,  1424,  1458,    64,     4,    21,     3,  1430, 
     2747     194,  1458,     3,   194,     4,   194,   194,   194,   194,   794, 
     2748       3,     0,     1,  1505,   193,   191,     3,   194,   191,   191, 
     2749     191,   806,     3,   191,     4,     4,   811,  1458,   813,    21, 
     2750       5,   194,  1494,     3,    22,    24,   194,  1494,     4,    28, 
     2751      29,    30,    31,   194,  1536,  1502,     3,   194,    37,   194, 
     2752    1542,  1543,  1544,   193,     3,   124,  1513,   194,  1550,   844, 
     2753     194,   194,  1682,  1494,     3,    49,     4,     4,  1560,  1561, 
     2754       3,  1502,  1458,   194,   316,    64,     4,  1576,  1704,   100, 
     2755     149,   323,  1513,  1575,   909,  1006,  1006,   411,    20,  1265, 
     2756    1274,   715,  1219,   515,  1262,  1266,   165,   166,    87,  1682, 
     2757    1264,    11,  1006,   420,  1424,  1423,   175,  1564,   404,   252, 
     2758     782,   896,  1545,  1047,  1544,   184,   185,   902,   187,   188, 
     2759     495,  1410,   191,   192,   193,   114,  1550,   784,   197,   718, 
     2760     372,  1010,   201,  1006,   980,   377,   378,   796,  1282,     4, 
     2761     382,   926,   927,  1057,  1680,  1576,    11,  1639,   459,  1213, 
     2762    1417,   993,   937,  1022,    19,    20,   882,  1503,   550,   944, 
     2763     124,  1653,   947,   948,  1513,  1627,   556,  1080,  1095,  1505, 
     2764    1627,   556,  1333,  1345,  1514,   447,   266,   446,   451,   454, 
     2765     758,   449,   801,   172,   798,   149,   175,   176,   177,   178, 
     2766     803,   556,   561,   316,   183,   325,  1627,   561,  1111,   556, 
     2767     189,   165,   166,  1373,  1117,   385,  1698,   611,   197,  1701, 
     2768     556,   175,  1111,   613,   594,   556,  1117,   872,     4,  1132, 
     2769     184,   185,  1714,   187,   188,    11,   556,   191,   192,   193, 
     2770     925,  1430,   928,    19,    20,   556,  1693,   201,   901,   378, 
     2771     556,  1627,  1628,  1132,  1029,   895,   556,   330,   556,  1680, 
     2772      54,  1671,   494,   495,   496,   281,  1041,   467,  1043,   124, 
     2773    1183,   708,  1693,  1048,   155,     4,   692,   556,   630,    26, 
     2774    1055,  1056,    11,  1182,   102,  1386,   167,    -1,  1082,   107, 
     2775      19,    20,   110,  1186,   149,    -1,    -1,   655,    -1,  1074, 
     2776    1075,    -1,    -1,    -1,   122,    -1,    -1,   125,   126,    -1, 
     2777     165,   166,    -1,    -1,    -1,   547,    -1,    -1,    -1,  1094, 
     2778     175,   139,    -1,    -1,   556,    -1,   144,    -1,    -1,   184, 
     2779     185,    -1,   187,   188,    -1,    -1,   191,   192,   193,    -1, 
     2780      -1,    -1,    -1,  1118,    -1,    -1,   201,    -1,   124,    -1, 
     2781     231,    -1,   584,   585,    -1,    -1,   237,    -1,    -1,    -1, 
     2782      -1,   593,   594,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2783    1145,   252,    -1,   149,    -1,    -1,  1151,    -1,    -1,   611, 
     2784    1155,    -1,    -1,  1158,    -1,   617,  1161,  1162,    -1,   165, 
     2785     166,    -1,  1167,    -1,  1169,   124,    -1,    -1,    -1,   175, 
     2786     632,    -1,    -1,    -1,  1179,    -1,    -1,    -1,   184,   185, 
     2787      -1,   187,   188,    -1,    -1,   191,   192,   193,    -1,   651, 
     2788     149,    -1,    -1,    -1,   305,   201,    -1,    -1,    -1,    -1, 
     2789      -1,    -1,  1207,    -1,    -1,   316,   165,   166,   319,  1214, 
     2790      -1,    -1,  1217,    -1,    -1,  1220,   175,    -1,    -1,    -1, 
     2791      -1,    -1,    -1,   334,   335,   184,   185,    -1,   187,   188, 
     2792     692,    -1,   191,   192,   193,    25,    -1,    38,    -1,    -1, 
     2793     351,    -1,   201,   354,    -1,     5,     6,     7,     8,     9, 
     2794      10,    -1,    12,    13,    14,    15,    16,    17,   720,    19, 
     2795      20,    21,    22,    23,    -1,   376,   377,   378,   379,    -1, 
     2796      -1,    -1,    -1,    -1,    -1,    -1,    -1,    78,    -1,    -1, 
     2797      -1,  1286,    -1,  1288,    -1,    -1,    -1,     4,    -1,    -1, 
     2798      -1,    -1,    93,   404,    11,    -1,    -1,    -1,    -1,    -1, 
     2799      -1,    -1,    19,    20,    -1,    -1,    -1,   108,    -1,    99, 
     2800     100,   101,    -1,    -1,   115,    -1,  1321,   118,   119,   120, 
     2801     121,    -1,    -1,   124,    -1,    -1,   127,   128,   129,    -1, 
     2802      -1,    -1,  1337,    -1,    -1,    -1,    -1,    -1,    -1,  1344, 
     2803     130,    -1,   132,   133,   134,    -1,    -1,   137,   138,    -1, 
     2804     140,   141,   153,    -1,    -1,    -1,    -1,  1362,  1363,    -1, 
     2805    1365,    -1,    -1,    -1,    -1,  1370,   167,    -1,    -1,    -1, 
     2806      -1,    -1,    -1,    -1,    -1,  1380,    -1,    -1,    -1,    -1, 
     2807       4,    -1,   844,   184,   185,    -1,   187,    11,   499,    -1, 
     2808     191,   192,    -1,    -1,    -1,    19,    20,    -1,   509,   861, 
     2809      -1,    -1,    -1,    -1,    -1,    -1,   868,   124,    -1,    -1, 
     2810      -1,    -1,   874,   875,   876,   877,    -1,   879,    94,   881, 
     2811     882,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   104,    -1, 
     2812      -1,    -1,   149,    -1,   194,   195,   196,    -1,    -1,    -1, 
     2813      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   165,   166, 
     2814      -1,    -1,   914,    -1,    -1,    -1,    -1,    -1,   175,    -1, 
     2815      -1,    -1,    -1,   925,    -1,   927,   928,   184,   185,    -1, 
     2816     187,   188,    -1,    -1,   191,   192,   193,    -1,    -1,    -1, 
     2817      -1,    -1,    19,    20,   201,    -1,    -1,    -1,    -1,    -1, 
     2818      -1,     4,    -1,    -1,  1499,    -1,    -1,    -1,    11,  1504, 
     2819     124,   612,    -1,    -1,    -1,    -1,    19,    20,    -1,    -1, 
     2820    1515,  1516,  1517,    -1,    -1,    -1,  1521,  1522,    -1,    -1, 
     2821      -1,  1526,    -1,    -1,    -1,   149,    -1,  1532,    -1,  1534, 
    22562822      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2257       -1,    -1,    -1,    -1,    -1,   163,   164,   165,    -1,    -1, 
     2823     651,   165,   166,    -1,  1006,    -1,    -1,  1009,  1010,    -1, 
     2824      -1,   175,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   670, 
     2825     184,   185,    -1,   187,   188,  1027,    -1,   191,   192,   193, 
     2826      -1,    -1,    -1,    -1,    -1,    -1,    -1,   201,    -1,    -1, 
     2827      -1,   692,    -1,    -1,     4,    -1,    -1,   124,    -1,    -1, 
     2828      -1,    11,   703,    -1,   705,    -1,    -1,    -1,    -1,    19, 
     2829      20,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,  1071, 
     2830      -1,   124,   149,    -1,    -1,    -1,  1621,    -1,    -1,    -1, 
     2831      -1,    -1,  1084,    -1,    -1,    -1,  1631,    -1,   165,   166, 
     2832    1635,    -1,    -1,   744,    -1,   746,   149,    -1,   175,    -1, 
     2833     316,    -1,    -1,   754,    -1,    -1,    -1,   184,   185,    -1, 
     2834     187,   188,   165,   166,   191,   192,   193,    -1,  1120,    -1, 
     2835      -1,    -1,   175,    -1,   201,  1670,    -1,    -1,  1673,    -1, 
     2836      -1,   184,   185,    -1,   187,   188,    -1,    -1,   191,   192, 
     2837     193,    -1,    -1,    -1,    -1,    -1,  1148,    -1,   201,    -1, 
     2838    1152,    -1,    -1,    -1,     5,    -1,    -1,    -1,    -1,    -1, 
     2839      11,   377,   378,  1165,   124,    -1,    -1,    -1,    19,    20, 
     2840      -1,    22,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2841    1182,  1183,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   149, 
    22582842      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2259       -1,    -1,    -1,    -1,    -1,    -1,   163,   164,   165,     5, 
    2260        6,     7,     8,     9,    10,    -1,    12,    13,    14,    15, 
    2261       16,    17,    -1,    19,    20,    21,    22,    23,     5,     6, 
    2262        7,     8,     9,    10,    -1,    12,    13,    14,    15,    16, 
    2263       17,    -1,    19,    20,    21,    22,    23,     5,     6,     7, 
    2264        8,     9,    10,    -1,    12,    13,    14,    15,    16,    17, 
    2265       -1,    19,    20,    21,    22,    23,    -1,    -1,    -1,   164, 
    2266      165,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2267       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   164, 
    2268      165,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2269       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   164, 
    2270      165,     5,     6,     7,     8,     9,    10,    -1,    12,    13, 
    2271       14,    15,    16,    17,    -1,    19,    20,    21,    22,    23, 
    2272        5,     6,     7,     8,     9,    10,    -1,    12,    13,    14, 
    2273       15,    16,    17,    -1,    19,    20,    21,    22,    23,    -1, 
     2843      -1,   852,   853,   854,   855,   165,   166,    -1,    -1,   860, 
     2844      -1,    -1,    -1,    -1,    -1,   175,    -1,    -1,    -1,    -1, 
     2845      -1,   872,    -1,    -1,   184,   185,    -1,   187,   188,    -1, 
     2846      -1,   191,   192,   193,    -1,    -1,    -1,    -1,    -1,    -1, 
     2847      -1,   201,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2848      -1,     6,     7,    -1,     9,    10,   907,    12,    13,    14, 
     2849      15,    16,    17,    18,    19,    20,    21,    22,    23,    24, 
     2850      -1,    -1,    -1,   124,   925,   926,    -1,    -1,   494,   495, 
     2851      -1,   932,   933,    -1,    -1,   936,    -1,    -1,    -1,    -1, 
     2852      -1,    -1,   943,    -1,    -1,    -1,    -1,    -1,   149,    -1, 
     2853      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    64, 
     2854      -1,    -1,    -1,    -1,   165,   166,    -1,    -1,    -1,    -1, 
     2855     971,    -1,    -1,  1325,   175,    -1,    -1,    -1,   979,    -1, 
     2856      -1,   547,    -1,   184,   185,    -1,   187,   188,     5,    -1, 
     2857     191,   192,   193,  1345,    11,    -1,    -1,    -1,    -1,    -1, 
     2858     201,    -1,    19,    20,    -1,    -1,  1358,    -1,  1009,    -1, 
     2859      -1,    -1,    -1,    -1,    -1,  1367,  1017,    -1,   584,   585, 
     2860    1021,  1022,    -1,  1024,  1025,    -1,  1027,   593,   594,    -1, 
     2861      -1,    -1,    -1,    -1,     5,    -1,    -1,    -1,    -1,    -1, 
     2862      11,    -1,    -1,    -1,    -1,   611,    -1,    -1,    19,    20, 
     2863      -1,   617,    -1,    -1,    38,    -1,   161,   162,   163,   164, 
     2864      -1,    -1,    -1,    -1,    48,    -1,   632,    -1,    -1,    -1, 
     2865      -1,  1423,  1424,    -1,     5,    -1,  1077,    -1,  1430,  1080, 
     2866      11,    -1,  1083,    -1,    -1,   651,    -1,   192,    19,    20, 
     2867     195,   196,   197,    -1,    78,   200,    -1,  1449,    -1,    -1, 
     2868      -1,    -1,    -1,    -1,    -1,  1106,  1458,   124,    -1,    93, 
     2869      -1,    -1,  1113,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2870      -1,    -1,    -1,    -1,   108,    -1,   692,   111,   112,    -1, 
     2871      -1,   115,   149,    -1,   118,   119,   120,   121,    -1,    -1, 
     2872     124,    -1,  1494,   127,   128,   129,    -1,    -1,   165,   166, 
     2873    1502,  1152,    -1,   124,   720,    -1,    -1,    -1,   175,    -1, 
     2874      -1,  1513,    -1,    -1,    -1,    -1,    -1,   184,   185,   153, 
     2875     187,   188,  1173,    -1,   191,   192,   193,    -1,   149,    -1, 
     2876      -1,  1182,  1183,   167,   201,    -1,   170,    -1,    -1,    -1, 
     2877      -1,    -1,    -1,   124,   165,   166,    -1,    -1,   182,    -1, 
     2878     184,   185,    -1,   187,   175,    -1,    -1,   191,   192,    -1, 
     2879      -1,  1212,  1564,   184,   185,    -1,   187,   188,   149,    -1, 
     2880     191,   192,   193,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2881     201,    -1,    -1,    -1,   165,   166,    -1,    -1,    -1,    -1, 
     2882      -1,    -1,    -1,    -1,   175,  1246,    -1,    -1,    -1,  1250, 
     2883      -1,    -1,    -1,   184,   185,    -1,   187,   188,  1259,    -1, 
     2884     191,   192,   193,    -1,    -1,    -1,    -1,    38,    -1,    -1, 
     2885     201,    -1,    -1,    -1,    -1,  1627,    -1,    -1,    -1,    -1, 
    22742886      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2275       -1,    -1,    -1,    -1,    -1,    -1,    -1,   163,   164,   165, 
     2887    1291,    -1,    -1,    -1,    -1,   861,    -1,    -1,    -1,    -1, 
     2888      -1,    -1,   868,    -1,  1305,    -1,    -1,    78,   874,   875, 
     2889     876,   877,    -1,   879,    -1,   881,   882,    -1,    -1,    -1, 
     2890      -1,    -1,    93,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2891      -1,    -1,   103,    -1,    -1,    -1,    -1,   108,    -1,    -1, 
     2892      -1,  1342,    -1,    -1,   115,    -1,    -1,   118,   119,   120, 
     2893     121,    -1,    -1,   124,  1355,    -1,   127,   128,   129,   925, 
     2894      -1,   927,   928,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2895      -1,    -1,  1373,    -1,  1375,    -1,    -1,     6,     7,    -1, 
     2896       9,    10,   153,    12,    13,    14,    15,    16,    17,    18, 
     2897      19,    20,    21,    22,    23,    24,   167,    -1,    -1,    -1, 
    22762898      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2277       -1,    -1,    -1,    -1,    -1,    -1,   163,   164,   165,    -1, 
     2899      -1,    -1,    -1,   184,   185,    -1,   187,    -1,    -1,    -1, 
     2900     191,   192,  1423,  1424,    -1,    -1,    -1,    -1,  1429,  1430, 
     2901      -1,    -1,    -1,    -1,    -1,    64,    -1,    -1,    -1,    -1, 
     2902      -1,    -1,    -1,  1009,    -1,    -1,    -1,  1448,    -1,    -1, 
     2903      -1,    -1,    -1,    -1,    -1,    -1,    11,    -1,    -1,    -1, 
     2904      -1,  1027,    -1,    -1,    19,    20,    -1,    -1,    -1,    -1, 
     2905      -1,    -1,  1473,  1474,  1475,  1476,  1477,  1478,  1479,  1480, 
     2906    1481,  1482,  1483,  1484,  1485,  1486,  1487,  1488,  1489,  1490, 
     2907    1491,    -1,    -1,    -1,    49,    -1,    51,    52,    53,    54, 
     2908      -1,    56,    -1,    58,    59,  1071,    -1,    -1,    -1,    -1, 
     2909      65,    -1,    67,    -1,    69,    -1,    -1,    -1,    -1,    -1, 
    22782910      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2279       -1,    -1,    -1,    -1,    -1,   163,   164,   165,     5,     6, 
    2280        7,     8,     9,    10,    -1,    12,    13,    14,    15,    16, 
    2281       17,    -1,    19,    20,    21,    22,    23,     5,     6,     7, 
    2282        8,     9,    10,    -1,    12,    13,    14,    15,    16,    17, 
    2283       -1,    19,    20,    21,    22,    23,     5,     6,     7,     8, 
    2284        9,    10,    -1,    12,    13,    14,    15,    16,    17,    -1, 
    2285       19,    20,    21,    22,    23,    -1,    -1,    -1,    -1,   163, 
    2286      164,   165,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2287       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   163,   164, 
    2288      165,     5,     6,     7,     8,     9,    10,    -1,    12,    13, 
    2289       14,    15,    16,    17,    -1,    19,    20,    21,    22,    23, 
    2290        5,     6,     7,     8,     9,    10,    -1,    12,    13,    14, 
    2291       15,    16,    17,    -1,    19,    20,    21,    22,    23,     5, 
    2292        6,     7,     8,     9,    10,    -1,    12,    13,    14,    15, 
    2293       16,    17,    -1,    19,    20,    21,    22,    23,    -1,    -1, 
    2294       -1,    -1,    -1,    -1,    33,    34,    -1,    -1,    -1,    -1, 
    2295       39,    40,    41,    42,    43,    -1,   163,   164,   165,    -1, 
    2296       -1,    -1,    -1,    -1,    -1,    54,    55,    56,    57,    58, 
    2297       59,    60,   160,    62,    63,    64,   164,   165,    67,    68, 
    2298       69,    -1,    71,    72,    73,    74,    75,    -1,    77,    -1, 
    2299       -1,    -1,    -1,    -1,   163,   164,   165,     5,     6,     7, 
    2300        8,     9,    10,    -1,    12,    13,    14,    15,    16,    17, 
    2301       -1,    19,    20,    21,    22,    23,     5,     6,     7,     8, 
    2302        9,    10,    -1,    12,    13,    14,    15,    16,    17,    -1, 
    2303       19,    20,    21,    22,    23,    -1,    -1,    -1,    -1,   163, 
    2304      164,   165,    -1,   132,    -1,    -1,    -1,    -1,    -1,   138, 
    2305      139,    -1,    -1,    -1,    -1,   144,    -1,    -1,   163,   164, 
    2306      165,    -1,    -1,    -1,   153,   154,    -1,   156,   157,    -1, 
    2307       -1,   160,   161,   162,    -1,    -1,    -1,   163,   164,   165, 
    2308        5,     6,     7,     8,     9,    10,    -1,    12,    13,    14, 
    2309       15,    16,    17,    -1,    19,    20,    21,    22,    23,     5, 
    2310        6,     7,     8,     9,    10,    -1,    12,    13,    14,    15, 
    2311       16,    17,    -1,    19,    20,    21,    22,    23,     5,     6, 
    2312        7,     8,     9,    10,    -1,    12,    13,    14,    15,    16, 
    2313       17,    -1,    19,    20,    21,    22,    23,    -1,    -1,    -1, 
     2911      -1,    -1,   161,   162,   163,   164,    -1,    -1,  1539,    -1, 
    23142912      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2315       -1,    -1,    -1,    -1,    -1,   163,   164,   165,    -1,    -1, 
     2913      -1,    -1,    -1,    -1,  1120,    -1,    -1,    -1,    -1,    -1, 
     2914      -1,    -1,  1563,   192,   193,    -1,   195,   196,   197,   124, 
     2915     199,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,  1580, 
     2916      -1,    -1,  1148,    -1,    11,    -1,  1152,    -1,    -1,    -1, 
     2917      -1,    -1,    19,    20,   149,    -1,  1597,  1598,    -1,    -1, 
     2918      -1,  1602,    -1,  1604,    -1,    -1,    -1,    -1,    -1,    -1, 
     2919     165,   166,    -1,    -1,    11,    -1,  1182,  1183,    -1,    -1, 
     2920     175,    -1,    19,    20,    21,    -1,    -1,    -1,    -1,   184, 
     2921     185,    -1,   187,   188,    -1,    -1,   191,   192,   193,    -1, 
     2922      -1,    -1,    -1,    -1,    -1,    -1,   201,    -1,    -1,    -1, 
     2923      -1,    -1,    -1,    50,    -1,    -1,    -1,    -1,    -1,    -1, 
     2924    1661,    58,    -1,    60,    61,    62,    63,    94,    65,    -1, 
     2925      67,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     2926      -1,    -1,    -1,    -1,    -1,    -1,  1687,    -1,    -1,    -1, 
     2927      -1,    -1,    -1,    -1,    -1,    -1,    -1,   124,    -1,    11, 
     2928      -1,  1702,    -1,  1704,  1705,    -1,    -1,    19,    20,    -1, 
     2929    1711,    -1,    -1,    -1,    -1,  1716,    -1,    -1,    -1,    -1, 
     2930      -1,    -1,   149,    -1,    -1,    -1,    -1,   124,    -1,    -1, 
     2931      -1,    -1,    -1,    -1,    -1,    -1,    -1,    49,   165,   166, 
     2932      -1,    53,    54,    55,    56,    57,    58,    -1,   175,    -1, 
     2933      -1,    -1,   149,    65,    66,    67,    -1,   184,   185,  1325, 
     2934     187,   188,    -1,    -1,   191,   192,   193,    -1,   165,   166, 
     2935     167,    -1,    -1,    -1,   201,    11,    -1,    -1,   175,  1345, 
     2936      -1,    -1,    -1,    19,    20,    -1,    -1,   184,   185,    -1, 
     2937     187,   188,  1358,    -1,   191,   192,   193,    -1,    -1,    -1, 
     2938      -1,    -1,    -1,    -1,   201,    -1,    -1,    -1,    -1,    -1, 
     2939      -1,    -1,   124,    49,    -1,    51,    -1,    53,    54,    -1, 
     2940      56,    -1,    58,    59,    -1,    -1,    -1,    -1,    -1,    65, 
     2941      -1,    67,    -1,    69,    -1,    -1,    -1,   149,    -1,    -1, 
    23162942      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2317       -1,    -1,    -1,    -1,   163,   164,   165,     5,     6,     7, 
    2318        8,     9,    10,    -1,    12,    13,    14,    15,    16,    17, 
    2319       -1,    19,    20,    21,    22,    23,     5,     6,     7,     8, 
    2320        9,    10,    -1,    12,    13,    14,    15,    16,    17,    -1, 
    2321       19,    20,    21,    22,    23,     5,     6,     7,     8,     9, 
    2322       10,    -1,    12,    13,    14,    15,    16,    17,    -1,    19, 
    2323       20,    21,    22,    23,    -1,    -1,    -1,    -1,   163,   164, 
    2324      165,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2325       -1,    -1,    -1,    -1,    -1,    -1,    -1,   163,   164,   165, 
     2943      -1,    -1,    -1,   165,   166,    -1,    -1,  1423,  1424,    -1, 
     2944      11,    -1,    -1,   175,  1430,    -1,    -1,    -1,    19,    20, 
     2945      -1,    -1,   184,   185,    -1,   187,   188,    -1,    -1,   191, 
     2946     192,   193,    -1,    -1,    -1,    -1,    -1,    -1,   124,   201, 
     2947      -1,    -1,    -1,    44,    -1,    -1,    -1,    -1,    -1,    -1, 
     2948      -1,    -1,    -1,    -1,    -1,    -1,    -1,    58,    -1,    -1, 
     2949      -1,    -1,    -1,   149,    65,    11,    67,    68,    -1,    -1, 
     2950      -1,    -1,    -1,    19,    20,    -1,    -1,    -1,    -1,   165, 
     2951     166,    -1,    -1,    -1,    -1,    -1,  1502,    -1,    -1,   175, 
     2952      -1,    -1,    -1,    -1,    -1,    11,    -1,  1513,   184,   185, 
     2953      -1,   187,   188,    19,    20,   191,   192,   193,   109,    -1, 
     2954      -1,    -1,    58,    -1,    -1,   201,    -1,    -1,    -1,    65, 
     2955      -1,    67,    68,   124,    -1,    -1,    -1,    -1,    -1,    -1, 
    23262956      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2327       -1,    -1,    -1,    -1,    -1,    -1,   163,   164,   165,     5, 
    2328        6,     7,     8,     9,    10,    -1,    12,    13,    14,    15, 
    2329       16,    17,    -1,    19,    20,    21,    22,    23,     5,     6, 
    2330        7,     8,     9,    10,    -1,    12,    13,    14,    15,    16, 
    2331       17,    -1,    19,    20,    21,    22,    23,    -1,    -1,    -1, 
     2957      -1,    -1,    58,    -1,    -1,    -1,    -1,    -1,   149,    65, 
     2958      11,    67,    68,    -1,   155,    -1,    -1,    -1,    19,    20, 
     2959      -1,    -1,    -1,    -1,   165,   166,    -1,    -1,    -1,    -1, 
     2960      -1,    -1,    -1,    -1,   175,    -1,    -1,    -1,   124,    -1, 
     2961      -1,    -1,    -1,   184,   185,    -1,   187,   188,    -1,    -1, 
     2962     191,   192,   193,    -1,    -1,    -1,    57,    58,    -1,    -1, 
     2963     201,    -1,    -1,   149,    65,    11,    67,    -1,   124,    -1, 
     2964      -1,    -1,    -1,    19,    20,    -1,    11,    -1,    24,   165, 
     2965     166,    -1,    -1,    -1,    19,    20,    21,    -1,    -1,   175, 
     2966      -1,    -1,    -1,   149,    -1,    -1,    -1,    -1,   184,   185, 
     2967      -1,   187,   188,    -1,    -1,   191,   192,   193,    -1,   165, 
     2968     166,    -1,    -1,    -1,    -1,   201,    -1,    -1,    64,   175, 
     2969      -1,    -1,    -1,   124,    -1,    -1,    -1,    -1,   184,   185, 
     2970      11,   187,   188,    -1,    -1,   191,   192,   193,    19,    20, 
     2971      21,    11,    -1,    -1,    -1,   201,    -1,    -1,   149,    19, 
     2972      20,    -1,    -1,    -1,    24,    -1,    -1,    -1,    -1,    -1, 
     2973      -1,    -1,    -1,    -1,   165,   166,    -1,    -1,    -1,    -1, 
     2974      -1,    -1,    -1,    -1,   175,    -1,    -1,    -1,   124,    -1, 
     2975      -1,    -1,    -1,   184,   185,    -1,   187,   188,    11,   124, 
     2976     191,   192,   193,    -1,    64,    -1,    19,    20,    -1,    -1, 
     2977     201,    -1,    -1,   149,    -1,    -1,    -1,    -1,    -1,    -1, 
     2978      -1,    -1,    -1,    -1,   149,    -1,    -1,    -1,    -1,   165, 
     2979     166,    -1,    -1,    -1,    -1,    11,    -1,    -1,    -1,   175, 
     2980     165,   166,   167,    19,    20,    21,    -1,    -1,   184,   185, 
     2981     175,   187,   188,   124,    -1,   191,   192,   193,    -1,   184, 
     2982     185,   197,   187,   188,   124,   201,   191,   192,   193,    -1, 
     2983      -1,    -1,    11,    -1,    -1,    -1,   201,    -1,   149,    -1, 
     2984      19,    20,    21,    11,    -1,    -1,    -1,    -1,    -1,   149, 
     2985      -1,    19,    20,    -1,   165,   166,    -1,    -1,    -1,    -1, 
     2986      -1,    -1,    -1,    -1,   175,   165,   166,    -1,    -1,    -1, 
     2987      -1,   124,    -1,   184,   185,   175,   187,   188,    -1,    -1, 
     2988     191,   192,   193,    -1,   184,   185,    -1,   187,   188,    -1, 
     2989     201,   191,   192,   193,    -1,    -1,   149,   197,    11,    -1, 
     2990      -1,   201,    -1,    -1,    -1,    -1,    19,    20,   124,    -1, 
     2991      -1,    -1,   165,   166,    -1,    -1,    -1,    -1,    -1,    -1, 
     2992      -1,    -1,   175,    -1,    -1,    -1,    -1,    -1,    11,    -1, 
     2993      -1,   184,   185,   149,   187,   188,    19,    20,   191,   192, 
     2994     193,   194,    -1,    11,    -1,   124,    -1,    -1,   201,   165, 
     2995     166,    19,    20,    -1,    -1,    -1,   124,    -1,    -1,   175, 
     2996      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   184,   185, 
     2997     149,   187,   188,    -1,    11,   191,   192,   193,    -1,    -1, 
     2998      -1,   149,    19,    20,    -1,   201,   165,   166,    -1,    -1, 
     2999      -1,    -1,    -1,    -1,    -1,    -1,   175,   165,   166,    -1, 
     3000      -1,    -1,    -1,    -1,    -1,   184,   185,   175,   187,   188, 
     3001      -1,   124,   191,   192,   193,    -1,   184,   185,    -1,   187, 
     3002     188,    11,   201,   191,   192,   193,    -1,    -1,    -1,    19, 
     3003      20,    -1,    -1,   201,    -1,    -1,   149,    -1,    -1,    -1, 
     3004      -1,   124,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     3005      11,    -1,   165,   166,    -1,    -1,   124,    -1,    19,    20, 
     3006      -1,    -1,   175,    -1,    -1,    -1,   149,    -1,    -1,    -1, 
     3007      -1,   184,   185,    -1,   187,   188,    -1,    -1,   191,   192, 
     3008     193,   149,   165,   166,    -1,    -1,    -1,   124,   201,    -1, 
     3009      -1,    -1,   175,    -1,    -1,    -1,    -1,   165,   166,    -1, 
     3010      -1,   184,   185,    -1,   187,   188,    -1,   175,   191,   192, 
     3011     193,    -1,   149,    -1,    -1,    -1,   184,   185,   201,   187, 
     3012     188,    -1,    -1,   191,   192,   193,    -1,    -1,   165,   166, 
     3013      -1,    -1,    25,   201,   124,    -1,    -1,    -1,   175,    32, 
     3014      -1,    -1,    -1,    -1,    -1,    -1,    -1,   184,   185,    -1, 
     3015     187,   188,    -1,    -1,   191,   192,   193,    -1,    -1,   149, 
     3016      -1,    -1,    -1,   124,   201,    -1,    -1,    -1,    -1,    -1, 
     3017      -1,    -1,    -1,    -1,    -1,   165,   166,    -1,    -1,    -1, 
     3018      -1,    -1,    -1,    -1,    -1,   175,    -1,    -1,   149,    82, 
     3019      -1,    -1,    -1,    -1,   184,   185,    -1,   187,   188,    -1, 
     3020      -1,   191,   192,   193,   165,   166,    99,   100,    -1,    -1, 
     3021      -1,   201,    -1,    -1,   175,    -1,    -1,    -1,   111,    -1, 
     3022      -1,    -1,    -1,   184,   185,    -1,   187,   188,    -1,    -1, 
     3023     191,   192,   193,    -1,    -1,    -1,    -1,   130,    -1,   132, 
     3024     201,   134,   135,    -1,    -1,    -1,    -1,   140,    -1,   142, 
     3025      -1,    32,    -1,    -1,   147,    -1,    -1,    38,    -1,    -1, 
     3026      -1,    -1,    -1,    -1,    -1,    -1,    47,    48,    -1,    -1, 
     3027      -1,    -1,    -1,    -1,   167,    -1,    -1,   170,   171,   172, 
     3028      -1,    -1,   175,   176,   177,   178,    -1,    -1,    -1,    -1, 
     3029     183,   184,   185,   186,   187,    -1,   189,    78,   191,   192, 
    23323030      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2333       -1,    -1,    -1,    -1,    -1,   163,   164,   165,    -1,    -1, 
    2334       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2335       -1,    -1,    -1,    -1,   163,   164,   165,    -1,    -1,    -1, 
    2336       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2337       -1,    -1,    -1,   163,   164,   165,     5,     6,     7,     8, 
    2338        9,    10,    -1,    12,    13,    14,    15,    16,    17,    -1, 
    2339       19,    20,    21,    22,    23,     5,     6,     7,     8,     9, 
    2340       10,    -1,    12,    13,    14,    15,    16,    17,    -1,    19, 
    2341       20,    21,    22,    23,     5,     6,     7,     8,     9,    10, 
    2342       -1,    12,    13,    14,    15,    16,    17,    -1,    19,    20, 
    2343       21,    22,    23,    -1,    -1,    -1,    -1,   163,   164,   165, 
    2344       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2345       -1,    -1,    -1,    -1,    -1,    -1,   163,   164,   165,     5, 
    2346        6,     7,     8,     9,    10,    -1,    12,    13,    14,    15, 
    2347       16,    17,    -1,    19,    20,    21,    22,    23,     5,     6, 
    2348        7,     8,     9,    10,    -1,    12,    13,    14,    15,    16, 
    2349       17,    -1,    19,    20,    21,    22,    23,     5,     6,     7, 
    2350        8,     9,    10,    -1,    12,    13,    14,    15,    16,    17, 
    2351       -1,    19,    20,    21,    22,    23,    -1,    -1,    -1,    -1, 
    2352       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2353       -1,    -1,    -1,    -1,   163,   164,   165,    -1,    -1,    -1, 
    2354       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2355       -1,    -1,    -1,   163,   164,   165,    -1,    -1,    -1,    -1, 
    2356       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2357       -1,    -1,   163,   164,   165,     5,     6,     7,     8,     9, 
    2358       10,    -1,    12,    13,    14,    15,    16,    17,    -1,    19, 
    2359       20,    21,    22,    23,    -1,    -1,    -1,    -1,    -1,    -1, 
    2360       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2361       -1,    -1,    -1,    -1,    -1,     4,    -1,   163,   164,   165, 
    2362       -1,    -1,    11,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2363       19,    20,    21,    -1,    -1,    -1,   163,   164,   165,    -1, 
    2364       -1,    -1,    -1,    -1,    33,    34,    -1,    -1,    -1,    -1, 
    2365       39,    40,    41,    42,    43,   163,   164,   165,    -1,    -1, 
    2366       -1,    -1,    -1,    -1,    -1,    54,    55,    56,    57,    58, 
    2367       59,    60,    -1,    62,    63,    64,    -1,    -1,    67,    68, 
    2368       69,    -1,    71,    72,    73,    74,    75,    34,    77,    -1, 
    2369       -1,    -1,    39,    40,    -1,    42,    43,    -1,    -1,    -1, 
    2370       -1,    -1,    -1,    -1,    -1,    -1,    -1,    54,    55,    56, 
    2371       57,    58,    59,    60,    -1,    62,    63,    64,    -1,    -1, 
    2372       67,    68,    69,    -1,     4,    72,    73,    74,    75,    -1, 
    2373       77,    11,    -1,    -1,   164,   165,   125,    -1,    -1,    19, 
    2374       20,    -1,    -1,   132,    -1,    -1,    -1,    -1,    -1,   138, 
    2375      139,    -1,    -1,    33,    34,   144,    -1,    -1,    -1,    39, 
    2376       40,    41,    42,    43,   153,   154,    -1,   156,   157,    -1, 
    2377       -1,   160,   161,   162,    54,    55,    56,    57,    58,    59, 
    2378       60,    -1,    62,    63,    64,    -1,    -1,    67,    68,    69, 
    2379       -1,    71,    72,    73,    74,    75,    -1,    77,    -1,    -1, 
    2380       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2381       -1,    -1,    -1,   160,    -1,    -1,    -1,    -1,    -1,    -1, 
    2382       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2383       -1,    -1,    -1,     4,    -1,    -1,    -1,    -1,    -1,    -1, 
    2384       11,    -1,    -1,    -1,    -1,   125,    -1,    -1,    19,    20, 
    2385       -1,    -1,   132,    -1,    -1,    -1,    -1,    -1,   138,   139, 
    2386       -1,    -1,    33,    34,   144,    -1,    -1,    -1,    39,    40, 
    2387       41,    42,    43,   153,   154,    -1,   156,   157,    -1,    -1, 
    2388      160,   161,   162,    54,    55,    56,    57,    58,    59,    60, 
    2389       -1,    62,    63,    64,    -1,    -1,    67,    68,    69,    -1, 
    2390       71,    72,    73,    74,    75,    -1,    77,    -1,    -1,    -1, 
     3031      -1,    -1,    93,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     3032      -1,    -1,    -1,   104,   105,   106,    -1,   108,    -1,    32, 
     3033     111,    -1,   113,    -1,   115,    38,    -1,   118,   119,   120, 
     3034     121,    -1,    -1,   124,    -1,    48,   127,   128,   129,    -1, 
     3035     131,    -1,    32,    -1,    -1,    -1,    -1,    -1,    38,    -1, 
     3036      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    48,    -1, 
     3037      -1,    -1,   153,    -1,    -1,    78,    -1,    -1,    -1,    -1, 
     3038      -1,    -1,    -1,    -1,    -1,    -1,   167,   168,   169,   170, 
     3039      93,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    78,    -1, 
     3040      -1,    -1,    -1,   184,   185,   108,   187,    -1,   111,   112, 
     3041     191,   192,   115,    93,    -1,   118,   119,   120,   121,    -1, 
     3042      -1,   124,    -1,    -1,   127,   128,   129,    -1,   108,    -1, 
     3043      -1,   111,   112,    38,    -1,   115,    -1,    -1,   118,   119, 
     3044     120,   121,    -1,    -1,   124,    -1,    -1,   127,   128,   129, 
     3045     153,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     3046      -1,    -1,    -1,    -1,   167,    -1,    -1,   170,    -1,    -1, 
     3047      -1,    -1,    -1,   153,    -1,    -1,    -1,    -1,    -1,   182, 
     3048      -1,   184,   185,    -1,   187,    -1,    -1,   167,   191,   192, 
     3049     170,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     3050      -1,    -1,   182,   108,   184,   185,    -1,   187,   113,    -1, 
     3051      -1,   191,   192,   118,   119,   120,   121,    -1,    -1,   124, 
     3052      -1,    -1,   127,   128,   129,    -1,    -1,    -1,    -1,    -1, 
    23913053      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    23923054      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    23933055      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2394       -1,    -1,     4,    -1,    -1,    -1,    -1,    -1,    -1,    11, 
    2395       -1,    -1,    -1,    -1,   125,    -1,    -1,    19,    20,    -1, 
    2396       -1,   132,    -1,    -1,    -1,    -1,    -1,   138,   139,    -1, 
    2397       -1,    33,    34,   144,    -1,    -1,    -1,    39,    40,    41, 
    2398       42,    43,   153,   154,    -1,   156,   157,    -1,    -1,   160, 
    2399      161,   162,    54,    55,    56,    57,    58,    59,    60,    -1, 
    2400       62,    63,    64,    -1,    -1,    67,    68,    69,    -1,    71, 
    2401       72,    73,    74,    75,    -1,    77,    -1,    -1,    -1,    -1, 
    2402       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2403       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2404       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2405       -1,    -1,     5,    -1,    -1,    -1,    -1,    -1,    11,    -1, 
    2406       -1,    -1,    -1,   125,    -1,    -1,    19,    20,    21,    -1, 
    2407      132,    -1,    -1,    -1,    -1,    -1,   138,   139,    -1,    -1, 
    2408       33,    34,   144,    -1,    -1,    -1,    39,    40,    41,    42, 
    2409       43,   153,   154,    -1,   156,   157,    -1,    -1,   160,   161, 
    2410      162,    54,    55,    56,    57,    58,    59,    60,    -1,    62, 
    2411       63,    64,    -1,    -1,    67,    68,    69,    -1,    71,    72, 
    2412       73,    74,    75,    -1,    77,    -1,    -1,    -1,    -1,    -1, 
    2413       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2414       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2415       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2416       -1,     5,    -1,    -1,    -1,    -1,    -1,    11,    -1,    -1, 
    2417       -1,    -1,   125,    -1,    -1,    19,    20,    -1,    22,   132, 
    2418       -1,    -1,    -1,    -1,    -1,   138,   139,    -1,    -1,    33, 
    2419       34,   144,    -1,    -1,    -1,    39,    40,    41,    42,    43, 
    2420      153,   154,    -1,   156,   157,    -1,    -1,   160,   161,   162, 
    2421       54,    55,    56,    57,    58,    59,    60,    -1,    62,    63, 
    2422       64,    -1,    -1,    67,    68,    69,    -1,    71,    72,    73, 
    2423       74,    75,    -1,    77,    -1,    -1,    -1,    -1,    -1,    -1, 
    2424       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2425       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2426       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2427        5,    -1,    -1,    -1,    -1,    -1,    11,    -1,    -1,    -1, 
    2428       -1,   125,    -1,    -1,    19,    20,    21,    -1,   132,    -1, 
    2429       -1,    -1,    -1,    -1,   138,   139,    -1,    -1,    33,    34, 
    2430      144,    -1,    -1,    -1,    39,    40,    41,    42,    43,   153, 
    2431      154,    -1,   156,   157,    -1,    -1,   160,   161,   162,    54, 
    2432       55,    56,    57,    58,    59,    60,    -1,    62,    63,    64, 
    2433       -1,    -1,    67,    68,    69,    -1,    71,    72,    73,    74, 
    2434       75,    -1,    77,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2435       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2436       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2437       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,     5, 
    2438       -1,    -1,    -1,    -1,    -1,    11,    -1,    -1,    -1,    -1, 
    2439      125,    -1,    -1,    19,    20,    -1,    -1,   132,    -1,    -1, 
    2440       -1,    -1,    -1,   138,   139,    -1,    -1,    33,    34,   144, 
    2441       -1,    -1,    -1,    39,    40,    41,    42,    43,   153,   154, 
    2442       -1,   156,   157,    -1,    -1,   160,   161,   162,    54,    55, 
    2443       56,    57,    58,    59,    60,    -1,    62,    63,    64,    -1, 
    2444       -1,    67,    68,    69,    -1,    71,    72,    73,    74,    75, 
    2445       -1,    77,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2446       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2447       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2448       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,     5,    -1, 
    2449       -1,    -1,    -1,    -1,    11,    -1,    -1,    -1,    -1,   125, 
    2450       -1,    -1,    19,    20,    -1,    -1,   132,    -1,    -1,    -1, 
    2451       -1,    -1,   138,   139,    -1,    -1,    33,    34,   144,    -1, 
    2452       -1,    -1,    39,    40,    41,    42,    43,   153,   154,    -1, 
    2453      156,   157,    -1,    -1,   160,   161,   162,    54,    55,    56, 
    2454       57,    58,    59,    60,    -1,    62,    63,    64,    -1,    -1, 
    2455       67,    68,    69,    -1,    71,    72,    73,    74,    75,    -1, 
    2456       77,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2457       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2458       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2459       -1,    -1,    -1,    -1,    -1,    -1,    -1,     5,    -1,    -1, 
    2460       -1,    -1,    -1,    11,    -1,    -1,    -1,    -1,   125,    -1, 
    2461       -1,    19,    20,    -1,    -1,   132,    -1,    -1,    -1,    -1, 
    2462       -1,   138,   139,    -1,    -1,    33,    34,   144,    -1,    -1, 
    2463       -1,    39,    40,    41,    42,    43,   153,   154,    -1,   156, 
    2464      157,    -1,    -1,   160,   161,   162,    54,    55,    56,    57, 
    2465       58,    59,    60,    -1,    62,    63,    64,    -1,    -1,    67, 
    2466       68,    69,    -1,    71,    72,    73,    74,    75,    -1,    77, 
    2467       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2468       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2469       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2470       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2471       -1,    -1,    11,    -1,    -1,    -1,    -1,   125,    -1,    -1, 
    2472       19,    20,    -1,    -1,   132,    -1,    -1,    -1,    -1,    -1, 
    2473      138,   139,    -1,    -1,    33,    34,   144,    -1,    -1,    -1, 
    2474       39,    40,    41,    42,    43,   153,   154,    -1,   156,   157, 
    2475       -1,    -1,   160,   161,   162,    54,    55,    56,    57,    58, 
    2476       59,    60,    -1,    62,    63,    64,    -1,    -1,    67,    68, 
    2477       69,    -1,    71,    72,    73,    74,    75,    -1,    77,    -1, 
    2478       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2479       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2480       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2481       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2482       -1,    -1,    -1,    -1,    -1,    -1,   125,    -1,    -1,    -1, 
    2483       -1,    -1,    -1,   132,    -1,    -1,    -1,    -1,    -1,   138, 
    2484      139,    -1,    -1,    -1,    -1,   144,    -1,    -1,    -1,    -1, 
    2485       -1,    -1,    -1,    -1,   153,   154,    11,   156,   157,    -1, 
    2486       -1,   160,   161,   162,    19,    20,    21,   166,    23,    -1, 
    2487       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    33,    34, 
    2488       -1,    -1,    -1,    -1,    39,    40,    41,    42,    43,    -1, 
    2489       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    54, 
    2490       55,    56,    57,    58,    59,    60,    -1,    62,    63,    64, 
    2491       -1,    -1,    67,    68,    69,    -1,    71,    72,    73,    74, 
    2492       75,    -1,    77,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2493       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2494       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2495       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2496       -1,    -1,    -1,    -1,    -1,    11,    -1,    -1,    -1,    -1, 
    2497      125,    -1,    -1,    19,    20,    21,    -1,   132,    -1,    -1, 
    2498       -1,    -1,    -1,   138,   139,    -1,    -1,    33,    34,   144, 
    2499       -1,    -1,    -1,    39,    40,    41,    42,    43,   153,   154, 
    2500       -1,   156,   157,    -1,    -1,   160,   161,   162,    54,    55, 
    2501       56,    57,    58,    59,    60,    -1,    62,    63,    64,    -1, 
    2502       -1,    67,    68,    69,    -1,    71,    72,    73,    74,    75, 
    2503       -1,    77,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2504       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2505       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2506       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2507       -1,    -1,    -1,    -1,    11,    -1,    -1,    -1,    -1,   125, 
    2508       -1,    -1,    19,    20,    21,    -1,   132,    -1,    -1,    -1, 
    2509       -1,    -1,   138,   139,    -1,    -1,    33,    34,   144,    -1, 
    2510       -1,    -1,    39,    40,    41,    42,    43,   153,   154,    -1, 
    2511      156,   157,    -1,    -1,   160,   161,   162,    54,    55,    56, 
    2512       57,    58,    59,    60,    -1,    62,    63,    64,    -1,    -1, 
    2513       67,    68,    69,    -1,    71,    72,    73,    74,    75,    -1, 
    2514       77,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2515       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2516       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2517       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2518       -1,    -1,    -1,    11,    -1,    -1,    -1,    -1,   125,    -1, 
    2519       -1,    19,    20,    21,    -1,   132,    -1,    -1,    -1,    -1, 
    2520       -1,   138,   139,    -1,    -1,    33,    34,   144,    -1,    -1, 
    2521       -1,    39,    40,    41,    42,    43,   153,   154,    -1,   156, 
    2522      157,    -1,    -1,   160,   161,   162,    54,    55,    56,    57, 
    2523       58,    59,    60,    -1,    62,    63,    64,    -1,    -1,    67, 
    2524       68,    69,    -1,    71,    72,    73,    74,    75,    -1,    77, 
    2525       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2526       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2527       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2528       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2529       -1,    -1,    11,    -1,    -1,    -1,    -1,   125,    -1,    -1, 
    2530       19,    20,    21,    -1,   132,    -1,    -1,    -1,    -1,    -1, 
    2531      138,   139,    -1,    -1,    33,    34,   144,    -1,    -1,    -1, 
    2532       39,    40,    41,    42,    43,   153,   154,    -1,   156,   157, 
    2533       -1,    -1,   160,   161,   162,    54,    55,    56,    57,    58, 
    2534       59,    60,    -1,    62,    63,    64,    -1,    -1,    67,    68, 
    2535       69,    -1,    71,    72,    73,    74,    75,    -1,    77,    -1, 
    2536       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2537       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2538       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2539       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2540       -1,    -1,    -1,    -1,    -1,    -1,   125,    -1,    -1,    -1, 
    2541       -1,    -1,    -1,   132,    -1,    -1,    -1,    -1,    -1,   138, 
    2542      139,    -1,    11,    -1,    -1,   144,    -1,    -1,    -1,    -1, 
    2543       19,    20,    -1,    -1,   153,   154,    -1,   156,   157,    -1, 
    2544       -1,   160,   161,   162,    33,    34,    35,    -1,    -1,    -1, 
    2545       39,    40,    41,    42,    43,    -1,    -1,    -1,    -1,    -1, 
    2546       -1,    -1,    -1,    -1,    -1,    54,    55,    56,    57,    58, 
    2547       59,    60,    -1,    62,    63,    64,    -1,    -1,    67,    68, 
    2548       69,    -1,    71,    72,    73,    74,    75,    -1,    77,    -1, 
    2549       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2550       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2551       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2552       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2553       -1,    11,    -1,    -1,    -1,    -1,   125,    -1,    -1,    19, 
    2554       20,    21,    -1,   132,    -1,    -1,    -1,    -1,    -1,   138, 
    2555      139,    -1,    -1,    33,    34,   144,    -1,    -1,    -1,    39, 
    2556       40,    41,    42,    43,   153,   154,    -1,   156,   157,    -1, 
    2557       -1,   160,   161,   162,    54,    55,    56,    57,    58,    59, 
    2558       60,    -1,    62,    63,    64,    -1,    -1,    67,    68,    69, 
    2559       -1,    71,    72,    73,    74,    75,    -1,    77,    -1,    -1, 
    2560       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2561       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2562       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2563       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2564       11,    -1,    -1,    -1,    -1,   125,    -1,    -1,    19,    20, 
    2565       21,    -1,   132,    -1,    -1,    -1,    -1,    -1,   138,   139, 
    2566       -1,    -1,    33,    34,   144,    -1,    -1,    -1,    39,    40, 
    2567       41,    42,    43,   153,   154,    -1,   156,   157,    -1,    -1, 
    2568      160,   161,   162,    54,    55,    56,    57,    58,    59,    60, 
    2569       -1,    62,    63,    64,    -1,    -1,    67,    68,    69,    -1, 
    2570       71,    72,    73,    74,    75,    -1,    77,    -1,    -1,    -1, 
    2571       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2572       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2573       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2574       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    11, 
    2575       -1,    -1,    -1,    -1,   125,    -1,    -1,    19,    20,    -1, 
    2576       -1,   132,    -1,    -1,    -1,    -1,    -1,   138,   139,    -1, 
    2577       -1,    33,    34,   144,    -1,    -1,    -1,    39,    40,    41, 
    2578       42,    43,   153,   154,    -1,   156,   157,    -1,    -1,   160, 
    2579      161,   162,    54,    55,    56,    57,    58,    59,    60,    -1, 
    2580       62,    63,    64,    -1,    -1,    67,    68,    69,    -1,    71, 
    2581       72,    73,    74,    75,    -1,    77,    -1,    -1,    -1,    -1, 
    2582       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2583       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2584       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2585       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    11,    -1, 
    2586       -1,    -1,    -1,   125,    -1,    -1,    19,    20,    -1,    -1, 
    2587      132,    -1,    -1,    -1,    -1,    -1,   138,   139,    -1,    -1, 
    2588       33,    34,   144,    -1,    -1,    -1,    39,    40,    41,    42, 
    2589       43,   153,   154,    -1,   156,   157,    -1,    -1,   160,   161, 
    2590      162,    54,    55,    56,    57,    58,    59,    60,    -1,    62, 
    2591       63,    64,    -1,    -1,    67,    68,    69,    -1,    71,    72, 
    2592       73,    74,    75,    -1,    77,    -1,    -1,    -1,    -1,    -1, 
    2593       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2594       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2595       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2596       -1,    -1,    -1,    -1,    -1,    -1,    -1,    11,    -1,    -1, 
    2597       -1,    -1,   125,    -1,    -1,    19,    20,    -1,    -1,   132, 
    2598       -1,    -1,    -1,    -1,    -1,   138,   139,    -1,    -1,    33, 
    2599       34,   144,    -1,    -1,    -1,    39,    40,    41,    42,    43, 
    2600      153,   154,    -1,   156,   157,    -1,    -1,   160,   161,   162, 
    2601       54,    55,    56,    57,    58,    59,    60,    -1,    62,    63, 
    2602       64,    -1,    -1,    67,    68,    69,    -1,    71,    72,    73, 
    2603       74,    75,    -1,    77,    -1,    -1,    -1,    -1,    -1,    -1, 
    2604       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2605       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2606       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2607       -1,    -1,    -1,    -1,    -1,    -1,    11,    -1,    -1,    -1, 
    2608       -1,   125,    -1,    -1,    19,    20,    -1,    -1,   132,    -1, 
    2609       -1,    -1,    -1,    -1,   138,   139,    -1,    -1,    33,    34, 
    2610      144,    -1,    -1,    -1,    39,    40,    41,    42,    43,   153, 
    2611      154,    -1,   156,   157,    -1,    -1,   160,   161,   162,    54, 
    2612       55,    56,    57,    58,    59,    60,    -1,    62,    63,    64, 
    2613       -1,    -1,    67,    68,    69,    -1,    71,    72,    73,    74, 
    2614       75,    -1,    77,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2615       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2616       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2617       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2618       -1,    -1,    -1,    -1,    -1,    11,    -1,    -1,    -1,    -1, 
    2619      125,    -1,    -1,    19,    20,    -1,    -1,   132,    -1,    -1, 
    2620       -1,    -1,    -1,   138,   139,    -1,    -1,    33,    34,   144, 
    2621       -1,    -1,    -1,    39,    40,    41,    42,    43,   153,   154, 
    2622       -1,   156,   157,    -1,    -1,   160,   161,   162,    54,    55, 
    2623       56,    57,    58,    59,    60,    -1,    62,    63,    64,    -1, 
    2624       -1,    67,    68,    69,    -1,    71,    72,    73,    74,    75, 
    2625       -1,    77,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2626       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2627       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2628       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2629       -1,    -1,    -1,    -1,    11,    -1,    -1,    -1,    -1,   125, 
    2630       -1,    -1,    19,    20,    -1,    -1,   132,    -1,    -1,    -1, 
    2631       -1,    -1,   138,   139,    -1,    -1,    33,    34,   144,    -1, 
    2632       -1,    -1,    39,    40,    41,    42,    43,   153,   154,    -1, 
    2633      156,   157,    -1,    -1,   160,   161,   162,    54,    55,    56, 
    2634       57,    58,    59,    60,    -1,    62,    63,    64,    -1,    -1, 
    2635       67,    68,    69,    -1,    71,    72,    73,    74,    75,    -1, 
    2636       77,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2637       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2638       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2639       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2640       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   125,    -1, 
    2641       -1,    -1,    -1,    -1,    -1,   132,    -1,    -1,    -1,    -1, 
    2642       -1,   138,   139,    -1,    -1,    -1,    -1,   144,    -1,    -1, 
    2643       -1,    -1,    -1,    -1,    -1,    -1,   153,   154,    -1,   156, 
    2644      157,    -1,    -1,   160,   161,   162,    19,    20,    21,    -1, 
    2645       23,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2646       33,    34,    -1,    -1,    -1,    -1,    39,    40,    41,    42, 
    2647       43,    -1,    -1,    46,    47,    48,    49,    50,    -1,    52, 
    2648       53,    54,    55,    56,    57,    58,    59,    60,    -1,    62, 
    2649       63,    64,    -1,    -1,    67,    68,    69,    -1,    71,    72, 
    2650       73,    74,    75,    -1,    77,    -1,    -1,    -1,    -1,    -1, 
    2651       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2652       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2653       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2654       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2655       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   132, 
    2656       -1,    -1,    -1,    -1,    -1,   138,   139,    -1,    -1,    -1, 
    2657       -1,   144,    -1,    -1,    -1,    -1,    19,    20,    21,    -1, 
    2658      153,   154,    -1,   156,   157,    -1,    -1,   160,   161,   162, 
    2659       33,    34,    -1,    -1,    -1,    -1,    39,    40,    41,    42, 
    2660       43,    -1,    -1,    46,    47,    48,    49,    50,    -1,    52, 
    2661       53,    54,    55,    56,    57,    58,    59,    60,    -1,    62, 
    2662       63,    64,    19,    20,    67,    68,    69,    -1,    71,    72, 
    2663       73,    74,    75,    -1,    77,    -1,    33,    34,    -1,    -1, 
    2664       -1,    -1,    39,    40,    41,    42,    43,    -1,    -1,    46, 
    2665       47,    48,    49,    50,    -1,    52,    53,    54,    55,    56, 
    2666       57,    58,    59,    60,    -1,    62,    63,    64,    -1,    -1, 
    2667       67,    68,    69,    -1,    71,    72,    73,    74,    75,    -1, 
    2668       77,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   132, 
    2669       -1,    -1,    -1,    -1,    -1,   138,   139,    -1,    -1,    -1, 
    2670       -1,   144,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2671      153,   154,    -1,   156,   157,    -1,    -1,   160,   161,   162, 
    2672       -1,    -1,    -1,    -1,    -1,    -1,    25,    -1,    -1,    28, 
    2673       -1,    30,    -1,    32,    -1,   132,    35,    -1,    -1,    -1, 
    2674       -1,   138,   139,    -1,    -1,    -1,    45,   144,    -1,    -1, 
    2675       -1,    -1,    -1,    -1,    -1,    -1,   153,   154,    -1,   156, 
    2676      157,    -1,    61,   160,   161,   162,    65,    66,    -1,    -1, 
    2677       -1,    70,    -1,    -1,    -1,    -1,    -1,    76,    -1,    78, 
    2678       79,    -1,    81,    -1,    -1,    -1,    -1,    86,    87,    88, 
    2679       89,    90,    -1,    92,    93,    -1,    -1,    96,    97,    98, 
    2680       99,   100,   101,   102,   103,   104,   105,   106,    -1,   108, 
    2681       -1,   110,   111,    -1,    -1,   114,   115,   116,    -1,   118, 
    2682       -1,   120,    -1,    -1,   123,   124,    -1,    -1,   127,   128, 
    2683      129,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   137,    -1, 
    2684       -1,    -1,   141,   142,   143,   144,   145,   146,   147,   148, 
    2685      149,   150,   151,   152,    -1,    -1,   155,    -1,    -1,   158, 
    2686      159,   160,   161,    25,    -1,    -1,    28,   166,    30,    -1, 
    2687       32,    -1,    -1,    35,    -1,    -1,    -1,    -1,    -1,    -1, 
    2688       -1,    -1,    -1,    45,    -1,    -1,    -1,    -1,    -1,    -1, 
    2689       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    61, 
    2690       -1,    -1,    -1,    65,    66,    -1,    -1,    -1,    70,    -1, 
    2691       -1,    -1,    -1,    -1,    76,    -1,    78,    79,    -1,    81, 
    2692       -1,    -1,    -1,    -1,    86,    87,    88,    89,    90,    -1, 
    2693       92,    93,    -1,    -1,    96,    97,    98,    99,   100,   101, 
    2694      102,   103,   104,   105,   106,    -1,   108,    -1,   110,   111, 
    2695       -1,    -1,   114,   115,   116,    -1,   118,    -1,   120,    -1, 
    2696       -1,   123,   124,    -1,    -1,   127,   128,   129,    -1,    -1, 
    2697       -1,    -1,    -1,    -1,    -1,   137,    -1,    -1,    -1,   141, 
    2698      142,   143,   144,   145,   146,   147,   148,   149,   150,   151, 
    2699      152,    32,    -1,   155,    35,    -1,   158,   159,   160,   161, 
    2700       -1,    -1,    -1,    -1,    45,    -1,    -1,    -1,    -1,    -1, 
    2701       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2702       61,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2703       -1,    -1,    -1,    -1,    -1,    76,    -1,    -1,    -1,    -1, 
    2704       81,    -1,    83,    -1,    -1,    86,    87,    88,    89,    90, 
    2705       -1,    -1,    93,    -1,    -1,    96,    97,    98,    99,   100, 
    2706      101,   102,   103,   104,   105,    -1,    -1,    32,    -1,    -1, 
    2707       35,    -1,    -1,    -1,   115,    -1,    -1,    -1,    -1,   120, 
    2708       45,    -1,    -1,    -1,    -1,    -1,   127,    -1,   129,    -1, 
    2709       -1,    -1,    -1,    -1,    -1,    -1,    61,    -1,    -1,    -1, 
    2710       -1,    -1,    -1,    -1,    -1,    -1,    -1,   148,   149,   150, 
    2711      151,    76,    -1,    -1,    -1,    -1,    81,    -1,    -1,   160, 
    2712      161,    86,    87,    88,    89,    90,    -1,    -1,    93,    -1, 
    2713       -1,    96,    97,    98,    99,   100,   101,   102,   103,   104, 
    2714      105,    -1,    -1,    -1,    -1,    -1,    35,    -1,    -1,    -1, 
    2715      115,    -1,    -1,    -1,    -1,   120,    -1,    -1,    -1,    -1, 
    2716       -1,    -1,   127,    -1,   129,    -1,    -1,    -1,    -1,    -1, 
    2717       -1,    -1,    61,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2718       -1,    -1,    -1,   148,   149,   150,   151,    76,    -1,    -1, 
    2719       -1,    -1,    81,    82,    -1,   160,   161,    86,    87,    88, 
    2720       -1,    90,    -1,    -1,    93,    -1,    -1,    96,    97,    98, 
    2721       99,   100,   101,   102,   103,   104,   105,    -1,    -1,    -1, 
    2722       -1,    -1,    35,    -1,    -1,    -1,   115,    -1,    -1,    -1, 
    2723       -1,   120,    -1,    -1,    -1,    -1,    -1,    -1,   127,    -1, 
    2724      129,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    61,    -1, 
    2725       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   148, 
    2726      149,   150,   151,    76,    -1,    -1,    -1,    -1,    81,    -1, 
    2727       -1,   160,   161,    86,    87,    88,    -1,    90,    -1,    -1, 
    2728       93,    -1,    -1,    96,    97,    98,    99,   100,   101,   102, 
    2729      103,   104,   105,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2730       -1,    -1,   115,    -1,    -1,    -1,    -1,   120,    -1,    -1, 
    2731       -1,    -1,    -1,    -1,   127,    -1,   129,    -1,    -1,    -1, 
    2732       -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
    2733       -1,    -1,    -1,    -1,    -1,   148,   149,   150,   151,    -1, 
    2734       -1,    -1,    -1,    -1,    -1,    -1,    -1,   160,   161 
     3056      -1,    -1,   167,    -1,    -1,    -1,    -1,    -1,    -1,    -1, 
     3057      -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,    -1,   184, 
     3058     185,    -1,   187,    -1,    -1,    -1,   191,   192 
    27353059}; 
    27363060 
     
    27393063static const yytype_uint16 yystos[] = 
    27403064{ 
    2741        0,   170,     0,     1,    24,    25,    28,    30,    32,    35, 
    2742       45,    61,    65,    66,    70,    76,    78,    79,    81,    86, 
    2743       87,    88,    89,    90,    92,    93,    96,    97,    98,    99, 
    2744      100,   101,   102,   103,   104,   105,   106,   108,   110,   111, 
    2745      114,   115,   116,   118,   120,   123,   124,   127,   128,   129, 
    2746      137,   140,   141,   142,   143,   144,   145,   146,   147,   148, 
    2747      149,   150,   151,   152,   155,   158,   159,   160,   161,   166, 
    2748      171,   172,   173,   174,   176,   178,   186,   198,   199,   203, 
    2749      204,   209,   210,   211,   212,   213,   215,   216,   223,   225, 
    2750      228,   231,   232,   267,   276,   277,   282,   283,   284,   286, 
    2751      287,   291,   300,   301,   302,   303,   304,   310,   315,   319, 
    2752      320,   323,   331,   332,   333,   334,   335,   338,   339,   341, 
    2753      344,   345,   348,   357,   359,   369,   153,   181,   160,   180, 
    2754      162,   162,    11,    19,    20,    33,    34,    39,    40,    41, 
    2755       42,    43,    54,    55,    56,    57,    58,    59,    60,    62, 
    2756       63,    64,    67,    68,    69,    71,    72,    73,    74,    75, 
    2757       77,   125,   132,   138,   139,   144,   153,   154,   156,   157, 
    2758      160,   161,   162,   166,   249,   250,   252,   253,   257,   259, 
    2759      260,   261,   262,   267,   268,   269,   273,   275,   162,   191, 
    2760      192,   162,   249,   272,   131,   166,   195,   166,   195,   273, 
    2761      161,   162,   162,     3,   161,   179,   220,   305,   160,   160, 
    2762      166,   336,   162,   162,   352,   160,   161,   162,   353,   162, 
    2763      162,   195,   195,    18,    22,   219,   267,   162,   190,   119, 
    2764      130,   123,   160,   224,   173,    78,    79,   187,   244,   133, 
    2765      160,   161,   237,   336,   160,   162,   200,   201,   206,     4, 
    2766      175,    24,   140,   166,    24,    29,    31,   175,   175,   160, 
    2767      162,   221,   222,   166,     3,   220,   160,   205,   219,     3, 
    2768      220,   220,     3,   220,   160,   217,   218,   219,     3,    31, 
    2769      131,   196,   197,   226,   240,    21,   162,   229,    21,   162, 
    2770      235,   337,   160,   172,   172,   172,   172,   336,   336,   336, 
    2771        5,   122,   168,   340,     3,   162,   342,   101,   160,   273, 
    2772      352,    19,    20,    21,    46,    47,    48,    49,    50,    52, 
    2773       53,   160,   162,   250,   257,   268,   350,   352,   358,   360, 
    2774      361,   362,   175,   249,   294,   249,   249,   249,   251,   162, 
    2775      162,   162,   251,   249,   251,   162,   162,   162,   162,   162, 
    2776      162,   162,   162,   162,   162,   162,   162,   249,   162,   251, 
    2777      162,   162,   162,   162,   249,   250,   252,   275,   366,   367, 
    2778      162,   249,   252,     5,     6,     7,     8,     9,    10,    12, 
     3065       0,   204,     0,     1,    24,    28,    30,    37,    64,    87, 
     3066     114,   172,   197,   205,   206,   207,   208,   210,   211,   264, 
     3067     265,   632,   635,   652,   654,   688,   689,   690,   691,   692, 
     3068     702,   703,   184,   212,   191,   191,   175,   176,   177,   178, 
     3069     183,   189,   191,   231,   266,   314,   209,    24,   197,    24, 
     3070     266,   236,   237,   405,   645,   647,   653,   653,    29,    31, 
     3071     114,   690,   653,   653,   209,   655,   636,   268,   267,   272, 
     3072     269,   271,   270,   193,   194,   194,   209,   197,   208,    25, 
     3073      32,    82,    99,   100,   111,   132,   134,   135,   147,   167, 
     3074     170,   171,   184,   185,   186,   187,   191,   192,   231,   238, 
     3075     239,   240,   251,   259,   260,   288,   290,   292,   330,   331, 
     3076     346,   364,   369,   386,   387,   392,   397,   398,   405,   406, 
     3077     412,   416,   422,   432,   434,   443,   445,   447,   450,   451, 
     3078     452,   513,   514,   539,   540,   541,   543,   549,   550,   553, 
     3079     587,   606,   631,   669,   672,   714,   160,   647,   259,   260, 
     3080     634,   641,   715,    38,    48,    78,    93,   108,   115,   118, 
     3081     119,   120,   121,   124,   127,   128,   129,   153,   191,   241, 
     3082     242,   252,   253,   259,   457,   474,   513,   514,   524,   525, 
     3083     529,   539,   558,   559,   564,   568,   569,   572,   584,   585, 
     3084     586,   587,   588,   593,   600,   604,   605,   606,   619,   622, 
     3085     625,   677,   682,   714,   191,   705,   191,   695,   241,   241, 
     3086     206,   206,    21,   193,   273,   274,   273,   273,   273,    21, 
     3087     193,   284,   285,   286,   273,     4,    11,    19,    20,    21, 
     3088     124,   149,   165,   166,   175,   188,   192,   193,   201,   231, 
     3089     254,   257,   263,   275,   276,   279,   280,   288,   289,   315, 
     3090     316,   321,   323,   432,   481,   482,   483,   484,   485,   488, 
     3091     489,   491,   493,   494,   495,   496,   497,   501,   504,   506, 
     3092     675,   684,   393,   206,   193,   417,   418,     3,   206,   213, 
     3093     544,   154,   191,   670,   671,   154,   400,    22,   423,   206, 
     3094     544,     3,   293,   294,   193,   373,   374,   376,   377,   432, 
     3095     434,     4,   193,   240,   102,   107,   139,   434,   193,   291, 
     3096     264,   366,   400,   130,   140,   142,   146,   193,   515,     5, 
     3097     193,   446,   537,   538,   546,   546,   646,   112,   633,   642, 
     3098     643,   644,   691,   702,   193,   193,   191,   231,   235,   501, 
     3099     557,   191,   206,   260,   191,   197,   717,   193,   193,   193, 
     3100     628,   193,   506,   591,   193,   591,   193,   193,   206,   501, 
     3101     503,   504,   509,   510,   511,   512,   589,     4,   112,   246, 
     3102     247,   243,   244,   245,   252,   631,   110,   122,   125,   126, 
     3103     144,   191,   526,   537,    47,   570,   571,   575,   193,   678, 
     3104     193,   709,   193,   246,   246,   192,    94,   511,   193,   276, 
     3105     287,    73,    94,   263,   193,   322,   325,   326,   327,   501, 
     3106     200,   200,   231,   275,   278,   279,   281,   488,   501,     5, 
     3107       3,   194,   322,    23,   486,    21,    22,   487,   275,   276, 
     3108     488,   276,   484,    12,    13,    14,    15,    16,    17,    18, 
     3109     161,   162,   163,   164,   195,   196,   490,   492,    10,   498, 
     3110       9,   499,     6,     7,   500,   491,   193,   193,   419,     3, 
     3111     206,   116,   117,   231,   545,   206,   670,     3,   206,   191, 
     3112     673,   674,   191,    18,    22,   425,   426,   206,   295,   296, 
     3113     346,   191,   154,   191,   377,   378,   379,   445,   449,   450, 
     3114     451,     3,   371,   372,   427,     3,    22,   111,   170,   448, 
     3115     206,   506,    21,   192,   260,   501,   503,   610,   206,     5, 
     3116     444,   505,   506,   264,   300,   301,   302,   303,     3,   333, 
     3117     334,   335,   365,   191,   367,   368,   668,   400,   400,   143, 
     3118     264,   408,   409,   191,   432,   433,   434,   501,   521,   522, 
     3119     523,   472,   506,   516,   517,   518,   519,   146,   501,   444, 
     3120     199,   245,   168,   169,   191,   261,   262,   542,   547,   548, 
     3121     551,   554,   555,   262,   547,     3,   154,   650,   716,   405, 
     3122     637,   644,   501,   532,   501,   206,   206,   206,   458,   594, 
     3123     601,   193,    58,    65,    67,    68,   501,   591,   623,   624, 
     3124     206,    58,    65,    67,    68,   591,   620,   621,   206,   475, 
     3125     231,   720,   206,    48,   206,   656,   657,   245,   501,    21, 
     3126      50,    58,    60,    61,    62,    63,    65,    67,   191,   434, 
     3127     438,   590,   591,   592,   607,   608,   609,   610,   607,   610, 
     3128     683,     4,   260,   513,   524,   525,   527,   530,   531,   104, 
     3129     560,   561,   565,   136,   193,   579,   131,   571,   576,   537, 
     3130     194,   680,   206,   710,   704,   693,   405,   699,   405,   706, 
     3131       5,   194,   263,     5,     5,     3,   194,   325,   501,   150, 
     3132       3,   191,   192,   277,   277,   174,   279,   194,   263,   316, 
     3133     202,   324,   276,   483,   483,   484,   485,   489,   493,   494, 
     3134     495,   194,   676,   191,   395,   396,   231,   421,   435,   443, 
     3135     445,   451,   418,   193,   536,     5,   206,   671,     3,   206, 
     3136      22,   191,   191,   429,   430,     3,   206,   193,     3,   370, 
     3137     427,   373,   376,   231,   275,   276,   278,   279,   288,   313, 
     3138     314,   317,   345,   375,   381,   384,   385,   432,   488,   675, 
     3139     206,   544,   206,   544,     4,    21,   154,   231,   453,   454, 
     3140     456,   501,   504,   206,     3,   206,   501,   194,     4,     3, 
     3141     154,   304,   173,   299,   302,    25,   101,   130,   132,   133, 
     3142     134,   137,   138,   140,   141,   336,   346,   191,   339,   340, 
     3143     342,   154,     3,   206,     3,   191,   389,   231,   341,   401, 
     3144     402,   403,   404,   426,   407,   193,     3,   206,   199,   206, 
     3145       4,     3,   194,     3,   194,   434,   520,   206,   194,   447, 
     3146     206,   544,     4,   113,    38,   127,   129,   259,   457,   474, 
     3147     513,   524,   552,   568,   585,   587,   593,   600,   604,   605, 
     3148     606,   619,   622,   625,   677,   546,   542,   555,   259,   134, 
     3149     661,   191,   206,   182,   194,   194,   435,   445,   450,   465, 
     3150     466,   467,    49,    53,    54,    55,    56,    57,    58,    65, 
     3151      66,    67,   591,   596,   597,    57,    58,    65,    67,   591, 
     3152     602,   603,    49,    51,    52,    53,    54,    56,    58,    59, 
     3153      65,    67,    69,   591,   629,   630,   591,   260,   434,   441, 
     3154     442,   434,   439,   440,   599,     3,   194,   591,   260,   441, 
     3155     599,     3,   194,   467,   477,     3,   194,   193,   248,   249, 
     3156     250,   691,   702,   182,   194,   506,    21,   590,   610,   191, 
     3157     608,   260,   260,   260,   441,     3,   194,   194,     3,   206, 
     3158     231,   684,   110,    39,   528,   533,   193,   105,   561,   562, 
     3159     563,   566,   537,   580,   191,   206,   191,   577,   679,   231, 
     3160     254,   434,   501,   685,   686,   687,    21,   191,   696,   711, 
     3161     712,   713,   206,   711,   182,   182,   511,   194,   263,   511, 
     3162     511,     3,   326,   231,   258,   275,   278,   282,   685,     5, 
     3163       3,   194,     3,   193,   501,   501,   674,   231,   414,   415, 
     3164     435,    22,   193,     3,   428,   296,   191,   297,   298,   231, 
     3165     379,   380,   545,   206,   373,   193,    21,   382,   382,   193, 
     3166       3,    22,   382,   276,   279,   206,   206,     4,   501,   260, 
     3167     501,     5,     3,   194,     4,   154,   455,   193,   501,   613, 
     3168     614,   615,   206,   505,   101,   130,   138,   305,   306,   346, 
     3169     231,   307,   308,   191,   206,   193,   193,     3,   332,   193, 
     3170     347,   336,   368,   193,     3,   388,   399,     3,   206,   191, 
     3171     410,   411,   409,   191,   521,   473,   506,   472,   518,   472, 
     3172     519,   146,   206,   206,   169,   191,   206,   193,   191,   192, 
     3173     193,   718,   193,   110,   262,   556,   546,   154,     3,   662, 
     3174     114,   639,   206,   531,   574,     3,   460,   193,   468,   502, 
     3175     503,   598,   502,   502,   502,   506,     5,   591,   260,   502, 
     3176     441,     3,   194,     5,   591,   260,   441,     3,   194,   598, 
     3177       5,   441,   439,   439,   441,   591,   434,   436,   437,   260, 
     3178     441,   436,     3,   194,   624,   206,   621,   206,     3,   478, 
     3179     231,   501,   250,    30,   659,   103,   253,   259,   260,   609, 
     3180     206,   613,   193,   206,   434,   611,   612,   615,   611,   501, 
     3181     532,    40,    41,   534,   535,   526,   501,   191,   206,   106, 
     3182     561,   567,   537,     4,   501,   581,   582,   583,   206,   578, 
     3183     206,   206,     5,     3,   194,   194,     3,   194,    31,   701, 
     3184      29,   708,   194,     3,   194,     3,   194,   194,   231,   328, 
     3185     329,   545,   194,   194,   501,   508,   396,   394,   420,   421, 
     3186     444,   194,     3,     3,   413,   431,   430,   424,   427,     3, 
     3187     194,     5,   193,   231,   255,   256,   257,   258,   275,   278, 
     3188     313,   317,   345,   383,   384,   194,   254,   318,   319,   320, 
     3189     434,   501,   520,   523,   381,   501,     4,    21,   501,   454, 
     3190       4,   501,   501,   501,   612,   614,   615,   616,   617,     3, 
     3191     206,   193,     3,   154,   193,   309,     3,   206,   206,   337, 
     3192     338,   340,   206,   348,    21,   283,   390,   191,   206,   206, 
     3193     403,    20,     3,   194,     4,     4,   520,   206,   544,   206, 
     3194     532,    11,    19,    20,    44,   109,   155,   165,   166,   184, 
     3195     185,   187,   188,   192,   214,   215,   219,   221,   224,   226, 
     3196     231,   232,   233,   501,   720,   501,   253,    27,   191,   663, 
     3197     664,   648,   191,   640,   206,    97,   145,   461,   462,   466, 
     3198     194,   469,   470,   471,   472,   502,   597,   595,   502,   603, 
     3199     206,   439,   194,   630,   626,    97,   145,   467,   479,   480, 
     3200     194,   194,   191,   660,   206,   110,     3,   206,     3,   206, 
     3201     206,   194,   194,   191,   206,   191,   206,   526,   194,   206, 
     3202     191,   206,   583,     3,   194,     4,   206,   231,   687,   686, 
     3203     681,   713,    26,   697,   698,   640,   640,    94,    73,   194, 
     3204       5,   206,     3,   194,   194,   501,   415,   206,   427,     4, 
     3205     349,   350,   351,   352,   353,   354,   355,   356,   357,   358, 
     3206     359,   360,   361,   362,   506,   507,   206,   426,   298,   206, 
     3207     511,   231,   275,     5,     3,   194,   501,   260,   501,     4, 
     3208       3,   614,     4,   310,   350,   352,   356,   306,   310,   283, 
     3209     308,   349,   157,   158,   159,   363,   349,   287,     5,   146, 
     3210     343,   344,   349,   193,   191,   411,   206,   206,   194,   501, 
     3211     194,   194,   501,   199,   443,   445,   193,   193,   194,   191, 
     3212     184,   234,   443,     5,     6,     7,     8,     9,    10,    12, 
    27793213      13,    14,    15,    16,    17,    19,    20,    21,    22,    23, 
    2780      164,   165,   254,   249,   168,   162,   271,   162,   162,   160, 
    2781      153,   270,   271,   193,   267,     3,   249,   133,   160,   214, 
    2782      214,   249,   249,   161,   305,    94,    95,   267,   306,   257, 
    2783      370,   371,    21,    23,   162,   267,   354,   355,   360,   361, 
    2784      366,   161,   252,   267,   371,   372,   267,   374,   214,    34, 
    2785       39,    40,    42,    43,    54,    55,    56,    57,    58,    59, 
    2786       60,    62,    63,    64,    67,    68,    69,    72,    73,    74, 
    2787       75,    77,   160,   188,   189,   160,   267,   194,   249,     3, 
    2788        3,   195,     5,    21,   238,   249,   163,    22,   162,   257, 
    2789      220,     3,    22,    45,    88,    89,   175,   166,   174,   180, 
    2790      180,     5,   221,     3,   205,   219,   162,   245,   205,   267, 
    2791      219,   160,   160,   219,   245,     3,   217,    25,    80,   106, 
    2792      108,   109,   110,   113,   114,   116,   117,   241,   242,   244, 
    2793      180,     3,   227,   160,   161,   162,   160,   230,   238,   161, 
    2794      162,   236,   249,   237,   245,     3,   288,   299,   307,   299, 
    2795       44,   321,   322,   324,   249,   249,   356,   161,    21,   249, 
    2796      343,   346,   347,   249,   249,   249,   249,   249,   249,   249, 
    2797        5,   360,   162,   250,   257,   268,   349,   363,   364,     3, 
    2798      351,    18,    21,    22,    23,   362,   360,   163,   163,     3, 
    2799      163,   251,   251,   249,   163,   163,   163,   249,   249,   249, 
    2800      249,   249,   249,   249,   249,   249,   249,   249,   249,   163, 
    2801      251,   163,   251,   251,   251,   252,   366,   367,     3,     3, 
    2802      126,     3,   251,   163,     3,     5,   249,   256,   249,   249, 
    2803      249,   249,   249,   249,   249,   249,   249,   249,   249,   249, 
    2804      249,   249,     5,    22,   249,   255,   249,     5,   249,     5, 
    2805      249,   356,   272,   258,   263,   263,     3,   163,   245,   192, 
    2806      163,     3,     3,   163,   162,   298,     5,     3,   373,   360, 
    2807       21,    23,   162,   249,     3,   163,   163,   163,   163,     3, 
    2808      373,     3,   163,     3,    22,     3,   163,   162,   160,   336, 
    2809      238,   202,   207,   208,   253,   249,     3,   201,   160,   206, 
    2810      202,   162,   162,   179,   305,   162,   182,   182,   249,   163, 
    2811      222,   220,     4,    21,   246,   247,   248,   249,   220,   245, 
    2812      245,   220,   218,   245,   162,     3,   131,   182,   160,   245, 
    2813      230,     5,   238,   163,     3,   239,    21,   163,   245,    27, 
    2814      160,   278,   279,   249,   285,   286,   287,   289,   292,   293, 
    2815      282,    91,   115,   308,   309,   330,    83,   311,   312,   316, 
    2816      112,   162,   326,   107,   322,   325,   172,   267,   161,   163, 
    2817        3,   249,   163,   363,   254,   365,   365,   365,     3,   363, 
    2818      360,   360,   360,   360,   360,   293,   249,   163,   163,   163, 
    2819      163,   163,   163,   163,   163,   163,   163,   163,   163,   163, 
    2820      163,   163,   163,   163,   163,   163,     3,     3,     3,   249, 
    2821      367,   249,   367,   249,   367,   163,   252,   249,   249,   249, 
    2822      249,   249,   257,     4,     4,   249,   264,   265,   266,   163, 
    2823      163,   267,   133,   160,   249,    35,    82,    88,   284,   249, 
    2824      249,   121,   371,   163,   249,   266,   168,   245,   355,   371, 
    2825      163,   267,   188,   249,   194,    22,     3,    19,    20,    21, 
    2826      167,   268,   163,   160,   368,    22,   249,   249,   305,    21, 
    2827      160,   163,   184,   185,    26,   177,   205,   249,     3,   163, 
    2828        4,   267,    21,   233,   233,   217,   134,   135,   136,   243, 
    2829      242,   245,   233,   163,   238,   239,   160,   163,     4,   122, 
    2830        3,    36,   290,   295,   172,   172,   160,   162,    84,   312, 
    2831      313,   314,   317,   172,     4,   249,   327,   328,   329,   160, 
    2832      160,   299,   337,   347,     3,   163,   254,   364,   160,   368, 
    2833      368,   368,   163,   272,     4,   249,     4,     3,   271,   245, 
    2834      163,   162,   162,   163,     3,     5,   163,   356,   163,   202, 
    2835      207,   207,   207,   207,     5,   163,   163,   163,     3,   163, 
    2836      162,   183,   247,   248,   249,   162,   234,   249,   163,   233, 
    2837        5,   122,   274,   239,   238,   160,   166,   280,   281,   160, 
    2838      279,   294,    37,    38,   296,   297,   172,   249,   160,    85, 
    2839      312,   318,   172,   299,   329,     3,   163,     4,   245,   368, 
    2840      365,   163,   163,   163,   163,   249,     4,   249,   265,     3, 
    2841      294,   249,   249,   257,   338,   249,    22,    82,   185,   163, 
    2842      184,    21,   274,   249,   249,   122,     3,   163,   160,   160, 
    2843      172,   288,   163,   160,   299,   328,   329,   245,   163,   249, 
    2844        4,   249,   163,   163,     3,     3,   202,   163,   163,   160, 
    2845      281,   160,   288,    82,   249,   249,   249,    22,   160,     3, 
    2846      249 
     3214     195,   196,   216,   194,   194,     4,   146,     3,   206,   638, 
     3215     439,   464,     5,     3,   459,     3,   194,   473,     4,   206, 
     3216     613,   206,   464,     5,     3,   476,   573,   658,   501,   260, 
     3217     612,   103,   191,   206,   206,   206,   103,   206,   582,   583, 
     3218     206,   193,   694,   707,   707,     5,     5,   506,   421,     3, 
     3219      22,   194,     3,     4,     3,     3,   352,   360,   507,    21, 
     3220       3,   429,     3,   320,   319,   501,   545,   617,   618,   194, 
     3221       3,     4,   194,     5,   146,   311,   312,   194,   194,   194, 
     3222     508,   313,   345,   432,   194,   391,   719,   222,   223,   225, 
     3223       5,   218,   501,   501,   501,   501,   501,   501,   501,   501, 
     3224     501,   501,   501,   501,   501,   501,   501,     5,    22,   217, 
     3225     501,   501,     5,   501,     5,   501,   191,   651,   664,   665, 
     3226     666,   667,   668,   191,   664,   206,   441,   463,   462,   206, 
     3227     470,   627,   463,   480,   206,   206,   206,   194,     3,   206, 
     3228     206,   191,   206,   191,   206,   700,   206,   511,   263,     3, 
     3229     501,   191,   351,   353,   507,     4,   352,   355,   357,     4, 
     3230      21,   362,   511,     5,   194,   508,   313,   345,   349,   219, 
     3231     231,   220,   227,   227,   227,   501,   501,   501,   501,   501, 
     3232     649,     3,   206,   260,   206,   194,   206,   194,   194,   506, 
     3233      22,     4,     3,   194,   506,   194,   193,     4,   228,   229, 
     3234     230,   501,   194,   194,   194,   206,   666,   206,     3,   414, 
     3235     511,     3,     4,   501,     3,     4,   443,   506,   194,   506, 
     3236     501,     4,   229,   501,     3,   501,     4,   506,   501 
    28473237}; 
    28483238 
     
    36444034  switch (yyn) 
    36454035    { 
    3646         case 7: 
    3647 /* Line 1807 of yacc.c  */ 
    3648 #line 319 "fortran.y" 
     4036        case 6: 
     4037/* Line 1807 of yacc.c  */ 
     4038#line 517 "fortran.y" 
    36494039    {yyerrok;yyclearin;} 
    36504040    break; 
    36514041 
    3652   case 18: 
    3653 /* Line 1807 of yacc.c  */ 
    3654 #line 337 "fortran.y" 
     4042  case 7: 
     4043/* Line 1807 of yacc.c  */ 
     4044#line 520 "fortran.y" 
     4045    {token_since_endofstmt = 0; increment_nbtokens = 0;} 
     4046    break; 
     4047 
     4048  case 16: 
     4049/* Line 1807 of yacc.c  */ 
     4050#line 533 "fortran.y" 
    36554051    { 
    36564052            if (inmoduledeclare == 0 ) 
     
    36624058    break; 
    36634059 
    3664   case 20: 
    3665 /* Line 1807 of yacc.c  */ 
    3666 #line 347 "fortran.y" 
     4060  case 18: 
     4061/* Line 1807 of yacc.c  */ 
     4062#line 558 "fortran.y" 
    36674063    { pos_cur = setposcur(); } 
    36684064    break; 
    36694065 
    3670   case 21: 
    3671 /* Line 1807 of yacc.c  */ 
    3672 #line 350 "fortran.y" 
    3673     { isrecursive = 0; } 
    3674     break; 
    3675  
    3676   case 22: 
    3677 /* Line 1807 of yacc.c  */ 
    3678 #line 351 "fortran.y" 
    3679     { isrecursive = 1; } 
    3680     break; 
    3681  
    3682   case 23: 
    3683 /* Line 1807 of yacc.c  */ 
    3684 #line 354 "fortran.y" 
    3685     { is_result_present = 0; } 
    3686     break; 
    3687  
    36884066  case 24: 
    36894067/* Line 1807 of yacc.c  */ 
    3690 #line 355 "fortran.y" 
    3691     { is_result_present = 1; } 
    3692     break; 
    3693  
    3694   case 25: 
    3695 /* Line 1807 of yacc.c  */ 
    3696 #line 359 "fortran.y" 
    3697     { 
    3698             insubroutinedeclare = 1; 
    3699             if ( firstpass ) 
    3700                 Add_SubroutineArgument_Var_1((yyvsp[(4) - (4)].l)); 
    3701             else 
    3702                 WriteBeginof_SubLoop(); 
    3703         } 
    3704     break; 
    3705  
    3706   case 26: 
    3707 /* Line 1807 of yacc.c  */ 
    3708 #line 367 "fortran.y" 
    3709     { 
    3710             insubroutinedeclare = 1; 
    3711             inprogramdeclare = 1; 
    3712             /* in the second step we should write the head of       */ 
    3713             /*    the subroutine sub_loop_<subroutinename>          */ 
    3714             if ( ! firstpass ) 
    3715                 WriteBeginof_SubLoop(); 
    3716         } 
     4068#line 582 "fortran.y" 
     4069    { Add_Include_1((yyvsp[(1) - (1)].na)); } 
    37174070    break; 
    37184071 
    37194072  case 27: 
    37204073/* Line 1807 of yacc.c  */ 
    3721 #line 376 "fortran.y" 
    3722     { 
    3723             insubroutinedeclare = 1; 
    3724             strcpy(DeclType, ""); 
    3725             /* we should to list of the subroutine argument the  */ 
    3726             /*    name of the function which has to be defined   */ 
    3727             if ( firstpass ) 
    3728             { 
    3729                 Add_SubroutineArgument_Var_1((yyvsp[(4) - (5)].l)); 
    3730                 if ( ! is_result_present ) 
    3731                     Add_FunctionType_Var_1((yyvsp[(3) - (5)].na)); 
    3732             } 
    3733             else 
    3734             /* in the second step we should write the head of    */ 
    3735             /*    the subroutine sub_loop_<subroutinename>       */ 
    3736                 WriteBeginof_SubLoop(); 
    3737         } 
     4074#line 1102 "fortran.y" 
     4075    { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    37384076    break; 
    37394077 
    37404078  case 28: 
    37414079/* Line 1807 of yacc.c  */ 
    3742 #line 393 "fortran.y" 
    3743     { 
    3744             GlobalDeclaration = 0; 
    3745             strcpy(curmodulename,(yyvsp[(2) - (2)].na)); 
    3746             strcpy(subroutinename,""); 
    3747             Add_NameOfModule_1((yyvsp[(2) - (2)].na)); 
    3748             if ( inmoduledeclare == 0 ) 
    3749             { 
    3750                 /* To know if there are in the module declaration    */ 
    3751                 inmoduledeclare = 1; 
    3752                 /* to know if a module has been met                  */ 
    3753                 inmodulemeet = 1; 
    3754                 /* to know if we are after the keyword contains      */ 
    3755                 aftercontainsdeclare = 0 ; 
    3756             } 
    3757         } 
     4080#line 1103 "fortran.y" 
     4081    { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
     4082    break; 
     4083 
     4084  case 29: 
     4085/* Line 1807 of yacc.c  */ 
     4086#line 1104 "fortran.y" 
     4087    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
     4088    break; 
     4089 
     4090  case 30: 
     4091/* Line 1807 of yacc.c  */ 
     4092#line 1105 "fortran.y" 
     4093    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    37584094    break; 
    37594095 
    37604096  case 31: 
    37614097/* Line 1807 of yacc.c  */ 
    3762 #line 415 "fortran.y" 
    3763     { strcpy((yyval.na), (yyvsp[(1) - (1)].na)); strcpy(subroutinename, (yyvsp[(1) - (1)].na)); } 
     4098#line 1106 "fortran.y" 
     4099    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    37644100    break; 
    37654101 
    37664102  case 32: 
    37674103/* Line 1807 of yacc.c  */ 
    3768 #line 417 "fortran.y" 
    3769     { Add_Include_1((yyvsp[(1) - (1)].na)); } 
     4104#line 1108 "fortran.y" 
     4105    { strcpy((yyval.na),"+"); } 
    37704106    break; 
    37714107 
    37724108  case 33: 
    37734109/* Line 1807 of yacc.c  */ 
    3774 #line 419 "fortran.y" 
    3775     { if ( firstpass ) (yyval.l)=NULL; } 
     4110#line 1109 "fortran.y" 
     4111    { strcpy((yyval.na),"-"); } 
    37764112    break; 
    37774113 
    37784114  case 34: 
    37794115/* Line 1807 of yacc.c  */ 
    3780 #line 420 "fortran.y" 
    3781     { if ( firstpass ) (yyval.l)=NULL; } 
     4116#line 1113 "fortran.y" 
     4117    { sprintf((yyval.na),"+%s",(yyvsp[(2) - (2)].na)); } 
    37824118    break; 
    37834119 
    37844120  case 35: 
    37854121/* Line 1807 of yacc.c  */ 
    3786 #line 421 "fortran.y" 
    3787     { if ( firstpass ) (yyval.l)=(yyvsp[(2) - (3)].l); } 
     4122#line 1114 "fortran.y" 
     4123    { sprintf((yyval.na),"-%s",(yyvsp[(2) - (2)].na)); } 
     4124    break; 
     4125 
     4126  case 36: 
     4127/* Line 1807 of yacc.c  */ 
     4128#line 1115 "fortran.y" 
     4129    { sprintf((yyval.na),"*%s",(yyvsp[(2) - (2)].na)); } 
     4130    break; 
     4131 
     4132  case 37: 
     4133/* Line 1807 of yacc.c  */ 
     4134#line 1116 "fortran.y" 
     4135    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    37884136    break; 
    37894137 
    37904138  case 38: 
    37914139/* Line 1807 of yacc.c  */ 
    3792 #line 425 "fortran.y" 
    3793     { if ( firstpass ) Add_SubroutineArgument_Var_1((yyvsp[(2) - (3)].l)); } 
     4140#line 1117 "fortran.y" 
     4141    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    37944142    break; 
    37954143 
    37964144  case 39: 
    37974145/* Line 1807 of yacc.c  */ 
    3798 #line 428 "fortran.y" 
    3799     { 
    3800             if ( firstpass == 1 ) 
    3801             { 
    3802                 strcpy(nameinttypenameback,nameinttypename); 
    3803                 strcpy(nameinttypename,""); 
    3804                 curvar = createvar((yyvsp[(1) - (1)].na),NULL); 
    3805                 strcpy(nameinttypename,nameinttypenameback); 
    3806                 curlistvar = insertvar(NULL,curvar); 
    3807                 (yyval.l) = settype("",curlistvar); 
    3808             } 
    3809         } 
     4146#line 1118 "fortran.y" 
     4147    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    38104148    break; 
    38114149 
    38124150  case 40: 
    38134151/* Line 1807 of yacc.c  */ 
    3814 #line 440 "fortran.y" 
    3815     { 
    3816             if ( firstpass == 1 ) 
    3817             { 
    3818                 strcpy(nameinttypenameback,nameinttypename); 
    3819                 strcpy(nameinttypename,""); 
    3820                 curvar = createvar((yyvsp[(3) - (3)].na),NULL); 
    3821                 strcpy(nameinttypename,nameinttypenameback); 
    3822                 (yyval.l) = insertvar((yyvsp[(1) - (3)].l),curvar); 
    3823             } 
    3824         } 
     4152#line 1119 "fortran.y" 
     4153    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    38254154    break; 
    38264155 
    38274156  case 41: 
    38284157/* Line 1807 of yacc.c  */ 
    3829 #line 451 "fortran.y" 
    3830     { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
     4158#line 1120 "fortran.y" 
     4159    { sprintf((yyval.na)," > %s",(yyvsp[(2) - (2)].na)); } 
    38314160    break; 
    38324161 
    38334162  case 42: 
    38344163/* Line 1807 of yacc.c  */ 
    3835 #line 452 "fortran.y" 
    3836     { strcpy((yyval.na),"*"); } 
     4164#line 1121 "fortran.y" 
     4165    { sprintf((yyval.na)," < %s",(yyvsp[(2) - (2)].na)); } 
     4166    break; 
     4167 
     4168  case 43: 
     4169/* Line 1807 of yacc.c  */ 
     4170#line 1122 "fortran.y" 
     4171    { sprintf((yyval.na)," >= %s",(yyvsp[(3) - (3)].na)); } 
    38374172    break; 
    38384173 
    38394174  case 44: 
    38404175/* Line 1807 of yacc.c  */ 
    3841 #line 455 "fortran.y" 
    3842     { inside_type_declare = 1; } 
     4176#line 1123 "fortran.y" 
     4177    { sprintf((yyval.na)," <= %s",(yyvsp[(3) - (3)].na)); } 
    38434178    break; 
    38444179 
    38454180  case 45: 
    38464181/* Line 1807 of yacc.c  */ 
    3847 #line 456 "fortran.y" 
    3848     { inside_type_declare = 0; } 
     4182#line 1124 "fortran.y" 
     4183    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
     4184    break; 
     4185 
     4186  case 46: 
     4187/* Line 1807 of yacc.c  */ 
     4188#line 1125 "fortran.y" 
     4189    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    38494190    break; 
    38504191 
    38514192  case 47: 
    38524193/* Line 1807 of yacc.c  */ 
    3853 #line 459 "fortran.y" 
    3854     { 
    3855             if ( ! inside_type_declare ) 
    3856             { 
    3857                 if ( firstpass ) 
    3858                 { 
    3859                     if ( insubroutinedeclare )  Add_Parameter_Var_1((yyvsp[(3) - (4)].l)); 
    3860                     else                        Add_GlobalParameter_Var_1((yyvsp[(3) - (4)].l)); 
    3861                 } 
    3862                 else 
    3863                 { 
    3864                     pos_end = setposcur(); 
    3865                     RemoveWordSET_0(fortran_out, pos_cur_decl, pos_end-pos_cur_decl); 
    3866                 } 
    3867             } 
    3868             VariableIsParameter =  0 ; 
    3869         } 
     4194#line 1126 "fortran.y" 
     4195    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    38704196    break; 
    38714197 
    38724198  case 48: 
    38734199/* Line 1807 of yacc.c  */ 
    3874 #line 476 "fortran.y" 
    3875     { 
    3876             if ( ! inside_type_declare ) 
    3877             { 
    3878                 if ( firstpass ) 
    3879                 { 
    3880                     if ( insubroutinedeclare )  Add_Parameter_Var_1((yyvsp[(2) - (2)].l)); 
    3881                     else                        Add_GlobalParameter_Var_1((yyvsp[(2) - (2)].l)); 
    3882                 } 
    3883                 else 
    3884                 { 
    3885                     pos_end = setposcur(); 
    3886                     RemoveWordSET_0(fortran_out,pos_cur_decl,pos_end-pos_cur_decl); 
    3887                 } 
    3888             } 
    3889             VariableIsParameter =  0 ; 
    3890         } 
     4200#line 1127 "fortran.y" 
     4201    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
     4202    break; 
     4203 
     4204  case 49: 
     4205/* Line 1807 of yacc.c  */ 
     4206#line 1128 "fortran.y" 
     4207    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    38914208    break; 
    38924209 
    38934210  case 50: 
    38944211/* Line 1807 of yacc.c  */ 
    3895 #line 494 "fortran.y" 
    3896     { 
    3897             pos_end = setposcur(); 
    3898             RemoveWordSET_0(fortran_out,pos_cursave,pos_end-pos_cursave); 
    3899         } 
     4212#line 1129 "fortran.y" 
     4213    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
     4214    break; 
     4215 
     4216  case 51: 
     4217/* Line 1807 of yacc.c  */ 
     4218#line 1130 "fortran.y" 
     4219    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    39004220    break; 
    39014221 
    39024222  case 52: 
    39034223/* Line 1807 of yacc.c  */ 
    3904 #line 500 "fortran.y" 
    3905     { 
    3906             /* if the variable is a parameter we can suppose that is   */ 
    3907             /*    value is the same on each grid. It is not useless to */ 
    3908             /*    create a copy of it on each grid                     */ 
    3909             if ( ! inside_type_declare ) 
    3910             { 
    3911                 if ( firstpass ) 
    3912                 { 
    3913                     Add_Globliste_1((yyvsp[(1) - (1)].l)); 
    3914                     /* if variableparamlists has been declared in a subroutine   */ 
    3915                     if ( insubroutinedeclare )     Add_Dimension_Var_1((yyvsp[(1) - (1)].l)); 
    3916                 } 
    3917                 else 
    3918                 { 
    3919                     pos_end = setposcur(); 
    3920                     RemoveWordSET_0(fortran_out,pos_curdimension,pos_end-pos_curdimension); 
    3921                 } 
    3922             } 
    3923             PublicDeclare = 0; 
    3924             PrivateDeclare = 0; 
    3925             ExternalDeclare = 0; 
    3926             strcpy(NamePrecision,""); 
    3927             c_star = 0; 
    3928             InitialValueGiven = 0 ; 
    3929             strcpy(IntentSpec,""); 
    3930             VariableIsParameter =  0 ; 
    3931             Allocatabledeclare = 0 ; 
    3932             Targetdeclare = 0 ; 
    3933             SaveDeclare = 0; 
    3934             pointerdeclare = 0; 
    3935             optionaldeclare = 0 ; 
    3936             dimsgiven=0; 
    3937             c_selectorgiven=0; 
    3938             strcpy(nameinttypename,""); 
    3939             strcpy(c_selectorname,""); 
    3940         } 
     4224#line 1131 "fortran.y" 
     4225    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    39414226    break; 
    39424227 
    39434228  case 53: 
    39444229/* Line 1807 of yacc.c  */ 
    3945 #line 537 "fortran.y" 
    3946     { 
    3947             if (firstpass == 0) 
    3948             { 
    3949                 if ((yyvsp[(1) - (1)].lnn)) 
    3950                 { 
    3951                     removeglobfromlist(&((yyvsp[(1) - (1)].lnn))); 
    3952                     pos_end = setposcur(); 
    3953                     RemoveWordSET_0(fortran_out,pos_cur,pos_end-pos_cur); 
    3954                     writelistpublic((yyvsp[(1) - (1)].lnn)); 
    3955                 } 
    3956             } 
    3957         } 
     4230#line 1132 "fortran.y" 
     4231    { sprintf((yyval.na),"%s",(yyvsp[(2) - (2)].na)); } 
     4232    break; 
     4233 
     4234  case 54: 
     4235/* Line 1807 of yacc.c  */ 
     4236#line 1133 "fortran.y" 
     4237    { sprintf((yyval.na),"%s",(yyvsp[(2) - (2)].na)); } 
     4238    break; 
     4239 
     4240  case 55: 
     4241/* Line 1807 of yacc.c  */ 
     4242#line 1135 "fortran.y" 
     4243    { strcpy((yyval.na),""); } 
     4244    break; 
     4245 
     4246  case 56: 
     4247/* Line 1807 of yacc.c  */ 
     4248#line 1136 "fortran.y" 
     4249    { sprintf((yyval.na),"/%s",(yyvsp[(1) - (1)].na)); } 
     4250    break; 
     4251 
     4252  case 57: 
     4253/* Line 1807 of yacc.c  */ 
     4254#line 1137 "fortran.y" 
     4255    { sprintf((yyval.na),"/= %s",(yyvsp[(2) - (2)].na));} 
     4256    break; 
     4257 
     4258  case 58: 
     4259/* Line 1807 of yacc.c  */ 
     4260#line 1138 "fortran.y" 
     4261    { sprintf((yyval.na),"//%s",(yyvsp[(2) - (2)].na)); } 
     4262    break; 
     4263 
     4264  case 59: 
     4265/* Line 1807 of yacc.c  */ 
     4266#line 1141 "fortran.y" 
     4267    { sprintf((yyval.na),"==%s",(yyvsp[(2) - (2)].na)); } 
     4268    break; 
     4269 
     4270  case 60: 
     4271/* Line 1807 of yacc.c  */ 
     4272#line 1142 "fortran.y" 
     4273    { sprintf((yyval.na),"= %s",(yyvsp[(1) - (1)].na)); } 
     4274    break; 
     4275 
     4276  case 61: 
     4277/* Line 1807 of yacc.c  */ 
     4278#line 1145 "fortran.y" 
     4279    { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    39584280    break; 
    39594281 
    39604282  case 62: 
    39614283/* Line 1807 of yacc.c  */ 
    3962 #line 558 "fortran.y" 
    3963     { 
    3964             /* we should remove the data declaration                */ 
    3965             pos_end = setposcur(); 
    3966             RemoveWordSET_0(fortran_out,pos_curdata,pos_end-pos_curdata); 
    3967  
    3968             if ( aftercontainsdeclare == 1  && firstpass == 0 ) 
    3969             { 
    3970                 ReWriteDataStatement_0(fortran_out); 
    3971                 pos_end = setposcur(); 
    3972             } 
    3973         } 
     4284#line 1146 "fortran.y" 
     4285    { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
     4286    break; 
     4287 
     4288  case 63: 
     4289/* Line 1807 of yacc.c  */ 
     4290#line 1147 "fortran.y" 
     4291    { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    39744292    break; 
    39754293 
    39764294  case 64: 
    39774295/* Line 1807 of yacc.c  */ 
    3978 #line 572 "fortran.y" 
    3979     { 
    3980             PublicDeclare = 0 ; 
    3981             PrivateDeclare = 0 ; 
    3982         } 
    3983     break; 
    3984  
    3985   case 102: 
    3986 /* Line 1807 of yacc.c  */ 
    3987 #line 630 "fortran.y" 
    3988     { 
    3989             /* if the variable is a parameter we can suppose that is*/ 
    3990             /*    value is the same on each grid. It is not useless */ 
    3991             /*    to create a copy of it on each grid               */ 
    3992             if ( ! inside_type_declare ) 
    3993             { 
    3994                 pos_end = setposcur(); 
    3995                 RemoveWordSET_0(fortran_out,pos_cur_decl,pos_end-pos_cur_decl); 
    3996                 ReWriteDeclarationAndAddTosubroutine_01((yyvsp[(1) - (2)].l)); 
    3997                 pos_cur_decl = setposcur(); 
    3998                 if ( firstpass == 0 && GlobalDeclaration == 0 
    3999                                     && insubroutinedeclare == 0 ) 
    4000                 { 
    4001                     fprintf(fortran_out,"\n#include \"Module_Declar_%s.h\"\n", curmodulename); 
    4002                     sprintf(ligne, "Module_Declar_%s.h", curmodulename); 
    4003                     module_declar = open_for_write(ligne); 
    4004                     GlobalDeclaration = 1 ; 
    4005                     pos_cur_decl = setposcur(); 
    4006                 } 
    4007                 (yyval.l) = (yyvsp[(1) - (2)].l); 
    4008  
    4009                 if ( firstpass ) 
    4010                 { 
    4011                     Add_Globliste_1((yyvsp[(1) - (2)].l)); 
    4012                     if ( insubroutinedeclare ) 
    4013                     { 
    4014                         if ( pointerdeclare ) Add_Pointer_Var_From_List_1((yyvsp[(1) - (2)].l)); 
    4015                         Add_Parameter_Var_1((yyvsp[(1) - (2)].l)); 
    4016                     } 
    4017                     else 
    4018                         Add_GlobalParameter_Var_1((yyvsp[(1) - (2)].l)); 
    4019  
    4020                     /* If there's a SAVE declaration in module's subroutines we should    */ 
    4021                     /*    remove it from the subroutines declaration and add it in the    */ 
    4022                     /*    global declarations                                             */ 
    4023                     if ( aftercontainsdeclare && SaveDeclare ) 
    4024                     { 
    4025                         if ( inmodulemeet ) Add_SubroutineDeclarationSave_Var_1((yyvsp[(1) - (2)].l)); 
    4026                         else                Add_Save_Var_dcl_1((yyvsp[(1) - (2)].l)); 
    4027                     } 
    4028                 } 
    4029             } 
    4030             else 
    4031             { 
    4032                 (yyval.l) = (listvar *) NULL; 
    4033             } 
    4034             PublicDeclare = 0; 
    4035             PrivateDeclare = 0; 
    4036             ExternalDeclare = 0; 
    4037             strcpy(NamePrecision,""); 
    4038             c_star = 0; 
    4039             InitialValueGiven = 0 ; 
    4040             strcpy(IntentSpec,""); 
    4041             VariableIsParameter =  0 ; 
    4042             Allocatabledeclare = 0 ; 
    4043             Targetdeclare = 0 ; 
    4044             SaveDeclare = 0; 
    4045             pointerdeclare = 0; 
    4046             optionaldeclare = 0 ; 
    4047             dimsgiven=0; 
    4048             c_selectorgiven=0; 
    4049             strcpy(nameinttypename,""); 
    4050             strcpy(c_selectorname,""); 
    4051             GlobalDeclarationType = 0; 
    4052         } 
    4053     break; 
    4054  
    4055   case 103: 
    4056 /* Line 1807 of yacc.c  */ 
    4057 #line 696 "fortran.y" 
    4058     { 
    4059             insubroutinedeclare = 1; 
    4060  
    4061             if ( firstpass ) 
    4062             { 
    4063                 Add_SubroutineArgument_Var_1((yyvsp[(3) - (3)].l)); 
    4064                 Add_FunctionType_Var_1((yyvsp[(2) - (3)].na)); 
    4065             } 
    4066             else 
    4067                 WriteBeginof_SubLoop(); 
    4068  
    4069             strcpy(nameinttypename,""); 
    4070         } 
    4071     break; 
    4072  
    4073   case 104: 
    4074 /* Line 1807 of yacc.c  */ 
    4075 #line 710 "fortran.y" 
    4076     { functiondeclarationisdone = 1; } 
    4077     break; 
    4078  
    4079   case 105: 
    4080 /* Line 1807 of yacc.c  */ 
    4081 #line 712 "fortran.y" 
    4082     { VariableIsParameter = 1; pos_curparameter = setposcur()-9; } 
    4083     break; 
    4084  
    4085   case 109: 
    4086 /* Line 1807 of yacc.c  */ 
    4087 #line 724 "fortran.y" 
    4088     { 
    4089             createstringfromlistname(ligne,(yyvsp[(3) - (4)].lnn)); 
    4090             if (firstpass == 1) Add_Data_Var_1(&List_Data_Var,(yyvsp[(1) - (4)].na),ligne); 
    4091             else                Add_Data_Var_1(&List_Data_Var_Cur,(yyvsp[(1) - (4)].na),ligne); 
    4092         } 
    4093     break; 
    4094  
    4095   case 110: 
    4096 /* Line 1807 of yacc.c  */ 
    4097 #line 730 "fortran.y" 
    4098     { 
    4099             if (firstpass == 1)  Add_Data_Var_Names_01(&List_Data_Var,(yyvsp[(1) - (4)].lnn),(yyvsp[(3) - (4)].lnn)); 
    4100             else                 Add_Data_Var_Names_01(&List_Data_Var_Cur,(yyvsp[(1) - (4)].lnn),(yyvsp[(3) - (4)].lnn)); 
    4101         } 
    4102     break; 
    4103  
    4104   case 111: 
    4105 /* Line 1807 of yacc.c  */ 
    4106 #line 735 "fortran.y" 
    4107     { 
    4108             createstringfromlistname(ligne,(yyvsp[(7) - (8)].lnn)); 
    4109             printf("###################################################################################################################\n"); 
    4110             printf("## CONV Error : data_implied_do statements (R537) are not yet supported. Please complain to the proper authorities.\n"); 
    4111             printf("l.%4d -- data_stmt_set : ( lhs , dospec ) /data_stmt_value_list/ -- lhs=|%s| dospec=|%s| data_stmt_value_list=|%s|\n", 
    4112                 line_num_input,(yyvsp[(2) - (8)].na),(yyvsp[(4) - (8)].na),ligne); 
    4113             printf("## But, are you SURE you NEED a DATA construct ?\n"); 
    4114             printf("###################################################################################################################\n"); 
    4115             exit(1); 
    4116         } 
    4117     break; 
    4118  
    4119   case 112: 
    4120 /* Line 1807 of yacc.c  */ 
    4121 #line 748 "fortran.y" 
    4122     { (yyval.lnn) = Insertname(NULL,(yyvsp[(1) - (1)].na),0); } 
    4123     break; 
    4124  
    4125   case 113: 
    4126 /* Line 1807 of yacc.c  */ 
    4127 #line 749 "fortran.y" 
    4128     { (yyval.lnn) = Insertname((yyvsp[(3) - (3)].lnn),(yyvsp[(1) - (3)].na),1);   } 
    4129     break; 
    4130  
    4131   case 118: 
    4132 /* Line 1807 of yacc.c  */ 
    4133 #line 758 "fortran.y" 
    4134     { pos_cursave = setposcur()-4; } 
    4135     break; 
    4136  
    4137   case 120: 
    4138 /* Line 1807 of yacc.c  */ 
    4139 #line 761 "fortran.y" 
    4140     { if ( ! inside_type_declare ) Add_Save_Var_1((yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].d)); } 
    4141     break; 
    4142  
    4143   case 121: 
    4144 /* Line 1807 of yacc.c  */ 
    4145 #line 764 "fortran.y" 
    4146     { (yyval.lnn) = Insertname(NULL,(yyvsp[(1) - (1)].na),0); } 
    4147     break; 
    4148  
    4149   case 122: 
    4150 /* Line 1807 of yacc.c  */ 
    4151 #line 765 "fortran.y" 
    4152     { printf("l.%4d -- INSTRUCTION NON TRAITEE : INITIALISATION DE DATA AVEC EXPRESSION\n",line_num_input); exit(0); } 
    4153     break; 
    4154  
    4155   case 123: 
    4156 /* Line 1807 of yacc.c  */ 
    4157 #line 766 "fortran.y" 
    4158     { (yyval.lnn) = concat_listname((yyvsp[(1) - (3)].lnn),(yyvsp[(3) - (3)].lnn)); } 
    4159     break; 
    4160  
    4161   case 124: 
    4162 /* Line 1807 of yacc.c  */ 
    4163 #line 769 "fortran.y" 
    4164     { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na));  } 
    4165     break; 
    4166  
    4167   case 125: 
    4168 /* Line 1807 of yacc.c  */ 
    4169 #line 770 "fortran.y" 
    4170     { sprintf((yyval.na),"%s+%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na)); } 
    4171     break; 
    4172  
    4173   case 126: 
    4174 /* Line 1807 of yacc.c  */ 
    4175 #line 771 "fortran.y" 
    4176     { sprintf((yyval.na),"%s-%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na)); } 
    4177     break; 
    4178  
    4179   case 127: 
    4180 /* Line 1807 of yacc.c  */ 
    4181 #line 772 "fortran.y" 
    4182     { sprintf((yyval.na),"%s*%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na)); } 
    4183     break; 
    4184  
    4185   case 128: 
    4186 /* Line 1807 of yacc.c  */ 
    4187 #line 773 "fortran.y" 
    4188     { sprintf((yyval.na),"%s/%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na)); } 
    4189     break; 
    4190  
    4191   case 129: 
    4192 /* Line 1807 of yacc.c  */ 
    4193 #line 775 "fortran.y" 
    4194     { strcpy((yyval.na),""); } 
    4195     break; 
    4196  
    4197   case 130: 
    4198 /* Line 1807 of yacc.c  */ 
    4199 #line 776 "fortran.y" 
    4200     { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    4201     break; 
    4202  
    4203   case 135: 
    4204 /* Line 1807 of yacc.c  */ 
    4205 #line 786 "fortran.y" 
    4206     { 
    4207             positioninblock = 0; 
    4208             pos_curdimension = setposcur()-9; 
    4209         } 
    4210     break; 
    4211  
    4212   case 136: 
    4213 /* Line 1807 of yacc.c  */ 
    4214 #line 793 "fortran.y" 
    4215     { 
    4216             printf("l.%4d -- dimension : before_dimension opt_comma TOK_NAME = |%s| -- MHCHECK\n",line_num_input,(yyvsp[(3) - (5)].na)); 
    4217             if ( inside_type_declare ) break; 
    4218             curvar = createvar((yyvsp[(3) - (5)].na),(yyvsp[(4) - (5)].d)); 
    4219             CreateAndFillin_Curvar("", curvar); 
    4220             curlistvar=insertvar(NULL, curvar); 
    4221             (yyval.l) = settype("",curlistvar); 
    4222             strcpy(vallengspec,""); 
    4223         } 
    4224     break; 
    4225  
    4226   case 137: 
    4227 /* Line 1807 of yacc.c  */ 
    4228 #line 803 "fortran.y" 
    4229     { 
    4230             printf("l.%4d -- dimension : dimension ',' TOK_NAME dims lengspec = |%s| -- MHCHECK\n",line_num_input,(yyvsp[(3) - (5)].na)); 
    4231             if ( inside_type_declare ) break; 
    4232             curvar = createvar((yyvsp[(3) - (5)].na),(yyvsp[(4) - (5)].d)); 
    4233             CreateAndFillin_Curvar("", curvar); 
    4234             curlistvar = insertvar((yyvsp[(1) - (5)].l), curvar); 
    4235             (yyval.l) = curlistvar; 
    4236             strcpy(vallengspec,""); 
    4237         } 
    4238     break; 
    4239  
    4240   case 140: 
    4241 /* Line 1807 of yacc.c  */ 
    4242 #line 818 "fortran.y" 
    4243     { (yyval.lnn) = (listname *) NULL; } 
    4244     break; 
    4245  
    4246   case 141: 
    4247 /* Line 1807 of yacc.c  */ 
    4248 #line 819 "fortran.y" 
    4249     { (yyval.lnn) = (yyvsp[(3) - (3)].lnn); } 
    4250     break; 
    4251  
    4252   case 142: 
    4253 /* Line 1807 of yacc.c  */ 
    4254 #line 822 "fortran.y" 
    4255     { (yyval.lnn) = Insertname(NULL,(yyvsp[(1) - (1)].na),0); } 
    4256     break; 
    4257  
    4258   case 143: 
    4259 /* Line 1807 of yacc.c  */ 
    4260 #line 823 "fortran.y" 
    4261     { (yyval.lnn) = Insertname(NULL,(yyvsp[(1) - (1)].na),0); } 
    4262     break; 
    4263  
    4264   case 144: 
    4265 /* Line 1807 of yacc.c  */ 
    4266 #line 824 "fortran.y" 
    4267     { (yyval.lnn) = Insertname((yyvsp[(1) - (3)].lnn),(yyvsp[(3) - (3)].na),0);   } 
    4268     break; 
    4269  
    4270   case 145: 
    4271 /* Line 1807 of yacc.c  */ 
    4272 #line 825 "fortran.y" 
    4273     { (yyval.lnn) = Insertname((yyvsp[(1) - (3)].lnn),(yyvsp[(3) - (3)].na),0);   } 
    4274     break; 
    4275  
    4276   case 146: 
    4277 /* Line 1807 of yacc.c  */ 
    4278 #line 829 "fortran.y" 
    4279     { 
    4280             if ( inside_type_declare ) break; 
    4281             pos_end = setposcur(); 
    4282             RemoveWordSET_0(fortran_out,pos_curcommon,pos_end-pos_curcommon); 
    4283         } 
    4284     break; 
    4285  
    4286   case 147: 
    4287 /* Line 1807 of yacc.c  */ 
    4288 #line 835 "fortran.y" 
    4289     { 
    4290             if ( inside_type_declare ) break; 
    4291             sprintf(charusemodule,"%s",(yyvsp[(2) - (3)].na)); 
    4292             Add_NameOfCommon_1((yyvsp[(2) - (3)].na),subroutinename); 
    4293             pos_end = setposcur(); 
    4294             RemoveWordSET_0(fortran_out,pos_curcommon,pos_end-pos_curcommon); 
    4295         } 
    4296     break; 
    4297  
    4298   case 148: 
    4299 /* Line 1807 of yacc.c  */ 
    4300 #line 843 "fortran.y" 
    4301     { 
    4302             if ( inside_type_declare ) break; 
    4303             sprintf(charusemodule,"%s",(yyvsp[(3) - (5)].na)); 
    4304             Add_NameOfCommon_1((yyvsp[(3) - (5)].na),subroutinename); 
    4305             pos_end = setposcur(); 
    4306             RemoveWordSET_0(fortran_out,pos_curcommon,pos_end-pos_curcommon); 
    4307         } 
    4308     break; 
    4309  
    4310   case 149: 
    4311 /* Line 1807 of yacc.c  */ 
    4312 #line 852 "fortran.y" 
    4313     { positioninblock = 0; pos_curcommon = setposcur()-6;   } 
    4314     break; 
    4315  
    4316   case 150: 
    4317 /* Line 1807 of yacc.c  */ 
    4318 #line 853 "fortran.y" 
    4319     { positioninblock = 0; pos_curcommon = setposcur()-6-7; } 
    4320     break; 
    4321  
    4322   case 151: 
    4323 /* Line 1807 of yacc.c  */ 
    4324 #line 856 "fortran.y" 
    4325     { if ( ! inside_type_declare ) Add_Common_var_1(); } 
    4326     break; 
    4327  
    4328   case 152: 
    4329 /* Line 1807 of yacc.c  */ 
    4330 #line 857 "fortran.y" 
    4331     { if ( ! inside_type_declare ) Add_Common_var_1(); } 
    4332     break; 
    4333  
    4334   case 153: 
    4335 /* Line 1807 of yacc.c  */ 
    4336 #line 861 "fortran.y" 
    4337     { 
    4338             positioninblock = positioninblock + 1 ; 
    4339             strcpy(commonvar,(yyvsp[(1) - (2)].na)); 
    4340             commondim = (yyvsp[(2) - (2)].d); 
    4341         } 
    4342     break; 
    4343  
    4344   case 154: 
    4345 /* Line 1807 of yacc.c  */ 
    4346 #line 869 "fortran.y" 
    4347     { 
    4348             strcpy((yyval.na),""); 
    4349             positioninblock=0; 
    4350             strcpy(commonblockname,""); 
    4351         } 
    4352     break; 
    4353  
    4354   case 155: 
    4355 /* Line 1807 of yacc.c  */ 
    4356 #line 875 "fortran.y" 
    4357     { 
    4358             strcpy((yyval.na),(yyvsp[(2) - (3)].na)); 
    4359             positioninblock=0; 
    4360             strcpy(commonblockname,(yyvsp[(2) - (3)].na)); 
    4361         } 
    4362     break; 
    4363  
    4364   case 158: 
    4365 /* Line 1807 of yacc.c  */ 
    4366 #line 885 "fortran.y" 
    4367     { (yyval.l)=insertvar(NULL,(yyvsp[(1) - (1)].v)); } 
    4368     break; 
    4369  
    4370   case 159: 
    4371 /* Line 1807 of yacc.c  */ 
    4372 #line 886 "fortran.y" 
    4373     { (yyval.l)=insertvar((yyvsp[(1) - (3)].l),(yyvsp[(3) - (3)].v));   } 
    4374     break; 
    4375  
    4376   case 160: 
    4377 /* Line 1807 of yacc.c  */ 
    4378 #line 890 "fortran.y" 
    4379     { 
    4380             if ( inside_type_declare ) break; 
    4381             curvar=(variable *) calloc(1,sizeof(variable)); 
    4382             Init_Variable(curvar); 
    4383             curvar->v_VariableIsParameter = 1; 
    4384             strcpy(curvar->v_nomvar,(yyvsp[(1) - (3)].na)); 
    4385             strcpy(curvar->v_subroutinename,subroutinename); 
    4386             strcpy(curvar->v_modulename,curmodulename); 
    4387             strcpy(curvar->v_initialvalue,(yyvsp[(3) - (3)].na)); 
    4388             strcpy(curvar->v_commoninfile,cur_filename); 
    4389             Save_Length((yyvsp[(3) - (3)].na),14); 
    4390             (yyval.v) = curvar; 
    4391         } 
    4392     break; 
    4393  
    4394   case 164: 
    4395 /* Line 1807 of yacc.c  */ 
    4396 #line 913 "fortran.y" 
    4397     { 
    4398             if ( insubroutinedeclare == 1 ) 
    4399             { 
    4400                 Add_ImplicitNoneSubroutine_1(); 
    4401                 pos_end = setposcur(); 
    4402                 RemoveWordSET_0(fortran_out,pos_end-13,13); 
    4403             } 
    4404         } 
    4405     break; 
    4406  
    4407   case 166: 
    4408 /* Line 1807 of yacc.c  */ 
    4409 #line 924 "fortran.y" 
    4410     { 
    4411             if ( ! inside_type_declare ) 
    4412             { 
    4413                 if (dimsgiven == 1) curvar = createvar((yyvsp[(2) - (5)].na),curdim); 
    4414                 else                curvar = createvar((yyvsp[(2) - (5)].na),(yyvsp[(3) - (5)].d)); 
    4415                 CreateAndFillin_Curvar(DeclType, curvar); 
    4416                 curlistvar = insertvar(NULL, curvar); 
    4417                 if (!strcasecmp(DeclType,"character")) 
    4418                 { 
    4419                     if (c_selectorgiven == 1) 
    4420                     { 
    4421                         strcpy(c_selectordim.first,"1"); 
    4422                         strcpy(c_selectordim.last,c_selectorname); 
    4423                         Save_Length(c_selectorname,1); 
    4424                         change_dim_char(insertdim(NULL,c_selectordim),curlistvar); 
    4425                     } 
    4426                 } 
    4427                 (yyval.l)=settype(DeclType,curlistvar); 
    4428             } 
    4429             strcpy(vallengspec,""); 
    4430         } 
    4431     break; 
    4432  
    4433   case 167: 
    4434 /* Line 1807 of yacc.c  */ 
    4435 #line 946 "fortran.y" 
    4436     { 
    4437             if ( ! inside_type_declare ) 
    4438             { 
    4439                 if (dimsgiven == 1) curvar = createvar((yyvsp[(3) - (6)].na), curdim); 
    4440                 else                curvar = createvar((yyvsp[(3) - (6)].na), (yyvsp[(4) - (6)].d)); 
    4441                 CreateAndFillin_Curvar((yyvsp[(1) - (6)].l)->var->v_typevar,curvar); 
    4442                 strcpy(curvar->v_typevar, (yyvsp[(1) - (6)].l)->var->v_typevar); 
    4443                 curvar->v_catvar = get_cat_var(curvar); 
    4444                 curlistvar = insertvar((yyvsp[(1) - (6)].l), curvar); 
    4445                 if (!strcasecmp(DeclType,"character")) 
    4446                 { 
    4447                     if (c_selectorgiven == 1) 
    4448                     { 
    4449                         strcpy(c_selectordim.first,"1"); 
    4450                         strcpy(c_selectordim.last,c_selectorname); 
    4451                         Save_Length(c_selectorname,1); 
    4452                         change_dim_char(insertdim(NULL,c_selectordim),curlistvar); 
    4453                     } 
    4454                 } 
    4455                 (yyval.l)=curlistvar; 
    4456             } 
    4457             strcpy(vallengspec,""); 
    4458         } 
    4459     break; 
    4460  
    4461   case 168: 
    4462 /* Line 1807 of yacc.c  */ 
    4463 #line 970 "fortran.y" 
    4464     { dimsgiven = 0; } 
    4465     break; 
    4466  
    4467   case 169: 
    4468 /* Line 1807 of yacc.c  */ 
    4469 #line 972 "fortran.y" 
    4470     { strcpy(DeclType,(yyvsp[(1) - (2)].na));  } 
    4471     break; 
    4472  
    4473   case 170: 
    4474 /* Line 1807 of yacc.c  */ 
    4475 #line 973 "fortran.y" 
    4476     { strcpy(DeclType,"character");  } 
    4477     break; 
    4478  
    4479   case 171: 
    4480 /* Line 1807 of yacc.c  */ 
    4481 #line 974 "fortran.y" 
    4482     { strcpy(DeclType,(yyvsp[(1) - (3)].na)); strcpy(nameinttypename,(yyvsp[(3) - (3)].na));  } 
    4483     break; 
    4484  
    4485   case 172: 
    4486 /* Line 1807 of yacc.c  */ 
    4487 #line 975 "fortran.y" 
    4488     { strcpy(DeclType,"type"); GlobalDeclarationType = 1;  } 
    4489     break; 
    4490  
    4491   case 174: 
    4492 /* Line 1807 of yacc.c  */ 
    4493 #line 978 "fortran.y" 
    4494     { c_selectorgiven = 1; strcpy(c_selectorname,(yyvsp[(2) - (2)].na)); } 
    4495     break; 
    4496  
    4497   case 175: 
    4498 /* Line 1807 of yacc.c  */ 
    4499 #line 979 "fortran.y" 
    4500     { c_star = 1;} 
    4501     break; 
    4502  
    4503   case 180: 
    4504 /* Line 1807 of yacc.c  */ 
    4505 #line 987 "fortran.y" 
    4506     { pos_cur_decl = setposcur()-9; } 
    4507     break; 
    4508  
    4509   case 181: 
    4510 /* Line 1807 of yacc.c  */ 
    4511 #line 990 "fortran.y" 
    4512     { strcpy((yyval.na),"integer"); pos_cur_decl = setposcur()-7; } 
    4513     break; 
    4514  
    4515   case 182: 
    4516 /* Line 1807 of yacc.c  */ 
    4517 #line 991 "fortran.y" 
    4518     { strcpy((yyval.na),"logical"); pos_cur_decl = setposcur()-7; } 
    4519     break; 
    4520  
    4521   case 183: 
    4522 /* Line 1807 of yacc.c  */ 
    4523 #line 992 "fortran.y" 
    4524     { strcpy((yyval.na),"real");    pos_cur_decl = setposcur()-4; } 
    4525     break; 
    4526  
    4527   case 184: 
    4528 /* Line 1807 of yacc.c  */ 
    4529 #line 993 "fortran.y" 
    4530     { strcpy((yyval.na),"complex"); pos_cur_decl = setposcur()-7; } 
    4531     break; 
    4532  
    4533   case 185: 
    4534 /* Line 1807 of yacc.c  */ 
    4535 #line 994 "fortran.y" 
    4536     { strcpy((yyval.na),"double complex"); pos_cur_decl = setposcur()-14; } 
    4537     break; 
    4538  
    4539   case 186: 
    4540 /* Line 1807 of yacc.c  */ 
    4541 #line 995 "fortran.y" 
    4542     { pos_cur_decl = setposcur()-16; strcpy((yyval.na),"real"); strcpy(nameinttypename,"8"); } 
    4543     break; 
    4544  
    4545   case 188: 
    4546 /* Line 1807 of yacc.c  */ 
    4547 #line 998 "fortran.y" 
    4548     {strcpy(vallengspec,(yyvsp[(2) - (2)].na));} 
    4549     break; 
    4550  
    4551   case 189: 
    4552 /* Line 1807 of yacc.c  */ 
    4553 #line 1001 "fortran.y" 
    4554     { sprintf((yyval.na),"*%s",(yyvsp[(1) - (1)].na)); } 
    4555     break; 
    4556  
    4557   case 190: 
    4558 /* Line 1807 of yacc.c  */ 
    4559 #line 1002 "fortran.y" 
    4560     { strcpy((yyval.na),"*(*)"); } 
    4561     break; 
    4562  
    4563   case 197: 
    4564 /* Line 1807 of yacc.c  */ 
    4565 #line 1014 "fortran.y" 
    4566     { 
    4567             if ( strstr((yyvsp[(3) - (3)].na),"0.d0") ) 
    4568             { 
    4569                 strcpy(nameinttypename,"8"); 
    4570                 strcpy(NamePrecision,""); 
    4571             } 
    4572             else 
    4573                 sprintf(NamePrecision,"%s = %s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na)); 
    4574         } 
    4575     break; 
    4576  
    4577   case 198: 
    4578 /* Line 1807 of yacc.c  */ 
    4579 #line 1023 "fortran.y" 
    4580     { strcpy(NamePrecision,(yyvsp[(1) - (1)].na)); } 
    4581     break; 
    4582  
    4583   case 199: 
    4584 /* Line 1807 of yacc.c  */ 
    4585 #line 1024 "fortran.y" 
    4586     { strcpy(NamePrecision,(yyvsp[(1) - (1)].na)); } 
    4587     break; 
    4588  
    4589   case 200: 
    4590 /* Line 1807 of yacc.c  */ 
    4591 #line 1025 "fortran.y" 
    4592     { strcpy(NamePrecision,(yyvsp[(1) - (1)].na)); } 
    4593     break; 
    4594  
    4595   case 201: 
    4596 /* Line 1807 of yacc.c  */ 
    4597 #line 1028 "fortran.y" 
    4598     { strcpy(CharacterSize,(yyvsp[(1) - (1)].na));  strcpy((yyval.na),(yyvsp[(1) - (1)].na));  } 
    4599     break; 
    4600  
    4601   case 202: 
    4602 /* Line 1807 of yacc.c  */ 
    4603 #line 1029 "fortran.y" 
    4604     { strcpy(CharacterSize,"*"); strcpy((yyval.na),"*"); } 
    4605     break; 
    4606  
    4607   case 210: 
    4608 /* Line 1807 of yacc.c  */ 
    4609 #line 1042 "fortran.y" 
    4610     { VariableIsParameter = 1; } 
    4611     break; 
    4612  
    4613   case 212: 
    4614 /* Line 1807 of yacc.c  */ 
    4615 #line 1044 "fortran.y" 
    4616     { Allocatabledeclare = 1; } 
    4617     break; 
    4618  
    4619   case 213: 
    4620 /* Line 1807 of yacc.c  */ 
    4621 #line 1045 "fortran.y" 
    4622     { dimsgiven = 1; curdim = (yyvsp[(2) - (2)].d); } 
    4623     break; 
    4624  
    4625   case 214: 
    4626 /* Line 1807 of yacc.c  */ 
    4627 #line 1046 "fortran.y" 
    4628     { ExternalDeclare = 1; } 
    4629     break; 
    4630  
    4631   case 215: 
    4632 /* Line 1807 of yacc.c  */ 
    4633 #line 1048 "fortran.y" 
    4634     { strcpy(IntentSpec,(yyvsp[(3) - (4)].na)); } 
    4635     break; 
    4636  
    4637   case 217: 
    4638 /* Line 1807 of yacc.c  */ 
    4639 #line 1050 "fortran.y" 
    4640     { optionaldeclare = 1 ; } 
    4641     break; 
    4642  
    4643   case 218: 
    4644 /* Line 1807 of yacc.c  */ 
    4645 #line 1051 "fortran.y" 
    4646     { pointerdeclare = 1 ; } 
    4647     break; 
    4648  
    4649   case 219: 
    4650 /* Line 1807 of yacc.c  */ 
    4651 #line 1052 "fortran.y" 
    4652     { SaveDeclare = 1 ; } 
    4653     break; 
    4654  
    4655   case 220: 
    4656 /* Line 1807 of yacc.c  */ 
    4657 #line 1053 "fortran.y" 
    4658     { Targetdeclare = 1; } 
    4659     break; 
    4660  
    4661   case 221: 
    4662 /* Line 1807 of yacc.c  */ 
    4663 #line 1056 "fortran.y" 
    4664     { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    4665     break; 
    4666  
    4667   case 222: 
    4668 /* Line 1807 of yacc.c  */ 
    4669 #line 1057 "fortran.y" 
    4670     { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    4671     break; 
    4672  
    4673   case 223: 
    4674 /* Line 1807 of yacc.c  */ 
    4675 #line 1058 "fortran.y" 
    4676     { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    4677     break; 
    4678  
    4679   case 224: 
    4680 /* Line 1807 of yacc.c  */ 
    4681 #line 1061 "fortran.y" 
    4682     { PublicDeclare = 1;  } 
    4683     break; 
    4684  
    4685   case 225: 
    4686 /* Line 1807 of yacc.c  */ 
    4687 #line 1062 "fortran.y" 
    4688     { PrivateDeclare = 1; } 
    4689     break; 
    4690  
    4691   case 226: 
    4692 /* Line 1807 of yacc.c  */ 
    4693 #line 1064 "fortran.y" 
    4694     { (yyval.d) = (listdim*) NULL; } 
    4695     break; 
    4696  
    4697   case 227: 
    4698 /* Line 1807 of yacc.c  */ 
    4699 #line 1066 "fortran.y" 
    4700     { 
    4701             (yyval.d) = (listdim*) NULL; 
    4702             if ( inside_type_declare ) break; 
    4703             if ( created_dimensionlist == 1 || agrif_parentcall == 1 )  (yyval.d)=(yyvsp[(2) - (3)].d); 
    4704         } 
    4705     break; 
    4706  
    4707   case 228: 
    4708 /* Line 1807 of yacc.c  */ 
    4709 #line 1074 "fortran.y" 
    4710     { 
    4711             (yyval.d) = (listdim*) NULL; 
    4712             if ( inside_type_declare ) break; 
    4713             if ( created_dimensionlist == 1 || agrif_parentcall == 1 )  (yyval.d)=insertdim(NULL,(yyvsp[(1) - (1)].dim1)); 
    4714         } 
    4715     break; 
    4716  
    4717   case 229: 
    4718 /* Line 1807 of yacc.c  */ 
    4719 #line 1080 "fortran.y" 
    4720     { 
    4721             (yyval.d) = (listdim*) NULL; 
    4722             if ( inside_type_declare ) break; 
    4723             if ( (!inside_type_declare) && created_dimensionlist == 1 ) (yyval.d)=insertdim((yyvsp[(1) - (3)].d),(yyvsp[(3) - (3)].dim1)); 
    4724         } 
    4725     break; 
    4726  
    4727   case 230: 
    4728 /* Line 1807 of yacc.c  */ 
    4729 #line 1086 "fortran.y" 
    4730     { strcpy((yyval.dim1).first,"1"); strcpy((yyval.dim1).last,(yyvsp[(1) - (1)].na)); Save_Length((yyvsp[(1) - (1)].na),1); } 
    4731     break; 
    4732  
    4733   case 231: 
    4734 /* Line 1807 of yacc.c  */ 
    4735 #line 1087 "fortran.y" 
    4736     { strcpy((yyval.dim1).first,"");  strcpy((yyval.dim1).last,"");                    } 
    4737     break; 
    4738  
    4739   case 232: 
    4740 /* Line 1807 of yacc.c  */ 
    4741 #line 1088 "fortran.y" 
    4742     { strcpy((yyval.dim1).first,(yyvsp[(1) - (2)].na));  Save_Length((yyvsp[(1) - (2)].na),2); strcpy((yyval.dim1).last,""); } 
    4743     break; 
    4744  
    4745   case 233: 
    4746 /* Line 1807 of yacc.c  */ 
    4747 #line 1089 "fortran.y" 
    4748     { strcpy((yyval.dim1).first,"");  strcpy((yyval.dim1).last,(yyvsp[(2) - (2)].na)); Save_Length((yyvsp[(2) - (2)].na),1); } 
    4749     break; 
    4750  
    4751   case 234: 
    4752 /* Line 1807 of yacc.c  */ 
    4753 #line 1090 "fortran.y" 
    4754     { strcpy((yyval.dim1).first,(yyvsp[(1) - (3)].na));  Save_Length((yyvsp[(1) - (3)].na),2); strcpy((yyval.dim1).last,(yyvsp[(3) - (3)].na)); Save_Length((yyvsp[(3) - (3)].na),1); } 
    4755     break; 
    4756  
    4757   case 235: 
    4758 /* Line 1807 of yacc.c  */ 
    4759 #line 1093 "fortran.y" 
    4760     { strcpy((yyval.na),"*"); } 
    4761     break; 
    4762  
    4763   case 236: 
    4764 /* Line 1807 of yacc.c  */ 
    4765 #line 1094 "fortran.y" 
    4766     { strcpy((yyval.na),(yyvsp[(1) - (1)].na));  } 
    4767     break; 
    4768  
    4769   case 237: 
    4770 /* Line 1807 of yacc.c  */ 
    4771 #line 1096 "fortran.y" 
    4772     { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    4773     break; 
    4774  
    4775   case 238: 
    4776 /* Line 1807 of yacc.c  */ 
    4777 #line 1097 "fortran.y" 
    4778     { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    4779     break; 
    4780  
    4781   case 239: 
    4782 /* Line 1807 of yacc.c  */ 
    4783 #line 1098 "fortran.y" 
    4784     { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    4785     break; 
    4786  
    4787   case 240: 
    4788 /* Line 1807 of yacc.c  */ 
    4789 #line 1099 "fortran.y" 
    4790     { sprintf((yyval.na),"(%s)",(yyvsp[(2) - (3)].na)); } 
    4791     break; 
    4792  
    4793   case 241: 
    4794 /* Line 1807 of yacc.c  */ 
    4795 #line 1103 "fortran.y" 
    4796     { sprintf((yyval.na),"SUM(%s)",(yyvsp[(2) - (3)].na));} 
    4797     break; 
    4798  
    4799   case 242: 
    4800 /* Line 1807 of yacc.c  */ 
    4801 #line 1104 "fortran.y" 
    4802     { sprintf((yyval.na),"MAX(%s)",(yyvsp[(2) - (3)].na));} 
    4803     break; 
    4804  
    4805   case 243: 
    4806 /* Line 1807 of yacc.c  */ 
    4807 #line 1105 "fortran.y" 
    4808     { sprintf((yyval.na),"TANH(%s)",(yyvsp[(3) - (4)].na));} 
    4809     break; 
    4810  
    4811   case 244: 
    4812 /* Line 1807 of yacc.c  */ 
    4813 #line 1106 "fortran.y" 
    4814     { sprintf((yyval.na),"MAXVAL(%s)",(yyvsp[(3) - (4)].na));} 
    4815     break; 
    4816  
    4817   case 245: 
    4818 /* Line 1807 of yacc.c  */ 
    4819 #line 1107 "fortran.y" 
    4820     { sprintf((yyval.na),"MIN(%s)",(yyvsp[(2) - (3)].na));} 
    4821     break; 
    4822  
    4823   case 246: 
    4824 /* Line 1807 of yacc.c  */ 
    4825 #line 1108 "fortran.y" 
    4826     { sprintf((yyval.na),"MINVAL(%s)",(yyvsp[(3) - (4)].na));} 
    4827     break; 
    4828  
    4829   case 247: 
    4830 /* Line 1807 of yacc.c  */ 
    4831 #line 1109 "fortran.y" 
    4832     { sprintf((yyval.na),"TRIM(%s)",(yyvsp[(3) - (4)].na));} 
    4833     break; 
    4834  
    4835   case 248: 
    4836 /* Line 1807 of yacc.c  */ 
    4837 #line 1110 "fortran.y" 
    4838     { sprintf((yyval.na),"SQRT(%s)",(yyvsp[(2) - (3)].na));} 
    4839     break; 
    4840  
    4841   case 249: 
    4842 /* Line 1807 of yacc.c  */ 
    4843 #line 1111 "fortran.y" 
    4844     { sprintf((yyval.na),"REAL(%s)",(yyvsp[(3) - (4)].na));} 
    4845     break; 
    4846  
    4847   case 250: 
    4848 /* Line 1807 of yacc.c  */ 
    4849 #line 1112 "fortran.y" 
    4850     { sprintf((yyval.na),"NINT(%s)",(yyvsp[(3) - (4)].na));} 
    4851     break; 
    4852  
    4853   case 251: 
    4854 /* Line 1807 of yacc.c  */ 
    4855 #line 1113 "fortran.y" 
    4856     { sprintf((yyval.na),"FLOAT(%s)",(yyvsp[(3) - (4)].na));} 
    4857     break; 
    4858  
    4859   case 252: 
    4860 /* Line 1807 of yacc.c  */ 
    4861 #line 1114 "fortran.y" 
    4862     { sprintf((yyval.na),"EXP(%s)",(yyvsp[(3) - (4)].na));} 
    4863     break; 
    4864  
    4865   case 253: 
    4866 /* Line 1807 of yacc.c  */ 
    4867 #line 1115 "fortran.y" 
    4868     { sprintf((yyval.na),"COS(%s)",(yyvsp[(3) - (4)].na));} 
    4869     break; 
    4870  
    4871   case 254: 
    4872 /* Line 1807 of yacc.c  */ 
    4873 #line 1116 "fortran.y" 
    4874     { sprintf((yyval.na),"COSH(%s)",(yyvsp[(3) - (4)].na));} 
    4875     break; 
    4876  
    4877   case 255: 
    4878 /* Line 1807 of yacc.c  */ 
    4879 #line 1117 "fortran.y" 
    4880     { sprintf((yyval.na),"ACOS(%s)",(yyvsp[(3) - (4)].na));} 
    4881     break; 
    4882  
    4883   case 256: 
    4884 /* Line 1807 of yacc.c  */ 
    4885 #line 1118 "fortran.y" 
    4886     { sprintf((yyval.na),"SIN(%s)",(yyvsp[(3) - (4)].na));} 
    4887     break; 
    4888  
    4889   case 257: 
    4890 /* Line 1807 of yacc.c  */ 
    4891 #line 1119 "fortran.y" 
    4892     { sprintf((yyval.na),"SINH(%s)",(yyvsp[(3) - (4)].na));} 
    4893     break; 
    4894  
    4895   case 258: 
    4896 /* Line 1807 of yacc.c  */ 
    4897 #line 1120 "fortran.y" 
    4898     { sprintf((yyval.na),"ASIN(%s)",(yyvsp[(3) - (4)].na));} 
    4899     break; 
    4900  
    4901   case 259: 
    4902 /* Line 1807 of yacc.c  */ 
    4903 #line 1121 "fortran.y" 
    4904     { sprintf((yyval.na),"LOG(%s)",(yyvsp[(3) - (4)].na));} 
    4905     break; 
    4906  
    4907   case 260: 
    4908 /* Line 1807 of yacc.c  */ 
    4909 #line 1122 "fortran.y" 
    4910     { sprintf((yyval.na),"TAN(%s)",(yyvsp[(3) - (4)].na));} 
    4911     break; 
    4912  
    4913   case 261: 
    4914 /* Line 1807 of yacc.c  */ 
    4915 #line 1123 "fortran.y" 
    4916     { sprintf((yyval.na),"ATAN(%s)",(yyvsp[(3) - (4)].na));} 
    4917     break; 
    4918  
    4919   case 262: 
    4920 /* Line 1807 of yacc.c  */ 
    4921 #line 1124 "fortran.y" 
    4922     { sprintf((yyval.na),"ABS(%s)",(yyvsp[(2) - (3)].na));} 
    4923     break; 
    4924  
    4925   case 263: 
    4926 /* Line 1807 of yacc.c  */ 
    4927 #line 1125 "fortran.y" 
    4928     { sprintf((yyval.na),"MOD(%s)",(yyvsp[(3) - (4)].na));} 
    4929     break; 
    4930  
    4931   case 264: 
    4932 /* Line 1807 of yacc.c  */ 
    4933 #line 1126 "fortran.y" 
    4934     { sprintf((yyval.na),"SIGN(%s)",(yyvsp[(2) - (3)].na));} 
    4935     break; 
    4936  
    4937   case 265: 
    4938 /* Line 1807 of yacc.c  */ 
    4939 #line 1127 "fortran.y" 
    4940     { sprintf((yyval.na),"MINLOC(%s)",(yyvsp[(3) - (4)].na));} 
    4941     break; 
    4942  
    4943   case 266: 
    4944 /* Line 1807 of yacc.c  */ 
    4945 #line 1128 "fortran.y" 
    4946     { sprintf((yyval.na),"MAXLOC(%s)",(yyvsp[(3) - (4)].na));} 
    4947     break; 
    4948  
    4949   case 267: 
    4950 /* Line 1807 of yacc.c  */ 
    4951 #line 1130 "fortran.y" 
    4952     {strcpy((yyval.na),(yyvsp[(1) - (1)].na));} 
    4953     break; 
    4954  
    4955   case 268: 
    4956 /* Line 1807 of yacc.c  */ 
    4957 #line 1131 "fortran.y" 
    4958     { sprintf((yyval.na),"%s,%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na)); } 
    4959     break; 
    4960  
    4961   case 269: 
    4962 /* Line 1807 of yacc.c  */ 
    4963 #line 1133 "fortran.y" 
    4964     { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    4965     break; 
    4966  
    4967   case 270: 
    4968 /* Line 1807 of yacc.c  */ 
    4969 #line 1134 "fortran.y" 
    4970     { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    4971     break; 
    4972  
    4973   case 271: 
    4974 /* Line 1807 of yacc.c  */ 
    4975 #line 1135 "fortran.y" 
    4976     { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    4977     break; 
    4978  
    4979   case 272: 
    4980 /* Line 1807 of yacc.c  */ 
    4981 #line 1136 "fortran.y" 
    4982     { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    4983     break; 
    4984  
    4985   case 273: 
    4986 /* Line 1807 of yacc.c  */ 
    4987 #line 1137 "fortran.y" 
    4988     { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    4989     break; 
    4990  
    4991   case 274: 
    4992 /* Line 1807 of yacc.c  */ 
    4993 #line 1138 "fortran.y" 
    4994     { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    4995     break; 
    4996  
    4997   case 275: 
    4998 /* Line 1807 of yacc.c  */ 
    4999 #line 1140 "fortran.y" 
    5000     { strcpy((yyval.na),"+"); } 
    5001     break; 
    5002  
    5003   case 276: 
    5004 /* Line 1807 of yacc.c  */ 
    5005 #line 1141 "fortran.y" 
    5006     { strcpy((yyval.na),"-"); } 
    5007     break; 
    5008  
    5009   case 277: 
    5010 /* Line 1807 of yacc.c  */ 
    5011 #line 1145 "fortran.y" 
    5012     { sprintf((yyval.na),"+%s",(yyvsp[(2) - (2)].na)); } 
    5013     break; 
    5014  
    5015   case 278: 
    5016 /* Line 1807 of yacc.c  */ 
    5017 #line 1146 "fortran.y" 
    5018     { sprintf((yyval.na),"-%s",(yyvsp[(2) - (2)].na)); } 
    5019     break; 
    5020  
    5021   case 279: 
    5022 /* Line 1807 of yacc.c  */ 
    5023 #line 1147 "fortran.y" 
    5024     { sprintf((yyval.na),"*%s",(yyvsp[(2) - (2)].na)); } 
    5025     break; 
    5026  
    5027   case 280: 
    5028 /* Line 1807 of yacc.c  */ 
    5029 #line 1148 "fortran.y" 
    5030     { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    5031     break; 
    5032  
    5033   case 281: 
    5034 /* Line 1807 of yacc.c  */ 
    5035 #line 1149 "fortran.y" 
    5036     { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    5037     break; 
    5038  
    5039   case 282: 
    5040 /* Line 1807 of yacc.c  */ 
    5041 #line 1150 "fortran.y" 
    5042     { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    5043     break; 
    5044  
    5045   case 283: 
    5046 /* Line 1807 of yacc.c  */ 
    50474296#line 1151 "fortran.y" 
    5048     { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    5049     break; 
    5050  
    5051   case 284: 
    5052 /* Line 1807 of yacc.c  */ 
    5053 #line 1152 "fortran.y" 
    5054     { sprintf((yyval.na)," > %s",(yyvsp[(2) - (2)].na)); } 
    5055     break; 
    5056  
    5057   case 285: 
    5058 /* Line 1807 of yacc.c  */ 
    5059 #line 1153 "fortran.y" 
    5060     { sprintf((yyval.na)," < %s",(yyvsp[(2) - (2)].na)); } 
    5061     break; 
    5062  
    5063   case 286: 
    5064 /* Line 1807 of yacc.c  */ 
    5065 #line 1154 "fortran.y" 
    5066     { sprintf((yyval.na)," >= %s",(yyvsp[(3) - (3)].na)); } 
    5067     break; 
    5068  
    5069   case 287: 
    5070 /* Line 1807 of yacc.c  */ 
    5071 #line 1155 "fortran.y" 
    5072     { sprintf((yyval.na)," <= %s",(yyvsp[(3) - (3)].na)); } 
    5073     break; 
    5074  
    5075   case 288: 
    5076 /* Line 1807 of yacc.c  */ 
    5077 #line 1156 "fortran.y" 
    5078     { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    5079     break; 
    5080  
    5081   case 289: 
    5082 /* Line 1807 of yacc.c  */ 
    5083 #line 1157 "fortran.y" 
    5084     { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    5085     break; 
    5086  
    5087   case 290: 
    5088 /* Line 1807 of yacc.c  */ 
    5089 #line 1158 "fortran.y" 
    5090     { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    5091     break; 
    5092  
    5093   case 291: 
    5094 /* Line 1807 of yacc.c  */ 
    5095 #line 1159 "fortran.y" 
    5096     { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    5097     break; 
    5098  
    5099   case 292: 
    5100 /* Line 1807 of yacc.c  */ 
    5101 #line 1160 "fortran.y" 
    5102     { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    5103     break; 
    5104  
    5105   case 293: 
    5106 /* Line 1807 of yacc.c  */ 
    5107 #line 1161 "fortran.y" 
    5108     { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    5109     break; 
    5110  
    5111   case 294: 
    5112 /* Line 1807 of yacc.c  */ 
    5113 #line 1162 "fortran.y" 
    5114     { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    5115     break; 
    5116  
    5117   case 295: 
    5118 /* Line 1807 of yacc.c  */ 
    5119 #line 1163 "fortran.y" 
    5120     { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    5121     break; 
    5122  
    5123   case 296: 
    5124 /* Line 1807 of yacc.c  */ 
    5125 #line 1164 "fortran.y" 
    5126     { sprintf((yyval.na),"%s",(yyvsp[(2) - (2)].na)); } 
    5127     break; 
    5128  
    5129   case 297: 
    5130 /* Line 1807 of yacc.c  */ 
    5131 #line 1165 "fortran.y" 
    5132     { sprintf((yyval.na),"%s",(yyvsp[(2) - (2)].na)); } 
    5133     break; 
    5134  
    5135   case 298: 
    5136 /* Line 1807 of yacc.c  */ 
    5137 #line 1167 "fortran.y" 
    5138     { strcpy((yyval.na),""); } 
    5139     break; 
    5140  
    5141   case 299: 
    5142 /* Line 1807 of yacc.c  */ 
    5143 #line 1168 "fortran.y" 
    5144     { sprintf((yyval.na),"/%s",(yyvsp[(1) - (1)].na)); } 
    5145     break; 
    5146  
    5147   case 300: 
    5148 /* Line 1807 of yacc.c  */ 
    5149 #line 1169 "fortran.y" 
    5150     { sprintf((yyval.na),"/= %s",(yyvsp[(2) - (2)].na));} 
    5151     break; 
    5152  
    5153   case 301: 
    5154 /* Line 1807 of yacc.c  */ 
    5155 #line 1170 "fortran.y" 
    5156     { sprintf((yyval.na),"//%s",(yyvsp[(2) - (2)].na)); } 
    5157     break; 
    5158  
    5159   case 302: 
    5160 /* Line 1807 of yacc.c  */ 
    5161 #line 1173 "fortran.y" 
    5162     { sprintf((yyval.na),"==%s",(yyvsp[(2) - (2)].na)); } 
    5163     break; 
    5164  
    5165   case 303: 
    5166 /* Line 1807 of yacc.c  */ 
    5167 #line 1174 "fortran.y" 
    5168     { sprintf((yyval.na),"= %s",(yyvsp[(1) - (1)].na)); } 
    5169     break; 
    5170  
    5171   case 304: 
    5172 /* Line 1807 of yacc.c  */ 
    5173 #line 1177 "fortran.y" 
    5174     { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    5175     break; 
    5176  
    5177   case 305: 
    5178 /* Line 1807 of yacc.c  */ 
    5179 #line 1178 "fortran.y" 
    5180     { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    5181     break; 
    5182  
    5183   case 306: 
    5184 /* Line 1807 of yacc.c  */ 
    5185 #line 1179 "fortran.y" 
    5186     { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    5187     break; 
    5188  
    5189   case 307: 
    5190 /* Line 1807 of yacc.c  */ 
    5191 #line 1183 "fortran.y" 
    51924297    { 
    51934298            agrif_parentcall = 0; 
     
    52014306    break; 
    52024307 
    5203   case 308: 
    5204 /* Line 1807 of yacc.c  */ 
    5205 #line 1194 "fortran.y" 
     4308  case 65: 
     4309/* Line 1807 of yacc.c  */ 
     4310#line 1162 "fortran.y" 
    52064311    { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); if ( incalldeclare == 0 ) inagrifcallargument = 0;   } 
    52074312    break; 
    52084313 
    5209   case 309: 
    5210 /* Line 1807 of yacc.c  */ 
    5211 #line 1195 "fortran.y" 
     4314  case 66: 
     4315/* Line 1807 of yacc.c  */ 
     4316#line 1163 "fortran.y" 
    52124317    { sprintf((yyval.na)," %s %s ",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    52134318    break; 
    52144319 
    5215   case 310: 
    5216 /* Line 1807 of yacc.c  */ 
    5217 #line 1196 "fortran.y" 
    5218     { sprintf((yyval.na)," %s ( %s )",(yyvsp[(1) - (4)].na),(yyvsp[(3) - (4)].na)); } 
    5219     break; 
    5220  
    5221   case 311: 
    5222 /* Line 1807 of yacc.c  */ 
    5223 #line 1197 "fortran.y" 
    5224     { sprintf((yyval.na)," %s ( %s ) %s ",(yyvsp[(1) - (5)].na),(yyvsp[(3) - (5)].na),(yyvsp[(5) - (5)].na)); } 
    5225     break; 
    5226  
    5227   case 312: 
    5228 /* Line 1807 of yacc.c  */ 
    5229 #line 1201 "fortran.y" 
     4320  case 67: 
     4321/* Line 1807 of yacc.c  */ 
     4322#line 1164 "fortran.y" 
     4323    {in_complex_literal=0;} 
     4324    break; 
     4325 
     4326  case 68: 
     4327/* Line 1807 of yacc.c  */ 
     4328#line 1164 "fortran.y" 
     4329    { sprintf((yyval.na)," %s ( %s )",(yyvsp[(1) - (5)].na),(yyvsp[(4) - (5)].na)); } 
     4330    break; 
     4331 
     4332  case 69: 
     4333/* Line 1807 of yacc.c  */ 
     4334#line 1165 "fortran.y" 
     4335    {in_complex_literal=0;} 
     4336    break; 
     4337 
     4338  case 70: 
     4339/* Line 1807 of yacc.c  */ 
     4340#line 1165 "fortran.y" 
     4341    { sprintf((yyval.na)," %s ( %s ) %s ",(yyvsp[(1) - (6)].na),(yyvsp[(4) - (6)].na),(yyvsp[(6) - (6)].na)); } 
     4342    break; 
     4343 
     4344  case 72: 
     4345/* Line 1807 of yacc.c  */ 
     4346#line 1168 "fortran.y" 
     4347    {in_complex_literal=0;} 
     4348    break; 
     4349 
     4350  case 73: 
     4351/* Line 1807 of yacc.c  */ 
     4352#line 1169 "fortran.y" 
    52304353    { 
    52314354            if ( inside_type_declare ) break; 
    5232             sprintf((yyval.na)," %s ( %s )",(yyvsp[(1) - (4)].na),(yyvsp[(3) - (4)].na)); 
    5233             ModifyTheAgrifFunction_0((yyvsp[(3) - (4)].na)); 
     4355            sprintf((yyval.na)," %s ( %s )",(yyvsp[(1) - (5)].na),(yyvsp[(4) - (5)].na)); 
     4356            ModifyTheAgrifFunction_0((yyvsp[(4) - (5)].na)); 
    52344357            agrif_parentcall = 0; 
    52354358        } 
    52364359    break; 
    52374360 
    5238   case 313: 
    5239 /* Line 1807 of yacc.c  */ 
    5240 #line 1210 "fortran.y" 
     4361  case 74: 
     4362/* Line 1807 of yacc.c  */ 
     4363#line 1178 "fortran.y" 
    52414364    { 
    52424365            sprintf((yyval.na)," %s %% %s ",(yyvsp[(1) - (4)].na),(yyvsp[(4) - (4)].na)); 
     
    52454368    break; 
    52464369 
    5247   case 314: 
    5248 /* Line 1807 of yacc.c  */ 
    5249 #line 1216 "fortran.y" 
    5250     { sprintf((yyval.na),"(/%s/)",(yyvsp[(2) - (3)].na)); } 
    5251     break; 
    5252  
    5253   case 315: 
    5254 /* Line 1807 of yacc.c  */ 
    5255 #line 1219 "fortran.y" 
     4370  case 75: 
     4371/* Line 1807 of yacc.c  */ 
     4372#line 1189 "fortran.y" 
    52564373    { strcpy((yyval.na)," "); } 
    52574374    break; 
    52584375 
    5259   case 316: 
    5260 /* Line 1807 of yacc.c  */ 
    5261 #line 1220 "fortran.y" 
     4376  case 76: 
     4377/* Line 1807 of yacc.c  */ 
     4378#line 1190 "fortran.y" 
    52624379    { strcpy((yyval.na),(yyvsp[(2) - (2)].na)); } 
    52634380    break; 
    52644381 
    5265   case 317: 
    5266 /* Line 1807 of yacc.c  */ 
    5267 #line 1223 "fortran.y" 
     4382  case 77: 
     4383/* Line 1807 of yacc.c  */ 
     4384#line 1193 "fortran.y" 
    52684385    {  strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    52694386    break; 
    52704387 
    5271   case 318: 
    5272 /* Line 1807 of yacc.c  */ 
    5273 #line 1224 "fortran.y" 
     4388  case 78: 
     4389/* Line 1807 of yacc.c  */ 
     4390#line 1194 "fortran.y" 
    52744391    {  sprintf((yyval.na),"%s,%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na)); } 
    52754392    break; 
    52764393 
    5277   case 319: 
    5278 /* Line 1807 of yacc.c  */ 
    5279 #line 1227 "fortran.y" 
     4394  case 79: 
     4395/* Line 1807 of yacc.c  */ 
     4396#line 1197 "fortran.y" 
    52804397    {strcpy((yyval.na),(yyvsp[(1) - (1)].na));} 
    52814398    break; 
    52824399 
    5283   case 320: 
    5284 /* Line 1807 of yacc.c  */ 
    5285 #line 1228 "fortran.y" 
     4400  case 80: 
     4401/* Line 1807 of yacc.c  */ 
     4402#line 1198 "fortran.y" 
    52864403    {strcpy((yyval.na),(yyvsp[(1) - (1)].na));} 
    52874404    break; 
    52884405 
    5289   case 321: 
    5290 /* Line 1807 of yacc.c  */ 
    5291 #line 1231 "fortran.y" 
     4406  case 81: 
     4407/* Line 1807 of yacc.c  */ 
     4408#line 1201 "fortran.y" 
    52924409    {  sprintf((yyval.na),"%s :%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na));} 
    52934410    break; 
    52944411 
    5295   case 322: 
    5296 /* Line 1807 of yacc.c  */ 
    5297 #line 1232 "fortran.y" 
     4412  case 82: 
     4413/* Line 1807 of yacc.c  */ 
     4414#line 1202 "fortran.y" 
    52984415    {  sprintf((yyval.na),"%s :%s :%s",(yyvsp[(1) - (5)].na),(yyvsp[(3) - (5)].na),(yyvsp[(5) - (5)].na));} 
    52994416    break; 
    53004417 
    5301   case 323: 
    5302 /* Line 1807 of yacc.c  */ 
    5303 #line 1233 "fortran.y" 
     4418  case 83: 
     4419/* Line 1807 of yacc.c  */ 
     4420#line 1203 "fortran.y" 
    53044421    {  sprintf((yyval.na),":%s :%s",(yyvsp[(2) - (4)].na),(yyvsp[(4) - (4)].na));} 
    53054422    break; 
    53064423 
    5307   case 324: 
    5308 /* Line 1807 of yacc.c  */ 
    5309 #line 1234 "fortran.y" 
     4424  case 84: 
     4425/* Line 1807 of yacc.c  */ 
     4426#line 1204 "fortran.y" 
    53104427    {  sprintf((yyval.na),": : %s",(yyvsp[(3) - (3)].na));} 
    53114428    break; 
    53124429 
    5313   case 325: 
    5314 /* Line 1807 of yacc.c  */ 
    5315 #line 1235 "fortran.y" 
     4430  case 85: 
     4431/* Line 1807 of yacc.c  */ 
     4432#line 1205 "fortran.y" 
    53164433    {  sprintf((yyval.na),":%s",(yyvsp[(2) - (2)].na));} 
    53174434    break; 
    53184435 
    5319   case 326: 
    5320 /* Line 1807 of yacc.c  */ 
    5321 #line 1236 "fortran.y" 
     4436  case 86: 
     4437/* Line 1807 of yacc.c  */ 
     4438#line 1206 "fortran.y" 
    53224439    {  sprintf((yyval.na),"%s :",(yyvsp[(1) - (2)].na));} 
    53234440    break; 
    53244441 
    5325   case 327: 
    5326 /* Line 1807 of yacc.c  */ 
    5327 #line 1237 "fortran.y" 
     4442  case 87: 
     4443/* Line 1807 of yacc.c  */ 
     4444#line 1207 "fortran.y" 
    53284445    {  sprintf((yyval.na),":");} 
    53294446    break; 
    53304447 
    5331   case 328: 
    5332 /* Line 1807 of yacc.c  */ 
    5333 #line 1240 "fortran.y" 
     4448  case 88: 
     4449/* Line 1807 of yacc.c  */ 
     4450#line 1210 "fortran.y" 
    53344451    { 
     4452       //  if (indeclaration == 1) break; 
    53354453            if ( afterpercent == 0 ) 
    53364454            { 
     
    53774495    break; 
    53784496 
    5379   case 329: 
    5380 /* Line 1807 of yacc.c  */ 
    5381 #line 1285 "fortran.y" 
     4497  case 89: 
     4498/* Line 1807 of yacc.c  */ 
     4499#line 1256 "fortran.y" 
    53824500    { strcpy((yyval.na),".TRUE.");} 
    53834501    break; 
    53844502 
    5385   case 330: 
    5386 /* Line 1807 of yacc.c  */ 
    5387 #line 1286 "fortran.y" 
     4503  case 90: 
     4504/* Line 1807 of yacc.c  */ 
     4505#line 1257 "fortran.y" 
    53884506    { strcpy((yyval.na),".FALSE.");} 
    53894507    break; 
    53904508 
    5391   case 331: 
    5392 /* Line 1807 of yacc.c  */ 
    5393 #line 1287 "fortran.y" 
     4509  case 91: 
     4510/* Line 1807 of yacc.c  */ 
     4511#line 1258 "fortran.y" 
    53944512    { strcpy((yyval.na),"NULL()"); } 
    53954513    break; 
    53964514 
    5397   case 332: 
    5398 /* Line 1807 of yacc.c  */ 
    5399 #line 1288 "fortran.y" 
     4515  case 92: 
     4516/* Line 1807 of yacc.c  */ 
     4517#line 1259 "fortran.y" 
    54004518    { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    54014519    break; 
    54024520 
    5403   case 333: 
    5404 /* Line 1807 of yacc.c  */ 
    5405 #line 1289 "fortran.y" 
     4521  case 93: 
     4522/* Line 1807 of yacc.c  */ 
     4523#line 1260 "fortran.y" 
    54064524    { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    54074525    break; 
    54084526 
    5409   case 334: 
    5410 /* Line 1807 of yacc.c  */ 
    5411 #line 1290 "fortran.y" 
     4527  case 94: 
     4528/* Line 1807 of yacc.c  */ 
     4529#line 1261 "fortran.y" 
    54124530    { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    54134531    break; 
    54144532 
    5415   case 335: 
    5416 /* Line 1807 of yacc.c  */ 
    5417 #line 1292 "fortran.y" 
     4533  case 95: 
     4534/* Line 1807 of yacc.c  */ 
     4535#line 1263 "fortran.y" 
    54184536    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
    54194537    break; 
    54204538 
    5421   case 337: 
    5422 /* Line 1807 of yacc.c  */ 
    5423 #line 1296 "fortran.y" 
     4539  case 97: 
     4540/* Line 1807 of yacc.c  */ 
     4541#line 1267 "fortran.y" 
    54244542    { strcpy((yyval.na),(yyvsp[(1) - (1)].na));} 
    54254543    break; 
    54264544 
    5427   case 339: 
    5428 /* Line 1807 of yacc.c  */ 
    5429 #line 1298 "fortran.y" 
     4545  case 99: 
     4546/* Line 1807 of yacc.c  */ 
     4547#line 1269 "fortran.y" 
    54304548    { strcpy((yyval.na),(yyvsp[(1) - (1)].na));} 
    54314549    break; 
    54324550 
    5433   case 340: 
    5434 /* Line 1807 of yacc.c  */ 
    5435 #line 1299 "fortran.y" 
     4551  case 100: 
     4552/* Line 1807 of yacc.c  */ 
     4553#line 1270 "fortran.y" 
    54364554    { strcpy((yyval.na),(yyvsp[(1) - (1)].na));} 
    54374555    break; 
    54384556 
    5439   case 341: 
    5440 /* Line 1807 of yacc.c  */ 
    5441 #line 1301 "fortran.y" 
     4557  case 101: 
     4558/* Line 1807 of yacc.c  */ 
     4559#line 1272 "fortran.y" 
    54424560    { strcpy((yyval.na)," ");} 
    54434561    break; 
    54444562 
    5445   case 342: 
    5446 /* Line 1807 of yacc.c  */ 
    5447 #line 1302 "fortran.y" 
     4563  case 102: 
     4564/* Line 1807 of yacc.c  */ 
     4565#line 1273 "fortran.y" 
    54484566    { strcpy((yyval.na),(yyvsp[(1) - (1)].na));} 
    54494567    break; 
    54504568 
    5451   case 343: 
    5452 /* Line 1807 of yacc.c  */ 
    5453 #line 1305 "fortran.y" 
    5454     { sprintf((yyval.na),"(%s :%s)",(yyvsp[(2) - (5)].na),(yyvsp[(4) - (5)].na));} 
    5455     break; 
    5456  
    5457   case 344: 
    5458 /* Line 1807 of yacc.c  */ 
    5459 #line 1307 "fortran.y" 
     4569  case 103: 
     4570/* Line 1807 of yacc.c  */ 
     4571#line 1283 "fortran.y" 
    54604572    { strcpy((yyval.na)," ");} 
    54614573    break; 
    54624574 
    5463   case 345: 
    5464 /* Line 1807 of yacc.c  */ 
    5465 #line 1308 "fortran.y" 
     4575  case 104: 
     4576/* Line 1807 of yacc.c  */ 
     4577#line 1284 "fortran.y" 
    54664578    { strcpy((yyval.na),(yyvsp[(1) - (1)].na));} 
    54674579    break; 
    54684580 
    5469   case 346: 
    5470 /* Line 1807 of yacc.c  */ 
    5471 #line 1311 "fortran.y" 
    5472     { strcpy((yyval.na)," ");} 
    5473     break; 
    5474  
    5475   case 347: 
    5476 /* Line 1807 of yacc.c  */ 
    5477 #line 1312 "fortran.y" 
    5478     { strcpy((yyval.na),(yyvsp[(1) - (1)].na));} 
    5479     break; 
    5480  
    5481   case 348: 
    5482 /* Line 1807 of yacc.c  */ 
    5483 #line 1314 "fortran.y" 
    5484     { InitialValueGiven = 0; } 
    5485     break; 
    5486  
    5487   case 349: 
    5488 /* Line 1807 of yacc.c  */ 
    5489 #line 1316 "fortran.y" 
    5490     { 
    5491             if ( inside_type_declare ) break; 
    5492             strcpy(InitValue,(yyvsp[(2) - (2)].na)); 
    5493             InitialValueGiven = 1; 
    5494         } 
    5495     break; 
    5496  
    5497   case 350: 
    5498 /* Line 1807 of yacc.c  */ 
    5499 #line 1322 "fortran.y" 
    5500     { 
    5501             if ( inside_type_declare ) break; 
    5502             strcpy(InitValue,(yyvsp[(2) - (2)].na)); 
    5503             InitialValueGiven = 2; 
    5504         } 
    5505     break; 
    5506  
    5507   case 351: 
    5508 /* Line 1807 of yacc.c  */ 
    5509 #line 1329 "fortran.y" 
    5510     {sprintf((yyval.na),"(%s,%s)",(yyvsp[(2) - (5)].na),(yyvsp[(4) - (5)].na)); } 
    5511     break; 
    5512  
    5513   case 352: 
    5514 /* Line 1807 of yacc.c  */ 
    5515 #line 1333 "fortran.y" 
    5516     { 
    5517             /* if variables has been declared in a subroutine       */ 
    5518             sprintf(charusemodule, "%s", (yyvsp[(2) - (2)].na)); 
    5519             if ( firstpass ) 
    5520             { 
    5521                 Add_NameOfModuleUsed_1((yyvsp[(2) - (2)].na)); 
    5522             } 
    5523             else 
    5524             { 
    5525                 if ( insubroutinedeclare ) 
    5526                     copyuse_0((yyvsp[(2) - (2)].na)); 
    5527  
    5528                 if ( inmoduledeclare == 0 ) 
    5529                 { 
    5530                     pos_end = setposcur(); 
    5531                     RemoveWordSET_0(fortran_out,pos_curuse,pos_end-pos_curuse); 
    5532                 } 
    5533             } 
    5534         } 
    5535     break; 
    5536  
    5537   case 353: 
    5538 /* Line 1807 of yacc.c  */ 
    5539 #line 1353 "fortran.y" 
    5540     { 
    5541             if ( firstpass ) 
    5542             { 
    5543                 if ( insubroutinedeclare ) 
    5544                 { 
    5545                     Add_CouplePointed_Var_1((yyvsp[(2) - (4)].na),(yyvsp[(4) - (4)].lc)); 
    5546                     coupletmp = (yyvsp[(4) - (4)].lc); 
    5547                     strcpy(ligne,""); 
    5548                     while ( coupletmp ) 
    5549                     { 
    5550                         strcat(ligne, coupletmp->c_namevar); 
    5551                         strcat(ligne, " => "); 
    5552                         strcat(ligne, coupletmp->c_namepointedvar); 
    5553                         coupletmp = coupletmp->suiv; 
    5554                         if ( coupletmp ) strcat(ligne,","); 
    5555                     } 
    5556                     sprintf(charusemodule,"%s",(yyvsp[(2) - (4)].na)); 
    5557                 } 
    5558                 Add_NameOfModuleUsed_1((yyvsp[(2) - (4)].na)); 
    5559             } 
    5560             if ( inmoduledeclare == 0 ) 
    5561             { 
    5562                 pos_end = setposcur(); 
    5563                 RemoveWordSET_0(fortran_out,pos_curuse,pos_end-pos_curuse); 
    5564             } 
    5565         } 
    5566     break; 
    5567  
    5568   case 354: 
    5569 /* Line 1807 of yacc.c  */ 
    5570 #line 1380 "fortran.y" 
    5571     { 
    5572             /* if variables has been declared in a subroutine       */ 
    5573             sprintf(charusemodule,"%s",(yyvsp[(2) - (6)].na)); 
    5574             if ( firstpass ) 
    5575             { 
    5576                 Add_NameOfModuleUsed_1((yyvsp[(2) - (6)].na)); 
    5577             } 
    5578             else 
    5579             { 
    5580                 if ( insubroutinedeclare ) 
    5581                     copyuseonly_0((yyvsp[(2) - (6)].na)); 
    5582  
    5583                 if ( inmoduledeclare == 0 ) 
    5584                 { 
    5585                     pos_end = setposcur(); 
    5586                     RemoveWordSET_0(fortran_out,pos_curuse,pos_end-pos_curuse); 
    5587                 } 
    5588             } 
    5589         } 
    5590     break; 
    5591  
    5592   case 355: 
    5593 /* Line 1807 of yacc.c  */ 
    5594 #line 1400 "fortran.y" 
    5595     { 
    5596             /* if variables has been declared in a subroutine      */ 
    5597             if ( firstpass ) 
    5598             { 
    5599                 if ( insubroutinedeclare ) 
    5600                 { 
    5601                     Add_CouplePointed_Var_1((yyvsp[(2) - (6)].na),(yyvsp[(6) - (6)].lc)); 
    5602                     coupletmp = (yyvsp[(6) - (6)].lc); 
    5603                     strcpy(ligne,""); 
    5604                     while ( coupletmp ) 
    5605                     { 
    5606                         strcat(ligne,coupletmp->c_namevar); 
    5607                         if ( strcasecmp(coupletmp->c_namepointedvar,"") )   strcat(ligne," => "); 
    5608                         strcat(ligne,coupletmp->c_namepointedvar); 
    5609                         coupletmp = coupletmp->suiv; 
    5610                         if ( coupletmp ) strcat(ligne,","); 
    5611                     } 
    5612                     sprintf(charusemodule,"%s",(yyvsp[(2) - (6)].na)); 
    5613                 } 
    5614                 Add_NameOfModuleUsed_1((yyvsp[(2) - (6)].na)); 
    5615             } 
    5616             else /* if ( firstpass == 0 ) */ 
    5617             { 
    5618                 if ( inmoduledeclare == 0 ) 
    5619                 { 
    5620                     pos_end = setposcur(); 
    5621                     RemoveWordSET_0(fortran_out,pos_curuse,pos_end-pos_curuse); 
    5622                     if (oldfortran_out)  variableisglobalinmodule((yyvsp[(6) - (6)].lc),(yyvsp[(2) - (6)].na),oldfortran_out,pos_curuseold); 
    5623                 } 
    5624                 else 
    5625                 { 
    5626                     /* if we are in the module declare and if the    */ 
    5627                     /* onlylist is a list of global variable         */ 
    5628                     variableisglobalinmodule((yyvsp[(6) - (6)].lc), (yyvsp[(2) - (6)].na), fortran_out,pos_curuse); 
    5629                 } 
    5630             } 
    5631         } 
    5632     break; 
    5633  
    5634   case 356: 
    5635 /* Line 1807 of yacc.c  */ 
    5636 #line 1440 "fortran.y" 
    5637     { 
    5638             pos_curuse = setposcur()-strlen((yyvsp[(1) - (1)].na)); 
    5639             if (firstpass == 0 && oldfortran_out) pos_curuseold = setposcurname(oldfortran_out); 
    5640         } 
    5641     break; 
    5642  
    5643   case 357: 
    5644 /* Line 1807 of yacc.c  */ 
    5645 #line 1447 "fortran.y" 
    5646     { 
    5647             (yyval.lc) = (yyvsp[(1) - (1)].lc); 
    5648         } 
    5649     break; 
    5650  
    5651   case 358: 
    5652 /* Line 1807 of yacc.c  */ 
    5653 #line 1451 "fortran.y" 
    5654     { 
    5655             /* insert the variable in the list $1                 */ 
    5656             (yyvsp[(3) - (3)].lc)->suiv = (yyvsp[(1) - (3)].lc); 
    5657             (yyval.lc) = (yyvsp[(3) - (3)].lc); 
    5658         } 
    5659     break; 
    5660  
    5661   case 359: 
    5662 /* Line 1807 of yacc.c  */ 
    5663 #line 1458 "fortran.y" 
    5664     { 
    5665             coupletmp = (listcouple *) calloc(1,sizeof(listcouple)); 
    5666             strcpy(coupletmp->c_namevar,(yyvsp[(1) - (3)].na)); 
    5667             strcpy(coupletmp->c_namepointedvar,(yyvsp[(3) - (3)].na)); 
    5668             coupletmp->suiv = NULL; 
    5669             (yyval.lc) = coupletmp; 
    5670         } 
    5671     break; 
    5672  
    5673   case 360: 
    5674 /* Line 1807 of yacc.c  */ 
    5675 #line 1467 "fortran.y" 
    5676     {  (yyval.lc) = (yyvsp[(1) - (1)].lc); } 
    5677     break; 
    5678  
    5679   case 361: 
    5680 /* Line 1807 of yacc.c  */ 
    5681 #line 1469 "fortran.y" 
    5682     { 
    5683             /* insert the variable in the list $1                 */ 
    5684             (yyvsp[(3) - (3)].lc)->suiv = (yyvsp[(1) - (3)].lc); 
    5685             (yyval.lc) = (yyvsp[(3) - (3)].lc); 
    5686         } 
    5687     break; 
    5688  
    5689   case 362: 
    5690 /* Line 1807 of yacc.c  */ 
    5691 #line 1477 "fortran.y" 
    5692     { 
    5693             coupletmp = (listcouple *)calloc(1,sizeof(listcouple)); 
    5694             strcpy(coupletmp->c_namevar,(yyvsp[(1) - (3)].na)); 
    5695             strcpy(coupletmp->c_namepointedvar,(yyvsp[(3) - (3)].na)); 
    5696             coupletmp->suiv = NULL; 
    5697             (yyval.lc) = coupletmp; 
    5698             pointedvar = 1; 
    5699             Add_UsedInSubroutine_Var_1((yyvsp[(1) - (3)].na)); 
    5700         } 
    5701     break; 
    5702  
    5703   case 363: 
    5704 /* Line 1807 of yacc.c  */ 
    5705 #line 1487 "fortran.y" 
    5706     { 
    5707             coupletmp = (listcouple *)calloc(1,sizeof(listcouple)); 
    5708             strcpy(coupletmp->c_namevar,(yyvsp[(1) - (1)].na)); 
    5709             strcpy(coupletmp->c_namepointedvar,""); 
    5710             coupletmp->suiv = NULL; 
    5711             (yyval.lc) = coupletmp; 
    5712         } 
    5713     break; 
    5714  
    5715   case 380: 
    5716 /* Line 1807 of yacc.c  */ 
    5717 #line 1522 "fortran.y" 
    5718     { inallocate = 0; } 
    5719     break; 
    5720  
    5721   case 381: 
    5722 /* Line 1807 of yacc.c  */ 
    5723 #line 1523 "fortran.y" 
    5724     { inallocate = 0; } 
    5725     break; 
    5726  
    5727   case 388: 
    5728 /* Line 1807 of yacc.c  */ 
    5729 #line 1531 "fortran.y" 
    5730     { 
    5731             GlobalDeclaration = 0 ; 
    5732             if ( firstpass == 0 && strcasecmp(subroutinename,"") ) 
    5733             { 
    5734                 if ( module_declar && insubroutinedeclare == 0 )    fclose(module_declar); 
    5735             } 
    5736             if ( strcasecmp(subroutinename,"") ) 
    5737             { 
    5738                 if ( inmodulemeet == 1 ) 
    5739                 { 
    5740                     /* we are in a module                                */ 
    5741                     if ( insubroutinedeclare == 1 ) 
    5742                     { 
    5743                         /* it is like an end subroutine <name>            */ 
    5744                         insubroutinedeclare = 0 ; 
    5745                         pos_cur = setposcur(); 
    5746                         closeandcallsubloopandincludeit_0(1); 
    5747                         functiondeclarationisdone = 0; 
    5748                     } 
    5749                     else 
    5750                     { 
    5751                         /* it is like an end module <name>                */ 
    5752                         inmoduledeclare = 0 ; 
    5753                         inmodulemeet = 0 ; 
    5754                     } 
    5755                 } 
    5756                 else 
    5757                 { 
    5758                     insubroutinedeclare = 0; 
    5759                     pos_cur = setposcur(); 
    5760                     closeandcallsubloopandincludeit_0(2); 
    5761                     functiondeclarationisdone = 0; 
    5762                 } 
    5763             } 
    5764             strcpy(subroutinename,""); 
    5765         } 
    5766     break; 
    5767  
    5768   case 389: 
    5769 /* Line 1807 of yacc.c  */ 
    5770 #line 1568 "fortran.y" 
    5771     { 
    5772             insubroutinedeclare = 0; 
    5773             inprogramdeclare = 0; 
    5774             pos_cur = setposcur(); 
    5775             closeandcallsubloopandincludeit_0(3); 
    5776             functiondeclarationisdone = 0; 
    5777             strcpy(subroutinename,""); 
    5778         } 
    5779     break; 
    5780  
    5781   case 390: 
    5782 /* Line 1807 of yacc.c  */ 
    5783 #line 1577 "fortran.y" 
    5784     { 
    5785             if ( strcasecmp(subroutinename,"") ) 
    5786             { 
    5787                 insubroutinedeclare = 0; 
    5788                 pos_cur = setposcur(); 
    5789                 closeandcallsubloopandincludeit_0(1); 
    5790                 functiondeclarationisdone = 0; 
    5791                 strcpy(subroutinename,""); 
    5792             } 
    5793         } 
    5794     break; 
    5795  
    5796   case 391: 
    5797 /* Line 1807 of yacc.c  */ 
    5798 #line 1588 "fortran.y" 
    5799     { 
    5800             insubroutinedeclare = 0; 
    5801             pos_cur = setposcur(); 
    5802             closeandcallsubloopandincludeit_0(0); 
    5803             functiondeclarationisdone = 0; 
    5804             strcpy(subroutinename,""); 
    5805         } 
    5806     break; 
    5807  
    5808   case 392: 
    5809 /* Line 1807 of yacc.c  */ 
    5810 #line 1596 "fortran.y" 
     4581  case 168: 
     4582/* Line 1807 of yacc.c  */ 
     4583#line 1481 "fortran.y" 
    58114584    { 
    58124585            /* if we never meet the contains keyword               */ 
     
    58324605    break; 
    58334606 
     4607  case 188: 
     4608/* Line 1807 of yacc.c  */ 
     4609#line 1534 "fortran.y" 
     4610    {in_complex_literal=0;} 
     4611    break; 
     4612 
     4613  case 191: 
     4614/* Line 1807 of yacc.c  */ 
     4615#line 1558 "fortran.y" 
     4616    {strcpy((yyval.na),"");} 
     4617    break; 
     4618 
     4619  case 195: 
     4620/* Line 1807 of yacc.c  */ 
     4621#line 1568 "fortran.y" 
     4622    {strcpy((yyval.na),"");} 
     4623    break; 
     4624 
     4625  case 196: 
     4626/* Line 1807 of yacc.c  */ 
     4627#line 1570 "fortran.y" 
     4628    {strcpy((yyval.na),(yyvsp[(1) - (1)].na));} 
     4629    break; 
     4630 
     4631  case 201: 
     4632/* Line 1807 of yacc.c  */ 
     4633#line 1590 "fortran.y" 
     4634    {pos_cur_decl=my_position_before;} 
     4635    break; 
     4636 
     4637  case 202: 
     4638/* Line 1807 of yacc.c  */ 
     4639#line 1591 "fortran.y" 
     4640    {strcpy((yyval.na),(yyvsp[(2) - (2)].na));} 
     4641    break; 
     4642 
     4643  case 204: 
     4644/* Line 1807 of yacc.c  */ 
     4645#line 1594 "fortran.y" 
     4646    {strcpy(DeclType,"type"); GlobalDeclarationType = 1;  } 
     4647    break; 
     4648 
     4649  case 205: 
     4650/* Line 1807 of yacc.c  */ 
     4651#line 1598 "fortran.y" 
     4652    {in_kind_selector = 1;} 
     4653    break; 
     4654 
     4655  case 206: 
     4656/* Line 1807 of yacc.c  */ 
     4657#line 1599 "fortran.y" 
     4658    {sprintf((yyval.na),"%s%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na));strcpy(DeclType,(yyvsp[(1) - (3)].na)); in_kind_selector =0;} 
     4659    break; 
     4660 
     4661  case 207: 
     4662/* Line 1807 of yacc.c  */ 
     4663#line 1600 "fortran.y" 
     4664    {in_kind_selector = 1;} 
     4665    break; 
     4666 
     4667  case 208: 
     4668/* Line 1807 of yacc.c  */ 
     4669#line 1601 "fortran.y" 
     4670    {sprintf((yyval.na),"%s%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na));strcpy(DeclType,(yyvsp[(1) - (3)].na));in_kind_selector =0;} 
     4671    break; 
     4672 
     4673  case 209: 
     4674/* Line 1807 of yacc.c  */ 
     4675#line 1602 "fortran.y" 
     4676    {in_kind_selector = 1;} 
     4677    break; 
     4678 
     4679  case 210: 
     4680/* Line 1807 of yacc.c  */ 
     4681#line 1603 "fortran.y" 
     4682    {sprintf((yyval.na),"%s%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na));strcpy(DeclType,"real"); strcpy(NamePrecision,"8");in_kind_selector =0;} 
     4683    break; 
     4684 
     4685  case 211: 
     4686/* Line 1807 of yacc.c  */ 
     4687#line 1604 "fortran.y" 
     4688    {in_kind_selector = 1;} 
     4689    break; 
     4690 
     4691  case 212: 
     4692/* Line 1807 of yacc.c  */ 
     4693#line 1605 "fortran.y" 
     4694    {sprintf((yyval.na),"%s%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na));strcpy(DeclType,(yyvsp[(1) - (3)].na));in_kind_selector =0;} 
     4695    break; 
     4696 
     4697  case 213: 
     4698/* Line 1807 of yacc.c  */ 
     4699#line 1606 "fortran.y" 
     4700    {in_char_selector = 1;} 
     4701    break; 
     4702 
     4703  case 214: 
     4704/* Line 1807 of yacc.c  */ 
     4705#line 1607 "fortran.y" 
     4706    {sprintf((yyval.na),"%s%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na));strcpy(DeclType,(yyvsp[(1) - (3)].na));in_char_selector = 0;} 
     4707    break; 
     4708 
     4709  case 215: 
     4710/* Line 1807 of yacc.c  */ 
     4711#line 1608 "fortran.y" 
     4712    {in_kind_selector = 1;} 
     4713    break; 
     4714 
     4715  case 216: 
     4716/* Line 1807 of yacc.c  */ 
     4717#line 1609 "fortran.y" 
     4718    {sprintf((yyval.na),"%s%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na));strcpy(DeclType,(yyvsp[(1) - (3)].na));in_kind_selector =0;} 
     4719    break; 
     4720 
     4721  case 217: 
     4722/* Line 1807 of yacc.c  */ 
     4723#line 1613 "fortran.y" 
     4724    {strcpy((yyval.na),"");strcpy(NamePrecision,"");} 
     4725    break; 
     4726 
     4727  case 218: 
     4728/* Line 1807 of yacc.c  */ 
     4729#line 1615 "fortran.y" 
     4730    {strcpy((yyval.na),(yyvsp[(1) - (1)].na));} 
     4731    break; 
     4732 
     4733  case 219: 
     4734/* Line 1807 of yacc.c  */ 
     4735#line 1621 "fortran.y" 
     4736    {sprintf((yyval.na),"(%s)",(yyvsp[(2) - (3)].na)); strcpy(NamePrecision,(yyvsp[(2) - (3)].na));} 
     4737    break; 
     4738 
     4739  case 220: 
     4740/* Line 1807 of yacc.c  */ 
     4741#line 1623 "fortran.y" 
     4742    {sprintf((yyval.na),"(KIND=%s)",(yyvsp[(4) - (5)].na)); strcpy(NamePrecision,(yyvsp[(4) - (5)].na));} 
     4743    break; 
     4744 
     4745  case 221: 
     4746/* Line 1807 of yacc.c  */ 
     4747#line 1625 "fortran.y" 
     4748    {sprintf((yyval.na),"*%s",(yyvsp[(2) - (2)].na));strcpy(NamePrecision,(yyvsp[(2) - (2)].na));} 
     4749    break; 
     4750 
     4751  case 223: 
     4752/* Line 1807 of yacc.c  */ 
     4753#line 1633 "fortran.y" 
     4754    {sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na));} 
     4755    break; 
     4756 
     4757  case 225: 
     4758/* Line 1807 of yacc.c  */ 
     4759#line 1639 "fortran.y" 
     4760    {sprintf((yyval.na),"%s_%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na));} 
     4761    break; 
     4762 
     4763  case 229: 
     4764/* Line 1807 of yacc.c  */ 
     4765#line 1662 "fortran.y" 
     4766    {sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na));} 
     4767    break; 
     4768 
     4769  case 231: 
     4770/* Line 1807 of yacc.c  */ 
     4771#line 1668 "fortran.y" 
     4772    {sprintf((yyval.na),"%s_%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na));} 
     4773    break; 
     4774 
     4775  case 232: 
     4776/* Line 1807 of yacc.c  */ 
     4777#line 1675 "fortran.y" 
     4778    {sprintf((yyval.na),"(%s,%s)",(yyvsp[(2) - (5)].na),(yyvsp[(4) - (5)].na));} 
     4779    break; 
     4780 
     4781  case 240: 
     4782/* Line 1807 of yacc.c  */ 
     4783#line 1693 "fortran.y" 
     4784    {char_length_toreset = 1;} 
     4785    break; 
     4786 
     4787  case 241: 
     4788/* Line 1807 of yacc.c  */ 
     4789#line 1697 "fortran.y" 
     4790    {strcpy((yyval.na),"");} 
     4791    break; 
     4792 
     4793  case 242: 
     4794/* Line 1807 of yacc.c  */ 
     4795#line 1699 "fortran.y" 
     4796    {strcpy((yyval.na),"");} 
     4797    break; 
     4798 
     4799  case 248: 
     4800/* Line 1807 of yacc.c  */ 
     4801#line 1712 "fortran.y" 
     4802    {strcpy(CharacterSize,(yyvsp[(2) - (3)].na));} 
     4803    break; 
     4804 
     4805  case 249: 
     4806/* Line 1807 of yacc.c  */ 
     4807#line 1714 "fortran.y" 
     4808    {strcpy(CharacterSize,(yyvsp[(4) - (5)].na));} 
     4809    break; 
     4810 
     4811  case 252: 
     4812/* Line 1807 of yacc.c  */ 
     4813#line 1721 "fortran.y" 
     4814    {c_star=1; strcpy(CharacterSize,(yyvsp[(2) - (3)].na));} 
     4815    break; 
     4816 
     4817  case 253: 
     4818/* Line 1807 of yacc.c  */ 
     4819#line 1723 "fortran.y" 
     4820    {c_selectorgiven = 1; strcpy(c_selectorname,(yyvsp[(1) - (1)].na));} 
     4821    break; 
     4822 
     4823  case 259: 
     4824/* Line 1807 of yacc.c  */ 
     4825#line 1738 "fortran.y" 
     4826    { inside_type_declare = 1;} 
     4827    break; 
     4828 
     4829  case 260: 
     4830/* Line 1807 of yacc.c  */ 
     4831#line 1739 "fortran.y" 
     4832    { inside_type_declare = 0;} 
     4833    break; 
     4834 
     4835  case 292: 
     4836/* Line 1807 of yacc.c  */ 
     4837#line 1814 "fortran.y" 
     4838    { 
     4839            PublicDeclare = 0; 
     4840            PrivateDeclare = 0; 
     4841            ExternalDeclare = 0; 
     4842            strcpy(NamePrecision,""); 
     4843            c_star = 0; 
     4844            InitialValueGiven = 0 ; 
     4845            strcpy(IntentSpec,""); 
     4846            VariableIsParameter =  0 ; 
     4847            Allocatabledeclare = 0 ; 
     4848            Targetdeclare = 0 ; 
     4849            SaveDeclare = 0; 
     4850            pointerdeclare = 0; 
     4851            optionaldeclare = 0 ; 
     4852            dimsgiven=0; 
     4853            c_selectorgiven=0; 
     4854            strcpy(nameinttypename,""); 
     4855            strcpy(c_selectorname,""); 
     4856            GlobalDeclarationType = 0; 
     4857         } 
     4858    break; 
     4859 
     4860  case 302: 
     4861/* Line 1807 of yacc.c  */ 
     4862#line 1857 "fortran.y" 
     4863    {strcpy(my_dim.last,"");} 
     4864    break; 
     4865 
     4866  case 303: 
     4867/* Line 1807 of yacc.c  */ 
     4868#line 1862 "fortran.y" 
     4869    {strcpy(NamePrecision,(yyvsp[(1) - (1)].na));} 
     4870    break; 
     4871 
     4872  case 318: 
     4873/* Line 1807 of yacc.c  */ 
     4874#line 1897 "fortran.y" 
     4875    { sprintf((yyval.na),"(/%s/)",(yyvsp[(2) - (3)].na));} 
     4876    break; 
     4877 
     4878  case 319: 
     4879/* Line 1807 of yacc.c  */ 
     4880#line 1899 "fortran.y" 
     4881    { sprintf((yyval.na),"[%s]",(yyvsp[(2) - (3)].na)); } 
     4882    break; 
     4883 
     4884  case 324: 
     4885/* Line 1807 of yacc.c  */ 
     4886#line 1927 "fortran.y" 
     4887    {sprintf((yyval.na),"%s,%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na));} 
     4888    break; 
     4889 
     4890  case 327: 
     4891/* Line 1807 of yacc.c  */ 
     4892#line 1937 "fortran.y" 
     4893    {sprintf((yyval.na),"(%s,%s)",(yyvsp[(2) - (5)].na),(yyvsp[(4) - (5)].na));} 
     4894    break; 
     4895 
     4896  case 328: 
     4897/* Line 1807 of yacc.c  */ 
     4898#line 1942 "fortran.y" 
     4899    {sprintf((yyval.na),"%s=%s,%s",(yyvsp[(1) - (5)].na),(yyvsp[(3) - (5)].na),(yyvsp[(5) - (5)].na));} 
     4900    break; 
     4901 
     4902  case 329: 
     4903/* Line 1807 of yacc.c  */ 
     4904#line 1944 "fortran.y" 
     4905    {sprintf((yyval.na),"%s=%s,%s,%s",(yyvsp[(1) - (7)].na),(yyvsp[(3) - (7)].na),(yyvsp[(5) - (7)].na),(yyvsp[(7) - (7)].na));} 
     4906    break; 
     4907 
     4908  case 331: 
     4909/* Line 1807 of yacc.c  */ 
     4910#line 1952 "fortran.y" 
     4911    {indeclaration=1;} 
     4912    break; 
     4913 
     4914  case 332: 
     4915/* Line 1807 of yacc.c  */ 
     4916#line 1953 "fortran.y" 
     4917    { 
     4918            /* if the variable is a parameter we can suppose that is*/ 
     4919            /*    value is the same on each grid. It is not useless */ 
     4920            /*    to create a copy of it on each grid               */ 
     4921            if ( ! inside_type_declare ) 
     4922            { 
     4923                pos_end = setposcur(); 
     4924                //printf("POS = %d %d\n",pos_cur_decl,pos_end); 
     4925                RemoveWordSET_0(fortran_out,pos_cur_decl,pos_end-pos_cur_decl); 
     4926                ReWriteDeclarationAndAddTosubroutine_01((yyvsp[(4) - (4)].l)); 
     4927                pos_cur_decl = setposcur(); 
     4928                if ( firstpass == 0 && GlobalDeclaration == 0 
     4929                                    && insubroutinedeclare == 0 ) 
     4930                { 
     4931                    fprintf(fortran_out,"\n#include \"Module_Declar_%s.h\"\n", curmodulename); 
     4932                    sprintf(ligne, "Module_Declar_%s.h", curmodulename); 
     4933                    module_declar = open_for_write(ligne); 
     4934                    GlobalDeclaration = 1 ; 
     4935                    pos_cur_decl = setposcur(); 
     4936                } 
     4937 
     4938                if ( firstpass ) 
     4939                { 
     4940                    Add_Globliste_1((yyvsp[(4) - (4)].l)); 
     4941                    if ( insubroutinedeclare ) 
     4942                    { 
     4943                        if ( pointerdeclare ) Add_Pointer_Var_From_List_1((yyvsp[(4) - (4)].l)); 
     4944                        Add_Parameter_Var_1((yyvsp[(4) - (4)].l)); 
     4945                    } 
     4946                    else 
     4947                        Add_GlobalParameter_Var_1((yyvsp[(4) - (4)].l)); 
     4948 
     4949                    /* If there's a SAVE declaration in module's subroutines we should    */ 
     4950                    /*    remove it from the subroutines declaration and add it in the    */ 
     4951                    /*    global declarations                                             */ 
     4952                                         
     4953                    if ( aftercontainsdeclare && SaveDeclare ) 
     4954                    { 
     4955                        if ( inmodulemeet ) Add_SubroutineDeclarationSave_Var_1((yyvsp[(4) - (4)].l)); 
     4956                        else                Add_Save_Var_dcl_1((yyvsp[(4) - (4)].l)); 
     4957                    } 
     4958                } 
     4959            } 
     4960            indeclaration = 0; 
     4961            PublicDeclare = 0; 
     4962            PrivateDeclare = 0; 
     4963            ExternalDeclare = 0; 
     4964            strcpy(NamePrecision,""); 
     4965            c_star = 0; 
     4966            InitialValueGiven = 0 ; 
     4967            strcpy(IntentSpec,""); 
     4968            VariableIsParameter =  0 ; 
     4969            Allocatabledeclare = 0 ; 
     4970            Targetdeclare = 0 ; 
     4971            SaveDeclare = 0; 
     4972            pointerdeclare = 0; 
     4973            optionaldeclare = 0 ; 
     4974            dimsgiven=0; 
     4975            c_selectorgiven=0; 
     4976            strcpy(nameinttypename,""); 
     4977            strcpy(c_selectorname,""); 
     4978            strcpy(DeclType,""); 
     4979            GlobalDeclarationType = 0; 
     4980        } 
     4981    break; 
     4982 
     4983  case 341: 
     4984/* Line 1807 of yacc.c  */ 
     4985#line 2036 "fortran.y" 
     4986    { Allocatabledeclare = 1; } 
     4987    break; 
     4988 
     4989  case 342: 
     4990/* Line 1807 of yacc.c  */ 
     4991#line 2037 "fortran.y" 
     4992    {in_complex_literal=0;} 
     4993    break; 
     4994 
     4995  case 343: 
     4996/* Line 1807 of yacc.c  */ 
     4997#line 2038 "fortran.y" 
     4998    { dimsgiven = 1; curdim = (yyvsp[(4) - (5)].d); } 
     4999    break; 
     5000 
     5001  case 344: 
     5002/* Line 1807 of yacc.c  */ 
     5003#line 2040 "fortran.y" 
     5004    { ExternalDeclare = 1; } 
     5005    break; 
     5006 
     5007  case 345: 
     5008/* Line 1807 of yacc.c  */ 
     5009#line 2041 "fortran.y" 
     5010    {in_complex_literal=0;} 
     5011    break; 
     5012 
     5013  case 346: 
     5014/* Line 1807 of yacc.c  */ 
     5015#line 2042 "fortran.y" 
     5016    { strcpy(IntentSpec,(yyvsp[(4) - (5)].na)); } 
     5017    break; 
     5018 
     5019  case 348: 
     5020/* Line 1807 of yacc.c  */ 
     5021#line 2045 "fortran.y" 
     5022    { optionaldeclare = 1 ; } 
     5023    break; 
     5024 
     5025  case 349: 
     5026/* Line 1807 of yacc.c  */ 
     5027#line 2047 "fortran.y" 
     5028    {VariableIsParameter = 1; } 
     5029    break; 
     5030 
     5031  case 350: 
     5032/* Line 1807 of yacc.c  */ 
     5033#line 2049 "fortran.y" 
     5034    { pointerdeclare = 1 ; } 
     5035    break; 
     5036 
     5037  case 351: 
     5038/* Line 1807 of yacc.c  */ 
     5039#line 2051 "fortran.y" 
     5040    { SaveDeclare = 1 ; } 
     5041    break; 
     5042 
     5043  case 352: 
     5044/* Line 1807 of yacc.c  */ 
     5045#line 2053 "fortran.y" 
     5046    { Targetdeclare = 1; } 
     5047    break; 
     5048 
     5049  case 353: 
     5050/* Line 1807 of yacc.c  */ 
     5051#line 2058 "fortran.y" 
     5052    {(yyval.l)=insertvar(NULL,(yyvsp[(1) - (1)].v));} 
     5053    break; 
     5054 
     5055  case 354: 
     5056/* Line 1807 of yacc.c  */ 
     5057#line 2060 "fortran.y" 
     5058    {(yyval.l)=insertvar((yyvsp[(1) - (3)].l),(yyvsp[(3) - (3)].v));} 
     5059    break; 
     5060 
     5061  case 355: 
     5062/* Line 1807 of yacc.c  */ 
     5063#line 2065 "fortran.y" 
     5064    { 
     5065            if ( ! inside_type_declare ) 
     5066            { 
     5067                if (dimsgiven == 1) curvar = createvar((yyvsp[(1) - (4)].na),curdim); 
     5068                else                curvar = createvar((yyvsp[(1) - (4)].na),(yyvsp[(2) - (4)].d)); 
     5069                CreateAndFillin_Curvar(DeclType, curvar); 
     5070                strcpy(curvar->v_typevar,DeclType); 
     5071                curvar->v_catvar = get_cat_var(curvar); 
     5072                 
     5073                if (!strcasecmp(DeclType,"character")) 
     5074                { 
     5075                    if (c_selectorgiven == 1) 
     5076                    { 
     5077                        Save_Length(c_selectorname,1); 
     5078                        strcpy(curvar->v_dimchar,c_selectorname); 
     5079                    } 
     5080                } 
     5081            } 
     5082            strcpy(vallengspec,""); 
     5083            if (char_length_toreset == 1) 
     5084            { 
     5085            c_selectorgiven = 0; 
     5086            c_star = 0; 
     5087            strcpy(c_selectorname,""); 
     5088            strcpy(CharacterSize,""); 
     5089            char_length_toreset = 0; 
     5090            } 
     5091            (yyval.v)=curvar; 
     5092        } 
     5093    break; 
     5094 
     5095  case 358: 
     5096/* Line 1807 of yacc.c  */ 
     5097#line 2104 "fortran.y" 
     5098    {InitialValueGiven = 0; } 
     5099    break; 
     5100 
     5101  case 360: 
     5102/* Line 1807 of yacc.c  */ 
     5103#line 2110 "fortran.y" 
     5104    { 
     5105            if ( inside_type_declare ) break; 
     5106            strcpy(InitValue,(yyvsp[(2) - (2)].na)); 
     5107            InitialValueGiven = 1; 
     5108        } 
     5109    break; 
     5110 
     5111  case 361: 
     5112/* Line 1807 of yacc.c  */ 
     5113#line 2116 "fortran.y" 
     5114    { 
     5115            if ( inside_type_declare ) break; 
     5116            strcpy(InitValue,(yyvsp[(2) - (2)].na)); 
     5117            InitialValueGiven = 2; 
     5118        } 
     5119    break; 
     5120 
     5121  case 362: 
     5122/* Line 1807 of yacc.c  */ 
     5123#line 2122 "fortran.y" 
     5124    { 
     5125            if ( inside_type_declare ) break; 
     5126            strcpy(InitValue,(yyvsp[(2) - (2)].na)); 
     5127            InitialValueGiven = 2; 
     5128        } 
     5129    break; 
     5130 
     5131  case 364: 
     5132/* Line 1807 of yacc.c  */ 
     5133#line 2135 "fortran.y" 
     5134    {PublicDeclare = 1;  } 
     5135    break; 
     5136 
     5137  case 365: 
     5138/* Line 1807 of yacc.c  */ 
     5139#line 2137 "fortran.y" 
     5140    {PrivateDeclare = 1;  } 
     5141    break; 
     5142 
     5143  case 366: 
     5144/* Line 1807 of yacc.c  */ 
     5145#line 2141 "fortran.y" 
     5146    {(yyval.d)=NULL;} 
     5147    break; 
     5148 
     5149  case 367: 
     5150/* Line 1807 of yacc.c  */ 
     5151#line 2142 "fortran.y" 
     5152    {in_complex_literal=0;} 
     5153    break; 
     5154 
     5155  case 368: 
     5156/* Line 1807 of yacc.c  */ 
     5157#line 2143 "fortran.y" 
     5158    {(yyval.d)=(yyvsp[(3) - (4)].d);} 
     5159    break; 
     5160 
     5161  case 369: 
     5162/* Line 1807 of yacc.c  */ 
     5163#line 2148 "fortran.y" 
     5164    {(yyval.d)=(yyvsp[(1) - (1)].d);} 
     5165    break; 
     5166 
     5167  case 370: 
     5168/* Line 1807 of yacc.c  */ 
     5169#line 2150 "fortran.y" 
     5170    {(yyval.d)=(yyvsp[(1) - (1)].d);} 
     5171    break; 
     5172 
     5173  case 371: 
     5174/* Line 1807 of yacc.c  */ 
     5175#line 2152 "fortran.y" 
     5176    {(yyval.d)=(yyvsp[(1) - (1)].d);} 
     5177    break; 
     5178 
     5179  case 372: 
     5180/* Line 1807 of yacc.c  */ 
     5181#line 2154 "fortran.y" 
     5182    {(yyval.d)=(yyvsp[(1) - (1)].d);} 
     5183    break; 
     5184 
     5185  case 373: 
     5186/* Line 1807 of yacc.c  */ 
     5187#line 2156 "fortran.y" 
     5188    {(yyval.d)=(yyvsp[(1) - (1)].d);} 
     5189    break; 
     5190 
     5191  case 374: 
     5192/* Line 1807 of yacc.c  */ 
     5193#line 2160 "fortran.y" 
     5194    { 
     5195            (yyval.d) = (listdim*) NULL; 
     5196            if ( inside_type_declare ) break; 
     5197            if ( created_dimensionlist == 1 || agrif_parentcall == 1 )  (yyval.d)=insertdim(NULL,(yyvsp[(1) - (1)].dim1)); 
     5198        } 
     5199    break; 
     5200 
     5201  case 375: 
     5202/* Line 1807 of yacc.c  */ 
     5203#line 2166 "fortran.y" 
     5204    { 
     5205            (yyval.d) = (listdim*) NULL; 
     5206            if ( inside_type_declare ) break; 
     5207            if ( (!inside_type_declare) && created_dimensionlist == 1 ) (yyval.d)=insertdim((yyvsp[(1) - (3)].d),(yyvsp[(3) - (3)].dim1)); 
     5208        } 
     5209    break; 
     5210 
     5211  case 376: 
     5212/* Line 1807 of yacc.c  */ 
     5213#line 2175 "fortran.y" 
     5214    {strcpy((yyval.dim1).first,(yyvsp[(1) - (3)].na));  Save_Length((yyvsp[(1) - (3)].na),2); strcpy((yyval.dim1).last,(yyvsp[(3) - (3)].na)); Save_Length((yyvsp[(3) - (3)].na),1); } 
     5215    break; 
     5216 
     5217  case 377: 
     5218/* Line 1807 of yacc.c  */ 
     5219#line 2177 "fortran.y" 
     5220    {strcpy((yyval.dim1).first,"1"); strcpy((yyval.dim1).last,(yyvsp[(1) - (1)].na)); Save_Length((yyvsp[(1) - (1)].na),1);} 
     5221    break; 
     5222 
     5223  case 378: 
     5224/* Line 1807 of yacc.c  */ 
     5225#line 2182 "fortran.y" 
     5226    {strcpy((yyval.na),(yyvsp[(1) - (1)].na));} 
     5227    break; 
     5228 
     5229  case 380: 
     5230/* Line 1807 of yacc.c  */ 
     5231#line 2191 "fortran.y" 
     5232    { 
     5233            (yyval.d) = (listdim*) NULL; 
     5234            if ( inside_type_declare ) break; 
     5235            if ( created_dimensionlist == 1 || agrif_parentcall == 1 )  (yyval.d)=insertdim(NULL,(yyvsp[(1) - (1)].dim1)); 
     5236        } 
     5237    break; 
     5238 
     5239  case 381: 
     5240/* Line 1807 of yacc.c  */ 
     5241#line 2197 "fortran.y" 
     5242    { 
     5243            (yyval.d) = (listdim*) NULL; 
     5244            if ( inside_type_declare ) break; 
     5245            if ( (!inside_type_declare) && created_dimensionlist == 1 ) (yyval.d)=insertdim((yyvsp[(1) - (3)].d),(yyvsp[(3) - (3)].dim1)); 
     5246        } 
     5247    break; 
     5248 
     5249  case 382: 
     5250/* Line 1807 of yacc.c  */ 
     5251#line 2206 "fortran.y" 
     5252    { strcpy((yyval.dim1).first,"");  strcpy((yyval.dim1).last,"");  } 
     5253    break; 
     5254 
     5255  case 383: 
     5256/* Line 1807 of yacc.c  */ 
     5257#line 2208 "fortran.y" 
     5258    { strcpy((yyval.dim1).first,(yyvsp[(1) - (2)].na));  Save_Length((yyvsp[(1) - (2)].na),2); strcpy((yyval.dim1).last,""); } 
     5259    break; 
     5260 
     5261  case 384: 
     5262/* Line 1807 of yacc.c  */ 
     5263#line 2213 "fortran.y" 
     5264    { 
     5265            (yyval.d) = (listdim*) NULL; 
     5266            if ( inside_type_declare ) break; 
     5267            if ( created_dimensionlist == 1 || agrif_parentcall == 1 )  (yyval.d)=insertdim(NULL,(yyvsp[(1) - (1)].dim1)); 
     5268        } 
     5269    break; 
     5270 
     5271  case 385: 
     5272/* Line 1807 of yacc.c  */ 
     5273#line 2219 "fortran.y" 
     5274    { 
     5275            (yyval.d) = (listdim*) NULL; 
     5276            if ( inside_type_declare ) break; 
     5277            if ( (!inside_type_declare) && created_dimensionlist == 1 ) (yyval.d)=insertdim((yyvsp[(1) - (3)].d),(yyvsp[(3) - (3)].dim1)); 
     5278        } 
     5279    break; 
     5280 
     5281  case 386: 
     5282/* Line 1807 of yacc.c  */ 
     5283#line 2228 "fortran.y" 
     5284    { strcpy((yyval.dim1).first,"");  strcpy((yyval.dim1).last,"");  } 
     5285    break; 
     5286 
     5287  case 387: 
     5288/* Line 1807 of yacc.c  */ 
     5289#line 2233 "fortran.y" 
     5290    { 
     5291            (yyval.d) = (listdim*) NULL; 
     5292            if ( inside_type_declare ) break; 
     5293            if ( created_dimensionlist == 1 || agrif_parentcall == 1 )  
     5294            { 
     5295            if (!strcasecmp((yyvsp[(2) - (3)].na),"")) 
     5296            { 
     5297            strcpy(my_dim.first,"1"); 
     5298            } 
     5299            else 
     5300            { 
     5301            strcpy(my_dim.first,(yyvsp[(2) - (3)].na)); 
     5302            } 
     5303            strcpy(my_dim.last,"*"); 
     5304            (yyval.d)=insertdim((yyvsp[(1) - (3)].d),my_dim); 
     5305            strcpy(my_dim.first,""); 
     5306            strcpy(my_dim.last,""); 
     5307            } 
     5308        } 
     5309    break; 
     5310 
     5311  case 388: 
     5312/* Line 1807 of yacc.c  */ 
     5313#line 2255 "fortran.y" 
     5314    {(yyval.d) = (listdim *) NULL;} 
     5315    break; 
     5316 
     5317  case 389: 
     5318/* Line 1807 of yacc.c  */ 
     5319#line 2257 "fortran.y" 
     5320    {(yyval.d) = (yyvsp[(1) - (2)].d);} 
     5321    break; 
     5322 
     5323  case 390: 
     5324/* Line 1807 of yacc.c  */ 
     5325#line 2275 "fortran.y" 
     5326    {strcpy((yyval.na),"");} 
     5327    break; 
     5328 
     5329  case 391: 
     5330/* Line 1807 of yacc.c  */ 
     5331#line 2277 "fortran.y" 
     5332    {strcpy((yyval.na),(yyvsp[(1) - (2)].na));} 
     5333    break; 
     5334 
    58345335  case 395: 
    58355336/* Line 1807 of yacc.c  */ 
    5836 #line 1620 "fortran.y" 
     5337#line 2290 "fortran.y" 
     5338    { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
     5339    break; 
     5340 
     5341  case 396: 
     5342/* Line 1807 of yacc.c  */ 
     5343#line 2292 "fortran.y" 
     5344    { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
     5345    break; 
     5346 
     5347  case 397: 
     5348/* Line 1807 of yacc.c  */ 
     5349#line 2294 "fortran.y" 
     5350    { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
     5351    break; 
     5352 
     5353  case 398: 
     5354/* Line 1807 of yacc.c  */ 
     5355#line 2299 "fortran.y" 
     5356    { 
     5357            if ((firstpass == 0) && (PublicDeclare == 1)) 
     5358            { 
     5359                if ((yyvsp[(2) - (2)].lnn)) 
     5360                { 
     5361                    removeglobfromlist(&((yyvsp[(2) - (2)].lnn))); 
     5362                    pos_end = setposcur(); 
     5363                    RemoveWordSET_0(fortran_out,pos_cur,pos_end-pos_cur); 
     5364                    writelistpublic((yyvsp[(2) - (2)].lnn)); 
     5365                } 
     5366            } 
     5367     PublicDeclare = 0; 
     5368     PrivateDeclare = 0; 
     5369     } 
     5370    break; 
     5371 
     5372  case 400: 
     5373/* Line 1807 of yacc.c  */ 
     5374#line 2317 "fortran.y" 
     5375    {(yyval.lnn)=(listname *)NULL;} 
     5376    break; 
     5377 
     5378  case 401: 
     5379/* Line 1807 of yacc.c  */ 
     5380#line 2319 "fortran.y" 
     5381    {(yyval.lnn)=(yyvsp[(2) - (2)].lnn);} 
     5382    break; 
     5383 
     5384  case 402: 
     5385/* Line 1807 of yacc.c  */ 
     5386#line 2323 "fortran.y" 
     5387    {(yyval.lnn)=Insertname(NULL,(yyvsp[(1) - (1)].na),0);} 
     5388    break; 
     5389 
     5390  case 403: 
     5391/* Line 1807 of yacc.c  */ 
     5392#line 2325 "fortran.y" 
     5393    {(yyval.lnn)=Insertname((yyvsp[(1) - (3)].lnn),(yyvsp[(3) - (3)].na),0);} 
     5394    break; 
     5395 
     5396  case 406: 
     5397/* Line 1807 of yacc.c  */ 
     5398#line 2335 "fortran.y" 
     5399    { 
     5400            /* we should remove the data declaration                */ 
     5401            pos_end = setposcur(); 
     5402            RemoveWordSET_0(fortran_out,pos_curdata,pos_end-pos_curdata); 
     5403            if ( aftercontainsdeclare == 1  && firstpass == 0 ) 
     5404            { 
     5405                ReWriteDataStatement_0(fortran_out); 
     5406                pos_end = setposcur(); 
     5407            } 
     5408            Init_List_Data_Var(); 
     5409        } 
     5410    break; 
     5411 
     5412  case 412: 
     5413/* Line 1807 of yacc.c  */ 
     5414#line 2359 "fortran.y" 
     5415    { 
     5416            if (firstpass == 1)   
     5417            { 
     5418            Add_Data_Var_Names_01(&List_Data_Var,(yyvsp[(1) - (4)].l),(yyvsp[(3) - (4)].lnn)); 
     5419            } 
     5420            else                 Add_Data_Var_Names_01(&List_Data_Var_Cur,(yyvsp[(1) - (4)].l),(yyvsp[(3) - (4)].lnn)); 
     5421        } 
     5422    break; 
     5423 
     5424  case 413: 
     5425/* Line 1807 of yacc.c  */ 
     5426#line 2369 "fortran.y" 
     5427    { (yyval.l)=insertvar(NULL,(yyvsp[(1) - (1)].v)); } 
     5428    break; 
     5429 
     5430  case 414: 
     5431/* Line 1807 of yacc.c  */ 
     5432#line 2371 "fortran.y" 
     5433    { 
     5434     (yyval.l) = insertvar((yyvsp[(1) - (3)].l),(yyvsp[(3) - (3)].v)); 
     5435     } 
     5436    break; 
     5437 
     5438  case 415: 
     5439/* Line 1807 of yacc.c  */ 
     5440#line 2377 "fortran.y" 
     5441    {(yyval.lnn)=Insertname(NULL,(yyvsp[(1) - (1)].na),0);} 
     5442    break; 
     5443 
     5444  case 416: 
     5445/* Line 1807 of yacc.c  */ 
     5446#line 2379 "fortran.y" 
     5447    {(yyval.lnn) = Insertname((yyvsp[(1) - (3)].lnn),(yyvsp[(3) - (3)].na),1);   } 
     5448    break; 
     5449 
     5450  case 419: 
     5451/* Line 1807 of yacc.c  */ 
     5452#line 2389 "fortran.y" 
     5453    {printf("DOVARIABLE = %s %s %s\n",(yyvsp[(4) - (9)].na),(yyvsp[(6) - (9)].na),(yyvsp[(8) - (9)].na)); 
     5454     printf("AUTRE = %s %s\n",(yyvsp[(2) - (9)].l)->var->v_nomvar,(yyvsp[(2) - (9)].l)->var->v_initialvalue_array); 
     5455     Insertdoloop((yyvsp[(2) - (9)].l)->var,(yyvsp[(4) - (9)].na),(yyvsp[(6) - (9)].na),(yyvsp[(8) - (9)].na),""); 
     5456     (yyval.v)=(yyvsp[(2) - (9)].l)->var; 
     5457     } 
     5458    break; 
     5459 
     5460  case 420: 
     5461/* Line 1807 of yacc.c  */ 
     5462#line 2395 "fortran.y" 
     5463    { 
     5464     Insertdoloop((yyvsp[(2) - (11)].l)->var,(yyvsp[(4) - (11)].na),(yyvsp[(6) - (11)].na),(yyvsp[(8) - (11)].na),(yyvsp[(10) - (11)].na)); 
     5465     (yyval.v)=(yyvsp[(2) - (11)].l)->var; 
     5466     } 
     5467    break; 
     5468 
     5469  case 421: 
     5470/* Line 1807 of yacc.c  */ 
     5471#line 2402 "fortran.y" 
     5472    {(yyval.l)=insertvar(NULL,(yyvsp[(1) - (1)].v));} 
     5473    break; 
     5474 
     5475  case 422: 
     5476/* Line 1807 of yacc.c  */ 
     5477#line 2404 "fortran.y" 
     5478    {(yyval.l) = insertvar((yyvsp[(1) - (3)].l),(yyvsp[(3) - (3)].v));} 
     5479    break; 
     5480 
     5481  case 424: 
     5482/* Line 1807 of yacc.c  */ 
     5483#line 2410 "fortran.y" 
     5484    {(yyval.v)->v_initialvalue_array=Insertname((yyval.v)->v_initialvalue_array,my_dim.last,0); 
     5485     strcpy(my_dim.last,""); 
     5486     } 
     5487    break; 
     5488 
     5489  case 427: 
     5490/* Line 1807 of yacc.c  */ 
     5491#line 2423 "fortran.y" 
     5492    {sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na));} 
     5493    break; 
     5494 
     5495  case 428: 
     5496/* Line 1807 of yacc.c  */ 
     5497#line 2425 "fortran.y" 
     5498    {sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na));} 
     5499    break; 
     5500 
     5501  case 429: 
     5502/* Line 1807 of yacc.c  */ 
     5503#line 2427 "fortran.y" 
     5504    {sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na));} 
     5505    break; 
     5506 
     5507  case 435: 
     5508/* Line 1807 of yacc.c  */ 
     5509#line 2436 "fortran.y" 
     5510    {strcpy((yyval.na),"");} 
     5511    break; 
     5512 
     5513  case 436: 
     5514/* Line 1807 of yacc.c  */ 
     5515#line 2438 "fortran.y" 
     5516    {sprintf((yyval.na),"*%s",(yyvsp[(2) - (2)].na));} 
     5517    break; 
     5518 
     5519  case 445: 
     5520/* Line 1807 of yacc.c  */ 
     5521#line 2474 "fortran.y" 
     5522    {strcpy(my_dim.last,"");} 
     5523    break; 
     5524 
     5525  case 446: 
     5526/* Line 1807 of yacc.c  */ 
     5527#line 2478 "fortran.y" 
     5528    {positioninblock = 0; pos_curdimension = my_position_before;} 
     5529    break; 
     5530 
     5531  case 447: 
     5532/* Line 1807 of yacc.c  */ 
     5533#line 2480 "fortran.y" 
     5534    { 
     5535            /* if the variable is a parameter we can suppose that is   */ 
     5536            /*    value is the same on each grid. It is not useless to */ 
     5537            /*    create a copy of it on each grid                     */ 
     5538            if ( ! inside_type_declare ) 
     5539            { 
     5540                if ( firstpass ) 
     5541                { 
     5542                    Add_Globliste_1((yyvsp[(4) - (4)].l)); 
     5543                    /* if variableparamlists has been declared in a subroutine   */ 
     5544                    if ( insubroutinedeclare )     Add_Dimension_Var_1((yyvsp[(4) - (4)].l)); 
     5545                     
     5546                    /* Add it to the List_SubroutineDeclaration_Var list if not present */ 
     5547                    /* NB: if not done, a variable declared with DIMENSION but with no type given */ 
     5548                    /* will not be declared by the conv */ 
     5549                    ReWriteDeclarationAndAddTosubroutine_01((yyvsp[(4) - (4)].l)); 
     5550                } 
     5551                else 
     5552                { 
     5553                    pos_end = setposcur(); 
     5554                    RemoveWordSET_0(fortran_out,pos_curdimension,pos_end-pos_curdimension); 
     5555                    ReWriteDeclarationAndAddTosubroutine_01((yyvsp[(4) - (4)].l)); 
     5556                } 
     5557            } 
     5558            PublicDeclare = 0; 
     5559            PrivateDeclare = 0; 
     5560            ExternalDeclare = 0; 
     5561            strcpy(NamePrecision,""); 
     5562            c_star = 0; 
     5563            InitialValueGiven = 0 ; 
     5564            strcpy(IntentSpec,""); 
     5565            VariableIsParameter =  0 ; 
     5566            Allocatabledeclare = 0 ; 
     5567            Targetdeclare = 0 ; 
     5568            SaveDeclare = 0; 
     5569            pointerdeclare = 0; 
     5570            optionaldeclare = 0 ; 
     5571            dimsgiven=0; 
     5572            c_selectorgiven=0; 
     5573            strcpy(nameinttypename,""); 
     5574            strcpy(c_selectorname,""); 
     5575        } 
     5576    break; 
     5577 
     5578  case 449: 
     5579/* Line 1807 of yacc.c  */ 
     5580#line 2525 "fortran.y" 
     5581    {in_complex_literal = 0;} 
     5582    break; 
     5583 
     5584  case 450: 
     5585/* Line 1807 of yacc.c  */ 
     5586#line 2526 "fortran.y" 
     5587    { 
     5588        if ( inside_type_declare ) break; 
     5589        curvar = createvar((yyvsp[(1) - (5)].na),(yyvsp[(4) - (5)].d)); 
     5590        CreateAndFillin_Curvar("", curvar); 
     5591        curlistvar=insertvar(NULL, curvar); 
     5592        (yyval.l) = settype("",curlistvar); 
     5593        strcpy(vallengspec,""); 
     5594     } 
     5595    break; 
     5596 
     5597  case 451: 
     5598/* Line 1807 of yacc.c  */ 
     5599#line 2534 "fortran.y" 
     5600    {in_complex_literal = 0;} 
     5601    break; 
     5602 
     5603  case 452: 
     5604/* Line 1807 of yacc.c  */ 
     5605#line 2535 "fortran.y" 
     5606    { 
     5607        if ( inside_type_declare ) break; 
     5608        curvar = createvar((yyvsp[(3) - (7)].na),(yyvsp[(6) - (7)].d)); 
     5609        CreateAndFillin_Curvar("", curvar); 
     5610        curlistvar = insertvar((yyvsp[(1) - (7)].l), curvar); 
     5611        (yyval.l) = curlistvar; 
     5612        strcpy(vallengspec,""); 
     5613        } 
     5614    break; 
     5615 
     5616  case 453: 
     5617/* Line 1807 of yacc.c  */ 
     5618#line 2547 "fortran.y" 
     5619    { VariableIsParameter = 1; pos_curparameter = setposcur()-9; } 
     5620    break; 
     5621 
     5622  case 454: 
     5623/* Line 1807 of yacc.c  */ 
     5624#line 2548 "fortran.y" 
     5625    { 
     5626            if ( ! inside_type_declare ) 
     5627            { 
     5628                if ( firstpass ) 
     5629                { 
     5630                    if ( insubroutinedeclare )  Add_Parameter_Var_1((yyvsp[(4) - (5)].l)); 
     5631                    else                        Add_GlobalParameter_Var_1((yyvsp[(4) - (5)].l)); 
     5632                } 
     5633                else 
     5634                { 
     5635                    pos_end = setposcur(); 
     5636                    RemoveWordSET_0(fortran_out, pos_curparameter, pos_end-pos_curparameter); 
     5637                } 
     5638            } 
     5639            VariableIsParameter =  0 ; 
     5640        } 
     5641    break; 
     5642 
     5643  case 456: 
     5644/* Line 1807 of yacc.c  */ 
     5645#line 2568 "fortran.y" 
     5646    {(yyval.l)=insertvar(NULL,(yyvsp[(1) - (1)].v));} 
     5647    break; 
     5648 
     5649  case 457: 
     5650/* Line 1807 of yacc.c  */ 
     5651#line 2570 "fortran.y" 
     5652    {(yyval.l)=insertvar((yyvsp[(1) - (3)].l),(yyvsp[(3) - (3)].v));} 
     5653    break; 
     5654 
     5655  case 458: 
     5656/* Line 1807 of yacc.c  */ 
     5657#line 2575 "fortran.y" 
     5658    { 
     5659            if ( inside_type_declare ) break; 
     5660            curvar=(variable *) calloc(1,sizeof(variable)); 
     5661            Init_Variable(curvar); 
     5662            curvar->v_VariableIsParameter = 1; 
     5663            strcpy(curvar->v_nomvar,(yyvsp[(1) - (3)].na)); 
     5664            strcpy(curvar->v_subroutinename,subroutinename); 
     5665            strcpy(curvar->v_modulename,curmodulename); 
     5666            curvar->v_initialvalue=Insertname(curvar->v_initialvalue,(yyvsp[(3) - (3)].na),0); 
     5667            strcpy(curvar->v_commoninfile,cur_filename); 
     5668            Save_Length((yyvsp[(3) - (3)].na),14); 
     5669            (yyval.v) = curvar; 
     5670        } 
     5671    break; 
     5672 
     5673  case 459: 
     5674/* Line 1807 of yacc.c  */ 
     5675#line 2591 "fortran.y" 
     5676    {pos_cursave = my_position_before;} 
     5677    break; 
     5678 
     5679  case 460: 
     5680/* Line 1807 of yacc.c  */ 
     5681#line 2592 "fortran.y" 
     5682    { 
     5683     pos_end = setposcur(); 
     5684     RemoveWordSET_0(fortran_out,pos_cursave,pos_end-pos_cursave); 
     5685     } 
     5686    break; 
     5687 
     5688  case 468: 
     5689/* Line 1807 of yacc.c  */ 
     5690#line 2613 "fortran.y" 
     5691    {if ( ! inside_type_declare ) Add_Save_Var_1((yyvsp[(1) - (1)].na),(listdim*) NULL); } 
     5692    break; 
     5693 
     5694  case 472: 
     5695/* Line 1807 of yacc.c  */ 
     5696#line 2623 "fortran.y" 
     5697    {my_position = my_position_before;} 
     5698    break; 
     5699 
     5700  case 474: 
     5701/* Line 1807 of yacc.c  */ 
     5702#line 2629 "fortran.y" 
     5703    { 
     5704            if ( insubroutinedeclare == 1 ) 
     5705            { 
     5706                Add_ImplicitNoneSubroutine_1(); 
     5707                pos_end = setposcur(); 
     5708                RemoveWordSET_0(fortran_out,my_position,pos_end-my_position); 
     5709            } 
     5710        } 
     5711    break; 
     5712 
     5713  case 492: 
     5714/* Line 1807 of yacc.c  */ 
     5715#line 2681 "fortran.y" 
     5716    {in_complex_literal=0;} 
     5717    break; 
     5718 
     5719  case 499: 
     5720/* Line 1807 of yacc.c  */ 
     5721#line 2696 "fortran.y" 
     5722    { positioninblock = 0; pos_curcommon = my_position_before; indeclaration=1;} 
     5723    break; 
     5724 
     5725  case 500: 
     5726/* Line 1807 of yacc.c  */ 
     5727#line 2697 "fortran.y" 
     5728    { 
     5729            indeclaration = 0; 
     5730            if ( inside_type_declare ) break; 
     5731            pos_end = setposcur(); 
     5732            RemoveWordSET_0(fortran_out,pos_curcommon,pos_end-pos_curcommon); 
     5733     } 
     5734    break; 
     5735 
     5736  case 503: 
     5737/* Line 1807 of yacc.c  */ 
     5738#line 2708 "fortran.y" 
     5739    { 
     5740     if ( inside_type_declare ) break; 
     5741     sprintf(charusemodule,"%s",(yyvsp[(1) - (1)].na)); 
     5742     Add_NameOfCommon_1((yyvsp[(1) - (1)].na),subroutinename); 
     5743     } 
     5744    break; 
     5745 
     5746  case 504: 
     5747/* Line 1807 of yacc.c  */ 
     5748#line 2716 "fortran.y" 
     5749    { 
     5750            strcpy((yyval.na),""); 
     5751            positioninblock=0; 
     5752            strcpy(commonblockname,""); 
     5753        } 
     5754    break; 
     5755 
     5756  case 505: 
     5757/* Line 1807 of yacc.c  */ 
     5758#line 2722 "fortran.y" 
     5759    { 
     5760            strcpy((yyval.na),(yyvsp[(2) - (3)].na)); 
     5761            positioninblock=0; 
     5762            strcpy(commonblockname,(yyvsp[(2) - (3)].na)); 
     5763        } 
     5764    break; 
     5765 
     5766  case 510: 
     5767/* Line 1807 of yacc.c  */ 
     5768#line 2739 "fortran.y" 
     5769    {if ( ! inside_type_declare ) Add_Common_var_1(); } 
     5770    break; 
     5771 
     5772  case 511: 
     5773/* Line 1807 of yacc.c  */ 
     5774#line 2741 "fortran.y" 
     5775    {if ( ! inside_type_declare ) Add_Common_var_1(); } 
     5776    break; 
     5777 
     5778  case 512: 
     5779/* Line 1807 of yacc.c  */ 
     5780#line 2749 "fortran.y" 
     5781    { 
     5782            positioninblock = positioninblock + 1 ; 
     5783            strcpy(commonvar,(yyvsp[(1) - (1)].na)); 
     5784            commondim = (listdim*) NULL; 
     5785        } 
     5786    break; 
     5787 
     5788  case 513: 
     5789/* Line 1807 of yacc.c  */ 
     5790#line 2754 "fortran.y" 
     5791    {in_complex_literal=0;} 
     5792    break; 
     5793 
     5794  case 514: 
     5795/* Line 1807 of yacc.c  */ 
     5796#line 2755 "fortran.y" 
     5797    { 
     5798            positioninblock = positioninblock + 1 ; 
     5799            strcpy(commonvar,(yyvsp[(1) - (5)].na)); 
     5800            commondim = (yyvsp[(4) - (5)].d); 
     5801        } 
     5802    break; 
     5803 
     5804  case 518: 
     5805/* Line 1807 of yacc.c  */ 
     5806#line 2767 "fortran.y" 
     5807    {(yyval.v)=createvar((yyvsp[(1) - (1)].na),NULL);} 
     5808    break; 
     5809 
     5810  case 520: 
     5811/* Line 1807 of yacc.c  */ 
     5812#line 2779 "fortran.y" 
     5813    {if (strcmp(my_dim.last,"")) 
     5814       { 
     5815       (yyval.v)->v_initialvalue_array=Insertname(NULL,my_dim.last,0); 
     5816       } 
     5817       strcpy(my_dim.last,""); 
     5818       } 
     5819    break; 
     5820 
     5821  case 530: 
     5822/* Line 1807 of yacc.c  */ 
     5823#line 2821 "fortran.y" 
     5824    {sprintf((yyval.na),"%s(%s)",(yyvsp[(1) - (4)].na),(yyvsp[(3) - (4)].na));} 
     5825    break; 
     5826 
     5827  case 531: 
     5828/* Line 1807 of yacc.c  */ 
     5829#line 2823 "fortran.y" 
     5830    {sprintf((yyval.na),"%s(%s)",(yyvsp[(1) - (4)].na),(yyvsp[(3) - (4)].na));} 
     5831    break; 
     5832 
     5833  case 532: 
     5834/* Line 1807 of yacc.c  */ 
     5835#line 2838 "fortran.y" 
     5836    {sprintf((yyval.na),"%s:%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na));} 
     5837    break; 
     5838 
     5839  case 533: 
     5840/* Line 1807 of yacc.c  */ 
     5841#line 2843 "fortran.y" 
     5842    {sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].v)->v_nomvar,(yyvsp[(2) - (2)].na));} 
     5843    break; 
     5844 
     5845  case 534: 
     5846/* Line 1807 of yacc.c  */ 
     5847#line 2847 "fortran.y" 
     5848    {strcpy((yyval.na),"");} 
     5849    break; 
     5850 
     5851  case 535: 
     5852/* Line 1807 of yacc.c  */ 
     5853#line 2849 "fortran.y" 
     5854    {sprintf((yyval.na),"%s%%%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].v)->v_nomvar);} 
     5855    break; 
     5856 
     5857  case 536: 
     5858/* Line 1807 of yacc.c  */ 
     5859#line 2854 "fortran.y" 
     5860    {(yyval.v)=createvar((yyvsp[(1) - (1)].na),NULL);} 
     5861    break; 
     5862 
     5863  case 537: 
     5864/* Line 1807 of yacc.c  */ 
     5865#line 2855 "fortran.y" 
     5866    {in_complex_literal=0;} 
     5867    break; 
     5868 
     5869  case 538: 
     5870/* Line 1807 of yacc.c  */ 
     5871#line 2856 "fortran.y" 
     5872    {sprintf(ligne,"%s(%s)",(yyvsp[(1) - (5)].na),(yyvsp[(4) - (5)].na));(yyval.v)=createvar((yyvsp[(1) - (5)].na),NULL);strcpy(my_dim.last,(yyvsp[(4) - (5)].na));} 
     5873    break; 
     5874 
     5875  case 540: 
     5876/* Line 1807 of yacc.c  */ 
     5877#line 2872 "fortran.y" 
     5878    {strcpy(my_dim.last,"");} 
     5879    break; 
     5880 
     5881  case 541: 
     5882/* Line 1807 of yacc.c  */ 
     5883#line 2877 "fortran.y" 
     5884    {strcpy(my_dim.last,"");} 
     5885    break; 
     5886 
     5887  case 542: 
     5888/* Line 1807 of yacc.c  */ 
     5889#line 2882 "fortran.y" 
     5890    {strcpy(my_dim.last,"");} 
     5891    break; 
     5892 
     5893  case 543: 
     5894/* Line 1807 of yacc.c  */ 
     5895#line 2884 "fortran.y" 
     5896    {strcpy(my_dim.last,"");} 
     5897    break; 
     5898 
     5899  case 544: 
     5900/* Line 1807 of yacc.c  */ 
     5901#line 2890 "fortran.y" 
     5902    {strcpy((yyval.na),"");} 
     5903    break; 
     5904 
     5905  case 545: 
     5906/* Line 1807 of yacc.c  */ 
     5907#line 2892 "fortran.y" 
     5908    {strcpy((yyval.na),(yyvsp[(1) - (1)].na));} 
     5909    break; 
     5910 
     5911  case 546: 
     5912/* Line 1807 of yacc.c  */ 
     5913#line 2894 "fortran.y" 
     5914    {sprintf((yyval.na),"%s,%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na));} 
     5915    break; 
     5916 
     5917  case 547: 
     5918/* Line 1807 of yacc.c  */ 
     5919#line 2916 "fortran.y" 
     5920    {sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na));} 
     5921    break; 
     5922 
     5923  case 548: 
     5924/* Line 1807 of yacc.c  */ 
     5925#line 2918 "fortran.y" 
     5926    {strcpy((yyval.na),":");} 
     5927    break; 
     5928 
     5929  case 549: 
     5930/* Line 1807 of yacc.c  */ 
     5931#line 2920 "fortran.y" 
     5932    {sprintf((yyval.na),":%s",(yyvsp[(2) - (2)].na));} 
     5933    break; 
     5934 
     5935  case 550: 
     5936/* Line 1807 of yacc.c  */ 
     5937#line 2922 "fortran.y" 
     5938    {sprintf((yyval.na),": :%s",(yyvsp[(3) - (3)].na));} 
     5939    break; 
     5940 
     5941  case 551: 
     5942/* Line 1807 of yacc.c  */ 
     5943#line 2924 "fortran.y" 
     5944    {sprintf((yyval.na),":%s :%s",(yyvsp[(2) - (4)].na),(yyvsp[(4) - (4)].na));} 
     5945    break; 
     5946 
     5947  case 552: 
     5948/* Line 1807 of yacc.c  */ 
     5949#line 2926 "fortran.y" 
     5950    {sprintf((yyval.na),"::%s",(yyvsp[(2) - (2)].na));} 
     5951    break; 
     5952 
     5953  case 554: 
     5954/* Line 1807 of yacc.c  */ 
     5955#line 2929 "fortran.y" 
     5956    {sprintf((yyval.na),"%s=%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na));} 
     5957    break; 
     5958 
     5959  case 555: 
     5960/* Line 1807 of yacc.c  */ 
     5961#line 2931 "fortran.y" 
     5962    {sprintf((yyval.na),"%s=*%s",(yyvsp[(1) - (4)].na),(yyvsp[(4) - (4)].na));} 
     5963    break; 
     5964 
     5965  case 556: 
     5966/* Line 1807 of yacc.c  */ 
     5967#line 2933 "fortran.y" 
     5968    {sprintf((yyval.na),"*%s",(yyvsp[(2) - (2)].na));} 
     5969    break; 
     5970 
     5971  case 557: 
     5972/* Line 1807 of yacc.c  */ 
     5973#line 2937 "fortran.y" 
     5974    {strcpy((yyval.na),":");} 
     5975    break; 
     5976 
     5977  case 558: 
     5978/* Line 1807 of yacc.c  */ 
     5979#line 2939 "fortran.y" 
     5980    {sprintf((yyval.na),":%s",(yyvsp[(2) - (2)].na));} 
     5981    break; 
     5982 
     5983  case 559: 
     5984/* Line 1807 of yacc.c  */ 
     5985#line 2941 "fortran.y" 
     5986    {sprintf((yyval.na),": :%s",(yyvsp[(3) - (3)].na));} 
     5987    break; 
     5988 
     5989  case 560: 
     5990/* Line 1807 of yacc.c  */ 
     5991#line 2943 "fortran.y" 
     5992    {sprintf((yyval.na),":%s :%s",(yyvsp[(2) - (4)].na),(yyvsp[(4) - (4)].na));} 
     5993    break; 
     5994 
     5995  case 561: 
     5996/* Line 1807 of yacc.c  */ 
     5997#line 2945 "fortran.y" 
     5998    {sprintf((yyval.na),"::%s",(yyvsp[(2) - (2)].na));} 
     5999    break; 
     6000 
     6001  case 562: 
     6002/* Line 1807 of yacc.c  */ 
     6003#line 2947 "fortran.y" 
     6004    {strcpy((yyval.na),"");} 
     6005    break; 
     6006 
     6007  case 564: 
     6008/* Line 1807 of yacc.c  */ 
     6009#line 2965 "fortran.y" 
     6010    {in_complex_literal=0;} 
     6011    break; 
     6012 
     6013  case 565: 
     6014/* Line 1807 of yacc.c  */ 
     6015#line 2966 "fortran.y" 
     6016    {inallocate = 0;} 
     6017    break; 
     6018 
     6019  case 589: 
     6020/* Line 1807 of yacc.c  */ 
     6021#line 3036 "fortran.y" 
     6022    {in_complex_literal=0;} 
     6023    break; 
     6024 
     6025  case 590: 
     6026/* Line 1807 of yacc.c  */ 
     6027#line 3037 "fortran.y" 
     6028    {inallocate = 0;} 
     6029    break; 
     6030 
     6031  case 600: 
     6032/* Line 1807 of yacc.c  */ 
     6033#line 3067 "fortran.y" 
     6034    { 
     6035      strcpy((yyval.na),(yyvsp[(1) - (1)].v)->v_nomvar); 
     6036      if (strcasecmp(my_dim.last,"")) 
     6037      { 
     6038      strcat((yyval.na),"("); 
     6039      strcat((yyval.na),my_dim.last); 
     6040      strcat((yyval.na),")"); 
     6041      } 
     6042      } 
     6043    break; 
     6044 
     6045  case 604: 
     6046/* Line 1807 of yacc.c  */ 
     6047#line 3080 "fortran.y" 
     6048    { sprintf((yyval.na),"(%s)",(yyvsp[(2) - (3)].na));} 
     6049    break; 
     6050 
     6051  case 605: 
     6052/* Line 1807 of yacc.c  */ 
     6053#line 3085 "fortran.y" 
     6054    {strcpy(my_dim.last,"");} 
     6055    break; 
     6056 
     6057  case 607: 
     6058/* Line 1807 of yacc.c  */ 
     6059#line 3091 "fortran.y" 
     6060    {sprintf((yyval.na),"%s**%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na));} 
     6061    break; 
     6062 
     6063  case 609: 
     6064/* Line 1807 of yacc.c  */ 
     6065#line 3096 "fortran.y" 
     6066    { sprintf((yyval.na),"%s%s%s",(yyvsp[(1) - (3)].na),(yyvsp[(2) - (3)].na),(yyvsp[(3) - (3)].na)); } 
     6067    break; 
     6068 
     6069  case 611: 
     6070/* Line 1807 of yacc.c  */ 
     6071#line 3104 "fortran.y" 
     6072    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
     6073    break; 
     6074 
     6075  case 612: 
     6076/* Line 1807 of yacc.c  */ 
     6077#line 3106 "fortran.y" 
     6078    { sprintf((yyval.na),"%s%s%s",(yyvsp[(1) - (3)].na),(yyvsp[(2) - (3)].na),(yyvsp[(3) - (3)].na)); } 
     6079    break; 
     6080 
     6081  case 614: 
     6082/* Line 1807 of yacc.c  */ 
     6083#line 3109 "fortran.y" 
     6084    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
     6085    break; 
     6086 
     6087  case 616: 
     6088/* Line 1807 of yacc.c  */ 
     6089#line 3118 "fortran.y" 
     6090    {strcpy((yyval.na),"*");} 
     6091    break; 
     6092 
     6093  case 618: 
     6094/* Line 1807 of yacc.c  */ 
     6095#line 3124 "fortran.y" 
     6096    {strcpy((yyval.na),"+");} 
     6097    break; 
     6098 
     6099  case 619: 
     6100/* Line 1807 of yacc.c  */ 
     6101#line 3126 "fortran.y" 
     6102    {strcpy((yyval.na),"-");} 
     6103    break; 
     6104 
     6105  case 621: 
     6106/* Line 1807 of yacc.c  */ 
     6107#line 3132 "fortran.y" 
     6108    { sprintf((yyval.na),"%s%s%s",(yyvsp[(1) - (3)].na),(yyvsp[(2) - (3)].na),(yyvsp[(3) - (3)].na)); } 
     6109    break; 
     6110 
     6111  case 624: 
     6112/* Line 1807 of yacc.c  */ 
     6113#line 3141 "fortran.y" 
     6114    { sprintf((yyval.na),"%s%s%s",(yyvsp[(1) - (3)].na),(yyvsp[(2) - (3)].na),(yyvsp[(3) - (3)].na)); } 
     6115    break; 
     6116 
     6117  case 633: 
     6118/* Line 1807 of yacc.c  */ 
     6119#line 3154 "fortran.y" 
     6120    {strcpy((yyval.na),"<");} 
     6121    break; 
     6122 
     6123  case 635: 
     6124/* Line 1807 of yacc.c  */ 
     6125#line 3157 "fortran.y" 
     6126    {strcpy((yyval.na),">");} 
     6127    break; 
     6128 
     6129  case 638: 
     6130/* Line 1807 of yacc.c  */ 
     6131#line 3165 "fortran.y" 
     6132    { sprintf((yyval.na),"%s%s",(yyvsp[(1) - (2)].na),(yyvsp[(2) - (2)].na)); } 
     6133    break; 
     6134 
     6135  case 640: 
     6136/* Line 1807 of yacc.c  */ 
     6137#line 3172 "fortran.y" 
     6138    { sprintf((yyval.na),"%s%s%s",(yyvsp[(1) - (3)].na),(yyvsp[(2) - (3)].na),(yyvsp[(3) - (3)].na)); } 
     6139    break; 
     6140 
     6141  case 642: 
     6142/* Line 1807 of yacc.c  */ 
     6143#line 3179 "fortran.y" 
     6144    { sprintf((yyval.na),"%s%s%s",(yyvsp[(1) - (3)].na),(yyvsp[(2) - (3)].na),(yyvsp[(3) - (3)].na)); } 
     6145    break; 
     6146 
     6147  case 644: 
     6148/* Line 1807 of yacc.c  */ 
     6149#line 3185 "fortran.y" 
     6150    { sprintf((yyval.na),"%s%s%s",(yyvsp[(1) - (3)].na),(yyvsp[(2) - (3)].na),(yyvsp[(3) - (3)].na)); } 
     6151    break; 
     6152 
     6153  case 654: 
     6154/* Line 1807 of yacc.c  */ 
     6155#line 3221 "fortran.y" 
     6156    {strcpy((yyval.na),"");} 
     6157    break; 
     6158 
     6159  case 657: 
     6160/* Line 1807 of yacc.c  */ 
     6161#line 3230 "fortran.y" 
     6162    { 
     6163     strcpy((yyval.na),(yyvsp[(1) - (1)].na)); 
     6164     } 
     6165    break; 
     6166 
     6167  case 658: 
     6168/* Line 1807 of yacc.c  */ 
     6169#line 3237 "fortran.y" 
     6170    {strcpy((yyval.na),(yyvsp[(1) - (1)].na));} 
     6171    break; 
     6172 
     6173  case 786: 
     6174/* Line 1807 of yacc.c  */ 
     6175#line 3609 "fortran.y" 
     6176    {in_select_case_stmt++;} 
     6177    break; 
     6178 
     6179  case 788: 
     6180/* Line 1807 of yacc.c  */ 
     6181#line 3610 "fortran.y" 
     6182    {in_select_case_stmt++;} 
     6183    break; 
     6184 
     6185  case 792: 
     6186/* Line 1807 of yacc.c  */ 
     6187#line 3619 "fortran.y" 
     6188    {in_select_case_stmt--;} 
     6189    break; 
     6190 
     6191  case 794: 
     6192/* Line 1807 of yacc.c  */ 
     6193#line 3620 "fortran.y" 
     6194    {in_select_case_stmt--;} 
     6195    break; 
     6196 
     6197  case 796: 
     6198/* Line 1807 of yacc.c  */ 
     6199#line 3625 "fortran.y" 
     6200    {in_complex_literal=0;} 
     6201    break; 
     6202 
     6203  case 820: 
     6204/* Line 1807 of yacc.c  */ 
     6205#line 3688 "fortran.y" 
     6206    {close_or_connect = 1;} 
     6207    break; 
     6208 
     6209  case 821: 
     6210/* Line 1807 of yacc.c  */ 
     6211#line 3688 "fortran.y" 
     6212    {close_or_connect = 0;} 
     6213    break; 
     6214 
     6215  case 838: 
     6216/* Line 1807 of yacc.c  */ 
     6217#line 3718 "fortran.y" 
     6218    {close_or_connect = 1;} 
     6219    break; 
     6220 
     6221  case 839: 
     6222/* Line 1807 of yacc.c  */ 
     6223#line 3719 "fortran.y" 
     6224    {close_or_connect = 0;} 
     6225    break; 
     6226 
     6227  case 905: 
     6228/* Line 1807 of yacc.c  */ 
     6229#line 3852 "fortran.y" 
     6230    {in_inquire=0;} 
     6231    break; 
     6232 
     6233  case 907: 
     6234/* Line 1807 of yacc.c  */ 
     6235#line 3855 "fortran.y" 
     6236    {in_inquire=0;} 
     6237    break; 
     6238 
     6239  case 909: 
     6240/* Line 1807 of yacc.c  */ 
     6241#line 3859 "fortran.y" 
     6242    {in_inquire=1;} 
     6243    break; 
     6244 
     6245  case 924: 
     6246/* Line 1807 of yacc.c  */ 
     6247#line 3886 "fortran.y" 
     6248    {pos_endsubroutine=setposcur();} 
     6249    break; 
     6250 
     6251  case 928: 
     6252/* Line 1807 of yacc.c  */ 
     6253#line 3895 "fortran.y" 
     6254    { 
     6255            GlobalDeclaration = 0; 
     6256            strcpy(curmodulename,(yyvsp[(2) - (2)].na)); 
     6257            strcpy(subroutinename,""); 
     6258            Add_NameOfModule_1((yyvsp[(2) - (2)].na)); 
     6259            if ( inmoduledeclare == 0 ) 
     6260            { 
     6261                /* To know if there are in the module declaration    */ 
     6262                inmoduledeclare = 1; 
     6263                /* to know if a module has been met                  */ 
     6264                inmodulemeet = 1; 
     6265                /* to know if we are after the keyword contains      */ 
     6266                aftercontainsdeclare = 0 ; 
     6267            } 
     6268        } 
     6269    break; 
     6270 
     6271  case 930: 
     6272/* Line 1807 of yacc.c  */ 
     6273#line 3915 "fortran.y" 
     6274    { 
     6275            /* if we never meet the contains keyword               */ 
     6276            if ( firstpass == 0 ) 
     6277            { 
     6278                RemoveWordCUR_0(fortran_out, setposcur()-my_position);    // Remove word "end module" 
     6279                if ( inmoduledeclare && ! aftercontainsdeclare ) 
     6280                { 
     6281                    Write_Closing_Module(1); 
     6282                } 
     6283                fprintf(fortran_out,"\n      end module %s\n", curmodulename); 
     6284                if ( module_declar && insubroutinedeclare == 0 ) 
     6285                { 
     6286                    fclose(module_declar); 
     6287                } 
     6288            } 
     6289            inmoduledeclare = 0 ; 
     6290            inmodulemeet = 0 ; 
     6291            aftercontainsdeclare = 1; 
     6292            strcpy(curmodulename, ""); 
     6293            GlobalDeclaration = 0 ; 
     6294        } 
     6295    break; 
     6296 
     6297  case 945: 
     6298/* Line 1807 of yacc.c  */ 
     6299#line 3967 "fortran.y" 
     6300    {if (firstpass == 0 && oldfortran_out) pos_curuseold = setposcurname(oldfortran_out);} 
     6301    break; 
     6302 
     6303  case 946: 
     6304/* Line 1807 of yacc.c  */ 
     6305#line 3972 "fortran.y" 
     6306    { 
     6307            if ( firstpass ) 
     6308            { 
     6309                if ( insubroutinedeclare ) 
     6310                { 
     6311                    if ((yyvsp[(6) - (6)].lc)) { 
     6312                      Add_CouplePointed_Var_1((yyvsp[(5) - (6)].na),(yyvsp[(6) - (6)].lc)); 
     6313                      coupletmp = (yyvsp[(6) - (6)].lc); 
     6314                      strcpy(ligne,""); 
     6315                      while ( coupletmp ) 
     6316                      { 
     6317                        strcat(ligne, coupletmp->c_namevar); 
     6318                        strcat(ligne, " => "); 
     6319                        strcat(ligne, coupletmp->c_namepointedvar); 
     6320                        coupletmp = coupletmp->suiv; 
     6321                        if ( coupletmp ) strcat(ligne,","); 
     6322                      } 
     6323                      } 
     6324                  sprintf(charusemodule,"%s",(yyvsp[(5) - (6)].na)); 
     6325                } 
     6326                Add_NameOfModuleUsed_1((yyvsp[(5) - (6)].na)); 
     6327            } 
     6328            else 
     6329            { 
     6330                if ( insubroutinedeclare ) 
     6331                { 
     6332                  copyuse_0((yyvsp[(5) - (6)].na)); 
     6333                    } 
     6334 
     6335                if ( inmoduledeclare == 0 ) 
     6336                { 
     6337                    pos_end = setposcur(); 
     6338                    RemoveWordSET_0(fortran_out,my_position,pos_end-my_position); 
     6339                } 
     6340            } 
     6341    } 
     6342    break; 
     6343 
     6344  case 948: 
     6345/* Line 1807 of yacc.c  */ 
     6346#line 4010 "fortran.y" 
     6347    { 
     6348            if ( firstpass ) 
     6349            { 
     6350                if ( insubroutinedeclare ) 
     6351                { 
     6352                  if ((yyvsp[(9) - (9)].lc)) 
     6353                  { 
     6354                    Add_CouplePointed_Var_1((yyvsp[(5) - (9)].na),(yyvsp[(9) - (9)].lc)); 
     6355                    coupletmp = (yyvsp[(9) - (9)].lc); 
     6356                    strcpy(ligne,""); 
     6357                    while ( coupletmp ) 
     6358                    { 
     6359                        strcat(ligne,coupletmp->c_namevar); 
     6360                        if ( strcasecmp(coupletmp->c_namepointedvar,"") )   strcat(ligne," => "); 
     6361                        strcat(ligne,coupletmp->c_namepointedvar); 
     6362                        coupletmp = coupletmp->suiv; 
     6363                        if ( coupletmp ) strcat(ligne,","); 
     6364                    } 
     6365                  } 
     6366                  sprintf(charusemodule,"%s",(yyvsp[(5) - (9)].na)); 
     6367                } 
     6368                Add_NameOfModuleUsed_1((yyvsp[(5) - (9)].na)); 
     6369            } 
     6370            else 
     6371            { 
     6372                if ( insubroutinedeclare ) 
     6373                    copyuseonly_0((yyvsp[(5) - (9)].na)); 
     6374 
     6375                if ( inmoduledeclare == 0 ) 
     6376                { 
     6377                    pos_end = setposcur(); 
     6378                    RemoveWordSET_0(fortran_out,my_position,pos_end-my_position); 
     6379                    if ((yyvsp[(9) - (9)].lc)) 
     6380                    { 
     6381                    if (oldfortran_out)  variableisglobalinmodule((yyvsp[(9) - (9)].lc),(yyvsp[(5) - (9)].na),oldfortran_out,pos_curuseold); 
     6382                    } 
     6383                } 
     6384                else 
     6385                { 
     6386                  if ((yyvsp[(9) - (9)].lc)) 
     6387                  { 
     6388                    /* if we are in the module declare and if the    */ 
     6389                    /* onlylist is a list of global variable         */ 
     6390                    variableisglobalinmodule((yyvsp[(9) - (9)].lc), (yyvsp[(5) - (9)].na), fortran_out,my_position); 
     6391                  } 
     6392                } 
     6393            } 
     6394    } 
     6395    break; 
     6396 
     6397  case 953: 
     6398/* Line 1807 of yacc.c  */ 
     6399#line 4067 "fortran.y" 
     6400    {(yyval.lc)=NULL;} 
     6401    break; 
     6402 
     6403  case 954: 
     6404/* Line 1807 of yacc.c  */ 
     6405#line 4069 "fortran.y" 
     6406    {(yyval.lc)=(yyvsp[(1) - (1)].lc);} 
     6407    break; 
     6408 
     6409  case 960: 
     6410/* Line 1807 of yacc.c  */ 
     6411#line 4086 "fortran.y" 
     6412    { 
     6413            strcpy(subroutinename,(yyvsp[(2) - (2)].na)); 
     6414            insubroutinedeclare = 1; 
     6415            inprogramdeclare = 1; 
     6416            /* in the second step we should write the head of       */ 
     6417            /*    the subroutine sub_loop_<subroutinename>          */ 
     6418            if ( ! firstpass ) 
     6419                WriteBeginof_SubLoop(); 
     6420        } 
     6421    break; 
     6422 
     6423  case 962: 
     6424/* Line 1807 of yacc.c  */ 
     6425#line 4099 "fortran.y" 
     6426    {pos_endsubroutine=my_position_before;} 
     6427    break; 
     6428 
     6429  case 963: 
     6430/* Line 1807 of yacc.c  */ 
     6431#line 4100 "fortran.y" 
     6432    { 
     6433            insubroutinedeclare = 0; 
     6434            inprogramdeclare = 0; 
     6435            pos_cur = setposcur(); 
     6436            closeandcallsubloopandincludeit_0(3); 
     6437            functiondeclarationisdone = 0; 
     6438            strcpy(subroutinename,"");      
     6439     } 
     6440    break; 
     6441 
     6442  case 970: 
     6443/* Line 1807 of yacc.c  */ 
     6444#line 4122 "fortran.y" 
     6445    { 
     6446    (yyval.lc)=NULL; 
     6447    } 
     6448    break; 
     6449 
     6450  case 971: 
     6451/* Line 1807 of yacc.c  */ 
     6452#line 4126 "fortran.y" 
     6453    { 
     6454    (yyval.lc)=(yyvsp[(2) - (2)].lc); 
     6455    } 
     6456    break; 
     6457 
     6458  case 972: 
     6459/* Line 1807 of yacc.c  */ 
     6460#line 4132 "fortran.y" 
     6461    { 
     6462     (yyval.lc)=(yyvsp[(1) - (1)].lc); 
     6463     } 
     6464    break; 
     6465 
     6466  case 973: 
     6467/* Line 1807 of yacc.c  */ 
     6468#line 4136 "fortran.y" 
     6469    { 
     6470     /* insert the variable in the list $1                 */ 
     6471     (yyvsp[(3) - (3)].lc)->suiv = (yyvsp[(1) - (3)].lc); 
     6472     (yyval.lc)=(yyvsp[(3) - (3)].lc); 
     6473     } 
     6474    break; 
     6475 
     6476  case 974: 
     6477/* Line 1807 of yacc.c  */ 
     6478#line 4145 "fortran.y" 
     6479    { 
     6480            coupletmp = (listcouple *) calloc(1,sizeof(listcouple)); 
     6481            strcpy(coupletmp->c_namevar,(yyvsp[(1) - (3)].na)); 
     6482            strcpy(coupletmp->c_namepointedvar,(yyvsp[(3) - (3)].na)); 
     6483            coupletmp->suiv = NULL; 
     6484            (yyval.lc) = coupletmp; 
     6485        } 
     6486    break; 
     6487 
     6488  case 975: 
     6489/* Line 1807 of yacc.c  */ 
     6490#line 4155 "fortran.y" 
     6491    {(yyval.lc)=(yyvsp[(1) - (1)].lc);} 
     6492    break; 
     6493 
     6494  case 976: 
     6495/* Line 1807 of yacc.c  */ 
     6496#line 4157 "fortran.y" 
     6497    { 
     6498            /* insert the variable in the list $1                 */ 
     6499            (yyvsp[(3) - (3)].lc)->suiv = (yyvsp[(1) - (3)].lc); 
     6500            (yyval.lc) = (yyvsp[(3) - (3)].lc); 
     6501        } 
     6502    break; 
     6503 
     6504  case 977: 
     6505/* Line 1807 of yacc.c  */ 
     6506#line 4166 "fortran.y" 
     6507    { 
     6508            coupletmp = (listcouple *)calloc(1,sizeof(listcouple)); 
     6509            strcpy(coupletmp->c_namevar,(yyvsp[(1) - (1)].na)); 
     6510            strcpy(coupletmp->c_namepointedvar,""); 
     6511            coupletmp->suiv = NULL; 
     6512            (yyval.lc) = coupletmp; 
     6513        } 
     6514    break; 
     6515 
     6516  case 978: 
     6517/* Line 1807 of yacc.c  */ 
     6518#line 4174 "fortran.y" 
     6519    { 
     6520            coupletmp = (listcouple *)calloc(1,sizeof(listcouple)); 
     6521            strcpy(coupletmp->c_namevar,(yyvsp[(1) - (1)].na)); 
     6522            strcpy(coupletmp->c_namepointedvar,""); 
     6523            coupletmp->suiv = NULL; 
     6524            (yyval.lc) = coupletmp; 
     6525        } 
     6526    break; 
     6527 
     6528  case 979: 
     6529/* Line 1807 of yacc.c  */ 
     6530#line 4182 "fortran.y" 
     6531    { 
     6532     (yyval.lc)=(yyvsp[(1) - (1)].lc); 
     6533     pointedvar = 1; 
     6534      Add_UsedInSubroutine_Var_1((yyvsp[(1) - (1)].lc)->c_namevar); 
     6535     } 
     6536    break; 
     6537 
     6538  case 992: 
     6539/* Line 1807 of yacc.c  */ 
     6540#line 4222 "fortran.y" 
     6541    {in_complex_literal=0;} 
     6542    break; 
     6543 
     6544  case 993: 
     6545/* Line 1807 of yacc.c  */ 
     6546#line 4223 "fortran.y" 
     6547    {sprintf((yyval.na),"%s(%s)",(yyvsp[(1) - (5)].na),(yyvsp[(4) - (5)].na));} 
     6548    break; 
     6549 
     6550  case 994: 
     6551/* Line 1807 of yacc.c  */ 
     6552#line 4229 "fortran.y" 
     6553    { 
     6554            inagrifcallargument = 0 ; 
     6555            incalldeclare=0; 
     6556            if ( oldfortran_out && (callagrifinitgrids == 1) && (firstpass == 0) ) 
     6557            { 
     6558                pos_end = setposcur(); 
     6559                RemoveWordSET_0(fortran_out,pos_curcall,pos_end-pos_curcall); 
     6560                strcpy(subofagrifinitgrids,subroutinename); 
     6561            } 
     6562            Instanciation_0(sameagrifname); 
     6563        } 
     6564    break; 
     6565 
     6566  case 996: 
     6567/* Line 1807 of yacc.c  */ 
     6568#line 4242 "fortran.y" 
     6569    { 
     6570            inagrifcallargument = 0 ; 
     6571            incalldeclare=0; 
     6572            if ( oldfortran_out && (callagrifinitgrids == 1) && (firstpass == 0) ) 
     6573            { 
     6574                pos_end = setposcur(); 
     6575                RemoveWordSET_0(fortran_out,pos_curcall,pos_end-pos_curcall); 
     6576                strcpy(subofagrifinitgrids,subroutinename); 
     6577            } 
     6578            Instanciation_0(sameagrifname); 
     6579        } 
     6580    break; 
     6581 
     6582  case 998: 
     6583/* Line 1807 of yacc.c  */ 
     6584#line 4254 "fortran.y" 
     6585    {in_complex_literal=0;} 
     6586    break; 
     6587 
     6588  case 999: 
     6589/* Line 1807 of yacc.c  */ 
     6590#line 4255 "fortran.y" 
     6591    { 
     6592            inagrifcallargument = 0 ; 
     6593            incalldeclare=0; 
     6594            if ( oldfortran_out && (callagrifinitgrids == 1) && (firstpass == 0) ) 
     6595            { 
     6596                pos_end = setposcur(); 
     6597                RemoveWordSET_0(fortran_out,pos_curcall,pos_end-pos_curcall); 
     6598                strcpy(subofagrifinitgrids,subroutinename); 
     6599            } 
     6600            Instanciation_0(sameagrifname); 
     6601        } 
     6602    break; 
     6603 
     6604  case 1001: 
     6605/* Line 1807 of yacc.c  */ 
     6606#line 4269 "fortran.y" 
     6607    {pos_curcall=my_position_before-strlen((yyvsp[(1) - (2)].na))-4;} 
     6608    break; 
     6609 
     6610  case 1002: 
     6611/* Line 1807 of yacc.c  */ 
     6612#line 4270 "fortran.y" 
     6613    { 
     6614            if (!strcasecmp((yyvsp[(4) - (4)].na),"MPI_Init") )    callmpiinit = 1; 
     6615            else                                callmpiinit = 0; 
     6616 
     6617            if (!strcasecmp((yyvsp[(4) - (4)].na),"Agrif_Init_Grids") ) 
     6618            { 
     6619                callagrifinitgrids = 1; 
     6620                strcpy(meetagrifinitgrids,subroutinename); 
     6621            } 
     6622            else 
     6623            { 
     6624                callagrifinitgrids = 0; 
     6625            } 
     6626            if ( Vartonumber((yyvsp[(4) - (4)].na)) == 1 ) 
     6627            { 
     6628                incalldeclare = 0; 
     6629                inagrifcallargument = 0 ; 
     6630                Add_SubroutineWhereAgrifUsed_1(subroutinename, curmodulename); 
     6631            } 
     6632        } 
     6633    break; 
     6634 
     6635  case 1007: 
     6636/* Line 1807 of yacc.c  */ 
     6637#line 4301 "fortran.y" 
     6638    {sprintf((yyval.na),"%s,%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na));} 
     6639    break; 
     6640 
     6641  case 1008: 
     6642/* Line 1807 of yacc.c  */ 
     6643#line 4306 "fortran.y" 
     6644    { 
     6645            if ( callmpiinit == 1 ) 
     6646            { 
     6647                strcpy(mpiinitvar,(yyvsp[(1) - (1)].na)); 
     6648                if ( firstpass == 1 )  Add_UsedInSubroutine_Var_1 (mpiinitvar); 
     6649            } 
     6650        } 
     6651    break; 
     6652 
     6653  case 1009: 
     6654/* Line 1807 of yacc.c  */ 
     6655#line 4314 "fortran.y" 
     6656    {sprintf((yyval.na),"%s = %s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na)); 
     6657                 if ( callmpiinit == 1 ) 
     6658            { 
     6659                strcpy(mpiinitvar,(yyvsp[(3) - (3)].na)); 
     6660                if ( firstpass == 1 )  Add_UsedInSubroutine_Var_1 (mpiinitvar); 
     6661            } 
     6662            } 
     6663    break; 
     6664 
     6665  case 1011: 
     6666/* Line 1807 of yacc.c  */ 
     6667#line 4326 "fortran.y" 
     6668    { 
     6669     strcpy((yyval.na),(yyvsp[(1) - (1)].v)->v_nomvar); 
     6670     if ((yyvsp[(1) - (1)].v)->v_initialvalue_array) 
     6671     { 
     6672     strcat((yyval.na),"("); 
     6673     strcat((yyval.na),(yyvsp[(1) - (1)].v)->v_initialvalue_array->n_name); 
     6674     strcat((yyval.na),")"); 
     6675     } 
     6676     } 
     6677    break; 
     6678 
     6679  case 1013: 
     6680/* Line 1807 of yacc.c  */ 
     6681#line 4338 "fortran.y" 
     6682    {isrecursive = 0;} 
     6683    break; 
     6684 
     6685  case 1017: 
     6686/* Line 1807 of yacc.c  */ 
     6687#line 4349 "fortran.y" 
     6688    {isrecursive = 0; functiondeclarationisdone = 1;} 
     6689    break; 
     6690 
     6691  case 1018: 
     6692/* Line 1807 of yacc.c  */ 
     6693#line 4351 "fortran.y" 
     6694    {isrecursive = 0;} 
     6695    break; 
     6696 
     6697  case 1019: 
     6698/* Line 1807 of yacc.c  */ 
     6699#line 4353 "fortran.y" 
     6700    {isrecursive = 1;} 
     6701    break; 
     6702 
     6703  case 1021: 
     6704/* Line 1807 of yacc.c  */ 
     6705#line 4362 "fortran.y" 
     6706    {in_complex_literal=0;} 
     6707    break; 
     6708 
     6709  case 1022: 
     6710/* Line 1807 of yacc.c  */ 
     6711#line 4363 "fortran.y" 
     6712    { 
     6713            insubroutinedeclare = 1; 
     6714            suborfun = 0; 
     6715            /* we should to list of the subroutine argument the  */ 
     6716            /*    name of the function which has to be defined   */ 
     6717            if ( firstpass ) 
     6718            { 
     6719                Add_SubroutineArgument_Var_1((yyvsp[(6) - (8)].l)); 
     6720                if ( ! is_result_present ) 
     6721                    Add_FunctionType_Var_1((yyvsp[(3) - (8)].na)); 
     6722            } 
     6723            else 
     6724            /* in the second step we should write the head of    */ 
     6725            /*    the subroutine sub_loop_<subroutinename>       */ 
     6726               { 
     6727                if (todebug == 1) fprintf(fortran_out,"      !DEBUG: Avant Writebeginof subloop\n"); 
     6728                WriteBeginof_SubLoop(); 
     6729                if (todebug == 1) fprintf(fortran_out,"      !DEBUG: Apres Writebeginof subloop\n"); 
     6730                } 
     6731     } 
     6732    break; 
     6733 
     6734  case 1024: 
     6735/* Line 1807 of yacc.c  */ 
     6736#line 4387 "fortran.y" 
     6737    { 
     6738     if (strcmp(subroutinename,"")) 
     6739     { 
     6740     strcpy(old_subroutinename,subroutinename); // can occur in internal-subprogram 
     6741     old_oldfortran_out=oldfortran_out; 
     6742     } 
     6743     else 
     6744     { 
     6745     old_oldfortran_out=(FILE *)NULL; 
     6746     } 
     6747     strcpy((yyval.na),(yyvsp[(1) - (1)].na));strcpy(subroutinename,(yyvsp[(1) - (1)].na)); 
     6748     } 
     6749    break; 
     6750 
     6751  case 1025: 
     6752/* Line 1807 of yacc.c  */ 
     6753#line 4412 "fortran.y" 
     6754    {strcpy((yyval.na),(yyvsp[(1) - (1)].na));} 
     6755    break; 
     6756 
     6757  case 1026: 
     6758/* Line 1807 of yacc.c  */ 
     6759#line 4416 "fortran.y" 
     6760    {is_result_present = 0; } 
     6761    break; 
     6762 
     6763  case 1028: 
     6764/* Line 1807 of yacc.c  */ 
     6765#line 4422 "fortran.y" 
     6766    {is_result_present = 1; 
     6767                 if ( firstpass == 1 ) 
     6768            { 
     6769                strcpy(nameinttypenameback,nameinttypename); 
     6770                strcpy(nameinttypename,""); 
     6771                curvar = createvar((yyvsp[(3) - (4)].na),NULL); 
     6772                strcpy(nameinttypename,nameinttypenameback); 
     6773                strcpy(curvar->v_typevar,""); 
     6774                curlistvar = insertvar(NULL,curvar); 
     6775                Add_SubroutineArgument_Var_1(curlistvar); 
     6776            } 
     6777     } 
     6778    break; 
     6779 
     6780  case 1029: 
     6781/* Line 1807 of yacc.c  */ 
     6782#line 4438 "fortran.y" 
     6783    {strcpy(DeclType, "");} 
     6784    break; 
     6785 
     6786  case 1034: 
     6787/* Line 1807 of yacc.c  */ 
     6788#line 4452 "fortran.y" 
     6789    { 
     6790            insubroutinedeclare = 1; 
     6791            suborfun = 1; 
     6792            if ( firstpass ) 
     6793                Add_SubroutineArgument_Var_1((yyvsp[(4) - (4)].l)); 
     6794            else 
     6795              { 
     6796                WriteBeginof_SubLoop(); 
     6797              } 
     6798        } 
     6799    break; 
     6800 
     6801  case 1036: 
     6802/* Line 1807 of yacc.c  */ 
     6803#line 4467 "fortran.y" 
     6804    { 
     6805     if (strcmp(subroutinename,"")) 
     6806     { 
     6807     strcpy(old_subroutinename,subroutinename); // can occur in internal-subprogram 
     6808     old_oldfortran_out=oldfortran_out; 
     6809     } 
     6810     else 
     6811     { 
     6812     old_oldfortran_out=(FILE *)NULL; 
     6813     } 
     6814     strcpy((yyval.na),(yyvsp[(1) - (1)].na));strcpy(subroutinename,(yyvsp[(1) - (1)].na)); 
     6815     } 
     6816    break; 
     6817 
     6818  case 1038: 
     6819/* Line 1807 of yacc.c  */ 
     6820#line 4488 "fortran.y" 
     6821    {pos_endsubroutine = my_position; 
     6822            GlobalDeclaration = 0 ; 
     6823            if ( firstpass == 0 && strcasecmp(subroutinename,"") ) 
     6824            { 
     6825                if ( module_declar && insubroutinedeclare == 0 )    fclose(module_declar); 
     6826            } 
     6827            if ( strcasecmp(subroutinename,"") ) 
     6828            { 
     6829                if ( inmodulemeet == 1 ) 
     6830                { 
     6831                    /* we are in a module                                */ 
     6832                    if ( insubroutinedeclare == 1 ) 
     6833                    { 
     6834                        /* it is like an end subroutine <name>            */ 
     6835                        insubroutinedeclare = 0 ; 
     6836                        pos_cur = setposcur(); 
     6837                        closeandcallsubloopandincludeit_0(suborfun); 
     6838                        functiondeclarationisdone = 0; 
     6839                    } 
     6840                    else 
     6841                    { 
     6842                        /* it is like an end module <name>                */ 
     6843                        inmoduledeclare = 0 ; 
     6844                        inmodulemeet = 0 ; 
     6845                    } 
     6846                } 
     6847                else 
     6848                { 
     6849                    insubroutinedeclare = 0; 
     6850                    pos_cur = setposcur(); 
     6851                    closeandcallsubloopandincludeit_0(2); 
     6852                    functiondeclarationisdone = 0; 
     6853                } 
     6854            } 
     6855            strcpy(subroutinename,""); 
     6856            if (strcmp(old_subroutinename,"")) 
     6857            { 
     6858            strcpy(subroutinename,old_subroutinename); 
     6859            strcpy(old_subroutinename,""); 
     6860            oldfortran_out=old_oldfortran_out; 
     6861            insubroutinedeclare=1; 
     6862            } 
     6863        } 
     6864    break; 
     6865 
     6866  case 1041: 
     6867/* Line 1807 of yacc.c  */ 
     6868#line 4537 "fortran.y" 
     6869    {if (firstpass) (yyval.l)=NULL;} 
     6870    break; 
     6871 
     6872  case 1042: 
     6873/* Line 1807 of yacc.c  */ 
     6874#line 4538 "fortran.y" 
     6875    {in_complex_literal=0;} 
     6876    break; 
     6877 
     6878  case 1043: 
     6879/* Line 1807 of yacc.c  */ 
     6880#line 4539 "fortran.y" 
     6881    {if (firstpass) (yyval.l)=(yyvsp[(3) - (4)].l);} 
     6882    break; 
     6883 
     6884  case 1044: 
     6885/* Line 1807 of yacc.c  */ 
     6886#line 4543 "fortran.y" 
     6887    {if (firstpass) (yyval.l)=NULL;} 
     6888    break; 
     6889 
     6890  case 1045: 
     6891/* Line 1807 of yacc.c  */ 
     6892#line 4545 "fortran.y" 
     6893    {if (firstpass) (yyval.l)=(yyvsp[(1) - (1)].l);} 
     6894    break; 
     6895 
     6896  case 1046: 
     6897/* Line 1807 of yacc.c  */ 
     6898#line 4550 "fortran.y" 
     6899    { 
     6900            if ( firstpass == 1 ) 
     6901            { 
     6902                strcpy(nameinttypenameback,nameinttypename); 
     6903                strcpy(nameinttypename,""); 
     6904                curvar = createvar((yyvsp[(1) - (1)].na),NULL); 
     6905                strcpy(nameinttypename,nameinttypenameback); 
     6906                curlistvar = insertvar(NULL,curvar); 
     6907                (yyval.l) = settype("",curlistvar); 
     6908            } 
     6909        } 
     6910    break; 
     6911 
     6912  case 1047: 
     6913/* Line 1807 of yacc.c  */ 
     6914#line 4562 "fortran.y" 
     6915    { 
     6916            if ( firstpass == 1 ) 
     6917            { 
     6918                strcpy(nameinttypenameback,nameinttypename); 
     6919                strcpy(nameinttypename,""); 
     6920                curvar = createvar((yyvsp[(3) - (3)].na),NULL); 
     6921                strcpy(nameinttypename,nameinttypenameback); 
     6922                (yyval.l) = insertvar((yyvsp[(1) - (3)].l),curvar); 
     6923            } 
     6924        } 
     6925    break; 
     6926 
     6927  case 1048: 
     6928/* Line 1807 of yacc.c  */ 
     6929#line 4576 "fortran.y" 
     6930    {strcpy((yyval.na),(yyvsp[(1) - (1)].na));} 
     6931    break; 
     6932 
     6933  case 1049: 
     6934/* Line 1807 of yacc.c  */ 
     6935#line 4578 "fortran.y" 
     6936    {strcpy((yyval.na),"*");} 
     6937    break; 
     6938 
     6939  case 1052: 
     6940/* Line 1807 of yacc.c  */ 
     6941#line 4588 "fortran.y" 
    58376942    { 
    58386943            if ( inside_type_declare ) break; 
     
    58656970    break; 
    58666971 
    5867   case 483: 
    5868 /* Line 1807 of yacc.c  */ 
    5869 #line 1898 "fortran.y" 
    5870     { 
    5871             strcpy((yyval.na),(yyvsp[(1) - (1)].na)); 
    5872             pos_endsubroutine = setposcur()-strlen((yyvsp[(1) - (1)].na)); 
    5873             functiondeclarationisdone = 0; 
    5874         } 
    5875     break; 
    5876  
    5877   case 484: 
    5878 /* Line 1807 of yacc.c  */ 
    5879 #line 1906 "fortran.y" 
    5880     { 
    5881             strcpy((yyval.na),(yyvsp[(1) - (1)].na)); 
    5882             pos_endsubroutine = setposcur()-strlen((yyvsp[(1) - (1)].na)); 
    5883         } 
    5884     break; 
    5885  
    5886   case 485: 
    5887 /* Line 1807 of yacc.c  */ 
    5888 #line 1913 "fortran.y" 
    5889     { 
    5890             strcpy((yyval.na),(yyvsp[(1) - (1)].na)); 
    5891             pos_endsubroutine = setposcur()-strlen((yyvsp[(1) - (1)].na)); 
    5892         } 
    5893     break; 
    5894  
    5895   case 486: 
    5896 /* Line 1807 of yacc.c  */ 
    5897 #line 1920 "fortran.y" 
    5898     { 
    5899             strcpy((yyval.na),(yyvsp[(1) - (1)].na)); 
    5900             pos_endsubroutine = setposcur()-strlen((yyvsp[(1) - (1)].na)); 
    5901         } 
    5902     break; 
    5903  
    5904   case 487: 
    5905 /* Line 1807 of yacc.c  */ 
    5906 #line 1926 "fortran.y" 
     6972  case 1054: 
     6973/* Line 1807 of yacc.c  */ 
     6974#line 4623 "fortran.y" 
    59076975    {strcpy((yyval.na),"");} 
    59086976    break; 
    59096977 
    5910   case 488: 
    5911 /* Line 1807 of yacc.c  */ 
    5912 #line 1927 "fortran.y" 
     6978  case 1055: 
     6979/* Line 1807 of yacc.c  */ 
     6980#line 4624 "fortran.y" 
    59136981    {strcpy((yyval.na),(yyvsp[(1) - (1)].na));} 
    59146982    break; 
    59156983 
    5916   case 489: 
    5917 /* Line 1807 of yacc.c  */ 
    5918 #line 1930 "fortran.y" 
    5919     { created_dimensionlist = 0; } 
    5920     break; 
    5921  
    5922   case 490: 
    5923 /* Line 1807 of yacc.c  */ 
    5924 #line 1934 "fortran.y" 
    5925     { 
    5926             created_dimensionlist = 1; 
    5927             if ( ((yyvsp[(3) - (4)].d) == NULL) || ((yyvsp[(4) - (4)].d) == NULL) ) break; 
    5928             if  ( agrif_parentcall == 1 ) 
    5929             { 
    5930                 ModifyTheAgrifFunction_0((yyvsp[(3) - (4)].d)->dim.last); 
    5931                 agrif_parentcall = 0; 
    5932                 fprintf(fortran_out," = "); 
    5933             } 
    5934         } 
    5935     break; 
    5936  
    5937   case 491: 
    5938 /* Line 1807 of yacc.c  */ 
    5939 #line 1945 "fortran.y" 
    5940     { 
    5941             created_dimensionlist = 1; 
    5942         } 
    5943     break; 
    5944  
    5945   case 496: 
    5946 /* Line 1807 of yacc.c  */ 
    5947 #line 1958 "fortran.y" 
    5948     { 
    5949             inagrifcallargument = 0 ; 
    5950             incalldeclare=0; 
    5951             if ( oldfortran_out && (callagrifinitgrids == 1) && (firstpass == 0) ) 
    5952             { 
    5953                 pos_end = setposcur(); 
    5954                 RemoveWordSET_0(fortran_out,pos_curcall,pos_end-pos_curcall); 
    5955                 strcpy(subofagrifinitgrids,subroutinename); 
    5956             } 
    5957             Instanciation_0(sameagrifname); 
    5958         } 
    5959     break; 
    5960  
    5961   case 502: 
    5962 /* Line 1807 of yacc.c  */ 
    5963 #line 1979 "fortran.y" 
    5964     { 
    5965             if (!strcasecmp((yyvsp[(2) - (2)].na),"MPI_Init") )    callmpiinit = 1; 
    5966             else                                callmpiinit = 0; 
    5967  
    5968             if (!strcasecmp((yyvsp[(2) - (2)].na),"Agrif_Init_Grids") ) 
    5969             { 
    5970                 callagrifinitgrids = 1; 
    5971                 strcpy(meetagrifinitgrids,subroutinename); 
    5972             } 
    5973             else 
    5974             { 
    5975                 callagrifinitgrids = 0; 
    5976             } 
    5977             if ( Vartonumber((yyvsp[(2) - (2)].na)) == 1 ) 
    5978             { 
    5979                 incalldeclare = 1; 
    5980                 inagrifcallargument = 1 ; 
    5981                 Add_SubroutineWhereAgrifUsed_1(subroutinename, curmodulename); 
    5982             } 
    5983         } 
    5984     break; 
    5985  
    5986   case 503: 
    5987 /* Line 1807 of yacc.c  */ 
    5988 #line 2000 "fortran.y" 
    5989     { pos_curcall=setposcur()-4; } 
    5990     break; 
    5991  
    5992   case 506: 
    5993 /* Line 1807 of yacc.c  */ 
    5994 #line 2008 "fortran.y" 
    5995     { 
    5996             if ( callmpiinit == 1 ) 
    5997             { 
    5998                 strcpy(mpiinitvar,(yyvsp[(1) - (1)].na)); 
    5999                 if ( firstpass == 1 )  Add_UsedInSubroutine_Var_1 (mpiinitvar); 
    6000             } 
    6001         } 
    6002     break; 
    6003  
    6004   case 532: 
    6005 /* Line 1807 of yacc.c  */ 
    6006 #line 2056 "fortran.y" 
     6984  case 1061: 
     6985/* Line 1807 of yacc.c  */ 
     6986#line 4752 "fortran.y" 
    60076987    { afterpercent = 1; } 
    60086988    break; 
    60096989 
    6010   case 572: 
    6011 /* Line 1807 of yacc.c  */ 
    6012 #line 2115 "fortran.y" 
    6013     { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    6014     break; 
    6015  
    6016   case 573: 
    6017 /* Line 1807 of yacc.c  */ 
    6018 #line 2116 "fortran.y" 
    6019     { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    6020     break; 
    6021  
    6022   case 574: 
    6023 /* Line 1807 of yacc.c  */ 
    6024 #line 2117 "fortran.y" 
    6025     { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    6026     break; 
    6027  
    6028   case 575: 
    6029 /* Line 1807 of yacc.c  */ 
    6030 #line 2118 "fortran.y" 
    6031     { strcpy((yyval.na),(yyvsp[(1) - (1)].na)); } 
    6032     break; 
    6033  
    6034   case 576: 
    6035 /* Line 1807 of yacc.c  */ 
    6036 #line 2119 "fortran.y" 
    6037     { sprintf((yyval.na),"%s,%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na)); } 
    6038     break; 
    6039  
    6040   case 577: 
    6041 /* Line 1807 of yacc.c  */ 
    6042 #line 2120 "fortran.y" 
    6043     { sprintf((yyval.na),"%s,%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na)); } 
    6044     break; 
    6045  
    6046   case 578: 
    6047 /* Line 1807 of yacc.c  */ 
    6048 #line 2121 "fortran.y" 
    6049     { sprintf((yyval.na),"%s,%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na)); } 
    6050     break; 
    6051  
    6052   case 579: 
    6053 /* Line 1807 of yacc.c  */ 
    6054 #line 2122 "fortran.y" 
    6055     { sprintf((yyval.na),"%s,%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na)); } 
    6056     break; 
    6057  
    6058   case 580: 
    6059 /* Line 1807 of yacc.c  */ 
    6060 #line 2123 "fortran.y" 
    6061     { sprintf((yyval.na),"%s,%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na)); } 
    6062     break; 
    6063  
    6064   case 581: 
    6065 /* Line 1807 of yacc.c  */ 
    6066 #line 2124 "fortran.y" 
    6067     { sprintf((yyval.na),"%s,%s",(yyvsp[(1) - (3)].na),(yyvsp[(3) - (3)].na)); } 
    6068     break; 
    6069  
    6070   case 582: 
    6071 /* Line 1807 of yacc.c  */ 
    6072 #line 2127 "fortran.y" 
    6073     { sprintf((yyval.na),"(%s,%s)",(yyvsp[(2) - (5)].na),(yyvsp[(4) - (5)].na)); } 
    6074     break; 
    6075  
    6076   case 583: 
    6077 /* Line 1807 of yacc.c  */ 
    6078 #line 2128 "fortran.y" 
    6079     { sprintf((yyval.na),"(%s,%s)",(yyvsp[(2) - (5)].na),(yyvsp[(4) - (5)].na)); } 
    6080     break; 
    6081  
    6082   case 584: 
    6083 /* Line 1807 of yacc.c  */ 
    6084 #line 2129 "fortran.y" 
    6085     { sprintf((yyval.na),"(%s,%s)",(yyvsp[(2) - (5)].na),(yyvsp[(4) - (5)].na)); } 
    6086     break; 
    6087  
    6088   case 585: 
    6089 /* Line 1807 of yacc.c  */ 
    6090 #line 2131 "fortran.y" 
    6091     { sprintf((yyval.na),"%s=%s,%s)",(yyvsp[(1) - (5)].na),(yyvsp[(3) - (5)].na),(yyvsp[(5) - (5)].na));} 
    6092     break; 
    6093  
    6094   case 586: 
    6095 /* Line 1807 of yacc.c  */ 
    6096 #line 2132 "fortran.y" 
    6097     { sprintf((yyval.na),"%s=%s,%s,%s)",(yyvsp[(1) - (7)].na),(yyvsp[(3) - (7)].na),(yyvsp[(5) - (7)].na),(yyvsp[(7) - (7)].na));} 
    6098     break; 
    6099  
    6100   case 591: 
    6101 /* Line 1807 of yacc.c  */ 
    6102 #line 2142 "fortran.y" 
    6103     { Add_Allocate_Var_1((yyvsp[(1) - (1)].na),curmodulename); } 
    6104     break; 
    6105  
    6106  
    6107 /* Line 1807 of yacc.c  */ 
    6108 #line 6110 "fortran.tab.c" 
     6990 
     6991/* Line 1807 of yacc.c  */ 
     6992#line 6993 "fortran.tab.c" 
    61096993      default: break; 
    61106994    } 
     
    63387222 
    63397223/* Line 2055 of yacc.c  */ 
    6340 #line 2156 "fortran.y" 
     7224#line 4849 "fortran.y" 
    63417225 
    63427226 
     
    67947678   (yy_c_buf_p) = yy_cp; 
    67957679 
    6796 #define YY_NUM_RULES 176 
    6797 #define YY_END_OF_BUFFER 177 
     7680#define YY_NUM_RULES 177 
     7681#define YY_END_OF_BUFFER 178 
    67987682/* This struct is not used in this scanner, 
    67997683   but its presence is necessary. */ 
     
    68037687   flex_int32_t yy_nxt; 
    68047688   }; 
    6805 static yyconst flex_int16_t yy_accept[1132] = 
     7689static yyconst flex_int16_t yy_acclist[1577] = 
    68067690    {   0, 
    6807         0,    0,    0,    0,    0,    0,    0,    0,    0,    0, 
    6808         0,    0,  177,  176,  166,  164,  175,  176,  155,  158, 
    6809       176,  176,  157,  157,  157,  160,  156,  144,  154,  157, 
    6810       159,  162,  161,  163,  151,  151,  151,  151,  151,  151, 
    6811       151,  151,  151,  151,  151,  151,  151,  151,  151,  151, 
    6812       151,  151,  151,  151,  166,  164,  166,  175,  154,  151, 
    6813       151,  151,  151,  151,  151,  176,  176,  172,  176,  176, 
    6814       176,  157,  151,    0,    0,  166,    0,    0,  175,  175, 
    6815       175,    0,  148,    0,    0,    0,  168,    0,    0,    0, 
    6816         0,    0,  147,    0,    0,  141,   25,    0,  153,    0, 
    6817  
    6818         0,    0,    0,    0,    0,    0,  142,    0,  154,    0, 
    6819       140,   23,  151,  151,  151,  151,  151,  151,  151,  151, 
    6820       151,  151,  151,  151,  151,  151,  151,  151,   42,  151, 
    6821       151,  151,  151,  151,  151,  151,  151,  151,  151,  151, 
    6822       151,  151,  100,  151,   89,  151,  151,  151,  151,  151, 
    6823       151,  151,  151,  151,  151,  151,  151,  151,  151,  151, 
    6824       151,  151,  151,  151,  151,  151,  151,  151,  151,  151, 
    6825       151,  151,  151,  151,    0,  166,  166,    0,  167,    0, 
    6826         0,    0,    0,    0,    0,  165,  166,    0,  175,  174, 
    6827       175,  175,  175,  167,  154,    0,  151,  151,  151,  151, 
    6828  
    6829        89,  151,  151,    0,  172,    0,    0,    0,    0,    0, 
    6830         0,  173,   25,    0,    0,    0,  151,  151,  151,  151, 
    6831       151,    0,    0,    0,  175,  175,    0,    0,    0,    0, 
    6832         0,    0,    0,    0,  146,    0,    0,    0,    0,    0, 
    6833         0,    0,    0,    0,    0,    0,    0,    0,  152,  152, 
    6834         0,  153,  151,  151,  151,  151,  151,  151,  151,  151, 
    6835       151,  151,  151,  151,  151,  151,  123,  151,  151,  151, 
    6836       151,  151,  151,  151,   14,  151,  151,  151,  151,  122, 
    6837       151,  151,  151,  151,  151,  151,  151,    0,  151,  151, 
    6838       151,  151,  151,  151,  129,  151,  151,  134,  151,  151, 
    6839  
    6840       151,  151,  151,  151,  151,  151,   93,  151,  151,  151, 
    6841       151,  151,  151,  151,  151,  151,  151,  151,  151,  151, 
    6842       151,  126,  151,  151,  151,  151,  151,  130,  151,  151, 
    6843       151,  151,  151,  151,  151,    0,  166,  166,    0,    0, 
    6844         0,    0,    0,    0,    0,    0,    0,  166,    0,  167, 
    6845       175,  175,  175,  154,    0,  151,  151,  151,  151,  151, 
    6846       151,  151,    0,    0,    0,    0,  173,    0,    0,    0, 
    6847       151,  151,  151,  151,  151,    0,    0,    0,  175,  175, 
    6848         0,    0,    0,    0,    0,    0,    0,    0,  153,    0, 
    6849        27,    0,   29,   28,   31,   30,   33,    0,    0,   35, 
    6850  
    6851         0,    0,  133,  125,  151,  151,  128,  151,  131,  151, 
    6852       151,   20,  151,  151,  151,  151,  151,  151,  124,  151, 
    6853       151,  151,  151,  151,  151,   98,    0,  115,  151,  151, 
    6854       151,  151,  151,  151,  151,  151,    0,  116,  151,    0, 
    6855       117,  151,  151,  151,  151,  151,  151,    0,  113,  151, 
    6856       151,    0,   92,  151,  151,  151,  151,  151,  151,  151, 
    6857         0,  102,  151,  151,    0,  119,  151,  151,  151,  151, 
    6858       120,    0,  114,   19,  151,   63,   77,  151,  151,  151, 
    6859       151,  151,  151,  151,  151,   82,   43,  151,  151,  151, 
    6860       151,   72,  151,  151,  127,  151,   76,   57,  151,    0, 
    6861  
    6862       101,  103,  151,   96,  105,  151,  151,  151,  151,   47, 
    6863       166,  166,    0,    0,    0,    0,    0,    0,    0,  166, 
    6864         0,  167,  175,  175,  175,  154,    0,  108,  151,  151, 
    6865       151,  151,  151,   16,    0,    0,    0,    0,    0,    0, 
    6866       151,  151,  151,  151,    0,    0,    0,  175,  175,    0, 
    6867         0,    0,    0,    0,    0,   37,   26,    0,   34,   36, 
    6868       151,  151,  151,  151,  151,  151,   52,  151,  151,  151, 
    6869       151,  132,  151,  151,  151,  151,  151,    0,  151,  151, 
    6870         0,    0,    0,    0,    0,    0,    0,    0,   41,  151, 
    6871        99,  151,  151,  151,  151,  151,  151,  151,  151,   79, 
    6872  
    6873        79,  151,    0,  111,  121,   85,  151,  151,   92,  151, 
    6874       151,   94,  151,  151,  151,  151,  151,  151,  151,  151, 
    6875       151,  151,  151,    0,    0,  151,  151,  151,   55,  151, 
    6876        80,  151,  151,  151,    0,  151,  151,  151,  151,  151, 
    6877         0,  135,  106,  151,  151,    0,  112,   58,   39,   84, 
    6878       166,  166,  108,    0,    0,    0,    0,    0,  166,    0, 
    6879       167,  175,  175,  175,  154,    0,  108,  151,   90,  151, 
    6880       151,   74,   73,   74,    0,    0,    0,    0,    0,  151, 
    6881        52,  151,  132,    0,   21,    0,  175,   21,    0,   21, 
    6882        21,    0,   21,    0,   21,   21,   21,   32,  151,  151, 
    6883  
    6884       151,   21,  151,  151,   66,  151,  151,  151,  151,  151, 
    6885       151,  151,  145,    0,    0,   97,  151,   41,    0,   99, 
    6886         0,    0,    0,    0,    0,    0,  151,  151,  151,  151, 
    6887       151,  151,  151,  151,    0,  118,  151,  151,  151,  151, 
    6888       151,  151,  151,   69,  151,  151,  137,  104,  136,  138, 
    6889        38,  151,    0,    6,  151,  151,  151,  151,  151,  151, 
    6890        87,    0,  151,    8,   78,   17,  151,  151,   86,  166, 
    6891       166,    0,    0,    0,  166,  175,  175,   21,    0,  151, 
    6892       151,  151,    0,    0,    0,   21,    0,  151,   21,   22, 
    6893         0,  169,   22,   22,   22,   22,   22,   22,   22,   22, 
    6894  
    6895       151,  151,  151,  151,   50,  151,  151,  151,  109,  151, 
    6896         0,  151,  151,   97,    0,  151,    0,    0,    0,    0, 
    6897         0,    0,    0,  151,  151,  151,  151,  151,   75,  151, 
    6898       151,  151,    0,    0,  151,  151,   15,   53,   44,  151, 
    6899        45,    0,  151,  151,    5,  151,  151,   70,   88,    3, 
    6900         0,    0,  151,    0,  151,  151,    0,    0,    0,  175, 
    6901        22,    0,  151,   67,  151,    0,    0,   22,    0,   22, 
    6902       151,    4,  151,  151,  151,  151,   91,  151,  151,    0, 
    6903         0,  151,  151,    0,  151,    0,    0,    0,    0,    0, 
    6904        75,    0,  151,  151,  151,  151,  151,   59,  151,   68, 
    6905  
    6906         0,    0,    0,    0,  143,    9,   18,  151,    0,  151, 
    6907        83,   71,  151,    0,  151,    0,  151,  151,    0,    0, 
    6908       175,    0,   62,  151,    0,    0,    0,  151,  151,  139, 
    6909        46,  151,  151,   54,    0,    0,  151,  151,    0,   61, 
    6910         0,    0,    0,    0,    0,   59,  151,   11,  151,  110, 
    6911       151,  151,    0,    0,    0,    0,    0,  143,   95,    0, 
    6912       151,   64,    0,   65,    0,  151,  151,   62,    0,  175, 
    6913         0,  149,    0,    0,    0,  151,  151,   40,    7,    0, 
    6914         0,  151,  151,   61,    0,   60,    0,   11,    0,  110, 
    6915         0,  151,   10,  151,  151,    0,    0,    0,  151,    0, 
    6916  
    6917         0,  107,    2,  149,  175,    0,    0,    0,    0,   51, 
    6918         0,    0,    0,    0,  151,  151,    0,   10,    0,   13, 
    6919       151,   56,    0,    0,    0,  151,    0,  107,  175,    0, 
    6920         0,    0,    0,    0,    0,    0,    0,  151,  151,   13, 
    6921         0,  151,    0,    0,    0,  151,    0,  175,    0,    0, 
    6922         0,    0,    0,   24,    0,    0,   49,  151,    0,   12, 
    6923         0,    0,    0,  151,    0,  175,    0,    0,    0,  150, 
    6924         0,   49,    0,  151,   12,    0,    0,    0,    0,  151, 
    6925         0,  175,    0,    0,    0,    0,   48,    0,    0,    0, 
    6926        81,    1,  175,    0,    0,    0,   48,   81,  175,    0, 
    6927  
    6928         0,    0,  175,    0,    0,    0,  175,    0,    0,    0, 
    6929       175,    0,    0,    0,  175,    0,    0,    0,  175,  170, 
    6930         0,  170,    0,    0,  170,    0,    0,    0,    0,  171, 
    6931         0 
     7691      143,  143,  178,  177,  166,  177,  165,  177,  176,  177, 
     7692      177,  155,  177,  159,  177,  169,  177,  177,  158,  177, 
     7693      158,  177,  158,  177,  161,  177,  156,  177,  140,  177, 
     7694      154,  177,  158,  177,  160,  177,  163,  177,  162,  177, 
     7695      164,  177,  150,  177,  150,  177,  150,  177,  150,  177, 
     7696      150,  177,  150,  177,  150,  177,  150,  177,  150,  177, 
     7697      150,  177,  150,  177,  150,  177,  150,  177,  150,  177, 
     7698      150,  177,  150,  177,  150,  177,  150,  177,  150,  177, 
     7699      150,  177,  150,  177,  166,  177,  165,  175,  177,  176, 
     7700      177,  150,  177,  150,  177,  150,  177,  150,  177,  150, 
     7701 
     7702      177,  177,  177,  173,  177,  177,  177,  177,  143,  177, 
     7703      144,  177,  177,  165,  177,  150,  177,  150,  177,  150, 
     7704      177,  150,  177,  150,  177,  150,  177,  150,  177,  150, 
     7705      177,  150,  177,  150,  177,  150,  177,  150,  177,  150, 
     7706      177,  150,  177,  150,  177,  150,  177,  150,  177,  150, 
     7707      177,  150,  177,  150,  177,  150,  177,  165,  175,  177, 
     7708      166,  177,  158,  177,  154,  177,  150,  177,  150,  177, 
     7709      150,  177,  150,  177,  150,  177,  166,  177,  154,  177, 
     7710      166,  176,  176,  176,  146,  169,  145,  138,   20,  153, 
     7711      139,  137,   34,  154,  136,   35,   33,   18,   36,  150, 
     7712 
     7713      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7714      150,  150,  150,   42,  150,  150,  150,  150,  150,  150, 
     7715      150,  150,  150,  150,  150,  150,  150,  150,  150,   91, 
     7716      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7717      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7718      150,  150,  150,  150,  150,  150,  150,  150,  150,  166, 
     7719      175,  176,  176,  176,  176,  150,  150,  150,  150,   91, 
     7720      150,  150,  173,  143,  142,  150,  150,  150,  150,  150, 
     7721      150,  150,  150,  150,  150,  150,  150,  150,  150,   42, 
     7722      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7723 
     7724      150,  150,  150,  150,  150,   91,  150,  150,  150,  150, 
     7725      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7726      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7727      150,  150,  150,  150,  150,  175,  166,  166,  174,   20, 
     7728      154,  174,  150,  150,  150,  150,  150,  150,  150,  150, 
     7729      150,  150,   91,  150,  150,  166,  154,  176,  176,  141, 
     7730      145,  152,  151,  152,  153,  153,  150,  150,  150,  150, 
     7731      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7732      150,  150,  150,  150,  150,    9,  150,  150,  150,  150, 
     7733      150,  150,  150,  150,  150,  150,  150,  150,  103,16485, 
     7734 
     7735      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7736      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7737       94,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7738      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7739      150,  150,  150,   11,  150,  150,  150,  150,  176,  176, 
     7740      176,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7741      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7742      150,  150,  150,  150,  150,  150,    9,  150,  150,  150, 
     7743      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7744      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7745 
     7746      150,  150,  150,  150,  150,  150,  150,  150,  150,   94, 
     7747      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7748      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7749      150,  150,   11,  150,  150,  150,  150,  166,  166,  154, 
     7750      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7751      150,  150,  150,  176,  176,  153,   22,   24,   23,   26, 
     7752       25,   28,   30,  150,  150,  150,  150,  150,  150,  150, 
     7753       15,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7754      150,  150,   41,   41,  150,  150,   99,  150,  116,  150, 
     7755      150,  150,  150,  150,  117,  150,  126,  150,  150,   79, 
     7756 
     7757      150,  150,  150,  150,  114,  150,  150,   93,  150,  150, 
     7758      150,  150,  150,  150,  150,  150,  150,  150,  150,  118, 
     7759      150,  150,  150,  150,  115,   14,  150,  150,   63,  150, 
     7760       77,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7761      150,   83,  150,   43,  150,  130,  150,  150,  150,  150, 
     7762      150,   72,  150,  150,  150,   76,  150,   57,  150,  150, 
     7763      150,   97,  150,  150,  150,  150,  150,   47,  176,  176, 
     7764      176,  105,  150,  150,  150,  150,  150,  150,16458,  150, 
     7765      150,  150,  150,  150,  150,  150,   15,  150,  150,  150, 
     7766      150,  150,  150,  150,  150,  150,  150,  150,   41,  150, 
     7767 
     7768      150,   99,  150,  150,  150,  150,  150,  150,  150,  150, 
     7769      150,   79,  150,  150,  150,  150,  150,  150,   93,  150, 
     7770      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7771      150,  150,  150,  150,   14,  150,  150,   63,  150,   77, 
     7772      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7773       83,  150,   43,  150,  150,  150,  150,  150,  150,   72, 
     7774      150,  150,  150,   76,  150,   57,  150,  150,  150,   97, 
     7775      150,  150,  150,  150,  150,  166,  154,   15,  150,  105, 
     7776      150,  150,  150,  150,  150,  150,  150,  150,  150,  150, 
     7777      150,  150,  150,  150,16458,  176,  176,  157,   32,   21, 
     7778 
     7779       29,   31,  150,  150,  150,  150,  150,  150,  150,  150, 
     7780       52,  150,  150,  150,  150,  150,  134,  150,  150,  150, 
     7781      150,  150,  150,  150,   40,  150,  100,  150,  150,  150, 
     7782      150,  150,  150,  150,  150,  108,   87,  150,  127,  150, 
     7783       93,  102,  150,  150,   95,  150,  150,  150,  150,  150, 
     7784      150,  150,  150,  119,  150,  150,  121,  128,  150,  150, 
     7785      150,  150,  150,   55,  150,  150,  150,   80,  150,  150, 
     7786      150,  150,   82,  129,  150,  150,  150,  150,  150,  150, 
     7787      150,  150,  150,  112,   58,  150,   38,  150,   86,  150, 
     7788      105,16458,  176,  176,  176,  105,  150,   92,  150,  150, 
     7789 
     7790     8266,   73, 8266,  150,  150,  150,  150,  150,  150,  150, 
     7791      150,   52,  150,  150,  150,  150,  150,  134,  150,  150, 
     7792      150,  150,  150,  150,  150,   40,  150,  100,  150,  150, 
     7793      150,  150,  150,  150,  150,  150,   87,  150,  150,  150, 
     7794      150,   95,  150,  150,  150,  150,  150,  150,  150,  150, 
     7795      150,  150,  150,  150,  150,  150,  150,   55,  150,  150, 
     7796      150,   80,  150,  150,  150,  150,  150,  150,  150,  150, 
     7797      150,  150,  150,  150,  150,   58,  150,   38,  150,   86, 
     7798      150,  166,  154,  105,  150,  150,   52,  150,  150,  150, 
     7799      150,  150,  150,  150,  134,  150,  150,  150,   16,  176, 
     7800 
     7801       16,  176,   16,   16,  146,   16,   16,   16,  145,   16, 
     7802       16,   16,   16,   16,   16,   27,  150,  150,  150,  150, 
     7803      150,   16,  150,  150,  150,   66,  150,  150,  150,  150, 
     7804      150,  150,  150,  150,   98,  150,  150,   40,  100,  150, 
     7805      150,  150,  150,  150,  133,  150,  150,  102, 8293,  102, 
     7806      150,  150,  150,  150,   69,  150,  150,  150,  124,  150, 
     7807      150,   37,  150,  150,  150,  150,  150,  150,  150,  150, 
     7808      150,  150,   89,  150,  150,    7,  150,   78,  150,   12, 
     7809      150,  150,  150,  132,  150,  150,   88,  150,   85,  176, 
     7810      176,   16,  176,  150,  150,  150,  150,  150,  150,  150, 
     7811 
     7812      150,   16,  150,  150,  150,   66,  150,  150,  150,  150, 
     7813      150,  150,  150,  150,   98,  150,  150,  150,  150,  150, 
     7814      150,  150,  150,  150,  150,  150,  150,  150,   69,  150, 
     7815      150,  150,  150,  150,   37,  150,  150,  150,  150,  150, 
     7816      150,  150,  150,  150,  150,   89,  150,  150,    7,  150, 
     7817       78,  150,   12,  150,  150,  150,  132,  150,  150,   88, 
     7818      150,   16,  150,  150,   66,  150,  150,  150,  150,  150, 
     7819       16,  150,  150,  150,   17,   17,  176,   17,   17,  146, 
     7820       17,   17,   17,  145,   17,   17,   17,   17,   17,   17, 
     7821      109,  110,   17,  150,  150,  150,  150,  150,   50,  150, 
     7822 
     7823      150,  150,  150,  106,  150,  150,  150,  150,   98,  150, 
     7824      150,   75,  150,  150,  150,  120,  150,  150, 8293,  150, 
     7825       10,  150,   53,  150,   44,  150,  150,  150,  125,   45, 
     7826      150,  150,  150,    5,  150,  113,  150,  150,   70,  150, 
     7827      150,   90,  150,    2,  150,  150,  150,  122,  131,  150, 
     7828      176,   17,  176,  150,   67,  150,  170,   17,  150,  150, 
     7829      150,  150,  150,   50,  150,  150,  150,  150,  106,  150, 
     7830      150,  150,  150,  150,  150,   75,  150,  150,  150,  150, 
     7831      150,  150,   10,  150,   53,  150,   44,  150,  150,  150, 
     7832       45,  150,  150,  150,    5,  150,  150,  150,   70,  150, 
     7833 
     7834      150,   90,  150,    2,  150,  150,  150,  150,  170,   17, 
     7835       17,  150,  150,   50,  150,  150,  150,  150,  150,  150, 
     7836        3,  150,  150,  150,  150,  150,    4,  150,  150,  150, 
     7837      150,  150,  150,   75,  150,   59,  150,  150,   68,  150, 
     7838        8,  150,   13,  150,  150,  150,  150,   84,  150,   71, 
     7839      150,  150,  150,  150,  150,  150,  176,   62,  150,  150, 
     7840      150,    3,  150,  150,  150,  150,  150,    4,  150,  150, 
     7841      150,  150,  150,  150,  150,   59,  150,  150,   68,  150, 
     7842        8,  150,   13,  150,  150,  150,  150,   84,  150,   71, 
     7843      150,  150,  150,  150,  150,  150,  150,  150,   62,  150, 
     7844 
     7845        4,  150,  150,  137,  150,  150,  135,  150,   46,  150, 
     7846      150,  150,   54,  150,  150,  150,   61,  150,   59,  107, 
     7847      150,  150,   96,  150,  111,  150,   64,  150,  123,   65, 
     7848      150,  150,  150,   62,  176,  147,  150,  149,  150,  150, 
     7849      135,  150,   46,  150,  150,  150,   54,  150,  150,  150, 
     7850       61,  150,  107,  150,  150,   96,  150,  150,   64,  150, 
     7851       65,  150,  150,  150,   46,  150,  150,  147,  150,  168, 
     7852      137,  150,  150,   39,  150,    6,  150,  150,  150,   61, 
     7853       60,  107,  150,  150,  104,  150,    1,  150,  147,  176, 
     7854      150,  150,   39,  150,    6,  150,  150,  150,  150,  150, 
     7855 
     7856      104,  150,    1,  150,  167,   39,  150,   51,  150,  150, 
     7857      150,   56,  150,  150,  104,  176,   51,  150,  150,  150, 
     7858       56,  150,  150,  168,  150,  150,  150,  176,  150,  150, 
     7859      150,  167,   19,   49,  150,  150,  150,  176,  148,  173, 
     7860       49,  150,  150,  150,  167,  167,   49,  150,  150,  176, 
     7861      150,  150,   48,  150,   81,  150,  176,   48,  150,   81, 
     7862      150,  167,   48,   81,  176,  176,  176,  176,  176,  176, 
     7863      171,  171,  171,  174,  172,  173 
     7864    } ; 
     7865 
     7866static yyconst flex_int16_t yy_accept[1850] = 
     7867    {   0, 
     7868        1,    1,    1,    1,    1,    1,    1,    1,    1,    2, 
     7869        3,    3,    3,    3,    3,    4,    5,    7,    9,   11, 
     7870       12,   14,   16,   18,   19,   21,   23,   25,   27,   29, 
     7871       31,   33,   35,   37,   39,   41,   43,   45,   47,   49, 
     7872       51,   53,   55,   57,   59,   61,   63,   65,   67,   69, 
     7873       71,   73,   75,   77,   79,   81,   83,   85,   87,   90, 
     7874       92,   94,   96,   98,  100,  102,  103,  104,  106,  107, 
     7875      108,  109,  111,  113,  114,  116,  118,  120,  122,  124, 
     7876      126,  128,  130,  132,  134,  136,  138,  140,  142,  144, 
     7877      146,  148,  150,  152,  154,  156,  158,  161,  163,  165, 
     7878 
     7879      167,  169,  171,  173,  175,  177,  179,  181,  181,  181, 
     7880      182,  183,  184,  185,  185,  186,  186,  186,  187,  187, 
     7881      187,  187,  187,  188,  188,  188,  188,  188,  189,  189, 
     7882      189,  189,  190,  190,  191,  191,  191,  191,  191,  191, 
     7883      191,  191,  191,  191,  191,  192,  193,  194,  194,  195, 
     7884      195,  196,  197,  198,  199,  200,  201,  202,  203,  204, 
     7885      205,  206,  207,  208,  209,  210,  211,  212,  213,  214, 
     7886      216,  217,  218,  219,  220,  221,  222,  223,  224,  225, 
     7887      226,  227,  228,  229,  230,  232,  233,  234,  235,  236, 
     7888      237,  238,  239,  240,  241,  242,  243,  244,  245,  246, 
     7889 
     7890      247,  248,  249,  250,  251,  252,  253,  254,  255,  256, 
     7891      257,  258,  259,  260,  260,  261,  262,  262,  262,  262, 
     7892      262,  262,  262,  262,  263,  263,  264,  265,  266,  266, 
     7893      267,  268,  269,  270,  272,  273,  273,  274,  274,  274, 
     7894      274,  274,  275,  275,  276,  276,  276,  276,  276,  276, 
     7895      276,  277,  278,  279,  280,  281,  282,  283,  284,  285, 
     7896      286,  287,  288,  289,  290,  292,  293,  294,  295,  296, 
     7897      297,  298,  299,  300,  301,  302,  303,  304,  305,  306, 
     7898      308,  309,  310,  311,  312,  313,  314,  315,  316,  317, 
     7899      318,  319,  320,  321,  322,  323,  324,  325,  326,  327, 
     7900 
     7901      328,  329,  330,  331,  332,  333,  334,  335,  336,  336, 
     7902      337,  337,  337,  338,  339,  339,  339,  340,  341,  341, 
     7903      341,  341,  341,  342,  343,  343,  344,  345,  346,  347, 
     7904      348,  349,  350,  351,  352,  353,  355,  356,  357,  357, 
     7905      357,  358,  358,  358,  358,  359,  360,  360,  360,  360, 
     7906      360,  360,  360,  360,  360,  362,  362,  362,  362,  362, 
     7907      362,  362,  362,  362,  362,  362,  362,  362,  362,  362, 
     7908      362,  362,  362,  362,  362,  362,  362,  362,  362,  362, 
     7909      362,  362,  362,  362,  362,  363,  366,  366,  367,  368, 
     7910      369,  370,  371,  372,  373,  374,  375,  376,  377,  378, 
     7911 
     7912      379,  380,  381,  382,  383,  383,  384,  385,  386,  388, 
     7913      389,  390,  391,  392,  393,  394,  395,  396,  397,  398, 
     7914      398,  399,  399,  401,  402,  403,  404,  405,  406,  407, 
     7915      408,  409,  410,  411,  412,  413,  414,  415,  416,  417, 
     7916      418,  419,  420,  421,  423,  424,  425,  426,  427,  428, 
     7917      429,  430,  431,  432,  433,  434,  435,  436,  437,  438, 
     7918      439,  440,  441,  442,  443,  444,  446,  447,  448,  449, 
     7919      449,  449,  449,  449,  449,  449,  449,  449,  449,  450, 
     7920      451,  452,  452,  453,  454,  455,  456,  457,  458,  458, 
     7921      458,  458,  458,  458,  458,  458,  458,  458,  458,  458, 
     7922 
     7923      458,  459,  460,  461,  462,  463,  464,  465,  466,  467, 
     7924      468,  469,  470,  471,  472,  473,  474,  475,  476,  477, 
     7925      479,  480,  481,  482,  483,  484,  485,  486,  487,  488, 
     7926      489,  490,  491,  492,  493,  494,  495,  496,  497,  498, 
     7927      499,  500,  501,  502,  503,  504,  505,  506,  507,  508, 
     7928      509,  510,  512,  513,  514,  515,  516,  517,  518,  519, 
     7929      520,  521,  522,  523,  524,  525,  526,  527,  528,  529, 
     7930      530,  531,  532,  533,  535,  536,  537,  538,  538,  538, 
     7931      538,  538,  539,  539,  540,  540,  540,  540,  540,  540, 
     7932      540,  541,  541,  542,  543,  544,  545,  546,  547,  548, 
     7933 
     7934      549,  550,  551,  552,  553,  554,  554,  554,  554,  554, 
     7935      555,  556,  556,  556,  556,  556,  556,  556,  556,  556, 
     7936      556,  556,  556,  556,  556,  556,  556,  556,  557,  557, 
     7937      558,  558,  559,  560,  561,  562,  563,  563,  563,  564, 
     7938      564,  564,  564,  564,  564,  564,  564,  564,  564,  564, 
     7939      564,  565,  566,  567,  568,  569,  570,  571,  573,  574, 
     7940      575,  576,  577,  578,  579,  580,  581,  582,  583,  584, 
     7941      586,  587,  589,  589,  590,  591,  592,  593,  594,  595, 
     7942      595,  596,  597,  597,  598,  599,  600,  602,  603,  604, 
     7943      605,  605,  606,  607,  608,  608,  610,  610,  610,  610, 
     7944 
     7945      610,  611,  612,  613,  614,  615,  616,  617,  618,  619, 
     7946      620,  620,  621,  622,  623,  624,  625,  625,  626,  628, 
     7947      629,  631,  633,  634,  635,  636,  637,  638,  639,  640, 
     7948      641,  642,  644,  646,  646,  647,  648,  649,  650,  651, 
     7949      652,  654,  655,  656,  658,  660,  661,  662,  664,  665, 
     7950      666,  667,  668,  669,  669,  669,  669,  669,  669,  669, 
     7951      670,  671,  672,  672,  674,  675,  676,  677,  678,  680, 
     7952      680,  680,  680,  680,  680,  680,  680,  680,  680,  681, 
     7953      682,  683,  684,  685,  686,  687,  689,  690,  691,  692, 
     7954      693,  694,  695,  696,  697,  698,  699,  701,  702,  704, 
     7955 
     7956      705,  706,  707,  708,  709,  710,  711,  712,  714,  715, 
     7957      716,  717,  718,  719,  721,  722,  723,  724,  725,  726, 
     7958      727,  728,  729,  730,  731,  732,  733,  734,  735,  737, 
     7959      738,  740,  742,  743,  744,  745,  746,  747,  748,  749, 
     7960      750,  751,  753,  755,  756,  757,  758,  759,  760,  762, 
     7961      763,  764,  766,  768,  769,  770,  772,  773,  774,  775, 
     7962      776,  776,  776,  776,  777,  777,  777,  777,  777,  777, 
     7963      778,  778,  780,  782,  783,  784,  785,  786,  787,  788, 
     7964      789,  790,  791,  792,  793,  794,  796,  796,  796,  796, 
     7965      797,  798,  798,  798,  798,  798,  798,  799,  799,  799, 
     7966 
     7967      799,  799,  799,  799,  800,  801,  801,  802,  803,  803, 
     7968      803,  803,  803,  803,  803,  804,  805,  806,  807,  808, 
     7969      809,  810,  811,  813,  814,  815,  816,  817,  819,  820, 
     7970      821,  822,  823,  823,  824,  825,  825,  825,  825,  825, 
     7971      825,  827,  829,  830,  831,  832,  833,  834,  835,  836, 
     7972      836,  837,  839,  839,  840,  841,  842,  842,  842,  842, 
     7973      843,  844,  845,  847,  848,  849,  850,  851,  852,  853, 
     7974      854,  854,  855,  856,  857,  857,  858,  858,  859,  860, 
     7975      861,  862,  863,  864,  866,  867,  868,  870,  871,  872, 
     7976      873,  873,  874,  874,  875,  876,  877,  878,  879,  880, 
     7977 
     7978      881,  882,  883,  884,  884,  885,  887,  889,  891,  892, 
     7979      892,  892,  892,  892,  893,  894,  895,  896,  896,  897, 
     7980      898,  899,  900,  901,  902,  903,  904,  904,  904,  904, 
     7981      904,  904,  904,  905,  906,  907,  908,  909,  910,  911, 
     7982      912,  914,  915,  916,  917,  918,  920,  921,  922,  923, 
     7983      924,  925,  926,  928,  930,  931,  932,  933,  934,  935, 
     7984      936,  937,  939,  940,  941,  942,  944,  945,  946,  947, 
     7985      948,  949,  950,  951,  952,  953,  954,  955,  956,  957, 
     7986      958,  960,  961,  962,  964,  965,  966,  967,  968,  969, 
     7987      970,  971,  972,  973,  974,  975,  976,  978,  980,  982, 
     7988 
     7989      982,  982,  982,  983,  983,  983,  983,  983,  983,  984, 
     7990      984,  985,  986,  987,  989,  990,  991,  992,  993,  994, 
     7991      995,  997,  998,  999,  999,  999, 1000, 1001, 1003, 1003, 
     7992     1004, 1006, 1006, 1007, 1008, 1010, 1010, 1010, 1010, 1010, 
     7993     1011, 1012, 1013, 1014, 1015, 1016, 1017, 1017, 1017, 1017, 
     7994     1017, 1018, 1019, 1020, 1021, 1022, 1024, 1025, 1026, 1028, 
     7995     1029, 1030, 1031, 1032, 1033, 1034, 1035, 1035, 1035, 1037, 
     7996     1038, 1039, 1040, 1040, 1040, 1040, 1041, 1042, 1043, 1044, 
     7997     1045, 1045, 1046, 1047, 1048, 1048, 1049, 1049, 1049, 1049, 
     7998     1049, 1050, 1051, 1052, 1053, 1054, 1055, 1057, 1058, 1059, 
     7999 
     8000     1059, 1060, 1061, 1062, 1064, 1065, 1066, 1067, 1068, 1069, 
     8001     1070, 1071, 1072, 1073, 1075, 1076, 1078, 1080, 1082, 1083, 
     8002     1084, 1086, 1087, 1089, 1089, 1090, 1090, 1090, 1090, 1091, 
     8003     1092, 1094, 1094, 1095, 1096, 1097, 1097, 1097, 1097, 1097, 
     8004     1097, 1097, 1098, 1099, 1100, 1101, 1102, 1104, 1105, 1106, 
     8005     1108, 1109, 1110, 1111, 1112, 1113, 1114, 1115, 1117, 1118, 
     8006     1119, 1120, 1121, 1122, 1123, 1124, 1125, 1126, 1127, 1128, 
     8007     1129, 1131, 1132, 1133, 1134, 1135, 1137, 1138, 1139, 1140, 
     8008     1141, 1142, 1143, 1144, 1145, 1146, 1148, 1149, 1151, 1153, 
     8009     1155, 1156, 1157, 1159, 1160, 1162, 1162, 1162, 1162, 1162, 
     8010 
     8011     1163, 1163, 1164, 1165, 1167, 1168, 1169, 1170, 1171, 1173, 
     8012     1174, 1175, 1175, 1176, 1178, 1179, 1181, 1182, 1183, 1185, 
     8013     1185, 1186, 1187, 1188, 1189, 1190, 1191, 1191, 1191, 1191, 
     8014     1191, 1191, 1192, 1192, 1193, 1195, 1196, 1197, 1198, 1199, 
     8015     1201, 1202, 1203, 1204, 1206, 1207, 1207, 1208, 1209, 1210, 
     8016     1210, 1211, 1211, 1211, 1211, 1212, 1214, 1215, 1216, 1216, 
     8017     1217, 1218, 1219, 1220, 1220, 1220, 1221, 1223, 1225, 1227, 
     8018     1228, 1229, 1229, 1230, 1232, 1232, 1233, 1234, 1236, 1236, 
     8019     1237, 1238, 1239, 1241, 1242, 1244, 1246, 1247, 1247, 1248, 
     8020     1248, 1249, 1249, 1250, 1251, 1251, 1251, 1251, 1252, 1254, 
     8021 
     8022     1254, 1255, 1256, 1257, 1257, 1257, 1257, 1258, 1258, 1258, 
     8023     1260, 1261, 1262, 1263, 1264, 1266, 1267, 1268, 1269, 1271, 
     8024     1272, 1273, 1274, 1275, 1276, 1278, 1279, 1280, 1281, 1282, 
     8025     1283, 1285, 1287, 1289, 1290, 1291, 1293, 1294, 1295, 1297, 
     8026     1298, 1299, 1301, 1302, 1304, 1306, 1307, 1308, 1309, 1309, 
     8027     1310, 1310, 1311, 1311, 1313, 1314, 1316, 1317, 1318, 1319, 
     8028     1320, 1320, 1320, 1320, 1320, 1320, 1321, 1323, 1324, 1325, 
     8029     1326, 1327, 1329, 1330, 1331, 1331, 1331, 1332, 1333, 1333, 
     8030     1334, 1334, 1335, 1335, 1336, 1338, 1339, 1341, 1343, 1343, 
     8031     1345, 1346, 1347, 1347, 1348, 1350, 1352, 1353, 1354, 1355, 
     8032 
     8033     1355, 1356, 1357, 1357, 1357, 1358, 1358, 1360, 1361, 1361, 
     8034     1361, 1361, 1361, 1361, 1362, 1364, 1365, 1366, 1367, 1368, 
     8035     1370, 1371, 1372, 1373, 1374, 1375, 1376, 1378, 1379, 1381, 
     8036     1383, 1385, 1386, 1387, 1388, 1390, 1392, 1393, 1394, 1395, 
     8037     1396, 1397, 1397, 1397, 1397, 1398, 1399, 1401, 1403, 1404, 
     8038     1404, 1404, 1404, 1404, 1404, 1404, 1404, 1405, 1406, 1407, 
     8039     1409, 1411, 1412, 1413, 1415, 1415, 1415, 1416, 1417, 1417, 
     8040     1419, 1419, 1420, 1422, 1423, 1425, 1425, 1426, 1426, 1427, 
     8041     1429, 1429, 1430, 1432, 1432, 1433, 1434, 1435, 1435, 1436, 
     8042     1436, 1438, 1438, 1438, 1438, 1439, 1440, 1441, 1443, 1445, 
     8043 
     8044     1446, 1447, 1449, 1450, 1451, 1453, 1455, 1456, 1458, 1459, 
     8045     1461, 1463, 1464, 1465, 1465, 1465, 1465, 1467, 1468, 1470, 
     8046     1470, 1470, 1471, 1471, 1471, 1471, 1472, 1473, 1474, 1476, 
     8047     1478, 1478, 1478, 1479, 1480, 1481, 1481, 1482, 1483, 1484, 
     8048     1484, 1485, 1485, 1487, 1489, 1490, 1491, 1491, 1491, 1491, 
     8049     1492, 1493, 1495, 1497, 1498, 1499, 1500, 1501, 1503, 1505, 
     8050     1505, 1505, 1505, 1506, 1506, 1508, 1508, 1508, 1508, 1508, 
     8051     1508, 1508, 1510, 1510, 1510, 1510, 1510, 1511, 1512, 1514, 
     8052     1514, 1515, 1516, 1517, 1517, 1517, 1517, 1519, 1520, 1521, 
     8053     1523, 1524, 1524, 1524, 1524, 1524, 1524, 1524, 1524, 1524, 
     8054 
     8055     1524, 1524, 1524, 1525, 1525, 1525, 1525, 1525, 1526, 1527, 
     8056     1527, 1528, 1529, 1529, 1529, 1529, 1530, 1531, 1532, 1532, 
     8057     1532, 1532, 1532, 1532, 1532, 1532, 1532, 1532, 1532, 1532, 
     8058     1533, 1533, 1533, 1533, 1533, 1533, 1534, 1534, 1534, 1536, 
     8059     1537, 1537, 1538, 1539, 1539, 1539, 1539, 1541, 1543, 1544, 
     8060     1545, 1545, 1545, 1545, 1545, 1545, 1545, 1546, 1546, 1546, 
     8061     1546, 1547, 1547, 1547, 1547, 1547, 1548, 1548, 1549, 1549, 
     8062     1550, 1551, 1551, 1551, 1552, 1553, 1553, 1553, 1553, 1553, 
     8063     1553, 1553, 1553, 1553, 1553, 1553, 1553, 1555, 1555, 1557, 
     8064     1558, 1558, 1558, 1560, 1562, 1562, 1562, 1562, 1562, 1562, 
     8065 
     8066     1562, 1563, 1563, 1564, 1565, 1566, 1566, 1566, 1566, 1566, 
     8067     1566, 1566, 1566, 1566, 1567, 1567, 1567, 1567, 1567, 1567, 
     8068     1567, 1567, 1567, 1568, 1568, 1568, 1568, 1568, 1569, 1569, 
     8069     1569, 1569, 1570, 1570, 1570, 1570, 1571, 1572, 1572, 1573, 
     8070     1573, 1573, 1575, 1575, 1575, 1575, 1575, 1577, 1577 
    69328071    } ; 
    69338072 
     
    69388077        1,    1,    1,    1,    1,    1,    1,    1,    1,    1, 
    69398078        1,    4,    5,    6,    7,    8,    9,   10,   11,   12, 
    6940        13,   14,   15,   16,   17,   18,   19,   20,   21,   22, 
    6941        23,   24,   25,   26,   27,   28,   29,   30,   31,   32, 
    6942        33,   34,    1,    1,   35,   36,   37,   38,   39,   40, 
    6943        41,   42,   43,   44,   45,   46,   47,   48,   49,   50, 
    6944        51,   52,   53,   54,   55,   56,   57,   58,   59,   60, 
    6945        61,    1,   62,    1,   63,    1,   64,   65,   66,   67, 
    6946  
    6947        68,   69,   70,   71,   72,   44,   73,   74,   75,   76, 
    6948        77,   78,   79,   80,   81,   82,   83,   84,   85,   86, 
    6949        87,   88,    1,   89,    1,    1,    1,    1,    1,    1, 
     8079       13,   14,   15,   16,   17,   18,   19,   20,   20,   20, 
     8080       20,   20,   20,   20,   20,   20,   20,   21,   22,   23, 
     8081       24,   25,    1,    1,   26,   27,   28,   29,   30,   31, 
     8082       32,   33,   34,   35,   36,   37,   38,   39,   40,   41, 
     8083       42,   43,   44,   45,   46,   47,   48,   49,   50,   51, 
     8084       52,    1,   53,    1,   54,    1,   55,   56,   57,   58, 
     8085 
     8086       59,   60,   61,   62,   63,   35,   64,   65,   66,   67, 
     8087       68,   69,   70,   71,   72,   73,   74,   75,   76,   77, 
     8088       78,   79,    1,   80,    1,    1,    1,    1,    1,    1, 
    69508089        1,    1,    1,    1,    1,    1,    1,    1,    1,    1, 
    69518090        1,    1,    1,    1,    1,    1,    1,    1,    1,    1, 
     
    69648103    } ; 
    69658104 
    6966 static yyconst flex_int32_t yy_meta[90] = 
     8105static yyconst flex_int32_t yy_meta[81] = 
    69678106    {   0, 
    6968         1,    1,    2,    1,    1,    3,    1,    1,    1,    1, 
    6969         1,    4,    1,    1,    1,    1,    1,    3,    1,    5, 
    6970         5,    5,    5,    5,    5,    5,    5,    5,    5,    1, 
    6971         1,    1,    1,    1,    6,    7,    7,    5,    5,    8, 
    6972         9,   10,   11,   11,   11,    9,   11,    9,   12,   11, 
    6973        13,    9,    9,    9,    9,   11,   11,   11,   11,   11, 
    6974         1,    1,   11,    6,    7,    7,    5,    5,    8,    9, 
    6975        10,   11,   11,    9,   11,    9,   12,   11,   13,    9, 
    6976         9,    9,    9,   11,   11,   11,   11,   11,    3 
     8107        1,    2,    3,    2,    4,    5,    4,    4,    1,    4, 
     8108        6,    7,    8,    4,    9,   10,   11,   12,   13,   14, 
     8109        1,    4,    1,    1,    1,   15,   14,   14,   14,   14, 
     8110       15,   16,   17,   17,   17,   17,   16,   17,   16,   16, 
     8111       17,   17,   16,   16,   16,   16,   17,   17,   17,   17, 
     8112       17,    1,    1,   18,   15,   14,   14,   14,   14,   15, 
     8113       16,   17,   17,   17,   16,   17,   16,   16,   17,   17, 
     8114       16,   16,   16,   16,   17,   17,   17,   17,   17,    5 
    69778115    } ; 
    69788116 
    6979 static yyconst flex_int16_t yy_base[1171] = 
     8117static yyconst flex_int16_t yy_base[2001] = 
    69808118    {   0, 
    6981         0,   88,    0,    0,    0,    0,  984,   93,    0,   85, 
    6982         0,    0,  891,   64,   98,  103,   80,  129,   96,   99, 
    6983       134,  137,  145,  133,  168,  135,  249,  180,  318,  136, 
    6984       156,  172,  212,  239,  246,  297,  366,  341,  414,  461, 
    6985       247,  294,  398,  334,  407,  476,  506,  517,  459,  566, 
    6986       572,  522,  571,  367,  653,  226,  656,  658,  737,  638, 
    6987       785,  655,  698,  806,  652, 4012,  878, 4012,  241,  116, 
    6988       124,  455,  893,   59,   76,  229,  253,  256,    0,  122, 
    6989       127,  872, 4012,  157,  188,  869,  866,  327,  302,  349, 
    6990       740,  416, 4012,  768,  592, 4012, 4012,  981,  730,  147, 
    6991  
    6992       184,  438,  495,  328,  184,  190, 4012, 1048,  335,  969, 
    6993      4012, 4012,    0,  269,  315,  149,  319,  486,  462,  248, 
    6994       318,  325,  269,  426,  736,  336,  767,  470,  500,  518, 
    6995       512,  403,  516,  525,  535,  801,  544,  620,  565,  570, 
    6996       589,  768,  483,  589,  810,  592,  613,  638,  650,  664, 
    6997       678,  736,  737,  740,  741,  949,  736,  788,  646,  956, 
    6998       756,  999,  739,  753,  804,  749, 1043,  972,  962,  769, 
    6999       813,  963,  972,  969,    0, 1057,    0,  839,  238, 1044, 
    7000       986,  789,  956, 1030,  965,  429, 1109, 1136,  830, 4012, 
    7001      1061, 1087, 1091, 1162, 1188,  990, 1095, 1120, 1006, 1042, 
    7002  
    7003      1170, 1050, 1046,  823, 4012, 1201, 1099, 1115, 1190,  797, 
    7004       483, 4012,  790, 1167, 1100, 1194, 1269, 1358, 1255, 1254, 
    7005      1195, 1103, 1098,  625, 1148, 1163, 1217, 1237, 1222, 1238, 
    7006      1095, 1305, 1325, 1234, 4012, 1334, 1302, 1326, 1107, 1182, 
    7007       738,  735,  731,  730, 1244, 1166,  713, 1242, 4012, 1428, 
    7008      1374, 1389, 1419, 1244, 1252, 1261, 1263, 1192, 1266, 1301, 
    7009      1333, 1333, 1352, 1352, 1387, 1392, 1388, 1389, 1390, 1404, 
    7010      1401, 1405, 1407, 1404, 1506, 1471, 1417, 1476, 1430,    0, 
    7011      1422, 1437, 1442, 1432, 1484, 1440, 1454, 1497, 1444, 1448, 
    7012      1451, 1443, 1445, 1475, 1459, 1530, 1536, 1464, 1477, 1470, 
    7013  
    7014      1531, 1490, 1491, 1482, 1509, 1511,    0, 1526, 1513, 1519, 
    7015      1524, 1527, 1524, 1555, 1516, 1519, 1522, 1546, 1557, 1564, 
    7016      1558, 1565, 1555, 1557, 1562, 1561, 1615, 1573, 1575, 1573, 
    7017      1576, 1570, 1574, 1582, 1576,  719,  351,  666, 1572,  713, 
    7018      1580, 1587, 1584, 1593, 1589, 1596, 1608, 1658, 1684, 1710, 
    7019      1652, 1645, 1661, 1741, 1626, 1629, 1635, 1634, 1637, 1703, 
    7020      1653,  709, 1654, 1744,  707,  998, 4012, 1712, 1674, 1715, 
    7021      1664, 1708, 1725, 1738, 1749, 1622, 1684, 1379, 1672, 1735, 
    7022      1743, 1771, 1723, 1772, 1787, 1804, 1815, 1807, 1821,  656, 
    7023      4012,  646, 4012, 4012, 4012, 4012, 4012, 1735,  614, 4012, 
    7024  
    7025       613, 1849, 4012,    0, 1741, 1751,    0, 1796,    0, 1799, 
    7026      1799,    0, 1820, 1819, 1811, 1816, 1808, 1821,    0, 1826, 
    7027      1822, 1814, 1822, 1825, 1819, 1871, 1955, 4012, 1825, 1821, 
    7028      1837, 1830, 1829, 1850, 1823, 1844, 1899, 4012, 1836, 1909, 
    7029      4012, 1841, 2040, 1856, 1915, 1858, 1874, 1920, 4012, 1886, 
    7030      1872, 1878,    0, 1886, 1879, 1881, 1888, 1896, 1895, 1902, 
    7031      1967, 4012, 1897, 1906, 1971, 4012, 1900, 1912, 1906, 1915, 
    7032         0, 1980, 4012,    0, 1988,    0,    0, 1929, 1939, 1926, 
    7033      1933, 1936, 1946, 1939, 1953,    0,  602, 1949, 1958, 1955, 
    7034      1963,    0, 1960, 2063,    0,  598,    0,    0, 1985, 2064, 
    7035  
    7036      4012,    0, 1960,    0,    0, 2019, 2022, 2024, 2025, 4012, 
    7037       792,  880, 2030, 2023, 2043, 2043, 2041, 2042,  581, 2092, 
    7038      2118, 2144, 2079, 2080, 2084, 2170, 2045, 1005, 2060, 1022, 
    7039      2071, 2134, 2199,  574, 2082, 2174, 2108, 2147, 2148, 2101, 
    7040      2154, 2184, 2187, 2190, 2087,    0, 1422, 2144,    0, 2200, 
    7041       138, 2202,  571, 2221, 2233, 4012, 4012,  514, 4012, 4012, 
    7042      2174, 2192, 2051, 2289, 2080, 2193,    0, 2109, 2194, 2193, 
    7043      2199,    0, 2201, 2207, 2204, 2195, 2198, 2270, 2240, 2240, 
    7044      2215, 2229, 2246, 2239, 2258, 2275, 2258, 2276,    0, 2276, 
    7045         0, 2287, 2279, 2283, 2295, 2283, 2295, 2300, 2335, 4012, 
    7046  
    7047         0, 2293, 2342, 4012,    0,    0, 2294, 2293, 4012, 2316, 
    7048      2321,    0, 2297, 2323, 2312, 2319, 2335, 2334, 2327, 2337, 
    7049      2333, 2341, 2338,  197,  451, 2343, 2337, 2347,    0, 2348, 
    7050         0, 2335, 2355, 2355,  477, 2343, 2343, 2350, 2355, 2348, 
    7051      2275, 4012, 4012, 2349, 2351, 2404, 4012,    0,    0,    0, 
    7052      1140, 1249, 1797, 2376, 2082, 2379, 2366, 2432, 2263,  424, 
    7053       569, 2417, 2420,  499, 2486, 2384, 2087, 2385, 2427, 2389, 
    7054      2398, 2437, 4012, 2448, 2444, 2439, 2452,  479, 2451, 2431, 
    7055      2410, 2565, 2416,    0, 4012, 2653,    0,    0,  475,  445, 
    7056      4012,  441,  436, 2458, 2462, 2468, 4012, 4012, 2682, 2404, 
    7057  
    7058      2428,    0, 2441, 2444,    0, 2442, 2449, 2447, 2480, 2465, 
    7059      2479, 2553,    0, 2487, 2489,    0, 2493, 4012, 2486, 4012, 
    7060      2497, 2509, 2513, 2527, 2535, 2549, 2552, 2538, 2550, 2555, 
    7061      2548, 2562, 2552, 2559, 2604, 4012, 2572, 2480, 2561, 2568, 
    7062      2573, 2575, 2564,    0, 2569, 2578,    0,    0,    0,    0, 
    7063      2660, 2572,  508, 4012, 2583, 2594, 2591, 2650, 2664, 2658, 
    7064         0, 2536, 2663,    0,    0,    0, 2715, 2654,    0, 2539, 
    7065      2479, 2668, 2663, 2678, 2644, 2682,  426,  421, 2680, 2677, 
    7066      2540, 2686, 2701, 2720,  411,  365, 2721, 2790, 2691, 4012, 
    7067      2725, 4012,    0,  343, 4012,  307, 2753, 2755, 4012,    0, 
    7068  
    7069      2747, 2692, 2702, 2706,    0, 2707, 2709, 2719,    0, 2685, 
    7070      2776, 2708, 2732, 4012, 2748, 2737, 2773, 2763, 2773, 2780, 
    7071      2773, 2788, 2777, 2776, 2785, 2780, 2796, 2786,    0, 2797, 
    7072      2798, 2794, 2647, 2867, 2796, 2791,    0,    0,    0, 2795, 
    7073         0, 2845, 2798, 2801,    0, 2815, 2825,    0,    0,    0, 
    7074      2872, 2840, 2825, 2883, 2847, 2843, 2840, 2548, 2855,  827, 
    7075       303,  239, 2841, 2765, 2855, 1020, 2888,  288, 1687, 2861, 
    7076      2861,    0, 2851, 2861, 2850, 2855,    0, 2851, 2858, 2858, 
    7077      2856, 2863, 2873, 2862, 2878, 2870, 2882, 2880, 2881, 2888, 
    7078      4012, 2904, 2901, 2906, 2913, 2885, 2895,    0, 2903,    0, 
    7079  
    7080      2951, 2978, 2955, 2982, 2994,    0,    0, 2933, 2910, 2917, 
    7081         0,    0, 2923,  248, 2932, 2941, 2930, 2939, 2936, 2956, 
    7082      2998, 2964,    0, 2967, 3005, 3006, 3007, 2966, 2959,    0, 
    7083         0, 2960, 2979,    0, 2973, 2982, 2973, 2987, 2986, 3025, 
    7084      2983, 2989, 2995, 2978, 2978, 4012, 2985,    0, 2991,    0, 
    7085      2985, 3006, 3066, 3074, 3078, 3090, 3094, 3106,    0, 3009, 
    7086      3019,    0, 3041,    0, 3018, 3050, 3056, 4012, 3062, 3076, 
    7087      3056,    0, 3087, 3103, 3099, 3072, 3111,    0,    0, 3064, 
    7088      3080, 3075, 3079, 3124, 3125, 4012, 3082, 4012, 3085, 4012, 
    7089      3080, 3093,    0, 3096, 3104, 3152, 3171, 3113, 3118,  245, 
    7090  
    7091      3119,    0,    0, 4012, 1737,  184, 3142, 3141, 1922,    0, 
    7092      3181, 3186, 3115, 3122, 3127, 3111, 3122, 4012, 3128,    0, 
    7093      3129,    0, 3208, 3211, 3152, 3158, 3150, 4012, 3194, 3154, 
    7094      2097, 3179, 3201, 3224, 3231, 3169, 3153, 3159, 3179, 4012, 
    7095      3183, 3184, 3251, 3258, 3191, 3183,  207, 3229, 3207, 3237, 
    7096       194, 3233, 3261, 4012, 3209, 3200,    0, 3220, 3211,    0, 
    7097      3309, 3283, 3218, 3228, 3221, 3285, 3236, 3273,  142, 4012, 
    7098      3286, 4012, 3243, 3250, 4012, 3339, 3342, 3367, 3248, 3286, 
    7099       108, 2482,   40, 2606, 2838, 3273,    0, 3395, 3399, 3290, 
    7100         0, 4012, 3302, 3294, 3311, 3350, 4012, 4012, 3299, 3320, 
    7101  
    7102      3357, 3358, 3375, 3318, 3359, 3380, 3404, 3376, 3300, 3412, 
    7103      3362, 3363, 3370, 3415, 3418, 3423, 3420, 3426, 3433, 4012, 
    7104      3447, 4012, 3428, 3451, 4012, 3430, 3439, 3454, 3457, 4012, 
    7105      4012, 3521, 3534, 3547, 3560, 3573, 3586, 3595, 3608, 3621, 
    7106      3634, 3647, 3656, 3669, 3678, 3686, 3699, 3712, 3725, 3738, 
    7107      3751, 3764, 3777, 3790, 3803, 3816, 3829, 3842, 3855, 3868, 
    7108      3881, 3894, 3907, 3920, 3933, 3946, 3959, 3972, 3985, 3998 
     8119        0,   79,    0,    0,    0,  151, 3195,   84,   88,   91, 
     8120      224,  303,    0,  375, 3194,   65,   99, 9211,   73,  100, 
     8121       74,   90,  308,  117,  325,  126,  137,  133,  447,  386, 
     8122      382,  144,  143,  285,  390,  302,  425,  449,  499,  497, 
     8123      547,  594,  443,  324,  535,  495,  503,  582,  618,  630, 
     8124      639,  398,  685,  688,  697,  689,  450,  769,  216,  538, 
     8125      583,  749,  745,  800,  802, 9211, 3186, 9211,  789,  114, 
     8126      155,   96, 9211, 3164,  851,  841,  692,  912,  860,  961, 
     8127      910,  853,  858,  948,  895,  896,  977, 1009, 1020, 1036, 
     8128     1033, 1069, 1085, 1081, 1118, 1123, 1162,  203,  908,  316, 
     8129 
     8130     1219,   71, 1145,  100, 1274,  339,  363,  106,  127,  198, 
     8131        0,  140,  144, 3153, 3107,  308,  348,  347, 3104,  181, 
     8132      698,  415, 3066,  434,  899,  631,  819, 9211, 1300, 1317, 
     8133     1342, 9211,  847,  697,  307,  331,  446,  607,  613,  363, 
     8134      425, 1050, 1361, 1167, 9211, 9211, 9211, 1311, 1358,  304, 
     8135     9211, 9211, 9211, 9211, 9211,    0,  831,  302,  435,  473, 
     8136      508,  359,  516,  367,  542,  749,  411,  906,  550, 1142, 
     8137      549,  489,  576,  624,  653,  926,  698,  692,  723,  735, 
     8138      804, 1040, 1301,  805, 1352, 1361,  860,  955,  489,  976, 
     8139      959,  965,  970,  981, 1013, 1060, 1011, 1138, 1311, 1089, 
     8140 
     8141      570, 1386, 1011, 1033, 1062, 1364,  573, 1088,  615,  649, 
     8142      765, 1343,  807,    0, 1278, 1190, 3073, 1353,  891, 1136, 
     8143     1135, 1386, 1195, 3024, 1345,  993, 1398, 1407,  957, 1400, 
     8144     1400, 1322, 1383, 1428, 1405, 3008, 9211, 1445, 1442, 1437, 
     8145     1457,  209, 2996, 2992, 1201, 1485, 1450, 2991, 2987, 1503, 
     8146     1480, 1498, 1504, 1517, 1506, 1524, 1455, 1547, 1544, 1548, 
     8147     1568, 1557, 1598, 1594, 1599, 1605, 1618, 1595, 1591, 1641, 
     8148     1654, 1659, 1661, 1652, 1665, 1674, 1701, 1738, 1692, 1711, 
     8149     1732, 1743, 1757, 1758, 1780, 1784, 1790, 1795, 1814, 1821, 
     8150     1700, 1815, 1839, 1820, 1861, 1846, 1883, 1869, 1880, 1876, 
     8151 
     8152     1920, 1924, 1919, 1913, 1939, 1959, 1977, 1972, 1519, 2023, 
     8153     1606, 2956, 1776,  318,  782, 2938, 9211, 2932, 1513, 1439, 
     8154     1964, 1999, 2037, 2044, 1628, 2107, 2187, 2016, 2101, 2025, 
     8155     2096, 2033, 2113, 1926, 2016, 2185, 2108, 1306, 2212, 2213, 
     8156     2218, 1560, 1432, 1596, 1620, 1649, 2879, 1833, 1746, 2866, 
     8157     1492, 2144, 2172, 1752, 2853, 2852, 2253, 2161,  497,  880, 
     8158     2266, 2267, 2833, 2277, 2287, 1124, 1042, 1697, 2832, 2801, 
     8159     2798, 2795, 1943, 1681, 2778, 1785, 1475, 2296, 1489, 2771, 
     8160     2752, 2324, 2335, 2692, 9211, 2326, 2670, 2656, 1076, 1267, 
     8161     1796, 1867, 1348, 1936, 1979, 2017, 2020, 2020, 2037, 2278, 
     8162 
     8163     2037, 2102, 1360, 1497, 2305, 2328, 1517, 1631, 2400, 1677, 
     8164     1658, 2292, 2107, 1816, 1846, 2114, 1797, 2180, 1951, 2315, 
     8165     2183, 2019, 1887, 2189, 2192, 2187, 2188, 2322, 1979, 2193, 
     8166     2229, 2192, 2355, 2241, 2234, 2286, 2317, 2362, 2332, 2330, 
     8167     2319, 2331, 2337,    0, 2348, 2333, 2341, 2348, 2360, 2351, 
     8168     2350, 2381, 2418, 2343, 2363, 2356, 2364, 2384, 2370, 2376, 
     8169     2384, 2383, 2396, 2392, 2387,    0, 2390, 2401, 2395, 2660, 
     8170     2397, 2643, 2406, 2412, 2407, 2416, 2417, 2424, 2464, 2433, 
     8171     2466, 2439, 2444, 2449, 2455, 2455, 2456, 2455, 2484, 2505, 
     8172     2622, 2081, 2500, 2621, 2572, 2515, 2527, 2519, 2562, 2553, 
     8173 
     8174     2488, 2494, 2498, 2486, 2510, 2492, 2531, 2533, 2534, 2530, 
     8175     2540, 2543, 2539, 2545, 2546, 2549, 2583, 2556, 2555, 2655, 
     8176     2587, 2558, 2615, 2590, 2566, 2577, 2550, 2627, 2561, 2610, 
     8177     2612, 2617, 2623, 2594, 2620, 2634, 2639, 2629, 2638, 2646, 
     8178     2641, 2644, 2645, 2658, 2667, 2706, 2682, 2669, 2671, 2647, 
     8179     2689, 2548, 2699, 2652, 2712, 2714, 2717, 2726, 2729, 2730, 
     8180     2736, 2719, 2732, 2734, 2739, 2740, 2733, 2741, 2742, 2747, 
     8181     2759, 2750, 2758, 2547, 2769, 2743, 2760, 2819, 2823, 2485, 
     8182     2832, 2888, 2707,  388, 2828, 2837, 2778, 2799, 2840, 2845, 
     8183     2854, 2768, 2961, 3041, 2822, 2808, 2836, 2868, 2959, 2840, 
     8184 
     8185     2845, 2852, 2874, 2885, 2891, 2717, 2860, 2867, 2888, 2881, 
     8186     2893, 2937, 2896, 2851, 2985, 2419, 2989, 3009, 3006, 3013, 
     8187     3065, 3020, 2938, 2989, 3068, 3071, 2396, 2386, 2357, 9211, 
     8188     2354, 9211, 9211, 9211, 9211, 9211, 2882, 2318, 9211, 2294, 
     8189     3033, 3093, 2289, 2263, 3101, 3113, 3132, 2242, 2238, 3142, 
     8190     2888, 2957, 2957, 2974, 3047, 3051, 2962,    0, 3073, 3072, 
     8191     3056, 3089, 3083, 3075, 3084, 3102, 3102, 3110, 2208, 2199, 
     8192     3113, 3151, 3226, 9211, 3116, 3102, 3128, 3110, 3130, 3162, 
     8193     9211, 3118, 3167, 9211, 3124, 3127,    0, 3130, 3178, 3141, 
     8194     3193, 9211, 3202, 3134, 3141,    0, 3207, 2171, 2156, 3220, 
     8195 
     8196     3149, 3144, 3163, 3171, 3206, 3177, 3174, 3193, 3203, 3244, 
     8197     3245, 9211, 3215, 3194, 3259, 3273, 3262, 9211,    0, 3217, 
     8198        0, 3222, 3217, 3224, 3223, 3220, 3231, 3233, 3253, 3244, 
     8199     3254, 3299,    0, 3290, 9211, 3303, 3248, 3258, 3253, 3270, 
     8200        0, 3284, 3285, 3270,    0, 3278, 3290,    0, 3324, 3291, 
     8201     3292, 3295, 9211, 3299, 3286, 3306, 3306, 3304, 3305, 3327, 
     8202     3333, 3336, 3297,  462, 3319,  602, 3317, 3341, 3367, 3344, 
     8203     3387, 3353, 3392, 3399, 3405, 3409, 2140, 2134, 3362, 3378, 
     8204     3372, 3396, 3390, 3397, 3373, 2097, 3416, 3422, 3420, 3425, 
     8205     3383, 3429, 3428, 3430, 3423, 3427,  427, 3433, 3445, 3432, 
     8206 
     8207     3451, 3456, 3434, 3440, 3438, 3452, 3458, 2096, 3435, 3514, 
     8208     3471, 3523, 3462, 2091, 3465, 3474, 3477, 3480, 3498, 3506, 
     8209     3507, 3473, 3516, 3549, 3526, 3520, 3558, 3564, 2084, 3529, 
     8210     2065, 3546, 3538, 3541, 3561, 3536, 3542, 3552, 3567, 3553, 
     8211     3555, 3596, 2049, 3608, 3574, 3577, 3583, 3591, 2030, 3599, 
     8212     3600, 3587, 2017, 3581, 3601, 2011, 3635, 3610, 3613, 3616, 
     8213     3648, 3660, 3314, 3674, 3664, 3669, 3678, 3641, 3667, 3710, 
     8214     3644, 3780, 3860, 3679, 3691, 3686, 3739, 3763, 3760, 3825, 
     8215     3697, 3718,  685, 3718, 3854, 3809, 3557, 3637,    0, 3674, 
     8216        0, 3712,  532, 3828, 3747, 2309, 9211, 3887, 3888, 1978, 
     8217 
     8218     3632, 3900, 3959, 9211, 9211, 1976, 9211, 9211, 3770, 3812, 
     8219     3924, 3934, 1975, 3986, 3681, 3769, 3677, 3723, 3770, 4043, 
     8220     3774, 3790,    0, 3781, 3793, 3779, 3787,    0, 3854, 3858, 
     8221     3852, 3794, 3953, 3872, 3884, 3879, 3902, 3926, 3908, 3959, 
     8222        0,    0, 3957, 3954, 3967, 3972, 3967, 3907, 3963, 4013, 
     8223     9211,    0, 4016, 9211, 3969, 9211, 4067, 4068, 4085, 4091, 
     8224     3976, 3977,    0, 3965, 3979, 4001, 4034, 4002, 4075, 4041, 
     8225     4103, 9211, 4064, 4063, 4108, 9211, 4109, 9211, 4082, 4086, 
     8226     4091, 4085, 4091,    0, 4095, 4092,    0, 4083, 4103, 4102, 
     8227     4132, 9211, 4133, 9211, 4094, 4094, 4101, 4102, 4096, 4113, 
     8228 
     8229     4098, 4105, 4108, 4159, 9211,    0,    0, 4172, 1158, 4136, 
     8230     1531, 4138, 4130, 4173, 4175, 4177, 1971, 4148, 1928, 4152, 
     8231     2140, 4151, 4159, 4196, 9211, 4202, 4192, 4184, 3840, 3946, 
     8232     4220, 4226, 4189, 4193, 4207, 4194, 4196, 4266, 4224, 4283, 
     8233     1954, 4253, 4291, 4255, 4256, 1936, 4259, 4293, 4261, 4294, 
     8234     4297, 4298, 1933, 1920, 4299, 4300, 4304, 4306, 4305, 4311, 
     8235     4303, 1912, 4309, 4319, 4322, 1878, 4313, 4314, 4326, 4335, 
     8236     4307, 4379, 4342, 4349, 4359, 4345, 4346, 4356, 4352, 4362, 
     8237     1877, 4364, 4375, 1841, 4351, 4385, 4392, 4383, 4387, 4390, 
     8238     4404, 4394, 4395, 4397, 4398, 4402, 1829, 1810, 4238, 4241, 
     8239 
     8240     4249, 4379, 4474, 2558, 4432, 4433, 4423, 1803, 4469, 4425, 
     8241     3757, 4547, 4627, 4177, 4455, 4438, 4453, 4452, 4479, 4707, 
     8242     4385, 4409, 4453, 4396,    0, 9211,    0,    0, 1208, 1785, 
     8243     1781, 4530, 4564, 4570, 1756, 4599, 4574, 4448, 4787, 4580, 
     8244     4587, 4593, 4606, 4652, 1728, 9211, 4512, 4521, 4659, 4671, 
     8245     4581, 4663, 4867, 4385, 4463,    0, 4465, 4534,    0, 4537, 
     8246     4545, 4544, 4564, 4612, 4625, 4699, 4635, 4638,    0, 4674, 
     8247     9211, 9211, 4621, 4636, 4704, 4705, 4706, 4695, 4702, 4745, 
     8248     4746, 9211, 4716, 4704, 4813, 4738, 4818, 4766, 3843, 1687, 
     8249     4841, 4835, 4711, 4716, 4727, 4709,    0, 4710, 4740, 4812, 
     8250 
     8251     9211, 4825, 4786, 4853, 4788, 4784, 4893, 4844, 4851, 4857, 
     8252     4861, 4857, 4864,    0, 4869,    0,    0,    0, 4903, 4902, 
     8253     4909, 4863,    0, 4613, 9211, 4875, 4875, 4879, 4911, 1691, 
     8254     1671, 4892, 4879, 2805, 4899, 4924, 4931, 2934, 3088, 4540, 
     8255     4687, 4941, 4946, 4990, 4965, 4950, 1656, 4932, 4972, 1615, 
     8256     4969, 4976, 4974, 5021, 4977, 5018, 5023, 1595, 5025, 5026, 
     8257     5027, 5020, 5028, 5030, 5032, 5033, 5034, 5036, 5037, 5056, 
     8258     1584, 5038, 5057, 5101, 5069, 5072, 5050, 5058, 5113, 5074, 
     8259     5066, 5076, 5080, 5059, 5085, 1554, 5087, 1538, 1511, 1481, 
     8260     5129, 5140, 5150, 5095, 1473, 4694, 5156, 4911, 1468, 1458, 
     8261 
     8262     5125, 5186, 5266, 5346, 4892, 4914, 5068, 5092,    0, 4774, 
     8263     5123, 5100, 9211,    0, 1397, 1385, 4953, 4971, 1373, 5163, 
     8264     5167, 5210, 5232, 5238, 5239, 1348, 3487, 4074, 5213, 5293, 
     8265     5220, 9211, 5227, 9211,    0, 5274, 5116, 5127, 5147,    0, 
     8266     5190, 5203, 5209,    0, 5179, 5338, 5197, 5251, 9211, 5269, 
     8267     5259, 5275, 5276, 5265, 5281,    0, 5284, 5285, 5321, 9211, 
     8268     5276, 5333, 5372, 5360, 5389, 5335,    0,    0,    0, 5347, 
     8269     5349, 5401, 9211,    0, 5386, 5343, 5349,    0, 5413, 9211, 
     8270     5379, 5353,    0, 5379,    0,    0, 5372, 5426, 5383, 5419, 
     8271     9211, 5427, 9211, 5386, 5393, 4739, 5398,  582, 1358, 1274, 
     8272 
     8273     5389, 4817, 5406,  796, 5432, 4859, 9211, 4974, 5110, 1309, 
     8274     5436, 5438, 5439, 5442, 1303, 5447, 5454, 5433, 1215, 5453, 
     8275     5462, 5455, 5461, 5471, 1214, 5470, 5475, 5445, 5468, 5467, 
     8276     1135, 1114, 1109, 5482, 5476, 1094, 5477, 5473, 1078, 5478, 
     8277     5511, 1024, 5483,  962,  931, 5484, 5516, 5489, 5177,  904, 
     8278     5444,  889,  804,    0, 5478,    0, 5494, 5467, 5495, 5530, 
     8279     5545, 5322, 5558, 5562, 5580, 5500,    0, 5512, 5514, 5520, 
     8280     5530,    0, 5529, 5536, 5536, 5535, 5542, 5556, 5545, 5559, 
     8281     5564, 9211, 5563, 5550,    0, 5557,    0,    0, 5596,    0, 
     8282     5573, 5603, 5567, 5572,    0,    0, 5571, 5615, 5595, 5600, 
     8283 
     8284     5584, 5590, 5587, 5604, 5631, 5604,    0, 5605, 5633, 5634, 
     8285     5639, 5643,    0, 5643,  878, 5646, 5647, 5648, 5649,  874, 
     8286     5650, 5663, 5655, 5666, 5668, 5664,  834, 5665,  822,  817, 
     8287      808, 5669, 5676, 5670,  778,  774, 5671, 5679, 5681, 5684, 
     8288     5683, 5731, 5703, 5714, 5647, 5662,    0,    0, 5709, 5742, 
     8289     1312, 5743, 5226, 5755, 5759, 5777, 5773, 5687, 5721,    0, 
     8290        0, 5722, 5690,    0, 5732, 5725, 5730, 5736, 5743, 5799, 
     8291     5740, 9211,    0, 5758,    0, 5786, 9211, 5749, 5763,    0, 
     8292     5802, 9211,    0, 5753, 5770, 5775, 9211, 5777, 5805, 5769, 
     8293        0, 5809, 5813, 5817,    0, 5815, 5811,  751,  743, 5820, 
     8294 
     8295     5824,  726, 5821, 5825, 5828,  703, 5830,  690, 5832,  638, 
     8296      627, 5839, 5840, 5845, 5250, 5835,    0, 5799,  602, 1570, 
     8297     5892, 1581, 5904, 5908, 5914,  596, 5820, 5859,    0,    0, 
     8298     5805, 5831, 5827, 5852, 5918, 5924, 9211, 9211, 5870, 5885, 
     8299     5891, 5895,    0,    0, 9211,  938,  540, 5928, 5931, 5932, 
     8300     5935,  549,  451, 5929, 5937, 5938, 5940,  383,  379, 5307, 
     8301     5970, 5977, 5942,  979,    0, 5999, 6003, 5943, 6015, 6019, 
     8302      369,    0, 5965, 5961, 5924, 5930, 5980, 5939,    0, 5984, 
     8303     5986, 9211, 5989, 5987, 1003, 6027,  368, 6028, 5992,  322, 
     8304     6032, 6044, 6063, 6048,  312,  198, 6068, 6090, 6072, 5993, 
     8305 
     8306     6086, 6103, 6099, 6113, 6119, 6010, 6007, 6006, 6011, 6030, 
     8307     6051, 6095, 6061, 6081,  178, 6077, 6108, 6111, 6136, 6144, 
     8308      173,  166, 6148, 6162, 6176, 6174, 6185, 6189, 6201, 6197, 
     8309     6128, 6213, 6225, 6221, 5947, 9211, 6078, 6099,    0, 6105, 
     8310     6123, 6150, 6167, 6149, 6180,  146, 9211,  126, 6205, 6198, 
     8311     6242, 6247, 6251, 6255, 6229, 6272, 6268, 6276, 6288, 6293, 
     8312     6291, 6305, 6309, 6314, 6260, 9211, 6169, 6233, 6277, 6203, 
     8313     1153,   69, 1740, 6296, 6322, 6324, 6334, 6351, 6355, 6367, 
     8314     6380, 6331, 6393, 6337, 1772, 6282,    0, 6316,    0, 6328, 
     8315     6306, 6371,  106,   82, 5168, 6438, 6409, 6413, 6389, 6462, 
     8316 
     8317     6417, 6359, 9211, 9211, 6364, 6357, 6384, 6384, 6466, 6518, 
     8318     6483, 6433, 6402, 6418, 6399, 6453, 6429, 6497, 6471, 6501, 
     8319     6542, 6450, 6457, 6477, 1866, 6546, 6510, 6512, 6433, 6513, 
     8320     6522, 6558, 6571, 6534, 6576, 6579, 6585, 6589, 9211, 6566, 
     8321     6597, 9211, 6581, 6561, 6600, 6606, 9211, 9211, 6636, 6654, 
     8322     6672, 6690, 6708, 6725, 6729, 6747, 6765, 6783, 6799, 6817, 
     8323     6835, 6853, 6871, 6889, 6907, 6924, 6941, 6946,  101, 6964, 
     8324     6982, 7000, 7018, 7036, 7054, 7072, 7090, 7108, 7126, 7144, 
     8325     7162, 7180, 7198, 7216, 7233, 7249, 7254, 7271, 7289, 7307, 
     8326     7325, 7330, 7348, 7361, 7376, 7394, 7412, 7430, 7448, 7466, 
     8327 
     8328     7484, 7502, 7518, 7536, 7554, 7572, 7590, 7608, 7626, 7644, 
     8329     7662, 7679, 7695, 7712, 7730, 7748, 7766, 7784, 7789, 7807, 
     8330     7825, 7843, 7861, 7879, 7897, 7915, 7933, 7951, 7969, 7987, 
     8331     8005, 8023, 8041, 8059, 8077, 8094, 8099, 8115, 8132, 8150, 
     8332     8168, 8186, 8204, 8222, 8240, 8258, 8276, 8294, 8312, 8330, 
     8333     8348, 8366, 8384, 8402, 8420, 8438, 8456, 8474, 8492, 8510, 
     8334     8528, 8545, 8563, 8580, 8596, 8601, 8618, 8636, 8654, 8672, 
     8335     8690, 8708, 8726, 8744, 8761, 8778, 8796, 8814, 8832, 8850, 
     8336     8868, 8886, 8904, 8921, 8938, 8954, 8971, 8976, 8994, 9012, 
     8337     9030, 9048, 9066, 9084, 9102, 9120, 9138, 9156, 9174, 9192 
     8338 
    71098339    } ; 
    71108340 
    7111 static yyconst flex_int16_t yy_def[1171] = 
     8341static yyconst flex_int16_t yy_def[2001] = 
    71128342    {   0, 
    7113      1131,    1, 1132, 1132,    1,    2, 1133, 1133,    1,    2, 
    7114         1,    2, 1131, 1131, 1131, 1131, 1134, 1135, 1131, 1131, 
    7115      1136, 1137, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    7116      1131, 1131, 1131, 1131, 1138, 1138, 1138, 1138, 1138, 1138, 
    7117      1138, 1138, 1138, 1138, 1138,   40, 1138, 1138, 1138, 1138, 
    7118      1138, 1138, 1138, 1138, 1131, 1131,   55, 1139, 1131,   37, 
    7119      1138, 1138, 1138, 1138, 1138, 1131, 1140, 1131, 1140, 1140, 
    7120      1140, 1141, 1131, 1131, 1131, 1131, 1131, 1131, 1134, 1134, 
    7121      1134, 1135, 1131, 1135, 1135, 1136, 1131, 1136, 1136, 1137, 
    7122      1142, 1137, 1131, 1137, 1137, 1131, 1131, 1131, 1143, 1131, 
    7123  
    7124      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1144,   29, 1131, 
    7125      1131, 1131, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7126      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7127      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7128      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7129      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7130      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7131      1138, 1138, 1138, 1138, 1145,   55,  176, 1146, 1131, 1131, 
    7132      1131, 1131, 1131, 1131, 1131, 1131,  176, 1131, 1139, 1131, 
    7133      1139, 1139, 1139, 1131, 1131, 1131, 1138, 1138, 1138, 1138, 
    7134  
    7135      1138, 1138, 1138, 1140, 1131, 1140, 1140, 1140, 1140, 1147, 
    7136      1147, 1131, 1147, 1147, 1147, 1147, 1148, 1148,  218,  218, 
    7137       218, 1131, 1131, 1131, 1134, 1134, 1135, 1135, 1136, 1136, 
    7138      1142, 1142, 1142, 1142, 1131, 1137, 1137, 1131, 1131, 1131, 
    7139      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1144, 
    7140      1131, 1131, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7141      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7142      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7143      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1131, 1138, 1138, 
    7144      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7145  
    7146      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7147      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7148      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7149      1138, 1138, 1138, 1138, 1138, 1145,  176,  176, 1131, 1146, 
    7150      1131, 1131, 1131, 1131, 1131, 1131, 1131,  187, 1131, 1131, 
    7151      1139, 1139, 1139, 1131, 1131, 1138, 1138, 1138, 1138, 1138, 
    7152      1138, 1138, 1140, 1140, 1147, 1147, 1131, 1147, 1147, 1147, 
    7153       218,  218,  218,  218,  218, 1131, 1131, 1131, 1134, 1134, 
    7154      1135, 1135, 1136, 1136, 1142, 1137, 1137, 1131, 1131, 1131, 
    7155      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    7156  
    7157      1131, 1131, 1131, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7158      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7159      1138, 1138, 1138, 1138, 1138, 1138, 1131, 1131, 1138, 1138, 
    7160      1138, 1138, 1138, 1138, 1138, 1138, 1131, 1131, 1138, 1131, 
    7161      1131, 1138, 1149, 1138, 1138, 1138, 1138, 1131, 1131, 1138, 
    7162      1138, 1131, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7163      1131, 1131, 1138, 1138, 1131, 1131, 1138, 1138, 1138, 1138, 
    7164      1138, 1131, 1131, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7165      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7166      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1131, 
    7167  
    7168      1131, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1131, 
    7169       176,  176, 1131, 1131, 1131, 1131, 1131, 1131, 1131,  187, 
    7170      1131, 1131, 1139, 1139, 1139, 1131, 1131, 1138, 1138, 1138, 
    7171      1138, 1138, 1138, 1131, 1140, 1140, 1140, 1147, 1147, 1147, 
    7172       218,  218,  218,  218, 1131, 1150, 1131, 1134, 1151, 1135, 
    7173      1152, 1136, 1153, 1137, 1154, 1131, 1131, 1131, 1131, 1131, 
    7174      1138, 1138, 1138, 1155, 1138, 1138, 1138, 1138, 1138, 1138, 
    7175      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1131, 1138, 1138, 
    7176      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1138, 1138, 
    7177      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1131, 
    7178  
    7179      1138, 1138, 1131, 1131, 1138, 1138, 1138, 1138, 1131, 1138, 
    7180      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7181      1138, 1138, 1138, 1131, 1131, 1138, 1138, 1138, 1138, 1138, 
    7182      1138, 1138, 1138, 1138, 1131, 1138, 1138, 1138, 1138, 1138, 
    7183      1131, 1131, 1131, 1138, 1138, 1131, 1131, 1138, 1138, 1138, 
    7184       176,  176, 1131, 1131, 1131, 1131, 1131, 1131,  176, 1131, 
    7185      1131, 1139, 1139, 1156, 1131, 1131, 1131, 1138, 1131, 1138, 
    7186      1138, 1131, 1131, 1131, 1140, 1140, 1147, 1157, 1147,  218, 
    7187       218, 1158,  218, 1159, 1131, 1131, 1160, 1134, 1161, 1135, 
    7188      1131, 1162, 1136, 1163, 1137, 1137, 1131, 1131, 1164, 1138, 
    7189  
    7190      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7191      1138, 1138, 1138, 1131, 1131, 1138, 1138, 1131, 1131, 1131, 
    7192      1131, 1131, 1131, 1131, 1131, 1131, 1138, 1138, 1138, 1138, 
    7193      1138, 1138, 1138, 1138, 1131, 1131, 1138, 1138, 1138, 1138, 
    7194      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7195      1138, 1138, 1131, 1131, 1138, 1138, 1138, 1138, 1138, 1138, 
    7196      1138, 1131, 1138, 1138, 1138, 1138, 1138, 1138, 1138,  176, 
    7197       176, 1131, 1131, 1131,  176, 1139, 1165, 1139, 1131, 1138, 
    7198      1138, 1138, 1140, 1140, 1166, 1147, 1147, 1167,  218, 1131, 
    7199      1131, 1131, 1134, 1135, 1131, 1136, 1137, 1137, 1131, 1138, 
    7200  
    7201      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7202      1131, 1138, 1138, 1131, 1131, 1138, 1131, 1131, 1131, 1131, 
    7203      1131, 1131, 1131, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7204      1138, 1138, 1131, 1168, 1138, 1138, 1138, 1138, 1138, 1138, 
    7205      1138, 1131, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7206      1131, 1131, 1138, 1131, 1138, 1138, 1131, 1131, 1131, 1139, 
    7207      1139, 1131, 1138, 1131, 1138, 1140, 1140, 1147, 1147,  218, 
    7208      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1131, 
    7209      1131, 1138, 1138, 1131, 1138, 1131, 1131, 1131, 1131, 1131, 
    7210      1131, 1131, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 
    7211  
    7212      1168, 1168, 1131, 1169, 1168, 1138, 1138, 1138, 1131, 1138, 
    7213      1138, 1138, 1138, 1131, 1138, 1131, 1138, 1138, 1131, 1131, 
    7214      1139, 1131, 1138, 1138, 1140, 1140, 1147, 1138, 1138, 1138, 
    7215      1138, 1138, 1138, 1138, 1131, 1131, 1138, 1138, 1131, 1138, 
    7216      1131, 1131, 1131, 1131, 1131, 1131, 1138, 1138, 1138, 1138, 
    7217      1138, 1138, 1131, 1169, 1169, 1168, 1169, 1169, 1138, 1131, 
    7218      1138, 1138, 1131, 1138, 1131, 1138, 1138, 1131, 1131, 1139, 
    7219      1131, 1138, 1140, 1140, 1147, 1138, 1138, 1138, 1138, 1131, 
    7220      1131, 1138, 1138, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    7221      1131, 1138, 1138, 1138, 1138, 1131, 1168, 1131, 1138, 1131, 
    7222  
    7223      1131, 1138, 1138, 1131, 1139, 1131, 1140, 1140, 1147, 1138, 
    7224      1131, 1131, 1131, 1131, 1138, 1138, 1131, 1131, 1131, 1138, 
    7225      1138, 1138, 1131, 1168, 1131, 1138, 1131, 1131, 1139, 1131, 
    7226      1140, 1140, 1147, 1131, 1131, 1131, 1131, 1138, 1138, 1131, 
    7227      1131, 1138, 1131, 1168, 1131, 1138, 1131, 1139, 1131, 1140, 
    7228      1170, 1147, 1131, 1131, 1131, 1131, 1138, 1138, 1131, 1138, 
    7229      1131, 1168, 1131, 1138, 1131, 1139, 1131, 1140, 1170, 1131, 
    7230      1147, 1131, 1131, 1138, 1131, 1131, 1168, 1168, 1131, 1138, 
    7231      1131, 1139, 1131, 1140, 1147, 1131, 1138, 1168, 1169, 1131, 
    7232      1138, 1131, 1139, 1131, 1140, 1147, 1131, 1131, 1139, 1131, 
    7233  
    7234      1140, 1147, 1139, 1131, 1140, 1147, 1139, 1131, 1140, 1147, 
    7235      1139, 1131, 1140, 1147, 1139, 1131, 1140, 1147, 1139, 1131, 
    7236      1131, 1131, 1140, 1147, 1131, 1140, 1140, 1140, 1140, 1131, 
    7237         0, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    7238      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    7239      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    7240      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131 
     8343     1848,    1, 1849, 1849,    1,    1, 1850, 1850, 1849, 1849, 
     8344     1848,   11,    1,    1, 1848, 1848, 1848, 1848, 1851, 1852, 
     8345     1848, 1848, 1848, 1853, 1854, 1848, 1848, 1848, 1848, 1848, 
     8346     1848, 1848, 1848, 1848, 1848, 1848, 1855, 1855, 1855, 1855, 
     8347     1855, 1855, 1855, 1855, 1855, 1855, 1855, 1855, 1855, 1855, 
     8348       49, 1855, 1855, 1855, 1855, 1855, 1855, 1848, 1848, 1856, 
     8349       39, 1855, 1855, 1855, 1855, 1848, 1857, 1848, 1857, 1857, 
     8350     1857, 1848, 1848, 1858, 1848, 1859, 1859, 1859, 1859,   79, 
     8351       79,   79, 1859, 1859,   79,   79,   79,   79, 1859,   88, 
     8352       79,   79, 1859,   89, 1859, 1859, 1848,   58, 1860,   31, 
     8353 
     8354     1848,   79,   79,   84,   78,   58,   31, 1848, 1848, 1848, 
     8355     1861, 1861, 1861, 1862, 1848, 1862, 1862, 1848, 1863, 1864, 
     8356     1865, 1864, 1848, 1864, 1864, 1866, 1866, 1848, 1866, 1866, 
     8357     1866, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     8358     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1867, 1848, 1848, 
     8359     1848, 1848, 1848, 1848, 1848, 1868, 1868, 1868, 1868, 1868, 
     8360     1868, 1868, 1868, 1868, 1868, 1868, 1868, 1868, 1868, 1868, 
     8361     1868, 1868, 1868, 1868, 1868, 1868, 1868, 1868, 1868, 1868, 
     8362     1868, 1868, 1868, 1868, 1868, 1868, 1868, 1868, 1868, 1868, 
     8363     1868, 1868, 1868, 1868, 1868, 1868, 1868, 1868, 1868, 1868, 
     8364 
     8365     1868, 1868, 1868, 1868, 1868, 1868, 1868, 1868, 1868, 1868, 
     8366     1868, 1868, 1868, 1869,   58, 1848, 1870, 1848, 1848, 1848, 
     8367     1848, 1848, 1848, 1871, 1848, 1871, 1871, 1871, 1848, 1868, 
     8368     1868, 1868, 1868, 1868, 1868, 1872, 1848, 1872, 1872, 1872, 
     8369     1872, 1848, 1873, 1848, 1848, 1848, 1848, 1874, 1875, 1848, 
     8370       84,   84,  252,  252,  252,  252,  252,  252,  252,  252, 
     8371      252,  252,  252,  252,  252,  252,  252,  252,  252,  252, 
     8372      252,  252,  252,  252,  252,  252,  252,  252,  252,  252, 
     8373      252,  252,  252,  252,  252,  252,  252,  252,  252,  252, 
     8374      252,  252,  252,  252,  252,  252,  252,  252,  252,  252, 
     8375 
     8376      252,  252,  252,  252,  252,  252,  252,  252, 1848, 1848, 
     8377     1848, 1876,  215,  313, 1848, 1877, 1848, 1877, 1877, 1877, 
     8378     1848, 1848, 1848, 1848, 1877, 1878, 1878,  327,  327,  327, 
     8379      327,  327,  327,  252,  252,  252,  252,  215, 1848, 1848, 
     8380     1848, 1848, 1848, 1848, 1879, 1879, 1880, 1880, 1880, 1881, 
     8381     1882, 1882, 1882, 1882, 1848, 1883, 1884, 1884, 1848, 1885, 
     8382     1848, 1886, 1887, 1886, 1886, 1848, 1848, 1848, 1848, 1848, 
     8383     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1888, 
     8384     1889, 1848, 1848, 1890, 1848, 1891, 1848, 1848, 1892, 1892, 
     8385     1892, 1892, 1892, 1892, 1892, 1892, 1892, 1892, 1892, 1892, 
     8386 
     8387     1892, 1892, 1892, 1892, 1848, 1892, 1892, 1892, 1892, 1892, 
     8388     1892, 1892, 1892, 1892, 1892, 1892, 1892, 1892, 1892, 1848, 
     8389     1892, 1848, 1893, 1892, 1892, 1892, 1892, 1892, 1892, 1892, 
     8390     1892, 1892, 1892, 1892, 1892, 1892, 1892, 1892, 1892, 1892, 
     8391     1892, 1892, 1892, 1892, 1892, 1892, 1892, 1892, 1892, 1892, 
     8392     1892, 1892, 1892, 1892, 1892, 1892, 1892, 1892, 1892, 1892, 
     8393     1892, 1892, 1892, 1892, 1892, 1892, 1892, 1892, 1892, 1894, 
     8394     1848, 1895, 1848, 1848, 1848, 1848, 1848, 1848, 1896, 1896, 
     8395     1896, 1848, 1892, 1892, 1892, 1892, 1892, 1892, 1897, 1897, 
     8396     1898, 1848, 1848, 1899, 1900, 1848, 1848, 1848, 1901, 1902, 
     8397 
     8398     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8399     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8400     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8401     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8402     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8403     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8404     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8405     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1848, 1848, 1904, 
     8406     1848, 1848, 1848,  582, 1848, 1848, 1905, 1905, 1848, 1848, 
     8407     1848, 1905, 1906, 1906,  594,  594,  594,  594,  594,  594, 
     8408 
     8409      594, 1903, 1903, 1903, 1903, 1848, 1848, 1848, 1848, 1907, 
     8410     1907, 1908, 1908, 1909, 1910, 1911, 1910, 1910, 1912, 1912, 
     8411     1912, 1848, 1848, 1913, 1914, 1914, 1848, 1848, 1848, 1848, 
     8412     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     8413     1848, 1848, 1915, 1916, 1848, 1848, 1848, 1917, 1918, 1848, 
     8414     1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 
     8415     1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1848, 1919, 
     8416     1919, 1919, 1848, 1848, 1919, 1919, 1919, 1919, 1919, 1848, 
     8417     1848, 1919, 1848, 1848, 1919, 1919, 1919, 1919, 1919, 1919, 
     8418     1848, 1848, 1919, 1919, 1848, 1919, 1920, 1921, 1922, 1920, 
     8419 
     8420     1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 
     8421     1848, 1848, 1919, 1919, 1919, 1919, 1848, 1848, 1919, 1919, 
     8422     1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 
     8423     1919, 1919, 1919, 1848, 1848, 1919, 1919, 1919, 1919, 1919, 
     8424     1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 
     8425     1919, 1919, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1923, 
     8426     1923, 1923, 1848, 1919, 1919, 1919, 1919, 1919, 1919, 1924, 
     8427     1924, 1924, 1848, 1848, 1848, 1848, 1925, 1926, 1903, 1903, 
     8428     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8429     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8430 
     8431     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8432     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8433     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8434     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8435     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8436     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8437     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1927, 1927, 1848, 
     8438     1927, 1928, 1928,  873,  873,  873,  873,  873,  873,  873, 
     8439      873,  873, 1903, 1903, 1903, 1903, 1848, 1848, 1929, 1930, 
     8440     1931, 1932, 1933, 1934, 1935, 1848, 1848, 1848, 1936, 1937, 
     8441 
     8442     1938, 1939, 1940, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     8443     1848, 1848, 1941, 1848, 1919, 1919, 1919, 1919, 1919, 1942, 
     8444     1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 
     8445     1919, 1919, 1848, 1919, 1919, 1848, 1848, 1848, 1848, 1848, 
     8446     1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1848, 
     8447     1848, 1919, 1848, 1848, 1919, 1848, 1943, 1944, 1945, 1946, 
     8448     1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 
     8449     1848, 1848, 1919, 1919, 1848, 1848, 1848, 1848, 1919, 1919, 
     8450     1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 
     8451     1848, 1848, 1848, 1848, 1919, 1919, 1919, 1919, 1919, 1919, 
     8452 
     8453     1919, 1919, 1919, 1848, 1848, 1919, 1919, 1919, 1848, 1848, 
     8454     1848, 1848, 1848, 1848, 1947, 1947, 1948, 1848, 1848, 1919, 
     8455     1848, 1919, 1919, 1848, 1848, 1848, 1949, 1949, 1848, 1848, 
     8456     1848, 1848, 1903, 1903, 1903, 1903, 1903, 1950, 1903, 1903, 
     8457     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8458     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8459     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8460     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8461     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8462     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1848, 
     8463 
     8464     1848, 1848, 1848, 1848, 1848, 1848, 1951, 1952, 1848, 1951, 
     8465     1951, 1953, 1953, 1113, 1113, 1113, 1113, 1113, 1113, 1954, 
     8466     1113, 1903, 1903, 1848, 1955, 1848, 1956, 1957, 1958, 1959, 
     8467     1848, 1960, 1961, 1961, 1848, 1848, 1848, 1962, 1963, 1848, 
     8468     1964, 1848, 1965, 1965, 1966, 1848, 1848, 1848, 1848, 1848, 
     8469     1919, 1919, 1967, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 
     8470     1919, 1919, 1919, 1919, 1919, 1919, 1848, 1848, 1919, 1919, 
     8471     1848, 1848, 1848, 1848, 1848, 1919, 1919, 1919, 1919, 1919, 
     8472     1848, 1848, 1919, 1919, 1968, 1968, 1969, 1970, 1971, 1970, 
     8473     1971, 1971, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1848, 
     8474 
     8475     1848, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 
     8476     1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 1919, 
     8477     1919, 1919, 1919, 1848, 1848, 1848, 1848, 1848, 1972, 1973, 
     8478     1972, 1848, 1919, 1919, 1919, 1974, 1974, 1848, 1975, 1848, 
     8479     1848, 1903, 1903, 1976, 1903, 1903, 1903, 1903, 1903, 1903, 
     8480     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8481     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8482     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8483     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8484     1903, 1903, 1903, 1903, 1903, 1848, 1975, 1848, 1977, 1978, 
     8485 
     8486     1978, 1979, 1980, 1980, 1304, 1304, 1304, 1304, 1304, 1903, 
     8487     1903, 1848, 1848, 1981, 1982, 1848, 1983, 1983, 1848, 1984, 
     8488     1848, 1964, 1848, 1965, 1965, 1966, 1848, 1985, 1848, 1848, 
     8489     1848, 1848, 1848, 1848, 1919, 1919, 1919, 1919, 1919, 1919, 
     8490     1919, 1919, 1919, 1919, 1919, 1848, 1919, 1919, 1848, 1848, 
     8491     1919, 1848, 1848, 1848, 1919, 1919, 1919, 1919, 1848, 1848, 
     8492     1919, 1919, 1970, 1970, 1971, 1919, 1919, 1919, 1919, 1919, 
     8493     1919, 1848, 1848, 1919, 1848, 1919, 1919, 1919, 1848, 1848, 
     8494     1919, 1919, 1919, 1919, 1919, 1919, 1919, 1848, 1919, 1848, 
     8495     1848, 1848, 1848, 1919, 1848, 1848, 1848, 1972, 1972, 1848, 
     8496 
     8497     1919, 1848, 1919, 1974, 1974, 1848, 1848, 1848, 1986, 1903, 
     8498     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8499     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8500     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8501     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1848, 1987, 
     8502     1848, 1978, 1978, 1304, 1304, 1304, 1304, 1304, 1304, 1903, 
     8503     1848, 1848, 1848, 1848, 1985, 1919, 1919, 1919, 1919, 1919, 
     8504     1919, 1919, 1919, 1919, 1848, 1848, 1919, 1919, 1848, 1919, 
     8505     1848, 1848, 1848, 1919, 1919, 1919, 1919, 1919, 1970, 1919, 
     8506     1919, 1919, 1848, 1919, 1919, 1919, 1919, 1919, 1919, 1848, 
     8507 
     8508     1919, 1919, 1848, 1848, 1972, 1848, 1919, 1919, 1974, 1974, 
     8509     1848, 1848, 1988, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8510     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8511     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8512     1903, 1848, 1848, 1978, 1304, 1304, 1304, 1304, 1903, 1848, 
     8513     1989, 1848, 1848, 1848, 1990, 1848, 1848, 1919, 1919, 1919, 
     8514     1919, 1919, 1919, 1919, 1848, 1848, 1919, 1919, 1848, 1919, 
     8515     1848, 1848, 1919, 1919, 1919, 1848, 1848, 1848, 1919, 1919, 
     8516     1848, 1848, 1919, 1848, 1919, 1919, 1848, 1848, 1972, 1848, 
     8517     1919, 1974, 1974, 1848, 1988, 1903, 1903, 1903, 1903, 1903, 
     8518 
     8519     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 
     8520     1903, 1903, 1903, 1848, 1991, 1978, 1304, 1304, 1903, 1989, 
     8521     1989, 1989, 1848, 1990, 1990, 1990, 1919, 1919, 1919, 1919, 
     8522     1848, 1848, 1919, 1919, 1848, 1848, 1848, 1848, 1919, 1848, 
     8523     1919, 1848, 1919, 1919, 1848, 1972, 1848, 1974, 1974, 1903, 
     8524     1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1903, 1991, 
     8525     1848, 1991, 1991, 1978, 1304, 1989, 1989, 1992, 1990, 1848, 
     8526     1990, 1919, 1848, 1848, 1848, 1848, 1919, 1919, 1919, 1848, 
     8527     1919, 1848, 1972, 1848, 1974, 1974, 1903, 1903, 1903, 1903, 
     8528     1903, 1848, 1848, 1848, 1993, 1994, 1991, 1991, 1995, 1978, 
     8529 
     8530     1992, 1992, 1992, 1848, 1848, 1848, 1848, 1919, 1919, 1848, 
     8531     1919, 1972, 1848, 1974, 1996, 1903, 1903, 1903, 1848, 1848, 
     8532     1993, 1994, 1991, 1991, 1991, 1997, 1998, 1995, 1995, 1995, 
     8533     1978, 1992, 1989, 1992, 1848, 1848, 1848, 1848, 1919, 1919, 
     8534     1848, 1919, 1972, 1848, 1974, 1996, 1848, 1903, 1903, 1903, 
     8535     1848, 1848, 1991, 1991, 1997, 1997, 1997, 1998, 1848, 1998, 
     8536     1998, 1995, 1991, 1995, 1978, 1848, 1848, 1919, 1848, 1919, 
     8537     1972, 1848, 1974, 1903, 1903, 1848, 1848, 1991, 1991, 1997, 
     8538     1991, 1997, 1998, 1999, 1978, 1848, 1919, 1848, 1919, 1972, 
     8539     1848, 1974, 1903, 1903, 1848, 1991, 1991, 1991, 1999, 1999, 
     8540 
     8541     1999, 1978, 1848, 1848, 1972, 1848, 1974, 1848, 1991, 2000, 
     8542     1999, 1999, 1978, 1972, 1848, 1974, 1848, 1991, 1995, 1991, 
     8543     1991, 1978, 1972, 1848, 1974, 1991, 1978, 1972, 1848, 1974, 
     8544     1978, 1972, 1848, 1974, 1978, 1972, 1848, 1848, 1848, 1974, 
     8545     1978, 1848, 1974, 1974, 1974, 1974, 1848,    0, 1848, 1848, 
     8546     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     8547     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     8548     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     8549     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     8550     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     8551 
     8552     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     8553     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     8554     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     8555     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     8556     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     8557     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     8558     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     8559     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     8560     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     8561     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848 
     8562 
    72418563    } ; 
    72428564 
    7243 static yyconst flex_int16_t yy_nxt[4102] = 
     8565static yyconst flex_int16_t yy_nxt[9292] = 
    72448566    {   0, 
    7245        14,   15,   16,   15,   17,   18,   14,   19,   20,   21, 
    7246        22,   23,   24,   25,   24,   26,   24,   27,   28,   29, 
    7247        29,   29,   29,   29,   29,   29,   29,   29,   29,   30, 
    7248        31,   32,   33,   34,   35,   36,   37,   38,   39,   40, 
    7249        41,   42,   43,   42,   42,   44,   45,   46,   47,   48, 
    7250        42,   49,   50,   51,   52,   42,   53,   42,   42,   54, 
    7251        24,   24,   42,   35,   36,   37,   38,   39,   40,   41, 
    7252        42,   43,   42,   44,   45,   46,   47,   48,   42,   49, 
    7253        50,   51,   52,   42,   53,   42,   42,   54,   14,   55, 
    7254        56,   57,   58,  222,   69,   68,   69,   70,   72,   76, 
    7255  
    7256        77,   76, 1094,   74,   78,   77,   78,   59,   59,   59, 
    7257        59,   59,   59,   59,   59,   59,   59,   75,  205,   80, 
    7258      1092,   73,  222,  208,   60,   61,  205,  223,   62,   70, 
    7259        63,   71,   74,   81,   83,   74,   87,   74,   74,   91, 
    7260        82,   64,   65,  691, 1070,   75,   92,   93,   80,   75, 
    7261        73,   75,   75,   60,   61,  223,  225,   62,   70,   63, 
    7262        71,   81,   83,   96,   74,  111,   74,   74,   84,   64, 
    7263        65,  209,   74,   88,   74,   74,   94,   75,  226,   75, 
    7264        75,   97,   85,  255,   74,  225,   75,   89,   75,   75, 
    7265        95,  227,  107,   83,  239,   74, 1070,   84,   75,  209, 
    7266  
    7267       624,   74,   88,   74,   74,   94,  226,   74,  625,   75, 
    7268        85,   74,  255,   74,   75,   89,   75,   75,   95,   74, 
    7269       227,   75,  239, 1065,   74,   75,   75,   78,   77,   78, 
    7270        76,   77,   76,   75,  240,  247,   74,   75,  248,  228, 
    7271        74,  179,  206,  205,  206,  112, 1030,  179,   74,   75, 
    7272        98,   74,   98,   75,   78,   77,   78,  224,   77,  224, 
    7273      1027,   75,  240,  247,  963,   75,  248,  228,   99,   99, 
    7274        99,   99,   99,   99,   99,   99,   99,   99,   74,  207, 
    7275        74,  114,  115,  100,  261,  116,  116,  101,   74,  102, 
    7276       212,  117,   75,   75,  103,  142,  104,  105,  118,  119, 
    7277  
    7278       121,  922,   75,  263,   87,  190,  106,   74,  207,   87, 
    7279       114,  115,  100,  261,  116,  116,  101,   74,  102,  117, 
    7280        75,  253,  103,  142,  104,  105,  118,  119,  121,   87, 
    7281        75,  120,  263,  116,  106,  108,  116,  109,  109,  109, 
    7282       109,  109,  109,  109,  109,  109,  109,  121,   83,  253, 
    7283       121,   91,  511,  230,  512,  110,  110,   74,   92,   93, 
    7284       120,  229,  116,  254,  256,  116,  245,  212,  110,  260, 
    7285       262,   75,  268,  116, 1131,  121,  246,  175,  121,  127, 
    7286       116,  230,  146,  128,  110,  110,   74,  121, 1131,  129, 
    7287       229,  254,  256,  130,  121,  245,  110,  260,  262,   75, 
    7288  
    7289       122,  268,  116, 1131,  246,  116,  116,  123,  127,  116, 
    7290       146,  124,  128,  212,  125,  121, 1131,  129,   91,  121, 
    7291       121,  130,  121,  190,  126,   92,   93,  179,  190,  122, 
    7292        78,   77,   78,  179,  116,  116,  123,  143,   87,  124, 
    7293       275,  147,  125,   87,  144,  145,  116,  121,  121,  148, 
    7294        83,  121,  126,  116,  753,  149,  211,  212,  211,  131, 
    7295       121,  132,  133,  754,  134,  135,  143,  121,  213,  275, 
    7296       147,  136,  144,  145,  264,  116,  241,   82,  148,  121, 
    7297       795,  212,  116,  149,  366,  367,  366,  131,  121,  132, 
    7298       133,  242,  134,  135,  214,  121,  259,  162,  116,  136, 
    7299  
    7300       116,  190,  264,  137,  762,  241,  138,  139,  215,  140, 
    7301       150,  753,  121,  260,  121,  141,  271,  255,  151,  242, 
    7302       754,  113,  152,  214,  153,  259,  162,  116,  257,  116, 
    7303       154,  698,  137,  243,  138,  139,  215,  140,  258,  150, 
    7304       121,  260,  121,  141,  271,  116,  255,  151,  244,  113, 
    7305       152,  158,  153,  155,  272,  156,  116,  257,  154,  121, 
    7306       157,  116,  243,  273,  274,  159,  258,  276,  160,  172, 
    7307       121,  161,  179,   87,  116,  121,  244,  534,  179,  277, 
    7308       158,  155,  272,  156,  534,  116,  278,  121,  157,  282, 
    7309       116,  273,  274,  159,   91,  276,  160,  172,  121,  161, 
    7310  
    7311       163,   92,   93,  121,  164,  116,  169,  277,  165,  643, 
    7312       116,  116,  173,  170,  278,  635,  166,  282,  285,  167, 
    7313       168,  286,  174,  171,  121,  121,  378,   77,  378,  163, 
    7314       560,  559,  295,  164,  116,  169,  287,  165,  290,  116, 
    7315       116,  173,  170,  237,  166,  196,  285,  167,  168,  286, 
    7316       174,  171,  121,  121,  176,   77,  177,  178,  186,  187, 
    7317       190,  295,  179,  557,  287,  191,  290,  511,  283,  512, 
    7318       296,  237,  197,  556,  284,  188,  188,  188,  188,  188, 
    7319       188,  188,  188,  188,  188,  297,  198,  298,  310,  180, 
    7320       181,  116,   74,  182,  116,  183,  283,  192,  296,  172, 
    7321  
    7322       200,  197,  284,  142,  203,  121,  184,  185,  121,  212, 
    7323       299,  193,  534,  297,  198,  190,  298,  310,  180,  181, 
    7324       116,   74,  182,  116,  183,  300,  192,  172,  200,  510, 
    7325       400,  142,  203,  121,  184,  185,  121,  143,  299,  193, 
    7326       194,  232,  233,  232,  144,  201,  179,  396,  395,  234, 
    7327       235,  121,  394,  300,  108,  393,  195,  195,  195,  195, 
    7328       195,  195,  195,  195,  195,  195,  143,  238,  238,  288, 
    7329        91,  288,  144,  201,  110,  110,   74,   92,   93,  121, 
    7330       238,  301,  265,  266,  302,  303,  304,  110,  267,  307, 
    7331        75,  313,  212,  651,  319,  652,  238,  238,  320,  212, 
    7332  
    7333       323,  269,  236,  110,  110,   74,  270,  330,  238,  301, 
    7334       265,  266,  302,  303,  304,  110,  267,  307,   75,  199, 
    7335       313,  289,  319,  127,  116,  205,  320,  128,  323,  190, 
    7336       269,  236,  190,  129,  344,  270,  330,  130,  121,  308, 
    7337       169,  190,  309,  279,  321,  116,  291,  170,  199,  289, 
    7338       280,  322,  127,  116,  281,  331,  128,  171,  292,  121, 
    7339       293,  129,  344,  294,  202,  130,  121,  308,   87,  169, 
    7340       309,   87,  279,  321,  116,  291,  170,   83,  280,  322, 
    7341       205,  651,  281,  652,  331,  171,  292,  121,  293,  921, 
    7342      1131,  294,  202,  210,  211,  212,  211,  210,  210,  210, 
    7343  
    7344       216,  210,  210,  210,  210,  210,  210,  210,  210,  210, 
    7345       210,  210,  217,  217,  217,  217,  217,  217,  217,  217, 
    7346       217,  217,  210,  210,  210,  210,  210,  197,  217,  217, 
    7347       217,  217,  218,  217,  123,  217,  217,  217,  219,  217, 
    7348       217,  198,  217,  217,  217,  217,  220,  217,  217,  217, 
    7349       217,  221,  217,  210,  210,  217,  197,  217,  217,  217, 
    7350       217,  218,  217,  123,  217,  217,  219,  217,  217,  198, 
    7351       217,  217,  217,  217,  220,  217,  217,  217,  217,  221, 
    7352       217,  210,   98,  251,   98,  251,   68,  305,  252,  252, 
    7353       252,  252,  252,  252,  252,  252,  252,  252,  311,  366, 
    7354  
    7355       367,  366,  306,  345,  312,  332,  667,  326,  667,  328, 
    7356       333,  335, 1131,  329,  334,  100,  305,  347,  327,  101, 
    7357       343,  102,  205,  669,  355,  669,  103,  311,  104,  105, 
    7358       306,  345,  312,  314,  332,  315,  326,  328,  106,  333, 
    7359       335,  329, 1131,  334,  100,  347,  327, 1131,  101,  343, 
    7360       102,  316,  317,  355,  103,  318,  104,  105,  337,  358, 
    7361       338, 1131,  314,  190,  315, 1131,  106,  250,  250,  250, 
    7362       250,  250,  250,  250,  250,  250,  250,  324,  341,  316, 
    7363       317,  223,  925,  318,  362,  110,  110,  358,  346,  190, 
    7364       359,  325,  342,  190,  260,  351, 1131,  233,  110,  361, 
    7365  
    7366      1131,  205,  212, 1131,  385,  235,  324,  341, 1131,  223, 
    7367       339,  186,  348,  362,  110,  110,  346,  205,  359,  325, 
    7368       342,  352,  260, 1131,  351, 1131,  110,  361,  349,  349, 
    7369       349,  349,  349,  349,  349,  349,  349,  349,  339,  350, 
    7370       262,  770,  353,  771,  390,  179,  209,  356,  376,  363, 
    7371       352,  369,  377, 1131, 1131,  349,  349,  349,  349,  349, 
    7372       349,  349,  349,  349,  349,  350,  265,  357,  262,  212, 
    7373       353,  179,  267,  390,  209,  356,  376, 1131,  363,  369, 
    7374       377,  349,  349,  349,  349,  349,  349,  349,  349,  349, 
    7375       349,  350,  205,  379,  265,  357,  212,  179, 1131,  391, 
    7376  
    7377       267,  368,  206,  205,  206,  108,  291,  354,  354,  354, 
    7378       354,  354,  354,  354,  354,  354,  354,  380,  292,  399, 
    7379       293,  379,   83,  360,   87,  110,  110,  364,  370,  371, 
    7380       368,  375, 1131, 1131,  408,  291,  233,  392,  110,  207, 
    7381        87, 1131,   83,  385,  235,  380,  292,  399,  293, 1131, 
    7382       770,  360,  771, 1131,  110,  110,  364,  370,  371, 1131, 
    7383       375,  397,  381,  408, 1131,  392,  110,  383,  207,  365, 
    7384       365,  212,  365,  365,  365,  365,  365,  365,  365,  365, 
    7385       365,  365,  365,  365,  365,  365,  365,  365,  371,  371, 
    7386       381,  382,  384,  401,  398,  383,  404,  405,  365,  365, 
    7387  
    7388       365,  365,  365,  373,   91,  374,  232,  233,  232,  406, 
    7389       407,   92,   93,  409,  234,  235, 1131,  371,  371,  382, 
    7390       384,  401,  398, 1131,  404,  405,  232,  233,  232,  365, 
    7391       365,  373, 1131,  374,  234,  235,   91,  406,  407, 1131, 
    7392       388,  409,  388,   92,   93,  389,  389,  389,  389,  389, 
    7393       389,  389,  389,  389,  389,  410,  387,  365,  365,  365, 
    7394       212,  365,  365,  365,  365,  365,  365,  365,  365,  365, 
    7395       365,  365,  365,  365,  365,  365,  365,  411,  412,  386, 
    7396       547,   77,  547,  410,  387, 1131, 1131,  365,  365,  365, 
    7397       365,  365,  372,  252,  252,  252,  252,  252,  252,  252, 
    7398  
    7399       252,  252,  252,  413,  414,  411,  412,  386,  252,  252, 
    7400       252,  252,  252,  252,  252,  252,  252,  252,  365,  365, 
    7401       402,  372,  402,  686,   77,  686, 1131, 1131,  417,  419, 
    7402       403,  413,  414,  415,  420,  421,  416, 1131,  422,  423, 
    7403       424,  425,  426, 1131, 1131,  418,  365,  250,  250,  250, 
    7404       250,  250,  250,  250,  250,  250,  250,  417,  419,  439, 
    7405       444,  415,  420,  421,  416,  238,  238,  422,  423,  424, 
    7406       425,  426,  437,  418,  437,  445,  446,  440,  238,  440, 
    7407      1131, 1131,  442,  443,  447,  448,  450,  448,  439,  444, 
    7408       451, 1131,  453,  454,  238,  238,  455,  456,  288,  457, 
    7409  
    7410       288,  460, 1131,  438,  445,  446,  238,  427,  441,  427, 
    7411       442,  443,  447,  458,  450,  470,  449, 1131,  469,  451, 
    7412       453,  454, 1131,  471,  455,  456,  459,  457,  474, 1131, 
    7413       460,  461,  472,  461,  472, 1131,  475,  465,  428,  465, 
    7414       476,  462,  458,  429,  470,  430,  469,  466,  431, 1131, 
    7415       452,  471,  432,  478,  459,  433,  477,  474,  434,  435, 
    7416       479, 1131,  436,  473,  475,  480,  481,  484,  476,  485, 
    7417       488,  482,  429,  489,  430,  463,  490,  431,  452,  483, 
    7418       432,  467,  478,  433,  477,  464,  434,  435,  491,  479, 
    7419       436,  468,  486,  480,  481,  492,  484,  485,  488,  482, 
    7420  
    7421       487,  489,  493,  463,  490,  494,  495,  483,  496,  467, 
    7422       497,  498,  499,  464,  502,  503,  500,  491,  500,  468, 
    7423       504,  486,  505,  506,  492,  507,  501,  508,  487,  509, 
    7424       346,  493,  513,  494,  514,  495,  496,  515,  497,  498, 
    7425       499,  516,  517,  502,  503,  518,  519,  190,  504, 1131, 
    7426       505,  506, 1131,  507,  190,  508,  205,  509,  346,  511, 
    7427       513,  520,  514,  190, 1131,  515,  527,  528,  530,  516, 
    7428       517,  417,  531,  518,  545,  519,  212,  521,  521,  521, 
    7429       521,  521,  521,  521,  521,  521,  521,  522,  529,  212, 
    7430       524,  533,  523,  179,  535,  527,  528,  530,  371, 1131, 
    7431  
    7432       417,  531,  545,  521,  521,  521,  521,  521,  521,  521, 
    7433       521,  521,  521,  522,  212,  525,  529,  212,  524,  179, 
    7434       533,  523,  546,  535,  548,   87, 1131,  371,  539,  521, 
    7435       521,  521,  521,  521,  521,  521,  521,  521,  521,  190, 
    7436      1131,  532,  371,  525,  522,  536,  205,  536,   83,  927, 
    7437       179,  546,  548,  541,  459,  540,  539,  538,  108,  371, 
    7438       526,  526,  526,  526,  526,  526,  526,  526,  526,  526, 
    7439       532,  371,  371,  549,   87,  552,   83,  542,  110,  110, 
    7440      1131,  541,  459,  371,  540,  538,  537,  562,  371,  233, 
    7441       558,  110,  543,  561,  544,  550,  385,  235,  667, 1029, 
    7442  
    7443       667,  371,  549,  552, 1131,  542,   91,  110,  110,  551, 
    7444       553, 1131,  371,   92,   93,  537,  562,   91,  558,  110, 
    7445       543,  561,  544,  550,   92,   93,  389,  389,  389,  389, 
    7446       389,  389,  389,  389,  389,  389,  563,  564,  551,  553, 
    7447       389,  389,  389,  389,  389,  389,  389,  389,  389,  389, 
    7448       402,  565,  402,  555,  566, 1131,  554,  567, 1131,  568, 
    7449       403,  569,  570,  571,  572,  563,  564,  573,  574,  575, 
    7450       576,  577,  578,  589,  578,  590,  591, 1131,  592,  565, 
    7451       593,  596,  555,  566,  554,  597,  567,  568,  594,  569, 
    7452       570,  598,  571,  572,  599,  573,  574,  575,  576,  577, 
    7453  
    7454       437,  589,  437,  590,  595,  591,  592,  602,  593,  596, 
    7455       440,  605,  440,  579,  597,  606,  603,  594,  603,  598, 
    7456       607,  448,  599,  448,  212,  608,  609,  580,  610, 1131, 
    7457       613,  438,  595,  611,  612,  602,  614,  616,  617,  605, 
    7458       619,  441,  579,  615,  606,  618,  621,  604,  620,  607, 
    7459      1131,  622,  449,  608,  609,  580,  427,  610,  427,  613, 
    7460       623,  611,  612, 1131,  629,  614,  616,  617,  461,  619, 
    7461       461,  615,  465,  618,  465,  621,  620,  627,  462,  622, 
    7462       632,  472,  466,  472, 1033,  628,  630,  428,  623,  631, 
    7463       633,  624,  581,  629,  582,  634,  640,  583,  645,  625, 
    7464  
    7465       636,  584, 1131,  637,  585,  627,  638,  586,  587,  632, 
    7466       639,  588,  473,  628,  630, 1131, 1131,  631,  633, 1131, 
    7467       646,  581,  646,  582,  634,  640,  583,  645,  636,  584, 
    7468       626,  637,  585,  644,  638,  586,  587, 1131,  639,  588, 
    7469       600,  600,  600,  600,  600,  600,  600,  600,  600,  600, 
    7470       600,  647,  600,  600,  600,  600,  600,  600,  600,  626, 
    7471       648,  644,  649,  650,  641,  500,  641,  500,  653,  600, 
    7472       600,  600,  600,  600,  642,  501,  654,  655,  656,  657, 
    7473       658,  190,  190,  669,  205,  669,  190, 1131,  667,  648, 
    7474       667,  649,  650,  651,  668,  659,  666,  653,  701,  205, 
    7475  
    7476       600,  600,  571,  212,  654,  670,  655,  656,  657,  658, 
    7477       205,  660,  660,  660,  660,  660,  660,  660,  660,  660, 
    7478       660,  661,  664,  668,  666,  684,  701,  179,  600,  703, 
    7479       662,  571,  663,  675,  670, 1131, 1131,  660,  660,  660, 
    7480       660,  660,  660,  660,  660,  660,  660,  661, 1131,  212, 
    7481       212,  664,  679,  179,  684,  676,  705,  703,  662, 1050, 
    7482       663,  675, 1131,  660,  660,  660,  660,  660,  660,  660, 
    7483       660,  660,  660,  661,  614,  536,  205,  536, 1131,  179, 
    7484       679,  615,  687,  676,  705,  671,  678,  108,  371,  665, 
    7485       665,  665,  665,  665,  665,  665,  665,  665,  665,  677, 
    7486  
    7487       672, 1131,  672,  614,   87,   83,  680,  110,  110,  615, 
    7488       673,  687,  699,  671,  674,  678,  537,  371,  371, 1131, 
    7489       110,  371,  681,   91,  371,  682,  700,  677,  683,  704, 
    7490        92,   93,  706,  712,  680,   91,  110,  110,  689,  713, 
    7491       692,  699,  696,  697,  707,  537,  708,  371,  110,  709, 
    7492       371,  681,  710,  371,  682,  700,  711,  683,  704,  694, 
    7493      1131,  706,  712,  718,  770,  186,  775,  689,  713,  692, 
    7494      1131,  578,  707,  578,  708, 1131,  641,  709,  641,  716, 
    7495       710,  717, 1131,  719,  711,  720,  642,  721,  694,  685, 
    7496       685,  718,  685,  685,  685,  685,  685,  685,  685,  685, 
    7497  
    7498       685,  685,  685,  685,  685,  685,  685,  685,  716,  722, 
    7499       717,  719,  714,  723,  720,  721,  725,  726,  685,  685, 
    7500       685,  685,  685,  727,  728, 1131,  715,  729,  730,  724, 
    7501       731, 1131,  732,  733,  734,  739,  735,  722,  735, 1131, 
    7502       737,  714,  723,  603,  725,  603,  726,  738,  742,  685, 
    7503       685,  727,  740,  728,  715,  729,  730,  724,  741,  731, 
    7504       732,  743,  733,  734,  739,  744,  745,  736,  737,  746, 
    7505       747, 1131,  748,  749,  604,  738,  742,  685,  750,  751, 
    7506       752,  740,  755, 1131,  756,  757,  758,  741,  759,  760, 
    7507       743,  761,  766,  744,  745,  763,  764,  765,  746,  747, 
    7508  
    7509       748,  767,  749,  768,  769,  646,  750,  646,  751,  752, 
    7510       772,  755,  756,  773,  757,  758,  759,  774,  760,  190, 
    7511       761,  766,  190,  763,  764,  765,  779,  780,  669,  767, 
    7512       669,  768,  769,  672,  781,  672,  647,  782,  672,  772, 
    7513       672,  205,  773,  673,  371,  774,  205,  674,  673,  674, 
    7514       371,  674,  674,  212,  212,  779,  780,  801,  777,  776, 
    7515        91, 1131,  781,  674,   91,  371,  782,  798,  799,  788, 
    7516        91,   92,   93,  371,  802,  803, 1131,   92,   93,  371, 
    7517       770,  833,  771,  833,  190,  801,  783,  777,  776,  179, 
    7518       785,  834,  784,  787,  371,  179, 1131,  804,  788,  805, 
    7519  
    7520       806,  807,  802,  108,  803,  109,  109,  109,  109,  109, 
    7521       109,  109,  109,  109,  109,  783,  808, 1131,  809,  785, 
    7522       784,  810,  787,  110,  110,  804,  814,  805,  806,  807, 
    7523       815,  816, 1131,  817,  818, 1131,  110,  851, 1131,  851, 
    7524       770,  864,  770,  864, 1093,  808,  809,  852, 1131,  864, 
    7525       810,  864,  110,  110,  811,  814,  811,  819,  820,  815, 
    7526       816,  817,  821,  818,  110,  786,  786,  212,  786,  786, 
    7527       786,  786,  786,  786,  786,  786,  786,  786,  786,  786, 
    7528       786,  786,  786,  786,  822,  819,  820,  823,  824,  812, 
    7529       826,  821,  825,  827,  786,  786,  786,  786,  786,  828, 
    7530  
    7531       829, 1131,  813,  830,  831,  735,  832,  735,  205,  835, 
    7532       836,  837,  822,  838, 1131,  839,  823,  824,  812,  826, 
    7533       825,  840,  827,  841,  844,  786,  786,  828,  846,  829, 
    7534       813,  830,  831, 1131, 1131,  832,  736,  835, 1131,  836, 
    7535       837,  845,  838,  839,  847,  770,  186,  775,  833,  840, 
    7536       833,  841,  844,  786,  791,   77,  791,  846,  834,  792, 
    7537       792,  842,  792,  842, 1131, 1131,  792,  792, 1095,  845, 
    7538       792, 1131,  847,  792,  792,  792,  792,  792,  792,  792, 
    7539       792,  792,  790,  790,  190,  790,  790,  790,  790,  790, 
    7540       790,  790,  790,  790,  790,  790,  790,  790,  790,  790, 
    7541  
    7542       790,  848,  849,  205,  850,  853, 1131,  856,  858,  843, 
    7543       857,  790,  790,  790,  790,  790,  854,  859,  854,  862, 
    7544       865,  860,  205,  212,  863,  371,  791,   77,  791,  848, 
    7545       873,  849,  850,  879,  853,  856,  858,  843,  874,  857, 
    7546       866, 1131,  790,  790,  875,  876,  859,  877,  862,  865, 
    7547       860,  855,  863,  878,  371,   91,  882,   91,  867,  873, 
    7548       869,  879,   92,   93,   92,   93,  864,  874,  864,  866, 
    7549       790, 1131, 1131,  875,  876, 1131,  877,  811, 1131,  811, 
    7550       855,  871,  878,  883,  882,  872,  884,  867,  885,  869, 
    7551       868,  868,  212,  868,  868,  868,  868,  868,  868,  868, 
    7552  
    7553       868,  868,  868,  868,  868,  868,  868,  868,  868,  886, 
    7554       871,  883,  880,  888,  872,  884,  885,  887,  889,  868, 
    7555       868,  868,  868,  868,  890,  881,  891, 1131,  892,  893, 
    7556       894,  895,  896, 1131,  897,  898,  899,  908,  886,  900, 
    7557       212,  880,  888,  906,  907,  887,  842,  889,  842,  910, 
    7558       868,  868,  890,  881,  911,  891,  892,  893,  894,  895, 
    7559       912,  896,  897,  913,  898,  899,  908,  900,  902,  903, 
    7560       902,  906,  907,  851,  914,  851,  904,  910,  868,  905, 
    7561       915,  917,  911,  852,  854,  918,  854,  919,  912,  920, 
    7562       205,  924,  913,  923,  909,  371,  928, 1131,  929,  930, 
    7563  
    7564      1096,  931,  932,  914,  933,  934,  935,  936,  915,  937, 
    7565       917,  938, 1131,  939,  918,  919,  940,  944,  920,  916, 
    7566       924,  923,  909,  941,  371,  928,  929,  942,  930,  931, 
    7567       932,  943,  933,  934,  935,  936,  945,  937,  950,  926, 
    7568       938,  939,  946,  947,  948,  940,  944,  949,  916,  951, 
    7569       952,  941,  902,  903,  902,  942,  953,  903,  953,  943, 
    7570       904,  960, 1131,  905,  945,  961,  950,  926, 1131,  959, 
    7571       964,  946,  947,  948,  962,  965,  949,  951,  952,  902, 
    7572       903,  902,  966,  955,  956,  955,  967,  904,  968,  960, 
    7573       905,  957,  969,  961,  958,  902,  903,  902,  959,  964, 
    7574  
    7575       190,  971,  962,  904,  965,  972,  905,  205,  205,  212, 
    7576       966,  976,  977,  978,  967, 1131,  968,  979, 1131,  980, 
    7577       981,  969,  982,  983,  984,  987,  985,  988,  985,  989, 
    7578       971,  990,  991,  992,  972,  970,  986,  993,  994,  976, 
    7579       977,  978,  995,  973,  975,  974,  979,  980, 1131,  981, 
    7580       982, 1131,  983,  984,  987,  999,  988,  998,  989,  990, 
    7581       991,  992, 1131, 1131,  970,  993,  994,  996,  903,  996, 
    7582      1001,  995,  973,  975,  974,  955,  956,  955,  190,  955, 
    7583       956,  955, 1000,  957,  999,  998,  958,  957, 1002,  205, 
    7584       958,  997,  956,  997, 1003,  955,  956,  955, 1001,  904, 
    7585  
    7586      1004,  212,  905,  957, 1006,  205,  958,  955,  956,  955, 
    7587      1010, 1000, 1011, 1013, 1011,  957, 1014, 1002,  958, 1131, 
    7588      1015, 1016, 1012, 1003, 1005,  985,  985,  985,  985, 1004, 
    7589      1017, 1018, 1006, 1019, 1007,  986,  986, 1008, 1021, 1010, 
    7590      1020, 1013, 1022,  205,  205, 1014, 1131, 1009, 1015, 1025, 
    7591      1016, 1131, 1005, 1023,  903, 1023, 1026, 1028, 1017, 1018, 
    7592      1036, 1019, 1007, 1039, 1037, 1038, 1008, 1021, 1020, 1040, 
    7593      1041, 1022, 1024,  903, 1024, 1009, 1042, 1032, 1025, 1031, 
    7594       904,  205, 1011,  905, 1011, 1026, 1028, 1034, 1036, 1034, 
    7595      1045, 1039, 1012, 1037, 1038, 1046,  190, 1040, 1047, 1041, 
    7596  
    7597      1035, 1049, 1035,  212, 1042, 1056, 1032, 1055, 1031, 1043, 
    7598       903, 1043, 1044,  903, 1044, 1131, 1057, 1051, 1035, 1045, 
    7599       904, 1058, 1060,  905, 1046, 1034, 1047, 1034, 1063, 1049, 
    7600      1059,  190, 1053, 1056, 1053,  212, 1055, 1064, 1035,  205, 
    7601      1035, 1048, 1073, 1054, 1057, 1035, 1051, 1035, 1052, 1075, 
    7602      1058, 1060, 1061,  903, 1061, 1067, 1035, 1063, 1059, 1062, 
    7603       903, 1062, 1053, 1035, 1053, 1064, 1072,  904, 1074, 1048, 
    7604       905, 1073, 1079, 1054, 1068,  205, 1052, 1066, 1075, 1080, 
    7605      1081, 1071, 1131, 1067, 1078,  903, 1078,  190,  212, 1083, 
    7606      1131, 1086,  904, 1131, 1072,  905, 1074, 1087, 1131, 1090, 
    7607  
    7608      1079,  190,  205, 1068,  190, 1066, 1131, 1080, 1081, 1071, 
    7609      1076,  903, 1076,  205, 1131, 1077, 1077, 1083, 1077, 1086, 
    7610      1097, 1084, 1077, 1077, 1091, 1087, 1077, 1090, 1098, 1077, 
    7611      1077, 1077, 1077, 1077, 1077, 1077, 1077, 1077, 1082, 1085, 
    7612      1076,  903, 1076,  902,  903,  902, 1131, 1100, 1097, 1084, 
    7613      1103,  904,  212, 1091,  905, 1099, 1108, 1098, 1101,  205, 
    7614       212,  205, 1113, 1131,  190, 1131, 1082, 1085,  902,  903, 
    7615       902, 1104,  205, 1088, 1088, 1100, 1089,  190, 1103,  905, 
    7616      1088, 1088,  212, 1099, 1088, 1108, 1101, 1088, 1088, 1088, 
    7617      1088, 1088, 1088, 1088, 1088, 1088,  902,  903,  902, 1104, 
    7618  
    7619       955,  956,  955, 1102,  904, 1105,  190,  905,  957, 1106, 
    7620      1112,  958, 1109, 1107,  212, 1115, 1116,  212, 1110, 1119, 
    7621      1120, 1119,  205, 1117, 1121, 1122, 1121, 1124, 1125, 1124, 
    7622       205, 1102,  205, 1105, 1119, 1120, 1119, 1106, 1111, 1112, 
    7623      1109,  205, 1107, 1115, 1116, 1131, 1114, 1110, 1121, 1122, 
    7624      1121, 1117, 1124, 1125, 1124, 1129, 1130, 1129, 1129, 1130, 
    7625      1129, 1131, 1131, 1131, 1127, 1131, 1126, 1111, 1118, 1131, 
    7626      1131, 1123, 1131, 1131, 1131, 1114, 1131, 1131, 1131, 1131, 
    7627      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    7628      1131, 1131, 1128, 1127, 1131, 1126, 1118, 1131, 1131, 1123, 
    7629  
    7630      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    7631      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    7632      1128,   66,   66,   66,   66,   66,   66,   66,   66,   66, 
     8567       16,   17,   18,   17,   19,   20,   16,   21,   22,   23, 
     8568       24,   25,   26,   27,   26,   28,   26,   29,   30,   31, 
     8569       32,   33,   34,   35,   36,   37,   38,   39,   40,   41, 
     8570       42,   43,   44,   45,   44,   46,   47,   48,   49,   50, 
     8571       51,   44,   52,   53,   54,   55,   44,   56,   44,   44, 
     8572       57,   26,   26,   26,   37,   38,   39,   40,   41,   42, 
     8573       43,   44,   45,   46,   47,   48,   49,   50,   51,   44, 
     8574       52,   53,   54,   55,   44,   56,   44,   44,   57,   16, 
     8575       58,   59,   58,   60,  250,   69,   68,   69,   70,   72, 
     8576       73,   72,   72,   73,   72,  108,  334,  242,   74,  242, 
     8577 
     8578      110,   74,  110,  112,  108,  115,   61,   62,  250,  109, 
     8579       63,   70,   64,   71,  470,  470,  237,  113,  109,  121, 
     8580      108,  240, 1791,   65,  108,  334,  122,  123,  250,  108, 
     8581      116,  343,  112,  108,  109,   61,   62,  109,  336,   63, 
     8582       70,   64,   71,  109,  117,  113,  109,  124, 1747,  108, 
     8583      132,   65,   58,   59,   58,   60,  108,  237,  108,  116, 
     8584      343,  125,  109,  108,  151,  345,  336,  108, 1693,  344, 
     8585      109,  109,  117,  108,  108, 1693,  124,  109,   61,   62, 
     8586     1747,  109,   63,  121,   64,  108,  346,  109,  109,  125, 
     8587      122,  123,  108,  241,  345,   65,  108,  344,  109,  110, 
     8588 
     8589     1693,  110,  108,  108,  313,  109,  314,   61,   62,  109, 
     8590      242,   63,  242,   64,  346,  109,  109,  223,  216,  223, 
     8591      217,  241,  315,   65,   16,   17,   75,   17,   19,   20, 
     8592       16,   21,   22,   23,   24,   25,   26,   27,   26,   28, 
     8593       26,   29,   30,   31,   32,   33,   34,   35,   36,   76, 
     8594       77,   78,   79,   80,   81,   82,   83,   84,   83,   85, 
     8595       86,   87,   88,   89,   90,   83,   91,   92,   93,   94, 
     8596       83,   95,   83,   83,   96,   26,   26,   26,   76,   77, 
     8597       78,   79,   80,   81,   82,   83,   84,   85,   86,   87, 
     8598       88,   89,   90,   83,   91,   92,   93,   94,   83,   95, 
     8599 
     8600       83,   83,   96,   16,   58,   97,   98,   60,  152,  118, 
     8601      118,  118,  119,  115, 1693,  108,   99,  321,  387,  322, 
     8602      387,  584,  100,  388,  250,  155,  126,  391,  126,  109, 
     8603      101,  102,  108,  348,  103,  323,  104,  585,  108,  127, 
     8604      338,  127,  338,  128,  108,  367,  109,  105,  118,  118, 
     8605      118,  119,  109,  115,  158,  130,  391,  109,  339,  101, 
     8606      102,  108,  348,  103,  340,  104,  340,  108,  161,  131, 
     8607      250,  650,  368,  367,  109,  105,  106,   59,  106,   60, 
     8608      109,  250,  341,  158,  130,  250,  395,  142,  143,  142, 
     8609      349,  864,  397,  342,  107,  144,  161,  131,  145,  148, 
     8610 
     8611      368,  149,   61,   62,  146,  375,   63,  865,   64,  147, 
     8612      150,  150,  108,  153,  154,  395,  108,  121,  349,   65, 
     8613      108,  397,  342,  150,  122,  123,  109,  202,  158,  250, 
     8614      109,   61,   62,  375,  109,   63,  121,   64,  401,  150, 
     8615      150,  108,  161,  122,  123,  108,  797,   65,  133,  108, 
     8616      133,  150,  157,  250,  109,  158,  202,  158,  109,  357, 
     8617      214,  159,  109, 1019,  376, 1019,  134,  401,  160,  161, 
     8618      161,  392,  135,  158,  162,  369,  136,  108,  137,  158, 
     8619      158,  157,  182,  138,  158,  139,  140,  161,  357,  159, 
     8620      370,  109,  376,  161,  161,  141,  160,  161,  359,  392, 
     8621 
     8622      359,  135,  158,  162,  369,  136,  108,  137,  158,  158, 
     8623      182,  138,  360,  139,  140,  161,  393,  409,  370,  109, 
     8624      434,  161,  161,  141,  163,  158,  168,  158,  187,  158, 
     8625      169,  164,  188,  158,  114,  165,  170, 1131,  166,  161, 
     8626      225,  161,  189,  161,  393,  226,  409,  161,  167,  434, 
     8627      394,  250,  396,  163,  158,  168,  158,  187,  158,  169, 
     8628      164,  188,  158,  165,  170,  183,  166,  161,  227,  161, 
     8629      189,  161,  184,  185,  186,  161,  167,  158,  394,  161, 
     8630      396,  398,  228,  171,  225,  172,  173,  404,  174,  175, 
     8631      229,  161,  408, 1684,  183,  176,  451,  227,  650,  462, 
     8632 
     8633      184,  185,  186, 1021,  250, 1021,  158,  161,  230,  398, 
     8634      228,  171,  158,  172,  173,  404,  174,  175,  410,  161, 
     8635      408,  190,  231,  176,  158,  451,  161,  177,  462,  250, 
     8636      178,  179,  126,  180,  126, 1505,  371,  230,  161,  181, 
     8637      250,  158,  373,  191,  464,  127,  410,  127,  158,  190, 
     8638      231,  372,  374,  158,  161,  192,  177,  193,  178,  179, 
     8639      158,  180,  161,  194,  198,  371,  161,  181,  195,  411, 
     8640      196,  373,  191,  464,  161,  197,  156,  158,  199,  372, 
     8641      374,  200,  465,  192,  201,  193, 1021,  250, 1021,  158, 
     8642      161,  194,  250,  198,  250,  412,  195,  411,  196,  352, 
     8643 
     8644      353,  352,  161,  197,  156,  250,  199,  354,  355,  200, 
     8645      203,  465,  201,  208,  204,  158,  134,  257,  158,  158, 
     8646      209,  212,  253,  412,  205,  366,  366,  158,  250,  206, 
     8647      207,  213,  161,  161,  415,  210,  256,  416,  366,  203, 
     8648      211,  161,  208,  204,  158,  250,  257,  158,  158,  209, 
     8649      212,  253,  205,  250,  366,  366,  158,  206,  207,  213, 
     8650      161,  161,  415,  210,  256,  416,  366,  417,  211,  161, 
     8651      215,  216,  215,  217,  232,  158,  250,  418,  168,  158, 
     8652      250,  233,  169,  321,  182,  586,  399,  400,  170,  161, 
     8653      238,  237,  238,  161,  466,  417,  218,  219,  237,  108, 
     8654 
     8655      220,  585,  221,  232,  158,  418,  317,  168,  158,  233, 
     8656      250,  169,  182,  222,  399,  400,  170,  161,  239,  250, 
     8657     1848,  161, 1848,  466,  250,  218,  219,  208,  108,  220, 
     8658      183,  221,  158, 1848,  209, 1848,  250,  184,  234,  186, 
     8659      469,  222,  419,  250,  161,  424,  161,  239,  133, 1509, 
     8660      133,  235,  245,  246,  247,  248,  208, 1544,  389,  183, 
     8661      250,  158,  250,  209,  249,  184,  234,  186,  252,  469, 
     8662      419,  253,  161,  424,  161,  390,  250,  254,  249,  235, 
     8663      250,  619,  251,  619,  255,  256,  251,  389,  253,  263, 
     8664      253,  317,  277,  264,  620,  141,  620,  252,  432,  265, 
     8665 
     8666      253,  121,  256,  390,  256,  254,  225,  249,  122,  123, 
     8667      317,  251,  255,  256,  250,  251,  475,  253,  263,  253, 
     8668      277,  318,  264,  141,  251,  283,  432,  265,  282,  251, 
     8669      256,  402,  256,  250,  251,  284,  403,  258,  319,  251, 
     8670      225,  358,  253,  272,  259,  475,  273,  274,  260,  275, 
     8671      250,  261,  320,  251,  283,  276,  256,  282,  251,  413, 
     8672      402,  262,  251,  284,  250,  403,  258,  319,  251,  358, 
     8673      414,  253,  272,  259,  273,  274,  260,  275,  278,  261, 
     8674      320,  317,  482,  276,  256,  279,  280,  281,  413,  262, 
     8675      251, 1683,  256,  433,  251,  225,  437,  266,  414,  267, 
     8676 
     8677      268,  438,  269,  270,  435,  237,  251,  278,  439,  271, 
     8678      251,  482,  436,  279,  280,  281,  285,  440,  479,  251, 
     8679      256,  433,  250,  251,  437,  266,  250,  267,  268,  438, 
     8680      269,  270, 1700,  435,  286,  251,  439,  271,  251,  251, 
     8681      436,  420,  251,  420,  285,  440,  287,  479,  288,  441, 
     8682      253,  142,  143,  142,  289,  444, 1714,  457,  290,  144, 
     8683      291,  293,  297,  286,  256,  292,  251,  251,  146,  458, 
     8684      629,  251,  251,  251,  287,  294,  288,  441,  295,  253, 
     8685      250,  296,  289,  444,  421,  457,  290,  250,  291,  442, 
     8686      293,  297,  256,  292,  298,  251,  250,  458,  299,  629, 
     8687 
     8688      251,  251,  251,  294,  443,  651,  295,  459,  300,  296, 
     8689      303,  250,  421,  301,  302,  253,  250,  304,  442,  305, 
     8690      250,  251,  449,  298,  306,  250,  251,  299,  450,  256, 
     8691      463,  251,  443,  214,  651,  459,  300,  250,  627,  303, 
     8692      627,  301,  302,  628,  253,  405,  304,  305,  253,  251, 
     8693      307,  449,  306,  253,  251,  225,  450,  256,  463, 1019, 
     8694      308, 1019,  256,  309,  310,  311,  312,  256,  382,  383, 
     8695      382,  384,  476,  477,  251,  249,  144,  253,  251,  307, 
     8696      445,  335,  253,  446,  277,  146,  406,  407,  308,  249, 
     8697      256,  223,  216,  223,  217,  256,  223,  216,  223,  217, 
     8698 
     8699      476,  477,  492,  251,  492,  248, 1790,  251,  445,  335, 
     8700      114,  446,  277, 1316,  406,  407,  250,  250,  249,  316, 
     8701      316,  324,  316,  316,  316,  316,  325,  316,  316,  316, 
     8702      316,  316,  316,  316,  316,  316,  316,  316,  326,  316, 
     8703      316,  316,  316,  316,  327,  326,  326,  326,  326,  328, 
     8704      326,  329,  326,  326,  326,  330,  326,  326,  331,  326, 
     8705      326,  326,  326,  332,  326,  326,  326,  326,  333,  326, 
     8706      316,  316,  326,  327,  326,  326,  326,  326,  328,  326, 
     8707      329,  326,  326,  330,  326,  326,  331,  326,  326,  326, 
     8708      326,  332,  326,  326,  326,  326,  333,  326,  316,  303, 
     8709 
     8710      652,  359,  422,  359,  422,  250,  304,  338, 1848,  338, 
     8711      251,  250,  423,  251, 1848,  360, 1848,  361,  359,  362, 
     8712      359, 1621,  471,  337, 1622,  339,  391, 1506,  303,  652, 
     8713      386, 1848,  360, 1848,  361,  304,  362, 1848,  251,  150, 
     8714      150,  251,  364,  359,  447,  359,  223,  216,  223,  217, 
     8715      471,  337,  150,  363,  448,  391, 1848,  360, 1848,  361, 
     8716      225,  362,  377,  378,  379,  380,  485,  623,  150,  150, 
     8717      363,  364,  467,  447,  381,  148,  468,  149,  473,  425, 
     8718      150,  655,  448,  356,  365,  667,  150,  150,  381,  460, 
     8719      347,  426,  474,  427,  485,  363,  428,  429,  430,  150, 
     8720 
     8721      225,  467,  115,  461,  431,  468,  394,  473,  425,  225, 
     8722      655,  452,  365,  453,  667,  150,  150,  381,  460,  426, 
     8723      474,  427,  486,  480,  428,  429,  430,  150,  344,  454, 
     8724      455,  461,  431,  456,  394,  478,  396,  399,  484,  237, 
     8725      452,  317,  453,  483,  237,  488,  238,  237,  238,  481, 
     8726      486,  492,  480,  493,  248,  425,  344,  454,  455,  237, 
     8727      317,  456,  489,  478,  396,  399,  484,  426,  608,  427, 
     8728      317,  483,  487,  488,  239,  250,  641,  481,  641,  380, 
     8729      241,  588,  507,  250,  425,  490,  245,  246,  247,  248, 
     8730      641,  489,  642,  380,  353,  426,  608,  427,  249,  251, 
     8731 
     8732      487,  614,  355,  239,  496,  497,  498,  499,  241,  588, 
     8733      251,  507,  249,  250,  490,  317,  500,  251,  251,  251, 
     8734      578,  216,  578,  312,  251,  501,  668,  251,  251,  503, 
     8735      500,  251, 1021,  251, 1021,  251,  251,  251,  587,  251, 
     8736      250,  249,  502,  671,  251,  251,  251,  251,  251,  505, 
     8737      251,  251,  251,  504,  501,  668,  250,  251,  503,  500, 
     8738      251,  251,  251,  251,  251,  251,  506,  587,  251,  509, 
     8739      502,  251,  671,  251,  251,  251,  251,  505,  251, 1621, 
     8740      251,  504, 1622,  508,  513,  343,  250,  510,  251,  251, 
     8741     1621,  251,  251, 1622,  506,  251,  251,  250,  509,  607, 
     8742 
     8743      251,  251,  405,  251,  251,  511,  512,  578,  216,  579, 
     8744      312,  508,  251,  513,  343,  510,  251,  250,  251,  251, 
     8745      251,  251,  251,  514,  251,  251,  251,  607,  515,  251, 
     8746      317,  516,  251,  511,  512,  251,  522,  521,  251,  251, 
     8747      251,  609,  251,  517,  518,  251,  520,  251,  519,  251, 
     8748      251,  251,  514,  592,  251,  251,  610,  515,  250,  516, 
     8749      672,  251,  251,  251,  522,  521,  251,  251,  251,  609, 
     8750      251,  517,  518,  225,  251,  520,  519,  251,  680,  251, 
     8751      680,  251,  592,  523,  610,  251,  251,  524,  251,  672, 
     8752      251,  682,  251,  225,  611,  526,  528,  251,  525, 1363, 
     8753 
     8754      681,  251,  420,  251,  420,  251,  527,  529,  251,  251, 
     8755      251,  523,  530,  251,  630,  251,  524,  251,  251,  251, 
     8756      682,  251,  611,  526,  528,  638,  525,  251,  251,  550, 
     8757      251,  251,  532,  251,  527,  529,  251,  251,  533,  422, 
     8758      530,  422,  237,  631,  551,  531,  251,  623,  251,  423, 
     8759      534,  115,  535,  638,  353,  536,  251,  251,  550,  251, 
     8760      532,  614,  355,  503,  251,  251,  356,  533,  537,  538, 
     8761      251,  631,  551,  531,  317,  539,  251,  582,  534,  582, 
     8762      535,  540,  251,  536,  251,  251,  347,  251,  251,  542, 
     8763      115,  613,  503, 1792,  251,  541,  537,  538,  691,  251, 
     8764 
     8765      691,  251,  251,  539,  251,  317,  583,  251,  543,  540, 
     8766      251,  251,  250,  251,  251,  251,  544,  251,  542,  613, 
     8767      692,  545,  251,  541,  251, 1802,  546,  640,  251,  251, 
     8768      251,  250,  653,  547,  251,  583,  251,  543,  115,  251, 
     8769      251,  251,  251,  250,  544,  688,  251,  251,  251,  545, 
     8770      548,  251,  251,  555,  546,  640,  251,  549,  251,  552, 
     8771      653,  547,  251,  556,  251,  251,  251,  251,  237,  612, 
     8772      251,  251,  559,  251,  688,  689,  251,  251,  548,  250, 
     8773      250,  553,  555,  251,  554,  549,  251,  552,  251,  698, 
     8774      251,  556,  251,  251,  557,  251,  251,  612,  699,  700, 
     8775 
     8776      558,  559,  251,  251,  689,  251,  654,  251,  560,  553, 
     8777      561,  251,  554,  251,  250,  565,  566,  251,  251, 1830, 
     8778      251,  567,  250,  557,  251,  251,  562,  563,  558, 1019, 
     8779      564, 1019,  251,  251,  654,  250,  251,  560,  250,  561, 
     8780      251,  251,  572,  565,  566,  568,  251,  251,  251,  567, 
     8781      570,  251,  251,  251,  562,  563,  250,  251,  564,  569, 
     8782      636,  571,  506,  251,  251,  589,  251,  589,  251,  251, 
     8783      602,  572,  573,  225,  568,  251,  251,  914,  694,  570, 
     8784      251,  656,  251,  251,  637,  251,  251,  569,  574,  571, 
     8785      506,  251,  251, 1146,  583,  251,  251, 1137,  602,  251, 
     8786 
     8787      589,  573,  590,  251,  251,  577,  575,  694,  707,  656, 
     8788      576,  251,  637,  250,  657,  251,  251,  574,  585,  250, 
     8789      422,  251,  422,  583,  309,  310,  311,  312,  251,  583, 
     8790      423,  251,  250,  251,  577,  575,  249,  707,  321,  576, 
     8791      586,  595,  657,  251,  251,  496,  497,  498,  499,  251, 
     8792      249,  250,  326,  658,  148,  603,  591,  500,  583,  326, 
     8793      251,  326,  659,  660,  597,  150,  150,  250,  326,  326, 
     8794      595,  500,  251,  665,  661,  600,  326,  662,  150,  249, 
     8795      326,  658,  773,  603,  773,  248,  250,  326,  251,  326, 
     8796      659,  660,  597,  250,  150,  150,  326,  326,  250,  250, 
     8797 
     8798      500,  665,  661,  600,  326,  662,  150,  316,  316,  324, 
     8799      316,  316,  316,  316,  316,  316,  316,  316,  316,  316, 
     8800      316,  316,  316,  316,  316,  316,  596,  316,  316,  316, 
     8801      316,  316,  326,  598,  599,  251,  497,  326,  666,  326, 
     8802      601, 1021,  497, 1021,  326,  352,  353,  352,  605,  326, 
     8803      686,  687,  251,  354,  355,  596,  326,  690,  316,  316, 
     8804      326,  598,  599,  121,  251,  326,  666,  326,  958,  601, 
     8805      122,  123,  326,  352,  353,  352,  605,  326,  686,  687, 
     8806      251,  354,  355,  957,  326,  690,  316,  316,  316,  324, 
     8807      316,  316,  316,  316,  316,  316,  316,  316,  316,  316, 
     8808 
     8809      316,  316,  316,  316,  316,  316,  618,  316,  316,  316, 
     8810      316,  316,  533,  340,  340,  340,  340,  693,  670,  340, 
     8811      710,  340,  696,  593,  534,  701,  535,  669,  702,  604, 
     8812      594,  339,  703,  704,  618,  148,  708,  341,  316,  316, 
     8813      650,  533,  606,  606,  914,  693,  150,  150,  606,  710, 
     8814      696,  593,  534,  701,  535,  121,  702,  604,  594,  150, 
     8815      703,  704,  122,  123,  708,  378,  316,  359,  359,  359, 
     8816      359,  606,  606,  709,  713,  150,  150,  606,  359,  714, 
     8817      359,  360,  360,  361,  361,  622,  362,  150,  359,  617, 
     8818      359,  378,  360,  683,  361,  683,  362,  377,  378,  379, 
     8819 
     8820      380,  709,  360,  713,  361,  663,  362,  714,  405,  381, 
     8821      896,  908,  896,  625,  715,  684,  420,  617,  420,  363, 
     8822      363,  897,  664,  381,  669,  382,  383,  382,  384,  685, 
     8823      363,  405,  626,  144,  663,  907,  645,  646,  647,  648, 
     8824      363,  625,  146,  715,  144,  386,  716,  670,  381,  405, 
     8825      664,  705,  381,  146,  366,  366,  711,  685,  711,  695, 
     8826      626,  719,  381,  717,  706,  717,  720,  366,  721,  722, 
     8827      723,  905,  406,  724,  904,  716,  725,  405,  712,  726, 
     8828      705,  727,  730,  366,  366,  718,  731,  695,  738,  740, 
     8829      719,  381,  706,  741,  720,  366,  721,  722,  728,  723, 
     8830 
     8831      406,  673,  724,  673,  725,  628,  729,  726,  739,  732, 
     8832      727,  730,  743,  742,  731,  628,  738,  733,  740,  734, 
     8833      744,  734,  741,  674,  745,  746,  728,  747,  675,  123, 
     8834      748,  749,  750,  676,  729,  225,  739,  751,  732,  752, 
     8835      743,  735,  742,  677,  678,  733,  478,  679,  744,  754, 
     8836      755,  756,  745,  746,  736,  757,  747,  675,  748,  749, 
     8837      750,  758,  676,  737,  759,  751,  225,  752,  225,  761, 
     8838      763,  677,  678,  764,  478,  679,  663,  754,  755,  756, 
     8839      766,  767,  736,  757,  769,  768,  237,  581,  250,  758, 
     8840      250,  737,  759,  765,  250,  760,  250,  761,  706,  763, 
     8841 
     8842      250,  773,  764,  774,  248,  663,  771,  237,  771,  766, 
     8843      767,  762,  250,  769,  768,  770,  775,  779,  775,  499, 
     8844      775,  765,  776,  499,  760,  782,  706,  780,  496,  497, 
     8845      498,  499,  250,  250,  781,  250,  250,  784,  772,  762, 
     8846      500,  250,  250,  783,  770,  250,  779,  250,  250,  250, 
     8847      250,  250,  250,  782,  500,  497,  780,  250,  250,  321, 
     8848      250,  321,  781,  250,  497,  784,  785,  772,  250,  786, 
     8849      791,  795,  783,  788,  246,  793,  787,  789,  796,  250, 
     8850      790,  794,  798,  500,  799,  250,  405,  792,  680,  250, 
     8851      680,  805,  250,  811,  785,  809,  250,  786,  812,  791, 
     8852 
     8853      795,  788,  797,  793,  787,  789,  810,  796,  790,  794, 
     8854      681,  798,  250,  799,  250,  792,  683,  250,  683,  250, 
     8855      805,  811,  250,  246,  809,  250,  812,  517,  691,  250, 
     8856      691,  250,  244,  807,  808,  810,  250,  813,  684,  817, 
     8857      250,  250,  711,  250,  711,  225,  250,  250,  250,  250, 
     8858      692,  814,  806,  815,  250,  517,  673,  250,  673,  816, 
     8859      250,  807,  808,  819,  712,  818,  813,  817,  821,  250, 
     8860      753,  250,  822,  250,  824,  388,  820,  825,  674,  814, 
     8861      806,  815,  823,  800,  250,  832,  827,  816,  801,  388, 
     8862      826,  250,  819,  818,  650,  835,  828,  821,  802,  803, 
     8863 
     8864      822,  250,  804,  824,  820,  830,  825,  717,  250,  717, 
     8865      823,  829,  800,  832,  250,  827,  250,  801,  826,  250, 
     8866      831,  250,  833,  835,  834,  828,  802,  803,  250,  718, 
     8867      804,  250,  250,  830,  250,  250,  250,  734,  250,  734, 
     8868      829,  250,  250,  250,  250,  250,  863,  837,  831,  250, 
     8869      836,  833,  250,  834,  378,  838,  607,  840,  842,  735, 
     8870      250,  250,  250,  839,  846,  841,  843,  848,  849,  850, 
     8871      317,  250,  844,  378,  863,  851,  837,  847,  836,  859, 
     8872      317,  845,  853,  838,  607,  852,  840,  842,  856,  854, 
     8873      855,  839,  846,  841,  843,  639,  848,  849,  850,  871, 
     8874 
     8875      844,  317,  857,  851,  860,  847, 1402,  859, 1402,  845, 
     8876      853,  858,  635,  852,  868,  634,  856,  854,  633,  855, 
     8877      861,  216,  861,  312,  861,  216,  862,  312,  871,  321, 
     8878      857,  866,  860,  309,  310,  311,  312,  326,  589,  858, 
     8879      867,  589,  868,  589,  869,  249,  589,  865,  867,  632, 
     8880      875,  326,  623,  353,  250,  321,  865,  866,  874,  249, 
     8881      614,  355,  123,  615,  865,  326,  326,  583,  118,  326, 
     8882      583,  148,  869,  870,  326,  583,  250,  883,  875,  876, 
     8883      326,  882,  150,  150,  115,  881,  874,  250,  249,  582, 
     8884      216,  582,  217,  250,  326,  150,  583,  326,  326,  583, 
     8885 
     8886      884,  115,  887,  326,  583,  877,  883,  876,  878,  882, 
     8887      888,  150,  150,  881,  885,  218,  219,  889,  583,  220, 
     8888      886,  221,  891,  150,  890,  893,  326,  820,  906,  884, 
     8889      887,  915,  471,  877,  317, 1406,  878, 1406,  888,  359, 
     8890      317,  359,  115,  885,  218,  219,  889,  583,  220,  886, 
     8891      221,  891,  890,  360,  893,  820,  906,  623,  581,  915, 
     8892      471,  316,  316,  324,  316,  316,  316,  316,  316,  316, 
     8893      316,  316,  316,  316,  316,  316,  316,  316,  316,  316, 
     8894      892,  316,  316,  316,  316,  316,  879,  121,  326,  246, 
     8895      359,  121,  359,  246,  122,  123,  916,  872,  122,  123, 
     8896 
     8897      917,  918,  491,  880,  360,  921,  244,  619,  892,  619, 
     8898      237,  121,  316,  316, 1848,  879, 1848,  326,  122,  123, 
     8899      620,  359,  620,  359,  916,  872,  225, 1848,  917, 1848, 
     8900      918,  880,  894,  921,  909,  360,  909,  380,  895,  622, 
     8901      316,  316,  316,  324,  316,  316,  316,  316,  316,  316, 
     8902      316,  316,  316,  316,  316,  316,  316,  316,  316,  316, 
     8903      894,  316,  316,  316,  316,  316,  896,  895,  896,  359, 
     8904      873,  359,  359,  363,  359,  225,  356,  897,  919, 1848, 
     8905      920, 1848,  898,  360,  899,  361,  360,  362,  361, 1406, 
     8906      362, 1406,  316,  316,  909,  924,  910,  380,  922,  873, 
     8907 
     8908      903,  923,  911,  383,  911,  648,  118,  919,  927,  920, 
     8909      144,  902,  347,  928,  645,  646,  647,  648,  900,  146, 
     8910      316,  363,  144,  924,  363,  925,  381,  922,  926,  903, 
     8911      923,  146,  942,  911,  383,  912,  648,  927,  929,  902, 
     8912      381,  144,  928,  382,  383,  382,  384,  930,  931,  932, 
     8913      146,  144,  933,  925,  933,  941,  926,  943,  115,  944, 
     8914      146,  942,  945,  680,  946,  680,  929,  947,  683,  381, 
     8915      683,  948,  949,  952,  244,  930,  931,  932,  955,  950, 
     8916      956,  950,  961,  941,  934,  681,  943,  944,  237,  962, 
     8917      684,  945,  946, 1848,  691,  947,  691,   68,  935,  948, 
     8918 
     8919      949,  951,  952,  953,  964,  953,  955,  963,  956,  698, 
     8920      967,  961,  968,  934, 1848, 1848,  692,  962,  699,  700, 
     8921     1848,  959,  698,  959,  969,  954,  935,  673,  970,  673, 
     8922      974,  699,  700,  964,  960,  963,  960,  965, 1848,  967, 
     8923      968, 1848,  973,  960,  966,  971,  711,  971,  711,  674, 
     8924      980,  981,  984,  969,  936, 1848,  982,  970,  974,  937, 
     8925      975,  983,  975,  717,  985,  717,  965,  972,  712,  938, 
     8926      939,  973,  966,  940,  977,  986,  977,  987,  988,  980, 
     8927      981,  984,  976,  936,  982,  718,  989,  990,  937,  983, 
     8928      995,  734,  985,  734,  996,  997,  978,  938,  939,  960, 
     8929 
     8930      991,  940,  991,  986,  993,  987,  993,  988,  998,  979, 
     8931      992,  999, 1000,  735,  989, 1001,  990, 1002,  995, 1003, 
     8932     1006, 1007,  996,  997, 1008, 1004,  994, 1004, 1009,  225, 
     8933     1010, 1011, 1012, 1013, 1014,  225,  998,  979,  225, 1018, 
     8934      999, 1000, 1022, 1001, 1020, 1002,  237, 1005, 1003, 1006, 
     8935     1007, 1848,  927, 1008, 1848,  237, 1102, 1009, 1010, 1848, 
     8936     1011, 1012, 1013, 1014,  250, 1017, 1848, 1018, 1024, 1015, 
     8937     1024, 1022,  965, 1020,  250,  250, 1016, 1848, 1025,  966, 
     8938      250,  927, 1026, 1023, 1102,  250, 1027, 1026,  771,  237, 
     8939      771, 1028,  250, 1029, 1017, 1029,  248, 1015,  250,  250, 
     8940 
     8941     1029,  965, 1030,  248, 1016, 1033, 1031,  966, 1031,  499, 
     8942     1031, 1023, 1032,  499, 1027, 1035, 1039, 1034,  250, 1028, 
     8943      772, 1037,  250, 1036,  250,  250, 1038,  250, 1044,  250, 
     8944      250,  250,  250, 1033,  250,  250,  250,  250, 1848, 1848, 
     8945      250, 1040,  250, 1035, 1039, 1034,  933,  250,  933,  772, 
     8946     1037, 1041, 1036,  250,  250, 1038, 1044, 1046,  250, 1042, 
     8947      250, 1043, 1045, 1848,  250, 1049, 1047,  250, 1048, 1050, 
     8948     1040, 1053, 1057,  250, 1848,  250,  250, 1061, 1051,  250, 
     8949     1041, 1054,  250, 1056, 1058, 1055, 1046, 1042, 1462, 1043, 
     8950     1462, 1045, 1052, 1049, 1047, 1059, 1048, 1050, 1064, 1053, 
     8951 
     8952      250, 1057, 1060, 1062, 1072, 1061, 1063, 1051,  250,  250, 
     8953     1054, 1056, 1058, 1067, 1055,  950,  250,  950,  250, 1065, 
     8954     1052, 1066,  250, 1059,  953,  250,  953, 1064,  250, 1068, 
     8955     1060,  250, 1062, 1072, 1063, 1848, 1069,  951,  250, 1070, 
     8956      250, 1073, 1067,  250,  250, 1071,  954, 1065,  250, 1066, 
     8957      971,  250,  971, 1074,  250,  250, 1075,  250, 1068,  975, 
     8958      250,  975, 1077,  250, 1069,  977,  250,  977, 1070,  250, 
     8959     1073, 1848,  972, 1071, 1848, 1078,  250, 1079, 1080,  250, 
     8960     1082,  976, 1074,  250, 1075,  250, 1083,  978, 1087,  250, 
     8961     1081, 1077, 1085,  250, 1124, 1086, 1084,  991,  250,  991, 
     8962 
     8963     1076,  250,  250,  250, 1078, 1079, 1080,  992, 1082,  993, 
     8964      250,  993,  250, 1089, 1083,  250, 1088, 1087,  250, 1081, 
     8965     1095, 1085, 1124, 1086, 1084, 1090, 1092, 1093, 1076, 1091, 
     8966     1096,  994, 1094,  359, 1848,  359, 1004,  250, 1004, 1097, 
     8967     1848, 1089, 1098,  317, 1088, 1099,  317,  360, 1095, 1100, 
     8968      216, 1100,  312, 1090, 1848, 1092, 1093, 1091, 1005, 1096, 
     8969     1094, 1100,  216, 1101,  312,  321, 1125, 1105, 1097,  317, 
     8970      589, 1098, 1106, 1848, 1099,  582,  216, 1103,  217,  589, 
     8971      316, 1106,  316, 1104, 1107, 1848, 1110,  316, 1104,  316, 
     8972     1848, 1848,  316, 1104,  316, 1125, 1108, 1104,  316,  583, 
     8973 
     8974      316,  218,  219, 1127,  583,  220, 1153,  221,  583, 1848, 
     8975     1848,  321, 1107, 1105, 1110, 1114, 1113,  115,  471,  316, 
     8976      250,  316, 1112, 1848, 1151, 1108, 1120,  148,  583, 1109, 
     8977      218,  219, 1127,  583,  220, 1153,  221,  583,  150,  150, 
     8978      316, 1129,  316, 1122, 1114, 1113,  471, 1121, 1154,  121, 
     8979     1112,  150, 1151, 1848, 1848, 1120, 1134, 1135, 1111,  317, 
     8980     1111,  316, 1848,  316,  316, 1848,  316,  150,  150, 1848, 
     8981     1129, 1147, 1122, 1147,  380, 1848, 1121, 1154, 1115,  150, 
     8982      316,  316,  324,  316,  316,  316,  316,  316,  316,  316, 
     8983      316,  316,  316,  316,  316,  316,  316,  316,  316, 1116, 
     8984 
     8985      316,  316,  316,  316,  316, 1117, 1115, 1152, 1155, 1848, 
     8986     1024,  250, 1024, 1147, 1157, 1148,  380, 1158, 1848, 1159, 
     8987     1025, 1161, 1160, 1166, 1026, 1162,  316, 1116,  316, 1026, 
     8988      121,  316,  316, 1117, 1848, 1152, 1155,  122,  123, 1848, 
     8989     1848, 1238, 1157, 1238,  248,  698, 1158, 1159, 1848, 1161, 
     8990     1118, 1160, 1166, 1162, 1190, 1191,  250, 1132, 1119,  316, 
     8991      316, 1111,  324, 1111,  316,  316,  316,  316,  316,  316, 
     8992      316,  316,  316,  316,  316,  316,  316,  316,  316, 1118, 
     8993      316,  316,  316,  316,  316, 1068, 1132, 1119,  896,  896, 
     8994      896,  896, 1069, 1163, 1164, 1165, 1123, 1848, 1848,  897, 
     8995 
     8996      897,  359, 1169,  359,  898,  898, 1136,  899, 1181, 1848, 
     8997     1181,  316,  316, 1848, 1068,  360, 1170,  361, 1171,  362, 
     8998     1069, 1163, 1164, 1165, 1123, 1149,  383, 1149,  648, 1139, 
     8999     1182, 1169, 1172,  144, 1848, 1149,  383, 1150,  648,  316, 
     9000      900,  900,  146,  144, 1848, 1170, 1171, 1238, 1848, 1239, 
     9001      248, 1848,  146,  363,  933, 1173,  933, 1174, 1139, 1126, 
     9002     1140, 1172, 1140, 1126, 1126, 1126, 1126, 1126, 1126, 1126, 
     9003     1126, 1126, 1126, 1126, 1141, 1126, 1142, 1126, 1143, 1126, 
     9004     1126, 1126, 1126, 1126, 1173, 1174, 1167,  645,  646,  647, 
     9005      648, 1175, 1848, 1176, 1177,  144, 1178, 1179, 1180,  381, 
     9006 
     9007     1168, 1183, 1184, 1193,  146, 1194, 1848, 1195, 1196, 1848, 
     9008     1126, 1126, 1145,  381,  950, 1167,  950,  953, 1848,  953, 
     9009     1175, 1176, 1177, 1848, 1848, 1178, 1179, 1180, 1168, 1183, 
     9010     1848, 1184, 1193, 1199, 1194, 1195,  951, 1196, 1126,  954, 
     9011     1848, 1848,  381, 1126, 1126, 1197, 1126, 1126, 1126, 1126, 
     9012     1126, 1126, 1126, 1126, 1126, 1126, 1126, 1126, 1126, 1126, 
     9013     1126, 1126, 1199, 1126, 1126, 1126, 1126, 1126, 1185, 1187, 
     9014     1185, 1187, 1198, 1197, 1848, 1462, 1200, 1462, 1200,  957, 
     9015      958, 1186, 1188, 1186, 1188, 1202,  959,  698,  959, 1203, 
     9016     1186, 1188, 1204,  698, 1126, 1126,  699,  700, 1201,  960, 
     9017 
     9018     1198,  960, 1190, 1191,  971, 1192,  971, 1192,  960,  975, 
     9019      977,  975,  977, 1202, 1192, 1205, 1206, 1848, 1203, 1207, 
     9020     1209, 1204, 1126, 1208, 1210, 1211,  972, 1212, 1213, 1214, 
     9021     1218,  976,  978,  991,  993,  991,  993, 1215, 1216, 1217, 
     9022     1219, 1221, 1220,  992, 1205, 1206, 1186, 1188, 1207, 1209, 
     9023     1222, 1208, 1223, 1210, 1211, 1212,  994, 1213, 1214, 1218, 
     9024     1004, 1226, 1004, 1227,  960, 1215, 1216, 1217, 1219, 1221, 
     9025     1192, 1220, 1228, 1224, 1024, 1224, 1024,  225, 1222,  225, 
     9026     1223, 1232, 1005, 1225, 1025, 1233,  237, 1234, 1026, 1235, 
     9027     1226,  250, 1227, 1026,  237,  250,  250, 1024,  250, 1024, 
     9028 
     9029     1228, 1848, 1848, 1026,  326, 1026, 1230, 1025, 1229,  250, 
     9030     1232, 1026, 1848, 1848, 1233, 1234, 1026, 1026, 1235, 1245, 
     9031     1848, 1240, 1026, 1240,  499, 1236,  250, 1240, 1237, 1241, 
     9032      499, 1243, 1242,  326, 1246, 1230, 1244, 1229, 1848, 1224, 
     9033      250, 1224, 1296,  216, 1296,  312, 1848, 1848, 1245, 1225, 
     9034     1296,  216, 1297,  312, 1236,  250, 1237,  250,  250, 1243, 
     9035     1242,  250, 1246,  250, 1248, 1244, 1126, 1126,  250, 1126, 
     9036     1126, 1126, 1126, 1126, 1126, 1126, 1126, 1126, 1126, 1126, 
     9037     1126, 1126, 1126, 1126, 1126,  250, 1126, 1126, 1126, 1126, 
     9038     1126, 1250, 1248,  250, 1253,  250,  250, 1252, 1254,  250, 
     9039 
     9040      250,  250,  250, 1848, 1256,  250,  250,  250,  250,  250, 
     9041     1249,  250, 1181,  250, 1181,  250,  250, 1126, 1126, 1250, 
     9042     1251,  250, 1253, 1257,  250, 1252, 1254, 1258,  250, 1255, 
     9043     1259, 1263, 1256, 1262, 1182, 1260, 1264,  250, 1273, 1249, 
     9044     1261, 1265, 1266, 1270,  250, 1126, 1267,  250,  250, 1251, 
     9045     1268,  250, 1257,  250,  250, 1269, 1258, 1255,  250, 1259, 
     9046     1263,  250, 1262, 1260,  250, 1264,  250, 1273, 1261, 1265, 
     9047     1271, 1266, 1270, 1272, 1275, 1267, 1278,  250, 1277, 1268, 
     9048     1200,  250, 1200, 1269, 1279,  250, 1274,  250, 1276,  250, 
     9049     1280, 1281,  250, 1282,  250, 1284,  250,  250, 1271,  250, 
     9050 
     9051      250, 1272, 1201, 1275,  250, 1278,  250, 1277, 1283, 1848, 
     9052     1285,  250,  326, 1279, 1274, 1848, 1298, 1276, 1280, 1286, 
     9053     1281, 1312, 1282, 1284, 1292,  317, 1287,  317, 1289, 1336, 
     9054     1848, 1288, 1290,  589,  589,  589,  589, 1283, 1291, 1285, 
     9055     1293,  326, 1848, 1294, 1298, 1310, 1295, 1848, 1286,  896, 
     9056     1312,  896, 1299, 1292, 1287,  250, 1289, 1336, 1301, 1288, 
     9057      897, 1290,  583,  583, 1848,  326, 1291, 1305, 1293, 1848, 
     9058      321, 1294,  321, 1310, 1295,  582,  216,  582,  217,  326, 
     9059      326, 1299,  326, 1311, 1848, 1307,  148, 1301,  149, 1848, 
     9060     1338,  583,  583, 1304,  326, 1306, 1305,  150,  150, 1848, 
     9061 
     9062     1337,  218,  219, 1848,  583,  220,  326,  221,  326,  326, 
     9063      150,  326, 1311, 1327, 1307, 1327,  380, 1308,  471, 1338, 
     9064     1848, 1304, 1327, 1306, 1328,  380,  150,  150, 1337, 1848, 
     9065      218,  219,  121,  583,  220,  326,  221, 1848,  150, 1318, 
     9066     1319, 1408, 1848, 1408,  499, 1308,  471,  316,  316,  324, 
     9067      316,  316,  316,  316,  316,  316,  316,  316,  316,  316, 
     9068      316,  316,  316,  316,  316,  316,  121,  316,  316,  316, 
     9069      316,  316,  121,  122,  123,  896, 1302,  896, 1339,  122, 
     9070      123,  359, 1331,  359, 1331, 1340,  897, 1341,  619, 1342, 
     9071      619, 1343, 1848, 1137,  359,  360,  359, 1848,  316,  316, 
     9072 
     9073      896,  620,  896,  620, 1332, 1302, 1339,  359,  360,  359, 
     9074      361,  897,  622, 1340, 1224, 1341, 1224, 1342, 1136, 1848, 
     9075     1343,  360, 1848,  361, 1225,  362,  316,  316,  316,  324, 
     9076      316,  316,  316,  316,  316,  316,  316,  316,  316,  316, 
     9077      316,  316,  316,  316,  316,  316,  363,  316,  316,  316, 
     9078      316,  316,  900,  359, 1303,  359, 1344, 1352, 1345,  363, 
     9079     1329,  383, 1329,  648, 1333, 1349, 1333,  360,  144,  361, 
     9080     1350,  362, 1329,  383, 1330,  648, 1353,  146,  316,  316, 
     9081      144, 1848, 1848, 1303, 1344, 1352, 1334, 1345, 1408,  146, 
     9082     1409,  499, 1848, 1848, 1349, 1449,  216, 1449,  217, 1350, 
     9083 
     9084     1346, 1848, 1346, 1351, 1353,  363,  316, 1300, 1300,  324, 
     9085     1300, 1300, 1300, 1300, 1300, 1300, 1300, 1300, 1300, 1300, 
     9086     1300, 1300, 1300, 1300, 1300, 1300, 1347, 1300, 1300, 1300, 
     9087     1300, 1300, 1351, 1354, 1355, 1356, 1848, 1357, 1358, 1348, 
     9088     1402, 1361, 1402, 1362, 1366, 1367, 1359, 1181, 1359, 1181, 
     9089      957, 1369, 1186, 1370, 1186, 1347, 1368, 1848, 1300, 1300, 
     9090     1848, 1186, 1354, 1355, 1356, 1357, 1358, 1348, 1360, 1182, 
     9091     1361, 1362, 1848, 1366, 1367, 1402,  250, 1402, 1363, 1369, 
     9092     1364, 1370, 1364, 1848, 1371, 1368, 1300, 1313, 1321, 1364, 
     9093     1321, 1313, 1313, 1313, 1313, 1313, 1313, 1313, 1313, 1313, 
     9094 
     9095     1313, 1313, 1322, 1313, 1323, 1313, 1324, 1313, 1313, 1313, 
     9096     1313, 1313, 1371, 1200, 1185, 1200, 1185, 1186, 1402, 1187, 
     9097     1402, 1187, 1374, 1848, 1848,  957, 1372, 1186, 1372, 1186, 
     9098      958, 1377, 1188, 1378, 1188, 1201, 1186,  698, 1313, 1313, 
     9099     1326, 1188, 1365,  698, 1365, 1364, 1190, 1191, 1373, 1192, 
     9100     1374, 1192, 1190, 1191, 1375, 1192, 1375, 1192, 1192, 1377, 
     9101     1511, 1378, 1511,  248, 1192, 1848, 1313, 1313, 1313, 1381, 
     9102     1313, 1313, 1313, 1313, 1313, 1313, 1313, 1313, 1313, 1313, 
     9103     1313, 1313, 1313, 1313, 1313, 1313, 1385, 1313, 1313, 1313, 
     9104     1313, 1313, 1186, 1376, 1379, 1382, 1379, 1188, 1381, 1383, 
     9105 
     9106     1384, 1386, 1387, 1390, 1388, 1390, 1388, 1394, 1395, 1397, 
     9107     1392, 1396, 1392,  225, 1192, 1385, 1380, 1401, 1313, 1313, 
     9108     1192, 1376, 1400, 1382, 1403, 1391,  237, 1383, 1384, 1386, 
     9109     1389, 1387, 1393,  237,  250, 1394, 1451, 1395, 1397, 1396, 
     9110     1456, 1398, 1331,  250, 1331, 1401, 1313, 1333,  250, 1333, 
     9111     1848, 1400,  250, 1403, 1404,  121, 1457, 1413, 1848, 1389, 
     9112     1405, 1848,  122,  123, 1332, 1451, 1848,  250, 1456, 1334, 
     9113     1398,  250, 1848,  121,  250, 1512,  250, 1512,  250,  250, 
     9114      122,  123, 1848, 1404, 1457, 1848, 1413, 1412, 1848, 1405, 
     9115     1313, 1313,  250, 1313, 1313, 1313, 1313, 1313, 1313, 1313, 
     9116 
     9117     1313, 1313, 1313, 1313, 1313, 1313, 1313, 1313, 1313, 1411, 
     9118     1313, 1313, 1313, 1313, 1313, 1412, 1414, 1415, 1416, 1417, 
     9119      250, 1419,  250,  250, 1346,  250, 1346,  250,  250,  250, 
     9120      250, 1359,  250, 1359,  250,  250,  250, 1411,  250,  250, 
     9121      250, 1313, 1313, 1848, 1414, 1415, 1416, 1417, 1418, 1419, 
     9122     1421, 1420,  250, 1360, 1423, 1424, 1425, 1428,  250,  250, 
     9123      250,  250, 1426, 1422, 1427, 1431, 1432, 1430,  250, 1313, 
     9124     1848,  250, 1429, 1375,  250, 1375,  250, 1418,  250, 1421, 
     9125     1420, 1434,  250, 1423, 1424, 1425, 1428,  250, 1444,  250, 
     9126     1426, 1422, 1427, 1438, 1431, 1432, 1430,  250, 1433, 1440, 
     9127 
     9128     1429, 1435, 1372,  250, 1372, 1436, 1458, 1439, 1848, 1434, 
     9129     1441, 1512, 1437, 1512, 1379,  250, 1379, 1444, 1442, 1443, 
     9130     1446, 1438, 1445, 1848, 1373,  250, 1433,  317, 1440, 1435, 
     9131     1388,  250, 1388, 1436, 1458, 1439, 1380, 1459, 1441, 1448, 
     9132     1437, 1390,  250, 1390, 1461, 1468, 1442, 1443, 1460, 1446, 
     9133     1445, 1392,  250, 1392, 1469, 1453, 1447, 1449,  216, 1449, 
     9134     1450, 1848, 1848, 1391,  896, 1459,  896, 1448,  359, 1808, 
     9135      359, 1808, 1461, 1393, 1468,  897, 1470, 1460, 1542,  216, 
     9136     1542,  312,  360, 1469, 1453, 1447, 1452, 1452,  324, 1452, 
     9137     1452, 1452, 1452, 1452, 1452, 1452, 1452, 1452, 1452, 1452, 
     9138 
     9139     1452, 1452, 1452, 1452, 1452, 1470, 1452, 1452, 1452, 1452, 
     9140     1452,  619, 1848,  619, 1464,  383, 1464,  648, 1474, 1471, 
     9141     1848, 1331,  144, 1331,  620, 1848,  620, 1553, 1333, 1553, 
     9142     1333,  146, 1472,  359, 1473,  359, 1477, 1452, 1452,  359, 
     9143      359,  359,  359, 1332,  146, 1848, 1474,  360, 1471,  361, 
     9144     1334,  622, 1661,  360,  360,  361,  361,  362,  362, 1662, 
     9145     1848, 1472, 1663, 1473, 1477, 1452,  316,  316,  324,  316, 
     9146      316,  316,  316,  316,  316,  316,  316,  316,  316,  316, 
     9147      316,  316,  316,  316,  316,  363,  316,  316,  316,  316, 
     9148      316,  363,  363, 1478, 1464,  383, 1465,  648, 1479, 1466, 
     9149 
     9150     1848, 1480,  144, 1467, 1481, 1482, 1848, 1483, 1484, 1661, 
     9151     1455,  146, 1487, 1485, 1486, 1848, 1662,  316,  316, 1663, 
     9152     1848, 1478, 1359, 1552, 1359, 1552,  380, 1479, 1466, 1480, 
     9153     1848, 1848, 1467, 1481, 1482, 1483, 1848, 1484, 1455, 1346, 
     9154     1487, 1346, 1485, 1486, 1360,  316,  316,  316,  324,  316, 
     9155      316,  316,  316,  316,  316,  316,  316,  316,  316,  316, 
     9156      316,  316,  316,  316,  316, 1475,  316,  316,  316,  316, 
     9157      316, 1488, 1363, 1489, 1364, 1489, 1364, 1848, 1476, 1490, 
     9158     1491, 1492, 1497, 1364, 1363, 1494, 1364, 1375, 1364, 1375, 
     9159     1365,  698, 1365, 1495, 1475, 1364, 1848,  316,  316, 1488, 
     9160 
     9161     1190, 1191, 1372, 1192, 1372, 1192, 1476, 1490, 1501, 1491, 
     9162     1492, 1497, 1192, 1494, 1379, 1496, 1379, 1498, 1499, 1502, 
     9163     1390, 1495, 1390, 1504, 1373,  316, 1493, 1388, 1392, 1388, 
     9164     1392, 1503, 1507, 1508,  237,  250, 1380, 1501,  250, 1364, 
     9165      250,  250, 1391, 1496,  250, 1498, 1499,  250, 1502,  250, 
     9166     1393, 1364, 1504, 1500, 1493,  250,  250,  250, 1521, 1503, 
     9167     1507, 1514, 1508,  250,  250, 1515, 1517, 1516, 1192,  250, 
     9168      250, 1518,  250,  250, 1510,  250, 1519,  250,  250,  250, 
     9169      250, 1529, 1500, 1520,  250,  250,  250, 1521, 1543, 1848, 
     9170     1514,  250, 1522, 1848, 1515, 1517, 1516, 1524, 1526, 1527, 
     9171 
     9172     1518, 1523, 1510, 1525, 1528, 1519, 1530, 1545, 1533, 1529, 
     9173     1547, 1531, 1520,  250, 1536, 1532, 1543, 1535,  250, 1534, 
     9174     1522, 1538, 1541, 1546, 1548, 1524, 1558, 1526, 1527, 1523, 
     9175     1539, 1525,  250, 1528, 1530, 1848, 1545, 1533, 1547, 1531, 
     9176     1537, 1540, 1536, 1560, 1532, 1535, 1550, 1534, 1550, 1538, 
     9177     1559, 1541, 1546, 1548, 1848, 1558, 1551, 1549, 1539, 1553, 
     9178      143, 1553, 1561, 1554,  383, 1554,  384,  144, 1562, 1537, 
     9179     1540,  144, 1560, 1563, 1564, 1565,  146, 1566, 1559, 1567, 
     9180      146, 1554,  383, 1554, 1555, 1568, 1549, 1569, 1570, 1556, 
     9181     1561, 1571, 1572, 1848, 1573, 1574, 1562, 1489, 1557, 1489, 
     9182 
     9183     1575, 1563, 1564, 1565, 1576, 1566, 1576, 1567, 1363, 1578, 
     9184     1364, 1579, 1364, 1580, 1568, 1569, 1581, 1570, 1581, 1364, 
     9185     1571, 1572, 1573, 1574, 1583, 1584, 1577, 1585, 1586, 1575, 
     9186     1587, 1588, 1590,  225, 1591,  237,  237, 1578, 1582, 1579, 
     9187     1511, 1580, 1511,  248, 1594,  250, 1594,  499,  250,  250, 
     9188      250,  250,  250, 1583, 1584, 1585, 1586,  250, 1587, 1589, 
     9189     1588, 1590, 1592, 1591, 1593,  250,  250,  250,  250, 1596, 
     9190      250,  250,  250,  250, 1848, 1364, 1598, 1576,  250, 1576, 
     9191     1581,  250, 1581,  250, 1597,  250,  250, 1600, 1589, 1617, 
     9192     1599, 1592, 1603, 1593, 1601, 1604, 1608, 1605, 1596, 1577, 
     9193 
     9194     1618, 1602, 1582, 1607, 1614, 1598, 1614, 1848, 1606, 1609, 
     9195     1611,  250, 1597, 1610, 1615, 1600,  317, 1617, 1599, 1630, 
     9196     1603, 1613, 1601, 1627, 1604, 1608, 1605, 1612, 1618, 1602, 
     9197     1848, 1607, 1542,  216, 1542,  312, 1606, 1609, 1619, 1611, 
     9198     1848, 1610, 1616, 1550, 1552, 1550, 1552,  380, 1630, 1613, 
     9199     1848, 1627, 1848, 1551, 1632, 1612, 1623,  383, 1623,  648, 
     9200     1624,  383, 1624, 1634,  144, 1628, 1629, 1619, 1625, 1631, 
     9201     1633, 1616, 1635,  146, 1553,  143, 1553, 1626,  382,  383, 
     9202      382,  384,  144, 1632, 1638, 1639,  144, 1576, 1640, 1576, 
     9203     1641,  146, 1634, 1628, 1629,  146, 1642, 1631, 1633, 1643, 
     9204 
     9205     1636, 1635, 1636, 1581, 1644, 1581, 1645,  225, 1647, 1577, 
     9206     1637,  237, 1638,  250, 1639,  237, 1640,  250, 1594, 1641, 
     9207     1594,  499,  250,  250, 1642, 1582,  250,  250, 1643, 1636, 
     9208      250, 1636,  250, 1644,  250, 1645, 1647,  317, 1649, 1637, 
     9209     1848,  250,  250, 1665, 1646, 1675, 1614, 1648, 1614, 1672, 
     9210     1848, 1650, 1655, 1653, 1848, 1651, 1615, 1656, 1676, 1657, 
     9211     1673, 1654, 1673, 1677, 1652, 1848, 1848, 1649, 1658, 1659, 
     9212     1674, 1665, 1646, 1675, 1664, 1648, 1848, 1848, 1672, 1650, 
     9213     1848, 1655, 1653, 1651, 1848, 1678, 1656, 1676, 1657, 1654, 
     9214     1848, 1677, 1652, 1666, 1667, 1666, 1668, 1658, 1659, 1679, 
     9215 
     9216     1848, 1621, 1664, 1848, 1622, 1623,  383, 1623,  648, 1624, 
     9217      650, 1624, 1680,  144, 1678, 1669, 1670, 1669, 1671, 1636, 
     9218     1681, 1636,  146, 1625, 1682, 1636, 1626, 1636, 1679, 1637, 
     9219      237,  250, 1626,  237,  250, 1637, 1673,  250, 1673,  250, 
     9220      250, 1680,  250, 1848, 1661, 1667, 1674, 1848, 1735, 1681, 
     9221     1735, 1662, 1702, 1682, 1663, 1703, 1685, 1848, 1686, 1736, 
     9222     1706, 1687, 1704, 1707, 1704, 1688, 1673, 1690, 1673, 1691, 
     9223     1689, 1692, 1693, 1694, 1695, 1705, 1674, 1705, 1697, 1698, 
     9224     1697, 1699, 1709, 1696, 1705, 1685, 1662, 1686, 1706, 1663, 
     9225     1687,  225, 1707, 1688,  250,  317, 1690, 1696, 1691, 1689, 
     9226 
     9227     1666, 1667, 1666, 1668, 1666, 1667, 1666, 1668, 1621, 1708, 
     9228     1709, 1622, 1621, 1710, 1711, 1622, 1669, 1670, 1669, 1671, 
     9229      645,  646,  647,  648, 1625, 1713, 1696, 1712,  144,  237, 
     9230      250, 1731,  381, 1626,  250, 1717, 1848,  146, 1708, 1737, 
     9231     1848, 1848, 1710, 1711, 1740, 1719,  381, 1719, 1695, 1719, 
     9232     1738, 1720, 1695, 1713, 1739, 1712, 1715, 1716, 1741, 1731, 
     9233     1718, 1848, 1848, 1717, 1692, 1693, 1694, 1695, 1737, 1697, 
     9234     1698, 1697, 1699, 1740, 1698,  381, 1696, 1662, 1738,  250, 
     9235     1663, 1729, 1739,  237, 1730, 1715, 1716, 1741, 1667, 1718, 
     9236     1696, 1723, 1724, 1725, 1726, 1702, 1742,  225, 1703, 1662, 
     9237 
     9238     1744, 1667, 1663, 1727, 1732, 1733, 1732, 1734, 1702, 1745, 
     9239      250, 1703, 1702,  250, 1704, 1703, 1704, 1727, 1848, 1696, 
     9240     1735, 1848, 1735, 1848, 1742, 1748, 1766, 1705, 1744, 1705, 
     9241      317, 1736, 1767, 1705, 1743, 1705, 1705, 1751, 1745, 1751, 
     9242     1695, 1749, 1705, 1848, 1768, 1751, 1727, 1752, 1695, 1753, 
     9243     1698, 1753, 1726, 1748, 1766, 1848, 1750, 1662, 1848, 1848, 
     9244     1663, 1767, 1743, 1723, 1724, 1725, 1726, 1765, 1769,  225, 
     9245     1749, 1662, 1768, 1848, 1663, 1727, 1724, 1753, 1698, 1754, 
     9246     1726, 1848,  237, 1756, 1750, 1662, 1757, 1759, 1663, 1727, 
     9247     1848, 1698, 1770, 1772, 1760, 1765, 1769, 1761, 1729, 1698, 
     9248 
     9249      250, 1730, 1762, 1763, 1762, 1764, 1729,  250, 1786, 1730, 
     9250     1729, 1771, 1848, 1730, 1732, 1733, 1732, 1734, 1727, 1773, 
     9251     1770, 1772, 1702, 1667, 1848, 1703, 1666, 1667, 1666, 1668, 
     9252     1702, 1724, 1789, 1703, 1621, 1848, 1786, 1622, 1756, 1771, 
     9253     1775, 1757, 1848, 1776, 1774, 1776, 1695, 1773, 1776, 1848, 
     9254     1777, 1695, 1778, 1698, 1778, 1726, 1778, 1698, 1779, 1726, 
     9255     1662, 1789,  317, 1663, 1662, 1848, 1848, 1663, 1775, 1848, 
     9256     1724, 1787, 1774, 1780, 1781, 1780, 1782, 1756, 1759, 1848, 
     9257     1757, 1756, 1848, 1848, 1757, 1760, 1848, 1848, 1761, 1692, 
     9258     1693, 1694, 1695, 1759, 1783, 1724, 1783, 1784,  250, 1787, 
     9259 
     9260     1760, 1696, 1760, 1761, 1785, 1761, 1762, 1763, 1762, 1764, 
     9261     1723, 1724, 1725, 1726, 1729, 1696, 1698, 1730, 1662, 1788, 
     9262     1803, 1663, 1727, 1729,  250, 1795, 1730, 1795, 1695, 1848, 
     9263      225, 1848, 1785, 1724, 1793, 1795, 1727, 1796, 1695, 1724, 
     9264     1756, 1848, 1848, 1757, 1696, 1804, 1800, 1788, 1803, 1801, 
     9265     1806, 1794, 1797, 1698, 1797, 1726, 1797, 1698, 1798, 1726, 
     9266     1662,  317, 1793, 1663, 1662, 1727,  225, 1663, 1780, 1781, 
     9267     1780, 1782, 1805,  237, 1804, 1848, 1756, 1848, 1806, 1757, 
     9268     1794, 1723, 1724, 1725, 1726, 1817,  237, 1817, 1695, 1662, 
     9269     1848, 1724, 1663, 1727, 1783, 1724, 1783, 1784, 1800, 1815, 
     9270 
     9271     1805, 1801, 1760, 1813,  317, 1761, 1814, 1727, 1848, 1807, 
     9272     1809, 1698, 1809, 1726, 1809, 1698, 1810, 1726, 1662, 1724, 
     9273      225, 1663, 1662, 1816, 1848, 1663, 1800, 1815, 1824, 1801, 
     9274     1817, 1813, 1817, 1695, 1814, 1724, 1727, 1807, 1848, 1808, 
     9275     1848, 1808, 1800, 1848, 1822, 1801, 1848, 1823, 1848, 1848, 
     9276     1848, 1816,  317, 1848, 1848,  237, 1848, 1824, 1848,  225, 
     9277     1848, 1848, 1848, 1811, 1781, 1811, 1812, 1818, 1698, 1818, 
     9278     1699, 1800, 1822, 1698, 1801, 1662, 1823, 1833, 1663, 1827, 
     9279     1729, 1848, 1828, 1730, 1811, 1781, 1811, 1812, 1848, 1848, 
     9280     1848, 1848, 1800, 1848, 1848, 1801, 1848, 1825, 1826, 1698, 
     9281 
     9282     1826, 1726, 1829, 1661, 1848, 1833, 1662, 1848, 1827, 1663, 
     9283     1662, 1828,  317, 1663,  225,  237, 1848, 1848, 1660, 1818, 
     9284     1698, 1818, 1819, 1660,  317, 1825, 1660, 1821, 1660, 1660, 
     9285     1663, 1829, 1848, 1660, 1660, 1831,  237, 1848, 1660, 1848, 
     9286     1660, 1660, 1660, 1697, 1698, 1697, 1699, 1826, 1698, 1826, 
     9287     1726, 1662, 1848, 1848, 1663, 1662, 1832, 1834, 1663, 1836, 
     9288     1837, 1836, 1848,  237, 1831, 1848, 1835, 1848,  237, 1660, 
     9289     1660, 1660, 1838, 1839, 1838, 1848, 1840, 1841, 1842, 1841, 
     9290     1836, 1837, 1836,  237, 1832, 1834,  223,  216,  223,  217, 
     9291     1838, 1839, 1838, 1848, 1835, 1843, 1848, 1660, 1841, 1842, 
     9292 
     9293     1841, 1846, 1847, 1846, 1840, 1845, 1844, 1846, 1847, 1846, 
     9294     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     9295     1848, 1848, 1848, 1848, 1843, 1848, 1848, 1848, 1848, 1848, 
     9296     1848, 1848, 1848, 1845, 1848, 1844,   66,   66,   66,   66, 
     9297       66,   66,   66,   66,   66,   66,   66,   66,   66,   66, 
    76339298       66,   66,   66,   66,   67,   67,   67,   67,   67,   67, 
    7634        67,   67,   67,   67,   67,   67,   67,   79, 1131,   79, 
    7635        79,   79,   79,   79,   79,   79,   79,   79,   79,   79, 
    7636        82,   82,   82,   82,   82,   82,   82,   82,   82,   82, 
    7637        82,   82,   82,   86,   86,   86,   86,   86,   86,   86, 
    7638        86,   86,   86,   86,   86,   86,   90,   90,   90,   90, 
    7639        90,   90,   90,   90,   90,   90,   90,   90,   90,  113, 
    7640  
    7641       113,  113,  113,  113,  113,  113,  113,  113,  189,  189, 
    7642       189,  189,  189,  189,  189,  189,  189,  189,  189,  189, 
    7643       189,  204,  204,  204,  204,  204,  204,  204,  204,  204, 
    7644       204,  204,  204,  204,  210,  210,  210,  210,  210, 1131, 
    7645       210,  210,  210, 1131,  210, 1131,  210,  231,  231,  231, 
    7646       231,  231,  231,  231,  231,  231,  231,  231,  231,  231, 
    7647        99, 1131, 1131, 1131, 1131, 1131, 1131, 1131,   99,  249, 
    7648       249, 1131,  249,  249, 1131,  249, 1131, 1131,  249,  249, 
    7649      1131,  249,  336,  336,  336,  336,  340,  340,  340,  340, 
    7650       340,  340,  340,  340,  340,  340,  340,  340,  340,  365, 
    7651  
    7652       365,  365,  365,  365,  365,  365,  365,  365,  365,  365, 
    7653       365,  365,  371,  371,  371,  371,  371,  371,  371,  371, 
    7654       371,  371,  371,  371,  371,  601,  601,  601, 1131,  601, 
    7655       601,  601,  601,  601,  601,  601,  601,  601,  685, 1131, 
    7656       685,  685,  685,  685,  685,  685,  685,  685,  685,  685, 
    7657       685,  688, 1131,  688,  688,  688,  688,  688,  688,  688, 
    7658       688,  688,  688,  688,  690,  690,  690,  690,  690,  690, 
    7659       690,  690,  690,  690,  690,  690,  690,  693,  693,  693, 
    7660       693,  693,  693,  693,  693,  693,  693,  693,  693,  693, 
    7661       695,  695,  695,  695,  695,  695,  695,  695,  695,  695, 
    7662  
    7663       695,  695,  695,  702, 1131,  702,  702,  702,  702,  702, 
    7664       702,  702,  702,  702,  702,  702,  778,  778,  778,  778, 
    7665       778,  778,  778,  778,  778,  778,  778,  778,  778,  786, 
    7666       786,  786,  786,  786,  786,  786,  786,  786,  786,  786, 
    7667       786,  786,  789,  789,  789,  789,  789,  789,  789,  789, 
    7668       789,  789,  789,  789,  789,  790, 1131,  790,  790,  790, 
    7669       790,  790,  790,  790,  790,  790,  790,  790,  793, 1131, 
    7670       793,  793,  793,  793,  793,  793,  793,  793,  793,  793, 
    7671       793,  794,  794,  794,  794,  794,  794,  794,  794,  794, 
    7672       794,  794,  794,  794,  796,  796,  796,  796,  796,  796, 
    7673  
    7674       796,  796,  796,  796,  796,  796,  796,  797,  797,  797, 
    7675       797,  797,  797,  797,  797,  797,  797,  797,  797,  797, 
    7676       800, 1131,  800,  800,  800,  800,  800,  800,  800,  800, 
    7677       800,  800,  800,  861,  861,  861,  861,  861,  861,  861, 
    7678       861,  861,  861,  861,  861,  861,  868,  868,  868,  868, 
    7679       868,  868,  868,  868,  868,  868,  868,  868,  868,  870, 
    7680       870,  870,  870,  870,  870,  870,  870,  870,  870,  870, 
    7681       870,  870,  901,  901,  901,  901,  901,  901,  901,  901, 
    7682       901,  901,  901,  901,  901,  954,  954,  954,  954,  954, 
    7683       954,  954,  954,  954,  954,  954,  954,  954, 1069, 1069, 
    7684  
    7685      1069, 1069, 1069, 1069, 1069, 1069, 1069, 1069, 1069, 1069, 
    7686      1069,   13, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    7687      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    7688      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    7689      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    7690      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    7691      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    7692      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    7693      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    7694      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    7695  
    7696      1131 
     9299       67,   67,   67,   67,   67,   67,   67,   67,   67,   67, 
     9300       67,   67,  111,  111, 1848,  111,  111,  111,  111,  111, 
     9301      111,  111,  111,  111,  111,  111,  111,  111,  111,  111, 
     9302      114,  114,  114,  114,  114,  114,  114,  114,  114,  114, 
     9303 
     9304      114,  114,  114,  114,  114,  114,  114,  114,  120,  120, 
     9305      120,  120,  120,  120,  120,  120,  120,  120,  120,  120, 
     9306      120,  120,  120,  120,  120,  120,  129, 1848, 1848, 1848, 
     9307     1848, 1848, 1848,  129, 1848,  129, 1848,  129,  129,  129, 
     9308      129,  129,  156,  156,  156,  156,  156,  224,  224,  224, 
     9309      224,  224,  224,  224,  224,  224,  224,  224,  224,  224, 
     9310      224,  224,  224,  224,  224,  236,  236,  236,  236,  236, 
     9311      236,  236,  236,  236,  236,  236,  236,  236,  236,  236, 
     9312      236,  236,  236,  243,  243,  243,  243,  243,  243,  243, 
     9313      243,  243,  243,  243,  243,  243,  243,  243,  243,  243, 
     9314 
     9315      243,  251, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     9316     1848, 1848,  251,  251,  251,  251,  251,  316,  316,  316, 
     9317      316,  316,  316,  316,  316,  316,  316,  316,  316,  316, 
     9318      316,  316,  316,  316,  316,  111,  111, 1848,  111,  111, 
     9319      111,  111,  111,  111,  111,  111,  111,  111,  111,  111, 
     9320      111,  111,  111,  114,  114,  114,  114,  114,  114,  114, 
     9321      114,  114,  114,  114,  114,  114,  114,  114,  114,  114, 
     9322      114,  350,  350,  350,  350,  350,  350,  350,  350,  350, 
     9323      350,  350,  350,  350,  350,  350,  350,  350,  350,  120, 
     9324      120,  120,  120,  120,  120,  120,  120,  120,  120,  120, 
     9325 
     9326      120,  120,  120,  120,  120,  120,  120,  351,  351,  351, 
     9327      351,  351,  351,  351,  351,  351,  351,  351,  351,  351, 
     9328      351,  351,  351,  351,  351,  129, 1848, 1848, 1848, 1848, 
     9329     1848, 1848,  129, 1848,  129, 1848, 1848,  129,  129,  129, 
     9330      129,  385,  385,  385,  385, 1848,  385,  385,  385,  385, 
     9331      385,  385, 1848,  385,  385, 1848, 1848,  385,  385,  156, 
     9332      156,  156,  156,  156,  472,  472,  472,  472,  472,  472, 
     9333      472,  472,  472,  472,  472,  472,  472,  472,  472,  472, 
     9334      472,  472,  224,  224,  224,  224,  224,  224,  224,  224, 
     9335      224,  224,  224,  224,  224,  224,  224,  224,  224,  224, 
     9336 
     9337      236,  236,  236,  236,  236,  236,  236,  236,  236,  236, 
     9338      236,  236,  236,  236,  236,  236,  236,  236,  243,  243, 
     9339      243,  243,  243,  243,  243,  243,  243,  243,  243,  243, 
     9340      243,  243,  243,  243,  243,  243,  494,  494,  494,  494, 
     9341      494,  494,  494,  494,  494,  494,  494,  494,  494,  494, 
     9342      494,  494,  494,  494,  495,  495,  495,  495,  495,  495, 
     9343      495,  495,  495,  495,  495,  495,  495,  495,  495,  495, 
     9344      495,  495,  580,  580,  580,  580,  580,  580,  580,  580, 
     9345      580,  580,  580,  580,  580,  580,  580,  580,  580,  580, 
     9346      316,  316,  316,  316,  316,  316,  316,  316,  316,  316, 
     9347 
     9348      316,  316,  316,  316,  316,  316,  316,  316,  326,  326, 
     9349      326,  326,  326,  326,  326,  326,  326,  326,  326,  326, 
     9350      326,  326,  326,  326,  326,  326,  111,  111, 1848,  111, 
     9351      111,  111,  111,  111,  111,  111,  111,  111,  111,  111, 
     9352      111,  111,  111,  111,  114,  114,  114,  114,  114,  114, 
     9353      114,  114,  114,  114,  114,  114,  114,  114,  114,  114, 
     9354      114,  114,  350,  350,  350,  350,  350,  350,  350,  350, 
     9355      350,  350,  350,  350,  350,  350,  350,  350,  350,  350, 
     9356      351,  351,  351,  351,  351,  351,  351,  351,  351,  351, 
     9357      351,  351,  351,  351,  351,  351,  351,  351,  616,  616, 
     9358 
     9359      616,  616,  616,  616,  616,  616,  616,  616,  616,  616, 
     9360      616,  616,  616,  616,  616,  616,  120,  120,  120,  120, 
     9361      120,  120,  120,  120,  120,  120,  120,  120,  120,  120, 
     9362      120,  120,  120,  120,  621, 1848, 1848, 1848, 1848, 1848, 
     9363     1848,  621, 1848,  621, 1848, 1848,  621,  621,  621,  621, 
     9364      129, 1848, 1848, 1848, 1848, 1848, 1848, 1848,  129, 1848, 
     9365      129, 1848,  129,  129,  129,  129,  129,  624,  624,  624, 
     9366      624,  643,  643,  643,  643,  643,  643,  643,  643,  643, 
     9367      643,  643,  643,  643,  643,  643,  643,  643,  643,  644, 
     9368      644,  644,  644,  644,  644,  644,  644,  644,  644,  644, 
     9369 
     9370      644,  644,  644,  644,  644,  644,  644,  649,  649,  649, 
     9371      649,  649,  649,  649,  649,  649,  649,  649,  649,  649, 
     9372      649,  649,  649,  649,  649,  385,  385,  385,  385, 1848, 
     9373      385,  385,  385,  385,  385,  385, 1848,  385,  385, 1848, 
     9374     1848,  385,  385,  156,  156,  156,  156,  156,  697,  697, 
     9375      697,  697,  697,  697,  697,  697,  697,  697,  697,  697, 
     9376      697,  697,  697,  697,  697,  697,  470, 1848, 1848, 1848, 
     9377     1848, 1848, 1848, 1848,  470,  470,  472,  472,  472,  472, 
     9378      472,  472,  472,  472,  472,  472,  472,  472,  472,  472, 
     9379      472,  472,  472,  472,  224,  224,  224,  224,  224,  224, 
     9380 
     9381      224,  224,  224,  224,  224,  224,  224,  224,  224,  224, 
     9382      224,  224,  236,  236,  236,  236,  236,  236,  236,  236, 
     9383      236,  236,  236,  236,  236,  236,  236,  236,  236,  236, 
     9384      243,  243,  243,  243,  243,  243,  243,  243,  243,  243, 
     9385      243,  243,  243,  243,  243,  243,  243,  243,  494,  494, 
     9386      494,  494,  494,  494,  494,  494,  494,  494,  494,  494, 
     9387      494,  494,  494,  494,  494,  494,  495,  495,  495,  495, 
     9388      495,  495,  495,  495,  495,  495,  495,  495,  495,  495, 
     9389      495,  495,  495,  495,  777,  777,  777,  777,  777,  777, 
     9390      777,  777,  777,  777,  777,  777,  777,  777,  777,  777, 
     9391 
     9392      777,  777,  778,  778,  778,  778,  778,  778,  778,  778, 
     9393      778,  778,  778,  778,  778,  778,  778,  778,  778,  778, 
     9394      251, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     9395     1848,  251,  251,  251,  251,  251,  580,  580,  580,  580, 
     9396      580,  580,  580,  580,  580,  580,  580,  580,  580,  580, 
     9397      580,  580,  580,  580,  316,  316,  316,  316,  316,  316, 
     9398      316,  316,  316,  316,  316,  316,  316,  316,  316,  316, 
     9399      316,  316,  326,  326,  326,  326,  326,  326,  326,  326, 
     9400      326,  326,  326,  326,  326,  326,  326,  326,  326,  326, 
     9401      111,  111, 1848,  111,  111,  111,  111,  111,  111,  111, 
     9402 
     9403      111,  111,  111,  111,  111,  111,  111,  111,  114,  114, 
     9404      114,  114,  114,  114,  114,  114,  114,  114,  114,  114, 
     9405      114,  114,  114,  114,  114,  114,  351,  351,  351,  351, 
     9406      351,  351,  351,  351,  351,  351,  351,  351,  351,  351, 
     9407      351,  351,  351,  351,  120,  120,  120,  120,  120,  120, 
     9408      120,  120,  120,  120,  120,  120,  120,  120,  120,  120, 
     9409      120,  120,  616,  616,  616,  616,  616,  616,  616,  616, 
     9410      616,  616,  616,  616,  616,  616,  616,  616,  616,  616, 
     9411      621, 1848, 1848, 1848, 1848, 1848, 1848,  621, 1848,  621, 
     9412     1848, 1848,  621,  621,  621,  621,  901, 1848, 1848, 1848, 
     9413 
     9414     1848, 1848, 1848, 1848,  901, 1848, 1848, 1848,  901,  901, 
     9415      901,  901,  901,  129, 1848, 1848, 1848, 1848, 1848, 1848, 
     9416     1848,  129, 1848,  129, 1848,  129,  129,  129,  129,  129, 
     9417      643,  643,  643,  643,  643,  643,  643,  643,  643,  643, 
     9418      643,  643,  643,  643,  643,  643,  643,  643,  644,  644, 
     9419      644,  644,  644,  644,  644,  644,  644,  644,  644,  644, 
     9420      644,  644,  644,  644,  644,  644,  913,  913,  913,  913, 
     9421      913,  913,  913,  913,  913,  913,  913,  913,  913,  913, 
     9422      913,  913,  913,  913,  649,  649,  649,  649,  649,  649, 
     9423      649,  649,  649,  649,  649,  649,  649,  649,  649,  649, 
     9424 
     9425      649,  649,  156,  156,  156,  156,  156,  697,  697,  697, 
     9426      697,  697,  697,  697,  697,  697,  697,  697,  697,  697, 
     9427      697,  697,  697,  697,  697,  698,  698,  698,  698,  698, 
     9428      698, 1848,  698,  698,  698,  698,  698,  698,  698,  698, 
     9429      698,  698,  698,  699,  699, 1848,  699,  699,  699,  699, 
     9430      699,  699,  699,  699,  699,  699,  699,  699,  699,  699, 
     9431      699,  224,  224,  224,  224,  224,  224,  224,  224,  224, 
     9432      224,  224,  224,  224,  224,  224,  224,  224,  224,  236, 
     9433      236,  236,  236,  236,  236,  236,  236,  236,  236,  236, 
     9434      236,  236,  236,  236,  236,  236,  236,  777,  777,  777, 
     9435 
     9436      777,  777,  777,  777,  777,  777,  777,  777,  777,  777, 
     9437      777,  777,  777,  777,  777,  778,  778,  778,  778,  778, 
     9438      778,  778,  778,  778,  778,  778,  778,  778,  778,  778, 
     9439      778,  778,  778,  316,  316,  316,  316,  316,  316,  316, 
     9440      316,  316,  316,  316,  316,  316,  316,  316,  316,  316, 
     9441      316,  326,  326,  326,  326,  326,  326,  326,  326,  326, 
     9442      326,  326,  326,  326,  326,  326,  326,  326,  326, 1126, 
     9443     1126, 1848, 1126, 1126, 1126, 1126, 1126, 1126, 1126, 1126, 
     9444     1126, 1126, 1126, 1126, 1126, 1126, 1126,  111,  111, 1848, 
     9445      111,  111,  111,  111,  111,  111,  111,  111,  111,  111, 
     9446 
     9447      111,  111,  111,  111,  111, 1128, 1128, 1848, 1128, 1128, 
     9448     1128, 1128, 1128, 1128, 1128, 1128, 1128, 1128, 1128, 1128, 
     9449     1128, 1128, 1128,  114,  114,  114,  114,  114,  114,  114, 
     9450      114,  114,  114,  114,  114,  114,  114,  114,  114,  114, 
     9451      114, 1130, 1130, 1130, 1130, 1130, 1130, 1130, 1130, 1130, 
     9452     1130, 1130, 1130, 1130, 1130, 1130, 1130, 1130, 1130,  120, 
     9453      120,  120,  120,  120,  120,  120,  120,  120,  120,  120, 
     9454      120,  120,  120,  120,  120,  120,  120, 1133, 1133, 1133, 
     9455     1133, 1133, 1133, 1133, 1133, 1133, 1133, 1133, 1133, 1133, 
     9456     1133, 1133, 1133, 1133, 1133,  621, 1848, 1848, 1848, 1848, 
     9457 
     9458     1848,  621, 1848, 1848, 1848,  621, 1848,  621,  621,  621, 
     9459      621,  621, 1138, 1138, 1138, 1138,  901, 1848, 1848, 1848, 
     9460     1848, 1848, 1848, 1848,  901, 1848, 1848, 1848,  901,  901, 
     9461      901,  901,  901,  129, 1848, 1848, 1848, 1848, 1848, 1848, 
     9462     1848,  129, 1848,  129, 1848,  129,  129,  129,  129,  129, 
     9463     1144, 1144, 1848, 1144, 1144, 1144, 1144, 1144, 1144, 1144, 
     9464     1144, 1144, 1144, 1144, 1144, 1144, 1144, 1144,  913,  913, 
     9465      913,  913,  913,  913,  913,  913,  913,  913,  913,  913, 
     9466      913,  913,  913,  913,  913,  913, 1156, 1156, 1848, 1156, 
     9467     1156, 1156, 1156, 1156, 1156, 1156, 1156, 1156, 1156, 1156, 
     9468 
     9469     1156, 1156, 1156, 1156,  698,  698,  698,  698,  698,  698, 
     9470     1848,  698,  698,  698,  698,  698,  698,  698,  698,  698, 
     9471      698,  698,  699,  699, 1848,  699,  699,  699,  699,  699, 
     9472      699,  699,  699,  699,  699,  699,  699,  699,  699,  699, 
     9473      697,  697,  697,  697,  697,  697,  697,  697,  697,  697, 
     9474      697,  697,  697,  697,  697,  697,  697,  697, 1189, 1189, 
     9475     1189, 1189, 1189, 1189, 1189, 1189, 1189, 1189, 1189, 1189, 
     9476     1189, 1189, 1189, 1189, 1189, 1189,  224,  224,  224,  224, 
     9477      224,  224,  224,  224,  224,  224,  224,  224,  224,  224, 
     9478      224,  224,  224,  224, 1231, 1231, 1231, 1231, 1231, 1231, 
     9479 
     9480     1231, 1231, 1231, 1231, 1231, 1231, 1231, 1231, 1231, 1231, 
     9481     1231, 1231,  236,  236,  236,  236,  236,  236,  236,  236, 
     9482      236,  236,  236,  236,  236,  236,  236,  236,  236,  236, 
     9483     1247, 1247, 1247, 1247, 1247, 1247, 1247, 1247, 1247, 1247, 
     9484     1247, 1247, 1247, 1247, 1247, 1247, 1247, 1247,  316,  316, 
     9485      316,  316,  316,  316,  316,  316,  316,  316,  316,  316, 
     9486      316,  316,  316,  316,  316,  316, 1300, 1300, 1300, 1300, 
     9487     1300, 1300, 1300, 1300, 1300, 1300, 1300, 1300, 1300, 1300, 
     9488     1300, 1300, 1300, 1300,  326,  326,  326,  326,  326,  326, 
     9489      326,  326,  326,  326,  326,  326,  326,  326,  326,  326, 
     9490 
     9491      326,  326, 1309, 1309, 1309, 1309, 1309, 1309, 1309, 1309, 
     9492     1309, 1309, 1309, 1309, 1309, 1309, 1309, 1309, 1309, 1309, 
     9493     1313, 1313, 1848, 1313, 1313, 1313, 1313, 1313, 1313, 1313, 
     9494     1313, 1313, 1313, 1313, 1313, 1313, 1313, 1313, 1314, 1314, 
     9495     1848, 1314, 1314, 1314, 1314, 1314, 1314, 1314, 1314, 1314, 
     9496     1314, 1314, 1314, 1314, 1314, 1314,  111,  111, 1848,  111, 
     9497      111,  111,  111,  111,  111,  111,  111,  111,  111,  111, 
     9498      111,  111,  111,  111, 1315, 1315, 1315, 1315, 1315, 1315, 
     9499     1315, 1315, 1315, 1315, 1315, 1315, 1315, 1315, 1315, 1315, 
     9500     1315, 1315,  114,  114,  114,  114,  114,  114,  114,  114, 
     9501 
     9502      114,  114,  114,  114,  114,  114,  114,  114,  114,  114, 
     9503     1317, 1317, 1317, 1317, 1317, 1317, 1317, 1317, 1317, 1317, 
     9504     1317, 1317, 1317, 1317, 1317, 1317, 1317, 1317,  120,  120, 
     9505      120,  120,  120,  120,  120,  120,  120,  120,  120,  120, 
     9506      120,  120,  120,  120,  120,  120, 1320, 1848, 1848, 1848, 
     9507     1848, 1848, 1320, 1848, 1848, 1848, 1848, 1848, 1320, 1320, 
     9508     1320, 1320, 1320, 1325, 1325, 1848, 1325, 1325, 1325, 1325, 
     9509     1325, 1325, 1325, 1325, 1325, 1325, 1325, 1325, 1325, 1325, 
     9510     1325,  621, 1848, 1848, 1848, 1848, 1848, 1848,  621, 1848, 
     9511      621, 1848, 1848,  621,  621,  621,  621,  129, 1848, 1848, 
     9512 
     9513     1848, 1848, 1848, 1848, 1848,  129, 1848,  129, 1848,  129, 
     9514      129,  129,  129,  129,  624,  624,  624,  624, 1335, 1335, 
     9515     1848, 1335, 1335, 1335, 1335, 1335, 1335, 1335, 1335, 1335, 
     9516     1335, 1335, 1335, 1335, 1335, 1335,  698,  698,  698,  698, 
     9517      698,  698, 1848,  698,  698,  698,  698,  698,  698,  698, 
     9518      698,  698,  698,  698,  699,  699, 1848,  699,  699,  699, 
     9519      699,  699,  699,  699,  699,  699,  699,  699,  699,  699, 
     9520      699,  699, 1190, 1190, 1848, 1190, 1190, 1190, 1190, 1190, 
     9521     1190, 1190, 1190, 1190, 1190, 1190, 1190, 1190, 1190, 1190, 
     9522     1189, 1189, 1189, 1189, 1189, 1189, 1189, 1189, 1189, 1189, 
     9523 
     9524     1189, 1189, 1189, 1189, 1189, 1189, 1189, 1189,  224,  224, 
     9525      224,  224,  224,  224,  224,  224,  224,  224,  224,  224, 
     9526      224,  224,  224,  224,  224,  224, 1399, 1399, 1399, 1399, 
     9527     1399, 1399, 1399, 1399, 1399, 1399, 1399, 1399, 1399, 1399, 
     9528     1399, 1399, 1399, 1399,  236,  236,  236,  236,  236,  236, 
     9529      236,  236,  236,  236,  236,  236,  236,  236,  236,  236, 
     9530      236,  236, 1407, 1848, 1407, 1848, 1848, 1848, 1848, 1407, 
     9531     1848, 1848, 1407, 1407, 1407, 1407, 1407, 1407, 1410, 1410, 
     9532     1410, 1410, 1410, 1410, 1410, 1410, 1410, 1410, 1410, 1410, 
     9533     1410, 1410, 1410, 1410, 1410, 1410, 1452, 1452, 1452, 1452, 
     9534 
     9535     1452, 1452, 1452, 1452, 1452, 1452, 1452, 1452, 1452, 1452, 
     9536     1452, 1452, 1452, 1452,  316,  316,  316,  316,  316,  316, 
     9537      316,  316,  316,  316,  316,  316,  316,  316,  316,  316, 
     9538      316,  316, 1454, 1454, 1454, 1454, 1454, 1454, 1454, 1454, 
     9539     1454, 1454, 1454, 1454, 1454, 1454, 1454, 1454, 1454, 1454, 
     9540      326,  326,  326,  326,  326,  326,  326,  326,  326,  326, 
     9541      326,  326,  326,  326,  326,  326,  326,  326,  111,  111, 
     9542     1848,  111,  111,  111,  111,  111,  111,  111,  111,  111, 
     9543      111,  111,  111,  111,  111,  111,  114,  114,  114,  114, 
     9544      114,  114,  114,  114,  114,  114,  114,  114,  114,  114, 
     9545 
     9546      114,  114,  114,  114,  120,  120,  120,  120,  120,  120, 
     9547      120,  120,  120,  120,  120,  120,  120,  120,  120,  120, 
     9548      120,  120, 1320, 1848, 1848, 1848, 1848, 1848, 1320, 1848, 
     9549     1848, 1848, 1848, 1848, 1320, 1320, 1320, 1320, 1320, 1463, 
     9550     1848, 1463, 1848, 1848, 1848, 1848, 1463, 1848, 1848, 1463, 
     9551     1463, 1463, 1463, 1463, 1463, 1513, 1848, 1513, 1848, 1848, 
     9552     1848, 1848, 1513, 1848, 1848, 1513, 1513, 1513, 1513, 1513, 
     9553     1513,  472,  472,  472,  472,  472,  472,  472,  472,  472, 
     9554      472,  472,  472,  472,  472,  472,  472,  472,  472, 1595, 
     9555     1595, 1595, 1595, 1595, 1620, 1620, 1848, 1620, 1620, 1620, 
     9556 
     9557     1620, 1620, 1620, 1620, 1620, 1620, 1620, 1620, 1620, 1620, 
     9558     1620, 1620,  649,  649,  649,  649,  649,  649,  649,  649, 
     9559      649,  649,  649,  649,  649,  649,  649,  649,  649,  649, 
     9560     1660, 1660, 1660, 1660, 1660, 1660, 1660, 1660, 1660, 1660, 
     9561     1660, 1660, 1660, 1660, 1660, 1660, 1660, 1660, 1701, 1701, 
     9562     1701, 1701, 1701, 1701, 1701, 1701, 1701, 1701, 1701, 1701, 
     9563     1701, 1701, 1701, 1701, 1701, 1701, 1721, 1721, 1721, 1721, 
     9564     1721, 1721, 1721, 1721, 1721, 1721, 1721, 1721, 1721, 1721, 
     9565     1721, 1721, 1721, 1721, 1722, 1722, 1722, 1722, 1722, 1722, 
     9566     1722, 1722, 1722, 1722, 1722, 1722, 1722, 1722, 1722, 1722, 
     9567 
     9568     1722, 1722, 1728, 1728, 1728, 1728, 1728, 1728, 1728, 1728, 
     9569     1728, 1728, 1728, 1728, 1728, 1728, 1728, 1728, 1728, 1728, 
     9570     1746, 1746, 1746, 1746, 1746, 1746, 1746, 1746, 1746, 1746, 
     9571     1746, 1746, 1746, 1746, 1746, 1746, 1746, 1746, 1755, 1755, 
     9572     1755, 1755, 1755, 1755, 1755, 1755, 1755, 1755, 1755, 1755, 
     9573     1755, 1755, 1755, 1755, 1755, 1755, 1758, 1758, 1758, 1758, 
     9574     1758, 1758, 1758, 1758, 1758, 1758, 1758, 1758, 1758, 1758, 
     9575     1758, 1758, 1758, 1758, 1799, 1799, 1799, 1799, 1799, 1799, 
     9576     1799, 1799, 1799, 1799, 1799, 1799, 1799, 1799, 1799, 1799, 
     9577     1799, 1799, 1820, 1820, 1820, 1820, 1820, 1820, 1820, 1820, 
     9578 
     9579     1820, 1820, 1820, 1820, 1820, 1820, 1820, 1820, 1820, 1820, 
     9580       15, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     9581     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     9582     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     9583     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     9584     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     9585     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     9586     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     9587     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     9588     1848 
     9589 
    76979590    } ; 
    76989591 
    7699 static yyconst flex_int16_t yy_chk[4102] = 
     9592static yyconst flex_int16_t yy_chk[9292] = 
    77009593    {   0, 
    77019594        1,    1,    1,    1,    1,    1,    1,    1,    1,    1, 
     
    77079600        1,    1,    1,    1,    1,    1,    1,    1,    1,    1, 
    77089601        1,    1,    1,    1,    1,    1,    1,    1,    1,    1, 
    7709         1,    1,    1,    1,    1,    1,    1,    1,    1,    2, 
    7710         2,    2,    2,   74,    8,    8,    8,    8,   10,   15, 
    7711  
    7712        15,   15, 1083,   14,   16,   16,   16,    2,    2,    2, 
    7713         2,    2,    2,    2,    2,    2,    2,   14,   70,   17, 
    7714      1081,   10,   74,   70,    2,    2,   71,   75,    2,    8, 
    7715         2,    8,   14,   17,   18,   19,   21,   15,   20,   22, 
    7716       551,    2,    2,  551, 1069,   14,   22,   22,   17,   19, 
    7717        10,   15,   20,    2,    2,   75,   80,    2,    8,    2, 
    7718         8,   17,   84,   23,   19,   30,   15,   20,   18,    2, 
    7719         2,   71,   24,   21,   26,   30,   22,   19,   81,   15, 
    7720        20,   25,   18,  116,   23,   80,   24,   21,   26,   30, 
    7721        22,   84,   28,   85,  100,   31, 1051,   18,   23,   71, 
    7722  
    7723       624,   24,   21,   26,   30,   22,   81,   25,  624,   31, 
    7724        18,   32,  116,   23,   24,   21,   26,   30,   22,   28, 
    7725        84,   25,  100, 1047,   31,   32,   23,   56,   56,   56, 
    7726        76,   76,   76,   28,  101,  105,   25,   31,  106,   85, 
    7727        32,  179,   69,   69,   69,   33, 1006,  179,   28,   25, 
    7728        27,   33,   27,   32,   77,   77,   77,   78,   78,   78, 
    7729      1000,   28,  101,  105,  914,   33,  106,   85,   27,   27, 
    7730        27,   27,   27,   27,   27,   27,   27,   27,   34,   69, 
    7731        33,   35,   35,   27,  120,   35,   41,   27,   27,   27, 
    7732       868,   35,   34,   33,   27,   41,   27,   27,   35,   35, 
    7733  
    7734        41,  862,   27,  123,   89,  861,   27,   34,   69,  796, 
    7735        35,   35,   27,  120,   35,   41,   27,   27,   27,   35, 
    7736        34,  114,   27,   41,   27,   27,   35,   35,   41,   88, 
    7737        27,   36,  123,   42,   27,   29,   36,   29,   29,   29, 
    7738        29,   29,   29,   29,   29,   29,   29,   42,  794,  114, 
    7739        36,   90,  337,   89,  337,   29,   29,   29,   90,   90, 
    7740        36,   88,   42,  115,  117,   36,  104,  786,   29,  121, 
    7741       122,   29,  126,   44,  109,   42,  104,   54,   36,   38, 
    7742        38,   89,   44,   38,   29,   29,   29,   44,  109,   38, 
    7743        88,  115,  117,   38,   38,  104,   29,  121,  122,   29, 
    7744  
    7745        37,  126,   44,  109,  104,   37,   54,   37,   38,   38, 
    7746        44,   37,   38,  785,   37,   44,  109,   38,   92,   37, 
    7747        54,   38,   38,  778,   37,   92,   92,  660,  777,   37, 
    7748       186,  186,  186,  660,   37,   54,   37,   43,  693,   37, 
    7749       132,   45,   37,  692,   43,   43,   45,   37,   54,   45, 
    7750       690,   43,   37,   39,  625,   45,   72,   72,   72,   39, 
    7751        45,   39,   39,  625,   39,   39,   43,   39,   72,  132, 
    7752        45,   39,   43,   43,  124,   45,  102,  689,   45,   43, 
    7753       689,  678,   39,   45,  211,  211,  211,   39,   45,   39, 
    7754        39,  102,   39,   39,   72,   39,  119,   49,   49,   39, 
    7755  
    7756        40,  664,  124,   40,  635,  102,   40,   40,   72,   40, 
    7757        46,  753,   49,  119,   40,   40,  128,  143,   46,  102, 
    7758       753,   46,   46,   72,   46,  119,   49,   49,  118,   40, 
    7759        46,  558,   40,  103,   40,   40,   72,   40,  118,   46, 
    7760        49,  119,   40,   40,  128,   47,  143,   46,  103,   46, 
    7761        46,   48,   46,   47,  129,   47,   48,  118,   46,   47, 
    7762        47,   52,  103,  130,  131,   48,  118,  133,   48,   52, 
    7763        48,   48,  661,  553,   47,   52,  103,  534,  661,  134, 
    7764        48,   47,  129,   47,  519,   48,  135,   47,   47,  137, 
    7765        52,  130,  131,   48,   95,  133,   48,   52,   48,   48, 
    7766  
    7767        50,   95,   95,   52,   50,   50,   51,  134,   50,  496, 
    7768        53,   51,   53,   51,  135,  487,   50,  137,  139,   50, 
    7769        50,  140,   53,   51,   53,   51,  224,  224,  224,   50, 
    7770       401,  399,  146,   50,   50,   51,  141,   50,  144,   53, 
    7771        51,   53,   51,   95,   50,   60,  139,   50,   50,  140, 
    7772        53,   51,   53,   51,   55,   55,   55,   55,   57,   57, 
    7773        58,  146,   55,  392,  141,   58,  144,  338,  138,  338, 
    7774       147,   95,   60,  390,  138,   57,   57,   57,   57,   57, 
    7775        57,   57,   57,   57,   57,  148,   60,  149,  159,   55, 
    7776        55,   65,   55,   55,   62,   55,  138,   58,  147,   65, 
    7777  
    7778        62,   60,  138,   62,   65,   65,   55,   55,   62,  365, 
    7779       150,   58,  362,  148,   60,  340,  149,  159,   55,   55, 
    7780        65,   55,   55,   62,   55,  151,   58,   65,   62,  336, 
    7781       247,   62,   65,   65,   55,   55,   62,   63,  150,   58, 
    7782        59,   91,   91,   91,   63,   63,   59,  244,  243,   91, 
    7783        91,   63,  242,  151,   59,  241,   59,   59,   59,   59, 
    7784        59,   59,   59,   59,   59,   59,   63,   99,   99,  142, 
    7785        94,  142,   63,   63,   59,   59,   59,   94,   94,   63, 
    7786        99,  152,  125,  125,  153,  154,  155,   59,  125,  157, 
    7787        59,  161,  213,  511,  163,  511,   99,   99,  164,  210, 
    7788  
    7789       166,  127,   94,   59,   59,   59,  127,  170,   99,  152, 
    7790       125,  125,  153,  154,  155,   59,  125,  157,   59,   61, 
    7791       161,  142,  163,   61,   61,  204,  164,   61,  166,  860, 
    7792       127,   94,  189,   61,  182,  127,  170,   61,   61,  158, 
    7793        64,  178,  158,  136,  165,   64,  145,   64,   61,  142, 
    7794       136,  165,   61,   61,  136,  171,   61,   64,  145,   64, 
    7795       145,   61,  182,  145,   64,   61,   61,  158,   87,   64, 
    7796       158,   86,  136,  165,   64,  145,   64,   82,  136,  165, 
    7797        67,  512,  136,  512,  171,   64,  145,   64,  145,  860, 
    7798        13,  145,   64,   73,   73,   73,   73,   73,   73,   73, 
    7799  
    7800        73,   73,   73,   73,   73,   73,   73,   73,   73,   73, 
    7801        73,   73,   73,   73,   73,   73,   73,   73,   73,   73, 
    7802        73,   73,   73,   73,   73,   73,   73,   73,   73,   73, 
    7803        73,   73,   73,   73,   73,   73,   73,   73,   73,   73, 
    7804        73,   73,   73,   73,   73,   73,   73,   73,   73,   73, 
    7805        73,   73,   73,   73,   73,   73,   73,   73,   73,   73, 
    7806        73,   73,   73,   73,   73,   73,   73,   73,   73,   73, 
    7807        73,   73,   73,   73,   73,   73,   73,   73,   73,   73, 
    7808        73,   73,   98,  110,   98,  110,    7,  156,  110,  110, 
    7809       110,  110,  110,  110,  110,  110,  110,  110,  160,  366, 
    7810  
    7811       366,  366,  156,  183,  160,  172,  528,  168,  528,  169, 
    7812       173,  174,    0,  169,  173,   98,  156,  185,  168,   98, 
    7813       181,   98,  866,  530,  196,  530,   98,  160,   98,   98, 
    7814       156,  183,  160,  162,  172,  162,  168,  169,   98,  173, 
    7815       174,  169,    0,  173,   98,  185,  168,    0,   98,  181, 
    7816        98,  162,  162,  196,   98,  162,   98,   98,  176,  199, 
    7817       176,    0,  162,  191,  162,    0,   98,  108,  108,  108, 
    7818       108,  108,  108,  108,  108,  108,  108,  167,  180,  162, 
    7819       162,  184,  866,  162,  203,  108,  108,  199,  184,  192, 
    7820       200,  167,  180,  193,  167,  191,  176,  231,  108,  202, 
    7821  
    7822         0,  207,  215,    0,  231,  231,  167,  180,    0,  184, 
    7823       176,  187,  187,  203,  108,  108,  184,  208,  200,  167, 
    7824       180,  192,  167,    0,  191,  176,  108,  202,  187,  187, 
    7825       187,  187,  187,  187,  187,  187,  187,  187,  176,  188, 
    7826       197,  651,  193,  651,  239,  188,  207,  197,  222,  208, 
    7827       192,  215,  223,    0,    0,  188,  188,  188,  188,  188, 
    7828       188,  188,  188,  188,  188,  194,  198,  198,  197,  214, 
    7829       193,  194,  198,  239,  207,  197,  222,    0,  208,  215, 
    7830       223,  194,  194,  194,  194,  194,  194,  194,  194,  194, 
    7831       194,  195,  209,  225,  198,  198,  216,  195,    0,  240, 
    7832  
    7833       198,  214,  206,  206,  206,  195,  201,  195,  195,  195, 
    7834       195,  195,  195,  195,  195,  195,  195,  226,  201,  246, 
    7835       201,  225,  227,  201,  229,  195,  195,  209,  216,  221, 
    7836       214,  221,    0,    0,  258,  201,  234,  240,  195,  206, 
    7837       230,    0,  228,  234,  234,  226,  201,  246,  201,    0, 
    7838       652,  201,  652,    0,  195,  195,  209,  216,  221,    0, 
    7839       221,  245,  227,  258,    0,  240,  195,  229,  206,  217, 
    7840       217,  217,  217,  217,  217,  217,  217,  217,  217,  217, 
    7841       217,  217,  217,  217,  217,  217,  217,  217,  220,  219, 
    7842       227,  228,  230,  248,  245,  229,  254,  255,  217,  217, 
    7843  
    7844       217,  217,  217,  219,  237,  220,  232,  232,  232,  256, 
    7845       257,  237,  237,  259,  232,  232,    0,  220,  219,  228, 
    7846       230,  248,  245,    0,  254,  255,  233,  233,  233,  217, 
    7847       217,  219,    0,  220,  233,  233,  236,  256,  257,    0, 
    7848       238,  259,  238,  236,  236,  238,  238,  238,  238,  238, 
    7849       238,  238,  238,  238,  238,  260,  237,  217,  218,  218, 
    7850       218,  218,  218,  218,  218,  218,  218,  218,  218,  218, 
    7851       218,  218,  218,  218,  218,  218,  218,  261,  262,  236, 
    7852       378,  378,  378,  260,  237,    0,    0,  218,  218,  218, 
    7853       218,  218,  218,  251,  251,  251,  251,  251,  251,  251, 
    7854  
    7855       251,  251,  251,  263,  264,  261,  262,  236,  252,  252, 
    7856       252,  252,  252,  252,  252,  252,  252,  252,  218,  218, 
    7857       253,  218,  253,  547,  547,  547,    0,    0,  266,  267, 
    7858       253,  263,  264,  265,  268,  269,  265,    0,  270,  271, 
    7859       272,  273,  274,    0,    0,  266,  218,  250,  250,  250, 
    7860       250,  250,  250,  250,  250,  250,  250,  266,  267,  277, 
    7861       281,  265,  268,  269,  265,  250,  250,  270,  271,  272, 
    7862       273,  274,  276,  266,  276,  282,  283,  278,  250,  278, 
    7863         0,    0,  279,  279,  284,  285,  286,  285,  277,  281, 
    7864       287,    0,  289,  290,  250,  250,  291,  292,  288,  293, 
    7865  
    7866       288,  295,    0,  276,  282,  283,  250,  275,  278,  275, 
    7867       279,  279,  284,  294,  286,  299,  285,    0,  298,  287, 
    7868       289,  290,    0,  300,  291,  292,  294,  293,  302,    0, 
    7869       295,  296,  301,  296,  301,    0,  303,  297,  275,  297, 
    7870       304,  296,  294,  275,  299,  275,  298,  297,  275,    0, 
    7871       288,  300,  275,  306,  294,  275,  305,  302,  275,  275, 
    7872       308,    0,  275,  301,  303,  309,  310,  312,  304,  313, 
    7873       315,  311,  275,  316,  275,  296,  317,  275,  288,  311, 
    7874       275,  297,  306,  275,  305,  296,  275,  275,  318,  308, 
    7875       275,  297,  314,  309,  310,  319,  312,  313,  315,  311, 
    7876  
    7877       314,  316,  320,  296,  317,  321,  322,  311,  323,  297, 
    7878       324,  325,  326,  296,  328,  329,  327,  318,  327,  297, 
    7879       330,  314,  331,  332,  319,  333,  327,  334,  314,  335, 
    7880       339,  320,  341,  321,  342,  322,  323,  343,  324,  325, 
    7881       326,  344,  345,  328,  329,  346,  347,  352,  330,    0, 
    7882       331,  332,    0,  333,  351,  334,  363,  335,  339,  348, 
    7883       341,  348,  342,  353,    0,  343,  355,  356,  358,  344, 
    7884       345,  357,  359,  346,  376,  347,  369,  348,  348,  348, 
    7885       348,  348,  348,  348,  348,  348,  348,  349,  357,  869, 
    7886       352,  361,  351,  349,  363,  355,  356,  358,  371,    0, 
    7887  
    7888       357,  359,  376,  349,  349,  349,  349,  349,  349,  349, 
    7889       349,  349,  349,  350,  368,  353,  357,  370,  352,  350, 
    7890       361,  351,  377,  363,  379,  383,    0,  371,  369,  350, 
    7891       350,  350,  350,  350,  350,  350,  350,  350,  350, 1005, 
    7892         0,  360,  372,  353,  354,  364,  364,  364,  381,  869, 
    7893       354,  377,  379,  372,  360,  370,  369,  368,  354,  373, 
    7894       354,  354,  354,  354,  354,  354,  354,  354,  354,  354, 
    7895       360,  372,  374,  380,  384,  383,  382,  373,  354,  354, 
    7896         0,  372,  360,  375,  370,  368,  364,  406,  373,  385, 
    7897       398,  354,  374,  405,  375,  381,  385,  385,  653, 1005, 
    7898  
    7899       653,  374,  380,  383,    0,  373,  386,  354,  354,  382, 
    7900       384,    0,  375,  386,  386,  364,  406,  387,  398,  354, 
    7901       374,  405,  375,  381,  387,  387,  388,  388,  388,  388, 
    7902       388,  388,  388,  388,  388,  388,  408,  410,  382,  384, 
    7903       389,  389,  389,  389,  389,  389,  389,  389,  389,  389, 
    7904       402,  411,  402,  387,  413,    0,  386,  414,    0,  415, 
    7905       402,  416,  417,  418,  420,  408,  410,  421,  422,  423, 
    7906       424,  425,  426,  429,  426,  430,  431,    0,  432,  411, 
    7907       433,  435,  387,  413,  386,  436,  414,  415,  434,  416, 
    7908       417,  439,  418,  420,  442,  421,  422,  423,  424,  425, 
    7909  
    7910       437,  429,  437,  430,  434,  431,  432,  444,  433,  435, 
    7911       440,  446,  440,  426,  436,  447,  445,  434,  445,  439, 
    7912       450,  448,  442,  448, 1009,  451,  452,  426,  454,    0, 
    7913       457,  437,  434,  455,  456,  444,  458,  459,  460,  446, 
    7914       464,  440,  426,  458,  447,  463,  468,  445,  467,  450, 
    7915         0,  469,  448,  451,  452,  426,  427,  454,  427,  457, 
    7916       470,  455,  456,    0,  480,  458,  459,  460,  461,  464, 
    7917       461,  458,  465,  463,  465,  468,  467,  478,  461,  469, 
    7918       483,  472,  465,  472, 1009,  479,  481,  427,  470,  482, 
    7919       484,  475,  427,  480,  427,  485,  493,  427,  503,  475, 
    7920  
    7921       488,  427,    0,  489,  427,  478,  490,  427,  427,  483, 
    7922       491,  427,  472,  479,  481,    0,    0,  482,  484,    0, 
    7923       506,  427,  506,  427,  485,  493,  427,  503,  488,  427, 
    7924       475,  489,  427,  499,  490,  427,  427,    0,  491,  427, 
    7925       443,  443,  443,  443,  443,  443,  443,  443,  443,  443, 
    7926       443,  506,  443,  443,  443,  443,  443,  443,  443,  475, 
    7927       507,  499,  508,  509,  494,  500,  494,  500,  513,  443, 
    7928       443,  443,  443,  443,  494,  500,  514,  515,  516,  517, 
    7929       518,  523,  524,  655,  535,  655,  525,    0,  667,  507, 
    7930       667,  508,  509,  520,  529,  520,  527,  513,  563, 1031, 
    7931  
    7932       443,  443,  529,  540,  514,  531,  515,  516,  517,  518, 
    7933       537,  520,  520,  520,  520,  520,  520,  520,  520,  520, 
    7934       520,  521,  525,  529,  527,  545,  563,  521,  443,  565, 
    7935       523,  529,  524,  535,  531,    0,    0,  521,  521,  521, 
    7936       521,  521,  521,  521,  521,  521,  521,  522,    0,  538, 
    7937       539,  525,  540,  522,  545,  537,  568,  565,  523, 1031, 
    7938       524,  535,    0,  522,  522,  522,  522,  522,  522,  522, 
    7939       522,  522,  522,  526,  532,  536,  536,  536,    0,  526, 
    7940       540,  532,  548,  537,  568,  532,  539,  526,  541,  526, 
    7941       526,  526,  526,  526,  526,  526,  526,  526,  526,  538, 
    7942  
    7943       533,    0,  533,  532,  552,  550,  541,  526,  526,  532, 
    7944       533,  548,  561,  532,  533,  539,  536,  541,  542,    0, 
    7945       526,  543,  542,  554,  544,  543,  562,  538,  544,  566, 
    7946       554,  554,  569,  576,  541,  555,  526,  526,  550,  577, 
    7947       552,  561,  555,  555,  570,  536,  571,  542,  526,  573, 
    7948       543,  542,  574,  544,  543,  562,  575,  544,  566,  554, 
    7949         0,  569,  576,  581,  659,  659,  659,  550,  577,  552, 
    7950         0,  578,  570,  578,  571,    0,  641,  573,  641,  579, 
    7951       574,  580,    0,  582,  575,  583,  641,  584,  554,  564, 
    7952       564,  581,  564,  564,  564,  564,  564,  564,  564,  564, 
    7953  
    7954       564,  564,  564,  564,  564,  564,  564,  564,  579,  585, 
    7955       580,  582,  578,  586,  583,  584,  587,  588,  564,  564, 
    7956       564,  564,  564,  590,  592,    0,  578,  593,  594,  586, 
    7957       595,    0,  596,  597,  598,  608,  599,  585,  599,    0, 
    7958       602,  578,  586,  603,  587,  603,  588,  607,  613,  564, 
    7959       564,  590,  610,  592,  578,  593,  594,  586,  611,  595, 
    7960       596,  614,  597,  598,  608,  615,  616,  599,  602,  617, 
    7961       618,    0,  619,  620,  603,  607,  613,  564,  621,  622, 
    7962       623,  610,  626,    0,  627,  628,  630,  611,  632,  633, 
    7963       614,  634,  639,  615,  616,  636,  637,  638,  617,  618, 
    7964  
    7965       619,  640,  620,  644,  645,  646,  621,  646,  622,  623, 
    7966       654,  626,  627,  656,  628,  630,  632,  657,  633,  662, 
    7967       634,  639,  663,  636,  637,  638,  666,  668,  669,  640, 
    7968       669,  644,  645,  658,  670,  658,  646,  671,  672,  654, 
    7969       672,  676,  656,  658,  681,  657,  675,  658,  672,  674, 
    7970       683,  674,  672,  679,  677,  666,  668,  700,  663,  662, 
    7971       694,    0,  670,  674,  695,  680,  671,  694,  694,  680, 
    7972       696,  695,  695,  681,  701,  703,    0,  696,  696,  683, 
    7973       771,  738,  771,  738, 1082,  700,  675,  663,  662,  665, 
    7974       677,  738,  676,  679,  680,  665,    0,  704,  680,  706, 
    7975  
    7976       707,  708,  701,  665,  703,  665,  665,  665,  665,  665, 
    7977       665,  665,  665,  665,  665,  675,  709,    0,  710,  677, 
    7978       676,  711,  679,  665,  665,  704,  714,  706,  707,  708, 
    7979       715,  717,    0,  719,  721,    0,  665,  762,    0,  762, 
    7980       770,  781,  770,  781, 1082,  709,  710,  762,  770,  858, 
    7981       711,  858,  665,  665,  712,  714,  712,  722,  723,  715, 
    7982       717,  719,  724,  721,  665,  682,  682,  682,  682,  682, 
    7983       682,  682,  682,  682,  682,  682,  682,  682,  682,  682, 
    7984       682,  682,  682,  682,  725,  722,  723,  726,  727,  712, 
    7985       729,  724,  728,  730,  682,  682,  682,  682,  682,  731, 
    7986  
    7987       732,    0,  712,  733,  734,  735,  737,  735, 1084,  739, 
    7988       740,  741,  725,  742,    0,  743,  726,  727,  712,  729, 
    7989       728,  745,  730,  746,  752,  682,  682,  731,  756,  732, 
    7990       712,  733,  734,    0,    0,  737,  735,  739,    0,  740, 
    7991       741,  755,  742,  743,  757,  775,  775,  775,  833,  745, 
    7992       833,  746,  752,  682,  686,  686,  686,  756,  833,  686, 
    7993       686,  751,  686,  751,    0,    0,  686,  686, 1084,  755, 
    7994       686,    0,  757,  686,  686,  686,  686,  686,  686,  686, 
    7995       686,  686,  699,  699,  776,  699,  699,  699,  699,  699, 
    7996       699,  699,  699,  699,  699,  699,  699,  699,  699,  699, 
    7997  
    7998       699,  758,  759,  783,  760,  763,    0,  768,  773,  751, 
    7999       772,  699,  699,  699,  699,  699,  767,  774,  767,  779, 
    8000       782,  776,  784,  787,  780,  789,  791,  791,  791,  758, 
    8001       802,  759,  760,  810,  763,  768,  773,  751,  803,  772, 
    8002       783,    0,  699,  699,  804,  806,  774,  807,  779,  782, 
    8003       776,  767,  780,  808,  789,  797,  812,  798,  784,  802, 
    8004       787,  810,  797,  797,  798,  798,  864,  803,  864,  783, 
    8005       699,    0,    0,  804,  806,    0,  807,  811,    0,  811, 
    8006       767,  801,  808,  813,  812,  801,  815,  784,  816,  787, 
    8007       788,  788,  788,  788,  788,  788,  788,  788,  788,  788, 
    8008  
    8009       788,  788,  788,  788,  788,  788,  788,  788,  788,  817, 
    8010       801,  813,  811,  819,  801,  815,  816,  818,  820,  788, 
    8011       788,  788,  788,  788,  821,  811,  822,    0,  823,  824, 
    8012       825,  826,  827,    0,  828,  830,  831,  840,  817,  832, 
    8013      1085,  811,  819,  835,  836,  818,  842,  820,  842,  843, 
    8014       788,  788,  821,  811,  844,  822,  823,  824,  825,  826, 
    8015       846,  827,  828,  847,  830,  831,  840,  832,  834,  834, 
    8016       834,  835,  836,  851,  852,  851,  834,  843,  788,  834, 
    8017       853,  855,  844,  851,  854,  856,  854,  857,  846,  859, 
    8018       867,  865,  847,  863,  842,  870,  871,    0,  873,  874, 
    8019  
    8020      1085,  875,  876,  852,  878,  879,  880,  881,  853,  882, 
    8021       855,  883,    0,  884,  856,  857,  885,  889,  859,  854, 
    8022       865,  863,  842,  886,  870,  871,  873,  887,  874,  875, 
    8023       876,  888,  878,  879,  880,  881,  890,  882,  896,  867, 
    8024       883,  884,  892,  893,  894,  885,  889,  895,  854,  897, 
    8025       899,  886,  901,  901,  901,  887,  903,  903,  903,  888, 
    8026       901,  909,    0,  901,  890,  910,  896,  867,    0,  908, 
    8027       915,  892,  893,  894,  913,  916,  895,  897,  899,  902, 
    8028       902,  902,  917,  904,  904,  904,  918,  902,  919,  909, 
    8029       902,  904,  920,  910,  904,  905,  905,  905,  908,  915, 
    8030  
    8031       921,  922,  913,  905,  916,  924,  905,  925,  926,  927, 
    8032       917,  928,  929,  932,  918,    0,  919,  933,    0,  935, 
    8033       936,  920,  937,  938,  939,  941,  940,  942,  940,  943, 
    8034       922,  944,  945,  947,  924,  921,  940,  949,  951,  928, 
    8035       929,  932,  952,  925,  927,  926,  933,  935,    0,  936, 
    8036       937,    0,  938,  939,  941,  961,  942,  960,  943,  944, 
    8037       945,  947,    0,    0,  921,  949,  951,  953,  953,  953, 
    8038       965,  952,  925,  927,  926,  954,  954,  954,  970,  955, 
    8039       955,  955,  963,  954,  961,  960,  954,  955,  966,  973, 
    8040       955,  956,  956,  956,  967,  957,  957,  957,  965,  956, 
    8041  
    8042       969,  975,  956,  957,  971,  974,  957,  958,  958,  958, 
    8043       976,  963,  977,  980,  977,  958,  981,  966,  958,    0, 
    8044       982,  983,  977,  967,  970,  984,  985,  984,  985,  969, 
    8045       987,  989,  971,  991,  973,  984,  985,  974,  994,  976, 
    8046       992,  980,  995, 1008, 1007,  981,    0,  975,  982,  998, 
    8047       983,    0,  970,  996,  996,  996,  999, 1001,  987,  989, 
    8048      1013,  991,  973, 1016, 1014, 1015,  974,  994,  992, 1017, 
    8049      1019,  995,  997,  997,  997,  975, 1021, 1008,  998, 1007, 
    8050       997, 1032, 1011,  997, 1011,  999, 1001, 1012, 1013, 1012, 
    8051      1025, 1016, 1011, 1014, 1015, 1026, 1029, 1017, 1027, 1019, 
    8052  
    8053      1012, 1030, 1012, 1033, 1021, 1037, 1008, 1036, 1007, 1023, 
    8054      1023, 1023, 1024, 1024, 1024,    0, 1038, 1032, 1012, 1025, 
    8055      1024, 1039, 1042, 1024, 1026, 1034, 1027, 1034, 1045, 1030, 
    8056      1041, 1048, 1035, 1037, 1035, 1052, 1036, 1046, 1034, 1050, 
    8057      1034, 1029, 1056, 1035, 1038, 1035, 1032, 1035, 1033, 1059, 
    8058      1039, 1042, 1043, 1043, 1043, 1049, 1034, 1045, 1041, 1044, 
    8059      1044, 1044, 1053, 1035, 1053, 1046, 1055, 1044, 1058, 1029, 
    8060      1044, 1056, 1063, 1053, 1050, 1068, 1033, 1048, 1059, 1064, 
    8061      1065, 1052,    0, 1049, 1062, 1062, 1062, 1066, 1071, 1067, 
    8062         0, 1073, 1062,    0, 1055, 1062, 1058, 1074,    0, 1079, 
    8063  
    8064      1063, 1099, 1109, 1050, 1093, 1048,    0, 1064, 1065, 1052, 
    8065      1061, 1061, 1061, 1095,    0, 1061, 1061, 1067, 1061, 1073, 
    8066      1086, 1068, 1061, 1061, 1080, 1074, 1061, 1079, 1090, 1061, 
    8067      1061, 1061, 1061, 1061, 1061, 1061, 1061, 1061, 1066, 1071, 
    8068      1076, 1076, 1076, 1077, 1077, 1077,    0, 1094, 1086, 1068, 
    8069      1099, 1077, 1096, 1080, 1077, 1093, 1104, 1090, 1095, 1101, 
    8070      1102, 1105, 1109,    0, 1111,    0, 1066, 1071, 1078, 1078, 
    8071      1078, 1100, 1113, 1078, 1078, 1094, 1078, 1103, 1099, 1078, 
    8072      1078, 1078, 1106, 1093, 1078, 1104, 1095, 1078, 1078, 1078, 
    8073      1078, 1078, 1078, 1078, 1078, 1078, 1088, 1088, 1088, 1100, 
    8074  
    8075      1089, 1089, 1089, 1096, 1088, 1101, 1107, 1088, 1089, 1102, 
    8076      1108, 1089, 1105, 1103, 1110, 1111, 1112, 1114, 1106, 1115, 
    8077      1115, 1115, 1117, 1113, 1116, 1116, 1116, 1118, 1118, 1118, 
    8078      1123, 1096, 1126, 1101, 1119, 1119, 1119, 1102, 1107, 1108, 
    8079      1105, 1127, 1103, 1111, 1112,    0, 1110, 1106, 1121, 1121, 
    8080      1121, 1113, 1124, 1124, 1124, 1128, 1128, 1128, 1129, 1129, 
    8081      1129,    0,    0,    0, 1126,    0, 1123, 1107, 1114,    0, 
    8082         0, 1117,    0,    0,    0, 1110,    0,    0,    0,    0, 
     9602        2,    2,    2,    2, 1794,    8,    8,    8,    8,    9, 
     9603        9,    9,   10,   10,   10,   16,  102,   72,    9,   72, 
     9604 
     9605       17,   10,   17,   19,   21,   20,    2,    2, 1793,   16, 
     9606        2,    8,    2,    8, 1869, 1869,   70,   19,   21,   24, 
     9607       22,   70, 1772,    2,   16,  102,   24,   24, 1748,   17, 
     9608       20,  108,   19,   21,   22,    2,    2,   16,  104,    2, 
     9609        8,    2,    8,   17,   20,   19,   21,   24, 1746,   22, 
     9610       27,    2,    6,    6,    6,    6,   26,   71,   17,   20, 
     9611      108,   24,   22,   28,   32,  112,  104,   27, 1722,  109, 
     9612       26,   17,   20,   33,   32, 1721,   24,   28,    6,    6, 
     9613     1715,   27,    6,  120,    6,   26,  113,   33,   32,   24, 
     9614      120,  120,   28,   71,  112,    6,   27,  109,   26,  110, 
     9615 
     9616     1696,  110,   33,   32,   98,   28,   98,    6,    6,   27, 
     9617      242,    6,  242,    6,  113,   33,   32,   59,   59,   59, 
     9618       59,   71,   98,    6,   11,   11,   11,   11,   11,   11, 
     9619       11,   11,   11,   11,   11,   11,   11,   11,   11,   11, 
     9620       11,   11,   11,   11,   11,   11,   11,   11,   11,   11, 
     9621       11,   11,   11,   11,   11,   11,   11,   11,   11,   11, 
     9622       11,   11,   11,   11,   11,   11,   11,   11,   11,   11, 
     9623       11,   11,   11,   11,   11,   11,   11,   11,   11,   11, 
     9624       11,   11,   11,   11,   11,   11,   11,   11,   11,   11, 
     9625       11,   11,   11,   11,   11,   11,   11,   11,   11,   11, 
     9626 
     9627       11,   11,   11,   11,   12,   12,   12,   12,   34,   23, 
     9628       23,   23,   23,  116, 1695,   34,   12,  100,  150,  100, 
     9629      150,  314,   12,  150, 1690,   36,   25,  158,   25,   34, 
     9630       12,   12,   36,  116,   12,  100,   12,  314,   23,   25, 
     9631      106,   25,  106,   25,   34,  135,   36,   12,  118,  118, 
     9632      118,  118,   23,  117,   44,   25,  158,   34,  106,   12, 
     9633       12,   36,  116,   12,  107,   12,  107,   23,   44,   25, 
     9634     1687, 1671,  136,  135,   36,   12,   14,   14,   14,   14, 
     9635       23, 1659,  107,   44,   25, 1658,  162,   30,   30,   30, 
     9636      117,  584,  164,  107,   14,   30,   44,   25,   30,   31, 
     9637 
     9638      136,   31,   14,   14,   30,  140,   14,  584,   14,   30, 
     9639       31,   31,   31,   35,   35,  162,   30,  122,  117,   14, 
     9640       35,  164,  107,   31,  122,  122,   31,   52,   52,  797, 
     9641       30,   14,   14,  140,   35,   14,  124,   14,  167,   31, 
     9642       31,   31,   52,  124,  124,   30,  797,   14,   29,   35, 
     9643       29,   31,   37, 1653,   31,   37,   52,   52,   30,  124, 
     9644       57,   37,   35,  764,  141,  764,   29,  167,   37,   37, 
     9645       52,  159,   29,   43,   38,  137,   29,   29,   29,   38, 
     9646       57,   37,   43,   29,   37,   29,   29,   43,  124,   37, 
     9647      137,   29,  141,   38,   57,   29,   37,   37,  359,  159, 
     9648 
     9649      359,   29,   43,   38,  137,   29,   29,   29,   38,   57, 
     9650       43,   29,  359,   29,   29,   43,  160,  172,  137,   29, 
     9651      189,   38,   57,   29,   39,   46,   40,   40,   46,   39, 
     9652       40,   39,   47,   47,  893,   39,   40,  893,   39,   46, 
     9653       60,   40,   47,   39,  160,   60,  172,   47,   39,  189, 
     9654      161, 1652,  163,   39,   46,   40,   40,   46,   39,   40, 
     9655       39,   47,   47,   39,   40,   45,   39,   46,   60,   40, 
     9656       47,   39,   45,   45,   45,   47,   39,   41,  161,   45, 
     9657      163,  165,   60,   41, 1398,   41,   41,  169,   41,   41, 
     9658       61,   41,  171, 1647,   45,   41,  201,   60, 1626,  207, 
     9659 
     9660       45,   45,   45,  766, 1619,  766,   41,   45,   61,  165, 
     9661       60,   41,   48,   41,   41,  169,   41,   41,  173,   41, 
     9662      171,   48,   61,   41,   42,  201,   48,   42,  207, 1611, 
     9663       42,   42,  126,   42,  126, 1398,  138,   61,   42,   42, 
     9664     1610,   48,  139,   49,  209,  126,  173,  126,   49,   48, 
     9665       61,  138,  139,   42,   48,   49,   42,   49,   42,   42, 
     9666       50,   42,   49,   49,   51,  138,   42,   42,   50,  174, 
     9667       50,  139,   49,  209,   50,   50,   51,   49,   51,  138, 
     9668      139,   51,  210,   49,   51,   49,  883,  883,  883,   50, 
     9669       49,   49, 1608,   51,   77,  175,   50,  174,   50,  121, 
     9670 
     9671      121,  121,   50,   50,   51, 1606,   51,  121,  121,   51, 
     9672       53,  210,   51,   54,   53,   53,  134,   77,   54,   56, 
     9673       54,   56,   77,  175,   53,  134,  134,   55, 1602,   53, 
     9674       53,   56,   54,   56,  177,   55,   77,  178,  134,   53, 
     9675       55,   55,   54,   53,   53, 1599,   77,   54,   56,   54, 
     9676       56,   77,   53, 1598,  134,  134,   55,   53,   53,   56, 
     9677       54,   56,  177,   55,   77,  178,  134,  179,   55,   55, 
     9678       58,   58,   58,   58,   62,   63, 1536,  180,   62,   62, 
     9679     1535,   63,   62,  315,   63,  315,  166,  166,   62,   63, 
     9680       69,   69,   69,   62,  211,  179,   58,   58, 1404,   58, 
     9681 
     9682       58,  315,   58,   62,   63,  180, 1453,   62,   62,   63, 
     9683     1531,   62,   63,   58,  166,  166,   62,   63,   69, 1530, 
     9684      127,   62,  127,  211, 1529,   58,   58,   65,   58,   58, 
     9685       64,   58,   65,  127,   65,  127, 1527,   64,   64,   64, 
     9686      213,   58,  181,   76,   64,  184,   65,   69,  133, 1404, 
     9687      133,   65,   75,   75,   75,   75,   65, 1453,  157,   64, 
     9688       83,   65,   79,   65,   75,   64,   64,   64,   76,  213, 
     9689      181,   76,   64,  184,   65,  157, 1520,   76,   75,   65, 
     9690     1515,  360,   82,  360,   76,   76,   82,  157,   83,   79, 
     9691       79, 1452,   82,   79,  360,  133,  360,   76,  187,   79, 
     9692 
     9693       76,  125,   83,  157,   79,   76, 1450,   75,  125,  125, 
     9694       99,   82,   76,   76,   78,   82,  219,   83,   79,   79, 
     9695       82,   99,   79,  133,   85,   86,  187,   79,   85,   86, 
     9696       83,  168,   79, 1445,   85,   86,  168,   78,   99,   81, 
     9697     1646,  125,   78,   81,   78,  219,   81,   81,   78,   81, 
     9698       84,   78,   99,   85,   86,   81,   78,   85,   86,  176, 
     9699      168,   78,   85,   86, 1444,  168,   78,   99,   81,  125, 
     9700      176,   78,   81,   78,   81,   81,   78,   81,   84,   78, 
     9701       99, 1664,  229,   81,   78,   84,   84,   84,  176,   78, 
     9702       80, 1646,   84,  188,   80,  226,  191,   80,  176,   80, 
     9703 
     9704       80,  192,   80,   80,  190, 1685,   87,   84,  193,   80, 
     9705       87,  229,  190,   84,   84,   84,   87,  194,  226,   80, 
     9706       84,  188,   89,   80,  191,   80, 1442,   80,   80,  192, 
     9707       80,   80, 1664,  190,   88,   87,  193,   80,   88,   87, 
     9708      190,  182,   88,  182,   87,  194,   88,  226,   88,  195, 
     9709       89,  142,  142,  142,   88,  197, 1685,  203,   89,  142, 
     9710       89,   90,   91,   88,   89,   89,   91,   88,  142,  204, 
     9711      367,   88,   91,   90,   88,   90,   88,  195,   90,   89, 
     9712     1439,   90,   88,  197,  182,  203,   89,   93,   89,  196, 
     9713       90,   91,   89,   89,   92,   91, 1436,  204,   92,  367, 
     9714 
     9715       91,   90,   92,   90,  196,  389,   90,  205,   92,   90, 
     9716       93, 1433,  182,   92,   92,   93, 1432,   93,  196,   94, 
     9717       95,   94,  200,   92,   94,   96,   94,   92,  200,   93, 
     9718      208,   92,  196,   96,  389,  205,   92, 1431,  366,   93, 
     9719      366,   92,   92,  366,   93,  170,   93,   94,   95,   94, 
     9720       95,  200,   94,   96,   94, 1771,  200,   93,  208, 1009, 
     9721       95, 1009,   95,   97,   97,   97,   97,   96,  144,  144, 
     9722      144,  144,  220,  221,  103,   97,  144,   95,  103,   95, 
     9723      198,  103,   96,  198,  103,  144,  170,  170,   95,   97, 
     9724       95,  216,  216,  216,  216,   96,  223,  223,  223,  223, 
     9725 
     9726      220,  221,  245,  103,  245,  245, 1771,  103,  198,  103, 
     9727     1129,  198,  103, 1129,  170,  170, 1425, 1419,   97,  101, 
     9728      101,  101,  101,  101,  101,  101,  101,  101,  101,  101, 
     9729      101,  101,  101,  101,  101,  101,  101,  101,  101,  101, 
     9730      101,  101,  101,  101,  101,  101,  101,  101,  101,  101, 
     9731      101,  101,  101,  101,  101,  101,  101,  101,  101,  101, 
     9732      101,  101,  101,  101,  101,  101,  101,  101,  101,  101, 
     9733      101,  101,  101,  101,  101,  101,  101,  101,  101,  101, 
     9734      101,  101,  101,  101,  101,  101,  101,  101,  101,  101, 
     9735      101,  101,  101,  101,  101,  101,  101,  101,  101,  105, 
     9736 
     9737      390,  129,  183,  129,  183, 1415,  105,  338,  215,  338, 
     9738      105, 1410,  183,  105,  129,  129,  129,  129,  130,  129, 
     9739      130, 1551,  215,  105, 1551,  338,  183, 1400,  105,  390, 
     9740      148,  130,  130,  130,  130,  105,  130,  215,  105,  148, 
     9741      148,  105,  130,  131,  199,  131,  225,  225,  225,  225, 
     9742      215,  105,  148,  129,  199,  183,  131,  131,  131,  131, 
     9743     1399,  131,  143,  143,  143,  143,  232, 1326,  148,  148, 
     9744      130,  130,  212,  199,  143,  149,  212,  149,  218,  185, 
     9745      148,  393,  199, 1319,  131,  403,  149,  149,  143,  206, 
     9746     1316,  185,  218,  185,  232,  131,  185,  186,  186,  149, 
     9747 
     9748      227,  212, 1315,  206,  186,  212,  206,  218,  185,  228, 
     9749      393,  202,  131,  202,  403,  149,  149,  143,  206,  185, 
     9750      218,  185,  233,  227,  185,  186,  186,  149,  222,  202, 
     9751      202,  206,  186,  202,  206,  222,  230,  231,  231,  240, 
     9752      202,  320,  202,  230,  239,  235,  238,  238,  238,  228, 
     9753      233,  247,  227,  247,  247,  234,  222,  202,  202,  241, 
     9754     1300,  202,  240,  222,  230,  231,  231,  234,  343,  234, 
     9755     1299,  230,  234,  235,  238, 1295,  377,  228,  377,  377, 
     9756      239,  320,  257, 1290,  234,  241,  246,  246,  246,  246, 
     9757      379,  240,  379,  379,  351,  234,  343,  234,  246,  257, 
     9758 
     9759      234,  351,  351,  238,  250,  250,  250,  250,  239,  320, 
     9760      251,  257,  246, 1289,  241,  319,  250,  251,  251,  251, 
     9761      309,  309,  309,  309,  251,  252,  404,  257,  252,  253, 
     9762      250,  253, 1011,  255, 1011,  252,  252,  252,  319,  251, 
     9763     1288,  246,  252,  407,  254,  251,  251,  251,  253,  255, 
     9764      255,  256,  251,  254,  252,  404, 1286,  252,  253,  250, 
     9765      253,  254,  255,  252,  252,  252,  256,  319,  256,  259, 
     9766      252,  259,  407,  254,  258,  260,  253,  255,  255, 1620, 
     9767      256,  254, 1620,  258,  262,  342, 1271,  260,  259,  254, 
     9768     1622,  258,  260, 1622,  256,  261,  256, 1258,  259,  342, 
     9769 
     9770      259,  262,  265,  258,  260,  261,  261,  311,  311,  311, 
     9771      311,  258,  261,  262,  342,  260,  259, 1250,  269,  258, 
     9772      260,  264,  268,  263,  261,  263,  265,  342,  263,  262, 
     9773      325,  264,  266,  261,  261,  269,  269,  268,  264,  268, 
     9774      261,  344,  263,  265,  265,  267,  267,  269,  266,  266, 
     9775      264,  268,  263,  325,  263,  265,  345,  263, 1247,  264, 
     9776      408,  266,  267,  269,  269,  268,  264,  268,  270,  344, 
     9777      263,  265,  265, 1231,  267,  267,  266,  266,  410,  274, 
     9778      410,  271,  325,  270,  345,  270,  272,  271,  273,  408, 
     9779      267,  411,  275, 1230,  346,  272,  274,  270,  271, 1190, 
     9780 
     9781      410,  276,  277,  272,  277,  273,  273,  275,  274,  275, 
     9782      271,  270,  276,  270,  368,  272,  271,  273,  276,  279, 
     9783      411,  275,  346,  272,  274,  374,  271,  291,  277,  291, 
     9784      276,  272,  279,  273,  273,  275,  279,  275,  280,  278, 
     9785      276,  278, 1773,  368,  291,  277,  276, 1145,  279,  278, 
     9786      280,  349,  280,  374,  354,  280,  291,  277,  291,  281, 
     9787      279,  354,  354,  278,  279,  278, 1135,  280,  281,  281, 
     9788      282,  368,  291,  277, 1785,  281,  281,  313,  280,  313, 
     9789      280,  282,  278,  280,  283,  284, 1131,  282,  281,  284, 
     9790     1130,  349,  278, 1773,  278,  283,  281,  281,  417,  282, 
     9791 
     9792      417,  283,  284,  281,  281, 1108,  313,  285,  285,  282, 
     9793      278,  286, 1098,  283,  284,  282,  285,  287,  284,  349, 
     9794      417,  286,  288,  283,  285, 1785,  287,  376,  286,  283, 
     9795      284, 1097,  391,  288,  287,  313,  285,  285,  348,  288, 
     9796      286,  289,  292, 1084,  285,  414,  287,  294,  290,  286, 
     9797      289,  288,  285,  294,  287,  376,  286,  290,  289,  292, 
     9798      391,  288,  287,  294,  294,  290,  293,  288, 1825,  348, 
     9799      289,  292,  296,  296,  414,  415,  294,  290,  289, 1081, 
     9800     1066,  293,  294,  293,  293,  290,  289,  292,  295,  423, 
     9801      296,  294,  294,  290,  295,  293,  298,  348,  423,  423, 
     9802 
     9803      295,  296,  296,  300,  415,  295,  392,  299,  297,  293, 
     9804      297,  293,  293,  298, 1062,  298,  299,  295,  296, 1825, 
     9805      300,  300, 1054,  295,  299,  298,  297,  297,  295, 1019, 
     9806      297, 1019,  300,  295,  392, 1053,  299,  297, 1046,  297, 
     9807      304,  298,  304,  298,  299,  301,  303,  301,  300,  300, 
     9808      302,  302,  299,  334,  297,  297, 1041,  304,  297,  301, 
     9809      373,  303,  301,  303,  301,  321,  305,  321,  302,  304, 
     9810      334,  304,  305, 1017,  301,  303,  301,  913,  419,  302, 
     9811      302,  394,  334,  305,  373,  304,  306,  301,  306,  303, 
     9812      301,  303,  301,  906,  321,  305,  302,  900,  334,  308, 
     9813 
     9814      322,  305,  322,  306,  307,  308,  307,  419,  429,  394, 
     9815      307,  305,  373,  856,  395,  306,  308,  306,  322,  853, 
     9816      422,  307,  422,  321,  310,  310,  310,  310,  308,  322, 
     9817      422,  306,  849,  307,  308,  307,  310,  429,  323,  307, 
     9818      323,  328,  395,  335,  308,  324,  324,  324,  324,  307, 
     9819      310,  843,  328,  396,  323,  335,  323,  324,  322,  328, 
     9820      335,  330,  397,  398,  330,  323,  323,  831,  330,  332, 
     9821      328,  324,  335,  401,  399,  332,  332,  399,  323,  310, 
     9822      328,  396,  492,  335,  492,  492,  829,  328,  335,  330, 
     9823      397,  398,  330,  814,  323,  323,  330,  332,  808,  786, 
     9824 
     9825      324,  401,  399,  332,  332,  399,  323,  326,  326,  326, 
     9826      326,  326,  326,  326,  326,  326,  326,  326,  326,  326, 
     9827      326,  326,  326,  326,  326,  326,  329,  326,  326,  326, 
     9828      326,  326,  331,  331,  331,  337,  778,  329,  402,  331, 
     9829      333, 1021,  777, 1021,  329,  352,  352,  352,  337,  333, 
     9830      413,  413,  337,  352,  352,  329,  333,  416,  326,  326, 
     9831      331,  331,  331,  358,  337,  329,  402,  331,  699,  333, 
     9832      358,  358,  329,  353,  353,  353,  337,  333,  413,  413, 
     9833      337,  353,  353,  698,  333,  416,  326,  327,  327,  327, 
     9834      327,  327,  327,  327,  327,  327,  327,  327,  327,  327, 
     9835 
     9836      327,  327,  327,  327,  327,  327,  358,  327,  327,  327, 
     9837      327,  327,  336,  339,  340,  339,  340,  418,  670,  341, 
     9838      432,  341,  421,  327,  336,  424,  336,  669,  425,  336, 
     9839      327,  339,  426,  427,  358,  341,  430,  341,  327,  327, 
     9840      649,  336,  339,  340,  648,  418,  341,  341,  341,  432, 
     9841      421,  327,  336,  424,  336,  357,  425,  336,  327,  341, 
     9842      426,  427,  357,  357,  430,  644,  327,  361,  362,  361, 
     9843      362,  339,  340,  431,  434,  341,  341,  341,  364,  435, 
     9844      364,  361,  362,  361,  362,  361,  362,  341,  365,  357, 
     9845      365,  643,  364,  412,  364,  412,  364,  378,  378,  378, 
     9846 
     9847      378,  431,  365,  434,  365,  400,  365,  435,  405,  378, 
     9848      896,  640,  896,  364,  436,  412,  420,  357,  420,  361, 
     9849      362,  896,  400,  378,  405,  382,  382,  382,  382,  412, 
     9850      364,  406,  365,  382,  400,  638,  383,  383,  383,  383, 
     9851      365,  364,  382,  436,  383,  386,  437,  406,  383,  405, 
     9852      400,  428,  378,  383,  386,  386,  433,  412,  433,  420, 
     9853      365,  439,  383,  438,  428,  438,  440,  386,  441,  442, 
     9854      443,  631,  406,  445,  629,  437,  446,  405,  433,  447, 
     9855      428,  448,  450,  386,  386,  438,  451,  420,  454,  456, 
     9856      439,  383,  428,  457,  440,  386,  441,  442,  449,  443, 
     9857 
     9858      406,  409,  445,  409,  446,  628,  449,  447,  455,  452, 
     9859      448,  450,  459,  458,  451,  627,  454,  452,  456,  453, 
     9860      460,  453,  457,  409,  461,  462,  449,  463,  409,  616, 
     9861      464,  465,  467,  409,  449,  480,  455,  468,  452,  469, 
     9862      459,  453,  458,  409,  409,  452,  471,  409,  460,  473, 
     9863      474,  475,  461,  462,  453,  476,  463,  409,  464,  465, 
     9864      467,  477,  409,  453,  478,  468,  479,  469,  481,  480, 
     9865      482,  409,  409,  483,  471,  409,  484,  473,  474,  475, 
     9866      485,  486,  453,  476,  488,  487,  489,  580,  504,  477, 
     9867      501,  453,  478,  484,  506,  479,  502,  480,  487,  482, 
     9868 
     9869      503,  493,  483,  493,  493,  484,  490,  490,  490,  485, 
     9870      486,  481,  505,  488,  487,  489,  496,  501,  496,  496, 
     9871      498,  484,  498,  498,  479,  504,  487,  502,  497,  497, 
     9872      497,  497,  510,  507,  503,  508,  509,  506,  490,  481, 
     9873      497,  513,  511,  505,  489,  512,  501,  514,  515,  574, 
     9874      552,  516,  527,  504,  497,  500,  502,  519,  518, 1104, 
     9875      522, 1104,  503,  529,  499,  506,  507,  490,  525,  508, 
     9876      512,  515,  505,  510,  495,  513,  509,  511,  516,  526, 
     9877      511,  514,  518,  497,  519,  517,  517,  512,  521,  521, 
     9878      521,  522,  524,  527,  507,  525,  534,  508,  529,  512, 
     9879 
     9880      515,  510,  517,  513,  509,  511,  526,  516,  511,  514, 
     9881      521,  518,  530,  519,  531,  512,  523,  523,  523,  532, 
     9882      522,  527,  535,  494,  525,  533,  529,  517,  528,  528, 
     9883      528,  538,  491,  524,  524,  526,  536,  530,  523,  534, 
     9884      539,  537,  541,  541,  541,  472,  542,  543,  540,  550, 
     9885      528,  531,  523,  532,  554,  517,  520,  520,  520,  533, 
     9886      544,  524,  524,  536,  541,  535,  530,  534,  537,  545, 
     9887      470,  548,  538,  549,  540,  388,  536,  542,  520,  531, 
     9888      523,  532,  539,  520,  547,  550,  544,  533,  520,  387, 
     9889      543,  551,  536,  535,  384,  554,  545,  537,  520,  520, 
     9890 
     9891      538,  553,  520,  540,  536,  548,  542,  546,  546,  546, 
     9892      539,  547,  520,  550,  555,  544,  556,  520,  543,  557, 
     9893      549,  562,  551,  554,  553,  545,  520,  520,  558,  546, 
     9894      520,  559,  560,  548,  563,  567,  564,  561,  561,  561, 
     9895      547,  565,  566,  568,  569,  576,  583,  556,  549,  570, 
     9896      555,  551,  572,  553,  381,  557,  606,  558,  560,  561, 
     9897      573,  571,  577,  557,  562,  559,  560,  564,  565,  566, 
     9898      592,  575,  561,  380,  583,  567,  556,  563,  555,  576, 
     9899      587,  561,  569,  557,  606,  568,  558,  560,  572,  570, 
     9900      571,  557,  562,  559,  560,  375,  564,  565,  566,  592, 
     9901 
     9902      561,  588,  573,  567,  577,  563, 1234,  576, 1234,  561, 
     9903      569,  575,  372,  568,  587,  371,  572,  570,  370,  571, 
     9904      578,  578,  578,  578,  579,  579,  579,  579,  592,  585, 
     9905      573,  585,  577,  581,  581,  581,  581,  596,  586,  575, 
     9906      586,  589,  587,  589,  588,  581,  590,  585,  590,  369, 
     9907      596,  595,  363,  614,  602,  591,  586,  591,  595,  581, 
     9908      614,  614,  356,  355,  590,  597,  596,  586,  350,  600, 
     9909      589,  591,  588,  591,  601,  590,  603,  602,  596,  597, 
     9910      595,  601,  591,  591,  347,  600,  595,  604,  581,  582, 
     9911      582,  582,  582,  605,  597,  591,  586,  598,  600,  589, 
     9912 
     9913      603,  613,  607,  601,  590,  598,  602,  597,  598,  601, 
     9914      608,  591,  591,  600,  604,  582,  582,  609,  582,  582, 
     9915      605,  582,  611,  591,  610,  613,  598,  604,  637,  603, 
     9916      607,  651,  582,  598,  318, 1238,  598, 1238,  608,  623, 
     9917      316,  623,  612,  604,  582,  582,  609,  582,  582,  605, 
     9918      582,  611,  610,  623,  613,  604,  637,  623,  312,  651, 
     9919      582,  593,  593,  593,  593,  593,  593,  593,  593,  593, 
     9920      593,  593,  593,  593,  593,  593,  593,  593,  593,  593, 
     9921      612,  593,  593,  593,  593,  593,  599,  615,  599,  249, 
     9922      624,  617,  624,  248,  615,  615,  652,  593,  617,  617, 
     9923 
     9924      653,  654,  244,  599,  624,  657,  243,  619,  612,  619, 
     9925      236,  618,  593,  593,  620,  599,  620,  599,  618,  618, 
     9926      619,  622,  619,  622,  652,  593,  224,  620,  653,  620, 
     9927      654,  599,  617,  657,  641,  622,  641,  641,  618,  622, 
     9928      593,  594,  594,  594,  594,  594,  594,  594,  594,  594, 
     9929      594,  594,  594,  594,  594,  594,  594,  594,  594,  594, 
     9930      617,  594,  594,  594,  594,  594,  621,  618,  621,  625, 
     9931      594,  625,  626,  622,  626,  217,  123,  621,  655,  621, 
     9932      656,  621,  621,  625,  621,  625,  626,  625,  626, 1239, 
     9933      626, 1239,  594,  594,  642,  661,  642,  642,  659,  594, 
     9934 
     9935      626,  660,  645,  645,  645,  645,  119,  655,  664,  656, 
     9936      645,  625,  115,  665,  646,  646,  646,  646,  621,  645, 
     9937      594,  625,  646,  661,  626,  662,  646,  659,  663,  626, 
     9938      660,  646,  676,  647,  647,  647,  647,  664,  666,  625, 
     9939      646,  647,  665,  650,  650,  650,  650,  667,  668,  671, 
     9940      647,  650,  672,  662,  672,  675,  663,  677,  114,  678, 
     9941      650,  676,  679,  680,  682,  680,  666,  685,  683,  646, 
     9942      683,  686,  688,  690,   74,  667,  668,  671,  694,  689, 
     9943      695,  689,  701,  675,  672,  680,  677,  678,   67,  702, 
     9944      683,  679,  682,   15,  691,  685,  691,    7,  672,  686, 
     9945 
     9946      688,  689,  690,  693,  704,  693,  694,  703,  695,  697, 
     9947      706,  701,  707,  672,    0,    0,  691,  702,  697,  697, 
     9948        0,  700,  700,  700,  708,  693,  672,  673,  709,  673, 
     9949      714,  700,  700,  704,  700,  703,  700,  705,    0,  706, 
     9950      707,    0,  713,  700,  705,  710,  711,  710,  711,  673, 
     9951      720,  722,  725,  708,  673,    0,  723,  709,  714,  673, 
     9952      715,  724,  715,  717,  726,  717,  705,  710,  711,  673, 
     9953      673,  713,  705,  673,  716,  727,  716,  728,  729,  720, 
     9954      722,  725,  715,  673,  723,  717,  730,  731,  673,  724, 
     9955      737,  734,  726,  734,  738,  739,  716,  673,  673,  700, 
     9956 
     9957      732,  673,  732,  727,  736,  728,  736,  729,  740,  716, 
     9958      732,  742,  743,  734,  730,  744,  731,  746,  737,  747, 
     9959      750,  751,  738,  739,  752,  749,  736,  749,  754,  760, 
     9960      755,  756,  757,  758,  759,  761,  740,  716,  762,  763, 
     9961      742,  743,  767,  744,  765,  746,  770,  749,  747,  750, 
     9962      751,    0,  765,  752,    0,  772,  863,  754,  755,    0, 
     9963      756,  757,  758,  759,  779,  762,    0,  763,  769,  760, 
     9964      769,  767,  768,  765,  781,  785,  761,    0,  769,  768, 
     9965      780,  765,  769,  768,  863,  791,  770,  769,  771,  771, 
     9966      771,  772,  783,  773,  762,  773,  773,  760,  782,  784, 
     9967 
     9968      774,  768,  774,  774,  761,  779,  775,  768,  775,  775, 
     9969      776,  768,  776,  776,  770,  781,  785,  780,  787,  772, 
     9970      771,  783,  789,  782,  788,  795,  784,  790,  791,  796, 
     9971      793,  792,  794,  779,  800,  798,  803,  809,    0,    0, 
     9972      805,  787,  804,  781,  785,  780,  799,  799,  799,  771, 
     9973      783,  788,  782,  801,  806,  784,  791,  793,  802,  789, 
     9974      807,  790,  792,    0,  813,  796,  794,  815,  795,  798, 
     9975      787,  800,  804,  811,    0,  822,  816,  809,  799,  817, 
     9976      788,  801,  818,  803,  805,  802,  793,  789, 1327,  790, 
     9977     1327,  792,  799,  796,  794,  806,  795,  798,  815,  800, 
     9978 
     9979      819,  804,  807,  811,  822,  809,  813,  799,  820,  821, 
     9980      801,  803,  805,  818,  802,  810,  810,  810,  823,  816, 
     9981      799,  817,  826,  806,  812,  812,  812,  815,  825,  819, 
     9982      807,  830,  811,  822,  813,    0,  819,  810,  836,  820, 
     9983      833,  823,  818,  834,  837,  821,  812,  816,  832,  817, 
     9984      824,  824,  824,  825,  838,  840,  826,  841,  819,  827, 
     9985      827,  827,  830,  835,  819,  828,  828,  828,  820,  839, 
     9986      823,    0,  824,  821,    0,  832,  845,  833,  834,  846, 
     9987      836,  827,  825,  854,  826,  847,  837,  828,  841,  852, 
     9988      835,  830,  839,  848,  887,  840,  838,  842,  842,  842, 
     9989 
     9990      828,  850,  851,  855,  832,  833,  834,  842,  836,  844, 
     9991      844,  844,  858,  846,  837,  859,  845,  841,  860,  835, 
     9992      854,  839,  887,  840,  838,  847,  850,  851,  828,  848, 
     9993      855,  844,  852,  901,    0,  901,  857,  857,  857,  858, 
     9994        0,  846,  859,  868,  845,  860,  871,  901,  854,  861, 
     9995      861,  861,  861,  847,    0,  850,  851,  848,  857,  855, 
     9996      852,  862,  862,  862,  862,  865,  888,  865,  858,  869, 
     9997      866,  859,  866,    0,  860,  864,  864,  864,  864,  867, 
     9998      874,  867,  874,  865,  868,    0,  871,  876,  866,  876, 
     9999        0,    0,  875,  864,  875,  888,  869,  867,  881,  866, 
     10000 
     10001      881,  864,  864,  890,  864,  864,  917,  864,  867,    0, 
     10002        0,  870,  868,  870,  871,  876,  875,  892,  864,  882, 
     10003      884,  882,  874,    0,  915,  869,  881,  870,  866,  870, 
     10004      864,  864,  890,  864,  864,  917,  864,  867,  870,  870, 
     10005      877,  892,  877,  884,  876,  875,  864,  882,  918,  895, 
     10006      874,  870,  915,    0,    0,  881,  895,  895, 1111, 1111, 
     10007     1111,  879,    0,  879,  878,    0,  878,  870,  870,    0, 
     10008      892,  909,  884,  909,  909,    0,  882,  918,  877,  870, 
     10009      872,  872,  872,  872,  872,  872,  872,  872,  872,  872, 
     10010      872,  872,  872,  872,  872,  872,  872,  872,  872,  878, 
     10011 
     10012      872,  872,  872,  872,  872,  879,  877,  916,  919,    0, 
     10013      886,  886,  886,  910,  921,  910,  910,  922,    0,  924, 
     10014      886,  926,  925,  932,  886,  927,  880,  878,  880,  886, 
     10015      894,  872,  872,  879,    0,  916,  919,  894,  894,    0, 
     10016        0, 1029,  921, 1029, 1029, 1189,  922,  924,    0,  926, 
     10017      880,  925,  932,  927, 1189, 1189,  885,  894,  880,  872, 
     10018      873,  873,  873,  873,  873,  873,  873,  873,  873,  873, 
     10019      873,  873,  873,  873,  873,  873,  873,  873,  873,  880, 
     10020      873,  873,  873,  873,  873,  885,  894,  880,  898,  899, 
     10021      898,  899,  885,  929,  930,  931,  885,    0,    0,  898, 
     10022 
     10023      899,  902,  934,  902,  898,  899,  898,  899,  948,    0, 
     10024      948,  873,  873,    0,  885,  902,  935,  902,  936,  902, 
     10025      885,  929,  930,  931,  885,  911,  911,  911,  911,  902, 
     10026      948,  934,  937,  911,    0,  912,  912,  912,  912,  873, 
     10027      898,  899,  911,  912,    0,  935,  936, 1030,    0, 1030, 
     10028     1030,    0,  912,  902,  933,  938,  933,  939,  902,  903, 
     10029      903,  937,  903,  903,  903,  903,  903,  903,  903,  903, 
     10030      903,  903,  903,  903,  903,  903,  903,  903,  903,  903, 
     10031      903,  903,  903,  903,  938,  939,  933,  914,  914,  914, 
     10032      914,  940,    0,  943,  944,  914,  945,  946,  947,  914, 
     10033 
     10034      933,  949,  955,  961,  914,  962,    0,  964,  965,    0, 
     10035      903,  903,  903,  914,  950,  933,  950,  953,    0,  953, 
     10036      940,  943,  944,    0,    0,  945,  946,  947,  933,  949, 
     10037        0,  955,  961,  968,  962,  964,  950,  965,  903,  953, 
     10038        0,    0,  914,  920,  920,  966,  920,  920,  920,  920, 
     10039      920,  920,  920,  920,  920,  920,  920,  920,  920,  920, 
     10040      920,  920,  968,  920,  920,  920,  920,  920,  957,  958, 
     10041      957,  958,  967,  966,    0, 1328,  969, 1328,  969,  957, 
     10042      958,  957,  958,  957,  958,  970,  959,  959,  959,  973, 
     10043      957,  958,  974,  960,  920,  920,  959,  959,  969,  959, 
     10044 
     10045      967,  959,  960,  960,  971,  960,  971,  960,  959,  975, 
     10046      977,  975,  977,  970,  960,  979,  980,    0,  973,  981, 
     10047      983,  974,  920,  982,  985,  986,  971,  988,  989,  990, 
     10048      998,  975,  977,  991,  993,  991,  993,  995,  996,  997, 
     10049      999, 1001, 1000,  991,  979,  980,  957,  958,  981,  983, 
     10050     1002,  982, 1003,  985,  986,  988,  993,  989,  990,  998, 
     10051     1004, 1010, 1004, 1012,  959,  995,  996,  997,  999, 1001, 
     10052      960, 1000, 1013, 1008, 1014, 1008, 1014, 1015, 1002, 1016, 
     10053     1003, 1018, 1004, 1008, 1014, 1020, 1028, 1022, 1014, 1023, 
     10054     1010, 1033, 1012, 1014, 1027, 1034, 1036, 1024, 1037, 1024, 
     10055 
     10056     1013,    0,    0, 1026, 1114, 1026, 1016, 1024, 1015, 1035, 
     10057     1018, 1024,    0,    0, 1020, 1022, 1024, 1026, 1023, 1036, 
     10058        0, 1031, 1026, 1031, 1031, 1027, 1039, 1032, 1028, 1032, 
     10059     1032, 1034, 1033, 1114, 1037, 1016, 1035, 1015,    0, 1099, 
     10060     1099, 1099, 1100, 1100, 1100, 1100,    0,    0, 1036, 1099, 
     10061     1101, 1101, 1101, 1101, 1027, 1042, 1028, 1044, 1045, 1034, 
     10062     1033, 1047, 1037, 1049, 1039, 1035, 1038, 1038, 1038, 1038, 
     10063     1038, 1038, 1038, 1038, 1038, 1038, 1038, 1038, 1038, 1038, 
     10064     1038, 1038, 1038, 1038, 1038, 1040, 1038, 1038, 1038, 1038, 
     10065     1038, 1042, 1039, 1043, 1045, 1048, 1050, 1044, 1047, 1051, 
     10066 
     10067     1052, 1055, 1056,    0, 1049, 1061, 1057, 1059, 1058, 1071, 
     10068     1040, 1063, 1060, 1060, 1060, 1067, 1068, 1038, 1038, 1042, 
     10069     1043, 1064, 1045, 1050, 1065, 1044, 1047, 1051, 1069, 1048, 
     10070     1052, 1058, 1049, 1057, 1060, 1055, 1059, 1070, 1071, 1040, 
     10071     1056, 1061, 1063, 1068, 1073, 1038, 1064, 1076, 1077, 1043, 
     10072     1065, 1074, 1050, 1085, 1079, 1067, 1051, 1048, 1078, 1052, 
     10073     1058, 1075, 1057, 1055, 1080, 1059, 1082, 1071, 1056, 1061, 
     10074     1069, 1063, 1068, 1070, 1074, 1064, 1077, 1083, 1076, 1065, 
     10075     1072, 1072, 1072, 1067, 1078, 1088, 1073, 1086, 1075, 1089, 
     10076     1079, 1080, 1090, 1082, 1087, 1085, 1092, 1093, 1069, 1094, 
     10077 
     10078     1095, 1070, 1072, 1074, 1096, 1077, 1091, 1076, 1083,    0, 
     10079     1086, 1122, 1121, 1078, 1073,    0, 1102, 1075, 1079, 1087, 
     10080     1080, 1124, 1082, 1085, 1093, 1107, 1088, 1110, 1090, 1154, 
     10081        0, 1089, 1091, 1105, 1106, 1105, 1106, 1083, 1092, 1086, 
     10082     1094, 1121,    0, 1095, 1102, 1122, 1096,    0, 1087, 1138, 
     10083     1124, 1138, 1107, 1093, 1088, 1123, 1090, 1154, 1110, 1089, 
     10084     1138, 1091, 1105, 1106,    0, 1116, 1092, 1116, 1094,    0, 
     10085     1109, 1095, 1109, 1122, 1096, 1103, 1103, 1103, 1103, 1118, 
     10086     1117, 1107, 1115, 1123,    0, 1118, 1109, 1110, 1109,    0, 
     10087     1157, 1105, 1106, 1115, 1116, 1117, 1116, 1109, 1109,    0, 
     10088 
     10089     1155, 1103, 1103,    0, 1103, 1103, 1119, 1103, 1118, 1117, 
     10090     1109, 1115, 1123, 1147, 1118, 1147, 1147, 1119, 1103, 1157, 
     10091        0, 1115, 1148, 1117, 1148, 1148, 1109, 1109, 1155,    0, 
     10092     1103, 1103, 1132, 1103, 1103, 1119, 1103,    0, 1109, 1132, 
     10093     1132, 1240,    0, 1240, 1240, 1119, 1103, 1112, 1112, 1112, 
     10094     1112, 1112, 1112, 1112, 1112, 1112, 1112, 1112, 1112, 1112, 
     10095     1112, 1112, 1112, 1112, 1112, 1112, 1133, 1112, 1112, 1112, 
     10096     1112, 1112, 1134, 1133, 1133, 1137, 1112, 1137, 1158, 1134, 
     10097     1134, 1140, 1151, 1140, 1151, 1160, 1137, 1161, 1141, 1162, 
     10098     1141, 1163,    0, 1137, 1142, 1140, 1142,    0, 1112, 1112, 
     10099 
     10100     1136, 1141, 1136, 1141, 1151, 1112, 1158, 1143, 1142, 1143, 
     10101     1142, 1136, 1142, 1160, 1224, 1161, 1224, 1162, 1136,    0, 
     10102     1163, 1143,    0, 1143, 1224, 1143, 1112, 1113, 1113, 1113, 
     10103     1113, 1113, 1113, 1113, 1113, 1113, 1113, 1113, 1113, 1113, 
     10104     1113, 1113, 1113, 1113, 1113, 1113, 1142, 1113, 1113, 1113, 
     10105     1113, 1113, 1136, 1144, 1113, 1144, 1164, 1173, 1165, 1143, 
     10106     1149, 1149, 1149, 1149, 1152, 1167, 1152, 1144, 1149, 1144, 
     10107     1168, 1144, 1150, 1150, 1150, 1150, 1174, 1149, 1113, 1113, 
     10108     1150,    0,    0, 1113, 1164, 1173, 1152, 1165, 1241, 1150, 
     10109     1241, 1241,    0,    0, 1167, 1296, 1296, 1296, 1296, 1168, 
     10110 
     10111     1166,    0, 1166, 1170, 1174, 1144, 1113, 1120, 1120, 1120, 
     10112     1120, 1120, 1120, 1120, 1120, 1120, 1120, 1120, 1120, 1120, 
     10113     1120, 1120, 1120, 1120, 1120, 1120, 1166, 1120, 1120, 1120, 
     10114     1120, 1120, 1170, 1175, 1176, 1177,    0, 1178, 1179, 1166, 
     10115     1396, 1183, 1396, 1184, 1193, 1194, 1180, 1181, 1180, 1181, 
     10116     1186, 1196, 1186, 1198, 1186, 1166, 1195,    0, 1120, 1120, 
     10117        0, 1186, 1175, 1176, 1177, 1178, 1179, 1166, 1180, 1181, 
     10118     1183, 1184,    0, 1193, 1194, 1310, 1310, 1310, 1188, 1196, 
     10119     1188, 1198, 1188,    0, 1199, 1195, 1120, 1139, 1139, 1188, 
     10120     1139, 1139, 1139, 1139, 1139, 1139, 1139, 1139, 1139, 1139, 
     10121 
     10122     1139, 1139, 1139, 1139, 1139, 1139, 1139, 1139, 1139, 1139, 
     10123     1139, 1139, 1199, 1200, 1185, 1200, 1185, 1186, 1402, 1187, 
     10124     1402, 1187, 1203,    0,    0, 1185, 1202, 1185, 1202, 1185, 
     10125     1187, 1205, 1187, 1206, 1187, 1200, 1185, 1192, 1139, 1139, 
     10126     1139, 1187, 1191, 1191, 1191, 1188, 1192, 1192, 1202, 1192, 
     10127     1203, 1192, 1191, 1191, 1204, 1191, 1204, 1191, 1192, 1205, 
     10128     1406, 1206, 1406, 1406, 1191,    0, 1139, 1153, 1153, 1208, 
     10129     1153, 1153, 1153, 1153, 1153, 1153, 1153, 1153, 1153, 1153, 
     10130     1153, 1153, 1153, 1153, 1153, 1153, 1212, 1153, 1153, 1153, 
     10131     1153, 1153, 1185, 1204, 1207, 1209, 1207, 1187, 1208, 1210, 
     10132 
     10133     1211, 1213, 1215, 1220, 1219, 1220, 1219, 1222, 1226, 1228, 
     10134     1221, 1227, 1221, 1229, 1192, 1212, 1207, 1233, 1153, 1153, 
     10135     1191, 1204, 1232, 1209, 1235, 1220, 1236, 1210, 1211, 1213, 
     10136     1219, 1215, 1221, 1237, 1248, 1222, 1298, 1226, 1228, 1227, 
     10137     1305, 1229, 1242, 1242, 1242, 1233, 1153, 1243, 1243, 1243, 
     10138        0, 1232, 1246, 1235, 1236, 1317, 1306, 1248,    0, 1219, 
     10139     1237,    0, 1317, 1317, 1242, 1298,    0, 1245, 1305, 1243, 
     10140     1229, 1251,    0, 1318, 1249, 1408, 1253, 1408, 1252, 1255, 
     10141     1318, 1318,    0, 1236, 1306,    0, 1248, 1246,    0, 1237, 
     10142     1244, 1244, 1244, 1244, 1244, 1244, 1244, 1244, 1244, 1244, 
     10143 
     10144     1244, 1244, 1244, 1244, 1244, 1244, 1244, 1244, 1244, 1245, 
     10145     1244, 1244, 1244, 1244, 1244, 1246, 1249, 1251, 1252, 1253, 
     10146     1256, 1255, 1262, 1254, 1257, 1257, 1257, 1259, 1260, 1261, 
     10147     1263, 1264, 1264, 1264, 1265, 1266, 1267, 1245, 1268, 1269, 
     10148     1272, 1244, 1244,    0, 1249, 1251, 1252, 1253, 1254, 1255, 
     10149     1257, 1256, 1277, 1264, 1259, 1260, 1261, 1265, 1270, 1273, 
     10150     1278, 1284, 1262, 1257, 1263, 1268, 1269, 1267, 1281, 1244, 
     10151        0, 1275, 1266, 1276, 1276, 1276, 1280, 1254, 1282, 1257, 
     10152     1256, 1272, 1283, 1259, 1260, 1261, 1265, 1285, 1284, 1287, 
     10153     1262, 1257, 1263, 1277, 1268, 1269, 1267, 1294, 1270, 1280, 
     10154 
     10155     1266, 1273, 1274, 1274, 1274, 1275, 1307, 1278,    0, 1272, 
     10156     1281, 1409, 1276, 1409, 1279, 1279, 1279, 1284, 1282, 1283, 
     10157     1287, 1277, 1285,    0, 1274, 1311, 1270, 1301, 1280, 1273, 
     10158     1291, 1291, 1291, 1275, 1307, 1278, 1279, 1308, 1281, 1294, 
     10159     1276, 1292, 1292, 1292, 1312, 1337, 1282, 1283, 1311, 1287, 
     10160     1285, 1293, 1293, 1293, 1338, 1301, 1291, 1297, 1297, 1297, 
     10161     1297,    0,    0, 1292, 1320, 1308, 1320, 1294, 1321, 1795, 
     10162     1321, 1795, 1312, 1293, 1337, 1320, 1339, 1311, 1449, 1449, 
     10163     1449, 1449, 1321, 1338, 1301, 1291, 1302, 1302, 1302, 1302, 
     10164     1302, 1302, 1302, 1302, 1302, 1302, 1302, 1302, 1302, 1302, 
     10165 
     10166     1302, 1302, 1302, 1302, 1302, 1339, 1302, 1302, 1302, 1302, 
     10167     1302, 1322,    0, 1322, 1329, 1329, 1329, 1329, 1345, 1341, 
     10168        0, 1331, 1329, 1331, 1322,    0, 1322, 1553, 1333, 1553, 
     10169     1333, 1329, 1342, 1323, 1343, 1323, 1347, 1302, 1302, 1324, 
     10170     1325, 1324, 1325, 1331, 1553,    0, 1345, 1323, 1341, 1323, 
     10171     1333, 1323, 1615, 1324, 1325, 1324, 1325, 1324, 1325, 1615, 
     10172        0, 1342, 1615, 1343, 1347, 1302, 1303, 1303, 1303, 1303, 
     10173     1303, 1303, 1303, 1303, 1303, 1303, 1303, 1303, 1303, 1303, 
     10174     1303, 1303, 1303, 1303, 1303, 1323, 1303, 1303, 1303, 1303, 
     10175     1303, 1324, 1325, 1348, 1330, 1330, 1330, 1330, 1350, 1336, 
     10176 
     10177        0, 1351, 1330, 1336, 1352, 1353,    0, 1354, 1355, 1660, 
     10178     1303, 1330, 1361, 1357, 1358,    0, 1660, 1303, 1303, 1660, 
     10179        0, 1348, 1359, 1462, 1359, 1462, 1462, 1350, 1336, 1351, 
     10180        0,    0, 1336, 1352, 1353, 1354,    0, 1355, 1303, 1346, 
     10181     1361, 1346, 1357, 1358, 1359, 1303, 1304, 1304, 1304, 1304, 
     10182     1304, 1304, 1304, 1304, 1304, 1304, 1304, 1304, 1304, 1304, 
     10183     1304, 1304, 1304, 1304, 1304, 1346, 1304, 1304, 1304, 1304, 
     10184     1304, 1362, 1364, 1363, 1364, 1363, 1364,    0, 1346, 1366, 
     10185     1370, 1371, 1382, 1364, 1363, 1376, 1363, 1375, 1363, 1375, 
     10186     1365, 1365, 1365, 1377, 1346, 1363,    0, 1304, 1304, 1362, 
     10187 
     10188     1365, 1365, 1372, 1365, 1372, 1365, 1346, 1366, 1389, 1370, 
     10189     1371, 1382, 1365, 1376, 1379, 1381, 1379, 1384, 1387, 1394, 
     10190     1390, 1377, 1390, 1397, 1372, 1304, 1375, 1388, 1392, 1388, 
     10191     1392, 1395, 1401, 1403, 1405, 1418, 1379, 1389, 1411, 1364, 
     10192     1412, 1413, 1390, 1381, 1414, 1384, 1387, 1428, 1394, 1416, 
     10193     1392, 1363, 1397, 1388, 1375, 1420, 1417, 1422, 1418, 1395, 
     10194     1401, 1411, 1403, 1423, 1421, 1411, 1413, 1412, 1365, 1430, 
     10195     1429, 1414, 1426, 1424, 1405, 1438, 1416, 1427, 1435, 1437, 
     10196     1440, 1428, 1388, 1417, 1434, 1443, 1446, 1418, 1451,    0, 
     10197     1411, 1448, 1420,    0, 1411, 1413, 1412, 1422, 1424, 1426, 
     10198 
     10199     1414, 1421, 1405, 1423, 1427, 1416, 1429, 1455, 1435, 1428, 
     10200     1458, 1430, 1417, 1441, 1440, 1434, 1451, 1438, 1447, 1437, 
     10201     1420, 1443, 1448, 1457, 1459, 1422, 1466, 1424, 1426, 1421, 
     10202     1446, 1423, 1460, 1427, 1429,    0, 1455, 1435, 1458, 1430, 
     10203     1441, 1447, 1440, 1469, 1434, 1438, 1461, 1437, 1461, 1443, 
     10204     1468, 1448, 1457, 1459,    0, 1466, 1461, 1460, 1446, 1463, 
     10205     1463, 1463, 1470, 1464, 1464, 1464, 1464, 1463, 1471, 1441, 
     10206     1447, 1464, 1469, 1473, 1474, 1475, 1463, 1476, 1468, 1477, 
     10207     1464, 1465, 1465, 1465, 1465, 1478, 1460, 1479, 1480, 1465, 
     10208     1470, 1481, 1483,    0, 1484, 1486, 1471, 1489, 1465, 1489, 
     10209 
     10210     1491, 1473, 1474, 1475, 1492, 1476, 1492, 1477, 1489, 1493, 
     10211     1489, 1494, 1489, 1497, 1478, 1479, 1498, 1480, 1498, 1489, 
     10212     1481, 1483, 1484, 1486, 1499, 1500, 1492, 1501, 1502, 1491, 
     10213     1503, 1504, 1506, 1505, 1508, 1509, 1510, 1493, 1498, 1494, 
     10214     1511, 1497, 1511, 1511, 1512, 1514, 1512, 1512, 1516, 1517, 
     10215     1518, 1519, 1521, 1499, 1500, 1501, 1502, 1523, 1503, 1505, 
     10216     1504, 1506, 1509, 1508, 1510, 1522, 1526, 1528, 1524, 1514, 
     10217     1525, 1532, 1534, 1537,    0, 1489, 1517, 1533, 1533, 1533, 
     10218     1538, 1538, 1538, 1539, 1516, 1541, 1540, 1519, 1505, 1545, 
     10219     1518, 1509, 1523, 1510, 1521, 1524, 1532, 1525, 1514, 1533, 
     10220 
     10221     1546, 1522, 1538, 1528, 1543, 1517, 1543,    0, 1526, 1534, 
     10222     1539, 1549, 1516, 1537, 1543, 1519, 1544, 1545, 1518, 1563, 
     10223     1523, 1541, 1521, 1558, 1524, 1532, 1525, 1540, 1546, 1522, 
     10224        0, 1528, 1542, 1542, 1542, 1542, 1526, 1534, 1549, 1539, 
     10225        0, 1537, 1544, 1550, 1552, 1550, 1552, 1552, 1563, 1541, 
     10226        0, 1558,    0, 1550, 1566, 1540, 1554, 1554, 1554, 1554, 
     10227     1555, 1555, 1555, 1568, 1554, 1559, 1562, 1549, 1555, 1565, 
     10228     1567, 1544, 1569, 1554, 1557, 1557, 1557, 1555, 1556, 1556, 
     10229     1556, 1556, 1557, 1566, 1571, 1574, 1556, 1576, 1578, 1576, 
     10230     1579, 1557, 1568, 1559, 1562, 1556, 1584, 1565, 1567, 1585, 
     10231 
     10232     1570, 1569, 1570, 1581, 1586, 1581, 1588, 1589, 1590, 1576, 
     10233     1570, 1592, 1571, 1597, 1574, 1593, 1578, 1596, 1594, 1579, 
     10234     1594, 1594, 1600, 1603, 1584, 1581, 1601, 1604, 1585, 1605, 
     10235     1605, 1605, 1607, 1586, 1609, 1588, 1590, 1616, 1593, 1605, 
     10236        0, 1612, 1613, 1618, 1589, 1631, 1614, 1592, 1614, 1627, 
     10237        0, 1596, 1604, 1601,    0, 1597, 1614, 1607, 1632, 1609, 
     10238     1628, 1603, 1628, 1633, 1600,    0,    0, 1593, 1612, 1613, 
     10239     1628, 1618, 1589, 1631, 1616, 1592,    0,    0, 1627, 1596, 
     10240        0, 1604, 1601, 1597,    0, 1634, 1607, 1632, 1609, 1603, 
     10241        0, 1633, 1600, 1621, 1621, 1621, 1621, 1612, 1613, 1639, 
     10242 
     10243        0, 1621, 1616,    0, 1621, 1623, 1623, 1623, 1623, 1624, 
     10244     1624, 1624, 1640, 1623, 1634, 1625, 1625, 1625, 1625, 1635, 
     10245     1641, 1635, 1623, 1625, 1642, 1636, 1624, 1636, 1639, 1635, 
     10246     1648, 1654, 1625, 1649, 1650, 1636, 1651, 1651, 1651, 1655, 
     10247     1656, 1640, 1657,    0, 1663, 1668, 1651,    0, 1735, 1641, 
     10248     1735, 1663, 1668, 1642, 1663, 1668, 1648,    0, 1649, 1735, 
     10249     1675, 1650, 1674, 1676, 1674, 1654, 1673, 1656, 1673, 1657, 
     10250     1655, 1661, 1661, 1661, 1661, 1674, 1673, 1674, 1662, 1662, 
     10251     1662, 1662, 1678, 1661, 1674, 1648, 1662, 1649, 1675, 1662, 
     10252     1650, 1683, 1676, 1654, 1689, 1700, 1656, 1661, 1657, 1655, 
     10253 
     10254     1666, 1666, 1666, 1666, 1667, 1667, 1667, 1667, 1666, 1677, 
     10255     1678, 1666, 1667, 1680, 1681, 1667, 1669, 1669, 1669, 1669, 
     10256     1670, 1670, 1670, 1670, 1669, 1684, 1661, 1683, 1670, 1686, 
     10257     1688, 1700, 1670, 1669, 1691, 1689,    0, 1670, 1677, 1706, 
     10258        0,    0, 1680, 1681, 1709, 1692, 1670, 1692, 1692, 1694, 
     10259     1707, 1694, 1694, 1684, 1708, 1683, 1686, 1688, 1710, 1700, 
     10260     1691,    0,    0, 1689, 1693, 1693, 1693, 1693, 1706, 1697, 
     10261     1697, 1697, 1697, 1709, 1699, 1670, 1693, 1697, 1707, 1716, 
     10262     1697, 1699, 1708, 1714, 1699, 1686, 1688, 1710, 1701, 1691, 
     10263     1693, 1698, 1698, 1698, 1698, 1701, 1711, 1712, 1701, 1698, 
     10264 
     10265     1713, 1703, 1698, 1698, 1702, 1702, 1702, 1702, 1703, 1714, 
     10266     1717, 1703, 1702, 1718, 1704, 1702, 1704, 1698,    0, 1693, 
     10267     1705,    0, 1705,    0, 1711, 1716, 1737, 1704, 1713, 1704, 
     10268     1731, 1705, 1738, 1705, 1712, 1705, 1704, 1719, 1714, 1719, 
     10269     1719, 1717, 1705,    0, 1740, 1720, 1698, 1720, 1720, 1723, 
     10270     1723, 1723, 1723, 1716, 1737,    0, 1718, 1723,    0,    0, 
     10271     1723, 1738, 1712, 1724, 1724, 1724, 1724, 1731, 1741, 1743, 
     10272     1717, 1724, 1740,    0, 1724, 1724, 1726, 1725, 1725, 1725, 
     10273     1725,    0, 1745, 1726, 1718, 1725, 1726, 1727, 1725, 1724, 
     10274        0, 1728, 1742, 1744, 1727, 1731, 1741, 1727, 1728, 1730, 
     10275 
     10276     1750, 1728, 1729, 1729, 1729, 1729, 1730, 1749, 1767, 1730, 
     10277     1729, 1743,    0, 1729, 1732, 1732, 1732, 1732, 1724, 1745, 
     10278     1742, 1744, 1732, 1734,    0, 1732, 1733, 1733, 1733, 1733, 
     10279     1734, 1755, 1770, 1734, 1733,    0, 1767, 1733, 1755, 1743, 
     10280     1750, 1755,    0, 1751, 1749, 1751, 1751, 1745, 1752,    0, 
     10281     1752, 1752, 1753, 1753, 1753, 1753, 1754, 1754, 1754, 1754, 
     10282     1753, 1770, 1765, 1753, 1754,    0,    0, 1754, 1750,    0, 
     10283     1757, 1768, 1749, 1756, 1756, 1756, 1756, 1757, 1758,    0, 
     10284     1757, 1756,    0,    0, 1756, 1758,    0,    0, 1758, 1759, 
     10285     1759, 1759, 1759, 1761, 1760, 1760, 1760, 1760, 1774, 1768, 
     10286 
     10287     1761, 1759, 1760, 1761, 1765, 1760, 1762, 1762, 1762, 1762, 
     10288     1763, 1763, 1763, 1763, 1762, 1759, 1764, 1762, 1763, 1769, 
     10289     1786, 1763, 1763, 1764, 1775, 1776, 1764, 1776, 1776,    0, 
     10290     1790,    0, 1765, 1782, 1774, 1777, 1763, 1777, 1777, 1784, 
     10291     1782,    0,    0, 1782, 1759, 1788, 1784, 1769, 1786, 1784, 
     10292     1791, 1775, 1778, 1778, 1778, 1778, 1779, 1779, 1779, 1779, 
     10293     1778, 1802, 1774, 1778, 1779, 1763, 1805, 1779, 1780, 1780, 
     10294     1780, 1780, 1790, 1792, 1788,    0, 1780,    0, 1791, 1780, 
     10295     1775, 1781, 1781, 1781, 1781, 1808, 1807, 1808, 1808, 1781, 
     10296        0, 1799, 1781, 1781, 1783, 1783, 1783, 1783, 1799, 1806, 
     10297 
     10298     1790, 1799, 1783, 1802, 1813, 1783, 1805, 1781,    0, 1792, 
     10299     1797, 1797, 1797, 1797, 1798, 1798, 1798, 1798, 1797, 1801, 
     10300     1814, 1797, 1798, 1807,    0, 1798, 1801, 1806, 1815, 1801, 
     10301     1817, 1802, 1817, 1817, 1805, 1812, 1781, 1792, 1796, 1796, 
     10302     1796, 1796, 1812, 1796, 1813, 1812, 1796, 1814, 1796, 1796, 
     10303     1796, 1807, 1822, 1796, 1796, 1816,    0, 1815, 1796, 1823, 
     10304     1796, 1796, 1796, 1800, 1800, 1800, 1800, 1809, 1809, 1809, 
     10305     1809, 1800, 1813, 1819, 1800, 1809, 1814, 1829, 1809, 1822, 
     10306     1819,    0, 1823, 1819, 1811, 1811, 1811, 1811,    0, 1796, 
     10307     1796, 1796, 1811,    0,    0, 1811,    0, 1816, 1818, 1818, 
     10308 
     10309     1818, 1818, 1824, 1820,    0, 1829, 1818,    0, 1822, 1818, 
     10310     1820, 1823, 1827, 1820, 1828, 1830,    0, 1796, 1810, 1810, 
     10311     1810, 1810, 1810, 1810, 1831, 1816, 1810, 1810, 1810, 1810, 
     10312     1810, 1824,    0, 1810, 1810, 1827, 1834,    0, 1810,    0, 
     10313     1810, 1810, 1810, 1821, 1821, 1821, 1821, 1826, 1826, 1826, 
     10314     1826, 1821,    0,    0, 1821, 1826, 1828, 1830, 1826, 1832, 
     10315     1832, 1832,    0, 1844, 1827,    0, 1831,    0, 1840, 1810, 
     10316     1810, 1810, 1833, 1833, 1833,    0, 1834, 1835, 1835, 1835, 
     10317     1836, 1836, 1836, 1843, 1828, 1830, 1837, 1837, 1837, 1837, 
     10318     1838, 1838, 1838,    0, 1831, 1840,    0, 1810, 1841, 1841, 
     10319 
     10320     1841, 1845, 1845, 1845, 1834, 1844, 1843, 1846, 1846, 1846, 
    808310321        0,    0,    0,    0,    0,    0,    0,    0,    0,    0, 
    8084         0,    0, 1127, 1126,    0, 1123, 1114,    0,    0, 1117, 
    8085  
    8086         0,    0,    0,    0,    0,    0,    0,    0,    0,    0, 
    8087         0,    0,    0,    0,    0,    0,    0,    0,    0,    0, 
    8088      1127, 1132, 1132, 1132, 1132, 1132, 1132, 1132, 1132, 1132, 
    8089      1132, 1132, 1132, 1132, 1133, 1133, 1133, 1133, 1133, 1133, 
    8090      1133, 1133, 1133, 1133, 1133, 1133, 1133, 1134,    0, 1134, 
    8091      1134, 1134, 1134, 1134, 1134, 1134, 1134, 1134, 1134, 1134, 
    8092      1135, 1135, 1135, 1135, 1135, 1135, 1135, 1135, 1135, 1135, 
    8093      1135, 1135, 1135, 1136, 1136, 1136, 1136, 1136, 1136, 1136, 
    8094      1136, 1136, 1136, 1136, 1136, 1136, 1137, 1137, 1137, 1137, 
    8095      1137, 1137, 1137, 1137, 1137, 1137, 1137, 1137, 1137, 1138, 
    8096  
    8097      1138, 1138, 1138, 1138, 1138, 1138, 1138, 1138, 1139, 1139, 
    8098      1139, 1139, 1139, 1139, 1139, 1139, 1139, 1139, 1139, 1139, 
    8099      1139, 1140, 1140, 1140, 1140, 1140, 1140, 1140, 1140, 1140, 
    8100      1140, 1140, 1140, 1140, 1141, 1141, 1141, 1141, 1141,    0, 
    8101      1141, 1141, 1141,    0, 1141,    0, 1141, 1142, 1142, 1142, 
    8102      1142, 1142, 1142, 1142, 1142, 1142, 1142, 1142, 1142, 1142, 
    8103      1143,    0,    0,    0,    0,    0,    0,    0, 1143, 1144, 
    8104      1144,    0, 1144, 1144,    0, 1144,    0,    0, 1144, 1144, 
    8105         0, 1144, 1145, 1145, 1145, 1145, 1146, 1146, 1146, 1146, 
    8106      1146, 1146, 1146, 1146, 1146, 1146, 1146, 1146, 1146, 1147, 
    8107  
    8108      1147, 1147, 1147, 1147, 1147, 1147, 1147, 1147, 1147, 1147, 
    8109      1147, 1147, 1148, 1148, 1148, 1148, 1148, 1148, 1148, 1148, 
    8110      1148, 1148, 1148, 1148, 1148, 1149, 1149, 1149,    0, 1149, 
    8111      1149, 1149, 1149, 1149, 1149, 1149, 1149, 1149, 1150,    0, 
    8112      1150, 1150, 1150, 1150, 1150, 1150, 1150, 1150, 1150, 1150, 
    8113      1150, 1151,    0, 1151, 1151, 1151, 1151, 1151, 1151, 1151, 
    8114      1151, 1151, 1151, 1151, 1152, 1152, 1152, 1152, 1152, 1152, 
    8115      1152, 1152, 1152, 1152, 1152, 1152, 1152, 1153, 1153, 1153, 
    8116      1153, 1153, 1153, 1153, 1153, 1153, 1153, 1153, 1153, 1153, 
    8117      1154, 1154, 1154, 1154, 1154, 1154, 1154, 1154, 1154, 1154, 
    8118  
    8119      1154, 1154, 1154, 1155,    0, 1155, 1155, 1155, 1155, 1155, 
    8120      1155, 1155, 1155, 1155, 1155, 1155, 1156, 1156, 1156, 1156, 
    8121      1156, 1156, 1156, 1156, 1156, 1156, 1156, 1156, 1156, 1157, 
    8122      1157, 1157, 1157, 1157, 1157, 1157, 1157, 1157, 1157, 1157, 
    8123      1157, 1157, 1158, 1158, 1158, 1158, 1158, 1158, 1158, 1158, 
    8124      1158, 1158, 1158, 1158, 1158, 1159,    0, 1159, 1159, 1159, 
    8125      1159, 1159, 1159, 1159, 1159, 1159, 1159, 1159, 1160,    0, 
    8126      1160, 1160, 1160, 1160, 1160, 1160, 1160, 1160, 1160, 1160, 
    8127      1160, 1161, 1161, 1161, 1161, 1161, 1161, 1161, 1161, 1161, 
    8128      1161, 1161, 1161, 1161, 1162, 1162, 1162, 1162, 1162, 1162, 
    8129  
    8130      1162, 1162, 1162, 1162, 1162, 1162, 1162, 1163, 1163, 1163, 
    8131      1163, 1163, 1163, 1163, 1163, 1163, 1163, 1163, 1163, 1163, 
    8132      1164,    0, 1164, 1164, 1164, 1164, 1164, 1164, 1164, 1164, 
    8133      1164, 1164, 1164, 1165, 1165, 1165, 1165, 1165, 1165, 1165, 
    8134      1165, 1165, 1165, 1165, 1165, 1165, 1166, 1166, 1166, 1166, 
    8135      1166, 1166, 1166, 1166, 1166, 1166, 1166, 1166, 1166, 1167, 
    8136      1167, 1167, 1167, 1167, 1167, 1167, 1167, 1167, 1167, 1167, 
    8137      1167, 1167, 1168, 1168, 1168, 1168, 1168, 1168, 1168, 1168, 
    8138      1168, 1168, 1168, 1168, 1168, 1169, 1169, 1169, 1169, 1169, 
    8139      1169, 1169, 1169, 1169, 1169, 1169, 1169, 1169, 1170, 1170, 
    8140  
    8141      1170, 1170, 1170, 1170, 1170, 1170, 1170, 1170, 1170, 1170, 
    8142      1170, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    8143      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    8144      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    8145      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    8146      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    8147      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    8148      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    8149      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    8150      1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 1131, 
    8151  
    8152      1131 
     10322        0,    0,    0,    0, 1840,    0,    0,    0,    0,    0, 
     10323        0,    0,    0, 1844,    0, 1843, 1849, 1849, 1849, 1849, 
     10324     1849, 1849, 1849, 1849, 1849, 1849, 1849, 1849, 1849, 1849, 
     10325     1849, 1849, 1849, 1849, 1850, 1850, 1850, 1850, 1850, 1850, 
     10326     1850, 1850, 1850, 1850, 1850, 1850, 1850, 1850, 1850, 1850, 
     10327     1850, 1850, 1851, 1851,    0, 1851, 1851, 1851, 1851, 1851, 
     10328     1851, 1851, 1851, 1851, 1851, 1851, 1851, 1851, 1851, 1851, 
     10329     1852, 1852, 1852, 1852, 1852, 1852, 1852, 1852, 1852, 1852, 
     10330 
     10331     1852, 1852, 1852, 1852, 1852, 1852, 1852, 1852, 1853, 1853, 
     10332     1853, 1853, 1853, 1853, 1853, 1853, 1853, 1853, 1853, 1853, 
     10333     1853, 1853, 1853, 1853, 1853, 1853, 1854,    0,    0,    0, 
     10334        0,    0,    0, 1854,    0, 1854,    0, 1854, 1854, 1854, 
     10335     1854, 1854, 1855, 1855, 1855, 1855, 1855, 1856, 1856, 1856, 
     10336     1856, 1856, 1856, 1856, 1856, 1856, 1856, 1856, 1856, 1856, 
     10337     1856, 1856, 1856, 1856, 1856, 1857, 1857, 1857, 1857, 1857, 
     10338     1857, 1857, 1857, 1857, 1857, 1857, 1857, 1857, 1857, 1857, 
     10339     1857, 1857, 1857, 1858, 1858, 1858, 1858, 1858, 1858, 1858, 
     10340     1858, 1858, 1858, 1858, 1858, 1858, 1858, 1858, 1858, 1858, 
     10341 
     10342     1858, 1859,    0,    0,    0,    0,    0,    0,    0,    0, 
     10343        0,    0, 1859, 1859, 1859, 1859, 1859, 1860, 1860, 1860, 
     10344     1860, 1860, 1860, 1860, 1860, 1860, 1860, 1860, 1860, 1860, 
     10345     1860, 1860, 1860, 1860, 1860, 1861, 1861,    0, 1861, 1861, 
     10346     1861, 1861, 1861, 1861, 1861, 1861, 1861, 1861, 1861, 1861, 
     10347     1861, 1861, 1861, 1862, 1862, 1862, 1862, 1862, 1862, 1862, 
     10348     1862, 1862, 1862, 1862, 1862, 1862, 1862, 1862, 1862, 1862, 
     10349     1862, 1863, 1863, 1863, 1863, 1863, 1863, 1863, 1863, 1863, 
     10350     1863, 1863, 1863, 1863, 1863, 1863, 1863, 1863, 1863, 1864, 
     10351     1864, 1864, 1864, 1864, 1864, 1864, 1864, 1864, 1864, 1864, 
     10352 
     10353     1864, 1864, 1864, 1864, 1864, 1864, 1864, 1865, 1865, 1865, 
     10354     1865, 1865, 1865, 1865, 1865, 1865, 1865, 1865, 1865, 1865, 
     10355     1865, 1865, 1865, 1865, 1865, 1866,    0,    0,    0,    0, 
     10356        0,    0, 1866,    0, 1866,    0,    0, 1866, 1866, 1866, 
     10357     1866, 1867, 1867, 1867, 1867,    0, 1867, 1867, 1867, 1867, 
     10358     1867, 1867,    0, 1867, 1867,    0,    0, 1867, 1867, 1868, 
     10359     1868, 1868, 1868, 1868, 1870, 1870, 1870, 1870, 1870, 1870, 
     10360     1870, 1870, 1870, 1870, 1870, 1870, 1870, 1870, 1870, 1870, 
     10361     1870, 1870, 1871, 1871, 1871, 1871, 1871, 1871, 1871, 1871, 
     10362     1871, 1871, 1871, 1871, 1871, 1871, 1871, 1871, 1871, 1871, 
     10363 
     10364     1872, 1872, 1872, 1872, 1872, 1872, 1872, 1872, 1872, 1872, 
     10365     1872, 1872, 1872, 1872, 1872, 1872, 1872, 1872, 1873, 1873, 
     10366     1873, 1873, 1873, 1873, 1873, 1873, 1873, 1873, 1873, 1873, 
     10367     1873, 1873, 1873, 1873, 1873, 1873, 1874, 1874, 1874, 1874, 
     10368     1874, 1874, 1874, 1874, 1874, 1874, 1874, 1874, 1874, 1874, 
     10369     1874, 1874, 1874, 1874, 1875, 1875, 1875, 1875, 1875, 1875, 
     10370     1875, 1875, 1875, 1875, 1875, 1875, 1875, 1875, 1875, 1875, 
     10371     1875, 1875, 1876, 1876, 1876, 1876, 1876, 1876, 1876, 1876, 
     10372     1876, 1876, 1876, 1876, 1876, 1876, 1876, 1876, 1876, 1876, 
     10373     1877, 1877, 1877, 1877, 1877, 1877, 1877, 1877, 1877, 1877, 
     10374 
     10375     1877, 1877, 1877, 1877, 1877, 1877, 1877, 1877, 1878, 1878, 
     10376     1878, 1878, 1878, 1878, 1878, 1878, 1878, 1878, 1878, 1878, 
     10377     1878, 1878, 1878, 1878, 1878, 1878, 1879, 1879,    0, 1879, 
     10378     1879, 1879, 1879, 1879, 1879, 1879, 1879, 1879, 1879, 1879, 
     10379     1879, 1879, 1879, 1879, 1880, 1880, 1880, 1880, 1880, 1880, 
     10380     1880, 1880, 1880, 1880, 1880, 1880, 1880, 1880, 1880, 1880, 
     10381     1880, 1880, 1881, 1881, 1881, 1881, 1881, 1881, 1881, 1881, 
     10382     1881, 1881, 1881, 1881, 1881, 1881, 1881, 1881, 1881, 1881, 
     10383     1882, 1882, 1882, 1882, 1882, 1882, 1882, 1882, 1882, 1882, 
     10384     1882, 1882, 1882, 1882, 1882, 1882, 1882, 1882, 1883, 1883, 
     10385 
     10386     1883, 1883, 1883, 1883, 1883, 1883, 1883, 1883, 1883, 1883, 
     10387     1883, 1883, 1883, 1883, 1883, 1883, 1884, 1884, 1884, 1884, 
     10388     1884, 1884, 1884, 1884, 1884, 1884, 1884, 1884, 1884, 1884, 
     10389     1884, 1884, 1884, 1884, 1885,    0,    0,    0,    0,    0, 
     10390        0, 1885,    0, 1885,    0,    0, 1885, 1885, 1885, 1885, 
     10391     1886,    0,    0,    0,    0,    0,    0,    0, 1886,    0, 
     10392     1886,    0, 1886, 1886, 1886, 1886, 1886, 1887, 1887, 1887, 
     10393     1887, 1888, 1888, 1888, 1888, 1888, 1888, 1888, 1888, 1888, 
     10394     1888, 1888, 1888, 1888, 1888, 1888, 1888, 1888, 1888, 1889, 
     10395     1889, 1889, 1889, 1889, 1889, 1889, 1889, 1889, 1889, 1889, 
     10396 
     10397     1889, 1889, 1889, 1889, 1889, 1889, 1889, 1890, 1890, 1890, 
     10398     1890, 1890, 1890, 1890, 1890, 1890, 1890, 1890, 1890, 1890, 
     10399     1890, 1890, 1890, 1890, 1890, 1891, 1891, 1891, 1891,    0, 
     10400     1891, 1891, 1891, 1891, 1891, 1891,    0, 1891, 1891,    0, 
     10401        0, 1891, 1891, 1892, 1892, 1892, 1892, 1892, 1893, 1893, 
     10402     1893, 1893, 1893, 1893, 1893, 1893, 1893, 1893, 1893, 1893, 
     10403     1893, 1893, 1893, 1893, 1893, 1893, 1894,    0,    0,    0, 
     10404        0,    0,    0,    0, 1894, 1894, 1895, 1895, 1895, 1895, 
     10405     1895, 1895, 1895, 1895, 1895, 1895, 1895, 1895, 1895, 1895, 
     10406     1895, 1895, 1895, 1895, 1896, 1896, 1896, 1896, 1896, 1896, 
     10407 
     10408     1896, 1896, 1896, 1896, 1896, 1896, 1896, 1896, 1896, 1896, 
     10409     1896, 1896, 1897, 1897, 1897, 1897, 1897, 1897, 1897, 1897, 
     10410     1897, 1897, 1897, 1897, 1897, 1897, 1897, 1897, 1897, 1897, 
     10411     1898, 1898, 1898, 1898, 1898, 1898, 1898, 1898, 1898, 1898, 
     10412     1898, 1898, 1898, 1898, 1898, 1898, 1898, 1898, 1899, 1899, 
     10413     1899, 1899, 1899, 1899, 1899, 1899, 1899, 1899, 1899, 1899, 
     10414     1899, 1899, 1899, 1899, 1899, 1899, 1900, 1900, 1900, 1900, 
     10415     1900, 1900, 1900, 1900, 1900, 1900, 1900, 1900, 1900, 1900, 
     10416     1900, 1900, 1900, 1900, 1901, 1901, 1901, 1901, 1901, 1901, 
     10417     1901, 1901, 1901, 1901, 1901, 1901, 1901, 1901, 1901, 1901, 
     10418 
     10419     1901, 1901, 1902, 1902, 1902, 1902, 1902, 1902, 1902, 1902, 
     10420     1902, 1902, 1902, 1902, 1902, 1902, 1902, 1902, 1902, 1902, 
     10421     1903,    0,    0,    0,    0,    0,    0,    0,    0,    0, 
     10422        0, 1903, 1903, 1903, 1903, 1903, 1904, 1904, 1904, 1904, 
     10423     1904, 1904, 1904, 1904, 1904, 1904, 1904, 1904, 1904, 1904, 
     10424     1904, 1904, 1904, 1904, 1905, 1905, 1905, 1905, 1905, 1905, 
     10425     1905, 1905, 1905, 1905, 1905, 1905, 1905, 1905, 1905, 1905, 
     10426     1905, 1905, 1906, 1906, 1906, 1906, 1906, 1906, 1906, 1906, 
     10427     1906, 1906, 1906, 1906, 1906, 1906, 1906, 1906, 1906, 1906, 
     10428     1907, 1907,    0, 1907, 1907, 1907, 1907, 1907, 1907, 1907, 
     10429 
     10430     1907, 1907, 1907, 1907, 1907, 1907, 1907, 1907, 1908, 1908, 
     10431     1908, 1908, 1908, 1908, 1908, 1908, 1908, 1908, 1908, 1908, 
     10432     1908, 1908, 1908, 1908, 1908, 1908, 1909, 1909, 1909, 1909, 
     10433     1909, 1909, 1909, 1909, 1909, 1909, 1909, 1909, 1909, 1909, 
     10434     1909, 1909, 1909, 1909, 1910, 1910, 1910, 1910, 1910, 1910, 
     10435     1910, 1910, 1910, 1910, 1910, 1910, 1910, 1910, 1910, 1910, 
     10436     1910, 1910, 1911, 1911, 1911, 1911, 1911, 1911, 1911, 1911, 
     10437     1911, 1911, 1911, 1911, 1911, 1911, 1911, 1911, 1911, 1911, 
     10438     1912,    0,    0,    0,    0,    0,    0, 1912,    0, 1912, 
     10439        0,    0, 1912, 1912, 1912, 1912, 1913,    0,    0,    0, 
     10440 
     10441        0,    0,    0,    0, 1913,    0,    0,    0, 1913, 1913, 
     10442     1913, 1913, 1913, 1914,    0,    0,    0,    0,    0,    0, 
     10443        0, 1914,    0, 1914,    0, 1914, 1914, 1914, 1914, 1914, 
     10444     1915, 1915, 1915, 1915, 1915, 1915, 1915, 1915, 1915, 1915, 
     10445     1915, 1915, 1915, 1915, 1915, 1915, 1915, 1915, 1916, 1916, 
     10446     1916, 1916, 1916, 1916, 1916, 1916, 1916, 1916, 1916, 1916, 
     10447     1916, 1916, 1916, 1916, 1916, 1916, 1917, 1917, 1917, 1917, 
     10448     1917, 1917, 1917, 1917, 1917, 1917, 1917, 1917, 1917, 1917, 
     10449     1917, 1917, 1917, 1917, 1918, 1918, 1918, 1918, 1918, 1918, 
     10450     1918, 1918, 1918, 1918, 1918, 1918, 1918, 1918, 1918, 1918, 
     10451 
     10452     1918, 1918, 1919, 1919, 1919, 1919, 1919, 1920, 1920, 1920, 
     10453     1920, 1920, 1920, 1920, 1920, 1920, 1920, 1920, 1920, 1920, 
     10454     1920, 1920, 1920, 1920, 1920, 1921, 1921, 1921, 1921, 1921, 
     10455     1921,    0, 1921, 1921, 1921, 1921, 1921, 1921, 1921, 1921, 
     10456     1921, 1921, 1921, 1922, 1922,    0, 1922, 1922, 1922, 1922, 
     10457     1922, 1922, 1922, 1922, 1922, 1922, 1922, 1922, 1922, 1922, 
     10458     1922, 1923, 1923, 1923, 1923, 1923, 1923, 1923, 1923, 1923, 
     10459     1923, 1923, 1923, 1923, 1923, 1923, 1923, 1923, 1923, 1924, 
     10460     1924, 1924, 1924, 1924, 1924, 1924, 1924, 1924, 1924, 1924, 
     10461     1924, 1924, 1924, 1924, 1924, 1924, 1924, 1925, 1925, 1925, 
     10462 
     10463     1925, 1925, 1925, 1925, 1925, 1925, 1925, 1925, 1925, 1925, 
     10464     1925, 1925, 1925, 1925, 1925, 1926, 1926, 1926, 1926, 1926, 
     10465     1926, 1926, 1926, 1926, 1926, 1926, 1926, 1926, 1926, 1926, 
     10466     1926, 1926, 1926, 1927, 1927, 1927, 1927, 1927, 1927, 1927, 
     10467     1927, 1927, 1927, 1927, 1927, 1927, 1927, 1927, 1927, 1927, 
     10468     1927, 1928, 1928, 1928, 1928, 1928, 1928, 1928, 1928, 1928, 
     10469     1928, 1928, 1928, 1928, 1928, 1928, 1928, 1928, 1928, 1929, 
     10470     1929,    0, 1929, 1929, 1929, 1929, 1929, 1929, 1929, 1929, 
     10471     1929, 1929, 1929, 1929, 1929, 1929, 1929, 1930, 1930,    0, 
     10472     1930, 1930, 1930, 1930, 1930, 1930, 1930, 1930, 1930, 1930, 
     10473 
     10474     1930, 1930, 1930, 1930, 1930, 1931, 1931,    0, 1931, 1931, 
     10475     1931, 1931, 1931, 1931, 1931, 1931, 1931, 1931, 1931, 1931, 
     10476     1931, 1931, 1931, 1932, 1932, 1932, 1932, 1932, 1932, 1932, 
     10477     1932, 1932, 1932, 1932, 1932, 1932, 1932, 1932, 1932, 1932, 
     10478     1932, 1933, 1933, 1933, 1933, 1933, 1933, 1933, 1933, 1933, 
     10479     1933, 1933, 1933, 1933, 1933, 1933, 1933, 1933, 1933, 1934, 
     10480     1934, 1934, 1934, 1934, 1934, 1934, 1934, 1934, 1934, 1934, 
     10481     1934, 1934, 1934, 1934, 1934, 1934, 1934, 1935, 1935, 1935, 
     10482     1935, 1935, 1935, 1935, 1935, 1935, 1935, 1935, 1935, 1935, 
     10483     1935, 1935, 1935, 1935, 1935, 1936,    0,    0,    0,    0, 
     10484 
     10485        0, 1936,    0,    0,    0, 1936,    0, 1936, 1936, 1936, 
     10486     1936, 1936, 1937, 1937, 1937, 1937, 1938,    0,    0,    0, 
     10487        0,    0,    0,    0, 1938,    0,    0,    0, 1938, 1938, 
     10488     1938, 1938, 1938, 1939,    0,    0,    0,    0,    0,    0, 
     10489        0, 1939,    0, 1939,    0, 1939, 1939, 1939, 1939, 1939, 
     10490     1940, 1940,    0, 1940, 1940, 1940, 1940, 1940, 1940, 1940, 
     10491     1940, 1940, 1940, 1940, 1940, 1940, 1940, 1940, 1941, 1941, 
     10492     1941, 1941, 1941, 1941, 1941, 1941, 1941, 1941, 1941, 1941, 
     10493     1941, 1941, 1941, 1941, 1941, 1941, 1942, 1942,    0, 1942, 
     10494     1942, 1942, 1942, 1942, 1942, 1942, 1942, 1942, 1942, 1942, 
     10495 
     10496     1942, 1942, 1942, 1942, 1943, 1943, 1943, 1943, 1943, 1943, 
     10497        0, 1943, 1943, 1943, 1943, 1943, 1943, 1943, 1943, 1943, 
     10498     1943, 1943, 1944, 1944,    0, 1944, 1944, 1944, 1944, 1944, 
     10499     1944, 1944, 1944, 1944, 1944, 1944, 1944, 1944, 1944, 1944, 
     10500     1945, 1945, 1945, 1945, 1945, 1945, 1945, 1945, 1945, 1945, 
     10501     1945, 1945, 1945, 1945, 1945, 1945, 1945, 1945, 1946, 1946, 
     10502     1946, 1946, 1946, 1946, 1946, 1946, 1946, 1946, 1946, 1946, 
     10503     1946, 1946, 1946, 1946, 1946, 1946, 1947, 1947, 1947, 1947, 
     10504     1947, 1947, 1947, 1947, 1947, 1947, 1947, 1947, 1947, 1947, 
     10505     1947, 1947, 1947, 1947, 1948, 1948, 1948, 1948, 1948, 1948, 
     10506 
     10507     1948, 1948, 1948, 1948, 1948, 1948, 1948, 1948, 1948, 1948, 
     10508     1948, 1948, 1949, 1949, 1949, 1949, 1949, 1949, 1949, 1949, 
     10509     1949, 1949, 1949, 1949, 1949, 1949, 1949, 1949, 1949, 1949, 
     10510     1950, 1950, 1950, 1950, 1950, 1950, 1950, 1950, 1950, 1950, 
     10511     1950, 1950, 1950, 1950, 1950, 1950, 1950, 1950, 1951, 1951, 
     10512     1951, 1951, 1951, 1951, 1951, 1951, 1951, 1951, 1951, 1951, 
     10513     1951, 1951, 1951, 1951, 1951, 1951, 1952, 1952, 1952, 1952, 
     10514     1952, 1952, 1952, 1952, 1952, 1952, 1952, 1952, 1952, 1952, 
     10515     1952, 1952, 1952, 1952, 1953, 1953, 1953, 1953, 1953, 1953, 
     10516     1953, 1953, 1953, 1953, 1953, 1953, 1953, 1953, 1953, 1953, 
     10517 
     10518     1953, 1953, 1954, 1954, 1954, 1954, 1954, 1954, 1954, 1954, 
     10519     1954, 1954, 1954, 1954, 1954, 1954, 1954, 1954, 1954, 1954, 
     10520     1955, 1955,    0, 1955, 1955, 1955, 1955, 1955, 1955, 1955, 
     10521     1955, 1955, 1955, 1955, 1955, 1955, 1955, 1955, 1956, 1956, 
     10522        0, 1956, 1956, 1956, 1956, 1956, 1956, 1956, 1956, 1956, 
     10523     1956, 1956, 1956, 1956, 1956, 1956, 1957, 1957,    0, 1957, 
     10524     1957, 1957, 1957, 1957, 1957, 1957, 1957, 1957, 1957, 1957, 
     10525     1957, 1957, 1957, 1957, 1958, 1958, 1958, 1958, 1958, 1958, 
     10526     1958, 1958, 1958, 1958, 1958, 1958, 1958, 1958, 1958, 1958, 
     10527     1958, 1958, 1959, 1959, 1959, 1959, 1959, 1959, 1959, 1959, 
     10528 
     10529     1959, 1959, 1959, 1959, 1959, 1959, 1959, 1959, 1959, 1959, 
     10530     1960, 1960, 1960, 1960, 1960, 1960, 1960, 1960, 1960, 1960, 
     10531     1960, 1960, 1960, 1960, 1960, 1960, 1960, 1960, 1961, 1961, 
     10532     1961, 1961, 1961, 1961, 1961, 1961, 1961, 1961, 1961, 1961, 
     10533     1961, 1961, 1961, 1961, 1961, 1961, 1962,    0,    0,    0, 
     10534        0,    0, 1962,    0,    0,    0,    0,    0, 1962, 1962, 
     10535     1962, 1962, 1962, 1963, 1963,    0, 1963, 1963, 1963, 1963, 
     10536     1963, 1963, 1963, 1963, 1963, 1963, 1963, 1963, 1963, 1963, 
     10537     1963, 1964,    0,    0,    0,    0,    0,    0, 1964,    0, 
     10538     1964,    0,    0, 1964, 1964, 1964, 1964, 1965,    0,    0, 
     10539 
     10540        0,    0,    0,    0,    0, 1965,    0, 1965,    0, 1965, 
     10541     1965, 1965, 1965, 1965, 1966, 1966, 1966, 1966, 1967, 1967, 
     10542        0, 1967, 1967, 1967, 1967, 1967, 1967, 1967, 1967, 1967, 
     10543     1967, 1967, 1967, 1967, 1967, 1967, 1968, 1968, 1968, 1968, 
     10544     1968, 1968,    0, 1968, 1968, 1968, 1968, 1968, 1968, 1968, 
     10545     1968, 1968, 1968, 1968, 1969, 1969,    0, 1969, 1969, 1969, 
     10546     1969, 1969, 1969, 1969, 1969, 1969, 1969, 1969, 1969, 1969, 
     10547     1969, 1969, 1970, 1970,    0, 1970, 1970, 1970, 1970, 1970, 
     10548     1970, 1970, 1970, 1970, 1970, 1970, 1970, 1970, 1970, 1970, 
     10549     1971, 1971, 1971, 1971, 1971, 1971, 1971, 1971, 1971, 1971, 
     10550 
     10551     1971, 1971, 1971, 1971, 1971, 1971, 1971, 1971, 1972, 1972, 
     10552     1972, 1972, 1972, 1972, 1972, 1972, 1972, 1972, 1972, 1972, 
     10553     1972, 1972, 1972, 1972, 1972, 1972, 1973, 1973, 1973, 1973, 
     10554     1973, 1973, 1973, 1973, 1973, 1973, 1973, 1973, 1973, 1973, 
     10555     1973, 1973, 1973, 1973, 1974, 1974, 1974, 1974, 1974, 1974, 
     10556     1974, 1974, 1974, 1974, 1974, 1974, 1974, 1974, 1974, 1974, 
     10557     1974, 1974, 1975,    0, 1975,    0,    0,    0,    0, 1975, 
     10558        0,    0, 1975, 1975, 1975, 1975, 1975, 1975, 1976, 1976, 
     10559     1976, 1976, 1976, 1976, 1976, 1976, 1976, 1976, 1976, 1976, 
     10560     1976, 1976, 1976, 1976, 1976, 1976, 1977, 1977, 1977, 1977, 
     10561 
     10562     1977, 1977, 1977, 1977, 1977, 1977, 1977, 1977, 1977, 1977, 
     10563     1977, 1977, 1977, 1977, 1978, 1978, 1978, 1978, 1978, 1978, 
     10564     1978, 1978, 1978, 1978, 1978, 1978, 1978, 1978, 1978, 1978, 
     10565     1978, 1978, 1979, 1979, 1979, 1979, 1979, 1979, 1979, 1979, 
     10566     1979, 1979, 1979, 1979, 1979, 1979, 1979, 1979, 1979, 1979, 
     10567     1980, 1980, 1980, 1980, 1980, 1980, 1980, 1980, 1980, 1980, 
     10568     1980, 1980, 1980, 1980, 1980, 1980, 1980, 1980, 1981, 1981, 
     10569        0, 1981, 1981, 1981, 1981, 1981, 1981, 1981, 1981, 1981, 
     10570     1981, 1981, 1981, 1981, 1981, 1981, 1982, 1982, 1982, 1982, 
     10571     1982, 1982, 1982, 1982, 1982, 1982, 1982, 1982, 1982, 1982, 
     10572 
     10573     1982, 1982, 1982, 1982, 1983, 1983, 1983, 1983, 1983, 1983, 
     10574     1983, 1983, 1983, 1983, 1983, 1983, 1983, 1983, 1983, 1983, 
     10575     1983, 1983, 1984,    0,    0,    0,    0,    0, 1984,    0, 
     10576        0,    0,    0,    0, 1984, 1984, 1984, 1984, 1984, 1985, 
     10577        0, 1985,    0,    0,    0,    0, 1985,    0,    0, 1985, 
     10578     1985, 1985, 1985, 1985, 1985, 1986,    0, 1986,    0,    0, 
     10579        0,    0, 1986,    0,    0, 1986, 1986, 1986, 1986, 1986, 
     10580     1986, 1987, 1987, 1987, 1987, 1987, 1987, 1987, 1987, 1987, 
     10581     1987, 1987, 1987, 1987, 1987, 1987, 1987, 1987, 1987, 1988, 
     10582     1988, 1988, 1988, 1988, 1989, 1989,    0, 1989, 1989, 1989, 
     10583 
     10584     1989, 1989, 1989, 1989, 1989, 1989, 1989, 1989, 1989, 1989, 
     10585     1989, 1989, 1990, 1990, 1990, 1990, 1990, 1990, 1990, 1990, 
     10586     1990, 1990, 1990, 1990, 1990, 1990, 1990, 1990, 1990, 1990, 
     10587     1991, 1991, 1991, 1991, 1991, 1991, 1991, 1991, 1991, 1991, 
     10588     1991, 1991, 1991, 1991, 1991, 1991, 1991, 1991, 1992, 1992, 
     10589     1992, 1992, 1992, 1992, 1992, 1992, 1992, 1992, 1992, 1992, 
     10590     1992, 1992, 1992, 1992, 1992, 1992, 1993, 1993, 1993, 1993, 
     10591     1993, 1993, 1993, 1993, 1993, 1993, 1993, 1993, 1993, 1993, 
     10592     1993, 1993, 1993, 1993, 1994, 1994, 1994, 1994, 1994, 1994, 
     10593     1994, 1994, 1994, 1994, 1994, 1994, 1994, 1994, 1994, 1994, 
     10594 
     10595     1994, 1994, 1995, 1995, 1995, 1995, 1995, 1995, 1995, 1995, 
     10596     1995, 1995, 1995, 1995, 1995, 1995, 1995, 1995, 1995, 1995, 
     10597     1996, 1996, 1996, 1996, 1996, 1996, 1996, 1996, 1996, 1996, 
     10598     1996, 1996, 1996, 1996, 1996, 1996, 1996, 1996, 1997, 1997, 
     10599     1997, 1997, 1997, 1997, 1997, 1997, 1997, 1997, 1997, 1997, 
     10600     1997, 1997, 1997, 1997, 1997, 1997, 1998, 1998, 1998, 1998, 
     10601     1998, 1998, 1998, 1998, 1998, 1998, 1998, 1998, 1998, 1998, 
     10602     1998, 1998, 1998, 1998, 1999, 1999, 1999, 1999, 1999, 1999, 
     10603     1999, 1999, 1999, 1999, 1999, 1999, 1999, 1999, 1999, 1999, 
     10604     1999, 1999, 2000, 2000, 2000, 2000, 2000, 2000, 2000, 2000, 
     10605 
     10606     2000, 2000, 2000, 2000, 2000, 2000, 2000, 2000, 2000, 2000, 
     10607     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     10608     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     10609     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     10610     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     10611     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     10612     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     10613     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     10614     1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 1848, 
     10615     1848 
     10616 
    815310617    } ; 
    8154  
    8155 static yy_state_type yy_last_accepting_state; 
    8156 static char *yy_last_accepting_cpos; 
    815710618 
    815810619extern int fortran__flex_debug; 
    815910620int fortran__flex_debug = 0; 
    816010621 
    8161 /* The intent behind this definition is that it'll catch 
    8162  * any uses of REJECT which flex missed. 
    8163  */ 
    8164 #define REJECT reject_used_but_not_detected 
     10622static yy_state_type *yy_state_buf=0, *yy_state_ptr=0; 
     10623static char *yy_full_match; 
     10624static int yy_lp; 
     10625static int yy_looking_for_trail_begin = 0; 
     10626static int yy_full_lp; 
     10627static int *yy_full_state; 
     10628#define YY_TRAILING_MASK 0x2000 
     10629#define YY_TRAILING_HEAD_MASK 0x4000 
     10630#define REJECT \ 
     10631{ \ 
     10632*yy_cp = (yy_hold_char); /* undo effects of setting up fortran_text */ \ 
     10633yy_cp = (yy_full_match); /* restore poss. backed-over text */ \ 
     10634(yy_lp) = (yy_full_lp); /* restore orig. accepting pos. */ \ 
     10635(yy_state_ptr) = (yy_full_state); /* restore orig. state */ \ 
     10636yy_current_state = *(yy_state_ptr); /* restore curr. state */ \ 
     10637++(yy_lp); \ 
     10638goto find_rule; \ 
     10639} 
     10640 
    816510641#define yymore() yymore_used_but_not_detected 
    816610642#define YY_MORE_ADJ 0 
     
    820710683 
    820810684 
    8209 #line 44 "fortran.lex" 
     10685 
     10686#line 45 "fortran.lex" 
    821010687#include <math.h> 
    821110688#include <stdlib.h> 
     
    821310690extern FILE * fortran_in; 
    821410691#define MAX_INCLUDE_DEPTH 30 
     10692#define YY_BUF_SIZE 64000 
    821510693YY_BUFFER_STATE include_stack[MAX_INCLUDE_DEPTH]; 
    8216 int line_num_input = 1; 
     10694int line_num_input = 0; 
    821710695int newlinef90 = 0; 
    8218 char tmpc; 
    8219 #define PRINT_LINE_NUM()     // { fprintf(stderr,"== Parsing l.%4d...\n", line_num_input); } 
    8220 #define INCREMENT_LINE_NUM() { line_num_input++; PRINT_LINE_NUM(); } 
    8221  
    8222 /******************************************************************************/ 
    8223 /**************PETITS PB NON PREVUS *******************************************/ 
    8224 /******************************************************************************/ 
    8225 /* NEXTLINF77 un ligne fortran 77 peut commencer par -      &a=b or on        */ 
    8226 /*            a prevu seulement       & a=b avec l'espace entre le symbole    */ 
    8227 /*            de la 7eme et le debut de la ligne de commande                  */ 
    8228 /*            le ! est aussi interdit comme symbole de la 7 eme colonne       */ 
    8229 /*            Normalement NEXTLINEF77 \n+[ ]{5}[^ ]                           */ 
    8230 /******************************************************************************/ 
    8231 #define YY_USER_ACTION  if (firstpass == 0) ECHO; 
     10696int tmpc; 
     10697 
     10698int lastwasendofstmt = 1; 
     10699 
     10700extern char linebuf1[1024]; 
     10701extern char linebuf2[1024]; 
     10702 
     10703int count_newlines(const char* str_in) 
     10704{ 
     10705    int k, i = 0; 
     10706    for( k=0 ; k<strlen(str_in) ; k++) 
     10707        if (str_in[k] == '\n') i++; 
     10708    return i; 
     10709} 
     10710 
     10711#define PRINT_LINE_NUM()    // { fprintf(stderr,"== Parsing l.%4d...\n", line_num_input); } 
     10712#define INCREMENT_LINE_NUM() { line_num_input+=count_newlines(fortran_text) ; PRINT_LINE_NUM(); } 
     10713#define YY_USER_ACTION       { if (increment_nbtokens !=0) token_since_endofstmt++; increment_nbtokens = 1; if (token_since_endofstmt>=1) lastwasendofstmt=0; /*printf("VALLIJSDFLSD = %d %d %s \n",lastwasendofstmt,token_since_endofstmt,fortran_text); */ if (firstpass) { strcpy(linebuf1, linebuf2); strncpy(linebuf2, fortran_text,80);} \ 
     10714                               else {my_position_before=setposcur();/*printf("muposition = %d\n",my_position_before);*/ECHO;} } 
     10715#define YY_BREAK {/*printf("VALL = %d %d\n",lastwasendofstmt,token_since_endofstmt);*/if (token_since_endofstmt>=1) lastwasendofstmt=0; break;} 
    823210716 
    823310717void out_of_donottreat(void); 
    823410718 
    8235 #line 1826 "fortran.yy.c" 
     10719#line 3426 "fortran.yy.c" 
    823610720 
    823710721#define INITIAL 0 
     
    823910723#define character 2 
    824010724#define donottreat 3 
    8241 #define fortran77style 4 
    8242 #define fortran90style 5 
     10725#define includestate 4 
     10726#define fortran77style 5 
     10727#define fortran90style 6 
    824310728 
    824410729#ifndef YY_NO_UNISTD_H 
     
    842310908   register int yy_act; 
    842410909     
    8425 #line 97 "fortran.lex" 
     10910#line 100 "fortran.lex" 
    842610911 
    842710912  if (infixed) BEGIN(fortran77style) ; 
    842810913  if (infree)  BEGIN(fortran90style) ; 
    842910914 
    8430 #line 2021 "fortran.yy.c" 
     10915#line 3622 "fortran.yy.c" 
    843110916 
    843210917   if ( !(yy_init) ) 
     
    843710922      YY_USER_INIT; 
    843810923#endif 
     10924 
     10925        /* Create the reject buffer large enough to save one state per allowed character. */ 
     10926        if ( ! (yy_state_buf) ) 
     10927            (yy_state_buf) = (yy_state_type *)fortran_alloc(YY_STATE_BUF_SIZE  ); 
     10928            if ( ! (yy_state_buf) ) 
     10929                YY_FATAL_ERROR( "out of dynamic memory in fortran_lex()" ); 
    843910930 
    844010931      if ( ! (yy_start) ) 
     
    847010961      yy_current_state = (yy_start); 
    847110962      yy_current_state += YY_AT_BOL(); 
     10963 
     10964      (yy_state_ptr) = (yy_state_buf); 
     10965      *(yy_state_ptr)++ = yy_current_state; 
     10966 
    847210967yy_match: 
    847310968      do 
    847410969         { 
    847510970         register YY_CHAR yy_c = yy_ec[YY_SC_TO_UI(*yy_cp)]; 
    8476          if ( yy_accept[yy_current_state] ) 
    8477             { 
    8478             (yy_last_accepting_state) = yy_current_state; 
    8479             (yy_last_accepting_cpos) = yy_cp; 
    8480             } 
    848110971         while ( yy_chk[yy_base[yy_current_state] + yy_c] != yy_current_state ) 
    848210972            { 
    848310973            yy_current_state = (int) yy_def[yy_current_state]; 
    8484             if ( yy_current_state >= 1132 ) 
     10974            if ( yy_current_state >= 1849 ) 
    848510975               yy_c = yy_meta[(unsigned int) yy_c]; 
    848610976            } 
    848710977         yy_current_state = yy_nxt[yy_base[yy_current_state] + (unsigned int) yy_c]; 
     10978         *(yy_state_ptr)++ = yy_current_state; 
    848810979         ++yy_cp; 
    848910980         } 
    8490       while ( yy_base[yy_current_state] != 4012 ); 
     10981      while ( yy_base[yy_current_state] != 9211 ); 
    849110982 
    849210983yy_find_action: 
    8493       yy_act = yy_accept[yy_current_state]; 
    8494       if ( yy_act == 0 ) 
    8495          { /* have to back up */ 
    8496          yy_cp = (yy_last_accepting_cpos); 
    8497          yy_current_state = (yy_last_accepting_state); 
    8498          yy_act = yy_accept[yy_current_state]; 
     10984      yy_current_state = *--(yy_state_ptr); 
     10985      (yy_lp) = yy_accept[yy_current_state]; 
     10986goto find_rule; /* Shut up GCC warning -Wall */ 
     10987find_rule: /* we branch to this label when backing up */ 
     10988      for ( ; ; ) /* until we find what rule we matched */ 
     10989         { 
     10990         if ( (yy_lp) && (yy_lp) < yy_accept[yy_current_state + 1] ) 
     10991            { 
     10992            yy_act = yy_acclist[(yy_lp)]; 
     10993            if ( yy_act & YY_TRAILING_HEAD_MASK || 
     10994                 (yy_looking_for_trail_begin) ) 
     10995               { 
     10996               if ( yy_act == (yy_looking_for_trail_begin) ) 
     10997                  { 
     10998                  (yy_looking_for_trail_begin) = 0; 
     10999                  yy_act &= ~YY_TRAILING_HEAD_MASK; 
     11000                  break; 
     11001                  } 
     11002               } 
     11003            else if ( yy_act & YY_TRAILING_MASK ) 
     11004               { 
     11005               (yy_looking_for_trail_begin) = yy_act & ~YY_TRAILING_MASK; 
     11006               (yy_looking_for_trail_begin) |= YY_TRAILING_HEAD_MASK; 
     11007               } 
     11008            else 
     11009               { 
     11010               (yy_full_match) = yy_cp; 
     11011               (yy_full_state) = (yy_state_ptr); 
     11012               (yy_full_lp) = (yy_lp); 
     11013               break; 
     11014               } 
     11015            ++(yy_lp); 
     11016            goto find_rule; 
     11017            } 
     11018         --yy_cp; 
     11019         yy_current_state = *--(yy_state_ptr); 
     11020         (yy_lp) = yy_accept[yy_current_state]; 
    849911021         } 
    850011022 
     
    850511027      switch ( yy_act ) 
    850611028   { /* beginning of action switch */ 
    8507          case 0: /* must back up */ 
    8508          /* undo the effects of YY_DO_BEFORE_ACTION */ 
    8509          *yy_cp = (yy_hold_char); 
    8510          yy_cp = (yy_last_accepting_cpos); 
    8511          yy_current_state = (yy_last_accepting_state); 
    8512          goto yy_find_action; 
    8513  
    851411029case 1: 
    851511030YY_RULE_SETUP 
    8516 #line 101 "fortran.lex" 
    8517 { return TOK_REAL8; } 
     11031#line 104 "fortran.lex" 
     11032{ return TOK_SUBROUTINE; } 
    851811033   YY_BREAK 
    851911034case 2: 
    852011035YY_RULE_SETUP 
    8521 #line 102 "fortran.lex" 
    8522 { return TOK_SUBROUTINE; } 
     11036#line 105 "fortran.lex" 
     11037{ return TOK_PROGRAM; } 
    852311038   YY_BREAK 
    852411039case 3: 
    852511040YY_RULE_SETUP 
    8526 #line 103 "fortran.lex" 
    8527 { return TOK_PROGRAM; } 
     11041#line 106 "fortran.lex" 
     11042{ inallocate = 1; return TOK_ALLOCATE; } 
    852811043   YY_BREAK 
    852911044case 4: 
    853011045YY_RULE_SETUP 
    8531 #line 104 "fortran.lex" 
    8532 { inallocate = 1; return TOK_ALLOCATE; } 
     11046#line 107 "fortran.lex" 
     11047{ return TOK_CONTINUE; } 
    853311048   YY_BREAK 
    853411049case 5: 
    853511050YY_RULE_SETUP 
    8536 #line 105 "fortran.lex" 
     11051#line 108 "fortran.lex" 
    853711052{ return TOK_NULLIFY; } 
    853811053   YY_BREAK 
    853911054case 6: 
    854011055YY_RULE_SETUP 
    8541 #line 106 "fortran.lex" 
    8542 { return TOK_NULL_PTR; } 
     11056#line 109 "fortran.lex" 
     11057{ inallocate = 1; return TOK_DEALLOCATE; } 
    854311058   YY_BREAK 
    854411059case 7: 
    854511060YY_RULE_SETUP 
    8546 #line 107 "fortran.lex" 
    8547 { inallocate = 1; return TOK_DEALLOCATE; } 
     11061#line 110 "fortran.lex" 
     11062{ return TOK_RESULT; } 
    854811063   YY_BREAK 
    854911064case 8: 
    855011065YY_RULE_SETUP 
    8551 #line 108 "fortran.lex" 
    8552 { return TOK_RESULT; } 
     11066#line 111 "fortran.lex" 
     11067{ return TOK_FUNCTION; } 
    855311068   YY_BREAK 
    855411069case 9: 
    855511070YY_RULE_SETUP 
    8556 #line 109 "fortran.lex" 
    8557 { return TOK_FUNCTION; } 
     11071#line 112 "fortran.lex" 
     11072{ strcpy(yylval.na,fortran_text); return TOK_ENDUNIT;} 
    855811073   YY_BREAK 
    855911074case 10: 
    856011075YY_RULE_SETUP 
    8561 #line 110 "fortran.lex" 
    8562 { strcpy(yylval.na,fortran_text); return TOK_ENDPROGRAM;} 
     11076#line 113 "fortran.lex" 
     11077{ pos_curinclude = setposcur()-9; BEGIN(includestate); } 
    856311078   YY_BREAK 
    856411079case 11: 
    856511080YY_RULE_SETUP 
    8566 #line 111 "fortran.lex" 
    8567 { strcpy(yylval.na,fortran_text); return TOK_ENDMODULE; } 
     11081#line 114 "fortran.lex" 
     11082{ return TOK_USE;} 
    856811083   YY_BREAK 
    856911084case 12: 
    857011085YY_RULE_SETUP 
    8571 #line 112 "fortran.lex" 
    8572 { strcpy(yylval.na,fortran_text); return TOK_ENDSUBROUTINE;} 
     11086#line 115 "fortran.lex" 
     11087{ return TOK_REWIND; } 
    857311088   YY_BREAK 
    857411089case 13: 
    857511090YY_RULE_SETUP 
    8576 #line 113 "fortran.lex" 
    8577 { strcpy(yylval.na,fortran_text); return TOK_ENDFUNCTION;} 
     11091#line 116 "fortran.lex" 
     11092{ return TOK_IMPLICIT; } 
    857811093   YY_BREAK 
    857911094case 14: 
    858011095YY_RULE_SETUP 
    8581 #line 114 "fortran.lex" 
    8582 { strcpy(yylval.na,fortran_text); return TOK_ENDUNIT;} 
     11096#line 117 "fortran.lex" 
     11097{ return TOK_NONE; } 
    858311098   YY_BREAK 
    858411099case 15: 
    858511100YY_RULE_SETUP 
    8586 #line 115 "fortran.lex" 
    8587 { pos_curinclude = setposcur()-9; return TOK_INCLUDE;} 
     11101#line 118 "fortran.lex" 
     11102{ return TOK_CALL; } 
    858811103   YY_BREAK 
    858911104case 16: 
    859011105YY_RULE_SETUP 
    8591 #line 116 "fortran.lex" 
    8592 { strcpy(yylval.na,fortran_text); 
    8593                               tmpc = (char) input(); unput(tmpc); 
    8594                               if ( ( tmpc >= 'a' && tmpc <= 'z' ) || 
    8595                                    ( tmpc >= 'A' && tmpc <= 'Z' )  )  return TOK_USE; 
    8596                               else                                    return TOK_NAME; 
     11106#line 119 "fortran.lex" 
     11107{ strcpy(yylval.na,fortran_text); return TOK_TRUE; } 
     11108   YY_BREAK 
     11109case 17: 
     11110YY_RULE_SETUP 
     11111#line 120 "fortran.lex" 
     11112{ strcpy(yylval.na,fortran_text); return TOK_FALSE; } 
     11113   YY_BREAK 
     11114case 18: 
     11115YY_RULE_SETUP 
     11116#line 121 "fortran.lex" 
     11117{ return TOK_POINT_TO; } 
     11118   YY_BREAK 
     11119case 19: 
     11120YY_RULE_SETUP 
     11121#line 122 "fortran.lex" 
     11122{ strcpy(yylval.na,fortran_text); return TOK_ASSIGNTYPE;} 
     11123   YY_BREAK 
     11124case 20: 
     11125YY_RULE_SETUP 
     11126#line 123 "fortran.lex" 
     11127{ strcpy(yylval.na,fortran_text); return TOK_DASTER; } 
     11128   YY_BREAK 
     11129case 21: 
     11130YY_RULE_SETUP 
     11131#line 124 "fortran.lex" 
     11132{ strcpy(yylval.na,fortran_text); return TOK_EQV; } 
     11133   YY_BREAK 
     11134case 22: 
     11135YY_RULE_SETUP 
     11136#line 125 "fortran.lex" 
     11137{ strcpy(yylval.na,fortran_text); return TOK_EQ;  } 
     11138   YY_BREAK 
     11139case 23: 
     11140YY_RULE_SETUP 
     11141#line 126 "fortran.lex" 
     11142{ strcpy(yylval.na,fortran_text); return TOK_GT;  } 
     11143   YY_BREAK 
     11144case 24: 
     11145YY_RULE_SETUP 
     11146#line 127 "fortran.lex" 
     11147{ strcpy(yylval.na,fortran_text); return TOK_GE;  } 
     11148   YY_BREAK 
     11149case 25: 
     11150YY_RULE_SETUP 
     11151#line 128 "fortran.lex" 
     11152{ strcpy(yylval.na,fortran_text); return TOK_LT;  } 
     11153   YY_BREAK 
     11154case 26: 
     11155YY_RULE_SETUP 
     11156#line 129 "fortran.lex" 
     11157{ strcpy(yylval.na,fortran_text); return TOK_LE;  } 
     11158   YY_BREAK 
     11159case 27: 
     11160YY_RULE_SETUP 
     11161#line 130 "fortran.lex" 
     11162{ strcpy(yylval.na,fortran_text); return TOK_NEQV;} 
     11163   YY_BREAK 
     11164case 28: 
     11165YY_RULE_SETUP 
     11166#line 131 "fortran.lex" 
     11167{ strcpy(yylval.na,fortran_text); return TOK_NE;  } 
     11168   YY_BREAK 
     11169case 29: 
     11170YY_RULE_SETUP 
     11171#line 132 "fortran.lex" 
     11172{ strcpy(yylval.na,fortran_text); return TOK_NOT; } 
     11173   YY_BREAK 
     11174case 30: 
     11175YY_RULE_SETUP 
     11176#line 133 "fortran.lex" 
     11177{ strcpy(yylval.na,fortran_text); return TOK_OR;  } 
     11178   YY_BREAK 
     11179case 31: 
     11180YY_RULE_SETUP 
     11181#line 134 "fortran.lex" 
     11182{ strcpy(yylval.na,fortran_text); return TOK_XOR; } 
     11183   YY_BREAK 
     11184case 32: 
     11185YY_RULE_SETUP 
     11186#line 135 "fortran.lex" 
     11187{ strcpy(yylval.na,fortran_text); return TOK_AND; } 
     11188   YY_BREAK 
     11189case 33: 
     11190YY_RULE_SETUP 
     11191#line 136 "fortran.lex" 
     11192{ strcpy(yylval.na,fortran_text); return TOK_EQUALEQUAL; } 
     11193   YY_BREAK 
     11194case 34: 
     11195YY_RULE_SETUP 
     11196#line 137 "fortran.lex" 
     11197{ strcpy(yylval.na,fortran_text); return TOK_SLASHEQUAL; } 
     11198   YY_BREAK 
     11199case 35: 
     11200YY_RULE_SETUP 
     11201#line 138 "fortran.lex" 
     11202{ strcpy(yylval.na,fortran_text); return TOK_INFEQUAL; } 
     11203   YY_BREAK 
     11204case 36: 
     11205YY_RULE_SETUP 
     11206#line 139 "fortran.lex" 
     11207{ strcpy(yylval.na,fortran_text); return TOK_SUPEQUAL; } 
     11208   YY_BREAK 
     11209case 37: 
     11210YY_RULE_SETUP 
     11211#line 140 "fortran.lex" 
     11212{ return TOK_MODULE; } 
     11213   YY_BREAK 
     11214case 38: 
     11215YY_RULE_SETUP 
     11216#line 141 "fortran.lex" 
     11217{ return TOK_WHILE; } 
     11218   YY_BREAK 
     11219case 39: 
     11220YY_RULE_SETUP 
     11221#line 142 "fortran.lex" 
     11222{ return TOK_CONCURRENT; } 
     11223   YY_BREAK 
     11224case 40: 
     11225YY_RULE_SETUP 
     11226#line 143 "fortran.lex" 
     11227{ return TOK_ENDDO; } 
     11228   YY_BREAK 
     11229case 41: 
     11230YY_RULE_SETUP 
     11231#line 144 "fortran.lex" 
     11232{ strcpy(yylval.na,&fortran_text[2]); 
     11233                              if (testandextractfromlist(&List_Do_labels,&fortran_text[2]) == 1) 
     11234                              { 
     11235                              return TOK_PLAINDO_LABEL_DJVIEW; 
     11236                              } 
     11237                              else 
     11238                              { 
     11239                              List_Do_labels=Insertname(List_Do_labels,yylval.na,1); 
     11240                              return TOK_PLAINDO_LABEL; 
     11241                             } 
     11242                             } 
     11243   YY_BREAK 
     11244case 42: 
     11245YY_RULE_SETUP 
     11246#line 155 "fortran.lex" 
     11247{ increment_nbtokens = 0; return TOK_PLAINDO;} 
     11248   YY_BREAK 
     11249case 43: 
     11250YY_RULE_SETUP 
     11251#line 156 "fortran.lex" 
     11252{ strcpy(yylval.na,fortran_text); return TOK_REAL; } 
     11253   YY_BREAK 
     11254case 44: 
     11255YY_RULE_SETUP 
     11256#line 157 "fortran.lex" 
     11257{ strcpy(yylval.na,fortran_text); return TOK_INTEGER; } 
     11258   YY_BREAK 
     11259case 45: 
     11260YY_RULE_SETUP 
     11261#line 158 "fortran.lex" 
     11262{ strcpy(yylval.na,fortran_text); return TOK_LOGICAL; } 
     11263   YY_BREAK 
     11264case 46: 
     11265YY_RULE_SETUP 
     11266#line 159 "fortran.lex" 
     11267{ strcpy(yylval.na,fortran_text); return TOK_CHARACTER; } 
     11268   YY_BREAK 
     11269case 47: 
     11270YY_RULE_SETUP 
     11271#line 160 "fortran.lex" 
     11272{ strcpy(yylval.na,fortran_text); return TOK_HEXA;} 
     11273   YY_BREAK 
     11274case 48: 
     11275YY_RULE_SETUP 
     11276#line 161 "fortran.lex" 
     11277{ strcpy(yylval.na,fortran_text); return TOK_DOUBLEPRECISION; } 
     11278   YY_BREAK 
     11279case 49: 
     11280YY_RULE_SETUP 
     11281#line 162 "fortran.lex" 
     11282{ strcpy(yylval.na,fortran_text); return TOK_DOUBLECOMPLEX; } 
     11283   YY_BREAK 
     11284case 50: 
     11285YY_RULE_SETUP 
     11286#line 163 "fortran.lex" 
     11287{ strcpy(yylval.na,fortran_text); return TOK_COMPLEX; } 
     11288   YY_BREAK 
     11289case 51: 
     11290YY_RULE_SETUP 
     11291#line 164 "fortran.lex" 
     11292{ return TOK_ALLOCATABLE; } 
     11293   YY_BREAK 
     11294case 52: 
     11295YY_RULE_SETUP 
     11296#line 165 "fortran.lex" 
     11297{ return TOK_CLOSE; } 
     11298   YY_BREAK 
     11299case 53: 
     11300YY_RULE_SETUP 
     11301#line 166 "fortran.lex" 
     11302{ return TOK_INQUIRE; } 
     11303   YY_BREAK 
     11304case 54: 
     11305YY_RULE_SETUP 
     11306#line 167 "fortran.lex" 
     11307{ return TOK_DIMENSION; } 
     11308   YY_BREAK 
     11309case 55: 
     11310YY_RULE_SETUP 
     11311#line 168 "fortran.lex" 
     11312{ return TOK_PAUSE; } 
     11313   YY_BREAK 
     11314case 56: 
     11315YY_RULE_SETUP 
     11316#line 169 "fortran.lex" 
     11317{ return TOK_EQUIVALENCE; } 
     11318   YY_BREAK 
     11319case 57: 
     11320YY_RULE_SETUP 
     11321#line 170 "fortran.lex" 
     11322{ return TOK_STOP; } 
     11323   YY_BREAK 
     11324case 58: 
     11325YY_RULE_SETUP 
     11326#line 171 "fortran.lex" 
     11327{ return TOK_WHERE; } 
     11328   YY_BREAK 
     11329case 59: 
     11330YY_RULE_SETUP 
     11331#line 172 "fortran.lex" 
     11332{ return TOK_ENDWHERE; } 
     11333   YY_BREAK 
     11334case 60: 
     11335YY_RULE_SETUP 
     11336#line 173 "fortran.lex" 
     11337{ return TOK_ELSEWHEREPAR; } 
     11338   YY_BREAK 
     11339case 61: 
     11340YY_RULE_SETUP 
     11341#line 174 "fortran.lex" 
     11342{ return TOK_ELSEWHERE; } 
     11343   YY_BREAK 
     11344case 62: 
     11345YY_RULE_SETUP 
     11346#line 175 "fortran.lex" 
     11347{ return TOK_CONTAINS; } 
     11348   YY_BREAK 
     11349case 63: 
     11350YY_RULE_SETUP 
     11351#line 176 "fortran.lex" 
     11352{ return TOK_ONLY; } 
     11353   YY_BREAK 
     11354case 64: 
     11355YY_RULE_SETUP 
     11356#line 177 "fortran.lex" 
     11357{ return TOK_PARAMETER; } 
     11358   YY_BREAK 
     11359case 65: 
     11360YY_RULE_SETUP 
     11361#line 178 "fortran.lex" 
     11362{ return TOK_RECURSIVE; } 
     11363   YY_BREAK 
     11364case 66: 
     11365YY_RULE_SETUP 
     11366#line 179 "fortran.lex" 
     11367{ return TOK_COMMON; } 
     11368   YY_BREAK 
     11369case 67: 
     11370YY_RULE_SETUP 
     11371#line 180 "fortran.lex" 
     11372{ return TOK_GLOBAL; } 
     11373   YY_BREAK 
     11374case 68: 
     11375YY_RULE_SETUP 
     11376#line 181 "fortran.lex" 
     11377{ return TOK_EXTERNAL; } 
     11378   YY_BREAK 
     11379case 69: 
     11380YY_RULE_SETUP 
     11381#line 182 "fortran.lex" 
     11382{ return TOK_INTENT; } 
     11383   YY_BREAK 
     11384case 70: 
     11385YY_RULE_SETUP 
     11386#line 183 "fortran.lex" 
     11387{ return TOK_POINTER; } 
     11388   YY_BREAK 
     11389case 71: 
     11390YY_RULE_SETUP 
     11391#line 184 "fortran.lex" 
     11392{ return TOK_OPTIONAL; } 
     11393   YY_BREAK 
     11394case 72: 
     11395YY_RULE_SETUP 
     11396#line 185 "fortran.lex" 
     11397{ return TOK_SAVE; } 
     11398   YY_BREAK 
     11399case 73: 
     11400YY_RULE_SETUP 
     11401#line 186 "fortran.lex" 
     11402{ pos_cur_decl = setposcur()-5; return TOK_TYPEPAR; } 
     11403   YY_BREAK 
     11404case 74: 
     11405YY_RULE_SETUP 
     11406#line 187 "fortran.lex" 
     11407{ return TOK_TYPE; } 
     11408   YY_BREAK 
     11409case 75: 
     11410YY_RULE_SETUP 
     11411#line 188 "fortran.lex" 
     11412{ return TOK_ENDTYPE; } 
     11413   YY_BREAK 
     11414case 76: 
     11415YY_RULE_SETUP 
     11416#line 189 "fortran.lex" 
     11417{ if (inallocate == 1) return TOK_STAT; else { strcpy(yylval.na,fortran_text); return TOK_NAME; } } 
     11418   YY_BREAK 
     11419case 77: 
     11420YY_RULE_SETUP 
     11421#line 190 "fortran.lex" 
     11422{ return TOK_OPEN; } 
     11423   YY_BREAK 
     11424case 78: 
     11425YY_RULE_SETUP 
     11426#line 191 "fortran.lex" 
     11427{ return TOK_RETURN; } 
     11428   YY_BREAK 
     11429case 79: 
     11430YY_RULE_SETUP 
     11431#line 192 "fortran.lex" 
     11432{ return TOK_EXIT; } 
     11433   YY_BREAK 
     11434case 80: 
     11435YY_RULE_SETUP 
     11436#line 193 "fortran.lex" 
     11437{ return TOK_PRINT; } 
     11438   YY_BREAK 
     11439case 81: 
     11440YY_RULE_SETUP 
     11441#line 194 "fortran.lex" 
     11442{ return TOK_PROCEDURE; } 
     11443   YY_BREAK 
     11444case 82: 
     11445YY_RULE_SETUP 
     11446#line 195 "fortran.lex" 
     11447{ return TOK_READ_PAR; } 
     11448   YY_BREAK 
     11449case 83: 
     11450YY_RULE_SETUP 
     11451#line 196 "fortran.lex" 
     11452{ return TOK_READ; } 
     11453   YY_BREAK 
     11454case 84: 
     11455YY_RULE_SETUP 
     11456#line 197 "fortran.lex" 
     11457{ return TOK_NAMELIST; } 
     11458   YY_BREAK 
     11459case 85: 
     11460YY_RULE_SETUP 
     11461#line 198 "fortran.lex" 
     11462{ return TOK_WRITE_PAR; } 
     11463   YY_BREAK 
     11464case 86: 
     11465YY_RULE_SETUP 
     11466#line 199 "fortran.lex" 
     11467{ return TOK_WRITE; } 
     11468   YY_BREAK 
     11469case 87: 
     11470YY_RULE_SETUP 
     11471#line 200 "fortran.lex" 
     11472{ strcpy(yylval.na,fortran_text); return TOK_FLUSH; } 
     11473   YY_BREAK 
     11474case 88: 
     11475YY_RULE_SETUP 
     11476#line 201 "fortran.lex" 
     11477{ return TOK_TARGET; } 
     11478   YY_BREAK 
     11479case 89: 
     11480YY_RULE_SETUP 
     11481#line 202 "fortran.lex" 
     11482{ return TOK_PUBLIC; } 
     11483   YY_BREAK 
     11484case 90: 
     11485YY_RULE_SETUP 
     11486#line 203 "fortran.lex" 
     11487{ return TOK_PRIVATE; } 
     11488   YY_BREAK 
     11489case 91: 
     11490YY_RULE_SETUP 
     11491#line 204 "fortran.lex" 
     11492{ strcpy(yylval.na,fortran_text); return TOK_IN; } 
     11493   YY_BREAK 
     11494case 92: 
     11495YY_RULE_SETUP 
     11496#line 205 "fortran.lex" 
     11497{ pos_curdata = setposcur()-strlen(fortran_text); /*Init_List_Data_Var();*/ return TOK_DATA; } 
     11498   YY_BREAK 
     11499case 93: 
     11500YY_RULE_SETUP 
     11501#line 206 "fortran.lex" 
     11502{ return TOK_PLAINGOTO; } 
     11503   YY_BREAK 
     11504case 94: 
     11505YY_RULE_SETUP 
     11506#line 207 "fortran.lex" 
     11507{ strcpy(yylval.na,fortran_text); return TOK_OUT; } 
     11508   YY_BREAK 
     11509case 95: 
     11510YY_RULE_SETUP 
     11511#line 208 "fortran.lex" 
     11512{ strcpy(yylval.na,fortran_text); return TOK_INOUT; } 
     11513   YY_BREAK 
     11514case 96: 
     11515YY_RULE_SETUP 
     11516#line 209 "fortran.lex" 
     11517{ return TOK_INTRINSIC; } 
     11518   YY_BREAK 
     11519case 97: 
     11520YY_RULE_SETUP 
     11521#line 210 "fortran.lex" 
     11522{ return TOK_THEN; } 
     11523   YY_BREAK 
     11524case 98: 
     11525YY_RULE_SETUP 
     11526#line 211 "fortran.lex" 
     11527{ return TOK_ELSEIF; } 
     11528   YY_BREAK 
     11529case 99: 
     11530YY_RULE_SETUP 
     11531#line 212 "fortran.lex" 
     11532{ return TOK_ELSE; } 
     11533   YY_BREAK 
     11534case 100: 
     11535YY_RULE_SETUP 
     11536#line 213 "fortran.lex" 
     11537{ return TOK_ENDIF; } 
     11538   YY_BREAK 
     11539case 101: 
     11540YY_RULE_SETUP 
     11541#line 214 "fortran.lex" 
     11542{strcpy(yylval.na,fortran_text); 
     11543                            return TOK_LOGICALIF_PAR; 
    859711544                            } 
    859811545   YY_BREAK 
    8599 case 17: 
    8600 YY_RULE_SETUP 
    8601 #line 122 "fortran.lex" 
    8602 { return TOK_REWIND; } 
    8603    YY_BREAK 
    8604 case 18: 
    8605 YY_RULE_SETUP 
    8606 #line 123 "fortran.lex" 
    8607 { return TOK_IMPLICIT; } 
    8608    YY_BREAK 
    8609 case 19: 
    8610 YY_RULE_SETUP 
    8611 #line 124 "fortran.lex" 
    8612 { return TOK_NONE; } 
    8613    YY_BREAK 
    8614 case 20: 
    8615 YY_RULE_SETUP 
    8616 #line 125 "fortran.lex" 
    8617 { return TOK_CALL; } 
    8618    YY_BREAK 
    8619 case 21: 
    8620 YY_RULE_SETUP 
    8621 #line 126 "fortran.lex" 
    8622 { return TOK_TRUE; } 
    8623    YY_BREAK 
    8624 case 22: 
    8625 YY_RULE_SETUP 
    8626 #line 127 "fortran.lex" 
    8627 { return TOK_FALSE; } 
    8628    YY_BREAK 
    8629 case 23: 
    8630 YY_RULE_SETUP 
    8631 #line 128 "fortran.lex" 
    8632 { return TOK_POINT_TO; } 
    8633    YY_BREAK 
    8634 case 24: 
    8635 YY_RULE_SETUP 
    8636 #line 129 "fortran.lex" 
    8637 { strcpy(yylval.na,fortran_text); return TOK_ASSIGNTYPE;} 
    8638    YY_BREAK 
    8639 case 25: 
    8640 YY_RULE_SETUP 
    8641 #line 130 "fortran.lex" 
    8642 { strcpy(yylval.na,fortran_text); return TOK_DASTER; } 
    8643    YY_BREAK 
    8644 case 26: 
    8645 YY_RULE_SETUP 
    8646 #line 131 "fortran.lex" 
    8647 { strcpy(yylval.na,fortran_text); return TOK_EQV; } 
    8648    YY_BREAK 
    8649 case 27: 
    8650 YY_RULE_SETUP 
    8651 #line 132 "fortran.lex" 
    8652 { strcpy(yylval.na,fortran_text); return TOK_EQ;  } 
    8653    YY_BREAK 
    8654 case 28: 
    8655 YY_RULE_SETUP 
    8656 #line 133 "fortran.lex" 
    8657 { strcpy(yylval.na,fortran_text); return TOK_GT;  } 
    8658    YY_BREAK 
    8659 case 29: 
    8660 YY_RULE_SETUP 
    8661 #line 134 "fortran.lex" 
    8662 { strcpy(yylval.na,fortran_text); return TOK_GE;  } 
    8663    YY_BREAK 
    8664 case 30: 
    8665 YY_RULE_SETUP 
    8666 #line 135 "fortran.lex" 
    8667 { strcpy(yylval.na,fortran_text); return TOK_LT;  } 
    8668    YY_BREAK 
    8669 case 31: 
    8670 YY_RULE_SETUP 
    8671 #line 136 "fortran.lex" 
    8672 { strcpy(yylval.na,fortran_text); return TOK_LE;  } 
    8673    YY_BREAK 
    8674 case 32: 
    8675 YY_RULE_SETUP 
    8676 #line 137 "fortran.lex" 
    8677 { strcpy(yylval.na,fortran_text); return TOK_NEQV;} 
    8678    YY_BREAK 
    8679 case 33: 
    8680 YY_RULE_SETUP 
    8681 #line 138 "fortran.lex" 
    8682 { strcpy(yylval.na,fortran_text); return TOK_NE;  } 
    8683    YY_BREAK 
    8684 case 34: 
    8685 YY_RULE_SETUP 
    8686 #line 139 "fortran.lex" 
    8687 { strcpy(yylval.na,fortran_text); return TOK_NOT; } 
    8688    YY_BREAK 
    8689 case 35: 
    8690 YY_RULE_SETUP 
    8691 #line 140 "fortran.lex" 
    8692 { strcpy(yylval.na,fortran_text); return TOK_OR;  } 
    8693    YY_BREAK 
    8694 case 36: 
    8695 YY_RULE_SETUP 
    8696 #line 141 "fortran.lex" 
    8697 { strcpy(yylval.na,fortran_text); return TOK_XOR; } 
    8698    YY_BREAK 
    8699 case 37: 
    8700 YY_RULE_SETUP 
    8701 #line 142 "fortran.lex" 
    8702 { strcpy(yylval.na,fortran_text); return TOK_AND; } 
    8703    YY_BREAK 
    8704 case 38: 
    8705 YY_RULE_SETUP 
    8706 #line 143 "fortran.lex" 
    8707 { return TOK_MODULE; } 
    8708    YY_BREAK 
    8709 case 39: 
    8710 YY_RULE_SETUP 
    8711 #line 144 "fortran.lex" 
    8712 { return TOK_WHILE; } 
    8713    YY_BREAK 
    8714 case 40: 
    8715 YY_RULE_SETUP 
    8716 #line 145 "fortran.lex" 
    8717 { return TOK_CONCURRENT; } 
    8718    YY_BREAK 
    8719 case 41: 
    8720 YY_RULE_SETUP 
    8721 #line 146 "fortran.lex" 
    8722 { return TOK_ENDDO; } 
    8723    YY_BREAK 
    8724 case 42: 
    8725 YY_RULE_SETUP 
    8726 #line 147 "fortran.lex" 
    8727 { return TOK_PLAINDO;} 
    8728    YY_BREAK 
    8729 case 43: 
    8730 YY_RULE_SETUP 
    8731 #line 148 "fortran.lex" 
    8732 { strcpy(yylval.na,fortran_text); return TOK_REAL; } 
    8733    YY_BREAK 
    8734 case 44: 
    8735 YY_RULE_SETUP 
    8736 #line 149 "fortran.lex" 
    8737 { strcpy(yylval.na,fortran_text); return TOK_INTEGER; } 
    8738    YY_BREAK 
    8739 case 45: 
    8740 YY_RULE_SETUP 
    8741 #line 150 "fortran.lex" 
    8742 { strcpy(yylval.na,fortran_text); return TOK_LOGICAL; } 
    8743    YY_BREAK 
    8744 case 46: 
    8745 YY_RULE_SETUP 
    8746 #line 151 "fortran.lex" 
    8747 { strcpy(yylval.na,fortran_text); return TOK_CHARACTER; } 
    8748    YY_BREAK 
    8749 case 47: 
    8750 YY_RULE_SETUP 
    8751 #line 152 "fortran.lex" 
    8752 { strcpy(yylval.na,fortran_text); return TOK_HEXA;} 
    8753    YY_BREAK 
    8754 case 48: 
    8755 YY_RULE_SETUP 
    8756 #line 153 "fortran.lex" 
    8757 { strcpy(yylval.na,fortran_text); return TOK_DOUBLEPRECISION; } 
    8758    YY_BREAK 
    8759 case 49: 
    8760 YY_RULE_SETUP 
    8761 #line 154 "fortran.lex" 
    8762 { strcpy(yylval.na,fortran_text); return TOK_DOUBLECOMPLEX; } 
    8763    YY_BREAK 
    8764 case 50: 
    8765 YY_RULE_SETUP 
    8766 #line 155 "fortran.lex" 
    8767 { return TOK_COMPLEX; } 
    8768    YY_BREAK 
    8769 case 51: 
    8770 YY_RULE_SETUP 
    8771 #line 156 "fortran.lex" 
    8772 { return TOK_ALLOCATABLE; } 
    8773    YY_BREAK 
    8774 case 52: 
    8775 YY_RULE_SETUP 
    8776 #line 157 "fortran.lex" 
    8777 { return TOK_CLOSE; } 
    8778    YY_BREAK 
    8779 case 53: 
    8780 YY_RULE_SETUP 
    8781 #line 158 "fortran.lex" 
    8782 { return TOK_INQUIRE; } 
    8783    YY_BREAK 
    8784 case 54: 
    8785 YY_RULE_SETUP 
    8786 #line 159 "fortran.lex" 
    8787 { return TOK_DIMENSION; } 
    8788    YY_BREAK 
    8789 case 55: 
    8790 YY_RULE_SETUP 
    8791 #line 160 "fortran.lex" 
    8792 { return TOK_PAUSE; } 
    8793    YY_BREAK 
    8794 case 56: 
    8795 YY_RULE_SETUP 
    8796 #line 161 "fortran.lex" 
    8797 { return TOK_EQUIVALENCE; } 
    8798    YY_BREAK 
    8799 case 57: 
    8800 YY_RULE_SETUP 
    8801 #line 162 "fortran.lex" 
    8802 { return TOK_STOP; } 
    8803    YY_BREAK 
    8804 case 58: 
    8805 YY_RULE_SETUP 
    8806 #line 163 "fortran.lex" 
    8807 { return TOK_WHERE; } 
    8808    YY_BREAK 
    8809 case 59: 
    8810 YY_RULE_SETUP 
    8811 #line 164 "fortran.lex" 
    8812 { return TOK_ENDWHERE; } 
    8813    YY_BREAK 
    8814 case 60: 
    8815 YY_RULE_SETUP 
    8816 #line 165 "fortran.lex" 
    8817 { return TOK_ELSEWHEREPAR; } 
    8818    YY_BREAK 
    8819 case 61: 
    8820 YY_RULE_SETUP 
    8821 #line 166 "fortran.lex" 
    8822 { return TOK_ELSEWHERE; } 
    8823    YY_BREAK 
    8824 case 62: 
    8825 YY_RULE_SETUP 
    8826 #line 167 "fortran.lex" 
    8827 { return TOK_CONTAINS; } 
    8828    YY_BREAK 
    8829 case 63: 
    8830 YY_RULE_SETUP 
    8831 #line 168 "fortran.lex" 
    8832 { return TOK_ONLY; } 
    8833    YY_BREAK 
    8834 case 64: 
    8835 YY_RULE_SETUP 
    8836 #line 169 "fortran.lex" 
    8837 { return TOK_PARAMETER; } 
    8838    YY_BREAK 
    8839 case 65: 
    8840 YY_RULE_SETUP 
    8841 #line 170 "fortran.lex" 
    8842 { return TOK_RECURSIVE; } 
    8843    YY_BREAK 
    8844 case 66: 
    8845 YY_RULE_SETUP 
    8846 #line 171 "fortran.lex" 
    8847 { return TOK_COMMON; } 
    8848    YY_BREAK 
    8849 case 67: 
    8850 YY_RULE_SETUP 
    8851 #line 172 "fortran.lex" 
    8852 { return TOK_GLOBAL; } 
    8853    YY_BREAK 
    8854 case 68: 
    8855 YY_RULE_SETUP 
    8856 #line 173 "fortran.lex" 
    8857 { return TOK_EXTERNAL; } 
    8858    YY_BREAK 
    8859 case 69: 
    8860 YY_RULE_SETUP 
    8861 #line 174 "fortran.lex" 
    8862 { return TOK_INTENT; } 
    8863    YY_BREAK 
    8864 case 70: 
    8865 YY_RULE_SETUP 
    8866 #line 175 "fortran.lex" 
    8867 { return TOK_POINTER; } 
    8868    YY_BREAK 
    8869 case 71: 
    8870 YY_RULE_SETUP 
    8871 #line 176 "fortran.lex" 
    8872 { return TOK_OPTIONAL; } 
    8873    YY_BREAK 
    8874 case 72: 
    8875 YY_RULE_SETUP 
    8876 #line 177 "fortran.lex" 
    8877 { return TOK_SAVE; } 
    8878    YY_BREAK 
    8879 case 73: 
    8880 YY_RULE_SETUP 
    8881 #line 178 "fortran.lex" 
    8882 { pos_cur_decl = setposcur()-5; return TOK_TYPEPAR; } 
    8883    YY_BREAK 
    8884 case 74: 
    8885 YY_RULE_SETUP 
    8886 #line 179 "fortran.lex" 
    8887 { return TOK_TYPE; } 
    8888    YY_BREAK 
    8889 case 75: 
    8890 YY_RULE_SETUP 
    8891 #line 180 "fortran.lex" 
    8892 { return TOK_ENDTYPE; } 
    8893    YY_BREAK 
    8894 case 76: 
    8895 YY_RULE_SETUP 
    8896 #line 181 "fortran.lex" 
    8897 { if (inallocate == 1) return TOK_STAT; else { strcpy(yylval.na,fortran_text); return TOK_NAME; } } 
    8898    YY_BREAK 
    8899 case 77: 
    8900 YY_RULE_SETUP 
    8901 #line 182 "fortran.lex" 
    8902 { return TOK_OPEN; } 
    8903    YY_BREAK 
    8904 case 78: 
    8905 YY_RULE_SETUP 
    8906 #line 183 "fortran.lex" 
    8907 { return TOK_RETURN; } 
    8908    YY_BREAK 
    8909 case 79: 
    8910 /* rule 79 can match eol */ 
    8911 YY_RULE_SETUP 
    8912 #line 184 "fortran.lex" 
    8913 { return TOK_EXIT; } 
    8914    YY_BREAK 
    8915 case 80: 
    8916 YY_RULE_SETUP 
    8917 #line 185 "fortran.lex" 
    8918 { return TOK_PRINT; } 
    8919    YY_BREAK 
    8920 case 81: 
    8921 YY_RULE_SETUP 
    8922 #line 186 "fortran.lex" 
    8923 { return TOK_PROCEDURE; } 
    8924    YY_BREAK 
    8925 case 82: 
    8926 YY_RULE_SETUP 
    8927 #line 187 "fortran.lex" 
    8928 { return TOK_READ; } 
    8929    YY_BREAK 
    8930 case 83: 
    8931 YY_RULE_SETUP 
    8932 #line 188 "fortran.lex" 
    8933 { return TOK_NAMELIST; } 
    8934    YY_BREAK 
    8935 case 84: 
    8936 YY_RULE_SETUP 
    8937 #line 189 "fortran.lex" 
    8938 { return TOK_WRITE; } 
    8939    YY_BREAK 
    8940 case 85: 
    8941 YY_RULE_SETUP 
    8942 #line 190 "fortran.lex" 
    8943 { return TOK_FLUSH; } 
    8944    YY_BREAK 
    8945 case 86: 
    8946 YY_RULE_SETUP 
    8947 #line 191 "fortran.lex" 
    8948 { return TOK_TARGET; } 
    8949    YY_BREAK 
    8950 case 87: 
    8951 YY_RULE_SETUP 
    8952 #line 192 "fortran.lex" 
    8953 { return TOK_PUBLIC; } 
    8954    YY_BREAK 
    8955 case 88: 
    8956 YY_RULE_SETUP 
    8957 #line 193 "fortran.lex" 
    8958 { return TOK_PRIVATE; } 
    8959    YY_BREAK 
    8960 case 89: 
    8961 YY_RULE_SETUP 
    8962 #line 194 "fortran.lex" 
    8963 { strcpy(yylval.na,fortran_text); return TOK_IN; } 
    8964    YY_BREAK 
    8965 case 90: 
    8966 YY_RULE_SETUP 
    8967 #line 195 "fortran.lex" 
    8968 { pos_curdata = setposcur()-strlen(fortran_text); Init_List_Data_Var(); return TOK_DATA; } 
    8969    YY_BREAK 
    8970 case 91: 
    8971 YY_RULE_SETUP 
    8972 #line 196 "fortran.lex" 
    8973 { return TOK_CONTINUE; } 
    8974    YY_BREAK 
    8975 case 92: 
    8976 YY_RULE_SETUP 
    8977 #line 197 "fortran.lex" 
    8978 { return TOK_PLAINGOTO; } 
    8979    YY_BREAK 
    8980 case 93: 
    8981 YY_RULE_SETUP 
    8982 #line 198 "fortran.lex" 
    8983 { strcpy(yylval.na,fortran_text); return TOK_OUT; } 
    8984    YY_BREAK 
    8985 case 94: 
    8986 YY_RULE_SETUP 
    8987 #line 199 "fortran.lex" 
    8988 { strcpy(yylval.na,fortran_text); return TOK_INOUT; } 
    8989    YY_BREAK 
    8990 case 95: 
    8991 YY_RULE_SETUP 
    8992 #line 200 "fortran.lex" 
    8993 { return TOK_INTRINSIC; } 
    8994    YY_BREAK 
    8995 case 96: 
    8996 YY_RULE_SETUP 
    8997 #line 201 "fortran.lex" 
    8998 { return TOK_THEN; } 
    8999    YY_BREAK 
    9000 case 97: 
    9001 YY_RULE_SETUP 
    9002 #line 202 "fortran.lex" 
    9003 { return TOK_ELSEIF; } 
    9004    YY_BREAK 
    9005 case 98: 
    9006 YY_RULE_SETUP 
    9007 #line 203 "fortran.lex" 
    9008 { return TOK_ELSE; } 
    9009    YY_BREAK 
    9010 case 99: 
    9011 YY_RULE_SETUP 
    9012 #line 204 "fortran.lex" 
    9013 { return TOK_ENDIF; } 
    9014    YY_BREAK 
    9015 case 100: 
    9016 YY_RULE_SETUP 
    9017 #line 205 "fortran.lex" 
    9018 { return TOK_LOGICALIF; } 
    9019    YY_BREAK 
    9020 case 101: 
    9021 YY_RULE_SETUP 
    9022 #line 206 "fortran.lex" 
    9023 { return TOK_SUM; } 
    9024    YY_BREAK 
    902511546case 102: 
    9026 YY_RULE_SETUP 
    9027 #line 207 "fortran.lex" 
    9028 { return TOK_MAX; } 
     11547/* rule 102 can match eol */ 
     11548*yy_cp = (yy_hold_char); /* undo effects of setting up fortran_text */ 
     11549(yy_c_buf_p) = yy_cp = yy_bp + 2; 
     11550YY_DO_BEFORE_ACTION; /* set up fortran_text again */ 
     11551YY_RULE_SETUP 
     11552#line 217 "fortran.lex" 
     11553{strcpy(yylval.na,fortran_text); 
     11554                            return TOK_NAME; 
     11555                            } 
    902911556   YY_BREAK 
    903011557case 103: 
    903111558YY_RULE_SETUP 
    9032 #line 208 "fortran.lex" 
    9033 { return TOK_TANH; } 
     11559#line 220 "fortran.lex" 
     11560{strcpy(yylval.na,fortran_text); 
     11561                            return TOK_LOGICALIF_PAR; 
     11562                            } 
    903411563   YY_BREAK 
    903511564case 104: 
    903611565YY_RULE_SETUP 
    9037 #line 209 "fortran.lex" 
    9038 { return TOK_MAXVAL; } 
     11566#line 223 "fortran.lex" 
     11567{ return TOK_SELECTCASE; } 
    903911568   YY_BREAK 
    904011569case 105: 
    904111570YY_RULE_SETUP 
    9042 #line 210 "fortran.lex" 
    9043 { return TOK_TRIM; } 
     11571#line 224 "fortran.lex" 
     11572{ if (in_select_case_stmt > 0) return TOK_CASE ; else return TOK_NAME;} 
    904411573   YY_BREAK 
    904511574case 106: 
    904611575YY_RULE_SETUP 
    9047 #line 211 "fortran.lex" 
    9048 { return TOK_SQRT; } 
     11576#line 225 "fortran.lex" 
     11577{ return TOK_DEFAULT; } 
    904911578   YY_BREAK 
    905011579case 107: 
    905111580YY_RULE_SETUP 
    9052 #line 212 "fortran.lex" 
    9053 { return TOK_SELECTCASE; } 
     11581#line 226 "fortran.lex" 
     11582{ return TOK_ENDSELECT; } 
    905411583   YY_BREAK 
    905511584case 108: 
    905611585YY_RULE_SETUP 
    9057 #line 213 "fortran.lex" 
    9058 { return TOK_CASE; } 
     11586#line 227 "fortran.lex" 
     11587{ return TOK_FILE; } 
    905911588   YY_BREAK 
    906011589case 109: 
    906111590YY_RULE_SETUP 
    9062 #line 214 "fortran.lex" 
    9063 { return TOK_DEFAULT; } 
     11591#line 228 "fortran.lex" 
     11592{ return TOK_ACCESS; } 
    906411593   YY_BREAK 
    906511594case 110: 
    906611595YY_RULE_SETUP 
    9067 #line 215 "fortran.lex" 
    9068 { return TOK_ENDSELECT; } 
     11596#line 229 "fortran.lex" 
     11597{ return TOK_ACTION; } 
    906911598   YY_BREAK 
    907011599case 111: 
    907111600YY_RULE_SETUP 
    9072 #line 216 "fortran.lex" 
    9073 { return TOK_FILE; } 
     11601#line 230 "fortran.lex" 
     11602{ return TOK_IOLENGTH; } 
    907411603   YY_BREAK 
    907511604case 112: 
    907611605YY_RULE_SETUP 
    9077 #line 217 "fortran.lex" 
     11606#line 231 "fortran.lex" 
    907811607{ return TOK_UNIT; } 
    907911608   YY_BREAK 
    908011609case 113: 
    908111610YY_RULE_SETUP 
    9082 #line 218 "fortran.lex" 
     11611#line 232 "fortran.lex" 
     11612{ return TOK_OPENED; } 
     11613   YY_BREAK 
     11614case 114: 
     11615YY_RULE_SETUP 
     11616#line 233 "fortran.lex" 
    908311617{ return TOK_FMT; } 
    908411618   YY_BREAK 
    9085 case 114: 
    9086 YY_RULE_SETUP 
    9087 #line 219 "fortran.lex" 
     11619case 115: 
     11620YY_RULE_SETUP 
     11621#line 234 "fortran.lex" 
    908811622{ return TOK_NML; } 
    908911623   YY_BREAK 
    9090 case 115: 
    9091 YY_RULE_SETUP 
    9092 #line 220 "fortran.lex" 
     11624case 116: 
     11625YY_RULE_SETUP 
     11626#line 235 "fortran.lex" 
    909311627{ return TOK_END; } 
    909411628   YY_BREAK 
    9095 case 116: 
    9096 YY_RULE_SETUP 
    9097 #line 221 "fortran.lex" 
     11629case 117: 
     11630YY_RULE_SETUP 
     11631#line 236 "fortran.lex" 
    909811632{ return TOK_EOR; } 
    909911633   YY_BREAK 
    9100 case 117: 
    9101 YY_RULE_SETUP 
    9102 #line 222 "fortran.lex" 
     11634case 118: 
     11635*yy_cp = (yy_hold_char); /* undo effects of setting up fortran_text */ 
     11636(yy_c_buf_p) = yy_cp = yy_bp + 3; 
     11637YY_DO_BEFORE_ACTION; /* set up fortran_text again */ 
     11638YY_RULE_SETUP 
     11639#line 237 "fortran.lex" 
     11640{ 
     11641                            if (in_char_selector ==1) 
     11642                               return TOK_LEN; 
     11643                            else 
     11644                            { 
     11645                            strcpy(yylval.na,fortran_text); return TOK_NAME; 
     11646                            } 
     11647                            } 
     11648   YY_BREAK 
     11649case 119: 
     11650*yy_cp = (yy_hold_char); /* undo effects of setting up fortran_text */ 
     11651(yy_c_buf_p) = yy_cp = yy_bp + 4; 
     11652YY_DO_BEFORE_ACTION; /* set up fortran_text again */ 
     11653YY_RULE_SETUP 
     11654#line 245 "fortran.lex" 
     11655{ 
     11656                            if ((in_char_selector==1) || (in_kind_selector == 1)) 
     11657                               return TOK_KIND; 
     11658                            else 
     11659                            { 
     11660                            strcpy(yylval.na,fortran_text); return TOK_NAME; 
     11661                            } 
     11662                            } 
     11663   YY_BREAK 
     11664case 120: 
     11665YY_RULE_SETUP 
     11666#line 253 "fortran.lex" 
     11667{ return TOK_ERRMSG; } 
     11668   YY_BREAK 
     11669case 121: 
     11670YY_RULE_SETUP 
     11671#line 254 "fortran.lex" 
     11672{ return TOK_MOLD; } 
     11673   YY_BREAK 
     11674case 122: 
     11675YY_RULE_SETUP 
     11676#line 255 "fortran.lex" 
     11677{ return TOK_SOURCE; } 
     11678   YY_BREAK 
     11679case 123: 
     11680YY_RULE_SETUP 
     11681#line 256 "fortran.lex" 
     11682{ return TOK_POSITION; } 
     11683   YY_BREAK 
     11684case 124: 
     11685YY_RULE_SETUP 
     11686#line 257 "fortran.lex" 
     11687{ return TOK_IOMSG; } 
     11688   YY_BREAK 
     11689case 125: 
     11690YY_RULE_SETUP 
     11691#line 258 "fortran.lex" 
     11692{ return TOK_IOSTAT; } 
     11693   YY_BREAK 
     11694case 126: 
     11695YY_RULE_SETUP 
     11696#line 259 "fortran.lex" 
    910311697{ return TOK_ERR; } 
    910411698   YY_BREAK 
    9105 case 118: 
    9106 YY_RULE_SETUP 
    9107 #line 223 "fortran.lex" 
     11699case 127: 
     11700YY_RULE_SETUP 
     11701#line 260 "fortran.lex" 
     11702{ return TOK_FORM; } 
     11703   YY_BREAK 
     11704case 128: 
     11705*yy_cp = (yy_hold_char); /* undo effects of setting up fortran_text */ 
     11706(yy_c_buf_p) = yy_cp = yy_bp + 4; 
     11707YY_DO_BEFORE_ACTION; /* set up fortran_text again */ 
     11708YY_RULE_SETUP 
     11709#line 261 "fortran.lex" 
     11710{ 
     11711                            if (in_inquire==1) 
     11712                               return TOK_NAME_EQ; 
     11713                            else 
     11714                            { 
     11715                            strcpy(yylval.na,fortran_text); return TOK_NAME; 
     11716                            } 
     11717                            } 
     11718   YY_BREAK 
     11719case 129: 
     11720YY_RULE_SETUP 
     11721#line 269 "fortran.lex" 
     11722{ return TOK_RECL; } 
     11723   YY_BREAK 
     11724case 130: 
     11725YY_RULE_SETUP 
     11726#line 270 "fortran.lex" 
     11727{ return TOK_REC; } 
     11728   YY_BREAK 
     11729case 131: 
     11730*yy_cp = (yy_hold_char); /* undo effects of setting up fortran_text */ 
     11731(yy_c_buf_p) = yy_cp = yy_bp + 6; 
     11732YY_DO_BEFORE_ACTION; /* set up fortran_text again */ 
     11733YY_RULE_SETUP 
     11734#line 271 "fortran.lex" 
     11735{ if (close_or_connect == 1) 
     11736                              return TOK_STATUS; 
     11737                             else 
     11738                             { 
     11739                             strcpy(yylval.na,fortran_text); return TOK_NAME; 
     11740                             } 
     11741                             } 
     11742   YY_BREAK 
     11743case 132: 
     11744YY_RULE_SETUP 
     11745#line 278 "fortran.lex" 
     11746{ strcpy(yylval.na,fortran_text); return TOK_NAME;} 
     11747   YY_BREAK 
     11748case 133: 
     11749YY_RULE_SETUP 
     11750#line 279 "fortran.lex" 
    910811751{ return TOK_EXIST; } 
    910911752   YY_BREAK 
    9110 case 119: 
    9111 YY_RULE_SETUP 
    9112 #line 224 "fortran.lex" 
    9113 { return TOK_MIN; } 
    9114    YY_BREAK 
    9115 case 120: 
    9116 YY_RULE_SETUP 
    9117 #line 225 "fortran.lex" 
    9118 { return TOK_NINT; } 
    9119    YY_BREAK 
    9120 case 121: 
    9121 YY_RULE_SETUP 
    9122 #line 226 "fortran.lex" 
    9123 { return TOK_FLOAT; } 
    9124    YY_BREAK 
    9125 case 122: 
    9126 YY_RULE_SETUP 
    9127 #line 227 "fortran.lex" 
    9128 { return TOK_EXP; } 
    9129    YY_BREAK 
    9130 case 123: 
    9131 YY_RULE_SETUP 
    9132 #line 228 "fortran.lex" 
    9133 { return TOK_COS; } 
    9134    YY_BREAK 
    9135 case 124: 
    9136 YY_RULE_SETUP 
    9137 #line 229 "fortran.lex" 
    9138 { return TOK_COSH; } 
    9139    YY_BREAK 
    9140 case 125: 
    9141 YY_RULE_SETUP 
    9142 #line 230 "fortran.lex" 
    9143 { return TOK_ACOS; } 
    9144    YY_BREAK 
    9145 case 126: 
    9146 YY_RULE_SETUP 
    9147 #line 231 "fortran.lex" 
    9148 { return TOK_SIN; } 
    9149    YY_BREAK 
    9150 case 127: 
    9151 YY_RULE_SETUP 
    9152 #line 232 "fortran.lex" 
    9153 { return TOK_SINH; } 
    9154    YY_BREAK 
    9155 case 128: 
    9156 YY_RULE_SETUP 
    9157 #line 233 "fortran.lex" 
    9158 { return TOK_ASIN; } 
    9159    YY_BREAK 
    9160 case 129: 
    9161 YY_RULE_SETUP 
    9162 #line 234 "fortran.lex" 
    9163 { return TOK_LOG; } 
    9164    YY_BREAK 
    9165 case 130: 
    9166 YY_RULE_SETUP 
    9167 #line 235 "fortran.lex" 
    9168 { return TOK_TAN; } 
    9169    YY_BREAK 
    9170 case 131: 
    9171 YY_RULE_SETUP 
    9172 #line 236 "fortran.lex" 
    9173 { return TOK_ATAN; } 
    9174    YY_BREAK 
    9175 case 132: 
    9176 YY_RULE_SETUP 
    9177 #line 237 "fortran.lex" 
     11753case 134: 
     11754YY_RULE_SETUP 
     11755#line 280 "fortran.lex" 
    917811756{ return TOK_CYCLE; } 
    917911757   YY_BREAK 
    9180 case 133: 
    9181 YY_RULE_SETUP 
    9182 #line 238 "fortran.lex" 
    9183 { return TOK_ABS; } 
    9184    YY_BREAK 
    9185 case 134: 
    9186 YY_RULE_SETUP 
    9187 #line 239 "fortran.lex" 
    9188 { return TOK_MOD; } 
    9189    YY_BREAK 
    919011758case 135: 
    919111759YY_RULE_SETUP 
    9192 #line 240 "fortran.lex" 
    9193 { return TOK_SIGN; } 
     11760#line 281 "fortran.lex" 
     11761{ return TOK_BACKSPACE; } 
    919411762   YY_BREAK 
    919511763case 136: 
    919611764YY_RULE_SETUP 
    9197 #line 241 "fortran.lex" 
    9198 { return TOK_MINLOC; } 
     11765#line 282 "fortran.lex" 
     11766{ return TOK_FOURDOTS; } 
    919911767   YY_BREAK 
    920011768case 137: 
    9201 YY_RULE_SETUP 
    9202 #line 242 "fortran.lex" 
    9203 { return TOK_MAXLOC; } 
     11769/* rule 137 can match eol */ 
     11770YY_RULE_SETUP 
     11771#line 283 "fortran.lex" 
     11772{ strcpy(yylval.na,fortran_text); return TOK_DSLASH; } 
    920411773   YY_BREAK 
    920511774case 138: 
    920611775YY_RULE_SETUP 
    9207 #line 243 "fortran.lex" 
    9208 { return TOK_MINVAL; } 
     11776#line 284 "fortran.lex" 
     11777{ return TOK_LEFTAB; } 
    920911778   YY_BREAK 
    921011779case 139: 
    921111780YY_RULE_SETUP 
    9212 #line 244 "fortran.lex" 
    9213 { return TOK_BACKSPACE; } 
     11781#line 285 "fortran.lex" 
     11782{ return TOK_RIGHTAB; } 
    921411783   YY_BREAK 
    921511784case 140: 
    921611785YY_RULE_SETUP 
    9217 #line 245 "fortran.lex" 
    9218 { return TOK_FOURDOTS; } 
     11786#line 286 "fortran.lex" 
     11787{ strcpy(yylval.na,fortran_text); return TOK_SLASH; } 
    921911788   YY_BREAK 
    922011789case 141: 
    9221 YY_RULE_SETUP 
    9222 #line 246 "fortran.lex" 
    9223 { return TOK_LEFTAB; } 
     11790/* rule 141 can match eol */ 
     11791YY_RULE_SETUP 
     11792#line 287 "fortran.lex" 
     11793{ 
     11794                              INCREMENT_LINE_NUM() ; strcpy(yylval.na,fortran_text); return TOK_CHAR_CUT; } 
    922411795   YY_BREAK 
    922511796case 142: 
    9226 YY_RULE_SETUP 
    9227 #line 247 "fortran.lex" 
    9228 { return TOK_RIGHTAB; } 
     11797/* rule 142 can match eol */ 
     11798YY_RULE_SETUP 
     11799#line 289 "fortran.lex" 
     11800{Add_Include_1(fortran_text);} 
    922911801   YY_BREAK 
    923011802case 143: 
    9231 /* rule 143 can match eol */ 
    9232 YY_RULE_SETUP 
    9233 #line 248 "fortran.lex" 
     11803YY_RULE_SETUP 
     11804#line 290 "fortran.lex" 
     11805{} 
     11806   YY_BREAK 
     11807case 144: 
     11808/* rule 144 can match eol */ 
     11809YY_RULE_SETUP 
     11810#line 291 "fortran.lex" 
    923411811{ 
    9235                               return TOK_FORMAT; } 
    9236    YY_BREAK 
    9237 case 144: 
    9238 YY_RULE_SETUP 
    9239 #line 250 "fortran.lex" 
    9240 { strcpy(yylval.na,fortran_text); return TOK_SLASH; } 
     11812                  if (inmoduledeclare == 0 ) 
     11813                  { 
     11814                  pos_end=setposcur(); 
     11815                  RemoveWordSET_0(fortran_out,pos_curinclude,pos_end-pos_curinclude); 
     11816                  } 
     11817                  out_of_donottreat(); 
     11818                  } 
    924111819   YY_BREAK 
    924211820case 145: 
    9243 YY_RULE_SETUP 
    9244 #line 251 "fortran.lex" 
    9245 { strcpy(yylval.na,fortran_text); return TOK_DSLASH; } 
     11821/* rule 145 can match eol */ 
     11822YY_RULE_SETUP 
     11823#line 299 "fortran.lex" 
     11824{ strcpy(yylval.na,fortran_text);return TOK_CHAR_CONSTANT; } 
    924611825   YY_BREAK 
    924711826case 146: 
    924811827/* rule 146 can match eol */ 
    924911828YY_RULE_SETUP 
    9250 #line 252 "fortran.lex" 
    9251 { 
    9252                               strcpy(yylval.na,fortran_text); return TOK_CHAR_CUT; } 
     11829#line 300 "fortran.lex" 
     11830{ strcpy(yylval.na,fortran_text);return TOK_CHAR_MESSAGE; } 
    925311831   YY_BREAK 
    925411832case 147: 
    9255 /* rule 147 can match eol */ 
    9256 YY_RULE_SETUP 
    9257 #line 254 "fortran.lex" 
    9258 { strcpy(yylval.na,fortran_text);return TOK_CHAR_CONSTANT; } 
     11833YY_RULE_SETUP 
     11834#line 301 "fortran.lex" 
     11835{ BEGIN(donottreat); } 
    925911836   YY_BREAK 
    926011837case 148: 
    926111838/* rule 148 can match eol */ 
    926211839YY_RULE_SETUP 
    9263 #line 255 "fortran.lex" 
    9264 { strcpy(yylval.na,fortran_text);return TOK_CHAR_MESSAGE; } 
     11840#line 302 "fortran.lex" 
     11841{ out_of_donottreat(); return '\n'; } 
    926511842   YY_BREAK 
    926611843case 149: 
    9267 YY_RULE_SETUP 
    9268 #line 256 "fortran.lex" 
    9269 { BEGIN(donottreat); } 
     11844/* rule 149 can match eol */ 
     11845YY_RULE_SETUP 
     11846#line 303 "fortran.lex" 
     11847{strcpy(yylval.na,fortran_text); removenewline(yylval.na); 
     11848                            return TOK_NAME; } 
    927011849   YY_BREAK 
    927111850case 150: 
    9272 /* rule 150 can match eol */ 
    9273 YY_RULE_SETUP 
    9274 #line 257 "fortran.lex" 
    9275 { out_of_donottreat(); return '\n'; } 
     11851YY_RULE_SETUP 
     11852#line 305 "fortran.lex" 
     11853{ strcpy(yylval.na,fortran_text); return TOK_NAME; } 
    927611854   YY_BREAK 
    927711855case 151: 
    927811856YY_RULE_SETUP 
    9279 #line 258 "fortran.lex" 
    9280 { strcpy(yylval.na,fortran_text); return TOK_NAME; } 
     11857#line 306 "fortran.lex" 
     11858{strcpy(yylval.na,fortran_text); return TOK_CSTREAL; } 
    928111859   YY_BREAK 
    928211860case 152: 
     
    928611864YY_DO_BEFORE_ACTION; /* set up fortran_text again */ 
    928711865YY_RULE_SETUP 
    9288 #line 259 "fortran.lex" 
     11866#line 307 "fortran.lex" 
    928911867{  // REAL1 
    929011868                              strcpy(yylval.na,fortran_text); return TOK_CSTREAL; } 
     
    929211870case 153: 
    929311871YY_RULE_SETUP 
    9294 #line 261 "fortran.lex" 
     11872#line 309 "fortran.lex" 
    929511873{  // REAL2 
    929611874                              strcpy(yylval.na,fortran_text); return TOK_CSTREAL; } 
     
    929811876case 154: 
    929911877YY_RULE_SETUP 
    9300 #line 263 "fortran.lex" 
    9301 { strcpy(yylval.na,fortran_text); return TOK_CSTINT; } 
     11878#line 311 "fortran.lex" 
     11879{ strcpy(yylval.na,fortran_text); 
     11880                             if (lastwasendofstmt == 0) 
     11881                              return TOK_CSTINT; 
     11882                             else 
     11883                              if (testandextractfromlist(&List_Do_labels,fortran_text) == 1) 
     11884                              { 
     11885                              removefromlist(&List_Do_labels,yylval.na); 
     11886                              return TOK_LABEL_DJVIEW; 
     11887                              } 
     11888                              else 
     11889                              { 
     11890                              return TOK_LABEL; 
     11891                              } 
     11892                             } 
    930211893   YY_BREAK 
    930311894case 155: 
    930411895YY_RULE_SETUP 
    9305 #line 264 "fortran.lex" 
     11896#line 325 "fortran.lex" 
    930611897{} 
    930711898   YY_BREAK 
    930811899case 156: 
    930911900YY_RULE_SETUP 
    9310 #line 265 "fortran.lex" 
     11901#line 326 "fortran.lex" 
    931111902{} 
    931211903   YY_BREAK 
    931311904case 157: 
    9314 YY_RULE_SETUP 
    9315 #line 266 "fortran.lex" 
     11905*yy_cp = (yy_hold_char); /* undo effects of setting up fortran_text */ 
     11906(yy_c_buf_p) = yy_cp = yy_bp + 1; 
     11907YY_DO_BEFORE_ACTION; /* set up fortran_text again */ 
     11908YY_RULE_SETUP 
     11909#line 327 "fortran.lex" 
     11910{ 
     11911                            in_complex_literal = -1; 
     11912                            return (int) *fortran_text; 
     11913                            } 
     11914   YY_BREAK 
     11915case 158: 
     11916YY_RULE_SETUP 
     11917#line 331 "fortran.lex" 
    931611918{ strcpy(yylval.na,fortran_text); return (int) *fortran_text; } 
    931711919   YY_BREAK 
    9318 case 158: 
    9319 YY_RULE_SETUP 
    9320 #line 267 "fortran.lex" 
     11920case 159: 
     11921YY_RULE_SETUP 
     11922#line 332 "fortran.lex" 
    932111923{ strcpy(yylval.na,fortran_text); return (int) *fortran_text; } 
    932211924   YY_BREAK 
    9323 case 159: 
    9324 YY_RULE_SETUP 
    9325 #line 268 "fortran.lex" 
    9326 { return TOK_SEMICOLON; } 
    9327    YY_BREAK 
    932811925case 160: 
    932911926YY_RULE_SETUP 
    9330 #line 269 "fortran.lex" 
     11927#line 333 "fortran.lex" 
     11928{ lastwasendofstmt=1; token_since_endofstmt = 0; return TOK_SEMICOLON; } 
     11929   YY_BREAK 
     11930case 161: 
     11931YY_RULE_SETUP 
     11932#line 334 "fortran.lex" 
     11933{ if (in_complex_literal==-1) {return TOK_COMMACOMPLEX; in_complex_literal=0;} else; return (int) *fortran_text; } 
     11934   YY_BREAK 
     11935case 162: 
     11936YY_RULE_SETUP 
     11937#line 335 "fortran.lex" 
    933111938{ return (int) *fortran_text; } 
    933211939   YY_BREAK 
    9333 case 161: 
    9334 YY_RULE_SETUP 
    9335 #line 270 "fortran.lex" 
     11940case 163: 
     11941YY_RULE_SETUP 
     11942#line 336 "fortran.lex" 
    933611943{ return (int) *fortran_text; } 
    933711944   YY_BREAK 
    9338 case 162: 
    9339 YY_RULE_SETUP 
    9340 #line 271 "fortran.lex" 
     11945case 164: 
     11946YY_RULE_SETUP 
     11947#line 337 "fortran.lex" 
    934111948{ return (int) *fortran_text; } 
    934211949   YY_BREAK 
    9343 case 163: 
    9344 YY_RULE_SETUP 
    9345 #line 272 "fortran.lex" 
    9346 { return (int) *fortran_text; } 
    9347    YY_BREAK 
    9348 case 164: 
    9349 /* rule 164 can match eol */ 
    9350 YY_RULE_SETUP 
    9351 #line 273 "fortran.lex" 
    9352 { INCREMENT_LINE_NUM() ; return '\n'; } 
    9353    YY_BREAK 
    935411950case 165: 
    9355 *yy_cp = (yy_hold_char); /* undo effects of setting up fortran_text */ 
    9356 (yy_c_buf_p) = yy_cp -= 1; 
    9357 YY_DO_BEFORE_ACTION; /* set up fortran_text again */ 
    9358 YY_RULE_SETUP 
    9359 #line 274 "fortran.lex" 
    9360 {} 
     11951/* rule 165 can match eol */ 
     11952YY_RULE_SETUP 
     11953#line 338 "fortran.lex" 
     11954{ INCREMENT_LINE_NUM() ; lastwasendofstmt=1; token_since_endofstmt = 0; increment_nbtokens = 0; return '\n'; } 
    936111955   YY_BREAK 
    936211956case 166: 
    936311957YY_RULE_SETUP 
    9364 #line 275 "fortran.lex" 
    9365 {} 
     11958#line 339 "fortran.lex" 
     11959{increment_nbtokens = 0;} 
    936611960   YY_BREAK 
    936711961case 167: 
    9368 YY_RULE_SETUP 
    9369 #line 276 "fortran.lex" 
    9370 { if (newlinef90 == 0) return TOK_LABEL; else newlinef90 = 0; } 
     11962/* rule 167 can match eol */ 
     11963YY_RULE_SETUP 
     11964#line 340 "fortran.lex" 
     11965{ 
     11966                              return TOK_LABEL_FORMAT; } 
    937111967   YY_BREAK 
    937211968case 168: 
    937311969/* rule 168 can match eol */ 
    937411970YY_RULE_SETUP 
    9375 #line 277 "fortran.lex" 
    9376 { INCREMENT_LINE_NUM() ; newlinef90=1; } 
     11971#line 342 "fortran.lex" 
     11972{return TOK_LABEL_FORMAT; } 
    937711973   YY_BREAK 
    937811974case 169: 
    937911975/* rule 169 can match eol */ 
    938011976YY_RULE_SETUP 
    9381 #line 278 "fortran.lex" 
    9382 { INCREMENT_LINE_NUM() ; } 
     11977#line 343 "fortran.lex" 
     11978{ INCREMENT_LINE_NUM() ; newlinef90=1; } 
    938311979   YY_BREAK 
    938411980case 170: 
    938511981/* rule 170 can match eol */ 
    938611982YY_RULE_SETUP 
    9387 #line 280 "fortran.lex" 
    9388 { INCREMENT_LINE_NUM() ; BEGIN(donottreat); } 
     11983#line 344 "fortran.lex" 
     11984{ INCREMENT_LINE_NUM() ;} 
    938911985   YY_BREAK 
    939011986case 171: 
    939111987/* rule 171 can match eol */ 
    939211988YY_RULE_SETUP 
    9393 #line 281 "fortran.lex" 
    9394 { out_of_donottreat(); return '\n'; } 
     11989#line 346 "fortran.lex" 
     11990{ INCREMENT_LINE_NUM() ; BEGIN(donottreat); } 
    939511991   YY_BREAK 
    939611992case 172: 
    939711993/* rule 172 can match eol */ 
    939811994YY_RULE_SETUP 
    9399 #line 282 "fortran.lex" 
    9400 { INCREMENT_LINE_NUM() ; } 
     11995#line 347 "fortran.lex" 
     11996{ out_of_donottreat(); return '\n'; } 
    940111997   YY_BREAK 
    940211998case 173: 
    940311999/* rule 173 can match eol */ 
    940412000YY_RULE_SETUP 
    9405 #line 283 "fortran.lex" 
     12001#line 348 "fortran.lex" 
    940612002{ INCREMENT_LINE_NUM() ; } 
    940712003   YY_BREAK 
     
    940912005/* rule 174 can match eol */ 
    941012006YY_RULE_SETUP 
    9411 #line 284 "fortran.lex" 
    9412 { INCREMENT_LINE_NUM() ; } 
     12007#line 349 "fortran.lex" 
     12008{ INCREMENT_LINE_NUM() ; increment_nbtokens = 0;} 
    941312009   YY_BREAK 
    941412010case 175: 
    9415 YY_RULE_SETUP 
    9416 #line 285 "fortran.lex" 
    9417 {} 
     12011/* rule 175 can match eol */ 
     12012YY_RULE_SETUP 
     12013#line 350 "fortran.lex" 
     12014{ INCREMENT_LINE_NUM() ; increment_nbtokens = 0;} 
    941812015   YY_BREAK 
    941912016case 176: 
    942012017YY_RULE_SETUP 
    9421 #line 286 "fortran.lex" 
    9422 ECHO; 
    9423    YY_BREAK 
    9424 #line 3015 "fortran.yy.c" 
     12018#line 351 "fortran.lex" 
     12019{increment_nbtokens = 0;} 
     12020   YY_BREAK 
    942512021case YY_STATE_EOF(INITIAL): 
    942612022case YY_STATE_EOF(parameter): 
    942712023case YY_STATE_EOF(character): 
    942812024case YY_STATE_EOF(donottreat): 
     12025case YY_STATE_EOF(includestate): 
    942912026case YY_STATE_EOF(fortran77style): 
    943012027case YY_STATE_EOF(fortran90style): 
    9431    yyterminate(); 
     12028#line 352 "fortran.lex" 
     12029{endoffile = 1; yyterminate();} 
     12030   YY_BREAK 
     12031case 177: 
     12032YY_RULE_SETUP 
     12033#line 353 "fortran.lex" 
     12034ECHO; 
     12035   YY_BREAK 
     12036#line 4743 "fortran.yy.c" 
    943212037 
    943312038   case YY_END_OF_BUFFER: 
     
    961912224         { /* Not enough room in the buffer - grow it. */ 
    962012225 
    9621          /* just a shorter name for the current buffer */ 
    9622          YY_BUFFER_STATE b = YY_CURRENT_BUFFER; 
    9623  
    9624          int yy_c_buf_p_offset = 
    9625             (int) ((yy_c_buf_p) - b->yy_ch_buf); 
    9626  
    9627          if ( b->yy_is_our_buffer ) 
    9628             { 
    9629             yy_size_t new_size = b->yy_buf_size * 2; 
    9630  
    9631             if ( new_size <= 0 ) 
    9632                b->yy_buf_size += b->yy_buf_size / 8; 
    9633             else 
    9634                b->yy_buf_size *= 2; 
    9635  
    9636             b->yy_ch_buf = (char *) 
    9637                /* Include room in for 2 EOB chars. */ 
    9638                fortran_realloc((void *) b->yy_ch_buf,b->yy_buf_size + 2  ); 
    9639             } 
    9640          else 
    9641             /* Can't grow it, we don't own it. */ 
    9642             b->yy_ch_buf = 0; 
    9643  
    9644          if ( ! b->yy_ch_buf ) 
    9645             YY_FATAL_ERROR( 
    9646             "fatal error - scanner input buffer overflow" ); 
    9647  
    9648          (yy_c_buf_p) = &b->yy_ch_buf[yy_c_buf_p_offset]; 
    9649  
    9650          num_to_read = YY_CURRENT_BUFFER_LVALUE->yy_buf_size - 
    9651                   number_to_move - 1; 
     12226         YY_FATAL_ERROR( 
     12227"input buffer overflow, can't enlarge buffer because scanner uses REJECT" ); 
    965212228 
    965312229         } 
     
    970912285   yy_current_state += YY_AT_BOL(); 
    971012286 
     12287   (yy_state_ptr) = (yy_state_buf); 
     12288   *(yy_state_ptr)++ = yy_current_state; 
     12289 
    971112290   for ( yy_cp = (yytext_ptr) + YY_MORE_ADJ; yy_cp < (yy_c_buf_p); ++yy_cp ) 
    971212291      { 
    971312292      register YY_CHAR yy_c = (*yy_cp ? yy_ec[YY_SC_TO_UI(*yy_cp)] : 1); 
    9714       if ( yy_accept[yy_current_state] ) 
    9715          { 
    9716          (yy_last_accepting_state) = yy_current_state; 
    9717          (yy_last_accepting_cpos) = yy_cp; 
    9718          } 
    971912293      while ( yy_chk[yy_base[yy_current_state] + yy_c] != yy_current_state ) 
    972012294         { 
    972112295         yy_current_state = (int) yy_def[yy_current_state]; 
    9722          if ( yy_current_state >= 1132 ) 
     12296         if ( yy_current_state >= 1849 ) 
    972312297            yy_c = yy_meta[(unsigned int) yy_c]; 
    972412298         } 
    972512299      yy_current_state = yy_nxt[yy_base[yy_current_state] + (unsigned int) yy_c]; 
     12300      *(yy_state_ptr)++ = yy_current_state; 
    972612301      } 
    972712302 
     
    973712312{ 
    973812313   register int yy_is_jam; 
    9739       register char *yy_cp = (yy_c_buf_p); 
    9740  
     12314     
    974112315   register YY_CHAR yy_c = 1; 
    9742    if ( yy_accept[yy_current_state] ) 
    9743       { 
    9744       (yy_last_accepting_state) = yy_current_state; 
    9745       (yy_last_accepting_cpos) = yy_cp; 
    9746       } 
    974712316   while ( yy_chk[yy_base[yy_current_state] + yy_c] != yy_current_state ) 
    974812317      { 
    974912318      yy_current_state = (int) yy_def[yy_current_state]; 
    9750       if ( yy_current_state >= 1132 ) 
     12319      if ( yy_current_state >= 1849 ) 
    975112320         yy_c = yy_meta[(unsigned int) yy_c]; 
    975212321      } 
    975312322   yy_current_state = yy_nxt[yy_base[yy_current_state] + (unsigned int) yy_c]; 
    9754    yy_is_jam = (yy_current_state == 1131); 
     12323   yy_is_jam = (yy_current_state == 1848); 
     12324   if ( ! yy_is_jam ) 
     12325      *(yy_state_ptr)++ = yy_current_state; 
    975512326 
    975612327   return yy_is_jam ? 0 : yy_current_state; 
     
    1034212913    (yy_start) = 0; 
    1034312914 
     12915    (yy_state_buf) = 0; 
     12916    (yy_state_ptr) = 0; 
     12917    (yy_full_match) = 0; 
     12918    (yy_lp) = 0; 
     12919 
    1034412920/* Defined in main.c */ 
    1034512921#ifdef YY_STDINIT 
     
    1037112947   fortran_free((yy_buffer_stack) ); 
    1037212948   (yy_buffer_stack) = NULL; 
     12949 
     12950    fortran_free ( (yy_state_buf) ); 
     12951    (yy_state_buf)  = NULL; 
    1037312952 
    1037412953    /* Reset the globals. This is important in a non-reentrant scanner so the next time 
     
    1042713006#define YYTABLES_NAME "yytables" 
    1042813007 
    10429 #line 286 "fortran.lex" 
     13008#line 353 "fortran.lex" 
    1043013009 
    1043113010 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/LIB/main.c

    r5819 r6258  
    1 /* A Bison parser, made by GNU Bison 2.3.  */ 
    2  
    3 /* Skeleton implementation for Bison's Yacc-like parsers in C 
    4  
    5    Copyright (C) 1984, 1989, 1990, 2000, 2001, 2002, 2003, 2004, 2005, 2006 
    6    Free Software Foundation, Inc. 
    7  
    8    This program is free software; you can redistribute it and/or modify 
     1/* A Bison parser, made by GNU Bison 2.7.  */ 
     2 
     3/* Bison implementation for Yacc-like parsers in C 
     4    
     5      Copyright (C) 1984, 1989-1990, 2000-2012 Free Software Foundation, Inc. 
     6    
     7   This program is free software: you can redistribute it and/or modify 
    98   it under the terms of the GNU General Public License as published by 
    10    the Free Software Foundation; either version 2, or (at your option) 
    11    any later version. 
    12  
     9   the Free Software Foundation, either version 3 of the License, or 
     10   (at your option) any later version. 
     11    
    1312   This program is distributed in the hope that it will be useful, 
    1413   but WITHOUT ANY WARRANTY; without even the implied warranty of 
    1514   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the 
    1615   GNU General Public License for more details. 
    17  
     16    
    1817   You should have received a copy of the GNU General Public License 
    19    along with this program; if not, write to the Free Software 
    20    Foundation, Inc., 51 Franklin Street, Fifth Floor, 
    21    Boston, MA 02110-1301, USA.  */ 
     18   along with this program.  If not, see <http://www.gnu.org/licenses/>.  */ 
    2219 
    2320/* As a special exception, you may create a larger work that contains 
     
    3027   Bison output files to be licensed under the GNU General Public 
    3128   License without this special exception. 
    32  
     29    
    3330   This special exception was added by the Free Software Foundation in 
    3431   version 2.2 of Bison.  */ 
     
    4845 
    4946/* Bison version.  */ 
    50 #define YYBISON_VERSION "2.3" 
     47#define YYBISON_VERSION "2.7" 
    5148 
    5249/* Skeleton name.  */ 
     
    5653#define YYPURE 0 
    5754 
    58 /* Using locations.  */ 
    59 #define YYLSP_NEEDED 0 
     55/* Push parsers.  */ 
     56#define YYPUSH 0 
     57 
     58/* Pull parsers.  */ 
     59#define YYPULL 1 
     60 
    6061 
    6162/* Substitute the variable and function names.  */ 
    62 #define yyparse convert_parse 
    63 #define yylex   convert_lex 
    64 #define yyerror convert_error 
    65 #define yylval  convert_lval 
    66 #define yychar  convert_char 
    67 #define yydebug convert_debug 
    68 #define yynerrs convert_nerrs 
    69  
     63#define yyparse         convert_parse 
     64#define yylex           convert_lex 
     65#define yyerror         convert_error 
     66#define yylval          convert_lval 
     67#define yychar          convert_char 
     68#define yydebug         convert_debug 
     69#define yynerrs         convert_nerrs 
     70 
     71/* Copy the first part of user declarations.  */ 
     72/* Line 371 of yacc.c  */ 
     73#line 35 "convert.y" 
     74 
     75#include <stdlib.h> 
     76#include <stdio.h> 
     77#include <string.h> 
     78#include "decl.h" 
     79 
     80int line_num=1; 
     81extern FILE * convert_in; 
     82 
     83int convert_error(const char *s) 
     84{ 
     85    printf("##\n## ERROR in conv: '%s' (line %d, file: %s)\n##\n", s, line_num, config_file); 
     86    exit(0); 
     87} 
     88 
     89 
     90/* Line 371 of yacc.c  */ 
     91#line 92 "convert.tab.c" 
     92 
     93# ifndef YY_NULL 
     94#  if defined __cplusplus && 201103L <= __cplusplus 
     95#   define YY_NULL nullptr 
     96#  else 
     97#   define YY_NULL 0 
     98#  endif 
     99# endif 
     100 
     101/* Enabling verbose error messages.  */ 
     102#ifdef YYERROR_VERBOSE 
     103# undef YYERROR_VERBOSE 
     104# define YYERROR_VERBOSE 1 
     105#else 
     106# define YYERROR_VERBOSE 0 
     107#endif 
     108 
     109 
     110/* Enabling traces.  */ 
     111#ifndef YYDEBUG 
     112# define YYDEBUG 1 
     113#endif 
     114#if YYDEBUG 
     115extern int convert_debug; 
     116#endif 
    70117 
    71118/* Tokens.  */ 
     
    87134   }; 
    88135#endif 
    89 /* Tokens.  */ 
    90 #define TOK_SEP 258 
    91 #define TOK_KIND 259 
    92 #define TOK_EQUAL 260 
    93 #define TOK_USE 261 
    94 #define TOK_MODULEMAIN 262 
    95 #define TOK_NOTGRIDDEP 263 
    96 #define TOK_USEITEM 264 
    97 #define TOK_NAME 265 
    98 #define TOK_CSTINT 266 
    99 #define TOK_PROBTYPE 267 
    100  
    101  
    102  
    103  
    104 /* Copy the first part of user declarations.  */ 
    105 #line 35 "convert.y" 
    106  
    107 #include <stdlib.h> 
    108 #include <stdio.h> 
    109 #include <string.h> 
    110 #include "decl.h" 
    111  
    112 int line_num=1; 
    113 extern FILE * convert_in; 
    114  
    115 int convert_error(const char *s) 
    116 { 
    117     printf("##\n## ERROR in conv: '%s' (line %d, file: %s)\n##\n", s, line_num, config_file); 
    118     exit(0); 
    119 } 
    120  
    121  
    122  
    123 /* Enabling traces.  */ 
    124 #ifndef YYDEBUG 
    125 # define YYDEBUG 1 
    126 #endif 
    127  
    128 /* Enabling verbose error messages.  */ 
    129 #ifdef YYERROR_VERBOSE 
    130 # undef YYERROR_VERBOSE 
    131 # define YYERROR_VERBOSE 1 
    132 #else 
    133 # define YYERROR_VERBOSE 0 
    134 #endif 
    135  
    136 /* Enabling the token table.  */ 
    137 #ifndef YYTOKEN_TABLE 
    138 # define YYTOKEN_TABLE 0 
    139 #endif 
     136 
    140137 
    141138#if ! defined YYSTYPE && ! defined YYSTYPE_IS_DECLARED 
    142139typedef union YYSTYPE 
     140{ 
     141/* Line 387 of yacc.c  */ 
    143142#line 52 "convert.y" 
    144 { 
     143 
    145144    char na[LONG_M]; 
    146 } 
    147 /* Line 193 of yacc.c.  */ 
     145 
     146 
     147/* Line 387 of yacc.c  */ 
    148148#line 149 "convert.tab.c" 
    149    YYSTYPE; 
     149} YYSTYPE; 
     150# define YYSTYPE_IS_TRIVIAL 1 
    150151# define yystype YYSTYPE /* obsolescent; will be withdrawn */ 
    151152# define YYSTYPE_IS_DECLARED 1 
    152 # define YYSTYPE_IS_TRIVIAL 1 
    153 #endif 
     153#endif 
     154 
     155extern YYSTYPE convert_lval; 
     156 
     157#ifdef YYPARSE_PARAM 
     158#if defined __STDC__ || defined __cplusplus 
     159int convert_parse (void *YYPARSE_PARAM); 
     160#else 
     161int convert_parse (); 
     162#endif 
     163#else /* ! YYPARSE_PARAM */ 
     164#if defined __STDC__ || defined __cplusplus 
     165int convert_parse (void); 
     166#else 
     167int convert_parse (); 
     168#endif 
     169#endif /* ! YYPARSE_PARAM */ 
    154170 
    155171 
     
    157173/* Copy the second part of user declarations.  */ 
    158174 
    159  
    160 /* Line 216 of yacc.c.  */ 
    161 #line 162 "convert.tab.c" 
     175/* Line 390 of yacc.c  */ 
     176#line 177 "convert.tab.c" 
    162177 
    163178#ifdef short 
     
    212227#  if ENABLE_NLS 
    213228#   include <libintl.h> /* INFRINGES ON USER NAME SPACE */ 
    214 #   define YY_(msgid) dgettext ("bison-runtime", msgid) 
     229#   define YY_(Msgid) dgettext ("bison-runtime", Msgid) 
    215230#  endif 
    216231# endif 
    217232# ifndef YY_ 
    218 #  define YY_(msgid) msgid 
     233#  define YY_(Msgid) Msgid 
    219234# endif 
    220235#endif 
     
    222237/* Suppress unused-variable warnings by "using" E.  */ 
    223238#if ! defined lint || defined __GNUC__ 
    224 # define YYUSE(e) ((void) (e)) 
     239# define YYUSE(E) ((void) (E)) 
    225240#else 
    226 # define YYUSE(e) /* empty */ 
     241# define YYUSE(E) /* empty */ 
    227242#endif 
    228243 
    229244/* Identity function, used to suppress warnings about constant conditions.  */ 
    230245#ifndef lint 
    231 # define YYID(n) (n) 
     246# define YYID(N) (N) 
    232247#else 
    233248#if (defined __STDC__ || defined __C99__FUNC__ \ 
    234249     || defined __cplusplus || defined _MSC_VER) 
    235250static int 
    236 YYID (int i) 
     251YYID (int yyi) 
    237252#else 
    238253static int 
    239 YYID (i) 
    240     int i; 
    241 #endif 
    242 { 
    243   return i; 
     254YYID (yyi) 
     255    int yyi; 
     256#endif 
     257{ 
     258  return yyi; 
    244259} 
    245260#endif 
     
    262277#   else 
    263278#    define YYSTACK_ALLOC alloca 
    264 #    if ! defined _ALLOCA_H && ! defined _STDLIB_H && (defined __STDC__ || defined __C99__FUNC__ \ 
     279#    if ! defined _ALLOCA_H && ! defined EXIT_SUCCESS && (defined __STDC__ || defined __C99__FUNC__ \ 
    265280     || defined __cplusplus || defined _MSC_VER) 
    266281#     include <stdlib.h> /* INFRINGES ON USER NAME SPACE */ 
    267 #     ifndef _STDLIB_H 
    268 #      define _STDLIB_H 1 
     282      /* Use EXIT_SUCCESS as a witness for stdlib.h.  */ 
     283#     ifndef EXIT_SUCCESS 
     284#      define EXIT_SUCCESS 0 
    269285#     endif 
    270286#    endif 
     
    289305#   define YYSTACK_ALLOC_MAXIMUM YYSIZE_MAXIMUM 
    290306#  endif 
    291 #  if (defined __cplusplus && ! defined _STDLIB_H \ 
     307#  if (defined __cplusplus && ! defined EXIT_SUCCESS \ 
    292308       && ! ((defined YYMALLOC || defined malloc) \ 
    293309        && (defined YYFREE || defined free))) 
    294310#   include <stdlib.h> /* INFRINGES ON USER NAME SPACE */ 
    295 #   ifndef _STDLIB_H 
    296 #    define _STDLIB_H 1 
     311#   ifndef EXIT_SUCCESS 
     312#    define EXIT_SUCCESS 0 
    297313#   endif 
    298314#  endif 
    299315#  ifndef YYMALLOC 
    300316#   define YYMALLOC malloc 
    301 #   if ! defined malloc && ! defined _STDLIB_H && (defined __STDC__ || defined __C99__FUNC__ \ 
     317#   if ! defined malloc && ! defined EXIT_SUCCESS && (defined __STDC__ || defined __C99__FUNC__ \ 
    302318     || defined __cplusplus || defined _MSC_VER) 
    303319void *malloc (YYSIZE_T); /* INFRINGES ON USER NAME SPACE */ 
     
    306322#  ifndef YYFREE 
    307323#   define YYFREE free 
    308 #   if ! defined free && ! defined _STDLIB_H && (defined __STDC__ || defined __C99__FUNC__ \ 
     324#   if ! defined free && ! defined EXIT_SUCCESS && (defined __STDC__ || defined __C99__FUNC__ \ 
    309325     || defined __cplusplus || defined _MSC_VER) 
    310326void free (void *); /* INFRINGES ON USER NAME SPACE */ 
     
    322338union yyalloc 
    323339{ 
    324   yytype_int16 yyss; 
    325   YYSTYPE yyvs; 
    326   }; 
     340  yytype_int16 yyss_alloc; 
     341  YYSTYPE yyvs_alloc; 
     342}; 
    327343 
    328344/* The size of the maximum gap between one aligned stack and the next.  */ 
     
    335351      + YYSTACK_GAP_MAXIMUM) 
    336352 
    337 /* Copy COUNT objects from FROM to TO.  The source and destination do 
    338    not overlap.  */ 
    339 # ifndef YYCOPY 
    340 #  if defined __GNUC__ && 1 < __GNUC__ 
    341 #   define YYCOPY(To, From, Count) \ 
    342       __builtin_memcpy (To, From, (Count) * sizeof (*(From))) 
    343 #  else 
    344 #   define YYCOPY(To, From, Count)     \ 
    345       do             \ 
    346    {              \ 
    347      YYSIZE_T yyi;            \ 
    348      for (yyi = 0; yyi < (Count); yyi++)  \ 
    349        (To)[yyi] = (From)[yyi];     \ 
    350    }              \ 
    351       while (YYID (0)) 
    352 #  endif 
    353 # endif 
     353# define YYCOPY_NEEDED 1 
    354354 
    355355/* Relocate STACK from its old location to the new one.  The 
     
    358358   stack.  Advance YYPTR to a properly aligned location for the next 
    359359   stack.  */ 
    360 # define YYSTACK_RELOCATE(Stack)             \ 
     360# define YYSTACK_RELOCATE(Stack_alloc, Stack)            \ 
    361361    do                           \ 
    362362      {                          \ 
    363363   YYSIZE_T yynewbytes;                \ 
    364    YYCOPY (&yyptr->Stack, Stack, yysize);          \ 
    365    Stack = &yyptr->Stack               \ 
     364   YYCOPY (&yyptr->Stack_alloc, Stack, yysize);       \ 
     365   Stack = &yyptr->Stack_alloc;              \ 
    366366   yynewbytes = yystacksize * sizeof (*Stack) + YYSTACK_GAP_MAXIMUM; \ 
    367367   yyptr += yynewbytes / sizeof (*yyptr);          \ 
     
    370370 
    371371#endif 
     372 
     373#if defined YYCOPY_NEEDED && YYCOPY_NEEDED 
     374/* Copy COUNT objects from SRC to DST.  The source and destination do 
     375   not overlap.  */ 
     376# ifndef YYCOPY 
     377#  if defined __GNUC__ && 1 < __GNUC__ 
     378#   define YYCOPY(Dst, Src, Count) \ 
     379      __builtin_memcpy (Dst, Src, (Count) * sizeof (*(Src))) 
     380#  else 
     381#   define YYCOPY(Dst, Src, Count)              \ 
     382      do                                        \ 
     383        {                                       \ 
     384          YYSIZE_T yyi;                         \ 
     385          for (yyi = 0; yyi < (Count); yyi++)   \ 
     386            (Dst)[yyi] = (Src)[yyi];            \ 
     387        }                                       \ 
     388      while (YYID (0)) 
     389#  endif 
     390# endif 
     391#endif /* !YYCOPY_NEEDED */ 
    372392 
    373393/* YYFINAL -- State number of the termination state.  */ 
     
    451471#endif 
    452472 
    453 #if YYDEBUG || YYERROR_VERBOSE || YYTOKEN_TABLE 
     473#if YYDEBUG || YYERROR_VERBOSE || 0 
    454474/* YYTNAME[SYMBOL-NUM] -- String name of the symbol SYMBOL-NUM. 
    455475   First, the terminals, then, starting at YYNTOKENS, nonterminals.  */ 
     
    459479  "TOK_USE", "TOK_MODULEMAIN", "TOK_NOTGRIDDEP", "TOK_USEITEM", "TOK_NAME", 
    460480  "TOK_CSTINT", "TOK_PROBTYPE", "','", "';'", "'\\n'", "$accept", "input", 
    461   "line", 0 
     481  "line", YY_NULL 
    462482}; 
    463483#endif 
     
    487507}; 
    488508 
    489 /* YYDEFACT[STATE-NAME] -- Default rule to reduce with in state 
    490    STATE-NUM when YYTABLE doesn't specify something else to do.  Zero 
     509/* YYDEFACT[STATE-NAME] -- Default reduction number in state STATE-NUM. 
     510   Performed when YYTABLE doesn't specify something else to do.  Zero 
    491511   means the default is an error.  */ 
    492512static const yytype_uint8 yydefact[] = 
     
    521541/* YYTABLE[YYPACT[STATE-NUM]].  What to do in state STATE-NUM.  If 
    522542   positive, shift that token.  If negative, reduce the rule which 
    523    number is the opposite.  If zero, do what YYDEFACT says. 
    524    If YYTABLE_NINF, syntax error.  */ 
     543   number is the opposite.  If YYTABLE_NINF, syntax error.  */ 
    525544#define YYTABLE_NINF -1 
    526545static const yytype_uint8 yytable[] = 
     
    531550}; 
    532551 
     552#define yypact_value_is_default(Yystate) \ 
     553  (!!((Yystate) == (-13))) 
     554 
     555#define yytable_value_is_error(Yytable_value) \ 
     556  YYID (0) 
     557 
    533558static const yytype_int8 yycheck[] = 
    534559{ 
     
    559584/* Like YYERROR except do call yyerror.  This remains here temporarily 
    560585   to ease the transition to the new meaning of YYERROR, for GCC. 
    561    Once GCC version 2 has supplanted version 1, this can go.  */ 
     586   Once GCC version 2 has supplanted version 1, this can go.  However, 
     587   YYFAIL appears to be in use.  Nevertheless, it is formally deprecated 
     588   in Bison 2.4.2's NEWS entry, where a plan to phase it out is 
     589   discussed.  */ 
    562590 
    563591#define YYFAIL    goto yyerrlab 
     592#if defined YYFAIL 
     593  /* This is here to suppress warnings from the GCC cpp's 
     594     -Wunused-macros.  Normally we don't worry about that warning, but 
     595     some users do, and we want to make it easy for users to remove 
     596     YYFAIL uses, which will produce warnings from Bison 2.5.  */ 
     597#endif 
    564598 
    565599#define YYRECOVERING()  (!!yyerrstatus) 
    566600 
    567 #define YYBACKUP(Token, Value)               \ 
    568 do                      \ 
    569   if (yychar == YYEMPTY && yylen == 1)          \ 
    570     {                      \ 
    571       yychar = (Token);                \ 
    572       yylval = (Value);                \ 
    573       yytoken = YYTRANSLATE (yychar);           \ 
    574       YYPOPSTACK (1);                  \ 
    575       goto yybackup;                \ 
    576     }                      \ 
    577   else                        \ 
    578     {                      \ 
     601#define YYBACKUP(Token, Value)                                  \ 
     602do                                                              \ 
     603  if (yychar == YYEMPTY)                                        \ 
     604    {                                                           \ 
     605      yychar = (Token);                                         \ 
     606      yylval = (Value);                                         \ 
     607      YYPOPSTACK (yylen);                                       \ 
     608      yystate = *yyssp;                                         \ 
     609      goto yybackup;                                            \ 
     610    }                                                           \ 
     611  else                                                          \ 
     612    {                                                           \ 
    579613      yyerror (YY_("syntax error: cannot back up")); \ 
    580614      YYERROR;                   \ 
     
    582616while (YYID (0)) 
    583617 
    584  
     618/* Error token number */ 
    585619#define YYTERROR  1 
    586620#define YYERRCODE 256 
    587621 
    588622 
    589 /* YYLLOC_DEFAULT -- Set CURRENT to span from RHS[1] to RHS[N]. 
    590    If N is 0, then set CURRENT to the empty location which ends 
    591    the previous symbol: RHS[0] (always defined).  */ 
    592  
    593 #define YYRHSLOC(Rhs, K) ((Rhs)[K]) 
    594 #ifndef YYLLOC_DEFAULT 
    595 # define YYLLOC_DEFAULT(Current, Rhs, N)           \ 
    596     do                           \ 
    597       if (YYID (N))                                                    \ 
    598    {                       \ 
    599      (Current).first_line   = YYRHSLOC (Rhs, 1).first_line; \ 
    600      (Current).first_column = YYRHSLOC (Rhs, 1).first_column;  \ 
    601      (Current).last_line    = YYRHSLOC (Rhs, N).last_line;     \ 
    602      (Current).last_column  = YYRHSLOC (Rhs, N).last_column;   \ 
    603    }                       \ 
    604       else                       \ 
    605    {                       \ 
    606      (Current).first_line   = (Current).last_line   =    \ 
    607        YYRHSLOC (Rhs, 0).last_line;          \ 
    608      (Current).first_column = (Current).last_column =    \ 
    609        YYRHSLOC (Rhs, 0).last_column;           \ 
    610    }                       \ 
    611     while (YYID (0)) 
    612 #endif 
    613  
    614  
    615 /* YY_LOCATION_PRINT -- Print the location on the stream. 
    616    This macro was not mandated originally: define only if we know 
    617    we won't break user code: when these are the locations we know.  */ 
    618  
     623/* This macro is provided for backward compatibility. */ 
    619624#ifndef YY_LOCATION_PRINT 
    620 # if defined YYLTYPE_IS_TRIVIAL && YYLTYPE_IS_TRIVIAL 
    621 #  define YY_LOCATION_PRINT(File, Loc)       \ 
    622      fprintf (File, "%d.%d-%d.%d",        \ 
    623          (Loc).first_line, (Loc).first_column,  \ 
    624          (Loc).last_line,  (Loc).last_column) 
    625 # else 
    626 #  define YY_LOCATION_PRINT(File, Loc) ((void) 0) 
    627 # endif 
     625# define YY_LOCATION_PRINT(File, Loc) ((void) 0) 
    628626#endif 
    629627 
    630628 
    631629/* YYLEX -- calling `yylex' with the right arguments.  */ 
    632  
    633630#ifdef YYLEX_PARAM 
    634631# define YYLEX yylex (YYLEX_PARAM) 
     
    680677#endif 
    681678{ 
     679  FILE *yyo = yyoutput; 
     680  YYUSE (yyo); 
    682681  if (!yyvaluep) 
    683682    return; 
     
    691690    { 
    692691      default: 
    693    break; 
     692        break; 
    694693    } 
    695694} 
     
    729728     || defined __cplusplus || defined _MSC_VER) 
    730729static void 
    731 yy_stack_print (yytype_int16 *bottom, yytype_int16 *top) 
     730yy_stack_print (yytype_int16 *yybottom, yytype_int16 *yytop) 
    732731#else 
    733732static void 
    734 yy_stack_print (bottom, top) 
    735     yytype_int16 *bottom; 
    736     yytype_int16 *top; 
     733yy_stack_print (yybottom, yytop) 
     734    yytype_int16 *yybottom; 
     735    yytype_int16 *yytop; 
    737736#endif 
    738737{ 
    739738  YYFPRINTF (stderr, "Stack now"); 
    740   for (; bottom <= top; ++bottom) 
    741     YYFPRINTF (stderr, " %d", *bottom); 
     739  for (; yybottom <= yytop; yybottom++) 
     740    { 
     741      int yybot = *yybottom; 
     742      YYFPRINTF (stderr, " %d", yybot); 
     743    } 
    742744  YYFPRINTF (stderr, "\n"); 
    743745} 
     
    773775  for (yyi = 0; yyi < yynrhs; yyi++) 
    774776    { 
    775       fprintf (stderr, "   $%d = ", yyi + 1); 
     777      YYFPRINTF (stderr, "   $%d = ", yyi + 1); 
    776778      yy_symbol_print (stderr, yyrhs[yyprhs[yyrule] + yyi], 
    777779             &(yyvsp[(yyi + 1) - (yynrhs)]) 
    778780                         ); 
    779       fprintf (stderr, "\n"); 
     781      YYFPRINTF (stderr, "\n"); 
    780782    } 
    781783} 
     
    813815# define YYMAXDEPTH 10000 
    814816#endif 
    815  
    816  
    817817 
    818818 
     
    918918# endif 
    919919 
    920 /* Copy into YYRESULT an error message about the unexpected token 
    921    YYCHAR while in state YYSTATE.  Return the number of bytes copied, 
    922    including the terminating null byte.  If YYRESULT is null, do not 
    923    copy anything; just return the number of bytes that would be 
    924    copied.  As a special case, return 0 if an ordinary "syntax error" 
    925    message will do.  Return YYSIZE_MAXIMUM if overflow occurs during 
    926    size calculation.  */ 
    927 static YYSIZE_T 
    928 yysyntax_error (char *yyresult, int yystate, int yychar) 
    929 { 
    930   int yyn = yypact[yystate]; 
    931  
    932   if (! (YYPACT_NINF < yyn && yyn <= YYLAST)) 
    933     return 0; 
    934   else 
     920/* Copy into *YYMSG, which is of size *YYMSG_ALLOC, an error message 
     921   about the unexpected token YYTOKEN for the state stack whose top is 
     922   YYSSP. 
     923 
     924   Return 0 if *YYMSG was successfully written.  Return 1 if *YYMSG is 
     925   not large enough to hold the message.  In that case, also set 
     926   *YYMSG_ALLOC to the required number of bytes.  Return 2 if the 
     927   required number of bytes is too large to store.  */ 
     928static int 
     929yysyntax_error (YYSIZE_T *yymsg_alloc, char **yymsg, 
     930                yytype_int16 *yyssp, int yytoken) 
     931{ 
     932  YYSIZE_T yysize0 = yytnamerr (YY_NULL, yytname[yytoken]); 
     933  YYSIZE_T yysize = yysize0; 
     934  enum { YYERROR_VERBOSE_ARGS_MAXIMUM = 5 }; 
     935  /* Internationalized format string. */ 
     936  const char *yyformat = YY_NULL; 
     937  /* Arguments of yyformat. */ 
     938  char const *yyarg[YYERROR_VERBOSE_ARGS_MAXIMUM]; 
     939  /* Number of reported tokens (one for the "unexpected", one per 
     940     "expected"). */ 
     941  int yycount = 0; 
     942 
     943  /* There are many possibilities here to consider: 
     944     - Assume YYFAIL is not used.  It's too flawed to consider.  See 
     945       <http://lists.gnu.org/archive/html/bison-patches/2009-12/msg00024.html> 
     946       for details.  YYERROR is fine as it does not invoke this 
     947       function. 
     948     - If this state is a consistent state with a default action, then 
     949       the only way this function was invoked is if the default action 
     950       is an error action.  In that case, don't check for expected 
     951       tokens because there are none. 
     952     - The only way there can be no lookahead present (in yychar) is if 
     953       this state is a consistent state with a default action.  Thus, 
     954       detecting the absence of a lookahead is sufficient to determine 
     955       that there is no unexpected or expected token to report.  In that 
     956       case, just report a simple "syntax error". 
     957     - Don't assume there isn't a lookahead just because this state is a 
     958       consistent state with a default action.  There might have been a 
     959       previous inconsistent state, consistent state with a non-default 
     960       action, or user semantic action that manipulated yychar. 
     961     - Of course, the expected token list depends on states to have 
     962       correct lookahead information, and it depends on the parser not 
     963       to perform extra reductions after fetching a lookahead from the 
     964       scanner and before detecting a syntax error.  Thus, state merging 
     965       (from LALR or IELR) and default reductions corrupt the expected 
     966       token list.  However, the list is correct for canonical LR with 
     967       one exception: it will still contain any token that will not be 
     968       accepted due to an error action in a later state. 
     969  */ 
     970  if (yytoken != YYEMPTY) 
    935971    { 
    936       int yytype = YYTRANSLATE (yychar); 
    937       YYSIZE_T yysize0 = yytnamerr (0, yytname[yytype]); 
    938       YYSIZE_T yysize = yysize0; 
    939       YYSIZE_T yysize1; 
    940       int yysize_overflow = 0; 
    941       enum { YYERROR_VERBOSE_ARGS_MAXIMUM = 5 }; 
    942       char const *yyarg[YYERROR_VERBOSE_ARGS_MAXIMUM]; 
    943       int yyx; 
    944  
    945 # if 0 
    946       /* This is so xgettext sees the translatable formats that are 
    947     constructed on the fly.  */ 
    948       YY_("syntax error, unexpected %s"); 
    949       YY_("syntax error, unexpected %s, expecting %s"); 
    950       YY_("syntax error, unexpected %s, expecting %s or %s"); 
    951       YY_("syntax error, unexpected %s, expecting %s or %s or %s"); 
    952       YY_("syntax error, unexpected %s, expecting %s or %s or %s or %s"); 
    953 # endif 
    954       char *yyfmt; 
    955       char const *yyf; 
    956       static char const yyunexpected[] = "syntax error, unexpected %s"; 
    957       static char const yyexpecting[] = ", expecting %s"; 
    958       static char const yyor[] = " or %s"; 
    959       char yyformat[sizeof yyunexpected 
    960           + sizeof yyexpecting - 1 
    961           + ((YYERROR_VERBOSE_ARGS_MAXIMUM - 2) 
    962              * (sizeof yyor - 1))]; 
    963       char const *yyprefix = yyexpecting; 
    964  
    965       /* Start YYX at -YYN if negative to avoid negative indexes in 
    966     YYCHECK.  */ 
    967       int yyxbegin = yyn < 0 ? -yyn : 0; 
    968  
    969       /* Stay within bounds of both yycheck and yytname.  */ 
    970       int yychecklim = YYLAST - yyn + 1; 
    971       int yyxend = yychecklim < YYNTOKENS ? yychecklim : YYNTOKENS; 
    972       int yycount = 1; 
    973  
    974       yyarg[0] = yytname[yytype]; 
    975       yyfmt = yystpcpy (yyformat, yyunexpected); 
    976  
    977       for (yyx = yyxbegin; yyx < yyxend; ++yyx) 
    978    if (yycheck[yyx + yyn] == yyx && yyx != YYTERROR) 
    979      { 
    980        if (yycount == YYERROR_VERBOSE_ARGS_MAXIMUM) 
    981          { 
    982       yycount = 1; 
    983       yysize = yysize0; 
    984       yyformat[sizeof yyunexpected - 1] = '\0'; 
    985       break; 
    986          } 
    987        yyarg[yycount++] = yytname[yyx]; 
    988        yysize1 = yysize + yytnamerr (0, yytname[yyx]); 
    989        yysize_overflow |= (yysize1 < yysize); 
    990        yysize = yysize1; 
    991        yyfmt = yystpcpy (yyfmt, yyprefix); 
    992        yyprefix = yyor; 
    993      } 
    994  
    995       yyf = YY_(yyformat); 
    996       yysize1 = yysize + yystrlen (yyf); 
    997       yysize_overflow |= (yysize1 < yysize); 
    998       yysize = yysize1; 
    999  
    1000       if (yysize_overflow) 
    1001    return YYSIZE_MAXIMUM; 
    1002  
    1003       if (yyresult) 
    1004    { 
    1005      /* Avoid sprintf, as that infringes on the user's name space. 
    1006         Don't have undefined behavior even if the translation 
    1007         produced a string with the wrong number of "%s"s.  */ 
    1008      char *yyp = yyresult; 
    1009      int yyi = 0; 
    1010      while ((*yyp = *yyf) != '\0') 
    1011        { 
    1012          if (*yyp == '%' && yyf[1] == 's' && yyi < yycount) 
    1013       { 
    1014         yyp += yytnamerr (yyp, yyarg[yyi++]); 
    1015         yyf += 2; 
    1016       } 
    1017          else 
    1018       { 
    1019         yyp++; 
    1020         yyf++; 
    1021       } 
    1022        } 
    1023    } 
    1024       return yysize; 
     972      int yyn = yypact[*yyssp]; 
     973      yyarg[yycount++] = yytname[yytoken]; 
     974      if (!yypact_value_is_default (yyn)) 
     975        { 
     976          /* Start YYX at -YYN if negative to avoid negative indexes in 
     977             YYCHECK.  In other words, skip the first -YYN actions for 
     978             this state because they are default actions.  */ 
     979          int yyxbegin = yyn < 0 ? -yyn : 0; 
     980          /* Stay within bounds of both yycheck and yytname.  */ 
     981          int yychecklim = YYLAST - yyn + 1; 
     982          int yyxend = yychecklim < YYNTOKENS ? yychecklim : YYNTOKENS; 
     983          int yyx; 
     984 
     985          for (yyx = yyxbegin; yyx < yyxend; ++yyx) 
     986            if (yycheck[yyx + yyn] == yyx && yyx != YYTERROR 
     987                && !yytable_value_is_error (yytable[yyx + yyn])) 
     988              { 
     989                if (yycount == YYERROR_VERBOSE_ARGS_MAXIMUM) 
     990                  { 
     991                    yycount = 1; 
     992                    yysize = yysize0; 
     993                    break; 
     994                  } 
     995                yyarg[yycount++] = yytname[yyx]; 
     996                { 
     997                  YYSIZE_T yysize1 = yysize + yytnamerr (YY_NULL, yytname[yyx]); 
     998                  if (! (yysize <= yysize1 
     999                         && yysize1 <= YYSTACK_ALLOC_MAXIMUM)) 
     1000                    return 2; 
     1001                  yysize = yysize1; 
     1002                } 
     1003              } 
     1004        } 
    10251005    } 
     1006 
     1007  switch (yycount) 
     1008    { 
     1009# define YYCASE_(N, S)                      \ 
     1010      case N:                               \ 
     1011        yyformat = S;                       \ 
     1012      break 
     1013      YYCASE_(0, YY_("syntax error")); 
     1014      YYCASE_(1, YY_("syntax error, unexpected %s")); 
     1015      YYCASE_(2, YY_("syntax error, unexpected %s, expecting %s")); 
     1016      YYCASE_(3, YY_("syntax error, unexpected %s, expecting %s or %s")); 
     1017      YYCASE_(4, YY_("syntax error, unexpected %s, expecting %s or %s or %s")); 
     1018      YYCASE_(5, YY_("syntax error, unexpected %s, expecting %s or %s or %s or %s")); 
     1019# undef YYCASE_ 
     1020    } 
     1021 
     1022  { 
     1023    YYSIZE_T yysize1 = yysize + yystrlen (yyformat); 
     1024    if (! (yysize <= yysize1 && yysize1 <= YYSTACK_ALLOC_MAXIMUM)) 
     1025      return 2; 
     1026    yysize = yysize1; 
     1027  } 
     1028 
     1029  if (*yymsg_alloc < yysize) 
     1030    { 
     1031      *yymsg_alloc = 2 * yysize; 
     1032      if (! (yysize <= *yymsg_alloc 
     1033             && *yymsg_alloc <= YYSTACK_ALLOC_MAXIMUM)) 
     1034        *yymsg_alloc = YYSTACK_ALLOC_MAXIMUM; 
     1035      return 1; 
     1036    } 
     1037 
     1038  /* Avoid sprintf, as that infringes on the user's name space. 
     1039     Don't have undefined behavior even if the translation 
     1040     produced a string with the wrong number of "%s"s.  */ 
     1041  { 
     1042    char *yyp = *yymsg; 
     1043    int yyi = 0; 
     1044    while ((*yyp = *yyformat) != '\0') 
     1045      if (*yyp == '%' && yyformat[1] == 's' && yyi < yycount) 
     1046        { 
     1047          yyp += yytnamerr (yyp, yyarg[yyi++]); 
     1048          yyformat += 2; 
     1049        } 
     1050      else 
     1051        { 
     1052          yyp++; 
     1053          yyformat++; 
     1054        } 
     1055  } 
     1056  return 0; 
    10261057} 
    10271058#endif /* YYERROR_VERBOSE */ 
    1028  
    1029  
    10301059 
    10311060/*-----------------------------------------------. 
     
    10561085 
    10571086      default: 
    1058    break; 
     1087        break; 
    10591088    } 
    10601089} 
     
    10621091 
    10631092 
    1064 /* Prevent warnings from -Wmissing-prototypes.  */ 
    1065  
    1066 #ifdef YYPARSE_PARAM 
    1067 #if defined __STDC__ || defined __cplusplus 
    1068 int yyparse (void *YYPARSE_PARAM); 
    1069 #else 
    1070 int yyparse (); 
    1071 #endif 
    1072 #else /* ! YYPARSE_PARAM */ 
    1073 #if defined __STDC__ || defined __cplusplus 
    1074 int yyparse (void); 
    1075 #else 
    1076 int yyparse (); 
    1077 #endif 
    1078 #endif /* ! YYPARSE_PARAM */ 
    1079  
    1080  
    1081  
    1082 /* The look-ahead symbol.  */ 
     1093 
     1094/* The lookahead symbol.  */ 
    10831095int yychar; 
    10841096 
    1085 /* The semantic value of the look-ahead symbol.  */ 
    1086 YYSTYPE yylval; 
     1097 
     1098#ifndef YY_IGNORE_MAYBE_UNINITIALIZED_BEGIN 
     1099# define YY_IGNORE_MAYBE_UNINITIALIZED_BEGIN 
     1100# define YY_IGNORE_MAYBE_UNINITIALIZED_END 
     1101#endif 
     1102#ifndef YY_INITIAL_VALUE 
     1103# define YY_INITIAL_VALUE(Value) /* Nothing. */ 
     1104#endif 
     1105 
     1106/* The semantic value of the lookahead symbol.  */ 
     1107YYSTYPE yylval YY_INITIAL_VALUE(yyval_default); 
    10871108 
    10881109/* Number of syntax errors so far.  */ 
    10891110int yynerrs; 
    1090  
    10911111 
    10921112 
     
    11171137#endif 
    11181138{ 
    1119    
    1120   int yystate; 
     1139    int yystate; 
     1140    /* Number of tokens to shift before error messages enabled.  */ 
     1141    int yyerrstatus; 
     1142 
     1143    /* The stacks and their tools: 
     1144       `yyss': related to states. 
     1145       `yyvs': related to semantic values. 
     1146 
     1147       Refer to the stacks through separate pointers, to allow yyoverflow 
     1148       to reallocate them elsewhere.  */ 
     1149 
     1150    /* The state stack.  */ 
     1151    yytype_int16 yyssa[YYINITDEPTH]; 
     1152    yytype_int16 *yyss; 
     1153    yytype_int16 *yyssp; 
     1154 
     1155    /* The semantic value stack.  */ 
     1156    YYSTYPE yyvsa[YYINITDEPTH]; 
     1157    YYSTYPE *yyvs; 
     1158    YYSTYPE *yyvsp; 
     1159 
     1160    YYSIZE_T yystacksize; 
     1161 
    11211162  int yyn; 
    11221163  int yyresult; 
    1123   /* Number of tokens to shift before error messages enabled.  */ 
    1124   int yyerrstatus; 
    1125   /* Look-ahead token as an internal (translated) token number.  */ 
     1164  /* Lookahead token as an internal (translated) token number.  */ 
    11261165  int yytoken = 0; 
     1166  /* The variables used to return semantic value and location from the 
     1167     action routines.  */ 
     1168  YYSTYPE yyval; 
     1169 
    11271170#if YYERROR_VERBOSE 
    11281171  /* Buffer for error messages, and its allocated size.  */ 
     
    11321175#endif 
    11331176 
    1134   /* Three stacks and their tools: 
    1135      `yyss': related to states, 
    1136      `yyvs': related to semantic values, 
    1137      `yyls': related to locations. 
    1138  
    1139      Refer to the stacks thru separate pointers, to allow yyoverflow 
    1140      to reallocate them elsewhere.  */ 
    1141  
    1142   /* The state stack.  */ 
    1143   yytype_int16 yyssa[YYINITDEPTH]; 
    1144   yytype_int16 *yyss = yyssa; 
    1145   yytype_int16 *yyssp; 
    1146  
    1147   /* The semantic value stack.  */ 
    1148   YYSTYPE yyvsa[YYINITDEPTH]; 
    1149   YYSTYPE *yyvs = yyvsa; 
    1150   YYSTYPE *yyvsp; 
    1151  
    1152  
    1153  
    11541177#define YYPOPSTACK(N)   (yyvsp -= (N), yyssp -= (N)) 
    1155  
    1156   YYSIZE_T yystacksize = YYINITDEPTH; 
    1157  
    1158   /* The variables used to return semantic value and location from the 
    1159      action routines.  */ 
    1160   YYSTYPE yyval; 
    1161  
    11621178 
    11631179  /* The number of symbols on the RHS of the reduced rule. 
     
    11651181  int yylen = 0; 
    11661182 
     1183  yyssp = yyss = yyssa; 
     1184  yyvsp = yyvs = yyvsa; 
     1185  yystacksize = YYINITDEPTH; 
     1186 
    11671187  YYDPRINTF ((stderr, "Starting parse\n")); 
    11681188 
     
    11701190  yyerrstatus = 0; 
    11711191  yynerrs = 0; 
    1172   yychar = YYEMPTY;     /* Cause a token to be read.  */ 
    1173  
    1174   /* Initialize stack pointers. 
    1175      Waste one element of value and location stack 
    1176      so that they stay on the same level as the state stack. 
    1177      The wasted elements are never initialized.  */ 
    1178  
    1179   yyssp = yyss; 
    1180   yyvsp = yyvs; 
    1181  
     1192  yychar = YYEMPTY; /* Cause a token to be read.  */ 
    11821193  goto yysetstate; 
    11831194 
     
    12061217   yytype_int16 *yyss1 = yyss; 
    12071218 
    1208  
    12091219   /* Each stack pointer address is followed by the size of the 
    12101220      data in use in that stack, in bytes.  This used to be a 
     
    12141224          &yyss1, yysize * sizeof (*yyssp), 
    12151225          &yyvs1, yysize * sizeof (*yyvsp), 
    1216  
    12171226          &yystacksize); 
    12181227 
     
    12371246   if (! yyptr) 
    12381247     goto yyexhaustedlab; 
    1239    YYSTACK_RELOCATE (yyss); 
    1240    YYSTACK_RELOCATE (yyvs); 
    1241  
     1248   YYSTACK_RELOCATE (yyss_alloc, yyss); 
     1249   YYSTACK_RELOCATE (yyvs_alloc, yyvs); 
    12421250#  undef YYSTACK_RELOCATE 
    12431251   if (yyss1 != yyssa) 
     
    12501258      yyvsp = yyvs + yysize - 1; 
    12511259 
    1252  
    12531260      YYDPRINTF ((stderr, "Stack size increased to %lu\n", 
    12541261        (unsigned long int) yystacksize)); 
     
    12591266 
    12601267  YYDPRINTF ((stderr, "Entering state %d\n", yystate)); 
     1268 
     1269  if (yystate == YYFINAL) 
     1270    YYACCEPT; 
    12611271 
    12621272  goto yybackup; 
     
    12681278 
    12691279  /* Do appropriate processing given the current state.  Read a 
    1270      look-ahead token if we need one and don't already have one.  */ 
    1271  
    1272   /* First try to decide what to do without reference to look-ahead token.  */ 
     1280     lookahead token if we need one and don't already have one.  */ 
     1281 
     1282  /* First try to decide what to do without reference to lookahead token.  */ 
    12731283  yyn = yypact[yystate]; 
    1274   if (yyn == YYPACT_NINF) 
     1284  if (yypact_value_is_default (yyn)) 
    12751285    goto yydefault; 
    12761286 
    1277   /* Not known => get a look-ahead token if don't already have one.  */ 
    1278  
    1279   /* YYCHAR is either YYEMPTY or YYEOF or a valid look-ahead symbol.  */ 
     1287  /* Not known => get a lookahead token if don't already have one.  */ 
     1288 
     1289  /* YYCHAR is either YYEMPTY or YYEOF or a valid lookahead symbol.  */ 
    12801290  if (yychar == YYEMPTY) 
    12811291    { 
     
    13031313  if (yyn <= 0) 
    13041314    { 
    1305       if (yyn == 0 || yyn == YYTABLE_NINF) 
    1306    goto yyerrlab; 
     1315      if (yytable_value_is_error (yyn)) 
     1316        goto yyerrlab; 
    13071317      yyn = -yyn; 
    13081318      goto yyreduce; 
    13091319    } 
    1310  
    1311   if (yyn == YYFINAL) 
    1312     YYACCEPT; 
    13131320 
    13141321  /* Count tokens shifted since error; after three, turn off error 
     
    13171324    yyerrstatus--; 
    13181325 
    1319   /* Shift the look-ahead token.  */ 
     1326  /* Shift the lookahead token.  */ 
    13201327  YY_SYMBOL_PRINT ("Shifting", yytoken, &yylval, &yylloc); 
    13211328 
    1322   /* Discard the shifted token unless it is eof.  */ 
    1323   if (yychar != YYEOF) 
    1324     yychar = YYEMPTY; 
     1329  /* Discard the shifted token.  */ 
     1330  yychar = YYEMPTY; 
    13251331 
    13261332  yystate = yyn; 
     1333  YY_IGNORE_MAYBE_UNINITIALIZED_BEGIN 
    13271334  *++yyvsp = yylval; 
     1335  YY_IGNORE_MAYBE_UNINITIALIZED_END 
    13281336 
    13291337  goto yynewstate; 
     
    13621370    { 
    13631371        case 5: 
     1372/* Line 1807 of yacc.c  */ 
    13641373#line 76 "convert.y" 
    1365     { initdimprob(1,(yyvsp[(2) - (3)].na),"0","0"); ;} 
     1374    { initdimprob(1,(yyvsp[(2) - (3)].na),"0","0"); } 
    13661375    break; 
    13671376 
    13681377  case 6: 
     1378/* Line 1807 of yacc.c  */ 
    13691379#line 77 "convert.y" 
    1370     { initdimprob(2,(yyvsp[(2) - (5)].na), (yyvsp[(4) - (5)].na),"0"); ;} 
     1380    { initdimprob(2,(yyvsp[(2) - (5)].na), (yyvsp[(4) - (5)].na),"0"); } 
    13711381    break; 
    13721382 
    13731383  case 7: 
     1384/* Line 1807 of yacc.c  */ 
    13741385#line 78 "convert.y" 
    1375     { initdimprob(3,(yyvsp[(2) - (7)].na), (yyvsp[(4) - (7)].na), (yyvsp[(6) - (7)].na)); ;} 
     1386    { initdimprob(3,(yyvsp[(2) - (7)].na), (yyvsp[(4) - (7)].na), (yyvsp[(6) - (7)].na)); } 
    13761387    break; 
    13771388 
    13781389  case 8: 
     1390/* Line 1807 of yacc.c  */ 
    13791391#line 80 "convert.y" 
    13801392    { 
    13811393            listofmodules = Addtolistnom((yyvsp[(2) - (3)].na),listofmodules,0); 
    13821394            Addmoduletothelist((yyvsp[(2) - (3)].na)); 
    1383         ;} 
     1395        } 
    13841396    break; 
    13851397 
    13861398  case 9: 
     1399/* Line 1807 of yacc.c  */ 
    13871400#line 85 "convert.y" 
    13881401    { 
     
    14001413                exit(0); 
    14011414            } 
    1402         ;} 
     1415        } 
    14031416    break; 
    14041417 
    14051418  case 10: 
     1419/* Line 1807 of yacc.c  */ 
    14061420#line 101 "convert.y" 
    14071421    { 
    14081422            Add_NotGridDepend_Var_1((yyvsp[(3) - (4)].na)); 
    1409         ;} 
     1423        } 
    14101424    break; 
    14111425 
    14121426  case 11: 
     1427/* Line 1807 of yacc.c  */ 
    14131428#line 105 "convert.y" 
    14141429    { 
    14151430            if (!strcasecmp((yyvsp[(2) - (3)].na),"FIXED_GRIDS"))      fixedgrids = 1; 
    14161431            if (!strcasecmp((yyvsp[(2) - (3)].na),"ONLY_FIXED_GRIDS")) onlyfixedgrids = 1; 
    1417         ;} 
     1432        } 
    14181433    break; 
    14191434 
    14201435 
    1421 /* Line 1267 of yacc.c.  */ 
    1422 #line 1420 "convert.tab.c" 
     1436/* Line 1807 of yacc.c  */ 
     1437#line 1438 "convert.tab.c" 
    14231438      default: break; 
    14241439    } 
     1440  /* User semantic actions sometimes alter yychar, and that requires 
     1441     that yytoken be updated with the new translation.  We take the 
     1442     approach of translating immediately before every use of yytoken. 
     1443     One alternative is translating here after every semantic action, 
     1444     but that translation would be missed if the semantic action invokes 
     1445     YYABORT, YYACCEPT, or YYERROR immediately after altering yychar or 
     1446     if it invokes YYBACKUP.  In the case of YYABORT or YYACCEPT, an 
     1447     incorrect destructor might then be invoked immediately.  In the 
     1448     case of YYERROR or YYBACKUP, subsequent parser actions might lead 
     1449     to an incorrect destructor call or verbose syntax error message 
     1450     before the lookahead is translated.  */ 
    14251451  YY_SYMBOL_PRINT ("-> $$ =", yyr1[yyn], &yyval, &yyloc); 
    14261452 
     
    14301456 
    14311457  *++yyvsp = yyval; 
    1432  
    14331458 
    14341459  /* Now `shift' the result of the reduction.  Determine what state 
     
    14511476`------------------------------------*/ 
    14521477yyerrlab: 
     1478  /* Make sure we have latest lookahead translation.  See comments at 
     1479     user semantic actions for why this is necessary.  */ 
     1480  yytoken = yychar == YYEMPTY ? YYEMPTY : YYTRANSLATE (yychar); 
     1481 
    14531482  /* If not already recovering from an error, report this error.  */ 
    14541483  if (!yyerrstatus) 
     
    14581487      yyerror (YY_("syntax error")); 
    14591488#else 
     1489# define YYSYNTAX_ERROR yysyntax_error (&yymsg_alloc, &yymsg, \ 
     1490                                        yyssp, yytoken) 
    14601491      { 
    1461    YYSIZE_T yysize = yysyntax_error (0, yystate, yychar); 
    1462    if (yymsg_alloc < yysize && yymsg_alloc < YYSTACK_ALLOC_MAXIMUM) 
    1463      { 
    1464        YYSIZE_T yyalloc = 2 * yysize; 
    1465        if (! (yysize <= yyalloc && yyalloc <= YYSTACK_ALLOC_MAXIMUM)) 
    1466          yyalloc = YYSTACK_ALLOC_MAXIMUM; 
    1467        if (yymsg != yymsgbuf) 
    1468          YYSTACK_FREE (yymsg); 
    1469        yymsg = (char *) YYSTACK_ALLOC (yyalloc); 
    1470        if (yymsg) 
    1471          yymsg_alloc = yyalloc; 
    1472        else 
    1473          { 
    1474       yymsg = yymsgbuf; 
    1475       yymsg_alloc = sizeof yymsgbuf; 
    1476          } 
    1477      } 
    1478  
    1479    if (0 < yysize && yysize <= yymsg_alloc) 
    1480      { 
    1481        (void) yysyntax_error (yymsg, yystate, yychar); 
    1482        yyerror (yymsg); 
    1483      } 
    1484    else 
    1485      { 
    1486        yyerror (YY_("syntax error")); 
    1487        if (yysize != 0) 
    1488          goto yyexhaustedlab; 
    1489      } 
     1492        char const *yymsgp = YY_("syntax error"); 
     1493        int yysyntax_error_status; 
     1494        yysyntax_error_status = YYSYNTAX_ERROR; 
     1495        if (yysyntax_error_status == 0) 
     1496          yymsgp = yymsg; 
     1497        else if (yysyntax_error_status == 1) 
     1498          { 
     1499            if (yymsg != yymsgbuf) 
     1500              YYSTACK_FREE (yymsg); 
     1501            yymsg = (char *) YYSTACK_ALLOC (yymsg_alloc); 
     1502            if (!yymsg) 
     1503              { 
     1504                yymsg = yymsgbuf; 
     1505                yymsg_alloc = sizeof yymsgbuf; 
     1506                yysyntax_error_status = 2; 
     1507              } 
     1508            else 
     1509              { 
     1510                yysyntax_error_status = YYSYNTAX_ERROR; 
     1511                yymsgp = yymsg; 
     1512              } 
     1513          } 
     1514        yyerror (yymsgp); 
     1515        if (yysyntax_error_status == 2) 
     1516          goto yyexhaustedlab; 
    14901517      } 
     1518# undef YYSYNTAX_ERROR 
    14911519#endif 
    14921520    } 
     
    14961524  if (yyerrstatus == 3) 
    14971525    { 
    1498       /* If just tried and failed to reuse look-ahead token after an 
     1526      /* If just tried and failed to reuse lookahead token after an 
    14991527    error, discard it.  */ 
    15001528 
     
    15131541    } 
    15141542 
    1515   /* Else will try to reuse look-ahead token after shifting the error 
     1543  /* Else will try to reuse lookahead token after shifting the error 
    15161544     token.  */ 
    15171545  goto yyerrlab1; 
     
    15471575    { 
    15481576      yyn = yypact[yystate]; 
    1549       if (yyn != YYPACT_NINF) 
     1577      if (!yypact_value_is_default (yyn)) 
    15501578   { 
    15511579     yyn += YYTERROR; 
     
    15701598    } 
    15711599 
    1572   if (yyn == YYFINAL) 
    1573     YYACCEPT; 
    1574  
     1600  YY_IGNORE_MAYBE_UNINITIALIZED_BEGIN 
    15751601  *++yyvsp = yylval; 
     1602  YY_IGNORE_MAYBE_UNINITIALIZED_END 
    15761603 
    15771604 
     
    15971624  goto yyreturn; 
    15981625 
    1599 #ifndef yyoverflow 
     1626#if !defined yyoverflow || YYERROR_VERBOSE 
    16001627/*-------------------------------------------------. 
    16011628| yyexhaustedlab -- memory exhaustion comes here.  | 
     
    16081635 
    16091636yyreturn: 
    1610   if (yychar != YYEOF && yychar != YYEMPTY) 
    1611      yydestruct ("Cleanup: discarding lookahead", 
    1612        yytoken, &yylval); 
     1637  if (yychar != YYEMPTY) 
     1638    { 
     1639      /* Make sure we have latest lookahead translation.  See comments at 
     1640         user semantic actions for why this is necessary.  */ 
     1641      yytoken = YYTRANSLATE (yychar); 
     1642      yydestruct ("Cleanup: discarding lookahead", 
     1643                  yytoken, &yylval); 
     1644    } 
    16131645  /* Do not reclaim the symbols of the rule which action triggered 
    16141646     this YYABORT or YYACCEPT.  */ 
     
    16341666 
    16351667 
     1668/* Line 2055 of yacc.c  */ 
    16361669#line 110 "convert.y" 
    16371670 
     
    16571690    int infreegiven ; 
    16581691    int infixedgiven ; 
    1659     int lengthmainfile; 
    16601692 
    16611693    char filetoparse[LONG_FNAME]; 
     
    16871719    tmpuselocallist = (listusemodule *) NULL; 
    16881720    List_ContainsSubroutine = (listnom *) NULL; 
     1721    List_Do_labels = (listname *) NULL; 
    16891722    oldfortran_out = (FILE *) NULL; 
    16901723 
    1691     if (argc < 2) print_usage(); 
    1692      
     1724    if ( argc < 2 ) 
     1725        print_usage(); 
     1726 
    16931727    strcpy(config_file, argv[1]); 
    16941728    strcpy(work_dir, "."); 
     
    17841818            strcpy(filetoparse, argv[i+1]); 
    17851819            i++; 
    1786             lengthmainfile = strlen(filetoparse); 
    1787             if (!strcasecmp(&filetoparse[lengthmainfile-4], ".f90")) 
    1788             { 
    1789                 infixed = 0; 
    1790                 infree = 1; 
    1791             } 
    1792             else 
    1793             { 
    1794                 infixed = 1; 
    1795                 infree = 0; 
    1796             } 
     1820            infree  = (strstr(filetoparse, ".f90") != NULL) || (strstr(filetoparse, ".F90") != NULL); 
     1821            infixed = ! infree; 
    17971822        } 
    17981823        else if (!strcasecmp(argv[i], "-free")) 
     
    19271952    /* Build new subroutines                                                   */ 
    19281953    firstpass = 0; 
     1954    /* 
     1955    printf("**********************************\n"); 
     1956    printf("SECOND PASSES \n"); 
     1957    printf("**********************************\n"); 
     1958    */ 
    19291959    process_fortran(filetoparse); 
    19301960 
     
    19892019    return 0; 
    19902020} 
    1991  
    19922021#line 2 "convert.yy.c" 
    19932022 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/EXTERNAL/AGRIF/LIB/toamr.c

    r5819 r6258  
    4747        "tabvars_i"     // v_catvar == 4 
    4848    }; 
     49 
    4950    return tname[var->v_catvar];    // v_catvar should never be ouside the range [0:4]. 
    5051} 
     
    137138    static char tname_1[LONG_C]; 
    138139    static char tname_2[LONG_C]; 
    139  
     140     
    140141    if ( iorindice == 0 ) sprintf(tname_1, "Agrif_Gr %% %s(%d)", tabvarsname(var), var->v_indicetabvars); 
    141142    else                  sprintf(tname_1, "Agrif_Gr %% %s(i)",  tabvarsname(var)); 
    142143 
    143     if (!strcasecmp(var->v_typevar, "REAL")) 
     144    if (!strcasecmp(var->v_typevar, "real")) 
    144145    { 
    145146        if      ( !strcasecmp(var->v_nameinttypename,"8") ) sprintf(tname_2, "%% darray%d", var->v_nbdim); 
    146147        else if ( !strcasecmp(var->v_nameinttypename,"4") ) sprintf(tname_2, "%% sarray%d", var->v_nbdim); 
    147         else                                                sprintf(tname_2, "%% array%d",  var->v_nbdim); 
     148        else if ( !strcasecmp(var->v_precision,"8") ) sprintf(tname_2, "%% darray%d", var->v_nbdim); 
     149        else if ( !strcasecmp(var->v_precision,"4") ) sprintf(tname_2, "%% sarray%d", var->v_nbdim);         
     150        else   
     151          { 
     152          sprintf(tname_2, "%% array%d",  var->v_nbdim); 
     153          } 
    148154    } 
    149155    else if (!strcasecmp(var->v_typevar, "integer")) 
     
    195201        if (!strcasecmp(var->v_typevar, "REAL")) 
    196202        { 
    197             if      ( !strcasecmp(var->v_nameinttypename,"8") ) sprintf(tname_2, "%% darray%d", var->v_nbdim); 
    198             else if ( !strcasecmp(var->v_nameinttypename,"4") ) sprintf(tname_2, "%% sarray%d", var->v_nbdim); 
    199             else                                                sprintf(tname_2, "%% array%d", var->v_nbdim); 
     203            if      ( !strcasecmp(var->v_nameinttypename,"8") ) sprintf(tname_2, "darray%d", var->v_nbdim); 
     204            else if ( !strcasecmp(var->v_nameinttypename,"4") ) sprintf(tname_2, "sarray%d", var->v_nbdim); 
     205            else if ( !strcasecmp(var->v_precision,"8") ) sprintf(tname_2, "darray%d", var->v_nbdim); 
     206            else if ( !strcasecmp(var->v_precision,"4") ) sprintf(tname_2, "sarray%d", var->v_nbdim); 
     207            else sprintf(tname_2, "array%d", var->v_nbdim); 
    200208        } 
    201209        else if (!strcasecmp(var->v_typevar, "INTEGER")) 
    202210        { 
    203             sprintf(tname_2, "%% iarray%d", var->v_nbdim); 
     211            sprintf(tname_2, "iarray%d", var->v_nbdim); 
    204212        } 
    205213        else if (!strcasecmp(var->v_typevar, "LOGICAL")) 
    206214        { 
    207             sprintf(tname_2, "%% larray%d", var->v_nbdim); 
     215            sprintf(tname_2, "larray%d", var->v_nbdim); 
    208216        } 
    209217        else if (!strcasecmp(var->v_typevar, "CHARACTER")) 
    210218        { 
    211219            WARNING_CharSize(var); 
    212             sprintf(tname_2, "%% carray%d", var->v_nbdim); 
    213         } 
    214         strcat(tname_1, tname_2); 
     220            sprintf(tname_2, "carray%d", var->v_nbdim); 
     221        } 
     222        if (var->v_pointerdeclare) 
     223        { 
     224                strcat(tname_1,"%p"); 
     225                strcat(tname_1, tname_2); 
     226        } 
     227        else 
     228        { 
     229                strcat(tname_1,"%"); 
     230                strcat(tname_1, tname_2); 
     231        } 
    215232    } 
    216233    Save_Length(tname_1, 46); 
     
    232249 
    233250    sprintf(tname_1, "(%d)", var->v_indicetabvars); 
    234  
    235     if (!strcasecmp (var->v_typevar, "REAL")) 
    236     { 
    237         if      ( !strcasecmp(var->v_nameinttypename,"8") ) sprintf(tname_2, "%% darray%d", var->v_nbdim); 
    238         else if ( !strcasecmp(var->v_nameinttypename,"4") ) sprintf(tname_2, "%% sarray%d", var->v_nbdim); 
    239         else                                                sprintf(tname_2, "%% array%d", var->v_nbdim); 
    240     } 
    241     else if (!strcasecmp(var->v_typevar, "INTEGER")) 
    242     { 
    243         sprintf(tname_2, "%% iarray%d", var->v_nbdim); 
    244     } 
    245     else if (!strcasecmp(var->v_typevar, "LOGICAL")) 
    246     { 
    247         sprintf(tname_2, "%% larray%d", var->v_nbdim); 
    248     } 
    249     else if (!strcasecmp(var->v_typevar, "CHARACTER")) 
    250     { 
    251         WARNING_CharSize(var); 
    252         sprintf(tname_2, "%% carray%d", var->v_nbdim); 
    253     } 
    254  
    255     strcat(tname_1, tname_2); 
     251     
     252        if (!strcasecmp(var->v_typevar, "REAL")) 
     253        { 
     254            if      ( !strcasecmp(var->v_nameinttypename,"8") ) sprintf(tname_2, "darray%d", var->v_nbdim); 
     255            else if ( !strcasecmp(var->v_nameinttypename,"4") ) sprintf(tname_2, "sarray%d", var->v_nbdim); 
     256            else if ( !strcasecmp(var->v_precision,"8") ) sprintf(tname_2, "darray%d", var->v_nbdim); 
     257            else if ( !strcasecmp(var->v_precision,"4") ) sprintf(tname_2, "sarray%d", var->v_nbdim); 
     258            else sprintf(tname_2, "array%d", var->v_nbdim); 
     259        } 
     260        else if (!strcasecmp(var->v_typevar, "INTEGER")) 
     261        { 
     262            sprintf(tname_2, "iarray%d", var->v_nbdim); 
     263        } 
     264        else if (!strcasecmp(var->v_typevar, "LOGICAL")) 
     265        { 
     266            sprintf(tname_2, "larray%d", var->v_nbdim); 
     267        } 
     268        else if (!strcasecmp(var->v_typevar, "CHARACTER")) 
     269        { 
     270            WARNING_CharSize(var); 
     271            sprintf(tname_2, "carray%d", var->v_nbdim); 
     272        } 
     273        if (var->v_pointerdeclare) 
     274        { 
     275                strcat(tname_1,"%p"); 
     276                strcat(tname_1, tname_2); 
     277        } 
     278        else 
     279        { 
     280                strcat(tname_1,"%"); 
     281                strcat(tname_1, tname_2); 
     282        } 
     283 
    256284    Save_Length(tname_1, 46); 
    257285 
     
    535563    listvar *parcoursprec; 
    536564    listvar *parcours1; 
     565    listname *parcours_name; 
     566    listname *parcours_name_array; 
     567    listdoloop *parcours_loop; 
    537568    FILE *allocationagrif; 
    538569    FILE *paramtoamr; 
    539570    char ligne[LONG_M]; 
    540571    char ligne2[LONG_M]; 
     572    char ligne3[LONG_M]; 
    541573    variable *v; 
    542574    int IndiceMax; 
     
    550582    listindice *parcoursindic; 
    551583    int i; 
     584    int nb_initial; 
     585    int is_parameter_local; 
     586    int global_check; 
    552587 
    553588    parcoursprec = (listvar *) NULL; 
     
    561596            sprintf(ligne,"alloc_agrif_%s.h",parcours_nom->o_nom); 
    562597            allocationagrif = open_for_write(ligne); 
     598 
    563599            fprintf(allocationagrif,"#include \"Param_toamr_%s.h\" \n", parcours_nom->o_nom); 
    564  
    565600            sprintf(ligne,"Param_toamr_%s.h",parcours_nom->o_nom); 
    566601            paramtoamr = open_for_write(ligne); 
     
    568603            list_indic = (listindice **) calloc(NB_CAT_VARIABLES,sizeof(listindice *)); 
    569604 
    570 //             shouldincludempif = 1 ; 
     605             shouldincludempif = 1 ; 
    571606            parcours = List_Common_Var; 
    572607            while ( parcours ) 
     
    621656                                        IndiceMin = parcours->var->v_indicetabvars; 
    622657                                        IndiceMax = parcours->var->v_indicetabvars+compteur; 
    623                                         sprintf(ligne,"    allocate(%s", vargridnametabvars(v,1)); 
     658                                        sprintf(ligne,"    if (.not. allocated(%s)) allocate(%s", vargridnametabvars(v,1), vargridnametabvars(v,1)); 
    624659                                        sprintf(ligne2,"%s)", vargridparam(v)); 
    625660                                        strcat(ligne,ligne2); 
     
    639674                                    else 
    640675                                    { 
    641                                         sprintf(ligne,"allocate(%s", vargridnametabvars(v,0)); 
     676                                        sprintf(ligne,"if (.not. allocated(%s)) allocate(%s", vargridnametabvars(v,0), vargridnametabvars(v,0)); 
    642677                                        sprintf(ligne2,"%s)", vargridparam(v)); 
    643678                                        strcat(ligne,ligne2); 
     
    648683                                        list_indic[parcours->var->v_catvar] = parcoursindic; 
    649684                                    } 
    650                                     neededparameter = writedeclarationintoamr(List_Parameter_Var, 
    651                                                         paramtoamr,v,parcours_nom->o_nom,neededparameter,v->v_commonname); 
     685 
     686                                    global_check = 0; 
     687                                    is_parameter_local = writedeclarationintoamr(List_Parameter_Var, 
     688                                                        paramtoamr,v,parcours_nom->o_nom,&neededparameter,v->v_commonname,global_check); 
     689                                    if (is_parameter_local == 0) 
     690                                    { 
     691                                    global_check = 1; 
     692                                    is_parameter_local = writedeclarationintoamr(List_GlobalParameter_Var, 
     693                                                        paramtoamr,v,parcours_nom->o_nom,&neededparameter,v->v_commonname,global_check); 
     694                                    } 
    652695                                } 
    653696                            } /* end of the allocation part                                       */ 
    654697                            /*                INITIALISATION                                      */ 
    655                             if ( strcasecmp(v->v_initialvalue,"") ) 
     698                            if ( v->v_initialvalue ) 
     699                            { 
     700                            parcours_name = v->v_initialvalue; 
     701                            parcours_name_array = v->v_initialvalue_array; 
     702                            if (parcours_name_array) 
     703                            { 
     704                            while (parcours_name) 
    656705                            { 
    657706                                strcpy(ligne, vargridnametabvars(v,0)); 
     707                                if (parcours_name_array) 
     708                                { 
     709                                if (strcasecmp(parcours_name_array->n_name,"") ) 
     710                                { 
     711                                sprintf(ligne2,"(%s)",parcours_name_array->n_name); 
     712                                strcat(ligne,ligne2); 
     713                                } 
     714                                } 
    658715                                /* We should modify the initialvalue in the case of variable has been defined with others variables */ 
    659                                 strcpy(initialvalue,ChangeTheInitalvaluebyTabvarsName(v->v_initialvalue,List_Global_Var)); 
    660                                 if ( !strcasecmp(initialvalue,v->v_initialvalue) ) 
    661                                 { 
    662                                     strcpy(initialvalue,ChangeTheInitalvaluebyTabvarsName(v->v_initialvalue,List_Common_Var)); 
    663                                 } 
    664                                 if ( !strcasecmp(initialvalue,v->v_initialvalue) ) 
    665                                 { 
    666                                     strcpy(initialvalue,ChangeTheInitalvaluebyTabvarsName(v->v_initialvalue,List_ModuleUsed_Var)); 
     716                                strcpy(initialvalue,ChangeTheInitalvaluebyTabvarsName(parcours_name->n_name,List_Global_Var)); 
     717                                if ( !strcasecmp(initialvalue,parcours_name->n_name) ) 
     718                                { 
     719                                    strcpy(initialvalue,ChangeTheInitalvaluebyTabvarsName(parcours_name->n_name,List_Common_Var)); 
     720                                } 
     721                                if ( !strcasecmp(initialvalue,parcours_name->n_name) ) 
     722                                { 
     723                                    strcpy(initialvalue,ChangeTheInitalvaluebyTabvarsName(parcours_name->n_name,List_ModuleUsed_Var)); 
    667724                                } 
    668725                                strcat (ligne," = "); 
    669726 
    670                                 if (v->v_nbdim == 0) 
     727                                if (v->v_nbdim >= 0) 
    671728                                { 
    672729                                    strcpy(ligne2,initialvalue); 
     
    678735                                strcat(ligne,ligne2); 
    679736                                tofich(allocationagrif,ligne,1); 
     737                              
     738                             parcours_name = parcours_name->suiv; 
     739                             if (parcours_name_array) parcours_name_array = parcours_name_array->suiv; 
     740                            } 
     741                            } 
     742                            else 
     743                            { 
     744                            strcpy(ligne, vargridnametabvars(v,0)); 
     745                            strcat (ligne," = "); 
     746                            strcpy(ligne2,""); 
     747                            nb_initial = 0; 
     748                             
     749                            while (parcours_name) 
     750                            { 
     751                            nb_initial = nb_initial + 1; 
     752                                /* We should modify the initialvalue in the case of variable has been defined with others variables */ 
     753                                strcpy(initialvalue,ChangeTheInitalvaluebyTabvarsName(parcours_name->n_name,List_Global_Var)); 
     754                                if ( !strcasecmp(initialvalue,parcours_name->n_name) ) 
     755                                { 
     756                                    strcpy(initialvalue,ChangeTheInitalvaluebyTabvarsName(parcours_name->n_name,List_Common_Var)); 
     757                                } 
     758                                if ( !strcasecmp(initialvalue,parcours_name->n_name) ) 
     759                                { 
     760                                    strcpy(initialvalue,ChangeTheInitalvaluebyTabvarsName(parcours_name->n_name,List_ModuleUsed_Var)); 
     761                                } 
     762 
     763                                strcat(ligne2,initialvalue); 
     764                             if (parcours_name->suiv) 
     765                             { 
     766                             strcat(ligne2,","); 
     767                             } 
     768                              
     769                             parcours_name = parcours_name->suiv; 
     770                            } 
     771                            if (nb_initial > 1) 
     772                            { 
     773                            sprintf(ligne3,"reshape((/%s/),shape(%s))",ligne2,vargridnametabvars(v,0)); 
     774                            } 
     775                            else 
     776                            { 
     777                            strcpy(ligne3,ligne2); 
     778                            } 
     779                            strcat(ligne,ligne3); 
     780                            tofich(allocationagrif,ligne,1); 
     781                            } 
    680782                            } 
    681783                        } 
     
    705807    char ligne[LONG_M]; 
    706808    char ligne2[LONG_M]; 
     809    char ligne3[LONG_M]; 
     810    listname *parcours_name; 
     811    listname *parcours_name_array; 
    707812    variable *v; 
    708813    int IndiceMax; 
     
    714819    char initialvalue[LONG_M]; 
    715820    int typeiswritten ; 
     821    int nb_initial; 
    716822 
    717823    parcoursprec = (listvar *) NULL; 
     
    794900                                        IndiceMin = parcours->var->v_indicetabvars; 
    795901                                        IndiceMax = parcours->var->v_indicetabvars+compteur; 
    796                                         sprintf(ligne,"    allocate(%s", vargridnametabvars(v,1)); 
     902                                        sprintf(ligne,"    if (.not. allocated(%s)) allocate(%s", vargridnametabvars(v,1), vargridnametabvars(v,1)); 
    797903                                        sprintf(ligne2,"%s)", vargridparam(v)); 
    798904                                        strcat(ligne,ligne2); 
     
    803909                                    else 
    804910                                    { 
    805                                         sprintf(ligne,"allocate(%s", vargridnametabvars(v,0)); 
     911                                        sprintf(ligne,"if (.not. allocated(%s)) allocate(%s", vargridnametabvars(v,0), vargridnametabvars(v,0)); 
    806912                                        sprintf(ligne2,"%s)", vargridparam(v)); 
    807913                                        strcat(ligne,ligne2); 
     
    811917                            } /* end of the allocation part                                       */ 
    812918                            /*                INITIALISATION                                      */ 
    813                             if ( strcasecmp(v->v_initialvalue,"") ) 
     919 
     920               if ( v->v_initialvalue ) 
     921                            { 
     922                            parcours_name = v->v_initialvalue; 
     923                            parcours_name_array = v->v_initialvalue_array; 
     924                            if (parcours_name_array) 
     925                            { 
     926                            while (parcours_name) 
    814927                            { 
    815928                                strcpy(ligne, vargridnametabvars(v,0)); 
     929                                if (parcours_name_array) 
     930                                { 
     931                                if (strcasecmp(parcours_name_array->n_name,"") ) 
     932                                { 
     933                                sprintf(ligne2,"(%s)",parcours_name_array->n_name); 
     934                                strcat(ligne,ligne2); 
     935                                } 
     936                                } 
    816937                                /* We should modify the initialvalue in the case of variable has been defined with others variables */ 
    817                                 strcpy(initialvalue,ChangeTheInitalvaluebyTabvarsName(v->v_initialvalue,List_Global_Var)); 
    818                                 if ( !strcasecmp(initialvalue,v->v_initialvalue) ) 
    819                                 { 
    820                                     strcpy(initialvalue,ChangeTheInitalvaluebyTabvarsName(v->v_initialvalue,List_Common_Var)); 
    821                                 } 
    822                                 if ( !strcasecmp(initialvalue,v->v_initialvalue) ) 
    823                                 { 
    824                                     strcpy(initialvalue,ChangeTheInitalvaluebyTabvarsName(v->v_initialvalue,List_ModuleUsed_Var)); 
     938                                strcpy(initialvalue,ChangeTheInitalvaluebyTabvarsName(parcours_name->n_name,List_Global_Var)); 
     939                                if ( !strcasecmp(initialvalue,parcours_name->n_name) ) 
     940                                { 
     941                                    strcpy(initialvalue,ChangeTheInitalvaluebyTabvarsName(parcours_name->n_name,List_Common_Var)); 
     942                                } 
     943                                if ( !strcasecmp(initialvalue,parcours_name->n_name) ) 
     944                                { 
     945                                    strcpy(initialvalue,ChangeTheInitalvaluebyTabvarsName(parcours_name->n_name,List_ModuleUsed_Var)); 
    825946                                } 
    826947                                strcat (ligne," = "); 
    827                                 strcat (ligne,initialvalue); 
    828                                 Save_Length(ligne,48); 
     948 
     949                                if (v->v_nbdim >= 0) 
     950                                { 
     951                                    strcpy(ligne2,initialvalue); 
     952                                } 
     953                                else 
     954                                { 
     955                                    sprintf(ligne2,"reshape(%s,shape(%s))",initialvalue,vargridnametabvars(v,0)); 
     956                                } 
     957                                strcat(ligne,ligne2); 
    829958                                tofich(allocationagrif,ligne,1); 
     959                              
     960                             parcours_name = parcours_name->suiv; 
     961                             if (parcours_name_array) parcours_name_array = parcours_name_array->suiv; 
     962                            } 
     963                            } 
     964                            else 
     965                            { 
     966                            strcpy(ligne, vargridnametabvars(v,0)); 
     967                            strcat (ligne," = "); 
     968                            strcpy(ligne2,""); 
     969                            nb_initial = 0; 
     970                             
     971                            while (parcours_name) 
     972                            { 
     973                            nb_initial = nb_initial + 1; 
     974                                /* We should modify the initialvalue in the case of variable has been defined with others variables */ 
     975                                strcpy(initialvalue,ChangeTheInitalvaluebyTabvarsName(parcours_name->n_name,List_Global_Var)); 
     976                                if ( !strcasecmp(initialvalue,parcours_name->n_name) ) 
     977                                { 
     978                                    strcpy(initialvalue,ChangeTheInitalvaluebyTabvarsName(parcours_name->n_name,List_Common_Var)); 
     979                                } 
     980                                if ( !strcasecmp(initialvalue,parcours_name->n_name) ) 
     981                                { 
     982                                    strcpy(initialvalue,ChangeTheInitalvaluebyTabvarsName(parcours_name->n_name,List_ModuleUsed_Var)); 
     983                                } 
     984 
     985                                strcat(ligne2,initialvalue); 
     986                             if (parcours_name->suiv) 
     987                             { 
     988                             strcat(ligne2,","); 
     989                             } 
     990                              
     991                             parcours_name = parcours_name->suiv; 
     992                            } 
     993                            if (nb_initial > 1) 
     994                            { 
     995                            sprintf(ligne3,"reshape((/%s/),shape(%s))",ligne2,vargridnametabvars(v,0)); 
     996                            } 
     997                            else 
     998                            { 
     999                            strcpy(ligne3,ligne2); 
     1000                            } 
     1001                            strcat(ligne,ligne3); 
     1002                            tofich(allocationagrif,ligne,1); 
     1003                            } 
    8301004                            } 
    8311005                        } 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/NEMO/NST_SRC/agrif_oce.F90

    r5819 r6258  
    1717 
    1818   PUBLIC agrif_oce_alloc ! routine called by nemo_init in nemogcm.F90 
     19   PUBLIC reconstructandremap 
    1920 
    2021   !                                              !!* Namelist namagrif: AGRIF parameters 
     
    5859   INTEGER :: un_update_id, vn_update_id                              ! AGRIF profiles for udpates 
    5960   INTEGER :: tsn_sponge_id, un_sponge_id, vn_sponge_id               ! AGRIF profiles for sponge layers 
     61! VERTICAL REFINEMENT BEGIN 
     62   INTEGER :: scales_t_id, scales_u_id, scales_v_id 
     63! VERTICAL REFINEMENT END 
     64 
    6065# if defined key_top 
    6166   INTEGER :: trn_id, trn_sponge_id 
     
    6469   INTEGER :: ub2b_update_id, vb2b_update_id 
    6570   INTEGER :: e3t_id, e1u_id, e2v_id, sshn_id 
    66    INTEGER :: scales_t_id 
    6771# if defined key_zdftke 
    6872   INTEGER :: avt_id, avm_id, en_id 
     
    7377   !!---------------------------------------------------------------------- 
    7478   !! NEMO/NST 3.3.1 , NEMO Consortium (2011) 
    75    !! $Id$ 
     79   !! $Id: agrif_oce.F90 5081 2015-02-13 09:51:27Z smasson $ 
    7680   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    7781   !!---------------------------------------------------------------------- 
     
    104108   END FUNCTION agrif_oce_alloc 
    105109 
     110      subroutine reconstructandremap(tabin,hin,tabout,hout,N,Nout)       
     111      implicit none 
     112      integer N, Nout 
     113      real tabin(N), tabout(Nout) 
     114      real hin(N), hout(Nout) 
     115      real coeffremap(N,3),zwork(N,3) 
     116      real zwork2(N+1,3) 
     117      integer k 
     118      double precision, parameter :: dsmll=1.0d-8   
     119      real q,q01,q02,q001,q002,q0 
     120      real z_win(1:N+1), z_wout(1:Nout+1) 
     121      real,parameter :: dpthin = 1.D-3 
     122      integer :: k1, kbox, ktop, ka, kbot 
     123      real :: tsum, qbot, rpsum, zbox, ztop, zthk, zbot, offset, qtop 
     124 
     125      z_win(1)=0.; z_wout(1)= 0. 
     126      do k=1,N 
     127       z_win(k+1)=z_win(k)+hin(k) 
     128      enddo  
     129       
     130      do k=1,Nout 
     131       z_wout(k+1)=z_wout(k)+hout(k)        
     132      enddo        
     133 
     134        do k=2,N 
     135          zwork(k,1)=1./(hin(k-1)+hin(k)) 
     136        enddo 
     137         
     138        do k=2,N-1 
     139          q0 = 1./(hin(k-1)+hin(k)+hin(k+1)) 
     140          zwork(k,2)=hin(k-1)+2.*hin(k)+hin(k+1) 
     141          zwork(k,3)=q0 
     142        enddo        
     143       
     144        do k= 2,N 
     145        zwork2(k,1)=zwork(k,1)*(tabin(k)-tabin(k-1)) 
     146        enddo 
     147         
     148        coeffremap(:,1) = tabin(:) 
     149  
     150         do k=2,N-1 
     151        q001 = hin(k)*zwork2(k+1,1) 
     152        q002 = hin(k)*zwork2(k,1)         
     153        if (q001*q002 < 0) then 
     154          q001 = 0. 
     155          q002 = 0. 
     156        endif 
     157        q=zwork(k,2) 
     158        q01=q*zwork2(k+1,1) 
     159        q02=q*zwork2(k,1) 
     160        if (abs(q001) > abs(q02)) q001 = q02 
     161        if (abs(q002) > abs(q01)) q002 = q01 
     162         
     163        q=(q001-q002)*zwork(k,3) 
     164        q001=q001-q*hin(k+1) 
     165        q002=q002+q*hin(k-1) 
     166         
     167        coeffremap(k,3)=coeffremap(k,1)+q001 
     168        coeffremap(k,2)=coeffremap(k,1)-q002 
     169         
     170        zwork2(k,1)=(2.*q001-q002)**2 
     171        zwork2(k,2)=(2.*q002-q001)**2 
     172        enddo 
     173         
     174        do k=1,N 
     175        if     (k.eq.1 .or. k.eq.N .or.   hin(k).le.dpthin) then 
     176        coeffremap(k,3) = coeffremap(k,1) 
     177        coeffremap(k,2) = coeffremap(k,1) 
     178        zwork2(k,1) = 0. 
     179        zwork2(k,2) = 0. 
     180        endif 
     181        enddo 
     182         
     183        do k=2,N 
     184        q002=max(zwork2(k-1,2),dsmll) 
     185        q001=max(zwork2(k,1),dsmll) 
     186        zwork2(k,3)=(q001*coeffremap(k-1,3)+q002*coeffremap(k,2))/(q001+q002) 
     187        enddo 
     188         
     189        zwork2(1,3) = 2*coeffremap(1,1)-zwork2(2,3) 
     190        zwork2(N+1,3)=2*coeffremap(N,1)-zwork2(N,3) 
     191  
     192        do k=1,N 
     193        q01=zwork2(k+1,3)-coeffremap(k,1) 
     194        q02=coeffremap(k,1)-zwork2(k,3) 
     195        q001=2.*q01 
     196        q002=2.*q02 
     197        if (q01*q02<0) then 
     198          q01=0. 
     199          q02=0. 
     200        elseif (abs(q01)>abs(q002)) then 
     201          q01=q002 
     202        elseif (abs(q02)>abs(q001)) then 
     203          q02=q001 
     204        endif 
     205        coeffremap(k,2)=coeffremap(k,1)-q02 
     206        coeffremap(k,3)=coeffremap(k,1)+q01 
     207        enddo 
     208 
     209      zbot=0.0 
     210      kbot=1 
     211      do k=1,Nout 
     212        ztop=zbot  !top is bottom of previous layer 
     213        ktop=kbot 
     214        if     (ztop.ge.z_win(ktop+1)) then 
     215          ktop=ktop+1 
     216        endif 
     217         
     218        zbot=z_wout(k+1) 
     219        zthk=zbot-ztop 
     220 
     221        if     (zthk.gt.dpthin .and. ztop.lt.z_wout(Nout+1)) then 
     222 
     223          kbot=ktop 
     224          do while (z_win(kbot+1).lt.zbot.and.kbot.lt.N) 
     225            kbot=kbot+1 
     226          enddo 
     227          zbox=zbot 
     228          do k1= k+1,Nout 
     229            if     (z_wout(k1+1)-z_wout(k1).gt.dpthin) then 
     230              exit !thick layer 
     231            else 
     232              zbox=z_wout(k1+1)  !include thin adjacent layers 
     233              if     (zbox.eq.z_wout(Nout+1)) then 
     234                exit !at bottom 
     235              endif 
     236            endif 
     237          enddo 
     238          zthk=zbox-ztop 
     239 
     240          kbox=ktop 
     241          do while (z_win(kbox+1).lt.zbox.and.kbox.lt.N) 
     242            kbox=kbox+1 
     243          enddo 
     244           
     245          if     (ktop.eq.kbox) then 
     246 
     247 
     248            if     (z_wout(k)  .ne.z_win(kbox)   .or.z_wout(k+1).ne.z_win(kbox+1)     ) then 
     249 
     250              if     (hin(kbox).gt.dpthin) then 
     251                q001 = (zbox-z_win(kbox))/hin(kbox) 
     252                q002 = (ztop-z_win(kbox))/hin(kbox) 
     253                q01=q001**2+q002**2+q001*q002+1.-2.*(q001+q002) 
     254                q02=q01-1.+(q001+q002) 
     255                q0=1.-q01-q02 
     256              else 
     257                q0 = 1.0 
     258                q01 = 0. 
     259                q02 = 0. 
     260              endif 
     261          tabout(k)=q0*coeffremap(kbox,1)+q01*coeffremap(kbox,2)+q02*coeffremap(kbox,3) 
     262               
     263            else 
     264            tabout(k) = tabin(kbox) 
     265               
     266            endif  
     267 
     268          else 
     269 
     270            if     (ktop.le.k .and. kbox.ge.k) then 
     271              ka = k 
     272            elseif (kbox-ktop.ge.3) then 
     273              ka = (kbox+ktop)/2 
     274            elseif (hin(ktop).ge.hin(kbox)) then 
     275              ka = ktop 
     276            else 
     277              ka = kbox 
     278            endif !choose ka 
     279 
     280            offset=coeffremap(ka,1) 
     281 
     282            qtop = z_win(ktop+1)-ztop !partial layer thickness 
     283            if     (hin(ktop).gt.dpthin) then 
     284              q=(ztop-z_win(ktop))/hin(ktop) 
     285              q01=q*(q-1.) 
     286              q02=q01+q 
     287              q0=1-q01-q02             
     288            else 
     289              q0 = 1. 
     290              q01 = 0. 
     291              q02 = 0. 
     292            endif 
     293             
     294            tsum =((q0*coeffremap(ktop,1)+q01*coeffremap(ktop,2)+q02*coeffremap(ktop,3))-offset)*qtop 
     295 
     296            do k1= ktop+1,kbox-1 
     297              tsum =tsum +(coeffremap(k1,1)-offset)*hin(k1) 
     298            enddo !k1 
     299 
     300             
     301            qbot = zbox-z_win(kbox) !partial layer thickness 
     302            if     (hin(kbox).gt.dpthin) then 
     303              q=qbot/hin(kbox) 
     304              q01=(q-1.)**2 
     305              q02=q01-1.+q 
     306              q0=1-q01-q02                             
     307            else 
     308              q0 = 1.0 
     309              q01 = 0. 
     310              q02 = 0. 
     311            endif 
     312            
     313            tsum = tsum +((q0*coeffremap(kbox,1)+q01*coeffremap(kbox,2)+q02*coeffremap(kbox,3))-offset)*qbot 
     314             
     315            rpsum=1.0d0/zthk 
     316              tabout(k)=offset+tsum*rpsum 
     317               
     318          endif !single or multiple layers 
     319        else 
     320        if (k==1) then 
     321        write(*,'(a7,i4,i4,3f12.5)')'problem = ',N,Nout,zthk,z_wout(k+1),hout(1) 
     322        endif 
     323         tabout(k) = tabout(k-1) 
     324           
     325        endif !normal:thin layer 
     326      enddo !k 
     327             
     328      return 
     329      end subroutine reconstructandremap 
     330       
    106331#endif 
    107332   !!====================================================================== 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/NEMO/NST_SRC/agrif_opa_interp.F90

    r5819 r6258  
    3838 
    3939   PUBLIC   Agrif_tra, Agrif_dyn, Agrif_ssh, Agrif_dyn_ts, Agrif_ssh_ts, Agrif_dta_ts 
     40! VERTICAL REFINEMENT BEGIN    
     41   PUBLIC   Agrif_Init_InterpScales 
     42! VERTICAL REFINEMENT END 
    4043   PUBLIC   interpun, interpvn, interpun2d, interpvn2d  
    4144   PUBLIC   interptsn,  interpsshn 
     
    5053   !!---------------------------------------------------------------------- 
    5154   !! NEMO/NST 3.6 , NEMO Consortium (2010) 
    52    !! $Id$ 
     55   !! $Id: agrif_opa_interp.F90 5081 2015-02-13 09:51:27Z smasson $ 
    5356   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    5457   !!---------------------------------------------------------------------- 
    5558 
     59! VERTICAL REFINEMENT BEGIN 
     60   REAL, DIMENSION(:,:,:), ALLOCATABLE :: interp_scales_t, interp_scales_u, interp_scales_v 
     61!$AGRIF_DO_NOT_TREAT 
     62   LOGICAL :: scaleT, scaleU, scaleV = .FALSE. 
     63!$AGRIF_END_DO_NOT_TREAT 
     64! VERTICAL REFINEMENT END 
     65 
    5666CONTAINS 
     67 
     68! VERTICAL REFINEMENT BEGIN 
     69 
     70   SUBROUTINE Agrif_Init_InterpScales 
     71 
     72    scaleT = .TRUE. 
     73    Call Agrif_Bc_Variable(scales_t_id,calledweight=1.,procname=interpscales) 
     74    scaleT = .FALSE. 
     75     
     76    scaleU = .TRUE. 
     77    Call Agrif_Bc_Variable(scales_u_id,calledweight=1.,procname=interpscales) 
     78    scaleU = .FALSE. 
     79 
     80    scaleV = .TRUE. 
     81    Call Agrif_Bc_Variable(scales_v_id,calledweight=1.,procname=interpscales) 
     82    scaleV = .FALSE. 
     83 
     84   END SUBROUTINE Agrif_Init_InterpScales 
     85    
     86   SUBROUTINE interpscales(ptab,i1,i2,j1,j2,k1,k2,before) 
     87      !!--------------------------------------------- 
     88      !!   *** ROUTINE interpscales *** 
     89      !!--------------------------------------------- 
     90       
     91      INTEGER, INTENT(in) :: i1,i2,j1,j2,k1,k2 
     92      REAL(wp),DIMENSION(i1:i2,j1:j2,k1:k2), INTENT(inout) :: ptab 
     93 
     94      INTEGER :: ji, jj, jk 
     95      LOGICAL :: before 
     96 
     97      IF (before) THEN 
     98      IF (scaleT ) THEN 
     99      DO jk=k1,k2 
     100         DO jj=j1,j2 
     101            DO ji=i1,i2 
     102!               ptab(ji,jj,jk) = fse3t_n(ji,jj,jk) * tmask(ji,jj,jk) 
     103               ptab(ji,jj,jk) = fse3t_n(ji,jj,jk) 
     104            END DO 
     105         END DO 
     106      END DO 
     107      ELSEIF (scaleU) THEN 
     108      DO jk=k1,k2 
     109         DO jj=j1,j2 
     110            DO ji=i1,i2 
     111!               ptab(ji,jj,jk) = fse3u_n(ji,jj,jk) * umask(ji,jj,jk) 
     112!               ptab(ji,jj,jk) = fse3u_n(ji,jj,jk) 
     113                ptab(ji,jj,jk) = umask(ji,jj,jk) 
     114            END DO 
     115         END DO 
     116      END DO 
     117      ELSEIF (scaleV) THEN 
     118      DO jk=k1,k2 
     119         DO jj=j1,j2 
     120            DO ji=i1,i2 
     121!               ptab(ji,jj,jk) = fse3v_n(ji,jj,jk) * vmask(ji,jj,jk) 
     122!               ptab(ji,jj,jk) = fse3v_n(ji,jj,jk) 
     123               ptab(ji,jj,jk) = vmask(ji,jj,jk) 
     124            END DO 
     125         END DO 
     126      END DO 
     127      ENDIF 
     128      ELSE 
     129      IF (scaleT ) THEN 
     130      IF (.not.allocated(interp_scales_t)) allocate(interp_scales_t(jpi,jpj,k1:k2)) 
     131      DO jk=k1,k2 
     132         DO jj=j1,j2 
     133            DO ji=i1,i2 
     134               interp_scales_t(ji,jj,jk) = ptab(ji,jj,jk) 
     135            END DO 
     136         END DO 
     137      END DO 
     138      ELSEIF (scaleU) THEN 
     139      IF (.not.allocated(interp_scales_u)) allocate(interp_scales_u(jpi,jpj,k1:k2)) 
     140      DO jk=k1,k2 
     141         DO jj=j1,j2 
     142            DO ji=i1,i2 
     143               interp_scales_u(ji,jj,jk) = ptab(ji,jj,jk) 
     144            END DO 
     145         END DO 
     146      END DO 
     147      ELSEIF (scaleV) THEN 
     148      IF (.not.allocated(interp_scales_v)) allocate(interp_scales_v(jpi,jpj,k1:k2)) 
     149      DO jk=k1,k2 
     150         DO jj=j1,j2 
     151            DO ji=i1,i2 
     152               interp_scales_v(ji,jj,jk) = ptab(ji,jj,jk) 
     153            END DO 
     154         END DO 
     155      END DO 
     156      ENDIF 
     157      ENDIF 
     158 
     159   END SUBROUTINE interpscales 
     160 
     161! VERTICAL REFINEMENT END 
    57162 
    58163   SUBROUTINE Agrif_tra 
     
    611716      REAL(wp) ::   zalpha 
    612717      ! 
     718      return 
     719       
    613720      zalpha = REAL( Agrif_NbStepint() + Agrif_IRhot() - 1, wp ) / REAL( Agrif_IRhot(), wp ) 
    614721      IF( zalpha > 1. )   zalpha = 1. 
     
    638745      REAL(wp) ::   zalpha4, zalpha5, zalpha6, zalpha7 
    639746      LOGICAL :: western_side, eastern_side,northern_side,southern_side 
     747! VERTICAL REFINEMENT BEGIN 
     748      REAL(wp), DIMENSION(i1:i2,j1:j2,1:jpk,n1:n2) :: ptab_child 
     749      REAL(wp) :: h_in(k1:k2) 
     750      REAL(wp) :: h_out(1:jpk) 
     751      INTEGER :: N_in, N_out 
     752      REAL(wp) :: h_diff 
     753! VERTICAL REFINEMENT END 
    640754 
    641755      IF (before) THEN          
    642756         ptab(i1:i2,j1:j2,k1:k2,n1:n2) = tsn(i1:i2,j1:j2,k1:k2,n1:n2) 
    643       ELSE 
     757      ELSE  
     758! VERTICAL REFINEMENT BEGIN 
     759 
     760         ptab_child(:,:,:,:) = 0. 
     761         do jj=j1,j2 
     762         do ji=i1,i2 
     763           h_in(k1:k2) = interp_scales_t(ji,jj,k1:k2) 
     764           h_out(1:jpk) = fse3t(ji,jj,1:jpk) 
     765           h_diff = sum(h_out(1:jpk-1))-sum(h_in(k1:k2-1)) 
     766           N_in = k2-1 
     767           N_out = jpk-1 
     768           if (h_diff > 0) then 
     769             h_in(N_in+1) = h_diff 
     770             N_in = N_in + 1 
     771           else 
     772             h_out(N_out+1) = -h_diff 
     773             N_out = N_out + 1 
     774           endif  
     775           ptab(ji,jj,k2,:) = ptab(ji,jj,k2-1,:) 
     776           do jn=1,jpts 
     777             call reconstructandremap(ptab(ji,jj,1:N_in,jn),h_in,ptab_child(ji,jj,1:N_out,jn),h_out,N_in,N_out) 
     778           enddo 
     779!           if (abs(h_diff) > 1000.) then 
     780!           do jn=1,jpts 
     781!             do jk=1,N_out 
     782!             print *,'AVANT APRES = ',ji,jj,jk,N_out,ptab(ji,jj,jk,jn),ptab_child(ji,jj,jk,jn) 
     783!             enddo 
     784!           enddo 
     785!         endif 
     786         enddo 
     787         enddo 
     788 
     789! VERTICAL REFINEMENT END 
     790 
    644791         ! 
    645792         western_side  = (nb == 1).AND.(ndir == 1) 
     
    671818         IF((nbondi == +1).OR.(nbondi == 2)) imax = nlci-2         
    672819         ! 
     820! VERTICAL REFINEMENT BEGIN 
     821 
     822! WARNING : 
     823! ptab replaced by ptab_child in the following 
     824! k1 k2 replaced by 1 jpk 
     825! VERTICAL REFINEMENT END 
    673826         IF( eastern_side) THEN 
    674827            DO jn = 1, jpts 
    675                tsa(nlci,j1:j2,k1:k2,jn) = zalpha1 * ptab(nlci,j1:j2,k1:k2,jn) + zalpha2 * ptab(nlci-1,j1:j2,k1:k2,jn) 
     828               tsa(nlci,j1:j2,1:jpk,jn) = zalpha1 * ptab_child(nlci,j1:j2,1:jpk,jn) + zalpha2 * ptab_child(nlci-1,j1:j2,1:jpk,jn) 
    676829               DO jk = 1, jpkm1 
    677830                  DO jj = jmin,jmax 
     
    692845         IF( northern_side ) THEN             
    693846            DO jn = 1, jpts 
    694                tsa(i1:i2,nlcj,k1:k2,jn) = zalpha1 * ptab(i1:i2,nlcj,k1:k2,jn) + zalpha2 * ptab(i1:i2,nlcj-1,k1:k2,jn) 
     847               tsa(i1:i2,nlcj,1:jpk,jn) = zalpha1 * ptab_child(i1:i2,nlcj,1:jpk,jn) + zalpha2 * ptab_child(i1:i2,nlcj-1,1:jpk,jn) 
    695848               DO jk = 1, jpkm1 
    696849                  DO ji = imin,imax 
     
    711864         IF( western_side) THEN             
    712865            DO jn = 1, jpts 
    713                tsa(1,j1:j2,k1:k2,jn) = zalpha1 * ptab(1,j1:j2,k1:k2,jn) + zalpha2 * ptab(2,j1:j2,k1:k2,jn) 
     866               tsa(1,j1:j2,1:jpk,jn) = zalpha1 * ptab_child(1,j1:j2,1:jpk,jn) + zalpha2 * ptab_child(2,j1:j2,1:jpk,jn) 
    714867               DO jk = 1, jpkm1 
    715868                  DO jj = jmin,jmax 
     
    729882         IF( southern_side ) THEN            
    730883            DO jn = 1, jpts 
    731                tsa(i1:i2,1,k1:k2,jn) = zalpha1 * ptab(i1:i2,1,k1:k2,jn) + zalpha2 * ptab(i1:i2,2,k1:k2,jn) 
     884               tsa(i1:i2,1,1:jpk,jn) = zalpha1 * ptab_child(i1:i2,1,1:jpk,jn) + zalpha2 * ptab_child(i1:i2,2,1:jpk,jn) 
    732885               DO jk=1,jpk       
    733886                  DO ji=imin,imax 
     
    749902         ! East south 
    750903         IF ((eastern_side).AND.((nbondj == -1).OR.(nbondj == 2))) THEN 
    751             tsa(nlci-1,2,:,:) = ptab(nlci-1,2,:,:) 
     904            tsa(nlci-1,2,:,:) = ptab_child(nlci-1,2,:,:) 
    752905         ENDIF 
    753906         ! East north 
    754907         IF ((eastern_side).AND.((nbondj == 1).OR.(nbondj == 2))) THEN 
    755             tsa(nlci-1,nlcj-1,:,:) = ptab(nlci-1,nlcj-1,:,:) 
     908            tsa(nlci-1,nlcj-1,:,:) = ptab_child(nlci-1,nlcj-1,:,:) 
    756909         ENDIF 
    757910         ! West south 
    758911         IF ((western_side).AND.((nbondj == -1).OR.(nbondj == 2))) THEN 
    759             tsa(2,2,:,:) = ptab(2,2,:,:) 
     912            tsa(2,2,:,:) = ptab_child(2,2,:,:) 
    760913         ENDIF 
    761914         ! West north 
    762915         IF ((western_side).AND.((nbondj == 1).OR.(nbondj == 2))) THEN 
    763             tsa(2,nlcj-1,:,:) = ptab(2,nlcj-1,:,:) 
     916            tsa(2,nlcj-1,:,:) = ptab_child(2,nlcj-1,:,:) 
    764917         ENDIF 
    765918         ! 
     
    794947   END SUBROUTINE interpsshn 
    795948 
    796    SUBROUTINE interpun(ptab,i1,i2,j1,j2,k1,k2, before) 
     949   SUBROUTINE interpun(ptab,i1,i2,j1,j2,k1,k2,m1,m2,before,nb,ndir) 
    797950      !!--------------------------------------------- 
    798951      !!   *** ROUTINE interpun *** 
    799952      !!---------------------------------------------     
    800953      !! 
    801       INTEGER, INTENT(in) :: i1,i2,j1,j2,k1,k2 
    802       REAL(wp), DIMENSION(i1:i2,j1:j2,k1:k2), INTENT(inout) :: ptab 
     954      INTEGER, INTENT(in) :: i1,i2,j1,j2,k1,k2,m1,m2 
     955      REAL(wp), DIMENSION(i1:i2,j1:j2,k1:k2,m1:m2), INTENT(inout) :: ptab 
    803956      LOGICAL, INTENT(in) :: before 
     957      INTEGER, INTENT(in) :: nb , ndir 
    804958      !! 
    805959      INTEGER :: ji,jj,jk 
    806       REAL(wp) :: zrhoy  
     960      REAL(wp) :: zrhoy 
     961! VERTICAL REFINEMENT BEGIN 
     962      REAL(wp), DIMENSION(i1:i2,j1:j2,1:jpk) :: ptab_child 
     963      REAL(wp), DIMENSION(k1:k2) :: tabin 
     964      REAL(wp) :: h_in(k1:k2) 
     965      REAL(wp) :: h_out(1:jpk) 
     966      INTEGER :: N_in, N_out 
     967      REAL(wp) :: h_diff 
     968      LOGICAL :: western_side, eastern_side 
     969      INTEGER :: iref 
     970 
     971! VERTICAL REFINEMENT END 
    807972      !!---------------------------------------------     
    808973      ! 
     
    811976            DO jj=j1,j2 
    812977               DO ji=i1,i2 
    813                   ptab(ji,jj,jk) = e2u(ji,jj) * un(ji,jj,jk) 
    814                   ptab(ji,jj,jk) = ptab(ji,jj,jk) * fse3u(ji,jj,jk) 
     978                  ptab(ji,jj,jk,1) = e2u(ji,jj) * un(ji,jj,jk) 
     979                  ptab(ji,jj,jk,1) = ptab(ji,jj,jk,1) * fse3u(ji,jj,jk) 
     980                  ptab(ji,jj,jk,2) = fse3u(ji,jj,jk) 
    815981               END DO 
    816982            END DO 
    817983         END DO 
    818984      ELSE 
     985! VERTICAL REFINEMENT BEGIN 
     986         western_side  = (nb == 1).AND.(ndir == 1) 
     987         eastern_side  = (nb == 1).AND.(ndir == 2) 
     988          
     989         ptab_child(:,:,:) = 0. 
     990         do jj=j1,j2 
     991         do ji=i1,i2 
     992         iref = ji 
     993         IF (western_side) iref = 2 
     994         IF (eastern_side) iref = nlci-2 
     995 
     996         N_in = 0 
     997         do jk=k1,k2 
     998           if (interp_scales_u(ji,jj,jk) == 0) EXIT 
     999             N_in = N_in + 1 
     1000             tabin(jk) = ptab(ji,jj,jk,1)/ptab(ji,jj,jk,2) 
     1001             h_in(N_in) = ptab(ji,jj,jk,2) 
     1002         enddo 
     1003          
     1004         IF (N_in == 0) THEN 
     1005           ptab_child(ji,jj,:) = 0. 
     1006           CYCLE 
     1007         ENDIF 
     1008          
     1009         N_out = 0 
     1010         do jk=1,jpk 
     1011           if (umask(iref,jj,jk) == 0) EXIT 
     1012           N_out = N_out + 1 
     1013           h_out(N_out) = fse3u(ji,jj,jk) 
     1014         enddo 
     1015          
     1016         IF (N_out == 0) THEN 
     1017           ptab_child(ji,jj,:) = 0. 
     1018           CYCLE 
     1019         ENDIF 
     1020          
     1021         h_diff = sum(h_out(1:N_out))-sum(h_in(1:N_in)) 
     1022         IF (h_diff > 0.) THEN 
     1023           N_in = N_in + 1 
     1024           h_in(N_in) = h_diff 
     1025           tabin(N_in) = 0. 
     1026         ELSE 
     1027           h_out(N_out) = h_out(N_out) - h_diff 
     1028         ENDIF 
     1029          
     1030         call reconstructandremap(tabin(1:N_in),h_in(1:N_in),ptab_child(ji,jj,1:N_out),h_out(1:N_out),N_in,N_out) 
     1031          
     1032         ptab_child(ji,jj,N_out) = ptab_child(ji,jj,N_out) * h_out(N_out) / fse3u(ji,jj,N_out) 
     1033 
     1034         ENDDO 
     1035         ENDDO 
     1036 
     1037! in the following 
     1038! remove division of ua by fs e3u (already done) 
     1039! VERTICAL REFINEMENT END 
     1040 
    8191041         zrhoy = Agrif_Rhoy() 
    8201042         DO jk=1,jpkm1 
    8211043            DO jj=j1,j2 
    822                ua(i1:i2,jj,jk) = (ptab(i1:i2,jj,jk)/(zrhoy*e2u(i1:i2,jj))) 
    823                ua(i1:i2,jj,jk) = ua(i1:i2,jj,jk) / fse3u(i1:i2,jj,jk) 
     1044               ua(i1:i2,jj,jk) = (ptab_child(i1:i2,jj,jk)/(zrhoy*e2u(i1:i2,jj))) 
    8241045            END DO 
    8251046         END DO 
     
    8611082 
    8621083 
    863    SUBROUTINE interpvn(ptab,i1,i2,j1,j2,k1,k2, before) 
     1084   SUBROUTINE interpvn(ptab,i1,i2,j1,j2,k1,k2,m1,m2,before,nb,ndir) 
    8641085      !!--------------------------------------------- 
    8651086      !!   *** ROUTINE interpvn *** 
    8661087      !!---------------------------------------------     
    8671088      ! 
    868       INTEGER, INTENT(in) :: i1,i2,j1,j2,k1,k2 
    869       REAL(wp), DIMENSION(i1:i2,j1:j2,k1:k2), INTENT(inout) :: ptab 
     1089      INTEGER, INTENT(in) :: i1,i2,j1,j2,k1,k2,m1,m2 
     1090      REAL(wp), DIMENSION(i1:i2,j1:j2,k1:k2,m1:m2), INTENT(inout) :: ptab 
    8701091      LOGICAL, INTENT(in) :: before 
     1092      INTEGER, INTENT(in) :: nb , ndir 
    8711093      ! 
    8721094      INTEGER :: ji,jj,jk 
    873       REAL(wp) :: zrhox  
     1095      REAL(wp) :: zrhox 
     1096! VERTICAL REFINEMENT BEGIN 
     1097      REAL(wp), DIMENSION(i1:i2,j1:j2,1:jpk) :: ptab_child 
     1098      REAL(wp), DIMENSION(k1:k2) :: tabin 
     1099      REAL(wp) :: h_in(k1:k2) 
     1100      REAL(wp) :: h_out(1:jpk) 
     1101      INTEGER :: N_in, N_out 
     1102      REAL(wp) :: h_diff 
     1103      LOGICAL :: northern_side,southern_side 
     1104      INTEGER :: jref 
     1105 
     1106! VERTICAL REFINEMENT END 
    8741107      !!---------------------------------------------     
    8751108      !       
     
    8791112            DO jj=j1,j2 
    8801113               DO ji=i1,i2 
    881                   ptab(ji,jj,jk) = e1v(ji,jj) * vn(ji,jj,jk) 
    882                   ptab(ji,jj,jk) = ptab(ji,jj,jk) * fse3v(ji,jj,jk) 
     1114                  ptab(ji,jj,jk,1) = e1v(ji,jj) * vn(ji,jj,jk) 
     1115                  ptab(ji,jj,jk,1) = ptab(ji,jj,jk,1) * fse3v(ji,jj,jk) 
     1116                  ptab(ji,jj,jk,2) = fse3v(ji,jj,jk) 
    8831117               END DO 
    8841118            END DO 
    8851119         END DO 
    886       ELSE           
     1120      ELSE         
     1121! VERTICAL REFINEMENT BEGIN 
     1122         ptab_child(:,:,:) = 0. 
     1123         southern_side = (nb == 2).AND.(ndir == 1) 
     1124         northern_side = (nb == 2).AND.(ndir == 2) 
     1125         do jj=j1,j2 
     1126         jref = jj 
     1127         IF (southern_side) jref = 2 
     1128         IF (northern_side) jref = nlcj-2 
     1129         do ji=i1,i2 
     1130 
     1131         N_in = 0 
     1132         do jk=k1,k2 
     1133           if (interp_scales_v(ji,jj,jk) == 0) EXIT 
     1134             N_in = N_in + 1 
     1135             tabin(jk) = ptab(ji,jj,jk,1)/ptab(ji,jj,jk,2) 
     1136             h_in(N_in) = ptab(ji,jj,jk,2) 
     1137         enddo 
     1138         IF (N_in == 0) THEN 
     1139           ptab_child(ji,jj,:) = 0. 
     1140           CYCLE 
     1141         ENDIF 
     1142          
     1143         N_out = 0 
     1144         do jk=1,jpk 
     1145           if (vmask(ji,jref,jk) == 0) EXIT 
     1146           N_out = N_out + 1 
     1147           h_out(N_out) = fse3v(ji,jj,jk) 
     1148         enddo 
     1149         IF (N_out == 0) THEN 
     1150           ptab_child(ji,jj,:) = 0. 
     1151           CYCLE 
     1152         ENDIF 
     1153          
     1154         h_diff = sum(h_out(1:N_out))-sum(h_in(1:N_in)) 
     1155         IF (h_diff > 0.) THEN 
     1156           N_in = N_in + 1 
     1157           h_in(N_in) = h_diff 
     1158           tabin(N_in) = 0. 
     1159         ELSE 
     1160           h_out(N_out) = h_out(N_out) - h_diff 
     1161         ENDIF 
     1162          
     1163         call reconstructandremap(tabin(1:N_in),h_in(1:N_in),ptab_child(ji,jj,1:N_out),h_out(1:N_out),N_in,N_out) 
     1164          
     1165         ptab_child(ji,jj,N_out) = ptab_child(ji,jj,N_out) * h_out(N_out) / fse3v(ji,jj,N_out) 
     1166 
     1167         enddo 
     1168         enddo 
     1169! in the following 
     1170! remove division of va by fs e3v (already done) 
     1171! VERTICAL REFINEMENT END 
    8871172         zrhox= Agrif_Rhox() 
    8881173         DO jk=1,jpkm1 
    8891174            DO jj=j1,j2 
    890                va(i1:i2,jj,jk) = (ptab(i1:i2,jj,jk)/(zrhox*e1v(i1:i2,jj))) 
    891                va(i1:i2,jj,jk) = va(i1:i2,jj,jk) / fse3v(i1:i2,jj,jk) 
     1175               va(i1:i2,jj,jk) = (ptab_child(i1:i2,jj,jk)/(zrhox*e1v(i1:i2,jj))) 
    8921176            END DO 
    8931177         END DO 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/NEMO/NST_SRC/agrif_opa_update.F90

    r5819 r6258  
    1 #define TWO_WAY        /* TWO WAY NESTING */ 
     1#undef TWO_WAY        /* TWO WAY NESTING */ 
    22#undef DECAL_FEEDBACK /* SEPARATION of INTERFACES*/ 
    33  
     
    1818 
    1919   PUBLIC Agrif_Update_Tra, Agrif_Update_Dyn,Update_Scales 
     20    
     21! VERTICAL REFINEMENT BEGIN    
     22   PUBLIC Agrif_Init_UpdateScales 
     23   REAL, DIMENSION(:,:,:), ALLOCATABLE :: update_scales_t, update_scales_u, update_scales_v 
     24!$AGRIF_DO_NOT_TREAT 
     25   LOGICAL :: scaleT, scaleU, scaleV = .FALSE. 
     26!$AGRIF_END_DO_NOT_TREAT 
     27! VERTICAL REFINEMENT END 
     28 
    2029# if defined key_zdftke 
    2130   PUBLIC Agrif_Update_Tke 
     
    2332   !!---------------------------------------------------------------------- 
    2433   !! NEMO/NST 3.6 , NEMO Consortium (2010) 
    25    !! $Id$ 
     34   !! $Id: agrif_opa_update.F90 5081 2015-02-13 09:51:27Z smasson $ 
    2635   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    2736   !!---------------------------------------------------------------------- 
    2837 
     38#  include "domzgr_substitute.h90"   
     39 
    2940CONTAINS 
     41 
     42! VERTICAL REFINEMENT BEGIN 
     43   SUBROUTINE Agrif_Init_UpdateScales 
     44 
     45    scaleT = .TRUE. 
     46    Agrif_UseSpecialValueInUpdate = .FALSE. 
     47    Agrif_SpecialValueFineGrid = 0. 
     48    Call Agrif_Update_Variable(scales_t_id,procname=updatescales) 
     49    Agrif_UseSpecialValueInUpdate = .FALSE. 
     50    scaleT = .FALSE. 
     51 
     52    scaleU = .TRUE. 
     53    Call Agrif_Update_Variable(scales_u_id,procname=updatescales) 
     54    scaleU = .FALSE. 
     55 
     56    scaleV = .TRUE. 
     57    Call Agrif_Update_Variable(scales_v_id,procname=updatescales) 
     58    scaleV = .FALSE. 
     59 
     60   END SUBROUTINE Agrif_Init_UpdateScales 
     61    
     62   SUBROUTINE updatescales( ptab, i1, i2, j1, j2, k1, k2, before ) 
     63 
     64      INTEGER, INTENT(in) :: i1,i2,j1,j2,k1,k2 
     65      REAL(wp),DIMENSION(i1:i2,j1:j2,k1:k2), INTENT(inout) :: ptab 
     66      LOGICAL, iNTENT(in) :: before 
     67 
     68      INTEGER :: ji,jj,jk 
     69 
     70      IF (before) THEN 
     71        IF (scaleT) THEN 
     72         DO jk=k1,k2 
     73            DO jj=j1,j2 
     74               DO ji=i1,i2 
     75                  ptab(ji,jj,jk) = fse3t(ji,jj,jk)*tmask(ji,jj,jk) 
     76               END DO 
     77            END DO 
     78         END DO 
     79        ELSEIF (scaleU) THEN 
     80        DO jk=k1,k2 
     81            DO jj=j1,j2 
     82               DO ji=i1,i2 
     83                  ptab(ji,jj,jk) = fse3u(ji,jj,jk)*umask(ji,jj,jk) 
     84               END DO 
     85            END DO 
     86         END DO 
     87        ELSEIF (scaleV) THEN 
     88        DO jk=k1,k2 
     89            DO jj=j1,j2 
     90               DO ji=i1,i2 
     91                  ptab(ji,jj,jk) = fse3v(ji,jj,jk)*vmask(ji,jj,jk) 
     92               END DO 
     93            END DO 
     94         END DO 
     95        ENDIF 
     96      ELSE 
     97         IF (scaleT) THEN 
     98           Allocate(update_scales_t(i1:i2,j1:j2,k1:k2)) 
     99           update_scales_t(i1:i2,j1:j2,k1:k2) = ptab(i1:i2,j1:j2,k1:k2) 
     100         ELSEIF (scaleU) THEN 
     101           Allocate(update_scales_u(i1:i2,j1:j2,k1:k2)) 
     102           update_scales_u(i1:i2,j1:j2,k1:k2) = ptab(i1:i2,j1:j2,k1:k2) 
     103         ELSEIF (scaleV) THEN 
     104           Allocate(update_scales_v(i1:i2,j1:j2,k1:k2)) 
     105           update_scales_v(i1:i2,j1:j2,k1:k2) = ptab(i1:i2,j1:j2,k1:k2) 
     106         ENDIF 
     107      ENDIF 
     108 
     109   END SUBROUTINE updatescales 
     110! VERTICAL REFINEMENT END 
    30111 
    31112   RECURSIVE SUBROUTINE Agrif_Update_Tra( ) 
     
    160241      INTEGER, INTENT(in) :: kt 
    161242      !        
     243      return 
     244       
    162245      IF( ( Agrif_NbStepint() .NE. 0 ) .AND. (kt /= 0) ) RETURN 
    163246#  if defined TWO_WAY 
     
    177260# endif /* key_zdftke */ 
    178261 
    179    SUBROUTINE updateTS( tabres, i1, i2, j1, j2, k1, k2, n1, n2, before ) 
     262   SUBROUTINE updateTS( ptab, i1, i2, j1, j2, k1, k2, n1, n2, before ) 
    180263      !!--------------------------------------------- 
    181264      !!           *** ROUTINE updateT *** 
    182265      !!--------------------------------------------- 
    183 #  include "domzgr_substitute.h90" 
     266 
    184267      INTEGER, INTENT(in) :: i1,i2,j1,j2,k1,k2,n1,n2 
    185       REAL(wp),DIMENSION(i1:i2,j1:j2,k1:k2,n1:n2), INTENT(inout) :: tabres 
     268      REAL(wp),DIMENSION(i1:i2,j1:j2,k1:k2,n1:n2), INTENT(inout) :: ptab 
    186269      LOGICAL, INTENT(in) :: before 
    187270      !! 
    188271      INTEGER :: ji,jj,jk,jn 
     272! VERTICAL REFINEMENT BEGIN 
     273      REAL(wp), DIMENSION(i1:i2,j1:j2,1:jpk,n1:n2) :: ptab_child 
     274      REAL(wp) :: h_in(k1:k2) 
     275      REAL(wp) :: h_out(1:jpk) 
     276      INTEGER :: N_in, N_out 
     277      REAL(wp) :: h_diff 
     278      REAL(wp) :: tabin(k1:k2,n1:n2) 
     279! VERTICAL REFINEMENT END 
    189280      !!--------------------------------------------- 
    190281      ! 
     
    194285               DO jj=j1,j2 
    195286                  DO ji=i1,i2 
    196                      tabres(ji,jj,jk,jn) = tsn(ji,jj,jk,jn) 
     287                     ptab(ji,jj,jk,jn) = tsn(ji,jj,jk,jn) 
    197288                  END DO 
    198289               END DO 
     
    200291         END DO 
    201292      ELSE 
     293! VERTICAL REFINEMENT BEGIN 
     294         ptab_child(:,:,:,:) = 0. 
     295          
     296         DO jj=j1,j2 
     297         DO ji=i1,i2 
     298           N_in = 0 
     299           DO jk=k1,k2 
     300             IF (update_scales_t(ji,jj,jk) == 0) EXIT 
     301             N_in = N_in + 1 
     302             tabin(jk,:) = ptab(ji,jj,jk,:) 
     303             h_in(N_in) = update_scales_t(ji,jj,jk) 
     304           ENDDO 
     305           N_out = 0 
     306           DO jk=1,jpk 
     307             IF (tmask(ji,jj,jk) == 0) EXIT 
     308             N_out = N_out + 1 
     309             h_out(N_out) = fse3t(ji,jj,jk) 
     310           ENDDO 
     311           IF (N_in > 0) THEN 
     312             h_diff = sum(h_out(1:N_out))-sum(h_in(1:N_in)) 
     313             IF (h_diff > 0) THEN 
     314               N_in = N_in + 1 
     315               h_in(N_in) = h_diff 
     316               tabin(N_in,:) = tabin(N_in-1,:) 
     317             ELSEIF (h_diff < 0) THEN 
     318             print *,'CHECK YOUR bathy T points ...',ji,jj,h_diff,sum(h_in(1:N_in)),sum(h_out(1:N_out)) 
     319             print *,'Nval = ',N_out,mbathy(ji,jj) 
     320             print *,'BATHY = ',gdepw_0(ji,jj,mbathy(ji,jj)+1),sum(e3t_0(ji,jj,1:mbathy(ji,jj))) 
     321          !   STOP 
     322               N_out = N_out + 1 
     323               h_out(N_out) = - h_diff 
     324             ENDIF 
     325             DO jn=n1,n2 
     326               CALL reconstructandremap(tabin(1:N_in,jn),h_in(1:N_in),ptab_child(ji,jj,1:N_out,jn),h_out(1:N_out),N_in,N_out) 
     327             ENDDO 
     328          ENDIF 
     329         ENDDO 
     330         ENDDO 
     331          
     332! WARNING : 
     333! ptab replaced by ptab_child in the following 
     334! k1 k2 replaced by 1 jpk 
     335! VERTICAL REFINEMENT END 
     336 
    202337         IF (.NOT.(lk_agrif_fstep.AND.(neuler==0))) THEN 
    203338            ! Add asselin part 
    204339            DO jn = n1,n2 
    205                DO jk=k1,k2 
     340               DO jk=1,jpk 
    206341                  DO jj=j1,j2 
    207342                     DO ji=i1,i2 
    208                         IF( tabres(ji,jj,jk,jn) .NE. 0. ) THEN 
     343                        IF( ptab_child(ji,jj,jk,jn) .NE. 0. ) THEN 
    209344                           tsb(ji,jj,jk,jn) = tsb(ji,jj,jk,jn) &  
    210                                  & + atfp * ( tabres(ji,jj,jk,jn) & 
     345                                 & + atfp * ( ptab_child(ji,jj,jk,jn) & 
    211346                                 &             - tsn(ji,jj,jk,jn) ) * tmask(ji,jj,jk) 
    212347                        ENDIF 
     
    217352         ENDIF 
    218353         DO jn = n1,n2 
    219             DO jk=k1,k2 
     354            DO jk=1,jpk 
    220355               DO jj=j1,j2 
    221356                  DO ji=i1,i2 
    222                      IF( tabres(ji,jj,jk,jn) .NE. 0. ) THEN  
    223                         tsn(ji,jj,jk,jn) = tabres(ji,jj,jk,jn) * tmask(ji,jj,jk) 
     357                     IF( ptab_child(ji,jj,jk,jn) .NE. 0. ) THEN  
     358                        tsn(ji,jj,jk,jn) = ptab_child(ji,jj,jk,jn) * tmask(ji,jj,jk) 
    224359                     END IF 
    225360                  END DO 
     
    231366   END SUBROUTINE updateTS 
    232367 
    233    SUBROUTINE updateu( tabres, i1, i2, j1, j2, k1, k2, before ) 
     368   SUBROUTINE updateu( ptab, i1, i2, j1, j2, k1, k2, before ) 
    234369      !!--------------------------------------------- 
    235370      !!           *** ROUTINE updateu *** 
    236371      !!--------------------------------------------- 
    237 #  include "domzgr_substitute.h90" 
    238372      !! 
    239373      INTEGER, INTENT(in) :: i1, i2, j1, j2, k1, k2 
    240       REAL(wp), DIMENSION(i1:i2,j1:j2,k1:k2), INTENT(inout) :: tabres 
     374      REAL(wp), DIMENSION(i1:i2,j1:j2,k1:k2), INTENT(inout) :: ptab 
    241375      LOGICAL, INTENT(in) :: before 
    242376      !!  
    243377      INTEGER :: ji, jj, jk 
    244378      REAL(wp) :: zrhoy 
     379! VERTICAL REFINEMENT BEGIN 
     380      REAL(wp), DIMENSION(i1:i2,j1:j2,1:jpk) :: ptab_child 
     381      REAL(wp) :: h_in(k1:k2) 
     382      REAL(wp) :: h_out(1:jpk) 
     383      INTEGER :: N_in, N_out 
     384      REAL(wp) :: h_diff 
     385      REAL(wp) :: tabin(k1:k2) 
     386! VERTICAL REFINEMENT END 
    245387      !!--------------------------------------------- 
    246388      !  
     
    250392            DO jj=j1,j2 
    251393               DO ji=i1,i2 
    252                   tabres(ji,jj,jk) = e2u(ji,jj) * un(ji,jj,jk) 
    253                   tabres(ji,jj,jk) = tabres(ji,jj,jk) * fse3u_n(ji,jj,jk) 
    254                END DO 
    255             END DO 
    256          END DO 
    257          tabres = zrhoy * tabres 
    258       ELSE 
    259          DO jk=k1,k2 
    260             DO jj=j1,j2 
    261                DO ji=i1,i2 
    262                   tabres(ji,jj,jk) = tabres(ji,jj,jk) / e2u(ji,jj) / fse3u_n(ji,jj,jk) 
     394                  ptab(ji,jj,jk) = e2u(ji,jj) * un(ji,jj,jk) 
     395                  ptab(ji,jj,jk) = ptab(ji,jj,jk) * fse3u_n(ji,jj,jk) 
     396               END DO 
     397            END DO 
     398         END DO 
     399         ptab = zrhoy * ptab 
     400      ELSE 
     401! VERTICAL REFINEMENT BEGIN 
     402         ptab_child(:,:,:) = 0. 
     403          
     404         DO jj=j1,j2 
     405         DO ji=i1,i2 
     406           N_in = 0 
     407           DO jk=k1,k2 
     408             IF (update_scales_u(ji,jj,jk) == 0) EXIT 
     409             N_in = N_in + 1 
     410             tabin(jk) = ptab(ji,jj,jk)/update_scales_u(ji,jj,jk) 
     411             h_in(N_in) = update_scales_u(ji,jj,jk) 
     412           ENDDO 
     413           N_out = 0 
     414           DO jk=1,jpk 
     415             IF (umask(ji,jj,jk) == 0) EXIT 
     416             N_out = N_out + 1 
     417             h_out(N_out) = fse3u(ji,jj,jk) 
     418           ENDDO 
     419           IF (N_in * N_out > 0) THEN 
     420             h_diff = sum(h_out(1:N_out))-sum(h_in(1:N_in)) 
     421             if (h_diff < 0.) then 
     422             print *,'CHECK YOUR BATHY ...' 
     423             stop 
     424             else ! Extends with 0 
     425             N_in = N_in + 1 
     426             tabin(N_in) = 0. 
     427             h_in(N_in) = h_diff 
     428             endif 
     429             CALL reconstructandremap(tabin(1:N_in),h_in(1:N_in),ptab_child(ji,jj,1:N_out),h_out(1:N_out),N_in,N_out) 
     430          ENDIF 
     431         ENDDO 
     432         ENDDO 
     433          
     434! WARNING : 
     435! ptab replaced by ptab_child in the following 
     436! k1 k2 replaced by 1 jpk 
     437! remove division by fs e3u (already done) 
     438! VERTICAL REFINEMENT END 
     439 
     440         DO jk=1,jpk 
     441            DO jj=j1,j2 
     442               DO ji=i1,i2 
     443                  ptab_child(ji,jj,jk) = ptab_child(ji,jj,jk) / e2u(ji,jj) 
    263444                  ! 
    264445                  IF (.NOT.(lk_agrif_fstep.AND.(neuler==0))) THEN ! Add asselin part 
    265446                     ub(ji,jj,jk) = ub(ji,jj,jk) &  
    266                            & + atfp * ( tabres(ji,jj,jk) - un(ji,jj,jk) ) * umask(ji,jj,jk) 
     447                           & + atfp * ( ptab_child(ji,jj,jk) - un(ji,jj,jk) ) * umask(ji,jj,jk) 
    267448                  ENDIF 
    268449                  ! 
    269                   un(ji,jj,jk) = tabres(ji,jj,jk) * umask(ji,jj,jk) 
     450                  un(ji,jj,jk) = ptab_child(ji,jj,jk) * umask(ji,jj,jk) 
    270451               END DO 
    271452            END DO 
     
    275456   END SUBROUTINE updateu 
    276457 
    277    SUBROUTINE updatev( tabres, i1, i2, j1, j2, k1, k2, before ) 
     458   SUBROUTINE updatev( ptab, i1, i2, j1, j2, k1, k2, before ) 
    278459      !!--------------------------------------------- 
    279460      !!           *** ROUTINE updatev *** 
    280461      !!--------------------------------------------- 
    281 #  include "domzgr_substitute.h90" 
    282462      !! 
    283463      INTEGER :: i1,i2,j1,j2,k1,k2 
    284464      INTEGER :: ji,jj,jk 
    285       REAL(wp), DIMENSION(i1:i2,j1:j2,k1:k2) :: tabres 
     465      REAL(wp), DIMENSION(i1:i2,j1:j2,k1:k2) :: ptab 
    286466      LOGICAL :: before 
    287467      !! 
    288468      REAL(wp) :: zrhox 
     469! VERTICAL REFINEMENT BEGIN 
     470      REAL(wp), DIMENSION(i1:i2,j1:j2,1:jpk) :: ptab_child 
     471      REAL(wp) :: h_in(k1:k2) 
     472      REAL(wp) :: h_out(1:jpk) 
     473      INTEGER :: N_in, N_out 
     474      REAL(wp) :: h_diff 
     475      REAL(wp) :: tabin(k1:k2) 
     476! VERTICAL REFINEMENT END 
    289477      !!---------------------------------------------       
    290478      ! 
     
    294482            DO jj=j1,j2 
    295483               DO ji=i1,i2 
    296                   tabres(ji,jj,jk) = e1v(ji,jj) * vn(ji,jj,jk) 
    297                   tabres(ji,jj,jk) = tabres(ji,jj,jk) * fse3v_n(ji,jj,jk) 
    298                END DO 
    299             END DO 
    300          END DO 
    301          tabres = zrhox * tabres 
    302       ELSE 
     484                  ptab(ji,jj,jk) = e1v(ji,jj) * vn(ji,jj,jk) 
     485                  ptab(ji,jj,jk) = ptab(ji,jj,jk) * fse3v_n(ji,jj,jk) 
     486               END DO 
     487            END DO 
     488         END DO 
     489         ptab = zrhox * ptab 
     490      ELSE 
     491! VERTICAL REFINEMENT BEGIN 
     492         ptab_child(:,:,:) = 0. 
     493          
     494         DO jj=j1,j2 
     495         DO ji=i1,i2 
     496           N_in = 0 
     497           DO jk=k1,k2 
     498             IF (update_scales_v(ji,jj,jk) == 0) EXIT 
     499             N_in = N_in + 1 
     500             tabin(jk) = ptab(ji,jj,jk)/update_scales_v(ji,jj,jk) 
     501             h_in(N_in) = update_scales_v(ji,jj,jk) 
     502           ENDDO 
     503           N_out = 0 
     504           DO jk=1,jpk 
     505             IF (vmask(ji,jj,jk) == 0) EXIT 
     506             N_out = N_out + 1 
     507             h_out(N_out) = fse3v(ji,jj,jk) 
     508           ENDDO 
     509           IF (N_in * N_out > 0) THEN 
     510             h_diff = sum(h_out(1:N_out))-sum(h_in(1:N_in)) 
     511             if (h_diff < 0.) then 
     512             print *,'CHECK YOUR BATHY ...' 
     513             stop 
     514             else ! Extends with 0 
     515             N_in = N_in + 1 
     516             tabin(N_in) = 0. 
     517             h_in(N_in) = h_diff 
     518             endif 
     519             CALL reconstructandremap(tabin(1:N_in),h_in(1:N_in),ptab_child(ji,jj,1:N_out),h_out(1:N_out),N_in,N_out) 
     520          ENDIF 
     521         ENDDO 
     522         ENDDO 
     523          
     524! WARNING : 
     525! ptab replaced by ptab_child in the following 
     526! k1 k2 replaced by 1 jpk 
     527! remove division by fs e3v (already done) 
     528! VERTICAL REFINEMENT END 
     529 
    303530         DO jk=k1,k2 
    304531            DO jj=j1,j2 
    305532               DO ji=i1,i2 
    306                   tabres(ji,jj,jk) = tabres(ji,jj,jk) / e1v(ji,jj) / fse3v_n(ji,jj,jk) 
     533                  ptab_child(ji,jj,jk) = ptab_child(ji,jj,jk) / e1v(ji,jj) 
    307534                  ! 
    308535                  IF (.NOT.(lk_agrif_fstep.AND.(neuler==0))) THEN ! Add asselin part 
    309536                     vb(ji,jj,jk) = vb(ji,jj,jk) &  
    310                            & + atfp * ( tabres(ji,jj,jk) - vn(ji,jj,jk) ) * vmask(ji,jj,jk) 
     537                           & + atfp * ( ptab_child(ji,jj,jk) - vn(ji,jj,jk) ) * vmask(ji,jj,jk) 
    311538                  ENDIF 
    312539                  ! 
    313                   vn(ji,jj,jk) = tabres(ji,jj,jk) * vmask(ji,jj,jk) 
     540                  vn(ji,jj,jk) = ptab_child(ji,jj,jk) * vmask(ji,jj,jk) 
    314541               END DO 
    315542            END DO 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/NEMO/NST_SRC/agrif_user.F90

    r5819 r6258  
    22!!---------------------------------------------------------------------- 
    33!! NEMO/NST 3.4 , NEMO Consortium (2012) 
    4 !! $Id$ 
     4!! $Id: agrif_user.F90 5081 2015-02-13 09:51:27Z smasson $ 
    55!! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    66!!---------------------------------------------------------------------- 
     
    1717   USE par_oce 
    1818   USE dom_oce 
     19   USE Agrif_Util 
     20   USE lib_mpp         ! distributed memory computing 
    1921   USE nemogcm 
    2022   ! 
    2123   IMPLICIT NONE 
     24   INTEGER ::   ios 
     25   LOGICAL ::  is_open 
     26   NAMELIST/namcfg/ cp_cfg, cp_cfz, jp_cfg, jpidta, jpjdta, jpkdta, jpiglo, jpjglo, & 
     27         &             jpizoom, jpjzoom, jperio 
    2228   !!---------------------------------------------------------------------- 
    2329   ! 
     
    4551      nperio  = 0 
    4652      jperio  = 0 
     53   ELSE 
     54   IF (Agrif_Nb_step() == 0) THEN 
     55      INQUIRE(file = 'namelist_ref', opened = is_open) 
     56      IF (.not.is_open) THEN 
     57      !                             ! Open reference namelist and configuration namelist files 
     58      CALL ctl_opn( numnam_ref, 'namelist_ref', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 
     59      CALL ctl_opn( numnam_cfg, 'namelist_cfg', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 
     60       
     61      REWIND( numnam_ref )              ! Namelist namcfg in reference namelist : Control prints & Benchmark 
     62      READ  ( numnam_ref, namcfg, IOSTAT = ios, ERR = 903 ) 
     63903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfg in reference namelist', .TRUE. ) 
     64 
     65      REWIND( numnam_cfg )              ! Namelist namcfg in confguration namelist : Control prints & Benchmark 
     66      READ  ( numnam_cfg, namcfg, IOSTAT = ios, ERR = 904 ) 
     67904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfg in configuration namelist', .TRUE. )  
     68 
     69      IF( numnam_ref      /= -1 )   CLOSE( numnam_ref      )   ! oce reference namelist 
     70      IF( numnam_cfg      /= -1 )   CLOSE( numnam_cfg      )   ! oce configuration namelist 
     71      ENDIF 
     72   ENDIF 
    4773   ENDIF 
    4874   ! 
     
    6793   ! 0. Initializations 
    6894   !------------------- 
    69    IF( cp_cfg == 'orca' ) THEN 
    70       IF ( jp_cfg == 2 .OR. jp_cfg == 025 .OR. jp_cfg == 05 & 
    71             &                      .OR. jp_cfg == 4 ) THEN 
    72          jp_cfg = -1    ! set special value for jp_cfg on fine grids 
    73          cp_cfg = "default" 
    74       ENDIF 
    75    ENDIF 
    7695   ! Specific fine grid Initializations 
    7796   ! no tracer damping on fine grids 
     
    188207   !--------------------------------------------------------------------- 
    189208   CALL agrif_declare_var 
     209 
     210! VERTICAL REFINEMENT BEGIN 
     211   CALL Agrif_Init_InterpScales() 
     212   CALL Agrif_Init_UpdateScales() 
     213! VERTICAL REFINEMENT END 
    190214 
    191215   ! 2. First interpolations of potentially non zero fields 
     
    289313         CALL Agrif_Bc_variable(vmsk_id,calledweight=1.,procname=interpvmsk) 
    290314    ! check if tmask and vertical scale factors agree with parent over first two coarse grid points: 
    291          CALL Agrif_Bc_variable(e3t_id,calledweight=1.,procname=interpe3t) 
     315!        CALL Agrif_Bc_variable(e3t_id,calledweight=1.,procname=interpe3t) 
    292316         ! 
    293317         IF (lk_mpp) CALL mpp_sum( kindic_agr ) 
     
    343367   CALL agrif_declare_variable((/2,2,0,0/),(/3,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,jpts/),tsn_sponge_id) 
    344368 
    345    CALL agrif_declare_variable((/1,2,0/),(/2,3,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),un_interp_id) 
    346    CALL agrif_declare_variable((/2,1,0/),(/3,2,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),vn_interp_id) 
     369   CALL agrif_declare_variable((/1,2,0,0/),(/2,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,2/),un_interp_id) 
     370   CALL agrif_declare_variable((/2,1,0,0/),(/3,2,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,2/),vn_interp_id) 
    347371   CALL agrif_declare_variable((/1,2,0/),(/2,3,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),un_update_id) 
    348372   CALL agrif_declare_variable((/2,1,0/),(/3,2,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),vn_update_id) 
     
    353377   CALL agrif_declare_variable((/1,2,0/),(/2,3,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),umsk_id) 
    354378   CALL agrif_declare_variable((/2,1,0/),(/3,2,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),vmsk_id) 
    355  
    356    CALL agrif_declare_variable((/2,2,0,0/),(/3,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,3/),scales_t_id) 
    357379 
    358380   CALL agrif_declare_variable((/1,2/),(/2,3/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),unb_id) 
     
    365387   CALL agrif_declare_variable((/2,2/),(/3,3/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),sshn_id) 
    366388 
     389! VERTICAL REFINEMENT BEGIN 
     390   CALL agrif_declare_variable((/2,2,0/),(/3,3,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),scales_t_id) 
     391   CALL agrif_declare_variable((/1,2,0/),(/2,3,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),scales_u_id) 
     392   CALL agrif_declare_variable((/2,1,0/),(/3,2,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),scales_v_id) 
     393! VERTICAL REFINEMENT END 
     394 
    367395# if defined key_zdftke 
    368396   CALL agrif_declare_variable((/2,2,0/),(/3,3,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/), en_id) 
     
    393421   CALL Agrif_Set_bcinterp(umsk_id,interp=AGRIF_constant) 
    394422   CALL Agrif_Set_bcinterp(vmsk_id,interp=AGRIF_constant) 
     423 
     424! VERTICAL REFINEMENT BEGIN 
     425   CALL Agrif_Set_bcinterp(scales_t_id,interp=Agrif_linear) 
     426   CALL Agrif_Set_bcinterp(scales_u_id,interp1=Agrif_linear,interp2=Agrif_constant) 
     427   CALL Agrif_Set_bcinterp(scales_v_id,interp1=Agrif_constant,interp2=AGRIF_linear) 
     428! VERTICAL REFINEMENT END 
    395429 
    396430# if defined key_zdftke 
     
    422456   CALL Agrif_Set_bc(vmsk_id,(/0,0/)) 
    423457 
     458! VERTICAL REFINEMENT BEGIN 
     459   CALL Agrif_Set_bc(scales_t_id,(/-nn_sponge_len*Agrif_irhox()-1,1/)) 
     460   CALL Agrif_Set_bc(scales_u_id,(/-nn_sponge_len*Agrif_irhox()-1,1/)) 
     461   CALL Agrif_Set_bc(scales_v_id,(/-nn_sponge_len*Agrif_irhox()-1,1/)) 
     462! VERTICAL REFINEMENT END 
     463 
    424464# if defined key_zdftke 
    425465   CALL Agrif_Set_bc(avm_id ,(/0,1/)) 
     
    439479   CALL Agrif_Set_Updatetype(ub2b_update_id,update1 = Agrif_Update_Copy, update2 = Agrif_Update_Average) 
    440480   CALL Agrif_Set_Updatetype(vb2b_update_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy) 
     481 
     482! VERTICAL REFINEMENT BEGIN 
     483   CALL Agrif_Set_Updatetype(scales_t_id, update = AGRIF_Update_Average) 
     484   CALL Agrif_Set_Updatetype(scales_u_id,update1 = Agrif_Update_Copy, update2 = Agrif_Update_Average) 
     485   CALL Agrif_Set_Updatetype(scales_v_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy) 
     486! VERTICAL REFINEMENT END 
    441487 
    442488# if defined key_zdftke 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/NEMO/OPA_SRC/DIA/diawri.F90

    r5819 r6258  
    405405      !! 
    406406      LOGICAL ::   ll_print = .FALSE.                        ! =T print and flush numout 
    407       CHARACTER (len=40) ::   clhstnam, clop, clmx           ! local names 
     407      CHARACTER (len=60) ::   clhstnam, clop, clmx           ! local names 
    408408      INTEGER  ::   inum = 11                                ! temporary logical unit 
    409409      INTEGER  ::   ji, jj, jk                               ! dummy loop indices 
     
    779779      IF( lk_vvl ) THEN 
    780780         zw3d(:,:,:) = ( ( fse3t_n(:,:,:) - e3t_0(:,:,:) ) / e3t_0(:,:,:) * 100 * tmask(:,:,:) ) ** 2 
    781          CALL histwrite( nid_T, "vovvle3t", it, fse3t_n (:,:,:) , ndim_T , ndex_T  )   ! level thickness 
     781         CALL histwrite( nid_T, "vovvle3t", it, fse3t_n(:,:,:) , ndim_T , ndex_T  )   ! level thickness 
    782782         CALL histwrite( nid_T, "vovvldep", it, fsdept_n(:,:,:) , ndim_T , ndex_T  )   ! t-point depth 
    783783         CALL histwrite( nid_T, "vovvldef", it, zw3d             , ndim_T , ndex_T  )   ! level thickness deformation 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r5819 r6258  
    9797      END DO 
    9898      ! 
    99       IF( lk_vvl )           CALL dom_vvl_init ! Vertical variable mesh 
     99      IF( lk_vvl )           THEN 
     100        CALL dom_vvl_init ! Vertical variable mesh 
     101      ELSE 
     102        ln_vvl_ztilde = .FALSE. 
     103        ln_vvl_layer  = .FALSE. 
     104      ENDIF 
     105 
    100106      ! 
    101107      IF( lk_c1d         )   CALL cor_c1d      ! 1D configuration: Coriolis set at T-point 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/NEMO/OPA_SRC/DOM/domvvl.F90

    r5819 r6258  
    620620      ! - ML - fse3u_b and fse3v_b are allready computed in dynnxt 
    621621      ! - JC - hu_b, hv_b, hur_b, hvr_b also 
    622       CALL dom_vvl_interpol( fse3u_n(:,:,:), fse3f_n (:,:,:), 'F'  ) 
     622      CALL dom_vvl_interpol( fse3u_n(:,:,:), fse3f_n(:,:,:), 'F'  ) 
    623623      ! Vertical scale factor interpolations 
    624624      ! ------------------------------------ 
    625       CALL dom_vvl_interpol( fse3t_n(:,:,:), fse3w_n (:,:,:), 'W'  ) 
     625      CALL dom_vvl_interpol( fse3t_n(:,:,:), fse3w_n(:,:,:), 'W'  ) 
    626626      CALL dom_vvl_interpol( fse3u_n(:,:,:), fse3uw_n(:,:,:), 'UW' ) 
    627627      CALL dom_vvl_interpol( fse3v_n(:,:,:), fse3vw_n(:,:,:), 'VW' ) 
    628       CALL dom_vvl_interpol( fse3t_b(:,:,:), fse3w_b (:,:,:), 'W'  ) 
     628      CALL dom_vvl_interpol( fse3t_b(:,:,:), fse3w_b(:,:,:), 'W'  ) 
    629629      CALL dom_vvl_interpol( fse3u_b(:,:,:), fse3uw_b(:,:,:), 'UW' ) 
    630630      CALL dom_vvl_interpol( fse3v_b(:,:,:), fse3vw_b(:,:,:), 'VW' ) 
     
    652652      ! Local depth and Inverse of the local depth of the water column at u- and v- points 
    653653      ! ---------------------------------------------------------------------------------- 
    654       hu (:,:) = hu_a (:,:) 
    655       hv (:,:) = hv_a (:,:) 
     654      hu (:,:) = hu_a(:,:) 
     655      hv (:,:) = hv_a(:,:) 
    656656 
    657657      ! Inverse of the local depth 
     
    668668      ! Write outputs 
    669669      ! ============= 
    670       CALL iom_put(     "e3t" , fse3t_n  (:,:,:) ) 
    671       CALL iom_put(     "e3u" , fse3u_n  (:,:,:) ) 
    672       CALL iom_put(     "e3v" , fse3v_n  (:,:,:) ) 
    673       CALL iom_put(     "e3w" , fse3w_n  (:,:,:) ) 
    674       CALL iom_put( "tpt_dep" , fsde3w_n (:,:,:) ) 
     670      CALL iom_put(     "e3t" , fse3t_n(:,:,:) ) 
     671      CALL iom_put(     "e3u" , fse3u_n(:,:,:) ) 
     672      CALL iom_put(     "e3v" , fse3v_n(:,:,:) ) 
     673      CALL iom_put(     "e3w" , fse3w_n(:,:,:) ) 
     674      CALL iom_put( "tpt_dep" , fsde3w_n(:,:,:) ) 
    675675      IF( iom_use("e3tdef") )   & 
    676676         CALL iom_put( "e3tdef"  , ( ( fse3t_n(:,:,:) - e3t_0(:,:,:) ) / e3t_0(:,:,:) * 100 * tmask(:,:,:) ) ** 2 ) 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/NEMO/OPA_SRC/DOM/domzgr.F90

    r5819 r6258  
    294294               e3t_1d  (jk) =          za0      + za1        * TANH(       (zt-zkth) / zacr   ) 
    295295            END DO 
     296! MODIFY THE COMPUTATION OF GDEPW_1D - Laurent Debreu Change for Agrif Vertical interpolation 
     297            gdepw_1d(1) = 0. 
     298            do jk=2,jpk 
     299            gdepw_1d(jk) = gdepw_1d(jk-1)+e3t_1d(jk-1) 
     300            enddo 
    296301         ELSE 
    297302            DO jk = 1, jpk 
     
    898903      ! 
    899904      DO jk = 1, jpk 
    900          gdept_0 (:,:,jk) = gdept_1d(jk) 
    901          gdepw_0 (:,:,jk) = gdepw_1d(jk) 
     905         gdept_0(:,:,jk) = gdept_1d(jk) 
     906         gdepw_0(:,:,jk) = gdepw_1d(jk) 
    902907         gdep3w_0(:,:,jk) = gdepw_1d(jk) 
    903          e3t_0   (:,:,jk) = e3t_1d  (jk) 
    904          e3u_0   (:,:,jk) = e3t_1d  (jk) 
    905          e3v_0   (:,:,jk) = e3t_1d  (jk) 
    906          e3f_0   (:,:,jk) = e3t_1d  (jk) 
    907          e3w_0   (:,:,jk) = e3w_1d  (jk) 
    908          e3uw_0  (:,:,jk) = e3w_1d  (jk) 
    909          e3vw_0  (:,:,jk) = e3w_1d  (jk) 
     908         e3t_0(:,:,jk) = e3t_1d(jk) 
     909         e3u_0(:,:,jk) = e3t_1d(jk) 
     910         e3v_0(:,:,jk) = e3t_1d(jk) 
     911         e3f_0(:,:,jk) = e3t_1d(jk) 
     912         e3w_0(:,:,jk) = e3w_1d(jk) 
     913         e3uw_0(:,:,jk) = e3w_1d(jk) 
     914         e3vw_0(:,:,jk) = e3w_1d(jk) 
    910915      END DO 
    911916      ! 
     
    10431048                     &                             * ((gdept_1d(     ik  ) - gdepw_1d(ik) )   & 
    10441049                     &                             / ( gdepw_1d(     ik+1) - gdepw_1d(ik) )) 
    1045                   e3t_0  (ji,jj,ik) = e3t_1d  (ik) * ( gdepw_0 (ji,jj,ik+1) - gdepw_1d(ik) )   &  
     1050                  e3t_0(ji,jj,ik) = e3t_1d(ik) * ( gdepw_0 (ji,jj,ik+1) - gdepw_1d(ik) )   &  
    10461051                     &                             / ( gdepw_1d(      ik+1) - gdepw_1d(ik) )  
    10471052                  e3w_0(ji,jj,ik) = 0.5_wp * ( gdepw_0(ji,jj,ik+1) + gdepw_1d(ik+1) - 2._wp * gdepw_1d(ik) )   & 
    10481053                     &                     * ( e3w_1d(ik) / ( gdepw_1d(ik+1) - gdepw_1d(ik) ) ) 
    10491054                  !       ... on ik+1 
    1050                   e3w_0  (ji,jj,ik+1) = e3t_0  (ji,jj,ik) 
    1051                   e3t_0  (ji,jj,ik+1) = e3t_0  (ji,jj,ik) 
     1055                  e3w_0(ji,jj,ik+1) = e3t_0(ji,jj,ik) 
     1056                  e3t_0(ji,jj,ik+1) = e3t_0(ji,jj,ik) 
    10521057                  gdept_0(ji,jj,ik+1) = gdept_0(ji,jj,ik) + e3t_0(ji,jj,ik) 
    10531058               ENDIF 
     
    10891094                     &                               * ( gdepw_1d(ik+1) - gdept_1d(ik)      )   &  
    10901095                     &                               / ( gdepw_1d(ik+1) - gdepw_1d(ik)      )  
    1091                   e3t_0  (ji,jj,ik  ) = gdepw_1d(ik+1) - gdepw_0(ji,jj,ik)  
    1092                   e3w_0  (ji,jj,ik+1) = gdept_1d(ik+1) - gdept_0(ji,jj,ik) 
     1096                  e3t_0(ji,jj,ik  ) = gdepw_1d(ik+1) - gdepw_0(ji,jj,ik)  
     1097                  e3w_0(ji,jj,ik+1) = gdept_1d(ik+1) - gdept_0(ji,jj,ik) 
    10931098 
    10941099                  IF( ik + 1 == mbathy(ji,jj) ) THEN               ! ice shelf point only (2 cell water column)  
    1095                      e3w_0  (ji,jj,ik+1) = gdept_0(ji,jj,ik+1) - gdept_0(ji,jj,ik)  
     1100                     e3w_0(ji,jj,ik+1) = gdept_0(ji,jj,ik+1) - gdept_0(ji,jj,ik)  
    10961101                  ENDIF  
    10971102               !       ... on ik / ik-1  
     
    21212126      fsdepw(:,:,:) = gdepw_0 (:,:,:) 
    21222127      fsde3w(:,:,:) = gdep3w_0(:,:,:) 
    2123       fse3t (:,:,:) = e3t_0   (:,:,:) 
    2124       fse3u (:,:,:) = e3u_0   (:,:,:) 
    2125       fse3v (:,:,:) = e3v_0   (:,:,:) 
    2126       fse3f (:,:,:) = e3f_0   (:,:,:) 
    2127       fse3w (:,:,:) = e3w_0   (:,:,:) 
    2128       fse3uw(:,:,:) = e3uw_0  (:,:,:) 
    2129       fse3vw(:,:,:) = e3vw_0  (:,:,:) 
     2128      fse3t(:,:,:) = e3t_0(:,:,:) 
     2129      fse3u(:,:,:) = e3u_0(:,:,:) 
     2130      fse3v(:,:,:) = e3v_0(:,:,:) 
     2131      fse3f(:,:,:) = e3f_0(:,:,:) 
     2132      fse3w(:,:,:) = e3w_0(:,:,:) 
     2133      fse3uw(:,:,:) = e3uw_0(:,:,:) 
     2134      fse3vw(:,:,:) = e3vw_0(:,:,:) 
    21302135!! 
    21312136      ! HYBRID :  
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/NEMO/OPA_SRC/DYN/dynhpg.F90

    r5819 r6258  
    845845               &                   * (  rhd(ji,jj,1)                                    & 
    846846               &                     + 0.5_wp * ( rhd(ji,jj,2) - rhd(ji,jj,1) )         & 
    847                &                              * ( fse3w (ji,jj,1) - fsde3w(ji,jj,1) )   & 
     847               &                              * ( fse3w(ji,jj,1) - fsde3w(ji,jj,1) )   & 
    848848               &                              / ( fsde3w(ji,jj,2) - fsde3w(ji,jj,1) )  ) 
    849849         END DO 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg_flt.F90

    r5819 r6258  
    127127         ! read filtered free surface arrays in restart file 
    128128         ! when using agrif, sshn, gcx have to be read in istate 
    129          IF(.NOT. lk_agrif)   CALL flt_rst( nit000, 'READ' )      ! read or initialize the following fields: 
     129         IF(.NOT. lk_agrif) THEN 
     130            CALL flt_rst( nit000, 'READ' )      ! read or initialize the following fields: 
    130131         !                                                        ! gcx, gcxb 
     132         ELSE 
     133            gcx (:,:) = 0.e0 
     134            gcxb(:,:) = 0.e0 
     135         ENDIF 
    131136      ENDIF 
    132137 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/NEMO/OPA_SRC/SOL/solmat.F90

    r5819 r6258  
    213213      DO jj = 1, jpj 
    214214         DO ji = 1, jpi 
    215             IF( bmask(ji,jj) /= 0.e0 )   gcdprc(ji,jj) = 1.e0 / gcdmat(ji,jj) 
     215            IF( bmask(ji,jj) /= 0.e0 .AND.(gcdmat(ji,jj)/=0.) )   gcdprc(ji,jj) = 1.e0 / gcdmat(ji,jj) 
    216216         END DO 
    217217      END DO 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/NEMO/OPA_SRC/TRA/trazdf_imp.F90

    r5819 r6258  
    210210               DO ji = fs_2, fs_jpim1 
    211211                  ze3tb = ( 1. - r_vvl ) + r_vvl * fse3t_b(ji,jj,jk) 
    212                   ze3tn = ( 1. - r_vvl ) + r_vvl * fse3t  (ji,jj,jk) 
     212                  ze3tn = ( 1. - r_vvl ) + r_vvl * fse3t(ji,jj,jk) 
    213213                  zrhs = ze3tb * ptb(ji,jj,jk,jn) + p2dt(jk) * ze3tn * pta(ji,jj,jk,jn)   ! zrhs=right hand side  
    214214                  pta(ji,jj,jk,jn) = zrhs - zwi(ji,jj,jk) / zwt(ji,jj,jk-1) * pta(ji,jj,jk-1,jn) 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/NEMO/OPA_SRC/TRD/trdglo.F90

    r5819 r6258  
    8585      IF( MOD(kt,nn_trd) == 0 .OR. kt == nit000 .OR. kt == nitend ) THEN 
    8686         ! 
    87          SELECT CASE( ctype ) 
    88          ! 
    89          CASE( 'TRA' )          !==  Tracers (T & S)  ==! 
    90             DO jk = 1, jpkm1       ! global sum of mask volume trend and trend*T (including interior mask) 
    91                DO jj = 1, jpj 
    92                   DO ji = 1, jpi         
    93                      zvm = e1e2t(ji,jj) * fse3t(ji,jj,jk) * tmask(ji,jj,jk) * tmask_i(ji,jj) 
    94                      zvt = ptrdx(ji,jj,jk) * zvm 
    95                      zvs = ptrdy(ji,jj,jk) * zvm 
    96                      tmo(ktrd) = tmo(ktrd) + zvt    
    97                      smo(ktrd) = smo(ktrd) + zvs 
    98                      t2 (ktrd) = t2(ktrd)  + zvt * tsn(ji,jj,jk,jp_tem) 
    99                      s2 (ktrd) = s2(ktrd)  + zvs * tsn(ji,jj,jk,jp_sal) 
     87      SELECT CASE( ctype ) 
     88      ! 
     89      CASE( 'TRA' )          !==  Tracers (T & S)  ==! 
     90         DO jk = 1, jpkm1       ! global sum of mask volume trend and trend*T (including interior mask) 
     91            DO jj = 1, jpj 
     92               DO ji = 1, jpi         
     93                  zvm = e1e2t(ji,jj) * fse3t(ji,jj,jk) * tmask(ji,jj,jk) * tmask_i(ji,jj) 
     94                  zvt = ptrdx(ji,jj,jk) * zvm 
     95                  zvs = ptrdy(ji,jj,jk) * zvm 
     96                  tmo(ktrd) = tmo(ktrd) + zvt    
     97                  smo(ktrd) = smo(ktrd) + zvs 
     98                  t2 (ktrd) = t2(ktrd)  + zvt * tsn(ji,jj,jk,jp_tem) 
     99                  s2 (ktrd) = s2(ktrd)  + zvs * tsn(ji,jj,jk,jp_sal) 
    100100                  END DO 
    101101               END DO 
     
    113113               CALL glo_tra_wri( kt )             ! print the results in ocean.output 
    114114               !                 
    115                tmo(:) = 0._wp                     ! prepare the next time step (domain averaged array reset to zero) 
    116                smo(:) = 0._wp 
     115            tmo(:) = 0._wp                     ! prepare the next time step (domain averaged array reset to zero) 
     116            smo(:) = 0._wp 
    117117               t2 (:) = 0._wp 
    118118               s2 (:) = 0._wp 
     
    348348            WRITE (numout,9541) ( hke(jpdyn_keg) + hke(jpdyn_rvo) + hke(jpdyn_zad) ) / tvolt 
    349349            WRITE (numout,9542) ( hke(jpdyn_keg) + hke(jpdyn_zad) ) / tvolt 
    350             WRITE (numout,9543) ( hke(jpdyn_pvo) ) / tvolt 
    351             WRITE (numout,9544) ( hke(jpdyn_rvo) ) / tvolt 
    352             WRITE (numout,9545) ( hke(jpdyn_spg) ) / tvolt 
    353             WRITE (numout,9546) ( hke(jpdyn_ldf) ) / tvolt 
    354             WRITE (numout,9547) ( hke(jpdyn_zdf) ) / tvolt 
    355             WRITE (numout,9548) ( hke(jpdyn_hpg) ) / tvolt, rpktrd / tvolt 
     350            WRITE (numout,9543)   hke(jpdyn_pvo)  / tvolt 
     351            WRITE (numout,9544)   hke(jpdyn_rvo)  / tvolt 
     352            WRITE (numout,9545)   hke(jpdyn_spg)  / tvolt 
     353            WRITE (numout,9546)   hke(jpdyn_ldf)  / tvolt 
     354            WRITE (numout,9547)   hke(jpdyn_zdf)  / tvolt 
     355            WRITE (numout,9548)   hke(jpdyn_hpg)  / tvolt, rpktrd / tvolt 
    356356            WRITE (numout,*) 
    357357            WRITE (numout,*) 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/NEMO/OPA_SRC/TRD/trdmxl.F90

    r5819 r6258  
    464464      itmod = kt - nit000 + 1 
    465465 
    466       MODULO_NTRD : IF( MOD( itmod, nn_trd ) == 0 ) THEN        ! nitend MUST be multiple of nn_trd 
     466      IF( MOD( itmod, nn_trd ) == 0 ) THEN        ! nitend MUST be multiple of nn_trd 
    467467         ! 
    468468         ztmltot (:,:) = 0.e0   ;   zsmltot (:,:) = 0.e0   ! reset arrays to zero 
     
    636636         END IF 
    637637         ! 
    638       END IF MODULO_NTRD 
     638      END IF 
    639639 
    640640      ! ====================================================================== 
  • branches/2015/dev_r5803_UKMO_AGRIF_Vert_interp/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r5819 r6258  
    121121#if defined key_agrif 
    122122      CALL Agrif_Init_Grids()      ! AGRIF: set the meshes 
     123      nstop = 0 ! This is getting set to 2 somewhere Agrif_Init_Grids so reset to zero for now 
    123124#endif 
    124125 
Note: See TracChangeset for help on using the changeset viewer.