int64/0000755000175100001440000000000011666175544011253 5ustar hornikusersint64/MD50000644000175100001440000000466711666175544011600 0ustar hornikusers202f81114893214fe076a3dc7f2936d9 *ChangeLog ad8039cfff19dd6a5b3d80e956dd7d1f *DESCRIPTION ec0dab9f4dbc31f23248e064de4b4750 *NAMESPACE e2b20ee2374adef9b8d2e35b21088ec8 *R/int64.R bfaea06c518cea5a14b494255d1f4c12 *inst/NEWS a5ef93bd26d2947da854a7d685eea6d4 *inst/doc/int64.Rnw 39ff51af8d440147bc862eaf522b2a0b *inst/doc/int64.pdf 329359223514fcae4f78306c8410fccb *inst/include/int64.h 1e6c68713a8915b4eaef8eff5f2981fe *inst/include/int64/LongVector.h 179205e75eb83a1c92e05673990ff35f *inst/include/int64/arith.h 2b38d34e10b215a0dc6f8236a0767286 *inst/include/int64/as_character.h a296c9b8e57d75da41da1e88acacd849 *inst/include/int64/as_long.h 69a530398ec783efc30555b1451c7315 *inst/include/int64/compare.h 65225bac04d189edeb06064afa77bc5d *inst/include/int64/format_binary.h ba7328bdd3f75c73d2a2c9fbf2cdfc76 *inst/include/int64/get_bits.h d14b131f7d16cbe80d87756004756902 *inst/include/int64/get_class.h 096a0377b98cda9c78dc13ac6718d8b3 *inst/include/int64/get_long.h 4f0a3fb16cf49da953b92c433fa16e51 *inst/include/int64/int2.h 6e38efe0fb656615f1f4b86f99bace11 *inst/include/int64/int64.h 0a9536ae7b5237fa2c34c3c8d83fb42d *inst/include/int64/long_traits.h f5285db4b84d95689c39e9990f4177d4 *inst/include/int64/math.h 66b06e0ae7c6bd3b5a6136ea65a78b32 *inst/include/int64/read_string.h 02d718588767dec109548677beb847f8 *inst/include/int64/read_string_forward.h c012b69d9547ae54fd1d558cc44df0e3 *inst/include/int64/routines.h 64261b31645e581cb2302e631007928d *inst/include/int64/summary.h 71ba895b59243c94781bd832adffd007 *inst/unitTests/runTests.R 3f0d4d612d365d94246c3bb02e169f32 *inst/unitTests/runit.int64.R 7cf7d760f404594e04026b04550f9279 *man/as.int64.Rd f28492e65e51d865497034a22a077ea7 *man/as.uint64.Rd 87e8e12369cda981ffcbff1944a18c14 *man/binary-class.Rd a3c2dbd9fa9db038a6108fc8e443f8d3 *man/binary-methods.Rd 47d9b1e33644a68a821cd4656e122d99 *man/int64-class.Rd 848f1273eda3466d00faf831c06dcd60 *man/int64-package.Rd 83d1a8d85d3d7ba995e1f1fa62d72c8c *man/int64.Rd 13945b4cac0dcec9412935bee3b62c3f *man/numeric_limits.Rd 7a998dfe4fe6abf54bbe63a6e883b029 *man/sort-methods.Rd 14957d1c5b9d047beddde3cc88b9749d *man/uint64-class.Rd 0830f711d93f0651c0ed417c5deabd0d *man/uint64.Rd bbe2cc89e11938a692bd3110e4324449 *man/unique-methods.Rd e87abaa47a2160ce692e7d5306dd2aa7 *src/Makevars e87abaa47a2160ce692e7d5306dd2aa7 *src/Makevars.win 911fb44ffecb91fe582101dcc35b2d00 *src/int64.cpp 2a6617e4ef79ab3a96bd9d53ec077a69 *src/int64_init.c 4fd5a0fe161fa48793eeb0cc58d19cab *tests/doRUnit.R int64/tests/0000755000175100001440000000000011665656774012425 5ustar hornikusersint64/tests/doRUnit.R0000644000175100001440000000100411660746102014103 0ustar hornikusersif(require("RUnit", quietly = TRUE)) { pkg <- "int64" require( pkg, character.only=TRUE) path <- system.file("unitTests", package = pkg) stopifnot(file.exists(path), file.info(path.expand(path))$isdir) # without this, we get unit test failures Sys.setenv( R_TESTS = "" ) int64.unit.test.output.dir <- getwd() source(file.path(path, "runTests.R"), echo = TRUE) } else { print( "package RUnit not available, cannot run unit tests" ) } int64/src/0000755000175100001440000000000011665656774012052 5ustar hornikusersint64/src/Makevars.win0000644000175100001440000000004411665656774014340 0ustar hornikusersPKG_CPPFLAGS += -I../inst/include/ int64/src/Makevars0000644000175100001440000000004411665656774013544 0ustar hornikusersPKG_CPPFLAGS += -I../inst/include/ int64/src/int64_init.c0000644000175100001440000000342111665656774014205 0ustar hornikusers// int64_init.c : 64 bit integers // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #include #include #include #include // borrowed from Matrix #define CALLDEF(name, n) {#name, (DL_FUNC) &name, n} #define EXTDEF(name) {#name, (DL_FUNC) &name, -1} static R_CallMethodDef callEntries[] = { CALLDEF(int64_as_int64,1), CALLDEF(int64_format_binary,1), CALLDEF(int64_as_character_int64,2), CALLDEF(int64_arith_int64_int64,4), CALLDEF(int64_compare_int64_int64,4), CALLDEF(int64_summary_int64,3), CALLDEF(int64_as_uint64,1), CALLDEF(int64_limits,1), CALLDEF(int64_sort,3), CALLDEF(int64_math,3), CALLDEF(int64_signif,3), CALLDEF(int64_isna,2), {NULL, NULL, 0} }; void R_init_int64( DllInfo* info){ /* Register routines, allocate resources. */ R_registerRoutines(info, NULL /* .C*/, callEntries /*.Call*/, NULL /* .Fortran */, NULL /*.External*/ ); } void R_unload_int64(DllInfo *info) { /* Release resources. */ } int64/src/int64.cpp0000644000175100001440000001470011665656774013524 0ustar hornikusers// int64.cpp: int64 64 bit integers // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #define BUILDING_INT64 #include #include namespace Rint64{ namespace internal{ bool int64_naflag = false ; SEXP int64_format_binary__standard(SEXP x){ int n = Rf_length(x) ; SEXP res = PROTECT( Rf_allocVector( STRSXP, n ) ) ; switch( TYPEOF(x) ){ case INTSXP: { int* data = INTEGER(x) ; for( int i=0; i( data[i] ) ) ) ; } break ; } case REALSXP: { double* p_x = REAL(x) ; for( int i=0; i( p_x[i] ) ) ); } break ; } default: Rf_error( "incompatible type" ) ; } UNPROTECT(1) ; // res ; return res ; } } } extern "C" SEXP int64_format_binary(SEXP x){ if( Rf_inherits( x, "int64" ) ){ return Rint64::internal::int64_format_binary_long(x) ; } else if( Rf_inherits( x, "uint64" ) ){ return Rint64::internal::int64_format_binary_long(x) ; } else { return Rint64::internal::int64_format_binary__standard(x); } return R_NilValue ; } extern "C" SEXP int64_as_character_int64(SEXP x, SEXP unsign){ bool is_unsigned = INTEGER(unsign)[0] ; if( is_unsigned ){ return Rint64::internal::int64_as_character( x ) ; } else { return Rint64::internal::int64_as_character( x ) ; } } extern "C" SEXP int64_as_int64(SEXP x){ return Rint64::internal::as_long(x) ; } extern "C" SEXP int64_as_uint64(SEXP x){ return Rint64::internal::as_long(x) ; } extern "C" SEXP int64_arith_int64_int64(SEXP generic, SEXP e1, SEXP e2, SEXP unsign ) { const char* op = CHAR(STRING_ELT(generic, 0)) ; bool is_unsigned = INTEGER(unsign)[0] ; if( is_unsigned ){ return Rint64::internal::int64_arith__impl(op, e1, e2 ) ; } else { return Rint64::internal::int64_arith__impl(op, e1, e2 ) ; } } extern "C" SEXP int64_compare_int64_int64(SEXP generic, SEXP e1, SEXP e2, SEXP unsign) { const char* op = CHAR(STRING_ELT(generic, 0)) ; bool is_unsigned = INTEGER(unsign)[0]; if( is_unsigned ){ return Rint64::internal::int64_compare(op,e1,e2) ; } else { return Rint64::internal::int64_compare(op,e1,e2) ; } } extern "C" SEXP int64_summary_int64(SEXP generic, SEXP x, SEXP unsign){ const char* op = CHAR(STRING_ELT(generic, 0)) ; bool is_unsigned = INTEGER(unsign)[0] ; if( is_unsigned ){ return Rint64::internal::int64_summary(op, x ) ; } else { return Rint64::internal::int64_summary(op, x ) ; } } extern "C" SEXP int64_limits( SEXP type_ ){ const char* type = CHAR(STRING_ELT(type_, 0) ) ; if( !strncmp( type, "integer", 7 ) ){ SEXP res = PROTECT( Rf_allocVector(INTSXP, 2 ) ) ; INTEGER(res)[0] = std::numeric_limits::min() + 1 ; INTEGER(res)[1] = std::numeric_limits::max() ; UNPROTECT(1) ; return res ; } else if( ! strncmp( type, "int64", 5 ) ){ return Rint64::internal::new_long_2( Rint64::internal::long_traits::min() , Rint64::internal::long_traits::max() ) ; } else if( !strncmp( type, "uint64", 6 ) ){ return Rint64::internal::new_long_2( Rint64::internal::long_traits::min(), Rint64::internal::long_traits::max() ) ; } Rf_error( "unsupported type" ) ; return R_NilValue ; } extern "C" SEXP int64_sort( SEXP x, SEXP unsign, SEXP decr ){ bool is_unsigned = INTEGER(unsign)[0] ; bool decreasing = INTEGER(decr)[0] ; if( is_unsigned ){ return Rint64::LongVector(x).sort(decreasing ) ; } else { return Rint64::LongVector(x).sort(decreasing ) ; } } extern "C" SEXP int64_math( SEXP generic, SEXP x, SEXP unsign){ bool is_unsigned = INTEGER(unsign)[0]; const char* op = CHAR(STRING_ELT(generic, 0 ) ); if( is_unsigned ){ return Rint64::internal::math( op, x ) ; } else { return Rint64::internal::math( op, x ) ; } } extern "C" SEXP int64_signif( SEXP s_, SEXP digits_, SEXP len_){ std::string s ; int n = Rf_length(s_) ; int* digits = INTEGER(digits_) ; int* len = INTEGER(len_) ; SEXP res = PROTECT( Rf_allocVector( STRSXP, n ) ) ; for( int i=0; i len[i] ){ SET_STRING_ELT( res, i, STRING_ELT( s_, i ) ) ; } else { s = CHAR(STRING_ELT(s_, i )); for( int j=digits[i]; j( x_ ).is_na() ; } else { return Rint64::LongVector( x_ ).is_na() ; } } int64/R/0000755000175100001440000000000011665656774011464 5ustar hornikusersint64/R/int64.R0000644000175100001440000002361511664531377012550 0ustar hornikusers# Copyright (C) 2011 Romain Francois # Copyright (C) 2011 Google Inc. All rights reserved. # # This file is part of int64. # # int64 is free software: you can redistribute it and/or modify it # under the terms of the GNU General Public License as published by # the Free Software Foundation, either version 2 of the License, or # (at your option) any later version. # # int64 is distributed in the hope that it will be useful, but # WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with int64. If not, see . setClassUnion( "maybeNames", c("character", "NULL" ) ) names_int64 <- function(x){ x@NAMES } namesgets_int64 <- function( x, value){ if( missing(value) || is.null(value) ){ x@NAMES <- NULL } else if( is.character( value )){ if( length( value ) == length( x@.Data ) ){ x@NAMES <- value } else if(length(value) < length(x@.Data) ) { x@NAMES <- c( value, rep( NA, length(x@.Data) - length(value) ) ) } else { stop( "error assigning names" ) } } else { stop( "must be character vector or NULL" ) } x } setClass( "int64", contains = "list", representation( NAMES = "maybeNames") ) setClass( "uint64", contains = "list" , representation( NAMES = "maybeNames") ) setMethod( "names", "int64", names_int64 ) setMethod( "names<-", "int64", namesgets_int64 ) setMethod( "names", "uint64", names_int64 ) setMethod( "names<-", "uint64", namesgets_int64 ) setClass( "binary", representation( data = "character", bits = "integer" ) ) setGeneric( "binary", function(object) standardGeneric("binary") ) setMethod( "binary", "integer", function(object){ new( "binary", data = .Call( int64_format_binary, object ), bits = 32L ) } ) setMethod( "binary", "numeric", function(object){ new( "binary", data = .Call( int64_format_binary, object ), bits = 64L ) } ) setMethod( "binary", "int64", function(object){ new( "binary", data = .Call( int64_format_binary, object ), bits = 64L ) } ) setMethod( "binary", "uint64", function(object){ new( "binary", data = .Call( int64_format_binary, object ), bits = 64L ) } ) setMethod( "show", "binary", function(object){ print( noquote( object@data ) ) invisible(object) }) int64 <- function(length=0L){ x <- new("int64", rep( list(integer(2L)), length ) ) x } uint64 <- function(length=0L){ x <- new("uint64", rep( list(integer(2L)), length ) ) x } setMethod( "length", "int64", function(x){ length(x@.Data) } ) setMethod( "length", "uint64", function(x){ length(x@.Data) } ) show_int64 <- function(object){ if( !length(object)) { writeLines( sprintf( "%s(0)", class(object) ) ) } else { if( is.null( object@NAMES ) ){ print( noquote( as.character( object ) ) ) } else { x <- as.character( object ) names(x) <- object@NAMES print(noquote(x)) } } invisible(object) } setMethod( "show", "int64", show_int64) setMethod( "show", "uint64", show_int64) as.int64 <- function(x){ if( is.character(x) ){ wrong <- ! grepl("^[-]?[0-9]+$", x) if( any(wrong) ){ x[wrong] <- "NA" warning( "NAs introduced" ) } } new( "int64", .Call(int64_as_int64, x) ) } as.uint64 <- function(x){ if( is.character(x) ){ wrong <- ! grepl("^[0-9]+$", x) if( any(wrong) ){ x[wrong] <- "NA" warning( "NAs introduced" ) } } new( "uint64", .Call(int64_as_uint64, x) ) } setMethod( "[", "int64", function(x, i, j, ...){ new( "int64", x@.Data[ i ] ) } ) setMethod( "[", "uint64", function(x, i, j, ...){ new( "uint64", x@.Data[ i ] ) } ) setMethod( "[<-", "int64", function(x, i, j, ..., value ){ data <- x@.Data data[i] <- as.int64( value )@.Data new( "int64", data ) } ) setMethod( "[<-", "uint64", function(x, i, j, ..., value ){ data <- x@.Data data[i] <- as.uint64( value )@.Data new( "uint64", data ) } ) setMethod( "Arith", signature(e1 = "int64", e2 = "int64" ), function(e1,e2){ numbers <- .Call( int64_arith_int64_int64, .Generic, e1, e2, FALSE ) new( "int64", numbers ) } ) setMethod( "Arith", signature(e1 = "int64", e2 = "ANY" ), function(e1,e2){ numbers <- .Call( int64_arith_int64_int64, .Generic, e1, as.int64(e2), FALSE ) new( "int64", numbers ) } ) setMethod( "Arith", signature(e1 = "ANY", e2 = "int64" ), function(e1,e2){ numbers <- .Call( int64_arith_int64_int64, .Generic, as.int64(e1), e2, FALSE ) new( "int64", numbers ) } ) setMethod( "Arith", signature(e1 = "uint64", e2 = "uint64" ), function(e1,e2){ numbers <- .Call( int64_arith_int64_int64, .Generic, e1, e2, TRUE ) new( "uint64", numbers ) } ) setMethod( "Arith", signature(e1 = "uint64", e2 = "ANY" ), function(e1,e2){ numbers <- .Call( int64_arith_int64_int64, .Generic, e1, as.uint64(e2), TRUE ) new( "uint64", numbers ) } ) setMethod( "Arith", signature(e1 = "ANY", e2 = "uint64" ), function(e1,e2){ numbers <- .Call( int64_arith_int64_int64, .Generic, as.uint64(e1), e2, TRUE ) new( "uint64", numbers ) } ) setMethod( "Compare", signature(e1 = "int64", e2 = "int64" ), function(e1,e2){ .Call( int64_compare_int64_int64, .Generic, e1, e2, FALSE ) } ) setMethod( "Compare", signature(e1 = "ANY", e2 = "int64" ), function(e1,e2){ .Call( int64_compare_int64_int64, .Generic, as.int64(e1), e2, FALSE ) } ) setMethod( "Compare", signature(e1 = "int64", e2 = "ANY" ), function(e1,e2){ .Call( int64_compare_int64_int64, .Generic, e1, as.int64(e2), FALSE ) } ) setMethod( "Compare", signature(e1 = "uint64", e2 = "uint64" ), function(e1,e2){ .Call( int64_compare_int64_int64, .Generic, e1, e2, TRUE ) } ) setMethod( "Compare", signature(e1 = "ANY", e2 = "uint64" ), function(e1,e2){ .Call( int64_compare_int64_int64, .Generic, as.uint64(e1), e2, TRUE ) } ) setMethod( "Compare", signature(e1 = "uint64", e2 = "ANY" ), function(e1,e2){ .Call( int64_compare_int64_int64, .Generic, e1, as.uint64(e2), TRUE) } ) setMethod( "Summary", "int64", function(x,..., na.rm = FALSE){ .Call( int64_summary_int64, .Generic, x, FALSE) } ) setMethod( "Summary", "uint64", function(x,..., na.rm = FALSE){ .Call( int64_summary_int64, .Generic, x, TRUE) } ) setMethod( "as.character", "int64", function(x,...){ .Call( int64_as_character_int64, x, FALSE) }) setMethod( "as.character", "uint64", function(x,...){ .Call( int64_as_character_int64, x, TRUE) }) as.data.frame.int64 <- as.data.frame.uint64 <- as.data.frame.vector format.int64 <- format.uint64 <- function(x, ...){ as.character(x) } numeric_limits <- function( type ){ .Call( int64_limits, type ) } setGeneric( "unique" ) setMethod( "unique", "int64", function(x, incomparables = FALSE, ...){ new( "int64", .Data = unique( x@.Data, incomparables, ... ) ) } ) setMethod( "unique", "uint64", function(x, incomparables = FALSE, ...){ new( "uint64", .Data = unique( x@.Data, incomparables, ... ) ) } ) setGeneric( "sort" ) setMethod( "sort", "int64", function(x, decreasing = FALSE, ...){ .Call( int64_sort, x, FALSE, decreasing ) } ) setMethod( "sort", "uint64", function(x, decreasing = FALSE, ...){ .Call( int64_sort, x, TRUE, decreasing ) } ) setMethod( "Math", "int64", function(x){ .Call( int64_math, .Generic, x, FALSE) } ) setMethod( "Math", "uint64", function(x){ .Call( int64_math, .Generic, x, TRUE ) } ) # implementation of signif using string maniplation int64_Math2 <- function( type = "int64", .Generic, x, digits ){ if( .Generic == "round" ) x else{ if( any(digits<0 ) ) stop("digits must be positive") # signif s <- as.character( x ) len <- nchar( s ) signs <- ! grepl( "^-", s ) s <- sub( "^-", "", s ) # recycling digits <- as.integer( rep( digits, length = length( s ) ) ) digits[ digits == 0L ] <- 1L res <- .Call( int64_signif, s, digits, len ) res <- sprintf( "%s%s", ifelse(signs, "", "-"), res ) if( type == "int64" ) as.int64(res) else as.uint64(res) } } setMethod( "Math2", "int64", function(x, digits = 6L){ int64_Math2( "int64", .Generic, x, digits ) } ) setMethod( "Math2", "uint64", function(x, digits = 6L){ int64_Math2( "uint64", .Generic, x, digits ) } ) setMethod( "is.na", "int64", function(x){ .Call( int64_isna, x, FALSE ) }) setMethod( "is.na", "uint64", function(x){ .Call( int64_isna, x, TRUE ) }) c_int64 <- function(as, ctor){ function(x, ..., recursive = FALSE ){ dots <- list(...) if( !length(dots) ) return(x) dots <- lapply( dots, function(x) as(x)@.Data ) n <- length(x) + sum( sapply( dots, length ) ) res <- ctor(n) res@.Data[ 1:length(x) ] <- x@.Data start <- length(x)+1L for( i in 1:length(dots)){ data <- dots[[i]] res@.Data[ start:(start+length(data)-1L) ] <- data start <- start + length(data) } res } } setMethod( "c", "int64", c_int64( as.int64, int64 ) ) setMethod( "c", "uint64", c_int64( as.uint64, uint64 ) ) setAs("character", "int64", function(from) as.int64(from)) setAs("character", "uint64", function(from) as.uint64(from)) setAs("integer", "int64", function(from) as.int64(from)) setAs("integer", "uint64", function(from) as.uint64(from)) setAs("logical", "int64", function(from) as.int64(from)) setAs("logical", "uint64", function(from) as.uint64(from)) setAs("numeric", "int64", function(from) as.int64(from)) setAs("numeric", "uint64", function(from) as.uint64(from)) str.int64 <- str.uint64 <- function(object, ...){ writeLines( sprintf( " %s [1:%d] %s ...", class(object), length(object), paste( as.character( head( object, 3 ) ), collapse = " " ) ) ) } int64/NAMESPACE0000644000175100001440000000076711664531377012502 0ustar hornikusersuseDynLib( int64, .registration = TRUE ) import( methods ) exportClasses( "int64", "uint64", "binary" ) exportMethods( show, length, "[", Arith, Compare, Summary, Math, Math2, as.character, names, "names<-", binary, unique, sort, is.na, c ) export( int64, uint64, as.int64, as.uint64, numeric_limits ) S3method( format, int64 ) S3method( format, uint64 ) S3method( as.data.frame , int64 ) S3method( as.data.frame , uint64 ) S3method( str, int64 ) S3method( str, uint64 ) int64/man/0000755000175100001440000000000011665656774012036 5ustar hornikusersint64/man/unique-methods.Rd0000644000175100001440000000135311660746102015252 0ustar hornikusers\name{unique-methods} \docType{methods} \alias{unique-methods} \alias{unique,ANY-method} \alias{unique,int64-method} \alias{unique,uint64-method} \title{Unique implementation for 64 bit integer vectors} \description{ Implementation of \code{\link{unique}} for 64 bit integer vectors } \section{Methods}{ \describe{ \item{\code{signature(x = "ANY")}}{default implementation (from base)} \item{\code{signature(x = "int64")}}{ signed 64 bit integer vectors. \code{\linkS4class{int64}} } \item{\code{signature(x = "uint64")}}{ unsigned 64 bit integer vectors. \code{\linkS4class{uint64}} } }} \keyword{methods} \examples{ x <- as.int64( c(1:5, 1L, 5L) ) unique( x ) x <- as.uint64( c(1:5, 1L, 5L) ) unique( x ) } int64/man/uint64.Rd0000644000175100001440000000131111663177026013434 0ustar hornikusers\name{uint64} \alias{uint64} \title{ Creates new uint64 vectors of a given length } \description{ Creates new \code{\linkS4class{uint64}} vectors of a given length } \usage{ uint64(length = 0L) } \arguments{ \item{length}{ Length of the resulting vector } } \value{ A new \code{\linkS4class{uint64}} vector of the given length } \author{ Romain Francois, Sponsored by the Google Open Source Programs Office } \seealso{ \code{\link{as.uint64}} for converting integer or character vectors into \code{\linkS4class{uint64}} vectors. \code{\link{int64}} for signed 64 bit integer vectors, i.e. of class \code{\linkS4class{int64}}. } \examples{ x <- uint64(10L) } \keyword{manip} int64/man/uint64-class.Rd0000644000175100001440000000603711662667471014560 0ustar hornikusers\name{uint64-class} \Rdversion{1.1} \docType{class} \alias{uint64-class} \alias{Math,uint64-method} \alias{Math2,uint64-method} \alias{[,uint64-method} \alias{[<-,uint64-method} \alias{Arith,ANY,uint64-method} \alias{Arith,uint64,ANY-method} \alias{Arith,uint64,uint64-method} \alias{as.character,uint64-method} \alias{names,uint64-method} \alias{names<-,uint64-method} \alias{Compare,ANY,uint64-method} \alias{Compare,uint64,ANY-method} \alias{Compare,uint64,uint64-method} \alias{length,uint64-method} \alias{show,uint64-method} \alias{Summary,uint64-method} \alias{c,uint64-method} \alias{is.na,uint64-method} \title{Class \code{"uint64"}} \description{ Vector of signed 64 bit integers } \section{Objects from the Class}{ Objects can be created by using the \code{\link{uint64}} function, by converting character vectors or integer vectors using the \code{\link{as.uint64}} function. } \section{Slots}{ \describe{ \item{\code{.Data}:}{list of integer vectors of length 2. Each uint64 number is coded as two integers. } \item{\code{NAMES}:}{Used for names of vectors. This is only being used through the \code{names} and \code{names<-} functions. } } } \section{Extends}{ Class \code{"\linkS4class{list}"}, from data part. Class \code{"\linkS4class{vector}"}, by class "list", distance 2. } \section{Methods}{ \describe{ \item{[}{\code{signature(x = "uint64")}: ... } \item{[<-}{\code{signature(x = "uint64")}: ... } \item{Arith}{\code{signature(e1 = "ANY", e2 = "uint64")}: ... } \item{Arith}{\code{signature(e1 = "uint64", e2 = "ANY")}: ... } \item{Arith}{\code{signature(e1 = "uint64", e2 = "uint64")}: ... } \item{as.character}{\code{signature(x = "uint64")}: ... } \item{Compare}{\code{signature(e1 = "ANY", e2 = "uint64")}: ... } \item{Compare}{\code{signature(e1 = "uint64", e2 = "ANY")}: ... } \item{Compare}{\code{signature(e1 = "uint64", e2 = "uint64")}: ... } \item{length}{\code{signature(x = "uint64")}: ... } \item{Summary}{\code{signature(x = "uint64")}: ... } \item{Math}{\code{signature(x = "uint64")}: ... } \item{Math2}{\code{signature(x = "uint64")}: ... } \item{c}{\code{signature(x = "uint64")}: ... } \item{is.na}{\code{signature(x = "uint64")}: ... } } } \author{ Romain Francois. Sponsored the Google Open Source Programs Office. } \seealso{ \code{\link{as.uint64}} to convert character or integer vectors. \code{\link{uint64}} to create new \code{\linkS4class{uint64}} vectors of a given size. The \code{\linkS4class{int64}} class to represent signed 64 bit integer vectors. } \examples{ x <- uint64( 4 ) # setting subsets x[1:2] <- 1:2 x[3:4] <- c("123456789012345", "9876543219876") x # arithmetic operations x * 2L x + x x - 3L # logical operations x < 3L x != c( 1L, 2L ) # Summary operations range( x ) min( x ) max( x ) length(x) df <- data.frame( a = 1:4 ) df$b <- x df as.character( x ) } \keyword{classes} int64/man/sort-methods.Rd0000644000175100001440000000107311660746102014732 0ustar hornikusers\name{sort-methods} \docType{methods} \alias{sort-methods} \alias{sort,ANY-method} \alias{sort,int64-method} \alias{sort,uint64-method} \title{Sorting 64 bits integer vector} \description{ Sorting 64 bits integer vector } \section{Methods}{ \describe{ \item{\code{signature(x = "ANY")}}{ Standard method (from base) } \item{\code{signature(x = "int64")}}{ Sorting signed 64 bit integer vectors (\code{\linkS4class{int64}} } \item{\code{signature(x = "uint64")}}{ Sorting unsigned 64 bit integer vectors (\code{\linkS4class{uint64}} } }} \keyword{methods} int64/man/numeric_limits.Rd0000644000175100001440000000076011660746102015327 0ustar hornikusers\name{numeric_limits} \alias{numeric_limits} \title{ Give numeric limits of integer types } \description{ Give numeric limits of integer types } \usage{ numeric_limits(type) } \arguments{ \item{type}{type. must be integer, int64 or uint64. } } \value{ A vector of two values of the appropriate type. } \author{ Romain Francois, sponsored by the Google Open Source Programs Office } \examples{ numeric_limits( "integer" ) numeric_limits( "int64" ) numeric_limits( "uint64" ) } \keyword{manip} int64/man/int64.Rd0000644000175100001440000000130311662667262013255 0ustar hornikusers\name{int64} \alias{int64} \title{ Creates new int64 vectors of a given length } \description{ Creates new \code{\linkS4class{int64}} vectors of a given length } \usage{ int64(length = 0L) } \arguments{ \item{length}{ Length of the resulting vector } } \value{ A new \code{\linkS4class{int64}} vector of the given length } \author{ Romain Francois, Sponsored by the Google Open Source Programs Office } \seealso{ \code{\link{as.int64}} for converting integer or character vectors into \code{\linkS4class{int64}} vectors. \code{\link{uint64}} for unsigned 64 bit integer vectors, i.e. of class \code{\linkS4class{uint64}} } \examples{ x <- int64(10L) } \keyword{manip} int64/man/int64-package.Rd0000644000175100001440000000103211665622021014630 0ustar hornikusers\name{int64-package} \alias{int64-package} \docType{package} \title{ 64 bit integer types } \description{ 64 bit integer types } \details{ \tabular{ll}{ Package: \tab int64\cr Type: \tab Package\cr Version: \tab 1.1.2\cr Date: \tab 2011-12-01\cr License: \tab GPL (>= 2)\cr LazyLoad: \tab yes\cr } } \author{ Romain Francois, Sponsored by Google Open Source Programs Office Maintainer: Romain Francois } \examples{ as.int64( 1:4 ) as.int64( c("123456789", "9876543219876543" ) ) } \keyword{ package } int64/man/int64-class.Rd0000644000175100001440000000634311662667417014373 0ustar hornikusers\name{int64-class} \Rdversion{1.1} \docType{class} \alias{int64-class} \alias{[,int64-method} \alias{Math,int64-method} \alias{Math2,int64-method} \alias{[<-,int64-method} \alias{Arith,ANY,int64-method} \alias{Arith,int64,ANY-method} \alias{Arith,int64,int64-method} \alias{as.character,int64-method} \alias{names,int64-method} \alias{names<-,int64-method} \alias{Compare,ANY,int64-method} \alias{Compare,int64,ANY-method} \alias{Compare,int64,int64-method} \alias{length,int64-method} \alias{show,int64-method} \alias{Summary,int64-method} \alias{c,int64-method} \alias{is.na,int64-method} \title{Class \code{"int64"}} \description{ Vector of signed 64 bit integers } \section{Objects from the Class}{ Objects can be created by using the \code{\link{int64}} function, by converting character vectors or integer vectors using the \code{\link{as.int64}} function. } \section{Slots}{ \describe{ \item{\code{.Data}:}{list of integer vectors of length 2. Each int64 number is coded as two integers. } \item{\code{NAMES}:}{Used for names of vectors. This is only being used through the \code{names} and \code{names<-} functions. } } } \section{Extends}{ Class \code{"\linkS4class{list}"}, from data part. Class \code{"\linkS4class{vector}"}, by class "list", distance 2. } \section{Methods}{ \describe{ \item{[}{\code{signature(x = "int64")}: ... } \item{[<-}{\code{signature(x = "int64")}: ... } \item{Arith}{\code{signature(e1 = "ANY", e2 = "int64")}: ... } \item{Arith}{\code{signature(e1 = "int64", e2 = "ANY")}: ... } \item{Arith}{\code{signature(e1 = "int64", e2 = "int64")}: ... } \item{as.character}{\code{signature(x = "int64")}: ... } \item{Compare}{\code{signature(e1 = "ANY", e2 = "int64")}: ... } \item{Compare}{\code{signature(e1 = "int64", e2 = "ANY")}: ... } \item{Compare}{\code{signature(e1 = "int64", e2 = "int64")}: ... } \item{length}{\code{signature(x = "int64")}: ... } \item{Summary}{\code{signature(x = "int64")}: ... } \item{Math}{\code{signature(x = "int64")}: ... } \item{Math2}{\code{signature(x = "int64")}: ... } \item{c}{\code{signature(x = "int64")}: ... } \item{is.na}{\code{signature(x = "int64")}: ... } } } \author{ Romain Francois. Sponsored the Google Open Source Programs Office. } \seealso{ \code{\link{as.int64}} to convert character or integer vectors. \code{\link{int64}} to create new \code{\linkS4class{int64}} vectors of a given size. The \code{\linkS4class{uint64}} class to represent unsigned 64 bit integer vectors. } \examples{ x <- int64( 4 ) # setting subsets x[1:2] <- 1:2 x[3:4] <- c("123456789012345", "9876543219876") x # arithmetic operations x * 2L x + x x - 3L # arithmetic operations first convert both operands to 64 bit integer type # so some precision will be lost as.int64(1) + 1.5 # but it feels appropriate for dealing with large values as.int64(43124567245667) + 1.5 # logical operations x < 3L x != c( 1L, 2L ) # Summary operations range( x ) min( x ) max( x ) length(x) df <- data.frame( a = 1:4 ) df$b <- x df as.character( x ) } \keyword{classes} int64/man/binary-methods.Rd0000644000175100001440000000143211660746102015226 0ustar hornikusers\name{binary-methods} \docType{methods} \alias{binary} \alias{binary-methods} \alias{binary,integer-method} \alias{binary,int64-method} \alias{binary,uint64-method} \alias{binary,numeric-method} \title{Get binary representation} \description{ Get binary representation } \section{Methods}{ \describe{ \item{\code{signature(object = "integer")}}{ Method for integer Vectors } \item{\code{signature(object = "int64")}}{ Method for \code{\linkS4class{int64}} vectors } \item{\code{signature(object = "uint64")}}{ Method for \code{\linkS4class{uint64}} vectors } \item{\code{signature(object = "numeric")}}{ Method for numeric vectors } }} \examples{ binary( 1:4 ) binary( c( 1.0, 2.0 ) ) binary( as.int64( 1:4 ) ) binary( as.uint64( 1:4 ) ) } \keyword{methods} int64/man/binary-class.Rd0000644000175100001440000000122011660746102014663 0ustar hornikusers\name{binary-class} \Rdversion{1.1} \docType{class} \alias{binary-class} \alias{show,binary-method} \title{Class \code{"binary"}} \description{ Binary representation } \section{Objects from the Class}{ Objects can be created by one of the forms of the \code{\link{binary}} methods. } \section{Slots}{ \describe{ \item{\code{data}:}{Character vectors, with 0 and 1} \item{\code{bits}:}{Number of bits} } } \section{Methods}{ \describe{ \item{show}{\code{signature(object = "binary")}: display method } } } \author{ Romain Francois, sponsored by the Google Open Source Programs Office } \examples{ binary( 1:4 ) } \keyword{classes} int64/man/as.uint64.Rd0000644000175100001440000000145511660746102014041 0ustar hornikusers\name{as.uint64} \alias{as.uint64} \title{ Convert character or integer vectors into uint64 vectors. } \description{ Convert character or integer vectors into \code{\linkS4class{uint64}} vectors. } \usage{ as.uint64(x) } \arguments{ \item{x}{ A character or integer vector } } \details{ For conversion of character vectors, the C function \code{atol} is used. } \value{ A new \code{\linkS4class{int64}} vector. } \references{ C++ \code{atol} function: \url{http://www.cplusplus.com/reference/clibrary/cstdlib/atol/} } \seealso{ \code{\link{as.int64}} for conversion to signed long vectors. } \author{ Romain Francois, sponsored by the Google Open Source Programs Office } \examples{ as.uint64( c(1L, 2L ) ) as.uint64( c("123456789123456", "987654321987654" ) ) } \keyword{manip} int64/man/as.int64.Rd0000644000175100001440000000145111660746102013650 0ustar hornikusers\name{as.int64} \alias{as.int64} \title{ Convert character or integer vectors into int64 vectors. } \description{ Convert character or integer vectors into \code{\linkS4class{int64}} vectors. } \usage{ as.int64(x) } \arguments{ \item{x}{ A character or integer vector } } \details{ For conversion of character vectors, the C function \code{atol} is used. } \value{ A new \code{\linkS4class{int64}} vector. } \references{ C++ \code{atol} function: \url{http://www.cplusplus.com/reference/clibrary/cstdlib/atol/} } \seealso{ \code{\link{as.uint64}} for conversion to unsigned long vectors. } \author{ Romain Francois, sponsored by the Google Open Source Programs Office } \examples{ as.int64( c(1L, 2L ) ) as.int64( c("123456789123456", "987654321987654" ) ) } \keyword{manip} int64/inst/0000755000175100001440000000000011665656774012240 5ustar hornikusersint64/inst/unitTests/0000755000175100001440000000000011665656774014242 5ustar hornikusersint64/inst/unitTests/runTests.R0000644000175100001440000001305111660746102016170 0ustar hornikusers## Copyright (C) 2011 Romain Francois ## Copyright (C) 2011 Google Inc. All rights reserved. ## ## This file is part of int64. ## ## int64 is free software: you can redistribute it and/or modify it ## under the terms of the GNU General Public License as published by ## the Free Software Foundation, either version 2 of the License, or ## (at your option) any later version. ## ## int64 is distributed in the hope that it will be useful, but ## WITHOUT ANY WARRANTY; without even the implied warranty of ## MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the ## GNU General Public License for more details. ## ## You should have received a copy of the GNU General Public License ## along with int64. If not, see . pkg <- "int64" if(require("RUnit", quietly = TRUE)) { is_local <- function(){ if( exists( "argv", globalenv() ) && "--local" %in% argv ) return(TRUE) if( "--local" %in% commandArgs(TRUE) ) return(TRUE) FALSE } if (is_local() ) path <- getwd() library(package=pkg, character.only = TRUE) if(!(exists("path") && file.exists(path))) path <- system.file("unitTests", package = pkg) ## --- Testing --- ## Define tests testSuite <- defineTestSuite(name=paste(pkg, "unit testing"), dirs = path # , testFileRegexp = "Vector" ) ## this is crass but as we time out on Windows we have no choice ## but to disable a number of tests ## TODO: actually prioritize which ones we want allTests <- function() { if (.Platform$OS.type != "windows") return(TRUE) if (exists( "argv", globalenv() ) && "--allTests" %in% argv) return(TRUE) if ("--allTests" %in% commandArgs(TRUE)) return(TRUE) return(FALSE) } ## if (.Platform$OS.type == "windows" && allTests() == FALSE) { ## ## by imposing [D-Z] (instead of an implicit A-Z) we are going from ## ## 45 tests to run down to 38 (numbers as of release 0.8.3) ## testSuite$testFileRegexp <- "^runit.[D-Z]+\\.[rR]$" ## } if (interactive()) { cat("Now have RUnit Test Suite 'testSuite' for package '", pkg, "' :\n", sep='') str(testSuite) cat('', "Consider doing", "\t tests <- runTestSuite(testSuite)", "\nand later", "\t printTextProtocol(tests)", '', sep="\n") } else { ## run from shell / Rscript / R CMD Batch / ... ## Run tests <- runTestSuite(testSuite) output <- NULL process_args <- function(argv){ if( !is.null(argv) && length(argv) > 0 ){ rx <- "^--output=(.*)$" g <- grep( rx, argv, value = TRUE ) if( length(g) ){ sub( rx, "\\1", g[1L] ) } } } # R CMD check uses this if( exists( "int64.unit.test.output.dir", globalenv() ) ){ output <- int64.unit.test.output.dir } else { ## give a chance to the user to customize where he/she wants ## the unit tests results to be stored with the --output= command ## line argument if( exists( "argv", globalenv() ) ){ ## littler output <- process_args(argv) } else { ## Rscript output <- process_args(commandArgs(TRUE)) } } # if it did not work, try to use /tmp if( is.null(output) ){ if( file.exists( "/tmp" ) ){ output <- "/tmp" } else{ output <- getwd() } } ## Print results output.txt <- file.path( output, sprintf("%s-unitTests.txt", pkg)) output.html <- file.path( output, sprintf("%s-unitTests.html", pkg)) printTextProtocol(tests, fileName=output.txt) message( sprintf( "saving txt unit test report to '%s'", output.txt ) ) ## Print HTML version to a file ## printHTMLProtocol has problems on Mac OS X if (Sys.info()["sysname"] != "Darwin"){ message( sprintf( "saving html unit test report to '%s'", output.html ) ) printHTMLProtocol(tests, fileName=output.html) } ## stop() if there are any failures i.e. FALSE to unit test. ## This will cause R CMD check to return error and stop err <- getErrors(tests) if( (err$nFail + err$nErr) > 0) { data <- Filter( function(x) any( sapply(x, function(.) .[["kind"]] ) %in% c("error","failure") ) , tests[[1]]$sourceFileResults ) err_msg <- sapply( data, function(x) { raw.msg <- paste( sapply( Filter( function(.) .[["kind"]] %in% c("error","failure"), x ), "[[", "msg" ), collapse = " // " ) raw.msg <- gsub( "Error in compileCode(f, code, language = language, verbose = verbose) : \n", "", raw.msg, fixed = TRUE ) raw.msg <- gsub( "\n", "", raw.msg, fixed = TRUE ) raw.msg } ) msg <- sprintf( "unit test problems: %d failures, %d errors\n%s", err$nFail, err$nErr, paste( err_msg, collapse = "\n" ) ) stop( msg ) } else{ success <- err$nTestFunc - err$nFail - err$nErr - err$nDeactivated cat( sprintf( "%d / %d\n", success, err$nTestFunc ) ) } } } else { cat("R package 'RUnit' cannot be loaded -- no unit tests run\n", "for package", pkg,"\n") } int64/inst/unitTests/runit.int64.R0000644000175100001440000001050511663402306016444 0ustar hornikusers# Copyright (C) 2011 Romain Francois # Copyright (C) 2011 Google Inc. All rights reserved. # # This file is part of int64. # # int64 is free software: you can redistribute it and/or modify it # under the terms of the GNU General Public License as published by # the Free Software Foundation, either version 2 of the License, or # (at your option) any later version. # # int64 is distributed in the hope that it will be useful, but # WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with int64. If not, see . test.int64 <- function(){ ints <- c(-122L, 0L, 1L, 122L) x <- as.int64(ints) checkEquals( as.integer(as.character(x)), ints ) checkEquals( as.character(x+1L), as.character(ints+1L) ) checkEquals( as.character(x-1L), as.character(ints-1L) ) checkEquals( as.character(x*x), as.character(ints*ints) ) checkEquals( as.character(x/2L), as.character(as.integer(ints/2L)) ) checkEquals( x > 0L, ints > 0L ) checkEquals( x < 0L, ints < 0L ) checkEquals( x == 0L, ints == 0L ) checkEquals( x != 0L, ints != 0L ) checkEquals( x <= 0L, ints <= 0L ) checkEquals( x >= 0L, ints >= 0L ) checkEquals( range(x), as.int64(c(-122L, 122L)) ) checkEquals( min(x), as.int64(-122L) ) checkEquals( max(x), as.int64(122L) ) checkEquals( prod(x), as.int64(as.integer(prod(ints))) ) checkEquals( sum(x), as.int64(as.integer(sum(ints))) ) checkEquals( any(x), any(ints) ) checkEquals( all(x), all(ints) ) chars <- c( "-9223372036854775807", "9223372036854775807" ) x <- as.int64( chars ) checkEquals( as.character(x), chars ) } test.uint64 <- function(){ ints <- c(0L, 1L, 123L) x <- as.uint64(ints) checkEquals( as.integer(as.character(x)), ints ) chars <- c( "123456789123456789", "18446744073709551614" ) x <- as.uint64( chars ) checkEquals( as.character(x), chars ) } test.unique.int64 <- function(){ x <- as.int64( c(1:5, 1L, 3L) ) checkEquals( unique(x), as.int64(1:5) ) x <- as.uint64( c(1:5, 1L, 3L) ) checkEquals( unique(x), as.uint64(1:5) ) } test.sort <- function( ){ x <- as.int64( c(1:4, 3L ) ) checkEquals( sort( x ), as.int64( c(1:3,3L,4L) ) ) checkEquals( sort( x, decreasing = TRUE), as.int64( c(4L,3L,3:1) ) ) x <- as.uint64( c(1:4, 3L ) ) checkEquals( sort( x ), as.uint64( c(1:3,3L,4L) ) ) checkEquals( sort( x, decreasing = TRUE), as.uint64( c(4L,3L,3:1) ) ) } test.signif <- function(){ x <- as.int64( c( "12345", "12345", "12345" ) ) checkEquals( signif( x, c(2,3,7) ), as.int64( c("12000", "12300", "12345") ) ) x <- as.uint64( c( "12345", "12345", "12345" ) ) checkEquals( signif( x, c(2,3,7) ), as.uint64( c("12000", "12300", "12345") ) ) } test.names <- function(){ x <- as.int64( 1:5 ) checkTrue( is.null(names(x) ) ) names <- letters[1:5] names(x) <- names checkEquals( names(x), letters[1:5] ) names(x) <- NULL checkTrue( is.null(names(x) ) ) x <- as.uint64( 1:5 ) checkTrue( is.null(names(x) ) ) names <- letters[1:5] names(x) <- names checkEquals( names(x), letters[1:5] ) names(x) <- NULL checkTrue( is.null(names(x) ) ) } test.na <- function(){ old.op <- options( warn = 2 ) checkException( as.int64( "abcd12434" ) ) checkException( as.uint64( "abcd12434" ) ) checkEquals( as.int64("1234"), as.int64(1234)) checkEquals( as.uint64("1234"), as.uint64(1234)) options( old.op ) } test.dataframe <- function(){ df <- data.frame( a = 1:4 ) df$b <- as.int64( 1:4 ) df$c <- as.uint64( 1:4 ) checkEquals( df$b[3:4], df$b[1:2] + 2L ) checkEquals( df$c[3:4], df$c[1:2] + 2L ) } test.read.csv <- function(){ df <- data.frame( x = 1:10, y = 1:10, z = 1:10 ) tf <- tempfile() write.table( df, tf, row.names = FALSE, sep = "," ) df <- read.csv( tf, header = TRUE, colClasses = c( "integer", "int64", "uint64" ) ) checkEquals( df$x, 1:10 ) checkEquals( df$y, as.int64(1:10) ) checkEquals( df$z, as.uint64(1:10) ) } int64/inst/NEWS0000644000175100001440000000051711664531377012730 0ustar hornikusers1.1.1 2011-11-27 o str methods for [u]int64 classes. Requested by @hadleywickham o log and log10 method for [u]int64 classes. Requested by @hadleywickham 1.1.0 2011-11-24 o Implemented setAs so that read.csv can handle colClasses = "int64" and "uint64" using Gabor Grothendieck suggestion on R-devel int64/inst/include/0000755000175100001440000000000011665656774013663 5ustar hornikusersint64/inst/include/int64.h0000644000175100001440000000206211660746102014754 0ustar hornikusers// int64.h : 64 bit integers // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #ifndef int64__h #define int64__h #define R_NO_REMAP #include #include #include // replace with cstdint if newer C++ standard used #include // for numeric_limits #include #include #include #endif int64/inst/include/int64/0000755000175100001440000000000011665656774014627 5ustar hornikusersint64/inst/include/int64/summary.h0000644000175100001440000001306411661703756016466 0ustar hornikusers// summary.h : 64 bit integers // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #ifndef int64__summary__h #define int64__summary__h namespace Rint64{ namespace internal{ template SEXP summary__min( const Rint64::LongVector& data){ const LONG na = long_traits::na() ; LONG x = data.get(0) ; if( x == na ) return Rint64::internal::new_long( na ) ; LONG tmp = x ; int n = data.size() ; for( int i=1; i( x ) ; } template SEXP summary__max( const Rint64::LongVector& data){ const LONG na = long_traits::na() ; LONG x = data.get(0) ; LONG tmp = x ; int n = data.size() ; for( int i=1; i x ) x = tmp ; } return Rint64::internal::new_long( x ) ; } template SEXP summary__range( const Rint64::LongVector& data){ const LONG na = long_traits::na() ; LONG min = data.get(0) ; LONG max = data.get(0) ; if( min == na ) return Rint64::internal::new_long_2( na, na) ; LONG tmp = min ; int n = data.size() ; for( int i=1; i max ) max = tmp ; } return Rint64::internal::new_long_2( min, max) ; } template SEXP summary__prod( const Rint64::LongVector& data){ const LONG na = long_traits::na() ; LONG res = data.get(0) ; if( res == na ) return Rint64::internal::new_long( na ) ; int n = data.size() ; int64_naflag = false ; for( int i=1; i( res, data.get(i) ); if( res == na) break ; } if( int64_naflag ) Rf_warning( "NAs introduced by overflow" ) ; return Rint64::internal::new_long( res ) ; } template SEXP summary__sum( const Rint64::LongVector& data){ const LONG na = long_traits::na() ; LONG res = data.get(0) ; if( res == na ) return Rint64::internal::new_long( na ) ; int n = data.size() ; int64_naflag = false ; for( int i=1; i( res, data.get(i) ) ; if( res == na ) break ; } if( int64_naflag ) Rf_warning( "NAs introduced by overflow" ) ; return Rint64::internal::new_long( res ) ; } template SEXP summary__any( const Rint64::LongVector& data){ const LONG na = long_traits::na() ; int n = data.size() ; int res = 0 ; bool seen_na = false ; LONG tmp ; for( int i=0; i SEXP summary__all( const Rint64::LongVector& data){ const LONG na = long_traits::na() ; int n = data.size() ; int res = 1 ; LONG tmp ; bool seen_na = false ; for( int i=0; i SEXP int64_summary(const char* op, SEXP x){ Rint64::LongVector data( x ) ; if( ! strncmp(op, "min", 3) ){ return Rint64::internal::summary__min( data ) ; } else if( !strncmp(op, "max", 3) ){ return Rint64::internal::summary__max( data ) ; } else if( !strncmp(op, "range", 5 ) ){ return Rint64::internal::summary__range( data ) ; } else if( !strncmp(op, "prod", 4) ){ return Rint64::internal::summary__prod( data ) ; } else if( !strncmp(op, "sum", 3 ) ) { return Rint64::internal::summary__sum( data ) ; } else if( !strncmp(op, "any", 3 ) ){ return Rint64::internal::summary__any( data ) ; } else if( !strncmp(op, "all", 3) ){ return Rint64::internal::summary__all( data ) ; } Rf_error( "unknown operator" ) ; return R_NilValue ; } } // namespace internal } // namespace Rint64 #endif int64/inst/include/int64/routines.h0000644000175100001440000000330311660746102016623 0ustar hornikusers// routines.h: int64 64 bit integers - .Call exports // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #ifndef int64_routines_h #define int64_routines_h #define CALLFUN_0(name) SEXP name() #define CALLFUN_1(name) SEXP name(SEXP) #define CALLFUN_2(name) SEXP name(SEXP,SEXP) #define CALLFUN_3(name) SEXP name(SEXP,SEXP,SEXP) #define CALLFUN_4(name) SEXP name(SEXP,SEXP,SEXP,SEXP) #define CALLFUN_5(name) SEXP name(SEXP,SEXP,SEXP,SEXP,SEXP) #define EXTFUN(name) SEXP name(SEXP) // we have to do the ifdef __cplusplus dance because this file // is included both in C and C++ files #ifdef __cplusplus extern "C" { #endif CALLFUN_1(int64_as_int64) ; CALLFUN_1(int64_format_binary) ; CALLFUN_2(int64_as_character_int64) ; CALLFUN_4(int64_arith_int64_int64) ; CALLFUN_4(int64_compare_int64_int64) ; CALLFUN_3(int64_summary_int64) ; CALLFUN_1(int64_as_uint64) ; CALLFUN_1(int64_limits) ; CALLFUN_3(int64_sort) ; CALLFUN_3(int64_math) ; CALLFUN_3(int64_signif) ; CALLFUN_2(int64_isna) ; #ifdef __cplusplus } #endif #endif int64/inst/include/int64/read_string_forward.h0000644000175100001440000000207611661703756021017 0ustar hornikusers// read_string_forward.h : 64 bit integers // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #ifndef int64__read_string_forward_h #define int64__read_string_forward_h namespace Rint64{ namespace internal{ template inline LONG read_string(const char* s) ; } // namespace internal } // namespace Rint64 #endif int64/inst/include/int64/read_string.h0000644000175100001440000000310211661703756017262 0ustar hornikusers// read_string.h : 64 bit integers // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #ifndef int64__read_string__h #define int64__read_string__h namespace Rint64{ namespace internal{ template <> inline int64_t read_string(const char* s ){ errno = 0 ; int64_t res = strtoll( s, NULL, 0 ) ; if( errno == ERANGE ) { res = Rint64::LongVector::na() ; int64_naflag = true ; } return res ; } template <> inline uint64_t read_string(const char* s){ errno = 0 ; uint64_t res = strtoull( s, NULL, 0 ) ; if( errno == ERANGE ) { res = Rint64::LongVector::na() ; int64_naflag = true ; } return res ; } } // namespace internal } // namespace Rint64 #endif int64/inst/include/int64/math.h0000644000175100001440000001355411665622053015720 0ustar hornikusers// math.h : 64 bit integers // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #ifndef int64__math__h #define int64__math__h namespace Rint64{ namespace internal{ template SEXP abs( SEXP x ){ const LONG na = long_traits::na() ; Rint64::LongVector data(x) ; int n = data.size() ; LONG tmp ; Rint64::LongVector res(n) ; for( int i=0; i 0 ? tmp : -tmp ) ; } return res ; } template <> inline SEXP abs( SEXP x ){ return x ; } template SEXP sign( SEXP x){ const LONG na = long_traits::na() ; Rint64::LongVector data(x) ; int n = data.size() ; LONG tmp ; SEXP res = PROTECT(Rf_allocVector(REALSXP,n)) ; double* p_res = REAL(res) ; for( int i=0; i 0 ) ? 0.0 : 1.0 ; } } UNPROTECT(1) ; return res ; } template SEXP cummax( SEXP x){ const LONG na = long_traits::na() ; Rint64::LongVector data(x) ; int n = data.size() ; Rint64::LongVector res(n, na) ; LONG max = data.get(0) ; res.set( 0, max) ; LONG tmp = 0 ; for( int i=1; i max ) max=tmp ; res.set( i, max ) ; } return res ; } template SEXP cummin( SEXP x){ const LONG na = long_traits::na() ; Rint64::LongVector data(x) ; int n = data.size() ; Rint64::LongVector res(n, na) ; LONG max = data.get(0) ; res.set( 0, max) ; LONG tmp = 0 ; for( int i=1; i SEXP cumprod( SEXP x){ const LONG na = long_traits::na() ; Rint64::LongVector data(x) ; int n = data.size() ; Rint64::LongVector res(n, na) ; LONG prod = data.get(0) ; res.set( 0, prod) ; int64_naflag = false ; for( int i=1; i( prod, data.get(i) ); if( prod == na ) break ; res.set( i, prod ) ; } if( int64_naflag ) { Rf_warning( "NA introduced by overflow" ) ; } return res ; } template SEXP cumsum( SEXP x){ const LONG na = long_traits::na() ; Rint64::LongVector data(x) ; int n = data.size() ; Rint64::LongVector res(x) ; LONG prod = data.get(0) ; res.set( 0, prod) ; int64_naflag = false ; for( int i=1; i( prod, data.get(i) ); if( prod == na ) break ; res.set( i, prod ) ; } if( int64_naflag ) { Rf_warning( "NA introduced by overflow" ) ; } return res ; } template SEXP int64_log10( SEXP x ){ Rint64::LongVector data(x) ; int n = data.size() ; const LONG na = long_traits::na() ; SEXP res = PROTECT( Rf_allocVector( REALSXP, n ) ) ; double* p_res = REAL(res) ; LONG tmp; for(int i=0; i SEXP int64_log( SEXP x ){ Rint64::LongVector data(x) ; int n = data.size() ; const LONG na = long_traits::na() ; SEXP res = PROTECT( Rf_allocVector( REALSXP, n ) ) ; double* p_res = REAL(res) ; LONG tmp; for(int i=0; i SEXP math( const char* op, SEXP x ){ if( !strncmp( op, "abs", 3 ) ){ return abs(x) ; } else if( !strncmp(op, "sign", 4) ) { return sign(x) ; } else if( !strncmp( op, "trunc", 5 ) ){ return x ; } else if( !strncmp( op, "floor", 5) ){ return x ; } else if( !strncmp( op, "cummax", 6 ) ){ return cummax( x ) ; } else if( !strncmp( op, "cummin", 6 ) ){ return cummin( x ) ; } else if( !strncmp( op, "cumprod", 7 ) ){ return cumprod( x ) ; } else if( !strncmp( op, "cumsum", 6 ) ){ return cumsum( x ) ; } else if( !strncmp( op, "log10", 5 ) ){ return int64_log10( x ) ; } else if( !strncmp( op, "log", 3 ) ){ return int64_log( x) ; } Rf_error( "generic not implemented" ); return R_NilValue ; } } // namespace internal } // namespace Rint64 #endif int64/inst/include/int64/LongVector.h0000644000175100001440000002377011661703756017060 0ustar hornikusers// routines.h: int64 64 bit integers // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #ifndef int64_LongVector_h #define int64_LongVector_h #include #include #include #include namespace Rint64{ template class LongVector : public internal::long_traits { private : SEXP data ; public: LongVector(SEXP x) : data(x) { if( Rf_inherits( x, internal::get_class().c_str() ) ){ data = x ; R_PreserveObject(data) ; } else { switch( TYPEOF(x) ){ case INTSXP: { int n = Rf_length(x) ; SEXP y = PROTECT( Rf_allocVector( VECSXP, n ) ) ; int hb, lb ; LONG tmp ; int* p_i_x = INTEGER(x) ; for( int i=0; i(tmp) ; lb = internal::get_low_bits(tmp) ; SET_VECTOR_ELT( y, i, Rint64::internal::int2(hb,lb) ) ; } } UNPROTECT(1) ; // y data = y ; R_PreserveObject(data) ; break ; } case LGLSXP: { int n = Rf_length(x) ; SEXP y = PROTECT( Rf_allocVector( VECSXP, n ) ) ; int hb, lb ; LONG tmp ; int* p_i_x = INTEGER(x) ; for( int i=0; i(tmp) ; lb = internal::get_low_bits(tmp) ; SET_VECTOR_ELT( y, i, Rint64::internal::int2(hb,lb) ) ; } } UNPROTECT(1) ; // y data = y ; R_PreserveObject(data) ; break ; } case REALSXP: { int n = Rf_length(x) ; SEXP y = PROTECT( Rf_allocVector( VECSXP, n ) ) ; int hb, lb ; LONG tmp ; double* p_d_x = REAL(x) ; for( int i=0; i(tmp) ; lb = internal::get_low_bits(tmp) ; SET_VECTOR_ELT( y, i, Rint64::internal::int2(hb,lb) ) ; } } UNPROTECT(1) ; // y data = y ; R_PreserveObject(data) ; break ; } case STRSXP: { int n = Rf_length(x) ; Rint64::internal::int64_naflag = false ; SEXP y = PROTECT( Rf_allocVector( VECSXP, n ) ) ; int hb, lb ; LONG tmp ; for( int i=0; i( CHAR(STRING_ELT(x,i)) ) ; hb = internal::get_high_bits(tmp) ; lb = internal::get_low_bits(tmp) ; SET_VECTOR_ELT( y, i, Rint64::internal::int2(hb,lb) ) ; } } UNPROTECT(1) ; // y data = y ; R_PreserveObject(data) ; if( Rint64::internal::int64_naflag ) { Rf_warning( "NA introduced by overflow" ) ; } break ; } default: { Rf_error( "unimplemented conversion" ) ; } } } } operator SEXP(){ std::string klass = Rint64::internal::get_class() ; SEXP res = PROTECT( R_do_slot_assign( R_do_new_object( R_do_MAKE_CLASS( klass.c_str() ) ), Rf_install(".Data"), data ) ) ; UNPROTECT(1) ; return res ; } LongVector(int n) : data(R_NilValue) { SEXP x = PROTECT( Rf_allocVector( VECSXP, n ) ) ; for( int i=0; i( value ) ; int lb = internal::get_low_bits( value ) ; for( int i=0; i LongVector(int n, ITERATOR start, ITERATOR end) : data(R_NilValue) { SEXP x = PROTECT( Rf_allocVector( VECSXP, n ) ) ; int hb, lb ; for( int i=0; i(*start) ; lb = Rint64::internal::get_low_bits(*start) ; SET_VECTOR_ELT( x, i, Rint64::internal::int2(hb,lb) ) ; } UNPROTECT(1) ; // x data = x ; R_PreserveObject(data) ; } ~LongVector(){ R_ReleaseObject(data) ; } inline LONG get(int i) const { int* p = INTEGER(VECTOR_ELT(data,i)) ; return Rint64::internal::get_long( p[0], p[1] ) ; } inline void set(int i, LONG x){ int* p = INTEGER(VECTOR_ELT(data,i)) ; p[0] = Rint64::internal::get_high_bits(x) ; p[1] = Rint64::internal::get_low_bits(x) ; } inline int size() const { return Rf_length(data); } LongVector sort(bool decreasing) const { int n = size() ; std::vector x( n ) ; for( int i=0; i() ) ; } else { std::sort( x.begin(), x.end() ) ; } return LongVector( n, x.begin(), x.end() ) ; } SEXP is_na(){ int n = size() ; SEXP res = PROTECT( Rf_allocVector(LGLSXP,n)) ; int* p ; int* p_res = INTEGER(res) ; for( int i=0; i::na_lb(); } inline int na_hb(){ return internal::long_traits::na_hb(); } } ; } #endif int64/inst/include/int64/long_traits.h0000644000175100001440000000441311661703756017314 0ustar hornikusers// long_traits.h: int64 64 bit integers // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #ifndef int64_long_traits_h #define int64_long_traits_h namespace Rint64{ namespace internal{ template struct long_traits ; template<> struct long_traits{ static inline int64_t min () { return std::numeric_limits::min() + 1 ; } static inline int64_t max () { return std::numeric_limits::max() ; } static inline int64_t na () { return std::numeric_limits::min() ; } static inline int na_hb () { return get_high_bits( std::numeric_limits::min() ); } static inline int na_lb () { return get_low_bits( std::numeric_limits::min() ); } } ; template<> struct long_traits{ static inline uint64_t min () { return 0 ; } static inline uint64_t max () { return std::numeric_limits::max() - 1; } static inline uint64_t na () { return std::numeric_limits::max() ; } static inline int na_hb () { return get_high_bits( std::numeric_limits::max() ); } static inline int na_lb () { return get_low_bits( std::numeric_limits::max() ); } } ; } } #endif int64/inst/include/int64/int64.h0000644000175100001440000000371711665656352015744 0ustar hornikusers// int64.h : 64 bit integers // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #ifndef int64__int64__h #define int64__int64__h namespace Rint64{ namespace internal { extern bool int64_naflag ; } } #include #include #include #include #include #include #include #include #include #include #include namespace Rint64{ namespace internal { template SEXP new_long(LONG x){ std::string klass = get_class() ; Rint64::LongVector y(1) ; y.set(0, x) ; return y ; } template SEXP new_long_2(LONG x, LONG y){ std::string klass = get_class() ; Rint64::LongVector z(2) ; z.set(0, x ) ; z.set(1, y ) ; return z ; } } } #if defined(BUILDING_INT64) #include #endif #include #include #include #include #endif int64/inst/include/int64/int2.h0000644000175100001440000000230511661703756015641 0ustar hornikusers// routines.h: int64 64 bit integers // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #ifndef int64_int2_h #define int64_int2_h namespace Rint64{ namespace internal{ // we only use this for T=int template SEXP int2( T x, T y){ SEXP res = PROTECT( Rf_allocVector(INTSXP, 2) ) ; int* p = INTEGER(res) ; p[0] = x; p[1] = y ; UNPROTECT(1) ; return res ; } } } #endif int64/inst/include/int64/get_long.h0000644000175100001440000000215611661703756016567 0ustar hornikusers// get_long.h : 64 bit integers // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #ifndef int64__get_long__h #define int64__get_long__h namespace Rint64{ namespace internal{ template inline T get_long( int highbits, int lowbits ){ return ( ( (T) (unsigned int)highbits ) << 32 ) | ( (T) (unsigned int)lowbits ) ; } } // namespace internal } // namespace Rint64 #endif int64/inst/include/int64/get_class.h0000644000175100001440000000234511661703756016735 0ustar hornikusers// get_class.h : 64 bit integers // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #ifndef int64__get_class__h #define int64__get_class__h namespace Rint64{ namespace internal { template inline std::string get_class(){ return "" ; } template <> inline std::string get_class(){ return "int64" ; } template <> inline std::string get_class(){ return "uint64" ; } } } #endif int64/inst/include/int64/get_bits.h0000644000175100001440000000220611661703756016565 0ustar hornikusers// get_bits.h : 64 bit integers // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #ifndef int64__get_bits__h #define int64__get_bits__h namespace Rint64{ namespace internal{ template inline int get_low_bits( T64 x){ return (int)( x & 0x00000000FFFFFFFF ) ; } template inline int get_high_bits( T64 x){ return (int)( x >> 32 ) ; } } // namespace internal } // namespace Rint64 #endif int64/inst/include/int64/format_binary.h0000644000175100001440000000367711661703756017636 0ustar hornikusers// format_binary.h : 64 bit integers // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #ifndef int64__binary__h #define int64__binary__h namespace Rint64{ namespace internal{ template inline const char* format_binary__impl(T x) { const int SIZE = sizeof(T)*8 ; static std::string b( SIZE, '0' ) ; for (int z = 0; z < SIZE; z++) { b[SIZE-1-z] = ((x>>z) & 0x1) ? '1' : '0'; } return b.c_str() ; } template <> inline const char* format_binary__impl(double x){ int64_t* y = (int64_t*)&x ; return format_binary__impl(*y) ; } template SEXP int64_format_binary_long(SEXP x){ Rint64::LongVector data(x) ; int n = data.size() ; SEXP res = PROTECT( Rf_allocVector( STRSXP, n ) ) ; for( int i=0; i. #ifndef int64__compare__h #define int64__compare__h namespace Rint64{ namespace internal{ template inline bool equals(T x1,T x2){ return x1 == x2 ; } template inline bool not_equals(T x1,T x2){ return x1 != x2 ; } template inline bool lower_than(T x1,T x2){ return x1 < x2 ; } template inline bool lower_than_or_equal(T x1,T x2){ return x1 <= x2 ; } template inline bool greater_than(T x1,T x2){ return x1 > x2 ; } template inline bool greater_than_or_equal(T x1,T x2){ return x1 >= x2 ; } template SEXP compare_long_long(SEXP e1, SEXP e2){ const LONG na = long_traits::na() ; Rint64::LongVector x1( e1 ) ; Rint64::LongVector x2( e2 ) ; int n1 = x1.size(), n2 = x2.size() ; LONG tmp ; int i1=0, i2=0, i=0 ; int n = (n1>n2) ? n1 : n2 ; SEXP res = PROTECT(Rf_allocVector(LGLSXP, n)); int* p_res = INTEGER(res) ; if( n1 == n2 ){ for( i=0; i SEXP int64_compare(const char* op, SEXP e1, SEXP e2){ if( ! strncmp(op, "==", 2) ){ return Rint64::internal::compare_long_long >( e1, e2) ; } else if( ! strncmp( op, "!=", 2 ) ) { return Rint64::internal::compare_long_long >( e1, e2) ; } else if( ! strncmp( op, "<=", 2 ) ) { return Rint64::internal::compare_long_long >( e1, e2) ; } else if( ! strncmp( op, ">=", 2 ) ) { return Rint64::internal::compare_long_long >( e1, e2) ; } else if( ! strncmp( op, "<", 1 ) ) { return Rint64::internal::compare_long_long >( e1, e2) ; } else if( ! strncmp( op, ">", 1 ) ) { return Rint64::internal::compare_long_long >( e1, e2) ; } Rf_error( "unknown operator" ) ; return R_NilValue ; } } // namespace internal } // namespace Rint64 #endif int64/inst/include/int64/as_long.h0000644000175100001440000000205311661703756016407 0ustar hornikusers// as_long.h : 64 bit integers // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #ifndef int64__as_long__h #define int64__as_long__h namespace Rint64{ namespace internal{ template SEXP as_long(SEXP x){ return LongVector(x) ; } } // namespace internal } // namespace Rint64 #endif int64/inst/include/int64/as_character.h0000644000175100001440000000306611661703756017411 0ustar hornikusers// as_character.h : 64 bit integers // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #ifndef int64__as_character__h #define int64__as_character__h #include #include namespace Rint64{ namespace internal{ template SEXP int64_as_character( SEXP x){ Rint64::LongVector data( x ) ; int n = data.size() ; SEXP res = PROTECT( Rf_allocVector( STRSXP, n) ) ; std::ostringstream stream ; LONG tmp ; for( int i=0; i::na() ){ stream << "NA" ; } else { stream << data.get(i) ; } SET_STRING_ELT( res, i, Rf_mkChar(stream.str().c_str()) ) ; stream.str("") ; } UNPROTECT(1) ; // res return res ; } } // namespace internal } // namespace Rint64 #endif int64/inst/include/int64/arith.h0000644000175100001440000001205511661703756016077 0ustar hornikusers// arith.h : 64 bit integers // // Copyright (C) 2011 Romain Francois // Copyright (C) 2011 Google Inc. All rights reserved. // // This file is part of int64. // // int64 is free software: you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by // the Free Software Foundation, either version 2 of the License, or // (at your option) any later version. // // int64 is distributed in the hope that it will be useful, but // WITHOUT ANY WARRANTY; without even the implied warranty of // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the // GNU General Public License for more details. // // You should have received a copy of the GNU General Public License // along with int64. If not, see . #ifndef int64__arith__h #define int64__arith__h /* borrowed from R (arithmetic.c) */ # define OPPOSITE_SIGNS(x, y) ((x < 0) ^ (y < 0)) # define GOODISUM(x, y, z) (((x) > 0) ? ((y) < (z)) : ! ((y) < (z))) # define GOODIDIFF(x, y, z) (!(OPPOSITE_SIGNS(x, y) && OPPOSITE_SIGNS(x, z))) # define GOODIPROD(x, y, z) ((long double) (x) * (long double) (y) == (z)) namespace Rint64{ namespace internal{ template inline T plus(T x1,T x2){ const T na = Rint64::LongVector::na() ; if( x1 == na || x2 == na ){ return na ; } T res = x1 + x2 ; if (res != na && GOODISUM(x1, x2, res)){ return res ; } int64_naflag = true ; return na ; } template inline T minus(T x1,T x2){ const T na = Rint64::LongVector::na() ; if( x1 == na || x2 == na){ return na ; } T res = x1 - x2 ; if( res != na && GOODIDIFF(x1,x2,res) ){ return res ; } int64_naflag = true ; return na ; } template <> inline uint64_t minus( uint64_t x1, uint64_t x2){ const uint64_t na = Rint64::LongVector::na() ; if( x1 == na || x2 == na || x2 > x1) return na ; return x1 - x2 ; } template inline T times(T x1,T x2){ const T na = Rint64::LongVector::na() ; if( x1 == na || x2 == na){ return na ; } T res = x1 * x2 ; if( res != na && GOODIPROD(x1,x2,res)){ return res ; } int64_naflag = true ; return na ; } template inline T divide(T x1,T x2){ const T na = Rint64::LongVector::na() ; if( x1 == na || x2 == na ){ return na ; } return x1/x2 ; } template inline T modulo(T x1,T x2){ const T na = Rint64::LongVector::na() ; if( x1 == na || x2 == na ){ return na ; } return x1 % x2 ; } template inline T int_div(T x1,T x2){ const T na = Rint64::LongVector::na() ; if( x1 == na || x2 == na ){ return na ; } return x1 / x2 ; } template SEXP arith_long_long(SEXP e1, SEXP e2){ Rint64::LongVector x1( e1 ) ; Rint64::LongVector x2( e2 ) ; int64_naflag = false ; int n1 = x1.size(), n2 = x2.size(); LONG tmp ; int i1 = 0, i2 = 0, i = 0 ; int n = (n1>n2) ? n1 : n2 ; Rint64::LongVector res(n) ; if( n1 == n2 ){ for( i=0; i SEXP int64_arith__impl( const char* op, SEXP e1, SEXP e2){ if( ! strncmp(op, "+", 1) ){ return Rint64::internal::arith_long_long >( e1, e2) ; } else if( ! strncmp( op, "-", 1 ) ) { return Rint64::internal::arith_long_long >( e1, e2) ; } else if( ! strncmp( op, "*", 1) ) { return Rint64::internal::arith_long_long >( e1, e2) ; } else if( ! strncmp( op, "^", 1 ) ) { Rf_error( "pow not implemented for long type" ) ; } else if( ! strncmp( op, "/", 1 ) ) { return Rint64::internal::arith_long_long >( e1, e2) ; } else if( ! strncmp( op, "%%", 2 ) ) { return Rint64::internal::arith_long_long >( e1, e2) ; } else if( ! strncmp( op, "%/%", 3 ) ) { return Rint64::internal::arith_long_long >( e1, e2) ; } Rf_error( "unknown operator" ) ; return R_NilValue ; } } // namespace internal } // namespace Rint64 #endif int64/inst/doc/0000755000175100001440000000000011665656774013005 5ustar hornikusersint64/inst/doc/int64.Rnw0000644000175100001440000001725611663136552014435 0ustar hornikusers\documentclass[10pt]{article} %\VignetteIndexEntry{int64} \usepackage{vmargin} \setmargrb{0.75in}{0.75in}{0.75in}{0.75in} \usepackage{color,alltt} \usepackage[authoryear,round,longnamesfirst]{natbib} \usepackage[colorlinks]{hyperref} \definecolor{link}{rgb}{0,0,0.3} %% next few lines courtesy of RJournal.sty \hypersetup{ colorlinks,% citecolor=link,% filecolor=link,% linkcolor=link,% urlcolor=link } \newcommand{\proglang}[1]{\textsf{#1}} \newcommand{\pkg}[1]{{\fontseries{b}\selectfont #1}} %% defined as a stop-gap measure til interaction with highlight is sorted out \newcommand{\hlboxlessthan}{ \hlnormalsizeboxlessthan} \newcommand{\hlboxgreaterthan}{\hlnormalsizeboxgreaterthan} \newcommand{\hlboxopenbrace}{ \hlnormalsizeboxopenbrace} \newcommand{\hlboxclosebrace}{ \hlnormalsizeboxclosebrace} \newcommand{\hlboxbacktick}{ \hlnormalsizeboxbacktick} \newcommand{\hlboxunderscore}{ \hlnormalsizeboxunderscore} <>= prettyVersion <- packageDescription("int64")$Version prettyDate <- format(Sys.Date(), "%B %e, %Y") @ <>= require( int64 ) @ \begin{document} \author{Romain Fran\c{c}ois - \texttt{romain@r-enthusiasts.com} } \title{int64 : 64 bits integer vectors} \date{\pkg{int64} version \Sexpr{prettyVersion}} \maketitle \begin{abstract} The \texttt{int64} package adds 64 bit integer vectors to \texttt{R}. The package provides the \texttt{int64} and \texttt{uint64} classes for signed and unsigned integer vectors. This project has been sponsored by the Google Open Source Programs Office. \end{abstract} \section{Background} Integers in \texttt{R} are represented internally as 32 bit \texttt{int}. Aplications now require larger ranges of values to represent large quantities. This package exposes C++ types \texttt{int64\_t} and \texttt{uint64\_t} to \texttt{R} for this purpose. The table~\ref{limits} shows the limits of these types. \begin{table}[h] \centering \begin{tabular}{ccrr} \hline C++ type & R type & \multicolumn{1}{c}{min} & \multicolumn{1}{c}{max} \\ \hline \texttt{int} & \texttt{integer} & \texttt{\Sexpr{numeric_limits("integer")[1L]}} & \texttt{\Sexpr{numeric_limits("integer")[2L]}} \\ \texttt{int64\_t} & \texttt{int64} & \texttt{\Sexpr{as.character(numeric_limits("int64")[1L])}} & \texttt{\Sexpr{as.character(numeric_limits("int64")[2L])}} \\ \texttt{uint64\_t} & \texttt{uint64} & \texttt{\Sexpr{as.character(numeric_limits("uint64")[1L])}} & \texttt{\Sexpr{as.character(numeric_limits("uint64")[2L])}} \\ \hline \end{tabular} \caption{\label{limits}Numeric limits of integer types} \end{table} \section{Usage} This section shows a few examples on how to use the package. <<>>= # create a new int64 vector x <- int64( 4 ) # set a subset of values x[1:2] <- 1:2 # via integers x[3:4] <- c("123456789123456", "-9876543219876") # ... or characters x # convert integer or character vectors into int64 vectors x <- as.int64( 1:6 ) x y <- as.int64( c("-1234", "1234" ) ) y # create a data frame with a column of int64 df <- data.frame( a = 1:4 ) df$y <- as.int64( 1:4 ) df @ \section{The int64 and uint64 classes} \subsection{Class representation} Both \texttt{int64} and \texttt{uint64} are represented as lists of pairs of integers. <<>>= str( as.int64( 1:2 ) ) @ Each int64 or uint64 number is represented as a couple of 32 bit integers. Internally, the C++ code goes back and forth between the native representation of these numbers as C++ data types (\texttt{int64\_t} and \texttt{uint64\_t}) and their representation as couples of 32 bit integers by splitting the 64 bits. For example, the \texttt{int64\_t} value (-123) is represented in memory as: \vspace{1em} \begin{tabular}{|p{1em}cp{1em}|} \hline & \texttt{\Sexpr{binary( as.int64( "-123" ))@data}} & \\ \hline \end{tabular} \vspace{1em} These 64 bits are split into the two following chunks: <>= first.int <- as.int64( "-123" )[[1L]][1L] first <- binary( first.int)@data second.int <- as.int64( "-123" )[[1L]][2L] second <- binary( second.int )@data @ \vspace{1em} \begin{tabular}{|cp{.4em}|p{.4em}c|} \hline \texttt{\Sexpr{first}} & & & \texttt{\Sexpr{second}} \\ \hline \end{tabular} \vspace{1em} The R representation of -123 is therefore composed by the two integers whose binary representation is above, i.e (\Sexpr{first.int},\Sexpr{second.int}). This representation has been chosen against other alternatives to allow these key requirements: \begin{itemize} \item Data must be serializable \item int64 and uint64 vectors have to be usable of columns of data frames. \item The int64 and uint64 types must supposrt missing values (NA) \end{itemize} \subsection{Creating new vectors} The functions \texttt{int64} and \texttt{uint64} can be used to create new vectors of signed or usigned 64 bit integers of the given length. These functions are similar to the usual \texttt{R} functions \texttt{numeric}, \texttt{integer}, etc ... <<>>= int64(3) uint64(10) @ \subsection{Converting integer or character vectors} The functions \texttt{as.int64} and \texttt{as.uint64} can be used to convert \texttt{integer} or \texttt{character} vectors into signed or unsigned 64 bit integers. <<>>= as.int64( 1:4 ) as.uint64( c("123456789", "987654321987654321" ) ) @ Internally \texttt{integer} vectors are converted using a reguar cast, and \texttt{character} vectors are converted using the \texttt{C} function \texttt{atol}. \subsection{Subsetting} Extracting or setting subsets from a \texttt{int64} or \texttt{uint64} vector is similar to other vector classes in R. <<>>= x <- as.int64( 1:4 ) x[1:2] x[3:4] <- 5:6 x @ \subsection{Arithmetic operations} The \texttt{Arith} group generic is implemented for classes \texttt{int64} and \texttt{uint64}. <<>>= x <- as.int64( 1:4 ) x + 1L x - 1:2 x * x x / 2L x %% 2L x %/% 2L @ \subsection{Logical operations} The \texttt{Compare} group generic is implemented for classes \texttt{int64} and \texttt{uint64}. <<>>= x <- as.int64( 1:5 ) x < 3L x > 6L - x x != 3L x == 4L x <= 3L x >= 5L @ \subsection{Summary operations} The \texttt{Summary} group generic is implemented for classes \texttt{int64} and \texttt{uint64}. <<>>= x <- as.int64( 1:5 ) min( x ) max( x ) range( x ) prod( x ) sum( x ) any( x ) all( x ) @ \section{Binary representation} The \texttt{binary} generic function shows the bit representation of \texttt{numeric}, \texttt{integer}, \texttt{int64} and \texttt{uint64}. <<>>= binary( 1:4 ) # integer binary( c(1.2, 1.3) ) # numeric binary( as.int64( 1:4 ) ) # signed 64 bit integer (int64) binary( as.uint64( 1:4 ) ) # unsigned 64 bit integer (uint64) @ \section{Numeric limits and missing values} The \texttt{numeric\_limits} function gives the limits for types \texttt{integer}, \texttt{int64}, \texttt{uint64}. <<>>= numeric_limits( "integer" ) numeric_limits( "int64" ) numeric_limits( "uint64" ) @ int64 and uint64 classes support missing values using the same mechanism as R uses for integer vectors. For signed 64 bit integer vectors (int64), NA is represented by the value $-2^{63}$, hence the range of acceptable values is $$[-2^{63}+1,2^{63}-1]$$ For unsigned 64 bit integer vectors (uint64), NA is represented by the value $2^{64}-1$, hence the range of acceptable values is $$[0,2^{64}-2]$$ \section{Reading 64 bit integers from files} The \texttt{int64} implements the necessary methods so that \texttt{read.csv} can read signed and unsigned 64 bit integers from files. <<>>= tf <- tempfile() df <- data.frame( x = 1:10, y = 1:10, z = 1:10 ) write.table( df, tf, sep = ",", row.names = FALSE ) df <- read.csv( tf, colClasses = c("integer", "int64", "uint64" ) ) df sapply( df, class ) @ \end{document} int64/inst/doc/int64.pdf0000644000175100001440000050466611665656774014465 0ustar hornikusers%PDF-1.5 % 58 0 obj << /Length 1900 /Filter /FlateDecode >> stream xڭXYs6~}& i;M;Myh}J<Z֒I]삗(_xdv 4ٛgk3U d*8Q6s2p}'*_N˷dj_NV)9^΁̷5̝5NgvSUȔ(4J0J$xW WQEz5%$X lhϔNEP /-X!_7쉷©io3w+|?3ʾ&ZH`4$Mؖeʄ$X5AUӎ_.TEp.zwj #dGhv#eutVI#=Vya]J&)zKvlC(ipX"qT` >PjVP;6P|G'7ĸD_󸨒(^K/Jn)cKaK;?Du*4E_>Gba#ÙS>CEGTxuQ%3>='Lr?PQS73<, lnYM"r>ccP^2lź֯ͪ!E/xC$,:`=kN1QH4'\H w)+u hha-T)m)hb^-9~|  h%ߖh|r Ƃ")BzQh5H./TѬWQ6fS},H̾h̯e~b1d;"2Ev7wdWpNu``jOek%D߰(甗 jq2I,53[h %0.8h :L;u!@U͑6t::33k3G3p4 fJP/MJ6,3^c79\uÖf?pqY) [Rs(BڭNpÚȐ nTFcdS"p gMT# p…7`cZ09t|H%zRzx@EaOl(dfG2[:㛸uu /RSicW66FRPb٦Ќkpܸ"@V, Auס~X1e(P Dav@hME`S8ԳbU6Qrj.(twDdx'#hn2U={B4gb˛λ,;KS?*{>cM, ~w` U+nG',9jMՂ>.kO 4m2lr3UӠRw(8Tw'> wS97M=Br`zNZ\Rٜٚ#j+vo4뢂Pۃ$ ]at.d TѰzn]3^j/E|>qUjl{l󥥳=i8]#KծCǮ0 bGE%{˛2$ 9 wY<{&w5R4$R="ZϬ[o[so.cCrQڴGnivzBBu2b## [=A.uH!QRJ=qxӃ[ E? AB.&zniB5>j6I'-M|-Ջ]Ueݞde% ; C?<8g҇NǜmU:X%Wvn endstream endobj 76 0 obj << /Length 2247 /Filter /FlateDecode >> stream xr`͉RufS!U6;$ZVEzEɎEZ=T" h4$DIĶ?.SVF(3E(3:u9fTyeh.K)4eAdx7 |3bx7P4BhB+#RxqW:OLLA`k'!VGO~w(vBRi=yoWMq6Clxg) /R xLJaV0t *^Oiunm@<=1pX&pDU0bdඳ{u(2qf1 QhEvzU; pxG*.$+<@(+=)G"Z>I5A#tYDOt^cÔЂ8#QE1LD g,Ͽ'};0{;'/,[.n,jHDjlid[yTNAa 5N޶e䞜jnH~E2^VB"M7)D "0u 4b1.=T(;! p`jpKI* L⟹ٿQȹ'%o@2qg=mw``@b9K! kvgڮ_teqg00l!r{|6%0욾ysXo4_ŤC*U>6rwm5 UJ>P+9콍Uh 7gz[z:jC` _1q9q|̕ alOHs_LN H aO1!vw\+Z s"dZĀ u6)8yY w2,1f:8.گ~bXVW>t&@N$bӸaa_FWIpGZ?T 8M_`f.vV6pw[k}O#HD/nd˼ڢ!YOqN%X5kW-YJS.$IEPZ r]+k[wӧʾ 뎏 KxEʇm@N /K>\z!xc9Ĕ }N I\FUzW9`P"`j+WZk^$KE,K`>\-Me endstream endobj 81 0 obj << /Length 796 /Filter /FlateDecode >> stream xX[O0~WdHɦ;` 'C)TZ[Dݦ-MY8ι|4&4~@=Z4O#R<%#ђ%]rDf9c\WۦgMMu;+k+ND^^,`M` \Nmਸ਼#< sƝ{ӱ{;4lacB8Aբaɿ% .V2k]WHi"VQE}۟_6p>FVԇlDW,hV[S7 +8P\ByY4D=rEБmACDcҟTQ3#`< +K,8H&it 6tάj9[ցzHWԡ¸j5 zbb1^ FAٰX0 l364o6quS"E}q!\<yg2$ଂ+yW@鎭 kv(xks 1Ĕlзw1%t >b)F)|Z^tr_}E/a%» $um<0A{`5Fos(sDޞ ;o8x! ?M9O ɥS6m<13qVDw8q*_4~f-j㎍|~Y^䛆@h̙xtHnu$S]Ѭj]ٻ[S ~y/WdpiɜPZ-pZ4u endstream endobj 85 0 obj << /Length 810 /Filter /FlateDecode >> stream xYKo@W RavHI[zJsv"2FM}gv ~DNva|rervq N2r"`J97e7^N&Oxx"n>3^xX"f7JbiWxZ]ˈ ~;X+[)LM%xnmSctҁ> ̶V˯.Gh|OP=R}kxbnK&V\p!ZhqiQRw^ s*ҙ>NEj!חzAWęNٺ9eeCOo+'oGEFpQW~AQиݎR@.Ssޡ[1? &Oy4֙&'@]Q]K6M>ӎГFH?Epr]jg3;g6uɷ\?W~C'VVxӷTڰ}lTF.›-ǦR[uא,w~^⭤e]Z=/_5?VNp}\ ˿}־H`R)ϯ>;^ endstream endobj 89 0 obj << /Length 1583 /Filter /FlateDecode >> stream xڽXY6~_aIFc^@Zd E}. Z_M6ÙD\#4%\@ ~ 6QQ\ЭMH S\=5F 2\fYTlźi׿H_Q{ɸHw侭iyRk%4Lc >C[(1}']TAJsc݌߁eOZ㦉anO`1AJsB?bσs IvnttǪƣ}kB}esz>'`}Io4yJ0udai9_*[Zjq%naQAg֑L7?]dgܙ`mt:JPl+ǭ"QT8RT.I6ӧD@C3PITi|BMK {8Nm ;3* 5L:_K #ghZhiLn4DVSAMt&+_0_)&"w "wJe1kXy xw#;7GMYdo_}"\bO;zy:܃\rJɏ^%ԕ^}/O<fhLK[H=`~sBn`͠nN 9 11L7'Q2dP7'(W  p=^o-%ֻ3bz6>A %Kx)ŲgZ'`/ qN{ vxûn endstream endobj 110 0 obj << /Length1 1447 /Length2 6585 /Length3 0 /Length 7555 /Filter /FlateDecode >> stream xڍv4vZbo*J=# 5j)Um)Z-6v7o;}OI{s_sɪg(耲AP @Q! PATpОpR?0S`~:($@ @`)%rD*o@GB b}>YcB"q=_a{Z ۦE"b@-/=;Z=#&'-x\^+Ga C}+woԼf q#tR ] v9j cPib PD:!D@`_3&G0='Seîxb'nӿK"(_k'"@h vXI 7BH 8$)&vDyi+@@10K/aߢ]'ao_mAh O L.ÛN|eG8M3x&^gi/CGiTӋ< , 5QR/l Ivm(L|[H{GI+nN3/ o>>[|`qUH(g}z6 3_ãyW,ZI$ADNTx2p0X3 PZ}E7PV7';+d/Lѣe[9Z|Yh t> Q@gcJ{wmmKvfd3;[-”jdoF-Tersf%.'p{0RyԺ*.v,u"Dʫ$}KFO{_]ek{mmPUFfAlqVDq#ڷYٵ~ .3>!y:cSnR6.FܼXp3uޛ>>P@kh OUT\H[ZWEy^co]ӣZF^v=~Z'Np wWծ[pg^T^/НSlDGsRm.BY?ɲE6>7nQ5yqZ`Q;Gm)u0NAJ~r66͎=rH9^Xf%d=S*+~R }57!g۬}H.˨댏LߘNW ztd"9n~t(F2s 5f >zu2 Lz-KV%&0(dȵ_1~sV!&-բBص?. FV,w{8SCnP٨KVU0a<ԝM)hmigRUJՖV_uszLBw`-c_^^(Jf(5r(uI3$r>+dr~hl?F#>9}rP} r\;b?`m5:~倜|ێ`2mͯ{h֧H O?ᩬ)v%=>TPd\$zv^~.Arx7gt\숡 j (MyL,`wm7h\>l ~Lc7M|7>.cM`a*Na0}ֲuĦk7Z<:PlMq,D;̗WTfq:6pjTW|m?=2CktZ1֍$у>X$kj{(n@榼D TOcGᇽk& a5P5YweSDCέRiy"-tO-Q݁> mLdkGHv7'vfGZߒQᥧ5 5햖!lLW“F,}nRjFO+&kêp(U9}2G ϑ?}dE Uinoe#$?5\W0Y$nmĦCB?*&bZpI +ku*Jd=z"؂hiM(뫍 ;@*.cM\:UYfVzfd ^MDm p&ZhG仺92͚9Wq'4+Q4>ʬqv(R^ye-gKx\^m&oEG(AԵմ*Auv .Hcpbyfqoh*rA/$}w.8uz#ezD r𠐎Mf3)ƕF>/cc /Y6ѽwzSN?Q |?WA9f^Gժ6'$i2do}~;`,s?kk1xK'ԘkS%Aq2\3--7>>lChոųX`iy\_4S#wǛ'MϚ`u%ξ^.ج xdR2fϘcKzy%pͱ䎨s>u has5zio&tZNl}XĨI\^/-eh3-hm(m [#1p6ã&YhnTQCD{qңQ1vl#]^}r!ɔK"X-ɡG:CtIM}0L'-ؓ=ZmWߨO)> |ߪ"}]2[BнQ=(6m%5Xf߱Gے 'YMyYwqv` \>>]v.']p] |2mMIBrΔzٳK#Ƌ{:f6 1+(嘨71$o3L$R Usp[{\Q[YO2ɠRSY*`6{a6ukgMRGp1nxk9GUdR[rC.KigrEߕmH+miZ|V~4_`!U:"وi=—>&c"CSMįB $ &XHd˓2~\?)Ňv_A/ <.Hau?zJrd<+h.x5z^Zz  ⽬ 09ЛV.eʗ+gJJd+^)MmtfxRchc1FL{_T͛zrߦy6Wul5iߒfw]JJ^pG:dTzysW@]s-l}R[D?w$%G H%ꇾ9Qژ0wxl 㬇Tn!WC𣤽ml6fkqolgэ0. h?]gq6sm}+}zj:ujB^ Mnl5r5Yǐ 8_{=_>=U<.{⡝zPeuW{[ܖun{ng Ye`ͧ9o΅]JST۳ jha}K6#6]t }XV!S4X6„@ЃrsETIVTd1*(sFs4On:%dP;1<|-tx&Ԋڮn:08 `n ,졒&i?+i{v{]d5w`,a_'ܶ]GC+2/QWgMtu; Լ ^֮8'qŪ' j2י+^mr+܅ 0FgN`%鹕Ki$`ѢjiDeޭ-0:3~ )e);,\Oz.FgʺC(hlCC 0vlF72kP xL_,9>5eԳ&0:[T@BgsA7Oѭ3^B6:-*ZRkӺu  RjOkx[rXvCg_d }$dh`mi{ Oڳq"?\{tuUUr΋c1ff MFlow4(w9JfG_h[[GΥNN `5Rz:cvk3yE4Y{-&۸[)GZt%W.1y9kI\x!9h mjo+EAߞrb'W_8`Qf^`7k`}r_a5+3 g rW'~=}^Q pV Xo|}.lo}=~Sm6-"1x!f&l)x%++}@ 4;L!|(dd~{TOR5m(A[zG%6A6o 5yh57PY#2 FJ 5d+vo|0R`MTXFHv[Z䉎^1ݏ04&V%^g,7{cŻPofpUJڰ\,SMl:=Oi{ex2T2mk9vHVF-[ NMnL9*M endstream endobj 112 0 obj << /Length1 1982 /Length2 13098 /Length3 0 /Length 14306 /Filter /FlateDecode >> stream xڍP n54]݃C=!{p3gfUVWug[MA l`pwa`adʋhY((Ԭ\l#PhAV]eb.W[ _C/@ q:#P:8z,,]@mJ` lY],vMmV@ Aohl[XT@ e/j5K+(T]܍A@hjo޳T@ǀWs,,@V::9{Z[̭lE 9FzƶnV&n V3)řLyoĬ@@{2u6EVf0sudRrrJe.BGftp033sqN% <*YsvtpZ݀+ߊE,,3+S b<`9zc3Ih)Eo `aapq0|7/?JVUODi{sHwD ֆg9M߿X?/.f(+pSO_bM5Yh[v1~a{ ۿh,a4Sr1ރZp ,Gs6Y7u0cX98 'rpYޗ l\]| ?N$?$0ur n߈b0Lj|# & 0 @Vxnswp_f߫|/_n {u; m_RW;/,pҜ!In~{9. z^ÿٺ u|gƿϔ@7=K|!u!5 34 KNG/A[ᔡ>mqO/ǭ mIO>φ*Sߎ2}yqlurFQǸw.Qh^5,s4Cz^`,EI.) - zL"XBo ָ9 5VLIMJGȣVOX4 z"G'e9f~6 p*~b}ME &lֱjKWu~Fxn OT`-֘;S#ka=+,tik[*|WiY9ma߈Ǖ1nVik0F4O#'jY74=(6֫4mPB 3P2N;#[žT;N׮2/l;1cG[vnZ>uf:b&z:y4= 튤(ޅj!|pl<.i\ͷ,}/<ߡut|LqBk3vOns^吲@PP)WN*{P!Czk M5ӂp? P롖cC}_|&w! KU V}@_Ia4 IcH˴{fզ!S~:&47ƽnwCfS,l#HL~)r1ԢLSO/1_b/n ?G͂(sWՌ8ۖ*yɖevWAq6Eן~?mon*2X2>,H1"t(ӝixRcm%H!=6/eRa@s_uhk #\*:kOJ&RlV!AvRTɉf!usٽ1B;z0i>0JC5&Y&/:ZuE] ~wRwg c'_+n.@V$K !Ye8 әфh J,2<5.:Iiv3dQv\bUΌCqnI6~ز ߹ 81 'p Fܼ] )HlWp`-j/V5&Z7M,\v$28Iۏm?XaD_IdƬ ;d杹(V8vuanh^:rs G*N$h\;LN We_D9. ՐN|]RʺHv B_r{*//|c #$d[K%O,8гeN:gǫE&!7–N |ӓo#x1 2,6xO!^r ՞hǖQ-4 loͨz,2F0#M[MA4paD\[ wUޢ,M$0)a&EܱISe. BOS2d@Hw+%T9ˤ(5<{?vu5_Vi%V)8O=]wQ/[\"'\߼ ǿr8M[&ʞFEqQR7̚4eQ^MؼcU)Qj@`9m2a XmiiNOW6+R`āa_" jo>PF0aeOMe9zh?ȵe7Mu>lI"o ɭA !#Uލc^hOV9XL*`ZS5c8̙`#n2R ܤ "хyH^j|LbziP;x#OB{2K[t3<Hw3oZs\,puĉa$z!6m N27c(mAġ!Bhu2ҝ^-HfL('?CDx1tWi[EQ_cLAMIb)&E 5w @#,cUJ*sGMta'ًYDY_$!~F:lwҘʊwhdWOuy?$ۦ5ۯe>ttJ11\cH4At@Zhq:sB{N 8JYso`ٚWvGDtBS(Sp= w+D|?WC?iZ>4\A$7hΚ9hgj15}L ~ʈiVmН3xas:"zcO+ڋQk+Eå޳ZaNZ4e⯒A1AKXߝU0ai$T͍Bl=Q kfʯ;d'ȜSޯgp[UMzn75lO(}뀇w{~vtG,9$}hD{gyXYRp'&oce r[mP!I5${KTM{RCI@ }:)!/Moű!ȩ̣QzUp/)簨ykz?,9o'a=0iKrh^/UUOBkߓ~&jO H367)) #G-dzE_ֻeF  EűO ` 0dXWJ5òb&Y(u}LzըpkNT҉e5%Or~]YN'JsS ]'ijm;{uky{qsi$;Ijumj{PlY(^DH~(`ES-3x+ 3oS4mw@o_f`brG(ee4!SB)PJ<н36""'žWqV(/<M_ HN钆z0c}~A̸^#f E:Iդ;fhLaa`} 9[~v ~=K/ ZC 6=Wnn@1يNaBz1"v)@4mObFiЛUP`soqk cG6.ճk&/D3ΡGJrLE2xb(e yX\e_h+b-c?U&҄T$'V"bUmb=헽B *z`c'O5Fؑ5(x>xu?K[Fw އ6C&}Eb;4 e, #!MEaW L}D!5w\Va^εvYЅtx\E[ed }nGYP v Ns#1Q0h^z 䎰w(53y-@u_^&;85A5 :&)< 8A|u-J˱΄EŮǍYqZep/gBxˋy->HA3ӄF̛V-q_/'{@MvÃ[[R + l:[ k0㸫Y16CLBfijsR+B@W]c qqAпy.U{윺S[QګO҄eI3 2ו*] c85 S|RܞJ`6w~R=sЊ/ &96bP)KK7 - ]]FIF O(a7y;J^QY691sJB9o7Z5;YR{|o٭%SwS.\z")56Swro<)lQ >L@^Ox8q! rx Sf21GU`9M(ǿ2⑾i@vl=i@kXW+orܕf ;λJ6B ƗE̙xe 7$iz#GXIRGQvq#>sޱ󰙦$gU' I9&;daS}96Z";=p:L&1xȊCN$_U1v0sH&]JpAF6(>[9ĝ]$ rj-E8AA peՌP&Un Mڭ6Cŝ/vhl9NtD%1! 4YOȩP4r&X-cCwa 2rf"FNnRusKa!lWv`KQu_:9֔hѯo'KRpV8pdT`åN-.w`r49sNB 3E|QJ 3V\X!x $pLq]GLK*mǔ^%?ռ-[2?D,W+7&%F!AyLtTVCo7oWC04Ǻ9(]"4,?#cAJ'3Gp25~vSIp[md5'ŀOm;E̾da &:n~%µ^0N[:3`T ^W-,8|-@J3Ff|CT \2i! |%k{})A<}IBQ{[A\F&f%MpnH[T/䋜C5.Y'yjG }] =:!0i7ًiÅ&!%dS6g^_6P+`۞2zw}M,IC,ܯ-d;|1נSspjOQq@7xt'&qMh-Qn؏gwEtI"+K_T%HIΤO(y{}R3(![R; V^%d6gqDUn+8r2Ni!8?:>ۦG*MEDzLg4 Ee\*GQeN?"T+T!EͬO~(|фaG/8շ$%}~O|Ii9-4lkW1;9Y](yq;][Eg9(Jy nB,HYX}>E}:?{Ⴅ޶ +l{l#RQꫜn+LѾ;x?g~T#ϷZm9GSOQl ~j$w3^h1<GObuexKºrvsOV!T h]\4[n הwbL$, ı/*2s,aGyO`zhӱ+JS{v<1.g@2Ne6N*>i:Zl+/ST_+4@ڙdNȹc !ɦ:@07"4qXߞWdU>׊D ·_ MSVE)(1yЦrC2֑jwV - `uB#9&Wk"'5^|oYu|56iKp7zG /%d\VF VI.'^5@4 bgYuu9& W/ fC2 }Мr-(2,>li igoQ{ ͵f7o- V:ao.1m1`J>+2sZLBئ|f%!1Jœ)Bmjg뢐ku[v|_~QֵH ׸)U[6Y4NG[u;}Y؈b3ef+f4YOemc#5{qHp#|u=r+j۵dgX BK*~Y#I }%Z̕4r!_#9gvH/zp:(&pq3*h[IswXJ >$)?#`5 9E\Ǵ-J^w>~/۫X^T }_Bs/#OO~zt[J~}M"Ҧa _ H.e'B;(ڕTH+?2cEcf.IR؛ehQC.J0j.]ƚH%s0=}WؓlRA 6IX)ZDQ|o̩ /A Os]h7Mח|YZ˓X 4R1 4|)[$WZc RiPL`gDmv USz d{UQ`[I&>Uv̚Ѹb8;air[CǻV9e^+ӯ}zaV/ɓ)=Mbtb  P jJ9qfaK䑆P-v¾<6(mb1?O'j ,>Rlt$ޛ+.L웰M7FbKB c,:e'g>@_**rFK MwMˢ!r`Uݛ+2[ňY&&>}'LaߝS 7zĄ3!V0, !,p%zڣpm[gc {A #p @X8q]laq(jƹ讬<Y~lND!)H#ʰHKQ8B^HM;s@:-S!"!XvquIBfQZvv`0d@ӗU^`!$>edءA7iVfGD˪rYPR [Y!݇}.xq8 DX˺صvKziJ? ]|Hɜ J#׺"e6P]$F% gѯF=!_=2lZR3`rO8:XbCkcK4avǻLZУu#g턥m,L!-%W}%67! f3L!(E٦å%OeEq/?q mu9X2g YDz3Jw^kaaˡ]]Ҭ٩Q74@I48iKB#/Dߍi{Tu;hs L_eURyEޞC,-7ءX^꺎1EEzrJxDMs>x.fl Ľ2k{٬v͇i3o Z$rīY+Δ7'* IMZ/~GM8>krVm4pj'ӮkX=TYgfM%:ZrՅnC.tn '%Y&iZX ׅRB7N͊~xferċ^@rLToӊ뿆ӖNiU^JX׀p`{vju0 Z7eMk9QzNta,Ms9Cj[0*?'9O Ѭ]FZNq /ͱv§{}(^)itx&,jρ>)ؔ``|b4aRy(R 9ĥn 3a;7obҰkKF.>7~dSG+~čֶNqԝ; 9Ęor&8٢/b-wySLR'x?7a8L?)~Í@27$O_6 _Q E~g 5k9;&4-m~g&iϼj0P_ny8IF=밶8l֚eWd UNGxS/3B*{zo5Fi^Au+Z~ËnUKcۗ[)҇J UXqӦ?~$FsDj2sFh҉}Q/='>&^F(j,I. d ׊?PC77Lpe/54.R#O՟sijyVO+Y=AZLZyxP.koHcq}Y' qïьc<GEY8D"k2yw)J)B&_ܕ 0}p-WߦDOVYvNo51J %)Rvw,gj4"=$4>wE"I3y*ݬZ rF}< ~^?Lr7BʦCz@!I2<܏nRY0+џ(yb@6>^Ǖˢ ۻGq}/)Գ9Izbwey3ү]Fx*%vEBhja~mqLQ_T{AJR"qՋÐjƸi~'gtԓIy_ (?ֵ=x17a$ɿ N1N> F!O˭oUvߕ0o H ԟa(Ak +w%(>$zzI@(~c^rUX1a#黣 ${_P=E >&DsA*8HBMx|VHx /ba4U)GnOw*a^r-'0ЌW>{2^{TΖ0d "_U>g4I^gx5iksU'pZ$ endstream endobj 114 0 obj << /Length1 1470 /Length2 6897 /Length3 0 /Length 7877 /Filter /FlateDecode >> stream xڍw4\]6тDFeFE] 3 w;E'z zD I>}5g_w^gؘx H+2 (h@ ^M )&`{E0P@Ah"mD>882D`w PC".l H'/_K5'OLL;@YM5CZà^ !i$zxx]x([iNn uܡ/-#fl};r=p5pC@(zs܀?s;ܟ޿HG'0 Pce ^WOWne `w0 B>9, IsruuQ βtt"\]~OZO`C@l~9 0g7&h?2[+@Wx}/'o%/1 `&@/;r߈Y0?b]|` B{en/w}J54`N^  ||bBaN_K?'* :yp-8NwB{ @B ky~W@npo5o;^[=Hp (#֩!D2 цZAC@._W /zܬ׉ RUP4{K%5k` E.< | znltE6Hz rDV 1o'] BnBS 1PO5 Z"M۳j9:/Rl_ S9y|PmnDx/92-N^&YXS8g/%Q /cT jye7|:> rjPcqv%#?U+Q%NxU:kcT<Ŗk9MsוC}OI7Lj/vb }LO{/tҲҚ0` MVSR]d`1(F va,}a=ͷA kaq:lirjE'~='piI]'$]U(Cj^t@"NT_+N/z&"UҽqK03g`ey錙ZWo:-$?aΖg.'e4c#f݀AmC9aV'lՃdK Utuv璱B9>|+E110F2OjH$+ƒqaI=;PB2 !fjS=*NiB8zMĢ_J>fa30'q<>w[ChTRWHv{7U1:/Nxy;waBca"sG("Uj RSE^:R,OHMz$RyE/o ]z"'aeE VRT^I'i`}} -vep>P#ElDX ~I %n"S(]u:FfDr=P"աUm˙#ҍi:wo RR&r4"YgM&DnIf :hYW+9)5>ɪ L )S[qU=E bw"eH( (=/';ɏ2@Y=0\d[P+zN#BvBS#7l?[$]V(8LeT>O%HN j0yAA>Ƙ-j}aK1' KuOB"~eV`Yt㰨q>.II=!K,wbgt4rWX810& E*%,IL>q2%nL|dBhHءzgGB4Ҳ~ȘiVUVfHLSud:}lNM($J5mC8@1]mGĽhШc6@i_SR~̆}8܂caN^_DsAS_8uI| TmR_r$HTj8= Crqd |SFhTh80dyeHħHJ@i\9-.dqizOHFS`Ӗ:'S1'f-7r{gͲ::_vܰBDnE9y` súz~\#]F4=* O)(z{iGal#ܹp 惡إ"(Gl2AoMz8CdWx ҂շ8v&q"7p,G--wF!c6b, Iݺeΐ0(Y702t_E [Q}7NQ?,,'UC W2I9I=/LcOCukTLT{!P>[y-~D9|u"-njb&Ż58!_ں6hjȱӞ*|aAqL<7C9ֿCܢ1JDs.YW2%V;IbuԹvDh6n1W6#۞4Y4|}]USJ{Ev& ݚ(SMn|֡伆8 d?&BHʶaT~Ɠ\)ұpq02])kMۛ, 3 (B+eR3R'~}н~i;g;UՎP>7`ر l5* fR\SGO;{BklFӖ=@h(@qՄؽC_M] ̲Yh Q/]O@~ʙ%So6b LBqⲧግyB2#Wx a@;lȚJR Kϰר 귳$5"H Y)8fGA936 ۫ƃ\E !Tx4Ni(?^yVk2t`#MF;%'շli>oϞW'R+Ut\MjTxy˷6vKסoP%&sA7]}2:ZI$ -es ^Fɼv?WVs2W:HGHfu^d.@f[=*_R.Q#S[`=\B$y|SȕYde4pz}PPaUb !Vw"y+J B*TְXз+ś*;,ᾤvNV q߬oJ\ ק\I2#}zT{QOh{F|նɠ/t5^L z$*{\+1(Lkzڴq\2ə3-k0g|hﱴMG| 8:ޛZv({Y/((ĸaeR5\{|;Lm:>(]ץ֖A?ͷJ&v$,;GzOɄ//B{=&؏ K"_XH>,JrV8_BrixF&%Ȟ_c04D_.!io6eYvRYiN^Z ZA] dĻL.ϒ;q| 7omg0!=$ڂ{΋Z8S{C_ӻM%TieϾϽ,= &Ukir[wfgUR#w,CI@f2VCU,2UppN.$?o8<#8'h{^p"90zISZ :إsja?4rUk4.笺vnmt1W/LSdز֧aã` z[QE~ - oi3}vA&t*7 g-\K7JKxphN^ymZR[wZ(M߇l(w&שLx@̀Iյ\䢄&Saњ۬e]enP`bR= ZݼJoFʆYzW)Z4d(z*ѐ"xb!M̩ 8Z$ՓWܪo\JS"}87˪`vO^ܣ$RAv% !"y}뜖=(zzbReR{V5[xdoV-)X9+. 6Zh AwŜRǒ!=fRb[r /t ǺT`S{ߚjt7c&rR7:Q9ԋ&`|?V'cWy^m`jHާEP_㋴Qֿ/V[x!, &uf ]lTm"=c>edHohT?/r(.{y(?S:lWrOe j>n"ۣt~N:Zf\ΆB3:!nx˘N^瘮FNQv+6伐EӞmjA7e3]9$q{3٢&VB ]&TH!vf.iW$X|Ft eNݬ&֟Tiud%P x~ݸug.y n%^i/YF˾LNĢ+|D; 0|C'jR$VNy .rx.; éQEY%j._(T[* G+^60B&Q uT s0efT:l W1ܾ~U_YK'xdq<h g2[S=)3^Sdc0wn ¹7m#ҁnRQ${)YEYb,`yn76$te *(F"'^ت> stream xڍwTm? Mݝ #A;UA%U$%$Tw<9u}\wyX@8 HA AHi8, T!8| tE`qi4Da/POB±Nprrx`)) _@%w8 z3q`8%eq8 +88g x?!!?@g`@ #Owk p`? UOBd rGC |p@g C 7!GAqXA,'Fe׬tPAÑ8,T8 BDy#9"?a8xLO oIJH@Yg_4ӌFx@#B@`0p'x3? h keg _#Rl(0P@X D%E?FzstD}#C ?> Oh8`/YRYH헟wㇸ#|D ËCCw@xW D 'XT$ێ#|w8o2= |7~E|@s?\vAx!~?ϡ~jRXL` <%;1?/^/(>tDa?-&  Gi'iQ00Z%oQY# a[r\ڸRq^c`u[.}e+ 썾N鋃K)[ +ߐ.aPpp3]7}vx~gwmE.F6ɪ_B㬣3ovkhgi{ٞdžh{_UdU%1-k+qUqˡOQΖMn gT8gc6Z,r&x-C~$;Qˀ|!֬' b#vddO -azr+8{9FUNǐ˳Z7{>i.l%a"_6+lA+"BȬ6"iOhSkƣ&O0]d,UtPd;* pAJȞh+&,Q=VՇިONB^:D^!q'[~g[@}яk2f]NE}/˷gk+FΌDx;WhRW ~~@up0t#9!Ciq ge rAGrDXws宰[uڱ_@/Pv׾),&k1p9/"dguWkZ¹ jBS~_5p>˴+_.wC*vmڏ!{<Ͻ-CaV\ oGNL-E\$㛎Ӷ@MlcwifWi% HOJ3GH<Q0~yZoM7FS&]޼JB7{?zDټ^xU=}M#?VĊDK`L) &0;fMrb6]Wyp6ġfshQI){1i/0i>,j\K '!PUpIۨ Wa\Ԧc[7&8\[99lhzC WBt1grY`*_}jlÑ4*h-nEPצy3+&Q_'7rmu6 _ZFf,BoIxORyj#$&,|b] l;Bi8/'浇/O V RezT\Vܱlje /v{do+ *7T6>ٍ < t Sհ\w<59m IDґ"ƅ`R9aDد.5&o9 ۡFjO%݃a`T=ȑjX~j3[Z9Ęg_yJ^j8\G+|~=Y]82zt9:brו(ttP [Zj Dې):o|X*lB8þ̃]c ϔ:cϢI_vh9Or+\ _]fO[VVMd(?SuT&B@my5<qKl3N'u|No|Q J1q[R;XbZ9'oEI!s [odlR:0A=͔h!ʞuqGN2_HS+Iq}bmO?tP `Wʬ_ 7p:8e.R+WK}1f=.'MDwrIEN׭^EZjrQ66Irw UW_r瘪oSFgoYQfagmF!D$MC,O^tEtXܙ,4{ǽ7?A>`{6@5n9N:9/)Y^L^qthK=%"%K:NS[\$JhM9O]Í r-UYޡZXzSFW1~o1tsS*lU bk0c;nU6s]Ypq)i8aw:J 7LC7+ѼPv5n 5uJ,{.-k4.;pcɇRnO +kZ˶~ɽ<f ܕN.cF꨻&j6;D.sr[R@[(Yr)W1GzCv6&QYAezհ*\,{N P ӥ!k4!-4HKK{{!1YZw{@9n!kSk$Ddнۙ]ni/$ٯ5=ku>m){^Z]e űS@t} WXYvoxCv^uН  ǴPbO*hqG_^rtOMP8'0~pdTX9$Aop3dWfmd!=@jCcڄ#GIe}qn eLoGVpqI|\t$YȔWc}iɇ 9o-*LA9NgPq-1T˽A<ɀ',^ ^ pͪ3q1k?Ԡl]L1<3Y$`T-_;zB1^yPX,ʹc}=@KP<e4op ;McLk-OPb#WxeWA|>5`8@$:'S;T%}ݢzP4*w7s(5$q|k0xv_m[T9Gdoȯ)4ш 3s ׇ=sm/h J68nƐT %!$0. ܲ8Q`}@{"9 .#*H%Ɩ?h5m5|I{ע(A=HX?Waf&N6D?fdwëZ5@~rYaIUY9+v> }dU}6C:v舭kMiҭT3}Ǘ8u~̤PcFYt3dPuwAk*̐W^d[3Vq|mt(E֙l5AQ/82概qEB >Keo&R%9\^jjָo\qB=s'Sna0Dz,%Q?;#٭Ć#W5"XڜҶT bڶա2<  㤗> stream xڌTk gm۶qgۓ955ٶl7ٮɶzZwu.rE:!S{c =#7@DNB GNjb\lio'ˇLN j`b0s3qp32ch 5r4p"N.i 20qqq:Y\,Ml*&@ AkNodLodOM pt(Nn@S_F1#ZX:Kbon|l,Mvv@'Gr,@h/c]=@v;:yZڙ,mqYzZ_F6FnF6F .0 oz&N.Ζ6Qd+GLEmmv.pO hQvOu/ jv@)|́.6FFF.0`+o%_@_K3?8og#7 O"8&& hni'h/|'K1xx1 B4b_@`k8>>|7 K,}D3pGcAoyY.#m]mlVSQZxc]]>Bc9_,4tZ)3o--=.&t#P@ѰX8 W)LMZ8 +A#g1} '#kmG_&}3$Ilm$ )'7Bwu?G~?h2X~0k~\ q1IaLCqX?_ ocb>OX?:ظ:#? 1ۇB' bG?nB~?d=? G$/ӿR:}T{cE~ @ Ҽ OՏඇ!|wq]j:%v'$D ;m1[eWz谖xg8VIc~BX:U=WGkfNiGWN$<> ]jvihųƙs8P.t0.ofMjBQO,'RʌuB,-L'oM|Uκ?1nyCt@6DՎ`'^=$r"qw,HdAkuPo P|5 19@杣-R]E,$umRIr8KE7T,{-ܧɮy9($swRqo*d>JS~?y3K}`Ry[m3և-.s7*ajjq 9 Fs u;9=yY\&$AyS|d\YD@ -Ӱ%]*LyͿn8붴*K՜U`D1n_I?ek1V~sfI}9e;݃'dNkЯ SwbKxh KdzP!EP2+0Ψ'WK)<>U4cotdž`peF(GqSi]*p]ͲNk\߃X>9^!З/eBkyK%@vDͳ{{^YHSz`#t6:!a>ڛSZ^d}SØ3ٗn ^,~! ۞Cas70!,&”yv-KqdT)Jgj$Jp(PIX?{(ReLl1!-(HNl5B+q *mWR ??Co3fڴ+1r Q2ad ogTyꂧԲ i'& $$[y;jw*6Վ{9xd ԍ7vDwvZ{#,bA\LK℟,DRM&%_tm+[&E){,'B, &WXUZĥ=X/>WFj*lo/kW̤?hx(1TGQʩFTU|u y~wx[ rbuՐt?k h΂'h6八6iP=1]Dlg0͠(Z(l@ ց:bnX "ZB֦%m'gy$;]u#fƥ-; sEa5iT0= ~/͙: _*Yʳ{%Hށ~`2p".o"b!y}J}[SA_bIXXN@) +O5 Ogn̂2 5B(YJmf5 (p*ei~G[c(2,T >؃/lR2@_pgj/gTBZ'"F9uDǩ0eHTVHPut7.&wrbF&kY+~Pm%qdM.j>qLZC-N_f7R esa~Ll'oXзN7^;:5׃Y1*Pm~ Gs:XmcaJ!d+~月3p}e9~>X;sDD8^ϓs=Fl;McsgS2)ݻt Y^N&dtfz΃'ᾤ4f^%nAĿ ~{Ue0 Ͷ@].jp%ᘻ/@ V'e0>4F'"mTAe엡9%-KE;r$Հm!yH:YDdHu,}s ~YXx j&OKd/؁}?Wl:BPw|l(bVDoq<( bo\Qr)LVlBuķ[q pa%9-9NDMz1t+2TYʥGm.g`ZJ l2HޕuHɤMjVh5ޛ( 5ɯ$ē#GYP)Yݒl\Bt>Q)=|({T QPY2-@?7O#6D$D4DVT )*<8~ޠaQIOi5WXjqtFm)AI$wȶg@7;NL@m2kJ!O϶m,| Ȥ@ f,IǿI%JP+)䜧g55^}_gȭI$;Σ$ab F%䖋#@ot @[*o +a鯚KJL4z:T/&6rTWߠ@?.Liy[؀VPJ~٬%٭ɽQ9NȃN9w0:ЇX8V7l)P3!?0)lsعLW뀾KJ#KBhV:փIa`ۼ͏njvbb]sRy{5<ך*&> ߽ h2IJH/\wO:d^!~>B=Pp*iRR)Az-*?x[l%y,4c |}}HS8 e7Id/ge-jsDB%iVe4$]2v*xZVpdYNjA&(N{cKc9cVHl34:B ߁Z|Gx|& -uD`g- [QjXȵ/ nJ$h"N8Ea ἂOP偌$i4ӈ$~z?Nϓ s  DteWLTb2CrM2]fezB"?~A褾ЃW Ouݠof߁;)΃B+OQBnY[+-u%9;v3I%}*(~/ٽX[Aj1j,.hm~NZ_r(>\[I sR^ >Z3{w6 sM77lq?t p,(J aj(Rĩw/`sE\}ftI1aYԖ.]w3G Bn7JFb9_ 3ܩ.#a:roZ}*l^ v/hsGk'.mGi2 li}';WYoV6gV#rmB7n^δq1E:Cw dK@о[$fUT[ (U}Dzll\KRp:Z&7D f-|몰 WCPwhtYi|_FaڎqF? ՏdPԘ_C1I*{ y C)yLD |^lG_#3dX>.i*FU IPa>aMN3/NJ*rtcWjh F[K&Cѻd&UjM}8zR%iT0!= S/_vk>ESU@RNq佂}{Joozg>6 < gfSXB[Q}'٧)I'xGE5'mЀLW2<1`៩mР:t4WLLYea'UU8x{L+ %$;:wq¼[0SdpyXs=>-efp֫%TZ7Um0LPRHdq0EpjŸag|6s<ͭTPݐQ0*PtƃHqݍ#0 Իmƽ:(mbwUD':\ \#U^ԊH۶%'$܏9DS$)졸U6RRm uL~5Byz9W[\=S&* !:W[=;)$yތ;T (׋Mxz܍AL#ZXz}7&l;NS^ͦ0GVī;-ik퐦eD{wRJAz Ty=3ʨ܌x14g/Rv6ELr?74c A쒞aZ % ӹBXD_U)~}%5 ܸM\-rjB4vCʬDٗ0K6_5hJl,!kUUzڒ!Tõ{f\',J 9 Cjuӷڴ5jVB`&c\7p^HG:?h8f*[rH5MU%ݪ" k^=o~pK |h3nc.u9N؎ө\VT2"1):]SjbL6րy*zoq Q]uXq!vfͦi/iYK,4osn:J4B✜2̨m}3X6P%M[KȮtev3ue6By695\!aO٘6$^dNM ϊK1:9 U4JLBt6#k2/RzeM#'v%€?42T ca@]C:J82^ON8W`°,zC]J(," +mҁ&(_` 9aǗ<' f(ه!Z*-6yE$=O^kGRc3zóGױ ]mj`i)b.~}M:u~-ydp* 0]$3޸M[,whUWKmrrX>0K-!!.O\1]Su_j@짪r1%ћ倷Z&C>ɐ.L<}Ew=gn9ݐ }<"30f>48r"or}M* ӏ; Sp͸7x…y]ݹ_Yڒf]SR``d::xT3Il#!՚$g7}DjWRS =F[? %=j`&ɐҹv9jЄQQI Z֒K/Tc  h%f`E75KnJRtc"Fh --Q}܆Icy"e-⣲˜D8^vP 6˷t"(fdzd4 z&k_<Xy,G3RG#K]`vlSنlJtZqpTP#m@R$ 27ϫ\?1`:-XUþˇ(eܒiu;417} ǒJr旜-mCKfgq)\qY^゚0o&"9XRYcCiKm4,4ZBF> ;/%;5#ہ?'F Eptdc:n7Xp/U jbb6{0\a" xڹ\gr,0- . 8\"p6wM..<tX |XҊL ס; tז'm ]V2귾DIZjʔy5Lg4$c;|VxN %fA!zQs/dNe媬csR>$BB t&}Iz2CL!l&Rdxx.@ң@zdwm񆍅W6Ƥ3cA*8ҽ FFX_,%m?Dx3P\ 1 :T2y0/Bpv];WSB 8*uOY4l?!~CA3rUoFtpTLsBN%&bY&Gȑo/4?MNyw¹܁ W%eTIGlq0Fٯr߳ cbnRIS_Udup oJA_,>Ie?!KKvS4VM@4ʘI/~=5%m~mJzرvϭ0"}*Il[,2:8#A3;2L\ƃ! ,"S6u_&s_bHux\?Uʢ' ᛨWX+#AS BCQP{U? I8ٰ^Zҗw88}8 Vq!QD'3*m>z%+Rܩlu<ᄐ:$"4mm% !fSQVY}p 5˿I0>[S[+HArI>Vx3/'n$3r8q^qduVw\:>:5UȞ= bqNǜ_r Y@Fj_|.拳f8&P=ڟ X<yJl7bkB0#9sJ&=Õ ӄn b8 e/ȥb Դp}3N`;M +Ua5Zz,.&cr@ ׵;&*nQsB܇.м$ф_%>S ,l{fQrKCnS7|dg+i`>M!]z.+ W  ͻ5[̂=`n=q>y$ښ]y~pORw-+7ҸoPr,D=)SB-Hie}ܡ[{Y"GQ?%'Pr vˬgWާCN,xͿ ͬsY(Xs6aN:_{W;րC<% om!8Nu8q(CU޹ 2O;H-1ozN˶by~"OZnEjzDY|7 K3vگwkZh|A9H@B\z%㶁\*dT$vS+0ؿ1cMeUX1|OCNK_zA3.8f>ŧ]땥XZ,AIMw؇CAR=4>UҖn6c5nйL%Y<,}w oH;(;%g1rM:FdbS#e=}zś%Dya+UwwÆH-O*C@~fKܕڹ& |1Wtc9= W^(î^c$]j3Bg*,)s4S=\Qwx%?.cڷ>3e W>~ )(GԌJ%ZubK \j< kk!Ҏ#J)*(X?TgbM)Hy](7 )t%XCAn.#aokn.)܂+ ZJCbYѨnpj! ADSg*HS xmZn>DZu[Yuaגya엤GӼqW6V\$:i+´KU{wRFB lebyp5*<%Uy=Y[HD3鵿²p=B`k( HW, Y!&n\cr{,.X~7 |`Ou?f=1@\2gګO*Уq>4D1 &TaWKցǮ5^+|AEW O~j=}6Ҙ 7ڽ-?TlЕh=3zn1\vg\@Y5<߹ 1OdaY+7yD>in&ZܫMzbBט:Z v #_ 4uG+ge ho_hӾOU"D]fQZi aL U :1Ͱ_|Bѓ^25qg^tOoʡ!;{';Cʓiuï 4#Ӱ}R$4CTPo8*}6΋j/LQ [5HxR1nO&Z LFQGn?M;X픩2h1kҜi+ v3aSԊjQO8`WB\DދE U7!р[\LbKNw, 5^VC gu6jM/&p%RL3RŮ$D#B\9rm8 R=hLJP78EwC]~϶EڦWD{w&uܲoNT񖟾:ˌ \8*8[9"USr7[+^#2uu-mثc=ȭo>Si{._Vo0~ۢ ^,)vРιG/bYX ?neNOQ2Jv 1z|ꀻƇNYtcE}ZvZ@uF([% oZ4](=Ao :9_D'T0TM&!QxVd.۰z\)@(uȬ4?bE=۔쨂|=}nPPBK}PӁA#gG,E2#]C+s@ \ 4SrN071aHMqhA"H:aTR¼لa'y*veN6g4(h˱'/ $(/mNm1{a vIY^[<_?$"[p[?h SڭSi@ _ɮ8ts5焞X3:FyNW;Q$oXfu:U{+=;QaFpJ'V]gdP9P`Ǎ"-F tvfB͵MbDj5cZ0<:*q {CAE`aZ3o#Q8's;P .͏aNlQlemyX ChHZp=pqORc Ə\LQlϴvI՞ 4H|u_bLS2fw{9(/%"NR_PuIIo%!PBP_n7@+3Q_WN\ CWMeQECu>HøгP /I>(]=؃$tc*WfF[훇+@\gUg*$7Vt̓Z7M jÚdL-_,U2~{hZX sq޵ZrY#_5Z5gv2nY_n/^8qH+5U16 o=E##<bIEHH[Y`P*CE}_4~ʦU9E]H؆C$_"dc gs),=9$h6" Va%C͟-Lh:ƑĞ6j%"'ZY7tw5:BB$?m󪀝=h3|'t|P^ˬ/Zљ_.;9 8T%oŠ*)+)ȡ~vf88N *nC=du$5@w%|'σ" <+*9@yteG|X_=ucY5x*uIIQ|1Oh|/g(ǹI8r"7+8\&χ^_iZ7 ȓz]HG-bhtbvsX2.G*<ӎlY'_$7J+}Dmf!HԌ:4fbE^fKC2PIY82 *e9x?*(08E#^eIoI6Yd6!P rQ&"dkS]7wh%θX/9%dk0^c ƜID0t0r?ix{0]F~#.E{iQyQ1y0DWT^T FU^YyOf>YIJ˷Q'9|swEk)`s I1Q|jY %]8P@~[ uplJnV%jKסE^ոqܻuۛ}56SoE@IH%&@ܸ46|hxkc4h%uuJgvCJnr(̦yBDYRvTgLl;ʤl9g (AO0<P.kך$rhQ~I"I R5LcF]q|fray+l1Vt2XXt%HeǨ/ sҥͨiv{'@3sCvE >oġ=pE~wZ$Җu"jv"{ MFLa_XB7mdw2sd_(j5bb5*;6Cjg <(Dno]>(@I |,\G$<5 D?侮 L3or NL ' +(\𞵝~uRX`^I~F(W@'`s=ۏ}Yhe=6#ߖ<'Dek bG#_*\%G,P2HoEFN8n{O0^)k%I#ڮLsXX\( ݨ\z/C"a ˢG&c®N6>&mON.}ӄ&ԟ9=&X|4ŷ͘"*p  E8 i WV⚄-ڌ$g:sgYKn8m+8џdˇ9NwR ww8@BO,JON}eECKpl4UN z# SD$n6 pAr$Vlwb, :9U9[-8ܻDHW>"OEE򎆇?;-VŽzI.!;%cW@q`)9D=7 r%><(7?Qk#*@F[j]\6e:"N^bkD޴4| p;(T et'*:ζ2b|E5h˼ x^jSI 0^ǎ[1MV#wlӋT ؛,}¥9!9)'vS맨FD> stream xڍTT6L#-0t HH 038 0t4 -Jw# %*ҩ}kkͽ}}f&}n9[5XEp z| Pef6 qp7 */ BA;& Pww Dā@?((< M: veVz!eٰD~\p  !.w+ڀ0l8/'ōfxB=*rQ.3]f;3 upڂျjmW0._ + ` g7]<qY~P <78qU"4w]V*\\P)B`{qNP'O`*ݕ yVSrgfF@ F8Jo e +߽p}@`` A(?`?!HS__wA>_^#5 cC?*'/C|B|1QQ,W: ȟ{P jQ]*OU912̀B@g,7ݝ~?n OwS RL&^5n: Amu ?$)ܥw@:07ȯnlߍTl0pw -[^( q+`:Q W7Do/xzN࿡Rqg tm_{ww+nWw-Exzi;~w]¿50 H:ֆ_Tzro~`4Ngw_bWe/Rv*;x;5YOD6OE_q d|9v3=s%) UA. OonU ?Y:kcT2ɜo3E MI4yz6A;z˨ȉ-Vt?r{܀߭)=)N:epEȪ >6M-  85/:V$$,H#k7.$ȭHfUn6y GyJ#G(50p~g,ـEf1B+%5ZϠEACuHug,Xֈ j sCCNukJ"'sz3ZL؇)ٙy- :x浛_سv=Qi%e?QJw8-Ґ_SkunXMzvvâ!C^C:f4 ۚϮ |AFը~⯺JAǶ@I)~Ͻԫp0{~}:Z1`ѽIvI1*024iJ gO;i%=Y܂-= c^Qׇ#M%QxOdy 9Zg!$CmMŢAs{= NVmrR\2v$z< ݴQرkCzͲQ6-cC,wZWȫ3vD>MgD5dO)⤉re%^U*n*f=`4oμ2jh.J6N 3d_jܗ{U;fTj*F)ij I y.YZWS'czY^rLzèkLX*SrzG,פ +YojEISjrHGLЩTQ$P W09՜+'Y! 3IjM`iA/VjdM&bͩD V cXWE+sYI= E6#;C'V21-7|M``4]0<\snef7h&t9h)ˡ'!binSZ&e`z ֿ|&/vND8ΟFs]"YŒ.+"'{BE-G ;`k:'2c/V0ʴ"xZEc|CDnK,| sUΐo@${o9ɨla57LLul|#[v ;7S3lC&CζRI J"Td@7I0Mo^MmD a 2琘Pthk!U>L, t}|]Ѥ :FWêjB?[1ҟxHc5v~iO6\=>u^KW~LU$fq%6GY ӸD9H׾i: ٞȝ$G!l/S% >< hZG.1HXrI+퇇0܆,"IxPes5ɉG-?z1T2󕁨RS͓sf^8'X R$ʉ"a!YlJԙ1r_>cޔ*kŸ|*=YƏx9q-B:: M' wRx]m̘{.:DY #ݕ4(# _;bU`<{ƸOWݦ̣9ACfU"SN%}S=O%ѷ x^$_VCiBNy 6RPN#vXʈ#D7'skrT`b]Ó,(+."#|M,z*fjƿ5A\nciy+nd?^x'A|x[T0.7Y.mQB";Aͪhz\Bcv a iԡ"+ 20+sCl+ROіi&Q@x"UA UP+nf])^%v.c B5 Bym&w[zC[/eLU3egx\ Er'+j YT7w+T2K؏T0'?Gmtv!&mo/v-C,*@NJ:4&Z[H2Pl24~VAj-dK:ơ#@PchpE)FkɎz9I=U!++}af8yFϓ] lZրYqBOXw"3iH_LH(ŭDU]~ae`)8G*ii %$@%~5)5{9 f pl!WJ?un[NY4C@xOJ/ Tztߎ$\"r(,Z⟶I\G朳 D-Pb]7LJ1t\,SA󻴌f4 7>iW'>1P|*L9R{M'3aeQ{;A8z:"@23 p|9A*>MsӻG-ƫF81XEDU.*UZ>![C|;朗|rؕ4zH|rU"QW!ZnL}* 2| ZnGU_Pօ|į6axIe KMK,þK.E t1D 5:-p;N*>U4b:}DZi%8ͳ$i'흰:9XԐoV4Lklx:cB1 a܃eI!_j`411}7ܛU)1J{!=c 0&2vRCuF(X +% i6A|ɳB^uXFU%'s%-=GA99,hn5rcOqw듂\Xi-1>%;jcn?!K4irp;J(^7U·*.Gz"]88Gg 2}>'~޷rezDSg0{ Dҡу4^0ڷDu6 (${-! dJ.Ku̧=mudR: ~??[t>%#eڏ+QI,VKu&D`^z f_KV$;%?UqL8gwJd{^'@׺iwen!>RQ ڟ| %Q@:!Z1edcUn,^/ULE0Ù Hc#"D?4D 9Ot(z>(p<øhggSkZ&iӋ].(ᨖHhW^b'iG3CY'96DSXþzu+ |-' tǣw?Wus3( fW5g!z\DTB%-4~[j8kew.!$C#~HZ7[kFR|h*>aI4TfPn1Qe0\n^eDZ\*{frB2-[Ohă۳cSh6>8/ب>$Bf X].,:++4lφzA<0v\ѷq3_:Fd/eQڢ02Lթ w̷aʎDGsf&~.Iʜ^vVS[twU cP,};SFiFSo쬿kb!%yצ2Ɣ`]:".& [mv=[.a2! Ӏ\[20ﺣܵUXQ0O3Mڎy.Fr2:]ns鑽XQ['n*^fE G(yA,].Q̴yÝؙfrݟD\ 5JH[għYz.!q8:k*U?7uj̙A-TvrNk$Cӹa ~M뷘oX_c>8X33P2|ƾ N`XLkh=&GˆMMZ`K{y q8إ Wc¹iP>k[M_Z(K>h ︦UU J -+߾{'ҧ5Gl[ { g%oMӡ1'u&d&d/UZ5Qeނ REn'M ObG畦4J=]O1>}xU܉o;0{X3Z[:!JH2uu{<˵;u(W83TkmvS롶x5քKDrX3Ӆ[jtcUXb.(N5#Nex4nsFИ ZFNF37,(, rN2_ʼn٘?Pa{߷Vzy} s,e>w]Ln@fR5茤yX>sUd]ڑ!TWnڼgbbH ބB zDv4CVfA8NNrYқ,t!;zcRvQrɬky[ɪb8 &|MYX@QQ:MzCqTK+X~6yL/#mi̧7 *jslv$y].Л l\?;ݼ*ZotXηlZz&MJe~I uɫ Z{-#oz#E_nPg$.G<-4d^7kY=?Hkݨԡs2nG>)  Ui}ʐWJȥ}]@dD+޹IiҚW}R3+g*$ ռߐ{r=s Wu,Meq^S۲ɼ^3UumbhEػokJ9dB\h.0}N>h7 $~4IopYrvRf x:hepϻBt}>=Ho1T%J2vVDgےIL4MOtnblq91)DL\?)^&[yaT?{0%f W̐}0O8. ``LvAQ38b=L.UcVT2DJ>㒯|CPs=+gRXZXWEŃ{d^ٶc~Me=2Psb3 'K{?HąɽQf >!s ~R<ˏ%d9}>pbiyuږ:F/`AF#7n}`/@uBaSDŗᛋ V& Qш=0j1cu_%q/5CsgHkoՃjIs$Ldb"ÄM13sϾYO^E>ㇷ[?eЏ;g )sg,rnqTf>rz]YQdy@X<3ǡk\ZC_&IRs2`D7rbX[ߢ= O⎆J]rc_o<WF.AjvRMO|iN p`.Zr:gg6ۉ\3^G?x!kX1 L ] ^b ׮ N1kj0D~s{_sS E7QTL+1`$Չ{]xyI?'r#NS=3=&V.JC{BBXi2ёE>P-8BI_XX*0~~;=iYu`f-Wl$B̊}73E{ATՙiSQ&t>Ē|,X fzђ"__nI'!mҵ$rmϑYګzgH@VAZ*AƬ7bt)|r*iF+)5&'| {T˝XWJ1T~Z 9k`[Pv+C߽77?OպݱB [GTʅiQ]fiHdg 긛\c"oah'Ⱥ Z+O8# kY9:qp2!>^Oյf׵ES"eg%H9?>d(g쒱Lc2%㒙㑷lJ߿;,# /Pd`hWe`7LɻۭBþ;뿿97l1쾱B{Q)ɩʛDeA4ɬCLLJUًꜳos#Ž2$dĸ'8=Xo2|>`ySirmp@^XD$@ʜ)[hqi8~j2|0xD+:`Se14D)Z2eTYCNKF򏵭Ᏻ?PZ0_&|KgoD|~+c\ӹC̤m wJmw*{DZ{4y{ D)0]՟A>PhkZi@H\~q<=Es騤a2sls4czD&q"kpСDbBln$qӷ_S(V4}cLJil Ne-kHsT.3MВu%rTogOJyy68jD;,l"0;l8yGJ`OLI X1$HEԨ1ǿ84銖gBNB?DU P\/B7a0v9y䥐_9x M[> stream xڍP5 E ).)Ip)^)V(V;Jq@yi${޳wQi[,20+';P ف@.4::-=O7 +@l2w}SA nNn AN>A  sHC,F' srX۸>.#cw;C@P qE=@]SQQÃl- 4.`gw%afht-~M3谇P 7%8@S^ G+89.gBdsh@V{0@UFӕ`hn{7w7؛[<޹9@F\`HOz. g E_e, 98.h'qAaP? + K7Gm( ,/gȣ 5 x`'d񫼖#7z$Xм]Wg7ZhK`@[a?3`|',aP{/<$$`o6nn/ ۫fso C`?(N2q6 c7E]Cjmw!.2Od:(X u8 dxw ۭhs_ %JƦ%G']?Z޵G޲ᰙmU/&bcr-2]Qq=..'q(X|c ָ^LZr$%6 "GMV .)nbʻW4ޏDSb4m;؅"E kzzJM5ngp:,3; GitE0c9s|4FAx_V7O͹c· QWQ7Xl"1qpĚPAi# $DC넟y@g)0/ҹT/-£\2VPؼL[7Ȱ(Nyҷ"~^黛Bi"/8,E PqSn7~yt-U,!Z>,mQw_[䴂<^5=$1 3'i|͹0`ӻH%pZ{@ |H-;5 Pcnxq*\]E orkրMd׹&)4y`7u`#OI ن܎ovw/Ls0V3hoҽ:[xf*cfRK7̷c\;h{= PB3;QR5jI*,_s tV;7S鋟Ga Ǽ' ;H#26 RR۞(A[7zB XzMʇzJԝ"˹2e^S vpcExYNJ91Q<%Λ(ςNMy.#Y׶k-RzA BԧSy_θHMÎ6髻oKxz*Sً+ ):c-`[V.>O:߰CgUjlav -icB7@_e\2u:pqOҙVκ:,ЀӅ~p|Y(Kt{wi|/Lu i}2̗Ө<=P:"l5~dGl Q6>$̰Yak=&P/%*[4\<NFj *O 60?5Hb4u)`Yb+%Q[bP4vp*1-fIp^)Mo*zz*n ƄDE{,tćGnᅘ&s\u8>K }`; F6YwA`d}Q;\%naOt/'SV$:$MkhAytٺ @G4iZtׂ̽qo A]*vk{az٨-^k%Cewl &U 6RQ:g岆ԙ#/i;sK\' qL6huZ4[%P' 9$lqUEi2`xUNެ?ѽjGSѶvYqMDo?_0zI]hŎ 6J>^}!3c p05ӘqrN_D\bcSwTwƱJm|\\ĮnޏCRlPmNنl%R{ѽ QrSiwˑW#z kfY獻HKq]vAc %b?.$*F)ˆ㊛Mgo*=_ -0ٷ Ux мuD&VHV>eU13H,Ɓe&ܹ*~gAHc9`DMIKa7BSt78<UNg:My^p߀@{\frgMŎ@.~ 6eeKRdFj됮r \'\e5N$-=1G!SSOa?QΥ~q{Ah*r `}:g Yɡ,*c%$2>I; >ДX ^D}X>dz ؒBklkkLNՀ6zeׅ` $dTfx 9yn^_KRH^=h˝s7x+z^U̷3qN vuk`RFKfQuPXTS9F3MBʻqdI5g2BB} >m|ZnV%QŨ} &eYɜD>fV{NZ!6l}|CegJgHR̀, #57OQauឥe~gS#>.Js>QTf\cSFgf֨A&?4M}=,GīúP k.X\i\`/❺N3w__g7 ]*_:?LКN{6|ѷEћ"[i/ :/-o&:zMG//^p>lΏ"vYlIDpvSdDx/,̎r%D6E2qI7G4/xJFu:KITks[Q-R:%UuxTb }Eh}"Yf5F2M>ͷh'U%J?N7?4D7[PH,$\Ž6)(Jެ: H?@ebxi>pALSrƏnidmsab&.wWpɭ&ί 0)_䔿H Jvv'}ҨGq l^î={5 x<雝m w*rVQWBΨI,fػzKlj٧@p}#NsXBo{J9{X8&˔-6ݔ0*Ċ1 ~>2;a:zT9GaFBeN:,V6<1 ̨ڎӤo|/^ g;KX{#^&[Nn/)+~fKf%¤i[ 5/U$-9z~{H4hx!W2D1 0 B% a}ƄႃHuRNߑʦ,GߛheL?dkuO{QyD0k̰O/eʜ!̽% aE&b*h`6T /(PkJꍣX=gL_xE FSVw,ڛc6b+eW)t-IRb imȚRG;KoG`$[9}ףi"NG"i%.ߊx`9/ʉJZk ²^՛kD{S٤xT) ̠\(:{~/5'X[H6-}noi!S|o핧Vi7$Qm/L^JHQ6:*gGiԫȔ }1{~#V;и5q}L`ARI}4d|%#b1l.œ? 32=ѩCnu;1񹄟Pò"MM'QL=l9,4MXW&h#twaBVTrb. cG${.?Rv .|{#=v!?N17R1'QrV/ƛsa U/up_JyPN_+ ,Z Ѥwdl=r{2RsQkf5*pqO. ž$(>=_RLBT,\m̒w+F;cO ʓdj8M,c7>ثN?!:`tD>܉j\޼ng&#I74d`b"&)g tޔ;b_1 \ە$Ѣ"r5.?5՝iקv+[5sH U_GыT&7I02fG94{N¤J| &k z$Z?;(:ڎ٥Nc!yENxC ]#o'BЫ䋈A &B{lP#BT7 &AEG hr΋$gO"o|?!z O*')kDo>$|^x6mSj$P+@e? zj-^ڱ4-@[%g#D99iG&@\L2# k&!q|OgȀm47ݴ!3Qld'c$hԂFx8qI*guun/wZ5)k]Uk۳n]"IGis˶:]cD# ztfͪAϖ"ռ Ц3*/h.\27ɜYC5xE2? |=D}8!I6s*/m(_S~p4_'e/X=YvI/#ϯFY*JgՒd-8}qV!6C=_ݍvT-;vT?CGɋ\?vtxH̏w#7lQgY=p9m)zaM%W%_nܿ05 w]UϾ-7pq'잵9xeO0+黔]KUndbfeNxPfxw$8]}Ko2Q ܑ;H.cR$9HZxM7#:)[݃>Pxs M[T㽔sjCZrOr{"gD"{8G*&l&)% ¨ zOO <_ ෞXŽ3 :3ˏ\yd`Q@s'|f8Nt3;1!irJ{Vnfa)` 13}P$95א &70]$? ManPX |Ha^LA_B:He=9Nӂz==h [?@(@e2d sZpYaIG)0Adbintd`Eo6 PGL¸#JNR3!-`/$Jv[!ccqSI\n>?SbWTH?*~!Uq1'/뚔LQK6QV$ұ~l3g-w CV'bIX;E?Z֗U2d~v$(m(j`W˚Nʧr3n|ȃaV^$A™dR?$SCj% L DI'`QW9Vק _J+/||NH5o)jSB>CiRq6T;"y' <h LeH^'568$ؽ S恑G,B ?}0]ZwoPD ['G*F>)G9vEWؿpA\U:yƚ Fs.h.N&50\~\Kdq4z|ub׍MzL_~$+>:+19D'74?1O+gmȨ:><,qq{ R2vP:w?*KFjAYu!K wͷF.%y.&IX;;5;3yL4 Z[~rJ3&{Y̘ ߙЖ(@qOXw0f֧5HH9r:%a a&R|'-9~Jia]=d@DfW?å|GL[b׋3u]9jȜ3dy;tž-HzL=x+j.yBU*>օL qk E"3_t6(6d9{ʞ֪ tܜh~'td귎CV !+K_=9V:YbdFũ91S_8Vtz{& }ݓTZ\s 793Ym齷] EAk.EZ3/8y>+PcѪ:糛xD< ŝ]?*4\qWJ(Iإ#yLc\XN$Ojz愊j @mv!ߦw `L#_&[B3uA Ԡ5*@C^7Wo`{>PM۴5$IS+O}-u9m@m;|ijށjgd> stream xڍvTS[-MJE:)JOB"H  @HB TAAR+HH"E4* ?3Fs=_51UuE9ôPH(D ,T74b`8AV04B/:1 (fB DZ"#`Qhy 4ꡐ0 _{`U^\99@U w"P \0lпR(x`> P@@CݕEp a_tFP711?ܰP4 .0$t@s] B +W"8w0"Hw42bEP/G7CPgCZ@(_0.h#{bɚHWuCb1_Ӏa.[nYn(,p_?_xJ`90 x~%6B~|P>@7<X( p? EBq]@g; Ov< sw =rE! -Sc=] ߄18Qqeg&P_g'. CwK PxÀX wM?dme?P;/;^~XDsoWk؟!6mB񓡊t-x u#{O GLP P ?k.^O ߩ&~]Rr5sR@( IqpC ^( ꧔8CB@ 끆~#F6{{a@ `rr竻oT9DG &M~4di/#it4Upo^46:& /7& >PPY 9 EE?OƤ0S;|C i}򏢉 vwJF󝟌bEȅviGFr/E8yGc3,1l|l\ X>Jf G$>k/R(e_*_]q_BY߇юJr&Rq҇Hjesn7UPˋqzWrMs+MqkﱥW^QsRkr!p \å O)\SD*j8HDv# ,,8(zyy5}$&7 O Rx`:6E0'%}7c+q1EWGJ|Vsjt~.!d_RQgc+_9e=`*SZIA#FMK'Z}^N;c_Zj4+,Q_kw)=ՌMGZ$L6:=peoJ~fk'IS>_ܰ07ltps+MeD7?Zme |MtyE R׬h6UfߎNg3I{<_RP@*O›roeÚθh)k]L^ k]!_g_u@>hD7iT&j &}VHw(m[ֳ7?bͭ}q0l\bDxŔ\E/wO'(UP}ځ[7tUzX}Js<8^޲!5Ls5 a=ih?UxoXRD0Hc!2,ni3CF/̷-Ib'yh~^)y6oD! ۅG6`YMx`luż;uݺz'71<dDUx'qy:YA$?jk^@b_?L(N9ӵmy$r7IT/ >6 PΞ?O}Vn'Ur&z)f,6aJחκfX&շ揜h/An^7QL&S l؜Ok? =ڡ픶CX>hvC}9ee$_%-)WkC>%=0-)F. zGaX"1vmq`7XZMQRˁC/ܒȵEv!Y4=bԄѣjI.9yQmɃq~l+CWȦ=Cqjeן1x ֝fk :Έ63ljb+N6Ou?H`^(!"D{;h{pOl pf$aI/Lr$q>6sA+yu.e/ռ7윪LnLH,.K vSl,a$5"D[lxDWNܒ;`IV\#9nPϡhscƋ:ֶr- m.#V͑m>8;n]ǫV_+R*f=e<8ޭ-;Ǘӷ o<K6zhJs1䧥{Wo [GZ{!g# 4 ש.5L#ĢA>@p˕&T)U!az]K ;)[{yC#7bl!2T*!iaŪrNFRL0OcQjf[V7svĊM/7j؄fuiy̽m8o6xߤoGcЛ˞O;*XGY's)Ksc8>;)y@x"9w^"kߚm}ȑ[ԠW\T*Cv]ifIZޜ|FGOK;x{ rmCן$CLґjzV=)k "k`4۾U <9snoXgn% ~!%pJQCOq]N㇠KPCg6#U[Վ ߶W{EjO~i77?HFbrZωYF. !aR \mCģdыmH܏nt*fӘ ٱU޺+s5d9(n2X0-oC%oL&;!T~$.u\9b!XID$L$ߧq{`xy^FEU;<}+6e5>% 8E&-/W}Q\&X8W΋hp ׳%Ə&cps|BmmUDq;v]aeK?xu drN9m$x %&]ޏ}K!<4MT?!YV扡 xS,pONdL{GFӟfqԃp lŐ<$efk&]o_ˈF?o}aZ3dn*L3Ιڱ|/zKUMgmG{e\xb9XK5 f"/dj:Dt4J1)+udeevg3^n0g0ST%$7SjO,=ݝ[FEPd{ 6 ktT_~6XᾡoLCn]Mp{MN,۬4BIVaPh9^l?i`ist3tj)2{" .~LA5md]zF|yo®g{*.+gw [kH ; wrw}qD5+x"]~> :~PScJ Q% \xZ@vש$f@Z}W<]j6߆dhJqjNab .>YOLZ^Js4+83TjS8^l "+>C^ꪀ0bWS'0BǮmry40G3\FQSPN6r,8YDE%pw/jĆ0]f \A֡7>AIRٖ6-҄Ɍ[[Ny1ÄM0 Iٍ~V/GߦA} (g5j=i>5[;d7Ȫky_jK)rwu.`W 9mfL6m[ܦԪvѐVa(WLMH/ș_h9iܷ% ͹h3>ŷbh*xo]+"~~-Oĸqw9D*+ Rp~5P<! "x4HK2%im;Z3g,ߏTr;$loKV NcXC mBtN9$K q¥G΃?+t!_<=PX{Ru=H50?M\m40P:ͼTD ;.Q 9K3yrlkhU9jӏMU9-7a+(E>}#;$P.!vkLw$> ȍ1L*~|&SMau'JHlU۵`^87e~I 顰RqFGTFWC/XG;OGb\.%[sHTrZ-˔T5>k5GFo-)6S­)7srw**D!T/۾gdVzv }kswVH7o n{nJP) u:27IgiB;|!GK|EW>R>p le[ |ZK- kiw3gI%d[!)KS9gQM$b2Z ^+yȄk +,[e1{oDep ֹ&~wd0uMF.j믻ᨊrW^CSU?@5%AfԂW3Y>=^m_!,\@z<$UyO{|fe܏X6ttjX N i[o'C:.t]XSvBt pg׭wcyudշ)$wU ]k7d60)L[\ʋ ]KOY~_>ƿN-s`6RXAEtE nZ]e `z/'x2k'ۆY'*[KtIQjEɖ"$iA#c36&F% eg?xaFd/pw{*- 챟Py!˔E9 gdhS#n,](>*f-ކb }/d*D'rYX=$a)an 5B4IDDA 0T3$5B6 j&"tI:MVN͜a7o~&~"! Y$)땲3Lt/ 8t6d )H.9Ӊ\BCS..Oc Rl Lt,/>h-$(XΖZa`P/;_!ˆ"]pS%Ec+FYNF'Qvq->Maq2 Zekie>bl[ UۏInIbD oK16wxاPv,Pf/4Mf,]]JQ۸o >' 7;boxD+i|?ŗIpMqj$$Ɨ Lɪ}QK\/l~JZLumT^=U|սblOhfoeW8yLR-pb^Տ dϡf! Af]<݇wxWhC܏GM >oiXJ=7`nVΣ|)oqhқc_"UM]D2a/ "7ߣO9_8wO+% ٨P:NMlO /<(z(]@}*=3"m2ep963{Ms!NQ%#^QGn/V#-6cQiG59OloA3?7v=WULE5U)7(Rw\nLo8y ZORKjg~DA2jQ#f=#Y/`a"U0s6ЪfŸjڗR"8lA 2fO݆@~#gi$0̀O= endstream endobj 126 0 obj << /Length1 1828 /Length2 12679 /Length3 0 /Length 13823 /Filter /FlateDecode >> stream xڍT Nݭ%C H; [pw {g~{>NT&WVc5w0I9ػ2 | dGVڂ"Qk];L\l&oa Y7[| tpH ,Y{ 3:3zӟv g=@ dV`zO :+WWG~VV;gK!z& r9(؁ƂD PeVsp0q `37{s36@MF+X&w#&ffv&^`{KPgqte؛hblkb'q MԹ9]]X\(d#!Kڛ;ف]]'vjcalons7GV {HF?o&l Wc O3+?{9ta~x[~|\LAWg7Ͽ`3W)lO73/v`O?> z?/UY.㟂v9x|9\@,?&pQ ƅ\@/=G|lm؁mb7׷Ppx k@`7q5y Q{Kۿ"+]ͬj[z[=H3`fmlޞz-)io`̱sqLM. q|ކg_XY\߶,O6?L!>߈f ?7xf?4  X-oE,,c?n#e/_ Z |cm/FF_ÿ1ǿ![Ƿv?73t9]^o\ߘ 1uqOg9;N[4@ 39!ֵ!բD;c;Z_}~'We;ߊ&valI݈,=5Çd:ӂ07^p$ZKH̬.h .KƋ}ty$lnGe[t9V#F?x:4sΕ}v+{L68Gw=a{\ݥPkdGl?EާpoY,)ue= m]>m;'BKԇ[#3nUQ4k djfu*T+`s jV6 GnvhI9g6VK>DJHi&~8?;y2*<-Iڽeu,?bvXΜbhǂ\7sD52j~퓉sy*xG'7 pL98e VouXaŒMկBk[/ !!IӡւBl5I2v|ɍuir5r1qt2T@;(EBtac|y_A nF"WUYi,7oR2nL,j]Z TyvʽcG'Wch/+7z:kFJ9qtu3UUN.[+]VT">Ba 0J* k qfH{$:"*BY%O'HW%0tЩBD DrQxf0Q/!} GSRn5o鏬.W] PT*9&瓭#ᨹ10c0}lh![/bZro!#g5(;жwQW'_) Jx5sEqo~Zjګ2[ T=Baaſmf ,o~ЌQڌ<@Cŵ@;hW+[FL%I|\p;'55YW6&7쩘EgVkf a4{Ͷ^2^ w$2yl{FUo|_y1Jewb#<9LF_e&&Yb2(RGLqfJoGL~C>]lB7 ?`+ZsO7S:, 8|eVemi9kgt&O݊e,P3PLFhGlX]Q.5A@M0re|D͞K~xx7}:=t٢!(xƦY+Ɛ#0[1A ' GP{Dk:?PSŬg۰v~2͈MT{g\V809T:KG'j桂.j$ +Y)eWbz=3{i6K?&XexCYifAKFBxձ嗐oZ3gfRqc<ҴִբJ;@Nn#\ic=xϫj$#ZK^FS.l/5Cq }7RxPQE,# p*H-;6[sc <PHJg soӌŔGv1ʯg%d쨬Di'}w:G$b8h{R6|bHlwG^t*_ 8*(dx}7O)bOgj,zZ<[$q)il[ Cw:B4[CmV{żT\uq-rmY5 CbY;򲦘g谉Z h<'Xh]o975@2+0FBn9.'xp`!ċub02C!0Ay䗌< 'ywjvsx)!q8KuWѕ:E);%XgSiJtqM׵CLLWGj| it”mGǐU!vڎ&?IWGs$էrY#3݊c4 -(x )|}:z@%Խɕ(bJT^TD;يXˏaV֮՝ XIa|%" N{޵c(χyhv-?ÖfK߯v1 CAr_O^gN<߸)w=$F#kƻYƾ04|Npl@7ŝ뜲L9W U):"꩗EBO)fRl k >xG o_{wT-t;\1#1dJ>A 19'vUkYQKLwdAXb2pڠ6mq/U0^-/E=E@Tض'a>BUM *kb<i#vuJn>h/G suZqOhy3]3R%*cunu4(@?9z@G׍"\F3 Do?=8?t͇Ѝmnf-TpB h aø@VNh(#U+&BpKaإK%d& h88L94r[D'_fO}e2 ӈD>RǦA qDhDт$r3~bJ;3Y#MC-wzd$Xg Kwݘ#S׆Hm?pFN{Kn>$K6)RNLN d Ʈcٝ("dZ#]|Glt!>"7g3Sګj ')w] o0WVFJ%;*Y{ K!90U, > +`td>c!F,8 w'-E4Wļ4UJ4R*lF6u}b}4K /exBvߑA#| hQ1\zkZM-B;nt+% 5'Nֿ[h6s&S;𣷳Bl?n`sXO"P: \oysrUQ!~3rڅfbw' k򉹊 nMqcW4dbuQ腐9D!t/376x觓Sroh:N{se8v3JU*Aʰ[߃* Δct̅x} V2"Fզ3F:2d>| 5s @[Mk&Fgߨ?I -IJjqKœ0@/E/޷̔Nqs}*SmB5.`YT@ss@ }JU LV1>fbFר',(OabRѤL/fxa쵳ʐ$ˆ cnCXRn޾Yבq;"vF&a"h/[i^YrH%kY ^eGIg0ŋؒQ\I%'WZ \Yx]m?R4' @u[:9] uJ'Y J%y~d6&Rڦ_z[$8:t&ArH5-#"?3kk v\JQ^B'DB$|115LP |$&˜9?ja..CClXO=)hyBoi-3TL\jp*i;}vnYR?m)UC,xty(1(ߣ@xEe~}̟+rf,M f TKcAoJ44Z%S\+t\5>&ZķƯڷL#IJĢ;;_T_``oC$NC`'Qh+S2Jw Ӻ/WZl`W\W4pﰽ["P(8,JSn'*w]Q.*c58P |,K{?uUL#SzWĎoh4gMX94ۮK9Sx䉐:(sytI(lj3b!ŗ(mv4v_FqR~FAo̪PU e{gն[N{;GmؚGDN@dZtɫI˖8\^8[axi׶ގd2;l~s:B;I|)w,V4J\%„eQY!%HhoAFl-4d*[yE*^ep% 5W& c+y+BUxrMoYRCfe {[.Zrb "%iL hppF)}KS`\M֎.؅RzNCN΢83C-+{ڭt|B`bjG%]A-\ -)91}i 0:?p/q@tpsѴI{GF)f/oa:jSF$D>:(V~RVbI$VekWefJh/,]H: ƤPQ''7{@f#N<3d R:Ïͺ(W U9o]07x6JEz~7YilwnM$IݝCKOU#طlQA,)(fJOAr˓lxɯ,y3M[ zWs"3s$pT_?!.FWCMįb1hQyBD*K2֖$C(#uBH/u#l~h/AZ]T9i+_|f~ޏ*_?]lz40XBA٩Mo>YRKx^egsHtO8q7U*Dq(;v/l4+TCxa~O?]`ЫDF Q /y+A*2RAz saFaCRL,C?_V?F2gM4a&W%Cd~A>\?I} mւF+/d8Wk9?{B߹:˙O4W\ Vb*O۞A-kTQժ9lWM*ƄNhݒKyg>ju$XjI8bY=M/+ŊڧYų6ǃ?vK`(zM]`e%`*ȈIhKVu .&Wf"@;L4N9Z٢;W 4آVX Plzwͳeht Gĵ/|wwaxGU"iRa^z PYY!u&yS9d&x4$qa}7CX߬*SKp";g9/|o]M@{JcnQ KhXe̪G su諆5wu,GwyJiI^mqu ՊIv|tA!W>ja$@"#O@nE<ɹUwHFO̒'~WoX Rzz.LyWn9>F2BB#oZ$#6"A$$m:Yc siPs(ӵcX4vi)g Xrw>8k=0a[C7!aE:LׯӥIR66aCBnyq+m'NM|]Klktq(`8,n,09b7d`z{wםd1i3]L3M΁RHPg=GK-91sR9Dvv,$x^|a6pȻ*D pZٹ|G+h ' C誑-KwP>AyLZ~2RyOmѝ,T#pV;nqQ=j#Y@xAO7@<~Pn_Y!Wsj|ߢ&[<jn WSԧ!0`n}7[<SX;r[XK,t-R`Кa r:Nj\HIh cpop\^k4xl yA|a;lszǶ$$jVĻaɔ˾o>xf B*1)W+deJJrlʨ9C\ъ֖#x0s-B|.B-&Hj|t_mw=k2LA^HU:m;fXuPbϳ}Hx.s{@_|=8L2Os~t47kzkXe4Yw83xѥ. ohReB 31 םG>O!tA4)'31bf̃J+> u}zBOBCq R:&} pFNorYj;M=#''DmaBRвtن/E_b^b9T/+exq:QIsm!hXAњ'/:Z])Bfc-p{B3 ׃,DDŬ~-،]v4p`|DC*LJ_"qqh. @# Fx(V2]2O~+$ 7B!RGFa66gi:WX9@8k+Qa*@&3ЇY 3ӂZtH[&TˢjsZЭ;;8e*DP\O!iWM<@, I=]Sv(DB4&{-3't/n V?I?uٚPx( n؃ZQaIYJ:az"aׅf Hf$p¿+FY(XuWfyf;EyKF;q핗 PwJ2%iotUw"gp¾}ߵf C?r`\!47塰~+ߢfbL8)>=ã4]b}ak3s*1g>F-ӄ>d;{]\.ёR$иocu~&br9?|*j $ N9a1g[W܌&-noƺJ4A54+p! m$Ԡn͋5A0kZR擊o{R MUR/^qDd y9"aRV(f錴BWlȃ:8 A~z| FڥMKc;$>,6Y Q(@5Y>πM\{Iz^ 阘1E? VOb9> E T^ ` KDՕ僠G m̫I7|1^Cbځq12}rQ#ozj|؉ 9uŕ+]aCMO8NVyhQh\tn`}g6E7[1@q?ơ%*e#]ܢˡofBu70B8!7rgV~xK,%_U{$Ga슔l:J[<{Ԑ`6y8yUkǟM,oV:8vF>n͸w="OZvZy9֟ $d݄3NAP>`stbrIV ]+K%3qeMTLqi&Mgp6X]3y{!Y2§7:ol񵣰I`hg5YӛТ Hh4 ‡TN(v i+Yp86競b2פ?)#*J2ꨏn.!.,r`Vijzz~YG?;>V>0뽂sz $Nt={3"_H߁'RM$TѢj 9&/ _爸+v0da]ǩ;8@ͳc!iOLGRW ie܄e;%RunAy5%\]`%+nslP WIStZ`1Dh&Ow2_#oT*69'ZgtT=%94\X9oOi:s`J8=SB'd32r6R *k- 8b|aIZ^õubwbJ(YφlicJ ڑ\YGPW>WA;}ETn 5!y&*gIZIЪ1H+-7nT,Rɤ@4jnPh3jcx@%; 29 Z4a@%FP*Er6tH-=3NLy1I'M 3Z OR(sc45Z8G &z5+6#\rLvC(v{Qwpiͽ"~OLfœ;:%hcR;nw3I'Xae z{GWq ʼnz"ܬ1;˹ CɠHyu%v-tsfx^&@eo)Ϯ~YQƤ_d,"HnLe1HQ4Li)W8»6ؕD |FЋc m.K(CdžWFpr&o6v}Tx=tJafFb,ԾQFV8 B^HQ)qFos+5hXh@\IxHўl ̺h&iEQHaݴg4*Yʱ?"́bgZ>4T)֖\meI6@-Tձ;nhSE3f]T{hd~2cL*DaK=T}ɾ/R=aJǨEUW6;D%-[^r\ b t;"EaNLXDetHs1)$EMin;^Hy>!@ Z'Gqd[i*Ϩ9ݺ .J?cgKwJ'!9QLn^gz5 :z %OuOj.HlGgg.q@fW_> stream xڍeT\-;!;A;P48ww %]U}>jr5&13{ 3+?@BQMA]ʎBMvѠPkvH8.$BUȻ8ll<vVV@7@ oorFwt[X@<'Δq- l (],A@)?&-]\YXݙNw%=2N3 5@J@6`S3䐫 PS(;&+M`<6foC`MMmv`; 9PV`vpa~6@7 h!< - BrOΦN`gfg,Y~ZLd;>IRyOZlmgnbavtIY\\Ƃ SKN=@)~!yz;;!| 3 pqrz[ `6u,v(C 1d =VXe33{;?͢#%O=L&v7)K'3|?A%{Xt@y:?l_ R? -?`@D*v7U n+VY1; 31sr-;K=@f*`S˿xہT/ ֐KҴT ȂW);S{ߛ :9=QX!f)0ٻ@ P~ "[7HA|+E(x9,j >?!E;[XL 6rZ 9?$2Ę -ڲ9 ŀDcSzGWȬc6@Yk avj{P,8-~?i@@ұe 1 2 "䆤n{!W̐˄1.H 'Mq;W[o/OX:IDsG倄rNfD!0 JhHt_Sr$<ʞWP Ka;*#VT!+ :USGK*(,UiV^uU'\8:Ps"2nD{"si-(&QR 9G\%Nn䢕 ܅'?jlxTd){Sv-{F,{<=jLQ/4O*Lb^+r@6D&~G;3lҠ:Pf  VYwPća.}do[+#iv`ߴ@r3aBq!Lx?AXs;P<|ҟ3nr L\~xu3YhV^rQ:8jTӔJ݇i8%Zy=}BL^ VmEYwǵ#fJ<%"س J$tFf|x螇>䵕)_?u3-"o%^ ɇًMp?} 0ōZ\^eTk\3nrDD8kM}lkW.~qFݗ0H$m`s$u C'LCjfmR91XxI+FoCwֽ,^rpuPXp:$h$9} 0IF(Gn>~bįKS@B#!3N9#Wq >Mq{1˖AGGhwՓ$MAyE_ퟥO^"x=րؖ%Ļ>OG5v%1cKPvNJ^:[;3E{ã)SX;mG-?b8͘{|5:k>Ʒ'!dD*@|$|gjmFĀ[SńA{ b{Nt#?+Jb!Ǫ|7c{e k"j*&ayV5Hy/]ѐ {wg*uMa_BxFyJMarQ{yTL*ENz)#f/80y0q_λj>`kjL0잕G˩_DX,>nXKsքsE;JQRo˃tW'x!7/ [N,^=ړ[_puhW}>6] JAK~^X:$1GL޲?,!I?;6ѱaS?I&JPbߤ{.ˑ"^4"RqF&\],^4<(& 4Nj";_NTp˨ԥNݙq3XYU%_'IIiX/Tx^3! nAa?&㘕QA#̀{$5]j4gW)-.5TOL]?o~pR~" *V%™Q(:V)ȩ^=qp#z!s}K;?Q~{ƃlفb&OTU6ٯ6) ͜]pc4_:{fQ(MFs- ߔH$K=ϽM<6ڝ̗pƭ5)>mpxz^Èkټm'Z>j'FzY9+ETlb+t`$f"kN eVDaF ˰jO91:wk!zPϞ7snН!=VO⿫׈5/ V?l N)C,_P,foD&h¢a(u52[҃ _XZ8tj5啙=m0?hJ=pA&HC+Riw h1Du[a7} PNʧxd@g_3mD&Rrhp̡>["?CFq}^ vz8vu&|-̌IjO FحiD m^ӟц]\z=:vPxQ\tn m-o˭zS0,d&"kBxHD{+jߨf>QP%\$U=^Bϋz`u\iv*{G;혖Ⱦ\1G j+cSP7&t 7Nf4`e*1Ӂ;K$;[r״ ?"#;]`\5$\4۷ݻ'kqx82:+f#uNw88@ zEc_عWZV.`tL+6.f6KS9Q\ =7ze__!-×aJXSa:2 (8OR? cM ?y\l_"mҭj`'ף_$4O1^Nk`D  zT9ڏ5˵O:o;~c[D[U/Ny~^u,D9ۿKX \*AV*LaQ~m9 ^MqxP0;^*a$N/ y掳{ظRq8] $tܲy1.oaEۊ\ٸ%T5F;9)vA 6] eQ)EIH 0ۡ\1RxGp*ڌ̨P%8\ _KCcQݍlng|fΓ)2L7*۽.&88seO|q10a}I]HdO~r\[=z.xқ>L oa 2@[y,t_q64=[t)@H|>΅L%͗qk7lk?G@(rl[ߕD5ފ}RR* Fy"{c3aPe(!6]&=K_0͇97#:k4胄uI6qZٷ3'>.3nr>=ΐ177ڇ-dY/0)0u{[ Ռ (ʞS1 \ȓ6@© j"dj1x]ai#/BtT͔zW^L"P]HBXIV?8Ѽؽxdnj:Qj͓'o)?J\;$>ڙ=<"I^$'.;' -#;/tf>l>b ~ȓ }D&ûz#ڸqz!I.`2`q+\Pe H2e-2_VC9jx1r̞N$,I*J\|Tx!3FF\w~MU!Y'{ҙ7,d} w~ {@q÷ ̨ (sC4l?I×ߩ=ZfKHI! SzO ,5~ur浗=ٌ:v<~뙠P8g.VyJX]Fc 25pSQc4vY;&E~ Vʹ?Řσ昒#H+Q ;#lq\61+, EʽL8}ד ri*6sVԗ-F31N bҁoBUC{ j4lI'mW57;u1dĩ԰.Z=q}5V.E뭮9p Λ1|N$/z'evOCcHtQBӖܴ>|/E~vOqXp/AxGfOYZLGJzwtIUU!䏸^, عk>Vc2Seg̊oʏo-) WnCvp,EԔb5e5 Ϝ2ƙ |og|_+w.Vhcp-_B hIA#[mw#A ZP%C Xy 9R!2ʠ׷W³+Wj( 0g  c&u0jsb(_'j"*\UzXj I/+-V?:rW'ei<38jʈ0%* ~65.rj0|Ʉ! m$rM 6j.C)眾 !-PŔ1Aഗۊ@F100߰+ΫÈ z~P*Tq4|5/2Z,F/nJIn3+O|VTkn"fokF 3囚85"& 9X30/A0D ,xA܁TK/ӜXLZt0`7i&M!l{vUP?H:vDkc+fh4^ ֜Y5o+FU# NIc_(vs0w4c@!c,WBtAS!I2vbG cW(qzW9b۶\Jl}_dxӖ[U;\2w>#t(,\I} 3z})e1*=OsMH"WM6p:gu~<;$O<c쐜фx)h}YXmޡ5ӢߍM6bnQˑ..=1[.%VknvCd"<<*o#n˖r&\_zu +bx[אG}ER0bo3G;~w/06h%RIiud NS7pT0MBFߘh\_?+ 5ļů4x.Eiݚ! J}M咤lᑞxBX"Y>'& ZJ@_}W{>9!gKKߙFg#y`6U%?L{z3#p4ɦAVH,gV ){ebi0f{VY:xv:5̨Lp_Judxg.'ch2_PRګS,=gξf7飛/S\46Y<(#.[X:"~C{ >X uP(6vyҿV?`I/i?'.]F' GSyjDQ'|*naQ4B<>SxTЀƘG1Ap˟**  M=z`=)Ev/~\8̄0h{TqfOY;`T=K\. 94&-ŀ:^6-h9TuM3"C\ߋaz*AkҝftYJ|$tV<y`K3)'0#i*;:K̳€l&[P+y9f>wЛ%݈0,Ղao" ړߪAn+ҿۛ;Ilf-o?W8<R^˼A/X.@>{9kN(1րa;M V{P:(8J?+'j+^ZOͫ1o&""ԊZJ~f#VUb4Iz1IA!FQP\óu{# 7q_fqLMUD!՟&b0RETCajlLuN^z]V ]XeP.rƒ)v;=ɏ\kϴ-r Tu"@S3RSꖟRR^3I+@ EhI }yB)=vӛ@[Z. d鮙uWΑ$jp4^TCd'K;~_='-t.F+6>zw;ĩOT/@$ׯr0'ȥ גm4 OeoxG#%/EjyG/͝JA _W0sěH1:H + 3{6﯒*~:=-_MH""RN(N\ɇp ye w~7$C!ii&q*^ *:fRslq >.#>_&JFkR =H|̴'skƐo4E04*UH')eՓPrckc0b[>o?'%gs }k aA|t`sUD];3«WL 3Ce*(a LAIɥ%xcHY $l!j$r!)M2Yף5XfIdޗF5vm(J6òV#]&~¸+~JjN $֑a`GϮI|)4gT{H.[澰U[OљB=F񌜡R.{v_G?tdE/"4BW*ŕ;9PЯ6B-։5z(:>G>ܗEtPyo݆ƙ'yE"7m*h׼nb<ιpQMwIᛜ+O%K"LZ?|~>a$58qٛތ8Q_[G y87 Di_3/} Trw44O24i$>>ː!HA󠇵6!vM[%{`4EZyFK.?1 뷾E_!).7IF=HN+`|=ðYGK/#)GWꗬKuD<m[S2\54pK/E}Zy&$ TY50پa1i(OD:٪R65pōya]+Ol#{:@E:`3mG( (6(paaļF<6)2;HsaDސꫥ;O} H6(TzY@ ,GI_o #ӳNhi%o Y:NÍ[J= :LR-*J]MJ QOVhvp'<𧗿G|JWKbkB|yҫjy嫰#Uy9TP$a"R#^ȎDLxz]ۏ-~֎׵<-UM6wqfOqtl?U歋e6N ti|9d*(`@GWwo \IRn=gc_;DE-"EŰ %zx&%LJTB?mm"txaعIpqc72Eќі`h?%y%U7#C.Jm YHedNF>Ҧ-QUG|AK TB2?";`lvZ҃)mNZRQ!opWqڑa˅<" )u<;7;ZxNAQ1y7 gSت|RO ^50at&+`5t/&Bq~wKVk繇Ay{mqY%`Xf T}.Ϗ8n\=ɣht裆QVb? MR|/1 )Khx "}X=M. f%$c`LQN Dnҍ0]T22.g*\DE׳@+ nIyUmHZsM'Wmn;7E֙ x|["BTZ|AmREjlR?d+q} \Sl񣵇V ez i72Sو _sPR&CkG"^6$Lo0Ē;k-ֿ8-^6LAAvj_|Ku{Eb10DR9\@iJ>R>fnRF+w>[3ޛvyD> Ha&Mmka-KԔUbn(]ҜM"Z%{|S^ Hߩ$(ԎYԮ܅@hfuEsp߼D(lvƾgCFGxQ.˩]| u|}LRɧ'B αˬ 1"u/{Rŏe4U&ezB$ac@F#걟|z%ʇi6Os:U5 (~ lZ[:x21F:b9 xVp"goLRt90\.Ğp4O^[v_IJ㧔 ?q˄!!f!wZY8Wv2!o$VӺx2txPR_)8:(b:}vHz5'i,| ,T#"B^r4i3&ESS0m N %yFˤIV>ǘ, eRp?rw[k ̆/AkFJ)>wDϳB]% u%K|zq=NqMSE:ӯq#~P:Mz"JMV^UqPsiqFE5⏊Ф%$k}g| Pog: T~;D)OZF[rq>&Yd;ԬёUżۑ5!;܄x70gj2‚g{]T,ׅكdb?VXEl g;fTf' D 1xt\>NA`nvh%Y+w'9m q՗8[ TIJ]K!DC jy# bRבboml*0E=N\=q,z룂I=ggKe>&ݯGm'qxGn^ 1ESK ~*h񁫴|+y4[{2  (iiPgAiITyGE88B ø ^ w:YKM9ޭOR+w;Uԭ;ȿ佼swtpwAT; Ƞ47{(eRỈl@xa'{G]Z@cttm* X; 0猪r˅l*KLl #8*&]plY#r.W--ǴİD'J򁓋௕f:xI_I|pZon.c̰7;:й>U\}H`۠@Г7)' mPJn.vݦ `mf7sh|;T> F\T^hk!wkZ[d1}K~c|O\īmeJ;cs4ɝ:qJꐝjhJkƯ v2 e-CiQ+d?~ς`Yy[a=zaT"좫0as2[ڦJ{0&Y4/~6/6_jH9_u!liڏXm%2QtHy-/SWpp7a0-[Imy9 4يtCO3Il{|#>y[U_{dM_ĜvK <7!9\b!2STs"̄u_ f.r|-TAl䱸aE/#Mut]<>ke>J/<>Iej’4 kn 0*h"FD30XHsqɌtGYԡ10H"]!do``l#sK .OYg5 _7e;_&cd6Gs J\ĐSrUb>\:c?y/-O.àv~E=; +ۊX9(Q3<\EslIX5^WnУM۶C-'%&UwXɨЁ;+ M& <D,;۱,qrnC$; <0=ǁر|1﫩_%G1Clۢ#D{n6O۸ȎGYt9Z8pE~XGj\$lom5BcWt"޶%1(۰[ٯ;% endstream endobj 130 0 obj << /Length1 1401 /Length2 5902 /Length3 0 /Length 6856 /Filter /FlateDecode >> stream xڍxTS6"wkEjH $*IG^#Eқt)J/"={ߙgfgv6;1#Re]cK! M(o;> EGm*(4PhyB"!1)!q)  J DxHT콠]F+#}=N(to\ n8p tQ`7tE= `A(qFܥݐ'9n>7 0#^`G/={7jg(/1#!pG]`w9п l!Pj:( hC"^P{5EC=~H@Ba8 J>fU2 G!OWOs]o+E]} TAms@I11Q!rUیp@4PP@ts/$pPh3 ;kp[,faajJJ?$_R _'7V{GFM8&G\Ɔ z!PB_C;_YWH`|=ətu}L0.5^jNmW0@cj5`q֊3 i>F du!}3fI{#%1BFn0?6AY W 2BɦP93&DUg5Jy{=֠$TM⻗bo}ѫD[_-;l%-L-0P=ֹްn[VH x <2cf4VM;)=jK<Α cVI0HYZ×Қ@(5d / 2L07^@<+Ѭ56AF՟+"7IAµ+X4ƽy}[ԌtVAO{(2򙻦r6~5 VJ:-Fh+ԬK7,L Tn3C4<]jOiHcN˭y/>QV[sz6m/#\Cg|Z[A\NW2xlKQ!{1QsHϕ t!=)v(dx@=^1 8(<z8aU}U]Pa/K#,2Lfŀ3ArW,[#iYÞZ;\<첁2pC8UX/EX$=S=@kX֦HX  TPv|C$jge|a{!U<[ GܧkR Xzf #<` w6ɧ`{S̵Ɇ5NcBkO |Eѓ,1%Y"/r^MVbDkE PBLl(ѭ ;|hyq%^E(Ƒ3;[q>m~M*tS`X}Eٶ,L"S?ګǶ hgA2`epb~qMEE钆^ L TM)t*CTIcp9~%,cb#%Fl[ڤ~vLP]Y0 }?KB`b7}{jt}E:DA#MEwN3>_Y*)ȹOn;wcǯЀ $3ù<˝<@;& p3o|} ؐڰ܋jt4;a#NTw 7N p C̼ݯOk&7< 5qɋqRqS_j(E݁ysF=Bֵ8;r@qKpU],t ߺIP:u\oVfXjx6ޜoţ@:?gH ]@)W7Moz}Eim1*[7=0j=U\ƋnxFЪ׸)0 A1F4>+K!]ޮKQ4LBxPޣP6 ƪ^3yh7Y@@wO_&3Oh:)&&-nϾ%w'h >eFqO .>.wp.y^~!́> h6#:N:9e&-;WqBDq!q<:F})F$d[+WʱR2ю1s%ĉDbӇx\!rPzgo^_R )XK^Uؾ0l2m>O`E` X%b1LȤQHȵj4CPU=G]qQLK}_ ˶b/̽~{Ōa*T߅תT_:ПqNcA$xj-vm vdK0B0){%S8S\y)_pO.)8iXh`.5s->8Ud\?<0kґFڛ3Jwtc-*=BoaBbuq盨Yd4vAHtϸlQ^md2O#v*qh=\΂[:˰8'봙e;W2zi%G(ƒhKVWEM(njKf?-3Mt88Y<6 ɜ  uk]LStud?w+y@D52}92Y;!,]eK_79Krngavn$Xi/]Ft2?vc]~54Z+rXx>!LT^o.&Os|毚B9\;dv-Tlm˙{f}i-%ymp2r]$;3̰YlrJA[MLRuMI`U$MY䦝'-3۝vaj}E- J~6DOB؍;drV{^t{k֎}ɿÐ)Wȁ\i;l)UVz<9R]=BM-9k3>gb{)KA1t>W~QAMb-RIA;0ΣKS/|-{'mM)Iw4(ɈJ?PXW~΍]}#ז9~*鮮n;~SC8/ O"z: &TȎK'y5O֫}54`}=[1m'VqAu\q%ߐqYj'^|=8!ٚPj+AVA#˩lZ">glj24TOOp}Qɾ P9_-JQk1OQ{#AEf# դ%-5cL/*|> )^{8%F=Kl{ArsA".aa-קU.jTY*DAu!9MB2]@;FV]ԓ={~pnuՐ/d&>xZ'˟GDn?ȺϤ]ѿ]SELkR?ge3XvS%275(#OBRfՖ7HW`H4&yff 7 w:%%߃J[H16 +Y| q5r-) {yXJKL#cZr^oYB貌'!#ȺGO%c iH)ɫ*^'o}֖'E{w IG:/'8?g;Y,Y}yj>b֜7NJyq gJ6"ߺy4y_aj,{Ϝz.4_Pn88_~t]-&}M,R;7;vlwe.2xIQ =uVѴZ?*u5CWvQM ^8a6zOt(?y]5? KA2+Z$}g"檟.e (gtb 0,(⮔?Rj<8C"}J4eԴI76n8m{ 6IƷ2lo,k\bX|ާ{XT ۥfwd*0E{E$fr7G?$.iwVм@:`Vyd/d#/{vdxe)b7XuynU߱04sVtJ}cW)cZJmǬᛪrcv^/jM@s8G`XVt.U8ᾱ(/Y)OGd*/MYS+;nя^|>xLҭͤK& m )5 z'mɆXQī~t-C-/|O&+W#snYN̲a]gE:)qG('5>ޔJUt +^ AƱx'BEԻt<~BN݇=cY3.8=(YE{;̾HoOlӟ&1*i$ym؏w4qc|*?up|'V;PuwrW]0g"陰>vƐmAw˕ו4MK޾:dكN:< _ҝ \It~^$+ȵQƆo]o\Pm̈́Ieu!ZARtSrCBoSY ۟|Jϣ]zJ^}0A+'NfIx~xOQ>.+=FhmhziL9,/k4MumTtG剗=T&3J^Emy϶L;ޝEsytp f|Uyvgp_oðwS0r:߼Wdi|IYZҀ?בψV~rKXqR96@T$Iۚ ?Y6َNnj[U/(n4R.I9ϤD*Cd= ʮ> stream xڍP ܝi=!np9sf|_uouU,^kJf&@ {Wzf&3\_9_@c뇡=@ `aab01q fneg8]E,,]?@eJ ` lt25Z>2TL^ՑÃ΅Baj P݁f?(Qc#YZG`a |lL..nf@gGv@hcjpyOgcSS;Gc{/+{ -(!J07ҍs1urtuap#a>,no&`gwu>1+gG߽:\{{"s+{3?h92[9#ؙXY@'Ԓj^??88:8?h́?p>.@ߊEp3+SW b;[yt>Ə' 3s#fPVJO= oR%cjWgؙL??.&(+pSO_aM5YgyJlߍr)YZ91=V@%?=3}ǝqXMX=v||?v h\?\p);Q'Q `q2}?(7b0X 6?#߈#? hb@Ʀ69 ߊrMFLl?_e4H$2rKs70j7djh w 2"m??V_^ĿI?rQsX8:Q+_E0HEbE#ѿQ3_]`/bnG?L.f* G%eH/A@1usvxy}o1 h `j^σ`@3gչ:.7x^8{?8՝ћώfW$ك.钟MCjBoNA6=2Nn\JEhMCU?&—8d?Vǩ/|^&r'ADZG͟~'I;c-fZҋCM~:1K#r.SQſD51D;C|Σ+'d-9A5{jHqCBHlp4!ҙL=ZpgNi]1]]X]6 '?ty(C^J3yCOj 7D8蒴,$dVNIw hlzu]& z}Ժq$08]f;/}oM.f7Am#6M:M™_JTHYl|CaU mOc :#24УصtKK #R@1'Kuǧ( ?/>#C#a[:ژE*c~PɒlҏLSW n}GJRW;?_O93ߧ59Z0I!4CrйK-ig`nɚm*`m\e0q#|<]"vm:ڗDGs&^_ϼu,}gU!6.Shbl]I n\V|n[[Κ(!/^)).+5FkՐט~h=u'VM}GײhUkerw)T"ەv@zvg3s׊cs-oMrw~Ӭ™ ErxI ++}g/+ƚcA=U>"/ee5š{.( 5l#ȌS$ICbst\FlQ 3@q`:7eN/`4G,le=Bջz?OgO~ň{kSvV=GJ[c^Z2E?N`{}8f 4ɗ֏ȍjo䉟G0_*\?I98.{08#q,|ᳺ&R$LXlGz ̡{mb=#| YpL:G3˸)ˇs2-&TgV"3jx'Gs4q}#DNxa@cy{c89(ۈ@ ._~KJNh(A7OSFr*MC:"CU8jiVH"t6+(IrܮV+.Pf Aj)첞 >R"#P o+)DJ qo _-`jQ8 dp|˿y 6XUUw,7͖n7D3 ̀246 R# nGӉX?jУ+:h^M-A^* hZ=|0P`qx tB⇨f8*PRx GnDqJ-; zf5)])5D+iNyP=HwWnkNi2nD.uPL?ځUPvr$liXOvgr`pO3؝ i8|( rF~#;"G`$@kAEEA0[+zYcqϗz]N$րb:L]xfE+|sh]{Oa3H"dWZp@85WpmƔi*Lm B`7!cI#O NI˿# i .;B0FaXF9][uY}؝u8~YJw~nԈ2j摊 )ؖ{,EM,4j$kE~+d;>aXy"2s˧NqeA ufl5$,K͡UޏMMyާO][*iAv-{M`$cpɎ nzjo97^kQOsIWMޗ,^XR9hns W:Pjxs؈4 dQ=gg' m` H3YS̱Geտ+V5+3ܠhא8Qb$fom!T!Fx":(~1-Rr"Ԧ(Li[ȸ~g"x$@2Z7"w +DBm5[MTNUQeJ_Toru:Wbw7pgWBڻBw ;,܎{f"SK2*Tj4lĹq^ F-oTj`ѪI͓HcI )U _"x>-hIE1(blrBr&7ͼEAɷl}`qFZ8;s*TsS>vٸ#hoSdbH驋gޤdBkLj+PI {u hNipTQ)A{&"S\?$67.x;wLY"< y1vP:1]I 1;f,BU{I0?ؖ%uƳ<5sLb([IIlgT #|DS(C fSU3[m0#Aeh̋4O*3ҵj6W9&yR)f0 T [ˌ$v:i ՃkfpB%R./wç716no1K~li3BOu=[89ӌ>^fΓ؞xDϨ2[K׏ͪ+(q}p:~Λ(16wzwmzghwoٹ}xS<gP3iAYF1d(j)jcS9!I ,ii9ADDtɈԡz =.t1i8P|8ntS^ENHC"7Eukͭ 9gD/GhGWghOɅu W|!w3& b/vO@.dD)OxDfj$>V?0a@͡ҏ,C,< fχYo,D/ЕIeu"?g^(MA+X=h$"l4tRLVζHWcR4IH>*vPP(ɔ~[9UamI,X@8+rʢΓٷ#:v&\v Ơ m)ػK$. 3vv1?xkNs|kTS"w==WG]HUGwxOY{чPUḐ+`E_1+h r&TZqTdpd~49F΂E~Y+2CZTBj%D=Ӑ o% e3#[s4`nCL[ج=v[׷Mn添EpהҰ E]ќf7 8vUrPHͤr/9Cp:7|"牸qʷIUm!i?_te(շ&6B؞J.hIґ5pyKK|5HCwLڃVpE!Hr2=tܗ 3mC$՝%^^|#yyi6̋+-v /5)SwBN[nۃ(8p=ċ1"^^,HyȻX+qFg},t,L+s a ĞdK9套D/,(? TNkÄhz9"VN.}BO,kL4yrWz;'b.x[ `wӘ-npmL:|U_o v.S"͌#mĈ߶$;,ʛIOjS_[U]PH..ߠ[ `Ulm|kΘ=Af#ܽrBl F#JNj :c+ B~ILؑB.Qۢ;9l<)UC091݅>b2fzvMyizߘ f2Y a !VS.Pڊu M{pyim,%#SAC yvA }9pps~וt_2,l냉s gG*09B#MힰXW6821&,_p>A'p3=C3#'e(Ǥ'L^'A6G~V=ԡcт5o17I U5s%! }%5ј8]-3pߩ%u \Hд]ѭ~rnK~kNl2VW'22}_3}ٯq?{Xoœ^{4 r>:S= Dkښ5Iu2STqL_[(cC R*InӤ!>w$p83xj@5}*ޏ3*fas/]Z6y#\8:sKgiY1J}&*ׄ"n=-7F"BJ~:FkM&/)s'| p)֯a)JҨY?K3 yudKͅGҶ^Jf(޳ u'Z\g>?kap鸢$sq~8޲ӜP^@ؓLil _4J,F T%?vÉ_wgk _EBYу>ǧ د*ia' Cg[gPﰘeVan.*WË5[]K|@/ﱉP.`%~V~';MY-,eD_|B{WKѱorF|ke,O.7PDuӒ_Cz,eq(2ʾ+i_|v ?'S`onla0rXiCD66|:Lny 2JKIY9FIFNZǝZIO``,sFIb=py 38?yLT`rqE: ~p^/t<Hߵ9sg@Mbٱ--;ݿf~q^j=к>Zˌϴ`tȡx"%PGm ۢlvvyIu[>gV۹X$l^\) ]' (]6_IJs KVI'iڭu"g}Mmlߤ@+Pճ@ejr&Gq\H 3-|<1FsiU{Q50SIMZ4#Y׽ԋ~*,*I{topK>-!Tqˆ#KVݟ:u%dS|K9 k6YAɠ(vHݰd8OTe9A4o?\捆3 )Bۓw]˶/K~ MB_@j@&.4ܼP>c_M 4^{zMEdPZAAR3]*FEJ$ŴU"aiGsA@*,ytT s//~ٰt(Xe\Ҭ wm&ց.!_pVbN=Fdab]:r,a쨠eԶ=u O@<\,6g/bxXyMD" /t*8EeqzE\C-^s ys:q%G")'%QM V)r KjXoJy$ pvU[&Ef v\l]w{-m^%G鿯SNk[5&}*(8y&FՁ .ad TM6x a7 3 EJ e#a"L`_|)hfg8JGb +M%nӽb}*gmO_6A+_͈K)EW}4wgP=ASEj3frR Ri^vV+;+/?&w 01թn!:NӲZ au.~٩x,Npp^Bn%XN[8]lH]fy:cE%vdD1TJb?wXBS^F-BsӺ.Tz'Pi q0ezi.˳_r}[5_N M4E@Dy4pIU!㵨cd&x/$m@"rg٘`/QȼNdG#E HL7YƅU0_5$eixDUqaN  3Rh3vkOi3(XM;F6u~3KSˈRy1_ s`qZBM.ՙ樦3&Iޫ16 ]r׹3-i{w9*EʰdN]ן ,=?}%CӸ;f7=䟣{YY| n|x0=^A.nV5S޷. AʖQa=?E9=}-/zy-fmsM c1mJ:Ho|N*@3rm'u@2PP:?@;h`gZ7 }s;SS.*|*(A}nlDoqqFlh0A~ְMdg qmC;sQysJ):zQF&%xkǑu{QSʕJ16gx8CNI2!EjnKXJAᰍ6C7.s[o:xMykqY7x< flxS̔ {(?;i!J' MzVVɐgeQP_X<{PleaJh^:ٞkb}Z~dIos&Mj̻ A< ( wZK_Y'CތBZC<{]=vsSvW)OkuwrbV\|Nq)K>wN\'MM<,PObC]#gE|FZ.TeB -;hP{Q:GMdP^_k/KJeR]$˘!cҙτ7C L).)s0<7e[# TLDZm!ę]43ĩϠh.sRN>ń] ܅"by3Z c&^u^(@IWmLXNB(A\o4͗`t~Rߵfۆq>W$:yʹ <۳VHi@ξk٥R-W$/qA<;#V.dQ2 (xy#YʢGk7wJ:]o{]L*Yu[ce B kIwXilEK~͹pոÓ]E,J>< ,;]#6 ]f#g`q 0ffEX͆FA9Y( i0s=@XӃtKu§YbIՁddAw' dۄOv\WeuUFr{/vF^B#r npsb,PP%yꕱ<؍e6:wu-2`DڐYcR݆8Mikݟ (~!|Rylih~ Lp:ZK0?(꡶_ב O|%}/P!2# cWa%@&! WMQd4n-2l ))3kEO0lWQ;] .xiU7%y@`ZIa[w1 mvsDeobyęmf$@T力bҮkwte ( \@kWӈ$d겊ObFrʔcvxcEN< JZ#^6qžO1P[)(pvHF蟰nWBʳE&Z26Df1H ̱֓O%PՍ[4P j%;w=>oٶMYpQys ,uzݸ)ں3VJ;3x)]*MN=Euث8Fe9mGkإז=ܽ/+FNYM&4[l!۸Go-y7ȑI c7S_TOa߽Q!t].-d>KH6:ă&)@o "*OX8Z+ĵE,3Z7dA!E[GZ?W^MnM@ % ~iwѠN, Lec%~  x#ϳT45]:WhvZ,,m7ijZꆫ7礇B\+\]t0=m+/A5c9p/4h NH: ΪtѥXku^5{od}a;۞jcŒñVׯvVZl-'G."ML&e+p_#rRXCQ7}F2@'~۠h;j=歍RWi6{4b5C1Wk_d$8CY\M]dj?eB{/pQNvQ:cekM}z䆼_ؠ&GD\j:imRԗ{1~_{A9[[G29ymU!yWT6 ̞>j~R=]N8,nYظY\ S (z Jc%ߗCFitk%_b-Av|lG،Gfޠ];7lVB5ZxƲ z=U߇hn!^eAfվ)lӣ2zn<7 9;/ՖTB q:{0wU$Ucez zy`-VT*2x`ZMD<0l Ob "Pq@2̨-G.EWmwyꗇF ¸g (lw] ‰:R8&3`ܾeDmxT6iJog: xH`ZR)`**صrqfA'(}":<XZlأ6cD㖨#mM>b>IC TрZ'YIc:'~o&K?Pf0Cx;0J~ tSuvPIbJ `3z&# `}MaA/a3} hHQ_W,^-܂"a} AVh>˗yi_ #?zTR.:Kfb]P/@C'+4N_;ʄhoϝ0uls+s?܅N_^܋Нr?<9yJj~*$'&#bҨaX{=a/@-B hM.u08vH&!\Gw0T]ɟOQj7xy+>sR zd>"jFr \ 1:WJUF-:W6`2h<!q\|z`Lh+nc;TBx $a1VDfAt:ϝH\x2h-rCWVwRHԸ9!WԦdO+ `!O_n2ϐg5W̎d|TIQ^M X"Ȣ٪X)z_^[@Rׯ ,*X9,ё&n+QuW(eRW}gk0w %A0aVND*<و/NCHC[wPeGtYdtZq]~kCבM.LnV i;?+XZeqD[*XZ|pW;עdj)Pc}XAR@Q ,6Xeo).c0]JTJ:z|0l-?1}Bx'G,IW-D'ƾ Qn3=j}?jEڼlaIfIӺAq5R>HOs I륣0ģBbxbSEߦ oO =kcr e+`!j8'd@"#bk2:gK޺VbIo>*A,ƅI޶IZ r5y r@Q0Ml'AVͥy3uFHxdɹcV+cy?gA endstream endobj 134 0 obj << /Length1 1607 /Length2 3234 /Length3 0 /Length 4242 /Filter /FlateDecode >> stream xڍt 8o~![d)֐f/e'c2,,QȖ}fʒ I()QȒ}/뚙93:'dPtͬ(@5 sJق*LRK4ȦAD32 0{H4TRC*! PE$S=/c2 rJ钽)DW7T_@' UU7m/BaIzAqXO#4Rhhjp8a02< K R|A<.8JqJnD@c`) <8DB$bj=&b ΪsCu$uVuG-("āt noicMۀvxsBe\/)g?^ ܞ9l5М'09W0nSw)*xs{`"ۂu\?_tHU+(~fhk6Yt2tǤeno$ qfn*|Kd.GWiWv7^ְ{F]7tgV\I6Loxܨ,LGUw3U{')&ʆTٙr u]G<$N>9! 4_!ڽ?qIƤ+L=DgK3_]I:t:fedžt ]w9j⍈ZR5i}A[IgFc*$L}8vnއ}rGɆjUFFǬ֕cӼݣV6<̽?J@c?r\6$/\tv[XY2粋M{qg~F~gW Q׼jV?&mͤt+IGݺ=9mҵ!WwOE 2,#L,;z0~֮`X9n91KM:bgEkmxJ߫ߞ)xY(uafl>m ی -Nu2UX>Ŀ~;Twif I@ 󵐮=Gp˾!,)MW 'P> stream xڍtTTm6C$f. )`aKBiDZRiAiEEB?y[gs{_`瓷CTPH4?DP20 !~DaG#`A07w8 )E7}SqZ($pb HDIJPOC!a E}_-7 !!;wmH@ v9_h E([8 \Ҏh$uvG9hG@sPgA#>ut@܀}uM X/3W!8w2E=hѼi EP8js s(" @ I vw#~Q*s}H;E3 vڟ f{}>?:Dy!4H;_$<\pWҟk @ q! m~\k=sz,?@ H?կ0?3ȵȯ?ky١ VS37U17' "‚8"o SGڣ?\_,<ן {mԵa?7@l_gNWM!ww C?B@_z4 51Z0;GG: >F fG:_M#a:(w@+v=mN׷u~`(_S'(" @ܠ> ȵED?y5G)5PqAQn; ")ZE0?L1מm=ܮ' e6`0o-{TWg ^|d&96Ҹ>{'sd.'v/)s1_}niďlMmJh͎Q-,Hx@n0 G8N>ՙWwC_ȣ5D|qbCJ8liY|w(ɦNN')sF2K >>Xi INgJˈ}B92駰rfƯ8vYf9cٕ`gy .bS <,k8a?0ܱNV9P"MBoptl%>3\ YqU7s_NE'˧PseB)- 9AtJEk5fQWaU0ZanaL=ۅg~&U{`[\k"!_Ş1LK+lUP!|;ʶgsEli,$`hjI[!u)󄰸4tm,6N$XX O>bNw;" x]:i;.66R(1Q[w(Kԙb)m;(k#nҹNT>w;=*b"8IR{Cݜ=0Uf*!ShTXS47:X?wv6|nLJiS8?M{3|s`rŁeXX+mr=, BlH0.id`k Nh%-ƾ{cU^&lpB(ދ3Խ !'R;=)fE]a'K/9G9cdUzx|Wz7 "ưlCܲ61#>'Koi4ԧ ͓Uw\)}Yخ#<M=^-cnOʾ2wή>^&\R2R=ZwQ V󛥆rdKɡ;<-?kSlygyXKܭ/<["w/wi i; 6%l5 (Gݏ9BL9ֈW,`{Q\4Ap#xT}$΋oF"_sn߯/w6F40 /d`?f-9I(\xѧ0WR~TZ^9쓧 dyׅcp~ $uaϗg[*(L{OT!t%C:?sbݠfVHWv7 L7> Imụ<ms)@dڋ~=h1Um ί6]tIzS6zJ)sT\A|Z;aWgzv[GsxT3 PTfoNdwIYwQF4atvƩh~!_bA )(sha!^ޞs|ff"ֲZ\HknUg'SL̷n/ȓ%`~XA阬>" 7oZ< .kKLgR}Ӵ8f)lb9E IUT–hha"o\41K_CpGa˜¢egb7qrlw7{Spz?`<_4b$6arki(`5Wk}Q \qh$EU0_ƝQiXo /0F +ǐX&QaRI_SϿR>*BoG.#Pi@Jтg,r@P!X0T`g{APE̽-fE`հʂGC;fo#*{j8_ŭO>_{p4h.kL5WηsT3 ;i-6>ƞ-7ɭ,!.Z\[70TPy Z?Elw j6XQaUn2[^N0BrpWTn9IÙ.ߤRxU1j c״fq";2f":\@}pXcA?F@PْV6lx9:ī[w$P͢`aY(sN GEd=/\j>fBry\5?t @zpn}1>vW[jEl[Ecǚ7DnXzoe9*輪Eo)ly}<]S`EMZEA~.}_~({<#O#_ѩ\XE~\g.;9Ke uu>}q:5TtI&kݘ+HkՉ%wYivu,؛7 < 5r;SS1IR+;' ʌg;݀:~郂bs2e* NKA[@$6 k@::}Z_>! MoRS8'~|]VUT$o4[C[NdPwq=p8@Z۞IUC,  ږf=i}{O 3Yc$i0z'D|SSѿ!Il # 6XtOp4iDWua\ S #Was],Aw <cb1Ҙo*f90yIho$E?K\d9.'0d5MZݮ*nURI裵2Ēz }~"88LN7$ xl!IiMCe]YQ`Θ>nyBPޢǟdE.8Z,֕b쑃ޏj<<3n`FKŸDF2@'T6"h@߸+,ٓqk=^2H_yJhP\;Td/U֮u Ucg_ǦtohOI 7艉tJE^Դ6UXq9̪2hp:}w.0QD3%…|qbN_ܓz{$c7gb_E`M1gF-lvhd)xzo*)*Pp|Pa`/AcXX?oU#Qa6TPݖM,Hd=*tLrҋBc[(I'"Icߕd3=,Gd׽xW9eI7L^ ->]$ 8 T?k=&O6޿CgZyn>s*MC z"8Kg,Hˊ bmmV}{jvɓSGM2^d gC DH:Q}$@tFx8li '!gw YVH55 牌V:$hؽȑ=3[&pVf;ơ-evmKv߷=OKX r0̀^!bǩ ?_nۇ2UűuCۿMd?"S_~ ޕJ5M59Xa|jLKJS-U{)Qq]i^B:-zÝ[m!Ӆ81,婼CD4Ͱ_փ nlOZw8Lѯi$wMK`S*]~l~_d|@TitM+hbV;tۺx{M3X%v(*^/sz YWs7/jѮyRЄ0h\a;ZaBVaυe=m',鑽e3͘~A#˭ zB^@~)XoGb=Ř[:aa۳SW* UŔ1xQ*:"MBhl7*ZVw])L -X]"ӭݱ,mv%$eKRFOR- 5Pwge#^Tb&޴Sc˚Vk;*>zx>Kr>>Y i#e)SRcH9J+4!A'> @ wՐW~KĴ)OvPU<hbQWkJot۶ݥD$kK߶{$@ ??PP?&"$|~=oHz䐶VȐ^>[Žl/lvofXc\. AӌIyӳvJͅw1 Uw̤WX?LNHjUCl 4m#v98W e)8K)sl &Ppo<`dK˸CS=qSIqKv_!6lg~/ 5Wo5);/)*bCqKV4 )z6$_eہk2F䯭>-=4KoH,w8w&َi]j hôMAT[n+p5ߨJKD.6j`ќt b+U>+.4P8_jEgVځ&UT _ZܞZ,~Զ.%x/*Z u/[\`U-׹^_O !ǖǏ\f8|(1v`2A'!yOTE'MM#7L/5(t77|wdw!y(a$%!u O;\l2Ag9 ƣIw??OPV 93ͥ&p8r=4g~'\ynoB-$&aPЈ. [V|9\ 3"˵ ~`W#%J ]RA;ԣ#<^3\͉g,m. TAGj>2N/Kiqh]6ɡr#lyo-qo kJ7JtR϶ Ki)F5qxFԁ,m8(@ymN#x VEԦBA$L0d5x;ALԋJJ%CuW(\x0bt#ͅ$ ExHbƪnT@}BRZΛn'x^Ӭ+TScl)/ݼ[xS!_a"/xSsHq}ȳW3:߸8cFi0%6Qmf1j̕3l;LzƊ|2{ly/1{QAŞ|=~a4ҥ2nH۸@%~&AGN[qςy毤*s GpXd9U2"+'tANW;Cf?5xs' y3a}`^,4m+!OMIqcv-qm^3HPɋ*`{DHJljGB8E :";zX endstream endobj 138 0 obj << /Length1 721 /Length2 4672 /Length3 0 /Length 5264 /Filter /FlateDecode >> stream xmrg4ju :ѣ D%.E13 3ѣN"D'щ5DF^7]Zz>쳟˥A!0HDT`n `P<V2`pb 2^ `@D!c ȹ*➋`+\7"=`tBTʹ @F`N6NH@ CqA- p'0h8oM8?Ю,Z-A t4x5â>_//u'!p$ A!dM m<?wt-w p f?wrCQ t1p 0YP_z9 $N醀#VB- ]O?ڏcN;z?<50 ⯽bP? \""X7Oa#i|žc4׻9$ #d |r o Y {igKX /(lok} (V{"B-XOΞuZjuӘ'OM{$ަ,}'OίmE3;1|KyzI!TB3`eda0$3;6/3?=KqrytnEGu2rHtn%MbԈpsڧ BJ ;`e`FX(8WD"Q/]*\ұaRƨoV@~CM…bԙe3'3'>]}TJT!{QyŦr؞{ } 2%.Evpz#J, Jc9u}-*;\pf4ѫ&wϯ,3o;!@ LGl** 7$WWpYQ5Ϛ5# o9-ͰEq?sHf =R=]q'b."_{88  8ixxs=e26R>-MԜy$l$Hr*ReK\w:(_``M:ǦBԲmhR@NP >ѝU%' 13atLjgt4O ")<u@VoYA38IG 4_?)o~[u.ᅬpLw$,ttQ[ \6Qb})Ŏ72K@w>T8~5,N乁c-Tlv#$I2<-fJLZ摳lru^Pd<=.m1MMf+km(=[3/71,(m}!\.·ڔe=D{ωM^ E2 !w/3+H6= M4A'Z,Dƞi*s\F. ONޜՍ 6 ۹,W!#%Xfo߷90 )!Us*@>i}ޟ|Gv-z C-d9Du1N,tA po%ǞMݩvIeʾ&Ĵ6flVk;;v^-YlM.#&l^D3 KYOhlu9ZM:IQtf\jwwŶLaG|-;+qm@٧ N4 8$ZTcg3-KVn*?CmY;S^cyס8'"R\R.E(/^,j&Ny[뙧}x0Q;>vdJKo7f>!ʏs5hr\TesnX͈S)lY,W%!%?b:I9;D>b60*/꘤p&8y\/+5D 8ǒܚsϩRXKIHdݢxN m& V}ih6{͎Q z|yń'<3reh;Xy3E ="A`.jbZ_+2f%vI^ف7Ҥz3q|Po_-g畈 eWGߚ&PJ/$/32pDqDwu&:`O#4) =lp7X\~\m+r-]hQ"eG>xTh "#Ud5i\*!' xAE@}oU4gnş5Y,tl:/IZo8io'"v){gdXߟ;ٺE+u7{</&Uiѝ*v|0l (kN1S#k>w?{Y9Ay|'?8*Yf dW(jP ]~:e!=0iټ౱]PEf-|ѝ6%~R)'ryhz`v,z5bphѵ1[$1ʪ{Jb~Կ s;_<9|9t*ʝX|Jy~>M۩^L(ݡ ֣KHڪzԴDjt³ޘy&m=t9+r[lS3΄QDgy+3f^x_hiޠdd357hm Oڻ;=F!}7;\+9n"jqK5T灁?"(l ,A]Dn,,fhaP)Feɻ3o52i@{;H8dg%lo VUÜ{#gZ#K 2f}{UZIݴzEW1M;7I^_w󱛍^1cŐ=!m endstream endobj 2 0 obj << /Type /ObjStm /N 100 /First 801 /Length 3540 /Filter /FlateDecode >> stream x[mo7_-w( N紩$n|P䍭,+)MJZz8 @Lq<3!Wp kDUBG*E!ڸB;8 c+L(#b‚ ‚&)a9;"> 2>ȉ51)Aamz ]( l>ÒdMxv ]GWR`'"xXTO:>aDj=qa("} " bCڑ@i/ANt#>HqF4|I)C.ԁz|  I`cϓZx iadГ^&0($0Dzυ|4= P|7+tWߋ~}?~8: n*N.J1a`r&;frvŻJD,*gd>-+k ԓs1)1;ɬ>N>yYi%j0nlfl {h~qYGC1*+6x(MGRAuڪфVlKeYr4qL\f3`(o[x\Έan4_g&WK~4B y8%&?ؓ'J!!{ÄR6q9.a9L#O˳`I)$OϬ>Pad vo(䷽ <ݓ9?&zrZ/ʑ_<}}dX#ez(!FY5>/%DC!OO[|;܂p[װ=g2l*TVws+OE>+ҽ\;Ivkyc[]э?ѵ1~ڻaj&ICt p?wlZ78 -Rq:|ݎ'mOVPSؔ(q_?2 /ΆFLة4[f/{m~Һ~NS=-d1^Nnn}sMukZd6#d.S6˓>;2,DLg,%_z5wi^wNUxz飈v37ǣ>k+&u2l6 s˒WCaBA"jβ7r&] WưGdEPǗ5U-1SmP48zkxЌ-00㖞%.j<p",oQˆT(LLD $-%뺛[׾"9M49i['TGMy${׭huŊX{i=}nUF6Γѱl #\xo+z3f,oRCB96ume7uGƭb0鈝DqP0|9:f[U`Ro yfބz$0= ՌWpǕZk3"ײ (U"Zٸ>lUXqT*ZQX~kZnښ6y&o<# RuW+) r[^iOqv z{N`V/X)x* a* m^fӡvvoiʚ7Q7EW. 7{'bݱi.y^cc"?bEN us5GwooM6g|6uN&2RĔF @_#(;|͕W}X@j`P69:e\,dζ|[u٤qWT^485oor6FWi:˧:OU|&l&総pxK_;njo6(/=y0z\/}O{h|0 &Ryyz x\ *z|?]Tr$'r6$gEGXT|չͮgdש7 F?U K}y X>'wr(d)#Xf @LtR+yUV陬Lʏe_Te)MB~ϛ]0ūߎYcA%u S2Ddr+.f=?}/IWU۸.s]]Zt0 M.:} :K{t{V~ӚP>>aǽ|\/Gta.7⃙r/7x1=r$?˿e5݄?'G'^03K:?<B:w7;W?aC&^tLw6uLiU,"gF#eN~yl0Ue:8:to3m޴jtG&:<=}1N"pnY~[tr4Y6 2kOow+Pyg(uNtK u٩<~uzI/QeD΍2/T"?>{v_E<{{K8n ۆꟾ8hܱTDJ0MڼPM+.Ee1sCny2ү_!k}dK?zko) HOGj6']=y4"{l~1߈m۷x6kwߺඥtڅƻݥm!j.uglN[ [Wt}->6/}Җn|Sz߸E_9NkAmۢś "3#җ:kAW4kѫ4ˉA endstream endobj 149 0 obj << /Author()/Title()/Subject()/Creator(LaTeX with hyperref package)/Producer(pdfTeX-1.40.12)/Keywords() /CreationDate (D:20111201115908+01'00') /ModDate (D:20111201115908+01'00') /Trapped /False /PTEX.Fullbanner (This is pdfTeX, Version 3.1415926-2.3-1.40.12 (TeX Live 2011) kpathsea version 6.0.1) >> endobj 140 0 obj << /Type /ObjStm /N 26 /First 200 /Length 831 /Filter /FlateDecode >> stream xڝVN@}W#Ֆ\ZZă ,N}gwmk,g3=F'LO$SAfbPR0mDW K0%3arSIꒉRaDE@fz(@̤ t4j3R1Ţ(Z@|\Q|mjyU7j&m?*UZ/W!T/WU}(ME~h{/= !>=j^_> !doϮ_f7ۗ'32/~6\ L(R{xX>'~OEŇ5_ nu{{w}u=/*ᨍ.s2l8T7XdABVsU+_Y;J~drZqdFpy8A=<6'mEbd' t^mz0!5Vu26x0,*\WQ0b;1l 8C}W-BwkÎsuΏnh wc>_ :[Gˇ:_PoNr6O e^.(W^.'%O˗]wCAUP˅^[1/1#)b0hu8T1{E`uҊYNI6Ӂ:iܵ[@pd|) u~?[@(tN}X)htR yu>_>EB3^o%ox*f"}1vwKuPp=وSm$(6ݑX[@vHӡ endstream endobj 150 0 obj << /Type /XRef /Index [0 151] /Size 151 /W [1 3 1] /Root 148 0 R /Info 149 0 R /ID [<3EB266AF104F3227F77C6F67DD5A66C7> <3EB266AF104F3227F77C6F67DD5A66C7>] /Length 384 /Filter /FlateDecode >> stream xRSAkq54DMĉY !BZȦwV| pƥo 6:](Lx& 8 Ҥ;t$tIg,ܣ  )i@3 tZENiKtectZ:>]p Cu\n@v4&]:|Qs{ܒŀvh`[fY( Description: 64 bit integer types License: GPL (>= 2) LazyLoad: yes Depends: methods Suggests: RUnit Packaged: 2011-12-01 10:59:08 UTC; romain Repository: CRAN Date/Publication: 2011-12-02 16:23:00 int64/ChangeLog0000644000175100001440000000246511664531377013032 0ustar hornikusers2011-11-26 Romain Francois * inst/include/int64/math.h: log method for [u]int64 2011-11-26 Romain Francois * R/int64.R: str and log10 methods for [u]int64 as requested by Hadley Wickham 2011-11-23 Romain Francois * inst/unitTests/runit.int64.R: testing read.csv 2011-11-23 Romain Francois * R/int64.R: implementing setAs so that read.csv can handle colClasses = "int64" and "uint64". Suggestion from Gabor Grothendieck on R-devel * R/int64.R: show.[u]int64 did not handle zero length vectors correctly * man/int64.Rd: cross links with uint64.Rd * man/uint64.Rd: cross links with int64.Rd 2011-11-06 Romain Francois * R/int64.R: adding names and names<- to show 64 big integer vectors with names 2011-11-01 Romain Francois * R/int64.R: implementation of sort for int64 and uint64 * inst/include/int64/LongVector.h: LongVector<>::sort 2011-11-01 Romain Francois * R/int64.R: implementation of unique for int64 and uint64 * man/unique-methods.Rd: documentation of the above * inst/unitTests/runit.int64.R: unit tests for unique