diff --git a/doc/As65 Assembler.html b/doc/As65 Assembler.html new file mode 100644 index 0000000..e70ce69 --- /dev/null +++ b/doc/As65 Assembler.html @@ -0,0 +1,2195 @@ + + + As65 Assembler + + + + + + + +
+

+

+

+

+

+ Assembler (As65)

+

+ The assembler (As65) produces a relocatable object modules by compiling lines of + source code held in local files. The format of each source line must follow the + pattern shown below. The 'square' brackets enclose optional components within the + line (like the label) whilst the  '(X|Y)' pattern indicates a choice between + types delimited by '|' characters. 

+
[[label[:]] [(opcode|directive|macro) [arguments]]] [; comment]
+

+ Opcodes and directives names are case insensitive in source code but labels and + macro names are case sensitive. Given this syntax all of the following examples + are valid.

+
; A comment line
+a_label_by_itself
+        NOP             ; Opcode with no argument followed by a comment
+        nop             ; Same as above
+        LDA #1
+        .6502		; Generate code for 6502 processor
+        MYMACRO 1,2,3   ; Generate a parameterised macro
+

+ Labels

+

+ Labels can  be placed before all opcodes or on lines by themselves. A global + label is comprised of a letter or underscore ('_') followed by a series of alphanumeric + and/or underscore characters. A label may optionally be followed by a colon (':').

+

+ A local label has the same grammatical construction as a global label but begins + with a period ('.'). Whilst a global label may only be used once with a module a + local label may be defined several times provided it appears each time within the + scope of a different global label.

+
SomeGlobalLabel:
+.ALocalLabel:
+

+ Most directives do not allow labels. Those that do give them special meaning (e.g. + macro name, symbol name in .EQU and .SET, etc.)

+

+ Expressions

+

+ The arguments provided to most opcodes and directives are expression comprised of + absolute (e.g. constant literals), relative (e.g. the address of some relocatable + instruction or piece of data) and external values (e.g. values defined in other + source modules).

+

+ The expression parser evaluates operations on absolute values during processing + to produce constant values but expressions involving relative and external terms + are left for the linker to resolve. The following table shows all the supported + operators in decreasing order or precedence.  

+

+ + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
+ Operator + Description
+ $
+ *
+ . +
+ @
+ The current instruction origin
+ ( sub-expression )
+ number
+ symbol
+ 'character literal'
+ Unary values
+ +
+ -
+ ~
+ !
+ LO
+ HI
+ BANK
+ Unary plus (ignored)
+ Negation
+ Complement
+ Logical Not
+ Bits 7 to 0
+ Bits 15 to 8
+ Bits 31 to 16
+ *
+ /
+ %
+ Multiply
+ Divide
+ Remainder
+ +
+ -
+ Addition
+ Subtraction
+ <<
+ >>
+ Right Shift
+ Left Shift
+ <
+ <=
+ >
+ >=
+ Less Than
+ Less Than Or Equal
+ Greater Than
+ Greater Than Or Equal
+ ==
+ !=
+ Equal
+ Not Equal
+ &
+ |
+ ^
+ Binary AND
+ Binary OR
+ Binary XOR
+ &&
+ ||
+ Logical AND
+ Logical OR
+

+

+ Expressions may only contain numeric values. There are no string functions.

+

+ Literals

+

+ Literal numeric values can be expressed in binary, decimal, octal, decimal and as + character values. Literal values may be up to 32-bits in size and all expressions + are evaluated at this precision. Values are masked to 8- and 16- bits when generating + code.

+
        LDA #%10101100    ; Load a binary constant
+        LDX #@177         ; Load an octal constant
+        LDA 127           ; Load from a location specified in decimal
+        STA $FFC1         ; Store at a location specified in hexadecimal
+        lda #'X'          ; Load ASCII for 'X' into the accumlator
+        .LONG 'ABCD'      ; A 32-bit character constant
+

+ Directives

+

+ This section descibes commands which control the assembler and the generation of code.

+

+ .6501

+

+ This directive places the assembler in 6501 processor mode. The 6501 processor supports + all normal 6502 instructions as well as the extended BBR, BBS, SMB and RMB instructions.

+

+ .6502

+

+ This directive places the assembler in 6502 processor mode. Only the traditional + 6502 instructions and addressing modes are supported.

+

+ .65C02

+

+ This directive places the assembler in 65C02 processor mode.  The 65C02 processor + supports all normal 6502 instructions plus new addressing modes and extra some instructions + including the BBR, BBS, SMB and RMB instructions, 

+

+ .65SC02

+

+ This directive places the assembler in 65SC02 processor mode.  The 65SC02 processor + supports the same instructions as the 65C02 BUT does not have then extended BBR, + BBS, SMB and RMB instructions, 

+

+ .65816

+

+ This directive places the assembler into 65816 processor mode.

+

+ .65832

+

+ This directive places the assembler into 65832 processor mode. +

+

+ (The 65832 was designed by WDC but never actually made it into production. It is + very similar to the 65816 but supports 32-bit accumulator and index registers. This + feature is experimental).

+

+ .EQU <expr>

+

+ Creates a symbol having the value indicated by the expression, for example the following + creates a symbol for the ASII carriage return character. An error will be generated + if the symbol is already defined.

+
CR      .EQU  $0D
+

+ As65 accepts '= <expr>' as an alternative syntax when defining equates for + compatibility with other assemblers.

+

+ .SET <expr>

+

+ Creates a symbol having the value indicated by the expression. Unlink .EQU the .SET + directive will not complain if the same symbol is assigned a value multiple times. + This can be useful when defining counters or calculating intermediate results within + macros.

+
COUNT   .SET COUNT+1
+

+ .CODE

+

+ The .CODE directive tells the assembler to place any code generated by instructution + or data directives into the object files code section.

+

+ .DATA

+

+ The .DATA directive tells the assembler to place any code generated by instructution + or data directives into the object files initialised data section.

+

+ .BSS

+

+ The .BSS directive tells the assembler to place any code generated by instructution + or data directives into the object files uninitialised data section.

+

+ .PAGE0

+

+ The .PAGE0 directive tells the assembler to place any code generated by instructution + or data directives into a specially marked section that will be located on page + 0 ($0000-$00FF on 8-bit CPUs or $000000-$00FFFF on 16-bit CPUs) .

+

+ .ORG <constant expr>

+

+ The .ORG directive sets the absolute target address for the current section. For + compatibility with other assemblers As65 will also accept  '*= <expr>'.

+

+ .DPAGE <constant expr> (65816/65832 only)

+

+ The .DPAGE directive informs the assembler of the assumed value of the direct page + register for the following sequence of instructions so that direct-page addressing + can be used instead of absolute where possible.

+

+ .DBREG <constant expr> (65816/65832 only)

+

+ The .DBREG directive informs the assembler of the assumed value of the data bank + register for the following sequence of instructions so that absolute address can + be used instead of long absolute where possible.

+

+ .LONGA (ON|OFF) (65816/65832 only)

+

+ When compiling for the 65816 processor this directive controls the size of immediate + values loaded into the accumulator. If a .LONGA ON directive has been processed + then 16 bit literals will be generated otherwise they will be 8 bits.

+

+ .LONGI (ON|OFF) (65816/65832 only)

+

+ When compiling for the 65816 processor this directive controls the size of immediate + values loaded into the X and Y registers. If a .LONGI ON directive has been processed + then 16 bit literals will be generated otherwise they will be 8 bits.

+

+ .WIDEA (ON|OFF) (65832 only)

+

+ When compiling for the 65832 processor this directive controls the size of immediate + values loaded into the accumulator. If a .WIDEA ON directive has been processed + then 32 bit literals will be generated otherwise they will be 8 bits.

+

+ .WIDEI (ON|OFF) (65832 only)

+

+ When compiling for the 65832 processor this directive controls the size of immediate + values loaded into the X and Y registers. If a .WIDEI ON directive has been processed + then 32 bit literals will be generated otherwise they will be 8 bits.

+

+ .IF <constant expr>

+

+ Assembles the following source code up to the matching .ELSE or .ENDIF if the constant + expression evaluates to a non-zero value.

+
        JSR DoSomething
+        .IF DEBUGGING
+        JSR DumpRegisters
+        .ENDIF
+        JSR DoTheNextBit
+

+ .IFABS <expr>

+

+ Assembles the following source code up to the matching .ELSE or .ENDIF if the expression + evaluates to a absolute (i.e. constant) value.

+

+ This directive is useful in macros to test the type of the parameter value.

+

+ .IFNABS <expr>

+

+ Assembles the following source code up to the matching .ELSE or .ENDIF if the expression + does not evaluate to a absolute (i.e. constant) value.

+

+ This directive is useful in macros to test the type of the parameter value.

+

+ .IFREL <expr>

+

+ Assembles the following source code up to the matching .ELSE or .ENDIF if the expression + evaluates to a relocatable value.

+

+ This directive is useful in macros to test the type of the parameter value.

+

+ .IFNREL <expr>

+

+ Assembles the following source code up to the matching .ELSE or .ENDIF if the expression + does not evaluate to a relocatable value.

+

+ This directive is useful in macros to test the type of the parameter value.

+

+ .ELSE

+

+ Assembles the folloing source code up the matching .ENDIF if the condition for the + preceding matching .IF, .IFABS, .IFNABS, .IFREL, .IFNREL directive was not met. 

+

+ .ENDIF

+

+ The .ENDIF directive marks the end of condition code section.

+

+ .INCLUDE "filename"

+

+ Causes the contents of the indicated file to be read and processed before the remainder + of the current file.

+

+ .APPEND "filename"

+

+ The current source file is close and processing continues at the first line of the + indicated file.

+
        NOP
+
+        .APPEND "AnotherFile.asm"
+
+        NOP             ; This line will not be processed.
+

+ .END

+

+ The .END directive marks the end of the source code.

+
        NOP
+
+        .END
+
+        NOP             ; This line will not be processed.
+

+ .INSERT "filename"

+

+ The .INSERT directive reads the binary contents of the indicated file and inserts + it directly into the generated object code.

+

+ A typically use is to insert pre-compiled data such as graphics images, encryption + keys or lookup tables into the code.

+

+ .REPEAT <constant expr>

+

+ Causes the source lines up to the matching .ENDR directive to repeated the number + of times indicated by the constant expression

+
        .REPEAT 8       ; Generate 8 NOPs
+        NOP
+        .ENDR
+

+ .ENDR

+

+ Marks the end of .REPEAT section.

+

+ .MACRO [<arg>[,<arg>]*]

+

+ The .MACRO directive indicates that the following source lines upto the matching + .ENDM should be used to define a macro. The name of the macro is taken from the + label preceding the .MACRO command.

+
_NOT16 .MACRO VLA,RES
+        LDA VLA+0
+        EOR #$FF
+        STA RES+0
+        LDA VLA+1
+        EOR #$FF
+        STA RES+1
+        .ENDM
+

+ Macro arguments can be accessed by defining symbolic names for them or by positional + references (using \0 thru \9). The sequence \? can be used with a macro to obtain + the macro expansion count, for example to generate unique labels for branches within + the macro.

+

+ .ENDM

+

+ Marks the end of a .MACRO definition

+

+ .EXITM

+

+ When used within a macro it causes an immediate termination of the expansion process.

+

+ .GLOBAL <symbol>[,<symbol>]*

+

+ The .GLOBAL directive lists one or more symbols defined in the current module that + can be referenced by code in other modules.

+

+ .EXTERN <symbol>[,<symbol>]*

+

+ The .EXTERN directive lists one or more symbols defined in other modules so that + they can be used in expressions within the current module (e.g. subroutine addresses, + key data areas, etc.).

+

+ .BYTE  (<expr>|<string>)[,(<expr>|<string>)]*

+

+ The .BYTE directive deposits a series of 8-bit values into the object code for the + current module. The values can be defined as the result of an expression (this includes + simple numeric values) or as strings delimited by quotes.

+
        .BYTE "Hello World",$0D,$0A,0
+

.DBYTE <expr>[,<expr>]*

+

The .DBYTE directive deposits a series of 16-bit values defined by a series of expressions + into the object code for the current module. The values are defined most significant byte + first.

+
        .DBYTE 1,$2,3+5
+

+ .WORD <expr>[,<expr>]*

+

+ The .WORD directive deposits a series of 16-bit values defined by a series of expressions + into the object code for the current module. The values are defined least significant byte + first.

+
        .WORD 1,$2,3+5
+

+ .ADDR <expr>,[<expr>]*

+

+ The .ADDR directive deposits a series of 24-bit values defined by a series of expressions + into the object code for the current module.

+
        .ADDR Function1,Function2
+

+ The .ADDR directive is primarily intended for creating function jump tables for + the 65816 processor.

+

+ .LONG <expr>[,<expr>]*

+

+ The .LONG directive deposits a series of 32-bit values defined by a series of expressions + into the object code for the current module.

+
        .LONG 1,$2,3+5
+

+ .SPACE <constant expr>

+

+ The .SPACE directive reserves the specified number of zero valued bytes in the object + code.

+
PTRA    .SPACE 2
+

+ .LIST

+

+ The .LIST directive enables the output of lines to the listing file.

+

+ .NOLIST

+

+ The .NOLIST directive suspends the generation of a listing.

+

+ .TITLE

+

+ The .TITLE directive sets the string shown as the title at the top of the listing + page.

+

+ .PAGE

+

+ The .PAGE directive forces the listing to restart at the top of the next page.

+

+ Opcodes

+

+ The assembler recognizes all the opcodes for the 6501, 6502, 65C02, 65SC02 and 65816 + processors but will only generate code for currently selected processor type. Using + an inappropriate opcode will generate an error.

+

+ + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
+ Opcode + 6501 + 6502 + 65C02 + 65SC02 + 65816
+ ADC + Y + Y + Y + Y + Y
+ AND + Y + Y + Y + Y + Y
+ ASL + Y + Y + Y + Y + Y
+ BBR0
+ BBR1
+ BBR2
+ BBR3
+ BBR4
+ BBR5
+ BBR6
+ BBR7
+ Y +   + Y +   +  
+ BBS0
+ BBS1
+ BBS2
+ BBS3
+ BBS4
+ BBS5
+ BBS6
+ BBS7
+ Y +   + Y +   +  
+ BCC + Y + Y + Y + Y + Y
+ BCS + Y + Y + Y + Y + Y
+ BEQ + Y + Y + Y + Y + Y
+ BIT + Y + Y + Y + Y + Y
+ BMI + Y + Y + Y + Y + Y
+ BNE + Y + Y + Y + Y + Y
+ BPL + Y + Y + Y + Y + Y
+ BRA +   +   + Y + Y + Y
+ BRK + Y + Y + Y + Y + Y
+ BRL +   +   +   +   + Y
+ BVC + Y + Y + Y + Y + Y
+ BVS + Y + Y + Y + Y + Y
+ CLC + Y + Y + Y + Y + Y
+ CLD + Y + Y + Y + Y + Y
+ CLI + Y + Y + Y + Y + Y
+ CLV + Y + Y + Y + Y + Y
+ CMP + Y + Y + Y + Y + Y
+ COP +   +   +   +   + Y
+ CPX + Y + Y + Y + Y + Y
+ CPY + Y + Y + Y + Y + Y
+ DEC + Y + Y + Y + Y + Y
+ DEX + Y + Y + Y + Y + Y
+ DEY + Y + Y + Y + Y + Y
+ EOR + Y + Y + Y + Y + Y
+ INC + Y + Y + Y + Y + Y
+ INX + Y + Y + Y + Y + Y
+ INY + Y + Y + Y + Y + Y
+ JML +   +   +   +   + Y
+ JSL +   +   +   +   + Y
+ LDA + Y + Y + Y + Y + Y
+ LDX + Y + Y + Y + Y + Y
+ LDY + Y + Y + Y + Y + Y
+ LSR + Y + Y + Y + Y + Y
+ MVN +   +   +   +   + Y
+ MVP +   +   +   +   + Y
+ NOP + Y + Y + Y + Y + Y
+ ORA + Y + Y + Y + Y + Y
+ PEA +   +   +   +   + Y
+ PEI +   +   +   +   + Y
+ PER +   +   +   +   + Y
+ PHA + Y + Y + Y + Y + Y
+ PHB +   +   +   +   + Y
+ PHD +   +   +   +   + Y
+ PHK +   +   +   +   + Y
+ PHX +   +   + Y + Y + Y
+ PHY +   +   + Y + Y + Y
+ PLA + Y + Y + Y + Y + Y
+ PLB +   +   +   +   + Y
+ PLD +   +   +   +   + Y
+ PLP + Y + Y + Y + Y + Y
+ PLX +   +   + Y + Y + Y
+ PLY +   +   + Y + Y + Y
+ REP +   +   +   +   +  
+ RMB0
+ RMB1
+ RMB2
+ RMB3
+ RMB4
+ RMB5
+ RMB6
+ RMB7
+ Y +   + Y +   +  
+ ROL + Y + Y + Y + Y + Y
+ ROR + Y + Y + Y + Y + Y
+ RTI + Y + Y + Y + Y + Y
+ RTL +   +   +   +   + Y
+ RTS + Y + Y + Y + Y + Y
+ SBC + Y + Y + Y + Y + Y
+ SEC + Y + Y + Y + Y + Y
+ SED + Y + Y + Y + Y + Y
+ SEI + Y + Y + Y + Y + Y
+ SEP +   +   +   +   + Y
+ SMB0
+ SMB1
+ SMB2
+ SMB3
+ SMB4
+ SMB5
+ SMB6
+ SMB7
+ Y +   + Y +   +  
+ STA + Y + Y + Y + Y + Y
+ STP +   +   + Y + Y + Y
+ STX + Y + Y + Y + Y + Y
+ STY + Y + Y + Y + Y + Y
+ STZ +   +   + Y + Y + Y
+ TAX + Y + Y + Y + Y + Y
+ TAY + Y + Y + Y + Y + Y
+ TCD +   +   +   +   + Y
+ TCS +   +   +   +   + Y
+ TDC +   +   +   +   + Y
+ TRB +   +   + Y + Y + Y
+ TSB +   +   + Y + Y + Y
+ TSX + Y + Y + Y + Y + Y
+ TXA + Y + Y + Y + Y + Y
+ TXS + Y + Y + Y + Y + Y
+ TXY +   +   +   +   + Y
+ TYA + Y + Y + Y + Y + Y
+ TYX +   +   +   +   + Y
+ WAI +   +   + Y + Y + Y
+ WDM +   +   +   +   + Y
+ XBA +   +   +   +   + Y
+ XCE +   +   +   +   + Y
+

+

+  

+

+ Addressing Modes

+

+ The 65xx family of processors support a number of different addressing modes which + can be used with each instruction.

+

+ + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
+ Syntax + Description
+ + Implied
+ A + Accumulator
+ #expr + Immediate
+ #<expr + Immediate (lo byte)
+ #>expr + Immediate (hi byte)
+ #^expr + Immediate (bank byte)
+ <expr + Direct
+ <expr,X + Direct Indexed by X 
+ <expr,Y + Direct Indexed by Y
+ >expr + Absolute Long (65816 only)
+ >expr,X + Absolute Long Indexed by X (65816 only)
+ [expr] + Long Indirect (65816 only)
+ [expr],Y + Long Indirect Indexed (65816 only)
+ (expr,X) + Indexed Indirect
+ (expr),Y + Indirect Indexed
+ (expr,S),Y + + Stack Relative Indirect Indexed (65816 only)
+ (expr) + Indirect
+ |expr + Absolute
+ |expr,X + Absolute Indexed by X
+ |expr,Y + Absolute Indexed by Y
+ expr + Absolute or Direct
+ expr,X + Absolute or Direct Indexed by X
+ expr,Y + Absolute or Direct Indexed by Y 
+ expr,S + Stack Relative (65816 only)
+

+

+ If the absolute address of the target memory location is known the assembler will + attempt to generate the smallest instruction (e.g. direct page instead of absolute). + The explicit direct (< expr) and absolute (| expr or !expr) allow the programmer + to specify an exact addressing mode for expressions which are not absolute, for + example those referencing external symbols.

+

+ The assembler allows the implied addressing mode to be used with shift and + rotate instructions and treats it as if the accumulator mode had been specified.

+

+ BRK & COP

+

+ The BRK and COP instructions are usually documented as implied although they both + expect the opcode to be followed by a data byte and the PC is incremented by two.

+

+ The assembler allows these instructions to be used either in the normal implied + way or with the immediate addressing mode to specify the data byte. For example + the following results in the same code.

+
         BRK             ; Normal usage
+        .BYTE $7E
+
+        BRK #$7E        ; Generate opcode and data byte together
+

+ Code Sections

+

+ The assembler can generate code into four different sections (e.g. CODE, DATA, BSS + and PAGE0). At the start of each pass the sections are defined as relative. Using + the .ORG directive any section can be forced to place code or data at a specific + absolute memory address.

+
         .CODE
+        NOP             ; A relocatable NOP
+
+        .ORG $F000      ; Make the section absolute
+        NOP             ; Place a NOP at $F000
+
+        .DATA           ; Switch to the (relative) DATA section
+        .BYTE 1,2,3
+
+
+        .CODE           ; Switch back to the absolute code section
+        NOP             ; Place a NOP at $F001
+
+

+ You can switch between the sections throughout your code. Any code or data generated + will be added where the section was left when it was previously used.

+

+ Once a section has been made absolute it can not be made relative again. The .ORG + directive can be used multiple times within the same section, for example to reserve + memory in different RAM areas.

+

+ Structured Assembly

+

+ The assembler supports a simple from of structured programming (e.g. IF..ELSE..ENDIF, + REPEAT..UNTIL, etc.) based on the flag bits in the condition register. The assembler + will generate the branches needed to implement these control structures without + you having to define any labels. It also tries to generate the smallest amount of + code using relative branches (e.g. BRA, BEQ, BPL, etc.) when it can, only resorting + to JMP when it has to.

+

+ Structured code may not be as efficient as normal hand coded routines (due to the + extra branches) but this is often outweighed by the enhanced readability and reduction + in labels.

+

+ IF..ELSE..ENDIF

+

+ An IF command starts a block of code that will only be executed if the indicated + condition (e.g. EQ, NE, CC, CS, PL, MI, VC or VS) exists . For example a simple + 16-bit increment can be coded as follows

+
        INC VAL+0
+        IF EQ
+         INC VAL+1
+        ENDIF
+

+ The ELSE command can be used to defined an alternate block of code to be executed + if the condition was not true.

+
        AND #$01
+        IF EQ
+         ; A contained an even number
+        ELSE
+         ; A contained an odd number
+        ENDIF
+

+ REPEAT..UNTIL|FOREVER

+

+ The REPEAT and UNTIL commands can be used to defined a piece of code that repeats + (at least once) until some condition is true. For example the following code counts + the bits in A by arithmetically shifting it left until result of the shift is zero.

+
        LDX #0
+        REPEAT
+         ASL A
+         PHP
+         IF CS
+          INX
+         ENDIF
+         PLP
+        UNTIL EQ
+

+ If you want a loop that repeats endlessly then use the FOREVER keyword at the end + instead of UNTIL.

+

+ WHILE..ENDW

+

+ The WHILE and ENDW commands produce a block of code that will repeat while some + condition is true.

+
        WHILE EQ
+        ENDW 
+

+ BREAK & CONTINUE

+

+ Both the REPEAT and WHILE loops can contain the loop modifiers BREAK and CONTINUE.

+

+ The BREAK command generates a branch to the next instruction immediately after the + matching UNTIL, FOREVER or ENDW.

+
        LDX #0
+        REPEAT
+         CPX #7
+         IF EQ
+          BREAK
+         ENDIF
+         INX
+        FOREVER
+

+ Similarly the CONTINUE generates a branch back to the start of REPEAT or WHILE loop + to force the start of the next iteration.

+

+ Both BREAK and CONTINUE allow an optional condition code argument that makes the + branch conditional. For example the last example could be written more + efficiently as follows.

+
        LDX #0
+        REPEAT
+         CPX #7
+         BREAK EQ
+         INX
+        FOREVER
+

+  

+ + + + + + + +
+  << Back +
+ Home
+
+ Contents + Next >>
+
+ + + + +
+ + + + + + +
+

+ This page was last updated on 9th March 2018

+ + + + \ No newline at end of file diff --git a/doc/As65 Assembler_files/a.html b/doc/As65 Assembler_files/a.html new file mode 100644 index 0000000..1721083 --- /dev/null +++ b/doc/As65 Assembler_files/a.html @@ -0,0 +1,2 @@ + + \ No newline at end of file diff --git a/doc/As65 Assembler_files/ads.html b/doc/As65 Assembler_files/ads.html new file mode 100644 index 0000000..4330bb4 --- /dev/null +++ b/doc/As65 Assembler_files/ads.html @@ -0,0 +1,3 @@ + + +
Advertisement
\ No newline at end of file diff --git a/doc/As65 Assembler_files/ads_002.html b/doc/As65 Assembler_files/ads_002.html new file mode 100644 index 0000000..f05d97a --- /dev/null +++ b/doc/As65 Assembler_files/ads_002.html @@ -0,0 +1,3 @@ + + +
\ No newline at end of file diff --git a/doc/As65 Assembler_files/ads_003.html b/doc/As65 Assembler_files/ads_003.html new file mode 100644 index 0000000..8227595 --- /dev/null +++ b/doc/As65 Assembler_files/ads_003.html @@ -0,0 +1,3 @@ + + +
Sponsored Searches
\ No newline at end of file diff --git a/doc/As65 Assembler_files/ads_004.html b/doc/As65 Assembler_files/ads_004.html new file mode 100644 index 0000000..1721083 --- /dev/null +++ b/doc/As65 Assembler_files/ads_004.html @@ -0,0 +1,2 @@ + + \ No newline at end of file diff --git a/doc/As65 Assembler_files/ads_data/Enqz_20U.html b/doc/As65 Assembler_files/ads_data/Enqz_20U.html new file mode 100644 index 0000000..97fd2f4 --- /dev/null +++ b/doc/As65 Assembler_files/ads_data/Enqz_20U.html @@ -0,0 +1,44 @@ + + + + \ No newline at end of file diff --git a/doc/As65 Assembler_files/ads_data/PSA_display_728x90.png b/doc/As65 Assembler_files/ads_data/PSA_display_728x90.png new file mode 100644 index 0000000..0988e75 Binary files /dev/null and b/doc/As65 Assembler_files/ads_data/PSA_display_728x90.png differ diff --git a/doc/As65 Assembler_files/ads_data/UFYwWwmt.js b/doc/As65 Assembler_files/ads_data/UFYwWwmt.js new file mode 100644 index 0000000..eb073fe --- /dev/null +++ b/doc/As65 Assembler_files/ads_data/UFYwWwmt.js @@ -0,0 +1,70 @@ +(function(){var l,aa="function"==typeof Object.defineProperties?Object.defineProperty:function(a,b,c){a!=Array.prototype&&a!=Object.prototype&&(a[b]=c.value)},m="undefined"!=typeof window&&window===this?this:"undefined"!=typeof global&&null!=global?global:this,ba=function(){ba=function(){};m.Symbol||(m.Symbol=ca)},ca=function(){var a=0;return function(b){return"jscomp_symbol_"+(b||"")+a++}}(),p=function(){ba();var a=m.Symbol.iterator;a||(a=m.Symbol.iterator=m.Symbol("iterator"));"function"!=typeof Array.prototype[a]&& +aa(Array.prototype,a,{configurable:!0,writable:!0,value:function(){return da(this)}});p=function(){}},da=function(a){var b=0;return ea(function(){return ba?null:v(b)?b.charAt(a):b[a]},Da=function(a,b){b=xa(a,b);var c;(c=0<=b)&&Array.prototype.splice.call(a,b,1);return c},Ea=function(a){return Array.prototype.concat.apply([],arguments)},Aa=function(a){var b=a.length;if(0b?1:0},Ha=function(){return"opacity".replace(/\-([a-z])/g,function(a,b){return b.toUpperCase()})},Ia=function(a){var b=v(void 0)?"undefined".replace(/([-()\[\]{}+?*.$\^|,:#parseFloat(Ua)){Ta=String(Wa);break a}}Ta=Ua}var Xa=Ta,Ya={},Za;var $a=u.document;Za=$a&&F?Sa()||("CSS1Compat"==$a.compatMode?parseInt(Xa,10):5):void 0;var Ba=function(){var a,b;var c=document;if(c.querySelectorAll&&c.querySelector)return c.querySelectorAll(".GoogleActiveViewClass");if(c.getElementsByClassName){var d=c.getElementsByClassName("GoogleActiveViewClass");return d}d=c.getElementsByTagName("*");var e={};for(a=b=0;c=d[a];a++){var f=c.className,g;if(g="function"==typeof f.split)g=0<=xa(f.split(/\s+/),"GoogleActiveViewClass");g&&(e[b++]=c)}e.length=b;return e},bb=function(a){return 9==a.nodeType?a:a.ownerDocument||a.document};var cb=function(a,b){this.Ma=100;this.Ea=a;this.Qa=b;this.aa=0;this.g=null};cb.prototype.get=function(){if(0=a.length)throw J;if(b in a)return a[b++];b++}};return c}throw Error("Not implemented");},Fb=function(a,b){if(z(a))try{za(a,b,void 0)}catch(c){if(c!==J)throw c;}else{a=Eb(a);try{for(;;)b.call(void 0,a.next(),void 0,a)}catch(c){if(c!==J)throw c;}}},Gb=function(a,b){var c=1;Fb(a,function(a){c=b.call(void 0,c,a)});return c},Hb=function(a,b){var c=Eb(a);a=new K; +a.next=function(){var a=c.next();if(b.call(void 0,a,void 0,c))return a;throw J;};return a};var L=function(a,b){this.o={};this.c=[];this.Y=this.b=0;var c=arguments.length;if(12*this.b&&Ib(this),!0):!1};var Ib=function(a){if(a.b!=a.c.length){for(var b=0,c=0;b=d.c.length)throw J;var e=d.c[b++];return a?e:d.o[e]};return e}; +var M=function(a,b){return Object.prototype.hasOwnProperty.call(a,b)};var Jb=function(a){if(a.v&&"function"==typeof a.v)return a.v();if(v(a))return a.split("");if(z(a)){for(var b=[],c=a.length,d=0;db)throw Error("Bad port number "+b);a.N=b}else a.N=null},Pb=function(a,b,c){O(a);b instanceof P?(a.s=b,a.s.ma(a.i)):(c||(b=Rb(b,Wb)),a.s=new P(b,a.i))},Q=function(a,b,c){O(a);a.s.set(b,c);return a};N.prototype.removeParameter=function(a){O(this);this.s.remove(a);return this};var O=function(a){if(a.Ka)throw Error("Tried to modify a read-only Uri");}; +N.prototype.ma=function(a){this.i=a;this.s&&this.s.ma(a)}; +var Qb=function(a,b){return a?b?decodeURI(a.replace(/%25/g,"%2525")):decodeURIComponent(a):""},Rb=function(a,b,c){return v(a)?(a=encodeURI(a).replace(b,Xb),c&&(a=a.replace(/%25([0-9a-fA-F]{2})/g,"%$1")),a):null},Xb=function(a){a=a.charCodeAt(0);return"%"+(a>>4&15).toString(16)+(a&15).toString(16)},Sb=/[#\/\?@]/g,Ub=/[#\?:]/g,Tb=/[#\?]/g,Wb=/[#\?@]/g,Vb=/#/g,P=function(a,b){this.b=this.a=null;this.h=a||null;this.i=!!b},R=function(a){a.a||(a.a=new L,a.b=0,a.h&&Mb(a.h,function(b,c){a.add(decodeURIComponent(b.replace(/\+/g, +" ")),c)}))};l=P.prototype;l.add=function(a,b){R(this);this.h=null;a=S(this,a);var c=this.a.get(a);c||this.a.set(a,c=[]);c.push(b);this.b+=1;return this};l.remove=function(a){R(this);a=S(this,a);return this.a.R(a)?(this.h=null,this.b-=this.a.get(a).length,this.a.remove(a)):!1};l.clear=function(){this.a=this.h=null;this.b=0};l.R=function(a){R(this);a=S(this,a);return this.a.R(a)};l.forEach=function(a,b){R(this);this.a.forEach(function(c,d){za(c,function(c){a.call(b,c,d,this)},this)},this)}; +l.B=function(){R(this);for(var a=this.a.v(),b=this.a.B(),c=[],d=0;de?encodeURIComponent(lc(a,b,c,d,e+1)):"...";return encodeURIComponent(String(a))},T=function(a,b,c,d){a.J.push(b);a.P[b]=jc(c,d)},nc=function(a,b,c,d){b=b+"//"+c+d;var e=mc(a)-d.length;if(0>e)return"";a.J.sort(function(a,b){return a-b});d=null;c="";for(var f=0;f=n.length){e-=n.length;b+=n;c=a.W;break}else a.pa&&(c=e,n[c-1]==a.W&&--c,b+=n.substr(0, +c),c=a.W,e=0);d=null==d?g:d}}f="";a.da&&null!=d&&(f=c+a.da+"="+(a.Sa||d));return b+f+""},mc=function(a){if(!a.da)return a.sa;var b=1,c;for(c in a.P)b=c.length>b?c.length:b;return a.sa-a.da.length-b-a.W.length-1};var oc=function(a,b,c,d,e){if((d?a.Ra:Math.random())<(e||a.Fa))try{if(c instanceof ic)var f=c;else f=new ic,dc(c,function(a,b){var c=f,d=c.Na++;a=jc(b,a);c.J.push(d);c.P[d]=a});var g=nc(f,a.Pa,a.l,a.j+b+"&");g&&hc(u,g)}catch(h){}};var pc=null;var qc=function(){var a=u.performance;return a&&a.now&&a.timing?Math.floor(a.now()+a.timing.navigationStart):va()},rc=function(){var a=void 0===a?u:a;return(a=a.performance)&&a.now?a.now():null};var sc=function(a,b,c){this.label=a;this.type=b;this.value=c;this.duration=0;this.uniqueId=this.label+"_"+this.type+"_"+Math.random();this.slotId=void 0};var U=u.performance,tc=!!(U&&U.mark&&U.measure&&U.clearMarks),uc=db(function(){var a;if(a=tc){var b;if(null===pc){pc="";try{a="";try{a=u.top.location.hash}catch(c){a=u.location.hash}a&&(pc=(b=a.match(/\bdeid=([\d,]+)/))?b[1]:"")}catch(c){}}b=pc;a=!!b.indexOf&&0<=b.indexOf("1337")}return a}),wc=function(){var a=vc;this.T=[];this.Ja=a||u;var b=null;a&&(a.google_js_reporting_queue=a.google_js_reporting_queue||[],this.T=a.google_js_reporting_queue,b=a.google_measure_js_timing);this.L=uc()||(null!=b?b: +1>Math.random())};wc.prototype.disable=function(){this.L=!1;this.T!=this.Ja.google_js_reporting_queue&&(uc()&&za(this.T,xc),this.T.length=0)};var xc=function(a){a&&U&&uc()&&(U.clearMarks("goog_"+a.uniqueId+"_start"),U.clearMarks("goog_"+a.uniqueId+"_end"))};wc.prototype.start=function(a,b){if(!this.L)return null;var c=rc()||qc();a=new sc(a,b,c);b="goog_"+a.uniqueId+"_start";U&&uc()&&U.mark(b);return a}; +wc.prototype.end=function(a){if(this.L&&w(a.value)){var b=rc()||qc();a.duration=b-a.value;b="goog_"+a.uniqueId+"_end";U&&uc()&&U.mark(b);this.L&&this.T.push(a)}};var Ac=function(){var a=yc;this.va=zc;this.Ha="jserror";this.ya=!0;this.oa=null;this.Ga=this.ta;this.ca=void 0===a?null:a;this.Ba=!1},Cc=function(a,b){try{if(a.ca&&a.ca.L){var c=a.ca.start((374).toString(),3);var d=b();a.ca.end(c)}else d=b()}catch(f){b=a.ya;try{xc(c);var e=Bc(f);b=a.Ga.call(a,374,e,void 0,void 0)}catch(g){a.ta(217,g)}if(!b)throw f;}return d},Ec=function(a){var b=Dc;return function(c){for(var d=[],e=0;e=a.keyCode)a.keyCode=-1}catch(b){}};var nd="closure_listenable_"+(1E6*Math.random()|0),od=0;var pd=function(a,b,c,d,e){this.listener=a;this.ba=null;this.src=b;this.type=c;this.capture=!!d;this.ka=e;this.key=++od;this.X=this.ha=!1},qd=function(a){a.X=!0;a.listener=null;a.ba=null;a.src=null;a.ka=null};var rd=function(a){this.src=a;this.m={};this.ea=0};rd.prototype.add=function(a,b,c,d,e){var f=a.toString();a=this.m[f];a||(a=this.m[f]=[],this.ea++);var g=td(a,b,d,e);-1d.keyCode||void 0!=d.returnValue)){a:{var e=!1;if(0==d.keyCode)try{d.keyCode=-1;break a}catch(g){e=!0}if(e||void 0==d.returnValue)d.returnValue=!0}d=[];for(e=b.currentTarget;e;e=e.parentNode)d.push(e);a= +a.type;for(e=d.length-1;!b.la&&0<=e;e--){b.currentTarget=d[e];var f=Gd(d[e],a,!0,b);c=c&&f}for(e=0;!b.la&&e>>0),zd=function(a){if(A(a))return a;a[Hd]||(a[Hd]=function(b){return a.handleEvent(b)});return a[Hd]};var Id=function(a){var b=a._scs_,c=a._li_,d=Rc();if(d&&d.getBoundingClientRect){var e=0;yd(d,"mouseover",function(){++e});yd(d,"mousedown",function(a){var f=d.getBoundingClientRect(),h=0;md(a,0)?h=1:md(a,2)?h=4:md(a,1)&&(h=2);h&&a.shiftKey&&(h|=8);h&&a.altKey&&(h|=16);h&&a.ctrlKey&&(h|=32);var k=Math.floor(100*Wc(d)),n=Math.floor(a.clientX-f.left);f=Math.floor(a.clientY-f.top);var y=e;a=a.isTrusted;var t=document.defaultView&&document.defaultView.mozPaintCount;t=void 0===t?-1:w(t)&&Number.isInteger(t)? +0>t?-3:t:-2;k=Q(Q(Q(Q(Q(Q(Q(Q(Q(Q(new N("//pagead2.googlesyndication.com/pagead/gen_204"),"id","sodarde"),"v",30),"nx",n),"ny",f),"bgai",b),"mb",h),"ox",k),"nm",y),"tr",Sc(a)),"mz",t);c&&Q(k,"li",c);hc(window,k.toString())})}};var Jd=document,Kd=window;var Ld=!!window.google_async_iframe_id,Z=Ld&&window.parent||window;var zc,Dc;if(Ld&&!cc(Z)){var Md="."+Jd.domain;try{for(;2{c&&c(f);d.removeEventListener&&d.removeEventListener("load",e,!1);d.removeEventListener&&d.removeEventListener("error",e,!1)};_.I(d,"load",e);_.I(d,"error",e)}d.src=b;a.google_image_requests.push(d)};_.kb=function(a){var b=a.indexOf("#");0>b&&(b=a.length);var c=a.indexOf("?");if(0>c||c>b){c=b;var d=""}else d=a.substring(c+1,b);return[a.substr(0,c),d,a.substr(b)]}; +_.lb=function(a,b){return b?a?a+"&"+b:b:a};_.nb=function(a,b){if(!b)return a;a=_.kb(a);a[1]=_.lb(a[1],b);return a[0]+(a[1]?"?"+a[1]:"")+a[2]};_.ob=function(a,b,c){if(Array.isArray(b))for(var d=0;de?encodeURIComponent(wb(a,b,c,d,e+1)):"...";return encodeURIComponent(String(a))};xb=function(a,b,c,d){a.b.push(b);a.c[b]=ub(c,d)}; +yb=function(a){if(!a.h)return a.l;let b=1;for(const c in a.c)b=c.length>b?c.length:b;return a.l-a.h.length-b-a.g.length-1}; +zb=function(a,b,c,d){b=b+"//"+c+d;let e=yb(a)-d.length;if(0>e)return"";a.b.sort(function(g,h){return g-h});d=null;c="";for(var f=0;f=n.length){e-=n.length;b+=n;c=a.g;break}a.j&&(c=e,n[c-1]==a.g&&--c,b+=n.substr(0,c),c=a.g,e=0);d=null==d?g:d}}}f="";a.h&&null!=d&&(f=c+a.h+"="+(a.A||d));return b+f}; +_.Bb=function(a,b,c,d,e,f){if((d?a.b:Math.random())<(e||a.c))try{let g;c instanceof Ab?g=c:(g=new Ab,sb(c,(k,n)=>{var q=g,p=q.w++;k=ub(n,k);q.b.push(p);q.c[p]=k}));const h=zb(g,a.j,a.g,a.h+b+"&");h&&("undefined"===typeof f?_.jb(_.m,h):_.jb(_.m,h,f))}catch(g){}};Db=function(a){a&&K&&Cb()&&(K.clearMarks(`goog_${a.label}_${a.uniqueId}_start`),K.clearMarks(`goog_${a.label}_${a.uniqueId}_end`))}; +Eb=function(a){let b=a.toString();a.name&&-1==b.indexOf(a.name)&&(b+=": "+a.name);a.message&&-1==b.indexOf(a.message)&&(b+=": "+a.message);if(a.stack){a=a.stack;try{-1==a.indexOf(b)&&(a=b+"\n"+a);let c;for(;a!=c;)c=a,a=a.replace(/((https?:\/..*\/)[^\/:]*:\d+(?:.|\n)*)\2/,"$1");b=a.replace(/\n */g,"\n")}catch(c){}}return b}; +_.Gb=function(a,b,c){let d,e;try{a.b&&a.b.b?(e=a.b.start(b.toString(),3),d=c(),a.b.end(e)):d=c()}catch(f){c=a.l;try{Db(e),c=a.v(b,new Fb(f,{message:Eb(f)}),void 0,void 0)}catch(g){a.g(217,g)}if(!c)throw f;}return d}; +_.Hb=function(a,b){if(!a||/[?&]dsh=1(&|$)/.test(a))return null;if(/[?&]ae=1(&|$)/.test(a)){var c=/[?&]adurl=([^&]+)/.exec(a);if(!c)return null;b=b?c.index:a.length;try{return{ia:a.slice(0,b)+"&act=1"+a.slice(b),F:decodeURIComponent(c[1])}}catch(d){return null}}if(/[?&]ae=2(&|$)/.test(a)){c=a;let d="";b&&(b=a.indexOf("&adurl="),0Date.now()-c)a=!1;else if(b=a.getAttribute("data-orig-async-clicktrack-url")){const {U:d,aa:e}=_.Ib(b);Jb(a,d);a=e}else a.setAttribute("data-orig-async-clicktrack-url",a.href),a=Kb(a);else a=Kb(a);return a};_.Ib=function(a){const b=_.Hb(a,!0);return b?navigator.sendBeacon?navigator.sendBeacon(_.Mb(b.ia,"&ri=1"),"")?{U:b.F,aa:!0}:{U:_.Mb(a,"&ri=2"),aa:!1}:{U:_.Mb(a,"&ri=16"),aa:!1}:{U:a,aa:!1}}; +_.Mb=function(a,b){const c=a.search(/&adurl=/);return 0>c?a+b:a.slice(0,c)+b+a.slice(c)};_.Nb=function(a){return null!=a&&-1===a.indexOf("dbm/clk")&&null!==_.Hb(a)};Ob=function(a){return _.Nb(a.href)||(a.getAttribute("data-orig-async-clicktrack-url")?_.Nb(a.getAttribute("data-orig-async-clicktrack-url")):!1)};Qb=function(a,b,c){let d=b=b.getAttribute("data-original-click-url");if(d)for(let e=0;e_.G(a.b,39,0)}; +Tb=function(a,b){-1===b.href.indexOf("dbm/clk")&&(Ob(b)||_.H(a.b,38))&&_.Gb(_.Sb,446,()=>{{const c=Date.now();Rb(a,c)&&Lb(b,_.H(a.b,45),a.l)&&(a.l=c)}})}; +Wb=function(a,b,c,d){if(0!=a.j.length&&(d.preventDefault?!d.defaultPrevented:!1!==d.returnValue)){var e=1==d.which&&!d.ctrlKey&&"_blank"!=b.target&&"_new"!=b.target;e&&_.Ub(d);var f=[];for(let g=0;g{_.jb(_.L,h,n)});f.push(k)}}c=Promise.all(f);f=new Promise(g=>{window.setTimeout(g,2E3)});e&&Promise.race([c,f]).then((0,_.t)(Vb.prototype.$,a,b,d))}}; +Xb=function(a,b,c){const d=b.href;if(a.g){const e=Date.now(),f=Rb(a,e);if(a.g.b(b,c,a.b,a.w,f))return f&&(a.l=e),!0}else if(_.m.googdlu&&(_.m.googdlu.tryOpenPlayStore&&_.m.googdlu.tryOpenPlayStore(c,d,_.G(a.b,15,""))||_.m.googdlu.tryOpenItunesStore&&_.m.googdlu.tryOpenItunesStore(c,d,_.G(a.b,15,""),_.H(a.b,42),_.H(a.b,43),_.G(a.h,7,""),_.G(a.h,8,""))))return!0;return _.H(a.b,31)&&_.H(a.b,30)&&_.G(a.b,28,"")&&_.m.googdlu&&_.m.googdlu.tryOpenAppUrl?(_.m.googdlu.tryOpenAppUrl(c,d,_.G(a.b,32,""),_.G(a.b, +28,"")),!0):!1};Yb=function(a,b,c,d,e){if(a.g){const f=Rb(a,Date.now()),g=Ta(a.h,$a,23);return a.g.g(b,c,a.b,a.w,e,f,g,d)}return new Promise(f=>{f(!1)})};Zb=function(a,b,c){const d=Ta(a.h,$a,23);let e=!1;for(const f of d)if("use_async_for_js_click_handler"===_.G(f,1,"")&&"True"===_.G(f,2,"")){e=!0;break}e&&a.g&&2===a.v?(_.Ub(c),Yb(a,b,c,a.v,a.H).then(f=>{f||Tb(a,b)})):Xb(a,b,c)||Tb(a,b)};$b=function(a,b,c,d){a.c[d]||(a.c[d]={});a.c[d][c]||(a.c[d][c]=[]);_.I(b,d,(0,_.t)(a.Z,a,b,c,d))}; +ac=function(a){return"string"==typeof a.className?a.className:a.getAttribute&&a.getAttribute("class")||""};bc=function(a,b){"string"==typeof a.className?a.className=b:a.setAttribute&&a.setAttribute("class",b)};cc=function(a,b){a.classList?b=a.classList.contains(b):(a=a.classList?a.classList:ac(a).match(/\S+/g)||[],b=0<=Array.prototype.indexOf.call(a,b,void 0));return b};_.dc=function(a,b){if(a.classList)a.classList.add(b);else if(!cc(a,b)){var c=ac(a);bc(a,c+(0{c[e]&&(d[e]=_.pa(_.Fc(2,c[e],b)))});return new Gc(d,b,a)};Jc=function(a,b){const c=_.Sa(b,bb,16);c&&_.H(c,12)&&_.H(b,5)&&Ic(a,{backgroundColor:"transparent",backgroundImage:"none"})};_.aa=[];_.m=this||self;Kc="closure_uid_"+(1E9*Math.random()>>>0); +Lc=0;_.M=Date.now||function(){return+new Date};ta.prototype.R=!0;ta.prototype.b=function(){return this.c};var sa={},ra={},Ja=_.z("");var xa;_.A.prototype.R=!0;_.A.prototype.b=function(){return this.g.toString()};_.A.prototype.na=!0;_.A.prototype.c=ba(2);xa={};_.wa={};_.Mc=String.prototype.trim?function(a){return a.trim()}:function(a){return/^[\s\xa0]*([\s\S]*?)[\s\xa0]*$/.exec(a)[1]};var Ca,Aa;_.B.prototype.R=!0;_.B.prototype.b=function(){return this.g.toString()};_.B.prototype.na=!0;_.B.prototype.c=ba(1);Ca=/^(?:(?:https?|mailto|ftp):|[^:/?#]*(?:[/?#]|$))/i;Aa={};_.za={};var Ea;a:{var Nc=_.m.navigator;if(Nc){var Oc=Nc.userAgent;if(Oc){Ea=Oc;break a}}Ea=""};_.Ga.prototype.na=!0;_.Ga.prototype.c=ba(0);_.Ga.prototype.R=!0;_.Ga.prototype.b=function(){return this.g.toString()};var Fa={};_.Ia("",0);var gc=_.Ia("",0);_.Ia("
",0);_.Pc=qa(function(){var a=document.createElement("div"),b=document.createElement("div");b.appendChild(document.createElement("div"));a.appendChild(b);b=a.firstChild.firstChild;a.innerHTML=_.Ha(gc);return!b.parentElement});Ma[" "]=_.ca;var Sc,Yc,cd;_.Qc=C("Opera");_.Rc=C("Trident")||C("MSIE");Sc=C("Edge");_.Tc=C("Gecko")&&!(-1!=Ea.toLowerCase().indexOf("webkit")&&!C("Edge"))&&!(C("Trident")||C("MSIE"))&&!C("Edge");_.Uc=-1!=Ea.toLowerCase().indexOf("webkit")&&!C("Edge");_.Vc=C("Android");_.Wc=La();_.Xc=C("iPad"); +a:{var Zc="",$c=function(){var a=Ea;if(_.Tc)return/rv:([^\);]+)(\)|;)/.exec(a);if(Sc)return/Edge\/([\d\.]+)/.exec(a);if(_.Rc)return/\b(?:MSIE|rv)[: ]([^\);]+)(\)|;)/.exec(a);if(_.Uc)return/WebKit\/(\S+)/.exec(a);if(_.Qc)return/(?:Version)[ \/]?(\S+)/.exec(a)}();$c&&(Zc=$c?$c[1]:"");if(_.Rc){var ad=Oa();if(null!=ad&&ad>parseFloat(Zc)){Yc=String(ad);break a}}Yc=Zc}_.bd=Yc;if(_.m.document&&_.Rc){var dd=Oa();cd=dd?dd:parseInt(_.bd,10)||void 0}else cd=void 0;_.ed=cd;_.fd=La()||C("iPod");_.gd=C("iPad");_.hd=C("Android")&&!((C("Chrome")||C("CriOS"))&&!C("Edge")||C("Firefox")||C("FxiOS")||C("Opera")||C("Silk"));var Pa="function"==typeof Uint8Array,Qa=[];_.y(_.Wa,_.D);var Va=[20,33];_.y(Za,_.D);_.y($a,_.D);_.y(_.ab,_.D);_.y(bb,_.D);_.y(db,_.D);var cb=[1,23];var Ec;Ec={eb:0,Gb:1,Hb:45,Ib:46,ub:48,URL:2,Xa:3,Pa:4,Fb:5,zb:7,lb:8,Va:9,ob:6,rb:34,fb:13,Qa:14,nb:15,pb:16,qb:40,Db:47,Lb:29,ab:30,Eb:49,vb:17,Ya:18,cb:19,bb:20,Bb:23,Ta:24,yb:25,xb:26,Ua:27,wb:28,Kb:39,Jb:31,$a:32,Sa:33,gb:35,sb:36,Ra:37,Za:38,tb:42,Ab:43,Cb:44,Wa:50,ib:1E3,jb:1001,kb:1002};_.id=[16,47,49,18,27,28,39];fb.prototype.ceil=function(){this.b=Math.ceil(this.b);this.c=Math.ceil(this.c);return this};fb.prototype.floor=function(){this.b=Math.floor(this.b);this.c=Math.floor(this.c);return this};fb.prototype.round=function(){this.b=Math.round(this.b);this.c=Math.round(this.c);return this};_.P=0;_.jd=document;_.L=window;_.Ub=a=>{a.preventDefault?a.preventDefault():a.returnValue=!1};_.J.prototype.h=!1;_.J.prototype.ka=ba(3);_.J.prototype.G=ba(5);/* + Copyright (c) Microsoft Corporation. All rights reserved. + Licensed under the Apache License, Version 2.0 (the "License"); you may not use + this file except in compliance with the License. You may obtain a copy of the + License at http://www.apache.org/licenses/LICENSE-2.0 + + THIS CODE IS PROVIDED ON AN *AS IS* BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY + KIND, EITHER EXPRESS OR IMPLIED, INCLUDING WITHOUT LIMITATION ANY IMPLIED + WARRANTIES OR CONDITIONS OF TITLE, FITNESS FOR A PARTICULAR PURPOSE, + MERCHANTABLITY OR NON-INFRINGEMENT. + + See the Apache Version 2.0 License for specific language governing permissions + and limitations under the License. +*/ +var kd=/^((market|itms|intent|itms-appss):\/\/)/i;var Jb;Jb=(a,b)=>{var c=_.ld(599);b=b instanceof _.B||!kd.test(b)?b:new _.B(_.za,b);_.tb(b,c);c=b instanceof _.B?b:_.Da(b);a.href=_.Ba(c)};_.ld=a=>{var b=`${"http:"===_.L.location.protocol?"http:":"https:"}//${"pagead2.googlesyndication.com"}/pagead/gen_204`;return c=>{c=_.qb(b,{id:"unsafeurl",ctx:a,url:c});navigator.sendBeacon&&navigator.sendBeacon(c,"")}};var Dc=(a,b)=>{if(a)for(let c in a)Object.prototype.hasOwnProperty.call(a,c)&&b.call(void 0,a[c],c,a)},md=!!window.google_async_iframe_id,Ic;let nd=md&&window.parent||window;_.ua(_.z("//fonts.googleapis.com/css"));_.Fc=(a,b,c=_.jd)=>{switch(a){case 2:return c.getElementsByClassName(b);case 3:return c.getElementsByTagName(b)}return[]};_.Q=(a,b,c=_.jd)=>{switch(a){case 1:if(c.getElementById)return c.getElementById(b);break;case 2:case 3:if(a=_.Fc(a,b,c),0{a&&Dc(b,(c,d)=>{a.style[d]=c})};_.od=a=>{for(const b of a)if("use_refactored_boomerang_click_handler"===_.G(b,1,"")&&"true"===_.G(b,2,"").toLowerCase())return!0;return!1};var Fb=class{constructor(a,b,c={}){this.error=a;this.context=b.context;this.msg=b.message||"";this.id=b.id||"jserror";this.meta=c}};const pd=/^https?:\/\/(\w|-)+\.cdn\.ampproject\.(net|org)(\?|\/|$)/;var qd=class{constructor(a,b){this.b=a;this.c=b}},rd=class{constructor(a,b,c,d,e){this.url=a;this.Ba=!!d;this.depth="number"===typeof e?e:null}};var Ab=class{constructor(a,b,c,d,e){this.l=c||4E3;this.g=a||"&";this.v=b||",$";this.h=void 0!==d?d:"trn";this.A=e||null;this.j=!1;this.c={};this.w=0;this.b=[]}};var sd=class{constructor(a,b,c,d){this.j=a;this.g=b;this.h=c;this.c=d;this.b=Math.random()}};let td=null;var ud=()=>{const a=_.m.performance;return a&&a.now&&a.timing?Math.floor(a.now()+a.timing.navigationStart):(0,_.M)()},vd=()=>{const a=_.m.performance;return a&&a.now?a.now():null};var wd=class{constructor(a,b,c,d=0,e){this.label=a;this.type=b;this.value=c;this.duration=d;this.uniqueId=Math.random();this.slotId=e}};const K=_.m.performance,xd=!!(K&&K.mark&&K.measure&&K.clearMarks),Cb=qa(()=>{var a;if(a=xd){var b;if(null===td){td="";try{a="";try{a=_.m.top.location.hash}catch(c){a=_.m.location.hash}a&&(td=(b=a.match(/\bdeid=([\d,]+)/))?b[1]:"")}catch(c){}}b=td;a=!!b.indexOf&&0<=b.indexOf("1337")}return a}); +var yd=class{constructor(a,b){this.events=[];this.c=b||_.m;let c=null;b&&(b.google_js_reporting_queue=b.google_js_reporting_queue||[],this.events=b.google_js_reporting_queue,c=b.google_measure_js_timing);this.b=Cb()||(null!=c?c:Math.random(){Bd.google_measure_js_timing||(Cd.b=!1,Cd.events!=Cd.c.google_js_reporting_queue&&(Cb()&&_.ma(Cd.events,Db),Cd.events.length=0))};_.Ad=new sd("http:"===_.L.location.protocol?"http:":"https:","pagead2.googlesyndication.com","/pagead/gen_204?id=",.01); +"number"!==typeof Bd.google_srt&&(Bd.google_srt=Math.random());var Ed=Bd.google_srt;0<=Ed&&1>=Ed&&(_.Ad.b=Ed);_.Sb=new _.zd(_.Ad,"jserror",!0,Cd); +_.Sb.c=a=>{var b=_.L.jerExpIds;if("array"==_.da(b)&&0!==b.length){var c=a.eid;if(c){c=[...c.split(","),...b];b={};for(var d=0,e=0;e{Dd()});var Fd=(a,b,c,d,e)=>{c="&"+b+"="+c;const f=a.indexOf("&"+d+"=");c=0>f?a+c:a.substring(0,f)+c+a.substring(f);return 2E3{b=c(d,b);if(!(b instanceof Array))return a;_.ma(b,e=>{if(2!==e.length&&3!==e.length)return a;a=Fd(a,e[0],e[1],"adurl",e[2])});return a};var Vb=class{constructor(a,b,c){this.b=a;this.h=b;this.g=c;this.D=[];this.j=[];this.N={};this.c={};this.w=this.A=!1;this.v=Gd(this.b);this.H=new Promise(d=>{d(!1)});this.l=-1;a=_.Xa(this.b);b=_.Ya(this.b);c=Ta(this.h,$a,23);this.g&&this.b&&a&&b&&_.od(c)&&2===Gd(this.b)&&(this.v=2,this.H=this.g.c({url:a,id:a,C:b}))}$(a,b){this.A=!0;var c=!1;if(b.target){{c=b.target;var d=b.button,e=b.ctrlKey,f=b.shiftKey,g=b.metaKey,h=b.altKey,k=new fb(b.x,b.y);let n;document.createEvent?(n=document.createEvent("MouseEvents"), +n.initMouseEvent("click",!0,!0,null,0,k.b,k.c,k.b,k.c,e,h,f,g,d,null),c.dispatchEvent?(c.dispatchEvent(n),c=!0):c=!1):c=!1}}!a.href||c||Xb(this,a,b)||(Tb(this,a),_.L.top.location=a.href)}Z(a,b,c,d){if(this.A)this.A=!1;else{d||(d=_.L.event);this.c[c][b].forEach(e=>{e(d)});if(a.href){const e=Qb(this,a,d.type);e&&(a.href=e)}"click"==c&&(Wb(this,a,b,d),(d.preventDefault?d.defaultPrevented:!1===d.returnValue)||Zb(this,a,d))}}};const Gd=a=>_.H(a,31)&&_.G(a,28,"")?1:_.Xa(a)&&_.Ya(a)?_.H(a,44)?3:2:0;var rc;var sc=new class{constructor(a,b,c){this.h=c;this.g=a;this.j=b;this.c=0;this.b=null}get(){let a;0{_.m.google_logging_queue||(_.m.google_logging_queue=[]);_.m.google_logging_queue.push([10,a])};var zc=class{constructor(a,b,c){this.w=new _.tc;this.l=a;this.g=b;this.b=c;this.j=[];this.v=!1;this.c=null}forEachAd(a){_.ma(this.g,a)}h(a){this.g.push(a)}A(a){if(a=_.Q(1,a))this.l=a;if(0==this.g.length)_.m.css=null;else{for(a=0;a{b.gqid=Jd;b.qqid=Kd;b.com=a;_.Bb(_.Ad,"glaurung",b,!0,c,void 0)},Cc={[1]:"title-link",[2]:"url-link",[3]:"body-link",[4]:"button-link",[8]:"favicon-link",[6]:"image-link",[26]:"price",[23]:"reviews",[43]:"rating-stars",[44]:"reviews-count",[24]:"app-store",[25]:"promo-headline",[33]:"app-icon",[16]:"image-gallery",[40]:"image-gallery-image-link",[36]:"logo-link",[37]:"advertiser-link",[38]:"call-to-action-link",[39]:"video",[42]:"logo",[50]:"badge-box",[9]:"ad-background"},Nd=(a, +b,c)=>{_.Q(2,"app-icon-link",b)&&(Cc[33]="app-icon-link");var d=a.b,e=_.Q(1,"adunit",b),f=_.Q(1,"ads",b);if(!e||!f)return 1;var g={overflow:"hidden"};0==_.G(d,32,0)?(g.width=_.G(d,2,0)+"px",g.height=_.G(d,3,0)+"px",g.position="absolute",g.top="0",g.left="0"):(g.width="100%",g.height="100%");Ic(e,g);Jc(e,d);Jc(f,d);try{c(f,a)}catch(n){return _.H(d,13)&&(Ld=n),2}c=0;d=eb(d);for(e=0;e{const d=(new Date).getTime();let e=1,f=!1;Ld=null;try{const g=a.b;f=_.H(g,13);Jd=_.G(g,8,"");Kd=_.G(g,7,"");e=Nd(a,b,c)}catch(g){f&&(Ld=g),e=1}Md("bridge",{["r"]:e,["d"]:(new Date).getTime()-d});return e},void 0);_.r("glaurungError",()=>Ld,void 0);_.r("glaurungBridge.log",Md,void 0); +_.r("glaurungBridge.getAdPieceClassName",a=>Cc[a],void 0);_.r("buildImageAd",function(a,b){if(0>b||b>=eb(a.b).length)a=null;else{{a=eb(a.b)[b];b=_.Q(1,"google_image_div");const c=_.Q(1,"aw0");a=b&&c?new Od(a,c,b):null}}return a},void 0);_.r("buildRichmediaAd",function(a,b){return 0>b||b>=eb(a.b).length?null:new Pd(eb(a.b)[b],_.jd.body)},void 0); +_.r("buildTextAd",(a,b)=>{const c=a.b;if(!(0>b||b>=eb(c).length)){if(0>b||b>=eb(a.b).length)var d=null;else{{d=eb(a.b)[b];const g=_.Q(1,"taw"+b);if(g){{var e=g;const h={};h[0]=[e];for(const k in Ec){{var f=Ec[k];const n=Sd[f];n&&(h[f]=_.pa(_.Fc(2,n,e)))}}e=h}d=new Qd(e,g,d)}else d=null}}d&&(_.L.registerAd&&_.L.registerAd(d,"taw"+b),a.h(d),_.H(eb(c)[b],11)&&_.L.initAppPromo&&_.L.initAppPromo(d,a))}},void 0);})(window.hydra=window.hydra||{}); diff --git a/doc/As65 Assembler_files/ads_data_002/46339091cebf433f739dcd073ea6d266.js b/doc/As65 Assembler_files/ads_data_002/46339091cebf433f739dcd073ea6d266.js new file mode 100644 index 0000000..3e10662 --- /dev/null +++ b/doc/As65 Assembler_files/ads_data_002/46339091cebf433f739dcd073ea6d266.js @@ -0,0 +1,13 @@ +(function(){/* + + Copyright The Closure Library Authors. + SPDX-License-Identifier: Apache-2.0 +*/ +'use strict';var aa="function"==typeof Object.create?Object.create:function(a){function b(){}b.prototype=a;return new b},e;if("function"==typeof Object.setPrototypeOf)e=Object.setPrototypeOf;else{var g;a:{var ba={h:!0},h={};try{h.__proto__=ba;g=h.h;break a}catch(a){}g=!1}e=g?function(a,b){a.__proto__=b;if(a.__proto__!==b)throw new TypeError(a+" is not extensible");return a}:null}var k=e; +function l(a,b){a.prototype=aa(b.prototype);a.prototype.constructor=a;if(k)k(a,b);else for(var c in b)if("prototype"!=c)if(Object.defineProperties){var d=Object.getOwnPropertyDescriptor(b,c);d&&Object.defineProperty(a,c,d)}else a[c]=b[c]}var m=this||self; +function ca(a){var b=typeof a;if("object"==b)if(a){if(a instanceof Array)return"array";if(a instanceof Object)return b;var c=Object.prototype.toString.call(a);if("[object Window]"==c)return"object";if("[object Array]"==c||"number"==typeof a.length&&"undefined"!=typeof a.splice&&"undefined"!=typeof a.propertyIsEnumerable&&!a.propertyIsEnumerable("splice"))return"array";if("[object Function]"==c||"undefined"!=typeof a.call&&"undefined"!=typeof a.propertyIsEnumerable&&!a.propertyIsEnumerable("call"))return"function"}else return"null"; +else if("function"==b&&"undefined"==typeof a.call)return"object";return b}var da=Date.now||function(){return+new Date};function n(a,b){function c(){}c.prototype=b.prototype;a.prototype=new c;a.prototype.constructor=a};var ea=Array.prototype.forEach?function(a,b){Array.prototype.forEach.call(a,b,void 0)}:function(a,b){for(var c=a.length,d="string"===typeof a?a.split(""):a,f=0;fMath.random())}function pa(a){a&&F&&G()&&(F.clearMarks("goog_"+a.label+"_"+a.uniqueId+"_start"),F.clearMarks("goog_"+a.label+"_"+a.uniqueId+"_end"))} +H.prototype.start=function(a,b){if(!this.b)return null;var c=void 0===c?m:c;c=c.performance;(c=c&&c.now?c.now():null)||(c=(c=m.performance)&&c.now&&c.timing?Math.floor(c.now()+c.timing.navigationStart):da());a=new na(a,b,c);b="goog_"+a.label+"_"+a.uniqueId+"_start";F&&G()&&F.mark(b);return a};if(D&&!B()){var J="."+A.domain;try{for(;2 + + \ No newline at end of file diff --git a/doc/As65 Assembler_files/ads_data_002/ads_data/Qh1z7zbz5tCe3803wA8GK4W8DMNijuMntDnjdovpGbs.js b/doc/As65 Assembler_files/ads_data_002/ads_data/Qh1z7zbz5tCe3803wA8GK4W8DMNijuMntDnjdovpGbs.js new file mode 100644 index 0000000..a15f7b8 --- /dev/null +++ b/doc/As65 Assembler_files/ads_data_002/ads_data/Qh1z7zbz5tCe3803wA8GK4W8DMNijuMntDnjdovpGbs.js @@ -0,0 +1 @@ +/* Anti-spam. Want to say hello? Contact (base64) Ym90Z3VhcmQtY29udGFjdEBnb29nbGUuY29t */Function('var C=function(S,N){return(N=z(S),N&128)&&(N=N&127|z(S)<<7),N},H=function(S,N){N.j.splice(0,0,S)},D=function(S,N,v,b,L){for(L=(b=[],v=0);LN?b[v++]=N:(2048>N?b[v++]=N>>6|192:(55296==(N&64512)&&L+1>18|240,b[v++]=N>>12&63|128):b[v++]=N>>12|224,b[v++]=N>>6&63|128),b[v++]=N&63|128);return b},g={},SZ=function(S,N,v,b,L){for(;N.j.length;){if(S=S&&v)N.G&&N.m?(S=0!=document.hidden?false:true,N.m=false):S=false;if(S){L=N,N.Z4(function(){d(false,v,L,false)});break}b=(S=true,N.j).pop(),b=k(b,N)}return b},V={},p=function(S,N){return N[S]<<24|N[S+1]<<16|N[S+2]<<8|N[S+3]},Z=this||self,Y=function(S,N,v){if(0>=v.G||1>>5)+N^b+S[b&3],b+=2489668359,N+=(v<<4^v>>>5)+v^b+S[b>>>11&3];return[v>>>24,v>>16&255,v>>8&255,v&255,N>>>24,N>>16&255,N>>8&255,N&255]}catch(L){throw L;}},vS=function(S,N){I(((S.R.push(S.M.slice()),S.M)[23]=void 0,23),S,N)},U=function(S,N){for(N=[];S--;)N.push(255*Math.random()|0);return N},as=function(S,N,v,b,L){for((v.X=((v.w=[],v).H=25,v.G=(v.Y=(v.U=(L=0,void 0),false),((v.Ml=function(e,Q,a){return a=(Q=function(){return a()},function(){return e}),Q[this.B]=function(l){e=l},Q},b=[],v).l=function(e,Q,a,l,P,c){return(P=this,c=(l=function(){return l[P.P+(c[P.D]===Q)-!a[P.D]]},function(){return l()}),a=P.N,c[P.B]=function(w){l[P.h]=w},c)[P.B](e),e=c},v).m=false,0),void 0),v).f=0;128>L;L++)b[L]=String.fromCharCode(L);I(219,((I(1,v,(I(136,(I(126,(I(211,v,(I(189,v,(I(68,(I(243,(I(226,(I(121,(I((I(65,v,(I(134,(I(209,(I((I(155,v,(I(45,(I(25,(I((I(125,(I(96,(I(40,v,(I(161,(I(17,(I(148,v,(v.kP=(L=(I(84,(I(246,(I(56,v,(I(254,(I(69,v,(I(90,v,(I(239,((I(83,(I(22,(I((I(13,v,(I(23,v,((v.s=(v.M=[],[]),v).Z=(v.yY=function(e){this.Z=e},v),0)),0)),185),v,function(e,Q){(e=(Q=z(e),e.S(Q)),e)[0].removeEventListener(e[1],e[2],false)}),v),function(e,Q,a){Y(true,5,e)||(a=z(e),Q=z(e),I(Q,e,function(l){return eval(l)}(e.S(a))))}),v),[]),v).R=[],I(130,v,function(e){NH(e,1)}),v),[165,0,0]),0)),[0,0,0])),v),function(e,Q,a,l){I((a=(l=(Q=z((l=z(e),e)),e.S(l)),e.S(Q)),Q),e,a+l)}),function(e,Q,a,l,P,c,w,u,J,O,K,h,y){for(h=(l=(a=(w=(c=z(e),J=0),O=function(f,m){for(;w>=f,m},O(3))+1,O(5)),Q=[],P=0);h=B.length;)B.push(z(f));M=B[M]}m.push(M)}f.U=(f.X=f.l(u.slice(),f.L),f).l(m,f.L)})})),v),function(e){n(e,1)}),I(236,v,function(e){n(e,4)}),v),function(e,Q,a){I((a=(a=z(e),Q=z(e),e).S(a),Q),e,os(a))}),window).performance||{},L.timeOrigin||(L.timing||{}).navigationStart)||0,I(249,v,function(){}),function(e){n(e,2)})),v),function(e,Q,a,l){l=(Q=(Q=z((l=z(e),e)),a=z(e),e.S(Q)),e.S(l)),I(a,e,l[Q])}),v),function(e,Q,a,l,P){(l=(P=(Q=z(e),z(e)),z(e)),e).Z==e&&(l=e.S(l),a=e.S(Q),P=e.S(P),a[P]=l,25==Q&&(e.v=void 0,2==P&&(e.I=void 0,I(23,e,e.S(23)+32))))}),v.j=[],function(e,Q,a,l,P,c,w){Y(true,5,e)||(a=b2(e),l=a.K,w=a.o,c=a.c,P=c.length,0==P?Q=new l[w]:1==P?Q=new l[w](c[0]):2==P?Q=new l[w](c[0],c[1]):3==P?Q=new l[w](c[0],c[1],c[2]):4==P?Q=new l[w](c[0],c[1],c[2],c[3]):F(22,e),I(a.A,e,Q))})),v),v),v),0),70),v,[]),v),[0,0,0]),v),function(e,Q,a,l){a=(l=(Q=z(e),a=z(e),z)(e),e.S(a)),Q=e.S(Q),I(l,e,(Q in a)+0)}),I(14,v,function(e,Q,a,l,P,c,w){if((Q=(P=C((l=z(e),e)),""),e).M[187])for(w=e.S(187),c=0,a=w.length;P--;)c=(c+C(e))%a,Q+=b[w[c]];else for(;P--;)Q+=b[z(e)];I(l,e,Q)}),v.jp=function(e,Q){(Q.push(e[0]<<24|e[1]<<16|e[2]<<8|e[3]),Q).push(e[4]<<24|e[5]<<16|e[6]<<8|e[7]),Q.push(e[8]<<24|e[9]<<16|e[10]<<8|e[11])},function(e){e.T(4)})),171),v,function(e,Q,a,l,P){(l=(P=(Q=z((l=z((a=z(e),P=z(e),e)),e)),e.S(P)),Q=e.S(Q),e.S(l)),I)(a,e,Q$(Q,e,l,P))}),v),function(e,Q){Y(true,5,e)||(Q=b2(e),I(Q.A,e,Q.o.apply(Q.K,Q.c)))}),v),function(e,Q,a,l,P,c){if(!Y(true,255,e)){if((e=(P=(c=(l=(c=(P=(l=(Q=z(e),z(e)),z(e)),z)(e),e.S(l)),e.S(c)),e).S(P),e.S(Q)),"object")==os(e)){for(a in Q=[],e)Q.push(a);e=Q}for(a=(Q=0,e).length,P=0>l)}),v),2048),v),function(e,Q,a,l){(a=(Q=(l=(a=z((Q=z(e),e)),z)(e),e.S(Q)),e).S(a),I)(l,e,+(Q==a))}),v),U(4)),v),function(e,Q){vS(e,(Q=e.S(z(e)),Q))}),function(e,Q,a,l,P){for(l=(Q=z(e),C(e)),P=0,a=[];P>3,b>=S.O)throw F(31,S),S.i;return(I(23,S,((void 0==S.I&&(S.I=p(N-4,S.C),S.v=void 0),S).v!=N>>3&&(S.v=N>>3,v=S.S(25),S.Sp=eZ([0,0,v[1],v[2]],S.v,S.I)),b+8)),S.C[N])^S.Sp[N%8]},Ly={},Q$=function(S,N,v,b,L,e){return function(){if(N.Z==N){var Q=[R,b,v,void 0,L,e,arguments],a=S&1;if(S&2)var l=d(false,false,N,!(H(Q,N),0));else a&&N.j.length?H(Q,N):a?(H(Q,N),d(false,false,N,true)):l=k(Q,N);return l}}},q={},W,n=function(S,N,v,b){for(v=(b=z(S),0);0>3,S),L>>8&255,L&255],b)&&S.push(b),N).S(83).length&&(N.M[83]=void 0,I(83,N,S)),""),v)&&(v.message&&(b+=v.message),v.stack&&(b+=":"+v.stack)),v=N.S(121),3>8*v&255;return b}),os=(r.prototype.zJ=function(S,N,v){if(3==S.length){for(v=0;3>v;v++)N[v]+=S[v];for(S=[13,8,(v=0,13),12,16,5,3,10,15];9>v;v++)N[3](N,v%3,S[v])}},function(S,N,v){if("object"==(N=typeof S,N))if(S){if(S instanceof Array)return"array";if(S instanceof Object)return N;if("[object Window]"==(v=Object.prototype.toString.call(S),v))return"object";if("[object Array]"==v||"number"==typeof S.length&&"undefined"!=typeof S.splice&&"undefined"!=typeof S.propertyIsEnumerable&&!S.propertyIsEnumerable("splice"))return"array";if("[object Function]"==v||"undefined"!=typeof S.call&&"undefined"!=typeof S.propertyIsEnumerable&&!S.propertyIsEnumerable("call"))return"function"}else return"null";else if("function"==N&&"undefined"==typeof S.call)return"object";return N}),l2=((r.prototype.OR=function(S,N,v,b){try{b=S[(N+2)%3],S[N]=S[N]-S[(N+1)%3]-b^(1==N?b<>>v)}catch(L){throw L;}},r).prototype.B="toString",function(S,N,v,b,L,e,Q){S.f++;try{for(v=(b=(Q=0,L=5001,S.O),void 0);(S.W||--L)&&(S.X||(Q=S.S(23))>17,N=(N^N<<5)&v)||(N=1),N)},r.prototype.L=function(S){return(S=S().shift(),this).X().length||this.U().length||(this.U=this.X=void 0,this.f--),S},r.prototype.b=function(S,N,v,b,L,e){if(this.F)return this.F;try{v=[],e=[],b=!!S,H([q,e,N],this),H([V,S,e,v],this),d(true,b,this,false),L=v[0]}catch(Q){E(Q,this),L=this.F,S&&S(L)}return L},function(S,N,v,b){for(;v--;)23!=v&&13!=v&&N.M[v]&&(N.M[v]=N[b](N[S](v),this));N[S]=this}),function(S,N){N.F=("E:"+S.message+":"+S.stack).slice(0,2048)}),d=(r.prototype.T=function(S,N,v,b){G((v=z((b=S&4,S&=3,N=z(this),this)),N=this.S(N),b&&(N=D((""+N).replace(/\\r\\n/g,"\\n"))),S&&G(this,v,T(N.length,2)),this),v,N)},(r.prototype.D="caller",r.prototype).ql=function(S,N,v,b,L){for(L=b=0;L>6;return(b=new Number((S=(b+=b<<3,b^=b>>11,b+(b<<15))>>>0,S)&(1<>>N)%v,b},function(S,N,v,b,L){if(0!=v.j.length){if(L=0==v.f)v.a=v.$();return(S=SZ(S,v,N),L)&&(L=v.$()-v.a,L<(b?10:0)||0>=v.H--||v.w.push(254>=L?L:254)),S}}),x=function(S,N,v){return l2(((v=S.S(23),S.C)&&v>3,a)){a=(a<<(L.g=a,3))-(P=[0,0,e[1],e[2]],4);try{L.J=eZ(P,p(a+4,L),p(a,L))}catch(c){throw c;}}L.push(L.J[l&7]^Q)},e=S.S(69)):N=function(Q){L.push(Q)},b&&N(b&255),b=0,S=v.length;b>L&255);return v},window.performance)||{}).now?function(){return Math.floor(this.kP+window.performance.now())}:function(){return+new Date},function(S,N,v){if(23==S||13==S)if(N.M[S])N.M[S][N.B](v);else N.M[S]=N.Ml(v);else if(239!=S&&243!=S&&70!=S&&83!=S&&69!=S||!N.M[S])N.M[S]=N.l(v,N.S);25==S&&(N.I=void 0,I(23,N,N.S(23)+32))}),NH=(r.prototype.N=function(S,N,v,b,L,e){if((e=S[0],e)==t){b=S[1];try{for(S=(b=(v=atob(b),[]),N=0);S>=8),b[N++]=L;this.O=(this.C=b,this.C.length<<3)}catch(Q){F(17,this,Q)}l2(this)}else if(e==q)v=S[1],v.push(this.S(239).length,this.S(121),this.S(243).length,this.S(70).length),I(219,this,S[2]),this.M[142]&&x(this,this.S(142));else{if(e==V){L=(S=(v=S[2],T(this.S(239).length+2,2)),this).Z,this.Z=this;try{N=this.S(83),0=a.b.offsetWidth||1>=a.b.offsetHeight)return!1;a.a.remove();V(a.c,"spanReady");return!0};function W(a,b){this.a=a;this.c=b;new sa;this.b=0}function ya(a){a.b&=-31}function X(a,b){a.b|=b}W.prototype.f=function(){};function za(a,b,c,d){this.b=new ta(a,b);a=new T(c);this.a=d(this.b,a)}function Aa(a,b,c){if(b&&c){var d=L(a.a.c,S,6);H(d,2,b,0);H(d,3,c,0)}N(na,U(a.b.a,"engine_msg")||"[]");return a.a.f()||Promise.resolve()} +function Ba(a){ya(a.a);X(a.a,1);window.AFMA_Communicator&&window.AFMA_Communicator.addEventListener("onshow",function(){X(a.a,32);ua(a.b)});var b=0,c=a.b.a;c.addEventListener("browserRender",function(){++b;if(1==b)V(a.b,"overallStart"),Aa(a).then(function(){V(a.b,"overallQuiet")});else{var d=c.clientWidth,g=c.clientHeight;d&&g&&Aa(a,d,g)}})};function Ca(){this.b=this.a=!1;this.c=[]}function Da(a){a.c.length=0;a.b=!0}function Ea(a,b){function c(){a.b=!1;var d=a.c.shift();return void 0===d?(a.a=!1,Promise.resolve()):Ea(a,d())}b=void 0===b?null:b;a.a=!0;return b?b.then(c,function(){if(a.b)return c();a.a=!1;return Promise.reject()}):c()}function Fa(a,b){b=m(b);for(var c=b.next();!c.done;c=b.next())a.c.push(c.value);return a.a?null:Ea(a)};function Y(a,b){W.call(this,a,b);this.g=new Ca}Y.prototype=ba(W.prototype);Y.prototype.constructor=Y;if(u)u(Y,W);else for(var Z in W)if("prototype"!=Z)if(Object.defineProperties){var Ga=Object.getOwnPropertyDescriptor(W,Z);Ga&&Object.defineProperty(Y,Z,Ga)}else Y[Z]=W[Z]; +Y.prototype.f=function(){var a=this;Da(this.g);return Fa(this.g,[function(){return null},function(){var b=null,c=L(L(a.c,S,6),R,1);c&&(b=(new wa(a.a,c)).wait());V(a.a,"browserStart");V(a.a,"browserStartEnd");ya(a);X(a,2);return b},function(){return Ha(a)},function(){V(a.a,"browserQuiet");V(a.a,"browserQuietEnd");X(a,8);return null}])}; +function Ha(a){V(a.a,"browserReady");V(a.a,"browserReadyEnd");X(a,4);0!=(a.b&32)&&ua(a.a);"complete"===document.readyState?Ia(a):window.addEventListener("load",function(){Ia(a)});V(a.a,"overallReady");return null} +function Ia(a){a=a.a.b;for(var b=a.ownerDocument,c=m(a.querySelectorAll("meta[x-phase]")),d=c.next();!d.done;d=c.next()){d=d.value;var g=b.createElement("STYLE");g.setAttribute("x-phase",d.getAttribute("x-phase"));g.setAttribute("x-layout",d.getAttribute("x-layout"));g.appendChild(b.createTextNode(d.getAttribute("x-css")));a.appendChild(g);d.remove()}} +(function(a){var b=null;w("mys.engine.init",function(c,d){var g=N(T,U(d,"render_config")||"[]");b=new za(c,d,g.a,a);Ba(b)});w("mys.engine.stage",function(){return b?b.a.b:0})})(function(a,b){if(null!=D(b,6))var c=L(b,S,6);else{c=L(b,Q,1);var d=L(b,P,12)||new P;var g=new S;var k=E(d,6)||!1;g=H(g,10,k,!1);k=D(d,2)||0;g=H(g,7,k,0);k=E(d,16)||!1;g=H(g,19,k,!1);k=E(d,15)||!1;g=H(g,18,k,!1);k=new R;k=H(k,3,100,0);k=H(k,4,1E4,0);E(d,4)?(H(k,6,!0,!1),H(k,7,"monospace",""),H(k,8,"IMWimw0.!?@","")):(E(d,5)&& +H(k,9,!0,!1),H(k,5,!0,!1));M(g,1,k);k=new pa;L(c,O,10)&&F(L(c,O,10),6)&&H(k,1,!0,!1);F(c,16)&&!E(d,1)&&H(k,2,!0,!1);M(g,4,k);c=g}M(b,6,c);return new Y(a,b)});}).call(this); diff --git a/doc/As65 Assembler_files/ads_data_002/css.css b/doc/As65 Assembler_files/ads_data_002/css.css new file mode 100644 index 0000000..c7aeaa9 --- /dev/null +++ b/doc/As65 Assembler_files/ads_data_002/css.css @@ -0,0 +1,83 @@ +/* + * See: https://fonts.google.com/license/googlerestricted + */ +/* cyrillic */ +@font-face { + font-family: 'Google Sans'; + font-style: normal; + font-weight: 400; + src: local('Google Sans Regular'), local('GoogleSans-Regular'), url(https://fonts.gstatic.com/s/googlesans/v16/4UaGrENHsxJlGDuGo1OIlL3Kwp5MKg.woff2) format('woff2'); + unicode-range: U+0400-045F, U+0490-0491, U+04B0-04B1, U+2116; +} +/* greek */ +@font-face { + font-family: 'Google Sans'; + font-style: normal; + font-weight: 400; + src: local('Google Sans Regular'), local('GoogleSans-Regular'), url(https://fonts.gstatic.com/s/googlesans/v16/4UaGrENHsxJlGDuGo1OIlL3Nwp5MKg.woff2) format('woff2'); + unicode-range: U+0370-03FF; +} +/* vietnamese */ +@font-face { + font-family: 'Google Sans'; + font-style: normal; + font-weight: 400; + src: local('Google Sans Regular'), local('GoogleSans-Regular'), url(https://fonts.gstatic.com/s/googlesans/v16/4UaGrENHsxJlGDuGo1OIlL3Bwp5MKg.woff2) format('woff2'); + unicode-range: U+0102-0103, U+0110-0111, U+0128-0129, U+0168-0169, U+01A0-01A1, U+01AF-01B0, U+1EA0-1EF9, U+20AB; +} +/* latin-ext */ +@font-face { + font-family: 'Google Sans'; + font-style: normal; + font-weight: 400; + src: local('Google Sans Regular'), local('GoogleSans-Regular'), url(https://fonts.gstatic.com/s/googlesans/v16/4UaGrENHsxJlGDuGo1OIlL3Awp5MKg.woff2) format('woff2'); + unicode-range: U+0100-024F, U+0259, U+1E00-1EFF, U+2020, U+20A0-20AB, U+20AD-20CF, U+2113, U+2C60-2C7F, U+A720-A7FF; +} +/* latin */ +@font-face { + font-family: 'Google Sans'; + font-style: normal; + font-weight: 400; + src: local('Google Sans Regular'), local('GoogleSans-Regular'), url(https://fonts.gstatic.com/s/googlesans/v16/4UaGrENHsxJlGDuGo1OIlL3Owp4.woff2) format('woff2'); + unicode-range: U+0000-00FF, U+0131, U+0152-0153, U+02BB-02BC, U+02C6, U+02DA, U+02DC, U+2000-206F, U+2074, U+20AC, U+2122, U+2191, U+2193, U+2212, U+2215, U+FEFF, U+FFFD; +} +/* cyrillic */ +@font-face { + font-family: 'Google Sans'; + font-style: normal; + font-weight: 500; + src: local('Google Sans Medium'), local('GoogleSans-Medium'), url(https://fonts.gstatic.com/s/googlesans/v16/4UabrENHsxJlGDuGo1OIlLU94Yt3CwZ-Pw.woff2) format('woff2'); + unicode-range: U+0400-045F, U+0490-0491, U+04B0-04B1, U+2116; +} +/* greek */ +@font-face { + font-family: 'Google Sans'; + font-style: normal; + font-weight: 500; + src: local('Google Sans Medium'), local('GoogleSans-Medium'), url(https://fonts.gstatic.com/s/googlesans/v16/4UabrENHsxJlGDuGo1OIlLU94YtwCwZ-Pw.woff2) format('woff2'); + unicode-range: U+0370-03FF; +} +/* vietnamese */ +@font-face { + font-family: 'Google Sans'; + font-style: normal; + font-weight: 500; + src: local('Google Sans Medium'), local('GoogleSans-Medium'), url(https://fonts.gstatic.com/s/googlesans/v16/4UabrENHsxJlGDuGo1OIlLU94Yt8CwZ-Pw.woff2) format('woff2'); + unicode-range: U+0102-0103, U+0110-0111, U+0128-0129, U+0168-0169, U+01A0-01A1, U+01AF-01B0, U+1EA0-1EF9, U+20AB; +} +/* latin-ext */ +@font-face { + font-family: 'Google Sans'; + font-style: normal; + font-weight: 500; + src: local('Google Sans Medium'), local('GoogleSans-Medium'), url(https://fonts.gstatic.com/s/googlesans/v16/4UabrENHsxJlGDuGo1OIlLU94Yt9CwZ-Pw.woff2) format('woff2'); + unicode-range: U+0100-024F, U+0259, U+1E00-1EFF, U+2020, U+20A0-20AB, U+20AD-20CF, U+2113, U+2C60-2C7F, U+A720-A7FF; +} +/* latin */ +@font-face { + font-family: 'Google Sans'; + font-style: normal; + font-weight: 500; + src: local('Google Sans Medium'), local('GoogleSans-Medium'), url(https://fonts.gstatic.com/s/googlesans/v16/4UabrENHsxJlGDuGo1OIlLU94YtzCwY.woff2) format('woff2'); + unicode-range: U+0000-00FF, U+0131, U+0152-0153, U+02BB-02BC, U+02C6, U+02DA, U+02DC, U+2000-206F, U+2074, U+20AC, U+2122, U+2191, U+2193, U+2212, U+2215, U+FEFF, U+FFFD; +} diff --git a/doc/As65 Assembler_files/ads_data_002/load_preloaded_resource_fy2019.js b/doc/As65 Assembler_files/ads_data_002/load_preloaded_resource_fy2019.js new file mode 100644 index 0000000..e31d787 --- /dev/null +++ b/doc/As65 Assembler_files/ads_data_002/load_preloaded_resource_fy2019.js @@ -0,0 +1,7 @@ +(function(){/* + + Copyright The Closure Library Authors. + SPDX-License-Identifier: Apache-2.0 +*/ +'use strict';var e=(a=null)=>a&&26==a.getAttribute("data-jc")?a:document.querySelector('[data-jc="26"]');var f=document;class h{constructor(){var a=f.head,b=a.querySelectorAll("link[data-reload-stylesheet][as=style][rel=preload]");for(var c=0;c{new h};"complete"===f.readyState||"interactive"===f.readyState?new h:f.addEventListener("DOMContentLoaded",l);}).call(this); diff --git a/doc/As65 Assembler_files/ads_data_002/one_click_handler_one_afma_fy2019.js b/doc/As65 Assembler_files/ads_data_002/one_click_handler_one_afma_fy2019.js new file mode 100644 index 0000000..ae85bc8 --- /dev/null +++ b/doc/As65 Assembler_files/ads_data_002/one_click_handler_one_afma_fy2019.js @@ -0,0 +1,50 @@ +(function(){/* + + Copyright The Closure Library Authors. + SPDX-License-Identifier: Apache-2.0 +*/ +'use strict';var m=this||self; +function n(a){var b=typeof a;if("object"==b)if(a){if(a instanceof Array)return"array";if(a instanceof Object)return b;var c=Object.prototype.toString.call(a);if("[object Window]"==c)return"object";if("[object Array]"==c||"number"==typeof a.length&&"undefined"!=typeof a.splice&&"undefined"!=typeof a.propertyIsEnumerable&&!a.propertyIsEnumerable("splice"))return"array";if("[object Function]"==c||"undefined"!=typeof a.call&&"undefined"!=typeof a.propertyIsEnumerable&&!a.propertyIsEnumerable("call"))return"function"}else return"null";else if("function"== +b&&"undefined"==typeof a.call)return"object";return b}function p(a){return"function"==n(a)}var aa="closure_uid_"+(1E9*Math.random()>>>0),ba=0,ca=Date.now||function(){return+new Date};function q(a,b){function c(){}c.prototype=b.prototype;a.prototype=new c;a.prototype.constructor=a};function da(a,b){a:{for(var c=a.length,d="string"===typeof a?a.split(""):a,e=0;eb?null:"string"===typeof a?a.charAt(b):a[b]};function ea(a){let b=!1,c;return function(){b||(c=a(),b=!0);return c}};function t(a,b){this.b=a===fa&&b||"";this.c=ha}t.prototype.f=!0;t.prototype.a=function(){return this.b.toString()};var ia=/^(?:(?:https?|mailto|ftp):|[^:/?#]*(?:[/?#]|$))/i;function ka(a){if(a instanceof t)return a;a="object"==typeof a&&a.f?a.a():String(a);ia.test(a)||(a="about:invalid#zClosurez");return new t(fa,a)}var ha={},fa={};var u;a:{var la=m.navigator;if(la){var ma=la.userAgent;if(ma){u=ma;break a}}u=""};function pa(){return-1!=u.indexOf("iPhone")&&-1==u.indexOf("iPod")&&-1==u.indexOf("iPad")};function qa(a){qa[" "](a);return a}qa[" "]=function(){};var ra=pa(),sa=-1!=u.indexOf("iPad");var ta=pa()||-1!=u.indexOf("iPod"),ua=-1!=u.indexOf("iPad");function x(a,b){this.b=a;this.f=b;this.a={};this.c=!0;if(0{c&&c(f);Ka(d,"load",e);Ka(d,"error",e)};M(d,"load",e);M(d,"error",e)}d.src=b;a.google_image_requests.push(d)};let Ma=0;var Na=(a,b=null)=>b&&b.getAttribute("data-jc")==a?b:document.querySelector(`[${"data-jc"}="${a}"]`),Oa=a=>{if(!(.01{"complete"===O.readyState||"interactive"===O.readyState?a():O.addEventListener("DOMContentLoaded",a)};/* + Copyright (c) Microsoft Corporation. All rights reserved. + Licensed under the Apache License, Version 2.0 (the "License"); you may not use + this file except in compliance with the License. You may obtain a copy of the + License at http://www.apache.org/licenses/LICENSE-2.0 + + THIS CODE IS PROVIDED ON AN *AS IS* BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY + KIND, EITHER EXPRESS OR IMPLIED, INCLUDING WITHOUT LIMITATION ANY IMPLIED + WARRANTIES OR CONDITIONS OF TITLE, FITNESS FOR A PARTICULAR PURPOSE, + MERCHANTABLITY OR NON-INFRINGEMENT. + + See the Apache Version 2.0 License for specific language governing permissions + and limitations under the License. +*/ +var Sa=/^((market|itms|intent|itms-appss):\/\/)/i;var S=(a,b,c)=>{b=b instanceof t||!Sa.test(b)?b:new t(fa,b);"about:invalid#zClosurez"===(b instanceof t?b:ka(b)).a()&&c(String(b));c=b instanceof t?b:ka(b);c instanceof t&&c.constructor===t&&c.c===ha?c=c.b:(n(c),c="type_error:SafeUrl");a.href=c},T=a=>{var b=`${"http:"===P.location.protocol?"http:":"https:"}//${"pagead2.googlesyndication.com"}/pagead/gen_204`;return c=>{c={id:"unsafeurl",ctx:a,url:c};var d=[];for(e in c)Pa(e,c[e],d);var e=d.join("&");if(e){c=b.indexOf("#");0>c&&(c=b.length);d=b.indexOf("?"); +if(0>d||d>c){d=c;var f=""}else f=b.substring(d+1,c);c=[b.substr(0,d),f,b.substr(c)];d=c[1];c[1]=e?d?d+"&"+e:e:d;e=c[0]+(c[1]?"?"+c[1]:"")+c[2]}else e=b;navigator.sendBeacon&&navigator.sendBeacon(e,"")}};var Ta=!!window.google_async_iframe_id;let U=Ta&&window.parent||window;var Ua=a=>{try{return O.querySelectorAll("*["+a+"]")}catch(b){return[]}};class Va{constructor(a,b,c={}){this.error=a;this.context=b.context;this.msg=b.message||"";this.id=b.id||"jserror";this.meta=c}};const Wa=/^https?:\/\/(\w|-)+\.cdn\.ampproject\.(net|org)(\?|\/|$)/;var Xa=class{constructor(a,b){this.a=a;this.b=b}},Ya=class{constructor(a,b,c,d,e){this.url=a;this.v=!!d;this.depth="number"===typeof e?e:null}};function $a(a,b){const c={};c[a]=b;return[c]}function ab(a,b,c,d,e){const f=[];Qa(a,function(h,g){(h=bb(h,b,c,d,e))&&f.push(g+"="+h)});return f.join(b)} +function bb(a,b,c,d,e){if(null==a)return"";b=b||"&";c=c||",$";"string"==typeof c&&(c=c.split(""));if(a instanceof Array){if(d=d||0,de?encodeURIComponent(ab(a,b,c,d,e+1)):"...";return encodeURIComponent(String(a))}function cb(a,b,c,d){a.a.push(b);a.b[b]=$a(c,d)} +function db(a){if(!a.f)return a.h;let b=1;for(const c in a.b)b=c.length>b?c.length:b;return a.h-a.f.length-b-a.c.length-1} +function eb(a,b,c,d){b=b+"//"+c+d;let e=db(a)-d.length;if(0>e)return"";a.a.sort(function(h,g){return h-g});d=null;c="";for(var f=0;f=k.length){e-=k.length;b+=k;c=a.c;break}a.g&&(c=e,k[c-1]==a.c&&--c,b+=k.substr(0,c),c=a.c,e=0);d=null==d?h:d}}}f="";a.f&&null!=d&&(f=c+a.f+"="+(a.u||d));return b+f} +class fb{constructor(a,b,c,d,e){this.h=c||4E3;this.c=a||"&";this.j=b||",$";this.f=void 0!==d?d:"trn";this.u=e||null;this.g=!1;this.b={};this.m=0;this.a=[]}};function gb(a,b,c,d,e,f){if((d?a.a:Math.random())<(e||a.b))try{let h;c instanceof fb?h=c:(h=new fb,Qa(c,(l,k)=>{var v=h,r=v.m++;l=$a(k,l);v.a.push(r);v.b[r]=l}));const g=eb(h,a.g,a.c,a.f+b+"&");g&&("undefined"===typeof f?N(m,g):N(m,g,f))}catch(h){}}class ib{constructor(a,b,c,d){this.g=a;this.c=b;this.f=c;this.b=d;this.a=Math.random()}};let jb=null;var kb=()=>{const a=m.performance;return a&&a.now&&a.timing?Math.floor(a.now()+a.timing.navigationStart):ca()},lb=()=>{const a=m.performance;return a&&a.now?a.now():null};class nb{constructor(a,b,c,d=0,e){this.label=a;this.type=b;this.value=c;this.duration=d;this.uniqueId=Math.random();this.slotId=e}};const V=m.performance,ob=!!(V&&V.mark&&V.measure&&V.clearMarks),W=ea(()=>{var a;if(a=ob){var b;if(null===jb){jb="";try{a="";try{a=m.top.location.hash}catch(c){a=m.location.hash}a&&(jb=(b=a.match(/\bdeid=([\d,]+)/))?b[1]:"")}catch(c){}}b=jb;a=!!b.indexOf&&0<=b.indexOf("1337")}return a});function pb(a){a&&V&&W()&&(V.clearMarks(`goog_${a.label}_${a.uniqueId}_start`),V.clearMarks(`goog_${a.label}_${a.uniqueId}_end`))} +class qb{constructor(a,b){this.b=[];this.c=b||m;let c=null;b&&(b.google_js_reporting_queue=b.google_js_reporting_queue||[],this.b=b.google_js_reporting_queue,c=b.google_measure_js_timing);this.a=W()||(null!=c?c:Math.random()sb(c,a,()=>b.apply(void 0,d))} +class vb{constructor(a,b,c,d=null){this.c=a;this.m=b;this.h=c;this.b=null;this.j=this.g;this.a=d;this.f=!1}pinger(){return this.c}g(a,b,c,d,e){e=e||this.m;let f;try{const w=new fb;w.g=!0;cb(w,1,"context",a);b.error&&b.meta&&b.id||(b=new Va(b,{message:rb(b)}));b.msg&&cb(w,2,"msg",b.msg.substring(0,512));var h=b.meta||{};b=h;if(this.b)try{this.b(b)}catch(J){}if(d)try{d(b)}catch(J){}d=w;h=[h];d.a.push(3);d.b[3]=h;{{d=m;h=[];b=null;let na;do{var g=d;if(R(g)){var l=g.location.href;b=g.document&&g.document.referrer|| +null;na=!0}else l=b,b=null,na=!1;h.push(new Ya(l||"",g,na));try{d=g.parent}catch(Q){d=null}}while(d&&g!=d);for(let Q=0,Za=h.length-1;Q<=Za;++Q)h[Q].depth=Za-Q;g=m;if(g.location&&g.location.ancestorOrigins&&g.location.ancestorOrigins.length==h.length-1)for(l=1;l{Y.google_measure_js_timing||(Z.a=!1,Z.b!=Z.c.google_js_reporting_queue&&(W()&&Array.prototype.forEach.call(Z.b,pb,void 0),Z.b.length=0))};X=new ib("http:"===P.location.protocol?"http:":"https:","pagead2.googlesyndication.com","/pagead/gen_204?id=",.01);"number"!==typeof Y.google_srt&&(Y.google_srt=Math.random()); +var xb=Y.google_srt;0<=xb&&1>=xb&&(X.a=xb);ub=new vb(X,"jserror",!0,Z); +ub.b=a=>{var b=P.jerExpIds;if("array"==n(b)&&0!==b.length){var c=a.eid;if(c){c=[...c.split(","),...b];b={};for(var d=0,e=0;e{wb()});var yb=(a,b)=>tb(a,b);function zb(a){if(!a||/[?&]dsh=1(&|$)/.test(a))return null;if(/[?&]ae=1(&|$)/.test(a)){var b=/[?&]adurl=([^&]+)/.exec(a);if(!b)return null;var c=b.index;try{return{o:a.slice(0,c)+"&act=1"+a.slice(c),finalUrl:decodeURIComponent(b[1])}}catch(d){return null}}if(/[?&]ae=2(&|$)/.test(a)){b=a;c="";{const d=a.indexOf("&adurl=");0Date.now()-c||((b=a.getAttribute("data-orig-async-clicktrack-url"))?({l:b}=Bb(b),S(a,b,T(599))):(a.setAttribute("data-orig-async-clicktrack-url",a.href),Ab(a))):Ab(a)}function Bb(a){const b=zb(a);return b?navigator.sendBeacon?navigator.sendBeacon(Db(b.o,"&ri=1"),"")?{l:b.finalUrl,s:!0}:{l:Db(a,"&ri=2"),s:!1}:{l:Db(a,"&ri=16"),s:!1}:{l:a,s:!1}} +function Db(a,b){const c=a.search(/&adurl=/);return 0>c?a+b:a.slice(0,c)+b+a.slice(c)};var Eb=(a,b)=>{b=F(a,2,"")||b;if(!b)return"";const c=/[?&]adurl=([^&]+)/.exec(b);if(!c)return b;const d=[b.slice(0,c.index+1)];wa(H(a,4,null),(e,f)=>{d.push(encodeURIComponent(f)+"="+encodeURIComponent(e)+"&")});d.push(b.slice(c.index+1));return d.join("")},Fb=a=>{const b=Ua("data-asoch-targets");a=H(a,1,L);const c=[];for(let g=0;g{for(const b of a)if(a=b.data,"A"==b.element.tagName&&!G(a,1)){const c=b.element,d=Eb(a,c.href);0c.element===b)}function Kb(a){P.fetch?P.fetch(a,{method:"GET",keepalive:!0,mode:"no-cors"}).then(b=>{b.ok||N(P,a)}):N(P,a)} +function Lb(a,b,c){const d=za(b);let e=F(d,2,"");wa(H(b,10,null),(f,h)=>{{var g=e;h=encodeURIComponent(h);const l=encodeURIComponent(f);f=new RegExp("[?&]"+h+"=([^&]+)");const k=f.exec(g);console.log(k);h=h+"="+l;e=k?g.replace(f,k[0].charAt(0)+h):g.replace("?","?"+h+"&")}});return c.redirectForStoreU2({clickUrl:a,trackingUrl:F(d,3,""),finalUrl:e,pingFunc:c.click,openFunc:c.openIntentOrNativeApp})}function Mb(){Ra(yb(556,()=>{new Nb(70)}))} +function Ob(a,b,c,d){for(var e;!c.id;)if(e="asoch-id-"+(Math.floor(2147483648*Math.random()).toString(36)+Math.abs(Math.floor(2147483648*Math.random())^ca()).toString(36)),!O.getElementById(e)){c.id=e;break}e=c.id;p(window.xy)&&window.xy(b,c,O.body);p(window.mb)&&window.mb(c);p(window.bgz)&&window.bgz(e);p(window.ja)&&window.ja(e,d?F(d,5,0):0);a.c&&p(window.ss)&&(a.u?window.ss(e,1,a.c):window.ss(a.c,1))} +class Nb{constructor(a){const b=Ua("data-asoch-meta");1!==b.length?gb(X,"gdn-asoch",{type:2,data:b.length},!0,void 0,void 0):(this.j=a,this.b=new Ea(JSON.parse(b[0].getAttribute("data-asoch-meta"))||[]),this.a=Fb(this.b),this.f=-Infinity,this.c=F(this.b,5,"")||"",this.u=!1,this.m=ta||ra||ua||sa,this.h=this.g=null,G(this.b,3)||(Gb(this.a),I(this.b,3,!0)),Ib(this.a),M(O,"click",yb(557,c=>{a:if(!c.defaultPrevented||this.g===c){for(var d,e,f=c.target;(!d||!e)&&f;){e||"A"!=f.tagName||(e=f);if(!d&&("A"== +f.tagName||f.hasAttribute("data-asoch-targets"))){var h=Jb(this.a,f);h&&(d=h.data)}f=f.parentElement}if(f=d&&!G(d,1)){if(c.defaultPrevented){var g=d;if(this.g===c&&this.h){f=new Ca(this.h);d=F(g,9,"");h="";switch(F(f,4,1)){case 2:if(F(f,2,0))h="blocked_fast_click";else if(F(f,1,"")||F(f,7,""))h="blocked_border_click";break;case 3:f=O.getElementById?O.getElementById("common_15click_anchor"):null,p(window.copfcChm)&&f&&(g=new g.constructor(K(g.i())),I(g,5,12),H(g,4,null).set("nb",(12).toString()),(h= +Jb(this.a,f))?h.data=g:this.a.push({element:f,data:g}),e&&(Ob(this,c,e,g),I(g,2,e.href)),window.copfcChm(c,Eb(g,f.href))),h="onepointfiveclick_first_click"}d&&h&&Kb(d+"&label="+h);Oa(this.j)}break a}h=d;for(g of E(h,6))Kb(g)}if(e&&f){d=f?d:null;(g=Jb(this.a,e))?g=g.data:(g=new L,I(g,2,e.href),I(g,11,e.target||"_top"),this.a.push({element:e,data:g}));g=Eb(d||g,F(g,2,""));0f?e+"&ri=1":e.slice(0,f)+"&ri=1"+e.slice(f),(0,c.click)(e)),e=d.finalUrl),e.startsWith("intent:")?c.openIntentOrNativeApp(e):c.openSystemBrowser(e,{useFirstPackage:!0,useRunningProcess:!0}))}else g&&Cb(e,G(this.b,8),this.f);g&&(this.f=Date.now());Oa(this.j)}}}),Ga),this.c&&p(window.ss)&&M(O.body,"mouseover",yb(626,()=>{window.ss(this.c,0)}),Ha),window.googqscp&&p(window.googqscp.registerCallback)&&window.googqscp.registerCallback((c,d)=>{this.g=c;this.h=d}))}};var Pb=yb(555,()=>Mb());Ma=70;Pb();}).call(this); diff --git a/doc/As65 Assembler_files/ads_data_002/osd_listener.js b/doc/As65 Assembler_files/ads_data_002/osd_listener.js new file mode 100644 index 0000000..166395c --- /dev/null +++ b/doc/As65 Assembler_files/ads_data_002/osd_listener.js @@ -0,0 +1,6 @@ +(function(window,document){/* + + Copyright The Closure Library Authors. + SPDX-License-Identifier: Apache-2.0 +*/ +var l;function aa(a){var b=0;return function(){return bb?-c:c}});var t=this||self;function pa(a,b){a=a.split(".");var c=t;a[0]in c||"undefined"==typeof c.execScript||c.execScript("var "+a[0]);for(var d;a.length&&(d=a.shift());)a.length||void 0===b?c[d]&&c[d]!==Object.prototype[d]?c=c[d]:c=c[d]={}:c[d]=b}function qa(){}function u(a){a.Ka=void 0;a.g=function(){return a.Ka?a.Ka:a.Ka=new a}}function ra(a){var b=typeof a;if("object"==b)if(a){if(a instanceof Array)return"array";if(a instanceof Object)return b;var c=Object.prototype.toString.call(a);if("[object Window]"==c)return"object";if("[object Array]"==c||"number"==typeof a.length&&"undefined"!=typeof a.splice&&"undefined"!=typeof a.propertyIsEnumerable&&!a.propertyIsEnumerable("splice"))return"array";if("[object Function]"==c||"undefined"!=typeof a.call&&"undefined"!=typeof a.propertyIsEnumerable&&!a.propertyIsEnumerable("call"))return"function"}else return"null";else if("function"==b&&"undefined"==typeof a.call)return"object";return b}function sa(a){var b=ra(a);return"array"==b||"object"==b&&"number"==typeof a.length}function ta(a,b){var c=Array.prototype.slice.call(arguments,1);return function(){var d=c.slice();d.push.apply(d,arguments);return a.apply(this,d)}}function ua(a,b){function c(){}c.prototype=b.prototype;a.prototype=new c;a.prototype.constructor=a};var va;function wa(a,b){if("string"===typeof a)return"string"!==typeof b||1!=b.length?-1:a.indexOf(b,0);for(var c=0;cb?null:"string"===typeof a?a.charAt(b):a[b]}function w(a,b){return 0<=wa(a,b)}function Ca(a){return Array.prototype.concat.apply([],arguments)}function Da(a){var b=a.length;if(0=arguments.length?Array.prototype.slice.call(a,b):Array.prototype.slice.call(a,b,c)}function Fa(a,b){a.sort(b||Ga)}function Ga(a,b){return a>b?1:ab?1:0};var z;a:{var Va=t.navigator;if(Va){var Wa=Va.userAgent;if(Wa){z=Wa;break a}}z=""}function A(a){return-1!=z.indexOf(a)};function Xa(){return A("Safari")&&!(Ya()||A("Coast")||A("Opera")||A("Edge")||A("Edg/")||A("OPR")||A("Firefox")||A("FxiOS")||A("Silk")||A("Android"))}function Ya(){return(A("Chrome")||A("CriOS"))&&!A("Edge")};function Za(a){var b=Number(a);return 0==b&&/^[\s\xa0]*$/.test(a)?NaN:b}function $a(){return"opacity".replace(/\-([a-z])/g,function(a,b){return b.toUpperCase()})}function ab(a){return String(a).replace(/([A-Z])/g,"-$1").toLowerCase()}function bb(a){return a.replace(/(^|[\s]+)([a-z])/g,function(b,c,d){return c+d.toUpperCase()})};function cb(a){cb[" "](a);return a}cb[" "]=qa;function db(a,b){try{return cb(a[b]),!0}catch(c){}return!1}function eb(a,b){var c=fb;return Object.prototype.hasOwnProperty.call(c,a)?c[a]:c[a]=b(a)};var gb=A("Opera"),B=A("Trident")||A("MSIE"),hb=A("Edge"),ib=A("Gecko")&&!(y(z,"WebKit")&&!A("Edge"))&&!(A("Trident")||A("MSIE"))&&!A("Edge"),jb=y(z,"WebKit")&&!A("Edge"),kb=jb&&A("Mobile");function lb(){var a=t.document;return a?a.documentMode:void 0}var mb;a:{var nb="",ob=function(){var a=z;if(ib)return/rv:([^\);]+)(\)|;)/.exec(a);if(hb)return/Edge\/([\d\.]+)/.exec(a);if(B)return/\b(?:MSIE|rv)[: ]([^\);]+)(\)|;)/.exec(a);if(jb)return/WebKit\/(\S+)/.exec(a);if(gb)return/(?:Version)[ \/]?(\S+)/.exec(a)}();ob&&(nb=ob?ob[1]:"");if(B){var pb=lb();if(null!=pb&&pb>parseFloat(nb)){mb=String(pb);break a}}mb=nb}var qb=mb,fb={};function rb(a){return eb(a,function(){for(var b=0,c=Sa(String(qb)).split("."),d=Sa(String(a)).split("."),e=Math.max(c.length,d.length),f=0;0==b&&f>>=7;a.a.push(b)}function Bb(a,b){a.a.push(b>>>0&255);a.a.push(b>>>8&255);a.a.push(b>>>16&255);a.a.push(b>>>24&255)};function Cb(){this.b=[];this.a=new zb}function Db(a,b,c){if(null!=c){Ab(a.a,8*b);a=a.a;var d=c;c=0>d;d=Math.abs(d);b=d>>>0;d=Math.floor((d-b)/4294967296);d>>>=0;c&&(d=~d>>>0,b=(~b>>>0)+1,4294967295>>7|b<<25)>>>0,b>>>=7;a.a.push(c)}};function Eb(){}var Fb="function"==typeof Uint8Array,Gb=[];function Hb(a){var b=a.c+a.f;a.a[b]||(a.b=a.a[b]={})}function Ib(a,b){if(be?encodeURIComponent(jd(a,b,c,d,e+1)):"...";return encodeURIComponent(String(a))}function ld(a,b,c,d){a.a.push(b);a.b[b]=id(c,d)}function md(a,b,c){b=b+"//pagead2.googlesyndication.com"+c;var d=nd(a)-c.length;if(0>d)return"";a.a.sort(function(n,p){return n-p});c=null;for(var e="",f=0;f=k.length){d-=k.length;b+=k;e=a.c;break}a.f&&(e=d,k[e-1]==a.c&&--e,b+=k.substr(0,e),e=a.c,d=0);c=null==c?g:c}}a="";null!=c&&(a=e+"trn="+c);return b+a}function nd(a){var b=1,c;for(c in a.b)b=c.length>b?c.length:b;return 3997-b-a.c.length-1};function od(){this.b=new cd;this.a=ad()?new $c:new O}od.prototype.setInterval=function(a,b){return D.setInterval(a,b)};od.prototype.clearInterval=function(a){D.clearInterval(a)};od.prototype.setTimeout=function(a,b){return D.setTimeout(a,b)};od.prototype.clearTimeout=function(a){D.clearTimeout(a)};function pd(a){P();var b=I()||D;oc(b,a,!1)}u(od);function qd(){}function P(){var a=qd.g();if(!a.a){if(!D)throw Error("Context has not been set and window is undefined.");a.a=od.g()}return a.a}u(qd);function rd(a){this.h=null;a||(a=[]);this.f=-1;this.a=a;a:{if(a=this.a.length){--a;var b=this.a[a];if(!(null===b||"object"!=typeof b||Array.isArray(b)||Fb&&b instanceof Uint8Array)){this.c=a- -1;this.b=b;break a}}this.c=Number.MAX_VALUE}}ua(rd,Eb);function sd(a){this.f=a;this.a=-1;this.b=this.c=0}function td(a,b){return function(c){for(var d=[],e=0;eMath.random())}function Hd(a){a&&S&&Fd()&&(S.clearMarks("goog_"+a.label+"_"+a.uniqueId+"_start"),S.clearMarks("goog_"+a.label+"_"+a.uniqueId+"_end"))}Gd.prototype.start=function(a,b){if(!this.a)return null;var c=Cd()||Bd();a=new Dd(a,b,c);b="goog_"+a.label+"_"+a.uniqueId+"_start";S&&Fd()&&S.mark(b);return a};function Id(){var a=Jd;this.i=Kd;this.h="jserror";this.f=!0;this.c=null;this.j=this.a;this.b=void 0===a?null:a}function Ld(a,b,c){return td(vd().a,function(){try{if(a.b&&a.b.a){var d=a.b.start(b.toString(),3);var e=c();var f=a.b,g=d;if(f.a&&"number"===typeof g.value){var h=Cd()||Bd();g.duration=h-g.value;var m="goog_"+g.label+"_"+g.uniqueId+"_end";S&&Fd()&&S.mark(m);!f.a||2048b&&(d=b);for(b=0;bc.height?m>n?(d=m,e=k):(d=n,e=p):mc++;){if(a===b)return!0;try{a:{var d=void 0;if(Sb&&!(B&&rb("9")&&!rb("10")&&t.SVGElement&&a instanceof t.SVGElement)&&(d=a.parentElement)){var e=d;break a}d=a.parentNode;var f=typeof d;e=("object"==f&&null!=d||"function"==f)&&1==d.nodeType?d:null}if(a=e||a){var g=G(a),h=g&&Xb(g),m=h&&h.frameElement;m&&(a=m)}}catch(k){break}}return!1}function Be(a,b,c){if(!a||!b)return!1;b=mc(lc(a),-b.left,-b.top);a=(b.left+b.right)/2;b=(b.top+b.bottom)/2;var d=I();dc(d.top)&&d.top&&d.top.document&&(d=d.top);if(!$d(d))return!1;a=d.document.elementFromPoint(a,b);if(!a)return!1;b=(b=(b=G(c))&&b.defaultView&&b.defaultView.frameElement)&&Ae(b,a);d=a===c;a=!d&&a&&$b(a,function(e){return e===c});return!(b||d||a)}function Ce(a,b,c,d){return W.g().h?!1:0>=jc(a)||0>=kc(a)?!0:c&&d?Rd(208,function(){return Be(a,b,c)}):!1};function De(a,b,c){var d=new H(0,0,0,0);this.time=a;this.volume=null;this.c=b;this.a=d;this.b=c};function Ee(a,b,c,d,e,f,g){this.j=a;this.i=b;this.c=c;this.a=d;this.h=e;this.b=f;this.f=g};function Fe(a){this.c=a;this.b=0;this.a=null}Fe.prototype.cancel=function(){P().clearTimeout(this.a);this.a=null};function Ge(a){var b=P();a.a=b.setTimeout(td(vd().a,Sd(143,function(){a.b++;a.c.sb()})),Xd())};function He(a,b,c){this.o=a;this.H=void 0===c?"na":c;this.f=[];this.A=!1;this.c=new De(-1,!0,this);this.a=this;this.h=b;this.m=this.C=this.l=!1;this.F="uk";this.G=!1;this.i=!0}l=He.prototype;l.Ra=function(){return this.ka()};l.ka=function(){return!1};l.sa=function(){return this.A=!0};l.aa=function(){return this.a.F};l.ga=function(){return this.a.m};function Ie(a,b){a.m||(a.m=!0,a.F=b,a.h=0,a.ma(),a.a!=a||Je(a))}l.u=function(){return this.a.H};l.K=function(){return this.a.cb()};l.cb=function(){return{}};l.M=function(){return this.a.h};function Ke(a,b){w(a.f,b)||(a.f.push(b),b.fa(a.a),b.Y(a.c),b.ca()&&(a.l=!0))}function Le(a,b){var c=a.f,d=wa(c,b);0<=d&&Array.prototype.splice.call(c,d,1);a.l&&b.ca()&&Me(a)}l.Oa=function(){var a=W.g();a.a=wc(!0,this.o,a.i)};l.Qa=function(){ue(W.g(),this.o)};l.Pa=function(){ve(W.g(),this.o)};l.pb=function(){var a=W.g();a.b=wc(!1,this.o,a.i)};l.eb=function(){return this.c.a};function Ne(a){a=a.a;a.Qa();a.Oa();a.pb();a.Pa();a.c.a=a.eb()}l.sb=function(){};function Me(a){a.l=a.f.length?Aa(a.f,function(b){return b.ca()}):!1}l.ma=function(){};function Oe(a){var b=Da(a.f);v(b,function(c){c.Y(a.c)})}function Je(a){var b=Da(a.f);v(b,function(c){c.fa(a.a)});a.a!=a||Oe(a)}l.fa=function(a){var b=this.a,c=a.M();this.a=c>=this.h?a:this;b!==this.a?(this.a==this||1==c&&0!=this.h||this.ma(),this.i=this.a.i,Je(this)):this.i!==this.a.i&&(this.i=this.a.i,Je(this))};l.Y=function(a){if(a.b===this.a){var b;if(!(b=this.C)){b=this.c;var c=this.l;if(c=a&&(void 0===c||!c||b.volume==a.volume)&&b.c==a.c)b=b.a,c=a.a,c=b==c?!0:b&&c?b.top==c.top&&b.right==c.right&&b.bottom==c.bottom&&b.left==c.left:!1;b=!c}this.c=a;b&&Oe(this)}};function Pe(a,b){a.h!==b&&(a.a!=a&&b>a.a.h&&(a.a=a,Je(a)),a.h=b)}l.ca=function(){return this.l};l.L=function(){this.G=!0};l.ta=function(){return this.G};function Qe(a,b,c,d){this.c=a;this.a=new H(0,0,0,0);this.l=new H(0,0,0,0);this.b=b;this.B=c;this.C=d;this.A=!1;this.timestamp=-1;this.h=new Ee(b.c,this.a,new H(0,0,0,0),0,0,U(),0)}l=Qe.prototype;l.ob=function(){return!0};l.ja=function(){};l.Ia=function(){if(this.c){var a=this.c,b=this.b.a.o;try{try{var c=je(a.getBoundingClientRect())}catch(k){c=new H(0,0,0,0)}var d=c.right-c.left,e=c.bottom-c.top,f=tc(a,b),g=f.a,h=f.b;var m=new H(Math.round(h),Math.round(g+d),Math.round(h+e),Math.round(g))}catch(k){m=lc(xe)}this.a=m}};l.Xa=function(){this.l=this.b.c.a};l.$=function(){this.Ia();this.h=new Ee(this.b.c,this.a,this.h.c,this.h.a,this.h.h,U(),this.h.f)};l.L=function(){this.ta()||(Le(this.b,this),this.ja(),this.A=!0)};l.ta=function(){return this.A};l.K=function(){return this.b.K()};l.M=function(){return this.b.M()};l.aa=function(){return this.b.aa()};l.ga=function(){return this.b.ga()};l.fa=function(){};l.Y=function(){this.$()};l.ca=function(){return this.C};function Re(a){this.h=!1;this.a=a;this.f=qa}l=Re.prototype;l.M=function(){return this.a.M()};l.aa=function(){return this.a.aa()};l.ga=function(){return this.a.ga()};l.create=function(a,b,c){var d=null;this.a&&(d=this.Ja(a,b,c),Ke(this.a,d));return d};l.Ma=function(){return this.ha()};l.ha=function(){return!1};l.mb=function(a){return this.a.sa()?(Ke(this.a,this),this.f=a,!0):!1};l.fa=function(a){0==a.M()&&this.f(a.aa(),this)};l.Y=function(){};l.ca=function(){return!1};l.L=function(){this.h=!0};l.ta=function(){return this.h};l.K=function(){return{}};function Se(a,b,c){this.c=void 0===c?0:c;this.b=a;this.a=null==b?"":b}function Te(a){switch(Math.trunc(a.c)){case -16:return-16;case -8:return-8;case 0:return 0;case 8:return 8;case 16:return 16;default:return 16}}function Ue(a,b){return a.cb.c?!1:a.bb.b?!1:typeof a.atypeof b.a?!1:a.a=h;h=!(0=h)||d;jf(a.b[f],g&&m,e,!g||h)}}function nf(a,b,c){a=ya(a.b,function(d){return b(d)});return c?a:qf(a)}function qf(a){return ya(a,function(b,c,d){return 0=(this.ia()?.3:.5),a.b=Math.max(a.b,e.D),pf(a.f,e.f,c.f,e.c,f,d),pf(a.a,e.D,c.D,e.c,f,d),d=d||c.a!=e.a?c.isVisible()&&e.isVisible():c.isVisible(),c=!e.isVisible()||e.c,jf(a.c,d,f,c),this.G=b,0=a.length)throw Bf;if(b in a)return a[b++];b++}};return c}throw Error("Not implemented");}function Ef(a,b){if(sa(a))try{v(a,b,void 0)}catch(c){if(c!==Bf)throw c;}else{a=Df(a);try{for(;;)b.call(void 0,a.next(),void 0,a)}catch(c){if(c!==Bf)throw c;}}}function Ff(a,b){var c=1;Ef(a,function(d){c=b.call(void 0,c,d)});return c}function Gf(a,b){var c=Df(a);a=new Cf;a.next=function(){var d=c.next();if(b.call(void 0,d,void 0,c))return d;throw Bf;};return a}function Hf(a){var b=Df(a);a=new Cf;var c=100;a.next=function(){if(0=a.bottom||a.left>=a.right?new H(0,0,0,0):a;a=this.b.c;var c=0,d=0,e=0;0<(this.a.bottom-this.a.top)*(this.a.right-this.a.left)&&(this.hb(b)?b=new H(0,0,0,0):(c=W.g().m,e=new H(0,c.height,c.width,0),c=ye(b,this.a),d=ye(b,W.g().a),e=ye(b,e)));b=b.top>=b.bottom||b.left>=b.right?new H(0,0,0,0):mc(b,-this.a.left,-this.a.top);we()||(d=c=0);this.h=new Ee(a,this.a,b,c,d,this.timestamp,e)};Uf.prototype.u=function(){return this.b.u()};function Vf(a){var b=[];Wf(new Xf,a,b);return b.join("")}function Xf(){}function Wf(a,b,c){if(null==b)c.push("null");else{if("object"==typeof b){if(Array.isArray(b)){var d=b;b=d.length;c.push("[");for(var e="",f=0;fc.time?b:c},a[0])}l.Ia=function(){};l.hb=function(){return!1};l.Xa=function(){};l.K=function(){var a={};return Object.assign(this.b.K(),(a.niot_obs=this.s,a.niot_cbk=this.m,a))};var pg={threshold:[0,.3,.5,.75,1]};function qg(a,b,c,d){mg.call(this,a,b,c,d);this.i=this.j=this.f=null}r(qg,mg);qg.prototype.u=function(){return"nio"};qg.prototype.ja=function(){if(this.f&&this.c)try{this.f.unobserve(this.c),this.j?(this.j.unobserve(this.c),this.j=null):this.i&&(this.i.disconnect(),this.i=null)}catch(a){}};function rg(a){return a.f&&a.f.takeRecords?a.f.takeRecords():[]}qg.prototype.w=function(){var a=this;if(!this.c)return!1;var b=this.c,c=this.b.a.o,d=vd().a;this.f=new c.IntersectionObserver(td(d,function(e){return ng(a,e)}),pg);d=td(d,function(){a.f.unobserve(b);a.f.observe(b);ng(a,rg(a))});c.ResizeObserver?(this.j=new c.ResizeObserver(d),this.j.observe(b)):c.MutationObserver&&(this.i=new t.MutationObserver(d),this.i.observe(b,{attributes:!0,childList:!0,characterData:!0,subtree:!0}));this.f.observe(b);ng(this,rg(this));return!0};qg.prototype.$=function(){var a=rg(this);0e?1:0)?-e:e;if(0===e)yb=0<1/e?0:2147483648,xb=0;else if(isNaN(e))yb=2147483647,xb=4294967295;else if(1.7976931348623157E308>>0,xb=0;else if(2.2250738585072014E-308>e)e/=Math.pow(2,-1074),yb=(c<<31|e/4294967296)>>>0,xb=e>>>0;else{f=e;d=0;if(2<=f)for(;2<=f&&1023>d;)d++,f/=2;else for(;1>f&&-1022>>0;xb=4503599627370496*e>>>0}Bb(p,xb);Bb(p,yb)}p=Jb(k,2);0!==p&&null!=p&&Db(n,2,p);p=Jb(k,3);0!==p&&null!=p&&Db(n,3,p);p=Jb(k,4);0!==p&&null!=p&&Db(n,4,p);p=Jb(k,5);if(0!==p&&null!=p&&null!=p)if(Ab(n.a,40),k=n.a,0<=p)Ab(k,p);else{for(c=0;9>c;c++)k.a.push(p&127|128),p>>=7;k.a.push(1)}k=new Uint8Array(n.a.length());c=n.b;d=c.length;for(e=p=0;ec;c++)for(d=n.concat(p[c].split("")),vb[c]=d,e=0;e>2,g=(g&3)<<4|h>>4,h=(h&15)<<2|f>>6,f&=63,d||(f=64,c||(h=64)),n.push(q[e],q[g],q[h]||"",q[f]||"");q=(b.pf=n.join(""),b)}else q={};x(a,q);return a}function Cg(){v(gg(),function(a){a.b.a&&tg.g()})}function zg(a){"osd"==a.h&&v(hg.a,function(b){var c={};Mf(b,0,(c.r=void 0,c))})}function Ag(a,b){a=a.l;Wd&&(a+=b-Vd);return a}function Dg(a){return(a=a.match(/[&\?;]adf=([0-9]+)/))&&2==a.length?parseInt(a[1],10):0}function Eg(){var a=Y;var b=void 0===b?function(){return{}}:b;T.h="av-js";Kd.a=.01;Qd([function(c){var d=Q.g(),e={};x(c,(e.bin=d.b,e.type="error",e),Kc(d.a),Bg(a,D),b());if(d=bf())e={},x(c,(e.v=encodeURIComponent(d),e))}])}function Fg(a){var b=new Gg;switch(a){case 0:case 5:return[];default:return a=4===Q.g().b,[new cg(b),new eg(b),new dg(b)].concat(ca(a?[]:[new ag]))}}u(ug);var Y=ug.g();function Gg(){}function bg(a,b){b=b||{};var c=void 0===b.Ua?{}:b.Ua;b=void 0===b.La?{}:b.La;var d=b.r,e=c[0],f=Bg(Y,I(),!1),g={};x(g,f,c);c={};var h=g;h=void 0===h?{}:h;g={};var m=W.g();f=Kc(a.i);var k=m.j,n=uf(a);f.p=[n.top+k.b,n.left+k.a,n.bottom+k.b,n.right+k.a];k=a.c;f.tos=mf(k.a);f.mtos=of(k.a);f.mcvt=k.c.a;f.rs=a.X;(n=5==a.X)||(f.ht=a.Da);0<=a.oa&&(f.tfs=a.oa,f.tls=a.qb);f.mc=ge(k.b);f.lte=ge(a.U);f.bas=a.bb;f.bac=a.J;m.h&&(f["if"]=a.F?0:1);f.met=a.b.c;n&&a.s&&(f.req=encodeURIComponent(a.s).substring(0,100));a.ia()&&(f.la="1");a.Ea&&(f.pa="1");f.avms=a.a?a.a.u():"ns";a.a&&x(f,a.a.K());0!=a.h&&(f.md=a.h);f.btr=null!=a.m&&""!=a.m?1:0;f.lm=a.T;x(f,Rf(a));h&&x(f,h);f.adk=a.l;a.lb&&a.Ca&&(f.adf=a.Ca);h=a.F;m=Q.g();!d&&h&&m.f&&(d=m.f);d&&(f.r=d);0===a.H&&(f.invis=1);d=af(f).join("&");g[3]=d;g[11]=h;g[29]=Q.g().b;g[0]=e;g[7]=a.f.D;g[9]=le(a.qa);g[28]=a.X;g[32]=a.a?a.a.u():"ns";g[5]=sf(a.c)&&4!=a.T;g[13]=of(a.c.a).join(",");g[18]=0==ze(uf(a));null!=a.Z&&(g[20]=a.Z.b,g[21]=a.Z.a);e=W.g();null!=e.b&&(g[22]=jc(e.b),g[23]=kc(e.b));null!=e.a&&(g[30]=jc(e.a),g[31]=kc(e.a),g[38]=le(e.a));d=e.j;f=uf(a);g[37]=le(new H(f.top+d.b,f.right+d.a,f.bottom+d.b,f.left+d.a));e.c&&(e=e.c,g[39]=e.width+"-"+e.height);-1!=a.H&&(g[25]=a.H);de(new Yc(a.l,a.P),g);x(c,g,b);b=a.b.a;a=a.za;try{var p=ee(c);ne(b,p,a)}catch(q){}return!0};function Hg(a,b,c,d){mg.call(this,a,b,c,d);this.f=function(){return null}}r(Hg,mg);Hg.prototype.u=function(){return"aio"};Hg.prototype.ja=function(){if(this.f)try{this.f()}catch(a){}};Hg.prototype.w=function(){var a=this;if(!this.c)return!1;this.f=nc(this.b.a.o).observeIntersection(td(vd().a,function(b){return ng(a,b)}));return!0};function Ig(a){a=void 0===a?D:a;Re.call(this,new He(a,2))}r(Ig,Re);Ig.prototype.u=function(){return"aio"};Ig.prototype.Ma=function(){return W.g().h&&this.ha()};Ig.prototype.ha=function(){var a;if(a=!W.g().f)a=nc(this.a.a.o),a=!(!a||!a.observeIntersection);return a};Ig.prototype.Ja=function(a,b,c){return new Hg(a,this.a,b,c)};function Jg(){He.call(this,D,2,"iem")}r(Jg,He);l=Jg.prototype;l.eb=function(){function a(q,R){return!!b.o.document.elementFromPoint(q,R)}var b=this,c=new H(0,this.o.innerWidth||this.o.width,this.o.innerHeight||this.o.height,0),d=Wb(document),e=Math.floor(c.left-d.a),f=Math.floor(c.top-d.b),g=Math.floor(c.right-d.a),h=Math.floor(c.bottom-d.b);c=a(e,f);d=a(g,h);if(c&&d)return new H(f,g,h,e);var m=a(g,f),k=a(e,h);if(c)h=Z(f,h,function(q){return a(e,q)}),g=Z(e,g,function(q){return a(q,f)});else if(m)h=Z(f,h,function(q){return a(g,q)}),e=Z(g,e,function(q){return a(q,f)});else if(k)f=Z(h,f,function(q){return a(e,q)}),g=Z(e,g,function(q){return a(q,h)});else if(d)f=Z(h,f,function(q){return a(g,q)}),e=Z(g,e,function(q){return a(q,h)});else{var n=Math.floor((e+g)/2),p=Math.floor((f+h)/2);if(!a(n,p))return new H(0,0,0,0);f=Z(p,f,function(q){return a(n,q)});h=Z(p,h,function(q){return a(n,q)});e=Z(n,e,function(q){return a(q,p)});g=Z(n,g,function(q){return a(q,p)})}return new H(f,g,h,e)};function Z(a,b,c){if(c(b))return b;for(var d=15;d--;){var e=Math.floor((a+b)/2);if(e==a||e==b)break;c(e)?a=e:b=e}return a}l.ka=function(){return W.g().h&&B&&rb(8)&&$d(this.o)};l.Oa=function(){};l.Qa=function(){};l.Pa=function(){};l.pb=function(){};u(Jg);function Kg(){He.call(this,D,1,"osd");this.b=null;this.B=[];this.I=this.s=this.j=this.w=0;this.C=!0}r(Kg,He);l=Kg.prototype;l.cb=function(){var a={};return a.exg=1,a};l.Ab=function(a){w(this.B,a)||this.B.push(a)};function Lg(a){var b=0;a=a.o;try{if(a&&a.Goog_AdSense_getAdAdapterInstance)return a}catch(c){}for(;a&&5>b;){try{if(a.google_osd_static_frame)return a.google_osd_static_frame}catch(c){}try{if(a.aswift_0&&a.aswift_0.google_osd_static_frame)return a.aswift_0.google_osd_static_frame}catch(c){}b++;a=a!=a.parent?a.parent:null}return null}function Mg(a,b){var c={};de(Q.g().c,c);c[0]="goog_request_monitoring";c[6]=4;c[16]=!1;c[19]=Q.g().h;a.b&&Ng(a.b,c);try{var d=ee(c);b.postMessage(d,"*")}catch(e){}}function Og(a){++a.s;if(2==a.w)Pg(a);else{if(10=h)){var m=Number(g.substr(0,h));g=g.substr(h+1);switch(m){case 36:case 26:case 15:case 8:case 11:case 16:case 5:case 18:g="true"==g;break;case 4:case 33:case 6:case 25:case 28:case 29:case 24:case 31:case 30:case 23:case 22:case 7:case 21:case 20:g=Number(g);break;case 19:case 3:if("function"==ra(decodeURIComponent))try{g=decodeURIComponent(g)}catch(n){throw Error("Error: URI malformed: "+g);}}e[m]=g}}e=e[0]?e:null}if(d=e)d=new Yc(e[4],e[12]),f=Q.g().c,d=f.a||d.a?f.a==d.a:f.b||d.b?f.b==d.b:!1;if(d&&(d=e[29],f=e[0],w(["goog_acknowledge_monitoring","goog_get_mode","goog_update_data","goog_image_request","goog_adspeed"],f))){Qg(a,e);if("goog_get_mode"==f&&c.source){m={};de(Q.g().c,m);m[0]="goog_provide_mode";m[6]=4;m[16]=!1;m[19]=Q.g().h;a.b&&Ng(a.b,m);try{var k=ee(m);c.source.postMessage(k,c.origin);Rg(a,k)}catch(n){T.a(406,n,void 0,void 0)}}if("goog_get_mode"==f||"goog_acknowledge_monitoring"==f)a.b&&(a.b.V=e[28]),a.w=2,Pg(a);if(c=e[32])a.H=c;if(a.b||a.f.length){if(4!=d){m=e[0];k=!1;f=W.g();c=a.c.a;"goog_acknowledge_monitoring"==m&&((void 0!==e[36]?e[36]:!e[8])?Pe(a,2):Pe(a,0),Je(a));e[37]&&(m=me(e[37]))&&(k=!0,f.j=new E(m.left,m.top));if(e[38]){if(m=me(e[38]))k=!0,f.a=m}else isNaN(e[30])||isNaN(e[31])||(f.a||(f.a=new H(0,0,0,0)),k=!0,f.a.right=f.a.left+e[30],f.a.bottom=f.a.top+e[31]);e[9]&&(k=!0,m=me(e[9]))&&(c=m,f.l=m);e[39]&&((m=e[39])?(m=m.split("-"),m=2==m.length?new F(Za(m[0]),Za(m[1])):null):m=null,m&&(f.c=m));k&&(k=U(),f=we(),k=new De(k,f,a),k.a=c,a.Y(k))}c=pe(e[3]).r;if(4==d){f=e[0];d=100*e[25];"number"!==typeof d||isNaN(d)||a.b&&(window.document["4CGeArbVQ"]=d|0);void 0!=e[18]&&a.b&&(a.b.U=e[18]);d=e[7];void 0!=d&&0a&&23==a.getAttribute("data-jc")?a:document.querySelector('[data-jc="23"]');var I=document,J=window;function wa(a,b,c){if(Array.isArray(b))for(var d=0;d{"complete"===I.readyState||"interactive"===I.readyState?a():I.addEventListener("DOMContentLoaded",a)};function M(){this.b=this.b;this.c=this.c}M.prototype.b=!1;function ya(a){a.b||(a.b=!0,a.f())}M.prototype.f=function(){if(this.c)for(;this.c.length;)this.c.shift()()};/* + Copyright (c) Microsoft Corporation. All rights reserved. + Licensed under the Apache License, Version 2.0 (the "License"); you may not use + this file except in compliance with the License. You may obtain a copy of the + License at http://www.apache.org/licenses/LICENSE-2.0 + + THIS CODE IS PROVIDED ON AN *AS IS* BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY + KIND, EITHER EXPRESS OR IMPLIED, INCLUDING WITHOUT LIMITATION ANY IMPLIED + WARRANTIES OR CONDITIONS OF TITLE, FITNESS FOR A PARTICULAR PURPOSE, + MERCHANTABLITY OR NON-INFRINGEMENT. + + See the Apache Version 2.0 License for specific language governing permissions + and limitations under the License. +*/ +var za=/^((market|itms|intent|itms-appss):\/\/)/i;var Aa=()=>{var a=`${"http:"===J.location.protocol?"http:":"https:"}//${"pagead2.googlesyndication.com"}/pagead/gen_204`;return b=>{b={id:"unsafeurl",ctx:625,url:b};var c=[];for(d in b)wa(d,b[d],c);var d=c.join("&");if(d){b=a.indexOf("#");0>b&&(b=a.length);c=a.indexOf("?");if(0>c||c>b){c=b;var e=""}else e=a.substring(c+1,b);b=[a.substr(0,c),e,a.substr(b)];c=b[1];b[1]=d?c?c+"&"+d:d:c;d=b[0]+(b[1]?"?"+b[1]:"")+b[2]}else d=a;navigator.sendBeacon&&navigator.sendBeacon(d,"")}};var Ba=(a,b)=>{if(a)for(let c in a)Object.prototype.hasOwnProperty.call(a,c)&&b.call(void 0,a[c],c,a)},Ca=!!window.google_async_iframe_id;let L=Ca&&window.parent||window;var Da=(a,b)=>{a&&Ba(b,(c,d)=>{a.style[d]=c})},Ea=a=>{var b=I.body;const c=document.createDocumentFragment(),d=a.length;for(let e=0;e{g.google_logging_queue||(g.google_logging_queue=[]);g.google_logging_queue.push([12,a])};let N=null;class Ga{constructor(a,b,c,d=0,e){this.label=a;this.type=b;this.value=c;this.duration=d;this.uniqueId=Math.random();this.slotId=e}};const O=g.performance,Ha=!!(O&&O.mark&&O.measure&&O.clearMarks),T=ha(()=>{var a;if(a=Ha){var b;if(null===N){N="";try{a="";try{a=g.top.location.hash}catch(c){a=g.location.hash}a&&(N=(b=a.match(/\bdeid=([\d,]+)/))?b[1]:"")}catch(c){}}b=N;a=!!b.indexOf&&0<=b.indexOf("1337")}return a});function Ia(a){a&&O&&T()&&(O.clearMarks(`goog_${a.label}_${a.uniqueId}_start`),O.clearMarks(`goog_${a.label}_${a.uniqueId}_end`))} +class Ja{constructor(a,b){this.a=[];this.c=b||g;let c=null;b&&(b.google_js_reporting_queue=b.google_js_reporting_queue||[],this.a=b.google_js_reporting_queue,c=b.google_measure_js_timing);this.b=T()||(null!=c?c:Math.random(){U.google_measure_js_timing||(V.b=!1,V.a!=V.c.google_js_reporting_queue&&(T()&&r(V.a,Ia),V.a.length=0))};"number"!==typeof U.google_srt&&(U.google_srt=Math.random());"complete"==U.document.readyState?Ka():V.b&&H(U,"load",()=>{Ka()});var La=a=>{H(J,"message",b=>{let c;try{c=JSON.parse(b.data)}catch(d){return}!c||"ig"!==c.googMsgType||a(c,b)})};function W(a,b,c){M.call(this);this.g=a;this.s=b||0;this.i=c;this.j=k(this.m,this)}q(W,M);W.prototype.a=0;W.prototype.f=function(){W.B.f.call(this);this.stop();delete this.g;delete this.i};W.prototype.start=function(a){this.stop();var b=this.j;a=void 0!==a?a:this.s;if("function"!=ca(b))if(b&&"function"==typeof b.handleEvent)b=k(b.handleEvent,b);else throw Error("Invalid listener argument");this.a=2147483647{a&&(a.style.display=b?"inline-block":"none")};function Oa(a=""){const b={top:0,right:0,bottom:0,left:0};a&&(a=a.split(","),4==a.length&&a.reduce((c,d)=>c&&!isNaN(d),!0)&&([b.top,b.right,b.bottom,b.left]=a.map(c=>+c)));return b} +function Pa(a,b,c=2147483647){const d=I.createElement("DIV");Da(d,Object.assign(Ma,{"z-index":c},b));F(a.a,10)&&H(d,"click",ba);if(F(a.a,11)){a=b=I.createElement("A");c=Aa();var e;za.test("#")?e=new u(v,"#"):e="#";"about:invalid#zClosurez"===(e instanceof u?e:ka(e)).a()&&c(String(e));e=e instanceof u?e:ka(e);a.href=e instanceof u&&e.constructor===u&&e.c===ia?e.b:"type_error:SafeUrl";b.appendChild(d);return b}return d} +function Qa(a,b){switch(D(b.h,5,1)){case 2:J.AFMA_Communicator&&J.AFMA_Communicator.addEventListener&&J.AFMA_Communicator.addEventListener("onshow",()=>{Y(a,b)});break;case 10:H(J,"i-creative-view",()=>{Y(a,b)});break;case 4:H(I,"DOMContentLoaded",()=>{Y(a,b)});break;case 8:La(c=>{c.rr&&Y(a,b)});break;case 9:if(J.IntersectionObserver){const c=new IntersectionObserver(d=>{for(let e of d)if(0{Y(a,b)})}}function Ra(a,b){b=Oa(b);const c=D(a.a,9,0);a.f=[{width:"100%",height:b.top+c+"px",top:-c+"px",left:"0"},{width:b.right+c+"px",height:"100%",top:"0",right:-c+"px"},{width:"100%",height:b.bottom+c+"px",bottom:-c+"px",left:"0"},{width:b.left+c+"px",height:"100%",top:"0",left:-c+"px"}].map(d=>Pa(a,d,9019))} +function Sa(a){var b=0;for(let d of a.w){const e=d.h,p=a.m[D(e,5,1)];d.l||void 0===p||(b=Math.max(b,p+D(e,2,0)))}a.g&&ya(a.g);b-=Date.now();const c=a.b;0{X(c,!1)},b),a.g.start()):X(c,!1)}function Y(a,b){if(!b.l){var c=D(b.h,5,1);a.m[c]=Date.now();F(b.h,9)&&(a.w.push(b),Sa(a))}} +class Ta{constructor(){this.f=[];this.g=this.b=null;this.w=[];this.a=null;this.s=[];this.c=[];this.j=[];this.m={};this.A=[];this.i=null}init(a){Fa([a]);this.a=new qa(a);a=ma(this.a);r(na(a),e=>{this.j.push({u:0,l:!1,v:0,h:e,o:-1})});try{var b=I.querySelectorAll("*[data-ifc]")}catch(e){b=[]}this.c=b;let c=!1;b=this.c.length;for(let e=0;e{this.j.push({u:0,l:!1,v:0,h:p,o:e});1===D(p,4,1)&&(c=!0)});b=!1;for(var d of this.j)a= +d.h,0{const e=I.body.querySelectorAll(".amp-fcp, .amp-bcp");for(let f=0;f{var p=-1,f=[];for(let y of this.j){var h=y.o,m=-1!==h;if(!(D(y.h,3,0)<=p||y.l||m&& +!1===f[h])){var n=!m||f[h]||this.c[h].contains(e.target);m&&n&&(f[h]=!0);if(h=n)if(h=e,n=y,m=n.h,0P||0>Q)h=!1;else{n=Oa(D(n.h, +1,""));B=!(P>=n.left&&Z-P>n.right&&Q>=n.top&&aa-Q>n.bottom);if(this.i&&F(this.a,12)&&500>h.timeStamp-this.i.timeStamp){h=this.i.changedTouches[0];const [R,S]=[h.clientX/E-m.left,h.clientY/E-m.top];!isNaN(R)&&!isNaN(S)&&0<=R&&0<=S&&(B=B||!(R>=n.left&&Z-R>n.right&&S>=n.top&&aa-S>n.bottom))}h=B}}}else h=!0;if(h){var l=y;p=D(y.h,3,0)}}}if(l)switch(p=l.h,D(p,4,1)){case 2:case 3:e.preventDefault?e.preventDefault():e.returnValue=!1;f=Date.now();500=D(f,8,0))if(l.l= +!0,this.b&&0{this.i=e},sa)}registerCallback(a){this.s.push(a)}};window.googqscp=new Ta;}).call(this); diff --git a/doc/As65 Assembler_files/ads_data_002/si.html b/doc/As65 Assembler_files/ads_data_002/si.html new file mode 100644 index 0000000..1721083 --- /dev/null +++ b/doc/As65 Assembler_files/ads_data_002/si.html @@ -0,0 +1,2 @@ + + \ No newline at end of file diff --git a/doc/As65 Assembler_files/ads_data_002/window_focus_fy2019.js b/doc/As65 Assembler_files/ads_data_002/window_focus_fy2019.js new file mode 100644 index 0000000..5ea0dbb --- /dev/null +++ b/doc/As65 Assembler_files/ads_data_002/window_focus_fy2019.js @@ -0,0 +1,23 @@ +(function(){/* + + Copyright The Closure Library Authors. + SPDX-License-Identifier: Apache-2.0 +*/ +'use strict';function f(a,c,d){a.addEventListener&&a.addEventListener(c,d,!1)};function g(a,c,d=null){h(a,c,d)}function h(a,c,d){a.google_image_requests||(a.google_image_requests=[]);const b=a.document.createElement("img");if(d){const e=r=>{d&&d(r);b.removeEventListener&&b.removeEventListener("load",e,!1);b.removeEventListener&&b.removeEventListener("error",e,!1)};f(b,"load",e);f(b,"error",e)}b.src=c;a.google_image_requests.push(b)};var k=(a=null)=>a&&22==a.getAttribute("data-jc")?a:document.querySelector('[data-jc="22"]');var l=document,m=window;function n(a,c,d){if(Array.isArray(c))for(var b=0;b{if(l[a.a])a.b&&(a.b=!1,a.c=Date.now(),q(a,0));else{if(-1!=a.c){const c=Date.now()-a.c;0a.handleClick(c))} +function q(a,c,d){var b={gqid:a.h,qqid:a.i};0==c&&(b["return"]=0);1==c&&(b["return"]=1,b.timeDelta=d);2==c&&(b.bgload=1);3==c&&(b.fg=1);c=[];for(var e in b)n(e,b[e],c);g(m,a.g+"&label=window_focus&"+c.join("&"),void 0);if(!(.01{this.b=!1},5E3)}};{const a=k(document.currentScript);if(null==a)throw Error("JSC not found 22");var v;{const c={},d=a.attributes;for(let b=d.length-1;0<=b;b--){const e=d[b].name;0===e.indexOf("data-jcp-")&&(c[e.substring(9)]=d[b].value)}v=c}window.window_focus_for_click=new u(v.url,v["gws-id"],v["qem-id"])};}).call(this); diff --git a/doc/As65 Assembler_files/ads_data_003/abg_lite_fy2019.js b/doc/As65 Assembler_files/ads_data_003/abg_lite_fy2019.js new file mode 100644 index 0000000..5a8263f --- /dev/null +++ b/doc/As65 Assembler_files/ads_data_003/abg_lite_fy2019.js @@ -0,0 +1,48 @@ +(function(){/* + + Copyright The Closure Library Authors. + SPDX-License-Identifier: Apache-2.0 +*/ +'use strict';var l=this||self,ca=/^[\w+/_-]+[=]{0,2}$/,n=null; +function da(a){var b=typeof a;if("object"==b)if(a){if(a instanceof Array)return"array";if(a instanceof Object)return b;var c=Object.prototype.toString.call(a);if("[object Window]"==c)return"object";if("[object Array]"==c||"number"==typeof a.length&&"undefined"!=typeof a.splice&&"undefined"!=typeof a.propertyIsEnumerable&&!a.propertyIsEnumerable("splice"))return"array";if("[object Function]"==c||"undefined"!=typeof a.call&&"undefined"!=typeof a.propertyIsEnumerable&&!a.propertyIsEnumerable("call"))return"function"}else return"null"; +else if("function"==b&&"undefined"==typeof a.call)return"object";return b}var p="closure_uid_"+(1E9*Math.random()>>>0),ea=0,fa=Date.now||function(){return+new Date};function ha(a,b){function c(){}c.prototype=b.prototype;a.prototype=new c;a.prototype.constructor=a};function q(a,b){this.h=a===ia&&b||"";this.g=ja}var ja={},ia={};function r(a){r[" "](a);return a}r[" "]=function(){};function ka(){}var la="function"==typeof Uint8Array;function ma(a,b,c){a.i=null;b||(b=[]);a.o=void 0;a.j=-1;a.g=b;a:{if(b=a.g.length){--b;var d=a.g[b];if(!(null===d||"object"!=typeof d||Array.isArray(d)||la&&d instanceof Uint8Array)){a.l=b-a.j;a.h=d;break a}}a.l=Number.MAX_VALUE}a.m={};if(c)for(b=0;ba&&60==a.getAttribute("data-jc")?a:document.querySelector('[data-jc="60"]'),va=()=>{if(!(.01(1>=Math.abs(c.left- +b.left)&&1>=Math.abs(c.right-b.right)?b.bottom-b.top:b.right-b.left)&&(a=!0)}else a=!1;window.goog_multislot_cache.hd=a}}else a=!1;this.A=a;this.u=B("abgcp"+this.creativeIndexSuffix);this.s=B("abgc"+this.creativeIndexSuffix);this.h=B("abgs"+this.creativeIndexSuffix);B("abgl"+this.creativeIndexSuffix);this.o=B("abgb"+this.creativeIndexSuffix);this.F=B("abgac"+this.creativeIndexSuffix);B("mute_panel"+this.creativeIndexSuffix);this.v=C("goog_delegate_attribution"+this.creativeIndexSuffix);this.isDelegateAttributionActive= +!!this.v&&!!this.H&&!C("goog_delegate_disabled")&&!this.w;if(this.h)a:{a=this.h;b="A";c=a.childNodes;for(let d=0;d{if(a)for(let c in a)Object.prototype.hasOwnProperty.call(a,c)&&b.call(void 0,a[c],c,a)},Ha=!!window.google_async_iframe_id;let L=Ha&&window.parent||window;var M=(a,b)=>{a&&Ga(b,(c,d)=>{a.style[d]=c})};class Ia{constructor(a,b,c={}){this.error=a;this.context=b.context;this.msg=b.message||"";this.id=b.id||"jserror";this.meta=c}};const Ja=/^https?:\/\/(\w|-)+\.cdn\.ampproject\.(net|org)(\?|\/|$)/;var Ka=class{constructor(a,b){this.g=a;this.h=b}},La=class{constructor(a,b,c,d,e){this.url=a;this.D=!!d;this.depth="number"===typeof e?e:null}};function Ma(a,b){const c={};c[a]=b;return[c]}function Na(a,b,c,d,e){const g=[];Aa(a,function(f,h){(f=Oa(f,b,c,d,e))&&g.push(h+"="+f)});return g.join(b)} +function Oa(a,b,c,d,e){if(null==a)return"";b=b||"&";c=c||",$";"string"==typeof c&&(c=c.split(""));if(a instanceof Array){if(d=d||0,de?encodeURIComponent(Na(a,b,c,d,e+1)):"...";return encodeURIComponent(String(a))}function N(a,b,c,d){a.g.push(b);a.h[b]=Ma(c,d)} +function Pa(a){if(!a.j)return a.m;let b=1;for(const c in a.h)b=c.length>b?c.length:b;return a.m-a.j.length-b-a.i.length-1} +function Qa(a,b,c,d){b=b+"//"+c+d;let e=Pa(a)-d.length;if(0>e)return"";a.g.sort(function(f,h){return f-h});d=null;c="";for(var g=0;g=k.length){e-=k.length;b+=k;c=a.i;break}a.l&&(c=e,k[c-1]==a.i&&--c,b+=k.substr(0,c),c=a.i,e=0);d=null==d?f:d}}}g="";a.j&&null!=d&&(g=c+a.j+"="+(a.u||d));return b+g} +class O{constructor(a,b,c,d,e){this.m=c||4E3;this.i=a||"&";this.o=b||",$";this.j=void 0!==d?d:"trn";this.u=e||null;this.l=!1;this.h={};this.s=0;this.g=[]}};function Ra(a,b,c,d,e){if((d?a.g:Math.random())<(e||a.h))try{let g;c instanceof O?g=c:(g=new O,Aa(c,(h,m)=>{var k=g,w=k.s++;h=Ma(m,h);k.g.push(w);k.h[w]=h}));const f=Qa(g,a.l,a.i,a.j+b+"&");f&&D(l,f)}catch(g){}}class Sa{constructor(a,b,c,d){this.l=a;this.i=b;this.j=c;this.h=d;this.g=Math.random()}};let P=null;var Ta=()=>{const a=l.performance;return a&&a.now&&a.timing?Math.floor(a.now()+a.timing.navigationStart):fa()},Ua=()=>{const a=l.performance;return a&&a.now?a.now():null};class Va{constructor(a,b,c,d=0,e){this.label=a;this.type=b;this.value=c;this.duration=d;this.uniqueId=Math.random();this.slotId=e}};const Q=l.performance,Wa=!!(Q&&Q.mark&&Q.measure&&Q.clearMarks),R=function(a){let b=!1,c;return function(){b||(c=a(),b=!0);return c}}(()=>{var a;if(a=Wa){var b;if(null===P){P="";try{a="";try{a=l.top.location.hash}catch(c){a=l.location.hash}a&&(P=(b=a.match(/\bdeid=([\d,]+)/))?b[1]:"")}catch(c){}}b=P;a=!!b.indexOf&&0<=b.indexOf("1337")}return a});function Xa(a){a&&Q&&R()&&(Q.clearMarks(`goog_${a.label}_${a.uniqueId}_start`),Q.clearMarks(`goog_${a.label}_${a.uniqueId}_end`))} +class Ya{constructor(a,b){this.h=[];this.i=b||l;let c=null;b&&(b.google_js_reporting_queue=b.google_js_reporting_queue||[],this.h=b.google_js_reporting_queue,c=b.google_measure_js_timing);this.g=R()||(null!=c?c:Math.random()Za(c,a,()=>b.apply(void 0,d))} +class ab{constructor(a,b,c,d=null){this.l=a;this.s=b;this.m=c;this.h=null;this.o=this.j;this.g=d;this.i=!1}j(a,b,c,d,e){e=e||this.s;let g;try{const u=new O;u.l=!0;N(u,1,"context",a);b.error&&b.meta&&b.id||(b=new Ia(b,{message:S(b)}));b.msg&&N(u,2,"msg",b.msg.substring(0,512));var f=b.meta||{};b=f;if(this.h)try{this.h(b)}catch(G){}if(d)try{d(b)}catch(G){}d=u;f=[f];d.g.push(3);d.h[3]=f;{{d=l;f=[];b=null;let aa;do{var h=d;if(J(h)){var m=h.location.href;b=h.document&&h.document.referrer||null;aa=!0}else m= +b,b=null,aa=!1;f.push(new La(m||"",h,aa));try{d=h.parent}catch(K){d=null}}while(d&&h!=d);for(let K=0,Fa=f.length-1;K<=Fa;++K)f[K].depth=Fa-K;h=l;if(h.location&&h.location.ancestorOrigins&&h.location.ancestorOrigins.length==f.length-1)for(m=1;m{U.google_measure_js_timing||(V.g=!1,V.h!=V.i.google_js_reporting_queue&&(R()&&Array.prototype.forEach.call(V.h,Xa,void 0),V.h.length=0))};bb=new Sa("http:"===H.location.protocol?"http:":"https:","pagead2.googlesyndication.com","/pagead/gen_204?id=",.01);"number"!==typeof U.google_srt&&(U.google_srt=Math.random()); +var db=U.google_srt;0<=db&&1>=db&&(bb.g=db);T=new ab(bb,"jserror",!0,V); +T.h=a=>{var b=H.jerExpIds;if("array"==da(b)&&0!==b.length){var c=a.eid;if(c){c=[...c.split(","),...b];b={};for(var d=0,e=0;e{cb()});var W=(a,b)=>$a(a,b);function eb(a){if(a.g.j&&a.g.O){const b=na(a.g.g);b&&null!=v(b,5)&&null!=v(b,6)&&(a.i=new za(y(b,5,""),y(b,6,""),y(b,19,"")));A(a.g.j,"click",W(452,()=>{if(!a.j&&(a.j=!0,a.i)){{var c=a.i;let d=c.h+"&label=closebutton_whythisad_click";d+="&label_instance=1";c.g&&(d+="&cid="+c.g);D(window,d)}}}))}} +function fb(a){if(a.g.R)A(a.g.i,"click",W(365,b=>{const c=H.goog_interstitial_display;c&&(c(b),b&&(b.stopPropagation(),b.preventDefault()))}));else if(a.g.isMutableImpression&&a.g.isMobileDevice)A(a.g.i,"click",()=>a.h());else if(a.g.isMutableImpression&&!a.g.isMobileDevice&&a.g.l&&A(a.g.l,"click",()=>a.h()),a.g.J)gb(a);else{A(a.g.i,"mouseover",W(367,()=>gb(a)));A(a.g.i,"mouseout",W(369,()=>hb(a,500)));A(a.g.i,"touchstart",W(368,()=>gb(a)));const b=W(370,()=>hb(a,4E3));A(a.g.i,"mouseup",b);A(a.g.i, +"touchend",b);A(a.g.i,"touchcancel",b);a.g.j&&A(a.g.j,"click",W(371,c=>a.preventDefault(c)))}}function gb(a){window.clearTimeout(a.g.m);a.g.m=null;a.g.h&&"block"==a.g.h.style.display||(a.g.C=Date.now(),a.g.o&&a.g.h&&(a.g.o.style.display="none",a.g.h.style.display="block"))}function hb(a,b){window.clearTimeout(a.g.m);a.g.m=window.setTimeout(()=>ib(a),b)}function kb(a){const b=a.g.F;b.style.display="block";a.g.enableNativeJakeUi&&window.requestAnimationFrame(()=>{I(b,"abgacfo")})} +function ib(a){window.clearTimeout(a.g.m);a.g.m=null;a.g.o&&a.g.h&&(a.g.o.style.display="block",a.g.h.style.display="none")} +class lb{constructor(a,b){this.g=a;this.h=b;this.g.S||(this.j=!1,this.i=null,!this.g.A||this.g.adbadgeEnabled||this.g.K?eb(this):(a={display:"none"},b={width:"15px",height:"15px"},this.g.isMobileDevice?(M(this.g.o,a),M(this.g.h,a),M(this.g.u,b),M(this.g.s,b)):M(this.g.s,a)),fb(this),this.g.enableNativeJakeUi&&I(this.g.F,"abgnac"),this.g.isDelegateAttributionActive?(I(document.body,"goog_delegate_active"),I(document.body,"jaa")):(!this.g.isMutableImpression&&this.g.l&&ta(this.g.l),setTimeout(()=>{I(document.body, +"jar")},this.g.I?750:100)),this.g.w&&I(document.body,"goog_delegate_disabled"),this.g.G&&H.addEventListener("load",()=>this.h()))}preventDefault(a){if(this.g.h&&"block"==this.g.h.style.display&&500>Date.now()-this.g.C)a.preventDefault?a.preventDefault():a.returnValue=!1;else if(this.g.openAttributionInline){var b=this.g.j.getAttribute("href");window.adSlot?window.adSlot.openAttribution(b)&&(a.preventDefault?a.preventDefault():a.returnValue=!1):window.openAttribution&&(window.openAttribution(b),a.preventDefault? +a.preventDefault():a.returnValue=!1)}else this.g.N&&(b=this.g.j.getAttribute("href"),window.adSlot?window.adSlot.openSystemBrowser(b)&&(a.preventDefault?a.preventDefault():a.returnValue=!1):window.openSystemBrowser&&(window.openSystemBrowser(b),a.preventDefault?a.preventDefault():a.returnValue=!1))}};function mb(a){if(!a.g&&(a.g=!0,H.goog_delegate_deferred_token=void 0,a.h)){var b=a.i;a=a.h;if(!a)throw Error("bad attrdata");a=new ya(a);new b(a)}}class nb{constructor(a,b){if(!a)throw Error("bad ctor");this.i=a;this.h=b;this.g=!1;C("goog_delegate_deferred")?void 0!==H.goog_delegate_deferred_token?mb(this):(a=()=>{mb(this)},H.goog_delegate_deferred_token=a,setTimeout(a,5E3)):mb(this)}};var ob=()=>{a:{if(Ba)try{var a=H.google_cafe_host||H.top.google_cafe_host;if(a){var b=a;break a}}catch(c){}b="pagead2.googlesyndication.com"}a=Da?"https":"http";if("relative"===b)return"/pagead/js/r20200428/r20110914/abg_survey.js";a||(a=Ea?"https":"http");l.location&&"https:"==l.location.protocol&&"http"==a&&(a="https");return[a,"://",b,"/pagead/js/r20200428/r20110914/abg_survey.js"].join("")};var pb=(a=[])=>{l.google_logging_queue||(l.google_logging_queue=[]);l.google_logging_queue.push([11,a])};class qb{constructor(){this.g=new Promise(a=>{this.h=a})}};var rb=class{constructor(){const a=new qb;this.promise=a.g;this.resolve=a.h}};function sb(a,b){a.google_llp||(a.google_llp={});a=a.google_llp;a[5]||(a[5]=new rb,b&&b());return a[5]} +function tb(){var a=window,b=ob();return sb(a,function(){{var c=a.document;const e=c.createElement("script");var d=new q(ia,b);d instanceof q&&d.constructor===q&&d.g===ja?d=d.h:(da(d),d="type_error:TrustedResourceUrl");e.src=d;if(null===n)a:{d=l.document;if((d=d.querySelector&&d.querySelector("script[nonce]"))&&(d=d.nonce||d.getAttribute("nonce"))&&ca.test(d)){n=d;break a}n=""}(d=n)&&e.setAttribute("nonce",d);(c=c.getElementsByTagName("script")[0])&&c.parentNode&&c.parentNode.insertBefore(e,c)}}).promise} +;function ub(a){Za(T,373,()=>{ib(a.h);kb(a.h)});tb().then(b=>{b.createAttributionCard(a.g);a.g.P=b;b.expandAttributionCard()});va()}class vb{constructor(a){this.g=a;this.h=new lb(this.g,W(359,()=>ub(this)))}};E=60;function wb(a){pb([a]);new nb(vb,a)}var X=["buildAttribution"],Y=l;X[0]in Y||"undefined"==typeof Y.execScript||Y.execScript("var "+X[0]);for(var Z;X.length&&(Z=X.shift());)X.length||void 0===wb?Y[Z]&&Y[Z]!==Object.prototype[Z]?Y=Y[Z]:Y=Y[Z]={}:Y[Z]=wb;}).call(this); diff --git a/doc/As65 Assembler_files/ads_data_003/css.css b/doc/As65 Assembler_files/ads_data_003/css.css new file mode 100644 index 0000000..e320031 --- /dev/null +++ b/doc/As65 Assembler_files/ads_data_003/css.css @@ -0,0 +1,126 @@ +/* cyrillic-ext */ +@font-face { + font-family: 'Roboto'; + font-style: normal; + font-weight: 400; + font-display: swap; + src: local('Roboto'), local('Roboto-Regular'), url(https://fonts.gstatic.com/s/roboto/v20/KFOmCnqEu92Fr1Mu72xKOzY.woff2) format('woff2'); + unicode-range: U+0460-052F, U+1C80-1C88, U+20B4, U+2DE0-2DFF, U+A640-A69F, U+FE2E-FE2F; +} +/* cyrillic */ +@font-face { + font-family: 'Roboto'; + font-style: normal; + font-weight: 400; + font-display: swap; + src: local('Roboto'), local('Roboto-Regular'), url(https://fonts.gstatic.com/s/roboto/v20/KFOmCnqEu92Fr1Mu5mxKOzY.woff2) format('woff2'); + unicode-range: U+0400-045F, U+0490-0491, U+04B0-04B1, U+2116; +} +/* greek-ext */ +@font-face { + font-family: 'Roboto'; + font-style: normal; + font-weight: 400; + font-display: swap; + src: local('Roboto'), local('Roboto-Regular'), url(https://fonts.gstatic.com/s/roboto/v20/KFOmCnqEu92Fr1Mu7mxKOzY.woff2) format('woff2'); + unicode-range: U+1F00-1FFF; +} +/* greek */ +@font-face { + font-family: 'Roboto'; + font-style: normal; + font-weight: 400; + font-display: swap; + src: local('Roboto'), local('Roboto-Regular'), url(https://fonts.gstatic.com/s/roboto/v20/KFOmCnqEu92Fr1Mu4WxKOzY.woff2) format('woff2'); + unicode-range: U+0370-03FF; +} +/* vietnamese */ +@font-face { + font-family: 'Roboto'; + font-style: normal; + font-weight: 400; + font-display: swap; + src: local('Roboto'), local('Roboto-Regular'), url(https://fonts.gstatic.com/s/roboto/v20/KFOmCnqEu92Fr1Mu7WxKOzY.woff2) format('woff2'); + unicode-range: U+0102-0103, U+0110-0111, U+0128-0129, U+0168-0169, U+01A0-01A1, U+01AF-01B0, U+1EA0-1EF9, U+20AB; +} +/* latin-ext */ +@font-face { + font-family: 'Roboto'; + font-style: normal; + font-weight: 400; + font-display: swap; + src: local('Roboto'), local('Roboto-Regular'), url(https://fonts.gstatic.com/s/roboto/v20/KFOmCnqEu92Fr1Mu7GxKOzY.woff2) format('woff2'); + unicode-range: U+0100-024F, U+0259, U+1E00-1EFF, U+2020, U+20A0-20AB, U+20AD-20CF, U+2113, U+2C60-2C7F, U+A720-A7FF; +} +/* latin */ +@font-face { + font-family: 'Roboto'; + font-style: normal; + font-weight: 400; + font-display: swap; + src: local('Roboto'), local('Roboto-Regular'), url(https://fonts.gstatic.com/s/roboto/v20/KFOmCnqEu92Fr1Mu4mxK.woff2) format('woff2'); + unicode-range: U+0000-00FF, U+0131, U+0152-0153, U+02BB-02BC, U+02C6, U+02DA, U+02DC, U+2000-206F, U+2074, U+20AC, U+2122, U+2191, U+2193, U+2212, U+2215, U+FEFF, U+FFFD; +} +/* cyrillic-ext */ +@font-face { + font-family: 'Roboto'; + font-style: normal; + font-weight: 700; + font-display: swap; + src: local('Roboto Bold'), local('Roboto-Bold'), url(https://fonts.gstatic.com/s/roboto/v20/KFOlCnqEu92Fr1MmWUlfCRc4EsA.woff2) format('woff2'); + unicode-range: U+0460-052F, U+1C80-1C88, U+20B4, U+2DE0-2DFF, U+A640-A69F, U+FE2E-FE2F; +} +/* cyrillic */ +@font-face { + font-family: 'Roboto'; + font-style: normal; + font-weight: 700; + font-display: swap; + src: local('Roboto Bold'), local('Roboto-Bold'), url(https://fonts.gstatic.com/s/roboto/v20/KFOlCnqEu92Fr1MmWUlfABc4EsA.woff2) format('woff2'); + unicode-range: U+0400-045F, U+0490-0491, U+04B0-04B1, U+2116; +} +/* greek-ext */ +@font-face { + font-family: 'Roboto'; + font-style: normal; + font-weight: 700; + font-display: swap; + src: local('Roboto Bold'), local('Roboto-Bold'), url(https://fonts.gstatic.com/s/roboto/v20/KFOlCnqEu92Fr1MmWUlfCBc4EsA.woff2) format('woff2'); + unicode-range: U+1F00-1FFF; +} +/* greek */ +@font-face { + font-family: 'Roboto'; + font-style: normal; + font-weight: 700; + font-display: swap; + src: local('Roboto Bold'), local('Roboto-Bold'), url(https://fonts.gstatic.com/s/roboto/v20/KFOlCnqEu92Fr1MmWUlfBxc4EsA.woff2) format('woff2'); + unicode-range: U+0370-03FF; +} +/* vietnamese */ +@font-face { + font-family: 'Roboto'; + font-style: normal; + font-weight: 700; + font-display: swap; + src: local('Roboto Bold'), local('Roboto-Bold'), url(https://fonts.gstatic.com/s/roboto/v20/KFOlCnqEu92Fr1MmWUlfCxc4EsA.woff2) format('woff2'); + unicode-range: U+0102-0103, U+0110-0111, U+0128-0129, U+0168-0169, U+01A0-01A1, U+01AF-01B0, U+1EA0-1EF9, U+20AB; +} +/* latin-ext */ +@font-face { + font-family: 'Roboto'; + font-style: normal; + font-weight: 700; + font-display: swap; + src: local('Roboto Bold'), local('Roboto-Bold'), url(https://fonts.gstatic.com/s/roboto/v20/KFOlCnqEu92Fr1MmWUlfChc4EsA.woff2) format('woff2'); + unicode-range: U+0100-024F, U+0259, U+1E00-1EFF, U+2020, U+20A0-20AB, U+20AD-20CF, U+2113, U+2C60-2C7F, U+A720-A7FF; +} +/* latin */ +@font-face { + font-family: 'Roboto'; + font-style: normal; + font-weight: 700; + font-display: swap; + src: local('Roboto Bold'), local('Roboto-Bold'), url(https://fonts.gstatic.com/s/roboto/v20/KFOlCnqEu92Fr1MmWUlfBBc4.woff2) format('woff2'); + unicode-range: U+0000-00FF, U+0131, U+0152-0153, U+02BB-02BC, U+02C6, U+02DA, U+02DC, U+2000-206F, U+2074, U+20AC, U+2122, U+2191, U+2193, U+2212, U+2215, U+FEFF, U+FFFD; +} diff --git a/doc/As65 Assembler_files/ads_data_003/osd_listener.js b/doc/As65 Assembler_files/ads_data_003/osd_listener.js new file mode 100644 index 0000000..166395c --- /dev/null +++ b/doc/As65 Assembler_files/ads_data_003/osd_listener.js @@ -0,0 +1,6 @@ +(function(window,document){/* + + Copyright The Closure Library Authors. + SPDX-License-Identifier: Apache-2.0 +*/ +var l;function aa(a){var b=0;return function(){return bb?-c:c}});var t=this||self;function pa(a,b){a=a.split(".");var c=t;a[0]in c||"undefined"==typeof c.execScript||c.execScript("var "+a[0]);for(var d;a.length&&(d=a.shift());)a.length||void 0===b?c[d]&&c[d]!==Object.prototype[d]?c=c[d]:c=c[d]={}:c[d]=b}function qa(){}function u(a){a.Ka=void 0;a.g=function(){return a.Ka?a.Ka:a.Ka=new a}}function ra(a){var b=typeof a;if("object"==b)if(a){if(a instanceof Array)return"array";if(a instanceof Object)return b;var c=Object.prototype.toString.call(a);if("[object Window]"==c)return"object";if("[object Array]"==c||"number"==typeof a.length&&"undefined"!=typeof a.splice&&"undefined"!=typeof a.propertyIsEnumerable&&!a.propertyIsEnumerable("splice"))return"array";if("[object Function]"==c||"undefined"!=typeof a.call&&"undefined"!=typeof a.propertyIsEnumerable&&!a.propertyIsEnumerable("call"))return"function"}else return"null";else if("function"==b&&"undefined"==typeof a.call)return"object";return b}function sa(a){var b=ra(a);return"array"==b||"object"==b&&"number"==typeof a.length}function ta(a,b){var c=Array.prototype.slice.call(arguments,1);return function(){var d=c.slice();d.push.apply(d,arguments);return a.apply(this,d)}}function ua(a,b){function c(){}c.prototype=b.prototype;a.prototype=new c;a.prototype.constructor=a};var va;function wa(a,b){if("string"===typeof a)return"string"!==typeof b||1!=b.length?-1:a.indexOf(b,0);for(var c=0;cb?null:"string"===typeof a?a.charAt(b):a[b]}function w(a,b){return 0<=wa(a,b)}function Ca(a){return Array.prototype.concat.apply([],arguments)}function Da(a){var b=a.length;if(0=arguments.length?Array.prototype.slice.call(a,b):Array.prototype.slice.call(a,b,c)}function Fa(a,b){a.sort(b||Ga)}function Ga(a,b){return a>b?1:ab?1:0};var z;a:{var Va=t.navigator;if(Va){var Wa=Va.userAgent;if(Wa){z=Wa;break a}}z=""}function A(a){return-1!=z.indexOf(a)};function Xa(){return A("Safari")&&!(Ya()||A("Coast")||A("Opera")||A("Edge")||A("Edg/")||A("OPR")||A("Firefox")||A("FxiOS")||A("Silk")||A("Android"))}function Ya(){return(A("Chrome")||A("CriOS"))&&!A("Edge")};function Za(a){var b=Number(a);return 0==b&&/^[\s\xa0]*$/.test(a)?NaN:b}function $a(){return"opacity".replace(/\-([a-z])/g,function(a,b){return b.toUpperCase()})}function ab(a){return String(a).replace(/([A-Z])/g,"-$1").toLowerCase()}function bb(a){return a.replace(/(^|[\s]+)([a-z])/g,function(b,c,d){return c+d.toUpperCase()})};function cb(a){cb[" "](a);return a}cb[" "]=qa;function db(a,b){try{return cb(a[b]),!0}catch(c){}return!1}function eb(a,b){var c=fb;return Object.prototype.hasOwnProperty.call(c,a)?c[a]:c[a]=b(a)};var gb=A("Opera"),B=A("Trident")||A("MSIE"),hb=A("Edge"),ib=A("Gecko")&&!(y(z,"WebKit")&&!A("Edge"))&&!(A("Trident")||A("MSIE"))&&!A("Edge"),jb=y(z,"WebKit")&&!A("Edge"),kb=jb&&A("Mobile");function lb(){var a=t.document;return a?a.documentMode:void 0}var mb;a:{var nb="",ob=function(){var a=z;if(ib)return/rv:([^\);]+)(\)|;)/.exec(a);if(hb)return/Edge\/([\d\.]+)/.exec(a);if(B)return/\b(?:MSIE|rv)[: ]([^\);]+)(\)|;)/.exec(a);if(jb)return/WebKit\/(\S+)/.exec(a);if(gb)return/(?:Version)[ \/]?(\S+)/.exec(a)}();ob&&(nb=ob?ob[1]:"");if(B){var pb=lb();if(null!=pb&&pb>parseFloat(nb)){mb=String(pb);break a}}mb=nb}var qb=mb,fb={};function rb(a){return eb(a,function(){for(var b=0,c=Sa(String(qb)).split("."),d=Sa(String(a)).split("."),e=Math.max(c.length,d.length),f=0;0==b&&f>>=7;a.a.push(b)}function Bb(a,b){a.a.push(b>>>0&255);a.a.push(b>>>8&255);a.a.push(b>>>16&255);a.a.push(b>>>24&255)};function Cb(){this.b=[];this.a=new zb}function Db(a,b,c){if(null!=c){Ab(a.a,8*b);a=a.a;var d=c;c=0>d;d=Math.abs(d);b=d>>>0;d=Math.floor((d-b)/4294967296);d>>>=0;c&&(d=~d>>>0,b=(~b>>>0)+1,4294967295>>7|b<<25)>>>0,b>>>=7;a.a.push(c)}};function Eb(){}var Fb="function"==typeof Uint8Array,Gb=[];function Hb(a){var b=a.c+a.f;a.a[b]||(a.b=a.a[b]={})}function Ib(a,b){if(be?encodeURIComponent(jd(a,b,c,d,e+1)):"...";return encodeURIComponent(String(a))}function ld(a,b,c,d){a.a.push(b);a.b[b]=id(c,d)}function md(a,b,c){b=b+"//pagead2.googlesyndication.com"+c;var d=nd(a)-c.length;if(0>d)return"";a.a.sort(function(n,p){return n-p});c=null;for(var e="",f=0;f=k.length){d-=k.length;b+=k;e=a.c;break}a.f&&(e=d,k[e-1]==a.c&&--e,b+=k.substr(0,e),e=a.c,d=0);c=null==c?g:c}}a="";null!=c&&(a=e+"trn="+c);return b+a}function nd(a){var b=1,c;for(c in a.b)b=c.length>b?c.length:b;return 3997-b-a.c.length-1};function od(){this.b=new cd;this.a=ad()?new $c:new O}od.prototype.setInterval=function(a,b){return D.setInterval(a,b)};od.prototype.clearInterval=function(a){D.clearInterval(a)};od.prototype.setTimeout=function(a,b){return D.setTimeout(a,b)};od.prototype.clearTimeout=function(a){D.clearTimeout(a)};function pd(a){P();var b=I()||D;oc(b,a,!1)}u(od);function qd(){}function P(){var a=qd.g();if(!a.a){if(!D)throw Error("Context has not been set and window is undefined.");a.a=od.g()}return a.a}u(qd);function rd(a){this.h=null;a||(a=[]);this.f=-1;this.a=a;a:{if(a=this.a.length){--a;var b=this.a[a];if(!(null===b||"object"!=typeof b||Array.isArray(b)||Fb&&b instanceof Uint8Array)){this.c=a- -1;this.b=b;break a}}this.c=Number.MAX_VALUE}}ua(rd,Eb);function sd(a){this.f=a;this.a=-1;this.b=this.c=0}function td(a,b){return function(c){for(var d=[],e=0;eMath.random())}function Hd(a){a&&S&&Fd()&&(S.clearMarks("goog_"+a.label+"_"+a.uniqueId+"_start"),S.clearMarks("goog_"+a.label+"_"+a.uniqueId+"_end"))}Gd.prototype.start=function(a,b){if(!this.a)return null;var c=Cd()||Bd();a=new Dd(a,b,c);b="goog_"+a.label+"_"+a.uniqueId+"_start";S&&Fd()&&S.mark(b);return a};function Id(){var a=Jd;this.i=Kd;this.h="jserror";this.f=!0;this.c=null;this.j=this.a;this.b=void 0===a?null:a}function Ld(a,b,c){return td(vd().a,function(){try{if(a.b&&a.b.a){var d=a.b.start(b.toString(),3);var e=c();var f=a.b,g=d;if(f.a&&"number"===typeof g.value){var h=Cd()||Bd();g.duration=h-g.value;var m="goog_"+g.label+"_"+g.uniqueId+"_end";S&&Fd()&&S.mark(m);!f.a||2048b&&(d=b);for(b=0;bc.height?m>n?(d=m,e=k):(d=n,e=p):mc++;){if(a===b)return!0;try{a:{var d=void 0;if(Sb&&!(B&&rb("9")&&!rb("10")&&t.SVGElement&&a instanceof t.SVGElement)&&(d=a.parentElement)){var e=d;break a}d=a.parentNode;var f=typeof d;e=("object"==f&&null!=d||"function"==f)&&1==d.nodeType?d:null}if(a=e||a){var g=G(a),h=g&&Xb(g),m=h&&h.frameElement;m&&(a=m)}}catch(k){break}}return!1}function Be(a,b,c){if(!a||!b)return!1;b=mc(lc(a),-b.left,-b.top);a=(b.left+b.right)/2;b=(b.top+b.bottom)/2;var d=I();dc(d.top)&&d.top&&d.top.document&&(d=d.top);if(!$d(d))return!1;a=d.document.elementFromPoint(a,b);if(!a)return!1;b=(b=(b=G(c))&&b.defaultView&&b.defaultView.frameElement)&&Ae(b,a);d=a===c;a=!d&&a&&$b(a,function(e){return e===c});return!(b||d||a)}function Ce(a,b,c,d){return W.g().h?!1:0>=jc(a)||0>=kc(a)?!0:c&&d?Rd(208,function(){return Be(a,b,c)}):!1};function De(a,b,c){var d=new H(0,0,0,0);this.time=a;this.volume=null;this.c=b;this.a=d;this.b=c};function Ee(a,b,c,d,e,f,g){this.j=a;this.i=b;this.c=c;this.a=d;this.h=e;this.b=f;this.f=g};function Fe(a){this.c=a;this.b=0;this.a=null}Fe.prototype.cancel=function(){P().clearTimeout(this.a);this.a=null};function Ge(a){var b=P();a.a=b.setTimeout(td(vd().a,Sd(143,function(){a.b++;a.c.sb()})),Xd())};function He(a,b,c){this.o=a;this.H=void 0===c?"na":c;this.f=[];this.A=!1;this.c=new De(-1,!0,this);this.a=this;this.h=b;this.m=this.C=this.l=!1;this.F="uk";this.G=!1;this.i=!0}l=He.prototype;l.Ra=function(){return this.ka()};l.ka=function(){return!1};l.sa=function(){return this.A=!0};l.aa=function(){return this.a.F};l.ga=function(){return this.a.m};function Ie(a,b){a.m||(a.m=!0,a.F=b,a.h=0,a.ma(),a.a!=a||Je(a))}l.u=function(){return this.a.H};l.K=function(){return this.a.cb()};l.cb=function(){return{}};l.M=function(){return this.a.h};function Ke(a,b){w(a.f,b)||(a.f.push(b),b.fa(a.a),b.Y(a.c),b.ca()&&(a.l=!0))}function Le(a,b){var c=a.f,d=wa(c,b);0<=d&&Array.prototype.splice.call(c,d,1);a.l&&b.ca()&&Me(a)}l.Oa=function(){var a=W.g();a.a=wc(!0,this.o,a.i)};l.Qa=function(){ue(W.g(),this.o)};l.Pa=function(){ve(W.g(),this.o)};l.pb=function(){var a=W.g();a.b=wc(!1,this.o,a.i)};l.eb=function(){return this.c.a};function Ne(a){a=a.a;a.Qa();a.Oa();a.pb();a.Pa();a.c.a=a.eb()}l.sb=function(){};function Me(a){a.l=a.f.length?Aa(a.f,function(b){return b.ca()}):!1}l.ma=function(){};function Oe(a){var b=Da(a.f);v(b,function(c){c.Y(a.c)})}function Je(a){var b=Da(a.f);v(b,function(c){c.fa(a.a)});a.a!=a||Oe(a)}l.fa=function(a){var b=this.a,c=a.M();this.a=c>=this.h?a:this;b!==this.a?(this.a==this||1==c&&0!=this.h||this.ma(),this.i=this.a.i,Je(this)):this.i!==this.a.i&&(this.i=this.a.i,Je(this))};l.Y=function(a){if(a.b===this.a){var b;if(!(b=this.C)){b=this.c;var c=this.l;if(c=a&&(void 0===c||!c||b.volume==a.volume)&&b.c==a.c)b=b.a,c=a.a,c=b==c?!0:b&&c?b.top==c.top&&b.right==c.right&&b.bottom==c.bottom&&b.left==c.left:!1;b=!c}this.c=a;b&&Oe(this)}};function Pe(a,b){a.h!==b&&(a.a!=a&&b>a.a.h&&(a.a=a,Je(a)),a.h=b)}l.ca=function(){return this.l};l.L=function(){this.G=!0};l.ta=function(){return this.G};function Qe(a,b,c,d){this.c=a;this.a=new H(0,0,0,0);this.l=new H(0,0,0,0);this.b=b;this.B=c;this.C=d;this.A=!1;this.timestamp=-1;this.h=new Ee(b.c,this.a,new H(0,0,0,0),0,0,U(),0)}l=Qe.prototype;l.ob=function(){return!0};l.ja=function(){};l.Ia=function(){if(this.c){var a=this.c,b=this.b.a.o;try{try{var c=je(a.getBoundingClientRect())}catch(k){c=new H(0,0,0,0)}var d=c.right-c.left,e=c.bottom-c.top,f=tc(a,b),g=f.a,h=f.b;var m=new H(Math.round(h),Math.round(g+d),Math.round(h+e),Math.round(g))}catch(k){m=lc(xe)}this.a=m}};l.Xa=function(){this.l=this.b.c.a};l.$=function(){this.Ia();this.h=new Ee(this.b.c,this.a,this.h.c,this.h.a,this.h.h,U(),this.h.f)};l.L=function(){this.ta()||(Le(this.b,this),this.ja(),this.A=!0)};l.ta=function(){return this.A};l.K=function(){return this.b.K()};l.M=function(){return this.b.M()};l.aa=function(){return this.b.aa()};l.ga=function(){return this.b.ga()};l.fa=function(){};l.Y=function(){this.$()};l.ca=function(){return this.C};function Re(a){this.h=!1;this.a=a;this.f=qa}l=Re.prototype;l.M=function(){return this.a.M()};l.aa=function(){return this.a.aa()};l.ga=function(){return this.a.ga()};l.create=function(a,b,c){var d=null;this.a&&(d=this.Ja(a,b,c),Ke(this.a,d));return d};l.Ma=function(){return this.ha()};l.ha=function(){return!1};l.mb=function(a){return this.a.sa()?(Ke(this.a,this),this.f=a,!0):!1};l.fa=function(a){0==a.M()&&this.f(a.aa(),this)};l.Y=function(){};l.ca=function(){return!1};l.L=function(){this.h=!0};l.ta=function(){return this.h};l.K=function(){return{}};function Se(a,b,c){this.c=void 0===c?0:c;this.b=a;this.a=null==b?"":b}function Te(a){switch(Math.trunc(a.c)){case -16:return-16;case -8:return-8;case 0:return 0;case 8:return 8;case 16:return 16;default:return 16}}function Ue(a,b){return a.cb.c?!1:a.bb.b?!1:typeof a.atypeof b.a?!1:a.a=h;h=!(0=h)||d;jf(a.b[f],g&&m,e,!g||h)}}function nf(a,b,c){a=ya(a.b,function(d){return b(d)});return c?a:qf(a)}function qf(a){return ya(a,function(b,c,d){return 0=(this.ia()?.3:.5),a.b=Math.max(a.b,e.D),pf(a.f,e.f,c.f,e.c,f,d),pf(a.a,e.D,c.D,e.c,f,d),d=d||c.a!=e.a?c.isVisible()&&e.isVisible():c.isVisible(),c=!e.isVisible()||e.c,jf(a.c,d,f,c),this.G=b,0=a.length)throw Bf;if(b in a)return a[b++];b++}};return c}throw Error("Not implemented");}function Ef(a,b){if(sa(a))try{v(a,b,void 0)}catch(c){if(c!==Bf)throw c;}else{a=Df(a);try{for(;;)b.call(void 0,a.next(),void 0,a)}catch(c){if(c!==Bf)throw c;}}}function Ff(a,b){var c=1;Ef(a,function(d){c=b.call(void 0,c,d)});return c}function Gf(a,b){var c=Df(a);a=new Cf;a.next=function(){var d=c.next();if(b.call(void 0,d,void 0,c))return d;throw Bf;};return a}function Hf(a){var b=Df(a);a=new Cf;var c=100;a.next=function(){if(0=a.bottom||a.left>=a.right?new H(0,0,0,0):a;a=this.b.c;var c=0,d=0,e=0;0<(this.a.bottom-this.a.top)*(this.a.right-this.a.left)&&(this.hb(b)?b=new H(0,0,0,0):(c=W.g().m,e=new H(0,c.height,c.width,0),c=ye(b,this.a),d=ye(b,W.g().a),e=ye(b,e)));b=b.top>=b.bottom||b.left>=b.right?new H(0,0,0,0):mc(b,-this.a.left,-this.a.top);we()||(d=c=0);this.h=new Ee(a,this.a,b,c,d,this.timestamp,e)};Uf.prototype.u=function(){return this.b.u()};function Vf(a){var b=[];Wf(new Xf,a,b);return b.join("")}function Xf(){}function Wf(a,b,c){if(null==b)c.push("null");else{if("object"==typeof b){if(Array.isArray(b)){var d=b;b=d.length;c.push("[");for(var e="",f=0;fc.time?b:c},a[0])}l.Ia=function(){};l.hb=function(){return!1};l.Xa=function(){};l.K=function(){var a={};return Object.assign(this.b.K(),(a.niot_obs=this.s,a.niot_cbk=this.m,a))};var pg={threshold:[0,.3,.5,.75,1]};function qg(a,b,c,d){mg.call(this,a,b,c,d);this.i=this.j=this.f=null}r(qg,mg);qg.prototype.u=function(){return"nio"};qg.prototype.ja=function(){if(this.f&&this.c)try{this.f.unobserve(this.c),this.j?(this.j.unobserve(this.c),this.j=null):this.i&&(this.i.disconnect(),this.i=null)}catch(a){}};function rg(a){return a.f&&a.f.takeRecords?a.f.takeRecords():[]}qg.prototype.w=function(){var a=this;if(!this.c)return!1;var b=this.c,c=this.b.a.o,d=vd().a;this.f=new c.IntersectionObserver(td(d,function(e){return ng(a,e)}),pg);d=td(d,function(){a.f.unobserve(b);a.f.observe(b);ng(a,rg(a))});c.ResizeObserver?(this.j=new c.ResizeObserver(d),this.j.observe(b)):c.MutationObserver&&(this.i=new t.MutationObserver(d),this.i.observe(b,{attributes:!0,childList:!0,characterData:!0,subtree:!0}));this.f.observe(b);ng(this,rg(this));return!0};qg.prototype.$=function(){var a=rg(this);0e?1:0)?-e:e;if(0===e)yb=0<1/e?0:2147483648,xb=0;else if(isNaN(e))yb=2147483647,xb=4294967295;else if(1.7976931348623157E308>>0,xb=0;else if(2.2250738585072014E-308>e)e/=Math.pow(2,-1074),yb=(c<<31|e/4294967296)>>>0,xb=e>>>0;else{f=e;d=0;if(2<=f)for(;2<=f&&1023>d;)d++,f/=2;else for(;1>f&&-1022>>0;xb=4503599627370496*e>>>0}Bb(p,xb);Bb(p,yb)}p=Jb(k,2);0!==p&&null!=p&&Db(n,2,p);p=Jb(k,3);0!==p&&null!=p&&Db(n,3,p);p=Jb(k,4);0!==p&&null!=p&&Db(n,4,p);p=Jb(k,5);if(0!==p&&null!=p&&null!=p)if(Ab(n.a,40),k=n.a,0<=p)Ab(k,p);else{for(c=0;9>c;c++)k.a.push(p&127|128),p>>=7;k.a.push(1)}k=new Uint8Array(n.a.length());c=n.b;d=c.length;for(e=p=0;ec;c++)for(d=n.concat(p[c].split("")),vb[c]=d,e=0;e>2,g=(g&3)<<4|h>>4,h=(h&15)<<2|f>>6,f&=63,d||(f=64,c||(h=64)),n.push(q[e],q[g],q[h]||"",q[f]||"");q=(b.pf=n.join(""),b)}else q={};x(a,q);return a}function Cg(){v(gg(),function(a){a.b.a&&tg.g()})}function zg(a){"osd"==a.h&&v(hg.a,function(b){var c={};Mf(b,0,(c.r=void 0,c))})}function Ag(a,b){a=a.l;Wd&&(a+=b-Vd);return a}function Dg(a){return(a=a.match(/[&\?;]adf=([0-9]+)/))&&2==a.length?parseInt(a[1],10):0}function Eg(){var a=Y;var b=void 0===b?function(){return{}}:b;T.h="av-js";Kd.a=.01;Qd([function(c){var d=Q.g(),e={};x(c,(e.bin=d.b,e.type="error",e),Kc(d.a),Bg(a,D),b());if(d=bf())e={},x(c,(e.v=encodeURIComponent(d),e))}])}function Fg(a){var b=new Gg;switch(a){case 0:case 5:return[];default:return a=4===Q.g().b,[new cg(b),new eg(b),new dg(b)].concat(ca(a?[]:[new ag]))}}u(ug);var Y=ug.g();function Gg(){}function bg(a,b){b=b||{};var c=void 0===b.Ua?{}:b.Ua;b=void 0===b.La?{}:b.La;var d=b.r,e=c[0],f=Bg(Y,I(),!1),g={};x(g,f,c);c={};var h=g;h=void 0===h?{}:h;g={};var m=W.g();f=Kc(a.i);var k=m.j,n=uf(a);f.p=[n.top+k.b,n.left+k.a,n.bottom+k.b,n.right+k.a];k=a.c;f.tos=mf(k.a);f.mtos=of(k.a);f.mcvt=k.c.a;f.rs=a.X;(n=5==a.X)||(f.ht=a.Da);0<=a.oa&&(f.tfs=a.oa,f.tls=a.qb);f.mc=ge(k.b);f.lte=ge(a.U);f.bas=a.bb;f.bac=a.J;m.h&&(f["if"]=a.F?0:1);f.met=a.b.c;n&&a.s&&(f.req=encodeURIComponent(a.s).substring(0,100));a.ia()&&(f.la="1");a.Ea&&(f.pa="1");f.avms=a.a?a.a.u():"ns";a.a&&x(f,a.a.K());0!=a.h&&(f.md=a.h);f.btr=null!=a.m&&""!=a.m?1:0;f.lm=a.T;x(f,Rf(a));h&&x(f,h);f.adk=a.l;a.lb&&a.Ca&&(f.adf=a.Ca);h=a.F;m=Q.g();!d&&h&&m.f&&(d=m.f);d&&(f.r=d);0===a.H&&(f.invis=1);d=af(f).join("&");g[3]=d;g[11]=h;g[29]=Q.g().b;g[0]=e;g[7]=a.f.D;g[9]=le(a.qa);g[28]=a.X;g[32]=a.a?a.a.u():"ns";g[5]=sf(a.c)&&4!=a.T;g[13]=of(a.c.a).join(",");g[18]=0==ze(uf(a));null!=a.Z&&(g[20]=a.Z.b,g[21]=a.Z.a);e=W.g();null!=e.b&&(g[22]=jc(e.b),g[23]=kc(e.b));null!=e.a&&(g[30]=jc(e.a),g[31]=kc(e.a),g[38]=le(e.a));d=e.j;f=uf(a);g[37]=le(new H(f.top+d.b,f.right+d.a,f.bottom+d.b,f.left+d.a));e.c&&(e=e.c,g[39]=e.width+"-"+e.height);-1!=a.H&&(g[25]=a.H);de(new Yc(a.l,a.P),g);x(c,g,b);b=a.b.a;a=a.za;try{var p=ee(c);ne(b,p,a)}catch(q){}return!0};function Hg(a,b,c,d){mg.call(this,a,b,c,d);this.f=function(){return null}}r(Hg,mg);Hg.prototype.u=function(){return"aio"};Hg.prototype.ja=function(){if(this.f)try{this.f()}catch(a){}};Hg.prototype.w=function(){var a=this;if(!this.c)return!1;this.f=nc(this.b.a.o).observeIntersection(td(vd().a,function(b){return ng(a,b)}));return!0};function Ig(a){a=void 0===a?D:a;Re.call(this,new He(a,2))}r(Ig,Re);Ig.prototype.u=function(){return"aio"};Ig.prototype.Ma=function(){return W.g().h&&this.ha()};Ig.prototype.ha=function(){var a;if(a=!W.g().f)a=nc(this.a.a.o),a=!(!a||!a.observeIntersection);return a};Ig.prototype.Ja=function(a,b,c){return new Hg(a,this.a,b,c)};function Jg(){He.call(this,D,2,"iem")}r(Jg,He);l=Jg.prototype;l.eb=function(){function a(q,R){return!!b.o.document.elementFromPoint(q,R)}var b=this,c=new H(0,this.o.innerWidth||this.o.width,this.o.innerHeight||this.o.height,0),d=Wb(document),e=Math.floor(c.left-d.a),f=Math.floor(c.top-d.b),g=Math.floor(c.right-d.a),h=Math.floor(c.bottom-d.b);c=a(e,f);d=a(g,h);if(c&&d)return new H(f,g,h,e);var m=a(g,f),k=a(e,h);if(c)h=Z(f,h,function(q){return a(e,q)}),g=Z(e,g,function(q){return a(q,f)});else if(m)h=Z(f,h,function(q){return a(g,q)}),e=Z(g,e,function(q){return a(q,f)});else if(k)f=Z(h,f,function(q){return a(e,q)}),g=Z(e,g,function(q){return a(q,h)});else if(d)f=Z(h,f,function(q){return a(g,q)}),e=Z(g,e,function(q){return a(q,h)});else{var n=Math.floor((e+g)/2),p=Math.floor((f+h)/2);if(!a(n,p))return new H(0,0,0,0);f=Z(p,f,function(q){return a(n,q)});h=Z(p,h,function(q){return a(n,q)});e=Z(n,e,function(q){return a(q,p)});g=Z(n,g,function(q){return a(q,p)})}return new H(f,g,h,e)};function Z(a,b,c){if(c(b))return b;for(var d=15;d--;){var e=Math.floor((a+b)/2);if(e==a||e==b)break;c(e)?a=e:b=e}return a}l.ka=function(){return W.g().h&&B&&rb(8)&&$d(this.o)};l.Oa=function(){};l.Qa=function(){};l.Pa=function(){};l.pb=function(){};u(Jg);function Kg(){He.call(this,D,1,"osd");this.b=null;this.B=[];this.I=this.s=this.j=this.w=0;this.C=!0}r(Kg,He);l=Kg.prototype;l.cb=function(){var a={};return a.exg=1,a};l.Ab=function(a){w(this.B,a)||this.B.push(a)};function Lg(a){var b=0;a=a.o;try{if(a&&a.Goog_AdSense_getAdAdapterInstance)return a}catch(c){}for(;a&&5>b;){try{if(a.google_osd_static_frame)return a.google_osd_static_frame}catch(c){}try{if(a.aswift_0&&a.aswift_0.google_osd_static_frame)return a.aswift_0.google_osd_static_frame}catch(c){}b++;a=a!=a.parent?a.parent:null}return null}function Mg(a,b){var c={};de(Q.g().c,c);c[0]="goog_request_monitoring";c[6]=4;c[16]=!1;c[19]=Q.g().h;a.b&&Ng(a.b,c);try{var d=ee(c);b.postMessage(d,"*")}catch(e){}}function Og(a){++a.s;if(2==a.w)Pg(a);else{if(10=h)){var m=Number(g.substr(0,h));g=g.substr(h+1);switch(m){case 36:case 26:case 15:case 8:case 11:case 16:case 5:case 18:g="true"==g;break;case 4:case 33:case 6:case 25:case 28:case 29:case 24:case 31:case 30:case 23:case 22:case 7:case 21:case 20:g=Number(g);break;case 19:case 3:if("function"==ra(decodeURIComponent))try{g=decodeURIComponent(g)}catch(n){throw Error("Error: URI malformed: "+g);}}e[m]=g}}e=e[0]?e:null}if(d=e)d=new Yc(e[4],e[12]),f=Q.g().c,d=f.a||d.a?f.a==d.a:f.b||d.b?f.b==d.b:!1;if(d&&(d=e[29],f=e[0],w(["goog_acknowledge_monitoring","goog_get_mode","goog_update_data","goog_image_request","goog_adspeed"],f))){Qg(a,e);if("goog_get_mode"==f&&c.source){m={};de(Q.g().c,m);m[0]="goog_provide_mode";m[6]=4;m[16]=!1;m[19]=Q.g().h;a.b&&Ng(a.b,m);try{var k=ee(m);c.source.postMessage(k,c.origin);Rg(a,k)}catch(n){T.a(406,n,void 0,void 0)}}if("goog_get_mode"==f||"goog_acknowledge_monitoring"==f)a.b&&(a.b.V=e[28]),a.w=2,Pg(a);if(c=e[32])a.H=c;if(a.b||a.f.length){if(4!=d){m=e[0];k=!1;f=W.g();c=a.c.a;"goog_acknowledge_monitoring"==m&&((void 0!==e[36]?e[36]:!e[8])?Pe(a,2):Pe(a,0),Je(a));e[37]&&(m=me(e[37]))&&(k=!0,f.j=new E(m.left,m.top));if(e[38]){if(m=me(e[38]))k=!0,f.a=m}else isNaN(e[30])||isNaN(e[31])||(f.a||(f.a=new H(0,0,0,0)),k=!0,f.a.right=f.a.left+e[30],f.a.bottom=f.a.top+e[31]);e[9]&&(k=!0,m=me(e[9]))&&(c=m,f.l=m);e[39]&&((m=e[39])?(m=m.split("-"),m=2==m.length?new F(Za(m[0]),Za(m[1])):null):m=null,m&&(f.c=m));k&&(k=U(),f=we(),k=new De(k,f,a),k.a=c,a.Y(k))}c=pe(e[3]).r;if(4==d){f=e[0];d=100*e[25];"number"!==typeof d||isNaN(d)||a.b&&(window.document["4CGeArbVQ"]=d|0);void 0!=e[18]&&a.b&&(a.b.U=e[18]);d=e[7];void 0!=d&&0=e}}); +oa("Array.prototype.find",function(a){return a?a:function(b,c){a:{var d=this;d instanceof String&&(d=String(d));for(var e=d.length,f=0;f>>0),Ba=0;function Ca(a,b,c){return a.call.apply(a.bind,arguments)} +function Da(a,b,c){if(!a)throw Error();if(2b?null:"string"===typeof a?a.charAt(b):a[b]} +function Na(a,b){a:{for(var c="string"===typeof a?a.split(""):a,d=a.length-1;0<=d;d--)if(d in c&&b.call(void 0,c[d],d,a)){b=d;break a}b=-1}return 0>b?null:"string"===typeof a?a.charAt(b):a[b]}function Oa(a,b){a:if("string"===typeof a)a="string"!==typeof b||1!=b.length?-1:a.indexOf(b,0);else{for(var c=0;c/g,db=/"/g,eb=/'/g,fb=/\x00/g;function gb(a,b){return-1!=a.indexOf(b)} +function hb(a,b){var c=0;a=$a(String(a)).split(".");b=$a(String(b)).split(".");for(var d=Math.max(a.length,b.length),e=0;0==c&&eb?1:0};function jb(a,b){this.c=a===kb&&b||"";this.f=lb}jb.prototype.b=!0;jb.prototype.a=function(){return this.c.toString()};function mb(a){if(a instanceof jb&&a.constructor===jb&&a.f===lb)return a.c;xa(a);return"type_error:SafeUrl"}var nb=/^(?:(?:https?|mailto|ftp):|[^:/?#]*(?:[/?#]|$))/i,lb={},kb={};var ob;a:{var pb=p.navigator;if(pb){var qb=pb.userAgent;if(qb){ob=qb;break a}}ob=""}function t(a){return gb(ob,a)}function rb(a){for(var b=/(\w[\w ]+)\/([^\s]+)\s*(?:\((.*?)\))?/g,c=[],d;d=b.exec(a);)c.push([d[1],d[2],d[3]||void 0]);return c};function sb(){return(t("Chrome")||t("CriOS"))&&!t("Edge")}function tb(){function a(e){e=Ma(e,d);return c[e]||""}var b=ob;if(t("Trident")||t("MSIE"))return ub(b);b=rb(b);var c={};Ha(b,function(e){c[e[0]]=e[1]});var d=Fa(Ua,c);return t("Opera")?a(["Version","Opera"]):t("Edge")?a(["Edge"]):t("Edg/")?a(["Edg"]):sb()?a(["Chrome","CriOS","HeadlessChrome"]):(b=b[2])&&b[1]||""} +function ub(a){var b=/rv: *([\d\.]*)/.exec(a);if(b&&b[1])return b[1];b="";var c=/MSIE +([\d\.]+)/.exec(a);if(c&&c[1])if(a=/Trident\/(\d.\d)/.exec(a),"7.0"==c[1])if(a&&a[1])switch(a[1]){case "4.0":b="8.0";break;case "5.0":b="9.0";break;case "6.0":b="10.0";break;case "7.0":b="11.0"}else b="7.0";else b=c[1];return b};function vb(a,b){a.src=Za(b);(b=ra())&&a.setAttribute("nonce",b)};var wb={"\x00":"\\0","\b":"\\b","\f":"\\f","\n":"\\n","\r":"\\r","\t":"\\t","\x0B":"\\x0B",'"':'\\"',"\\":"\\\\","<":"\\u003C"},xb={"'":"\\'"};function yb(a){return String(a).replace(/\-([a-z])/g,function(b,c){return c.toUpperCase()})};function zb(){return t("iPhone")&&!t("iPod")&&!t("iPad")};function Ab(a){Ab[" "](a);return a}Ab[" "]=va;var Bb=zb()||t("iPod"),Cb=t("Safari")&&!(sb()||t("Coast")||t("Opera")||t("Edge")||t("Edg/")||t("OPR")||t("Firefox")||t("FxiOS")||t("Silk")||t("Android"))&&!(zb()||t("iPad")||t("iPod"));var Db={},Eb=null;function x(){}var Fb="function"==typeof Uint8Array;function y(a,b,c,d){a.a=null;b||(b=[]);a.u=void 0;a.f=-1;a.b=b;a:{if(b=a.b.length){--b;var e=a.b[b];if(!(null===e||"object"!=typeof e||Array.isArray(e)||Fb&&e instanceof Uint8Array)){a.g=b-a.f;a.c=e;break a}}a.g=Number.MAX_VALUE}a.o={};if(c)for(b=0;be;e++){var f=c.concat(d[e].split(""));Db[e]=f;for(var g=0;g> +2;k=(k&3)<<4|m>>4;m=(m&15)<<2|h>>6;h&=63;f||(h=64,e||(m=64));c.push(b[g],b[k],b[m]||"",b[h]||"")}return c.join("")};try{return JSON.stringify(this.b&&Qb(this),Rb)}finally{Uint8Array.prototype.toJSON=a}}:function(){return JSON.stringify(this.b&&Qb(this),Rb)};function Rb(a,b){return"number"!==typeof b||!isNaN(b)&&Infinity!==b&&-Infinity!==b?b:String(b)}function Sb(a,b){return new a(b?JSON.parse(b):null)};function Tb(a){y(this,a,Ub,null)}q(Tb,x);function Vb(a){y(this,a,null,null)}q(Vb,x);var Ub=[2,3];function Wb(a){y(this,a,null,null)}q(Wb,x);function Xb(a){var b=new Wb;return Nb(b,1,a)}function Yb(a,b){return Nb(a,2,b)}function Zb(a,b){return Nb(a,3,b)}function $b(a,b){return Nb(a,4,b)};var ac=document,E=window;var bc={"120x90":!0,"160x90":!0,"180x90":!0,"200x90":!0,"468x15":!0,"728x15":!0};function cc(a,b){if(15==b){if(728<=a)return 728;if(468<=a)return 468}else if(90==b){if(200<=a)return 200;if(180<=a)return 180;if(160<=a)return 160;if(120<=a)return 120}return null};function dc(){this.a=E.document||{cookie:""}} +dc.prototype.set=function(a,b,c){var d=!1;if("object"===typeof c){var e=c.fb;d=c.Wa||!1;var f=c.domain||void 0;var g=c.path||void 0;var h=c.Oa}if(/[;=\s]/.test(a))throw Error('Invalid cookie name "'+a+'"');if(/[;\r\n]/.test(b))throw Error('Invalid cookie value "'+b+'"');void 0===h&&(h=-1);this.a.cookie=a+"="+b+(f?";domain="+f:"")+(g?";path="+g:"")+(0>h?"":0==h?";expires="+(new Date(1970,1,1)).toUTCString():";expires="+(new Date(+new Date+1E3*h)).toUTCString())+(d?";secure":"")+(null!=e?";samesite="+ +e:"")};dc.prototype.get=function(a,b){for(var c=a+"=",d=(this.a.cookie||"").split(";"),e=0,f;ec++&&(!lc(b)||!a(b));)a:{try{var d=b.parent;if(d&&d!=b){b=d;break a}}catch(e){}b=null}}function nc(){var a=p;mc(function(b){a=b;return!1});return a}function oc(a,b){var c=a.createElement("script");vb(c,hc(b));return(a=a.getElementsByTagName("script")[0])&&a.parentNode?(a.parentNode.insertBefore(c,a),c):null} +function pc(a,b){return b.getComputedStyle?b.getComputedStyle(a,null):a.currentStyle}function qc(a,b,c){var d=!1;void 0===c||c||(d=rc());return!d&&!sc()&&(c=Math.random(),c>2)+a.charCodeAt(d)&4294967295;return 0Math.random()}); +function xc(a,b){var c=-1;try{a.localStorage&&(c=parseInt(a.localStorage.getItem(b),10))}catch(d){return null}return 0<=c&&1E3>c?c:null}function yc(a){return sc()?null:Math.floor(1E3*tc(a))}function zc(a,b,c){try{if(a.localStorage)return a.localStorage.setItem(b,c),c}catch(d){}return null}function Ac(a,b){var c=yc(a);return c&&zc(a,b,String(c))?c:null}var rc=Qa(function(){return wc("MSIE")});function wc(a){return gb(ob,a)}var Bc=/^([0-9.]+)px$/,Cc=/^(-?[0-9.]{1,30})$/; +function Dc(a){return Cc.test(a)&&(a=Number(a),!isNaN(a))?a:null}function Ec(a,b){return b?!/^false$/.test(a):/^true$/.test(a)}function G(a){return(a=Bc.exec(a))?+a[1]:null}function Fc(a){a=a&&a.toString&&a.toString();return"string"===typeof a&&gb(a,"[native code]")}var Gc=Qa(function(){return jc()?2:kc()?1:0}); +function Hc(a){var b={display:"none"};a.style.setProperty?F(b,function(c,d){a.style.setProperty(d,c,"important")}):a.style.cssText=Ic(Jc(Kc(a.style.cssText),Lc(b,function(c){return c+" !important"})))}var Jc=Object.assign||function(a,b){for(var c=1;ca;case 12:return(new RegExp(a)).test(e); +case 10:return-1==hb(e,a);case 11:return 1==hb(e,a)}}}}function fd(a,b){return!a||!(!b||!dd(a,b))};function gd(a){y(this,a,hd,null)}q(gd,x);var hd=[4];function id(a){y(this,a,jd,kd)}q(id,x);function ld(a){y(this,a,null,null)}q(ld,x);var jd=[5],kd=[[1,2,3,6,7]];function md(){var a={};this.a=(a[3]={},a[4]={},a[5]={},a)}wa(md);var nd=Ec("false",!1);function od(a,b){switch(b){case 1:return A(a,1,0);case 2:return A(a,2,0);case 3:return A(a,3,0);case 6:return A(a,6,0);default:return null}}function pd(a,b){if(!a)return null;switch(b){case 1:return Lb(a,1);case 7:return A(a,3,"");case 2:return Mb(a,2);case 3:return A(a,3,"");case 6:return z(a,4);default:return null}}var qd=Qa(function(){if(!nd)return{};try{var a=window.sessionStorage&&window.sessionStorage.getItem("GGDFSSK");if(a)return JSON.parse(a)}catch(b){}return{}}); +function rd(a,b,c,d){d=void 0===d?0:d;var e=qd();if(e[a]&&null!=e[a][b])return e[a][b];b=sd(d)[a][b];if(!b)return c;b=new id(b);b=td(b);a=pd(b,a);return null!=a?a:c}function td(a){var b=md.h().a;if(b){var c=Na(C(a,ld,5),function(d){return fd(B(d,Zc,1),b)});if(c)return B(c,gd,2)}return B(a,gd,4)}function ud(){this.a={};this.b=[]}wa(ud);function vd(a,b,c){return!!rd(1,a,void 0===b?!1:b,c)}function wd(a,b,c){b=void 0===b?0:b;a=Number(rd(2,a,b,c));return isNaN(a)?b:a} +function xd(a,b,c){return rd(3,a,void 0===b?"":b,c)}function yd(a,b,c){b=void 0===b?[]:b;return rd(6,a,b,c)}function sd(a){var b={};return ud.h().a[a]||(ud.h().a[a]=(b[1]={},b[2]={},b[3]={},b[6]={},b))}function zd(a,b){var c=sd(b);F(a,function(d,e){return F(d,function(f,g){return c[e][g]=f})})}function Ad(a,b){var c=sd(b);Ha(a,function(d){var e=Ib(d,kd[0]),f=od(d,e);f&&(c[e][f]=Qb(d))})} +function Bd(a,b){var c=sd(b);Ha(a,function(d){var e=new id(d),f=Ib(e,kd[0]);(e=od(e,f))&&(c[f][e]||(c[f][e]=d))})}function Cd(){return Ja(Object.keys(ud.h().a),function(a){return Number(a)})}function Dd(a){Oa(ud.h().b,a)||zd(sd(4),a)};function H(a){this.methodName=a}var Ed=new H(1),Fd=new H(15),Gd=new H(2),Hd=new H(3),Id=new H(4),Jd=new H(5),Kd=new H(6),Ld=new H(7),Md=new H(8),Nd=new H(9),Od=new H(10),Pd=new H(11),Qd=new H(12),Rd=new H(13),Sd=new H(14);function I(a,b,c){c.hasOwnProperty(a.methodName)||Object.defineProperty(c,String(a.methodName),{value:b})}function Td(a,b,c){return b[a.methodName]||c||function(){}}function Ud(a){I(Jd,vd,a);I(Kd,wd,a);I(Ld,xd,a);I(Md,yd,a);I(Rd,Bd,a);I(Fd,Dd,a)} +function Vd(a){I(Id,function(b){md.h().a=b},a);I(Nd,function(b,c){var d=md.h();d.a[3][b]||(d.a[3][b]=c)},a);I(Od,function(b,c){var d=md.h();d.a[4][b]||(d.a[4][b]=c)},a);I(Pd,function(b,c){var d=md.h();d.a[5][b]||(d.a[5][b]=c)},a);I(Sd,function(b){for(var c=md.h(),d=ea([3,4,5]),e=d.next();!e.done;e=d.next()){var f=e.value;e=void 0;var g=c.a[f];f=b[f];for(e in f)g[e]=f[e]}},a)}function Wd(a){a.hasOwnProperty("init-done")||Object.defineProperty(a,"init-done",{value:!0})};function Xd(){this.b=function(a,b){return void 0===b?!1:b};this.a=function(){}}function Yd(a,b,c){a.b=function(d,e){return Td(Jd,b)(d,e,c)};a.a=function(){Td(Fd,b)(c)}}wa(Xd);function J(a){var b=void 0===b?!1:b;return Xd.h().b(a,b)};function Zd(a){a=void 0===a?p:a;var b=a.context||a.AMP_CONTEXT_DATA;if(!b)try{b=a.parent.context||a.parent.AMP_CONTEXT_DATA}catch(c){}try{if(b&&b.pageViewId&&b.canonicalUrl)return b}catch(c){}return null}function $d(a){return(a=a||Zd())?lc(a.master)?a.master:null:null};function ae(a,b){p.google_image_requests||(p.google_image_requests=[]);var c=p.document.createElement("img");if(b){var d=function(e){b&&b(e);c.removeEventListener&&c.removeEventListener("load",d,!1);c.removeEventListener&&c.removeEventListener("error",d,!1)};ec(c,"load",d);ec(c,"error",d)}c.src=a;p.google_image_requests.push(c)};function be(a,b){if(a)for(var c in a)Object.prototype.hasOwnProperty.call(a,c)&&b.call(void 0,a[c],c,a)}function ce(a){return!(!a||!a.call)&&"function"===typeof a}function de(a){a=$d(Zd(a))||a;a.google_unique_id?++a.google_unique_id:a.google_unique_id=1}function ee(a){a=a.google_unique_id;return"number"===typeof a?a:0}function fe(a){a=$d(Zd(a))||a;a=a.google_unique_id;return"number"===typeof a?a:0}var ge=!!window.google_async_iframe_id,he=ge&&window.parent||window; +function ie(){if(ge&&!lc(he)){var a="."+ac.domain;try{for(;2e?encodeURIComponent(We(a,b,c,d,e+1)):"...";return encodeURIComponent(String(a))}function Ye(a,b,c,d){a.a.push(b);a.b[b]=Ve(c,d)} +function Ze(a,b,c){b=b+"//pagead2.googlesyndication.com"+c;var d=$e(a)-c.length;if(0>d)return"";a.a.sort(function(n,r){return n-r});c=null;for(var e="",f=0;f=m.length){d-=m.length;b+=m;e=a.c;break}a.f&&(e=d,m[e-1]==a.c&&--e,b+=m.substr(0,e),e=a.c,d=0);c=null==c?g:c}}a="";null!=c&&(a=e+"trn="+c);return b+a} +function $e(a){var b=1,c;for(c in a.b)b=c.length>b?c.length:b;return 3997-b-a.c.length-1};function af(a,b,c,d,e,f){if((d?a.a:Math.random())<(e||.01))try{if(c instanceof Ue)var g=c;else g=new Ue,F(c,function(k,m){var n=g,r=n.g++;k=Ve(m,k);n.a.push(r);n.b[r]=k});var h=Ze(g,a.b,"/pagead/gen_204?id="+b+"&");h&&("undefined"===typeof f?ae(h,null):ae(h,void 0===f?null:f))}catch(k){}};var bf=null;function cf(){if(null===bf){bf="";try{var a="";try{a=p.top.location.hash}catch(c){a=p.location.hash}if(a){var b=a.match(/\bdeid=([\d,]+)/);bf=b?b[1]:""}}catch(c){}}return bf};function df(){var a=p.performance;return a&&a.now&&a.timing?Math.floor(a.now()+a.timing.navigationStart):+new Date}function ef(){var a=void 0===a?p:a;return(a=a.performance)&&a.now?a.now():null};function ff(a,b,c){this.label=a;this.type=b;this.value=c;this.duration=0;this.uniqueId=Math.random();this.slotId=void 0};var gf=p.performance,hf=!!(gf&&gf.mark&&gf.measure&&gf.clearMarks),jf=Qa(function(){var a;if(a=hf)a=cf(),a=!!a.indexOf&&0<=a.indexOf("1337");return a});function kf(){var a=lf;this.b=[];this.c=a||p;var b=null;a&&(a.google_js_reporting_queue=a.google_js_reporting_queue||[],this.b=a.google_js_reporting_queue,b=a.google_measure_js_timing);this.a=jf()||(null!=b?b:1>Math.random())} +function mf(a){a&&gf&&jf()&&(gf.clearMarks("goog_"+a.label+"_"+a.uniqueId+"_start"),gf.clearMarks("goog_"+a.label+"_"+a.uniqueId+"_end"))}kf.prototype.start=function(a,b){if(!this.a)return null;var c=ef()||df();a=new ff(a,b,c);b="goog_"+a.label+"_"+a.uniqueId+"_start";gf&&jf()&&gf.mark(b);return a};function nf(){var a=of;this.j=pf;this.c=!0;this.b=null;this.g=this.J;this.a=void 0===a?null:a;this.f=!1}l=nf.prototype;l.Ba=function(a){this.g=a};l.ma=function(a){this.b=a};l.Ca=function(a){this.c=a};l.Da=function(a){this.f=a}; +l.fa=function(a,b,c){try{if(this.a&&this.a.a){var d=this.a.start(a.toString(),3);var e=b();var f=this.a;b=d;if(f.a&&"number"===typeof b.value){var g=ef()||df();b.duration=g-b.value;var h="goog_"+b.label+"_"+b.uniqueId+"_end";gf&&jf()&&gf.mark(h);!f.a||2048(void 0===c?.01:c))return this.b;Qe(b)||(b=new Pe(b,{context:a,id:void 0===e?"jserror":e}));if(d||this.a)b.meta={},this.a&&this.a(b.meta),d&&d(b.meta);p.google_js_errors=p.google_js_errors||[];p.google_js_errors.push(b);p.error_rep_loaded||(oc(p.document,p.location.protocol+"//pagead2.googlesyndication.com/pagead/js/err_rep.js"),p.error_rep_loaded=!0);return this.b}; +l.fa=function(a,b,c){try{var d=b()}catch(e){if(!this.c(a,e,.01,c,"jserror"))throw e;}return d};l.xa=function(a,b,c,d){var e=this;return function(f){for(var g=[],h=0;h=xf&&(wf.a=xf);sf=new nf;sf.ma(function(a){uf(a);vf(a)});sf.Da(!0);"complete"==lf.document.readyState?tf():of.a&&ec(lf,"load",function(){tf()});function yf(){var a=[zf,Af];sf.ma(function(b){Ha(a,function(c){c(b)});uf(b);vf(b)})}function Bf(a,b,c){return sf.fa(a,b,c)}function Cf(a,b){return sf.xa(a,b,void 0,void 0)}function Df(a,b,c){af(pf,a,b,!0,c,void 0)} +function Ef(a,b,c,d){var e;Qe(b)?e=b.msg||qf(b.error):e=qf(b);return 0==e.indexOf("TagError")?(c=b instanceof Pe?b.error:b,c.pbr||(c.pbr=!0,sf.J(a,b,.1,d,"puberror")),!1):sf.J(a,b,c,d)};function Ff(a,b){this.ra=a;this.ya=b}function Gf(a){var b=[].slice.call(arguments).filter(Pa(function(e){return null===e}));if(!b.length)return null;var c=[],d={};b.forEach(function(e){c=c.concat(e.ra||[]);d=Object.assign(d,e.ya)});return new Ff(c,d)} +function Hf(a){switch(a){case 1:return new Ff(null,{google_ad_semantic_area:"mc"});case 2:return new Ff(null,{google_ad_semantic_area:"h"});case 3:return new Ff(null,{google_ad_semantic_area:"f"});case 4:return new Ff(null,{google_ad_semantic_area:"s"});default:return null}};var If=new Ff(["google-auto-placed"],{google_tag_origin:"qs"});var Jf={},Kf=(Jf.google_ad_channel=!0,Jf.google_ad_host=!0,Jf);function Lf(a,b){a.location.href&&a.location.href.substring&&(b.url=a.location.href.substring(0,200));Df("ama",b,.01)}function Mf(a){var b={};F(Kf,function(c,d){d in a&&(b[d]=a[d])});return b};var Nf=Pc("2019",2012);function Of(a,b,c){if("relative"===a)return b;c||(c=Wc?"https":"http");p.location&&"https:"==p.location.protocol&&"http"==c&&(c="https");return[c,"://",a,b].join("")}function Pf(a,b,c){a=Of(a,b,c);2012P(a)))return 4;if(!(a.innerHeight>=a.innerWidth))return 5;var f=P(a);if(!f||(f-c)/f>d)a=6;else{if(c="true"!=e.google_full_width_responsive)a:{c=P(a);for(b=b.parentElement;b;b=b.parentElement)if((d=pc(b,a))&&(e=G(d.width))&&!(e>=c)&&"visible"!=d.overflow){c=!0;break a}c=!1}a=c?7:!0}return a} +function pg(a,b,c,d){var e=og(b,c,a,.3,d);!0!==e?a=e:"true"==d.google_full_width_responsive||mg(c,b)?qg(b)?a=!0:(b=P(b),a=b-a,a=b&&0<=a?!0:b?-10>a?11:0>a?14:12:10):a=9;return a}function rg(a,b,c){a=a.style;"rtl"==b?J(251)?a.setProperty("margin-right",c,"important"):a.marginRight=c:J(251)?a.setProperty("margin-left",c,"important"):a.marginLeft=c} +function sg(a,b){if(3==b.nodeType)return/\S/.test(b.data);if(1==b.nodeType){if(/^(script|style)$/i.test(b.nodeName))return!1;try{var c=pc(b,a)}catch(d){}return!c||"none"!=c.display&&!("absolute"==c.position&&("hidden"==c.visibility||"collapse"==c.visibility))}return!1}function tg(a,b){for(var c=0;100>c&&b.parentElement;++c){for(var d=b.parentElement.childNodes,e=0;e=f)}}function Ag(a){return function(b){return b.height()<=a}}function yg(a,b){return kg(a,b)f}function e(f){f=Hg(f);return null==f?!1:cc&&(c+=b.length),b=0<=c&&cf&&(f+=e.length);0<=f&&f=g){f=!0;break a}r= +z(f[n],1);if(null==r)break;w=c[r];var u=B(f[n],Xf,2);null!=u&&null!=Jb(u,1)&&null!=Jb(u,2)&&null!=Jb(u,3)&&(u=new Tf(Jb(u,1),Jb(u,2),Jb(u,3)),Xg(m,k,u)&&(r=oh(a,w,r,b,d,h),null!=r&&null!=r.W&&(r=r.W.getBoundingClientRect(),m.push(r))))}f=0<(mh(a).numAutoAdsPlaced||0)}}if(f)return!0;f=ag(a.a);if(null!==f&&Lb(f,2))return mh(a).eatf=!0,Sf(7,[!0,0,!1]),!0;f=new Vf([2]);!e&&B(a.b,Me,15)&&Lb(B(a.b,Me,15),15)&&f.add(4);for(e=0;e=c.offsetWidth);f=!c}if(!(c=f)){c=a.o;f=z(b,2);g= +za(d);g=c.b.a.get(g);if(!(g=g?g.contains(f):!1))a:{if(c.a.contains(za(d)))switch(f){case 2:case 3:g=!0;break a;default:g=!1;break a}for(f=d.parentElement;f;){if(c.a.contains(za(f))){g=!0;break a}f=f.parentElement}g=!1}c=g}if(c)return null;c=B(b,Ae,3);f={};c&&(f.Fa=z(c,1),f.qa=z(c,2),f.clearBoth=!!Kb(c,3));c=B(b,Be,4)&&z(B(b,Be,4),2)?z(B(b,Be,4),2):null;c=Hf(c);b=null==z(b,12)?null:z(b,12);b=Gf(a.j,c,null==b?null:new Ff(null,{google_ml_rank:b}));c=a.a;a=a.u;var h=c.document,k=f.clearBoth||!1;g=fc((new gc(h)).a, +"DIV");var m=g.style;m.width="100%";m.height="auto";m.clear=k?"both":"none";k=g.style;k.textAlign="center";f.Qa&&Jg(k,f.Qa);h=fc((new gc(h)).a,"INS");k=h.style;k.display="block";k.margin="auto";k.backgroundColor="transparent";f.Fa&&(k.marginTop=f.Fa);f.qa&&(k.marginBottom=f.qa);f.Ha&&Jg(k,f.Ha);g.appendChild(h);f={ia:g,W:h};f.W.setAttribute("data-ad-format","auto");g=[];if(h=b&&b.ra)f.ia.className=h.join(" ");h=f.W;h.className="adsbygoogle";h.setAttribute("data-ad-client",a);g.length&&h.setAttribute("data-ad-channel", +g.join("+"));a:{try{var n=f.ia;var r=void 0===r?0:r;if(J(313)){r=void 0===r?0:r;var w=Gg(d,e,r);if(w.G){var u=w.G;for(d=u;d=w.da(d);)u=d;var D={anchor:u,position:w.ea}}else D={anchor:d,position:e};n["google-ama-order-assurance"]=r;Fg(n,D.anchor,D.position)}else Fg(n,d,e);b:{var v=f.W;v.setAttribute("data-adsbygoogle-status","reserved");v.className+=" adsbygoogle-noablate";n={element:v};var M=b&&b.ya;if(v.hasAttribute("data-pub-vars")){try{M=JSON.parse(v.getAttribute("data-pub-vars"))}catch(Ka){break b}v.removeAttribute("data-pub-vars")}M&& +(n.params=M);(c.adsbygoogle=c.adsbygoogle||[]).push(n)}}catch(Ka){(v=f.ia)&&v.parentNode&&(M=v.parentNode,M.removeChild(v),Eg(M)&&(M.style.display=M.getAttribute("data-init-display")||"none"));v=!1;break a}v=!0}return v?f:null}function mh(a){return a.a.google_ama_state=a.a.google_ama_state||{}};function qh(){this.b=new rh(this);this.a=0}qh.prototype.resolve=function(a){sh(this);this.a=1;this.f=a;th(this.b)};qh.prototype.reject=function(a){sh(this);this.a=2;this.c=a;th(this.b)};function sh(a){if(0!=a.a)throw Error("Already resolved/rejected.");}function rh(a){this.a=a}rh.prototype.then=function(a,b){if(this.b)throw Error("Then functions already set.");this.b=a;this.c=b;th(this)}; +function th(a){switch(a.a.a){case 0:break;case 1:a.b&&a.b(a.a.f);break;case 2:a.c&&a.c(a.a.c);break;default:throw Error("Unhandled deferred state.");}};function uh(a,b){this.exception=b}function vh(a,b){this.c=p;this.a=a;this.b=b}vh.prototype.start=function(){this.f()};vh.prototype.f=function(){try{switch(this.c.document.readyState){case "complete":case "interactive":nh(this.a,!0);wh(this);break;default:nh(this.a,!1)?wh(this):this.c.setTimeout(Ea(this.f,this),100)}}catch(a){wh(this,a)}};function wh(a,b){try{a.b.resolve(new uh(lh(a.a),b))}catch(c){a.b.reject(c)}};function xh(a){Lf(a,{atf:1})}function yh(a,b){(a.google_ama_state=a.google_ama_state||{}).exception=b;Lf(a,{atf:0})};function zh(){this.debugCard=null;this.debugCardRequested=!1};function Ah(a,b){if(!a)return!1;a=a.hash;if(!a||!a.indexOf)return!1;if(-1!=a.indexOf(b))return!0;b=Bh(b);return"go"!=b&&-1!=a.indexOf(b)?!0:!1}function Bh(a){var b="";be(a.split("_"),function(c){b+=c.substr(0,2)});return b};var Ch={13:"0.001",22:"0.01",24:"0.05",28:"0.001",29:"0.01",60:"0.03",66:"0.1",79:"1200",82:"3",98:"0.01",118:"false", +126:"0.001",128:"false",129:"0.02",136:"0.02",137:"0.01",149:"0",150:"1000",155:"0.06",177:"0.02",179:"100",180:"20"};var Dh=null;function Eh(){this.a=Ch};function Fh(a,b,c){var d="script";d=void 0===d?"":d;var e=a.createElement("link");try{e.rel="preload";if(gb("preload","stylesheet"))var f=Za(b).toString();else{if(b instanceof Wa)var g=Za(b).toString();else{if(b instanceof jb)var h=mb(b);else{if(b instanceof jb)var k=b;else b="object"==typeof b&&b.b?b.a():String(b),nb.test(b)||(b="about:invalid#zClosurez"),k=new jb(kb,b);h=mb(k)}g=h}f=g}e.href=f}catch(m){return}d&&(e.as=d);c&&e.setAttribute("nonce",c);if(a=a.getElementsByTagName("head")[0])try{a.appendChild(e)}catch(m){}} +;function Gh(a){var b={},c={};return c.enable_page_level_ads=(b.pltais=!0,b),c.google_ad_client=a,c};function Hh(a){if(!a)return"";(a=a.toLowerCase())&&"ca-"!=a.substring(0,3)&&(a="ca-"+a);return a};function Ih(a,b,c){return Jh(a,void 0===c?"":c,function(d){return La(C(d,Vb,2),function(e){return z(e,1)===b})})}function Kh(a,b,c){c=void 0===c?"":c;var d=le(a)||a;return Lh(d,b)?!0:Jh(a,c,function(e){return La(z(e,3),function(f){return f===b})})}function Mh(a){return Jh(p,void 0===a?"":a,function(){return!0})}function Lh(a,b){a=(a=(a=a.location&&a.location.hash)&&a.match(/forced_clientside_labs=([\d,]+)/))&&a[1];return!!a&&Oa(a.split(","),b.toString())} +function Jh(a,b,c){a=le(a)||a;var d=Nh(a);b&&(b=Hh(String(b)));return Ta(d,function(e,f){return Object.prototype.hasOwnProperty.call(d,f)&&(!b||b===f)&&c(e)})}function Nh(a){a=Oh(a);var b={};be(a,function(c,d){try{var e=new Tb(c);b[d]=e}catch(f){}});return b} +function Oh(a){try{var b=a.localStorage.getItem("google_adsense_settings");if(!b)return{};var c=JSON.parse(b);return c!==Object(c)?{}:Sa(c,function(d,e){return Object.prototype.hasOwnProperty.call(c,e)&&"string"===typeof e&&"array"==xa(d)})}catch(d){return{}}};function Ph(){this.b=function(){};this.a=function(){return[]}}function Qh(a,b,c){a.b=function(d){Td(Gd,b,function(){return[]})(d,c)};a.a=function(){return Td(Hd,b,function(){return[]})(c)}}wa(Ph);var Rh={i:"368226950",s:"368226951"},Sh={i:"368226960",s:"368226961"},Th={i:"368226470",V:"368226471"},Uh={i:"368226480",V:"368226481"},Vh={i:"368226500",s:"368226501"},Wh={i:"36998750",s:"36998751"},Xh={A:"20040067",i:"20040068",oa:"1337"},Yh={i:"21060548",A:"21060549"},Zh={i:"21060623",A:"21060624"},$h={i:"21062271",A:"21062272"};function ai(a){return Tc&&!!a.google_disable_experiments}ie();function bi(a){var b=Kh(p,12,a.google_ad_client);a="google_ad_host"in a;var c=me(p,Rh.s),d=Ah(p.location,"google_ads_preview");return b&&!a&&c||d} +function ci(a){if(p.google_apltlad||ke(p)!=p||!a.google_ad_client)return null;var b=bi(a),c=!me(p,Th.V);if(!b&&!c)return null;p.google_apltlad=!0;var d=Gh(a.google_ad_client),e=d.enable_page_level_ads;F(a,function(f,g){re[g]&&"google_ad_client"!=g&&(e[g]=f)});b?e.google_ad_channel="AutoInsertAutoAdCode":c&&(e.google_pgb_reactive=7,"google_ad_section"in a||"google_ad_region"in a)&&(e.google_ad_section=a.google_ad_section||a.google_ad_region);return d} +function di(a){return ya(a.enable_page_level_ads)&&7==a.enable_page_level_ads.google_pgb_reactive};function Af(a){try{var b=K(p).eids||[];null!=b&&0Math.random()&&Nc({data:a},"ls_tamp")};var ri=new ni(5);function si(a){a=void 0===a?p:a;return a.ggeac||(a.ggeac={})};function ti(a,b){a=ua(a);a="function"===typeof a?a():a;return typeof a===b?a:void 0} +function ui(){var a={};this[3]=(a[8]=function(b){return!!ua(b)},a[9]=function(b){b=ua(b);return"function"==xa(b)&&Fc(b)},a[10]=function(){return window==window.top},a[6]=function(b){return Oa(Ph.h().a(),parseInt(b,10))},a[27]=function(b){b=ti(b,"boolean");return void 0!==b?b:void 0},a);a={};this[4]=(a[3]=function(){return Gc()},a[6]=function(b){b=ti(b,"number");return void 0!==b?b:void 0},a);a={};this[5]=(a[2]=function(){return window.location.href},a[3]=function(){try{return window.top.location.hash}catch(b){return""}}, +a[4]=function(b){b=ti(b,"string");return void 0!==b?b:void 0},a)}wa(ui);function vi(a){y(this,a,wi,null)}q(vi,x);var wi=[2];vi.prototype.Y=function(){return A(this,1,0)};vi.prototype.X=function(){return A(this,7,0)};function xi(a){y(this,a,yi,null)}q(xi,x);var yi=[2];xi.prototype.X=function(){return A(this,5,0)};function zi(a){y(this,a,Ai,null)}q(zi,x);function Bi(a){y(this,a,Ci,null)}q(Bi,x);var Ai=[1,4,2,3],Ci=[2];Bi.prototype.X=function(){return A(this,1,0)};var Di=[12,13];function Ei(){}Ei.prototype.G=function(a,b,c){var d=this,e=void 0===c?{}:c;c=void 0===e.ta?!1:e.ta;var f=void 0===e.Pa?{}:e.Pa;e=void 0===e.Xa?[]:e.Xa;this.a=a;this.g=c;this.f=f;a={};this.b=(a[b]=e,a[4]=[],a);this.c={};(b=cf())&&Ha(b.split(",")||[],function(g){(g=parseInt(g,10))&&(d.c[g]=!0)});return this}; +function Fi(a,b,c){var d=[],e=Gi(a.a,b);if(e.length){9!==b&&(a.a=Hi(a.a,b));var f=Oa(Di,b);Ha(e,function(g){if(g=Ii(a,g,c)){var h=g.Y();d.push(h);Ji(a,h,f?4:c);var k=C(g,id,2);k&&(f?Ha(Cd(),function(m){return Ad(k,m)}):Ad(k,c))}})}return d}function Ji(a,b,c){a.b[c]||(a.b[c]=[]);a=a.b[c];Oa(a,b)?Nc({eids:JSON.stringify(a),dup:b},"gpt_dupeid"):a.push(b)}function Ki(a,b){a.a.push.apply(a.a,fa(Ia(Ja(b,function(c){return new Bi(c)}),function(c){return!Oa(Di,c.X())})))} +function Ii(a,b,c){var d=md.h().a;if(!fd(B(b,Zc,3),d))return null;var e=C(b,vi,2),f=e.length*A(b,1,0),g=A(b,6,0);if(g)return f=2==c?pi(g):oi(window,g),null===f&&(f=Math.floor(1E3*tc(window))),b=Li(b,f),!b||d&&!fd(B(b,Zc,3),d)?null:Mi(a,[b],1);c=d?Ia(e,function(h){return fd(B(h,Zc,3),d)}):e;return c.length?(b=A(b,4,0))?Ni(a,b,f,c):Mi(a,c,f/1E3):null}function Ni(a,b,c,d){var e=null!=a.f[b]?a.f[b]:1E3;if(0>=e)return null;d=Mi(a,d,c/e);a.f[b]=d?0:e-c;return d} +function Mi(a,b,c){var d=a.c,e=Ma(b,function(f){return!!d[f.Y()]});return e?e:a.g?null:qc(b,c,!1)}function Oi(a,b){I(Ed,function(c){a.c[c]=!0},b);I(Gd,function(c,d){return Fi(a,c,d)},b);I(Hd,function(c){return(a.b[c]||[]).concat(a.b[4])},b);I(Qd,function(c){return Ki(a,c)},b)}wa(Ei);function Gi(a,b){return(a=Ma(a,function(c){return c.X()==b}))&&C(a,xi,2)||[]}function Hi(a,b){return Ia(a,function(c){return c.X()!=b})} +function Li(a,b){var c=C(a,vi,2),d=c.length,e=A(a,1,0);a=A(a,8,0);var f=(b-a)%d;return b=d*e-1?null:c[f]};function Pi(){this.a=function(){}}wa(Pi);function Qi(a){Pi.h().a(a)};function Ri(a,b,c,d){var e=1;d=void 0===d?si():d;e=void 0===e?0:e;d.hasOwnProperty("init-done")?(Td(Qd,d)(Ja(C(a,Bi,2),function(f){return Qb(f)})),Td(Rd,d)(Ja(C(a,id,1),function(f){return Qb(f)}),e),b&&Td(Sd,d)(b),Si(d,e)):(Oi(Ei.h().G(C(a,Bi,2),e,c),d),Ud(d),Vd(d),Wd(d),Si(d,e),Ad(C(a,id,1),e),nd=nd||!(!c||!c.Ma),Qi(ui.h()),b&&Qi(b))}function Si(a,b){a=void 0===a?si():a;b=void 0===b?0:b;var c=a,d=b;d=void 0===d?0:d;Qh(Ph.h(),c,d);c=a;b=void 0===b?0:b;Yd(Xd.h(),c,b);Pi.h().a=Td(Sd,a);Xd.h().a()};function S(a,b){b&&a.push(b)}function Ti(a,b){for(var c=[],d=1;d=d?c=null:(g=new mi(c,c+d-1),(d=d%f||d/f%e.length)||(d=b.b,d=!(d.start<=g.start&&d.a>=g.a)),d?c=null:(a=oi(a,b.a),c=null!==a&&g.start<=a&&g.a>=a?e[Math.floor((a-c)/f)%e.length]:null)));return c};function Wi(a,b,c){if(lc(a.document.getElementById(b).contentWindow))a=a.document.getElementById(b).contentWindow,b=a.document,b.body&&b.body.firstChild||(/Firefox/.test(navigator.userAgent)?b.open("text/html","replace"):b.open(),a.google_async_iframe_close=!0,b.write(c));else{a=a.document.getElementById(b).contentWindow;c=String(c);b=['"'];for(var d=0;df))if(f=e,f in xb)e=xb[f];else if(f in wb)e=xb[f]=wb[f]; +else{h=f.charCodeAt(0);if(31h)e=f;else{if(256>h){if(e="\\x",16>h||256h&&(e+="0");e+=h.toString(16).toUpperCase()}e=xb[f]=e}h=e}b[g]=h}b.push('"');a.location.replace("javascript:"+b.join(""))}};var Xi=null;function T(a,b,c,d){d=void 0===d?!1:d;Q.call(this,a,b);this.Z=c;this.Na=d}na(T,Q);T.prototype.ga=function(){return this.Z};T.prototype.ba=function(a,b,c){b.google_ad_resize||(c.style.height=this.height()+"px",b.rpe=!0)};function Yi(a){return function(b){return!!(b.Z&a)}};var Zi=Ab("script");function $i(a,b,c,d,e,f,g,h,k,m,n,r,w,u){this.I=a;this.a=b;this.Z=void 0===c?null:c;this.c=void 0===d?null:d;this.T=void 0===e?null:e;this.b=void 0===f?null:f;this.f=void 0===g?null:g;this.o=void 0===h?!1:h;this.u=void 0===k?!1:k;this.P=void 0===m?null:m;this.$=void 0===n?null:n;this.g=void 0===r?null:r;this.j=void 0===w?null:w;this.aa=void 0===u?null:u;this.U=this.L=this.K=null} +function aj(a,b,c){null!=a.Z&&(c.google_responsive_formats=a.Z);null!=a.T&&(c.google_safe_for_responsive_override=a.T);null!=a.b&&(!0===a.b?c.google_full_width_responsive_allowed=!0:(c.google_full_width_responsive_allowed=!1,c.gfwrnwer=a.b));null!=a.f&&!0!==a.f&&(c.gfwrnher=a.f);a.o&&(c.google_bfa=a.o);a.u&&(c.ebfa=a.u);var d=a.j||c.google_ad_width;null!=d&&(c.google_resizing_width=d);d=a.g||c.google_ad_height;null!=d&&(c.google_resizing_height=d);d=a.a.R(b);var e=a.a.height();c.google_ad_resize|| +(c.google_ad_width=d,c.google_ad_height=e,c.google_ad_format=a.a.ja(b),c.google_responsive_auto_format=a.I,null!=a.c&&(c.armr=a.c),c.google_ad_resizable=!0,c.google_override_format=1,c.google_loader_features_used=128,!0===a.b&&(c.gfwrnh=a.a.height()+"px"));null!=a.P&&(c.gfwroml=a.P);null!=a.$&&(c.gfwromr=a.$);null!=a.g&&(c.gfwroh=a.g);null!=a.j&&(c.gfwrow=a.j);null!=a.aa&&(c.gfwroz=a.aa);null!=a.K&&(c.gml=a.K);null!=a.L&&(c.gmr=a.L);null!=a.U&&(c.gzi=a.U);b=ie();b=le(b)||b;Ah(b.location,"google_responsive_slot_debug")&& +(c.ds="outline:thick dashed "+(d&&e?!0!==a.b||!0!==a.f?"#ffa500":"#0f0":"#f00")+" !important;");Ah(b.location,"google_responsive_dummy_ad")&&(Oa([1,2,3,4,5,6,7,8],a.I)||1===a.c)&&2!==a.c&&(a=JSON.stringify({googMsgType:"adpnt",key_value:[{key:"qid",value:"DUMMY_AD"}]}),c.dash="<"+Zi+">window.top.postMessage('"+a+"', '*');\n \n
\n

Requested size:'+ +d+"x"+e+"

\n

Rendered size:"+d+"x"+e+"

\n
")};/* + + Copyright 2019 The AMP HTML Authors. All Rights Reserved. + + Licensed under the Apache License, Version 2.0 (the "License"); + you may not use this file except in compliance with the License. + You may obtain a copy of the License at + + http://www.apache.org/licenses/LICENSE-2.0 + + Unless required by applicable law or agreed to in writing, software + distributed under the License is distributed on an "AS-IS" BASIS, + WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. + See the License for the specific language governing permissions and + limitations under the License. +*/ +var bj={},cj=(bj.image_stacked=1/1.91,bj.image_sidebyside=1/3.82,bj.mobile_banner_image_sidebyside=1/3.82,bj.pub_control_image_stacked=1/1.91,bj.pub_control_image_sidebyside=1/3.82,bj.pub_control_image_card_stacked=1/1.91,bj.pub_control_image_card_sidebyside=1/3.74,bj.pub_control_text=0,bj.pub_control_text_card=0,bj),dj={},ej=(dj.image_stacked=80,dj.image_sidebyside=0,dj.mobile_banner_image_sidebyside=0,dj.pub_control_image_stacked=80,dj.pub_control_image_sidebyside=0,dj.pub_control_image_card_stacked= +85,dj.pub_control_image_card_sidebyside=0,dj.pub_control_text=80,dj.pub_control_text_card=80,dj),fj={},gj=(fj.pub_control_image_stacked=100,fj.pub_control_image_sidebyside=200,fj.pub_control_image_card_stacked=150,fj.pub_control_image_card_sidebyside=250,fj.pub_control_text=100,fj.pub_control_text_card=150,fj); +function hj(a){var b=0;a.C&&b++;a.v&&b++;a.w&&b++;if(3>b)return{B:"Tags data-matched-content-ui-type, data-matched-content-columns-num and data-matched-content-rows-num should be set together."};b=a.C.split(",");var c=a.w.split(",");a=a.v.split(",");if(b.length!==c.length||b.length!==a.length)return{B:'Lengths of parameters data-matched-content-ui-type, data-matched-content-columns-num and data-matched-content-rows-num must match. Example: \n data-matched-content-rows-num="4,2"\ndata-matched-content-columns-num="1,6"\ndata-matched-content-ui-type="image_stacked,image_card_sidebyside"'}; +if(2a?c?(c=a-8-8,c=Math.floor(c/1.91+70)+Math.floor(11*(c*cj.mobile_banner_image_sidebyside+ej.mobile_banner_image_sidebyside)+96),a={O:a,M:c,v:1,w:12,C:"mobile_banner_image_sidebyside"}):(a=ij(a),a={O:a.width,M:a.height,v:1,w:13,C:"image_sidebyside"}):(a=ij(a),a={O:a.width,M:a.height,v:4,w:2,C:"image_stacked"});nj(b,a);return new $i(9,new kj(a.O,a.M))} +function oj(a,b){mj(a,b);var c=hj({w:b.google_content_recommendation_rows_num,v:b.google_content_recommendation_columns_num,C:b.google_content_recommendation_ui_type});if(c.B)a={O:0,M:0,v:0,w:0,C:"image_stacked",B:c.B};else{var d=2===c.wa.length&&468<=a?1:0;var e=c.wa[d];e=0===e.indexOf("pub_control_")?e:"pub_control_"+e;var f=gj[e];for(var g=c.v[d];a/g=a)throw new O("Invalid responsive width from Matched Content slot "+b.google_ad_slot+": "+a+". Please ensure to put this Matched Content slot into a non-zero width div container.");} +function nj(a,b){a.google_content_recommendation_ui_type=b.C;a.google_content_recommendation_columns_num=b.v;a.google_content_recommendation_rows_num=b.w};function pj(a,b){Q.call(this,a,b)}na(pj,Q);pj.prototype.R=function(){return this.minWidth()};pj.prototype.ba=function(a,b,c){vg(a,c);b.google_ad_resize||(c.style.height=this.height()+"px",b.rpe=!0)};var qj={"image-top":function(a){return 600>=a?284+.414*(a-250):429},"image-middle":function(a){return 500>=a?196-.13*(a-250):164+.2*(a-500)},"image-side":function(a){return 500>=a?205-.28*(a-250):134+.21*(a-500)},"text-only":function(a){return 500>=a?187-.228*(a-250):130},"in-article":function(a){return 420>=a?a/1.2:460>=a?a/1.91+130:800>=a?a/4:200}};function rj(a,b){Q.call(this,a,b)}na(rj,Q);rj.prototype.R=function(){return Math.min(1200,this.minWidth())}; +function sj(a,b,c,d,e){var f=e.google_ad_layout||"image-top";if("in-article"==f&&"false"!=e.google_full_width_responsive){var g=og(b,c,a,.2,e);if(!0!==g)e.gfwrnwer=g;else if(g=P(b))e.google_full_width_responsive_allowed=!0,c.parentElement&&(tg(b,c),vg(b,c),a=g)}if(250>a)throw new O("Fluid responsive ads must be at least 250px wide: availableWidth="+a);a=Math.min(1200,Math.floor(a));if(d&&"in-article"!=f){f=Math.ceil(d);if(50>f)throw new O("Fluid responsive ads must be at least 50px tall: height="+ +f);return new $i(11,new Q(a,f))}if("in-article"!=f&&(d=e.google_ad_layout_key)){f=""+d;b=Math.pow(10,3);if(d=(c=f.match(/([+-][0-9a-z]+)/g))&&c.length){e=[];for(g=0;gP(c)&&qg(c)&&tg(c,d),b=pg(a,c,d,e),c=!0!==b?{l:a,m:b}:{l:P(c)||a,m:!0}):c={l:a,m:2};b=c.m;return!0!==b?{l:a,m:b}:d.parentElement?{l:c.l,m:b}:{l:a,m:b}} +function yj(a,b,c,d,e){var f=Bf(247,function(){return wj(a,b,c,d,e)}),g=f.l;f=f.m;var h=!0===f,k=G(d.style.width),m=G(d.style.height),n=zj(g,b,c,d,e,h);g=n.N;h=n.H;var r=n.D,w=n.F,u=n.ga;n=n.va;var D=Aj(b,u),v,M=(v=R(d,c,"marginLeft",G))?v+"px":"",Ka=(v=R(d,c,"marginRight",G))?v+"px":"";v=R(d,c,"zIndex")||"";return new $i(D,g,u,null,n,f,h,r,w,M,Ka,m,k,v)}function xj(a){return"auto"==a||/^((^|,) *(horizontal|vertical|rectangle) *)+$/.test(a)} +function zj(a,b,c,d,e,f){b="auto"==b?.25>=a/Math.min(1200,P(c))?4:3:ng(b);var g=!1,h=!1;if(488>P(c)){var k=mg(d,c);var m=yg(d,c);g=!m&&k;h=m&&k}m=488>P(c);var n=[wg(a),Yi(b)];qg(c)||n.push(xg(m,c,d,h));null!=e.google_max_responsive_height&&n.push(Ag(e.google_max_responsive_height));var r=[function(u){return!u.Na}];!g&&!h||qg(c)||(g=Cg(c,d),r.push(Ag(g)));var w=m&&!f&&3===b&&Bj(c)?new T(a,Math.floor(a/1.2),1):uj(vj.slice(0),tj(n),tj(r));if(!w)throw new O("No slot size for availableWidth="+a);r=Bf(248, +function(){var u;a:if(f){if(e.gfwrnh&&(u=G(e.gfwrnh))){u={N:new pj(a,u),H:!0,D:!1,F:!1};break a}u=!1;var D=hg(c).clientHeight,v=kg(d,c),M=c.google_lpabyc,Ka=Bg(d,c);Ka&&2D)&&(D=.9*hg(c).clientHeight,v=Math.min(D,Cj(c,d,e)),D&&v==D&&(v=c.google_pbfabyc,u=!v,v||(c.google_pbfabyc=kg(d,c)+D)));D=a/1.2;if(qg(c))v=D;else if(v=Math.min(D,Cj(c,d,e)),v<.5*D||100>v)v=D;J(282)&&!yg(d,c)&&(v=Math.max(v,.5*hg(c).clientHeight));u={N:new pj(a,Math.floor(v)),H:va*d.height()?new T(b.minWidth(),b.height(),1):d}function Dj(a){return J(227)||a.location&&"#hffwroe2etoq"==a.location.hash}function Bj(a){return J(232)||a.location&&"#affwroe2etoq"==a.location.hash};function Fj(a,b){Q.call(this,a,b)}na(Fj,Q);Fj.prototype.R=function(){return this.minWidth()};Fj.prototype.ja=function(a){return Q.prototype.ja.call(this,a)+"_0ads_al"};var Gj=[new Fj(728,15),new Fj(468,15),new Fj(200,90),new Fj(180,90),new Fj(160,90),new Fj(120,90)]; +function Hj(a,b,c){var d=250,e=90;d=void 0===d?130:d;e=void 0===e?30:e;var f=uj(Gj,wg(a));if(!f)throw new O("No link unit size for width="+a+"px");a=Math.min(a,1200);f=f.height();b=Math.max(f,b);d=(new $i(10,new Fj(a,Math.min(b,15==f?e:d)))).a;b=d.minWidth();d=d.height();15<=c&&(d=c);return new $i(10,new Fj(b,d))} +function Ij(a,b,c,d){if("false"==d.google_full_width_responsive)return d.google_full_width_responsive_allowed=!1,d.gfwrnwer=1,a;var e=pg(a,b,c,d);if(!0!==e)return d.google_full_width_responsive_allowed=!1,d.gfwrnwer=e,a;e=P(b);if(!e)return a;d.google_full_width_responsive_allowed=!0;vg(b,c);return e};function Jj(a,b,c,d,e){var f;(f=P(b))?488>P(b)?b.innerHeight>=b.innerWidth?(e.google_full_width_responsive_allowed=!0,vg(b,c),f={l:f,m:!0}):f={l:a,m:5}:f={l:a,m:4}:f={l:a,m:10};var g=f;f=g.l;g=g.m;if(!0!==g||a==f)return new $i(12,new Q(a,d),null,null,!0,g,100);a=zj(f,"auto",b,c,e,!0);return new $i(1,a.N,a.ga,2,!0,g,a.H,a.D,a.F)};function Kj(a,b){var c=b.google_ad_format;if("autorelaxed"==c){a:{if("pedestal"!=b.google_content_recommendation_ui_type)for(a=ea(jj),c=a.next();!c.done;c=a.next())if(null!=b[c.value]){b=!0;break a}b=!1}return b?9:5}if(xj(c))return 1;if("link"==c)return 4;if("fluid"==c){if(c="in-article"===b.google_ad_layout)c=J(208)||J(227)||a.location&&("#hffwroe2etop"==a.location.hash||"#hffwroe2etoq"==a.location.hash);return c?(Lj(b),1):8}if(c=27===b.google_reactive_ad_format)c=J(266)||a.location&&"#cefwroe2etoq"== +a.location.hash;if(c)return Lj(b),1}function Mj(a,b,c,d,e){e=b.offsetWidth||(c.google_ad_resize||(void 0===e?!1:e))&&R(b,d,"width",G)||c.google_ad_width||0;(J(310)||d.location&&"#ooimne2e"==d.location.hash)&&4===a&&(c.google_ad_format="auto",c.google_ad_slot="",a=1);var f=(f=Nj(a,e,b,c,d))?f:yj(e,c.google_ad_format,d,b,c);f.a.ba(d,c,b);aj(f,e,c);1!=a&&(a=f.a.height(),b.style.height=a+"px")} +function Nj(a,b,c,d,e){var f=d.google_ad_height||R(c,e,"height",G);switch(a){case 5:return a=Bf(247,function(){return wj(b,d.google_ad_format,e,c,d)}),f=a.l,a=a.m,!0===a&&b!=f&&vg(e,c),!0===a?d.google_full_width_responsive_allowed=!0:(d.google_full_width_responsive_allowed=!1,d.gfwrnwer=a),lj(f,d);case 9:return oj(b,d);case 4:return a=Ij(b,e,c,d),Hj(a,Cg(e,c),f);case 8:return sj(b,e,c,f,d);case 10:return Jj(b,e,c,f,d)}}function Lj(a){a.google_ad_format="auto";a.armr=3};function V(a){this.f=[];this.b=a||window;this.a=0;this.c=null;this.g=0}var Oj;l=V.prototype;l.Ja=function(a,b){0!=this.a||0!=this.f.length||b&&b!=window?this.sa(a,b):(this.a=2,this.Aa(new Pj(a,window)))};l.sa=function(a,b){this.f.push(new Pj(a,b||this.b));Qj(this)};l.Ra=function(a){this.a=1;if(a){var b=Cf(188,Ea(this.za,this,!0));this.c=this.b.setTimeout(b,a)}};l.za=function(a){a&&++this.g;1==this.a&&(null!=this.c&&(this.b.clearTimeout(this.c),this.c=null),this.a=0);Qj(this)}; +l.Ya=function(){return!(!window||!Array)};l.La=function(){return this.g};function Qj(a){var b=Cf(189,Ea(a.Za,a));a.b.setTimeout(b,0)}l.Za=function(){if(0==this.a&&this.f.length){var a=this.f.shift();this.a=2;var b=Cf(190,Ea(this.Aa,this,a));a.a.setTimeout(b,0);Qj(this)}};l.Aa=function(a){this.a=0;a.b()};function Rj(a){try{return a.sz()}catch(b){return!1}}function Sj(a){return!!a&&("object"===typeof a||"function"===typeof a)&&Rj(a)&&ce(a.nq)&&ce(a.nqa)&&ce(a.al)&&ce(a.rl)} +function Tj(){if(Oj&&Rj(Oj))return Oj;var a=Lg(),b=a.google_jobrunner;return Sj(b)?Oj=b:a.google_jobrunner=Oj=new V(a)}function Uj(a,b){Tj().nq(a,b)}function Vj(a,b){Tj().nqa(a,b)}V.prototype.nq=V.prototype.Ja;V.prototype.nqa=V.prototype.sa;V.prototype.al=V.prototype.Ra;V.prototype.rl=V.prototype.za;V.prototype.sz=V.prototype.Ya;V.prototype.tc=V.prototype.La;function Pj(a,b){this.b=a;this.a=b};function Wj(a,b){var c=le(b);if(c){c=P(c);var d=pc(a,b)||{},e=d.direction;if("0px"===d.width&&"none"!=d.cssFloat)return-1;if("ltr"===e&&c)return Math.floor(Math.min(1200,c-a.getBoundingClientRect().left));if("rtl"===e&&c)return a=b.document.body.getBoundingClientRect().right-a.getBoundingClientRect().right,Math.floor(Math.min(1200,c-a-Math.floor((c-b.document.body.clientWidth)/2)))}return-1};function Xj(a){var b=this;this.a=a;a.google_iframe_oncopy||(a.google_iframe_oncopy={handlers:{},upd:function(c,d){var e=Yj("rx",c),f=Number;a:{if(c&&(c=c.match("dt=([^&]+)"))&&2==c.length){c=c[1];break a}c=""}f=f(c);f=(new Date).getTime()-f;e=e.replace(/&dtd=(\d+|-?M)/,"&dtd="+(1E5<=f?"M":0<=f?f:"-M"));b.set(d,e);return e}});this.b=a.google_iframe_oncopy} +Xj.prototype.set=function(a,b){var c=this;this.b.handlers[a]=b;this.a.addEventListener&&this.a.addEventListener("load",function(){var d=c.a.document.getElementById(a);try{var e=d.contentWindow.document;if(d.onload&&e&&(!e.body||!e.body.firstChild))d.onload()}catch(f){}},!1)};function Yj(a,b){var c=new RegExp("\\b"+a+"=(\\d+)"),d=c.exec(b);d&&(b=b.replace(c,a+"="+(+d[1]+1||1)));return b}var Zj,ak="var i=this.id,s=window.google_iframe_oncopy,H=s&&s.handlers,h=H&&H[i],w=this.contentWindow,d;try{d=w.document}catch(e){}if(h&&d&&(!d.body||!d.body.firstChild)){if(h.call){setTimeout(h,0)}else if(h.match){try{h=s.upd(h,i)}catch(e){}w.location.replace(h)}}"; +var W=ak;/[\x00&<>"']/.test(W)&&(-1!=W.indexOf("&")&&(W=W.replace(ab,"&")),-1!=W.indexOf("<")&&(W=W.replace(bb,"<")),-1!=W.indexOf(">")&&(W=W.replace(cb,">")),-1!=W.indexOf('"')&&(W=W.replace(db,""")),-1!=W.indexOf("'")&&(W=W.replace(eb,"'")),-1!=W.indexOf("\x00")&&(W=W.replace(fb,"�")));ak=W;Zj=ak;var bk={},ck=(bk.google_ad_modifications=!0,bk.google_analytics_domain_name=!0,bk.google_analytics_uacct=!0,bk.google_pause_ad_requests=!0,bk);function dk(a){switch(a){case "":case "Test":case "Real":return!0;default:return!1}}function ek(a){this.c=E;this.b=void 0===a?!1:a;this.a=new dc}function fk(a){var b=a.a.get("__gads","");return a.b&&!dk(b)?"Real":b}ek.prototype.write=function(a){var b=z(a,1);if(this.b){if(!dk(this.a.get("__gads","")))return;dk(b)||(b="Real")}this.a.set("__gads",b,{Oa:z(a,2)-this.c.Date.now()/1E3,path:z(a,3),domain:z(a,4),Wa:!1})};var gk=/^\.google\.(com?\.)?[a-z]{2,3}$/,hk=/\.(cn|com\.bi|do|sl|ba|by|ma|am)$/;function ik(a){return gk.test(a)&&!hk.test(a)}var jk=p;function kk(a){a="https://adservice"+(a+"/adsid/integrator.js");var b=["domain="+encodeURIComponent(p.location.hostname)];X[3]>=+new Date&&b.push("adsid="+encodeURIComponent(X[1]));return a+"?"+b.join("&")}var X,Y; +function lk(){jk=p;X=jk.googleToken=jk.googleToken||{};var a=+new Date;X[1]&&X[3]>a&&0=+new Date)||"NT"==X[1]);var m=!(X[3]>=+new Date)&& +0!=b;if(k||d||m)d=+new Date,e=d+1E3*e,f=d+1E3*f,1E-5>Math.random()&&ae("https://pagead2.googlesyndication.com/pagead/gen_204?id=imerr&err="+b,null),h[5]=b,h[1]=a,h[2]=e,h[3]=f,h[4]=g,h[6]=c,lk();if(k||!mk.ka()){b=mk.Ka();for(a=0;a=+new Date&&X[2]>=+new Date||mk.Sa()};var ok=Ab("script"); +function pk(){E.google_sa_impl&&!E.document.getElementById("google_shimpl")&&(E.google_sa_queue=null,E.google_sl_win=null,E.google_sa_impl=null);if(!E.google_sa_queue){E.google_sa_queue=[];E.google_sl_win=E;E.google_process_slots=function(){return qk(E)};var a=rk();Fc(E.Promise)&&Fc(E.Symbol)?oc(E.document,a).id="google_shimpl":(a=fc(document,"IFRAME"),a.id="google_shimpl",a.style.display="none",E.document.documentElement.appendChild(a),Wi(E,"google_shimpl","<"+(ok+">google_sl_win=window.parent;google_async_iframe_id='google_shimpl';")+sk()+""),a.contentWindow.document.close())}}var qk=Cf(215,function(a){var b=a.google_sa_queue,c=b.shift();a.google_sa_impl||Df("shimpl",{t:"no_fn"});"function"==xa(c)&&Bf(216,c);b.length&&a.setTimeout(function(){return qk(a)},0)});function tk(a,b,c){a.google_sa_queue=a.google_sa_queue||[];a.google_sa_impl?c(b):a.google_sa_queue.push(b)}function sk(){var a=rk();return"<"+ok+' src="'+a+'">"} +function rk(){var a="/show_ads_impl.js";a=void 0===a?"/show_ads_impl.js":a;a:{if(Tc)try{var b=E.google_cafe_host||E.top.google_cafe_host;if(b){var c=b;break a}}catch(d){}c=Xc()}return Pf(c,["/pagead/js/",Sc(),"/r20190131",a,""].join(""),"https")} +function uk(a,b,c,d){return function(){var e=!1;d&&Tj().al(3E4);try{Wi(a,b,c),e=!0}catch(g){var f=Lg().google_jobrunner;Sj(f)&&f.rl()}e&&(e=Yj("google_async_rrc",c),(new Xj(a)).set(b,uk(a,b,e,!1)))}} +function vk(a){if(!Xi)a:{for(var b=[p.top],c=[],d=0,e;e=b[d++];){c.push(e);try{if(e.frames)for(var f=e.frames.length,g=0;gb.length;++g)b.push(e.frames[g])}catch(k){}}for(b=0;b");m=m.join(" ")}var n=e.id; +var r="";r=void 0===r?"":r;g="border:none;height:"+h+"px;margin:0;padding:0;position:relative;visibility:visible;width:"+(g+"px;background-color:transparent;");n=['':">",'',m,""].join("");16==f.google_reactive_ad_format?(f=d.createElement("div"),f.innerHTML=n,c.appendChild(f.firstChild)):c.innerHTML=n;return e.id})} +function xk(a,b,c,d){var e=b.google_ad_width,f=b.google_ad_height;(!Bb&&!Cb||J(325))&&J(284)&&(b.google_enable_single_iframe=!0);var g={};null!=e&&(g.width=e&&'"'+e+'"');null!=f&&(g.height=f&&'"'+f+'"');g.frameborder='"0"';g.marginwidth='"0"';g.marginheight='"0"';g.vspace='"0"';g.hspace='"0"';g.allowtransparency='"true"';g.scrolling='"no"';g.allowfullscreen='"true"';g.onload='"'+Zj+'"';d=d(a,g,b);yk(a,c,b);(c=vk(b.google_ad_client))&&a.document.documentElement.appendChild(c);c=Ga;e=(new Date).getTime(); +b.google_lrv=Sc();b.google_async_iframe_id=d;b.google_unique_id=fe(a);b.google_start_time=c;b.google_bpp=e>c?e-c:1;b.google_async_rrc=0;a.google_sv_map=a.google_sv_map||{};a.google_sv_map[d]=b;a.google_t12n_vars=Ch;if(b.google_enable_single_iframe){var h={pubWin:a,iframeWin:null,vars:b};tk(a,function(){a.google_sa_impl(h)},a.document.getElementById(d+"_anchor")?Uj:Vj)}else tk(a,uk(a,d,["","<"+ok+">","google_sl_win=window.parent;google_iframe_start_time=new Date().getTime();", +'google_async_iframe_id="'+d+'";',"","<"+ok+">window.parent.google_sa_impl({iframeWin: window, pubWin: window.parent, vars: window.parent['google_sv_map']['"+(d+"']});",""].join(""),!0),a.document.getElementById(d)?Uj:Vj)} +function yk(a,b,c){var d=c.google_ad_output,e=c.google_ad_format,f=c.google_ad_width||0,g=c.google_ad_height||0;e||"html"!=d&&null!=d||(e=f+"x"+g);d=!c.google_ad_slot||c.google_override_format||!bc[c.google_ad_width+"x"+c.google_ad_height]&&"aa"==c.google_loader_used;e&&d?e=e.toLowerCase():e="";c.google_ad_format=e;if("number"!==typeof c.google_reactive_sra_index||!c.google_ad_unit_key){e=[c.google_ad_slot,c.google_orig_ad_format||c.google_ad_format,c.google_ad_type,c.google_orig_ad_width||c.google_ad_width, +c.google_orig_ad_height||c.google_ad_height];d=[];f=0;for(g=b;g&&25>f;g=g.parentNode,++f)9===g.nodeType?d.push(""):d.push(g.id);(d=d.join())&&e.push(d);c.google_ad_unit_key=vc(e.join(":")).toString();var h=void 0===h?!1:h;e=[];for(d=0;b&&25>d;++d){f="";void 0!==h&&h||(f=(f=9!==b.nodeType&&b.id)?"/"+f:"");a:{if(b&&b.nodeName&&b.parentElement){g=b.nodeName.toString().toLowerCase();for(var k=b.parentElement.childNodes,m=0,n=0;ne;++e){var u=w.frames;for(d=0;de){var f=parseInt(a.style.height,10);d=!!bc[d+"x"+f];var g=e;if(d){var h=cc(e,f);if(h)g=h,b.google_ad_format=h+"x"+f+"_0ads_al";else throw new O("No slot size for availableWidth="+e);}b.google_ad_resize=!0;b.google_ad_width=g;d||(b.google_ad_format=null,b.google_override_format=!0);e=g;a.style.width=e+"px";f=yj(e,"auto",c,a,b);g=e;f.a.ba(c,b,a);aj(f, +g,b);f=f.a;b.google_responsive_formats=null;f.minWidth()>e&&!d&&(b.google_ad_width=f.minWidth(),a.style.width=f.minWidth()+"px")}}d=a.offsetWidth||R(a,c,"width",G)||b.google_ad_width||0;e=Fa(yj,d,"auto",c,a,b,!1,!0);f=le(c)||c;g=b.google_ad_client;f=f.location&&"#ftptohbh"===f.location.hash?2:Ah(f.location,"google_responsive_slot_debug")||Ah(f.location,"google_responsive_slot_preview")||J(217)?1:J(218)?2:Ih(f,1,g)?1:0;if(g=0!==f)b:if(!(488>P(c)||J(216))||b.google_reactive_ad_format||Kj(c,b)||jg(a, +b))g=!1;else{for(g=a;g;g=g.parentElement){h=pc(g,c);if(!h){b.gfwrnwer=18;g=!1;break b}if(!Oa(["static","relative"],h.position)){b.gfwrnwer=17;g=!1;break b}}if(!J(216)&&(g=og(c,a,d,.3,b),!0!==g)){b.gfwrnwer=g;g=!1;break b}g=ke(c)==c?!0:!1}g?(b.google_resizing_allowed=!0,b.ovlp=!0,2===f?(f={},aj(e(),d,f),b.google_resizing_width=f.google_ad_width,b.google_resizing_height=f.google_ad_height,f.ds&&(b.ds=f.ds),b.iaaso=!1):(b.google_ad_format="auto",b.iaaso=!0,b.armr=1),d=!0):d=!1;if(e=Kj(c,b))Mj(e,a,b, +c,d);else{if(jg(a,b)){if(d=pc(a,c))a.style.width=d.width,a.style.height=d.height,ig(d,b);b.google_ad_width||(b.google_ad_width=a.offsetWidth);b.google_ad_height||(b.google_ad_height=a.offsetHeight);b.google_loader_features_used=256;b.google_responsive_auto_format=Dk(c)}else ig(a.style,b);c.location&&"#gfwmrp"==c.location.hash||12==b.google_responsive_auto_format&&"true"==b.google_full_width_responsive&&!me(c,Vh.s)?Mj(10,a,b,c,!1):me(c,Wh.s)&&12==b.google_responsive_auto_format&&(a=pg(a.offsetWidth|| +parseInt(a.style.width,10)||b.google_ad_width,c,a,b),!0!==a?(b.efwr=!1,b.gfwrnwer=a):b.efwr=!0)}};function Fk(a,b,c){var d=window;return function(){var e=ef(),f=3;try{var g=b.apply(this,arguments)}catch(h){f=13;if(c)return c(a,h),g;throw h;}finally{d.google_measure_js_timing&&e&&(e={label:a.toString(),value:e,duration:(ef()||0)-e,type:f},f=d.google_js_reporting_queue=d.google_js_reporting_queue||[],2048>f.length&&f.push(e))}return g}}function Gk(a,b){return Fk(a,b,function(c,d){(new rf).J(c,d)})};function Z(a,b){return null==b?"&"+a+"=null":"&"+a+"="+Math.floor(b)} +function Hk(){var a=this;this.I=this.$=this.o=this.j=this.f=0;this.K=!1;this.u=this.g=this.c=0;this.L=.1>Math.random();this.P=p===p.top;var b=document.querySelector("[data-google-query-id]");if(this.a=b?b.getAttribute("data-google-query-id"):null)b=null;else{if("number"!==typeof p.goog_pvsid)try{Object.defineProperty(p,"goog_pvsid",{value:Math.floor(Math.random()*Math.pow(2,52))})}catch(c){}b=Number(p.goog_pvsid)||-1}this.T=b;this.L&&(b="https://pagead2.googlesyndication.com/pagead/gen_204?id=plmetrics"+ +(this.a?"&qqid="+encodeURIComponent(this.a):Z("pvsid",this.T)),b+=Z("test",1),b+="&top="+(this.P?1:0),Ik(b));this.aa=new PerformanceObserver(Gk(640,function(c){c=ea(c.getEntries());for(var d=c.next();!d.done;d=c.next()){d=d.value;if("layout-shift"===d.entryType){var e=d;e.hadRecentInput||J(241)&&!(.01a.j&&(a.j=Number(e.value)),a.o+=1)}"largest-contentful-paint"===d.entryType&&(e=d,a.$=Math.floor(e.renderTime||e.loadTime));"first-input"===d.entryType&& +(e=d,a.I=Number((e.processingStart-e.startTime).toFixed(3)),a.K=!0);"longtask"===d.entryType&&(a.c+=d.duration,d.duration>a.g&&(a.g=d.duration),a.u+=1)}}));this.U=!1;this.b=Gk(641,this.b.bind(this))}na(Hk,Yc); +Hk.prototype.b=function(){var a=document;if(2===({visible:1,hidden:2,prerender:3,preview:4,unloaded:5}[a.visibilityState||a.webkitVisibilityState||a.mozVisibilityState||""]||0)&&!this.U){this.U=!0;this.aa.takeRecords();a="https://pagead2.googlesyndication.com/pagead/gen_204?id=plmetrics";window.LayoutShift&&(a+="&cls="+this.f.toFixed(3),a+="&mls="+this.j.toFixed(3),a+=Z("nls",this.o));window.LargestContentfulPaint&&(a+=Z("lcp",this.$));window.PerformanceEventTiming&&this.K&&(a+=Z("fid",this.I));window.PerformanceLongTaskTiming&& +(a+=Z("cbt",this.c),a+=Z("mbt",this.g),a+=Z("nlt",this.u));for(var b=0,c=ea(document.getElementsByTagName("iframe")),d=c.next();!d.done;d=c.next())if(d=d.value,d.id.includes("google_ads_iframe_")||d.id.includes("aswift"))b+=1;a+=Z("nif",b);a+=Z("ifi",ee(window));b=Ph.h().a();a+="&eid="+encodeURIComponent(b.join());this.L&&(a+=Z("test",1));a+="&top="+(this.P?1:0);a+=this.a?"&qqid="+encodeURIComponent(this.a):Z("pvsid",this.T);Ik(a)}}; +function Ik(a){window.fetch(a,{keepalive:!0,credentials:"include",redirect:"follow",method:"get",mode:"no-cors"})};var Jk=["https://www.google.com"],Kk=void 0;function Lk(a){this.c=Jk;this.a=2;this.b=a}na(Lk,Yc);function Mk(a){null===a.b||3<=a.a||(a.a=3,Ha(a.c,function(b){a.b.fetch(b+"/.well-known/trust-token",{keepalive:!0,redirect:"follow",method:"get",mode:"no-cors",hb:{type:"srr-token-redemption",bb:b,eb:"none"}}).then(function(c){if(!c.ok)throw Error("Network response was not ok");c.blob();a.a=5}).catch(function(){4>a.a&&(a.a=4)})}))};function Nk(a){return je.test(a.className)&&"done"!=a.getAttribute("data-adsbygoogle-status")}function Ok(a,b){a.setAttribute("data-adsbygoogle-status","done");Pk(a,b)} +function Pk(a,b){var c=window,d=ie();d.google_spfd||(d.google_spfd=Ek);(d=b.google_reactive_ads_config)||Ek(a,b,c);if(!Qk(a,b,c)){d||(c.google_lpabyc=ei(c,a));if(d){d=d.page_level_pubvars||{};if(K(E).page_contains_reactive_tag&&!K(E).allow_second_reactive_tag){if(d.pltais){oe(!1);return}throw new O("Only one 'enable_page_level_ads' allowed per page.");}K(E).page_contains_reactive_tag=!0;oe(7===d.google_pgb_reactive)}else de(c);be(ck,function(e,f){b[f]=b[f]||c[f]});b.google_loader_used="aa";b.google_reactive_tag_first= +1===(K(E).first_tag_on_page||0);Bf(164,function(){wk(c,b,a)})}} +function Qk(a,b,c){var d=b.google_reactive_ads_config;if(d){var e=d.page_level_pubvars;var f=(ya(e)?e:{}).google_tag_origin}e="string"===typeof a.className&&/(\W|^)adsbygoogle-noablate(\W|$)/.test(a.className);var g=b.google_ad_slot;var h=f||b.google_tag_origin;f=K(c);pe(f.ad_whitelist||[],g,h)?g=null:(h=f.space_collapsing||"none",g=(g=pe(f.ad_blacklist||[],g))?{pa:!0,Ea:g.space_collapsing||h}:f.remove_ads_by_default?{pa:!0,Ea:h,ha:f.ablation_viewport_offset}:null);if(g&&g.pa&&"on"!=b.google_adtest&& +!e&&(e=Bg(a,c),!g.ha||g.ha&&(e||0)>=g.ha))return a.className+=" adsbygoogle-ablated-ad-slot",c=c.google_sv_map=c.google_sv_map||{},d=za(a),c[b.google_element_uid]=b,a.setAttribute("google_element_uid",d),"slot"==g.Ea&&(null!==Dc(a.getAttribute("width"))&&a.setAttribute("width",0),null!==Dc(a.getAttribute("height"))&&a.setAttribute("height",0),a.style.width="0px",a.style.height="0px"),!0;if((e=pc(a,c))&&"none"==e.display&&!("on"==b.google_adtest||0b?-c:c}});var u=this||self;function oa(){}function w(a){a.Pa=void 0;a.g=function(){return a.Pa?a.Pa:a.Pa=new a}}function pa(a){var b=typeof a;if("object"==b)if(a){if(a instanceof Array)return"array";if(a instanceof Object)return b;var c=Object.prototype.toString.call(a);if("[object Window]"==c)return"object";if("[object Array]"==c||"number"==typeof a.length&&"undefined"!=typeof a.splice&&"undefined"!=typeof a.propertyIsEnumerable&&!a.propertyIsEnumerable("splice"))return"array";if("[object Function]"==c||"undefined"!=typeof a.call&&"undefined"!=typeof a.propertyIsEnumerable&&!a.propertyIsEnumerable("call"))return"function"}else return"null";else if("function"==b&&"undefined"==typeof a.call)return"object";return b}function qa(a){var b=pa(a);return"array"==b||"object"==b&&"number"==typeof a.length}function ra(a){return"function"==pa(a)}function sa(a){var b=typeof a;return"object"==b&&null!=a||"function"==b}function ta(a,b){var c=Array.prototype.slice.call(arguments,1);return function(){var d=c.slice();d.push.apply(d,arguments);return a.apply(this,d)}}function ua(a,b){a=a.split(".");var c=u;a[0]in c||"undefined"==typeof c.execScript||c.execScript("var "+a[0]);for(var d;a.length&&(d=a.shift());)a.length||void 0===b?c[d]&&c[d]!==Object.prototype[d]?c=c[d]:c=c[d]={}:c[d]=b}function va(a,b){function c(){}c.prototype=b.prototype;a.prototype=new c;a.prototype.constructor=a};var wa;function xa(a,b){if("string"===typeof a)return"string"!==typeof b||1!=b.length?-1:a.indexOf(b,0);for(var c=0;cb?null:"string"===typeof a?a.charAt(b):a[b]}function Fa(a,b,c){for(var d=a.length,e="string"===typeof a?a.split(""):a,f=0;fb?1:a/g,Xa=/"/g,Ya=/'/g,Za=/\x00/g,$a=/[\x00&<>"']/;function z(a,b){return-1!=a.toLowerCase().indexOf(b.toLowerCase())}function ab(a,b){return ab?1:0};var A;a:{var bb=u.navigator;if(bb){var cb=bb.userAgent;if(cb){A=cb;break a}}A=""}function B(a){return-1!=A.indexOf(a)};function db(){return B("Safari")&&!(eb()||B("Coast")||B("Opera")||B("Edge")||B("Edg/")||B("OPR")||B("Firefox")||B("FxiOS")||B("Silk")||B("Android"))}function eb(){return(B("Chrome")||B("CriOS"))&&!B("Edge")};function fb(a){$a.test(a)&&(-1!=a.indexOf("&")&&(a=a.replace(Ua,"&")),-1!=a.indexOf("<")&&(a=a.replace(Va,"<")),-1!=a.indexOf(">")&&(a=a.replace(Wa,">")),-1!=a.indexOf('"')&&(a=a.replace(Xa,""")),-1!=a.indexOf("'")&&(a=a.replace(Ya,"'")),-1!=a.indexOf("\x00")&&(a=a.replace(Za,"�")));return a}function gb(){return"opacity".replace(/\-([a-z])/g,function(a,b){return b.toUpperCase()})}function hb(a){return String(a).replace(/([A-Z])/g,"-$1").toLowerCase()}function ib(a){return a.replace(/(^|[\s]+)([a-z])/g,function(b,c,d){return c+d.toUpperCase()})};function jb(a){jb[" "](a);return a}jb[" "]=oa;function kb(a,b){try{return jb(a[b]),!0}catch(c){}return!1}function lb(a,b){var c=mb;return Object.prototype.hasOwnProperty.call(c,a)?c[a]:c[a]=b(a)};var nb=B("Opera"),C=B("Trident")||B("MSIE"),ob=B("Edge"),pb=B("Gecko")&&!(z(A,"WebKit")&&!B("Edge"))&&!(B("Trident")||B("MSIE"))&&!B("Edge"),qb=z(A,"WebKit")&&!B("Edge"),rb=qb&&B("Mobile");function sb(){var a=u.document;return a?a.documentMode:void 0}var tb;a:{var ub="",vb=function(){var a=A;if(pb)return/rv:([^\);]+)(\)|;)/.exec(a);if(ob)return/Edge\/([\d\.]+)/.exec(a);if(C)return/\b(?:MSIE|rv)[: ]([^\);]+)(\)|;)/.exec(a);if(qb)return/WebKit\/(\S+)/.exec(a);if(nb)return/(?:Version)[ \/]?(\S+)/.exec(a)}();vb&&(ub=vb?vb[1]:"");if(C){var wb=sb();if(null!=wb&&wb>parseFloat(ub)){tb=String(wb);break a}}tb=ub}var xb=tb,mb={};function yb(a){return lb(a,function(){for(var b=0,c=Ta(String(xb)).split("."),d=Ta(String(a)).split("."),e=Math.max(c.length,d.length),f=0;0==b&&f>>=7;a.a.push(b)}function Ib(a,b){a.a.push(b>>>0&255);a.a.push(b>>>8&255);a.a.push(b>>>16&255);a.a.push(b>>>24&255)};function Jb(){this.b=[];this.a=new Gb}function Kb(a,b,c){if(null!=c){Hb(a.a,8*b);a=a.a;var d=c;c=0>d;d=Math.abs(d);b=d>>>0;d=Math.floor((d-b)/4294967296);d>>>=0;c&&(d=~d>>>0,b=(~b>>>0)+1,4294967295>>7|b<<25)>>>0,b>>>=7;a.a.push(c)}};function Lb(){}var Mb="function"==typeof Uint8Array,Nb=[];function Ob(a){var b=a.c+a.f;a.a[b]||(a.b=a.a[b]={})}function Pb(a,b){if(b");f=f.join("")}f=ic(e,f);g&&("string"===typeof g?f.className=g:Array.isArray(g)?f.className=g.join(" "):dc(f,g));2e?encodeURIComponent(zd(a,b,c,d,e+1)):"...";return encodeURIComponent(String(a))}function Bd(a,b,c,d){a.a.push(b);a.b[b]=yd(c,d)}function Cd(a,b,c){b=b+"//pagead2.googlesyndication.com"+c;var d=Dd(a)-c.length;if(0>d)return"";a.a.sort(function(k,q){return k-q});c=null;for(var e="",f=0;f=m.length){d-=m.length;b+=m;e=a.c;break}a.f&&(e=d,m[e-1]==a.c&&--e,b+=m.substr(0,e),e=a.c,d=0);c=null==c?g:c}}a="";null!=c&&(a=e+"trn="+c);return b+a}function Dd(a){var b=1,c;for(c in a.b)b=c.length>b?c.length:b;return 3997-b-a.c.length-1};function Ed(){this.b=new sd;this.a=qd()?new pd:new O}Ed.prototype.setInterval=function(a,b){return E.setInterval(a,b)};Ed.prototype.clearInterval=function(a){E.clearInterval(a)};Ed.prototype.setTimeout=function(a,b){return E.setTimeout(a,b)};Ed.prototype.clearTimeout=function(a){E.clearTimeout(a)};function Fd(a){P();var b=J()||E;Hc(b,a,!1)}w(Ed);function Gd(){}function P(){var a=Gd.g();if(!a.a){if(!E)throw Error("Context has not been set and window is undefined.");a.a=Ed.g()}return a.a}w(Gd);function Hd(a){this.h=null;a||(a=[]);this.f=-1;this.a=a;a:{if(a=this.a.length){--a;var b=this.a[a];if(!(null===b||"object"!=typeof b||Array.isArray(b)||Mb&&b instanceof Uint8Array)){this.c=a- -1;this.b=b;break a}}this.c=Number.MAX_VALUE}}va(Hd,Lb);function Id(a){this.f=a;this.a=-1;this.b=this.c=0}function Jd(a,b){return function(c){for(var d=[],e=0;eMath.random())}function Wd(a){a&&R&&Ud()&&(R.clearMarks("goog_"+a.label+"_"+a.uniqueId+"_start"),R.clearMarks("goog_"+a.label+"_"+a.uniqueId+"_end"))}Vd.prototype.start=function(a,b){if(!this.a)return null;var c=Rd()||Qd();a=new Sd(a,b,c);b="goog_"+a.label+"_"+a.uniqueId+"_start";R&&Ud()&&R.mark(b);return a};function Xd(){var a=Yd;this.i=Zd;this.h="jserror";this.f=!0;this.b=null;this.j=this.c;this.a=void 0===a?null:a}function $d(a,b,c){return Jd(Ld().a,function(){try{if(a.a&&a.a.a){var d=a.a.start(b.toString(),3);var e=c();var f=a.a,g=d;if(f.a&&"number"===typeof g.value){var h=Rd()||Qd();g.duration=h-g.value;var p="goog_"+g.label+"_"+g.uniqueId+"_end";R&&Ud()&&R.mark(p);!f.a||2048c.height?p>k?(d=p,e=m):(d=k,e=q):pc++;){if(a===b)return!0;try{a:{var d=void 0;if(Zb&&!(C&&yb("9")&&!yb("10")&&u.SVGElement&&a instanceof u.SVGElement)&&(d=a.parentElement)){var e=d;break a}d=a.parentNode;e=sa(d)&&1==d.nodeType?d:null}if(a=e||a){var f=H(a),g=f&&gc(f),h=g&&g.frameElement;h&&(a=h)}}catch(p){break}}return!1}function Se(a,b,c){if(!a||!b)return!1;b=Fc(Ec(a),-b.left,-b.top);a=(b.left+b.right)/2;b=(b.top+b.bottom)/2;var d=J();pc(d.top)&&d.top&&d.top.document&&(d=d.top);if(!se(d))return!1;a=d.document.elementFromPoint(a,b);if(!a)return!1;b=(b=(b=H(c))&&b.defaultView&&b.defaultView.frameElement)&&Re(b,a);d=a===c;a=!d&&a&&mc(a,function(e){return e===c});return!(b||d||a)}function Te(a,b,c,d){return T.g().b?!1:0>=Cc(a)||0>=Dc(a)?!0:c&&d?ge(208,function(){return Se(a,b,c)}):!1};function Ue(a,b,c){var d=new I(0,0,0,0);this.time=a;this.volume=null;this.c=b;this.a=d;this.b=c};function Ve(a,b,c,d,e,f,g){this.j=a;this.i=b;this.c=c;this.a=d;this.h=e;this.b=f;this.f=g};function We(a){this.c=a;this.b=0;this.a=null}We.prototype.cancel=function(){P().clearTimeout(this.a);this.a=null};function Xe(a){var b=P();a.a=b.setTimeout(Jd(Ld().a,he(143,function(){a.b++;a.c.Ab()})),oe())};function U(a,b,c){this.o=a;this.O=void 0===c?"na":c;this.f=[];this.m=!1;this.c=new Ue(-1,!0,this);this.a=this;this.i=b;this.u=this.l=!1;this.D="uk";this.F=!1;this.j=!0}l=U.prototype;l.Z=function(){return!1};l.Oa=function(){return this.m=!0};l.W=function(){return this.a.D};l.ga=function(){return this.a.u};function Ye(a,b,c){if(!a.u||(void 0===c?0:c))a.u=!0,a.D=b,a.i=0,a.a!=a||Ze(a)}l.w=function(){return this.a.O};l.L=function(){return this.a.ib()};l.ib=function(){return{}};l.M=function(){return this.a.i};function $e(a,b){Ga(a.f,b)||(a.f.push(b),b.fa(a.a),b.R(a.c),b.S()&&(a.l=!0))}l.Sa=function(){var a=T.g();a.a=Sc(!0,this.o,a.i)};l.Ta=function(){Le(T.g(),this.o)};l.tb=function(){Me(T.g(),this.o)};l.ub=function(){var a=T.g();a.c=Sc(!1,this.o,a.i)};l.Ma=function(){return this.c.a};function af(a){a=a.a;a.Ta();a.Sa();a.ub();a.tb();a.c.a=a.Ma()}l.Ab=function(){};function bf(a){a.l=a.f.length?Ba(a.f,function(b){return b.S()}):!1}function cf(a){var b=Ia(a.f);x(b,function(c){c.R(a.c)})}function Ze(a){var b=Ia(a.f);x(b,function(c){c.fa(a.a)});a.a!=a||cf(a)}l.fa=function(a){var b=this.a;this.a=a.M()>=this.i?a:this;b!==this.a?(this.j=this.a.j,Ze(this)):this.j!==this.a.j&&(this.j=this.a.j,Ze(this))};l.R=function(a){if(a.b===this.a){var b=this.c,c=this.l;if(c=a&&(void 0===c||!c||b.volume==a.volume)&&b.c==a.c)b=b.a,c=a.a,c=b==c?!0:b&&c?b.top==c.top&&b.right==c.right&&b.bottom==c.bottom&&b.left==c.left:!1;this.c=a;!c&&cf(this)}};l.S=function(){return this.l};l.B=function(){this.F=!0};l.X=function(){return this.F};function df(a,b,c,d){this.c=a;this.a=new I(0,0,0,0);this.l=new I(0,0,0,0);this.b=b;this.D=c;this.F=d;this.C=!1;this.timestamp=-1;this.h=new Ve(b.c,this.a,new I(0,0,0,0),0,0,S(),0)}l=df.prototype;l.Aa=function(){return!0};l.H=function(){};l.La=function(){if(this.c){var a=this.c,b=this.b.a.o;try{try{var c=Ce(a.getBoundingClientRect())}catch(m){c=new I(0,0,0,0)}var d=c.right-c.left,e=c.bottom-c.top,f=Mc(a,b),g=f.x,h=f.y;var p=new I(Math.round(h),Math.round(g+d),Math.round(h+e),Math.round(g))}catch(m){p=Ec(Oe)}this.a=p}};l.bb=function(){this.l=this.b.c.a};l.P=function(){this.La();this.h=new Ve(this.b.c,this.a,this.h.c,this.h.a,this.h.h,S(),this.h.f)};l.B=function(){if(!this.X()){var a=this.b,b=a.f,c=xa(b,this);0<=c&&Array.prototype.splice.call(b,c,1);a.l&&this.S()&&bf(a);this.H();this.C=!0}};l.X=function(){return this.C};l.L=function(){return this.b.L()};l.M=function(){return this.b.M()};l.W=function(){return this.b.W()};l.ga=function(){return this.b.ga()};l.fa=function(){};l.R=function(){this.P()};l.S=function(){return this.F};function ef(a){this.h=!1;this.a=a;this.f=oa}l=ef.prototype;l.M=function(){return this.a.M()};l.W=function(){return this.a.W()};l.ga=function(){return this.a.ga()};l.create=function(a,b,c){var d=null;this.a&&(d=this.wa(a,b,c),$e(this.a,d));return d};l.Ra=function(){return this.Y()};l.Y=function(){return!1};l.mb=function(a){return this.a.Oa()?($e(this.a,this),this.f=a,!0):!1};l.fa=function(a){0==a.M()&&this.f(a.W(),this)};l.R=function(){};l.S=function(){return!1};l.B=function(){this.h=!0};l.X=function(){return this.h};l.L=function(){return{}};function ff(a,b,c){this.c=void 0===c?0:c;this.b=a;this.a=null==b?"":b}function gf(a){switch(Math.trunc(a.c)){case -16:return-16;case -8:return-8;case 0:return 0;case 8:return 8;case 16:return 16;default:return 16}}function hf(a,b){return a.cb.c?!1:a.bb.b?!1:typeof a.atypeof b.a?!1:a.a=Math.abs(this.b.s-this.a.s))};uf.prototype.h=function(){var a={};return a.b_name=this.a.U,a.v_name=this.b.U,a.b_vp_off=JSON.stringify(this.a.I),a.v_vp_off=JSON.stringify(this.b.I),a.b_vp_sz=JSON.stringify(this.a.Wa),a.v_vp_sz=JSON.stringify(this.b.Wa),a.b_exp=this.a.s,a.v_exp=this.b.s,a.efp_occ=this.a.Db,a.sbv=this.a.ia,a};function vf(){sf.call(this,"capt");this.f=[];this.c=[]}t(vf,sf);vf.prototype.i=function(a,b){sf.prototype.i.call(this,a,b);20<=this.c.length||(this.f.push(a.s),this.c.push(b.s))};vf.prototype.j=function(){return 20===this.c.length};vf.prototype.h=function(){var a=wf(this.f,this.c),b=xf(this.f,this.c),c={};return c.b_name=this.a.U,c.v_name=this.b.U,c.b_exp=this.f.join(","),c.v_exp=this.c.join(","),c.diff=a,c.diff_buckets=b,c};function wf(a,b){return Da(La(a,b),function(c){return c[0]!==c[1]})}function xf(a,b){function c(d){return.25*Math.floor(d/.25)}return wf(za(a,c),za(b,c))};function V(){this.O=this.O;this.ra=this.ra}V.prototype.O=!1;V.prototype.X=function(){return this.O};V.prototype.B=function(){this.O||(this.O=!0,this.V())};V.prototype.V=function(){if(this.ra)for(;this.ra.length;)this.ra.shift()()};function yf(a,b,c,d,e){e=void 0===e?[new tf,new uf,new vf]:e;V.call(this);this.a=a.wa(b,c,this.S());this.a.Aa();this.c=e;this.b=d}t(yf,V);yf.prototype.V=function(){this.a&&(this.a.H(),this.a.B())};function zf(a,b,c){x(a.c,function(d){var e=a.b;if(!d.l&&(d.i(b,c),d.j())){d.l=!0;var f=d.h(),g=new jf;g.add("id","av-js");g.add("type","verif");g.add("vtype",d.m);d=rf.g();g.add("i",d.a++);g.add("adk",e);lf(g,f);e=new of(g);var h=void 0===h?4E3:h;e=e.toString();/&v=[^&]+/.test(e)||(e=(f=qf())?e+"&v="+encodeURIComponent(f):e);e=e.substring(0,h);Fd(e)}})}yf.prototype.R=function(){};yf.prototype.fa=function(){};yf.prototype.S=function(){return!1};function Af(){this.a=this.b=this.c=0}function Bf(a,b,c,d){b&&(a.c+=c,a.b+=c,a.a=Math.max(a.a,a.b));if(void 0===d?!b:d)a.b=0};var Cf=[1,.75,.5,.3,0];function Df(a){this.a=a=void 0===a?Cf:a;this.b=za(this.a,function(){return new Af})}function Ef(a){return Ff(a,function(b){return b.c},!1)}function Gf(a){return Ff(a,function(b){return b.a},!0)}function Hf(a,b,c,d,e,f){var g=void 0===g?!0:g;c=f?Math.min(b,c):c;for(f=0;f=h;h=!(0=h)||d;Bf(a.b[f],g&&p,e,!g||h)}}function Ff(a,b,c){a=za(a.b,function(d){return b(d)});return c?a:If(a)}function If(a){return za(a,function(b,c,d){return 0=(this.ha()?.3:.5),a.b=Math.max(a.b,e.s),Hf(a.f,e.f,c.f,e.c,f,d),Hf(a.a,e.s,c.s,e.c,f,d),d=d||c.a!=e.a?c.isVisible()&&e.isVisible():c.isVisible(),c=!e.isVisible()||e.c,Bf(a.c,d,f,c),this.aa=b,0=a.length)throw Yf;if(b in a)return a[b++];b++}};return c}throw Error("Not implemented");}function ag(a,b){if(qa(a))try{x(a,b,void 0)}catch(c){if(c!==Yf)throw c;}else{a=$f(a);try{for(;;)b.call(void 0,a.next(),void 0,a)}catch(c){if(c!==Yf)throw c;}}}function bg(a,b){var c=1;ag(a,function(d){c=b.call(void 0,c,d)});return c}function cg(a,b){var c=$f(a);a=new Zf;a.next=function(){var d=c.next();if(b.call(void 0,d,void 0,c))return d;throw Yf;};return a}function dg(a){var b=$f(a);a=new Zf;var c=100;a.next=function(){if(0=a.bottom||a.left>=a.right?new I(0,0,0,0):a;a=this.b.c;var c=0,d=0,e=0;0<(this.a.bottom-this.a.top)*(this.a.right-this.a.left)&&(this.nb(b)?b=new I(0,0,0,0):(c=T.g().j,e=new I(0,c.height,c.width,0),c=Pe(b,this.a),d=Pe(b,T.g().a),e=Pe(b,e)));b=b.top>=b.bottom||b.left>=b.right?new I(0,0,0,0):Fc(b,-this.a.left,-this.a.top);Ne()||(d=c=0);this.h=new Ve(a,this.a,b,c,d,this.timestamp,e)};rg.prototype.w=function(){return this.b.w()};function sg(a){var b=[];tg(new ug,a,b);return b.join("")}function ug(){}function tg(a,b,c){if(null==b)c.push("null");else{if("object"==typeof b){if(Array.isArray(b)){var d=b;b=d.length;c.push("[");for(var e="",f=0;fc.time?b:c},a[0])}l.La=function(){};l.nb=function(){return!1};l.bb=function(){};l.L=function(){var a={};return Object.assign(this.b.L(),(a.niot_obs=this.u,a.niot_cbk=this.m,a))};var Sg={threshold:[0,.3,.5,.75,1]};function Tg(a,b,c,d){Pg.call(this,a,b,c,d);this.i=this.j=this.f=null}t(Tg,Pg);Tg.prototype.w=function(){return"nio"};Tg.prototype.H=function(){if(this.f&&this.c)try{this.f.unobserve(this.c),this.j?(this.j.unobserve(this.c),this.j=null):this.i&&(this.i.disconnect(),this.i=null)}catch(a){}};function Ug(a){return a.f&&a.f.takeRecords?a.f.takeRecords():[]}Tg.prototype.A=function(){var a=this;if(!this.c)return!1;var b=this.c,c=this.b.a.o,d=Ld().a;this.f=new c.IntersectionObserver(Jd(d,function(e){return Qg(a,e)}),Sg);d=Jd(d,function(){a.f.unobserve(b);a.f.observe(b);Qg(a,Ug(a))});c.ResizeObserver?(this.j=new c.ResizeObserver(d),this.j.observe(b)):c.MutationObserver&&(this.i=new u.MutationObserver(d),this.i.observe(b,{attributes:!0,childList:!0,characterData:!0,subtree:!0}));this.f.observe(b);Qg(this,Ug(this));return!0};Tg.prototype.P=function(){var a=Ug(this);0this.a.i&&(this.a=this,Ze(this)),this.i=a);return 2==a};function Xg(){Q.g();var a=T.g();return a.b||a.f?0:2}w(Wg);var Yg={},Zg=(Yg[1]=function(){return new Vg},Yg[2]=function(){return new Ng([Wg.g()])},Yg);function $g(){this.a=null;this.b=Zg}function ah(){var a=$g.g();a:{var b=N(Q.g().a,"mv");if(null!=b&&(b=a.b[b])&&(b=b())&&b.Y())break a;b=null}a.a=b}w($g);function bh(){this.done=!1;this.a={$a:0,Za:0,lc:0,eb:0,xa:-1,Hb:0,Gb:0,Ib:0};this.j=null;this.h=this.l=!1;this.i="";this.b=null;this.m=0;this.c=new We(this)}function ch(a){var b=Y;if(!b.l){b.l=!0;if(a){a=Hg();for(var c,d=0;dd?1:0)?-d:d;if(0===d)Fb=0<1/d?0:2147483648,Eb=0;else if(isNaN(d))Fb=2147483647,Eb=4294967295;else if(1.7976931348623157E308>>0,Eb=0;else if(2.2250738585072014E-308>d)d/=Math.pow(2,-1074),Fb=(q<<31|d/4294967296)>>>0,Eb=d>>>0;else{e=d;c=0;if(2<=e)for(;2<=e&&1023>c;)c++,e/=2;else for(;1>e&&-1022>>0;Eb=4503599627370496*d>>>0}Ib(k,Eb);Ib(k,Fb)}k=Qb(b,2);0!==k&&null!=k&&Kb(m,2,k);k=Qb(b,3);0!==k&&null!=k&&Kb(m,3,k);k=Qb(b,4);0!==k&&null!=k&&Kb(m,4,k);k=Qb(b,5);if(0!==k&&null!=k&&null!=k)if(Hb(m.a,40),b=m.a,0<=k)Hb(b,k);else{for(q=0;9>q;q++)b.a.push(k&127|128),k>>=7;b.a.push(1)}b=new Uint8Array(m.a.length());q=m.b;c=q.length;for(d=k=0;dq;q++)for(c=m.concat(k[q].split("")),Cb[q]=c,d=0;d>2,f=(f&3)<<4|g>>4,g=(g&15)<<2|e>>6,e&=63,c||(e=64,q||(g=64)),m.push(v[d],v[f],v[g]||"",v[e]||"");v=(n.pf=m.join(""),n)}else v={};y(a,v);return a}function kh(){x(Hg(),function(a){if(a.b.b){var b=a.l||0,c=$g.g();if(b=c.a?new yf(c.a,a.b.a,a.h,b):null)a.F=b}})}function lh(){var a=Lg.g();if(null!=a.a){var b=a.a;x(Hg(),function(c){return Of(c,b)})}}function gh(a){"osd"==a.i&&x(X.a,function(b){var c={};jg(b,0,(c.r=void 0,c))})}function hh(a,b){a=a.m;ne&&(a+=b-le);return a}function mh(a){return(a=a.match(/[&\?;](?:dc_)?adk=([0-9]+)/))&&2==a.length?parseInt(a[1],10):0}function nh(a){return(a=a.match(/[&\?;]adf=([0-9]+)/))&&2==a.length?parseInt(a[1],10):0}function oh(){var a=Y;var b=void 0===b?function(){return{}}:b;de.h="av-js";Zd.a=.01;fe([function(c){var d=Q.g(),e={};y(c,(e.bin=d.c,e.type="error",e),fd(d.a),jh(a,E),b());if(d=qf())e={},y(c,(e.v=encodeURIComponent(d),e))}])}function ph(a){var b=new qh;switch(a){case 0:case 5:return[];default:return a=4===Q.g().c,[new Ag(b),new Cg(b),new Bg(b)].concat(r(a?[]:[new yg]))}}w(bh);var Y=bh.g();function qh(){}function zg(a,b){var c=b||{};b=void 0===c.Va?{}:c.Va;c=void 0===c.Qa?{}:c.Qa;var d=c.r,e=b[0],f=jh(Y,J(),!1),g={};y(g,f,b);b={};y(b,ng(a,e,d,g),c);Ge(a.b.b,b,a.ba);return!0};function rh(a,b,c,d){Pg.call(this,a,b,c,d);this.f=function(){return null}}t(rh,Pg);rh.prototype.w=function(){return"aio"};rh.prototype.H=function(){if(this.f)try{this.f()}catch(a){}};rh.prototype.A=function(){var a=this;if(!this.c)return!1;this.f=Gc(this.b.a.o).observeIntersection(Jd(Ld().a,function(b){return Qg(a,b)}));return!0};function sh(a){a=void 0===a?E:a;ef.call(this,new U(a,2))}t(sh,ef);sh.prototype.w=function(){return"aio"};sh.prototype.Ra=function(){return T.g().b&&this.Y()};sh.prototype.Y=function(){return!T.g().f&&re(this.a.a.o)};sh.prototype.wa=function(a,b,c){return new rh(a,this.a,b,c)};function th(){U.call(this,E,2,"iem")}t(th,U);l=th.prototype;l.Ma=function(){function a(n,v){return!!b.o.document.elementFromPoint(n,v)}var b=this,c=new I(0,this.o.innerWidth||this.o.width,this.o.innerHeight||this.o.height,0),d=fc(document),e=Math.floor(c.left-d.x),f=Math.floor(c.top-d.y),g=Math.floor(c.right-d.x),h=Math.floor(c.bottom-d.y);c=a(e,f);d=a(g,h);if(c&&d)return new I(f,g,h,e);var p=a(g,f),m=a(e,h);if(c)h=Z(f,h,function(n){return a(e,n)}),g=Z(e,g,function(n){return a(n,f)});else if(p)h=Z(f,h,function(n){return a(g,n)}),e=Z(g,e,function(n){return a(n,f)});else if(m)f=Z(h,f,function(n){return a(e,n)}),g=Z(e,g,function(n){return a(n,h)});else if(d)f=Z(h,f,function(n){return a(g,n)}),e=Z(g,e,function(n){return a(n,h)});else{var k=Math.floor((e+g)/2),q=Math.floor((f+h)/2);if(!a(k,q))return new I(0,0,0,0);f=Z(q,f,function(n){return a(k,n)});h=Z(q,h,function(n){return a(k,n)});e=Z(k,e,function(n){return a(n,q)});g=Z(k,g,function(n){return a(n,q)})}return new I(f,g,h,e)};function Z(a,b,c){if(c(b))return b;for(var d=15;d--;){var e=Math.floor((a+b)/2);if(e==a||e==b)break;c(e)?a=e:b=e}return a}l.Z=function(){return T.g().b&&C&&yb(8)&&se(this.o)};l.Sa=function(){};l.Ta=function(){};l.tb=function(){};l.ub=function(){};w(th);function uh(){U.call(this,E,2,"mraid");this.J=0;this.A=this.C=!1;this.h=null;this.b=qe(this.o);this.c.a=new I(0,0,0,0);this.K=!1}t(uh,U);l=uh.prototype;l.Z=function(){return null!=this.b.G};l.ib=function(){var a={};this.J&&(a.mraid=this.J);this.C&&(a.mlc=1);a.mtop=this.b.Ob;this.h&&(a.mse=this.h);this.K&&(a.msc=1);a.mcp=this.b.va;return a};l.N=function(a,b){for(var c=[],d=1;d=Qe(Nf(a))?0:null!=a.J&&null!=a.J.match(/\/pagead\/adview\?.*ai=.*&vt=\d+/i)&&!a.rb)&&(Ic(a.J),a.rb=!0)};function $h(a,b){if(b&&b.data&&b.source){var c=b.data;if("string"!==typeof c)var d=null;else{d={};c=c.split("\n");for(var e=0;e!=c.length;++e){var f=c[e],g=f.indexOf("=");if(!(0>=g)){var h=Number(f.substr(0,g));f=f.substr(g+1);switch(h){case 36:case 26:case 15:case 8:case 11:case 16:case 5:case 18:f="true"==f;break;case 4:case 33:case 6:case 25:case 28:case 29:case 24:case 31:case 30:case 23:case 22:case 7:case 21:case 20:f=Number(f);break;case 19:case 3:if(ra(decodeURIComponent))try{f=decodeURIComponent(f)}catch(p){throw Error("Error: URI malformed: "+f);}}d[h]=f}}d=d[0]?d:null}if(c=d)if(e=c[0],Ga("goog_creative_loaded goog_dom_content_loaded goog_listener_status goog_provide_mode goog_request_monitoring goog_stop_monitoring".split(" "),e)&&(d=Eg(new nd(c[4],c[12]))))if(h=c[33],0=e}}); +pa("Promise",function(a){function b(g){this.b=0;this.g=void 0;this.a=[];var h=this.c();try{g(h.resolve,h.reject)}catch(k){h.reject(k)}}function c(){this.a=null}function d(g){return g instanceof b?g:new b(function(h){h(g)})}if(a)return a;c.prototype.b=function(g){if(null==this.a){this.a=[];var h=this;this.c(function(){h.g()})}this.a.push(g)};var e=ea.setTimeout;c.prototype.c=function(g){e(g,0)};c.prototype.g=function(){for(;this.a&&this.a.length;){var g=this.a;this.a=[];for(var h=0;h>>0),za=0;function Aa(a,b,c){return a.call.apply(a.bind,arguments)}function Ba(a,b,c){if(!a)throw Error();if(2b?null:"string"===typeof a?a.charAt(b):a[b]} +function Ka(a,b){a:{for(var c="string"===typeof a?a.split(""):a,d=a.length-1;0<=d;d--)if(d in c&&b.call(void 0,c[d],d,a)){b=d;break a}b=-1}return 0>b?null:"string"===typeof a?a.charAt(b):a[b]}function La(a,b){a:if("string"===typeof a)a="string"!==typeof b||1!=b.length?-1:a.indexOf(b,0);else{for(var c=0;c/g,Ya=/"/g,Za=/'/g,$a=/\x00/g;function ab(a,b){return-1!=a.indexOf(b)} +function bb(a,b){var c=0;a=Ua(String(a)).split(".");b=Ua(String(b)).split(".");for(var d=Math.max(a.length,b.length),e=0;0==c&&eb?1:0};function db(a,b){this.c=a===eb&&b||"";this.f=fb}db.prototype.b=!0;db.prototype.a=function(){return this.c.toString()};function gb(a){return a instanceof db&&a.constructor===db&&a.f===fb?a.c:"type_error:SafeUrl"}var hb=/^(?:(?:https?|mailto|ftp):|[^:/?#]*(?:[/?#]|$))/i,fb={},eb={};var ib;a:{var jb=r.navigator;if(jb){var kb=jb.userAgent;if(kb){ib=kb;break a}}ib=""}function z(a){return ab(ib,a)}function lb(a){for(var b=/(\w[\w ]+)\/([^\s]+)\s*(?:\((.*?)\))?/g,c=[],d;d=b.exec(a);)c.push([d[1],d[2],d[3]||void 0]);return c};function mb(){return(z("Chrome")||z("CriOS"))&&!z("Edge")}function nb(){function a(e){e=Ja(e,d);return c[e]||""}var b=ib;if(z("Trident")||z("MSIE"))return ob(b);b=lb(b);var c={};w(b,function(e){c[e[0]]=e[1]});var d=Da(Pa,c);return z("Opera")?a(["Version","Opera"]):z("Edge")?a(["Edge"]):z("Edg/")?a(["Edg"]):mb()?a(["Chrome","CriOS","HeadlessChrome"]):(b=b[2])&&b[1]||""} +function ob(a){var b=/rv: *([\d\.]*)/.exec(a);if(b&&b[1])return b[1];b="";var c=/MSIE +([\d\.]+)/.exec(a);if(c&&c[1])if(a=/Trident\/(\d.\d)/.exec(a),"7.0"==c[1])if(a&&a[1])switch(a[1]){case "4.0":b="8.0";break;case "5.0":b="9.0";break;case "6.0":b="10.0";break;case "7.0":b="11.0"}else b="7.0";else b=c[1];return b};function pb(a,b){a.src=Ta(b);(b=ra())&&a.setAttribute("nonce",b)};var qb={"\x00":"\\0","\b":"\\b","\f":"\\f","\n":"\\n","\r":"\\r","\t":"\\t","\x0B":"\\x0B",'"':'\\"',"\\":"\\\\","<":"\\u003C"},rb={"'":"\\'"};function sb(){return z("iPhone")&&!z("iPod")&&!z("iPad")};function tb(a){tb[" "](a);return a}tb[" "]=va;var ub=sb()||z("iPod"),vb=z("Safari")&&!(mb()||z("Coast")||z("Opera")||z("Edge")||z("Edg/")||z("OPR")||z("Firefox")||z("FxiOS")||z("Silk")||z("Android"))&&!(sb()||z("iPad")||z("iPod"));var wb={},xb=null;function A(){}var yb="function"==typeof Uint8Array;function B(a,b,c,d){a.a=null;b||(b=[]);a.o=void 0;a.c=-1;a.j=b;a:{if(b=a.j.length){--b;var e=a.j[b];if(!(null===e||"object"!=typeof e||Array.isArray(e)||yb&&e instanceof Uint8Array)){a.f=b-a.c;a.b=e;break a}}a.f=Number.MAX_VALUE}a.l={};if(c)for(b=0;be;e++){var f=c.concat(d[e].split(""));wb[e]=f;for(var g=0;g> +2;k=(k&3)<<4|l>>4;l=(l&15)<<2|h>>6;h&=63;f||(h=64,e||(l=64));c.push(b[g],b[k],b[l]||"",b[h]||"")}return c.join("")};try{return JSON.stringify(this.j&&this.j,Hb)}finally{Uint8Array.prototype.toJSON=a}}:function(){return JSON.stringify(this.j&&this.j,Hb)};function Hb(a,b){return"number"!==typeof b||!isNaN(b)&&Infinity!==b&&-Infinity!==b?b:String(b)};function Ib(a){B(this,a,Jb,null)}v(Ib,A);function Kb(a){B(this,a,null,null)}v(Kb,A);var Jb=[2,3];function Lb(a){B(this,a,null,null)}v(Lb,A);function Mb(a){var b=new Lb;return Db(b,1,a)}function Nb(a,b){return Db(a,2,b)}function Ob(a,b){return Db(a,3,b)}function Pb(a,b){return Db(a,4,b)};var Qb=document,Rb=window,Sb,Tb=null,Ub=Qb.getElementsByTagName("script");Ub&&Ub.length&&(Tb=Ub[Ub.length-1]);Sb=Tb;var Vb={"120x90":!0,"160x90":!0,"180x90":!0,"200x90":!0,"468x15":!0,"728x15":!0};function Wb(a,b){if(15==b){if(728<=a)return 728;if(468<=a)return 468}else if(90==b){if(200<=a)return 200;if(180<=a)return 180;if(160<=a)return 160;if(120<=a)return 120}return null};function Xb(a){this.a=a||{cookie:""}} +Xb.prototype.set=function(a,b,c){var d=!1;if("object"===typeof c){var e=c.Ia;d=c.ya||!1;var f=c.domain||void 0;var g=c.path||void 0;var h=c.ra}if(/[;=\s]/.test(a))throw Error('Invalid cookie name "'+a+'"');if(/[;\r\n]/.test(b))throw Error('Invalid cookie value "'+b+'"');void 0===h&&(h=-1);this.a.cookie=a+"="+b+(f?";domain="+f:"")+(g?";path="+g:"")+(0>h?"":0==h?";expires="+(new Date(1970,1,1)).toUTCString():";expires="+(new Date(+new Date+1E3*h)).toUTCString())+(d?";secure":"")+(null!=e?";samesite="+ +e:"")};Xb.prototype.get=function(a,b){for(var c=a+"=",d=(this.a.cookie||"").split(";"),e=0,f;e>2)+a.charCodeAt(d)&4294967295;return 0Math.random()});function mc(a,b){var c=-1;try{a.localStorage&&(c=parseInt(a.localStorage.getItem(b),10))}catch(d){return null}return 0<=c&&1E3>c?c:null}function nc(a){return hc()?null:Math.floor(1E3*ic(a))} +function oc(a,b,c){try{if(a.localStorage)return a.localStorage.setItem(b,c),c}catch(d){}return null}function pc(a,b){var c=nc(a);return c&&oc(a,b,String(c))?c:null}var gc=Ma(function(){return lc("MSIE")});function lc(a){return ab(ib,a)}var qc=/^([0-9.]+)px$/,rc=/^(-?[0-9.]{1,30})$/;function sc(a){return/^true$/.test(a)}function tc(a){return(a=qc.exec(a))?+a[1]:null}function uc(a){a=a&&a.toString&&a.toString();return"string"===typeof a&&ab(a,"[native code]")} +var vc=Ma(function(){return!bc()&&(z("iPod")||z("iPhone")||z("Android")||z("IEMobile"))?2:bc()?1:0});function wc(a,b){var c="https://pagead2.googlesyndication.com/pagead/gen_204?id="+b;jc(a,function(d,e){d&&(c+="&"+e+"="+encodeURIComponent(d))});window.fetch(c,{keepalive:!0,credentials:"include",redirect:"follow",method:"get",mode:"no-cors"})};function F(a){a=parseFloat(a);return isNaN(a)?0:a}var xc=/^([\w-]+\.)*([\w-]{2,})(:[0-9]+)?$/;function yc(a,b){return a?(a=a.match(xc))?a[0]:b:b};function zc(){return"r20200428"}var Ac=sc("false"),Bc=sc("false"),Cc=sc("false"),Dc=sc("false")||!Bc;function Ec(){return yc("","pagead2.googlesyndication.com")};function Fc(){};/* + Copyright (c) Microsoft Corporation. All rights reserved. + Licensed under the Apache License, Version 2.0 (the "License"); you may not use + this file except in compliance with the License. You may obtain a copy of the + License at http://www.apache.org/licenses/LICENSE-2.0 + + THIS CODE IS PROVIDED ON AN *AS IS* BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY + KIND, EITHER EXPRESS OR IMPLIED, INCLUDING WITHOUT LIMITATION ANY IMPLIED + WARRANTIES OR CONDITIONS OF TITLE, FITNESS FOR A PARTICULAR PURPOSE, + MERCHANTABLITY OR NON-INFRINGEMENT. + + See the Apache Version 2.0 License for specific language governing permissions + and limitations under the License. +*/ +function Gc(a){B(this,a,Hc,Ic)}v(Gc,A);var Hc=[2,8],Ic=[[3,4,5],[6,7]];function Jc(a){return null!=a?!a:a}function Kc(a,b){for(var c=!1,d=0;da;case 12:return(new RegExp(a)).test(e); +case 10:return-1==bb(e,a);case 11:return 1==bb(e,a)}}}}function Nc(a,b){return!a||!(!b||!Lc(a,b))};function Oc(a){B(this,a,Pc,null)}v(Oc,A);var Pc=[4];function Qc(a){B(this,a,Rc,Sc)}v(Qc,A);function Tc(a){B(this,a,null,null)}v(Tc,A);var Rc=[5],Sc=[[1,2,3,6,7]];function Uc(){var a={};this.a=(a[3]={},a[4]={},a[5]={},a)}wa(Uc);var Vc=sc("false");function Wc(a,b){switch(b){case 1:return D(a,1,0);case 2:return D(a,2,0);case 3:return D(a,3,0);case 6:return D(a,6,0);default:return null}}function Xc(a,b){if(!a)return null;switch(b){case 1:return a=C(a,1),a=null==a?a:!!a,null==a?!1:a;case 7:return D(a,3,"");case 2:return Cb(a,2);case 3:return D(a,3,"");case 6:return C(a,4);default:return null}}var Yc=Ma(function(){if(!Vc)return{};try{var a=window.sessionStorage&&window.sessionStorage.getItem("GGDFSSK");if(a)return JSON.parse(a)}catch(b){}return{}}); +function Zc(a,b,c,d){d=void 0===d?0:d;var e=Yc();if(e[a]&&null!=e[a][b])return e[a][b];b=$c(d)[a][b];if(!b)return c;b=new Qc(b);b=ad(b);a=Xc(b,a);return null!=a?a:c}function ad(a){var b=Uc.h().a;if(b){var c=Ka(E(a,Tc,5),function(d){return Nc(Fb(d,Gc,1),b)});if(c)return Fb(c,Oc,2)}return Fb(a,Oc,4)}function bd(){this.a={};this.b=[]}wa(bd);function cd(a,b,c){return!!Zc(1,a,void 0===b?!1:b,c)}function dd(a,b,c){b=void 0===b?0:b;a=Number(Zc(2,a,b,c));return isNaN(a)?b:a} +function ed(a,b,c){return Zc(3,a,void 0===b?"":b,c)}function fd(a,b,c){b=void 0===b?[]:b;return Zc(6,a,b,c)}function $c(a){var b={};return bd.h().a[a]||(bd.h().a[a]=(b[1]={},b[2]={},b[3]={},b[6]={},b))}function gd(a,b){var c=$c(b);jc(a,function(d,e){return jc(d,function(f,g){return c[e][g]=f})})}function hd(a,b){var c=$c(b);w(a,function(d){var e=Bb(d,Sc[0]),f=Wc(d,e);f&&(c[e][f]=d.j)})} +function id(a,b){var c=$c(b);w(a,function(d){var e=new Qc(d),f=Bb(e,Sc[0]);(e=Wc(e,f))&&(c[f][e]||(c[f][e]=d))})}function jd(){return Ga(Object.keys(bd.h().a),function(a){return Number(a)})}function kd(a){La(bd.h().b,a)||gd($c(4),a)};function G(a){this.methodName=a}var ld=new G(1),md=new G(15),nd=new G(2),od=new G(3),pd=new G(4),qd=new G(5),rd=new G(6),sd=new G(7),td=new G(8),ud=new G(9),vd=new G(10),wd=new G(11),xd=new G(12),yd=new G(13),zd=new G(14);function H(a,b,c){c.hasOwnProperty(a.methodName)||Object.defineProperty(c,String(a.methodName),{value:b})}function Ad(a,b,c){return b[a.methodName]||c||function(){}}function Bd(a){H(qd,cd,a);H(rd,dd,a);H(sd,ed,a);H(td,fd,a);H(yd,id,a);H(md,kd,a)} +function Cd(a){H(pd,function(b){Uc.h().a=b},a);H(ud,function(b,c){var d=Uc.h();d.a[3][b]||(d.a[3][b]=c)},a);H(vd,function(b,c){var d=Uc.h();d.a[4][b]||(d.a[4][b]=c)},a);H(wd,function(b,c){var d=Uc.h();d.a[5][b]||(d.a[5][b]=c)},a);H(zd,function(b){for(var c=Uc.h(),d=fa([3,4,5]),e=d.next();!e.done;e=d.next()){var f=e.value;e=void 0;var g=c.a[f];f=b[f];for(e in f)g[e]=f[e]}},a)}function Dd(a){a.hasOwnProperty("init-done")||Object.defineProperty(a,"init-done",{value:!0})};function Ed(){this.b=function(a,b){return void 0===b?!1:b};this.a=function(){}}function Fd(a,b,c){a.b=function(d,e){return Ad(qd,b)(d,e,c)};a.a=function(){Ad(md,b)(c)}}wa(Ed);function I(a){var b=void 0===b?!1:b;return Ed.h().b(a,b)};function Gd(a){a=void 0===a?r:a;var b=a.context||a.AMP_CONTEXT_DATA;if(!b)try{b=a.parent.context||a.parent.AMP_CONTEXT_DATA}catch(c){}try{if(b&&b.pageViewId&&b.canonicalUrl)return b}catch(c){}return null}function Hd(a){return(a=a||Gd())?cc(a.master)?a.master:null:null};function Id(a,b){r.google_image_requests||(r.google_image_requests=[]);var c=r.document.createElement("img");if(b){var d=function(e){b&&b(e);c.removeEventListener&&c.removeEventListener("load",d,!1);c.removeEventListener&&c.removeEventListener("error",d,!1)};Yb(c,"load",d);Yb(c,"error",d)}c.src=a;r.google_image_requests.push(c)};function Jd(a,b){if(a)for(var c in a)Object.prototype.hasOwnProperty.call(a,c)&&b.call(void 0,a[c],c,a)}function Kd(a){return!(!a||!a.call)&&"function"===typeof a}function Ld(a){"google_onload_fired"in a||(a.google_onload_fired=!1,Yb(a,"load",function(){a.google_onload_fired=!0}))}function Md(a){a=a.google_unique_id;return"number"===typeof a?a:0}function Nd(a){a=Hd(Gd(a))||a;a=a.google_unique_id;return"number"===typeof a?a:0}var Od=!!window.google_async_iframe_id,Pd=Od&&window.parent||window; +function Qd(){if(Od&&!cc(Pd)){var a="."+Qb.domain;try{for(;2e?encodeURIComponent(ge(a,b,c,d,e+1)):"...";return encodeURIComponent(String(a))}function ie(a,b,c,d){a.a.push(b);a.b[b]=fe(c,d)} +function je(a,b,c){b=b+"//pagead2.googlesyndication.com"+c;var d=ke(a)-c.length;if(0>d)return"";a.a.sort(function(n,p){return n-p});c=null;for(var e="",f=0;f=l.length){d-=l.length;b+=l;e=a.c;break}a.f&&(e=d,l[e-1]==a.c&&--e,b+=l.substr(0,e),e=a.c,d=0);c=null==c?g:c}}a="";null!=c&&(a=e+"trn="+c);return b+a} +function ke(a){var b=1,c;for(c in a.b)b=c.length>b?c.length:b;return 3997-b-a.c.length-1};function le(a,b,c,d,e,f){if((d?a.a:Math.random())<(e||.01))try{if(c instanceof ee)var g=c;else g=new ee,jc(c,function(k,l){var n=g,p=n.g++;k=fe(l,k);n.a.push(p);n.b[p]=k});var h=je(g,a.b,"/pagead/gen_204?id="+b+"&");h&&("undefined"===typeof f?Id(h,null):Id(h,void 0===f?null:f))}catch(k){}};var me=null;function ne(){if(null===me){me="";try{var a="";try{a=r.top.location.hash}catch(c){a=r.location.hash}if(a){var b=a.match(/\bdeid=([\d,]+)/);me=b?b[1]:""}}catch(c){}}return me};function oe(){var a=r.performance;return a&&a.now&&a.timing?Math.floor(a.now()+a.timing.navigationStart):+new Date}function pe(){var a=void 0===a?r:a;return(a=a.performance)&&a.now?a.now():null};function qe(a,b,c){this.label=a;this.type=b;this.value=c;this.duration=0;this.uniqueId=Math.random();this.slotId=void 0};var L=r.performance,re=!!(L&&L.mark&&L.measure&&L.clearMarks),se=Ma(function(){var a;if(a=re)a=ne(),a=!!a.indexOf&&0<=a.indexOf("1337");return a});function te(){var a=ue;this.b=[];this.c=a||r;var b=null;a&&(a.google_js_reporting_queue=a.google_js_reporting_queue||[],this.b=a.google_js_reporting_queue,b=a.google_measure_js_timing);this.a=se()||(null!=b?b:1>Math.random())} +function ve(a){a&&L&&se()&&(L.clearMarks("goog_"+a.label+"_"+a.uniqueId+"_start"),L.clearMarks("goog_"+a.label+"_"+a.uniqueId+"_end"))}te.prototype.start=function(a,b){if(!this.a)return null;var c=pe()||oe();a=new qe(a,b,c);b="goog_"+a.label+"_"+a.uniqueId+"_start";L&&se()&&L.mark(b);return a};function we(){var a=xe;this.l=ye;this.c=!0;this.b=null;this.g=this.B;this.a=void 0===a?null:a;this.f=!1}m=we.prototype;m.ha=function(a){this.g=a};m.Y=function(a){this.b=a};m.ia=function(a){this.c=a};m.ja=function(a){this.f=a}; +m.U=function(a,b,c){try{if(this.a&&this.a.a){var d=this.a.start(a.toString(),3);var e=b();var f=this.a;b=d;if(f.a&&"number"===typeof b.value){var g=pe()||oe();b.duration=g-b.value;var h="goog_"+b.label+"_"+b.uniqueId+"_end";L&&se()&&L.mark(h);!f.a||2048(void 0===c?.01:c))return this.b;ae(b)||(b=new $d(b,{context:a,id:void 0===e?"jserror":e}));if(d||this.a)b.meta={},this.a&&this.a(b.meta),d&&d(b.meta);r.google_js_errors=r.google_js_errors||[];r.google_js_errors.push(b);r.error_rep_loaded||(dc(r.document,r.location.protocol+"//pagead2.googlesyndication.com/pagead/js/err_rep.js"),r.error_rep_loaded=!0);return this.b}; +m.U=function(a,b,c){try{var d=b()}catch(e){if(!this.c(a,e,.01,c,"jserror"))throw e;}return d};m.ea=function(a,b,c,d){var e=this;return function(f){for(var g=[],h=0;h=Ie&&(He.a=Ie);N=new we;N.Y(function(a){Fe(a);Ge(a)});N.ja(!0);"complete"==ue.document.readyState?Be():xe.a&&Yb(ue,"load",function(){Be()});function Je(a,b){return N.U(a,b,void 0)}function Ke(a,b){return N.ea(a,b,void 0,void 0)};function Le(){this.wasPlaTagProcessed=!1;this.wasReactiveAdConfigReceived={};this.adCount={};this.wasReactiveAdVisible={};this.stateForType={};this.reactiveTypeEnabledInAsfe={};this.wasReactiveTagRequestSent=!1;this.reactiveTypeDisabledByPublisher={};this.tagSpecificState={};this.improveCollisionDetection=1;this.messageValidationEnabled=!1;this.floatingAdsStacking=new Me}function Me(){this.maxZIndexRestrictions={};this.nextRestrictionId=0;this.maxZIndexListeners=[]};function Ne(a){a=a.document;var b={};a&&(b="CSS1Compat"==a.compatMode?a.documentElement:a.body);return b||{}}function O(a){return Ne(a).clientWidth};function Oe(a,b,c){a=a.document;for(var d=b.id,e=0;!d||a.getElementById(d+"_anchor");)d="aswift_"+e++;b.id=d;b.name=d;d=c.google_ad_width;e=c.google_ad_height;var f=c.gml,g=c.gmr,h=c.gzi;f=(f?"margin-left:"+f+";":"")+(g?"margin-right:"+g+";":"")+(h?"z-index:"+h+";":"");if(g=c.ds)g+=g.endsWith(";")?"":";",f+=g;h=c.google_ad_slot;g="";if(!c.google_enable_single_iframe){c=["");g=c.join(" ")}k=b.id;c=h;c=void 0===c?"":c;d="border:none;height:"+e+"px;margin:0;padding:0;position:relative;visibility:visible;width:"+(d+"px;background-color:transparent;");a.write(['':">",'',g,""].join(""));return b.id} +function Pe(a,b,c){if(cc(a.document.getElementById(b).contentWindow))a=a.document.getElementById(b).contentWindow,b=a.document,b.body&&b.body.firstChild||(/Firefox/.test(navigator.userAgent)?b.open("text/html","replace"):b.open(),a.google_async_iframe_close=!0,b.write(c));else{a=a.document.getElementById(b).contentWindow;c=String(c);b=['"'];for(var d=0;df))if(f=e,f in rb)e=rb[f];else if(f in qb)e=rb[f]=qb[f]; +else{h=f.charCodeAt(0);if(31h)e=f;else{if(256>h){if(e="\\x",16>h||256h&&(e+="0");e+=h.toString(16).toUpperCase()}e=rb[f]=e}h=e}b[g]=h}b.push('"');a.location.replace("javascript:"+b.join(""))}};function Qe(a,b){if(!a)return!1;a=a.hash;if(!a||!a.indexOf)return!1;if(-1!=a.indexOf(b))return!0;b=Re(b);return"go"!=b&&-1!=a.indexOf(b)?!0:!1}function Re(a){var b="";Jd(a.split("_"),function(c){b+=c.substr(0,2)});return b};var Se=null;var Te,Ue=parseInt("2019",10);Te=isNaN(Ue)?2012:Ue;function Ve(a,b,c){if("relative"===a)return b;c||(c=Dc?"https":"http");r.location&&"https:"==r.location.protocol&&"http"==c&&(c="https");return[c,"://",a,b].join("")}function We(a,b,c){a=Ve(a,b,c);2012O(a)))return 4;if(!(a.innerHeight>=a.innerWidth))return 5;var f=O(a);if(!f||(f-c)/f>d)a=6;else{if(c="true"!=e.google_full_width_responsive)a:{c=O(a);for(b=b.parentElement;b;b=b.parentElement)if((d=ec(b,a))&&(e=tc(d.width))&&!(e>=c)&&"visible"!=d.overflow){c=!0;break a}c=!1}a=c?7:!0}return a} +function lf(a,b,c){a=a.style;"rtl"==b?I(251)?a.setProperty("margin-right",c,"important"):a.marginRight=c:I(251)?a.setProperty("margin-left",c,"important"):a.marginLeft=c}function mf(a,b){if(3==b.nodeType)return/\S/.test(b.data);if(1==b.nodeType){if(/^(script|style)$/i.test(b.nodeName))return!1;try{var c=ec(b,a)}catch(d){}return!c||"none"!=c.display&&!("absolute"==c.position&&("hidden"==c.visibility||"collapse"==c.visibility))}return!1} +function nf(a,b){for(var c=0;100>c&&b.parentElement;++c){for(var d=b.parentElement.childNodes,e=0;e=f)}}function Wf(a){return function(b){return b.height()<=a}}function Uf(a,b){return ff(a,b)window.top.postMessage('"+a+"', '*');\n \n
\n

Requested size:'+ +d+"x"+e+"

\n

Rendered size:"+d+"x"+e+"

\n
")};/* + + Copyright 2019 The AMP HTML Authors. All Rights Reserved. + + Licensed under the Apache License, Version 2.0 (the "License"); + you may not use this file except in compliance with the License. + You may obtain a copy of the License at + + http://www.apache.org/licenses/LICENSE-2.0 + + Unless required by applicable law or agreed to in writing, software + distributed under the License is distributed on an "AS-IS" BASIS, + WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. + See the License for the specific language governing permissions and + limitations under the License. +*/ +var ag=["google_content_recommendation_ui_type","google_content_recommendation_columns_num","google_content_recommendation_rows_num"];function bg(a,b){P.call(this,a,b)}oa(bg,P);bg.prototype.a=function(){return this.minWidth()};var cg={"image-top":function(a){return 600>=a?284+.414*(a-250):429},"image-middle":function(a){return 500>=a?196-.13*(a-250):164+.2*(a-500)},"image-side":function(a){return 500>=a?205-.28*(a-250):134+.21*(a-500)},"text-only":function(a){return 500>=a?187-.228*(a-250):130},"in-article":function(a){return 420>=a?a/1.2:460>=a?a/1.91+130:800>=a?a/4:200}};function dg(a,b){P.call(this,a,b)}oa(dg,P);dg.prototype.a=function(){return Math.min(1200,this.minWidth())};function eg(a){return function(b){for(var c=a.length-1;0<=c;--c)if(!a[c](b))return!1;return!0}}function fg(a,b){for(var c=gg.slice(0),d=c.length,e=null,f=0;fO(c)&&pf(c)&&nf(c,d);y=kf(c,d,a,.3,e);if(!0===y)if("true"==e.google_full_width_responsive||hf(d,c))if(pf(c))y=!0;else{y=O(c);var V=y-a;y=y&&0<=V?!0:y?-10>V?11:0>V?14:12:10}else y=9;y=!0!==y?{u:a,v:y}:{u:O(c)||a,v:!0}}else y={u:a,v:2};V=y;y=V.u;V=V.v;if(!0!==V)y={u:a,v:V};else if(J=ec(d,c)){var ba=tc(J.paddingLeft)|| +0;J=J.direction;var Ce=y-a;if(e.google_ad_resize)ba=-1*(Ce+ba)+"px";else{for(var Ha=d,De=0,Ee=0;100>Ee&&Ha;Ee++)De+=Ha.offsetLeft+Ha.clientLeft-Ha.scrollLeft,Ha=Ha.offsetParent;ba=De+ba;ba="rtl"==J?-1*(Ce-ba)+"px":-1*ba+"px"}J="rtl"==J;y={u:y,v:V,marginLeft:J?void 0:ba,marginRight:J?ba:void 0,zIndex:30}}else y={u:a,v:V};return y}),g=f.v,h=f.marginLeft,k=f.marginRight,l=f.zIndex,n=e.google_ad_height||0,p=jg(f.u,b,c,d,e,!0===g);f=p.J;var u=p.I,q=p.G,x=p.H,t=p.X;p=p.da;var Q=kg(b,t);return new Zf(Q, +f,t,null,p,g,u,q,x,"","",n,a,"",h,k,l)}function ig(a){return"auto"==a||/^((^|,) *(horizontal|vertical|rectangle) *)+$/.test(a)} +function jg(a,b,c,d,e,f){b="auto"==b?.25>=a/Math.min(1200,O(c))?4:3:jf(b);var g=!1,h=!1;if(488>O(c)){var k=hf(d,c);var l=Uf(d,c);g=!l&&k;h=l&&k}l=488>O(c);var n=[Sf(a),Qf(b)];pf(c)||n.push(Tf(l,c,d,h));null!=e.google_max_responsive_height&&n.push(Wf(e.google_max_responsive_height));var p=[function(q){return!q.qa}];!g&&!h||pf(c)||(g=Xf(c,d),p.push(Wf(g)));var u=l&&!f&&3===b&&lg(c)?new R(a,Math.floor(a/1.2),1):fg(eg(n),eg(p));if(!u)throw new M("No slot size for availableWidth="+a);p=Je(248,function(){var q; +a:if(f){if(e.gfwrnh&&(q=tc(e.gfwrnh))){q={J:new bg(a,q),I:!0,G:!1,H:!1};break a}q=!1;var x=Ne(c).clientHeight,t=ff(d,c),Q=c.google_lpabyc;var J=ff(d,c);var y=Ne(c).clientHeight;(J=0==y?null:J/y)&&2x)&&(x=.9*Ne(c).clientHeight,t=Math.min(x,mg(c,d,e)),x&&t==x&&(t=c.google_pbfabyc,q=!t,t||(c.google_pbfabyc=ff(d,c)+x)));x=a/1.2;if(pf(c))t=x;else if(t=Math.min(x,mg(c,d,e)),t<.5*x||100>t)t=x;I(282)&&!Uf(d,c)&&(t=Math.max(t,.5*Ne(c).clientHeight));q={J:new bg(a,Math.floor(t)), +I:tg)throw new M("Fluid responsive ads must be at least 250px wide: availableWidth="+g);g=Math.min(1200,Math.floor(g));if(f&&"in-article"!=h){h=Math.ceil(f);if(50>h)throw new M("Fluid responsive ads must be at least 50px tall: height="+h);g=new Zf(11,new P(g,h))}else{if("in-article"!= +h&&(e=e.google_ad_layout_key)){h=""+e;b=Math.pow(10,3);if(e=(c=h.match(/([+-][0-9a-z]+)/g))&&c.length){f=[];for(k=0;ka*d.height()?new R(g.minWidth(),g.height(),1):d}function ng(a){return I(227)||a.location&&"#hffwroe2etoq"==a.location.hash}function lg(a){return I(232)||a.location&&"#affwroe2etoq"==a.location.hash};function pg(a,b){var c=b.google_ad_format;if("autorelaxed"==c){a:{if("pedestal"!=b.google_content_recommendation_ui_type)for(a=fa(ag),c=a.next();!c.done;c=a.next())if(null!=b[c.value]){b=!0;break a}b=!1}return b?9:5}if(ig(c))return 1;if("link"==c)return 4;if("fluid"==c){if(c="in-article"===b.google_ad_layout)c=I(208)||I(227)||a.location&&("#hffwroe2etop"==a.location.hash||"#hffwroe2etoq"==a.location.hash);return c?(qg(b),1):8}if(c=27===b.google_reactive_ad_format)c=I(266)||a.location&&"#cefwroe2etoq"== +a.location.hash;if(c)return qg(b),1}function qg(a){a.google_ad_format="auto";a.armr=3};function T(a){this.f=[];this.b=a||window;this.a=0;this.c=null;this.g=0}var rg;m=T.prototype;m.ma=function(a,b){0!=this.a||0!=this.f.length||b&&b!=window?this.aa(a,b):(this.a=2,this.ga(new sg(a,window)))};m.aa=function(a,b){this.f.push(new sg(a,b||this.b));tg(this)};m.ta=function(a){this.a=1;if(a){var b=Ke(188,Ca(this.fa,this,!0));this.c=this.b.setTimeout(b,a)}};m.fa=function(a){a&&++this.g;1==this.a&&(null!=this.c&&(this.b.clearTimeout(this.c),this.c=null),this.a=0);tg(this)}; +m.Ba=function(){return!(!window||!Array)};m.oa=function(){return this.g};function tg(a){var b=Ke(189,Ca(a.Ca,a));a.b.setTimeout(b,0)}m.Ca=function(){if(0==this.a&&this.f.length){var a=this.f.shift();this.a=2;var b=Ke(190,Ca(this.ga,this,a));a.a.setTimeout(b,0);tg(this)}};m.ga=function(a){this.a=0;a.b()};function ug(a){try{return a.sz()}catch(b){return!1}}function vg(a){return!!a&&("object"===typeof a||"function"===typeof a)&&ug(a)&&Kd(a.nq)&&Kd(a.nqa)&&Kd(a.al)&&Kd(a.rl)} +function wg(){if(rg&&ug(rg))return rg;var a=$e(),b=a.google_jobrunner;return vg(b)?rg=b:a.google_jobrunner=rg=new T(a)}function xg(a,b){wg().nq(a,b)}function yg(a,b){wg().nqa(a,b)}T.prototype.nq=T.prototype.ma;T.prototype.nqa=T.prototype.aa;T.prototype.al=T.prototype.ta;T.prototype.rl=T.prototype.fa;T.prototype.sz=T.prototype.Ba;T.prototype.tc=T.prototype.oa;function sg(a,b){this.b=a;this.a=b};function zg(){var a={};this[3]=(a[23]=function(b){return tf(Rb,parseInt(b,10))},a[24]=function(b){return vf(Rb,parseInt(b,10))},a);this[4]={};this[5]={}}wa(zg);function Ag(a){B(this,a,Bg,null)}v(Ag,A);function Cg(a){B(this,a,null,null)}v(Cg,A);var Bg=[1];function Dg(a){var b=new Cg;return Eb(b,1,a)}function Eg(a,b){return Eb(a,2,b)}function Fg(a,b){Gb(a,Cg,1);var c=a.a[1];c||(c=a.a[1]=[]);b=b?b:new Cg;a=C(a,1);c.push(b);a.push(b.j)};function Gg(a,b){this.start=aMath.random()&&wc({data:a},"ls_tamp")};var Lg=new Hg(5);function Mg(a){a=void 0===a?r:a;return a.ggeac||(a.ggeac={})};function Ng(a,b){a=ua(a);a="function"===typeof a?a():a;return typeof a===b?a:void 0} +function Og(){var a={};this[3]=(a[8]=function(b){return!!ua(b)},a[9]=function(b){b=ua(b);return"function"==xa(b)&&uc(b)},a[10]=function(){return window==window.top},a[6]=function(b){return La(zf.h().a(),parseInt(b,10))},a[27]=function(b){b=Ng(b,"boolean");return void 0!==b?b:void 0},a);a={};this[4]=(a[3]=function(){return vc()},a[6]=function(b){b=Ng(b,"number");return void 0!==b?b:void 0},a);a={};this[5]=(a[2]=function(){return window.location.href},a[3]=function(){try{return window.top.location.hash}catch(b){return""}}, +a[4]=function(b){b=Ng(b,"string");return void 0!==b?b:void 0},a)}wa(Og);function Pg(a){B(this,a,Qg,null)}v(Pg,A);var Qg=[2];Pg.prototype.N=function(){return D(this,7,0)};function Rg(a){B(this,a,Sg,null)}v(Rg,A);var Sg=[2];Rg.prototype.N=function(){return D(this,5,0)};function Tg(a){B(this,a,Ug,null)}v(Tg,A);function Vg(a){B(this,a,Wg,null)}v(Vg,A);var Ug=[1,4,2,3],Wg=[2];Vg.prototype.N=function(){return D(this,1,0)};var Xg=[12,13];function Yg(){}function Zg(a,b,c,d){var e=void 0===d?{}:d;d=void 0===e.ba?!1:e.ba;var f=void 0===e.sa?{}:e.sa;e=void 0===e.za?[]:e.za;a.a=b;a.g=d;a.f=f;b={};a.b=(b[c]=e,b[4]=[],b);a.c={};(c=ne())&&w(c.split(",")||[],function(g){(g=parseInt(g,10))&&(a.c[g]=!0)});return a} +function $g(a,b,c){var d=[],e=ah(a.a,b);if(e.length){9!==b&&(a.a=bh(a.a,b));var f=La(Xg,b);w(e,function(g){if(g=ch(a,g,c)){var h=D(g,1,0);d.push(h);dh(a,h,f?4:c);var k=E(g,Qc,2);k&&(f?w(jd(),function(l){return hd(k,l)}):hd(k,c))}})}return d}function dh(a,b,c){a.b[c]||(a.b[c]=[]);a=a.b[c];La(a,b)?wc({eids:JSON.stringify(a),dup:b},"gpt_dupeid"):a.push(b)}function eh(a,b){a.a.push.apply(a.a,ha(Fa(Ga(b,function(c){return new Vg(c)}),function(c){return!La(Xg,c.N())})))} +function ch(a,b,c){var d=Uc.h().a;if(!Nc(Fb(b,Gc,3),d))return null;var e=E(b,Pg,2),f=e.length*D(b,1,0),g=D(b,6,0);if(g)return f=2==c?Jg(g):Ig(window,g),null===f&&(f=Math.floor(1E3*ic(window))),b=fh(b,f),!b||d&&!Nc(Fb(b,Gc,3),d)?null:gh(a,[b],1);c=d?Fa(e,function(h){return Nc(Fb(h,Gc,3),d)}):e;return c.length?(b=D(b,4,0))?hh(a,b,f,c):gh(a,c,f/1E3):null}function hh(a,b,c,d){var e=null!=a.f[b]?a.f[b]:1E3;if(0>=e)return null;d=gh(a,d,c/e);a.f[b]=d?0:e-c;return d} +function gh(a,b,c){var d=a.c,e=Ja(b,function(f){return!!d[D(f,1,0)]});return e?e:a.g?null:fc(b,c,!1)}function ih(a,b){H(ld,function(c){a.c[c]=!0},b);H(nd,function(c,d){return $g(a,c,d)},b);H(od,function(c){return(a.b[c]||[]).concat(a.b[4])},b);H(xd,function(c){return eh(a,c)},b)}wa(Yg);function ah(a,b){return(a=Ja(a,function(c){return c.N()==b}))&&E(a,Rg,2)||[]}function bh(a,b){return Fa(a,function(c){return c.N()!=b})} +function fh(a,b){var c=E(a,Pg,2),d=c.length,e=D(a,1,0);a=D(a,8,0);var f=(b-a)%d;return b=d*e-1?null:c[f]};function jh(){this.a=function(){}}wa(jh);function kh(a){jh.h().a(a)};function lh(a,b,c,d){var e=1;d=void 0===d?Mg():d;e=void 0===e?0:e;d.hasOwnProperty("init-done")?(Ad(xd,d)(Ga(E(a,Vg,2),function(f){return f.j})),Ad(yd,d)(Ga(E(a,Qc,1),function(f){return f.j}),e),b&&Ad(zd,d)(b),mh(d,e)):(ih(Zg(Yg.h(),E(a,Vg,2),e,c),d),Bd(d),Cd(d),Dd(d),mh(d,e),hd(E(a,Qc,1),e),Vc=Vc||!(!c||!c.pa),kh(Og.h()),b&&kh(b))}function mh(a,b){a=void 0===a?Mg():a;b=void 0===b?0:b;var c=a,d=b;d=void 0===d?0:d;Af(zf.h(),c,d);c=a;b=void 0===b?0:b;Fd(Ed.h(),c,b);jh.h().a=Ad(zd,a);Ed.h().a()};function U(a,b){b&&a.push(b)}function nh(a,b){for(var c=[],d=1;d=d?c=null:(g=new Gg(c,c+d-1),(d=d%f||d/f%e.length)||(d=b.b,d=!(d.start<=g.start&&d.a>=g.a)),d?c=null:(a=Ig(a,b.a),c=null!==a&&g.start<=a&&g.a>=a?e[Math.floor((a-c)/f)%e.length]:null)));return c};function qh(a,b){var c=K(b);if(c){c=O(c);var d=ec(a,b)||{},e=d.direction;if("0px"===d.width&&"none"!=d.cssFloat)return-1;if("ltr"===e&&c)return Math.floor(Math.min(1200,c-a.getBoundingClientRect().left));if("rtl"===e&&c)return a=b.document.body.getBoundingClientRect().right-a.getBoundingClientRect().right,Math.floor(Math.min(1200,c-a-Math.floor((c-b.document.body.clientWidth)/2)))}return-1};function rh(a){var b=this;this.a=a;a.google_iframe_oncopy||(a.google_iframe_oncopy={handlers:{},upd:function(c,d){var e=sh("rx",c),f=Number;a:{if(c&&(c=c.match("dt=([^&]+)"))&&2==c.length){c=c[1];break a}c=""}f=f(c);f=(new Date).getTime()-f;e=e.replace(/&dtd=(\d+|-?M)/,"&dtd="+(1E5<=f?"M":0<=f?f:"-M"));b.set(d,e);return e}});this.b=a.google_iframe_oncopy} +rh.prototype.set=function(a,b){var c=this;this.b.handlers[a]=b;this.a.addEventListener&&this.a.addEventListener("load",function(){var d=c.a.document.getElementById(a);try{var e=d.contentWindow.document;if(d.onload&&e&&(!e.body||!e.body.firstChild))d.onload()}catch(f){}},!1)};function sh(a,b){var c=new RegExp("\\b"+a+"=(\\d+)"),d=c.exec(b);d&&(b=b.replace(c,a+"="+(+d[1]+1||1)));return b}var th,uh="var i=this.id,s=window.google_iframe_oncopy,H=s&&s.handlers,h=H&&H[i],w=this.contentWindow,d;try{d=w.document}catch(e){}if(h&&d&&(!d.body||!d.body.firstChild)){if(h.call){setTimeout(h,0)}else if(h.match){try{h=s.upd(h,i)}catch(e){}w.location.replace(h)}}"; +var W=uh;/[\x00&<>"']/.test(W)&&(-1!=W.indexOf("&")&&(W=W.replace(Va,"&")),-1!=W.indexOf("<")&&(W=W.replace(Wa,"<")),-1!=W.indexOf(">")&&(W=W.replace(Xa,">")),-1!=W.indexOf('"')&&(W=W.replace(Ya,""")),-1!=W.indexOf("'")&&(W=W.replace(Za,"'")),-1!=W.indexOf("\x00")&&(W=W.replace($a,"�")));uh=W;th=uh;var vh="google_ad_block google_ad_channel google_ad_client google_ad_format google_ad_height google_ad_host google_ad_host_channel google_ad_host_tier_id google_ad_layout google_ad_layout_key google_ad_modifications google_ad_output google_ad_region google_ad_section google_ad_slot google_ad_type google_ad_unit_key google_ad_dom_fingerprint google_ad_semantic_area google_ad_width google_adtest google_allow_expandable_ads google_alternate_ad_url google_alternate_color google_analytics_domain_name google_analytics_uacct google_apsail google_captcha_token google_city google_color_bg google_color_border google_color_line google_color_link google_color_text google_color_url google_container_id google_content_recommendation_ad_positions google_content_recommendation_columns_num google_content_recommendation_rows_num google_content_recommendation_ui_type google_content_recommendation_use_square_imgs google_contents google_core_dbp google_country google_cpm google_ctr_threshold google_cust_age google_cust_ch google_cust_criteria google_cust_gender google_cust_id google_cust_interests google_cust_job google_cust_l google_cust_lh google_cust_u_url google_disable_video_autoplay google_bfa ebfa ebfaca google_eids google_enable_content_recommendations google_enable_ose google_encoding google_font_face google_font_size google_frame_id google_full_width_responsive_allowed efwr google_full_width_responsive gfwroh gfwrow gfwroml gfwromr gfwroz gfwrnh gfwrnwer gfwrnher google_gl google_hints google_image_size google_kw google_kw_type google_lact google_language google_loeid google_max_num_ads google_max_radlink_len google_max_responsive_height google_ml_rank google_mtl google_native_ad_template google_native_settings_key google_num_radlinks google_num_radlinks_per_unit google_only_pyv_ads google_override_format google_page_url google_pgb_reactive google_pucrd google_referrer_url google_region google_resizing_allowed google_resizing_height google_resizing_width rpe google_responsive_formats google_responsive_auto_format armr google_rl_dest_url google_rl_filtering google_rl_mode google_rt google_safe google_safe_for_responsive_override google_scs google_source_type google_tag_for_child_directed_treatment google_tag_for_under_age_of_consent google_tag_origin google_tag_partner google_targeting google_tfs google_video_doc_id google_video_product_type google_video_url_to_fetch google_webgl_support google_yt_pt google_yt_up google_package google_debug_params google_enable_single_iframe dash google_refresh_count google_restrict_data_processing".split(" "), +wh={},xh=(wh.google_ad_modifications=!0,wh.google_analytics_domain_name=!0,wh.google_analytics_uacct=!0,wh.google_pause_ad_requests=!0,wh);function yh(a){return(a=a.innerText||a.innerHTML)&&(a=a.replace(/^\s+/,"").split(/\r?\n/,1)[0].match(/^\x3c!--+(.*?)(?:--+>)?\s*$/))&&/google_ad_client/.test(a[1])?a[1]:null} +function zh(a){if(a=a.innerText||a.innerHTML)if(a=a.replace(/^\s+|\s+$/g,"").replace(/\s*(\r?\n)+\s*/g,";"),(a=a.match(/^\x3c!--+(.*?)(?:--+>)?$/)||a.match(/^\/*\s*)?$/i))&&/google_ad_client/.test(a[1]))return a[1];return null} +function Ah(a){try{a:{for(var b=a.document.getElementsByTagName("script"),c=a.navigator&&a.navigator.userAgent||"",d=/appbankapppuzdradb|daumapps|fban|fbios|fbav|fb_iab|gsa\/|messengerforios|naver|niftyappmobile|nonavigation|pinterest|twitter|ucbrowser|yjnewsapp|youtube/i.test(c)||/i(phone|pad|pod)/i.test(c)&&/applewebkit/i.test(c)&&!/version|safari/i.test(c)&&!Rd()?yh:zh,e=b.length-1;0<=e;e--){var f=b[e];if(!f.google_parsed_script){f.google_parsed_script=!0;var g=d(f);if(g){var h=g;break a}}}h=null}}catch(l){return!1}if(!h)return!1; +try{b=/(google_\w+) *= *(['"]?[\w.-]+['"]?) *(?:;|$)/gm;c={};for(var k;k=b.exec(h);)c[k[1]]=Bh(k[2]);Ch(c,a)}catch(l){return!1}return!!a.google_ad_client}function Dh(a){for(var b=0,c=vh.length;b=+new Date&&b.push("adsid="+encodeURIComponent(X[1]));return a+"?"+b.join("&")}var X,Y; +function Mh(){Kh=r;X=Kh.googleToken=Kh.googleToken||{};var a=+new Date;X[1]&&X[3]>a&&0=+new Date)||"NT"==X[1]);var l=!(X[3]>=+new Date)&& +0!=b;if(k||d||l)d=+new Date,e=d+1E3*e,f=d+1E3*f,1E-5>Math.random()&&Id("https://pagead2.googlesyndication.com/pagead/gen_204?id=imerr&err="+b,null),h[5]=b,h[1]=a,h[2]=e,h[3]=f,h[4]=g,h[6]=c,Mh();if(k||!Nh.V()){b=Nh.na();for(a=0;a=+new Date&&X[2]>=+new Date||Nh.ua()};var Ph=tb("script");function Qh(a){a.google_sa_impl&&!a.document.getElementById("google_shimpl")&&(a.google_sa_queue=null,a.google_sl_win=null,a.google_sa_impl=null)} +function Rh(a){Qh(a);if(!a.google_sa_queue){a.google_sa_queue=[];a.google_sl_win=a;a.google_process_slots=function(){return Sh(a)};var b=Th();uc(a.Promise)&&uc(a.Symbol)?dc(a.document,b).id="google_shimpl":(b=Zb(),b.id="google_shimpl",b.style.display="none",a.document.documentElement.appendChild(b),Pe(a,"google_shimpl","<"+(Ph+">google_sl_win=window.parent;google_async_iframe_id='google_shimpl';")+Uh()+""),b.contentWindow.document.close())}} +var Sh=Ke(215,function(a){var b=a.google_sa_queue,c=b.shift();a.google_sa_impl||le(ye,"shimpl",{t:"no_fn"},!0,void 0,void 0);"function"==xa(c)&&Je(216,c);b.length&&a.setTimeout(function(){return Sh(a)},0)});function Vh(a,b,c){a.google_sa_queue=a.google_sa_queue||[];a.google_sa_impl?c(b):a.google_sa_queue.push(b)}function Uh(){var a=Th();return"<"+Ph+' src="'+a+'">"} +function Th(){var a="/show_ads_impl.js";a=void 0===a?"/show_ads_impl.js":a;return We(Td(),["/pagead/js/",zc(),"/r20190131",a,""].join(""),"https")}function Wh(a,b,c,d){return function(){var e=!1;d&&wg().al(3E4);try{Pe(a,b,c),e=!0}catch(g){var f=$e().google_jobrunner;vg(f)&&f.rl()}e&&(e=sh("google_async_rrc",c),(new rh(a)).set(b,Wh(a,b,e,!1)))}} +function Xh(a){if(!Se)a:{for(var b=[r.top],c=[],d=0,e;e=b[d++];){c.push(e);try{if(e.frames)for(var f=e.frames.length,g=0;gb.length;++g)b.push(e.frames[g])}catch(k){}}for(b=0;bEa?d-Ea:1;b.google_async_rrc=0;a.google_sv_map=a.google_sv_map||{};a.google_sv_map[c]=b;a.google_t12n_vars=bf;if(b.google_enable_single_iframe){var f={pubWin:a,iframeWin:null,vars:b};Vh(a,function(){a.google_sa_impl(f)},a.document.getElementById(c+"_anchor")?xg:yg)}else Vh(a,Wh(a,c,["","<"+Ph+">","google_sl_win=window.parent;google_iframe_start_time=new Date().getTime();",'google_async_iframe_id="'+ +c+'";',"","<"+Ph+">window.parent.google_sa_impl({iframeWin: window, pubWin: window.parent, vars: window.parent['google_sv_map']['"+(c+"']});",""].join(""),!0),a.document.getElementById(c)?xg:yg)} +function Zh(a,b){var c=b.google_ad_output,d=b.google_ad_format,e=b.google_ad_width||0,f=b.google_ad_height||0;d||"html"!=c&&null!=c||(d=e+"x"+f);c=!b.google_ad_slot||b.google_override_format||!Vb[b.google_ad_width+"x"+b.google_ad_height]&&"aa"==b.google_loader_used;d&&c?d=d.toLowerCase():d="";b.google_ad_format=d;if("number"!==typeof b.google_reactive_sra_index||!b.google_ad_unit_key){d=[b.google_ad_slot,b.google_orig_ad_format||b.google_ad_format,b.google_ad_type,b.google_orig_ad_width||b.google_ad_width, +b.google_orig_ad_height||b.google_ad_height];c=[];e=0;for(f=Sb.parentElement;f&&25>e;f=f.parentNode,++e)9===f.nodeType?c.push(""):c.push(f.id);(c=c.join())&&d.push(c);b.google_ad_unit_key=kc(d.join(":")).toString();d=Sb;var g=void 0===g?!1:g;c=[];for(e=0;d&&25>e;++e){f="";void 0!==g&&g||(f=(f=9!==d.nodeType&&d.id)?"/"+f:"");a:{if(d&&d.nodeName&&d.parentElement){var h=d.nodeName.toString().toLowerCase();for(var k=d.parentElement.childNodes,l=0,n=0;nc;++c){var q=u.frames;for(e=0;ef.length&&f.push(e))}return g}}function di(a,b){return ci(a,b,function(c,d){(new Ae).B(c,d)})};function Z(a,b){return null==b?"&"+a+"=null":"&"+a+"="+Math.floor(b)} +function ei(){var a=this;this.A=this.P=this.o=this.l=this.f=0;this.C=!1;this.w=this.g=this.c=0;this.D=.1>Math.random();this.F=r===r.top;var b=document.querySelector("[data-google-query-id]");if(this.a=b?b.getAttribute("data-google-query-id"):null)b=null;else{if("number"!==typeof r.goog_pvsid)try{Object.defineProperty(r,"goog_pvsid",{value:Math.floor(Math.random()*Math.pow(2,52))})}catch(c){}b=Number(r.goog_pvsid)||-1}this.K=b;this.D&&(b="https://pagead2.googlesyndication.com/pagead/gen_204?id=plmetrics"+ +(this.a?"&qqid="+encodeURIComponent(this.a):Z("pvsid",this.K)),b+=Z("test",1),b+="&top="+(this.F?1:0),fi(b));this.R=new PerformanceObserver(di(640,function(c){c=fa(c.getEntries());for(var d=c.next();!d.done;d=c.next()){d=d.value;if("layout-shift"===d.entryType){var e=d;e.hadRecentInput||I(241)&&!(.01a.l&&(a.l=Number(e.value)),a.o+=1)}"largest-contentful-paint"===d.entryType&&(e=d,a.P=Math.floor(e.renderTime||e.loadTime));"first-input"===d.entryType&& +(e=d,a.A=Number((e.processingStart-e.startTime).toFixed(3)),a.C=!0);"longtask"===d.entryType&&(a.c+=d.duration,d.duration>a.g&&(a.g=d.duration),a.w+=1)}}));this.L=!1;this.b=di(641,this.b.bind(this))}oa(ei,Fc); +ei.prototype.b=function(){var a=document;if(2===({visible:1,hidden:2,prerender:3,preview:4,unloaded:5}[a.visibilityState||a.webkitVisibilityState||a.mozVisibilityState||""]||0)&&!this.L){this.L=!0;this.R.takeRecords();a="https://pagead2.googlesyndication.com/pagead/gen_204?id=plmetrics";window.LayoutShift&&(a+="&cls="+this.f.toFixed(3),a+="&mls="+this.l.toFixed(3),a+=Z("nls",this.o));window.LargestContentfulPaint&&(a+=Z("lcp",this.P));window.PerformanceEventTiming&&this.C&&(a+=Z("fid",this.A));window.PerformanceLongTaskTiming&& +(a+=Z("cbt",this.c),a+=Z("mbt",this.g),a+=Z("nlt",this.w));for(var b=0,c=fa(document.getElementsByTagName("iframe")),d=c.next();!d.done;d=c.next())if(d=d.value,d.id.includes("google_ads_iframe_")||d.id.includes("aswift"))b+=1;a+=Z("nif",b);a+=Z("ifi",Md(window));b=zf.h().a();a+="&eid="+encodeURIComponent(b.join());this.D&&(a+=Z("test",1));a+="&top="+(this.F?1:0);a+=this.a?"&qqid="+encodeURIComponent(this.a):Z("pvsid",this.K);fi(a)}}; +function fi(a){window.fetch(a,{keepalive:!0,credentials:"include",redirect:"follow",method:"get",mode:"no-cors"})};var gi=["https://www.google.com"],hi=void 0;function ii(a){this.c=gi;this.a=2;this.b=a}oa(ii,Fc);function ji(a){null===a.b||3<=a.a||(a.a=3,w(a.c,function(b){a.b.fetch(b+"/.well-known/trust-token",{keepalive:!0,redirect:"follow",method:"get",mode:"no-cors",Ka:{type:"srr-token-redemption",Ga:b,Ha:"none"}}).then(function(c){if(!c.ok)throw Error("Network response was not ok");c.blob();a.a=5}).catch(function(){4>a.a&&(a.a=4)})}))};(function(a){N.Y(function(b){w(a,function(c){c(b)});Fe(b);Ge(b)})})([function(a){a.shv=zc()},function(a){jc(Pf,function(b,c){try{null!=r[b]&&(a[c]=r[b])}catch(d){}})},function(a){try{var b=Ud(r).eids||[];null!=b&&0c)){d=h.google_ad_height;b=!!Vb[b+ +"x"+d];e=c;if(b)if(g=Wb(c,d))e=g,h.google_ad_format=g+"x"+d+"_0ads_al";else throw new M("No slot size for availableWidth="+c);h.google_ad_resize=!0;h.google_ad_width=e;b||(h.google_ad_format=null,h.google_override_format=!0);c=e;d=hg(c,"auto",a,f,h);$f(d,c,h);d=d.a;h.google_responsive_formats=null;d.minWidth()>c&&!b&&(h.google_ad_width=d.minWidth())}b=h.google_ad_width||0;d=Da(hg,b,"auto",a,f,h,!1,!0);c=K(a)||a;e=h.google_ad_client;c=c.location&&"#ftptohbh"===c.location.hash?2:Qe(c.location,"google_responsive_slot_debug")|| +Qe(c.location,"google_responsive_slot_preview")||I(217)?1:I(218)?2:tf(c,1,e)?1:0;if(e=0!==c)a:if((e=!(488>O(a))&&!I(216)||h.google_reactive_ad_format||pg(a,h))||(e=!((rc.test(h.google_ad_width)||qc.test(f.style.width))&&(rc.test(h.google_ad_height)||qc.test(f.style.height)))),e)e=!1;else{for(e=f;e;e=e.parentElement){g=ec(e,a);if(!g){h.gfwrnwer=18;e=!1;break a}if(!La(["static","relative"],g.position)){h.gfwrnwer=17;e=!1;break a}}if(!I(216)&&(e=kf(a,f,b,.3,h),!0!==e)){h.gfwrnwer=e;e=!1;break a}e=Sd(a)== +a?!0:!1}e&&(h.google_resizing_allowed=!0,h.ovlp=!0,2===c?(c={},$f(d(),b,c),h.google_resizing_width=c.google_ad_width,h.google_resizing_height=c.google_ad_height,c.ds&&(h.ds=c.ds),h.iaaso=!1):(h.google_ad_format="auto",h.iaaso=!0,h.armr=1));(b=(h.google_async_iframe_id?1==Md(h):!Md(h))&&Nf(a,h))&&rf(a,b);1==pg(a,h)&&(b=h.google_ad_width||0,$f(hg(b,h.google_ad_format,a,f,h),b,h));Yh(a,h)}}});}).call(this); diff --git a/doc/As65 Assembler_files/show_ads_impl_fy2019.js b/doc/As65 Assembler_files/show_ads_impl_fy2019.js new file mode 100644 index 0000000..ebbbc56 --- /dev/null +++ b/doc/As65 Assembler_files/show_ads_impl_fy2019.js @@ -0,0 +1,410 @@ +(function(window,document,location){/* + + Copyright The Closure Library Authors. + SPDX-License-Identifier: Apache-2.0 +*/ +'use strict';var n,q=this||self;function ca(a,b,c){a=a.split(".");c=c||q;a[0]in c||"undefined"==typeof c.execScript||c.execScript("var "+a[0]);for(var d;a.length&&(d=a.shift());)a.length||void 0===b?c[d]&&c[d]!==Object.prototype[d]?c=c[d]:c=c[d]={}:c[d]=b}function ea(){if(null===fa)a:{var a=q.document;if((a=a.querySelector&&a.querySelector("script[nonce]"))&&(a=a.nonce||a.getAttribute("nonce"))&&ia.test(a)){fa=a;break a}fa=""}return fa}var ia=/^[\w+/_-]+[=]{0,2}$/,fa=null;function la(){} +function na(a){a.lb=void 0;a.G=function(){return a.lb?a.lb:a.lb=new a}} +function oa(a){var b=typeof a;if("object"==b)if(a){if(a instanceof Array)return"array";if(a instanceof Object)return b;var c=Object.prototype.toString.call(a);if("[object Window]"==c)return"object";if("[object Array]"==c||"number"==typeof a.length&&"undefined"!=typeof a.splice&&"undefined"!=typeof a.propertyIsEnumerable&&!a.propertyIsEnumerable("splice"))return"array";if("[object Function]"==c||"undefined"!=typeof a.call&&"undefined"!=typeof a.propertyIsEnumerable&&!a.propertyIsEnumerable("call"))return"function"}else return"null"; +else if("function"==b&&"undefined"==typeof a.call)return"object";return b}function pa(a){return"array"==oa(a)}function qa(a){return"function"==oa(a)}function ra(a){var b=typeof a;return"object"==b&&null!=a||"function"==b}function sa(a){return Object.prototype.hasOwnProperty.call(a,ta)&&a[ta]||(a[ta]=++va)}var ta="closure_uid_"+(1E9*Math.random()>>>0),va=0;function wa(a,b,c){return a.call.apply(a.bind,arguments)} +function xa(a,b,c){if(!a)throw Error();if(2=arguments.length?Array.prototype.slice.call(a,b):Array.prototype.slice.call(a,b,c)} +function Sa(a){for(var b=[],c=0;c")&&(a=a.replace(Db,">"));-1!=a.indexOf('"')&&(a=a.replace(Eb,"""));-1!=a.indexOf("'")&&(a=a.replace(Fb,"'"));-1!=a.indexOf("\x00")&&(a=a.replace(Gb,"�"))}return a} +var zb=/&/g,Cb=//g,Eb=/"/g,Fb=/'/g,Gb=/\x00/g,Hb=/[\x00&<>"']/; +function Ib(a,b){let c=0;a=xb(String(a)).split(".");b=xb(String(b)).split(".");const d=Math.max(a.length,b.length);for(let g=0;0==c&&gb?1:0};function Kb(a,b){this.m=a===Lb&&b||"";this.o=Mb}Kb.prototype.Z=!0;Kb.prototype.j=function(){return this.m.toString()};Kb.prototype.kb=!0;Kb.prototype.l=function(){return 1};function Pb(a){if(a instanceof Kb&&a.constructor===Kb&&a.o===Mb)return a.m;oa(a);return"type_error:SafeUrl"} +var Qb=/^(?:audio\/(?:3gpp2|3gpp|aac|L16|midi|mp3|mp4|mpeg|oga|ogg|opus|x-m4a|x-matroska|x-wav|wav|webm)|font\/\w+|image\/(?:bmp|gif|jpeg|jpg|png|tiff|webp|x-icon)|text\/csv|video\/(?:mpeg|mp4|ogg|webm|quicktime|x-matroska))(?:;\w+=(?:\w+|"[\w;,= ]+"))*$/i,Rb=/^data:(.*);base64,[a-z0-9+\/]+=*$/i,Sb=/^(?:(?:https?|mailto|ftp):|[^:/?#]*(?:[/?#]|$))/i;function Tb(a){if(a instanceof Kb)return a;a="object"==typeof a&&a.Z?a.j():String(a);Sb.test(a)||(a="about:invalid#zClosurez");return new Kb(Lb,a)} +function Ub(a,b){if(a instanceof Kb)return a;a="object"==typeof a&&a.Z?a.j():String(a);if(b&&/^data:/i.test(a)){b=a.replace(/(%0A|%0D)/g,"");var c=b.match(Rb);c=c&&Qb.test(c[1]);b=new Kb(Lb,c?b:"about:invalid#zClosurez");if(b.j()==a)return b}Sb.test(a)||(a="about:invalid#zClosurez");return new Kb(Lb,a)}var Mb={},Lb={};function Vb(){this.l="";this.m=Wb}Vb.prototype.Z=!0;var Wb={};Vb.prototype.j=function(){return this.l};function Xb(a){var b=new Vb;b.l=a;return b}var Yb=Xb(""); +function Zb(a){if(a instanceof Kb)return'url("'+Pb(a).replace(/f?null:"string"===typeof e?e.charAt(f):e[f]]||""}var b=hc;if(mc())return rc(b);b=kc(b);var c={};Ga(b,function(e){c[e[0]]=e[1]});var d=za(fb,c);return lc()?a(["Version","Opera"]):A("Edge")?a(["Edge"]):A("Edg/")?a(["Edg"]):pc()?a(["Chrome","CriOS","HeadlessChrome"]):(b=b[2])&&b[1]||""} +function rc(a){var b=/rv: *([\d\.]*)/.exec(a);if(b&&b[1])return b[1];b="";var c=/MSIE +([\d\.]+)/.exec(a);if(c&&c[1])if(a=/Trident\/(\d.\d)/.exec(a),"7.0"==c[1])if(a&&a[1])switch(a[1]){case "4.0":b="8.0";break;case "5.0":b="9.0";break;case "6.0":b="10.0";break;case "7.0":b="11.0"}else b="7.0";else b=c[1];return b};function sc(){this.m="";this.v=tc;this.o=null}sc.prototype.kb=!0;sc.prototype.l=function(){return this.o};sc.prototype.Z=!0;sc.prototype.j=function(){return this.m.toString()};function uc(a){if(a instanceof sc&&a.constructor===sc&&a.v===tc)return a.m;oa(a);return"type_error:SafeHtml"}function vc(a){if(a instanceof sc)return a;var b="object"==typeof a,c=null;b&&a.kb&&(c=a.l());return wc(yb(b&&a.Z?a.j():String(a)),c)} +var xc=/^[a-zA-Z0-9-]+$/,yc={action:!0,cite:!0,data:!0,formaction:!0,href:!0,manifest:!0,poster:!0,src:!0},zc={APPLET:!0,BASE:!0,EMBED:!0,IFRAME:!0,LINK:!0,MATH:!0,META:!0,OBJECT:!0,SCRIPT:!0,STYLE:!0,SVG:!0,TEMPLATE:!0};function Ac(a){function b(f){Array.isArray(f)?Ga(f,b):(f=vc(f),e.push(uc(f).toString()),f=f.l(),0==d?d=f:0!=f&&d!=f&&(d=null))}var c=vc(Bc),d=c.l(),e=[];Ga(a,b);return wc(e.join(uc(c).toString()),d)}function Cc(a){return Ac(Array.prototype.slice.call(arguments))}var tc={}; +function wc(a,b){return Dc(a,b)}function Dc(a,b){var c=new sc;c.m=a;c.o=b;return c}Dc("",0);var Bc=Dc("",0);Dc("
",0);var Ec=Ya(function(){var a=document.createElement("div"),b=document.createElement("div");b.appendChild(document.createElement("div"));a.appendChild(b);b=a.firstChild.firstChild;a.innerHTML=uc(Bc);return!b.parentElement});function Fc(a,b){if(Ec())for(;a.lastChild;)a.removeChild(a.lastChild);a.innerHTML=uc(b)}function Gc(a,b){b=b instanceof Kb?b:Ub(b,/^data:image\//i.test(b));a.src=Pb(b)}function Hc(a,b){a.src=tb(b);(b=ea())&&a.setAttribute("nonce",b)};function Ic(a){return a=yb(a,void 0)}function Jc(a,b){var c={"&":"&","<":"<",">":">",""":'"'};var d=b?b.createElement("div"):q.document.createElement("div");return a.replace(Kc,function(e,f){var g=c[e];if(g)return g;"#"==f.charAt(0)&&(f=Number("0"+f.substr(1)),isNaN(f)||(g=String.fromCharCode(f)));g||(g=Dc(e+" ",null),Fc(d,g),g=d.firstChild.nodeValue.slice(0,-1));return c[e]=g})} +var Kc=/&([^;\s<&]+);?/g,Lc={"\x00":"\\0","\b":"\\b","\f":"\\f","\n":"\\n","\r":"\\r","\t":"\\t","\x0B":"\\x0B",'"':'\\"',"\\":"\\\\","<":"\\u003C"},Nc={"'":"\\'"};function Oc(a){for(var b=0,c=0;c>>0;return b}function Pc(a){return String(a).replace(/\-([a-z])/g,function(b,c){return c.toUpperCase()})}function Qc(a){return a.replace(/(^|[\s]+)([a-z])/g,function(b,c,d){return c+d.toUpperCase()})};function Rc(a){Rc[" "](a);return a}Rc[" "]=la;function Sc(a,b){try{return Rc(a[b]),!0}catch(c){}return!1}function Tc(a,b){var c=Uc;return Object.prototype.hasOwnProperty.call(c,a)?c[a]:c[a]=b(a)};var Vc=lc(),Wc=mc(),Xc=A("Edge"),Yc=Xc||Wc,Zc=A("Gecko")&&!(-1!=hc.toLowerCase().indexOf("webkit")&&!A("Edge"))&&!(A("Trident")||A("MSIE"))&&!A("Edge"),$c=-1!=hc.toLowerCase().indexOf("webkit")&&!A("Edge");function ad(){var a=q.document;return a?a.documentMode:void 0}var bd; +a:{var cd="",dd=function(){var a=hc;if(Zc)return/rv:([^\);]+)(\)|;)/.exec(a);if(Xc)return/Edge\/([\d\.]+)/.exec(a);if(Wc)return/\b(?:MSIE|rv)[: ]([^\);]+)(\)|;)/.exec(a);if($c)return/WebKit\/(\S+)/.exec(a);if(Vc)return/(?:Version)[ \/]?(\S+)/.exec(a)}();dd&&(cd=dd?dd[1]:"");if(Wc){var ed=ad();if(null!=ed&&ed>parseFloat(cd)){bd=String(ed);break a}}bd=cd}var fd=bd,Uc={};function gd(a){return Tc(a,function(){return 0<=Ib(fd,a)})}var hd; +if(q.document&&Wc){var id=ad();hd=id?id:parseInt(fd,10)||void 0}else hd=void 0;var jd=hd;var kd={},ld=null;function D(){}var md="function"==typeof Uint8Array; +function M(a,b,c,d){a.j=null;b||(b=[]);a.I=void 0;a.v=-1;a.m=b;a:{if(b=a.m.length){--b;var e=a.m[b];if(!(null===e||"object"!=typeof e||Array.isArray(e)||md&&e instanceof Uint8Array)){a.A=b-a.v;a.o=e;break a}}a.A=Number.MAX_VALUE}a.D={};if(c)for(b=0;be;e++){var f=c.concat(d[e].split(""));kd[e]=f;for(var g=0;g> +2;k=(k&3)<<4|l>>4;l=(l&15)<<2|h>>6;h&=63;f||(h=64,e||(l=64));c.push(b[g],b[k],b[l]||"",b[h]||"")}return c.join("")};try{return JSON.stringify(this.m&&xd(this),zd)}finally{Uint8Array.prototype.toJSON=a}}:function(){return JSON.stringify(this.m&&xd(this),zd)};function zd(a,b){return"number"!==typeof b||!isNaN(b)&&Infinity!==b&&-Infinity!==b?b:String(b)}function Ad(a,b){return new a(b?JSON.parse(b):null)}D.prototype.clone=function(){return new this.constructor(Bd(xd(this)))}; +function Bd(a){if(Array.isArray(a)){for(var b=Array(a.length),c=0;c{function e(){f.onload=null;f.onerror=null;b.document.body.removeChild(f)}const f=b.document.createElement("script");f.onload=()=>{e();c()};f.onerror=()=>{e();d(void 0)};f.type="text/javascript";Hc(f,a);"complete"!==b.document.readyState?R(b,"load",()=>{b.document.body.appendChild(f)}):b.document.body.appendChild(f)})};function ge(a){const b="https://pagead2.googlesyndication.com/getconfig/sodar"+`?sv=${200}&tid=${a.j}`+`&tv=${a.l}&st=`+`${a.ma}`;let c=Promise.resolve(void 0);try{c=he(b)}catch(d){}return c.then(d=>{if(d){var e=a.ya||d.sodar_query_id;if(e&&d.bg_hash_basename&&d.bg_binary)return{context:a.m,Pc:d.bg_hash_basename,Oc:d.bg_binary,ed:`${a.j}_${a.l}`,ya:e,ma:a.ma}}},()=>{})} +let he=a=>new Promise((b,c)=>{const d=new XMLHttpRequest;d.onreadystatechange=()=>{d.readyState===d.DONE&&(200<=d.status&&300>d.status?b(JSON.parse(d.responseText)):c())};d.open("GET",a,!0);d.send()}); +function ie(a){ge(a).then(b=>{if(b){var c=window,d=c.GoogleGcLKhOms;d&&"function"===typeof d.push||(d=c.GoogleGcLKhOms=[]);d.push({["_ctx_"]:b.context,["_bgv_"]:b.Pc,["_bgp_"]:b.Oc,["_li_"]:b.ed,["_jk_"]:b.ya,["_st_"]:b.ma});if(d=c.GoogleDX5YKUSk)c.GoogleDX5YKUSk=void 0,d[1]();c=ub(new mb(nb,"//tpc.googlesyndication.com/sodar/%{basename}.js"),{basename:"sodar2"});fe(c)}return b})};var je=class{constructor(a){this.j=a.j;this.l=a.l;this.m=a.m;this.ya=a.ya;this.win=a.K();this.ma=a.ma}},ke=class{constructor(a,b,c){this.j=a;this.l=b;this.m=c;this.win=window;this.ma="env"}K(){return this.win}};function le(a){M(this,a,me,null)}z(le,D);var me=[2,3];function ne(a){M(this,a,null,null)}z(ne,D);var oe=document,S=window;const pe={Id:"google_adtest",Md:"google_ad_client",Nd:"google_ad_format",Od:"google_ad_height",ae:"google_ad_width",Sd:"google_ad_layout",Td:"google_ad_layout_key",Ud:"google_ad_output",Vd:"google_ad_region",Yd:"google_ad_slot",Zd:"google_ad_type",$d:"google_ad_url",be:"google_allow_expandable_ads",re:"google_analytics_domain_name",se:"google_analytics_uacct",Ie:"google_container_id",Te:"google_gl",qf:"google_enable_ose",Cf:"google_full_width_responsive",xg:"google_rl_filtering",wg:"google_rl_mode", +yg:"google_rt",vg:"google_rl_dest_url",cg:"google_max_radlink_len",hg:"google_num_radlinks",ig:"google_num_radlinks_per_unit",Ld:"google_ad_channel",bg:"google_max_num_ads",dg:"google_max_responsive_height",De:"google_color_border",pf:"google_enable_content_recommendations",Qe:"google_content_recommendation_ui_type",Pe:"google_source_type",Oe:"google_content_recommendation_rows_num",Me:"google_content_recommendation_columns_num",Le:"google_content_recommendation_ad_positions",Re:"google_content_recommendation_use_square_imgs", +Fe:"google_color_link",Ee:"google_color_line",He:"google_color_url",Jd:"google_ad_block",Xd:"google_ad_section",Kd:"google_ad_callback",ze:"google_captcha_token",Ge:"google_color_text",pe:"google_alternate_ad_url",Rd:"google_ad_host_tier_id",Ae:"google_city",Pd:"google_ad_host",Qd:"google_ad_host_channel",qe:"google_alternate_color",Ce:"google_color_bg",tf:"google_encoding",zf:"google_font_face",We:"google_cust_ch",Ze:"google_cust_job",Ye:"google_cust_interests",Xe:"google_cust_id",$e:"google_cust_u_url", +Jf:"google_hints",Nf:"google_image_size",fe:"google_scs",rg:"google_core_dbp",eg:"google_mtl",gh:"google_cpm",Ke:"google_contents",gg:"google_native_settings_key",ph:"google_video_url_to_fetch",Se:"google_country",Xg:"google_targeting",Af:"google_font_size",ef:"google_disable_video_autoplay",oh:"google_video_product_type",mh:"google_video_doc_id",jg:"google_only_pyv_ads",Zf:"google_lact",kh:"google_cust_gender",sh:"google_yt_up",rh:"google_yt_pt",Tg:"google_cust_lh",Sg:"google_cust_l",fh:"google_tfs", +fg:"google_native_ad_template",Wf:"google_kw",Ug:"google_tag_for_child_directed_treatment",Vg:"google_tag_for_under_age_of_consent",Bg:"google_region",Ve:"google_cust_criteria",Wd:"google_safe",Ue:"google_ctr_threshold",Fg:"google_resizing_allowed",Hg:"google_resizing_width",Gg:"google_resizing_height",jh:"google_cust_age",LANGUAGE:"google_language",Xf:"google_kw_type",sg:"google_pucrd",qg:"google_page_url",Wg:"google_tag_partner",rf:"google_enable_single_iframe",Lg:"google_restrict_data_processing"};function qe(a){M(this,a,null,re)}z(qe,D);function se(a){M(this,a,null,null)}z(se,D);var re=[[3,4,5]];function te(a){this.j=a||{cookie:""}} +te.prototype.set=function(a,b,c){let d,e;let f=!1,g;if("object"===typeof c){g=c.xh;f=c.zd||!1;var h=c.domain||void 0;e=c.path||void 0;d=c.jd}if(/[;=\s]/.test(a))throw Error('Invalid cookie name "'+a+'"');if(/[;\r\n]/.test(b))throw Error('Invalid cookie value "'+b+'"');void 0===d&&(d=-1);this.j.cookie=a+"="+b+(h?";domain="+h:"")+(e?";path="+e:"")+(0>d?"":0==d?";expires="+(new Date(1970,1,1)).toUTCString():";expires="+(new Date(+new Date+1E3*d)).toUTCString())+(f?";secure":"")+(null!=g?";samesite="+ +g:"")};te.prototype.get=function(a,b){for(var c=a+"=",d=(this.j.cookie||"").split(";"),e=0,f;e(a=(new te(a)).get("DATA_USE_CONSENT",""))?a:null;var ve=a=>{var b=(b=(new te(a)).get("FCCDCF",""))?b:null;try{var c=b?Ad(qe,b):null}catch(d){c=null}if(!c)return ue(a);c=O(c,se,3);if(!c||null==N(c,1))return ue(a);a=N(c,2);b=Date.now();if(a){if(ba+33696E6)return null}else return null;return N(c,1)};function we(a){M(this,a,xe,null)}z(we,D);var xe=[1,2,3,4];function ye(a){ze();return new qb(rb,a)}var ze=la;function Ae(){return!(A("iPad")||A("Android")&&!A("Mobile")||A("Silk"))&&(A("iPod")||A("iPhone")||A("Android")||A("IEMobile"))};var Be=/^(?:([^:/?#.]+):)?(?:\/\/(?:([^\\/?#]*)@)?([^\\/?#]*?)(?::([0-9]+))?(?=[\\/?#]|$))?([^?#]+)?(?:\?([^#]*))?(?:#([\s\S]*))?$/;function Ce(a){return a.match(Be)}function De(a){return a?decodeURI(a):a};function Ee(a){try{return!!a&&null!=a.location.href&&Sc(a,"foo")}catch(b){return!1}}function Fe(a,b,c,d){d=d||q;c&&(d=Ge(d));for(c=0;d&&40>c++&&(!b&&!Ee(d)||!a(d));)d=Ge(d)}function He(){let a=q;Fe(b=>{a=b;return!1});return a}function Ge(a){try{const b=a.parent;if(b&&b!=a)return b}catch(b){}return null}function Ie(a,b){const c=a.createElement("script");Hc(c,ye(b));(a=a.getElementsByTagName("script")[0])&&a.parentNode&&a.parentNode.insertBefore(c,a)} +function Je(a,b){return b.getComputedStyle?b.getComputedStyle(a,null):a.currentStyle}function Ke(a,b,c=!0){let d=!1;c||(d=Le());return!d&&!Me()&&(c=Math.random(),c>2)+a.charCodeAt(d)&4294967295;return 0Ka(["Google Web Preview","Mediapartners-Google","Google-Read-Aloud","Google-Adwords"],Te)||1E-4>Math.random()),Le=Ya(()=>-1!=hc.indexOf("MSIE"));const Te=a=>-1!=hc.indexOf(a);var Ue=/^([0-9.]+)px$/,Ve=/^(-?[0-9.]{1,30})$/; +function We(a){return Ve.test(a)&&(a=Number(a),!isNaN(a))?a:null}function Xe(a){return/^true$/.test(a)}function Ye(a){return(a=Ue.exec(a))?+a[1]:null}function Ze(){var a=q.document.URL;if(!a)return"";const b=/.*[&#?]google_debug(=[^&]*)?(&.*)?$/;try{const c=b.exec(decodeURIComponent(a));if(c)return c[1]&&1Re($e));function of(){var a=["allow-top-navigation","allow-modals","allow-orientation-lock","allow-presentation"];const b=nf();return a.length?Ha(b,c=>!Ma(a,c)):b} +function pf(){const a=Td(document,"IFRAME"),b={};Ga(nf(),c=>{a.sandbox&&a.sandbox.supports&&a.sandbox.supports(c)&&(b[c]=!0)});return b} +var qf=(a,b)=>{try{return!(!a.frames||!a.frames[b])}catch(c){return!1}},rf=(a,b)=>{for(let c=0;50>c;++c){if(qf(a,b))return a;if(!(a=Ge(a)))break}return null},wf=(a,b)=>{a.style.setProperty?Oe(b,(c,d)=>{a.style.setProperty(d,c,"important")}):a.style.cssText=sf(tf(uf(a.style.cssText),vf(b,c=>c+" !important")))},tf=Object.assign||function(a,b){for(let c=1;c{const c= +{};for(let d in a)Object.prototype.hasOwnProperty.call(a,d)&&(c[d]=b.call(void 0,a[d],d,a));return c},sf=a=>{const b=[];Oe(a,(c,d)=>{null!=c&&""!==c&&b.push(d+":"+c)});return b.length?b.join(";")+";":""},uf=a=>{const b={};if(a){const c=/\s*:\s*/;Ga((a||"").split(/\s*;\s*/),d=>{if(d){var e=d.split(c);d=e[0];e=e[1];d&&e&&(b[d.toLowerCase()]=e)}})}return b},xf={"http://googleads.g.doubleclick.net":!0,"http://pagead2.googlesyndication.com":!0,"https://googleads.g.doubleclick.net":!0,"https://pagead2.googlesyndication.com":!0}, +yf=/\.proxy\.googleprod\.com(:\d+)?$/,zf=(a,b=!1)=>!!xf[a]||b&&yf.test(a),Af=(a,b)=>{b=La(a,b);if(0<=b){const c=a[b];Array.prototype.splice.call(a,b,1);return c}return null},Bf=a=>{if("number"!==typeof a.goog_pvsid)try{Object.defineProperty(a,"goog_pvsid",{value:Math.floor(Math.random()*2**52)})}catch(b){}return Number(a.goog_pvsid)||-1}; +function Cf(a,b,c,d=[]){const e=new a.MutationObserver(f=>{for(const g of f)for(const h of g.removedNodes)if(d&&(h===b||Ud(h,b))){for(const k of d)k.disconnect();d.length=0;c();return}});d.push(e);e.observe(a.document.documentElement,{childList:!0,subtree:!0});Fe(f=>{if(!f.parent||!Ee(f.parent))return!1;const g=f.parent.document.getElementsByTagName("iframe");for(let l=0;l{Cf(Sd(Pd(a)),a,b)};var Qe={Uf:0,Hf:1,Gf:2,Ff:3,tg:4,ug:5,Lf:6,If:7};const Ef=a=>{var b=document;try{const d=ve(b);var c=d?Ad(we,d):null}catch(d){c=null}if(!c)return 0;if(rd(c,7))return 4;if(a){if(Ma(N(c,3),a))return 2;if(Ma(N(c,4),a))return 3}return 1};function Ff(a,b,c=!1){switch(a){case 2:case 4:return!1;case 3:return!0;case 1:return b;default:return c&&b}}const Gf=Ya(()=>{const a=/[?&]fc(consent)?=alwaysshow([&#]|$)/;try{return a.test(q.top.location.href)}catch(b){return a.test(q.location.href)}}); +var Hf=(a,b)=>{for(var c=Pe().length,d=[],e=0;e{const d=Hf(a,b);d.jc?q.setTimeout(()=>{If(a,b,c)},1E3): +c(d)};class Jf{constructor(a,b,c,d){this.j=a;this.pubWin=b;this.iframeWin=c;this.B=d||c||{};this.o=b.document.getElementById(this.B.google_async_iframe_id+"_anchor");this.T=b.document.getElementById(this.B.google_async_iframe_id+"_expand");this.v=-1;this.A=!1;this.F="";this.l=0;this.C=this.J=null;this.H=0;this.D=null;this.N=0;this.m=[];this.tcString=this.I="";this.gdprApplies=void 0;this.addtlConsent=""}};var Kf=(a,b)=>{a=parseFloat(a);return isNaN(a)||1a?b:a};const Lf=/^([\w-]+\.)*([\w-]{2,})(:[0-9]+)?$/;var Mf=(a,b)=>a?(a=a.match(Lf))?a[0]:b:b;var Nf=()=>"r20200428",Of=Xe("false"),Pf=Xe("false"),Qf=Xe("false"),Rf=Xe("false"),Sf=Xe("false"),Tf=Xe("true");let Uf=Tf||!Rf;var Vf=Kf("0.02",0),Wf=Kf("0.0",0);var Xf=()=>Mf("","googleads.g.doubleclick.net"),Yf=()=>Mf("","pagead2.googlesyndication.com");function Zf(){this.T=this.T;this.$=this.$}Zf.prototype.T=!1;Zf.prototype.Ma=function(){this.T||(this.T=!0,this.l())};Zf.prototype.l=function(){if(this.$)for(;this.$.length;)this.$.shift()()};class $f{constructor(a){this.methodName=a}}var ag=new $f(15),bg=new $f(2),cg=new $f(3),dg=new $f(5),eg=new $f(6),fg=(a,b,c)=>b[a.methodName]||c||(()=>{});function gg(a,b){a.j=(c,d)=>fg(dg,b)(c,d,1);a.m=(c,d)=>fg(eg,b)(c,d,1);a.l=()=>{fg(ag,b)(1)}}class T{constructor(){this.j=(a,b=!1)=>b;this.m=(a,b=0)=>b;this.l=()=>{}}}na(T);const hg=(a,b=0)=>T.G().m(a,b);function ig(a,b,c,d){this.top=a;this.right=b;this.bottom=c;this.left=d}n=ig.prototype;n.Pa=function(){return this.right-this.left};n.gb=function(){return this.bottom-this.top};n.clone=function(){return new ig(this.top,this.right,this.bottom,this.left)};n.contains=function(a){return this&&a?a instanceof ig?a.left>=this.left&&a.right<=this.right&&a.top>=this.top&&a.bottom<=this.bottom:a.x>=this.left&&a.x<=this.right&&a.y>=this.top&&a.y<=this.bottom:!1}; +n.expand=function(a,b,c,d){ra(a)?(this.top-=a.top,this.right+=a.right,this.bottom+=a.bottom,this.left-=a.left):(this.top-=a,this.right+=Number(b),this.bottom+=Number(c),this.left-=Number(d));return this};function jg(a,b){return a.left<=b.right&&b.left<=a.right&&a.top<=b.bottom&&b.top<=a.bottom}n.ceil=function(){this.top=Math.ceil(this.top);this.right=Math.ceil(this.right);this.bottom=Math.ceil(this.bottom);this.left=Math.ceil(this.left);return this}; +n.floor=function(){this.top=Math.floor(this.top);this.right=Math.floor(this.right);this.bottom=Math.floor(this.bottom);this.left=Math.floor(this.left);return this};n.round=function(){this.top=Math.round(this.top);this.right=Math.round(this.right);this.bottom=Math.round(this.bottom);this.left=Math.round(this.left);return this}; +n.translate=function(a,b){a instanceof Ld?(this.left+=a.x,this.right+=a.x,this.top+=a.y,this.bottom+=a.y):(this.left+=a,this.right+=a,"number"===typeof b&&(this.top+=b,this.bottom+=b));return this};n.scale=function(a,b){b="number"===typeof b?b:a;this.left*=a;this.right*=a;this.top*=b;this.bottom*=b;return this};function kg(a,b,c,d){this.left=a;this.top=b;this.width=c;this.height=d}n=kg.prototype;n.clone=function(){return new kg(this.left,this.top,this.width,this.height)};function lg(a,b){var c=Math.max(a.left,b.left),d=Math.min(a.left+a.width,b.left+b.width);if(c<=d){var e=Math.max(a.top,b.top);a=Math.min(a.top+a.height,b.top+b.height);if(e<=a)return new kg(c,e,d-c,a-e)}return null} +function mg(a,b){var c=lg(a,b);if(!c||!c.height||!c.width)return[a.clone()];c=[];var d=a.top,e=a.height,f=a.left+a.width,g=a.top+a.height,h=b.left+b.width,k=b.top+b.height;b.top>a.top&&(c.push(new kg(a.left,a.top,a.width,b.top-a.top)),d=b.top,e-=b.top-a.top);ka.left&&c.push(new kg(a.left,d,b.left-a.left,e));h=this.left&&a.x<=this.left+this.width&&a.y>=this.top&&a.y<=this.top+this.height:this.left<=a.left&&this.left+this.width>=a.left+a.width&&this.top<=a.top&&this.top+this.height>=a.top+a.height};n.ceil=function(){this.left=Math.ceil(this.left);this.top=Math.ceil(this.top);this.width=Math.ceil(this.width);this.height=Math.ceil(this.height);return this}; +n.floor=function(){this.left=Math.floor(this.left);this.top=Math.floor(this.top);this.width=Math.floor(this.width);this.height=Math.floor(this.height);return this};n.round=function(){this.left=Math.round(this.left);this.top=Math.round(this.top);this.width=Math.round(this.width);this.height=Math.round(this.height);return this};n.translate=function(a,b){a instanceof Ld?(this.left+=a.x,this.top+=a.y):(this.left+=a,"number"===typeof b&&(this.top+=b));return this}; +n.scale=function(a,b){b="number"===typeof b?b:a;this.left*=a;this.width*=a;this.top*=b;this.height*=b;return this};const ng={"AMP-CAROUSEL":"ac","AMP-FX-FLYING-CARPET":"fc","AMP-LIGHTBOX":"lb","AMP-STICKY-AD":"sa"};function og(a=q){let b=a.context||a.AMP_CONTEXT_DATA;if(!b)try{b=a.parent.context||a.parent.AMP_CONTEXT_DATA}catch(c){}try{if(b&&b.pageViewId&&b.canonicalUrl)return b}catch(c){}return null}function pg(){const a=og();return a&&a.initialIntersection}function qg(){const a=pg();return a&&ra(a.rootBounds)?new Md(a.rootBounds.width,a.rootBounds.height):null} +function rg(a){return(a=a||og())?Ee(a.master)?a.master:null:null} +function sg(a,b){function c(g){if(a.ampInaboxInitialized)e();else{var h,k=T.G().j(198,!1)&&"amp-ini-load"===g.data;a.ampInaboxPendingMessages&&!k&&(h=/^amp-(\d{15,20})?/.exec(g.data))&&(a.ampInaboxPendingMessages.push(g),g=h[1],a.ampInaboxInitialized||g&&!/^\d{15,20}$/.test(g)||a.document.querySelector('script[src$="amp4ads-host-v0.js"]')||Ie(a.document,"https://cdn.ampproject.org/"+(g?`rtv/${g}/`:"")+"amp4ads-host-v0.js"))}}const d=a.ampInaboxIframes=a.ampInaboxIframes||[];let e=()=>{},f=()=>{}; +b&&(d.push(b),f=()=>{a.AMP&&a.AMP.inaboxUnregisterIframe&&a.AMP.inaboxUnregisterIframe(b);Na(d,b);e()});if(a.ampInaboxInitialized)return f;a.ampInaboxPendingMessages=a.ampInaboxPendingMessages||[];d.google_amp_listener_added||(d.google_amp_listener_added=!0,R(a,"message",c),e=()=>{ee(a,"message",c)});return f};function tg(a,b=null){ug(a,b)}function ug(a,b){q.google_image_requests||(q.google_image_requests=[]);const c=q.document.createElement("img");if(b){const d=e=>{b&&b(e);ee(c,"load",d);ee(c,"error",d)};R(c,"load",d);R(c,"error",d)}c.src=a;q.google_image_requests.push(c)};function vg(a,b,c){if("string"===typeof b)(b=wg(a,b))&&(a.style[b]=c);else for(var d in b){c=a;var e=b[d],f=wg(c,d);f&&(c.style[f]=e)}}var xg={};function wg(a,b){var c=xg[b];if(!c){var d=Pc(b);c=d;void 0===a.style[d]&&(d=($c?"Webkit":Zc?"Moz":Wc?"ms":Vc?"O":null)+Qc(d),void 0!==a.style[d]&&(c=d));xg[b]=c}return c}function yg(a,b){var c=Pd(a);return c.defaultView&&c.defaultView.getComputedStyle&&(a=c.defaultView.getComputedStyle(a,null))?a[b]||a.getPropertyValue(b)||"":""} +function zg(a){return yg(a,"position")||(a.currentStyle?a.currentStyle.position:null)||a.style&&a.style.position}function Ag(a){try{var b=a.getBoundingClientRect()}catch(c){return{left:0,top:0,right:0,bottom:0}}Wc&&a.ownerDocument.body&&(a=a.ownerDocument,b.left-=a.documentElement.clientLeft+a.body.clientLeft,b.top-=a.documentElement.clientTop+a.body.clientTop);return b} +function Bg(a){var b=Pd(a),c=new Ld(0,0);var d=b?Pd(b):document;d=!Wc||9<=Number(jd)||"CSS1Compat"==Nd(d).j.compatMode?d.documentElement:d.body;if(a==d)return c;a=Ag(a);b=Rd(Nd(b).j);c.x=a.left+b.x;c.y=a.top+b.y;return c}function Cg(a,b){if(/^\d+px?$/.test(b))return parseInt(b,10);var c=a.style.left,d=a.runtimeStyle.left;a.runtimeStyle.left=a.currentStyle.left;a.style.left=b;b=a.style.pixelLeft;a.style.left=c;a.runtimeStyle.left=d;return+b} +function Dg(a,b){return(b=a.currentStyle?a.currentStyle[b]:null)?Cg(a,b):0}var Eg={thin:2,medium:4,thick:6};function Fg(a,b){if("none"==(a.currentStyle?a.currentStyle[b+"Style"]:null))return 0;b=a.currentStyle?a.currentStyle[b+"Width"]:null;return b in Eg?Eg[b]:Cg(a,b)};var U=(a,b)=>{if(a)for(let c in a)Object.prototype.hasOwnProperty.call(a,c)&&b.call(void 0,a[c],c,a)},Gg=a=>!(!a||!a.call)&&"function"===typeof a,Hg=(a,b)=>{if(a.filter)return a.filter(b,void 0);const c=[];for(let d=0;d{var a=u();"google_onload_fired"in a||(a.google_onload_fired=!1,R(a,"load",()=>{a.google_onload_fired=!0}))},Jg=(a,b)=>{const c=b.slice(-1);let d="?"===c||"#"===c?"":"&";const e=[b];U(a,(f,g)=>{if(f||0===f||!1===f)"boolean"=== +typeof f&&(f=f?1:0),e.push(d),e.push(g),e.push("="),e.push(encodeURIComponent(String(f))),d="&"});return e.join("")},Kg=()=>{try{return S.history.length}catch(a){return 0}},Lg=a=>{a=rg(og(a))||a;a.google_unique_id?++a.google_unique_id:a.google_unique_id=1},Mg=a=>{a=a.google_unique_id;return"number"===typeof a?a:0},Ng=a=>{let b;b=9!==a.nodeType&&a.id;a:{if(a&&a.nodeName&&a.parentElement){var c=a.nodeName.toString().toLowerCase();const d=a.parentElement.childNodes;let e=0;for(let f=0;f!!a.google_async_iframe_id,Pg=Og(window);let Qg=Pg&&window.parent||window; +var u=()=>{if(Pg&&!Ee(Qg)){let a="."+oe.domain;try{for(;2function(){if(a){const b=a;a=null;b.apply(null,arguments)}},Ug=()=>{if(!S)return!1;try{return!(!S.navigator.standalone&&!Tg(S).navigator.standalone)}catch(a){return!1}},Vg=()=>{var a;let b;const c=window.ActiveXObject;if(navigator.plugins&&navigator.mimeTypes.length){if((a=navigator.plugins["Shockwave Flash"])&& +a.description)return a.description.replace(/([a-zA-Z]|\s)+/,"").replace(/(\s)+r/,".")}else{if(navigator.userAgent&&0<=navigator.userAgent.indexOf("Windows CE")){b=3;for(a=1;a;)try{a=new c("ShockwaveFlash.ShockwaveFlash."+(b+1)),b++}catch(d){a=null}return b.toString()}if(mc()){a=null;try{a=new c("ShockwaveFlash.ShockwaveFlash.7")}catch(d){b=0;try{a=new c("ShockwaveFlash.ShockwaveFlash.6"),b=6,a.AllowScriptAccess="always"}catch(e){if(6===b)return b.toString()}try{a=new c("ShockwaveFlash.ShockwaveFlash")}catch(e){}}if(a)return b= +a.GetVariable("$version").split(" ")[1],b.replace(/,/g,".")}}return"0"},Wg=a=>(a=a.google_ad_format)?0{if(Qf)try{const a=S.google_cafe_host||S.top.google_cafe_host;if(a)return a}catch(a){}return Yf()},Tg=a=>Qf&&a.google_top_window||a.top,Yg=a=>{a=Tg(a);return Ee(a)?a:null},Zg=a=>{let b=Number(a.google_ad_width),c=Number(a.google_ad_height);if(!(0a.source!==b.contentWindow&&a.source.parent!==b.contentWindow?!1:!0;var ah=a=>{a.google_ad_modifications||(a.google_ad_modifications={});return a.google_ad_modifications},bh=(a,b)=>{a=ah(a);a.processed_sra_frame_pingbacks=a.processed_sra_frame_pingbacks||{};const c=!a.processed_sra_frame_pingbacks[b];a.processed_sra_frame_pingbacks[b]=!0;return c};var ch={["google_ad_channel"]:"channel",["google_ad_type"]:"ad_type",["google_ad_format"]:"format",["google_color_bg"]:"color_bg",["google_color_border"]:"color_border",["google_color_link"]:"color_link",["google_color_text"]:"color_text",["google_color_url"]:"color_url",["google_page_url"]:"url",["google_allow_expandable_ads"]:"ea",["google_ad_section"]:"region",["google_cpm"]:"cpm",["google_encoding"]:"oe",["google_safe"]:"adsafe",["google_flash_version"]:"flash",["google_font_face"]:"f",["google_font_size"]:"fs", +["google_hints"]:"hints",["google_ad_host"]:"host",["google_ad_host_channel"]:"h_ch",["google_ad_host_tier_id"]:"ht_id",["google_kw_type"]:"kw_type",["google_kw"]:"kw",["google_contents"]:"contents",["google_targeting"]:"targeting",["google_adtest"]:"adtest",["google_alternate_color"]:"alt_color",["google_alternate_ad_url"]:"alternate_ad_url",["google_cust_age"]:"cust_age",["google_cust_ch"]:"cust_ch",["google_cust_gender"]:"cust_gender",["google_cust_interests"]:"cust_interests",["google_cust_job"]:"cust_job", +["google_cust_l"]:"cust_l",["google_cust_lh"]:"cust_lh",["google_cust_u_url"]:"cust_u_url",["google_cust_id"]:"cust_id",["google_language"]:"hl",["google_city"]:"gcs",["google_country"]:"gl",["google_region"]:"gr",["google_content_recommendation_ad_positions"]:"ad_pos",["google_content_recommendation_columns_num"]:"cr_col",["google_content_recommendation_rows_num"]:"cr_row",["google_content_recommendation_ui_type"]:"crui",["google_content_recommendation_use_square_imgs"]:"cr_sq_img",["google_color_line"]:"color_line", +["google_disable_video_autoplay"]:"disable_video_autoplay",["google_full_width_responsive_allowed"]:"fwr",["google_full_width_responsive"]:"fwrattr",["efwr"]:"efwr",["google_pgb_reactive"]:"pra",["google_resizing_allowed"]:"rs",["google_resizing_height"]:"rh",["google_resizing_width"]:"rw",["rpe"]:"rpe",["google_responsive_formats"]:"resp_fmts",["google_safe_for_responsive_override"]:"sfro",["google_video_doc_id"]:"video_doc_id",["google_video_product_type"]:"video_product_type",["google_webgl_support"]:"wgl", +["google_refresh_count"]:"rc"},dh={["google_ad_block"]:"ad_block",["google_ad_client"]:"client",["google_ad_output"]:"output",["google_ad_callback"]:"callback",["google_ad_height"]:"h",["google_ad_resize"]:"twa",["google_ad_slot"]:"slotname",["google_ad_unit_key"]:"adk",["google_ad_dom_fingerprint"]:"adf",["google_ad_width"]:"w",["google_captcha_token"]:"captok",["google_content_recommendation_columns_num"]:"cr_col",["google_content_recommendation_rows_num"]:"cr_row",["google_ctr_threshold"]:"ctr_t", +["google_cust_criteria"]:"cust_params",["gfwrnwer"]:"fwrn",["gfwrnher"]:"fwrnh",["google_bfa"]:"bfa",["ebfa"]:"ebfa",["ebfaca"]:"ebfaca",["google_image_size"]:"image_size",["google_last_modified_time"]:"lmt",["google_loeid"]:"loeid",["google_max_num_ads"]:"num_ads",["google_max_radlink_len"]:"max_radlink_len",["google_mtl"]:"mtl",["google_native_settings_key"]:"nsk",["google_enable_content_recommendations"]:"ecr",["google_num_radlinks"]:"num_radlinks",["google_num_radlinks_per_unit"]:"num_radlinks_per_unit", +["google_pucrd"]:"pucrd",["google_reactive_plaf"]:"plaf",["google_reactive_plat"]:"plat",["google_reactive_fba"]:"fba",["google_reactive_sra_channels"]:"plach",["google_responsive_auto_format"]:"rafmt",["armr"]:"armr",["google_rl_dest_url"]:"rl_dest_url",["google_rl_filtering"]:"rl_filtering",["google_rl_mode"]:"rl_mode",["google_rt"]:"rt",["google_source_type"]:"src_type",["google_restrict_data_processing"]:"rdp",["google_tag_for_child_directed_treatment"]:"tfcd",["google_tag_for_under_age_of_consent"]:"tfua", +["google_tag_origin"]:"to",["google_ad_semantic_area"]:"sem",["google_tfs"]:"tfs",["google_package"]:"pwprc",["google_tag_partner"]:"tp",["fra"]:"fpla",["google_ml_rank"]:"mlr",["google_apsail"]:"psa"},eh={["google_core_dbp"]:"dbp",["google_lact"]:"lact",["google_only_pyv_ads"]:"pyv",["google_scs"]:"scs",["google_video_url_to_fetch"]:"durl",["google_yt_pt"]:"yt_pt",["google_yt_up"]:"yt_up"};var fh=a=>{U(ch,(b,c)=>{a[c]=null});U(dh,(b,c)=>{a[c]=null});U(eh,(b,c)=>{a[c]=null});a.google_container_id=null;a.google_eids=null;a.google_page_location=null;a.google_referrer_url=null;a.google_enable_single_iframe=null;a.google_ad_region=null;a.google_gl=null;a.google_loader_used=null;a.google_loader_features_used=null;a.google_debug_params=null},gh=(a,b,c)=>{a.l|=2;return b[c%b.length]};var db={zg:0,vf:1,wf:2,Df:8,Og:9,Kg:16,cf:17,bf:24,Yf:25,ue:26,te:27,rc:30,Qf:32,Tf:40};var hh=a=>{const b=a.iframeWin;if(b&&Og(b)&&b!=b.parent&&b.google_async_iframe_close){const c=()=>{b.setTimeout(()=>{b.document.close()},0)};a.D?a.D(c):c()}};class ih{constructor(a,b,c={}){this.error=a;this.context=b.context;this.msg=b.message||"";this.id=b.id||"jserror";this.meta=c}};const jh=[/^https?:\/\/(secure)?pubads\.g\.doubleclick\.net(:\d+)?($|\/)/i,/^https?:\/\/(googleads|adx)\.g\.doubleclick\.net(:\d+)?($|\/)/i,/^https?:\/\/(?!adx)ad.*\.doubleclick\.net(:\d+)?($|\/)/i,/^https?:\/\/(tpc|pagead2)\.googlesyndication\.com(:\d+)?($|\/)/i,/^https?:\/\/www\.googletagservices\.com(:\d+)?($|\/)/i,/^https?:\/\/adservice\.google\.(com?\.)?[a-z]{2,3}(:\d+)?($|\/)/i];var kh=a=>Ka(jh,b=>b.test(a)); +function lh(a){if(a=/[-\w]+\.[-\w]+$/.exec(a))switch(Oc(a[0].toLowerCase())){case 1967261364:return 0;case 3147493546:return 1;case 1567346461:return 2;case 2183041838:return 3;case 763236279:return 4;case 1342279801:return 5;case 526831769:return 6;case 352806002:return 7;case 2755048925:return 8;case 3306848407:return 9;case 2207000920:return 10;case 484037040:return 11;case 3506871055:return 12;case 672143848:return 13;case 2528751226:return 14;case 2744854768:return 15;case 3703278665:return 16; +case 2014749173:return 17;case 133063824:return 18;case 2749334602:return 19;case 3131239845:return 20;case 2074086763:return 21;case 795772493:return 22;case 290857819:return 23;case 3035947606:return 24;case 2983138003:return 25;case 2197138676:return 26;case 4216016165:return 27;case 239803524:return 28;case 975993579:return 29;case 1794940339:return 30;case 1314429186:return 31;case 1643618937:return 32;case 497159982:return 33;case 3882239661:return 34}return-1} +function mh(a){if(!a.length)return 0;let b=[];for(var c=0;34>=c;c++)b[c]=0;for(c=a.length-1;0<=c;c--){const d=lh(a[c]);0<=d&&(b[34-d]=1)}return parseInt(b.join(""),2)};const nh=/^https?:\/\/(\w|-)+\.cdn\.ampproject\.(net|org)(\?|\/|$)/; +function oh(a){var b=a||q;const c=[];let d,e=null,f,g;do{g=b;Ee(g)?(d=g.location.href,e=g.document&&g.document.referrer||null,f=!0):(d=e,e=null,f=!1);c.push(new ph(d||"",g,f));try{b=g.parent}catch(h){b=null}}while(b&&g!=b);for(let h=0,k=c.length-1;h<=k;++h)c[h].depth=k-h;g=a||q;if(g.location&&g.location.ancestorOrigins&&g.location.ancestorOrigins.length==c.length-1)for(a=1;ae?encodeURIComponent(uh(a,b,c,d,e+1)):"...";return encodeURIComponent(String(a))}function wh(a,b,c,d){a.j.push(b);a.l[b]=th(c,d)} +function xh(a){if(!a.o)return a.A;let b=1;for(const c in a.l)b=c.length>b?c.length:b;return a.A-a.o.length-b-a.m.length-1} +function yh(a,b,c,d){b=b+"//"+c+d;let e=xh(a)-d.length;if(0>e)return"";a.j.sort(function(g,h){return g-h});d=null;c="";for(var f=0;f=l.length){e-=l.length;b+=l;c=a.m;break}a.v&&(c=e,l[c-1]==a.m&&--c,b+=l.substr(0,c),c=a.m,e=0);d=null==d?g:d}}}f="";a.o&&null!=d&&(f=c+a.o+"="+(a.F||d));return b+f} +class Oh{constructor(a,b,c,d,e){this.A=c||4E3;this.m=a||"&";this.C=b||",$";this.o=void 0!==d?d:"trn";this.F=e||null;this.v=!1;this.l={};this.D=0;this.j=[]}};function Ph(a,b,c,d,e,f){if((d?a.j:Math.random())<(e||a.l))try{let g;c instanceof Oh?g=c:(g=new Oh,Oe(c,(k,l)=>{var m=g,p=m.D++;k=th(l,k);m.j.push(p);m.l[p]=k}));const h=yh(g,a.v,a.m,a.o+b+"&");h&&("undefined"===typeof f?tg(h):tg(h,f))}catch(g){}}class Qh{constructor(a,b,c,d){this.v=a;this.m=b;this.o=c;this.l=d;this.j=Math.random()}};let Rh=!1,Sh=null;function Th(){var a=Uh();const b=new Vh;Oe(a.j,function(c,d){b.j[d]=c});Oe(a.l,function(c,d){b.l[d]=c});return b}function Wh(){if(null===Sh){Sh="";try{let a="";try{a=q.top.location.hash}catch(b){a=q.location.hash}if(a){const b=a.match(/\bdeid=([\d,]+)/);Sh=b?b[1]:""}}catch(a){}}return Sh}function Xh(a,b,c){return""==b?"":c?a.l.hasOwnProperty(c)?a.l[c]=b:"":(a.j[b]=!0,b)} +function Yh(a,b,c,d){if(a.m)return"";if(d?a.l.hasOwnProperty(d)&&""==a.l[d]:1){var e;e=(e=Wh())?(e=e.match(new RegExp("\\b("+b.join("|")+")\\b")))?e[0]:null:null;if(b=e?e:Rh?null:Ke(b,c,!1))return Xh(a,b,d)}return""}function Zh(a,b){return a.l.hasOwnProperty(b)?a.l[b]:""}function $h(a){const b=[];Oe(a.j,function(c,d){b.push(d)});Oe(a.l,function(c){""!=c&&b.push(c)});return b}class Vh{constructor(a){this.j={};this.l={};this.m=!1;a=a||[];for(let b=0,c=a.length;b{const a=q.performance;return a&&a.now&&a.timing?Math.floor(a.now()+a.timing.navigationStart):+new Date},bi=()=>{const a=q.performance;return a&&a.now?a.now():null};class ci{constructor(a,b,c,d=0,e){this.label=a;this.type=b;this.value=c;this.duration=d;this.uniqueId=Math.random();this.slotId=e}};const di=q.performance,ei=!!(di&&di.mark&&di.measure&&di.clearMarks),fi=Ya(()=>{var a;if(a=ei)a=Wh(),a=!!a.indexOf&&0<=a.indexOf("1337");return a});function gi(a){a&&di&&fi()&&(di.clearMarks(`goog_${a.label}_${a.uniqueId}_start`),di.clearMarks(`goog_${a.label}_${a.uniqueId}_end`))}function hi(a){a.j=!1;a.l!=a.m.google_js_reporting_queue&&(fi()&&Ga(a.l,gi),a.l.length=0)} +function ii(a,b){if(a.j&&"number"===typeof b.value){var c=bi()||ai();b.duration=c-b.value;c=`goog_${b.label}_${b.uniqueId}_end`;di&&fi()&&di.mark(c);!a.j||2048ni(a,b,()=>c.apply(d,f),e)} +class pi{constructor(a,b,c,d=null){this.A=a;this.D=b;this.o=c;this.l=null;this.C=this.j;this.m=d;this.v=!1}j(a,b,c,d,e){e=e||this.D;let f;try{const k=new Oh;k.v=!0;wh(k,1,"context",a);b.error&&b.meta&&b.id||(b=new ih(b,{message:li(b)}));b.msg&&wh(k,2,"msg",b.msg.substring(0,512));var g=b.meta||{};b=g;if(this.l)try{this.l(b)}catch(l){}if(d)try{d(b)}catch(l){}d=k;g=[g];d.j.push(3);d.l[3]=g;{const l=oh();let m=new ph(q.location.href,q,!0,!1);g=null;const p=l.length-1;for(d=p;0<=d;--d){var h=l[d];!g&& +nh.test(h.url)&&(g=h);if(h.url&&!h.Vb){m=h;break}}h=null;const r=l.length&&l[p].url;0!=m.depth&&r&&(h=l[p]);f=new sh(m,h,g)}f.l&&wh(k,4,"top",f.l.url||"");wh(k,5,"url",f.j.url||"");Ph(this.A,e,k,this.v,c)}catch(k){try{Ph(this.A,e,{context:"ecmserr",rctx:a,msg:li(k),url:f&&f.j.url},this.v,c)}catch(l){}}return this.o}};let qi,ri;const si=u(),ti=new ki(1,si),ui=a=>{var b=S.jerExpIds;if(pa(b)&&0!==b.length){var c=a.eid;if(c){b=[...c.split(","),...b];c={};for(var d=0,e=0;e{const b=S.jerUserAgent;b&&(a.useragent=b)}; +qi=new Qh("http:"===S.location.protocol?"http:":"https:","pagead2.googlesyndication.com","/pagead/gen_204?id=",.01);"number"!==typeof si.google_srt&&(si.google_srt=Math.random());var wi=si.google_srt;0<=wi&&1>=wi&&(qi.j=wi);ri=new pi(qi,"jserror",!0,ti);ri.l=a=>{ui(a);vi(a)};ri.v=!0;"complete"==si.document.readyState?si.google_measure_js_timing||hi(ti):ti.j&&R(si,"load",()=>{si.google_measure_js_timing||hi(ti)}); +var xi=()=>{},yi=(a,b)=>ni(ri,a,b,void 0),W=(a,b,c)=>oi(ri,a,b,c,void 0),Y=(a,b,c)=>{Ph(qi,a,b,!0,c,void 0)},zi=(a,b)=>{Y("rmvasft",{code:a,branch:b?"exp":"cntr"})};var Ai=(a,b)=>{const c=Ze();return a+(-1==a.indexOf("?")?"?":"&")+[0{const e=g=>{let h;try{h=JSON.parse(g.data)}catch(k){return}!h||h.googMsgType!==b||d&&/[:|%3A]javascript\(/i.test(g.data)&&!d(h,g)||c(h,g)};R(a,"message",e);let f=!1;return()=>{let g=!1;f||(f=!0,g=ee(a,"message",e));return g}},Di=(a,b,c,d=null)=>{const e=Ci(a,b,Wa(c,()=>e()),d);return e},Ei=class extends Error{constructor(){super()}},Fi=(a,b,c,d,e)=>{if(Array.isArray(a)){var f=a;for(var g=0;g{var c=Gi;return Ci(a,"ct",(d,e)=>{try{const f=Fi(d,c,null,null,null);b(f,e)}catch(f){if(!(f instanceof Ei))throw f;}})},Ii=(a,b,c,d,e)=>{if(!(0>=e)&&(c.googMsgType=b,a.postMessage(JSON.stringify(c),d),a=a.frames))for(let f=0;f{if(!a)return!1;a=a.hash;if(!a||!a.indexOf)return!1;if(-1!=a.indexOf(b))return!0;b=Oi(b);return"go"!=b&&-1!=a.indexOf(b)?!0:!1},Oi=a=>{let b="";U(a.split("_"),c=>{b+=c.substr(0,2)});return b},Qi=()=>{var a=q.location;let b=!1;U(Li,c=>{Pi(a,c)&&(b=!0)});return b},Ri=(a,b)=>{switch(a){case 1:return Pi(b,"google_ia_debug");case 2:return Pi(b,"google_bottom_anchor_debug");case 3:return Pi(b,"google_anchor_debug")||Pi(b,"googleads");case 4:return Pi(b,"google_scr_debug");case 6:return Pi(b, +"google_responsive_slot_debug")}return!1};let Si=null;function Ti(a){Si||(Si=new Ui(a.google_t12n_vars||{}));return Si}function Vi(a,b){a=parseFloat(a.j[b]);return a=isNaN(a)?0:a}class Ui{constructor(a){this.j=a}};let Wi=null;var Xi=(a,b)=>{let c=0,d=a,e=0;for(;a&&a!=a.parent;)if(a=a.parent,e++,Ee(a))d=a,c=e;else if(b)break;return{win:d,level:c}},Yi=()=>{Wi||(Wi=Xi(q,!0).win);return Wi};class Zi extends Vh{constructor(a){super(a);this.dfltBktExt=this.j;this.lrsExt=this.l}};function $i(){var a=u(),b=og(a);if(b)return(b=b||og())?(a=b.pageViewId,b=b.clientId,"string"===typeof b&&(a+=b.replace(/\D/g,"").substr(0,6))):a=null,+a;a=Xi(a,!1).win;(b=a.google_global_correlator)||(a.google_global_correlator=b=1+Math.floor(Math.random()*Math.pow(2,43)));return b}function aj(){if(bj)return bj;const a=rg()||u(),b=a.google_persistent_state_async;return null!=b&&"object"==typeof b&&null!=b.S&&"object"==typeof b.S?bj=b:a.google_persistent_state_async=bj=new cj} +function dj(a){return ej[a]||"google_ps_"+a}function fj(a,b,c){b=dj(b);a=a.S;const d=a[b];return void 0===d?a[b]=c:d}function gj(a,b){var c=fj(a,b,0)+1;return a.S[dj(b)]=c}function hj(){var a=aj();return fj(a,20,{})}class cj{constructor(){this.S={}}}var bj=null;const ej={[8]:"google_prev_ad_formats_by_region",[9]:"google_prev_ad_slotnames_by_region"};function ij(a,b){a.j=c=>fg(bg,b,()=>[])(c,1);a.l=()=>fg(cg,b,()=>[])(1)}class jj{constructor(){this.j=()=>[];this.l=()=>[]}}na(jj);const kj={Kf:5,uf:7,Vf:17,Be:41,Ag:62,kg:67,Cg:82,Dg:83,og:87,Ne:89,df:103,Mf:106,qh:107,Bf:108,Gd:124,lh:126,Hd:128,Pf:132,$f:138,ng:139};let lj=null; +var mj=a=>{try{return!!a&&Rc(!0)}catch(b){return!1}},nj=()=>{if(mj(lj))return!0;var a=aj();if(a=fj(a,3,null)){if(a&&a.dfltBktExt&&a.lrsExt){var b=new Zi;b.j=a.dfltBktExt;b.dfltBktExt=b.j;b.l=a.lrsExt;b.lrsExt=b.l;b.m=!0;a=b}else a=null;a||(a=new Zi,b={context:"ps::gpes::cf",url:u().location.href},Y("jserror",b))}return mj(a)?(lj=a,!0):!1},oj=a=>{if(!nj()){var b=Uh();a(b);b.m=!0}},Uh=()=>{if(nj())return lj;var a=aj(),b=new Zi(Re(kj));return lj=a.S[dj(3)]=b};let pj=null; +var qj=()=>{pj||(pj=Th());return pj},rj=a=>{let b=jj.G().l().join();const c=qj();c&&(b+=(b?",":"")+$h(c).join());b&&(a.eid=50Hg($h(a),b=>!!uj[b]),zj=(a=qj())=>Hg($h(a),b=>!uj[b]);var Aj={overlays:1,interstitials:2,vignettes:2,inserts:3,immersives:4,list_view:5},Bj={[1]:1,[2]:1,[8]:2,[27]:3,[9]:4,[30]:5};function Cj(a){a.google_reactive_ads_global_state?null==a.google_reactive_ads_global_state.floatingAdsStacking&&(a.google_reactive_ads_global_state.floatingAdsStacking=new Dj):a.google_reactive_ads_global_state=new Ej;return a.google_reactive_ads_global_state} +class Ej{constructor(){this.wasPlaTagProcessed=!1;this.wasReactiveAdConfigReceived={};this.adCount={};this.wasReactiveAdVisible={};this.stateForType={};this.reactiveTypeEnabledInAsfe={};this.wasReactiveTagRequestSent=!1;this.reactiveTypeDisabledByPublisher={};this.tagSpecificState={};this.improveCollisionDetection=1;this.messageValidationEnabled=!1;this.floatingAdsStacking=new Dj}}var Dj=class{constructor(){this.maxZIndexRestrictions={};this.nextRestrictionId=0;this.maxZIndexListeners=[]}};var Gj=(a,b)=>{var c=jj.G().j(13).concat(jj.G().j(11)),d=a.B;const e=ah(d);e.eids=[...e.eids||[],...Ia(c,String)];Ga(ah(d).eids||[],f=>{Xh(b,f)});c=Ti(a.pubWin);Yh(b,["551"],0,108);Zh(b,108)&&(Uf=Tf);d=["42631002","42631003"];Yh(b,d,Vi(c,22),17);d=["21062174","21062175"];Yh(b,d,Vi(c,129),126);d=["26835105","26835106"];Yh(b,d,Vi(c,24),41);(d=Rc(""))&&Xh(b,d);d=sj;d=[d.na,d.pa];Yh(b,d,Vi(c,28),67);d=tj;d=[d.Bb,d.na];Yh(b,d,Vi(c,29),87);d=vj;d=eb(d);Yh(b,d,Vi(c,126), +124);d=wj;d=[d.pa,d.na];Yh(b,d,Vi(c,177),139);a.j&&Fj(b,c,a.j)},Fj=(a,b,c)=>{const d=["410075105","410075106"];if(c=Cj(c))switch(Yh(a,d,Vi(b,155),132)){case "410075105":c.improveCollisionDetection=1;break;case "410075106":c.improveCollisionDetection=-1}};function Hj(a,b=q){a=a.scrollingElement||("CSS1Compat"==a.compatMode?a.documentElement:a.body);return new Ld(b.pageXOffset||a.scrollLeft,b.pageYOffset||a.scrollTop)}function Ij(a){try{return!(!a||!(a.offsetWidth||a.offsetHeight||a.getClientRects().length))}catch(b){return!1}};var Jj=(a,b=!1)=>{try{return b?(new Md(a.innerWidth,a.innerHeight)).round():Qd(a||window).round()}catch(c){return new Md(-12245933,-12245933)}},Kj=(a,b)=>{var c;var d;c=(d=(d=og())&&(c=d.initialLayoutRect)&&"number"===typeof c.top&&"number"===typeof c.left&&"number"===typeof c.width&&"number"===typeof c.height?new kg(c.left,c.top,c.width,c.height):null)?new Ld(d.left,d.top):(c=pg())&&ra(c.rootBounds)?new Ld(c.rootBounds.left+c.boundingClientRect.left,c.rootBounds.top+c.boundingClientRect.top):null; +if(c)return c;try{var e=a.j,f=new Ld(0,0),g=Sd(Pd(b));if(Sc(g,"parent")){a=b;do{if(g==e)var h=Bg(a);else{var k=Ag(a);h=new Ld(k.left,k.top)}b=h;f.x+=b.x;f.y+=b.y}while(g&&g!=e&&g!=g.parent&&(a=g.frameElement)&&(g=g.parent))}return f}catch(l){return new Ld(-12245933,-12245933)}};function Lj(a){M(this,a,Mj,null)}z(Lj,D);var Mj=[15];function Nj(a){M(this,a,null,null)}z(Nj,D);function Oj(a){M(this,a,null,null)}z(Oj,D);var Pj;{const a=parseInt("2019",10);Pj=isNaN(a)?2012:a};var Qj=(a,b,c)=>{if("relative"===a)return b;c||(c=Uf?"https":"http");q.location&&"https:"==q.location.protocol&&"http"==c&&(c="https");return[c,"://",a,b].join("")},Rj=(a,b,c)=>{a=Qj(a,b,c);2012{if(!Qf)return!1;if(null!=Sj)return Sj;Sj=!1;try{const a=Yg(q);a&&-1!=a.location.hash.indexOf("google_logging")&&(Sj=!0);q.localStorage.getItem("google_logging")&&(Sj=!0)}catch(a){}return Sj},Vj=(a,b=[])=>{let c=!1;q.google_logging_queue||(c=!0,q.google_logging_queue=[]);q.google_logging_queue.push([a,b]);c&&Uj()&&(a=Rj(Yf(),"/pagead/js/logging_library.js"),Ie(q.document,a))};function Wj(a){return{visible:1,hidden:2,prerender:3,preview:4,unloaded:5}[a.visibilityState||a.webkitVisibilityState||a.mozVisibilityState||""]||0}function Xj(a){let b;a.visibilityState?b="visibilitychange":a.mozVisibilityState?b="mozvisibilitychange":a.webkitVisibilityState&&(b="webkitvisibilitychange");return b}function Yj(a){return null!=a.hidden?a.hidden:null!=a.mozHidden?a.mozHidden:null!=a.webkitHidden?a.webkitHidden:null};function Zj(){var a=ak,b=bk;if(!(window&&Math.random&&navigator))return-1;if(window.__google_ad_urls){var c=window.__google_ad_urls;try{if(c&&c.getOseId())return c.getOseId()}catch(d){}}if(!window.__google_ad_urls_id){c=window.google_enable_ose;let d;!0===c?d=2:!1!==c&&(d=Ke([0],a),null==d&&((d=Ke([2],b))||(d=3)));if(!d)return 0;window.__google_ad_urls_id=d}return window.__google_ad_urls_id};const ck=new ki(1,u());var dk=()=>{const a=u();a&&"undefined"!=typeof a.google_measure_js_timing&&(a.google_measure_js_timing||hi(ck))};(()=>{const a=u();a&&a.document&&("complete"==a.document.readyState?dk():ck.j&&R(a,"load",()=>{dk()}))})();var ek=(a,b,c)=>{a&&(c?R(a,"load",b):ee(a,"load",b))},fk=()=>{const a=(u()||q).google_osd_amcb;return qa(a)?a:null},gk=(a="/r20100101")=>(Uf?"https:":"http:")+"//www.googletagservices.com/activeview/js/current/osd.js?cb="+encodeURIComponent(a);function Ba(){const a=u(),b=a.__google_ad_urls;if(!b)return a.__google_ad_urls=new hk(a);try{if(0<=b.getOseId())return b}catch(c){}try{return a.__google_ad_urls=new hk(a,b)}catch(c){return a.__google_ad_urls=new hk(a)}}function ik(a){var b=a.o?u():q;a=jk;b=b||q;b.google_osd_loaded?a=!1:(Ie(b.document,a),a=b.google_osd_loaded=!0);a&&Ig()} +class hk{constructor(a,b){this.l=b&&b.l?b.l:0;this.m=b?b.m:"";this.j=b&&b.j?b.j:[];this.o=!0;if(b)for(a=0;anull){e=fk();f=ai()||-1;let h=q.pageYOffset;0<=h||(h=-1);e&&d?e(d,a,b,!1,void 0,!1,g,f,h):(c=new kk(a,b,c,d,g,f,h),this.j.push(c),ek(d,c.v,!0),jk||(tg("//pagead2.googlesyndication.com/pagead/gen_204?id=osd&r=om"+`&rs=${b}`+`&req=${a}`),jk=gk("/r20190131")),ik(this))}unloadAdBlock(a,b=!1,c=!1){const d=this.o?u():window;void 0!==d.Goog_Osd_UnloadAdBlock&&d.Goog_Osd_UnloadAdBlock(a,b);c&&(b=Af(this.j,e=>e.j==a))&&ek(a, +b.v,!1)}setLoadOsdJsOnPubWindow(a){this.o=a}}var jk="",bk=0,ak=0,kk=class{constructor(a,b,c,d,e=la,f=-1,g=-1){this.A=a;this.H=b;this.j=d;this.o=this.m=this.l=!1;this.C=e;this.F=f;this.D=g;this.v=()=>this.l=!0}};ca("Goog_AdSense_getAdAdapterInstance",Ba,void 0);ca("Goog_AdSense_OsdAdapter",hk,void 0);function lk(){let a=u();const b=a.__google_ad_urls;return b?b:a.__google_ad_urls=new mk}class mk{constructor(){}getNewBlocks(){}setupOse(){}getOseId(){return-1}getCorrelator(){return""}numBlocks(){return 0}registerAdBlock(){}unloadAdBlock(){}setLoadOsdJsOnPubWindow(){}};var nk=(a,b,c,d)=>{c=c||a.google_ad_width;d=d||a.google_ad_height;if(a&&a.top==a)return!1;const e=b.documentElement;if(c&&d){let f=1,g=1;a.innerHeight?(f=a.innerWidth,g=a.innerHeight):e&&e.clientHeight?(f=e.clientWidth,g=e.clientHeight):b.body&&(f=b.body.clientWidth,g=b.body.clientHeight);if(g>2*d||f>2*c)return!1}return!0},ok=(a,b)=>{U(a,(c,d)=>{b[d]=c})},pk=a=>{let b=a.location.href;if(a==a.top)return{url:b,nb:!0};let c=!1;const d=a.document;d&&d.referrer&&(b=d.referrer,a.parent==a.top&&(c=!0)); +(a=a.location.ancestorOrigins)&&(a=a[a.length-1])&&-1==b.indexOf(a)&&(c=!1,b=a);return{url:b,nb:c}},qk=()=>{var a=u();if(a==a.top)return 0;for(;a&&a!=a.top&&Ee(a);a=a.parent){if(a.sf_)return 2;if(a.$sf)return 3;if(a.inGptIF)return 4;if(a.inDapIF)return 5}return 1};var rk={google:1,googlegroups:1,gmail:1,googlemail:1,googleimages:1,googleprint:1},sk=/(corp|borg)\.google\.com:\d+$/;var tk=728*1.38,uk=(a,b=420)=>(a=Z(a).clientWidth)?a>b?32768:320>a?65536:0:16384,vk=a=>{var b=Z(a).clientWidth;a=a.innerWidth;return(b=b&&a?b/a:0)?1.05b?524288:0:131072},xk=a=>Math.max(0,wk(a,!0)-Z(a).clientHeight),Z=a=>{a=a.document;let b={};a&&(b="CSS1Compat"==a.compatMode?a.documentElement:a.body);return b||{}},wk=(a,b)=>{const c=Z(a);return b?c.scrollHeight==Z(a).clientHeight?c.offsetHeight:c.scrollHeight:c.offsetHeight},yk=(a,b)=>a.adCount?1==b||2==b?!(!a.adCount[1]&&!a.adCount[2]): +(a=a.adCount[b])&&27!=b&&26!=b?1<=a:!1:!1,zk=(a,b)=>a&&a.source?a.source===b||a.source.parent===b:!1,Ak=a=>void 0===a.pageYOffset?(a.document.documentElement||a.document.body.parentNode||a.document.body).scrollTop:a.pageYOffset,Bk=a=>void 0===a.pageXOffset?(a.document.documentElement||a.document.body.parentNode||a.document.body).scrollLeft:a.pageXOffset,Ck=a=>{const b={};let c;Array.isArray(a)?c=a:a&&a.key_value&&(c=a.key_value);if(c)for(a=0;a{Ph(c,b,{c:e.data.substring(0,500),u:a.location.href.substring(0,500)},!0,.1);return!0};var Ek=a=>{a=a.google_reactive_ad_format;return cb(a)?""+a:null},Fk=a=>!!Ek(a)||null!=a.google_pgb_reactive,Gk=a=>{a=Ek(a);return 26==a||27==a||30==a||16==a};const Hk=a=>{const b=/[a-zA-Z0-9._~-]/,c=/%[89a-zA-Z]./;return a.replace(/(%[a-zA-Z0-9]{2})/g,function(d){if(!d.match(c)){const e=decodeURIComponent(d);if(e.match(b))return e}return d.toUpperCase()})},Ik=a=>{let b="";const c=/[/%?&=]/;for(let d=0;d{a=N(a,2);if(!a)return!1;for(let c=0;c{a=Ik(Hk(a.location.pathname)).replace(/(^\/)|(\/$)/g,"");const c=Se(a),d=Ql(a);return b.find(e=>{const f=null!=N(e,7)?N(O(e,Hl,7),1):N(e,1);e=null!=N(e,7)?N(O(e,Hl,7),2):2;if("number"!==typeof f)return!1;switch(e){case 1:return f==c;case 2:return d[f]||!1}return!1})||null},Ql=a=>{const b={};for(;;){b[Se(a)]=!0;if(!a)return b;a=a.substring(0,a.lastIndexOf("/"))}};function Sl(a){const b=[].slice.call(arguments).filter(Xa(e=>null===e));if(!b.length)return null;let c=[],d={};b.forEach(e=>{c=c.concat(e.Kb||[]);d=Object.assign(d,e.qb)});return new Tl(c,d)}function Ul(a){switch(a){case 1:return new Tl(null,{google_ad_semantic_area:"mc"});case 2:return new Tl(null,{google_ad_semantic_area:"h"});case 3:return new Tl(null,{google_ad_semantic_area:"f"});case 4:return new Tl(null,{google_ad_semantic_area:"s"});default:return null}} +class Tl{constructor(a,b){this.Kb=a;this.qb=b}};const Vl={["google_ad_channel"]:!0,["google_ad_host"]:!0};var Wl=(a,b)=>{a.location.href&&a.location.href.substring&&(b.url=a.location.href.substring(0,200));Y("ama",b,.01)},Xl=a=>{const b={};Oe(Vl,(c,d)=>{d in a&&(b[d]=a[d])});return b};var Yl=a=>{try{a.localStorage.removeItem("google_ama_config")}catch(b){Wl(a,{lserr:1})}};var am=(a,b)=>{const c=new Zl(a,1E3,b);return()=>$l(c)};function $l(a){if(a.j)return!1;if(null==a.l)return bm(a),!0;const b=a.l+a.o-(new Date).getTime();if(1>b)return bm(a),!0;cm(a,b);return!0}function bm(a){a.l=(new Date).getTime();a.m()}function cm(a,b){a.j=!0;a.v.setTimeout(()=>{a.j=!1;bm(a)},b)}class Zl{constructor(a,b,c){this.v=a;this.o=b;this.m=c;this.l=null;this.j=!1}};function dm(a,b){a.A?b(a.m):a.l.push(b)}function em(a,b){a.A=!0;a.m=b;a.l.forEach(c=>{c(a.m)});a.l=[]} +class fm{constructor(a){this.j=a;this.l=[];this.A=!1;this.v=this.m=null;this.C=am(a,()=>{if(null!=this.v){var b=wk(this.j,!0)-this.v;1E3{this.P(void 0,b)},a)}Ma(){null!=this.o&&this.j.clearTimeout(this.o);this.j.removeEventListener("scroll",this.C);this.l=[];this.m=null}};function gm(){this.j={};this.l={}}gm.prototype.set=function(a,b){this.j[a]=b;this.l[a]=a};gm.prototype.get=function(a,b){return void 0!==this.j[a]?this.j[a]:b};function hm(a){var b=[],c;for(c in a.j)void 0!==a.j[c]&&a.j.hasOwnProperty(c)&&b.push(a.l[c]);return b}function im(a){var b=[],c;for(c in a.j)void 0!==a.j[c]&&a.j.hasOwnProperty(c)&&b.push(a.j[c]);return b};function jm(a,b){return a.leftnew ig(b.top,b.right,b.bottom,b.left));a=lm(a);return{top:a.top,right:a.right,bottom:a.bottom,left:a.left}}function lm(a){if(!a.length)throw Error("pso:box:m:nb");return Ja(a.slice(1),(b,c)=>{b.left=Math.min(b.left,c.left);b.top=Math.min(b.top,c.top);b.right=Math.max(b.right,c.right);b.bottom=Math.max(b.bottom,c.bottom);return b},a[0].clone())};function mm(a,b,c){this.m=a;this.j=b;this.l=c}function nm(a,b,c){return{top:a.j-c,right:a.m+a.l+b,bottom:a.j+c,left:a.m-b}};class om{constructor(a,b,c){this.j=a;this.l=b;this.m=c}};class pm{constructor(a){this.j=a}P(){const a=this.j.document.createElement("SCRIPT");a.src="//www.google.com/adsense/search/ads.js";a.setAttribute("async","async");this.j.document.head.appendChild(a);(function(b,c){b[c]=b[c]||function(){(b[c].q=b[c].q||[]).push(arguments)};b[c].t=1*new Date})(this.j,"_googCsa")}};class qm{j(){}};function rm(a,b){sm(a).forEach(b,void 0)}function sm(a){for(var b=[],c=a.length,d=0;dc&&(c+=b.length),b=0<=c&&cf&&(f+=e.length);0<=f&&f{try{const c=b.document.documentElement.getBoundingClientRect(),d=a.getBoundingClientRect();return{x:d.left-c.left,y:d.top-c.top}}catch(c){return null}},Am=(a,b)=>!!a.google_ad_resizable&&!a.google_reactive_ad_format&&!!b.navigator&&/iPhone|iPod|iPad|Android|BlackBerry/.test(b.navigator.userAgent)&&Tg(b)==b,Bm=(a,b,c)=>{a=a.style;"rtl"==b?T.G().j(251,!1)?a.setProperty("margin-right",c,"important"):a.marginRight=c:T.G().j(251,!1)?a.setProperty("margin-left",c,"important"):a.marginLeft= +c};const Cm=(a,b,c)=>{a=zm(b,a);return"rtl"==c?-a.x:a.x};var Dm=(a,b)=>{b=b.parentElement;return b?(a=Je(b,a))?a.direction:"":""},Em=(a,b,c)=>{if(0===Cm(a,b,c))return!1;Bm(b,c,"0px");const d=Cm(a,b,c);Bm(b,c,-1*d+"px");a=Cm(a,b,c);0!==a&&a!==d&&Bm(b,c,d/(a-d)*d+"px");return!0};function Fm(a){if(1!=a.nodeType)var b=!1;else if(b="INS"==a.tagName)a:{b=["adsbygoogle-placeholder"];a=a.className?a.className.split(/\s+/):[];for(var c={},d=0;d{var e=Km(b,c,d);if(e.P){for(c=b=e.P;c=e.Oa(c);)b=c;e={anchor:b,position:e.Ua}}else e={anchor:b,position:c};a["google-ama-order-assurance"]=d;Im(a,e.anchor,e.position)},Mm=(a,b,c,d=0)=>{T.G().j(313,!1)?Lm(a,b,c,d):Im(a,b,c)}; +function Km(a,b,c){const d=f=>{f=Nm(f);return f=null==f?!1:c{f=Nm(f);return f=null==f?!1:c>f};switch(b){case 0:return{P:Om(a.previousSibling,d),Oa:f=>Om(f.previousSibling,d),Ua:0};case 2:return{P:Om(a.lastChild,d),Oa:f=>Om(f.previousSibling,d),Ua:0};case 3:return{P:Om(a.nextSibling,e),Oa:f=>Om(f.nextSibling,e),Ua:3};case 1:return{P:Om(a.firstChild,e),Oa:f=>Om(f.nextSibling,e),Ua:3}}throw Error("Un-handled RelativePosition: "+b);} +function Nm(a){return a.hasOwnProperty("google-ama-order-assurance")?a["google-ama-order-assurance"]:null}function Om(a,b){return a&&b(a)?a:null};function Pm(a,b){for(var c=0;cb.textContent).filter(b=>!!b):[]}};class en extends qm{constructor(a,b){super();this.m=a;this.l=b}j(){return(new URL(this.l)).searchParams.getAll(this.m)}};function fn(a,b){return b.map(c=>{{const d=O(c,Sk,1);if(d)c=new dn(a.l,d);else if(c=N(c,2))c=new en(c,a.j);else throw Error("Unable to get extractor for SearchQueryIdentifier");}return c})}class gn{constructor(a,b){this.l=a;this.j=b}};class hn{constructor(a,b,c){this.m=a;this.l=b;this.j=c}O(){return this.m}Pa(){return this.j.l}};function jn(a,b,c){a.l.push(b);a.j.push(c)}function kn(a){if(!a.j.length)return null;const b=a.j.reduce((d,e)=>Math.min(d,e.left),Number.MAX_VALUE),c=a.j.reduce((d,e)=>Math.max(d,e.right),Number.MIN_VALUE);a=a.j.reduce((d,e)=>Math.max(d,e.bottom),Number.MIN_VALUE);return new mm(b,a,c-b)}class ln{constructor(){this.l=[];this.j=[]}}function mn(a){return 2!=a.length?!1:!!a[0].parentElement&&!!a[1].parentElement&&a[0].parentElement==a[1].parentElement} +function nn(a,b){return a.length?b(a)?a:a.every(c=>!!c.parentElement)?nn(a.map(c=>c.parentElement),b):null:null};function on(a){const b=Z(a.j).clientHeight||0;return pn(a,c=>{c=c.j;var d;if(d=c.j>=b){d=a.o;a:{for(e of d.j)if(jm(nm(c,d.l,d.m),e)){var e=!0;break a}e=!1}d=!e}return d})} +function qn(a,b){var c=O(a.m,al,2);if(!c)return null;var d=N(c,1);if(!d)return null;var e=a.j.document.createElement(d);Pm(e.style,$m(Q(c,$k,2)));e.style.width=b.Pa()+"px";d=a.j.document.createElement("div");e.appendChild(d);e=[e];if(c=O(c,cl,3)){var f=N(c,1);f?(a=a.j.document.createElement(f),Pm(a.style,$m(Q(c,$k,2)))):a=null}else a=null;if(a)switch(b.l){case 0:case 3:e.push(a);break;case 1:case 2:e.unshift(a)}return{elements:e,container:d}} +function rn(a){const b=on(a);if(!b)return null;a=qn(a,b);if(!a)return null;a.elements.forEach(c=>{Im(c,b.O(),b.l)});return a.container} +function pn(a,b){const c=sn(a);for(let f=0;fd.getBoundingClientRect()),c=[new ln];jn(c[0],a.l[0],b[0]);for(let d=1;dc.j));a=a.reduce((c,d)=>c+d.l,0);return new xn(b,a)}class xn{constructor(a,b){this.j=a;this.l=b}};var Dn=(a,b)=>{const c=Pa(b.document.querySelectorAll(".google-auto-placed")),d=yn(b),e=zn(b),f=An(b),g=Bn(b),h=Pa(b.document.querySelectorAll("ins.adsbygoogle-ablated-ad-slot")),k=Pa(b.document.querySelectorAll("div.googlepublisherpluginad"));let l=Pa(b.document.querySelectorAll("iframe[id^=aswift_],iframe[id^=google_ads_frame]")).concat(Pa(b.document.querySelectorAll("ins.adsbygoogle")));b=[];for(const [p,r]of[[a.va,c],[a.ea,d],[a.bd,e],[a.wa,f],[a.xa,g],[a.$c,h],[a.ad,k]])a=r,!1===p?b=b.concat(a): +l=l.concat(a);var m;a=Cn(l);b=Cn(b);a=a.slice(0);for(m of b)for(b=0;b{try{return Ha(Ia(a.googletag.pubads().getSlots(),b=>a.document.getElementById(b.getSlotElementId())),b=>null!=b)}catch(b){}return null},yn=a=>Pa(a.document.querySelectorAll('ins.adsbygoogle[data-anchor-shown="true"]')),zn=a=>Pa(a.document.querySelectorAll("ins.adsbygoogle[data-ad-format=autorelaxed]")),An=a=>(En(a)||Pa(a.document.querySelectorAll("div[id^=div-gpt-ad]"))).concat(Pa(a.document.querySelectorAll("iframe[id^=google_ads_iframe]"))),Bn=a=>Pa(a.document.querySelectorAll("div.trc_related_container,div.OUTBRAIN,div[id^=rcjsload],div[id^=ligatusframe],div[id^=crt-],iframe[id^=cto_iframe],div[id^=yandex_], div[id^=Ya_sync],iframe[src*=adnxs],div.advertisement--appnexus,div[id^=apn-ad],div[id^=amzn-native-ad],iframe[src*=amazon-adsystem],iframe[id^=ox_],iframe[src*=openx],img[src*=openx],div[class*=adtech],div[id^=adtech],iframe[src*=adtech],div[data-content-ad-placement=true],div.wpcnt div[id^=atatags-]")); +var Cn=a=>{const b=[];for(const c of a){a=!0;for(let d=0;d{const c=Pa(b.document.querySelectorAll(".google-auto-placed")),d=yn(b),e=zn(b),f=An(b),g=Bn(b),h=Pa(b.document.querySelectorAll("ins.adsbygoogle-ablated-ad-slot"));b=Pa(b.document.querySelectorAll("div.googlepublisherpluginad"));return Cn((!0===a.va?c:[]).concat(!0===a.ea?d:[],!0===a.bd?e:[],!0===a.wa?f:[],!0===a.xa?g:[],!0===a.$c?h:[],!0===a.ad?b:[]))});function Hn(a,b,c){const d=In(a);b=Jn(d,b,c);return new Kn(a,d,b)}function Ln(a){return a.j.map(b=>b.ta)}function Mn(a){return a.j.reduce((b,c)=>b+c.ta.bottom-c.ta.top,0)}class Kn{constructor(a,b,c){this.o=a;this.j=b.slice(0);this.m=c.slice(0);this.l=null}} +function In(a){const b=Fn({ea:!1},a),c=Bk(a),d=Ak(a);return b.map(e=>{var f=e.getBoundingClientRect();return f=(e=!!e.className&&-1!=e.className.indexOf("google-auto-placed"))||1<(f.bottom-f.top)*(f.right-f.left)?{ta:{top:f.top+d,right:f.right+c,bottom:f.bottom+d,left:f.left+c},th:e?1:0}:null}).filter(Xa(e=>null===e))}function Jn(a,b,c){return void 0!=b&&a.length<=(void 0!=c?c:8)?Nn(a,b):Ia(a,d=>new xn(d.ta,1))} +function Nn(a,b){a=Ia(a,d=>new xn(d.ta,1));const c=[];for(;0{Qa(b,Ao(a,c))});return b}function Ao(a,b){let c=Bo(a,b);if(!c)return[];const d=N(b,3);d&&(c=d.replace("%s",c));const e=[];Q(b,el,1).forEach(f=>{var g;g=(g=O(f,Sk,1))?(g=Xm(g))?um(g,a.l.document):[]:[];g.length&&e.push(new un(a.l,a.o,c,f,g))});return e}function Bo(a,b){a=fn(new gn(a.l,a.v),Q(b,gl,2));return[].concat.apply([],a.map(c=>c.j())).filter(c=>!!c)[0]||null}class Co{constructor(a,b,c,d,e){this.l=a;this.v=b;this.j=c;this.m=d;this.o=e}};function Do(a){M(this,a,null,null)}z(Do,D);function Eo(a){M(this,a,null,null)}z(Eo,D);function Fo(a){M(this,a,null,null)}z(Fo,D);function Go(a){M(this,a,Ho,null)}z(Go,D);var Ho=[5];function Io(a){try{const b=a.localStorage.getItem("google_ama_settings");return b?Ad(Go,b):null}catch(b){return null}} +function Jo(a,b){if(void 0!==a.ua||void 0!==a.Na||void 0!==a.Za||void 0!==a.Ya){{let c=Io(b);c||(c=new Go);void 0!==a.ua&&pd(c,2,a.ua);void 0!==a.Na&&pd(c,8,a.Na);void 0!==a.Za&&yd(c,a.Za);void 0!==a.Ya&&wd(c,6,a.Ya);pd(c,1,+new Date+864E5);a=c.C();try{b.localStorage.setItem("google_ama_settings",a)}catch(d){}}}else if((a=Io(b))&&N(a,1)<+new Date)try{b.localStorage.removeItem("google_ama_settings")}catch(c){}};const Ko=["-webkit-text-fill-color"];function Lo(a){if(Yc){{const c=Je(a.document.body,a);if(c){a={};var b=c.length;for(let d=0;d{const a={all:"initial"};Ga(Ko,b=>{a[b]="unset"});return a};function Mo(a){Ga(Ko,b=>{delete a[b]});return a};var Oo=a=>{let b=0;try{b|=a!=a.top?512:0;{const f=Math.min(a.screen.width||0,a.screen.height||0);var c=f?320>f?8192:0:2048}b|=c;var d;if(d=a.navigator){var e=a.navigator.userAgent;d=/Firefox/.test(e)||/Android 2/.test(e)||/iPhone OS [34]_/.test(e)||/Windows Phone (?:OS )?[67]/.test(e)}b|=d?1048576:0}catch(f){b|=32}return b},Ro=(a,b)=>{let c=0;try{c|=a.innerHeight>=a.innerWidth?0:8,c|=uk(a,tk),c|=vk(a)}catch(e){c|=32}if(b=2==b){var d=a.innerWidth;b=Cj(a).improveCollisionDetection;d=Po(d,0,Math.round(a.innerWidth/ +320*50+15));b=null!=Qo(a,d,b)}b&&!T.G().j(269,!1)&&(c|=16777216);return c},So=a=>{const b=a.innerWidth,c=a.innerHeight;let d=c;for(;100{for(let k=0;k{const d=[];for(let e=0;3>e;e++)for(let f=0;3>f;f++)d.push({x:f/2*a,y:b+e/2*(c-b)});return d};function To(a){if(a.l&&"none"!=a.l.style.display){const b=Ak(a.j);if(b>a.m+100||bUo(a),200)}function Uo(a){var b=xk(a.j);a.m&&a.m>b&&(a.m=b);b=Ak(a.j);b>=a.m-100&&(a.m=Math.max(a.m,b),a.l||(a.l=Vo(a)),wf(a.l,{display:"block"}))}function Wo(a){a.l&&a.l.parentNode&&a.l.parentNode.removeChild(a.l);a.l=null;a.j.removeEventListener("scroll",a.A)} +function Vo(a){const b=a.j.document.createElement("ins");Xo(a,b);wf(b,{display:"inline-flex",padding:"8px 16px","background-color":"#FFF","border-radius":"20px","box-shadow":"0px 1px 3px 1px rgba(60,64,67,0.5)"});var c=a.j.document.createElement("img");Gc(c,"https://www.gstatic.com/adsense/autoads/icons/gpp_good_24px_blue_600.svg");Xo(a,c);wf(c,{margin:"0px 8px 0px 0px",width:"24px",height:"24px",cursor:"pointer"});c.addEventListener("click",f=>{a.v();f.stopPropagation()});var d=a.j.document.createElement("span"); +Xo(a,d);wf(d,{"line-height":"24px",cursor:"pointer"});d.appendChild(a.j.document.createTextNode(a.C));d.addEventListener("click",f=>{a.v();f.stopPropagation()});const e=a.j.document.createElement("img");Gc(e,"https://www.gstatic.com/adsense/autoads/icons/close_24px_grey_700.svg");e.setAttribute("aria-label",a.D);Xo(a,e);wf(e,{margin:"0px 0px 0px 8px",width:"24px",height:"24px",cursor:"pointer"});e.addEventListener("click",f=>{Wo(a);f.stopPropagation()});b.appendChild(c);b.appendChild(d);b.appendChild(e); +c=So(a.j);d=a.j.document.createElement("div");d.className="google-revocation-link-placeholder";wf(d,{position:"fixed",left:"0px",bottom:(null==c?30:c+30)+"px",width:"100vw","text-align":"center","z-index":2147483642,display:"none"});d.appendChild(b);a.j.document.body.appendChild(d);return d}function Xo(a,b){wf(b,Lo(a.j));wf(b,{"font-family":"Arial,sans-serif","font-weight":"bold","font-size":"14px","letter-spacing":"0.2px",color:"#1A73E8","user-select":"none"})} +class Yo{constructor(a,b,c,d){this.j=a;this.C=b;this.D=c;this.v=d;this.l=null;this.m=0;this.o=null;this.A=()=>To(this)}P(){this.j.addEventListener("scroll",this.A);this.m=xk(this.j);Uo(this)}};var Zo=a=>{let b=0;try{b|=a!=a.top?512:0,b|=a.getComputedStyle?0:2097152,b|=uk(a,1E4)}catch(c){b|=32}return b},$o=a=>{if(460<=a)return a=Math.min(a,1200),Math.ceil(800>a?a/4:200);a=Math.min(a,600);return 420>=a?Math.ceil(a/1.2):Math.ceil(a/1.91)+130};function ap(){}ap.prototype.l=function(a,b,c,d){return Qm(d.document,a,null,null,{},b)};ap.prototype.m=function(a){return $o(Math.min(a.screen.width||0,a.screen.height||0))};function bp(a){this.j=a}bp.prototype.l=function(a,b,c,d){return Qm(d.document,a,null,null,this.j,b)};bp.prototype.m=function(){return null};function cp(a){this.j=a} +cp.prototype.l=function(a,b,c,d){var e=0{a.v();e.stopPropagation()});var c=a.l.document.createElement("img");Gc(c,"https://www.gstatic.com/adsense/autoads/icons/gpp_good_24px_blue_600.svg");up(a,c);wf(c,{margin:"0px 8px 0px 0px",width:"24px",height:"24px"});const d=a.l.document.createElement("span");up(a,d);wf(d,{"line-height":"24px"});d.appendChild(a.l.document.createTextNode(a.o)); +b.appendChild(c);b.appendChild(d);c=mp(a.m.R);c.className="google-in-page-revocation-link";wf(c,{width:"100%","text-align":"center",display:"block",padding:"8px 0px","background-color":"#FFF","border-top":"2px solid #ECEDED","border-bottom":"2px solid #ECEDED"});c.appendChild(b);return c}function up(a,b){wf(b,Lo(a.l));wf(b,{"font-family":"Arial,sans-serif","font-weight":"bold","font-size":"14px","letter-spacing":"0.2px",color:"#1A73E8","user-select":"none",cursor:"pointer"})} +class vp{constructor(a,b,c,d){this.l=a;this.o=b;this.v=c;this.m=d;this.j=null}P(){this.j=tp(this);qp(this.m,this.j)}}function wp(a,b){b=b.filter(c=>5==N(O(c,ul,4),1)&&1==N(c,8));b=jp(b,a);a=rp(b,a);a.sort((c,d)=>d.M.j-c.M.j);return a[0]||null};function xp(a,b,c,d,e){yp(new zp(a,b,c,d,e))}function yp(a){Ap(a)?dm(Bp(a),()=>{if(null!=a.j){var b=a.j;b.j&&b.j.parentNode&&b.j.parentNode.removeChild(b.j);b.j=null;a.j=null}null!=a.l&&(Wo(a.l),a.l=null);Cp(a)}):Cp(a)}function Ap(a){{var b=a.o;var c=a.v,d=a.A;const e=wp(b,a.D);b=e?new vp(b,c,d,e):null}a.j=b;return a.j?(a.j.P(),!0):!1}function Bp(a){null==a.m&&(a.m=new fm(a.o),a.m.P(2E3));return a.m}function Cp(a){a.l=new Yo(a.o,a.v,a.C,a.A);a.l.P()} +class zp{constructor(a,b,c,d,e){this.o=a;this.v=b;this.C=c;this.A=d;this.D=e;this.l=this.j=this.m=null}};function Dp(a){const b=Ep(a);Ga(a.j.maxZIndexListeners,c=>c(b))}function Ep(a){a=Re(a.j.maxZIndexRestrictions);return a.length?Math.min.apply(null,a):null}class Fp{constructor(a){this.j=Cj(a).floatingAdsStacking}};function Gp(a){const b=a.l.googlefc=a.l.googlefc||{};b.callbackQueue=b.callbackQueue||[];b.callbackQueue.push(()=>Hp(a))}function Hp(a){const b=a.l.googlefc=a.l.googlefc||{};b&&b.getConsentStatus()!=b.ConsentStatusEnum.CONSENT_NOT_REQUIRED&&xp(a.l,b.getDefaultConsentRevocationText(),b.getDefaultConsentRevocationCloseText(),()=>b.showRevocationMessage(),a.A);Ip(a)}function Ip(a){if(null!=a.j){var b=a.m;delete b.j.maxZIndexRestrictions[a.j];Dp(b);a.j=null}} +class Jp{constructor(a,b,c,d,e){this.l=a;this.v=b;this.o=c;this.m=d;this.A=e;this.j=null}};function Kp(a,b,c){void 0!==a.j.j[b]||a.j.set(b,[]);a.j.get(b).push(c)}class Lp{constructor(){this.j=new gm}};function Mp(a){this.A={};this.A.c=a;this.m=[];this.l=null;this.o=[];this.C=0}function Np(a,b){a.A.wpc=b;return a}function Op(a,b){for(var c=0;ca.reduce((c,d)=>c.concat(b(d)),[]);function Vp(a,b,c,d){const e=c.childNodes;c=c.querySelectorAll(b);b=[];for(const f of c)c=Fa(e,f),0>c||b.push(new Wp(a,[f],c,f,3,Xd(f).trim(),d));return b} +function Xp(a,b,c){let d=[];const e=[],f=b.childNodes,g=f.length;let h=0,k="";for(let p=0;p{if(3==b.nodeType)return 3==b.nodeType?(b=b.data,a=-1!=b.indexOf("&")?Jc(b,a.document):b,a=/\S/.test(a)):a=!1,a;if(1==b.nodeType){var c=a.getComputedStyle(b);if(c="0"==c.opacity||"none"==c.display||"hidden"==c.visibility?!0:!1)return!1;if(c=(c=b.tagName)&&aq.contains(c.toUpperCase()))return!0;b=b.childNodes;for(c=0;c{a=dq(a,b);return Up(a,c=>{{var d=Oa(c.v?Xp(c.m,c.j,c.o):[],c.l?Vp(c.m,c.l,c.j,c.o):[]).slice(0);d.sort(Yp);c=[];const m=new cq(51,!1);for(l of d){d=m;var e={Va:l,Qa:l.A.length>=d.o};if(d.m||e.Qa){if(d.j.length){var f=d.j[d.j.length-1].Va;b:{var g=f.K();var h=f.ab[f.ab.length-1];f=e.Va.ab[0];if(!h||!f){g=!1;break b}var k=h.parentElement;const p=f.parentElement;if(k&&p&&k==p){k=0;for(h=h.nextSibling;10>k&&h;){if(h==f){g=!0;break b}if(bq(g,h))break;h=h.nextSibling;k++}g=!1}else g=!1}}else g= +!0;g?(d.j.push(e),e.Qa&&d.l.push(e.Va)):(d.j=[e],d.l=e.Qa?[e.Va]:[])}if(3<=m.l.length){if(1>=m.l.length)d=null;else{e=m.l[1];for(d=m;d.j.length&&!d.j[0].Qa;)d.j.shift();d.j.shift();d.l.shift();d=e}d&&c.push(d)}}var l=c}return l})},dq=(a,b)=>{const c=new gm;a.forEach(d=>{var e=Xm(O(d,Sk,1));if(e){{const f=e.toString();void 0!==c.j[f]||c.set(f,{Fc:d,Ec:e,La:null,Pb:!1});e=c.get(f);(d=(d=O(d,Sk,2))?N(d,7):null)?e.La=e.La?e.La+","+d:d:e.Pb=!0}}});return im(c).map(d=>{{const e=um(d.Ec,b.document);d=e.length? +new Zp(e[0],d,b):null}return d}).filter(d=>null!=d)};var fq=(a,b,c)=>{const d=O(a,ol,6);if(!d)return[];c=eq(Q(d,ql,1),c);return(a=Ol(a))&&rd(a,11)?c.map(e=>{{const f=vl();e=new ip(new fp(e.m,e.v),new bp({}),null,!1,2,[],f,e.j,null,null,null,e.o)}return e}):c.map(e=>{{const f=vl();e=new ip(new fp(e.m,e.v),new ap,new dp(b),!1,2,[],f,e.j,null,null,null,e.o)}return e})};var gq=!Wc&&!oc();function hq(a){if(/-[a-z]/.test("adFormat"))return null;if(gq&&a.dataset){if(!(!A("Android")||pc()||nc()||lc()||A("Silk")||"adFormat"in a.dataset))return null;a=a.dataset.adFormat;return void 0===a?null:a}return a.getAttribute("data-"+"adFormat".replace(/([A-Z])/g,"-$1").toLowerCase())};var iq=(a,b,c)=>{if(!b)return null;const d=Td(document,"INS");d.id="google_pedestal_container";d.style.width="100%";d.style.zIndex="-1";if(c){var e=a.getComputedStyle(c),f="";if(e&&"static"!=e.position){var g=c.parentNode.lastElementChild;for(f=e.position;g&&g!=c;){if("none"!=a.getComputedStyle(g).display){f=a.getComputedStyle(g).position;break}g=g.previousElementSibling}}if(c=f)d.style.position=c}b.appendChild(d);if(d){var h=a.document;f=h.createElement("div");f.style.width="100%";f.style.height= +"2000px";c=Z(a).clientHeight;e=h.body.scrollHeight;a=a.innerHeight;g=h.body.getBoundingClientRect().bottom;d.appendChild(f);var k=f.getBoundingClientRect().top;h=h.body.getBoundingClientRect().top;d.removeChild(f);f=e;e<=a&&0=.8*f}else a=!1;return a?d:(b.removeChild(d),null)},kq=a=>{let b=0;try{b|=a!=a.top?512:0;b|=a.getComputedStyle?0:2097152;Ae()||(b|=1048576);{const d=Math.floor(a.document.body.getBoundingClientRect().width),e=Vi(Ti(a),79);var c=d<=e}c||(b|=32768);jq(a)&& +(b|=33554432)}catch(d){b|=32}return b},jq=a=>{a=a.document.getElementsByClassName("adsbygoogle");for(let b=0;b{this.resolve=a;this.reject=b})}};function mq(a){try{a.setItem("__storage_test__","__storage_test__");const b=a.getItem("__storage_test__");a.removeItem("__storage_test__");return"__storage_test__"==b}catch(b){return!1}}function nq(a){try{if(null==a||!mq(a))return null;const b=a.getItem("__lsv__");if(!b)return[];let c;try{c=JSON.parse(b)}catch(d){}return!Array.isArray(c)||Ka(c,d=>!Number.isInteger(d))?(a.removeItem("__lsv__"),[]):oq(c)}catch(b){return null}}function oq(a=[]){const b=Date.now();return Ha(a,c=>36E5>b-c)};var pq=(a,b)=>{let c=0;try{c|=a!=a.top?512:0;c|=vk(a);c|=uk(a);c|=a.innerHeight>=a.innerWidth?0:8;c|=a.navigator&&/Android 2/.test(a.navigator.userAgent)?1048576:0;var d;if(d=b){b=null;try{b=a.localStorage}catch(f){}var e=nq(b);d=!(e&&1>e.length)}d&&(c|=134217728)}catch(f){c|=32}return c};function qq(a){var b=["Could not locate a suitable placement in the content below the fold."];Ri(4,a.location)&&(a=Cj(a).tagSpecificState[1]||null)&&(a=a.debugCard&&4===a.debugCard.getAdType()?a.debugCard:null)&&a.displayAdLoadedContent(b)};const rq={1:"0.5vp",2:"300px"},sq={1:700,2:1200},tq={[1]:{mc:"3vp",yb:"1vp",lc:"0.3vp"},[2]:{mc:"900px",yb:"300px",lc:"90px"}}; +function uq(a,b,c,d){var e=vq(a),f=Z(a).clientHeight||sq[e],g=void 0;d&&(g=(d=(d=wq(Q(d,Jk,2),e))?O(d,Mk,7):void 0)?xq(d,f):void 0);{d=g;g=vq(a);a=Z(a).clientHeight||sq[g];const h=yq(tq[g].yb,a);a=null===h?zq(g,a):new Aq(h,h,Bq(h,h,8),8,.3,d)}d=yq(tq[e].mc,f);g=yq(tq[e].yb,f);f=yq(tq[e].lc,f);e=a.m;d&&f&&g&&void 0!==b&&(e=.5>=b?g+(1-2*b)*(d-g):f+(2-2*b)*(g-f));c&&(e=Math.min(e,a.m));b=e;return b=new Aq(e,b,Bq(e,b,a.l),a.l,a.o,a.j)} +function Cq(a,b){const c=vq(a);a=Z(a).clientHeight||sq[c];if(b=wq(Q(b,Jk,2),c))if(b=Dq(b,a))return b;return zq(c,a)}function Eq(a){const b=vq(a);return zq(b,Z(a).clientHeight||sq[b])}function Fq(a,b){let c={za:a.m,ga:a.v};for(let d of a.A)d.adCount<=b&&(c=d.xb);return c}class Aq{constructor(a,b,c,d,e,f){this.m=a;this.v=b;this.A=c.sort((g,h)=>g.adCount-h.adCount);this.l=d;this.o=e;this.j=f}}function wq(a,b){for(let c of a)if(N(c,1)==b)return c;return null} +function Dq(a,b){const c=yq(N(a,2),b),d=yq(N(a,5),b);if(null===c)return null;const e=N(a,4);if(null==e)return null;const f=[];var g=Q(a,Lk,3);for(var h of g){g=N(h,1);const k=yq(N(h,2),b),l=yq(N(h,3),b);if("number"!==typeof g||null===k)return null;f.push({adCount:g,xb:{za:k,ga:l}})}b=(h=O(a,Mk,7))?xq(h,b):void 0;return new Aq(c,d,f,e,qd(a,6),b)}function zq(a,b){a=yq(rq[a],b);return new Aq(null===a?Infinity:a,null,[],3,null)} +function yq(a,b){if(!a)return null;const c=parseFloat(a);return isNaN(c)?null:a.endsWith("px")?c:a.endsWith("vp")?c*b:null}function vq(a){a=900<=Z(a).clientWidth;return Ae()&&!a?1:2}function Bq(a,b,c){if(4>c)return[];const d=Math.ceil(c/2);return[{adCount:d,xb:{za:2*a,ga:2*b}},{adCount:d+Math.ceil((c-d)/2),xb:{za:3*a,ga:3*b}}]}function xq(a,b){const c=yq(N(a,2),b)||0,d=N(a,3)||1;a=yq(N(a,1),b)||0;return{$b:c,Yb:d,ja:a}};function Gq(a){return new Tl(["pedestal_container"],{["google_reactive_ad_format"]:30,["google_phwr"]:2.189,["google_ad_width"]:Math.floor(a),["google_ad_format"]:"autorelaxed",["google_full_width_responsive"]:!0,["google_enable_content_recommendations"]:!0,["google_content_recommendation_ui_type"]:"pedestal"})}class Hq{constructor(){}j(a){return Gq(Math.floor(a.l))}};var Iq={};function Jq(a,b,c){let d=Kq(a,c,b);if(!d)return!0;let e=-1;const f=c.A.l;for(;d.Aa&&d.Aa.length;){const g=d.Aa.shift(),h=np(g.R),k=g.M.j;if((c.l.Ca||c.l.Da||c.l.Mb||k>e)&&(!h||h<=d.Ka)&&Lq(c,g,{Xb:d.Ka})){e=k;if(d.Ia.j.length+1>=f)return!0;d=Kq(a,c,b);if(!d)return!0}}return c.m} +var Kq=(a,b,c)=>{var d=b.A.l,e=b.A.o,f=b.A;f=Hn(b.K(),f.j?f.j.ja:void 0,d);if(f.j.length>=d)return null;e?(d=f.l||(f.l=Z(f.o).scrollHeight||null),e=!d||0>d?-1:f.l*e-Mn(f)):e=void 0;a=null==e||50<=e?Mq(b,f,{types:a},c):null;return{Ia:f,Ka:e,Aa:a}};Iq[2]=za(function(a,b){a=Mq(b,Hn(b.K()),{types:a,ia:Eq(b.K())},2);if(0==a.length)return!0;for(var c=0;c{var b;a.l.oc?b=new Aq(0,null,[],3,null):b=Eq(a.K());return{types:[0],ia:b}},Pq=a=>{var b=a.K().document.body.getBoundingClientRect().width;b=Gq(b);var c=a.j;var d=c.document.body,e=iq(c,d,null);if(e)c=e;else{if(c.document.body){e=Math.floor(c.document.body.getBoundingClientRect().width);for(var f=[{element:c.document.body,depth:0,height:0}],g=-1,h=null;0g&&(g=k,h=p);if(5>m.depth)for(k=0;k=.9*l&&B<=1.01*l)?!0:!1}l&&f.push({element:r,depth:m.depth+1,height:r.getBoundingClientRect().height})}}e=h}else e=null;c=e?iq(c,e.parentNode||d,e):null}c&&(b=Sl(a.F,b),d=Qm(a.j.document,a.D,null,null,{},b))&&(Mm(d.la,c,2,256),Oq(a,d,b))},Rq=(a,b)=>{var c=Nq(a);c.wb=[5];c=Mq(a,Hn(a.K()),c,8);Qq(a,c.reverse(),b)},Qq=(a,b,c)=>{for(const d of b)if(b=c.j(d.M),Lq(a,d,{xc:b}))return!0;return!1}; +Iq[8]=function(a){var b=a.K().document;if("complete"!=b.readyState)return b.addEventListener("readystatechange",()=>Iq[8](a),{once:!0}),!0;if(!a.m)return!1;if(!a.Ra())return!0;b=Nq(a);b.vb=[2,4,5];b=Mq(a,Hn(a.K()),b,8);const c=new Hq(a.l.cc||0);if(Qq(a,b,c))return!0;if(a.l.Nb)switch(a.l.ac||0){case 1:Rq(a,c);break;default:Pq(a)}return!0};Iq[6]=za(Jq,[2],6);Iq[7]=za(Jq,[1],7); +Iq[9]=function(a){const b=Kq([0,2],a,9);if(!b||!b.Aa)return a.o.push(17),qq(a.K()),a.m;for(const e of b.Aa){var c=e;var d=a.l.fb||null;null==d?c=null:(d=op(c.R,new Sq,new Tq(d,a.K())),c=new pp(d,c.O(),c.M));if(c&&!(np(c.R)>b.Ka)&&Lq(a,c,{Xb:b.Ka,Sc:!0}))return e.R.m=!0}a.o.push(17);qq(a.K());return a.m};class Sq{l(a,b,c,d){return Tm(d.document,a,b)}m(a){return Z(a).clientHeight||0}};var Uq=a=>{let b=0;try{b|=a!=a.top?512:0,b|=a.getComputedStyle?0:2097152,b|=a.document.querySelectorAll&&a.document.querySelector?0:4194304,b|=uk(a,1E4)}catch(c){b|=32}return b};var Vq=class{constructor(){const a=new lq;this.promise=a.j;this.resolve=a.resolve}};function Wq(a,b,c){b.google_llp||(b.google_llp={});b=b.google_llp;b[a]||(b[a]=new Vq,c&&c());return b[a]}function Xq(a,b,c){return Wq(a,b,function(){Ie(b.document,c)}).promise};var Yq=(a,b,c)=>{var d=0;try{d|=a!=a.top?512:0,d|=a.navigator&&/Android 2/.test(a.navigator.userAgent)?1048576:0}catch(k){d|=32}{var e=T.G().j(289,!1);let k=0;try{k|=uk(a,0l?-2147483648:0:1073741824}k|=f}k|=vk(a);e||(k|=a.innerHeight>=a.innerWidth?0:8);var g;if(g=b){var h=nq(c);g=!(h&&1>h.length)}g&&(k|=134217728)}catch(l){k|=32}a=k}return d|a};function Zq(a,b,c){const d=a.createElement("link");try{d.rel="preload",d.href=b instanceof qb?tb(b).toString():b instanceof Kb?Pb(b):Pb(Ub(b))}catch(e){return}d.as="script";c&&d.setAttribute("nonce",c);if(a=a.getElementsByTagName("head")[0])try{a.appendChild(d)}catch(e){}};const $q={[16]:4,[27]:512,[26]:128}; +var ar=(a,b,c,d)=>{switch(c){case 1:case 2:return!(Oo(a)|Ro(a,c));case 8:return b=!("on"===b.google_adtest||Pi(a.location,"google_ia_debug")),0==Yq(a,b,d);case 9:return d=T.G().j(230,!1)&&!("on"===b.google_adtest||Pi(a.location,"google_scr_debug")),!pq(a,d);case 30:return 0==kq(a);case 26:return 0==Uq(a)&&!0;case 27:return!Zo(a)&&!0;default:return!1}},br=(a,b,c,d)=>{switch(c){case 0:return 0;case 1:case 2:return Oo(a)|Ro(a,c);case 8:return Yq(a,!("on"===b.google_adtest||Pi(a.location,"google_ia_debug")), +d);case 9:return pq(a,T.G().j(230,!1)&&!("on"===b.google_adtest||Pi(a.location,"google_scr_debug")));case 16:return Am(b,a)?0:8388608;case 30:return kq(a);case 26:return Uq(a);case 27:return Zo(a);default:return 32}},cr=(a,b,c)=>{const d=b.google_reactive_ad_format;if(!cb(d))return!1;a=Yg(a);if(!a||!ar(a,b,d,c))return!1;b=Cj(a);if(yk(b,d))return!1;b.adCount[d]||(b.adCount[d]=0);b.adCount[d]++;return!0},dr=a=>!a.google_reactive_ads_config&&Fk(a)&&16!=a.google_reactive_ad_format,er=a=>{if(!a.hash)return null; +let b=null;U(Li,c=>{!b&&Pi(a,c)&&(b=Mi[c])});return b},gr=(a,b)=>{if(!a.document.getElementById("goog_info_card")){var c=Cj(a).tagSpecificState[1]||null;c&&U(Ni,d=>{!c.debugCardRequested&&Ri(d,a.location)&&(c.debugCardRequested=!0,fr(a,e=>{c.debugCard=e.createDebugCard(d,a,b)}))})}},ir=(a,b,c)=>{if(!b)return null;const d=Cj(b);let e=0;U(db,f=>{const g=$q[f];g&&0===hr(a,b,f,c)&&(e|=g)});d.wasPlaTagProcessed&&(e|=256);a.google_reactive_tag_first&&(e|=1024);return e?""+e:null},jr=(a,b,c)=>{const d=[]; +U(db,e=>{const f=hr(b,a,e,c);0!==f&&d.push(e+":"+f)});return d.join(",")||null},kr=a=>{const b=[],c={};U(a,(d,e)=>{if((e=Aj[e])&&!c[e]){c[e]=!0;if(d)d=1;else if(!1===d)d=2;else return;b.push(e+":"+d)}});return b.join(",")},lr=a=>{a=a.overlays;if(!a)return"";a=a.bottom;return"boolean"===typeof a?a?"1":"0":""},hr=(a,b,c,d)=>{if(!b)return 256;let e=0;const f=Cj(b),g=yk(f,c);if(a.google_reactive_ad_format==c||26!=c&&27!=c&&g)e|=64;let h=!1;U(f.reactiveTypeDisabledByPublisher,(k,l)=>{String(c)===l&&(h= +!0)});h&&er(b.location)!==c&&(e|=128);return e|br(b,a,c,d)},mr=(a,b)=>{if(a){var c=Cj(a),d={};U(b,(e,f)=>{(f=Aj[f])&&(!1===e||/^false$/i.test(e))&&(d[f]=!0)});U(db,e=>{d[Bj[e]]&&(c.reactiveTypeDisabledByPublisher[e]=!0)})}},nr=()=>{const a=Xg();return Rj(a,"/pagead/js/"+Nf()+"/r20190131/reactive_library.js",Tf?"https":"http")},or=(a,b)=>{a=W(a,b);return Xq(1, +u(),nr()).then(a)},fr=(a,b)=>{b=W(212,b);var c=Xg();c=Rj(c,"/pagead/js/"+Nf()+"/r20190131/debug_card_library.js",Tf?"https":"http");Xq(3,a,c).then(b)};const pr=a=>{if(!a.adsbygoogle){a.adsbygoogle=[];const b=Qj(Xg(),"/pagead/js/adsbygoogle.js");Ie(a.document,b)}}; +var qr=(a,b,c)=>{a.setAttribute("data-adsbygoogle-status","reserved");a.className+=" adsbygoogle-noablate";pr(c);c.adsbygoogle.push({element:a,params:b})},rr=(a,b,c)=>{const d=Bj[a],e={};a=b.page_level_pubvars;ra(a)&&ib(e,a);U(b,(f,g)=>{Aj[g]==d&&ra(f)&&ib(e,f)});ra(c)&&ib(e,c);return e},sr=(a,b)=>{R(a,"load",()=>{pr(a);a.adsbygoogle.push(b)})};class Tq{constructor(a,b){this.l=a;this.m=b}j(){{var a=this.l;var b=this.m;const c=a.B||{};c.google_ad_client=a.Fb;c.google_ad_height=Z(b).clientHeight||0;c.google_ad_width=Z(b).clientWidth||0;c.google_reactive_ad_format=9;c.google_rasc=a.l().C();a.j&&(c.google_adtest="on");a=c}return new Tl(["fsi_container"],a)}};class tr{constructor(a=1){this.j=a}next(){var a=48271*this.j%2147483647;this.j=0>2147483647*a?a+2147483647:a;return this.j/2147483647}};function ur(a){this.j=a.slice(0)}ur.prototype.filter=function(a){return new ur(Ha(this.j,a))};function vr(a,b,c){const d=[];for(const e of a.j)b(e)?d.push(e):c(e);return new ur(d)}ur.prototype.apply=function(a){return new ur(a(this.j.slice(0)))};function wr(a,b){return new ur(a.j.slice(0).sort(b))}function xr(a,b){if(0>b)return a;a=a.j.slice(0);a.splice(b,1);return new ur(a)}function yr(a,b=1){a=a.j.slice(0);const c=new tr(b);Ta(a,()=>c.next());return new ur(a)};class zr{constructor(a){this.j=new $p(a)}contains(a){return this.j.contains(a)}};function Ar(a,b,c){const d=nm(c,1,b+1);return!Ka(a,e=>jm(e,d))}function Br(a,b,c,d,e){e=e.M;const f=nm(e,0,b),g=nm(e,0,c),h=nm(e,0,d);return!Ka(a,k=>jm(k,g)||jm(k,f)&&!jm(k,h))}function Cr(a,b,c,d){const e=Ln(a);if(Ar(e,b,d.M))return!0;if(!Br(e,b,c.$b,c.ja,d))return!1;const f=new xn(nm(d.M,0,0),1);a=Ha(a.m,g=>vn(g,f,c.ja));b=Ja(a,(g,h)=>g+h.l,1);return 0===a.length||b>c.Yb?!1:!0};class Dr{constructor(){this.j=new gm}set(a,b){let c=this.j.get(a);c||(c=new $p,this.j.set(a,c));c.add(b)}};var Er=(a,b)=>{const c=[];let d=a;for(a=()=>{c.push({anchor:d.anchor,position:d.position});return d.anchor==b.anchor&&d.position==b.position};d;){switch(d.position){case 1:if(a())return c;d.position=2;case 2:if(a())return c;if(d.anchor.firstChild){d={anchor:d.anchor.firstChild,position:1};continue}else d.position=3;case 3:if(a())return c;d.position=4;case 4:if(a())return c}for(;d&&!d.anchor.nextSibling&&d.anchor.parentNode!=d.anchor.ownerDocument.body;){d={anchor:d.anchor.parentNode,position:3};if(a())return c; +d.position=4;if(a())return c}d&&d.anchor.nextSibling?d={anchor:d.anchor.nextSibling,position:1}:d=null}return c};function Fr(a,b){const c=new Dr,d=new $p;b.forEach(e=>{if(O(e,Xk,1)){e=O(e,Xk,1);if(O(e,Uk,1)&&O(e,Uk,1).O()&&O(e,Uk,2)&&O(e,Uk,2).O()){const g=Gr(a,O(e,Uk,1).O()),h=Gr(a,O(e,Uk,2).O());if(g&&h)for(var f of Er({anchor:g,position:O(e,Uk,1).l()},{anchor:h,position:O(e,Uk,2).l()}))c.set(sa(f.anchor),f.position)}O(e,Uk,3)&&O(e,Uk,3).O()&&(f=Gr(a,O(e,Uk,3).O()))&&c.set(sa(f),O(e,Uk,3).l())}else O(e,Yk,2)?Hr(a,O(e,Yk,2),c):O(e,Zk,3)&&Ir(a,O(e,Zk,3),d)});return new Jr(c,d)} +class Jr{constructor(a,b){this.l=a;this.j=b}}const Hr=(a,b,c)=>{O(b,Sk,1)&&(a=Kr(a,O(b,Sk,1)))&&a.forEach(d=>{d=sa(d);c.set(d,1);c.set(d,4);c.set(d,2);c.set(d,3)})},Ir=(a,b,c)=>{O(b,Sk,1)&&(a=Kr(a,O(b,Sk,1)))&&a.forEach(d=>{c.add(sa(d))})},Gr=(a,b)=>(a=Kr(a,b))&&0(b=Xm(b))?um(b,a):null;function Lr(a){return function(b){return rp(b,a)}}function Mr(a){const b=Z(a).clientHeight;return b?za(Nr,b+Ak(a)):Ua}function Or(a,b,c){if(0>a)throw Error("ama::ead:nd");if(Infinity===a)return Ua;const d=Ln(c||Hn(b));return e=>Ar(d,a,e.M)}function Pr(a,b,c,d){if(0>a||0>b.$b||0>b.Yb||0>b.ja)throw Error("ama::ead:nd");return Infinity===a?Ua:e=>Cr(d||Hn(c,b.ja),a,b,e)}function Qr(a){if(!a.length)return Ua;const b=new zr(a);return c=>b.contains(c.Sa)} +function Rr(a){return function(b){for(let c of b.ob)if(-1-1=a)return Va;const c=Z(b).scrollHeight-a;return function(d){return d.M.j<=c}}function Ur(a){const b={};a&&a.forEach(c=>{b[c]=!0});return function(c){return!b[N(c.Ba,2)||0]}}function Vr(a){return a.length?b=>a.includes(N(b.Ba,2)||0):Va} +function Wr(a){return a.length?b=>a.includes(N(b.Ba,1)||0):Va}function Xr(a,b){const c=Fr(a,b);return function(d){var e=d.O();d=cn[d.R.l()];var f=sa(e);f=(f=c.l.j.get(f))?f.contains(d):!1;if(!f)a:{if(c.j.contains(sa(e)))switch(d){case 2:case 3:f=!0;break a;default:f=!1;break a}for(e=e.parentElement;e;){if(c.j.contains(sa(e))){f=!0;break a}e=e.parentElement}f=!1}return!f}}const Nr=(a,b)=>b.M.j>=a,Yr=(a,b)=>b.M.j{c=c.M.l;return a<=c&&c<=b};class $r{constructor(a=0){this.j=a}};class as{constructor(a){this.l=a;this.j=-1}};function bs(a){const b=a.O();a=a.R.l();return 0==a||3==a?cs(b.parentElement):cs(b)}function cs(a){let b=0;for(;a;)(!b||a.previousElementSibling||a.nextElementSibling)&&b++,a=a.parentElement;return b};function ds(a,b){var c=b.M.j+200*Math.min(20,bs(b));var d=a.l;0>d.j&&(d.j=Z(d.l).scrollHeight||0);d=d.j-b.M.j;d=1E3=this.l.j.length)throw Error("AMA:PF:I");const d=a.Wb?a.Wb:[0];var e="number"===typeof a.Zb?a.Zb:0,f="number"===typeof a.minWidth?a.minWidth:0;const g="number"===typeof a.maxWidth?a.maxWidth:Infinity,h="number"===typeof a.ga?a.ga:0;c=xr(this.l,c);c=vr(vr(vr(vr(vr(vr(vr(c,Qr(d),is(1,b)),Rr(a.sa||[]),is(2,b)),Ur(a.eb||[]),is(3,b)),Vr(a.wh||[]),is(4,b)),Wr(a.wb|| +[]),is(5,b)),Sr(a.vb||[]),is(6,b)),Xa(kp),is(7,b));c=c.apply(Lr(this.j));e=a.Ja&&a.Lb?vr(c,Pr(e,a.Lb,this.j,a.Ia),js(16,b)):vr(c,Or(e,this.j,a.Ia),js(9,b));e=vr(e,za(Zr,f,g),js(10,b));a.Ha&&(e=vr(e,Xr(this.j.document,a.Ha),js(11,b)));a.Wa&&(f=fs(this,e),gs(this,f));e=vr(vr(e,Mr(this.j),js(12,b)),Tr(h,this.j),js(13,b));e=a.Da?wr(e,(k,l)=>{{var m=k.R.o;const p=l.R.o;null==m||null==p?null==m&&null==p?(m=this.m,k=ds(m,k)-ds(m,l)):k=null==m?1:-1:k=m-p}return k}):wr(e,(k,l)=>{var m=this.m;return ds(m,k)- +ds(m,l)});a.Ca&&(e=yr(e,Oc(this.j.location.href+this.j.localStorage.google_experiment_mod)));1===d.length&&Kp(this.o,d[0],{Ic:c.j.length,Ed:e.j.length});return e.j.slice(0)}}const is=(a,b)=>c=>lp(c,b,a),js=(a,b)=>c=>lp(c.R,b,a);function ks(a,b){if(!a)return!1;a=Je(a,b);if(!a)return!1;a=a.cssFloat||a.styleFloat;return"left"==a||"right"==a}function ls(a){for(a=a.previousSibling;a&&1!=a.nodeType;)a=a.previousSibling;return a?a:null}function ms(a){return!!a.nextSibling||!!a.parentNode&&ms(a.parentNode)};function ns(a){const b=wk(a,!0),c=Z(a).scrollWidth,d=Z(a).scrollHeight;let e="unknown";a&&a.document&&a.document.readyState&&(e=a.document.readyState);var f=Ak(a);const g=[];var h=[];const k=[],l=[];var m=[],p=[],r=[];let B=0,y=0,t=Infinity,E=Infinity,K=null;var aa=Dn({ea:!1},a);for(var V of aa){aa=V.getBoundingClientRect();const G=b-(aa.bottom+f);var da=void 0,ma=void 0;if(V.className&&-1!=V.className.indexOf("adsbygoogle-ablated-ad-slot")){da=V.getAttribute("google_element_uid");ma=a.google_sv_map; +if(!da||!ma||!ma[da])continue;da=(ma=Zg(ma[da]))?ma.height:0;ma=ma?ma.width:0}else if(da=aa.bottom-aa.top,ma=aa.right-aa.left,1>=da||1>=ma)continue;g.push(da);k.push(ma);l.push(da*ma);V.className&&-1!=V.className.indexOf("google-auto-placed")?(y+=1,V.className&&-1!=V.className.indexOf("pedestal_container")&&(K=da)):(t=Math.min(t,G),p.push(aa),B+=1,h.push(da),m.push(da*ma));E=Math.min(E,G);r.push(aa)}t=Infinity===t?null:t;E=Infinity===E?null:E;f=os(p);r=os(r);h=ps(b,h);p=ps(b,g);m=ps(b*c,m);V=ps(b* +c,l);return new qs(a,{Tc:e,rb:b,pd:c,od:d,gd:B,Hc:y,Kc:rs(g),Lc:rs(k),Jc:rs(l),pb:f,md:r,ld:t,kd:E,cb:h,bb:p,Dc:m,Cc:V,qd:K})} +function ss(a,b,c,d){const e=Ae()&&!(900<=Z(a.l).clientWidth);d=Ha(d,f=>Ma(a.m,f)).join(",");return{wpc:b,su:c,eid:d,doc:a.j.Tc,pg_h:ts(a.j.rb),pg_w:ts(a.j.pd),pg_hs:ts(a.j.od),c:ts(a.j.gd),aa_c:ts(a.j.Hc),av_h:ts(a.j.Kc),av_w:ts(a.j.Lc),av_a:ts(a.j.Jc),s:ts(a.j.pb),all_s:ts(a.j.md),b:ts(a.j.ld),all_b:ts(a.j.kd),d:ts(a.j.cb),all_d:ts(a.j.bb),ard:ts(a.j.Dc),all_ard:ts(a.j.Cc),pd_h:ts(a.j.qd),dt:e?"m":"d"}} +class qs{constructor(a,b){this.l=a;this.j=b;this.m="633794002 633794005 44715380 44715381 21065713 21065714 21065715 21065716".split(" ")}}function rs(a){return Kd.apply(null,Ha(a,b=>0=a?null:Jd.apply(null,b)/a} +function os(a){let b=Infinity;for(let e=0;ed.getBoundingClientRect()).filter(vs);b.yc=c.length;c=Gn({wa:!0},a).map(d=>d.getBoundingClientRect()).filter(vs);b.Uc=c.length;c=Gn({xa:!0},a).map(d=>d.getBoundingClientRect()).filter(vs);b.nd=c.length;c=Gn({va:!0},a).map(d=>d.getBoundingClientRect()).filter(vs);b.Bc=c.length;c=(Z(a).clientHeight||0)-Ak(a);c=Fn({ea:!1},a).map(d=>d.getBoundingClientRect()).filter(vs).filter(ya(xs,null,c));b.zc=c.length;a=ns(a);c=null!=a.j.cb?a.j.cb: +null;null!=c&&(b.hd=c);a=null!=a.j.bb?a.j.bb:null;null!=a&&(b.Ac=a);return b} +function Lq(a,b,{Xb:c,xc:d,Sc:e}={}){const f=b.R;if(f.m)return!1;var g=b.O(),h=f.l(),k=a.m;a:{var l=a.j;switch(h){case 0:l=ks(ls(g),l);break a;case 3:l=ks(g,l);break a;case 2:var m=g.lastChild;l=ks(m?1==m.nodeType?m:ls(m):null,l);break a}l=!1}if(k=!l&&!(!k&&2==h&&!ms(g)))g=1==h||2==h?g:g.parentNode,k=!(g&&!Fm(g)&&0>=g.offsetWidth);if(!k)return!1;c=null==c?null:new Tl(null,{google_max_responsive_height:c});g=Ul(N(f.Ba,2)||0);h=f.o;h=null==h?null:new Tl(null,{google_ml_rank:h});d=Sl(a.F,f.F?f.F.j(b.M): +null,c,d||null,g,h);b=b.fill(a.D,d);if(e){if(b){e=b.U;c=e.style.width;e.style.width="100%";g=e.offsetWidth;e.style.width=c;e=g;c=a.j;g=b.U;h=d&&d.qb||{};if(Tg(c)!=c)k=Yg(c)?3:16;else if(488>Z(c).clientWidth)if(c.innerHeight>=c.innerWidth)if(k=Z(c).clientWidth,!k||.3<(k-e)/k)k=6;else{if(k="true"!=h.google_full_width_responsive)c:{l=g.parentElement;for(k=Z(c).clientWidth;l;l=l.parentElement){m=Je(l,c);if(!m)continue;const p=Ye(m.width);if(p&&!(p>=k)&&"visible"!=m.overflow){k=!0;break c}}k=!1}k=k?7: +!0}else k=5;else k=4;if(!0!==k)e=k;else{if(!(h="true"==h.google_full_width_responsive))b:{do if((h=Je(g,c))&&"fixed"==h.position){h=!1;break b}while(g=g.parentElement);h=!0}h?T.G().j(233,!1)||c.location&&"#bffwroe2etoq"==c.location.hash?e=!0:(c=Z(c).clientWidth,e=c-e,e=c&&0<=e?!0:c?-10>e?11:0>e?14:12:10):e=9}if(e){e=a.j;c=b.U;if(g=Dm(e,c))c.style.border=c.style.borderStyle=c.style.outline=c.style.outlineStyle=c.style.transition="none",c.style.borderSpacing=c.style.padding="0",Bm(c,g,"0px"),c.style.width= +Z(e).clientWidth+"px",Em(e,c,g),c.style.zIndex=30;e=!0}else Jm(b.la),e=!1}else e=!1;e=!e}if(e||!Oq(a,b,d))return!1;Vj(9,[f.o,f.Sa]);return!0}function Mq(a,b,c,d){const e=c.ia?c.ia:a.A,f=Fq(e,b.j.length);return a.v.find({kc:ys(a),Wb:c.types,Zb:f.za,Ia:b,sa:a.J,ga:f.ga||void 0,Ca:!!a.l.Ca,Da:!!a.l.Da,vb:c.vb,minWidth:c.minWidth,maxWidth:c.maxWidth,eb:a.N,Ha:a.I,wb:c.wb,Wa:!!a.l.Wa,Ja:!!a.l.Ja,Lb:e.j},d)}function zs(a){return a.C?a.C:a.C=a.j.google_ama_state} +function ys(a){var b=zs(a);if(null==b)return-1;b=b.placement;return"number"!==typeof b||0>b||b>a.v.l.j.length?-1:b}function Oq(a,b,c){if(!b)return!1;try{Um(a.j,b.U,c)}catch(d){return Jm(b.la),a.o.push(6),!1}return!0}class As{constructor(a,b,c,d,e={}){this.v=a;this.D=b;this.j=c;this.A=d.ia;this.J=d.sa||[];this.F=d.Wc||null;this.N=d.eb||[];this.I=d.Ha||[];this.l=e;this.m=!1;this.H=[];this.o=[];this.C=void 0}K(){return this.j}Y(a){this.H.push(a)}mb(){return!!this.l.hc}Ra(){return!jq(this.j)}} +const vs=a=>1<(a.bottom-a.top)*(a.right-a.left),xs=(a,b)=>b.top<=a;function Bs(a,b,c,d,e){this.ra=a;this.da=b;this.Ea=c;this.j=d;this.l=e};var Cs=(a,b,{Ra:c=!1,mb:d=!1,yd:e=!1}={})=>{const f=[];e&&f.push(9);-1{const d={win:a.j,domInterface:{getDocument:()=>a.j.document,getContainer:()=>mp(b.R),attachToDom:e=>qp(b,e)},webPropertyCode:a.v,experimentIds:N(a.o,2)};Ns(a.l)&&c.handleRequest(d)})}}class Ts{constructor(a,b,c,d,e){this.j=a;this.v=b;this.m=c.replace("-","_").toLowerCase();this.o=d;this.A=e;this.l=new Os(a,O(d,yl,3)||new yl)}} +function Rs(a,b){b=jp(b,a).filter(Sr([5]));b=rp(b,a);const c=1.5*Z(a).clientHeight;a=b.filter(d=>d.M.j>c);a.sort((d,e)=>d.M.j-e.M.j);return a[0]||null}function Ss(a){a="__"+a;const b=Xg();return Rj(b,"/pagead/js/"+Nf()+"/r20190131/user_satisfaction/in_page_surveys"+a+".js",Tf?"https":"http")};class Us{j(){return new Tl([],{["google_tag_origin"]:"qs"})}};class Vs{j(){return new Tl(["adsbygoogle-resurrected-ad-slot"],{})}};function Ws(a){this.j=a}Ws.prototype.l=function(a,b,c,d){if(!this.j)return null;const e=this.j.google_ad_format||null,f=this.j.google_ad_slot||null;if(c=c.style){var g=[];for(let h=0;h{const c=new fp(b,3);b=new Ws(Wm(a.j,b));return new ip(c,b,a.l,!1,0,[],null,a.j,null)})}class Ys{constructor(a,b){this.j=a;this.l=b||null}};const Zs={Ab:"10px",$a:"10px"};function $s(a){return sm(a.j.document.querySelectorAll("INS.adsbygoogle-placeholder")).map(b=>new ip(new fp(b,1),new bp(Zs),a.l,!1,0,[],null,a.j,null))}class at{constructor(a,b){this.j=a;this.l=b||null}};function bt(a){this.j=a}function ct(a,b){a=b.v(a.j);a.r=.1;Y("ama_failure",a,.1)};var dt=(a,b,c,d,e,f)=>{try{const g=a.j,h=ae(a,"SCRIPT");h.async=!0;Hc(h,b);g.head.appendChild(h);h.addEventListener("load",()=>{e();d&&g.head.removeChild(h)});h.addEventListener("error",()=>{0{d(!1)})}class gt{constructor(a){this.j=new Od(a)}};var ht=(a,b)=>{Object.defineProperty(q,a,{configurable:!1,get:function(){return b},set:la})};var jt=(a,b)=>{it(a,"internal_api_load_with_sb",(c,d,e)=>{ft(b,c,d,e)});it(a,"internal_api_sb",()=>{})},it=(a,b,c)=>{a=q.btoa(a+b);ht(a,c)},kt=(a,...b)=>{a=q.btoa(a+"internal_api_load_with_sb");a=q[a];if(qa(a))a.apply(null,b);else throw Error("API not exported.");};function lt(){const a=()=>{if(!q.frames.googlefcPresent)if(document.body){const b=document.createElement("iframe");b.style.display="none";b.style.width="0px";b.style.height="0px";b.style.border="none";b.style.zIndex="-1000";b.style.left="-1000px";b.style.top="-1000px";b.name="googlefcPresent";document.body.appendChild(b)}else q.setTimeout(a,5)};a()}function mt(a){kt(a.j,a.l.C(),()=>{{var b=a.j;const c=q[q.btoa(b+"cached_js")];c&&(q.atob(c),b=q.btoa(b+"cached_js"),ca(b,null,void 0))}},()=>{})} +class nt{constructor(a){this.m=q.document;this.o=new gt(this.m);this.j=a;var b=ub(new mb(nb,"https://fundingchoicesmessages.google.com/uf/%{externalId}"),{externalId:this.j});a=new et;b=tb(b).toString();pd(a,4,b);this.l=a}start(){try{lt(),jt(this.j,this.o),q.googlefc=q.googlefc||{},"callbackQueue"in q.googlefc||(q.googlefc.callbackQueue=[]),mt(this)}catch(a){}}};var pt=(a,b,c,d,e=null)=>{ot(a,new bt(a),b,c,d,e,new fm(a))},ot=(a,b,c,d,e,f=null,g=null)=>{if(c)if(d){var h=[];O(d,ml,18)&&h.push(2);e.L&&h.push(0);O(d,kl,14)&&h.push(1);O(d,zl,21)&&O(O(d,zl,21),Al,1)&&h.push(3);try{qt(new rt(a,b,c,d,e,h,f,null,g,null))}catch(k){ct(b,Pp(Rp(Qp(Np(new Sp(0),c),d),h).Y(1),k))}}else ct(b,Np(new Sp(0),c).Y(8));else ct(b,(new Sp(0)).Y(9))}; +function qt(a){a.F.forEach(b=>{switch(b){case 0:st(a)&&tt(a,"p");Nl(a.j)&&1===N(Nl(a.j),1)&&(b=O(Nl(a.j),Kl,6))&&2===N(b,1)&&Vm(a.l);if(Ol(a.j)&&td(Ol(a.j),12)){b=a.l;var c=O(a.j,Ml,20),d=Io(b),e;if(e=d)e=(e=O(d,Ml,7))||c?e&&c?N(e,1)!==N(c,1):!0:!1;if(e){yd(d,[]);wd(d,6,void 0);wd(d,7,c);c=d.C();try{b.localStorage.setItem("google_ama_settings",c)}catch(p){}}}b=a.m.rd;d=Ol(a.j)?td(Ol(a.j),7):!1;c=Cq(a.l,b);a.m.L&&null!=N(a.m.L,10)?(d=qd(O(a.m.L,Il,10),1),null!==d&&void 0!==d&&(c=uq(a.l,d,!1,b))):d&& +(d=Ol(a.j)&&null!=N(Ol(a.j),9)?qd(Ol(a.j),9):null,null!==d&&(c=uq(a.l,d,!0)));d=a.m.L?N(a.m.L,6):[];e=a.m.L?Q(a.m.L,Vk,5):[];var f=a.j;var g=Q(f,wl,1),h=a.m.L&&Pl(a.m.L,1)?"text_image":"text",k=new Us,l=new Vs,m=jp(g,a.l,{Nc:k,cd:new ep(h)});g.length!=m.length&&a.D.push(13);m=m.concat($s(new at(a.l,k)));g=0;Nl(f)&&1===N(Nl(f),1)&&(k=O(Nl(f),Kl,6))&&(g=N(k,2)||0,1===N(k,1)&&(l=Xs(new Ys(a.l,l)),m=m.concat(l)));m=m.concat(fq(f,h,a.l));f=new hs(m,{},a.l,g);h=a.v;m=a.l;d={ia:c,Wc:a.N,sa:a.m.sa,eb:d,Ha:e}; +Ol(a.j)?(e=Ol(a.j),c={Ca:td(e,14),Da:td(e,2),Mb:td(e,3),oc:td(e,4),Nb:td(e,5),hc:td(e,6),cc:ud(e,8,0),ac:N(e,10),Wa:td(e,12),Ja:ut(a,c,e),fb:vt(a)}):c={Ca:!1,Da:!1,Mb:!1,oc:!1,Nb:!1,hc:!1,cc:0,ac:0,Wa:!1,Ja:!1,fb:vt(a)};a.o=new As(f,h,m,d,c);e=a.m.L?N(a.m.L,2):[];b=N(b,1);c=a.o;d=a.l;e=Cs(b,e,{Ra:c.Ra(),mb:c.mb(),yd:!!c.l.fb});b=new Es(e,b,c,d);a.A=b;b=a.A;c=new Fs;for(b.j.m=!0;0=b?a.I:null:a.I} +function ut(a,b,c){switch(N(c,17)){case 0:return!1;case 1:return!0;case 2:return a.m.L&&null!=N(a.m.L,10)?.5<=(qd(O(a.m.L,Il,10),1)||0):!0;case 3:return a=ns(a.l),a=null!=a.j.pb?a.j.pb:null,b=(b.j?b.j.ja:void 0)||0,null!=a&&a<=b;default:return!1}} +function wt(a,b){for(var c=Op(Op(new Sp(b.ra),b.da),a.D),d=b.Ea,e=0;e{tt(a,"s")});dm(a.C,c=>{tt(a,"d",c);a.C.Ma()})}}function tt(a,b,c){a={r:b,pg_h:Z(a.l).scrollHeight,su:a.l.location.hostname};void 0!==c&&(a.pg_hd=c);Y("ama_inf_scr",a,1)}function st(a){return Ol(a.j)&&td(Ol(a.j),18)?!0:!1} +class rt{constructor(a,b,c,d,e,f,g,h,k,l){this.l=a;this.J=b;this.v=c;this.j=d;this.m=e;this.F=f;this.N=g||null;this.D=[];this.T=h;this.C=k;this.I=l}V(a){try{const r=yt(this)||xt(this)?yt(this):void 0;if(Ol(this.j)&&td(Ol(this.j),12)){if(xt(this)){{var b=this.o;const y=Gn({wa:!0,xa:!0},b.j);var c=us(y,b.j)}}else{{var d=this.o;const y=Fn({ea:!1,va:!1},d.j);c=us(y,d.j)}}const B=O(this.j,Nk,19);if(B){const y=Cq(this.l,B),t=new Do;var e=Fq(y,0).za;pd(t,3,e);pd(t,1,y.l);Jo({ua:r,Na:c,Ya:t},this.l)}else Jo({ua:r, +Na:c},this.l)}else Jo({ua:r},this.l);zt(this);{var f=yt(this);{var g=zs(this.o);const y=a.j,t=y.j;let E=y.ra,K=y.da.slice(),aa=y.Ea.slice(),V=a.exception;if(g){g.numAutoAdsPlaced?E+=g.numAutoAdsPlaced:this.A.m&&aa.push(13);void 0!==g.exception&&(V=g.exception);var h={ra:E,sb:t,da:y.da.slice(),Ea:aa,exception:V,ib:f,Xa:!!g.eatf}}else aa.push(12),this.A.m&&aa.push(13),h={ra:E,sb:t,da:K,Ea:aa,exception:V,ib:f,Xa:!1}}e=h;e.Gb=ws(this.o.j);const B=a.j.l;B&&(e.Xc=B);e.rb=Z(this.l).scrollHeight;var k;if(!(k= +Qf))if(null!=Tj)k=Tj;else{Tj=!1;try{const y=Yg(q);if(y&&-1!=y.location.hash.indexOf("auto_ads_logging")||q.localStorage.getItem("auto_ads_logging"))Tj=!0}catch(y){}k=Tj}if(k){var l=this.o.v.l.j.slice(0);a=[];for(const y of l){l={};const t=y.C;for(const K of hm(t))l[K]=t.get(K);const E={anchorElement:y.v.j(y.j),position:y.l(),clearBoth:y.A,locationType:y.Sa,placed:y.m,placementProto:y.H?xd(y.H):null,rejectionReasons:l};a.push(E)}var m={placementIdentifiers:a};Vj(14,[m,this.o.D])}var p=e}wt(this,p)}catch(r){this.H(r)}}H(a){wt(this, +{ra:0,sb:void 0,da:[],Ea:[],exception:a,ib:void 0,Xa:void 0,Gb:void 0})}};var At=a=>5==a.google_pgb_reactive&&!!a.google_reactive_ads_config,Bt=a=>"number"===typeof a.google_reactive_sra_index,Gt=(a,b)=>{const c=b.j,d=b.B;var e=null;try{e=c.localStorage}catch(k){}d.google_reactive_plat=jr(c,d,e);(e=kr(a))&&(d.google_reactive_plaf=e);(e=lr(a))&&(d.google_reactive_fba=e);Ct(a,d);e=er(c.location);Dt(a,e,d);e?(d.fra=e,d.google_pgb_reactive=6):d.google_pgb_reactive=5;const f=qg()||Jj(Tg(b.pubWin));e=W(429,(k,l)=>Et(c,d.google_ad_client,a,f,k,l));const g=Cj(c),h=W(430,za(Dk, +c,431,qi));Di(c,"rsrai",e,h);g.wasReactiveTagRequestSent=!0;Ft(b,a)}; +const Ft=(a,b)=>{const c=a.j,d=a.B,e=ra(b.page_level_pubvars)?b.page_level_pubvars:{};a=W(353,(f,g)=>{var h=d.google_ad_client;if(zf(g.origin,Qf))a:{f=f.config;if(T.G().j(316,!1))var k=null;else try{k=c.localStorage.getItem("google_ama_config")}catch(r){k=null}try{var l=k?Ad(Cl,k):null}catch(r){l=null}k=l;b:{if(f)try{var m=Ad(Cl,f);break b}catch(r){Wl(c,{cfg:1,inv:1})}m=null}if(m){l=m;k=new El;wd(l,3,k);f=Ol(l)&&N(Ol(l),13)?N(Ol(l),13):1;pd(k,1,Date.now()+864E5*f);k=new l.constructor(Bd(xd(l)));Ol(l)&& +(f=new Ll,g=td(Ol(l),12),f=pd(f,12,g),l=td(Ol(l),15),l=pd(f,15,l),wd(k,15,l));l=Q(k,wl,1);for(f=0;f{if(!zf(f.origin,Qf))return!1;e=e.data;if(!e||!pa(e))return!1;if(!bh(a,1))return!0;Vj(6,[e]);const g=[];f=[];const h=Cj(a);for(let k=0;k{Ht(g,a,b,k,c,d)});return!0},Ht=(a,b,c,d,e,f)=>{const g=[];for(let l=0;lr.verifyAndProcessConfig(b,m))}else Y("rasra::ivc",{af:p,ak:h,c},.1)}Y("rasra::pr",{rt:g.join(","),c},.1)},Ct=(a,b)=>{const c=[];let d=!1;U(Aj,(e,f)=>{let g;if(a.hasOwnProperty(f)){const h=a[f];ra(h)&&h.google_ad_channel&&(g=String(h.google_ad_channel))}f=Aj[f]-1;c[f]&&"+"!=c[f]||(c[f]=g?g.replace(/,/g,"+"):"+",d=d||g)});d&&(b.google_reactive_sra_channels=c.join(","))},Dt=(a,b,c)=>{const d=a.page_level_pubvars;!c.google_adtest&&("on"==a.google_adtest||d&&"on"==d.google_adtest|| +b)&&(c.google_adtest="on")};Rc("script");/* + + Copyright 2019 The AMP HTML Authors. All Rights Reserved. + + Licensed under the Apache License, Version 2.0 (the "License"); + you may not use this file except in compliance with the License. + You may obtain a copy of the License at + + http://www.apache.org/licenses/LICENSE-2.0 + + Unless required by applicable law or agreed to in writing, software + distributed under the License is distributed on an "AS-IS" BASIS, + WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. + See the License for the specific language governing permissions and + limitations under the License. +*/ +var It={"image-top":0,"image-middle":1,"image-side":2,"text-only":3,"in-article":4};var Jt="google_ad_block google_ad_channel google_ad_client google_ad_format google_ad_height google_ad_host google_ad_host_channel google_ad_host_tier_id google_ad_layout google_ad_layout_key google_ad_modifications google_ad_output google_ad_region google_ad_section google_ad_slot google_ad_type google_ad_unit_key google_ad_dom_fingerprint google_ad_semantic_area google_ad_width google_adtest google_allow_expandable_ads google_alternate_ad_url google_alternate_color google_analytics_domain_name google_analytics_uacct google_apsail google_captcha_token google_city google_color_bg google_color_border google_color_line google_color_link google_color_text google_color_url google_container_id google_content_recommendation_ad_positions google_content_recommendation_columns_num google_content_recommendation_rows_num google_content_recommendation_ui_type google_content_recommendation_use_square_imgs google_contents google_core_dbp google_country google_cpm google_ctr_threshold google_cust_age google_cust_ch google_cust_criteria google_cust_gender google_cust_id google_cust_interests google_cust_job google_cust_l google_cust_lh google_cust_u_url google_disable_video_autoplay google_bfa ebfa ebfaca google_eids google_enable_content_recommendations google_enable_ose google_encoding google_font_face google_font_size google_frame_id google_full_width_responsive_allowed efwr google_full_width_responsive gfwroh gfwrow gfwroml gfwromr gfwroz gfwrnh gfwrnwer gfwrnher google_gl google_hints google_image_size google_kw google_kw_type google_lact google_language google_loeid google_max_num_ads google_max_radlink_len google_max_responsive_height google_ml_rank google_mtl google_native_ad_template google_native_settings_key google_num_radlinks google_num_radlinks_per_unit google_only_pyv_ads google_override_format google_page_url google_pgb_reactive google_pucrd google_referrer_url google_region google_resizing_allowed google_resizing_height google_resizing_width rpe google_responsive_formats google_responsive_auto_format armr google_rl_dest_url google_rl_filtering google_rl_mode google_rt google_safe google_safe_for_responsive_override google_scs google_source_type google_tag_for_child_directed_treatment google_tag_for_under_age_of_consent google_tag_origin google_tag_partner google_targeting google_tfs google_video_doc_id google_video_product_type google_video_url_to_fetch google_webgl_support google_yt_pt google_yt_up google_package google_debug_params google_enable_single_iframe dash google_refresh_count google_restrict_data_processing".split(" "), +Kt=a=>(a=a.innerText||a.innerHTML)&&(a=a.replace(/^\s+/,"").split(/\r?\n/,1)[0].match(/^\x3c!--+(.*?)(?:--+>)?\s*$/))&&/google_ad_client/.test(a[1])?a[1]:null,Lt=a=>{if(a=a.innerText||a.innerHTML)if(a=a.replace(/^\s+|\s+$/g,"").replace(/\s*(\r?\n)+\s*/g,";"),(a=a.match(/^\x3c!--+(.*?)(?:--+>)?$/)||a.match(/^\/*\s*)?$/i))&&/google_ad_client/.test(a[1]))return a[1];return null},Ot=a=>{try{a:{var b=a.document.getElementsByTagName("script"),c=a.navigator&&a.navigator.userAgent|| +"";const f=/appbankapppuzdradb|daumapps|fban|fbios|fbav|fb_iab|gsa\/|messengerforios|naver|niftyappmobile|nonavigation|pinterest|twitter|ucbrowser|yjnewsapp|youtube/i.test(c)||/i(phone|pad|pod)/i.test(c)&&/applewebkit/i.test(c)&&!/version|safari/i.test(c)&&!Ug()?Kt:Lt;for(let g=b.length-1;0<=g;g--){const h=b[g];if(!h.google_parsed_script){h.google_parsed_script=!0;const k=f(h);if(k){var d=k;break a}}}d=null}}catch(f){return!1}if(!d)return!1;try{{c=/(google_\w+) *= *(['"]?[\w.-]+['"]?) *(?:;|$)/gm; +b={};let f;for(;f=c.exec(d);)b[f[1]]=Mt(f[2]);var e=b}Nt(e,a)}catch(f){return!1}return!!a.google_ad_client},Pt=a=>{const b={};null==a.google_ad_client&&Ot(a)&&(b.google_loader_features_used=2048);Nt(a,b);return b},Mt=a=>{switch(a){case "true":return!0;case "false":return!1;case "null":return null;case "undefined":break;default:try{const b=a.match(/^(?:'(.*)'|"(.*)")$/);if(b)return b[1]||b[2]||"";if(/^[-+]?\d*(\.\d+)?$/.test(a)){const c=parseFloat(a);return c===c?c:void 0}}catch(b){}}},Nt=(a,b)=>{for(let c= +0;c{};const d=Vt(c,b);if(!d)return()=>{};const e=Qt(b);a=a==c?Pt(a):gb(c);const f={ub:d,B:a,offsetWidth:d.offsetWidth};e.push(f);return()=>Na(e,f)} +function Vt(a,b){a=b.document.getElementById(a.google_async_iframe_id);if(!a)return null;for(a=a.parentElement;a&&!Rg.test(a.className);)a=a.parentElement;return a} +function St(a,b){for(let g=0;g=a.innerWidth?0:90,R(a,"resize",()=>{var c=a.innerHeight>=a.innerWidth?0:90;if(this.j!=c){this.j=c;c=Qt(a);for(let d=0;d{Oe(Xt,(b,c)=>{try{null!=q[b]&&(a[c]=q[b])}catch(d){}})},Zt=a=>{a.shv=Nf()};ri.o=!Qf;var $t=class{constructor(a,b,c){this.o=a;this.m=b;this.j=c;this.l=null;this.v=this.A=0}C(){10<=++this.A&&q.clearInterval(this.l);var a=Dm(this.o,this.m),b=Em(this.o,this.m,a);a=zm(this.m,this.o);null!=a&&0===a.x||q.clearInterval(this.l);b&&(b=(ah(this.j).eids||[]).join(","),this.v++,Y("rspv:al",{aligns:this.v,attempt:this.A,client:this.j.google_ad_client,eoffs:null!=a?a.x:null,eids:b,slot:this.j.google_ad_slot,url:this.j.google_page_url},.01))}};function au(a){try{return a.sz()}catch(b){return!1}}function bu(a){return!!a&&("object"===typeof a||"function"===typeof a)&&au(a)&&Gg(a.nq)&&Gg(a.nqa)&&Gg(a.al)&&Gg(a.rl)}function cu(a){const b=W(189,ya(a.N,a));a.l.setTimeout(b,0)} +class du{constructor(a){this.o=[];this.l=a||window;this.j=0;this.m=null;this.D=0}F(a,b){0!=this.j||0!=this.o.length||b&&b!=window?this.v(a,b):(this.j=2,this.C(new eu(a,window)))}v(a,b){this.o.push(new eu(a,b||this.l));cu(this)}I(a){this.j=1;if(a){const b=W(188,ya(this.A,this,!0));this.m=this.l.setTimeout(b,a)}}A(a){a&&++this.D;1==this.j&&(null!=this.m&&(this.l.clearTimeout(this.m),this.m=null),this.j=0);cu(this)}J(){return!(!window||!Array)}H(){return this.D}N(){if(0==this.j&&this.o.length){const a= +this.o.shift();this.j=2;const b=W(190,ya(this.C,this,a));a.win.setTimeout(b,0);cu(this)}}C(a){this.j=0;a.j()}}var fu;du.prototype.nq=du.prototype.F;du.prototype.nqa=du.prototype.v;du.prototype.al=du.prototype.I;du.prototype.rl=du.prototype.A;du.prototype.sz=du.prototype.J;du.prototype.tc=du.prototype.H;var eu=class{constructor(a,b){this.j=a;this.win=b}};class gu extends Zf{constructor(a,b,c,d=!1){super();this.j=a;this.Fa=b;this.wc=c;this.vc=d;this.Ga={};this.Cb=oi(this.Fa,168,(e,f)=>{a:{try{if(!zf(f.origin,this.vc))break a}catch(k){break a}const g=e.msg_type;let h;"string"===typeof g&&(h=this.Ga[g])&&h.call(this,e,f)}});this.Eb=oi(this.Fa,169,(e,f)=>Dk(this.j,"ras::xsf",this.wc,e,f));this.V=[];this.N(this.Ga);this.V.push(Ci(this.j,"sth",this.Cb,this.Eb))}l(){for(const a of this.V)a();this.V.length=0;super.l()}};class hu extends gu{constructor(a){super(a,ri,qi,Qf);this.j=a}};function iu(a){try{const b=a.localStorage.getItem("google_adsense_settings");if(!b)return{};const c=JSON.parse(b);return c!==Object(c)?{}:bb(c,(d,e)=>Object.prototype.hasOwnProperty.call(c,e)&&"string"===typeof e&&pa(d))}catch(b){return{}}} +class ju extends hu{constructor(a,b){super(a);this.m=b;this.o=()=>{};R(this.m,"load",this.o)}l(){this.m&&ee(this.m,"load",this.o);super.l();this.m=null}N(a){a["adsense-labs"]=this.v}v(a){if(a=Ck(a).settings)try{var b=new le(JSON.parse(a));if(null!=N(b,1)){{var c=this.j,d=N(b,1)||"";const e=iu(c);null!==b&&(e[d]=xd(b));try{c.localStorage.setItem("google_adsense_settings",JSON.stringify(e))}catch(f){}}}}catch(e){}}};let ku=(new Date).getTime();var mu=a=>{const b={};b.dtd=lu((new Date).getTime(),ku);return Jg(b,a)},lu=(a,b,c=1E5)=>{a-=b;return a>=c?"M":0<=a?a:"-M"};class nu{constructor(a){this.j=a;a.google_iframe_oncopy||(a.google_iframe_oncopy={handlers:{},upd:(b,c)=>{{var d=b,e=/\brx=(\d+)/;const f=e.exec(d);f&&(d=d.replace(e,"rx="+(+f[1]+1||1)))}e=Number;a:{if(b&&(b=b.match("dt=([^&]+)"))&&2==b.length){b=b[1];break a}b=""}b=e(b);d=d.replace(/&dtd=(\d+|-?M)/,"&dtd="+lu((new Date).getTime(),b));this.set(c,d);return c=d}});this.l=a.google_iframe_oncopy}set(a,b){this.l.handlers[a]=b;this.j.addEventListener&&this.j.addEventListener("load",()=>{{const c=this.j.document.getElementById(a); +try{const d=c.contentWindow.document;if(c.onload&&d&&(!d.body||!d.body.firstChild))c.onload()}catch(d){}}},!1)}}Ic("var i=this.id,s=window.google_iframe_oncopy,H=s&&s.handlers,h=H&&H[i],w=this.contentWindow,d;try{d=w.document}catch(e){}if(h&&d&&(!d.body||!d.body.firstChild)){if(h.call){setTimeout(h,0)}else if(h.match){try{h=s.upd(h,i)}catch(e){}w.location.replace(h)}}");function ou(a){switch(a){case "":case "Test":case "Real":return!0;default:return!1}}var pu=class{constructor(a,b=!1){this.m=a;this.l=b;this.j=new te(a.document)}write(a){let b=a.J();if(this.l){if(!ou(this.j.get("__gads","")))return;ou(b)||(b="Real")}this.j.set("__gads",b,{jd:a.F()-this.m.Date.now()/1E3,path:a.H(),domain:a.l(),zd:!1})}};const qu=/^\.google\.(com?\.)?[a-z]{2,3}$/,ru=/\.(cn|com\.bi|do|sl|ba|by|ma|am)$/;let su=()=>q,tu=q;const vu=a=>{a="https://"+`adservice${a}/adsid/integrator.${"js"}`;const b=[`domain=${encodeURIComponent(q.location.hostname)}`];uu[3]>=+new Date&&b.push(`adsid=${encodeURIComponent(uu[1])}`);return a+"?"+b.join("&")};let uu,wu; +const xu=()=>{tu=su();uu=tu.googleToken=tu.googleToken||{};var a=+new Date;uu[1]&&uu[3]>a&&00{wu[8]++},ud:()=>{0{wu[8]=0},yh:()=>!1,Qb:()=>wu[5],Ib:a=>{try{a()}catch(b){q.setTimeout(()=> +{throw b;},0)}},dc:()=>{if(!yu.hb()){var a=q.document,b=e=>{e=vu(e);a:{try{var f=ea();break a}catch(g){}f=void 0}Zq(a,e,f);f=a.createElement("script");f.type="text/javascript";f.onerror=()=>q.processGoogleToken({},2);e=ye(e);Hc(f,e);try{(a.head||a.body||a.documentElement).appendChild(f),yu.td()}catch(g){}},c=wu[1];b(c);".google.com"!=c&&b(".google.com");var d={["newToken"]:"FBT"};q.setTimeout(()=>q.processGoogleToken(d,1),1E3)}}},zu=a=>{xu();const b=tu.googleToken[5]||0;a&&(0!=b||uu[3]>=+new Date? +yu.Ib(a):(yu.Qb().push(a),yu.dc()));uu[3]>=+new Date&&uu[2]>=+new Date||yu.dc()},Bu=a=>{q.processGoogleToken=q.processGoogleToken||((b,c)=>Au(b,c));zu(a)},Au=(a={},b=0)=>{var c=a.newToken||"",d="NT"==c,e=parseInt(a.freshLifetimeSecs||"",10),f=parseInt(a.validLifetimeSecs||"",10);const g=a["1p_jar"]||"";a=a.pucrd||"";xu();1==b?yu.vd():yu.ud();var h=tu.googleToken=tu.googleToken||{},k=0==b&&c&&"string"===typeof c&&!d&&"number"===typeof e&&0=+new Date)||"NT"==uu[1]);var l=!(uu[3]>=+new Date)&&0!=b;if(k||d||l)d=+new Date,e=d+1E3*e,f=d+1E3*f,1E-5>Math.random()&&tg("https://pagead2.googlesyndication.com/pagead/gen_204?id=imerr"+`&err=${b}`),h[5]=b,h[1]=c,h[2]=e,h[3]=f,h[4]=g,h[6]=a,xu();if(k||!yu.hb()){b=yu.Qb();for(c=0;c{const b=a.google_sa_queue,c=b.shift();a.google_sa_impl||Y("shimpl",{t:"no_fn"});qa(c)&&yi(216,c);b.length&&a.setTimeout(()=>Cu(a),0)}),Du=a=>{const b=Td(document,"IFRAME");U(a,(c,d)=>{null!=c&&b.setAttribute(d,c)});return b},Eu=a=>{const b=["{null!=c&&b.push(" "+d+'="'+Ic(c)+'"')});b.push(">");return b.join("")},Fu=a=>Qj(Xf(),["/pagead/html/",Nf(),"/r20190131/zrt_lookup.html#",encodeURIComponent(a)].join("")), +Gu=(a,b,c,d)=>{null!=b&&(a.width=b&&""+b);null!=c&&(a.height=c&&""+c);a.frameborder="0";d&&(a.src=d);a.marginwidth="0";a.marginheight="0";a.vspace="0";a.hspace="0";a.allowtransparency="true";a.scrolling="no";a.allowfullscreen="true"};var Hu=(a,b)=>Di(a,"adpnt",(c,d)=>{zk(d,b.contentWindow)?(b.dataset.googleQueryId||(c=Ck(c).qid,b.setAttribute("data-google-query-id",c)),c=!0):c=!1;return c});function Iu(a,b){const c=a.pubWin.document.getElementById(a.B.google_async_iframe_id+"_expand");return c?new Ju(a,b,c):null}function Ku(a){a.m=a.A;a.F.style.transition="height 500ms";a.o.style.transition="height 500ms";a.C.style.transition="height 500ms";a.D.style.transition="height 500ms";Lu(a)}function Mu(a,b){(a.v.contentWindow||a.v.contentWindow).postMessage(JSON.stringify({["msg_type"]:"expand-on-scroll-result",["eos_success"]:!0,["eos_amount"]:b,googMsgType:"sth"}),"*")} +function Lu(a){const b=`rect(0px, ${a.v.width}px, ${a.m}px, 0px)`;a.D.style.clip=b;a.C.style.clip=b;a.D&&(a.D.setAttribute("height",a.m),a.D.style.height=a.m+"px");a.C.setAttribute("height",a.m);a.C.style.height=a.m+"px";a.o.style.height=a.m+"px";a.F.style.height=a.m+"px"} +function Nu(a,b){b=We(b.r_nh);a.A=null==b?0:b;if(0>=a.A)return"1";a.J=Bg(a.F).y;a.H=Ak(a.j);if(a.J+a.mwk(a.j)-a.j.innerHeight)return"3";b=a.H;a.v.setAttribute("height",a.A);a.v.style.height=a.A+"px";a.C.style.overflow="hidden";a.F.style.position="relative";a.F.style.transition="height 100ms";a.o.style.transition="height 100ms";a.C.style.transition="height 100ms";a.D.style.transition="height 100ms";b=Math.min(b+a.j.innerHeight-a.J,a.m);vg(a.o,{position:"relative",top:"auto",bottom:"auto"}); +b=`rect(0px, ${a.v.width}px, ${b}px, 0px)`;vg(a.D,{clip:b});vg(a.C,{clip:b});return"0"}function Ou(a,b={}){a.W&&(b.eid=a.W);b.qid=a.aa;Y("eoscrl",b,Kf(String(a.ba),.05))} +class Ju extends hu{constructor(a,b,c){super(a.j);this.v=b;this.D=(b=a.iframeWin&&Og(a.B)?a.iframeWin.frameElement:b)?b:a.o;this.C=c.firstElementChild;this.o=c;this.F=this.o.parentElement&&"adsbygoogle"===this.o.parentElement.className?this.o.parentElement:this.o;this.m=parseInt(this.o.style.height,10);this.W=null;this.Db=this.ha=!1;this.aa="";this.X=this.H=this.A=0;this.Mc=this.m/5;this.J=Bg(this.F).y;this.ba=null;this.uc=ab(W(651,()=>{this.J=Bg(this.F).y;var d=this.H;this.H=Ak(this.j);this.m=this.Mc?(Ku(this),Mu(this,this.A)):(this.m=Math.min(this.A,this.m+d),Mu(this,d),Lu(this)))):ee(this.j,"scroll",this.I)}),this);this.I=()=>{var d=this.uc;S.requestAnimationFrame?S.requestAnimationFrame(d):d()}}N(a){a["expand-on-scroll"]=this.pc;a["expand-on-scroll-force-expand"]=this.Qc}pc(a,b){$g(b,this.v)&&(a=Ck(a),this.W=a.i_expid,this.aa=a.qid,this.ba=a.gen204_fraction,this.ha||(this.ha=!0,a=Nu(this,a),"0"===a&&R(this.j,"scroll",this.I,be),b.source.postMessage(JSON.stringify({["msg_type"]:"expand-on-scroll-result", +["eos_success"]:"0"===a,googMsgType:"sth"}),"*"),Ou(this,{err:a})))}Qc(a,b){$g(b,this.v)&&!this.Db&&(this.Db=!0,Ku(this),ee(this.j,"scroll",this.I))}l(){this.I&&ee(this.j,"scroll",this.I,be);super.l()}};function Pu(a){const b=a.o.getBoundingClientRect(),c=0>b.top+b.height;return!(b.top>a.m.innerHeight)&&!c} +class Qu extends Zf{constructor(a,b,c){super();this.m=a;this.A=b;this.o=c;this.C=0;this.o&&(this.v=Pu(this),this.F=$a(this.D,this),this.j=W(433,()=>{var d=this.F;S.requestAnimationFrame?S.requestAnimationFrame(d):d()}),R(this.m,"scroll",this.j,be))}D(){const a=Pu(this);if(a&&!this.v){{var b={rr:"vis-bcr"};const c=this.A.contentWindow;c&&(Ii(c,"ig",b,"*",2),10<=++this.C&&this.j&&ee(this.m,"scroll",this.j,be))}}this.v=a}};const Ru={display:"block",left:"auto",position:"fixed",bottom:"0px"};function Su(a,b){const c=a.pubWin.document.getElementById(a.B.google_async_iframe_id+"_anchor");return c?new Tu(a,b,c):null} +function Uu(a,b){if(!a.ba)return"1";b=We(b.r_nh);a.o=null==b?0:b;if(0>=a.o)return"2";a.v=Bg(a.A).y;b=a.j.innerHeight;if(a.v+a.Xwk(a.j)-b)return"3";a.A&&(a.A.setAttribute("height",a.o),a.A.style.height=a.o+"px");a.C.setAttribute("height",a.o);a.C.style.height=a.o+"px";vg(a.m,Ru);a.m.style.height=a.o+"px";a.D.style.position="relative";a.aa();return"0"}function Vu(a,b={}){a.H&&(b.eid=a.H);b.qid=a.I;Y("pscrl",b,Kf(String(a.J),.05))} +class Tu extends hu{constructor(a,b,c){a.j&&super(a.j);this.C=b;this.A=(this.F=a.iframeWin&&Og(a.B)?a.iframeWin.frameElement:b)?this.F:a.o;this.m=c;this.D=this.m.parentElement;this.X=parseInt(this.m.style.height,10);this.H=null;this.W=!1;this.I="";this.o=0;this.v=Bg(this.A).y;this.J=null;this.ba=q.requestAnimationFrame||q.webkitRequestAnimationFrame||q.mozRequestAnimationFrame||q.oRequestAnimationFrame||q.msRequestAnimationFrame;this.aa=W(636,()=>{this.ba.call(this.j,this.aa);var d=this.j.innerHeight, +e=Ak(this.j);this.v=Bg(this.D).y;e+d>this.v?(e=e+d-this.v,d=Math.min(e,this.X),e=this.o-e,e=Math.max(0,e),0>=e?vg(this.m,{position:"absolute",top:"0px",bottom:"auto"}):vg(this.m,{position:"fixed",top:"auto",bottom:"0px"}),vg(this.m,{clip:"rect("+e+"px, "+this.C.width+"px, "+(e+d)+"px, 0px)"})):vg(this.m,{clip:"rect(3000px, "+this.C.width+"px, 0px, 0px)"})})}N(a){a["parallax-scroll"]=this.ha}ha(a,b){a=Ck(a);this.H=a.i_expid;this.I=a.qid;this.J=a.gen204_fraction;!this.W&&$g(b,this.C)&&(this.W=!0,a= +Uu(this,a),b.source.postMessage(JSON.stringify({["msg_type"]:"parallax-scroll-result",["ps_success"]:"0"===a,googMsgType:"sth"}),"*"),Vu(this,{err:a}))}l(){this.D=this.m=this.A=this.F=null;super.l()}};function Wu(a,b){b=b&&b[0];if(!b)return null;b=b.target;const c=b.getBoundingClientRect(),d=Qd(a.j.K()||window);if(0>=c.bottom||c.bottom>d.height||0>=c.right||c.left>=d.width)return null;var e=Xu(a,b,c,a.j.j.elementsFromPoint(Ed(c.left+c.width/2,c.left,c.right-1),Ed(c.bottom-1-a.l,c.top,c.bottom-1)),1,[]),f=Xu(a,b,c,a.j.j.elementsFromPoint(Ed(c.left+c.width/2,c.left,c.right-1),Ed(c.top+a.l,c.top,c.bottom-1)),2,e.ca),g=Xu(a,b,c,a.j.j.elementsFromPoint(Ed(c.left+a.l,c.left,c.right-1),Ed(c.top+c.height/ +2,c.top,c.bottom-1)),3,[...e.ca,...f.ca]);const h=Xu(a,b,c,a.j.j.elementsFromPoint(Ed(c.right-1-a.l,c.left,c.right-1),Ed(c.top+c.height/2,c.top,c.bottom-1)),4,[...e.ca,...f.ca,...g.ca]);var k=Yu(a,b,c),l=p=>Ma(a.o,p.overlapType)&&Ma(a.v,p.overlapDepth)&&Ma(a.m,p.overlapDetectionPoint);e=Ha([...e.entries,...f.entries,...g.entries,...h.entries],l);l=Ha(k,l);k=[...e,...l];f=c.left<-a.l||c.right>d.width+a.l;f=0new kg(p.elementRect.left, +p.elementRect.top,p.elementRect.width,p.elementRect.height)),...Sa(Ia(l,p=>mg(m,p.elementRect))),...Ha(mg(m,new kg(0,0,d.width,d.height)),p=>0<=p.top&&p.top+p.height<=d.height)];return{entries:k,isOverlappingOrOutsideViewport:f,scrollPosition:{scrollX:g.x,scrollY:g.y},target:b,targetRect:c,viewportSize:{width:d.width,height:d.height},overlappedArea:20>e.length?Zu(m,e):$u(c,e)}} +function av(a,b){const c=a.j.K(),d=a.j.j;return new Promise((e,f)=>{const g=c.IntersectionObserver;if(g)if(d.elementsFromPoint)if(d.createNodeIterator)if(d.createRange)if(c.Range.prototype.getBoundingClientRect){var h=new g(k=>{const l=new ki(1),m=ji(l,()=>Wu(a,k));m&&(l.l.length&&(m.executionTime=Math.round(Number(l.l[0].duration))),h.disconnect(),e(m))},bv);h.observe(b)}else f(Error("5"));else f(Error("4"));else f(Error("3"));else f(Error("2"));else f(Error("1"))})} +function Xu(a,b,c,d,e,f){if(0===c.width||0===c.height)return{entries:[],ca:[]};const g=[],h=[];for(let p=0;pf.bottom+a.l?d.push(cv(a,c,b,f,5,1)):(e="auto"===e.overflowX||"scroll"===e.overflowX,!e&&c.leftf.right+a.l&&d.push(cv(a,c,b,f,5,4))))}}return d} +function Zu(a,b){if(0===a.width||0===a.height||0===b.length)return 0;let c=0;for(let d=1;d<1<=b[f].left&&d<=b[f].left+b[f].width&&e>=b[f].top&&e<=b[f].top+b[f].height){c++;break}return c/((a.width+1)*(a.height+1))} +function cv(a,b,c,d,e,f,g){const h={element:c,elementRect:d,overlapType:e,overlapDetectionPoint:f};if(Ma(a.o,e)&&Ma(a.m,f)){b=new ig(b.top,b.right-1,b.bottom-1,b.left);if((a=gv(a,c))&&jg(b,a))c=4;else{a=hv(c,d);if(Wc){e=Dg(c,"paddingLeft");f=Dg(c,"paddingRight");var k=Dg(c,"paddingTop"),l=Dg(c,"paddingBottom");e=new ig(k,f,l,e)}else e=yg(c,"paddingLeft"),f=yg(c,"paddingRight"),k=yg(c,"paddingTop"),l=yg(c,"paddingBottom"),e=new ig(parseFloat(k),parseFloat(f),parseFloat(l),parseFloat(e));a=new ig(a.top+ +e.top,a.right-e.right,a.bottom-e.bottom,a.left+e.left);jg(b,a)?c=3:(c=hv(c,d),c=jg(b,c)?2:1)}h.overlapDepth=c}g&&(h.suspectAncestor=g);return h} +function dv(a,b,c,d){const e=[];for(var f=b;f&&f!==c;f=f.parentElement)e.unshift(f);c=a.j.K();for(f=0;fg.bottom+a.l&&"visible"===h.overflowY)return f}return null} +function gv(a,b){var c=a.j.j;a=c.createRange();if(!a)return null;c=c.createNodeIterator(b,NodeFilter.SHOW_TEXT,{acceptNode:d=>/^[\s\xa0]*$/.test(d.nodeValue)?NodeFilter.FILTER_SKIP:NodeFilter.FILTER_ACCEPT});for(b=c.nextNode();c.nextNode(););c=c.previousNode();if(!b||!c)return null;a.setStartBefore(b);a.setEndAfter(c);a=a.getBoundingClientRect();return 0===a.width||0===a.height?null:new ig(a.top,a.right,a.bottom,a.left)} +function hv(a,b){if(!Wc||9<=Number(jd)){var c=yg(a,"borderLeftWidth");d=yg(a,"borderRightWidth");e=yg(a,"borderTopWidth");a=yg(a,"borderBottomWidth");c=new ig(parseFloat(e),parseFloat(d),parseFloat(a),parseFloat(c))}else{c=Fg(a,"borderLeft");var d=Fg(a,"borderRight"),e=Fg(a,"borderTop");a=Fg(a,"borderBottom");c=new ig(e,d,a,c)}return new ig(b.top+c.top,b.right-1-c.right,b.bottom-1-c.bottom,b.left+c.left)} +class jv{constructor(a,b=kv,c=lv,d=mv,e=0){this.j=Nd(a);this.o=b;this.v=c;this.m=d;this.l=e}}const ev={[1]:3,[4]:10,[3]:12,[2]:4,[5]:5},fv={[1]:6,[4]:11,[3]:13,[2]:7,[5]:8},kv=Ha(Re({mf:1,nf:2,Zg:3,$g:4,bh:5,hf:6,jf:7,lf:8,lg:9,ah:10,kf:11,Yg:12,gf:13}),a=>!Ma([1,2],a)),lv=Re({we:1,mg:2,Je:3,eh:4}),mv=Re({xe:1,hh:2,ag:3,Mg:4}),bv={threshold:[0,.25,.5,.75,.95,.96,.97,.98,.99,1]};function nv(a,b){Array.isArray(b)||(b=[b]);b=Ia(b,function(c){return"string"===typeof c?c:c.tb+" "+c.duration+"s "+c.timing+" "+c.delay+"s"});vg(a,"transition",b.join(","))} +var ov=Ya(function(){if(Wc)return gd("10.0");var a=Td(document,"DIV"),b=$c?"-webkit":Zc?"-moz":Wc?"-ms":Vc?"-o":null,c={transition:"opacity 1s linear"};b&&(c[b+"-transition"]="opacity 1s linear");b={style:c};if(!xc.test("div"))throw Error("");if("DIV"in zc)throw Error("");c=null;var d="";if(b)for(l in b){if(!xc.test(l))throw Error("");var e=b[l];if(null!=e){var f=l;var g=e;if(g instanceof mb)g=pb(g);else if("style"==f.toLowerCase()){e=void 0;if(!ra(g))throw Error("");if(!(g instanceof Vb)){var h= +"";for(e in g){if(!/^[-_a-zA-Z0-9]+$/.test(e))throw Error("Name allows only [-_a-zA-Z0-9], got: "+e);var k=g[e];null!=k&&(k=Array.isArray(k)?Ia(k,Zb).join(" "):Zb(k),h+=e+":"+k+";")}g=h?Xb(h):Yb}g instanceof Vb&&g.constructor===Vb&&g.m===Wb?e=g.l:(oa(g),e="type_error:SafeStyle");g=e}else{if(/^on/i.test(f))throw Error("");if(f.toLowerCase()in yc)if(g instanceof qb)g=tb(g).toString();else if(g instanceof Kb)g=Pb(g);else if("string"===typeof g)g=Tb(g).j();else throw Error("");}g.Z&&(g=g.j());f=f+'="'+ +yb(String(g))+'"';d+=" "+f}}var l="":(c=Cc(d),l+=">"+uc(c).toString()+"",c=c.l());(b=b&&b.dir)&&(/^(ltr|rtl|auto)$/i.test(b)?c=0:c=null);b=Dc(l,c);Fc(a,b);a=a.firstChild;b=a.style[Pc("transition")];return""!=("undefined"!==typeof b?b:a.style[wg(a,"transition")]||"")});function pv(a,b,c){0>a.l[b].indexOf(c)&&(a.l[b]+=c)}function qv(a,b){0<=a.j.indexOf(b)||(a.j=b+a.j)}function rv(a,b){0>a.m.indexOf(b)&&(a.m=b+a.m)}function sv(a,b,c,d){return""!=a.m||b?null:""==a.j.replace(tv,"")?null!=c&&a.l[0]||null!=d&&a.l[1]?!1:!0:!1}function uv(a){var b=sv(a,"",null,0);if(null===b)return"XS";b=b?"C":"N";a=a.j;return 0<=a.indexOf("a")?b+"A":0<=a.indexOf("f")?b+"F":b+"S"} +var vv=class{constructor(a,b){this.l=["",""];this.j=a||"";this.m=b||""}toString(){return[this.l[0],this.l[1],this.j,this.m].join("|")}}; +function wv(a){let b=a.V;a.H=function(){};xv(a,a.D,b);let c=a.D.parentElement;if(!c)return a.j;let d=!0,e=null;for(;c;){try{e=/^head|html$/i.test(c.nodeName)?null:Je(c,b)}catch(g){rv(a.j,"c")}const f=yv(a,b,c,e);c.classList.contains("adsbygoogle")&&e&&(/^\-.*/.test(e["margin-left"])||/^\-.*/.test(e["margin-right"]))&&(a.T=!0);if(d&&!f&&zv(e)){qv(a.j,"l");a.I=c;break}d=d&&f;if(e&&Av(a,e))break;c=c.parentElement;if(!c){if(b===a.ba)break;try{if(c=b.frameElement,b=b.parent,!Ee(b)){qv(a.j,"c");break}}catch(g){qv(a.j, +"c");break}}}a.F&&a.o&&Bv(a);return a.j} +function Cv(a){function b(){Dv(c,f,g);if(h&&!k&&!g){const l=function(m){for(let p=0;pa.C)?a.m:null,e=null!=a.A&&null!=a.l&&(a.W||a.l>a.A)?a.l:null;if(a.J){const l=a.J.length; +for(let m=0;m=B||null!==g&&a.C>=g);t=null!==a.A&&(null!==t&&a.A>=t||null!==k&&a.A>=k);k=!m&&zv(d);t=m||t||k||!(f||p||d&&(!Jv(String(d.minWidth))||!Kv(String(d.maxWidth)))); +l=m||g||k||l||!(h||y||d&&(!Jv(String(d.minHeight))||!Kv(String(d.maxHeight))));Lv(a,0,t,c,"width",f,a.C,a.m);Mv(a,0,"d",t,e,d,"width",p,a.C,a.m);Mv(a,0,"m",t,e,d,"minWidth",e&&e.minWidth,a.C,a.m);Mv(a,0,"M",t,e,d,"maxWidth",e&&e.maxWidth,a.C,a.m);if(a.ha){c=/^html|body$/i.test(c.nodeName);r=Ye(r);h=d?"auto"===d.overflowY||"scroll"===d.overflowY:!1;(f=null!=a.l&&d&&r&&Math.round(r)!==a.l)&&!(f=!h)&&(f=r,f=(T.G().j(260,!1)||b.location&&"#gffwroe2ettq"==b.location.hash)&&Math.round(f)<.8*Math.round(b.innerHeight)); +f=f&&"100%"!==d.minHeight;if(c=a.o&&!c&&f)c=!(a.Ga&&d&&(T.G().j(265,!1)||b.location&&"#gffwroe2etoq"==b.location.hash)&&Math.round(Ye(d.minHeight))===Math.round(b.innerHeight));c&&(e.setProperty("height","auto","important"),d&&!Jv(String(d.minHeight))&&e.setProperty("min-height","0px","important"),d&&!Kv(String(d.maxHeight))&&a.l&&Math.round(r)a.v.boundingClientRect.left?2:0)|(c.bottom>a.v.boundingClientRect.top?4:0)}}return 1}return 0} +function Lv(a,b,c,d,e,f,g,h){if(null!=h){if("string"==typeof f){if("100%"==f||!f)return;f=We(f);null==f&&(rv(a.j,"n"),pv(a.j,b,"d"))}if(null!=f)if(c){if(a.o)if(a.F){const k=Math.max(f+h-(g||0),0),l=a.H;a.H=function(m,p){m==b&&d.setAttribute(e,k-p);l&&l(m,p)}}else d.setAttribute(e,h)}else pv(a.j,b,"d")}} +function Mv(a,b,c,d,e,f,g,h,k,l){if(null!=l){f=f&&f[g];"string"!=typeof f||("m"==c?Jv(f):Kv(f))||(f=Ye(f),null==f?qv(a.j,"p"):null!=k&&qv(a.j,f==k?"E":"e"));if("string"==typeof h){if("m"==c?Jv(h):Kv(h))return;h=Ye(h);null==h&&(rv(a.j,"p"),pv(a.j,b,c))}if(null!=h)if(d&&e){if(a.o)if(a.F){const m=Math.max(h+l-(k||0),0),p=a.H;a.H=function(r,B){r==b&&(e[g]=m-B+"px");p&&p(r,B)}}else e[g]=l+"px"}else pv(a.j,b,c)}} +var Rv=class{constructor(a,b,c,d,e,f,g){this.ba=a;this.J=c;this.D=b;this.V=(a=this.D.ownerDocument)&&(a.defaultView||a.parentWindow);this.v=new Nv(this.D);this.o=g;this.Fa=Ov(this.v,d.zb,d.height,d.ic);this.C=this.o?this.v.boundingClientRect?this.v.boundingClientRect.right-this.v.boundingClientRect.left:null:e;this.A=this.o?this.v.boundingClientRect?this.v.boundingClientRect.bottom-this.v.boundingClientRect.top:null:f;this.m=Pv(d.width);this.l=Pv(d.height);this.N=this.o?Pv(d.opacity):null;this.$= +d.check;this.F="animate"==d.zb&&!Qv(this.v,this.l,this.X)&&ov();this.aa=!!d.Hb;this.j=new vv;Qv(this.v,this.l,this.X)&&qv(this.j,"r");e=this.v;e.j&&e.l>=e.m&&qv(this.j,"b");this.I=this.H=null;this.T=!1;this.W=!!d.xd;this.ha=!!d.ec;this.X=!!d.ic;this.Ga=d.Fb}};function Qv(a,b,c){var d;(d=a.j)&&!(d=!a.o)&&(c?(b=a.l+Math.min(b,Pv(a.gb())),a=a.j&&b>=a.m):a=a.j&&a.l>=a.m,d=a);return d} +var Nv=class{constructor(a){var b=a&&a.ownerDocument,c=b&&(b.defaultView||b.parentWindow),d;if(d=c)d=Ee(c.top)?c.top:null;c=d;this.j=!!c;this.boundingClientRect=null;if(a)try{this.boundingClientRect=a.getBoundingClientRect()}catch(f){}var e;{d=a;let f=0,g=this.boundingClientRect;for(;d;)try{g&&(f+=g.top);const h=(e=d.ownerDocument)&&(e.defaultView||e.parentWindow);(d=h&&h.frameElement)&&(g=d.getBoundingClientRect())}catch(h){break}e=f}this.l=e;c=c||q;this.m=("CSS1Compat"==c.document.compatMode?c.document.documentElement: +c.document.body).clientHeight;b=b&&Wj(b);this.o=!!a&&!(2==b||3==b)&&!(this.boundingClientRect&&this.boundingClientRect.top>=this.boundingClientRect.bottom&&this.boundingClientRect.left>=this.boundingClientRect.right)}isVisible(){return this.o}Pa(){return this.boundingClientRect?this.boundingClientRect.right-this.boundingClientRect.left:null}gb(){return this.boundingClientRect?this.boundingClientRect.bottom-this.boundingClientRect.top:null}}; +function Ov(a,b,c,d){switch(b){case "no_rsz":return!1;case "force":case "animate":return!0;default:return Qv(a,c,d)}}function zv(a){return!!a&&/^left|right$/.test(a.cssFloat||a.styleFloat)}function Sv(a,b,c,d){return Hv(new Rv(a,b,d,c,null,null,!0))}var Tv=new vv("s",""),tv=/[lonvafrbpEe]/g;function Kv(a){return!a||/^(auto|none|100%)$/.test(a)}function Jv(a){return!a||/^(0px|auto|none|0%)$/.test(a)} +function Dv(a,b,c){null!==b&&null!==We(a.getAttribute("width"))&&a.setAttribute("width",b);null!==c&&null!==We(a.getAttribute("height"))&&a.setAttribute("height",c);null!==b&&(a.style.width=b+"px");null!==c&&(a.style.height=c+"px")}var Ev="margin-left margin-right padding-left padding-right border-left-width border-right-width".split(" "),Fv="margin-top margin-bottom padding-top padding-bottom border-top-width border-bottom-width".split(" "),Uv; +{let a="opacity 1s cubic-bezier(.4, 0, 1, 1), width .2s cubic-bezier(.4, 0, 1, 1), height .3s cubic-bezier(.4, 0, 1, 1) .2s",b=Ev;for(let c=0;cMa([248427477,248427478],t))&&a.j===m&&av(new jv(a.j,[5,8,9],[3,4],void 0,2),B).then(t=>{Vj(8,[t]);return t}).then(t=>{Y("resize-ovlp",{adf:a.v,eid:a.F.join(","),io:Number(t.isOverlappingOrOutsideViewport),oa:t.overlappedArea.toFixed(2),qid:l.qid||"",slot:a.I,url:a.J,vp:t.viewportSize.width+"x"+t.viewportSize.height},1)}).catch(t=>{Y("resize-ovlp-err",{err:t.message},1)});return!0}l.err="1";Wv(a,l, +p);return!1}function Xv(a,b,c){const d={scrl:Ak(a.j||u()),adk:a.D,adf:a.v,fmt:a.C};b&&(d.str=Qv(b,We(c.r_nh),Xe(c.r_cab)),d.ad_y=b.l,d.vph=b.m);U(c,(e,f)=>{d[f]=e});return d}function Wv(a,b,c){const d=Kf(String(b.gen204_fraction),.05);b=Xv(a,c,b);b.url=a.j.document.URL;Y("resize",b,d)} +class Yv extends hu{constructor(a,b,c,d){super(a);this.m=b;this.o=c;this.D=String(d.google_ad_unit_key||"");this.v=String(d.google_ad_dom_fingerprint||"");this.C=String(d.google_ad_format||"");this.F=ah(d).eids||[];this.I=String(d.google_ad_slot||"");this.J=String(d.google_page_url||"")}N(a){a["ablate-me"]=this.A;a["resize-me"]=this.H}A(a,b){zk(b,this.m.contentWindow)&&(a=Ck(a),b=a.clp_btf_only,Vv(this,null,null,0,0,"animate"===a["collapse-after-close"]?"animate":"1"===b?"safe":"force",!1,!1,!1,a))}H(a, +b){if(zk(b,this.m.contentWindow)){a=Ck(a);var c=a.r_chk;if(null==c||""===c){var d=We(a.r_nw),e=We(a.r_nh),f=We(a.r_no);null!=f||0!==d&&0!==e||(f=0);var g=a.r_str;g=g?g:null;d=Vv(this,c,d,e,f,g,Xe(a.r_ao),Xe(a.r_ifr),Xe(a.r_cab),a);c={msg_type:"resize-result"};c.r_str=g;c.r_status=d;b=b.source;c.googMsgType="sth";b.postMessage(JSON.stringify(c),"*");this.m.dataset.googleQueryId||this.m.setAttribute("data-google-query-id",a.qid)}}}l(){super.l();this.m=null}};const Zv=(a,b,c)=>new a.IntersectionObserver(c,b),$v=(a,b,c)=>{R(a,b,c);return()=>ee(a,b,c)};let aw=null;const bw=()=>{aw=ai()},cw=(a,b)=>b?null===aw?(R(a,"mousemove",bw,{passive:!0}),R(a,"scroll",bw,{passive:!0}),aw=ai(),!1):ai()-aw>=1E3*b:!1; +function dw({win:a,element:b,Cd:c,Bd:d,Ad:e=0,Rc:f,Vc:g,options:h={},vh:k=Zv}){let l=null,m=!1,p=!1;const r=[],B=k(a,h,(y,t)=>{try{const E=()=>{r.length||(d&&(r.push($v(b,"mouseenter",()=>{m=!0;E()})),r.push($v(b,"mouseleave",()=>{m=!1;E()}))),r.push($v(a.document,"visibilitychange",()=>E())));const K=cw(a,e);!p||m||K||Yj(a.document)?(a.clearTimeout(l),l=null):l=l||a.setTimeout(()=>{cw(a,e)?E():(f(),t.disconnect())},1E3*c)};({isIntersecting:p}=y[y.length-1]);E()}catch(E){g&&g(E)}});B.observe(b);return()=> +{B.disconnect();for(const y of r)y();null!=l&&a.clearTimeout(l)}};function ew(a,b,c,d,e){return new fw(a,b,c,d,e)}function gw(a,b,c){const d=a.v,e=a.C;if(null!=e&&null!=d&&zk(c,d.contentWindow)&&(b=b.config,"string"===typeof b)){try{var f=JSON.parse(b);if(!pa(f))return;a.m=new ne(f)}catch(g){return}a.Ma();f=sd(a.m,1,30);0>=f||(f-=.2,a.o=dw({win:a.j,element:e,Bd:!Ae(),Ad:sd(a.m,3,90),Cd:f,Rc:()=>void hw(a,e),options:{threshold:ud(a.m,2,1)},Vc:g=>ri.j(623,g,void 0,void 0)}))}} +function hw(a,b){a.D(!!rd(a.m,4));setTimeout(W(624,()=>{a.A.google_refresh_count=(parseInt(a.A.google_refresh_count,10)||0)+1;var c;a:{if(Dd&&!(Wc&&gd("9")&&!gd("10")&&q.SVGElement&&b instanceof q.SVGElement)&&(c=b.parentElement))break a;c=b.parentNode;c=ra(c)&&1==c.nodeType?c:null}c&&Rg.test(c.className)||(c=Td(document,"INS"),c.className="adsbygoogle",b.parentNode&&b.parentNode.insertBefore(c,b.nextSibling));b&&b.parentNode&&b.parentNode.removeChild(b);a.v=null;qr(c,a.A,a.j)}),200)} +class fw extends hu{constructor(a,b,c,d,e){super(a);this.v=b;this.C=d;this.A=c;this.D=e;this.m=this.o=null;(b=(b=b.contentWindow)&&b.parent)&&a!=b&&this.V.push(Ci(b,"sth",this.Cb,this.Eb))}N(a){a.av_ref=(b,c)=>gw(this,b,c)}l(){super.l();this.C=this.v=null;this.o&&this.o()}};let iw=navigator;var jw=()=>{try{return iw.javaEnabled()}catch(a){return!1}},kw=a=>{let b=1;let c;if(void 0!=a&&""!=a)for(b=0,c=a.length-1;0<=c;c--){var d=a.charCodeAt(c);b=(b<<6&268435455)+d+(d<<14);d=b&266338304;b=0!=d?b^d>>21:b}return b},lw=(a,b)=>{if(!a||"none"==a)return 1;a=String(a);"auto"==a&&(a=b,"www."==a.substring(0,4)&&(a=a.substring(4,a.length)));return kw(a.toLowerCase())};const mw=/^\s*_ga=\s*1\.(\d+)[^.]*\.(.*?)\s*$/,nw=/^[^=]+=\s*GA1\.(\d+)[^.]*\.(.*?)\s*$/,ow=/^\s*_ga=\s*()(amp-[\w.-]{22,64})$/;const pw=/^blogger$/,qw=/^wordpress(.|\s|$)/i,rw=/^joomla!/i,sw=/^drupal/i,tw=/\/wp-content\//,uw=/\/wp-content\/plugins\/advanced-ads/,vw=/\/wp-content\/themes\/genesis/,ww=/\/wp-content\/plugins\/genesis/; +var xw=a=>{var b=a.getElementsByTagName("script"),c=b.length;for(var d=0;dc?b+2**d:b,0));return a.j}class zw{constructor(){this.l=[];this.j=-1}set(a,b=!0){0<=a&&52>a&&0===a%1&&this.l[a]!=b&&(this.l[a]=b,this.j=-1)}get(a){return!!this.l[a]}};const Aw=/[+, ]/; +var Gw=(a,b)=>{const c=a.B;{var d=u().document;const L={},w=u();{const v={};v.nc=Xi(u(),!1).win;v.Dd=pk(v.nc);v.Ub=nk(u(),d,c.google_ad_width,c.google_ad_height);{var e=v.Ub,f=v.Dd.nb;const F=u(),C=F.top==F?0:Ee(F.top)?1:2;let P=4;e||1!=C?e||2!=C?e&&1==C?P=7:e&&2==C&&(P=8):P=6:P=5;f&&(P|=16);var g=""+P}v.Zc=g;v.Ob=qk();var h=v}const H=h.nc,x=h.Ub;let J=!!c.google_page_url;L.google_iframing=h.Zc;0!=h.Ob&&(L.google_iframing_environment=h.Ob);if(!J&&"ad.yieldmanager.com"==d.domain){let v=d.URL.substring(d.URL.lastIndexOf("http")); +for(;-1Fh.length;)v[gf].src&&Fh.unshift(v[gf].src),gf--;var bo=qh(ff,Fh)}else bo=0}G.icsg=bo;const J=x.l[0].depth;J&&0w?w:null}kx.pem=lo;{var ba=L;const w=a.B,H=a.pubWin,x=a.j,J=Yi();ba.ref=w.google_referrer_url;ba.loc=w.google_page_location;{const I=og(H);if(I&&ra(I.data)&&"string"===typeof I.data.type){var Gh=I.data.type.toLowerCase();var mo="doubleclick"==Gh||"adsense"==Gh?null:Gh}else mo=null}const v=mo;v&&(ba.apn=v.substr(0,10));const F=pk(J);var Hh=F;ba.url||ba.loc||!Hh.url||(ba.url=Hh.url,Hh.nb||(ba.usrc=1));F.url!=(ba.loc||ba.url)&&(ba.top=F.url);w.google_async_rrc&&(ba.rr=w.google_async_rrc); +ba.rx=0;{if(fu&&au(fu))var no=fu;else{var Ih=Yi(),oo=Ih.google_jobrunner;no=bu(oo)?fu=oo:Ih.google_jobrunner=fu=new du(Ih)}const I=no;var po=Gg(I.tc)?I.tc():null}po&&(ba.jtc=po);0<=a.v&&(ba.eae=a.v);let C=null;try{C=x&&x.localStorage}catch(I){}const P=ir(w,x,C);P&&(ba.fc=P);if(!Wg(w)){var Id=(a.iframeWin||a.pubWin).document,qo="";if(Id.documentMode){var ec=ae(new Od(Id),"IFRAME");ec.frameBorder="0";ec.style.height=0;ec.style.width=0;ec.style.position="absolute";if(Id.body){Id.body.appendChild(ec); +try{var kf=ec.contentWindow.document;kf.open();kf.write("");kf.close();qo+=kf.documentMode}catch(I){}Id.body.removeChild(ec)}}ba.docm=qo}{let I,X,ua,ha,ka,jb;try{I=H.screenX,X=H.screenY}catch(Ob){}try{ua=H.outerWidth,ha=H.outerHeight}catch(Ob){}try{ka=H.innerWidth,jb=H.innerHeight}catch(Ob){}var lx=[H.screenLeft,H.screenTop,I,X,H.screen?H.screen.availWidth:void 0,H.screen?H.screen.availTop:void 0,ua,ha,ka,jb]}ba.brdim=lx.join();{var ro=H;{const X=sj.pa;var mx=Zh(qj(),67)===X}let I= +0;void 0===q.postMessage&&(I|=1);if(mx){{const X=og(ro);var nx=!(!X||!X.observeIntersection)}nx&&(I|=256);{const X=ro.document;var ox=X&&qa(X.elementFromPoint)}ox&&(I|=1024)}var so=I}0=++jb&&50>Date.now()-Ob&&(ka=Dw(ka));)1===ka.nodeType&&ha.push(ka);var lf=ha}b:{for(let ha=0;haDate.now()-ha;Ob++){const mf=lf[Ob];if(!ka.test(mf.tagName)&&jb.test(mf.style.position||zg(mf))){var Mh=mf;break b}}Mh=null}break a}}}catch(ua){}Mh=null}const X=Mh;X&&X.offsetWidth*X.offsetHeight<=4*Lh.width*Lh.height&&(I=1);ba.pfx=I}}if("26835106"===Zh(qj(),41)&&x){try{const X=x.document.getElementsByTagName("head")[0]; +var zo=X?xw(X):0}catch(X){zo=0}const I=zo;0!==I&&(ba.cms=I)}w.google_lrv!==Nf()&&(ba.alvm=w.google_lrv||"none")}L.fu=a.l;{const w=new zw;q.SVGElement&&q.document.createElementNS&&w.set(0);const H=pf();H["allow-top-navigation-by-user-activation"]&&w.set(1);H["allow-popups-to-escape-sandbox"]&&w.set(2);q.crypto&&q.crypto.subtle&&w.set(3);q.TextDecoder&&q.TextEncoder&&w.set(4);var rx=yw(w)}L.bc=rx;xu();L.jar=uu[4];var Bb=L;if(Qf){if(Qf){const w=Wh();w&&(Bb.debug_experiment_id=w)}Bb.creatives=Ew(/\b(?:creatives)=([\d,]+)/); +Bb.adgroups=Ew(/\b(?:adgroups)=([\d,]+)/);Bb.adgroups&&(Bb.adtest="on",Bb.disable_budget_throttling=!0,Bb.use_budget_filtering=!1,Bb.retrieve_only=!0,Bb.disable_fcap=!0)}Uj()&&(L.atl=!0);var sx=L}{const L=a.B,w=L.google_ad_channel;let H="/pagead/ads?";"ca-pub-6219811747049371"===L.google_ad_client&&Fw.test(w)&&(H="/pagead/lopri?");var ux=H}let Nh=Qj(ma,ux);3===Wj(a.pubWin.document)&&(a.A=!0,a.F=Nh,Nh=Qj(ma,"/pagead/blank.gif#?"));const vx=Jg(sx,Nh+(Qf&&c.google_debug_params?c.google_debug_params: +""));return c.google_ad_url=vx},Dw=a=>{try{if(a.parentNode)return a.parentNode}catch(c){return null}if(9===a.nodeType)a:{try{const c=Sd(a);if(c){const d=c.frameElement;if(d&&Ee(c.parent)){var b=d;break a}}}catch(c){}b=null}else b=null;return b};const Ew=a=>{try{const b=q.top.location.hash;if(b){const c=b.match(a);return c&&c[1]||""}}catch(b){}return""}; +var Cw=(a,b)=>{const c=fj(b,8,{});b=fj(b,9,{});const d=a.google_ad_section,e=a.google_ad_format;a=a.google_ad_slot;e?c[d]=c[d]?c[d]+`,${e}`:e:a&&(b[d]=b[d]?b[d]+`,${a}`:a)};const Hw=(a,b)=>{const c=a.C;c&&(c.wd&&(b.npa=1),c.Sb&&(b.guci=c.Sb),c.Fd&&(b.gdpr_consent=c.Fd,c.Yc&&(b.addtl_consent=c.Yc)));a.I&&(b.us_privacy=a.I);a.tcString&&(b.gdpr_consent=a.tcString);void 0!=a.gdprApplies&&(b.gdpr=a.gdprApplies?"1":"0");a.addtlConsent&&(b.addtl_consent=a.addtlConsent)}; +var Bw=(a,b)=>{const c=a.B;U(dh,(d,e)=>{b[d]=c[e]});Hw(a,b);U(ch,(d,e)=>{b[d]=c[e]});U(eh,(d,e)=>{b[d]=c[e]});Fk(c)&&(a=Ek(c),b.fa=a)};const Fw=/YtLoPri/;var Iw=(a=q)=>a.ggeac||(a.ggeac={});class Jw{constructor(){}}na(Jw);var Kw=(a=Iw())=>{ij(jj.G(),a);gg(T.G(),a);Jw.G();T.G().l()};function Lw(a){if(a.j)return a.j;a.j=rf(a.m,"__uspapiLocator");return a.j}function Mw(a){return qa(a.m.__uspapi)||null!=Lw(a)}function Nw(a,b){if(qa(a.m.__uspapi))a=a.m.__uspapi,a("getUSPData",1,b);else if(Lw(a)){Ow(a);const c=++a.A;a.v[c]=b;a.j&&a.j.postMessage({["__uspapiCall"]:{command:"getUSPData",version:1,callId:c}},"*")}}function Pw(a,b){let c={};if(Mw(a)){var d=Za(()=>b(c));Nw(a,(e,f)=>{f&&(c=e);d()});setTimeout(d,a.C)}else b(c)} +function Ow(a){a.o||(a.o=b=>{try{{let d;"string"===typeof b.data?d=JSON.parse(b.data):d=b.data;var c=d.__uspapiReturn}a.v[c.callId](c.returnValue,c.success)}catch(d){}},R(a.m,"message",a.o))}class Qw extends Zf{constructor(a,b=500){super();this.m=a;this.j=null;this.v={};this.A=0;this.C=b;this.o=null}l(){this.v={};this.o&&(ee(this.m,"message",this.o),delete this.o);delete this.v;delete this.m;delete this.j;super.l()}};function Rw(a){if(a.j)return a.j;a.j=rf(a.m,"__tcfapiLocator");return a.j}function Sw(a){return qa(a.m.__tcfapi)||null!=Rw(a)}function Tw(a,b,c,d){if(qa(a.m.__tcfapi))a=a.m.__tcfapi,a(b,2,c,d);else if(Rw(a)){Uw(a);const e=++a.A;a.v[e]=c;a.j&&a.j.postMessage({["__tcfapiCall"]:{command:b,version:2,callId:e,parameter:d}},"*")}} +function Vw(a,b){let c={};const d=Za(()=>b(c));Tw(a,"addEventListener",(e,f)=>{f&&(c=e);e=void 0!==c.tcString&&"string"!==typeof c.tcString||void 0!==c.gdprApplies&&"boolean"!==typeof c.gdprApplies||void 0!==c.listenerId&&"number"!==typeof c.listenerId||void 0!==c.addtlConsent&&"string"!==typeof c.addtlConsent||!c.cmpStatus||"error"===c.cmpStatus?!1:!0;e&&("loaded"!==c.cmpStatus||"tcloaded"!==c.eventStatus&&"useractioncomplete"!==c.eventStatus)||(e||(c.tcString="tcunavailable"),Tw(a,"removeEventListener", +()=>{},c.listenerId),d())})}function Uw(a){a.o||(a.o=b=>{try{{let d;"string"===typeof b.data?d=JSON.parse(b.data):d=b.data;var c=d.__tcfapiReturn}a.v[c.callId](c.returnValue,c.success)}catch(d){}},R(a.m,"message",a.o))}class Ww extends Zf{constructor(a){super();this.m=a;this.j=null;this.v={};this.A=0;this.o=null}l(){this.v={};this.o&&(ee(this.m,"message",this.o),delete this.o);delete this.v;delete this.m;delete this.j;super.l()}};function qx(a){var b=Nf();if(T.G().j(215,!1)&&!a.goog_sdr_l){Object.defineProperty(a,"goog_sdr_l",{value:!0});var c=()=>{const d=hg(37),e=()=>{var f=String(Bf(a));try{var g=new ke("gda",b,"pt");g.ya=f;g.win=a;ie(new je(g))}catch(h){}};d?a.setTimeout(e,d):e()};"complete"===a.document.readyState?c():R(a,"load",c)}};let tx=void 0;class wx extends Zf{constructor(){super()}l(){super.l()}};var yx=a=>{const b=a.iframeWin,c=a.vars;b&&(c.google_iframe_start_time=b.google_iframe_start_time);const d=new Jf(Yg(a.pubWin),a.pubWin,b,c);d.N=Date.now();Vj(1,[d.B]);a=yi(159,()=>xx(d));a=a.catch(e=>{if(!ri.j(159,e,void 0,void 0))throw e;});return a.then(()=>{yi(639,()=>{{var e=d.B;const g=d.j;if(g&&1===e.google_responsive_auto_format&&!0===e.google_full_width_responsive_allowed){var f;(f=(f=g.document.getElementById(e.google_async_iframe_id))?Zd(f):null)?(e=new $t(g,f,e),e.l=q.setInterval(ya(e.C, +e),500),e.C(),e=!0):e=!1}else e=!1}return e});yi(160,()=>{var e=d.iframeWin;!Og(d.B)&&e?fh(e):(e=Yi().google_jobrunner,bu(e)&&e.rl(),hh(d))})})},xx=a=>{if(/_sdo/.test(a.B.google_ad_format))return Promise.resolve();oj(d=>Gj(a,d));const b=qj();Zh(b,108)&&(Uf=Tf);const c=!og()&&!lc();return!c||c&&!zx(a,b)?Ax(a,b):Promise.resolve()}; +const Bx=(a,b,c=!1)=>{b=Kj(a,b);const d=qg()||Jj(Tg(a.pubWin));if(!b||-12245933==b.y||-12245933==d.width||-12245933==d.height||!d.height)return 0;let e=0;try{const f=Tg(a.pubWin);e=Hj(f.document,f).y}catch(f){return 0}a=e+d.height;return b.ya?(b.y-a)/d.height:0};function Cx(a){try{return a.iframeWin.frameElement}catch(b){}return null}function zx(a,b){return Dx(a,b)||Ex(a,b)} +function Dx(a,b){const c=a.B;if(!c.google_pause_ad_requests)return!1;const d=q.setTimeout(()=>{Y("abg:cmppar",{client:a.B.google_ad_client,url:a.B.google_page_url})},1E4),e=W(450,()=>{c.google_pause_ad_requests=!1;q.clearTimeout(d);a.pubWin.removeEventListener("adsbygoogle-pub-unpause-ad-requests-event",e);zx(a,b)||Ax(a,b)});a.pubWin.addEventListener("adsbygoogle-pub-unpause-ad-requests-event",e);return!0} +function Ex(a,b){const c=a.pubWin.document,d=Fx(a);if(0>d.hidden&&0>d.visible)return!1;const e=Cx(a),f=e||a.o;null==e&&null!=a.o&&Y("ins_no_ifr",{sf:a.B.google_enable_single_iframe});const g=Xj(c);if(!f||!g)return!1;if(!Yj(c))return Gx(a,b,d.visible,f);if(Bx(a,f)<=d.hidden)return!1;let h=W(332,()=>{!Yj(c)&&h&&(ee(c,g,h),Gx(a,b,d.visible,f)||Ax(a,b),h=null)});return R(c,g,h)} +function Fx(a){const b={hidden:0,visible:hg(30)||4};a=Ti(a.pubWin);var c;(c=!q.IntersectionObserver)||(c=Xe(a.j[118]));c&&(b.visible=-1);Ae()&&(a=hg(29)||Math.max(Vi(a,82),1),b.visible*=a);return b} +function Gx(a,b,c,d){if(!d||0>c)return!1;var e=a.B;if(Fk(e)||e.google_reactive_ads_config||!Ij(d)||Bx(a,d)<=c)return!1;var f=aj(),g=fj(f,8,{});f=fj(f,9,{});e=e.google_ad_section||e.google_ad_region||"";g=!g[e]&&!f[e];e=T.G().j(205,!1)&&!!a.pubWin.google_apltlad;if(g&&!e)return!1;a.J=new q.IntersectionObserver((h,k)=>{Ga(h,l=>{0>=l.intersectionRatio||(k.unobserve(l.target),yi(294,()=>{Ax(a,b)}))})},{rootMargin:100*c+"%"});a.J.observe(d);return!0} +var Ax=(a,b)=>{yi(326,()=>{var d=a.B;if(Og(d)?1==Mg(d):!Mg(d)){var e=(d=!!b.j["1337"])||b.j["21060549"]||b.j["20040067"]||Zh(b,87)==tj.Bb,f=u();if(e&&f===f.top){e=xd;var g=b.j["21060549"]&&b.j["21060624"],h=b.j["21062272"],k=new Nj;var l=new Oj;var m=Bf(a.pubWin);vd(k,1,m,0);m=$h(b).join();vd(k,5,m,"");vd(k,2,1,0);wd(l,1,k);k=new Lj;k=vd(k,10,!0,!1);k=vd(k,8,g,!1);k=vd(k,9,g,!1);k=vd(k,7,g,!1);g=vd(k,13,g,!1);h=vd(g,14,h,!1);wd(l,2,h);f.google_rum_config=e(l);f=f.document;e=Rj(Xg(),"/pagead/js/r20200428/r20190131/rum.js"); +Qf&&d&&(e=e.replace("rum","rum_debug"));d=e;Ie(f,d)}else hi(ti)}});a.B.google_ad_channel=Hx(a,a.B.google_ad_channel);a.B.google_tag_partner=Ix(a,a.B.google_tag_partner);Jx(a);var c=a.B.google_start_time;"number"===typeof c&&(ku=c,a.B.google_start_time=null);yi(161,()=>{{const f=a.B;null==f.google_ad_output&&(f.google_ad_output="html");if(null!=f.google_ad_client){var d;(d=String(f.google_ad_client))?(d=d.toLowerCase())&&"ca-"!=d.substring(0,3)&&(d="ca-"+d):d="";f.google_ad_client=d}null!=f.google_ad_slot&& +(f.google_ad_slot=String(f.google_ad_slot));if(null==f.google_flash_version){try{var e=Vg()}catch(g){e="0"}f.google_flash_version=e}f.google_webgl_support=!!S.WebGLRenderingContext;f.google_ad_section=f.google_ad_section||f.google_ad_region||"";f.google_country=f.google_country||f.google_gl||"";e=(new Date).getTime();pa(f.google_color_bg)&&(f.google_color_bg=gh(a,f.google_color_bg,e));pa(f.google_color_text)&&(f.google_color_text=gh(a,f.google_color_text,e));pa(f.google_color_link)&&(f.google_color_link= +gh(a,f.google_color_link,e));pa(f.google_color_url)&&(f.google_color_url=gh(a,f.google_color_url,e));pa(f.google_color_border)&&(f.google_color_border=gh(a,f.google_color_border,e));pa(f.google_color_line)&&(f.google_color_line=gh(a,f.google_color_line,e))}});Kx(a);if(c=a.B.google_reactive_ads_config)if(mr(a.j,c),a.j)Gt(c,a),c=c.page_level_pubvars,ra(c)&&ib(a.B,c);else return Promise.resolve();Fk(a.B)&&(Qi()&&(a.B.google_adtest=a.B.google_adtest||"on"),a.B.google_pgb_reactive=a.B.google_pgb_reactive|| +3);return Lx(a)},Kx=a=>{a.j&&(gr(a.j,a.B),er(a.j.location)&&sr(a.j,{["enable_page_level_ads"]:{["pltais"]:!0},["google_ad_client"]:a.B.google_ad_client}))},Hx=(a,b)=>(b?[b]:[]).concat(ah(a.B).ad_channels||[]).join("+"),Ix=(a,b)=>(b?[b]:[]).concat(ah(a.B).tag_partners||[]).join("+"),Ox=(a,b,c,d)=>{const e=d.iframeWin?d.B.google_container_id:d.o.id;c.src=mu(a);const f=(d.iframeWin||d.pubWin).document,g=f.currentScript||f.scripts&&f.scripts[0],h=u()==window.top;if(lc()||!g&&!e)c=Eu(c),h&&(sg(d.pubWin), +q.setTimeout(W(222,()=>{const k=f.getElementById(b);k?d.m.push(sg(d.pubWin,k)):Y("inabox:no-iframe",{adUrl:a})}),0)),e?Mx(e,f,c):f.write(c);else{const k=ae(new Od(f),"IFRAME");U(c,(l,m)=>{null!=l&&k.setAttribute(m,l)});h&&d.m.push(sg(d.pubWin,k));e?Nx(e,f,k):g.parentNode.insertBefore(k,g.nextSibling)}T.G().j(236,!1)&&!d.B.google_refresh_count&&q.setTimeout(W(644,()=>{Df(f.getElementById(b),()=>{q.setTimeout(()=>{for(const k of d.m)k();d.m.length=0},200)})}),0)},Px=(a,b,c)=>a.j?or(525,d=>{(a.iframeWin? +a.iframeWin.document.body:a.o).appendChild(b);d.createAdSlot(a.j,a.B,c,b);return b}):(Y("jserror",{context:"ac_crai"}),null); +function Qx(a,b,c,d,e=!1){qx(a.pubWin);const f="string"===typeof b?(a.iframeWin||a.pubWin).document.getElementById(b):b;if(f){var g=a.j,h=a.iframeWin&&Og(a.B)?a.iframeWin.frameElement:f;R(f,"load",()=>{f&&f.setAttribute("data-load-complete",!0);if((a.B.ovlp||T.G().j(190,!1))&&g&&g===a.pubWin&&h){const l=h.ownerDocument.getElementById(h.id+"_expand");l&&Rx(g,a,l,f)}});e=l=>{l&&a.m.push(()=>l.Ma())};var k=Sx(a);!g||Fk(a.B)&&!Gk(a.B)||(e(new Yv(g,f,h,a.B)),e(Su(a,f)),e(Iu(a,f)),e(g.IntersectionObserver? +null:new Qu(g,f,a.o)),e(ew(g,f,a.B,a.T,W(627,l=>{l||k();for(const m of a.m)m();a.m.length=0}))));g&&(e(new ju(g,f,a.B)),a.m.push(Ut(a.iframeWin,g,a.B)),a.m.push(Hu(g,f)),Wt.G().P(g));a.A&&Tx(a,f,a.pubWin.document);Ux(a,c,f);f&&f.setAttribute("data-google-container-id",d);e=a.B.iaaso;if(null!=e&&h){const l=h.ownerDocument.getElementById(h.id+"_expand"),m=l.parentElement;(m&&Rg.test(m.className)?m:l).setAttribute("data-auto-ad-size",e)}Vx(a)}else e?Y("jserror",{context:"ac::nfrm",url:c}):(e=W(162,()=> +Qx(a,b,c,d,!0)),q.setTimeout(e,0))}var Sx=a=>{const b=a.iframeWin||a.pubWin;if(!b)return()=>{};const c=a.B.google_ad_client,d=hj();let e=null;const f=Ci(b,"pvt",(g,h)=>{var k;if(k=h.source&&"string"===typeof g.token)a:{try{let l=h.source;h=b||S;for(let m=0;20>m;m++){if(l==h){k=!0;break a}if(l==h.top)break;l=l.parent}}catch(l){}k=!1}k&&(e=g.token,f(),d[c]=d[c]||[],d[c].push(e),100{e&&pa(d[c])&&(Na(d[c],e),d[c].length||delete d[c],e=null)}}; +const Vx=a=>{const b=og(a.pubWin);if(b)if("AMP-STICKY-AD"===b.container){const c=a.iframeWin||a.pubWin,d=f=>{"fill_sticky"===f.data&&(b.renderStart&&b.renderStart(),a.iframeWin&&ee(c,"message",d))},e=W(616,d,this);R(c,"message",e);a.m.push(()=>{ee(c,"message",d)})}else b.renderStart&&b.renderStart()},Rx=(a,b,c,d)=>{av(new jv(a,[5,8,9],[3,4],void 0,2),c).then(e=>{Vj(8,[e]);return e}).then(e=>{const f=c.parentElement;(f&&Rg.test(f.className)?f:c).setAttribute("data-overlap-observer-io",e.isOverlappingOrOutsideViewport); +return e}).then(e=>{const f=b.B.armr||"",g=(ah(b.B).eids||[]).join(","),h=e.executionTime||"",k=null==b.B.iaaso?"":Number(b.B.iaaso),l=Number(e.isOverlappingOrOutsideViewport),m=Ia(e.entries,r=>`${r.overlapType}:${r.overlapDepth}:${r.overlapDetectionPoint}`),p=e.overlappedArea.toFixed(2);Y("ovlp",{adf:b.B.google_ad_dom_fingerprint,armr:f,client:b.B.google_ad_client,eid:g,et:h,fwrattr:b.B.google_full_width_responsive,iaaso:k,io:l,saldr:b.B.google_loader_used,oa:p,oe:m.join(","),qid:d.dataset.googleQueryId|| +"",rafmt:b.B.google_responsive_auto_format,roa:p*e.targetRect.width*e.targetRect.height,slot:b.B.google_ad_slot,sp:e.scrollPosition.scrollX+","+e.scrollPosition.scrollY,tgt:Ng(e.target),tr:[e.targetRect.left,e.targetRect.top,e.targetRect.right,e.targetRect.bottom].join(),url:b.B.google_page_url,vp:e.viewportSize.width+"x"+e.viewportSize.height},1)}).catch(e=>{Vj(8,["Error:",e.message,c]);Y("ovlp-err",{err:e.message},1)})}; +var Tx=(a,b,c)=>{if(3!==Wj(c))Wx(a.F,b);else{const d=Xj(c);if(d){let e=()=>{ee(c,d,f);e=null};const f=()=>{Wx(a.F,b);e&&e()};R(c,d,f);a.m.push(()=>e&&e())}}a.A=!1},Xx=a=>{var b=A("Edge")?4E3:8100;var c=a;var d=b-8;c.length>b&&(c=c.substring(0,d),c=c.replace(/%\w?$/,""),c=c.replace(/&[^=]*=?$/,""),c+="&trunc=1");c!==a&&(b-=8,d=a.lastIndexOf("&",b),-1===d&&(d=a.lastIndexOf("?",b)),b=-1===d?"":a.substring(d+1),Y("trn",{ol:a.length,tr:b,url:a},.01));return c},Yx=(a,b)=>{var c=a.B,d=Mg(c);c=a.iframeWin? +"google_ads_frame"+d:c.google_async_iframe_id;var e=b,f=0===a.v;b=a.B;var g=b.google_async_iframe_id,h=a.iframeWin?"google_ads_frame"+d:g,k=b.google_ad_width,l=b.google_ad_height,m={id:h,name:h};a.iframeWin||(m.style="left:0;position:absolute;top:0;border:0;"+`width:${k}px;`+`height:${l}px;`);var p=Bt(b),r=!p&&!At(b)&&dr(b),B,y=pf();if(B=!(!y["allow-top-navigation-by-user-activation"]||!y["allow-popups-to-escape-sandbox"])){var t=e;if(y="fsb="+encodeURIComponent("1")){e=t.indexOf("#");0>e&&(e=t.length); +var E=t.indexOf("?");if(0>E||E>e){E=e;var K=""}else K=t.substring(E+1,e);t=[t.substr(0,E),K,t.substr(e)];e=t[1];t[1]=y?e?e+"&"+y:y:e;e=t[0]+(t[1]?"?"+t[1]:"")+t[2]}else e=t;y=m;t=of().join(" ");y.sandbox=t}t=e;e=Xx(e);K=f?e.replace(/&ea=[^&]*/,"")+"&ea=0":e;Gu(m,k,l,mu(K));y=Eu(m);E="";if(f){E=10;for(K="";0=d.width||0>=d.height||!d.Jb||!d.jb?void 0:Hi(d.jb,za(Ji,d,e)),d&&a.m.push(d));if(a.iframeWin&&Og(b)){a=g;d=["",y,""].join("");d=String(d);b=['"'];for(g=0;gf))if(f=k,f in Nc)k=Nc[f];else if(f in Lc)k=Nc[f]=Lc[f];else{h=f.charCodeAt(0); +if(31h)k=f;else{if(256>h){if(k="\\x",16>h||256h&&(k+="0");k+=h.toString(16).toUpperCase()}k=Nc[f]=k}h=k}b[l]=h}b.push('"');d="javascript:"+b.join("");b=u();(new nu(b)).set(a,d)}return(a=t)||c},Ux=(a,b,c)=>{const d=!mc()||0<=Ib(qc(),11)?Ba():lk();d.getOseId()&&(Aa(),d.registerAdBlock(b,1,"",c),a.m.push(()=>{d.unloadAdBlock(c,!!a.B.google_refresh_count,!0)}))}; +const ay=(a,b,c)=>{var d=a.B;const e=a.pubWin;let f=null;try{f=e.localStorage}catch(k){}let g="";Bt(d)?(g=Jg({["adk"]:d.google_ad_unit_key,["client"]:d.google_ad_client,["fa"]:d.google_reactive_ad_format},Fu("RS-"+d.google_reactive_sra_index+"-")),Cw(d,aj()),Zx(d)):(At(d)||!dr(d)||cr(e,d,f))&&Zx(d)&&(g=Gw(a,b));Vj(2,[d,g]);b&&b.id==c&&b&&b.parentNode&&b.parentNode.removeChild(b);if(g){Og(d)||Lg(e);c=Mg(d);var h=q.window===q.window.top?"a!"+c.toString(36):`${c.toString(36)}.${Math.floor(2147483648* +Math.random()).toString(36)+Math.abs(Math.floor(2147483648*Math.random())^+new Date).toString(36)}`;b=b?0{Qx(a,k,g,h)};"string"===typeof b?c(b):b.then(c).then(null,k=>{ri.j(223,k,void 0,void 0)})}},by=(a,b,c,d)=>{var e=a.B;e="aa"===e.google_loader_used||"sa"===e.google_loader_used; +const f=W(449,d);e&&(oc()?0<=Ib(qc(),11):nc()&&0<=Ib(qc(),65))?(Bu(()=>{f(a,b,c)}),a.D=Bu):d(a,b,c)},dy=(a,b,c,d)=>{T.G().j(259,!1)?Pw(new Qw(a.pubWin),e=>{e&&"string"===typeof e.uspString&&(a.I=e.uspString);cy(a,b,c,d)}):cy(a,b,c,d)};function ey(a,b,c,d){const e=new Ww(a.pubWin);T.G().j(279,!1)&&Sw(e)?Vw(e,f=>{a.tcString=f.tcString;a.gdprApplies=f.gdprApplies;a.addtlConsent=f.addtlConsent||"";dy(a,b,c,d)}):dy(a,b,c,d)} +const cy=(a,b,c,d)=>{var e=a.B;const f="aa"===e.google_loader_used||"sa"===e.google_loader_used,g=e.google_ad_client;e=Hf(Sf,g);if(f&&e.jc){const h=q.setTimeout(()=>{Y("abg:cmpnc",{client:a.B.google_ad_client,url:a.B.google_page_url,consent:JSON.stringify(Hf(Sf,g))})},1E4);If(Sf,g,W(450,k=>{q.clearTimeout(h);a.C=k;by(a,b,c,d)}))}else a.C=e,by(a,b,c,d)}; +var fy=(a,b,c)=>(new Promise(d=>{su=u;xu();qu.test("")&&!ru.test("")&&(wu[1]="");const e=()=>{ey(a,b,c,(g,h,k)=>{d([g,h,k])})},f=g=>{qf(q.top,"googlefcLoaded")?g():q.setTimeout(()=>{f(W(679,g))},500)};(q.googlefc||qf(q.top,"googlefcPresent"))&&T.G().j(304,!1)?f(e):e()})).then(d=>{let [e,f,g]=d;ay(e,f,g)}),Lx=a=>{var b=a.B.google_ad_width;var c=a.B.google_ad_height,d=a.pubWin.document,e=a.B,f=0;try{!1===e.google_allow_expandable_ads&& +(f|=1);if(!d.body||isNaN(e.google_ad_height)||isNaN(e.google_ad_width)||a.iframeWin&&d.domain!=a.iframeWin.location.hostname||!/^http/.test(d.location.protocol))f|=2;a:{e=navigator;var g=e.userAgent;const k=e.platform,l=/WebKit\/(\d+)/,m=/rv:(\d+\.\d+)/,p=/rv:1\.8([^.]|\.0)/;if(/Win|Mac|Linux|iPad|iPod|iPhone/.test(k)&&!/^Opera/.test(g)){const r=(l.exec(g)||[0,0])[1],B=(m.exec(g)||[0,0])[1];if(/Win/.test(k)&&/Trident/.test(g)&&11<=d.documentMode||!r&&"Gecko"===e.product&&27<=B&&!p.test(g)||536<=r){var h= +!0;break a}}h=!1}h||(f|=4)}catch(k){f|=8}h=f;nk(a.pubWin,a.pubWin.document,b,c)&&(h|=2);b=h;a.v=b;0===a.v||(a.B.google_allow_expandable_ads=!1);Yi()!=a.pubWin&&(a.l|=4);Uf&&(a.l|=16);Rf&&(a.l|=8);3===Wj(a.pubWin.document)&&(a.l|=32);if(b=a.j)b=a.j,b=!(Z(b).scrollWidth<=Z(b).clientWidth);b&&(a.l|=1024);null==a.iframeWin&&(a.l|=8192);a.B.google_loader_features_used&&(a.l|=a.B.google_loader_features_used);jk=gk();bk=Vf;ak=Wf;b=!mc()||0<=Ib(qc(),11)?Ba():lk();c=aj();a.H=b.setupOse(fj(c,7,$i()));b=""; +(c=a.B.google_async_iframe_id)&&null==a.iframeWin?c=a.o:c?c=a.pubWin.document.getElementById(c):(c=b="google_temp_span",h=a.B.google_container_id,f=a.iframeWin.document,g=h&&f.getElementById(h)||f.getElementById(c),g||h||!c||(f.write(""),g=f.getElementById(c)),c=g);return fy(a,c,b)},Nx=(a,b,c)=>{if(a=b.getElementById(a)){for(a.style.visibility="visible";b=a.firstChild;)a.removeChild(b);a.appendChild(c)}},Mx=(a,b,c)=>{a&&(a=b.getElementById(a))&&c&&(a.style.visibility="visible", +a.innerHTML=c)},Wx=(a,b)=>{var c=b.src,d=c.indexOf("/pagead/blank.gif#?");a=-1===d?c:a+c.substr(d+19);a!==c&&(c=b.nextSibling,d=b.parentNode,d.removeChild(b),b.src=a,d.insertBefore(b,c))},Zx=a=>{const b=aj(),c=a.google_ad_section;Fk(a)&&gj(b,15);if(Wg(a)){if(100{b&&a.B.rpe&&Sv(a.pubWin,b,{height:a.B.google_ad_height,zb:"force",Hb:!0,ec:!0,Fb:a.B.google_ad_client})},Jx=a=>{const b=a.j;if(b&&!ah(b).ads_density_stats_processed&& +!og(b)&&(ah(b).ads_density_stats_processed=!0,T.G().j(290,!1)||.01>Ne(b))){const c=()=>{if(b){var d=ss(ns(b),a.B.google_ad_client,b.location.hostname,ah(a.B).eids||[]);Y("ama_stats",d,1)}};"complete"===b.document.readyState?q.setTimeout(c,1E3):R(b,"load",()=>{q.setTimeout(c,1E3)})}};{(()=>{var b=[Zt,Yt,rj,xi];ri.l=c=>{Ga(b,d=>{d(c)});ui(c);vi(c)}})();const a=q.google_sl_win||q;a.google_sa_impl||(a.google_sa_impl=yx,Kw(Iw(a)),a.google_process_slots&&a.google_process_slots())};}).call(this,window,document,location) diff --git a/doc/As65 Assembler_files/zrt_lookup.html b/doc/As65 Assembler_files/zrt_lookup.html new file mode 100644 index 0000000..94b1855 --- /dev/null +++ b/doc/As65 Assembler_files/zrt_lookup.html @@ -0,0 +1,40 @@ + + + + \ No newline at end of file diff --git a/src/.Makefile.swp b/src/.Makefile.swp new file mode 100644 index 0000000..2f15452 Binary files /dev/null and b/src/.Makefile.swp differ diff --git a/src/asm/Makefile b/src/Makefile similarity index 72% rename from src/asm/Makefile rename to src/Makefile index c53bd91..50b2b57 100644 --- a/src/asm/Makefile +++ b/src/Makefile @@ -1,12 +1,10 @@ -MERLIN_URL=https://www.brutaldeluxe.fr/products/crossdevtools/merlin/Merlin32_v1.0.zip - PGM=rnd -BASE_DSK=prodos-2.0.3-boot.dsk +BASE_DSK=../storage/prodos-2.0.3-boot.dsk # It is necessary to use this older version of AppleCommander to support # the PowerBook G4 and iBook G3. This version only requires Java 1.3. -AC=java -jar AppleCommander-1.3.5-ac.jar -AS65=java -cp 65xx.zip uk.co.demon.obelisk.w65xx.As65 -LK65=java -cp 65xx.zip uk.co.demon.obelisk.w65xx.Lk65 +AC=java -jar ../lib/AppleCommander-1.3.5-ac.jar +AS65=java -cp ../lib/65xx.zip uk.co.demon.obelisk.w65xx.As65 +LK65=java -cp ../lib/65xx.zip uk.co.demon.obelisk.w65xx.Lk65 SRC=$(PGM).s VOL=$(PGM) DSK=$(PGM).dsk @@ -33,8 +31,9 @@ $(DSK): $(PGM) $(PGM): $(PGM).obj $(LK65) -output $(PGM) -bin $(PGM).obj +# as65 does not exit with a non-zero code so that make can detect when it failed. $(PGM).obj: symbols.s macros.s $(SRC) - $(AS65) $(SRC) + $(AS65) $(SRC) 2>&1 | tee as65-output.txt && [ ! -s as65-output.txt ] test: $(DSK) $(EMU) $(DSK) diff --git a/src/as65-output.txt b/src/as65-output.txt new file mode 100644 index 0000000..98a1d5a --- /dev/null +++ b/src/as65-output.txt @@ -0,0 +1,127 @@ +Error: symbols.s (1) No active section +Error: symbols.s (1) Unknown opcode or directive +Error: symbols.s (2) No active section +Error: symbols.s (2) Unknown opcode or directive +Error: symbols.s (3) No active section +Error: symbols.s (3) Unknown opcode or directive +Error: symbols.s (4) No active section +Error: symbols.s (4) Unknown opcode or directive +Error: symbols.s (5) No active section +Error: symbols.s (5) Unknown opcode or directive +Error: symbols.s (6) No active section +Error: symbols.s (6) Unknown opcode or directive +Error: symbols.s (7) No active section +Error: symbols.s (7) Unknown opcode or directive +Error: symbols.s (8) No active section +Error: symbols.s (8) Unknown opcode or directive +Error: symbols.s (14) No active section +Error: symbols.s (14) Unknown opcode or directive +Error: symbols.s (15) No active section +Error: symbols.s (15) Unknown opcode or directive +Error: symbols.s (16) No active section +Error: symbols.s (16) Unknown opcode or directive +Error: symbols.s (17) No active section +Error: symbols.s (17) Unknown opcode or directive +Error: symbols.s (18) No active section +Error: symbols.s (18) Unknown opcode or directive +Error: symbols.s (19) No active section +Error: symbols.s (19) Unknown opcode or directive +Error: symbols.s (43) No active section +Error: symbols.s (43) Unknown opcode or directive +Error: symbols.s (44) No active section +Error: symbols.s (44) Unknown opcode or directive +Error: symbols.s (45) No active section +Error: symbols.s (45) Unknown opcode or directive +Error: symbols.s (46) No active section +Error: symbols.s (46) Unknown opcode or directive +Error: symbols.s (47) No active section +Error: symbols.s (47) Unknown opcode or directive +Error: symbols.s (48) No active section +Error: symbols.s (48) Unknown opcode or directive +Error: symbols.s (49) No active section +Error: symbols.s (49) Unknown opcode or directive +Error: symbols.s (50) No active section +Error: symbols.s (50) Unknown opcode or directive +Error: symbols.s (76) No active section +Error: symbols.s (76) Unknown opcode or directive +Error: symbols.s (77) No active section +Error: symbols.s (77) Unknown opcode or directive +Error: symbols.s (78) No active section +Error: symbols.s (78) Unknown opcode or directive +Error: symbols.s (79) No active section +Error: symbols.s (79) Unknown opcode or directive +Error: symbols.s (80) No active section +Error: symbols.s (80) Unknown opcode or directive +Error: symbols.s (81) No active section +Error: symbols.s (81) Unknown opcode or directive +Error: symbols.s (82) No active section +Error: symbols.s (82) Unknown opcode or directive +Error: symbols.s (83) No active section +Error: symbols.s (83) Unknown opcode or directive +Error: macros.s (1) No active section +Error: macros.s (1) Unknown opcode or directive +Error: macros.s (2) No active section +Error: macros.s (2) Unknown opcode or directive +Error: macros.s (3) No active section +Error: macros.s (3) Unknown opcode or directive +Error: macros.s (4) No active section +Error: macros.s (4) Unknown opcode or directive +Error: macros.s (5) No active section +Error: macros.s (5) Unknown opcode or directive +Error: macros.s (6) No active section +Error: macros.s (6) Unknown opcode or directive +Error: macros.s (7) No active section +Error: macros.s (7) Unknown opcode or directive +Error: macros.s (8) No active section +Error: macros.s (8) Unknown opcode or directive +Error: macros.s (34) No active section +Error: macros.s (34) Unknown opcode or directive +Error: macros.s (35) No active section +Error: macros.s (35) Unknown opcode or directive +Error: macros.s (36) No active section +Error: macros.s (36) Unknown opcode or directive +Error: macros.s (37) No active section +Error: macros.s (37) Unknown opcode or directive +Error: macros.s (38) No active section +Error: macros.s (38) Unknown opcode or directive +Error: macros.s (39) No active section +Error: macros.s (39) Unknown opcode or directive +Error: macros.s (40) No active section +Error: macros.s (40) Unknown opcode or directive +Error: macros.s (55) No active section +Error: macros.s (55) Unknown opcode or directive +Error: macros.s (56) No active section +Error: macros.s (56) Unknown opcode or directive +Error: macros.s (57) No active section +Error: macros.s (57) Unknown opcode or directive +Error: macros.s (58) No active section +Error: macros.s (58) Unknown opcode or directive +Error: macros.s (59) No active section +Error: macros.s (59) Unknown opcode or directive +Error: macros.s (60) No active section +Error: macros.s (60) Unknown opcode or directive +Error: macros.s (61) No active section +Error: macros.s (61) Unknown opcode or directive +Error: macros.s (62) No active section +Error: macros.s (62) Unknown opcode or directive +Error: macros.s (63) No active section +Error: macros.s (63) Unknown opcode or directive +Error: macros.s (64) No active section +Error: macros.s (64) Unknown opcode or directive +Error: rnd.s (11) Unknown opcode or directive +Error: rnd.s (17) Unknown opcode or directive +Error: rnd.s (27) Label as already been defined: * +Error: rnd.s (27) Unknown opcode or directive +Error: rnd.s (37) Label as already been defined: * +Error: rnd.s (37) Unknown opcode or directive +Error: rnd.s (44) Label as already been defined: * +Error: rnd.s (44) Unknown opcode or directive +Error: rnd.s (50) Label as already been defined: * +Error: rnd.s (50) Unknown opcode or directive +Error: rnd.s (60) Label as already been defined: * +Error: rnd.s (60) Unknown opcode or directive +Error: rnd.s (61) Label as already been defined: * +Error: rnd.s (61) Unknown opcode or directive +Error: rnd.s (64) Illegal addressing mode +Error: rnd.s (67) Label as already been defined: * +Error: rnd.s (67) Unknown opcode or directive diff --git a/src/asm/symbols.s b/src/asm/symbols.s deleted file mode 100644 index a5e7c2c..0000000 --- a/src/asm/symbols.s +++ /dev/null @@ -1,100 +0,0 @@ -******************************** -* * -* SYMBOLS * -* * -* AUTHOR: BILL CHATFIELD * -* LICENSE: GPL2 * -* * -******************************** - -RNDL EQU $4e ;Continuously incremented while waiting for keyboard input -RNDH EQU $4f ;High byte of RNDL -FACEXP EQU $9d ;Address of FAC exponent used by FADDT,FSUBT,FMULTT,FDIVT - -******************************** -* * -* MEMORY MAPPED INPUT/OUTPUT * -* ADDRESSES $C000 - $C0FF * -* * -******************************** - -KBD EQU $C000 ;BIT 7 IS 1 IF KEY PRESSED -KBDSTRB EQU $C010 ;CLEARS KBD BIT 7 -CLR80STO EQU $C000 ;ALLOW PAGE2 PG1 & PG2 SWITCHING -SET80STO EQU $C001 ;ALLOW PAGE2 MAIN & AUX SWITCHNG -STO80 EQU $C018 ;1=PAGE2 SWITCHES MAIN/AUX - ;0=PAGE2 SWITCHES VIDEO PAGES -CLR80VID EQU $C00C ;TURN OFF 80-COL DISPLAY -SET80VID EQU $C00D ;TURN ON 80-COL DISPLAY -COL80 EQU $C01F ;0=40 COL IS ON, 1=80 COL IS ON -TEXTOFF EQU $C050 ;SELECTS GRAPHICS MODE -TEXTON EQU $C051 ;SELECTS TEXT MODE -TEXT EQU $C01A ;1=TEXT MODE ACTIVE,0=GRAPH MODE -MIXEDOFF EQU $C052 ;USE FULL-SCREEN GRAPHICS -MIXEDON EQU $C053 ;USE GRAPHICS WITH 4 LINES TEXT -MIXED EQU $C01B ;0=FULL SCREEN, 1=MIXED -PAGE2OFF EQU $C054 ;SELECTS PAGE1 OR MAIN VID MEM -PAGE2ON EQU $C055 ;SELECTS PAGE2 OR AUX VID MEM -PAGE2 EQU $C01C ;1=VID PG2 SELECTED OR AUX SEL -HIRESOFF EQU $C056 ;SELECTS LOW-RES GRAPHICS -HIRESON EQU $C057 ;SELECTS HIGH-RES GRAPHICS -HIRES EQU $C01D ;0=LOW-RES, 1=HIGH-RES - -******************************** -* * -* SUBROUTINES PROVIDED BY * -* APPLESOFT BASIC * -* IN READ-ONLY MEMORY * -* ADDRESSES $D000 - $F7FF * -* * -******************************** - -STROUT EQU $DB3A ;PRINT STRING IN Y,A -GIVAYF EQU $E2F2 ;CONVERT 2-BYTE INT A(HI) Y(LO) TO FLOAT IN FAC -CONINT EQU $E6FB ;CONVERT FAC TO BYTE IN X, ERR IF FAC > 255 -FADD EQU $E7BE ;FAC = MEM + FAC, MEM ADDR IS Y(HI) A(LO) -FSUB EQU $E7A7 ;FAC = MEM - FAC, MEM ADDR IS Y(HI) A(LO) -FMULT EQU $E97F ;FAC = MEM * FAC, MEM ADDR IS Y(HI) A(LO) -FDIV EQU $EA66 ;FAC = MEM / FAC, MEM ADDR IS Y(HI) A(LO) -FADDT EQU $E7C1 ;FAC = ARG + FAC, MUST LOAD FACEXP INTO A FIRST -FSUBT EQU $E7AA ;FAC = ARG - FAC, MUST LOAD FACEXP INTO A FIRST -FMULTT EQU $E982 ;FAC = ARG * FAC, MUST LOAD FACEXP INTO A FIRST -FDIVT EQU $EA69 ;FAC = ARG / FAC, MUST LOAD FACEXP INTO A FIRST -MUL10 EQU $EA39 ;MULTIPLY FAC BY 10 -FCOMP EQU $EBB2 ;COMP MEM TO FAC -QINT EQU $EBF2 ;CONVERT FAC TO INTEGER -FLOAT EQU $EB93 ;CONVERT A TO FAC, I THINK -MOVAF EQU $EB63 ;MOVE FAC INTO ARG -MOVMF EQU $EB2B ;MOVE FAC TO MEMORY Y,X -MOVFA EQU $EB53 ;MOVE ARG TO FAC -MOVFM EQU $EB2B ;MOVE MEMORY TO FAC -INT EQU $EC23 ;APPLESOFT INT FUNCTION -PRINTFAC EQU $ED2E ;PRINT FAC. USES FOUT,STROUT -FOUT EQU $ED34 ;FAC TO STRING, FAC DESTROYED -RND EQU $EFAE ;APPLESOFT RND FUNCTION - -******************************** -* * -* SUBROUTINES PROVIDED BY * -* SYSTEM MONITOR PROGRAM * -* IN READ-ONLY MEMORY * -* ADDRESSES $F800 - $FFFF * -* * -******************************** - -PLOT EQU $F800 ;PLOT BLOCK ON LOW-RES SCREEN -HLINE EQU $F819 ;HORIZONTAL LINE -VLINE EQU $F828 ;VERTICAL LINE -CLRSCR EQU $F832 ;CLEAR LOW-RES SCREEN -CLRTOP EQU $F836 ;CLEAR THE TOP OF LOW-RES -NEXTCOL EQU $F85F ;INCREMENT COLOR BY 3 -SETCOL EQU $F864 ;SET LOW-RES GRAPHICS COLOR -SCRN EQU $F871 ;READ THE LOW-RES SCREEN -TEXTCMD EQU $FB2F -TEXTMODE EQU $FB39 -GR EQU $FB40 ;BASIC GR COMMAND -WAIT EQU $FCA8 -COUT EQU $FDED ;WRITE A CHARACTER -CROUT EQU $FD8E ;WRITE A CARRIAGE RETURN -PRBYTE EQU $FDDA ;PRINT VALUE OF BYTE - diff --git a/src/blah.txt b/src/blah.txt new file mode 100644 index 0000000..98a1d5a --- /dev/null +++ b/src/blah.txt @@ -0,0 +1,127 @@ +Error: symbols.s (1) No active section +Error: symbols.s (1) Unknown opcode or directive +Error: symbols.s (2) No active section +Error: symbols.s (2) Unknown opcode or directive +Error: symbols.s (3) No active section +Error: symbols.s (3) Unknown opcode or directive +Error: symbols.s (4) No active section +Error: symbols.s (4) Unknown opcode or directive +Error: symbols.s (5) No active section +Error: symbols.s (5) Unknown opcode or directive +Error: symbols.s (6) No active section +Error: symbols.s (6) Unknown opcode or directive +Error: symbols.s (7) No active section +Error: symbols.s (7) Unknown opcode or directive +Error: symbols.s (8) No active section +Error: symbols.s (8) Unknown opcode or directive +Error: symbols.s (14) No active section +Error: symbols.s (14) Unknown opcode or directive +Error: symbols.s (15) No active section +Error: symbols.s (15) Unknown opcode or directive +Error: symbols.s (16) No active section +Error: symbols.s (16) Unknown opcode or directive +Error: symbols.s (17) No active section +Error: symbols.s (17) Unknown opcode or directive +Error: symbols.s (18) No active section +Error: symbols.s (18) Unknown opcode or directive +Error: symbols.s (19) No active section +Error: symbols.s (19) Unknown opcode or directive +Error: symbols.s (43) No active section +Error: symbols.s (43) Unknown opcode or directive +Error: symbols.s (44) No active section +Error: symbols.s (44) Unknown opcode or directive +Error: symbols.s (45) No active section +Error: symbols.s (45) Unknown opcode or directive +Error: symbols.s (46) No active section +Error: symbols.s (46) Unknown opcode or directive +Error: symbols.s (47) No active section +Error: symbols.s (47) Unknown opcode or directive +Error: symbols.s (48) No active section +Error: symbols.s (48) Unknown opcode or directive +Error: symbols.s (49) No active section +Error: symbols.s (49) Unknown opcode or directive +Error: symbols.s (50) No active section +Error: symbols.s (50) Unknown opcode or directive +Error: symbols.s (76) No active section +Error: symbols.s (76) Unknown opcode or directive +Error: symbols.s (77) No active section +Error: symbols.s (77) Unknown opcode or directive +Error: symbols.s (78) No active section +Error: symbols.s (78) Unknown opcode or directive +Error: symbols.s (79) No active section +Error: symbols.s (79) Unknown opcode or directive +Error: symbols.s (80) No active section +Error: symbols.s (80) Unknown opcode or directive +Error: symbols.s (81) No active section +Error: symbols.s (81) Unknown opcode or directive +Error: symbols.s (82) No active section +Error: symbols.s (82) Unknown opcode or directive +Error: symbols.s (83) No active section +Error: symbols.s (83) Unknown opcode or directive +Error: macros.s (1) No active section +Error: macros.s (1) Unknown opcode or directive +Error: macros.s (2) No active section +Error: macros.s (2) Unknown opcode or directive +Error: macros.s (3) No active section +Error: macros.s (3) Unknown opcode or directive +Error: macros.s (4) No active section +Error: macros.s (4) Unknown opcode or directive +Error: macros.s (5) No active section +Error: macros.s (5) Unknown opcode or directive +Error: macros.s (6) No active section +Error: macros.s (6) Unknown opcode or directive +Error: macros.s (7) No active section +Error: macros.s (7) Unknown opcode or directive +Error: macros.s (8) No active section +Error: macros.s (8) Unknown opcode or directive +Error: macros.s (34) No active section +Error: macros.s (34) Unknown opcode or directive +Error: macros.s (35) No active section +Error: macros.s (35) Unknown opcode or directive +Error: macros.s (36) No active section +Error: macros.s (36) Unknown opcode or directive +Error: macros.s (37) No active section +Error: macros.s (37) Unknown opcode or directive +Error: macros.s (38) No active section +Error: macros.s (38) Unknown opcode or directive +Error: macros.s (39) No active section +Error: macros.s (39) Unknown opcode or directive +Error: macros.s (40) No active section +Error: macros.s (40) Unknown opcode or directive +Error: macros.s (55) No active section +Error: macros.s (55) Unknown opcode or directive +Error: macros.s (56) No active section +Error: macros.s (56) Unknown opcode or directive +Error: macros.s (57) No active section +Error: macros.s (57) Unknown opcode or directive +Error: macros.s (58) No active section +Error: macros.s (58) Unknown opcode or directive +Error: macros.s (59) No active section +Error: macros.s (59) Unknown opcode or directive +Error: macros.s (60) No active section +Error: macros.s (60) Unknown opcode or directive +Error: macros.s (61) No active section +Error: macros.s (61) Unknown opcode or directive +Error: macros.s (62) No active section +Error: macros.s (62) Unknown opcode or directive +Error: macros.s (63) No active section +Error: macros.s (63) Unknown opcode or directive +Error: macros.s (64) No active section +Error: macros.s (64) Unknown opcode or directive +Error: rnd.s (11) Unknown opcode or directive +Error: rnd.s (17) Unknown opcode or directive +Error: rnd.s (27) Label as already been defined: * +Error: rnd.s (27) Unknown opcode or directive +Error: rnd.s (37) Label as already been defined: * +Error: rnd.s (37) Unknown opcode or directive +Error: rnd.s (44) Label as already been defined: * +Error: rnd.s (44) Unknown opcode or directive +Error: rnd.s (50) Label as already been defined: * +Error: rnd.s (50) Unknown opcode or directive +Error: rnd.s (60) Label as already been defined: * +Error: rnd.s (60) Unknown opcode or directive +Error: rnd.s (61) Label as already been defined: * +Error: rnd.s (61) Unknown opcode or directive +Error: rnd.s (64) Illegal addressing mode +Error: rnd.s (67) Label as already been defined: * +Error: rnd.s (67) Unknown opcode or directive diff --git a/src/asm/macros.s b/src/macros.s similarity index 75% rename from src/asm/macros.s rename to src/macros.s index 3d1024a..eaa1063 100644 --- a/src/asm/macros.s +++ b/src/macros.s @@ -7,42 +7,42 @@ * * ******************************** -PUSHY MAC +PUSHY .MACRO TYA PHA - EOM + .ENDM -POPY MAC +POPY .MACRO PLA TAY - EOM + .ENDM -PUSHXY MAC +PUSHXY .MACRO TXA PHA TYA PHA - EOM + .ENDM -POPXY MAC +POPXY .MACRO PLA TAY PLA TAX - EOM + .ENDM ******************************** * * -* PUTS MACRO - OUTPUTS STRING * +* PUTS .MACRORO - OUTPUTS STRING * * ]1 = ADDRESS OF NULL- * * TERMINATED STRING * * * ******************************** -PUTS MAC +PUTS .MACRO PUSHY LDY #0 ; PREPARE LOOP INDEX -NEXT LDA ]1,Y ; LOAD A CHARACTER +NEXT LDA \0,Y ; LOAD A CHARACTER CMP #0 ; CHECK FOR END OF STRING BEQ DONE ORA #%10000000 ; SET HIGH BIT FOR OUTPUT @@ -50,7 +50,7 @@ NEXT LDA ]1,Y ; LOAD A CHARACTER INY JMP NEXT DONE POPY - EOM + .ENDM ******************************** * * @@ -63,9 +63,9 @@ DONE POPY * * ******************************** -PUTF MAC +PUTF .MACRO JSR FOUT ;CONVERT FAC TO STRING - STA ]1 ;STORE LOW BYTE OF STRING - STY ]1+1 ;STORE HIGH BYTE OF STRING - PUTS (]1) ;PRINT STRING - EOM + STA \0 ;STORE LOW BYTE OF STRING + STY \0+1 ;STORE HIGH BYTE OF STRING + PUTS (\0) ;PRINT STRING + .ENDM diff --git a/src/asm/rnd.s b/src/rnd.s similarity index 96% rename from src/asm/rnd.s rename to src/rnd.s index 010dc91..3dc02cb 100644 --- a/src/asm/rnd.s +++ b/src/rnd.s @@ -3,9 +3,10 @@ ; Random dungeon generator ; ;************************** - use symbols - use macros - dsk rnd + .include "symbols.s" + .include "macros.s" + + .code org $8000 diff --git a/src/symbols.s b/src/symbols.s new file mode 100644 index 0000000..144d819 --- /dev/null +++ b/src/symbols.s @@ -0,0 +1,100 @@ +******************************** +* * +* SYMBOLS * +* * +* AUTHOR: BILL CHATFIELD * +* LICENSE: GPL2 * +* * +******************************** + +RNDL .EQU $4e ;Continuously incremented while waiting for keyboard input +RNDH .EQU $4f ;High byte of RNDL +FACEXP .EQU $9d ;Address of FAC exponent used by FADDT,FSUBT,FMULTT,FDIVT + +******************************** +* * +* MEMORY MAPPED INPUT/OUTPUT * +* ADDRESSES $C000 - $C0FF * +* * +******************************** + +KBD .EQU $C000 ;BIT 7 IS 1 IF KEY PRESSED +KBDSTRB .EQU $C010 ;CLEARS KBD BIT 7 +CLR80STO .EQU $C000 ;ALLOW PAGE2 PG1 & PG2 SWITCHING +SET80STO .EQU $C001 ;ALLOW PAGE2 MAIN & AUX SWITCHNG +STO80 .EQU $C018 ;1=PAGE2 SWITCHES MAIN/AUX + ;0=PAGE2 SWITCHES VIDEO PAGES +CLR80VID .EQU $C00C ;TURN OFF 80-COL DISPLAY +SET80VID .EQU $C00D ;TURN ON 80-COL DISPLAY +COL80 .EQU $C01F ;0=40 COL IS ON, 1=80 COL IS ON +TEXTOFF .EQU $C050 ;SELECTS GRAPHICS MODE +TEXTON .EQU $C051 ;SELECTS TEXT MODE +TEXT .EQU $C01A ;1=TEXT MODE ACTIVE,0=GRAPH MODE +MIXEDOFF .EQU $C052 ;USE FULL-SCREEN GRAPHICS +MIXEDON .EQU $C053 ;USE GRAPHICS WITH 4 LINES TEXT +MIXED .EQU $C01B ;0=FULL SCREEN, 1=MIXED +PAGE2OFF .EQU $C054 ;SELECTS PAGE1 OR MAIN VID MEM +PAGE2ON .EQU $C055 ;SELECTS PAGE2 OR AUX VID MEM +PAGE2 .EQU $C01C ;1=VID PG2 SELECTED OR AUX SEL +HIRESOFF .EQU $C056 ;SELECTS LOW-RES GRAPHICS +HIRESON .EQU $C057 ;SELECTS HIGH-RES GRAPHICS +HIRES .EQU $C01D ;0=LOW-RES, 1=HIGH-RES + +******************************** +* * +* SUBROUTINES PROVIDED BY * +* APPLESOFT BASIC * +* IN READ-ONLY MEMORY * +* ADDRESSES $D000 - $F7FF * +* * +******************************** + +STROUT .EQU $DB3A ;PRINT STRING IN Y,A +GIVAYF .EQU $E2F2 ;CONVERT 2-BYTE INT A(HI) Y(LO) TO FLOAT IN FAC +CONINT .EQU $E6FB ;CONVERT FAC TO BYTE IN X, ERR IF FAC > 255 +FADD .EQU $E7BE ;FAC = MEM + FAC, MEM ADDR IS Y(HI) A(LO) +FSUB .EQU $E7A7 ;FAC = MEM - FAC, MEM ADDR IS Y(HI) A(LO) +FMULT .EQU $E97F ;FAC = MEM * FAC, MEM ADDR IS Y(HI) A(LO) +FDIV .EQU $EA66 ;FAC = MEM / FAC, MEM ADDR IS Y(HI) A(LO) +FADDT .EQU $E7C1 ;FAC = ARG + FAC, MUST LOAD FACEXP INTO A FIRST +FSUBT .EQU $E7AA ;FAC = ARG - FAC, MUST LOAD FACEXP INTO A FIRST +FMULTT .EQU $E982 ;FAC = ARG * FAC, MUST LOAD FACEXP INTO A FIRST +FDIVT .EQU $EA69 ;FAC = ARG / FAC, MUST LOAD FACEXP INTO A FIRST +MUL10 .EQU $EA39 ;MULTIPLY FAC BY 10 +FCOMP .EQU $EBB2 ;COMP MEM TO FAC +QINT .EQU $EBF2 ;CONVERT FAC TO INTEGER +FLOAT .EQU $EB93 ;CONVERT A TO FAC, I THINK +MOVAF .EQU $EB63 ;MOVE FAC INTO ARG +MOVMF .EQU $EB2B ;MOVE FAC TO MEMORY Y,X +MOVFA .EQU $EB53 ;MOVE ARG TO FAC +MOVFM .EQU $EB2B ;MOVE MEMORY TO FAC +INT .EQU $EC23 ;APPLESOFT INT FUNCTION +PRINTFAC .EQU $ED2E ;PRINT FAC. USES FOUT,STROUT +FOUT .EQU $ED34 ;FAC TO STRING, FAC DESTROYED +RND .EQU $EFAE ;APPLESOFT RND FUNCTION + +******************************** +* * +* SUBROUTINES PROVIDED BY * +* SYSTEM MONITOR PROGRAM * +* IN READ-ONLY MEMORY * +* ADDRESSES $F800 - $FFFF * +* * +******************************** + +PLOT .EQU $F800 ;PLOT BLOCK ON LOW-RES SCREEN +HLINE .EQU $F819 ;HORIZONTAL LINE +VLINE .EQU $F828 ;VERTICAL LINE +CLRSCR .EQU $F832 ;CLEAR LOW-RES SCREEN +CLRTOP .EQU $F836 ;CLEAR THE TOP OF LOW-RES +NEXTCOL .EQU $F85F ;INCREMENT COLOR BY 3 +SETCOL .EQU $F864 ;SET LOW-RES GRAPHICS COLOR +SCRN .EQU $F871 ;READ THE LOW-RES SCREEN +TEXTCMD .EQU $FB2F +TEXTMODE .EQU $FB39 +GR .EQU $FB40 ;BASIC GR COMMAND +WAIT .EQU $FCA8 +COUT .EQU $FDED ;WRITE A CHARACTER +CROUT .EQU $FD8E ;WRITE A CARRIAGE RETURN +PRBYTE .EQU $FDDA ;PRINT VALUE OF BYTE +