plr/0000755000000000000000000000000012467405772010367 5ustar rootrootplr/expected/0000775000000000000000000000000012465736645012176 5ustar rootrootplr/expected/plr.out0000775000000000000000000011725412465736645013541 0ustar rootroot-- -- first, define the language and functions. Turn off echoing so that expected file -- does not depend on contents of plr.sql. -- \set ECHO none -- check version SELECT plr_version(); plr_version ------------- 08.03.00.16 (1 row) -- make typenames available in the global namespace select load_r_typenames(); load_r_typenames ------------------ OK (1 row) CREATE TABLE plr_modules ( modseq int4, modsrc text ); INSERT INTO plr_modules VALUES (0, 'pg.test.module.load <-function(msg) {print(msg)}'); select reload_plr_modules(); reload_plr_modules -------------------- OK (1 row) -- -- plr_modules test -- create or replace function pg_test_module_load(text) returns text as 'pg.test.module.load(arg1)' language 'plr'; select pg_test_module_load('hello world'); pg_test_module_load --------------------- hello world (1 row) -- -- user defined R function test -- select install_rcmd('pg.test.install <-function(msg) {print(msg)}'); install_rcmd -------------- OK (1 row) create or replace function pg_test_install(text) returns text as 'pg.test.install(arg1)' language 'plr'; select pg_test_install('hello world'); pg_test_install ----------------- hello world (1 row) -- -- a variety of plr functions -- create or replace function throw_notice(text) returns text as 'pg.thrownotice(arg1)' language 'plr'; select throw_notice('hello'); NOTICE: hello throw_notice -------------- hello (1 row) create or replace function paste(_text,_text,text) returns text[] as 'paste(arg1,arg2, sep = arg3)' language 'plr'; select paste('{hello, happy}','{world, birthday}',' '); paste ---------------------------------- {"hello world","happy birthday"} (1 row) create or replace function vec(_float8) returns _float8 as 'arg1' language 'plr'; select vec('{1.23, 1.32}'::float8[]); vec ------------- {1.23,1.32} (1 row) create or replace function vec(float, float) returns _float8 as 'c(arg1,arg2)' language 'plr'; select vec(1.23, 1.32); vec ------------- {1.23,1.32} (1 row) create or replace function echo(text) returns text as 'print(arg1)' language 'plr'; select echo('hello'); echo ------- hello (1 row) create or replace function reval(text) returns text as 'eval(parse(text = arg1))' language 'plr'; select reval('a <- sd(c(1,2,3)); b <- mean(c(1,2,3)); a + b'); reval ------- 3 (1 row) create or replace function "commandArgs"() returns text[] as '' language 'plr'; select "commandArgs"(); commandArgs ------------------------------------------------ {PL/R,--slave,--silent,--no-save,--no-restore} (1 row) create or replace function vec(float) returns text as 'c(arg1)' language 'plr'; select vec(1.23); vec ------ 1.23 (1 row) create or replace function reval(_text) returns text as 'eval(parse(text = arg1))' language 'plr'; select round(reval('{"sd(c(1.12,1.23,1.18,1.34))"}'::text[])::numeric,8); round ------------ 0.09322911 (1 row) create or replace function print(text) returns text as '' language 'plr'; select print('hello'); print ------- hello (1 row) create or replace function cube(int) returns float as 'sq <- function(x) {return(x * x)}; return(arg1 * sq(arg1))' language 'plr'; select cube(3); cube ------ 27 (1 row) create or replace function sd(_float8) returns float as 'sd(arg1)' language 'plr'; select round(sd('{1.23,1.31,1.42,1.27}'::_float8)::numeric,8); round ------------ 0.08180261 (1 row) create or replace function sd(_float8) returns float as '' language 'plr'; select round(sd('{1.23,1.31,1.42,1.27}'::_float8)::numeric,8); round ------------ 0.08180261 (1 row) create or replace function mean(_float8) returns float as '' language 'plr'; select mean('{1.23,1.31,1.42,1.27}'::_float8); mean -------- 1.3075 (1 row) create or replace function sprintf(text,text,text) returns text as 'sprintf(arg1,arg2,arg3)' language 'plr'; select sprintf('%s is %s feet tall', 'Sven', '7'); sprintf --------------------- Sven is 7 feet tall (1 row) -- -- test aggregates -- create table foo(f0 int, f1 text, f2 float8) with oids; insert into foo values(1,'cat1',1.21); insert into foo values(2,'cat1',1.24); insert into foo values(3,'cat1',1.18); insert into foo values(4,'cat1',1.26); insert into foo values(5,'cat1',1.15); insert into foo values(6,'cat2',1.15); insert into foo values(7,'cat2',1.26); insert into foo values(8,'cat2',1.32); insert into foo values(9,'cat2',1.30); create or replace function r_median(_float8) returns float as 'median(arg1)' language 'plr'; select r_median('{1.23,1.31,1.42,1.27}'::_float8); r_median ---------- 1.29 (1 row) CREATE AGGREGATE median (sfunc = plr_array_accum, basetype = float8, stype = _float8, finalfunc = r_median); select f1, median(f2) from foo group by f1 order by f1; f1 | median ------+-------- cat1 | 1.21 cat2 | 1.28 (2 rows) create or replace function r_gamma(_float8) returns float as 'gamma(arg1)' language 'plr'; select round(r_gamma('{1.23,1.31,1.42,1.27}'::_float8)::numeric,8); round ------------ 0.91075486 (1 row) CREATE AGGREGATE gamma (sfunc = plr_array_accum, basetype = float8, stype = _float8, finalfunc = r_gamma); select f1, round(gamma(f2)::numeric,8) from foo group by f1 order by f1; f1 | round ------+------------ cat1 | 0.91557649 cat2 | 0.93304093 (2 rows) -- -- test returning vectors, arrays, matricies, and dataframes -- as scalars, arrays, and records -- create or replace function test_vt() returns text as 'array(1:10,c(2,5))' language 'plr'; select test_vt(); test_vt --------- 1 (1 row) create or replace function test_vi() returns int as 'array(1:10,c(2,5))' language 'plr'; select test_vi(); test_vi --------- 1 (1 row) create or replace function test_mt() returns text as 'as.matrix(array(1:10,c(2,5)))' language 'plr'; select test_mt(); test_mt --------- 1 (1 row) create or replace function test_mi() returns int as 'as.matrix(array(1:10,c(2,5)))' language 'plr'; select test_mi(); test_mi --------- 1 (1 row) create or replace function test_dt() returns text as 'as.data.frame(array(1:10,c(2,5)))[[1]]' language 'plr'; select test_dt(); test_dt --------- 1 (1 row) create or replace function test_di() returns int as 'as.data.frame(array(1:10,c(2,5)))[[1]]' language 'plr'; select test_di() as error; error ------- 1 (1 row) create or replace function test_vta() returns text[] as 'array(1:10,c(2,5))' language 'plr'; select test_vta(); test_vta ---------------------------- {{1,3,5,7,9},{2,4,6,8,10}} (1 row) create or replace function test_via() returns int[] as 'array(1:10,c(2,5))' language 'plr'; select test_via(); test_via ---------------------------- {{1,3,5,7,9},{2,4,6,8,10}} (1 row) create or replace function test_mta() returns text[] as 'as.matrix(array(1:10,c(2,5)))' language 'plr'; select test_mta(); test_mta ---------------------------- {{1,3,5,7,9},{2,4,6,8,10}} (1 row) create or replace function test_mia() returns int[] as 'as.matrix(array(1:10,c(2,5)))' language 'plr'; select test_mia(); test_mia ---------------------------- {{1,3,5,7,9},{2,4,6,8,10}} (1 row) create or replace function test_dia() returns int[] as 'as.data.frame(array(1:10,c(2,5)))' language 'plr'; select test_dia(); test_dia ---------------------------- {{1,3,5,7,9},{2,4,6,8,10}} (1 row) create or replace function test_dta() returns text[] as 'as.data.frame(array(1:10,c(2,5)))' language 'plr'; select test_dta(); test_dta ---------------------------- {{1,3,5,7,9},{2,4,6,8,10}} (1 row) create or replace function test_dta1() returns text[] as 'as.data.frame(array(letters[1:10], c(2,5)))' language 'plr'; select test_dta1(); test_dta1 --------------------------- {{a,c,e,g,i},{b,d,f,h,j}} (1 row) create or replace function test_dta2() returns text[] as 'as.data.frame(data.frame(letters[1:10],1:10))' language 'plr'; select test_dta2(); test_dta2 ---------------------------------------------------------------- {{a,1},{b,2},{c,3},{d,4},{e,5},{f,6},{g,7},{h,8},{i,9},{j,10}} (1 row) -- generates expected error create or replace function test_dia1() returns int[] as 'as.data.frame(array(letters[1:10], c(2,5)))' language 'plr'; select test_dia1() as error; ERROR: invalid input syntax for integer: "a" CONTEXT: In PL/R function test_dia1 create or replace function test_dtup() returns setof record as 'data.frame(letters[1:10],1:10)' language 'plr'; select * from test_dtup() as t(f1 text, f2 int); f1 | f2 ----+---- a | 1 b | 2 c | 3 d | 4 e | 5 f | 6 g | 7 h | 8 i | 9 j | 10 (10 rows) create or replace function test_mtup() returns setof record as 'as.matrix(array(1:15,c(5,3)))' language 'plr'; select * from test_mtup() as t(f1 int, f2 int, f3 int); f1 | f2 | f3 ----+----+---- 1 | 6 | 11 2 | 7 | 12 3 | 8 | 13 4 | 9 | 14 5 | 10 | 15 (5 rows) create or replace function test_vtup() returns setof record as 'as.vector(array(1:15,c(5,3)))' language 'plr'; select * from test_vtup() as t(f1 int); f1 ---- 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 (15 rows) create or replace function test_vint() returns setof int as 'as.vector(array(1:15,c(5,3)))' language 'plr'; select * from test_vint(); test_vint ----------- 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 (15 rows) -- -- try again with named tuple types -- CREATE TYPE dtup AS (f1 text, f2 int); CREATE TYPE mtup AS (f1 int, f2 int, f3 int); CREATE TYPE vtup AS (f1 int); create or replace function test_dtup1() returns setof dtup as 'data.frame(letters[1:10],1:10)' language 'plr'; select * from test_dtup1(); f1 | f2 ----+---- a | 1 b | 2 c | 3 d | 4 e | 5 f | 6 g | 7 h | 8 i | 9 j | 10 (10 rows) create or replace function test_dtup2() returns setof dtup as 'data.frame(c("c","qw","ax","h","k","ax","l","t","b","u"),1:10)' language 'plr'; select * from test_dtup2(); f1 | f2 ----+---- c | 1 qw | 2 ax | 3 h | 4 k | 5 ax | 6 l | 7 t | 8 b | 9 u | 10 (10 rows) create or replace function test_mtup1() returns setof mtup as 'as.matrix(array(1:15,c(5,3)))' language 'plr'; select * from test_mtup1(); f1 | f2 | f3 ----+----+---- 1 | 6 | 11 2 | 7 | 12 3 | 8 | 13 4 | 9 | 14 5 | 10 | 15 (5 rows) create or replace function test_vtup1() returns setof vtup as 'as.vector(array(1:15,c(5,3)))' language 'plr'; select * from test_vtup1(); f1 ---- 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 (15 rows) -- -- test pg R support functions (e.g. SPI_exec) -- create or replace function pg_quote_ident(text) returns text as 'pg.quoteident(arg1)' language 'plr'; select pg_quote_ident('Hello World'); pg_quote_ident ---------------- "Hello World" (1 row) create or replace function pg_quote_literal(text) returns text as 'pg.quoteliteral(arg1)' language 'plr'; select pg_quote_literal('Hello''World'); pg_quote_literal ------------------ 'Hello''World' (1 row) create or replace function test_spi_t(text) returns text as '(pg.spi.exec(arg1))[[1]]' language 'plr'; select test_spi_t('select oid, typname from pg_type where typname = ''oid'' or typname = ''text'''); test_spi_t ------------ 25 (1 row) create or replace function test_spi_ta(text) returns text[] as 'pg.spi.exec(arg1)' language 'plr'; select test_spi_ta('select oid, typname from pg_type where typname = ''oid'' or typname = ''text'''); test_spi_ta ---------------------- {{25,text},{26,oid}} (1 row) create or replace function test_spi_tup(text) returns setof record as 'pg.spi.exec(arg1)' language 'plr'; select * from test_spi_tup('select oid, typname from pg_type where typname = ''oid'' or typname = ''text''') as t(typeid oid, typename name); typeid | typename --------+---------- 25 | text 26 | oid (2 rows) create or replace function fetch_pgoid(text) returns int as 'pg.reval(arg1)' language 'plr'; select fetch_pgoid('BYTEAOID'); fetch_pgoid ------------- 17 (1 row) create or replace function test_spi_prep(text) returns text as 'sp <<- pg.spi.prepare(arg1, c(NAMEOID, NAMEOID)); print("OK")' language 'plr'; select test_spi_prep('select oid, typname from pg_type where typname = $1 or typname = $2'); test_spi_prep --------------- OK (1 row) create or replace function test_spi_execp(text, text, text) returns setof record as 'pg.spi.execp(pg.reval(arg1), list(arg2,arg3))' language 'plr'; select * from test_spi_execp('sp','oid','text') as t(typeid oid, typename name); typeid | typename --------+---------- 25 | text 26 | oid (2 rows) create or replace function test_spi_lastoid(text) returns text as 'pg.spi.exec(arg1); pg.spi.lastoid()/pg.spi.lastoid()' language 'plr'; select test_spi_lastoid('insert into foo values(10,''cat3'',3.333)') as "ONE"; ONE ----- 1 (1 row) -- -- test NULL handling -- CREATE OR REPLACE FUNCTION r_test (float8) RETURNS float8 AS 'arg1' LANGUAGE 'plr'; select r_test(null) is null as "NULL"; NULL ------ t (1 row) CREATE OR REPLACE FUNCTION r_max (integer, integer) RETURNS integer AS 'if (is.null(arg1) && is.null(arg2)) return(NA);if (is.null(arg1)) return(arg2);if (is.null(arg2)) return(arg1);if (arg1 > arg2) return(arg1);arg2' LANGUAGE 'plr'; select r_max(1,2) as "TWO"; TWO ----- 2 (1 row) select r_max(null,2) as "TWO"; TWO ----- 2 (1 row) select r_max(1,null) as "ONE"; ONE ----- 1 (1 row) select r_max(null,null) is null as "NULL"; NULL ------ t (1 row) -- -- test tuple arguments -- create or replace function get_foo(int) returns foo as 'select * from foo where f0 = $1' language 'sql'; create or replace function test_foo(foo) returns foo as 'return(arg1)' language 'plr'; select * from test_foo(get_foo(1)); f0 | f1 | f2 ----+------+------ 1 | cat1 | 1.21 (1 row) -- -- test 2D array argument -- create or replace function test_in_m_tup(_int4) returns setof record as 'arg1' language 'plr'; select * from test_in_m_tup('{{1,3,5},{2,4,6}}') as t(f1 int, f2 int, f3 int); f1 | f2 | f3 ----+----+---- 1 | 3 | 5 2 | 4 | 6 (2 rows) -- -- test 3D array argument -- create or replace function arr3d(_int4,int4,int4,int4) returns int4 as ' if (arg2 < 1 || arg3 < 1 || arg4 < 1) return(NA) if (arg2 > dim(arg1)[1] || arg3 > dim(arg1)[2] || arg4 > dim(arg1)[3]) return(NA) return(arg1[arg2,arg3,arg4]) ' language 'plr' WITH (isstrict); select arr3d('{{{111,112},{121,122},{131,132}},{{211,212},{221,222},{231,232}}}',2,3,1) as "231"; 231 ----- 231 (1 row) -- for sake of comparison, see what normal pgsql array operations produces select f1[2][3][1] as "231" from (select '{{{111,112},{121,122},{131,132}},{{211,212},{221,222},{231,232}}}'::int4[] as f1) as t; 231 ----- 231 (1 row) -- out-of-bounds, returns null select arr3d('{{{111,112},{121,122},{131,132}},{{211,212},{221,222},{231,232}}}',1,4,1) is null as "NULL"; NULL ------ t (1 row) select f1[1][4][1] is null as "NULL" from (select '{{{111,112},{121,122},{131,132}},{{211,212},{221,222},{231,232}}}'::int4[] as f1) as t; NULL ------ t (1 row) select arr3d('{{{111,112},{121,122},{131,132}},{{211,212},{221,222},{231,232}}}',0,1,1) is null as "NULL"; NULL ------ t (1 row) select f1[0][1][1] is null as "NULL" from (select '{{{111,112},{121,122},{131,132}},{{211,212},{221,222},{231,232}}}'::int4[] as f1) as t; NULL ------ t (1 row) -- -- test 3D array return value -- create or replace function arr3d(_int4) returns int4[] as 'return(arg1)' language 'plr' WITH (isstrict); select arr3d('{{{111,112},{121,122},{131,132}},{{211,212},{221,222},{231,232}}}'); arr3d ------------------------------------------------------------------- {{{111,112},{121,122},{131,132}},{{211,212},{221,222},{231,232}}} (1 row) -- -- Trigger support tests -- -- -- test that NULL return value suppresses the change -- create or replace function rejectfoo() returns trigger as 'return(NULL)' language plr; create trigger footrig before insert or update or delete on foo for each row execute procedure rejectfoo(); select count(*) from foo; count ------- 10 (1 row) insert into foo values(11,'cat99',1.89); select count(*) from foo; count ------- 10 (1 row) update foo set f1 = 'zzz'; select count(*) from foo; count ------- 10 (1 row) delete from foo; select count(*) from foo; count ------- 10 (1 row) drop trigger footrig on foo; -- -- test that returning OLD/NEW as appropriate allow the change unmodified -- create or replace function acceptfoo() returns trigger as ' switch (pg.tg.op, INSERT = return(pg.tg.new), UPDATE = return(pg.tg.new), DELETE = return(pg.tg.old)) ' language plr; create trigger footrig before insert or update or delete on foo for each row execute procedure acceptfoo(); select count(*) from foo; count ------- 10 (1 row) insert into foo values(11,'cat99',1.89); select count(*) from foo; count ------- 11 (1 row) update foo set f1 = 'zzz' where f0 = 11; select * from foo where f0 = 11; f0 | f1 | f2 ----+-----+------ 11 | zzz | 1.89 (1 row) delete from foo where f0 = 11; select count(*) from foo; count ------- 10 (1 row) drop trigger footrig on foo; -- -- test that returning modifed tuple successfully modifies the result -- create or replace function modfoo() returns trigger as ' if (pg.tg.op == "INSERT") { retval <- pg.tg.new retval$f1 <- "xxx" } if (pg.tg.op == "UPDATE") { retval <- pg.tg.new retval$f1 <- "aaa" } if (pg.tg.op == "DELETE") retval <- pg.tg.old return(retval) ' language plr; create trigger footrig before insert or update or delete on foo for each row execute procedure modfoo(); select count(*) from foo; count ------- 10 (1 row) insert into foo values(11,'cat99',1.89); select * from foo where f0 = 11; f0 | f1 | f2 ----+-----+------ 11 | xxx | 1.89 (1 row) update foo set f1 = 'zzz' where f0 = 11; select * from foo where f0 = 11; f0 | f1 | f2 ----+-----+------ 11 | aaa | 1.89 (1 row) delete from foo where f0 = 11; select count(*) from foo; count ------- 10 (1 row) drop trigger footrig on foo; -- -- test statement level triggers and verify all arguments come -- across correctly -- create or replace function foonotice() returns trigger as ' msg <- paste(pg.tg.name,pg.tg.relname,pg.tg.when,pg.tg.level,pg.tg.op,pg.tg.args[1],pg.tg.args[2]) pg.thrownotice(msg) return(NULL) ' language plr; create trigger footrig after insert or update or delete on foo for each row execute procedure foonotice(); select count(*) from foo; count ------- 10 (1 row) insert into foo values(11,'cat99',1.89); NOTICE: footrig foo AFTER ROW INSERT NA NA select count(*) from foo; count ------- 11 (1 row) update foo set f1 = 'zzz' where f0 = 11; NOTICE: footrig foo AFTER ROW UPDATE NA NA select * from foo where f0 = 11; f0 | f1 | f2 ----+-----+------ 11 | zzz | 1.89 (1 row) delete from foo where f0 = 11; NOTICE: footrig foo AFTER ROW DELETE NA NA select count(*) from foo; count ------- 10 (1 row) drop trigger footrig on foo; create trigger footrig after insert or update or delete on foo for each statement execute procedure foonotice('hello','world'); select count(*) from foo; count ------- 10 (1 row) insert into foo values(11,'cat99',1.89); NOTICE: footrig foo AFTER STATEMENT INSERT hello world select count(*) from foo; count ------- 11 (1 row) update foo set f1 = 'zzz' where f0 = 11; NOTICE: footrig foo AFTER STATEMENT UPDATE hello world select * from foo where f0 = 11; f0 | f1 | f2 ----+-----+------ 11 | zzz | 1.89 (1 row) delete from foo where f0 = 11; NOTICE: footrig foo AFTER STATEMENT DELETE hello world select count(*) from foo; count ------- 10 (1 row) drop trigger footrig on foo; -- Test cursors: creating, scrolling forward, closing CREATE OR REPLACE FUNCTION cursor_fetch_test(integer,boolean) RETURNS SETOF integer AS 'plan<-pg.spi.prepare("SELECT * FROM generate_series(1,10)"); cursor<-pg.spi.cursor_open("curs",plan); dat<-pg.spi.cursor_fetch(cursor,arg2,arg1); pg.spi.cursor_close(cursor); return (dat);' language 'plr'; SELECT * FROM cursor_fetch_test(1,true); cursor_fetch_test ------------------- 1 (1 row) SELECT * FROM cursor_fetch_test(2,true); cursor_fetch_test ------------------- 1 2 (2 rows) SELECT * FROM cursor_fetch_test(20,true); cursor_fetch_test ------------------- 1 2 3 4 5 6 7 8 9 10 (10 rows) --Test cursors: scrolling backwards CREATE OR REPLACE FUNCTION cursor_direction_test() RETURNS SETOF integer AS'plan<-pg.spi.prepare("SELECT * FROM generate_series(1,10)"); cursor<-pg.spi.cursor_open("curs",plan); dat<-pg.spi.cursor_fetch(cursor,TRUE,as.integer(3)); dat2<-pg.spi.cursor_fetch(cursor,FALSE,as.integer(3)); pg.spi.cursor_close(cursor); return (dat2);' language 'plr'; SELECT * FROM cursor_direction_test(); cursor_direction_test ----------------------- 2 1 (2 rows) --Test cursors: Passing arguments to a plan CREATE OR REPLACE FUNCTION cursor_fetch_test_arg(integer) RETURNS SETOF integer AS 'plan<-pg.spi.prepare("SELECT * FROM generate_series(1,$1)",c(INT4OID)); cursor<-pg.spi.cursor_open("curs",plan,list(arg1)); dat<-pg.spi.cursor_fetch(cursor,TRUE,arg1); pg.spi.cursor_close(cursor); return (dat);' language 'plr'; SELECT * FROM cursor_fetch_test_arg(3); cursor_fetch_test_arg ----------------------- 1 2 3 (3 rows) --Test bytea arguments and return values: serialize/unserialize create or replace function test_serialize(text) returns bytea as ' mydf <- pg.spi.exec(arg1) return (mydf) ' language 'plr'; create or replace function restore_df(bytea) returns setof record as ' return (arg1) ' language 'plr'; select * from restore_df((select test_serialize('select oid, typname from pg_type where typname in (''oid'',''name'',''int4'')'))) as t(oid oid, typname name); oid | typname -----+--------- 19 | name 23 | int4 26 | oid (3 rows) --Test WINDOW functions -- create test table CREATE TABLE test_data ( fyear integer, firm float8, eps float8 ); -- insert data for test INSERT INTO test_data SELECT (b.f + 1) % 10 + 2000 AS fyear, floor((b.f+1)/10) + 50 AS firm, f::float8/100 AS eps FROM generate_series(-200,199,1) b(f); CREATE OR REPLACE FUNCTION r_regr_slope(float8, float8) RETURNS float8 AS $BODY$ slope <- NA y <- farg1 x <- farg2 if (fnumrows==9) try (slope <- lm(y ~ x)$coefficients[2]) return(slope) $BODY$ LANGUAGE plr WINDOW; SELECT *, round((r_regr_slope(eps, lag_eps) OVER w)::numeric,6) AS slope_R FROM (SELECT firm, fyear, eps, lag(eps) OVER (ORDER BY firm, fyear) AS lag_eps FROM test_data) AS a WHERE eps IS NOT NULL WINDOW w AS (ORDER BY firm, fyear ROWS 8 PRECEDING); firm | fyear | eps | lag_eps | slope_r ------+-------+-------+---------+---------- 31 | 1991 | -2 | | 31 | 1992 | -1.99 | -2 | 31 | 1993 | -1.98 | -1.99 | 31 | 1994 | -1.97 | -1.98 | 31 | 1995 | -1.96 | -1.97 | 31 | 1996 | -1.95 | -1.96 | 31 | 1997 | -1.94 | -1.95 | 31 | 1998 | -1.93 | -1.94 | 31 | 1999 | -1.92 | -1.93 | 1.000000 31 | 2000 | -1.91 | -1.92 | 1.000000 32 | 1991 | -1.9 | -1.91 | 1.000000 32 | 1992 | -1.89 | -1.9 | 1.000000 32 | 1993 | -1.88 | -1.89 | 1.000000 32 | 1994 | -1.87 | -1.88 | 1.000000 32 | 1995 | -1.86 | -1.87 | 1.000000 32 | 1996 | -1.85 | -1.86 | 1.000000 32 | 1997 | -1.84 | -1.85 | 1.000000 32 | 1998 | -1.83 | -1.84 | 1.000000 32 | 1999 | -1.82 | -1.83 | 1.000000 32 | 2000 | -1.81 | -1.82 | 1.000000 33 | 1991 | -1.8 | -1.81 | 1.000000 33 | 1992 | -1.79 | -1.8 | 1.000000 33 | 1993 | -1.78 | -1.79 | 1.000000 33 | 1994 | -1.77 | -1.78 | 1.000000 33 | 1995 | -1.76 | -1.77 | 1.000000 33 | 1996 | -1.75 | -1.76 | 1.000000 33 | 1997 | -1.74 | -1.75 | 1.000000 33 | 1998 | -1.73 | -1.74 | 1.000000 33 | 1999 | -1.72 | -1.73 | 1.000000 33 | 2000 | -1.71 | -1.72 | 1.000000 34 | 1991 | -1.7 | -1.71 | 1.000000 34 | 1992 | -1.69 | -1.7 | 1.000000 34 | 1993 | -1.68 | -1.69 | 1.000000 34 | 1994 | -1.67 | -1.68 | 1.000000 34 | 1995 | -1.66 | -1.67 | 1.000000 34 | 1996 | -1.65 | -1.66 | 1.000000 34 | 1997 | -1.64 | -1.65 | 1.000000 34 | 1998 | -1.63 | -1.64 | 1.000000 34 | 1999 | -1.62 | -1.63 | 1.000000 34 | 2000 | -1.61 | -1.62 | 1.000000 35 | 1991 | -1.6 | -1.61 | 1.000000 35 | 1992 | -1.59 | -1.6 | 1.000000 35 | 1993 | -1.58 | -1.59 | 1.000000 35 | 1994 | -1.57 | -1.58 | 1.000000 35 | 1995 | -1.56 | -1.57 | 1.000000 35 | 1996 | -1.55 | -1.56 | 1.000000 35 | 1997 | -1.54 | -1.55 | 1.000000 35 | 1998 | -1.53 | -1.54 | 1.000000 35 | 1999 | -1.52 | -1.53 | 1.000000 35 | 2000 | -1.51 | -1.52 | 1.000000 36 | 1991 | -1.5 | -1.51 | 1.000000 36 | 1992 | -1.49 | -1.5 | 1.000000 36 | 1993 | -1.48 | -1.49 | 1.000000 36 | 1994 | -1.47 | -1.48 | 1.000000 36 | 1995 | -1.46 | -1.47 | 1.000000 36 | 1996 | -1.45 | -1.46 | 1.000000 36 | 1997 | -1.44 | -1.45 | 1.000000 36 | 1998 | -1.43 | -1.44 | 1.000000 36 | 1999 | -1.42 | -1.43 | 1.000000 36 | 2000 | -1.41 | -1.42 | 1.000000 37 | 1991 | -1.4 | -1.41 | 1.000000 37 | 1992 | -1.39 | -1.4 | 1.000000 37 | 1993 | -1.38 | -1.39 | 1.000000 37 | 1994 | -1.37 | -1.38 | 1.000000 37 | 1995 | -1.36 | -1.37 | 1.000000 37 | 1996 | -1.35 | -1.36 | 1.000000 37 | 1997 | -1.34 | -1.35 | 1.000000 37 | 1998 | -1.33 | -1.34 | 1.000000 37 | 1999 | -1.32 | -1.33 | 1.000000 37 | 2000 | -1.31 | -1.32 | 1.000000 38 | 1991 | -1.3 | -1.31 | 1.000000 38 | 1992 | -1.29 | -1.3 | 1.000000 38 | 1993 | -1.28 | -1.29 | 1.000000 38 | 1994 | -1.27 | -1.28 | 1.000000 38 | 1995 | -1.26 | -1.27 | 1.000000 38 | 1996 | -1.25 | -1.26 | 1.000000 38 | 1997 | -1.24 | -1.25 | 1.000000 38 | 1998 | -1.23 | -1.24 | 1.000000 38 | 1999 | -1.22 | -1.23 | 1.000000 38 | 2000 | -1.21 | -1.22 | 1.000000 39 | 1991 | -1.2 | -1.21 | 1.000000 39 | 1992 | -1.19 | -1.2 | 1.000000 39 | 1993 | -1.18 | -1.19 | 1.000000 39 | 1994 | -1.17 | -1.18 | 1.000000 39 | 1995 | -1.16 | -1.17 | 1.000000 39 | 1996 | -1.15 | -1.16 | 1.000000 39 | 1997 | -1.14 | -1.15 | 1.000000 39 | 1998 | -1.13 | -1.14 | 1.000000 39 | 1999 | -1.12 | -1.13 | 1.000000 39 | 2000 | -1.11 | -1.12 | 1.000000 40 | 1991 | -1.1 | -1.11 | 1.000000 40 | 1992 | -1.09 | -1.1 | 1.000000 40 | 1993 | -1.08 | -1.09 | 1.000000 40 | 1994 | -1.07 | -1.08 | 1.000000 40 | 1995 | -1.06 | -1.07 | 1.000000 40 | 1996 | -1.05 | -1.06 | 1.000000 40 | 1997 | -1.04 | -1.05 | 1.000000 40 | 1998 | -1.03 | -1.04 | 1.000000 40 | 1999 | -1.02 | -1.03 | 1.000000 40 | 2000 | -1.01 | -1.02 | 1.000000 41 | 1991 | -1 | -1.01 | 1.000000 41 | 1992 | -0.99 | -1 | 1.000000 41 | 1993 | -0.98 | -0.99 | 1.000000 41 | 1994 | -0.97 | -0.98 | 1.000000 41 | 1995 | -0.96 | -0.97 | 1.000000 41 | 1996 | -0.95 | -0.96 | 1.000000 41 | 1997 | -0.94 | -0.95 | 1.000000 41 | 1998 | -0.93 | -0.94 | 1.000000 41 | 1999 | -0.92 | -0.93 | 1.000000 41 | 2000 | -0.91 | -0.92 | 1.000000 42 | 1991 | -0.9 | -0.91 | 1.000000 42 | 1992 | -0.89 | -0.9 | 1.000000 42 | 1993 | -0.88 | -0.89 | 1.000000 42 | 1994 | -0.87 | -0.88 | 1.000000 42 | 1995 | -0.86 | -0.87 | 1.000000 42 | 1996 | -0.85 | -0.86 | 1.000000 42 | 1997 | -0.84 | -0.85 | 1.000000 42 | 1998 | -0.83 | -0.84 | 1.000000 42 | 1999 | -0.82 | -0.83 | 1.000000 42 | 2000 | -0.81 | -0.82 | 1.000000 43 | 1991 | -0.8 | -0.81 | 1.000000 43 | 1992 | -0.79 | -0.8 | 1.000000 43 | 1993 | -0.78 | -0.79 | 1.000000 43 | 1994 | -0.77 | -0.78 | 1.000000 43 | 1995 | -0.76 | -0.77 | 1.000000 43 | 1996 | -0.75 | -0.76 | 1.000000 43 | 1997 | -0.74 | -0.75 | 1.000000 43 | 1998 | -0.73 | -0.74 | 1.000000 43 | 1999 | -0.72 | -0.73 | 1.000000 43 | 2000 | -0.71 | -0.72 | 1.000000 44 | 1991 | -0.7 | -0.71 | 1.000000 44 | 1992 | -0.69 | -0.7 | 1.000000 44 | 1993 | -0.68 | -0.69 | 1.000000 44 | 1994 | -0.67 | -0.68 | 1.000000 44 | 1995 | -0.66 | -0.67 | 1.000000 44 | 1996 | -0.65 | -0.66 | 1.000000 44 | 1997 | -0.64 | -0.65 | 1.000000 44 | 1998 | -0.63 | -0.64 | 1.000000 44 | 1999 | -0.62 | -0.63 | 1.000000 44 | 2000 | -0.61 | -0.62 | 1.000000 45 | 1991 | -0.6 | -0.61 | 1.000000 45 | 1992 | -0.59 | -0.6 | 1.000000 45 | 1993 | -0.58 | -0.59 | 1.000000 45 | 1994 | -0.57 | -0.58 | 1.000000 45 | 1995 | -0.56 | -0.57 | 1.000000 45 | 1996 | -0.55 | -0.56 | 1.000000 45 | 1997 | -0.54 | -0.55 | 1.000000 45 | 1998 | -0.53 | -0.54 | 1.000000 45 | 1999 | -0.52 | -0.53 | 1.000000 45 | 2000 | -0.51 | -0.52 | 1.000000 46 | 1991 | -0.5 | -0.51 | 1.000000 46 | 1992 | -0.49 | -0.5 | 1.000000 46 | 1993 | -0.48 | -0.49 | 1.000000 46 | 1994 | -0.47 | -0.48 | 1.000000 46 | 1995 | -0.46 | -0.47 | 1.000000 46 | 1996 | -0.45 | -0.46 | 1.000000 46 | 1997 | -0.44 | -0.45 | 1.000000 46 | 1998 | -0.43 | -0.44 | 1.000000 46 | 1999 | -0.42 | -0.43 | 1.000000 46 | 2000 | -0.41 | -0.42 | 1.000000 47 | 1991 | -0.4 | -0.41 | 1.000000 47 | 1992 | -0.39 | -0.4 | 1.000000 47 | 1993 | -0.38 | -0.39 | 1.000000 47 | 1994 | -0.37 | -0.38 | 1.000000 47 | 1995 | -0.36 | -0.37 | 1.000000 47 | 1996 | -0.35 | -0.36 | 1.000000 47 | 1997 | -0.34 | -0.35 | 1.000000 47 | 1998 | -0.33 | -0.34 | 1.000000 47 | 1999 | -0.32 | -0.33 | 1.000000 47 | 2000 | -0.31 | -0.32 | 1.000000 48 | 1991 | -0.3 | -0.31 | 1.000000 48 | 1992 | -0.29 | -0.3 | 1.000000 48 | 1993 | -0.28 | -0.29 | 1.000000 48 | 1994 | -0.27 | -0.28 | 1.000000 48 | 1995 | -0.26 | -0.27 | 1.000000 48 | 1996 | -0.25 | -0.26 | 1.000000 48 | 1997 | -0.24 | -0.25 | 1.000000 48 | 1998 | -0.23 | -0.24 | 1.000000 48 | 1999 | -0.22 | -0.23 | 1.000000 48 | 2000 | -0.21 | -0.22 | 1.000000 49 | 1991 | -0.2 | -0.21 | 1.000000 49 | 1992 | -0.19 | -0.2 | 1.000000 49 | 1993 | -0.18 | -0.19 | 1.000000 49 | 1994 | -0.17 | -0.18 | 1.000000 49 | 1995 | -0.16 | -0.17 | 1.000000 49 | 1996 | -0.15 | -0.16 | 1.000000 49 | 1997 | -0.14 | -0.15 | 1.000000 49 | 1998 | -0.13 | -0.14 | 1.000000 49 | 1999 | -0.12 | -0.13 | 1.000000 49 | 2000 | -0.11 | -0.12 | 1.000000 50 | 1991 | -0.1 | -0.11 | 1.000000 50 | 1992 | -0.09 | -0.1 | 1.000000 50 | 1993 | -0.08 | -0.09 | 1.000000 50 | 1994 | -0.07 | -0.08 | 1.000000 50 | 1995 | -0.06 | -0.07 | 1.000000 50 | 1996 | -0.05 | -0.06 | 1.000000 50 | 1997 | -0.04 | -0.05 | 1.000000 50 | 1998 | -0.03 | -0.04 | 1.000000 50 | 1999 | -0.02 | -0.03 | 1.000000 50 | 2000 | -0.01 | -0.02 | 1.000000 50 | 2001 | 0 | -0.01 | 1.000000 50 | 2002 | 0.01 | 0 | 1.000000 50 | 2003 | 0.02 | 0.01 | 1.000000 50 | 2004 | 0.03 | 0.02 | 1.000000 50 | 2005 | 0.04 | 0.03 | 1.000000 50 | 2006 | 0.05 | 0.04 | 1.000000 50 | 2007 | 0.06 | 0.05 | 1.000000 50 | 2008 | 0.07 | 0.06 | 1.000000 50 | 2009 | 0.08 | 0.07 | 1.000000 51 | 2000 | 0.09 | 0.08 | 1.000000 51 | 2001 | 0.1 | 0.09 | 1.000000 51 | 2002 | 0.11 | 0.1 | 1.000000 51 | 2003 | 0.12 | 0.11 | 1.000000 51 | 2004 | 0.13 | 0.12 | 1.000000 51 | 2005 | 0.14 | 0.13 | 1.000000 51 | 2006 | 0.15 | 0.14 | 1.000000 51 | 2007 | 0.16 | 0.15 | 1.000000 51 | 2008 | 0.17 | 0.16 | 1.000000 51 | 2009 | 0.18 | 0.17 | 1.000000 52 | 2000 | 0.19 | 0.18 | 1.000000 52 | 2001 | 0.2 | 0.19 | 1.000000 52 | 2002 | 0.21 | 0.2 | 1.000000 52 | 2003 | 0.22 | 0.21 | 1.000000 52 | 2004 | 0.23 | 0.22 | 1.000000 52 | 2005 | 0.24 | 0.23 | 1.000000 52 | 2006 | 0.25 | 0.24 | 1.000000 52 | 2007 | 0.26 | 0.25 | 1.000000 52 | 2008 | 0.27 | 0.26 | 1.000000 52 | 2009 | 0.28 | 0.27 | 1.000000 53 | 2000 | 0.29 | 0.28 | 1.000000 53 | 2001 | 0.3 | 0.29 | 1.000000 53 | 2002 | 0.31 | 0.3 | 1.000000 53 | 2003 | 0.32 | 0.31 | 1.000000 53 | 2004 | 0.33 | 0.32 | 1.000000 53 | 2005 | 0.34 | 0.33 | 1.000000 53 | 2006 | 0.35 | 0.34 | 1.000000 53 | 2007 | 0.36 | 0.35 | 1.000000 53 | 2008 | 0.37 | 0.36 | 1.000000 53 | 2009 | 0.38 | 0.37 | 1.000000 54 | 2000 | 0.39 | 0.38 | 1.000000 54 | 2001 | 0.4 | 0.39 | 1.000000 54 | 2002 | 0.41 | 0.4 | 1.000000 54 | 2003 | 0.42 | 0.41 | 1.000000 54 | 2004 | 0.43 | 0.42 | 1.000000 54 | 2005 | 0.44 | 0.43 | 1.000000 54 | 2006 | 0.45 | 0.44 | 1.000000 54 | 2007 | 0.46 | 0.45 | 1.000000 54 | 2008 | 0.47 | 0.46 | 1.000000 54 | 2009 | 0.48 | 0.47 | 1.000000 55 | 2000 | 0.49 | 0.48 | 1.000000 55 | 2001 | 0.5 | 0.49 | 1.000000 55 | 2002 | 0.51 | 0.5 | 1.000000 55 | 2003 | 0.52 | 0.51 | 1.000000 55 | 2004 | 0.53 | 0.52 | 1.000000 55 | 2005 | 0.54 | 0.53 | 1.000000 55 | 2006 | 0.55 | 0.54 | 1.000000 55 | 2007 | 0.56 | 0.55 | 1.000000 55 | 2008 | 0.57 | 0.56 | 1.000000 55 | 2009 | 0.58 | 0.57 | 1.000000 56 | 2000 | 0.59 | 0.58 | 1.000000 56 | 2001 | 0.6 | 0.59 | 1.000000 56 | 2002 | 0.61 | 0.6 | 1.000000 56 | 2003 | 0.62 | 0.61 | 1.000000 56 | 2004 | 0.63 | 0.62 | 1.000000 56 | 2005 | 0.64 | 0.63 | 1.000000 56 | 2006 | 0.65 | 0.64 | 1.000000 56 | 2007 | 0.66 | 0.65 | 1.000000 56 | 2008 | 0.67 | 0.66 | 1.000000 56 | 2009 | 0.68 | 0.67 | 1.000000 57 | 2000 | 0.69 | 0.68 | 1.000000 57 | 2001 | 0.7 | 0.69 | 1.000000 57 | 2002 | 0.71 | 0.7 | 1.000000 57 | 2003 | 0.72 | 0.71 | 1.000000 57 | 2004 | 0.73 | 0.72 | 1.000000 57 | 2005 | 0.74 | 0.73 | 1.000000 57 | 2006 | 0.75 | 0.74 | 1.000000 57 | 2007 | 0.76 | 0.75 | 1.000000 57 | 2008 | 0.77 | 0.76 | 1.000000 57 | 2009 | 0.78 | 0.77 | 1.000000 58 | 2000 | 0.79 | 0.78 | 1.000000 58 | 2001 | 0.8 | 0.79 | 1.000000 58 | 2002 | 0.81 | 0.8 | 1.000000 58 | 2003 | 0.82 | 0.81 | 1.000000 58 | 2004 | 0.83 | 0.82 | 1.000000 58 | 2005 | 0.84 | 0.83 | 1.000000 58 | 2006 | 0.85 | 0.84 | 1.000000 58 | 2007 | 0.86 | 0.85 | 1.000000 58 | 2008 | 0.87 | 0.86 | 1.000000 58 | 2009 | 0.88 | 0.87 | 1.000000 59 | 2000 | 0.89 | 0.88 | 1.000000 59 | 2001 | 0.9 | 0.89 | 1.000000 59 | 2002 | 0.91 | 0.9 | 1.000000 59 | 2003 | 0.92 | 0.91 | 1.000000 59 | 2004 | 0.93 | 0.92 | 1.000000 59 | 2005 | 0.94 | 0.93 | 1.000000 59 | 2006 | 0.95 | 0.94 | 1.000000 59 | 2007 | 0.96 | 0.95 | 1.000000 59 | 2008 | 0.97 | 0.96 | 1.000000 59 | 2009 | 0.98 | 0.97 | 1.000000 60 | 2000 | 0.99 | 0.98 | 1.000000 60 | 2001 | 1 | 0.99 | 1.000000 60 | 2002 | 1.01 | 1 | 1.000000 60 | 2003 | 1.02 | 1.01 | 1.000000 60 | 2004 | 1.03 | 1.02 | 1.000000 60 | 2005 | 1.04 | 1.03 | 1.000000 60 | 2006 | 1.05 | 1.04 | 1.000000 60 | 2007 | 1.06 | 1.05 | 1.000000 60 | 2008 | 1.07 | 1.06 | 1.000000 60 | 2009 | 1.08 | 1.07 | 1.000000 61 | 2000 | 1.09 | 1.08 | 1.000000 61 | 2001 | 1.1 | 1.09 | 1.000000 61 | 2002 | 1.11 | 1.1 | 1.000000 61 | 2003 | 1.12 | 1.11 | 1.000000 61 | 2004 | 1.13 | 1.12 | 1.000000 61 | 2005 | 1.14 | 1.13 | 1.000000 61 | 2006 | 1.15 | 1.14 | 1.000000 61 | 2007 | 1.16 | 1.15 | 1.000000 61 | 2008 | 1.17 | 1.16 | 1.000000 61 | 2009 | 1.18 | 1.17 | 1.000000 62 | 2000 | 1.19 | 1.18 | 1.000000 62 | 2001 | 1.2 | 1.19 | 1.000000 62 | 2002 | 1.21 | 1.2 | 1.000000 62 | 2003 | 1.22 | 1.21 | 1.000000 62 | 2004 | 1.23 | 1.22 | 1.000000 62 | 2005 | 1.24 | 1.23 | 1.000000 62 | 2006 | 1.25 | 1.24 | 1.000000 62 | 2007 | 1.26 | 1.25 | 1.000000 62 | 2008 | 1.27 | 1.26 | 1.000000 62 | 2009 | 1.28 | 1.27 | 1.000000 63 | 2000 | 1.29 | 1.28 | 1.000000 63 | 2001 | 1.3 | 1.29 | 1.000000 63 | 2002 | 1.31 | 1.3 | 1.000000 63 | 2003 | 1.32 | 1.31 | 1.000000 63 | 2004 | 1.33 | 1.32 | 1.000000 63 | 2005 | 1.34 | 1.33 | 1.000000 63 | 2006 | 1.35 | 1.34 | 1.000000 63 | 2007 | 1.36 | 1.35 | 1.000000 63 | 2008 | 1.37 | 1.36 | 1.000000 63 | 2009 | 1.38 | 1.37 | 1.000000 64 | 2000 | 1.39 | 1.38 | 1.000000 64 | 2001 | 1.4 | 1.39 | 1.000000 64 | 2002 | 1.41 | 1.4 | 1.000000 64 | 2003 | 1.42 | 1.41 | 1.000000 64 | 2004 | 1.43 | 1.42 | 1.000000 64 | 2005 | 1.44 | 1.43 | 1.000000 64 | 2006 | 1.45 | 1.44 | 1.000000 64 | 2007 | 1.46 | 1.45 | 1.000000 64 | 2008 | 1.47 | 1.46 | 1.000000 64 | 2009 | 1.48 | 1.47 | 1.000000 65 | 2000 | 1.49 | 1.48 | 1.000000 65 | 2001 | 1.5 | 1.49 | 1.000000 65 | 2002 | 1.51 | 1.5 | 1.000000 65 | 2003 | 1.52 | 1.51 | 1.000000 65 | 2004 | 1.53 | 1.52 | 1.000000 65 | 2005 | 1.54 | 1.53 | 1.000000 65 | 2006 | 1.55 | 1.54 | 1.000000 65 | 2007 | 1.56 | 1.55 | 1.000000 65 | 2008 | 1.57 | 1.56 | 1.000000 65 | 2009 | 1.58 | 1.57 | 1.000000 66 | 2000 | 1.59 | 1.58 | 1.000000 66 | 2001 | 1.6 | 1.59 | 1.000000 66 | 2002 | 1.61 | 1.6 | 1.000000 66 | 2003 | 1.62 | 1.61 | 1.000000 66 | 2004 | 1.63 | 1.62 | 1.000000 66 | 2005 | 1.64 | 1.63 | 1.000000 66 | 2006 | 1.65 | 1.64 | 1.000000 66 | 2007 | 1.66 | 1.65 | 1.000000 66 | 2008 | 1.67 | 1.66 | 1.000000 66 | 2009 | 1.68 | 1.67 | 1.000000 67 | 2000 | 1.69 | 1.68 | 1.000000 67 | 2001 | 1.7 | 1.69 | 1.000000 67 | 2002 | 1.71 | 1.7 | 1.000000 67 | 2003 | 1.72 | 1.71 | 1.000000 67 | 2004 | 1.73 | 1.72 | 1.000000 67 | 2005 | 1.74 | 1.73 | 1.000000 67 | 2006 | 1.75 | 1.74 | 1.000000 67 | 2007 | 1.76 | 1.75 | 1.000000 67 | 2008 | 1.77 | 1.76 | 1.000000 67 | 2009 | 1.78 | 1.77 | 1.000000 68 | 2000 | 1.79 | 1.78 | 1.000000 68 | 2001 | 1.8 | 1.79 | 1.000000 68 | 2002 | 1.81 | 1.8 | 1.000000 68 | 2003 | 1.82 | 1.81 | 1.000000 68 | 2004 | 1.83 | 1.82 | 1.000000 68 | 2005 | 1.84 | 1.83 | 1.000000 68 | 2006 | 1.85 | 1.84 | 1.000000 68 | 2007 | 1.86 | 1.85 | 1.000000 68 | 2008 | 1.87 | 1.86 | 1.000000 68 | 2009 | 1.88 | 1.87 | 1.000000 69 | 2000 | 1.89 | 1.88 | 1.000000 69 | 2001 | 1.9 | 1.89 | 1.000000 69 | 2002 | 1.91 | 1.9 | 1.000000 69 | 2003 | 1.92 | 1.91 | 1.000000 69 | 2004 | 1.93 | 1.92 | 1.000000 69 | 2005 | 1.94 | 1.93 | 1.000000 69 | 2006 | 1.95 | 1.94 | 1.000000 69 | 2007 | 1.96 | 1.95 | 1.000000 69 | 2008 | 1.97 | 1.96 | 1.000000 69 | 2009 | 1.98 | 1.97 | 1.000000 70 | 2000 | 1.99 | 1.98 | 1.000000 (400 rows) plr/plr.c0000775000000000000000000014155312465736645011352 0ustar rootroot/* * PL/R - PostgreSQL support for R as a * procedural language (PL) * * Copyright (c) 2003-2015 by Joseph E. Conway * ALL RIGHTS RESERVED * * Joe Conway * * Based on pltcl by Jan Wieck * and inspired by REmbeddedPostgres by * Duncan Temple Lang * http://www.omegahat.org/RSPostgres/ * * License: GPL version 2 or newer. http://www.gnu.org/copyleft/gpl.html * * This program 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. * * This program 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 this program; if not, write to the Free Software * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA * * plr.c - Language handler and support functions */ #include "plr.h" PG_MODULE_MAGIC; /* * Global data */ MemoryContext plr_caller_context; MemoryContext plr_SPI_context = NULL; HTAB *plr_HashTable = (HTAB *) NULL; char *last_R_error_msg = NULL; static bool plr_pm_init_done = false; static bool plr_be_init_done = false; /* namespace OID for the PL/R language handler function */ static Oid plr_nspOid = InvalidOid; int R_SignalHandlers = 1; /* Exposed in R_interface.h */ /* * defines */ /* real max is 3 (for "PLR") plus number of characters in an Oid */ #define MAX_PRONAME_LEN NAMEDATALEN #define OPTIONS_NULL_CMD "options(error = expression(NULL))" #define THROWRERROR_CMD \ "pg.throwrerror <-function(msg) " \ "{" \ " msglen <- nchar(msg);" \ " if (substr(msg, msglen, msglen + 1) == \"\\n\")" \ " msg <- substr(msg, 1, msglen - 1);" \ " .C(\"throw_r_error\", as.character(msg));" \ "}" #define OPTIONS_THROWRERROR_CMD \ "options(error = expression(pg.throwrerror(geterrmessage())))" #define THROWNOTICE_CMD \ "pg.thrownotice <-function(msg) " \ "{.C(\"throw_pg_notice\", as.character(msg))}" #define THROWERROR_CMD \ "pg.throwerror <-function(msg) " \ "{stop(msg, call. = FALSE)}" #define OPTIONS_THROWWARN_CMD \ "options(warning.expression = expression(pg.thrownotice(last.warning)))" #define QUOTE_LITERAL_CMD \ "pg.quoteliteral <-function(sql) " \ "{.Call(\"plr_quote_literal\", sql)}" #define QUOTE_IDENT_CMD \ "pg.quoteident <-function(sql) " \ "{.Call(\"plr_quote_ident\", sql)}" #define SPI_EXEC_CMD \ "pg.spi.exec <-function(sql) {.Call(\"plr_SPI_exec\", sql)}" #define SPI_PREPARE_CMD \ "pg.spi.prepare <-function(sql, argtypes = NA) " \ "{.Call(\"plr_SPI_prepare\", sql, argtypes)}" #define SPI_EXECP_CMD \ "pg.spi.execp <-function(sql, argvalues = NA) " \ "{.Call(\"plr_SPI_execp\", sql, argvalues)}" #define SPI_CURSOR_OPEN_CMD \ "pg.spi.cursor_open<-function(cursor_name,plan,argvalues=NA) " \ "{.Call(\"plr_SPI_cursor_open\",cursor_name,plan,argvalues)}" #define SPI_CURSOR_FETCH_CMD \ "pg.spi.cursor_fetch<-function(cursor,forward,rows) " \ "{.Call(\"plr_SPI_cursor_fetch\",cursor,forward,rows)}" #define SPI_CURSOR_MOVE_CMD \ "pg.spi.cursor_move<-function(cursor,forward,rows) " \ "{.Call(\"plr_SPI_cursor_move\",cursor,forward,rows)}" #define SPI_CURSOR_CLOSE_CMD \ "pg.spi.cursor_close<-function(cursor) " \ "{.Call(\"plr_SPI_cursor_close\",cursor)}" #define SPI_LASTOID_CMD \ "pg.spi.lastoid <-function() " \ "{.Call(\"plr_SPI_lastoid\")}" #define SPI_DBDRIVER_CMD \ "dbDriver <-function(db_name)\n" \ "{return(NA)}" #define SPI_DBCONN_CMD \ "dbConnect <- function(drv,user=\"\",password=\"\",host=\"\",dbname=\"\",port=\"\",tty =\"\",options=\"\")\n" \ "{return(NA)}" #define SPI_DBSENDQUERY_CMD \ "dbSendQuery <- function(conn, sql) {\n" \ "plan <- pg.spi.prepare(sql)\n" \ "cursor_obj <- pg.spi.cursor_open(\"plr_cursor\",plan)\n" \ "return(cursor_obj)\n" \ "}" #define SPI_DBFETCH_CMD \ "fetch <- function(rs,n) {\n" \ "data <- pg.spi.cursor_fetch(rs, TRUE, as.integer(n))\n" \ "return(data)\n" \ "}" #define SPI_DBCLEARRESULT_CMD \ "dbClearResult <- function(rs) {\n" \ "pg.spi.cursor_close(rs)\n" \ "}" #define SPI_DBGETQUERY_CMD \ "dbGetQuery <-function(conn, sql) {\n" \ "data <- pg.spi.exec(sql)\n" \ "return(data)\n" \ "}" #define SPI_DBREADTABLE_CMD \ "dbReadTable <- function(con, name, row.names = \"row_names\", check.names = TRUE) {\n" \ "data <- dbGetQuery(con, paste(\"SELECT * from\", name))\n" \ "return(data)\n" \ "}" #define SPI_DBDISCONN_CMD \ "dbDisconnect <- function(con)\n" \ "{return(NA)}" #define SPI_DBUNLOADDRIVER_CMD \ "dbUnloadDriver <-function(drv)\n" \ "{return(NA)}" #define SPI_FACTOR_CMD \ "pg.spi.factor <- function(arg1) {\n" \ " for (col in 1:ncol(arg1)) {\n" \ " if (!is.numeric(arg1[,col])) {\n" \ " arg1[,col] <- factor(arg1[,col])\n" \ " }\n" \ " }\n" \ " return(arg1)\n" \ "}" #define REVAL \ "pg.reval <- function(arg1) {eval(parse(text = arg1))}" #define PG_STATE_FIRSTPASS \ "pg.state.firstpass <- TRUE" #define CurrentTriggerData ((TriggerData *) fcinfo->context) /* * static declarations */ static void plr_atexit(void); static void plr_load_builtins(Oid funcid); static void plr_init_all(Oid funcid); static Datum plr_trigger_handler(PG_FUNCTION_ARGS); static Datum plr_func_handler(PG_FUNCTION_ARGS); static plr_function *compile_plr_function(FunctionCallInfo fcinfo); static plr_function *do_compile(FunctionCallInfo fcinfo, HeapTuple procTup, plr_func_hashkey *hashkey); static SEXP plr_parse_func_body(const char *body); static SEXP plr_convertargs(plr_function *function, Datum *arg, bool *argnull, FunctionCallInfo fcinfo); static void plr_error_callback(void *arg); static Oid getNamespaceOidFromFunctionOid(Oid fnOid); static bool haveModulesTable(Oid nspOid); static char *getModulesSql(Oid nspOid); #ifdef HAVE_WINDOW_FUNCTIONS static void WinGetFrameData(WindowObject winobj, int argno, Datum *dvalues, bool *isnull, int *numels, bool *has_nulls); #endif static void plr_resolve_polymorphic_argtypes(int numargs, Oid *argtypes, char *argmodes, Node *call_expr, bool forValidator, const char *proname); /* * plr_call_handler - This is the only visible function * of the PL interpreter. The PostgreSQL * function manager and trigger manager * call this function for execution of * PL/R procedures. */ PG_FUNCTION_INFO_V1(plr_call_handler); Datum plr_call_handler(PG_FUNCTION_ARGS) { Datum retval; /* save caller's context */ plr_caller_context = CurrentMemoryContext; if (SPI_connect() != SPI_OK_CONNECT) elog(ERROR, "SPI_connect failed"); plr_SPI_context = CurrentMemoryContext; MemoryContextSwitchTo(plr_caller_context); /* initialize R if needed */ plr_init_all(fcinfo->flinfo->fn_oid); if (CALLED_AS_TRIGGER(fcinfo)) retval = plr_trigger_handler(fcinfo); else retval = plr_func_handler(fcinfo); return retval; } void load_r_cmd(const char *cmd) { SEXP cmdSexp, cmdexpr; int i, status; /* * Init if not already done. This can happen when PL/R is not preloaded * and reload_plr_modules() or install_rcmd() is called by the user prior * to any PL/R functions. */ if (!plr_pm_init_done) plr_init(); PROTECT(cmdSexp = NEW_CHARACTER(1)); SET_STRING_ELT(cmdSexp, 0, COPY_TO_USER_STRING(cmd)); PROTECT(cmdexpr = R_PARSEVECTOR(cmdSexp, -1, &status)); if (status != PARSE_OK) { UNPROTECT(2); if (last_R_error_msg) ereport(ERROR, (errcode(ERRCODE_DATA_EXCEPTION), errmsg("R interpreter parse error"), errdetail("%s", last_R_error_msg))); else ereport(ERROR, (errcode(ERRCODE_DATA_EXCEPTION), errmsg("R interpreter parse error"), errdetail("R parse error caught in \"%s\".", cmd))); } /* Loop is needed here as EXPSEXP may be of length > 1 */ for(i = 0; i < length(cmdexpr); i++) { R_tryEval(VECTOR_ELT(cmdexpr, i), R_GlobalEnv, &status); if(status != 0) { if (last_R_error_msg) ereport(ERROR, (errcode(ERRCODE_DATA_EXCEPTION), errmsg("R interpreter expression evaluation error"), errdetail("%s", last_R_error_msg))); else ereport(ERROR, (errcode(ERRCODE_DATA_EXCEPTION), errmsg("R interpreter expression evaluation error"), errdetail("R expression evaluation error caught " \ "in \"%s\".", cmd))); } } UNPROTECT(2); } /* * plr_cleanup() - Let the embedded interpreter clean up after itself * * DO NOT make this static --- it has to be registered as an on_proc_exit() * callback */ void PLR_CLEANUP { char *buf; char *tmpdir = getenv("R_SESSION_TMPDIR"); R_dot_Last(); R_RunExitFinalizers(); KillAllDevices(); if(tmpdir) { int rv; /* * length needed = 'rm -rf ""' == 9 * plus 1 for NULL terminator * plus length of dir string */ buf = (char *) palloc(9 + 1 + strlen(tmpdir)); sprintf(buf, "rm -rf \"%s\"", tmpdir); /* ignoring return value */ rv = system(buf); if (rv != 0) ; /* do nothing */ } } static void plr_atexit(void) { /* only react during plr startup */ if (plr_pm_init_done) return; ereport(ERROR, (errcode(ERRCODE_OBJECT_NOT_IN_PREREQUISITE_STATE), errmsg("the R interpreter did not initialize"), errhint("R_HOME must be correct in the environment " \ "of the user that starts the postmaster process."))); } /* * plr_init() - Initialize all that's safe to do in the postmaster * * DO NOT make this static --- it has to be callable by preload */ void plr_init(void) { char *r_home; int rargc; char *rargv[] = {"PL/R", "--slave", "--silent", "--no-save", "--no-restore"}; /* refuse to init more than once */ if (plr_pm_init_done) return; /* refuse to start if R_HOME is not defined */ r_home = getenv("R_HOME"); if (r_home == NULL) { size_t rh_len = strlen(R_HOME_DEFAULT); /* see if there is a compiled in default R_HOME */ if (rh_len) { char *rhenv; MemoryContext oldcontext; /* Needs to live until/unless we explicitly delete it */ oldcontext = MemoryContextSwitchTo(TopMemoryContext); rhenv = palloc(8 + rh_len); MemoryContextSwitchTo(oldcontext); sprintf(rhenv, "R_HOME=%s", R_HOME_DEFAULT); putenv(rhenv); } else ereport(ERROR, (errcode(ERRCODE_OBJECT_NOT_IN_PREREQUISITE_STATE), errmsg("environment variable R_HOME not defined"), errhint("R_HOME must be defined in the environment " \ "of the user that starts the postmaster process."))); } rargc = sizeof(rargv)/sizeof(rargv[0]); /* * register an exit callback to handle the case where R does not initialize * and just exits with R_suicide() */ atexit(plr_atexit); /* * Stop R using its own signal handlers */ R_SignalHandlers = 0; /* * When initialization fails, R currently exits. Check the return * value anyway in case this ever gets fixed */ if (!Rf_initEmbeddedR(rargc, rargv)) ereport(ERROR, (errcode(ERRCODE_OBJECT_NOT_IN_PREREQUISITE_STATE), errmsg("the R interpreter did not initialize"), errhint("R_HOME must be correct in the environment " \ "of the user that starts the postmaster process."))); /* arrange for automatic cleanup at proc_exit */ on_proc_exit(plr_cleanup, 0); #ifndef WIN32 /* * Force non-interactive mode since R may not do so. * See comment in Rembedded.c just after R_Interactive = TRUE: * "Rf_initialize_R set this based on isatty" * If Postgres still has the tty attached, R_Interactive remains TRUE */ R_Interactive = false; #endif plr_pm_init_done = true; } /* * plr_load_builtins() - load "builtin" PL/R functions into R interpreter */ static void plr_load_builtins(Oid funcid) { int j; char *cmd; char *cmds[] = { /* first turn off error handling by R */ OPTIONS_NULL_CMD, /* set up the postgres error handler in R */ THROWRERROR_CMD, OPTIONS_THROWRERROR_CMD, THROWNOTICE_CMD, THROWERROR_CMD, OPTIONS_THROWWARN_CMD, /* install the commands for SPI support in the interpreter */ QUOTE_LITERAL_CMD, QUOTE_IDENT_CMD, SPI_EXEC_CMD, SPI_PREPARE_CMD, SPI_EXECP_CMD, SPI_CURSOR_OPEN_CMD, SPI_CURSOR_FETCH_CMD, SPI_CURSOR_MOVE_CMD, SPI_CURSOR_CLOSE_CMD, SPI_LASTOID_CMD, SPI_DBDRIVER_CMD, SPI_DBCONN_CMD, SPI_DBSENDQUERY_CMD, SPI_DBFETCH_CMD, SPI_DBCLEARRESULT_CMD, SPI_DBGETQUERY_CMD, SPI_DBREADTABLE_CMD, SPI_DBDISCONN_CMD, SPI_DBUNLOADDRIVER_CMD, SPI_FACTOR_CMD, /* handy predefined R functions */ REVAL, /* terminate */ NULL }; /* * temporarily turn off R error reporting -- it will be turned back on * once the custom R error handler is installed from the plr library */ load_r_cmd(cmds[0]); /* next load the plr library into R */ load_r_cmd(get_load_self_ref_cmd(funcid)); /* * run the rest of the R bootstrap commands, being careful to start * at cmds[1] since we already executed cmds[0] */ for (j = 1; (cmd = cmds[j]); j++) load_r_cmd(cmds[j]); } /* * plr_load_modules() - Load procedures from * table plr_modules (if it exists) * * The caller is responsible to ensure SPI has already been connected * DO NOT make this static --- it has to be callable by reload_plr_modules() */ void plr_load_modules(void) { int spi_rc; char *cmd; int i; int fno; MemoryContext oldcontext; char *modulesSql; /* switch to SPI memory context */ SWITCHTO_PLR_SPI_CONTEXT(oldcontext); /* * Check if table plr_modules exists */ if (!haveModulesTable(plr_nspOid)) { /* clean up if SPI was used, and regardless restore caller's context */ CLEANUP_PLR_SPI_CONTEXT(oldcontext); return; } /* plr_modules table exists -- get SQL code extract table's contents */ modulesSql = getModulesSql(plr_nspOid); /* Read all the row's from it in the order of modseq */ spi_rc = SPI_exec(modulesSql, 0); /* modulesSql no longer needed -- cleanup */ pfree(modulesSql); if (spi_rc != SPI_OK_SELECT) /* internal error */ elog(ERROR, "plr_init_load_modules: select from plr_modules failed"); /* If there's nothing, no modules exist */ if (SPI_processed == 0) { SPI_freetuptable(SPI_tuptable); /* clean up if SPI was used, and regardless restore caller's context */ CLEANUP_PLR_SPI_CONTEXT(oldcontext); return; } /* * There is at least on module to load. Get the * source from the modsrc load it in the R interpreter */ fno = SPI_fnumber(SPI_tuptable->tupdesc, "modsrc"); for (i = 0; i < SPI_processed; i++) { cmd = SPI_getvalue(SPI_tuptable->vals[i], SPI_tuptable->tupdesc, fno); if (cmd != NULL) { load_r_cmd(cmd); pfree(cmd); } } SPI_freetuptable(SPI_tuptable); /* clean up if SPI was used, and regardless restore caller's context */ CLEANUP_PLR_SPI_CONTEXT(oldcontext); } static void plr_init_all(Oid funcid) { MemoryContext oldcontext; /* everything initialized needs to live until/unless we explicitly delete it */ oldcontext = MemoryContextSwitchTo(TopMemoryContext); /* execute postmaster-startup safe initialization */ if (!plr_pm_init_done) plr_init(); /* * Any other initialization that must be done each time a new * backend starts: */ if (!plr_be_init_done) { /* load "builtin" R functions */ plr_load_builtins(funcid); /* obtain & store namespace OID of PL/R language handler */ plr_nspOid = getNamespaceOidFromFunctionOid(funcid); /* try to load procedures from plr_modules */ plr_load_modules(); plr_be_init_done = true; } /* switch back to caller's context */ MemoryContextSwitchTo(oldcontext); } static Datum plr_trigger_handler(PG_FUNCTION_ARGS) { plr_function *function; SEXP fun; SEXP rargs; SEXP rvalue; Datum retval; Datum arg[FUNC_MAX_ARGS]; bool argnull[FUNC_MAX_ARGS]; TriggerData *trigdata = (TriggerData *) fcinfo->context; TupleDesc tupdesc = trigdata->tg_relation->rd_att; Datum *dvalues; ArrayType *array; #define FIXED_NUM_DIMS 1 int ndims = FIXED_NUM_DIMS; int dims[FIXED_NUM_DIMS]; int lbs[FIXED_NUM_DIMS]; #undef FIXED_NUM_DIMS TRIGGERTUPLEVARS; ERRORCONTEXTCALLBACK; int i; if (trigdata->tg_trigger->tgnargs > 0) dvalues = palloc(trigdata->tg_trigger->tgnargs * sizeof(Datum)); else dvalues = NULL; /* Find or compile the function */ function = compile_plr_function(fcinfo); /* set up error context */ PUSH_PLERRCONTEXT(plr_error_callback, function->proname); /* * Build up arguments for the trigger function. The data types * are mostly hardwired in advance */ /* first is trigger name */ arg[0] = DirectFunctionCall1(textin, CStringGetDatum(trigdata->tg_trigger->tgname)); argnull[0] = false; /* second is trigger relation oid */ arg[1] = ObjectIdGetDatum(trigdata->tg_relation->rd_id); argnull[1] = false; /* third is trigger relation name */ arg[2] = DirectFunctionCall1(textin, CStringGetDatum(get_rel_name(trigdata->tg_relation->rd_id))); argnull[2] = false; /* fourth is when trigger fired, i.e. BEFORE or AFTER */ if (TRIGGER_FIRED_BEFORE(trigdata->tg_event)) arg[3] = DirectFunctionCall1(textin, CStringGetDatum("BEFORE")); else if (TRIGGER_FIRED_AFTER(trigdata->tg_event)) arg[3] = DirectFunctionCall1(textin, CStringGetDatum("AFTER")); else /* internal error */ elog(ERROR, "unrecognized tg_event"); argnull[3] = false; /* * fifth is level trigger fired, i.e. ROW or STATEMENT * sixth is operation that fired trigger, i.e. INSERT, UPDATE, or DELETE * seventh is NEW, eigth is OLD */ if (TRIGGER_FIRED_FOR_STATEMENT(trigdata->tg_event)) { arg[4] = DirectFunctionCall1(textin, CStringGetDatum("STATEMENT")); if (TRIGGER_FIRED_BY_INSERT(trigdata->tg_event)) arg[5] = DirectFunctionCall1(textin, CStringGetDatum("INSERT")); else if (TRIGGER_FIRED_BY_DELETE(trigdata->tg_event)) arg[5] = DirectFunctionCall1(textin, CStringGetDatum("DELETE")); else if (TRIGGER_FIRED_BY_UPDATE(trigdata->tg_event)) arg[5] = DirectFunctionCall1(textin, CStringGetDatum("UPDATE")); else /* internal error */ elog(ERROR, "unrecognized tg_event"); arg[6] = (Datum) 0; argnull[6] = true; arg[7] = (Datum) 0; argnull[7] = true; } else if (TRIGGER_FIRED_FOR_ROW(trigdata->tg_event)) { arg[4] = DirectFunctionCall1(textin, CStringGetDatum("ROW")); if (TRIGGER_FIRED_BY_INSERT(trigdata->tg_event)) SET_INSERT_ARGS_567; else if (TRIGGER_FIRED_BY_DELETE(trigdata->tg_event)) SET_DELETE_ARGS_567; else if (TRIGGER_FIRED_BY_UPDATE(trigdata->tg_event)) SET_UPDATE_ARGS_567; else /* internal error */ elog(ERROR, "unrecognized tg_event"); } else /* internal error */ elog(ERROR, "unrecognized tg_event"); argnull[4] = false; argnull[5] = false; /* * finally, ninth argument is a text array of trigger arguments */ for (i = 0; i < trigdata->tg_trigger->tgnargs; i++) dvalues[i] = DirectFunctionCall1(textin, CStringGetDatum(trigdata->tg_trigger->tgargs[i])); dims[0] = trigdata->tg_trigger->tgnargs; lbs[0] = 1; array = construct_md_array(dvalues, NULL, ndims, dims, lbs, TEXTOID, -1, false, 'i'); arg[8] = PointerGetDatum(array); argnull[8] = false; /* * All done building args; from this point it is just like * calling a non-trigger function, except we need to be careful * that the return value tuple is the same tupdesc as the trigger tuple. */ PROTECT(fun = function->fun); /* Convert all call arguments */ PROTECT(rargs = plr_convertargs(function, arg, argnull, fcinfo)); /* Call the R function */ PROTECT(rvalue = call_r_func(fun, rargs)); /* * Convert the return value from an R object to a Datum. * We expect r_get_pg to do the right thing with missing or empty results. */ if (SPI_finish() != SPI_OK_FINISH) elog(ERROR, "SPI_finish failed"); retval = r_get_pg(rvalue, function, fcinfo); POP_PLERRCONTEXT; UNPROTECT(3); return retval; } static Datum plr_func_handler(PG_FUNCTION_ARGS) { plr_function *function; SEXP fun; SEXP rargs; SEXP rvalue; Datum retval; ERRORCONTEXTCALLBACK; /* Find or compile the function */ function = compile_plr_function(fcinfo); /* set up error context */ PUSH_PLERRCONTEXT(plr_error_callback, function->proname); PROTECT(fun = function->fun); /* Convert all call arguments */ PROTECT(rargs = plr_convertargs(function, fcinfo->arg, fcinfo->argnull, fcinfo)); /* Call the R function */ PROTECT(rvalue = call_r_func(fun, rargs)); /* * Convert the return value from an R object to a Datum. * We expect r_get_pg to do the right thing with missing or empty results. */ if (SPI_finish() != SPI_OK_FINISH) elog(ERROR, "SPI_finish failed"); retval = r_get_pg(rvalue, function, fcinfo); POP_PLERRCONTEXT; UNPROTECT(3); return retval; } /* ---------- * compile_plr_function * * Note: it's important for this to fall through quickly if the function * has already been compiled. * ---------- */ plr_function * compile_plr_function(FunctionCallInfo fcinfo) { Oid funcOid = fcinfo->flinfo->fn_oid; HeapTuple procTup; Form_pg_proc procStruct; plr_function *function; plr_func_hashkey hashkey; bool hashkey_valid = false; ERRORCONTEXTCALLBACK; /* * Lookup the pg_proc tuple by Oid; we'll need it in any case */ procTup = SearchSysCache(PROCOID, ObjectIdGetDatum(funcOid), 0, 0, 0); if (!HeapTupleIsValid(procTup)) /* internal error */ elog(ERROR, "cache lookup failed for proc %u", funcOid); procStruct = (Form_pg_proc) GETSTRUCT(procTup); /* set up error context */ PUSH_PLERRCONTEXT(plr_error_callback, NameStr(procStruct->proname)); /* * See if there's already a cache entry for the current FmgrInfo. * If not, try to find one in the hash table. */ function = (plr_function *) fcinfo->flinfo->fn_extra; if (!function) { /* First time through in this backend? If so, init hashtable */ if (!plr_HashTable) plr_HashTableInit(); /* Compute hashkey using function signature and actual arg types */ compute_function_hashkey(fcinfo, procStruct, &hashkey); hashkey_valid = true; /* And do the lookup */ function = plr_HashTableLookup(&hashkey); /* * first time through for this statement, set * firstpass to TRUE */ load_r_cmd(PG_STATE_FIRSTPASS); } if (function) { bool function_valid; /* We have a compiled function, but is it still valid? */ if (function->fn_xmin == HeapTupleHeaderGetXmin(procTup->t_data) && ItemPointerEquals(&function->fn_tid, &procTup->t_self)) function_valid = true; else function_valid = false; if (!function_valid) { /* * Nope, drop the hashtable entry. XXX someday, free all the * subsidiary storage as well. */ plr_HashTableDelete(function); /* free some of the subsidiary storage */ xpfree(function->proname); R_ReleaseObject(function->fun); xpfree(function); function = NULL; } } /* * If the function wasn't found or was out-of-date, we have to compile it */ if (!function) { /* * Calculate hashkey if we didn't already; we'll need it to store * the completed function. */ if (!hashkey_valid) compute_function_hashkey(fcinfo, procStruct, &hashkey); /* * Do the hard part. */ function = do_compile(fcinfo, procTup, &hashkey); } ReleaseSysCache(procTup); /* * Save pointer in FmgrInfo to avoid search on subsequent calls */ fcinfo->flinfo->fn_extra = (void *) function; POP_PLERRCONTEXT; /* * Finally return the compiled function */ return function; } /* * This is the slow part of compile_plr_function(). */ static plr_function * do_compile(FunctionCallInfo fcinfo, HeapTuple procTup, plr_func_hashkey *hashkey) { Form_pg_proc procStruct = (Form_pg_proc) GETSTRUCT(procTup); Datum prosrcdatum; bool isnull; bool is_trigger = CALLED_AS_TRIGGER(fcinfo) ? true : false; plr_function *function = NULL; Oid fn_oid = fcinfo->flinfo->fn_oid; char internal_proname[MAX_PRONAME_LEN]; char *proname; Oid result_typid; HeapTuple langTup; HeapTuple typeTup; Form_pg_language langStruct; Form_pg_type typeStruct; StringInfo proc_internal_def = makeStringInfo(); StringInfo proc_internal_args = makeStringInfo(); char *proc_source; MemoryContext oldcontext; char *p; /* grab the function name */ proname = NameStr(procStruct->proname); /* Build our internal proc name from the functions Oid */ sprintf(internal_proname, "PLR%u", fn_oid); /* * analyze the functions arguments and returntype and store * the in-/out-functions in the function block and create * a new hashtable entry for it. * * Then load the procedure into the R interpreter. */ /* the function structure needs to live until we explicitly delete it */ oldcontext = MemoryContextSwitchTo(TopMemoryContext); /* Allocate a new procedure description block */ function = (plr_function *) palloc(sizeof(plr_function)); if (function == NULL) ereport(ERROR, (errcode(ERRCODE_OUT_OF_MEMORY), errmsg("out of memory"))); MemSet(function, 0, sizeof(plr_function)); function->proname = pstrdup(proname); function->fn_xmin = HeapTupleHeaderGetXmin(procTup->t_data); function->fn_tid = procTup->t_self; #ifdef HAVE_WINDOW_FUNCTIONS /* Flag for window functions */ function->iswindow = procStruct->proiswindow; #endif /* Lookup the pg_language tuple by Oid*/ langTup = SearchSysCache(LANGOID, ObjectIdGetDatum(procStruct->prolang), 0, 0, 0); if (!HeapTupleIsValid(langTup)) { xpfree(function->proname); xpfree(function); /* internal error */ elog(ERROR, "cache lookup failed for language %u", procStruct->prolang); } langStruct = (Form_pg_language) GETSTRUCT(langTup); function->lanpltrusted = langStruct->lanpltrusted; ReleaseSysCache(langTup); /* get the functions return type */ if (procStruct->prorettype == ANYARRAYOID || procStruct->prorettype == ANYELEMENTOID) { result_typid = get_fn_expr_rettype(fcinfo->flinfo); if (result_typid == InvalidOid) result_typid = procStruct->prorettype; } else result_typid = procStruct->prorettype; /* * Get the required information for input conversion of the * return value. */ if (!is_trigger) { function->result_typid = result_typid; typeTup = SearchSysCache(TYPEOID, ObjectIdGetDatum(function->result_typid), 0, 0, 0); if (!HeapTupleIsValid(typeTup)) { xpfree(function->proname); xpfree(function); /* internal error */ elog(ERROR, "cache lookup failed for return type %u", procStruct->prorettype); } typeStruct = (Form_pg_type) GETSTRUCT(typeTup); /* Disallow pseudotype return type except VOID or RECORD */ /* (note we already replaced ANYARRAY/ANYELEMENT) */ if (typeStruct->typtype == 'p') { if (procStruct->prorettype == VOIDOID || procStruct->prorettype == RECORDOID) /* okay */ ; else if (procStruct->prorettype == TRIGGEROID) { xpfree(function->proname); xpfree(function); ereport(ERROR, (errcode(ERRCODE_FEATURE_NOT_SUPPORTED), errmsg("trigger functions may only be called as triggers"))); } else { xpfree(function->proname); xpfree(function); ereport(ERROR, (errcode(ERRCODE_FEATURE_NOT_SUPPORTED), errmsg("plr functions cannot return type %s", format_type_be(procStruct->prorettype)))); } } if (typeStruct->typrelid != InvalidOid || procStruct->prorettype == RECORDOID) function->result_istuple = true; perm_fmgr_info(typeStruct->typinput, &(function->result_in_func)); if (function->result_istuple) { int16 typlen; bool typbyval; char typdelim; Oid typinput, typelem; FmgrInfo inputproc; char typalign; TupleDesc tupdesc; int i; ReturnSetInfo *rsinfo = (ReturnSetInfo *) fcinfo->resultinfo; /* check to see if caller supports us returning a tuplestore */ if (!rsinfo || !(rsinfo->allowedModes & SFRM_Materialize) || rsinfo->expectedDesc == NULL) ereport(ERROR, (errcode(ERRCODE_SYNTAX_ERROR), errmsg("materialize mode required, but it is not " "allowed in this context"))); tupdesc = rsinfo->expectedDesc; function->result_natts = tupdesc->natts; function->result_fld_elem_typid = (Oid *) palloc0(function->result_natts * sizeof(Oid)); function->result_fld_elem_in_func = (FmgrInfo *) palloc0(function->result_natts * sizeof(FmgrInfo)); function->result_fld_elem_typlen = (int *) palloc0(function->result_natts * sizeof(int)); function->result_fld_elem_typbyval = (bool *) palloc0(function->result_natts * sizeof(bool)); function->result_fld_elem_typalign = (char *) palloc0(function->result_natts * sizeof(char)); for (i = 0; i < function->result_natts; i++) { function->result_fld_elem_typid[i] = get_element_type(tupdesc->attrs[i]->atttypid); if (OidIsValid(function->result_fld_elem_typid[i])) { get_type_io_data(function->result_fld_elem_typid[i], IOFunc_input, &typlen, &typbyval, &typalign, &typdelim, &typelem, &typinput); perm_fmgr_info(typinput, &inputproc); function->result_fld_elem_in_func[i] = inputproc; function->result_fld_elem_typbyval[i] = typbyval; function->result_fld_elem_typlen[i] = typlen; function->result_fld_elem_typalign[i] = typalign; } } } else { /* * Is return type an array? get_element_type will return InvalidOid * instead of actual element type if the type is not a varlena array. */ if (OidIsValid(get_element_type(function->result_typid))) function->result_elem = typeStruct->typelem; else /* not an array */ function->result_elem = InvalidOid; /* * if we have an array type, get the element type's in_func */ if (function->result_elem != InvalidOid) { int16 typlen; bool typbyval; char typdelim; Oid typinput, typelem; FmgrInfo inputproc; char typalign; get_type_io_data(function->result_elem, IOFunc_input, &typlen, &typbyval, &typalign, &typdelim, &typelem, &typinput); perm_fmgr_info(typinput, &inputproc); function->result_elem_in_func = inputproc; function->result_elem_typbyval = typbyval; function->result_elem_typlen = typlen; function->result_elem_typalign = typalign; } } ReleaseSysCache(typeTup); } else /* trigger */ { function->result_typid = TRIGGEROID; function->result_istuple = true; function->result_elem = InvalidOid; } /* * Get the required information for output conversion * of all procedure arguments */ if (!is_trigger) { int i; bool forValidator = false; int numargs; Oid *argtypes; char **argnames; char *argmodes; numargs = get_func_arg_info(procTup, &argtypes, &argnames, &argmodes); plr_resolve_polymorphic_argtypes(numargs, argtypes, argmodes, fcinfo->flinfo->fn_expr, forValidator, function->proname); function->nargs = procStruct->pronargs; for (i = 0; i < function->nargs; i++) { char argmode = argmodes ? argmodes[i] : PROARGMODE_IN; if (argmode != PROARGMODE_IN && argmode != PROARGMODE_INOUT && argmode != PROARGMODE_VARIADIC) continue; /* * Since we already did the replacement of polymorphic * argument types by actual argument types while computing * the hashkey, we can just use those results. */ function->arg_typid[i] = hashkey->argtypes[i]; typeTup = SearchSysCache(TYPEOID, ObjectIdGetDatum(function->arg_typid[i]), 0, 0, 0); if (!HeapTupleIsValid(typeTup)) { Oid arg_typid = function->arg_typid[i]; xpfree(function->proname); xpfree(function); /* internal error */ elog(ERROR, "cache lookup failed for argument type %u", arg_typid); } typeStruct = (Form_pg_type) GETSTRUCT(typeTup); /* Disallow pseudotype argument * note we already replaced ANYARRAY/ANYELEMENT */ if (typeStruct->typtype == 'p') { Oid arg_typid = function->arg_typid[i]; xpfree(function->proname); xpfree(function); ereport(ERROR, (errcode(ERRCODE_FEATURE_NOT_SUPPORTED), errmsg("plr functions cannot take type %s", format_type_be(arg_typid)))); } if (typeStruct->typrelid != InvalidOid) function->arg_is_rel[i] = 1; else function->arg_is_rel[i] = 0; perm_fmgr_info(typeStruct->typoutput, &(function->arg_out_func[i])); /* save argument typbyval in case we need for optimization in conversions */ function->arg_typbyval[i] = typeStruct->typbyval; /* * Is argument type an array? get_element_type will return InvalidOid * instead of actual element type if the type is not a varlena array. */ if (OidIsValid(get_element_type(function->arg_typid[i]))) function->arg_elem[i] = typeStruct->typelem; else /* not ant array */ function->arg_elem[i] = InvalidOid; if (i > 0) appendStringInfo(proc_internal_args, ","); SET_ARG_NAME; ReleaseSysCache(typeTup); if (function->arg_elem[i] != InvalidOid) { int16 typlen; bool typbyval; char typdelim; Oid typoutput, typelem; FmgrInfo outputproc; char typalign; get_type_io_data(function->arg_elem[i], IOFunc_output, &typlen, &typbyval, &typalign, &typdelim, &typelem, &typoutput); perm_fmgr_info(typoutput, &outputproc); function->arg_elem_out_func[i] = outputproc; function->arg_elem_typbyval[i] = typbyval; function->arg_elem_typlen[i] = typlen; function->arg_elem_typalign[i] = typalign; } } FREE_ARG_NAMES; #ifdef HAVE_WINDOW_FUNCTIONS if (function->iswindow) { for (i = 0; i < function->nargs; i++) { appendStringInfo(proc_internal_args, ","); SET_FRAME_ARG_NAME; } SET_FRAME_XARG_NAMES; } #endif } else { int16 typlen; bool typbyval; char typdelim; Oid typoutput, typelem; FmgrInfo outputproc; char typalign; function->nargs = TRIGGER_NARGS; /* take care of the only non-TEXT first */ get_type_io_data(OIDOID, IOFunc_output, &typlen, &typbyval, &typalign, &typdelim, &typelem, &typoutput); function->arg_typid[1] = OIDOID; function->arg_elem[1] = InvalidOid; function->arg_is_rel[1] = 0; perm_fmgr_info(typoutput, &(function->arg_out_func[1])); get_type_io_data(TEXTOID, IOFunc_output, &typlen, &typbyval, &typalign, &typdelim, &typelem, &typoutput); function->arg_typid[0] = TEXTOID; function->arg_elem[0] = InvalidOid; function->arg_is_rel[0] = 0; perm_fmgr_info(typoutput, &(function->arg_out_func[0])); function->arg_typid[2] = TEXTOID; function->arg_elem[2] = InvalidOid; function->arg_is_rel[2] = 0; perm_fmgr_info(typoutput, &(function->arg_out_func[2])); function->arg_typid[3] = TEXTOID; function->arg_elem[3] = InvalidOid; function->arg_is_rel[3] = 0; perm_fmgr_info(typoutput, &(function->arg_out_func[3])); function->arg_typid[4] = TEXTOID; function->arg_elem[4] = InvalidOid; function->arg_is_rel[4] = 0; perm_fmgr_info(typoutput, &(function->arg_out_func[4])); function->arg_typid[5] = TEXTOID; function->arg_elem[5] = InvalidOid; function->arg_is_rel[5] = 0; perm_fmgr_info(typoutput, &(function->arg_out_func[5])); function->arg_typid[6] = RECORDOID; function->arg_elem[6] = InvalidOid; function->arg_is_rel[6] = 1; function->arg_typid[7] = RECORDOID; function->arg_elem[7] = InvalidOid; function->arg_is_rel[7] = 1; function->arg_typid[8] = TEXTARRAYOID; function->arg_elem[8] = TEXTOID; function->arg_is_rel[8] = 0; get_type_io_data(function->arg_elem[8], IOFunc_output, &typlen, &typbyval, &typalign, &typdelim, &typelem, &typoutput); perm_fmgr_info(typoutput, &outputproc); function->arg_elem_out_func[8] = outputproc; function->arg_elem_typbyval[8] = typbyval; function->arg_elem_typlen[8] = typlen; function->arg_elem_typalign[8] = typalign; /* trigger procedure has fixed args */ appendStringInfo(proc_internal_args, "pg.tg.name,pg.tg.relid,pg.tg.relname,pg.tg.when," "pg.tg.level,pg.tg.op,pg.tg.new,pg.tg.old,pg.tg.args"); } /* * Create the R command to define the internal * procedure */ appendStringInfo(proc_internal_def, "%s <- function(%s) {", internal_proname, proc_internal_args->data); /* Add user's function definition to proc body */ prosrcdatum = SysCacheGetAttr(PROCOID, procTup, Anum_pg_proc_prosrc, &isnull); if (isnull) elog(ERROR, "null prosrc"); proc_source = DatumGetCString(DirectFunctionCall1(textout, prosrcdatum)); /* * replace any carriage returns with either a space or a newline, * as appropriate */ p = proc_source; while (*p != '\0') { if (p[0] == '\r') { if (p[1] == '\n') /* for crlf sequence, write over the cr with a space */ *p++ = ' '; else /* otherwise write over the cr with a nl */ *p++ = '\n'; } else p++; } /* parse or find the R function */ if(proc_source && proc_source[0]) appendStringInfo(proc_internal_def, "%s}", proc_source); else appendStringInfo(proc_internal_def, "%s(%s)}", function->proname, proc_internal_args->data); function->fun = plr_parse_func_body(proc_internal_def->data); R_PreserveObject(function->fun); pfree(proc_source); freeStringInfo(proc_internal_def); /* test that this is really a function. */ if(function->fun == R_NilValue) { xpfree(function->proname); xpfree(function); /* internal error */ elog(ERROR, "cannot create internal procedure %s", internal_proname); } /* switch back to the context we were called with */ MemoryContextSwitchTo(oldcontext); /* * add it to the hash table */ plr_HashTableInsert(function, hashkey); return function; } static SEXP plr_parse_func_body(const char *body) { SEXP rbody; SEXP fun; SEXP tmp; int status; PROTECT(rbody = mkString(body)); PROTECT(tmp = R_PARSEVECTOR(rbody, -1, &status)); if (tmp != R_NilValue) PROTECT(fun = VECTOR_ELT(tmp, 0)); else PROTECT(fun = R_NilValue); if (status != PARSE_OK) { UNPROTECT(3); if (last_R_error_msg) ereport(ERROR, (errcode(ERRCODE_DATA_EXCEPTION), errmsg("R interpreter parse error"), errdetail("%s", last_R_error_msg))); else ereport(ERROR, (errcode(ERRCODE_DATA_EXCEPTION), errmsg("R interpreter parse error"), errdetail("R parse error caught " \ "in \"%s\".", body))); } UNPROTECT(3); return(fun); } SEXP call_r_func(SEXP fun, SEXP rargs) { int i; int errorOccurred; SEXP obj, args, call, ans; long n = length(rargs); if(n > 0) { PROTECT(obj = args = allocList(n)); for (i = 0; i < n; i++) { SETCAR(obj, VECTOR_ELT(rargs, i)); obj = CDR(obj); } UNPROTECT(1); /* * NB: the headers of both R and Postgres define a function * called lcons, so use the full name to be precise about what * function we're calling. */ PROTECT(call = Rf_lcons(fun, args)); } else { PROTECT(call = allocVector(LANGSXP,1)); SETCAR(call, fun); } ans = R_tryEval(call, R_GlobalEnv, &errorOccurred); UNPROTECT(1); if(errorOccurred) { if (last_R_error_msg) ereport(ERROR, (errcode(ERRCODE_DATA_EXCEPTION), errmsg("R interpreter expression evaluation error"), errdetail("%s", last_R_error_msg))); else ereport(ERROR, (errcode(ERRCODE_DATA_EXCEPTION), errmsg("R interpreter expression evaluation error"))); } return ans; } static SEXP plr_convertargs(plr_function *function, Datum *arg, bool *argnull, FunctionCallInfo fcinfo) { int i; int m = 1; int c = 0; SEXP rargs, el; #ifdef HAVE_WINDOW_FUNCTIONS if (function->iswindow) { /* * For WINDOW functions, create an array of R objects with * the number of elements equal to twice the number of arguments. */ m = 2; c = 2; } #endif /* * Create an array of R objects with the number of elements * as a function of the number of arguments. */ PROTECT(rargs = allocVector(VECSXP, c + (m * function->nargs))); /* * iterate over the arguments, convert each of them and put them in * the array. */ for (i = 0; i < function->nargs; i++) { #ifdef HAVE_WINDOW_FUNCTIONS if (!function->iswindow) { #endif if (argnull[i]) { /* fast track for null arguments */ PROTECT(el = R_NilValue); } else if (function->arg_is_rel[i]) { /* for tuple args, convert to a one row data.frame */ CONVERT_TUPLE_TO_DATAFRAME; } else if (function->arg_elem[i] == InvalidOid) { /* for scalar args, convert to a one row vector */ Datum dvalue = arg[i]; Oid arg_typid = function->arg_typid[i]; FmgrInfo arg_out_func = function->arg_out_func[i]; PROTECT(el = pg_scalar_get_r(dvalue, arg_typid, arg_out_func)); } else { /* better be a pg array arg, convert to a multi-row vector */ Datum dvalue = (Datum) PG_DETOAST_DATUM(arg[i]); FmgrInfo out_func = function->arg_elem_out_func[i]; int typlen = function->arg_elem_typlen[i]; bool typbyval = function->arg_elem_typbyval[i]; char typalign = function->arg_elem_typalign[i]; PROTECT(el = pg_array_get_r(dvalue, out_func, typlen, typbyval, typalign)); } SET_VECTOR_ELT(rargs, i, el); UNPROTECT(1); #ifdef HAVE_WINDOW_FUNCTIONS } else { Datum dvalue; bool isnull; WindowObject winobj = PG_WINDOW_OBJECT(); /* get datum for the current row of the window frame */ dvalue = WinGetFuncArgInFrame(winobj, i, 0, WINDOW_SEEK_CURRENT, false, &isnull, NULL); if (isnull) { /* fast track for null arguments */ PROTECT(el = R_NilValue); } else if (function->arg_is_rel[i]) { /* keep compiler quiet */ el = R_NilValue; elog(ERROR, "Tuple arguments not supported in PL/R Window Functions"); } else if (function->arg_elem[i] == InvalidOid) { /* for scalar args, convert to a one row vector */ Oid arg_typid = function->arg_typid[i]; FmgrInfo arg_out_func = function->arg_out_func[i]; PROTECT(el = pg_scalar_get_r(dvalue, arg_typid, arg_out_func)); } else { /* better be a pg array arg, convert to a multi-row vector */ FmgrInfo out_func = function->arg_elem_out_func[i]; int typlen = function->arg_elem_typlen[i]; bool typbyval = function->arg_elem_typbyval[i]; char typalign = function->arg_elem_typalign[i]; dvalue = (Datum) PG_DETOAST_DATUM(dvalue); PROTECT(el = pg_array_get_r(dvalue, out_func, typlen, typbyval, typalign)); } SET_VECTOR_ELT(rargs, i, el); UNPROTECT(1); } #endif } #ifdef HAVE_WINDOW_FUNCTIONS /* now get an array of datums for the entire window frame for each argument */ if (function->iswindow) { WindowObject winobj = PG_WINDOW_OBJECT(); int64 totalrows = WinGetPartitionRowCount(winobj); int numels = 0; for (i = 0; i < function->nargs; i++) { Datum *dvalues = palloc0(totalrows * sizeof(Datum)); bool *isnulls = palloc0(totalrows * sizeof(bool)); Oid datum_typid; FmgrInfo datum_out_func; bool datum_typbyval; bool has_nulls; WinGetFrameData(winobj, i, dvalues, isnulls, &numels, &has_nulls); datum_typid = function->arg_typid[i]; datum_out_func = function->arg_out_func[i]; datum_typbyval = function->arg_typbyval[i]; PROTECT(el = pg_datum_array_get_r(dvalues, isnulls, numels, has_nulls, datum_typid, datum_out_func, datum_typbyval)); /* * We already set function->nargs arguments * so we must start with a function->nargs */ SET_VECTOR_ELT(rargs, function->nargs + i, el); UNPROTECT(1); } /* fnumrows */ PROTECT(el = NEW_NUMERIC(1)); NUMERIC_DATA(el)[0] = (double) numels; SET_VECTOR_ELT(rargs, m * function->nargs + 0, el); UNPROTECT(1); /* prownum */ PROTECT(el = NEW_NUMERIC(1)); NUMERIC_DATA(el)[0] = (double) WinGetCurrentPosition(winobj) + 1;; SET_VECTOR_ELT(rargs, m * function->nargs + 1, el); UNPROTECT(1); } #endif UNPROTECT(1); return(rargs); } /* * error context callback to let us supply a call-stack traceback */ static void plr_error_callback(void *arg) { if (arg) errcontext("In PL/R function %s", (char *) arg); } /* * getNamespaceOidFromFunctionOid - Returns the OID of the namespace for the * language handler function for the postgresql function with the OID equal * to the input argument. */ static Oid getNamespaceOidFromFunctionOid(Oid fnOid) { HeapTuple procTuple; HeapTuple langTuple; Form_pg_proc procStruct; Form_pg_language langStruct; Oid langOid; Oid hfnOid; Oid nspOid; /* Lookup the pg_proc tuple for the called function by OID */ procTuple = SearchSysCache(PROCOID, ObjectIdGetDatum(fnOid), 0, 0, 0); if (!HeapTupleIsValid(procTuple)) /* internal error */ elog(ERROR, "cache lookup failed for function %u", fnOid); procStruct = (Form_pg_proc) GETSTRUCT(procTuple); langOid = procStruct->prolang; ReleaseSysCache(procTuple); /* Lookup the pg_language tuple by OID */ langTuple = SearchSysCache(LANGOID, ObjectIdGetDatum(langOid), 0, 0, 0); if (!HeapTupleIsValid(langTuple)) /* internal error */ elog(ERROR, "cache lookup failed for language %u", langOid); langStruct = (Form_pg_language) GETSTRUCT(langTuple); hfnOid = langStruct->lanplcallfoid; ReleaseSysCache(langTuple); /* Lookup the pg_proc tuple for the language handler by OID */ procTuple = SearchSysCache(PROCOID, ObjectIdGetDatum(hfnOid), 0, 0, 0); if (!HeapTupleIsValid(procTuple)) /* internal error */ elog(ERROR, "cache lookup failed for function %u", hfnOid); procStruct = (Form_pg_proc) GETSTRUCT(procTuple); nspOid = procStruct->pronamespace; ReleaseSysCache(procTuple); return nspOid; } /* * haveModulesTable(Oid) -- Check if table plr_modules exists in the namespace * designated by the OID input argument. */ static bool haveModulesTable(Oid nspOid) { StringInfo sql = makeStringInfo(); char *sql_format = "SELECT NULL " "FROM pg_catalog.pg_class " "WHERE " "relname = 'plr_modules' AND " "relnamespace = %u"; int spiRc; appendStringInfo(sql, sql_format, nspOid); spiRc = SPI_exec(sql->data, 1); if (spiRc != SPI_OK_SELECT) /* internal error */ elog(ERROR, "haveModulesTable: select from pg_class failed"); return SPI_processed == 1; } /* * getModulesSql(Oid) - Builds and returns SQL needed to extract contents from * plr_modules table. The table must exist in the namespace designated by the * OID input argument. Results are ordered by the "modseq" field. * * IMPORTANT: return value must be pfree'd */ static char * getModulesSql(Oid nspOid) { StringInfo sql = makeStringInfo(); char *sql_format = "SELECT modseq, modsrc " "FROM %s " "ORDER BY modseq"; appendStringInfo(sql, sql_format, quote_qualified_identifier(get_namespace_name(nspOid), "plr_modules")); return sql->data; } #ifdef DEBUGPROTECT SEXP pg_protect(SEXP s, char *fn, int ln) { elog(NOTICE, "\tPROTECT\t1\t%s\t%d", fn, ln); return protect(s); } void pg_unprotect(int n, char *fn, int ln) { elog(NOTICE, "\tUNPROTECT\t%d\t%s\t%d", n, fn, ln); unprotect(n); } #endif /* DEBUGPROTECT */ #ifdef HAVE_WINDOW_FUNCTIONS /* * WinGetFrameData * Evaluate a window function's argument expression on a specified * window frame, returning an array of Datums for the frame * * argno: argument number to evaluate (counted from 0) * isnull: output argument, receives isnull status of result */ static void WinGetFrameData(WindowObject winobj, int argno, Datum *dvalues, bool *isnulls, int *numels, bool *has_nulls) { int64 i = 0; *has_nulls = false; for(;;) { Datum lcl_dvalue; bool lcl_isnull; bool isout; bool set_mark; if (i > 0) set_mark = false; else set_mark = true; lcl_dvalue = WinGetFuncArgInFrame(winobj, argno, i, WINDOW_SEEK_HEAD, set_mark, &lcl_isnull, &isout); if (!isout) { dvalues[i] = lcl_dvalue; isnulls[i] = lcl_isnull; if (lcl_isnull) *has_nulls = true; } else { *numels = i; break; } i++; }; } #endif /* * swiped out of plpgsql pl_comp.c * * This is the same as the standard resolve_polymorphic_argtypes() function, * but with a special case for validation: assume that polymorphic arguments * are integer, integer-array or integer-range. Also, we go ahead and report * the error if we can't resolve the types. */ static void plr_resolve_polymorphic_argtypes(int numargs, Oid *argtypes, char *argmodes, Node *call_expr, bool forValidator, const char *proname) { int i; if (!forValidator) { /* normal case, pass to standard routine */ if (!resolve_polymorphic_argtypes(numargs, argtypes, argmodes, call_expr)) ereport(ERROR, (errcode(ERRCODE_FEATURE_NOT_SUPPORTED), errmsg("could not determine actual argument " "type for polymorphic function \"%s\"", proname))); } else { /* special validation case */ for (i = 0; i < numargs; i++) { switch (argtypes[i]) { case ANYELEMENTOID: case ANYNONARRAYOID: case ANYENUMOID: /* XXX dubious */ argtypes[i] = INT4OID; break; case ANYARRAYOID: argtypes[i] = INT4ARRAYOID; break; #ifdef ANYRANGEOID case ANYRANGEOID: argtypes[i] = INT4RANGEOID; break; #endif default: break; } } } } plr/plr--8.3.0.16.sql0000664000000000000000000000551512465736645012667 0ustar rootroot-- keep this in sync with the plr.sql.in legacy install file CREATE FUNCTION plr_call_handler() RETURNS LANGUAGE_HANDLER AS 'MODULE_PATHNAME' LANGUAGE C; CREATE LANGUAGE plr HANDLER plr_call_handler; CREATE OR REPLACE FUNCTION plr_version () RETURNS text AS 'MODULE_PATHNAME','plr_version' LANGUAGE C; CREATE OR REPLACE FUNCTION reload_plr_modules () RETURNS text AS 'MODULE_PATHNAME','reload_plr_modules' LANGUAGE C; CREATE OR REPLACE FUNCTION install_rcmd (text) RETURNS text AS 'MODULE_PATHNAME','install_rcmd' LANGUAGE C WITH (isstrict); REVOKE EXECUTE ON FUNCTION install_rcmd (text) FROM PUBLIC; CREATE OR REPLACE FUNCTION plr_singleton_array (float8) RETURNS float8[] AS 'MODULE_PATHNAME','plr_array' LANGUAGE C WITH (isstrict); CREATE OR REPLACE FUNCTION plr_array_push (_float8, float8) RETURNS float8[] AS 'MODULE_PATHNAME','plr_array_push' LANGUAGE C WITH (isstrict); CREATE OR REPLACE FUNCTION plr_array_accum (_float8, float8) RETURNS float8[] AS 'MODULE_PATHNAME','plr_array_accum' LANGUAGE C; CREATE TYPE plr_environ_type AS (name text, value text); CREATE OR REPLACE FUNCTION plr_environ () RETURNS SETOF plr_environ_type AS 'MODULE_PATHNAME','plr_environ' LANGUAGE C; REVOKE EXECUTE ON FUNCTION plr_environ() FROM PUBLIC; CREATE TYPE r_typename AS (typename text, typeoid oid); CREATE OR REPLACE FUNCTION r_typenames() RETURNS SETOF r_typename AS ' x <- ls(name = .GlobalEnv, pat = "OID") y <- vector() for (i in 1:length(x)) {y[i] <- eval(parse(text = x[i]))} data.frame(typename = x, typeoid = y) ' language 'plr'; CREATE OR REPLACE FUNCTION load_r_typenames() RETURNS text AS ' sql <- "select upper(typname::text) || ''OID'' as typename, oid from pg_catalog.pg_type where typtype = ''b'' order by typname" rs <- pg.spi.exec(sql) for(i in 1:nrow(rs)) { typobj <- rs[i,1] typval <- rs[i,2] if (substr(typobj,1,1) == "_") typobj <- paste("ARRAYOF", substr(typobj,2,nchar(typobj)), sep="") assign(typobj, typval, .GlobalEnv) } return("OK") ' language 'plr'; CREATE TYPE r_version_type AS (name text, value text); CREATE OR REPLACE FUNCTION r_version() RETURNS setof r_version_type as ' cbind(names(version),unlist(version)) ' language 'plr'; CREATE OR REPLACE FUNCTION plr_set_rhome (text) RETURNS text AS 'MODULE_PATHNAME','plr_set_rhome' LANGUAGE C WITH (isstrict); REVOKE EXECUTE ON FUNCTION plr_set_rhome (text) FROM PUBLIC; CREATE OR REPLACE FUNCTION plr_unset_rhome () RETURNS text AS 'MODULE_PATHNAME','plr_unset_rhome' LANGUAGE C; REVOKE EXECUTE ON FUNCTION plr_unset_rhome () FROM PUBLIC; CREATE OR REPLACE FUNCTION plr_set_display (text) RETURNS text AS 'MODULE_PATHNAME','plr_set_display' LANGUAGE C WITH (isstrict); REVOKE EXECUTE ON FUNCTION plr_set_display (text) FROM PUBLIC; CREATE OR REPLACE FUNCTION plr_get_raw (bytea) RETURNS bytea AS 'MODULE_PATHNAME','plr_get_raw' LANGUAGE C WITH (isstrict); plr/plr.spec0000664000000000000000000000412712465736645012052 0ustar rootroot%define pkgdocdir %(pg_config --docdir) %define pkglibdir %(pg_config --pkglibdir) %define pkgsharedir %(pg_config --sharedir) Summary: A loadable procedural language that enables you to write PostgreSQL functions and triggers in the R programming language. Name: plr Version: 8.3.0.16 Release: 1%{?dist} License: BSD Group: Applications/Databases Source: http://www.joeconway.com/plr/plr-%{version}.tar.gz URL: http://www.joeconway.com/plr/ BuildRequires: postgresql-devel >= 8.3 BuildRequires: R-devel Requires: postgresql-server >= 8.3 Requires: R BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) %description PL/R is a loadable procedural language that enables you to write PostgreSQL functions and triggers in the R programming language. PL/R offers most (if not all) of the capabilities a function writer has in the R language. Commands are available to access the database via the PostgreSQL Server Programming Interface (SPI) and to raise messages via elog() . There is no way to access internals of the database backend. However the user is able to gain OS-level access under the permissions of the PostgreSQL user ID, as with a C function. Thus, any unprivileged database user should not be permitted to use this language. It must be installed as an untrusted procedural language so that only database superusers can create functions in it. The writer of a PL/R function must take care that the function cannot be used to do anything unwanted, since it will be able to do anything that could be done by a user logged in as the database administrator. An implementation restriction is that PL/R procedures cannot be used to create input/output functions for new data types. %prep %setup -q -n %{name} %build make USE_PGXS=1 %install rm -rf %{buildroot} make USE_PGXS=1 DESTDIR=%{buildroot}/ install %clean rm -rf %{buildroot} %files %defattr(644,root,root,755) %doc %{pkgdocdir}/extension/README.plr %{pkgsharedir}/extension/plr.sql %{pkgsharedir}/extension/plr.control %{pkgsharedir}/extension/plr--8.3.0.16.sql %{pkgsharedir}/extension/plr--unpackaged--8.3.0.16.sql %{pkglibdir}/plr.so* plr/pg_backend_support.c0000775000000000000000000002570112465736645014422 0ustar rootroot/* * PL/R - PostgreSQL support for R as a * procedural language (PL) * * Copyright (c) 2003-2015 by Joseph E. Conway * ALL RIGHTS RESERVED * * Joe Conway * * Based on pltcl by Jan Wieck * and inspired by REmbeddedPostgres by * Duncan Temple Lang * http://www.omegahat.org/RSPostgres/ * * License: GPL version 2 or newer. http://www.gnu.org/copyleft/gpl.html * * This program 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. * * This program 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 this program; if not, write to the Free Software * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA * * pg_backend_support.c - Postgres backend support functions */ #include "plr.h" #ifdef PGDLLIMPORT /* Postgres global */ extern PGDLLIMPORT char my_exec_path[]; #else /* Postgres global */ extern DLLIMPORT char my_exec_path[]; #endif /* PGDLLIMPORT */ /* compiled function hash table */ extern HTAB *plr_HashTable; /* caller's memory context */ extern MemoryContext plr_caller_context; /* * static declarations */ static char *get_lib_pathstr(Oid funcid); static char *expand_dynamic_library_name(const char *name); static char *substitute_libpath_macro(const char *name); static char *find_in_dynamic_libpath(const char *basename); static bool file_exists(const char *name); /* * Compute the hashkey for a given function invocation * * The hashkey is returned into the caller-provided storage at *hashkey. */ void compute_function_hashkey(FunctionCallInfo fcinfo, Form_pg_proc procStruct, plr_func_hashkey *hashkey) { int i; /* Make sure any unused bytes of the struct are zero */ MemSet(hashkey, 0, sizeof(plr_func_hashkey)); /* get function OID */ hashkey->funcOid = fcinfo->flinfo->fn_oid; /* if trigger, get relation OID */ if (CALLED_AS_TRIGGER(fcinfo)) { TriggerData *trigdata = (TriggerData *) fcinfo->context; hashkey->trigrelOid = RelationGetRelid(trigdata->tg_relation); } /* get the argument types */ for (i = 0; i < procStruct->pronargs; i++) { Oid argtypeid = PROARGTYPES(i); /* * Check for polymorphic arguments. If found, use the actual * parameter type from the caller's FuncExpr node, if we have one. * * We can support arguments of type ANY the same way as normal * polymorphic arguments. */ if (argtypeid == ANYARRAYOID || argtypeid == ANYELEMENTOID || argtypeid == ANYOID) { argtypeid = get_fn_expr_argtype(fcinfo->flinfo, i); if (!OidIsValid(argtypeid)) ereport(ERROR, (errcode(ERRCODE_FEATURE_NOT_SUPPORTED), errmsg("could not determine actual argument " "type for polymorphic function \"%s\"", NameStr(procStruct->proname)))); } hashkey->argtypes[i] = argtypeid; } } void plr_HashTableInit(void) { HASHCTL ctl; memset(&ctl, 0, sizeof(ctl)); ctl.keysize = sizeof(plr_func_hashkey); ctl.entrysize = sizeof(plr_HashEnt); ctl.hash = tag_hash; plr_HashTable = hash_create("PLR function cache", FUNCS_PER_USER, &ctl, HASH_ELEM | HASH_FUNCTION); } plr_function * plr_HashTableLookup(plr_func_hashkey *func_key) { plr_HashEnt *hentry; hentry = (plr_HashEnt*) hash_search(plr_HashTable, (void *) func_key, HASH_FIND, NULL); if (hentry) return hentry->function; else return (plr_function *) NULL; } void plr_HashTableInsert(plr_function *function, plr_func_hashkey *func_key) { plr_HashEnt *hentry; bool found; hentry = (plr_HashEnt*) hash_search(plr_HashTable, (void *) func_key, HASH_ENTER, &found); if (hentry == NULL) ereport(ERROR, (errcode(ERRCODE_OUT_OF_MEMORY), errmsg("out of memory"))); if (found) elog(WARNING, "trying to insert a function that exists"); hentry->function = function; /* prepare back link from function to hashtable key */ function->fn_hashkey = &hentry->key; } void plr_HashTableDelete(plr_function *function) { plr_HashEnt *hentry; hentry = (plr_HashEnt*) hash_search(plr_HashTable, (void *) function->fn_hashkey, HASH_REMOVE, NULL); if (hentry == NULL) elog(WARNING, "trying to delete function that does not exist"); } static char * get_lib_pathstr(Oid funcid) { HeapTuple procedureTuple; Form_pg_proc procedureStruct; Oid language; HeapTuple languageTuple; Form_pg_language languageStruct; Oid lang_funcid; Datum tmp; bool isnull; char *raw_path; char *cooked_path; /* get the pg_proc entry */ procedureTuple = SearchSysCache(PROCOID, ObjectIdGetDatum(funcid), 0, 0, 0); if (!HeapTupleIsValid(procedureTuple)) /* internal error */ elog(ERROR, "cache lookup failed for function %u", funcid); procedureStruct = (Form_pg_proc) GETSTRUCT(procedureTuple); /* now get the pg_language entry */ language = procedureStruct->prolang; ReleaseSysCache(procedureTuple); languageTuple = SearchSysCache(LANGOID, ObjectIdGetDatum(language), 0, 0, 0); if (!HeapTupleIsValid(languageTuple)) /* internal error */ elog(ERROR, "cache lookup failed for language %u", language); languageStruct = (Form_pg_language) GETSTRUCT(languageTuple); lang_funcid = languageStruct->lanplcallfoid; ReleaseSysCache(languageTuple); /* finally, get the pg_proc entry for the language handler */ procedureTuple = SearchSysCache(PROCOID, ObjectIdGetDatum(lang_funcid), 0, 0, 0); if (!HeapTupleIsValid(procedureTuple)) /* internal error */ elog(ERROR, "cache lookup failed for function %u", lang_funcid); procedureStruct = (Form_pg_proc) GETSTRUCT(procedureTuple); tmp = SysCacheGetAttr(PROCOID, procedureTuple, Anum_pg_proc_probin, &isnull); raw_path = DatumGetCString(DirectFunctionCall1(byteaout, tmp)); #if PG_VERSION_NUM >= 80500 /* Recognize hex input */ if (raw_path[0] == '\\' && raw_path[1] == 'x') { char *result; int bc; size_t len = strlen(raw_path); bc = (len - 2)/2 + 1; /* maximum possible length */ result = palloc0(bc); bc = hex_decode(raw_path + 2, len - 2, result); cooked_path = expand_dynamic_library_name(result); } else cooked_path = expand_dynamic_library_name(raw_path); #else cooked_path = expand_dynamic_library_name(raw_path); #endif if (!cooked_path) cooked_path = pstrdup(raw_path); ReleaseSysCache(procedureTuple); return cooked_path; } char * get_load_self_ref_cmd(Oid funcid) { char *libstr = get_lib_pathstr(funcid); char *buf = NULL; if (libstr) buf = (char *) palloc(strlen(libstr) + 12 + 1); else ereport(ERROR, (errcode_for_file_access(), errmsg("could not find path to PL/R shared library"))); sprintf(buf, "dyn.load(\"%s\")", libstr); return buf; } void perm_fmgr_info(Oid functionId, FmgrInfo *finfo) { fmgr_info_cxt(functionId, finfo, TopMemoryContext); INIT_AUX_FMGR_ATTS; } static bool file_exists(const char *name) { struct stat st; AssertArg(name != NULL); if (stat(name, &st) == 0) return S_ISDIR(st.st_mode) ? false : true; else if (!(errno == ENOENT || errno == ENOTDIR || errno == EACCES)) ereport(ERROR, (errcode_for_file_access(), errmsg("could not access file \"%s\": %m", name))); return false; } #ifndef DLSUFFIX #error "DLSUFFIX must be defined to compile this file." #endif /* * If name contains a slash, check if the file exists, if so return * the name. Else (no slash) try to expand using search path (see * find_in_dynamic_libpath below); if that works, return the fully * expanded file name. If the previous failed, append DLSUFFIX and * try again. If all fails, return NULL. * * A non-NULL result will always be freshly palloc'd. */ static char * expand_dynamic_library_name(const char *name) { bool have_slash; char *new; char *full; AssertArg(name); have_slash = (strchr(name, '/') != NULL); if (!have_slash) { full = find_in_dynamic_libpath(name); if (full) return full; } else { full = substitute_libpath_macro(name); if (file_exists(full)) return full; pfree(full); } new = palloc(strlen(name) + strlen(DLSUFFIX) + 1); strcpy(new, name); strcat(new, DLSUFFIX); if (!have_slash) { full = find_in_dynamic_libpath(new); pfree(new); if (full) return full; } else { full = substitute_libpath_macro(new); pfree(new); if (file_exists(full)) return full; pfree(full); } return NULL; } /* * Substitute for any macros appearing in the given string. * Result is always freshly palloc'd. */ static char * substitute_libpath_macro(const char *name) { const char *sep_ptr; char *ret; char pkglib_path[MAXPGPATH]; AssertArg(name != NULL); get_pkglib_path(my_exec_path, pkglib_path); if (name[0] != '$') return pstrdup(name); if ((sep_ptr = first_dir_separator(name)) == NULL) sep_ptr = name + strlen(name); if (strlen("$libdir") != sep_ptr - name || strncmp(name, "$libdir", strlen("$libdir")) != 0) ereport(ERROR, (errcode(ERRCODE_INVALID_NAME), errmsg("invalid macro name in dynamic library path: %s", name))); ret = palloc(strlen(pkglib_path) + strlen(sep_ptr) + 1); strcpy(ret, pkglib_path); strcat(ret, sep_ptr); return ret; } /* * Search for a file called 'basename' in the colon-separated search * path Dynamic_library_path. If the file is found, the full file name * is returned in freshly palloc'd memory. If the file is not found, * return NULL. */ static char * find_in_dynamic_libpath(const char *basename) { const char *p; size_t baselen; char *Dynamic_library_path = GetConfigOptionByName("dynamic_library_path", NULL); AssertArg(basename != NULL); AssertArg(strchr(basename, '/') == NULL); AssertState(Dynamic_library_path != NULL); p = Dynamic_library_path; if (strlen(p) == 0) return NULL; baselen = strlen(basename); for (;;) { size_t len; char *piece; char *mangled; char *full; len = strcspn(p, ":"); if (len == 0) ereport(ERROR, (errcode(ERRCODE_INVALID_NAME), errmsg("zero-length component in DYNAMIC_LIBRARY_PATH"))); piece = palloc(len + 1); strncpy(piece, p, len); piece[len] = '\0'; mangled = substitute_libpath_macro(piece); pfree(piece); /* only absolute paths */ if (mangled[0] != '/') ereport(ERROR, (errcode(ERRCODE_INVALID_NAME), errmsg("DYNAMIC_LIBRARY_PATH component is not absolute"))); full = palloc(strlen(mangled) + 1 + baselen + 1); sprintf(full, "%s/%s", mangled, basename); pfree(mangled); elog(DEBUG2, "find_in_dynamic_libpath: trying %s", full); if (file_exists(full)) return full; pfree(full); if (p[len] == '\0') break; else p += len + 1; } return NULL; } plr/README.plr0000775000000000000000000000400212465736645012050 0ustar rootroot/* * PL/R - PostgreSQL support for R as a * procedural language (PL) * * Copyright (c) 2003-2015 by Joseph E. Conway * ALL RIGHTS RESERVED * * Joe Conway * * Based on pltcl by Jan Wieck * and inspired by REmbeddedPostgres by * Duncan Temple Lang * http://www.omegahat.org/RSPostgres/ * * License: GPL version 2 or newer. http://www.gnu.org/copyleft/gpl.html * * This program 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. * * This program 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 this program; if not, write to the Free Software * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA * */ See http://www.joeconway.com/plr/ for release notes and latest docs Notes: - R headers are required. Download and install R prior to building PL/R. - R must have been built with the --enable-R-shlib option when it was configured, in order for the libR shared object library to be available. - R_HOME must be defined in the environment of the user under which PostgreSQL is started, before the postmaster is started. Otherwise PL/R will refuse to load. Installation: See http://www.joeconway.com/plr/doc/plr-install.html for the most up-to-date instructions. Documentation: See the following: See http://www.joeconway.com/plr/doc/ doc/plr.sgml - PL/R documentation source doc/*.html - Preprocessed html version of the documentation ====================================================================== -- Joe Conway plr/doc/0000775000000000000000000000000012467406750011133 5ustar rootrootplr/doc/html/0000755000000000000000000000000012467406712012073 5ustar rootrootplr/doc/html/plr-data.html0000644000000000000000000001711612467406712014473 0ustar rootroot Passing Data Values

Chapter 4. Passing Data Values

The argument values supplied to a PL/R function's script are the input arguments converted to a corresponding R form. See Table 4-1. Scalar PostgreSQL values become single element R vectors. One exception to this are scalar bytea values. These are first converted to R raw type, and then processed by the R unserialize command. One-dimensional PostgreSQL arrays are converted to multi-element R vectors, two-dimensional PostgreSQL arrays are mapped to R matrixes, and three-dimensional PostgreSQL arrays are converted to three-dimensional R arrays. Greater than three-dimensional arrays are not supported. Composite-types are transformed into R data.frames.

Table 4-1. Function Arguments

PostgreSQL typeR type
booleanlogical
int2, int4integer
int8, float4, float8, cash, numericnumeric
byteaobject
everything elsecharacter

Conversely, the return values are first coerced to R character, and therefore anything that resolves to a string that is acceptable input format for the function's declared return type will produce a result. Again, there is an exception for scalar bytea return values. In this case, the R object being returned is first processed by the R serialize command, and then the binary result is directly mapped into a PostgreSQL bytea datum. Similar to argument conversion, there is also a mapping between the dimensionality of the declared PostgreSQL return type and the type of R object. That mapping is shown in Table 4-2

Table 4-2. Function Result Dimensionality

PgSQL return typeR typeResultExample
scalararray, matrix, vectorfirst column of first rowc(1,2,3) in R returns 1 in PostgreSQL
setof scalar1D array, greater than 2D array, vectormulti-row, 1 column setarray(1:10) in R returns 10 rows in PostgreSQL
scalardata.frametextual representation of the first column's vectordata.frame(c(1,2,3)) in R returns 'c(1, 2, 3)'
setof scalar2D array, matrix, data.frame#columns > 1, error; #columns == 1, multi-row, 1 column set(as.data.frame(array(1:10,c(2,5))))[,1] in R returns 2 rows of scalar
array1D array, greater than 3D array, vector1D arrayarray(1:8,c(2,2,2,2)) in R returns {1,2,3,4,5,6,7,8,1,2,3,4,5,6,7,8}
array2D array, matrix, data.frame2D arrayarray(1:4,c(2,2)) in R returns {{1,3},{2,4}}
array3D array3D arrayarray(1:8,c(2,2,2)) in R returns {{{1,5},{3,7}},{{2,6},{4,8}}}
composite1D array, greater than 2D array, vectorfirst row, 1 columnarray(1:8,c(2,2,2)) in R returns 1 row of scalar
setof composite1D array, greater than 2D array, vectormulti-row, 1 column setarray(1:8,c(2,2,2)) in R returns 8 rows of scalar
composite2D array, matrix, data.framefirst row, multi-columnarray(1:4,c(2,2)) in R returns 1 row of 2 columns
setof composite2D array, matrix, data.framemulti-row, multi-column setarray(1:4,c(2,2)) in R returns 2 rows of 2 columns
plr/doc/html/plr-install.html0000644000000000000000000001406412467406712015227 0ustar rootroot Installation

Chapter 2. Installation

Place source tar file in contrib in the PostgreSQL source tree and untar it. The shared object for the R call handler is built and installed in the PostgreSQL library directory via the following commands (starting from /path/to/postgresql_source/contrib):

    cd plr
    make
    make install
   

As of PostgreSQL 8.0.0, PL/R can also be built without the PostgreSQL source tree. Untar PL/R whereever you prefer. The shared object for the R call handler is built and installed in the PostgreSQL library directory via the following commands (starting from /path/to/plr):

    cd plr
    USE_PGXS=1 make
    USE_PGXS=1 make install
   

Win32 - adjust paths according to your own setup, and be sure to restart the PostgreSQL service after changing:

    In Windows environment:
    R_HOME=C:\Progra~1\R\R-2.5.0
    Path=%PATH%;C:\Progra~1\R\R-2.5.0\bin

    In MSYS:
    export R_HOME=/c/progra~1/R/R-2.5.0
    export PATH=$PATH:/c/progra~1/PostgreSQL/8.2/bin
    USE_PGXS=1 make
    USE_PGXS=1 make install
   

You can use plr.sql (which is created in contrib/plr) to create the language and support functions in your database of choice:

    psql mydatabase < plr.sql
   

Alternatively you can create the language manually using SQL commands:

CREATE FUNCTION plr_call_handler()
RETURNS LANGUAGE_HANDLER
AS '$libdir/plr' LANGUAGE C;

CREATE LANGUAGE plr HANDLER plr_call_handler;
   

As of PostgreSQL 9.1 you can use the new CREATE EXTENSION command:

    CREATE EXTENSION plr;
   

This is not only simple, it has the added advantage of tracking all PL/R installed objects as dependent on the extension, and therefore they can be removed just as easily if desired:

    DROP EXTENSION plr;
   

Tip: If a language is installed into template1, all subsequently created databases will have the language installed automatically.

Tip: In addition to the documentation, the plr.out.* files in plr/expected are a good source of usage examples.

Tip: R headers are required. Download and install R prior to building PL/R. R must have been built with the --enable-R-shlib option when it was configured, in order for the libR shared object library to be available.

Tip: Additionally, libR must be findable by your runtime linker. On Linux, this involves adding an entry in /etc/ld.so.conf for the location of libR (typically $R_HOME/bin or $R_HOME/lib), and then running ldconfig. Refer to man ldconfig or its equivalent for your system.

Tip: R_HOME must be defined in the environment of the user under which PostgreSQL is started, before the postmaster is started. Otherwise PL/R will refuse to load. See plr_environ(), which allows examination of the environment available to the PostgreSQL postmaster process.

plr/doc/html/plr-overview.html0000644000000000000000000000703512467406712015427 0ustar rootroot Overview

Chapter 1. Overview

PL/R is a loadable procedural language that enables you to write PostgreSQL functions and triggers in the R programming language. PL/R offers most (if not all) of the capabilities a function writer has in the R language.

Commands are available to access the database via the PostgreSQL Server Programming Interface (SPI) and to raise messages via elog() . There is no way to access internals of the database backend. However the user is able to gain OS-level access under the permissions of the PostgreSQL user ID, as with a C function. Thus, any unprivileged database user should not be permitted to use this language. It must be installed as an untrusted procedural language so that only database superusers can create functions in it. The writer of a PL/R function must take care that the function cannot be used to do anything unwanted, since it will be able to do anything that could be done by a user logged in as the database administrator.

An implementation restriction is that PL/R procedures cannot be used to create input/output functions for new data types.

plr/doc/html/plr-window-funcs.html0000644000000000000000000001466512467406712016213 0ustar rootroot Window Functions

Chapter 9. Window Functions

Starting with version 8.4, PostgreSQL supports WINDOW functions which provide the ability to perform calculations across sets of rows that are related to the current query row. This is comparable to the type of calculation that can be done with an aggregate function. But unlike regular aggregate functions, use of a window function does not cause rows to become grouped into a single output row; the rows retain their separate identities. Behind the scenes, the window function is able to access more than just the current row of the query result. See the PostgreSQL documentation for more general information related to the use of this capability.

PL/R functions may be defined as WINDOW. For example:

CREATE OR REPLACE
FUNCTION r_regr_slope(float8, float8)
RETURNS float8 AS
$BODY$
  slope <- NA
  y <- farg1
  x <- farg2 
  if (fnumrows==9) try (slope <- lm(y ~ x)$coefficients[2])
  return(slope)
$BODY$
LANGUAGE plr WINDOW;
     

A number of variables are automatically provided by PL/R to the R interpreter:

fargN

farg1 and farg2 are R vectors containing the current row's data plus that of the related rows.

fnumrows

The number of rows in the current WINDOW frame.

prownum (not shown)

Provides the 1-based row offset of the current row in the current PARTITION.

A more complete example follows:

-- create test table
CREATE TABLE test_data (
  fyear integer,
  firm float8,
  eps float8
);

-- insert randomly pertubated data for test
INSERT INTO test_data
SELECT (b.f + 1) % 10 + 2000 AS fyear,
	floor((b.f+1)/10) + 50 AS firm,
       f::float8/100 + random()/10 AS eps
FROM generate_series(-500,499,1) b(f);

CREATE OR REPLACE
FUNCTION r_regr_slope(float8, float8)
RETURNS float8 AS
$BODY$
  slope <- NA
  y <- farg1
  x <- farg2 
  if (fnumrows==9) try (slope <- lm(y ~ x)$coefficients[2])
  return(slope)
$BODY$
LANGUAGE plr WINDOW;

SELECT *, r_regr_slope(eps, lag_eps) OVER w AS slope_R
FROM (SELECT firm, fyear, eps,
  lag(eps) OVER (ORDER BY firm, fyear) AS lag_eps
FROM test_data) AS a
WHERE eps IS NOT NULL
WINDOW w AS (ORDER BY firm, fyear ROWS 8 PRECEDING);
     

In this example, the variables farg1 and farg2 contain the current row value for eps and lag_eps, as well as the preceding 8 rows which are also in the same WINDOW frame within the same PARTITION. In this case since no PARTITION is explicitly defined, the PARTITION is the entire set of rows returned from the inner sub-select.

Another interesting example follows. The idea of "Winsorizing" is to return either the original value or, if that value is outside certain bounds, a trimmed value. So for example winsor(eps, 0.1) would return the value at the 10th percentile for values of eps less that that, the value of the 90th percentile for eps greater than that value, and the unmodified value of eps otherwise.

CREATE OR REPLACE FUNCTION winsorize(float8, float8)
RETURNS float8 AS
$BODY$
  library(psych)
  return(winsor(as.vector(farg1), arg2)[prownum])
$BODY$ LANGUAGE plr VOLATILE WINDOW;

SELECT fyear, eps, 
  winsorize(eps, 0.1) OVER (PARTITION BY fyear) AS w_eps
FROM test_data ORDER BY fyear, eps;
     

In this example, use of the variable prownum is illustrated.

plr/doc/html/plr-global-data.html0000644000000000000000000001427512467406712015734 0ustar rootroot Using Global Data

Chapter 5. Using Global Data

Sometimes it is useful to have some global status data that is held between two calls to a procedure or is shared between different procedures. Equally useful is the ability to create functions that your PL/R functions can share. This is easily done since all PL/R procedures executed in one backend share the same R interpreter. So, any global R variable is accessible to all PL/R procedure calls, and will persist for the duration of the SQL client connection. An example of using a global object appears in the pg.spi.execp example, in Chapter 6.

A globally available, user named, R function (the R function name of PL/R functions is not the same as its PostgreSQL function name; see: Chapter 11) can be created dynamically using the provided PostgreSQL function install_rcmd(text). Here is an example:

select install_rcmd('pg.test.install <-function(msg) {print(msg)}');
 install_rcmd 
--------------
 OK
(1 row)

create or replace function pg_test_install(text) returns text as '
  pg.test.install(arg1)
' language 'plr';

select pg_test_install('hello world');
 pg_test_install 
-----------------
 hello world
(1 row)
    

A globally available, user named, R function can also be automatically created and installed in the R interpreter. See: Chapter 10

PL/R also provides a global variable called pg.state.firstpass. This variable is reset to TRUE the first time each PL/R function is called, for a particular query. On subsequent calls the value is left unchanged. This allows one or more PL/R functions to perform a possibly expensive initialization on the first call, and reuse the results for the remaining rows in the query. For example:

create table t (f1 int);
insert into t values (1);
insert into t values (2);
insert into t values (3);

create or replace function f1() returns int as '
  msg <- paste("enter f1, pg.state.firstpass is", pg.state.firstpass)
  pg.thrownotice(msg)
  if (pg.state.firstpass == TRUE)
    pg.state.firstpass <<- FALSE
  msg <- paste("exit f1, pg.state.firstpass is", pg.state.firstpass)
  pg.thrownotice(msg)
  return(0)
' language plr;

create or replace function f2() returns int as '
  msg <- paste("enter f2, pg.state.firstpass is", pg.state.firstpass)
  pg.thrownotice(msg)
  if (pg.state.firstpass == TRUE)
    pg.state.firstpass <<- FALSE
  msg <- paste("exit f2, pg.state.firstpass is", pg.state.firstpass)
  pg.thrownotice(msg)
  return(0)
' language plr;

select f1(), f2(), f1 from t;
NOTICE:  enter f1, pg.state.firstpass is TRUE
NOTICE:  exit f1, pg.state.firstpass is FALSE
NOTICE:  enter f2, pg.state.firstpass is TRUE
NOTICE:  exit f2, pg.state.firstpass is FALSE
NOTICE:  enter f1, pg.state.firstpass is FALSE
NOTICE:  exit f1, pg.state.firstpass is FALSE
NOTICE:  enter f2, pg.state.firstpass is FALSE
NOTICE:  exit f2, pg.state.firstpass is FALSE
NOTICE:  enter f1, pg.state.firstpass is FALSE
NOTICE:  exit f1, pg.state.firstpass is FALSE
NOTICE:  enter f2, pg.state.firstpass is FALSE
NOTICE:  exit f2, pg.state.firstpass is FALSE
 f1 | f2 | f1
----+----+----
  0 |  0 |  1
  0 |  0 |  2
  0 |  0 |  3
(3 rows)

create or replace function row_number() returns int as '
  if (pg.state.firstpass)
  {
    assign("pg.state.firstpass", FALSE, env=.GlobalEnv)
    lclcntr <- 1
  }
  else
    lclcntr <- plrcounter + 1
  assign("plrcounter", lclcntr, env=.GlobalEnv)
  return(lclcntr)
' language 'plr';

SELECT row_number(), f1 from t;
 row_number | f1
------------+----
          1 |  1
          2 |  2
          3 |  3
(3 rows)
    

plr/doc/html/plr-func-naming.html0000644000000000000000000000625412467406712015765 0ustar rootroot R Function Names

Chapter 11. R Function Names

In PostgreSQL, one and the same function name can be used for different functions as long as the number of arguments or their types differ. R, however, requires all function names to be distinct. PL/R deals with this by constructing the internal R function names as a concatenation of the string "PLR" with the object ID of the procedure's pg_proc. Thus, PostgreSQL functions with the same name and different argument types will be different R functions too. This is not normally a concern for a PL/R programmer, but it might be visible when debugging.

If a specific, known, function name is needed so that an R function can be referenced by one or more PL/R functions, the install_rcmd(text) command can be used. See Chapter 5.

plr/doc/html/plr-spi-rsupport-funcs-normal.html0000644000000000000000000003652012467406712020653 0ustar rootroot Normal Support

6.1. Normal Support

pg.spi.exec (character query)

Execute an SQL query given as a string. An error in the query causes an error to be raised. Otherwise, the command's return value is the number of rows processed for INSERT, UPDATE, or DELETE statements, or zero if the query is a utility statement. If the query is a SELECT statement, the values of the selected columns are placed in an R data.frame with the target column names used as the frame column names. However, non-numeric columns are not converted to factors. If you want all non-numeric columns converted to factors, a convenience function pg.spi.factor (described below) is provided.

If a field of a SELECT result is NULL, the target variable for it is set to "NA". For example:

create or replace function test_spi_tup(text) returns setof record as '
  pg.spi.exec(arg1)
' language 'plr';

select * from test_spi_tup('select oid, NULL::text as nullcol,
  typname from pg_type where typname = ''oid'' or typname = ''text''')
  as t(typeid oid, nullcol text, typename name);
 typeid | nullcol | typename
--------+---------+----------
     25 |         | text
     26 |         | oid
(2 rows)
        

The NULL values were passed to R as "NA", and on return to PostgreSQL they were converted back to NULL.

pg.spi.prepare (character query, integer vector type_vector)

Prepares and saves a query plan for later execution. The saved plan will be retained for the life of the current backend.

The query may use arguments, which are placeholders for values to be supplied whenever the plan is actually executed. In the query string, refer to arguments by the symbols $1 ... $n. If the query uses arguments, the values of the argument types must be given as a vector. Pass NA for type_vector if the query has no arguments. The argument types must be identified by the type Oids, shown in pg_type. Global variables are provided for this use. They are named according to the convention TYPENAMEOID, where the actual name of the type, in all capitals, is substituted for TYPENAME. A support function, load_r_typenames() must be used to make the predefined global variables available for use:

select load_r_typenames();
 load_r_typenames
------------------
 OK
(1 row)
        

Another support function, r_typenames() may be used to list the predefined Global variables:

select * from r_typenames();
    typename     | typeoid
-----------------+---------
 ABSTIMEOID      |     702
 ACLITEMOID      |    1033
 ANYARRAYOID     |    2277
 ANYOID          |    2276
 BITOID          |    1560
 BOOLOID         |      16
  [...]
 TRIGGEROID      |    2279
 UNKNOWNOID      |     705
 VARBITOID       |    1562
 VARCHAROID      |    1043
 VOIDOID         |    2278
 XIDOID          |      28
(59 rows)
        

The return value from pg.spi.prepare is a query ID to be used in subsequent calls to pg.spi.execp. See spi_execp for an example.

pg.spi.execp (external pointer saved_plan, variable listvalue_list)

Execute a query previously prepared with pg.spi.prepare . saved_plan is the external pointer returned by pg.spi.prepare. If the query references arguments, a value_list must be supplied: this is an R list of actual values for the plan arguments. It must be the same length as the argument type_vector previously given to pg.spi.prepare. Pass NA for value_list if the query has no arguments. The following illustrates the use of pg.spi.prepare and pg.spi.execp with and without query arguments:

create or replace function test_spi_prep(text) returns text as '
  sp <<- pg.spi.prepare(arg1, c(NAMEOID, NAMEOID));
  print("OK")
' language 'plr';

select test_spi_prep('select oid, typname from pg_type 
  where typname = $1 or typname = $2');
 test_spi_prep 
---------------
 OK
(1 row)

create or replace function test_spi_execp(text, text, text) returns setof record as '
  pg.spi.execp(pg.reval(arg1), list(arg2,arg3))
' language 'plr';

select * from test_spi_execp('sp','oid','text') as t(typeid oid, typename name);
 typeid | typename 
--------+----------
     25 | text
     26 | oid
(2 rows)

create or replace function test_spi_prep(text) returns text as '
  sp <<- pg.spi.prepare(arg1, NA);
  print("OK")
' language 'plr';

select test_spi_prep('select oid, typname from pg_type
  where typname = ''bytea'' or typname = ''text''');
 test_spi_prep
---------------
 OK
(1 row)

create or replace function test_spi_execp(text) returns setof record as '
  pg.spi.execp(pg.reval(arg1), NA)
' language 'plr';

select * from test_spi_execp('sp') as t(typeid oid, typename name);
 typeid | typename
--------+----------
     17 | bytea
     25 | text
(2 rows)

create or replace function test_spi_prep(text) returns text as '
  sp <<- pg.spi.prepare(arg1);
  print("OK")
' language 'plr';

select test_spi_prep('select oid, typname from pg_type
  where typname = ''bytea'' or typname = ''text''');
 test_spi_prep
---------------
 OK
(1 row)

create or replace function test_spi_execp(text) returns setof record as '
  pg.spi.execp(pg.reval(arg1))
' language 'plr';

select * from test_spi_execp('sp') as t(typeid oid, typename name);
 typeid | typename
--------+----------
     17 | bytea
     25 | text
(2 rows)
        

NULL arguments should be passed as individual NA values in value_list.

Except for the way in which the query and its arguments are specified, pg.spi.execp works just like pg.spi.exec.

pg.spi.cursor_open( character cursor_name, external pointer saved_plan, variable list value_list)

Opens a cursor identified by cursor_name. The cursor can then be used to scroll through the results of a query plan previously prepared by pg.spi.prepare. Any arguments to the plan should be specified in argvalues similar to pg.spi.execp. Only read-only cursors are supported at the moment.

plan <- pg.spi.prepare('SELECT * FROM pg_class');
cursor_obj <- pg.spi.cursor_open('my_cursor',plan);
        

Returns a cursor object that be be passed to pg.spi.cursor_fetch

pg.spi.cursor_fetch( external pointer cursor, boolean forward, integer rows)

Fetches rows from the cursor object previosuly returned by pg.spi.cursor_open . If forward is TRUE then the cursor is moved forward to fetch at most the number of rows required by the rows parameter. If forward is FALSE then the cursor is moved backrwards at most the number of rows specified.

rows indicates the maximum number of rows that should be returned.

plan <- pg.spi.prepare('SELECT * FROM pg_class');
cursor_obj <- pg.spi.cursor_open('my_cursor',plan);
data <- pg.spi.cursor_fetch(cursor_obj,TRUE,as.integer(10));
        

Returns a data frame containing the results.

pg.spi.cursor_close( external pointercursor)

Closes a cursor previously opened by pg.spi.cursor_open

plan <- pg.spi.prepare('SELECT * FROM pg_class');
cursor_obj <- pg.spi.cursor_open('my_cursor',plan);
pg.spi.cursor_close(cursor_obj);
        

pg.spi.lastoid()

Returns the OID of the row inserted by the last query executed via pg.spi.exec or pg.spi.execp, if that query was a single-row INSERT. (If not, you get zero.)

pg.quoteliteral (character SQL_string)

Duplicates all occurrences of single quote and backslash characters in the given string. This may be used to safely quote strings that are to be inserted into SQL queries given to pg.spi.exec or pg.spi.prepare.

pg.quoteident (character SQL_string)

Return the given string suitably quoted to be used as an identifier in an SQL query string. Quotes are added only if necessary (i.e., if the string contains non-identifier characters or would be case-folded). Embedded quotes are properly doubled. This may be used to safely quote strings that are to be inserted into SQL queries given to pg.spi.exec or pg.spi.prepare.

pg.thrownotice (character message)
pg.throwerror (character message)

Emit a PostgreSQL NOTICE or ERROR message. ERROR also raises an error condition: further execution of the function is abandoned, and the current transaction is aborted.

pg.spi.factor (data.frame data)

Accepts an R data.frame as input, and converts all non-numeric columns to factors. This may be useful for data.frames produced by pg.spi.exec or pg.spi.prepare, because the PL/R conversion mechanism does not do that for you.

plr/doc/html/index.html0000644000000000000000000000504612467406712014075 0ustar rootroot PL/R User's Guide - R Procedural Languageplr/doc/html/plr-pgsql-support-funcs.html0000644000000000000000000002116312467406712017533 0ustar rootroot PostgreSQL Support Functions

Chapter 7. PostgreSQL Support Functions

The following commands are available to use in PostgreSQL queries to aid in the use of PL/R functions:

plr_version()

Displays PL/R version as a text string.

install_rcmd (text R_code)

Install R code, given as a string, into the interpreter. See Chapter 5 for an example.

reload_plr_modules ()

Force re-loading of R code from the plr_modules table. It is useful after modifying the contents of plr_modules, so that the change will have an immediate effect.

plr_singleton_array (float8 first_element)

Creates a new PostgreSQL array, using element first_element. This function is predefined to accept one float8 value and return a float8 array. The C function that implements this PostgreSQL function is capable of accepting and returning other data types, although the return type must be an array of the input parameter type. It can also accept multiple input parameters. For example, to define a plr_array function to create a text array from two input text values:

CREATE OR REPLACE FUNCTION plr_array (text, text)
RETURNS text[]
AS '$libdir/plr','plr_array'
LANGUAGE 'C' WITH (isstrict);

select plr_array('hello','world');
   plr_array
---------------
 {hello,world}
(1 row)
     

plr_array_push (float8[] array, float8 next_element)

Pushes a new element onto the end of an existing PostgreSQL array. This function is predefined to accept one float8 array and a float8 value, and return a float8 array. The C function that implements this PostgreSQL function is capable of accepting and returning other data types. For example, to define a plr_array_push function to add a text value to an existing text array:

CREATE OR REPLACE FUNCTION plr_array_push (_text, text)
RETURNS text[]
AS '$libdir/plr','plr_array_push'
LANGUAGE 'C' WITH (isstrict);

select plr_array_push(plr_array('hello','world'), 'how are you');
       plr_array_push
-----------------------------
 {hello,world,"how are you"}
(1 row)
     

plr_array_accum (float8[] state_value, float8 next_element)

Creates a new array using next_element if state_value is NULL. Otherwise, pushes next_element onto the end of state_value. This function is predefined to accept one float8 array and a float8 value, and return a float8 array. The C function that implements this PostgreSQL function is capable of accepting and returning other data types. For example, to define a plr_array_accum function to add an int4 value to an existing int4 array:

CREATE OR REPLACE FUNCTION plr_array_accum (_int4, int4)
RETURNS int4[]
AS '$libdir/plr','plr_array_accum'
LANGUAGE 'C';

select plr_array_accum(NULL, 42);
 plr_array_accum
-------------
 {42}
(1 row)
select plr_array_accum('{23,35}', 42);
 plr_array_accum
-----------------
 {23,35,42}
(1 row)
        

This function may be useful for creating custom aggregates. See Chapter 8 for an example.

load_r_typenames()

Installs datatype Oid variables into the R interpreter as globals. See also r_typenames below.

r_typenames()

Displays the datatype Oid variables installed into the R interpreter as globals. See Chapter 6 for an example.

plr_environ()

Displays the environment under which the Postmaster is currently running. This may be useful to debug issues related to R specific environment variables. This function is installed with EXECUTE permission revoked from PUBLIC.

plr_set_display(text display)

Sets the DISPLAY environment vaiable under which the Postmaster is currently running. This may be useful if using R to plot to a virtual frame buffer. This function is installed with EXECUTE permission revoked from PUBLIC.

plr_get_raw(bytea serialized_object)

By default, when R objects are returned as type bytea, the R object is serialized using an internal R function prior to sending to PostgreSQL. This function unserializes the R object using another internal R function, and returns the pure raw bytes to PostgreSQL. This is useful, for example, if the R object being returned is a JPEG or PNG graphic for use outside of R.

plr/doc/html/plr-aggregate-funcs.html0000644000000000000000000000761012467406712016622 0ustar rootroot Aggregate Functions

Chapter 8. Aggregate Functions

Aggregates in PostgreSQL are extensible via SQL commands. In general, to create a new aggregate, a state transition function and possibly a final function are specified. The final function is used in case the desired output of the aggregate is different from the data that needs to be kept in the running state value.

There is more than one way to create a new aggregate using PL/R. A simple aggregate can be defined using the predefined PostgreSQL C function, plr_array_accum (see Chapter 7) as a state transition function, and a PL/R function as a finalizer. For example:

create or replace function r_median(_float8) returns float as '
  median(arg1)
' language 'plr';

CREATE AGGREGATE median (
  sfunc = plr_array_accum,
  basetype = float8,
  stype = _float8,
  finalfunc = r_median
);

create table foo(f0 int, f1 text, f2 float8);
insert into foo values(1,'cat1',1.21);
insert into foo values(2,'cat1',1.24);
insert into foo values(3,'cat1',1.18);
insert into foo values(4,'cat1',1.26);
insert into foo values(5,'cat1',1.15);
insert into foo values(6,'cat2',1.15);
insert into foo values(7,'cat2',1.26);
insert into foo values(8,'cat2',1.32);
insert into foo values(9,'cat2',1.30);

select f1, median(f2) from foo group by f1 order by f1;
  f1  | median 
------+--------
 cat1 |   1.21
 cat2 |   1.28
(2 rows)
     

A more complex aggregate might be created by using a PL/R functions for both state transition and finalizer.

plr/doc/html/plr-spi-rsupport-funcs.html0000644000000000000000000000525112467406712017362 0ustar rootroot Database Access and Support Functions

Chapter 6. Database Access and Support Functions

The following commands are available to access the database from the body of a PL/R procedure, or in support thereof:

plr/doc/html/plr-funcs.html0000644000000000000000000002232012467406712014671 0ustar rootroot Functions and Arguments

Chapter 3. Functions and Arguments

To create a function in the PL/R language, use standard R syntax, but without the enclosing braces or function assignment. Instead of myfunc <- function(arguments) { function body }, the body of your PL/R function is just function body

CREATE OR REPLACE FUNCTION funcname (argument-types)
RETURNS return-type AS '
    function body
' LANGUAGE 'plr';
    

The body of the function is simply a piece of R script. When the function is called, the argument values are passed as variables arg1 ... argN to the R script. The result is returned from the R code in the usual way. For example, a function returning the greater of two integer values could be defined as:

CREATE OR REPLACE FUNCTION r_max (integer, integer) RETURNS integer AS '
    if (arg1 > arg2)
       return(arg1)
    else
       return(arg2)
' LANGUAGE 'plr' STRICT;
    

Starting with PostgreSQL 8.0, arguments may be explicitly named when creating a function. If an argument is explicitly named at function creation time, that name will be available to your R script in place of the usual argN variable. For example:

CREATE OR REPLACE FUNCTION sd(vals float8[]) RETURNS float AS '
    sd(vals)
' LANGUAGE 'plr' STRICT;
    

Starting with PostgreSQL 8.4, a PL/R function may be declared to be a WINDOW. In this case, in addition to the usual argN (or named) variables, PL/R automatically creates several other arguments to your function. For each explicit argument, a corresponding variable called farg1 ... fargN is passed to the R script. These contain an R vector of all the values of the related argument for the moving WINDOW frame within the current PARTITION. For example:

CREATE OR REPLACE
FUNCTION r_regr_slope(float8, float8)
RETURNS float8 AS
$BODY$
  slope <- NA
  y <- farg1
  x <- farg2 
  if (fnumrows==9) try (slope <- lm(y ~ x)$coefficients[2])
  return(slope)
$BODY$
LANGUAGE plr WINDOW;
    

In the preceding example, farg1 and farg2 are R vectors containing the current row's data plus that of related rows. The determination as to which rows qualify as related is determined by the frame specification of the query at run time.

The example also illustrates one of two additional autogenerated arguments. fnumrows is the number of rows in the current WINDOW frame. The other (not shown) auto-argument is called prownum. This argument provides the 1-based row offset of the current row in the current PARTITION. See Chapter 9 for more information and a more complete example.

In some of the the definitions above, note the clause STRICT, which saves us from having to think about NULL input values: if a NULL is passed, the function will not be called at all, but will just return a NULL result automatically. In a non-strict function, if the actual value of an argument is NULL, the corresponding argN variable will be set to a NULL R object. For example, suppose that we wanted r_max with one null and one non-null argument to return the non-null argument, rather than NULL:

CREATE OR REPLACE FUNCTION r_max (integer, integer) RETURNS integer AS '
    if (is.null(arg1) && is.null(arg2))
        return(NULL)
    if (is.null(arg1))
        return(arg2)
    if (is.null(arg2))
        return(arg1)
    if (arg1 > arg2)
       return(arg1)
    arg2
' LANGUAGE 'plr';
    

As shown above, to return a NULL value from a PL/R function, return NULL. This can be done whether the function is strict or not.

Composite-type (tuple) arguments are passed to the procedure as R data.frames. The element names of the frame are the attribute names of the composite type. If an attribute in the passed row has the NULL value, it will appear as an "NA" in the frame. Here is an example:

CREATE TABLE emp (name text, age int, salary numeric(10,2));
INSERT INTO emp VALUES ('Joe', 41, 250000.00);
INSERT INTO emp VALUES ('Jim', 25, 120000.00);
INSERT INTO emp VALUES ('Jon', 35, 50000.00);
CREATE OR REPLACE FUNCTION overpaid (emp) RETURNS bool AS '
    if (200000 < arg1$salary) {
        return(TRUE)
    }
    if (arg1$age < 30 && 100000 < arg1$salary) {
        return(TRUE)
    }
    return(FALSE)
' LANGUAGE 'plr';
SELECT name, overpaid(emp) FROM emp;
 name | overpaid
------+----------
 Joe  | t
 Jim  | t
 Jon  | f
(3 rows)

    

There is also support for returning a composite-type result value:

CREATE OR REPLACE FUNCTION get_emps() RETURNS SETOF emp AS '
    names <- c("Joe","Jim","Jon")
    ages <- c(41,25,35)
    salaries <- c(250000,120000,50000)
    df <- data.frame(name = names, age = ages, salary = salaries)
    return(df)
' LANGUAGE 'plr';
select * from get_emps();
 name | age |  salary
------+-----+-----------
 Jim  |  41 | 250000.00
 Joe  |  25 | 120000.00
 Jon  |  35 |  50000.00
(3 rows)

    

An alternative method may be used to create a function in PL/R, if certain criteria are met. First, the function must be a simple call to an existing R function. Second, the function name used for the PL/R function must match that of the R function exactly. If these two criteria are met, the PL/R function may be defined with no body, and the arguments will be passed directly to the R function of the same name. For example:

create or replace function sd(_float8) returns float as '' language 'plr';
select round(sd('{1.23,1.31,1.42,1.27}'::_float8)::numeric,8);
   round    
------------
 0.08180261
(1 row)
    

Tip: Because the function body is passed as an SQL string literal to CREATE FUNCTION, you have to escape single quotes and backslashes within your R source, typically by doubling them.

plr/doc/html/plr-module-funcs.html0000644000000000000000000000763112467406712016164 0ustar rootroot Loading R Modules at Startup

Chapter 10. Loading R Modules at Startup

PL/R has support for auto-loading R code during interpreter initialization. It uses a special table, plr_modules, which is presumed to contain modules of R code. If this table exists, the modules defined are fetched from the table and loaded into the R interpreter immediately after creation.

The definition of the table plr_modules is as follows:

CREATE TABLE plr_modules (
  modseq int4,
  modsrc text
);
     

The field modseq is used to control the order of installation. The field modsrc contains the full text of the R code to be executed, including assignment if that is desired. Consider, for example, the following statement:

INSERT INTO plr_modules
  VALUES (0, 'pg.test.module.load <-function(msg) {print(msg)}');
     

This statement will cause an R function named pg.test.module.load to be created in the R interpreter on initialization. A PL/R function may now simply reference the function directly as follows:

create or replace function pg_test_module_load(text) returns text as '
  pg.test.module.load(arg1)
' language 'plr';

select pg_test_module_load('hello world');
 pg_test_module_load 
---------------------
 hello world
(1 row)
     

The table plr_modules must be readable by all, but it is wise to make it owned and writable only by the database administrator.

plr/doc/html/plr-spi-rsupport-funcs-compat.html0000644000000000000000000001270712467406712020647 0ustar rootroot RPostgreSQL Compatibility Support

6.2. RPostgreSQL Compatibility Support

The following functions are intended to provide some level of compatibility between PL/R and RPostgreSQL (PostgreSQL DBI package). This allows, for example, a function to be first prototyped using an R client, and then easily moved to PL/R for production use.

dbDriver (character dvr_name)
dbConnect (DBIDriver drv, character user, character password, character host, character dbname, character port, character tty, character options)
dbSendQuery (DBIConnection conn, character sql)
fetch (DBIResult rs, integer num_rows)
dbClearResult (DBIResult rs)
dbGetQuery (DBIConnection conn, character sql)
dbReadTable (DBIConnection conn, character name)
dbDisconnect (DBIConnection conn)
dbUnloadDriver (DBIDriver drv)

These functions nominally work like their RPostgreSQL counterparts except that all queries are performed in the current database. Therefore all driver and connection related parameters are ignored, and dbDriver, dbConnect, dbDisconnect, and dbUnloadDriver are no-ops.

plr/doc/html/plr-trigger-func.html0000644000000000000000000001555412467406712016162 0ustar rootroot Trigger Procedures

Chapter 12. Trigger Procedures

Trigger procedures can be written in PL/R. PostgreSQL requires that a procedure that is to be called as a trigger must be declared as a function with no arguments and a return type of trigger.

The information from the trigger manager is passed to the procedure body in the following variables:

pg.tg.name

The name of the trigger from the CREATE TRIGGER statement.

pg.tg.relid

The object ID of the table that caused the trigger procedure to be invoked.

pg.tg.relname

The name of the table that caused the trigger procedure to be invoked.

pg.tg.when

The string BEFORE or AFTER depending on the type of trigger call.

pg.tg.level

The string ROW or STATEMENT depending on the type of trigger call.

pg.tg.op

The string INSERT, UPDATE, or DELETE depending on the type of trigger call.

pg.tg.new

When the trigger is defined FOR EACH ROW, a data.frame containing the values of the new table row for INSERT or UPDATE actions. For triggers defined FOR EACH STATEMENT and for DELETE actions, set to NULL. The atribute names are the table's column names. Columns that are null will be represented as NA.

pg.tg.old

When the trigger is defined FOR EACH ROW, a data.frame containing the values of the old table row for DELETE or UPDATE actions. For triggers defined FOR EACH STATEMENT and for INSERT actions, set to NULL. The atribute names are the table's column names. Columns that are null will be represented as NA.

pg.tg.args

A vector of the arguments to the procedure as given in the CREATE TRIGGER statement.

The return value from a trigger procedure can be NULL or a one row data.frame matching the number and type of columns in the trigger table. NULL tells the trigger manager to silently suppress the operation for this row. If a one row data.frame is returned, it tells PL/R to return a possibly modified row to the trigger manager that will be inserted instead of the one given in pg.tg.new. This works for INSERT and UPDATE only. Needless to say that all this is only meaningful when the trigger is BEFORE and FOR EACH ROW; otherwise the return value is ignored.

Here's a little example trigger procedure that forces an integer value in a table to keep track of the number of updates that are performed on the row. For new rows inserted, the value is initialized to 0 and then incremented on every update operation.

CREATE FUNCTION trigfunc_modcount() RETURNS trigger AS '

    if (pg.tg.op == "INSERT")
    {
      retval <- pg.tg.new
      retval[pg.tg.args[1]] <- 0
    }
    if (pg.tg.op == "UPDATE")
    {
      retval <- pg.tg.new
      retval[pg.tg.args[1]] <- pg.tg.old[pg.tg.args[1]] + 1
    }
    if (pg.tg.op == "DELETE")
      retval <- pg.tg.old

    return(retval)
' LANGUAGE plr;

CREATE TABLE mytab (num integer, description text, modcnt integer);

CREATE TRIGGER trig_mytab_modcount BEFORE INSERT OR UPDATE ON mytab
    FOR EACH ROW EXECUTE PROCEDURE trigfunc_modcount('modcnt');

Notice that the trigger procedure itself does not know the column name; that's supplied from the trigger arguments. This lets the trigger procedure be reused with different tables.

plr/doc/html/plr-license.html0000644000000000000000000000550712467406712015205 0ustar rootroot License

Chapter 13. License

License: GPL version 2 or newer. http://www.gnu.org/copyleft/gpl.html

This program 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.

This program 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 this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA

plr/doc/pg_doc0000775000000000000000000000051112465736645012320 0ustar rootroot#!/bin/bash jade -c ${DOCBOOKSTYLE}/catalog -d ${PGSRCROOT}/doc/src/sgml/stylesheet.dsl -i output-html -t sgml $1 openjade -D . -c ${DOCBOOKSTYLE}/catalog -d ${PGSRCROOT}/doc/src/sgml/stylesheet.dsl -t tex -V tex-backend -i output-print -V texpdf-output -V '%paper-type%'=USletter -o plr-US.tex-pdf $1 pdfjadetex plr-US.tex-pdfplr/doc/stylesheet.css0000775000000000000000000000253712465736645014057 0ustar rootrootBODY { color: #000000; background: #FFFFFF; } A { font-weight: normal; color: #020169; text-decoration: none; } A:link { color: #000066; } A:visited { color: #000099; } A:active { color: #FF0000; } A:hover { color: red; } BODY.BOOK H1.TITLE, BODY.SET H1.TITLE { text-align: center; font-size: 150%; font-family: helvetica,arial,sans-serif; color: #020167; } H3.CORPAUTHOR, H3.CORPAUTHOR { text-align: center; font-style: italic; font-weight: normal; } .COPYRIGHT, .COPYRIGHT { text-align: center; } DIV.EXAMPLE { padding-left: 15px; border-style: solid; border-width: 0px; border-left-width: 2px; border-color: black; margin: 0.5ex; } .SCREEN, .SYNOPSIS, .PROGRAMLISTING { margin-left: 4ex; } .NAVHEADER TH { font-style: italic; } .COMMENT { color: red; } VAR { font-family: monospace; font-style: inherit; } /* Konqueror's standard style for ACRONYM is italic. */ ACRONYM { font-style: inherit; } LI { font-family: helvetica,arial,sans-serif; } BIG { text-decoration: none; font-family: helvetica,arial,sans-serif; font-weight: bold; font-size: 14px; } SMALL { text-decoration: none; font-family: helvetica,arial,sans-serif; font-weight: normal; font-size: 10px; } ol, ul, p, body, td, tr, th, form, span, div { font-family: helvetica,arial,sans-serif; font-size: 12px; } h1, h2, h3, h4, h5, h6 { font-family: helvetica,arial,sans-serif; } plr/doc/plr-US.pdf0000644000000000000000000050707712467406713012765 0ustar rootroot%PDF-1.5 %ÐÔÅØ 73 0 obj << /Length 146 /Filter /FlateDecode >> stream xÚ=Ž1 Â0„÷þŠ·™ I_^mž]-H‡"q‡ÐÆ ˆBKþ¿•T—ûîà8!B[àʽ+Ê#Õ@[Í ¸;lt]5ÀˆšˆÀp}Wž¥"މ˦´(æœÛôC¶*c-ö“$ï!ŒiòOys'0•ÕÌTEË4çéοbòÒ ˆR-¾Õÿ½®øRÔ*ß endstream endobj 81 0 obj << /Length 189 /Filter /FlateDecode >> stream xÚMO= Â0Ýû+n3Ò^Rû‘Õ¢‚t‰“:« ¤é¿·åT\ÞÇñî‡ÐÂ:À/L­T:Ô©JÁ\ “aKÈ0ãùL ¶-£*ËÙ¾³~ÆSdùu«-IAô n=WÈÜÙÖ½¯î4+«¶é+.‘5\ŒhùÉlÆzýW ¤ u¢¨¹p)?ø[s}ŽWdG•HR 1#h²×ÙÇ•ô’¨píkÚ¯†©ê÷õ——&xÎ@B endstream endobj 116 0 obj << /Length 776 /Filter /FlateDecode >> stream xÚíÝKoÚ@†á}~Å,ÍÂŽg|_EiZ¢Vi›&´]D] àX–Œ°IÔ_À6K ¥hßMLxä!›óÍåĉ°Åå‰Ý\ß NNûÊʶ|/ôÄà^Ò )Û±”ã‹ÁX܃^hzØ“¶‘Å=S¡QÜ×׋"¯â¼*{?ÖÞöWDVä+9¤X¡’ÂT‹!CY)­Åýžm|~XŽÏ–?Òøqkœö*îL¹p«€ÌEJ<;{maJÏr\U‡JÕ„Ê÷yYé,ÓUZä]£úäI€# N&öçùhËúWë竵Æd>ùmÙrã㢇/½bã6Åúõ²&×e™æIýÆ[]éúÕ·^¤ ÍãÎb]:O€—ZTðšœòõ)¡\fÅPgi…fÓzŒo=š¡.ãfËÔh—»û¨nçÓi1«v7[uü !ªøÏ ­Ó¾Š6Zb)ÇŠänéÕöÄúTÌ&íÌr[eu|`@YÇ ;­sе ÓµCËõÃí Ù`}6qQí¬*¦ž §ªé°pWñ°€¿~-lŠÚó¤)g]Å{–°Òf·‡3‹šò}AÒ|\,Ûÿ=îC\‡o€×[W‘vi® =^÷¼©/‹ñ<‹ÛÍŽ¡ÛJϪù””¼ÂŒ¼l›ÜlÏÂ7Iô¤ûßïø|óüùI÷¶£É ¸Æ,M’xÖœÙ]n(Fñx^s(»;™H‡.¡8í tçeÜ™8ǨH™Ït´õ6:ÚºÒ¶¤RÂteh ZEÏ4M·n~78ùÔù‰ endstream endobj 137 0 obj << /Length 1205 /Filter /FlateDecode >> stream xÚmVK“Û6 ¾ûWè(ÏIJH½{kÓ×v2“MÖ·4Z¢e¶2åJÔzüïWv÷"’ˆÇÇ â  âàUÌã/»Õöw™2Žò¬Ì‚Ý!(DT$"(â$’Iìšà[øñ¨ÎNë,ÊPD4~~E‰ˆÃW£×" /ëÀ[TQ•Ë¥ETJldNÙÙó§íWð “ÐŒ8ÊPѲëU£ö&áyèkÝLƒêX«l;©–µî¨ɵÅ=#-®ýÄúž—Á8ÞòÜ®ôË—O¤:L¶v¦·s¶!¹LÛê=;ÔX ¶2ª2IÅ`%eŒÉ¶ƒ:Œmœê-Û“,ªŠÂc"b¥2H¢ G'âä FY›…UD¡>ˆÑÖ2 ”*hNP Íþ޳Øhn{Gæªë@.HÚ³Ëò“ZÕÞtÆ%Ú“b†‰VÏæGÅ–Æ>8ûê¡ndQ—Œ˜ 2fd¢œET% ­?à ¼ß,Tú+rHEͰZe:¦èý!£]]ëq$SÊ„rj¯F^½õ ¿£¬_ôðŠ4&šçáóý‘fá“…Êk ¼ªÙâüòüäa}‡L)Álá ÌÈlÏ4=²ÃȰګú_ô¨mñÿìñÐ.¿3ºD¤‚KÝSûMN#žB’PÆ(¡CǦ‰švl°$üü²éA:ÞT×€¯/Æ{µ ¹•s$žõp2ãHm5XâÅ’'ËÜdøôë2Q¼÷bÜ‘#“âã+¸ÊùBD‰Háx¦ý@ÞÊböWZLö<_’é|muC;Þ@÷v”ÈÇc?u Iý­GážÍ|¡ÎÍ><Š´›G5ˆÞ.¨W<9"Z’-‰VQ\$3ÓNÓèhóžºäf6¸»ÆŽºæ ³ÊÃ&óËöëɺÍêó°N³¬ß?`Nù!ÏZO¶wî(ó¨Lª9½±'üh€ÞvW’- «qœQN­žs«­-°1lb\ÄÜæèw§¾£ÞX.:hÉ]¸ V[έf˦[2¼hè]0’×Ô aÆ•ù™þ¿‹ ¡‡4{¶€:ÞÔÓØôœ8á›ÚZêКïõºÑXß3ÄÑx1]G³=k¸uÃÌG„±áñ!"ZPI0«‰ÖKGMoy¶¿²è6à :e«yQLŒËæ‡ ý,NÔ t{3ºA¹~XgYxÿFq¥?£³T†ætîôI[§æ4  »ÍŒ;4r5`‡œ¾ýáø4·3/4•óÖ#’Ñ»=OnÛO²Zr ýðÞaYß+/o0,׳}Í·Äßv«ÿV¦q æ_C|Ö³´ êÓêÛ÷8h@¢¤*ƒ‹·<"Maì‚—Õ—‡Íjñ¸±¿*ò’¯‰¸|ƒŸY†GçÎ?m·—Ëeñ ø?°üþѵ‹ FQ†íönç<>4®4‘,‚ þ˜b·ß¯eÅ? ò9 endstream endobj 148 0 obj << /Length 1246 /Filter /FlateDecode >> stream xÚWKsÛF ¾ûWðL¨™h¹»|+õAuåGÇqTIž4Sw4EILiRáî/ýíˆMº”›ö"b] àV\Ûj\»8áêûãâÄ8—¶&9slÏÖÍÌ5…ær“IÓÑkí7ýlìË( ¥ëé’Ñ÷*-Ê I‚2ÎÒÁA‘¯ùÌw¤ƒz,—yRhCéƒ>¥gša§=©Y•mêeóŽs™(f¬”ZBó@©c¡R_2Ç2ÁõZ]˜¥e¯úŒsf¹Í>PU«/wJ÷4+Êm͹îq&”‹Aº&V•6Æ%#bqÐUì‚ÄÁ‹Ó›,I²´õÇ8Ý+ÌîïÁºrëŽÛÈK”ã帺• [mòì¾'‹R0ÏöÙ1öA¹3ÊÌØ“³Å·dI 1Ž'Xx`F4GĨÇÒPxPÆä!Øô=U†!„Ëá\ß'yãµ(ñ}ðGt”_Taïñ íØÂ׆¶d6·èàÂe¹Žžmðkw²‚|qÆß+Ùµ1#* RI‘µŠHÔ*d?Æå.«J’ÕÙCn׊Ý9ʰÈ‘·TÜíž4>î"ÂÃ@Ø:§)Mý)«ú>6À´m‘¤Jà@æH×àÀ %íDpÔkÂ2àq€âÖÅ‘]ãù-ÔÛSú–?Z±è¹ß3*lÞA, @*€x‰ `µP«*èÈX‚qÓü'¨._”–c1û5G+^zã.U¼•øjÅ»$¾O–Ó‹_ç§‚¶C@ï¾ÿ„“}XxÆ”ÓׇðF0:8*ô¯@TEI\ŒJAû‚0ÌòuV\–}¡sÚKyI‰]Deµ¯NÖ•;Bµ°Ê£®è<˜4ÚF•Ü6ŠHiþ‡Jlp*öTTÕ»?GýݯŽG;?W)…ñsœ®³Ç‚QúçYz¥å¨/k³åå§“Ó³Ñ0­ižmóà/ô¬þB¼ïKã"zúv:^\¾ýðúi$W4‰Q‰4™)Ì®Ëç_æ£>+ÑŸû É›”«Fhì•%cf¼âaû,úyúGíóω1<&–—ÿZ±ß‹€ÿSÙ_B@V8ò}êáÒ‡žUD=¥`à ”D6̾þ׌mµgÜÅáŽLÔO°æQPÒCÄï<ÁÈ4mÿÅãéH³±}&ÜN³!+–úbµ5¢©3‚0¢¯‚­bÓ#ØEµ§l"wS¥!¾ z Ix ù]ìÔhš„êº%e° ÕqŠÖMw—¿a{ -¥öéY®hZã‘ð7y6¡»ÊËqÐOáñû<“§Æqåa ®ÒD«=GZѲ±àÒ ÊL©¨ŠfvÐÛ­5dúnÌÕe=õ^ŸMÆ‹ Ýëüöælqõ馹ågìRW,¦:»}ýe²¸ÝÌéàõøæâv|1Y^Žo~ºžÌúÀ6V{ß½‰ skë]÷8­Î>ôu”¶×ÝýX£5q0Þ{—Zióׯ87í6†„É, ’èxÌä*‰²sb²8ù± v endstream endobj 2 0 obj << /Type /ObjStm /N 100 /First 791 /Length 1905 /Filter /FlateDecode >> stream xÚÍY[oK~çWÔÛžóàž¾_¤èHÄ cH²»V°=Ë¢%`q9—¿_Í “.Y‡°vCUÍW_UwU÷(’äH[òä=%J’>ügð±¤ðqžT q3’–ž´"mdCkÒ>†„;ž éDÆF2’LÀ¥!+ îuwÈŠ‰ä¤&«È騰šœOø\‚4€G6 Iò¸é <L»@!àf¤¨ ­(ZÕðšbÐäÅ _ ëRrŽ‚¤ ¤à›L°Ábt¢÷T:RÚ„¬(a•9”ˆï#¼Qf J¬ÁcÁ  x‘‰Áã"(Ñ x@–Õ©(ò–¹Õ>¸ŠFDt*’Q2CÐð/9І „òsàñ ÷Ájt¦VB΀CÏ^)²†cƬZ ’™Ä7%Á|°, Rc䟂PˆxN5(zÈ‚jò‘[Ø H…Ìð!±a\DüCZ ‰YXæ 6ƒ°*ÄB!s‚BRÖ’C¦qaY˜5HWœO†ã1gdz°Ú7Þ¼¡l@Yk>œSvE?)!¦_~iüÔëd}z·ÌYRk=yÊ©O½Åü1Z/FSêŒfãõhœÿ¼cAo, GÓœæÿ¢Ëùl•ÏVË]Y³‘½ü÷èy•/H ºû5_ü:ÉÛ•¶ÛÒZP{¶\¦ÓÑj2Ÿíj¸m #èf={dé%fOÔ\Œ×ŸöƒóÛÊVPo´\Nfcº­Fô~4]ç{ö¢`’ÕZÓùÈcí]µ¸­æE!ù0ZæÔ||Ì—%äÁúùy¾X}vdŸ)%TiÌã’ºóÅ'<·ÒÜ'¯?˃Õ~o¾\ùàoDïÓ3è}˜L'«?›HÛèØúlåÐJn›ˆ‚šcVù‹šj[3 ú0™=Í{QM蘭Ô™ž8V}º?­§9H_Ñ`5Z¬ÖÏ{lì¦0øî×¥îèÓ¾Q;É 44\LÆc\o&Ú^ͤêLóÙrw:Þ£HàÉn&«¬õæM#þñœSÖÃômd›É‰uY?_Î× dÖŽòÎmþ4½ÿN÷7¼L"` !·êc†°€…xõŒ?=úïÿø'](’€:fŠél=~< ”X´Q…Á þD7 ®xDÂzÿ…ì 8 &î…µðSÆaä+ºYW7” óßWTkíe1ªÓëXŒò(÷ù€k›×ø£P·âú÷?x”5g³9,Þs;ÁˆÐMƒ/‡rŒåPÆD1”LºJ‡Ri%•VRi%•VRi%•V¸}(GUºM5ÚjtÕè«1Tc¬ÆÊžªì©Êžªì©ÒÞ£…ßl°~Xß;“ÙÙÛùâ)_ÌÉÙ_³vvy¯Š/Ìõ#‚„ê.œã– îÀí}ƒA „X“¶×†^§q÷þºÿ¾}ý¡X#¾ §QѸs.8EBVÿx 5#˜Ì¡V!a€’ … æ ’vw0lv:'`¤RSò£ÔŒXÔmô}hK·íh0…2ê ›wÝËÁ ø¨`Ô|üX5FŠ„ÉŠM '¬)!ƃ(®šÃæ ¸¨@Ô\üP5 ÀñÖ«s‘Ú kOÚVçîm³s*J*05%çS3#%ìD1¢Pxôm(± zí‹þà]¯wמlúTj~ΈIY,eس»ho«5beÐQa³,‚W߀é¢{׿mž`õÝ@ÛÐõ­f[S>Öàig-jÔÊoAvywÛkO@Z…¬&íìÈ6Ò9/%yì0b¥—á ´^ Ë‹OÉ ¨š®s‚ª™B)Ñ–á¢@$6ïÚ„Ôlµú×­æðúdUpjŽÎ¨æÀbqz+E`@Æ£ôꃀ>´»WwNFO…¦¦ç,hjnÀ‰ó|ˆŻËZ¡s{wõ®sºÌ©ÀÔÔœ̆4ò‚ÏY5v×ÞœôB¦ðbózÑmÞ¶»­ïÏÌLÍÌ9ÀÔÌ`Ÿϧ > stream xÚ¥WM“Û6 ½ï¯ð¡¹cÑ’¨Ïö”6›6™4»u|èLÓÉÐ×V"K®(Åë_€€´Rª$éÅA@Ú[Þâ—›Ÿ¶7ë2Zd"‹ƒx±}X„a,² Z$2i,¶ùâOçç£:·ºYºAä9 ïËÊ´ª,U[ÔÕò¯í«®_ÙÈ¢+ƒDÈD.Ü0aè“Ég†¬Ôô½¯M{hôÛß_Ó8> ׺#a¯*:£Ih,TzDνX¿€R8<ñp?‘"òSð‹ÙÜ>ÛÞ.ÝØóœÛ?¶·oÞ¾¼{CÛ&>§©ˆâa×¾>T•ÿ0cß B–& ø"ö³¯c‡ç²ùqæ@ÜÁvW†"JÈÊöXX2Ç~cˆ³nIQWå•$SœÎ¥^ñº–Öod„2Gå¹ÎiRåŸ-UµêÀ³”XÞ¨ýÇ¢:𞲤÷¯×>€rnMá¾Ý½oÙ¹þÌ\Ÿu•ëjpÃ(]?YϨ!uzéGÎc«+4Z‘°Ü臺åV_?ãÃŽ§}ªqþþh6ñ¡3-[eÆieŠ’m̾\›¢Ñ³î3ÎïóÍÝý·²Y6²páF™H“ˆ³[œûãÒ1a3!̼—àŸ GáG:¥ªÍ*‘¨%Ū«¶ÅáÅYb û ~o¹ÕÀÕjƇj&Iú•+vـǙngôß$QÄ©}£ÁRNÓ¹jÕNmhîRôûŽjxŽå`I€ÄåZ–¸~êAû¨|€;ŠÉŽ9HÒ a¨º¶>AÚƒîºô!b~à^˜Š øðY(à[2ó±n Ûà쀅oï8(òzß ÛW¼&gईå`ˆ"ꮵÞ.d*hÂÀ’Ðg'¿Ÿñ0°h´æç¥ÅN-ª™CˆI†£3×úñ  ðýÛ|Œïת†#Tô9ÔuN±›ºkö< }ÃfMBi^4ÍZg†¬é¥ôœG…Ê`q~%I}‰}9K¡3t%)#ç¨U®Cò„HŠE½ôá<«ynÛÃ¥*k•óâŠæ Øì.óNŠåßç©ûr/í«bj`.k¨#hÇM½×æéîýWœüû”<=ñùx¡H%YN¶Ünoþ=ËÏP endstream endobj 191 0 obj << /Length 1770 /Filter /FlateDecode >> stream xÚ¥XëoÛ6ÿÞ¿Â Dl–¤D=¶u€›&A† ÉÅÐ#ÉŽY2ôhb Ûß¾#z¹rÓ¢ŸtGïAÞýxl&trñ‚šï›Õ‹Wç\L8%®ðÅdµžxŒx6›xÔ&Üv'«hòÁ:}»*.¦sîù–Mð{^ga•äY‰¬Ì"$Å” kSoã¬*§ŸV€…`Àå®2àxÄçl2ç2VSŸZùtn;¶±¬b¤%~ÖÆ”⸕d8Z=©Û«WK¤R™mj¹‰gÈÖ¥‘(§ÌªÀCYD8`äË}VÉ'#}?åÔª+d“ê!oc‰[q¦y™d³¢a\"*VØÕ9ã$ë<çܱdY&›Lm Áˬ¬b!“¯q·6ña·\Gíã.pBõm÷JãtîRjý6Çocã#Tfãa8ýÏP ¹û<Ú#õïÈqÁ‰!£3ôOï‚"ôbìÜöb{ž‰™¡8Ä1ç‚Zû¼.ÂRTo?€KJüþ]—ÕXìÌ%^À7F"ÐN4bsÎHà7)»<[¬ÎPôf‰ßåÙíÕâÔ ž¿»>]]Þ\£]Ö'Ô %LC«Çζ_°FÖCÙºZ\_¼[\˜­?Ù¥Åɯ#yÅ™'¨mPA'œo›l徃¹å›ŠTD/¡€Ó be²Ý¥{“øÙ%qhÖ G€b˰Hvº"yÿg8ûMS2Mãhv +ü|~8òeÊ…%ÓO»ÅÖäƒZ(kØGHK]Â,-yŸŽæJàîôS‹Õ²ChWÊ„±B£„RÑStý¬¢*G_1r› >w› c«f²ˆË:­Æ¢wLRbÌÂZùvL£c…yd’ e[‰º¬ej@@¸ÄÞ}§ŒZr?u…EiÎÕÝ”XŠó$!UÔ…¡FäJ¡£ôk¬Sk£/*£«½JÛÌ ¾e•¶±i¤zÉ ù0¯ÓÉ{£5Š?RÊ;€Gå/#Fuµ¹Pm?vš+>oå’ ²”—àá G ×Ý Èôg‘bÅ ü T$ëÎŒÎOÍýŽà-À†3û`5n|³¶Ã¬š8-ãïSÔÙ„ëKµ=CÙ㈅äÝjyyº:‚^¶C‡î*YT˜4¾§Û ¤nó²‚̹ûó yÀl "ÐAA“ðá)øR·Ozb+÷(«s¾˜¸»4 “*5sꆊŒ1ƒaöRÆ ‘Ðk³› {¹Æ¯4k›õ3×eì8_ûs/@Ê Åz%£èrPñÉV £J[Vœ~LÒÇtüJ©êÔ°–’T¡£Ñ“ã´i<€Zâ‚’ñÛ¸°KehÖaãuÍm·(sP„¶OXwU5Û¦èÏÒXÕÏ¡`ûSµ_Fª ¾È´4mašËÊÿðéH½ëég«Ý¤|§»×·Œ ÂO•X¿AèÕ€®©1 k f|âÌ’ø1 )ˆöòƱҘAc¦Ð8LᎎPX'XoVއ–ɵíæÈß_^¿½y?ŠÍ ÷‚ö^F…—Æ êbaVD‰c¡,cEbÄd%ÆyôQMe1ãcÙÌìãÙìG<ÛØÐ*ú]º V—<&gΰu™¡ˆÙt d]å[ÕCíq_}%®(çªýjˆ ™¢D!cý.Ë,Á£±›Úgvæô®¸ŒÐ ¢Y[|¶X± ÔSŽ çúgfeü€æf—g¾ a¦;Ž`¯8–,ðÒðºÄúHgSÂýg[¸Þ‹m}äü”¢.é„+÷šÞSÅ£öQᓈ%Ž7}É00.†ÍžznsæÀ³Z')0Ò|—øÁS +8ÀëÆI‰i3UKöš¥žd+PÄ)äLdÖ;oY7&ÚÛ\ÿ¢Nj¤ "©-ž/\^™í® ¼§@»ÂwÞq”;Ãtko”°†¤ÉÆž¼¶Û*¿],W—Ý#uø@ ðãGo“À†§¦ÿý·IsGöü°¯,âMñ¹Ló]¬°ï–Yÿ¢i/:þ’퉶·ÎˆøË77oÿz‰ý%ž8¼ˆ”ß$׋1=ûƒ?)MýÊ=}-ÇrÞ×ýî:«·EþX¾~t—kUì;‰7Ó­š02ÿáçI-æñz ˆ¤ ïÿtl#»V·9-Öþñ{u)ÞË"Ê äÛ\@^4?ãœÁ‚³Õ‹ÿËÒ.K endstream endobj 220 0 obj << /Length 1956 /Filter /FlateDecode >> stream xÚ­Xëo7ÿž¿B(‚Z$f¹ïm(©saÈ,_qhJ¢¬íI»ê>â‡ûßo†3܇¼®“àôeÉá¼8Îo(gô0rFï_½]½zså£D$¡ŽV»‘—8ÂMâQä¹"ÜÑj;úuün¯N•.&37pÆž ïUmª4ÏJšªlKƒy1ñ¢ñC}ÔYUNþ¹úù•ÃÖÞ\ùrƒ©ÐGS37rDä‡0ðEàÄdëõÛÛŸþñå@f&¥ƒˆVnæ‹÷÷ó÷—“Yè8ãÓ¡ Á/׋Ÿnù%Þ\¹Ig/ ïf¿ÎÀ¿ÈW{w|*ôFoÓìèz"ƒñ'u<ô””õ¼•N("€R£m§Š9`ÓMD(CË…AP é¸]MîËš Mn.Éùè­ÞTyQ}“g•J³f;Í67uQÀQµÈ'n0~¼˜Á˜·ªRC]ZaÅùÎÅLÆžpü®HINú *mÎ=°ªK“áxeì}«!uŽi¦0YhM•´Tå4ܧ›}_ -üQ«CºûLKVªc5§eߊ¥¯YˆÂ„]¡ŽìQyÒ›ô7Çq7jÖ$n‹ÓÝ:êàîÍ—µ8à.>sÂWô-jf®Ò£¾H$žGúL(!Ijà«J1÷ì2ì?zˆË¼œqÚ"≠ðÐEoô¶¶¼Š…—ôÁ7²0ï |Þ"ÃÊ êƒfàj†D燳3‘$nž£IÄO{ 5‹ª‚ÈpÃÁ$ÖŒü¦•ì²oll˜Äzͬ懛vXm6L8n˜ìUyÆj3ê¼ÓiR™á!åCf G 9´â#WÍ?Hôýn1ñ‚ñü;Û£Ÿ‘}ÖáøoºiåÏ”t€ú+!h5{ÃC}<µ…*3†³JªoÔƒn …I¥:(üÇðîÓã(.iSDìý½ÅÅèzqw¹\‘Üõbu{æÂßç7÷—w­;?çú‚Mú’°sø Çyj%úF+éñ¢QÎé>kå›÷’Y+žµ¼dä+û†ü£.N*ݶfÁŸg…už¾¥K0qhþ—ÎäkÊ‰ÖØ¾FWËûË?‡ÑÿEå[_7)ÊyN¿q‘ßîsôò¹Up5¿¹»üó&åÐîüÛÜûcÛ—žðñÌ@ŠÄ HWГ¸\½úƒéêÔ endstream endobj 241 0 obj << /Length 1332 /Filter /FlateDecode >> stream xÚ­WKsÛ6¾ûWp|±ÔŠ0¾ö x$O2®ÊÊ©éd`’8¥H…¤ž¦ÿ½ ìR"e9É¡:‹Å¾°»ø9ÖÚr¬›³×˳˹ë[1‹XË•åÆqd…®`‘/¬ejý1ºÞÈ]£ª±-|gä2çm‘4YYÔ8•EŠÄ´»áhÝnUÑÔã?—oÏòv9÷¸«ÀÓ®l:,ô <æ;úz˜Ýή—c;pœQ!·j‚dùYU;™¥ßQÛ æ‹ûßö+íÏò™Y6ç,ðC4ª ¡Ðס9#o÷T°Íïg{ÿ;6LroK°ËÅÁpc#©lû-©°³U ¥V/E§“à¢LU~©M2@ôr.â^)Á|à1îǨ´Ü¨Ja‰²®fy]"U·»]Y58Y•TêJ5mUdÅšÄqHÊí®¬³FÙÍÓNu’u›“úç±ðÁt«®0¨AÑ!(;áÔõb6]Îp+÷ ³w·ÓkbÎßß]/ßÜßál­šPf½cçЋÙòýâî'³åý|ßHLiíÂ$üûàÿYƒÔ(ô‹c¢œCÏ'çP@ý-‹ó.×Ç%–ë“úŸâú/©Õ2—UvRR ¿‰nÌä%+éj¨ŸÊF²U{Ò†ÍÿëáXÕt® îÁšÞ-™Øž«]¸Ï¡4bÃh§éj/cN!_ ÁÛéÝÍûé ûb—W¯NæIå*ÁSã†ÀÖ‚ùuÑOfšV½ªÊíé¾A¶ç2ç»P±ÏÐW:”—@Ž~¼ }h0£Çî± ˜ãœ–>ü˜QømìžcíS€cF×nuàûÿ¢)xu p§²É4^|s¤ôB0ÚªfS¦(´•OH<*ÛZ¥(Ö”ÈI*%Z•¸´¢» ™ïn/b­P0QU#»õ¤P«2I¦ªC8 Y󬪲ÐlÔ>§‚ÅÝUÙó »Ú¶uƒ” _`€0ÔÙv—+‘yŽ”Ù‘2êä’òwVCŠøH£°f.P¦sÄpú ’²H'dg£†B8ÃÖÖ%QKh¬èè, vÆw&bA;± j’ 2›l*W¸h¬jƇ¾—ö'“&CJʼYuÖT­ÈÌ—1‡Kù‡2é™)“‰CéÒ"²ÌVžù¦©NÔîѨy£`Ó…N‘ž~Éš RE‰ãc™š€?Ÿž>À'Ç5æÑþ DVt•6 íd]w>Ò¬R& h§Øó1{Þ`å¸çµ6õ5ÅNq®3Þ]ï”~݉?pUwÇÌ<Ÿ*:ôj—Ë„˜‡èÌUažjWy)›èpWã A÷Y$”%Ö!<¤rY¬Û=ø~÷j j ã½_üÙp'œ¹>ž€ÿ½¸ºê…uuU@™ª,™D‡›Œ»GOcp°<Àýob= iÄ#Gü[xÊ÷xÚƒS¿WÈ ÛY’â2Ûu%Œ†¢Â !cFèµJd«”ëÄtÞèaÌLkJ?õص©Ë±Jš'Iúá÷[$ê:‚k¨]##×gTZ™“¿²×bN‡:>áûÌ=8Ï_ƒû‡ßó]…‚b¿« Ú èË'©gæ!ªúî-ÛõóaÖUHó #æbý©-ý4Ó4žq e¢mÿUç²Þt«"ô-¢i ¤ÂÙ‚Ì#1çm‚ x:gøŸÈªV":-[3Íñá­…7jËŽþJýks¡Ç¡'"EÁY0И-ÏþuT†Ø endstream endobj 254 0 obj << /Length 2565 /Filter /FlateDecode >> stream xÚÍ[ÝoãÆ÷_A 'Òf?ùÑ"Ò\¤PÇgôår´¼¶YP¢JRñ¹‡ûß;»³¤HiEY&‹ƒËårfö7_;C ütEÝõo·WßüÈUÀ) U¬‚Û‡ b$,ˆ¨ \„Áí}ðqöýSº­u9_ò(žI‚×ë¹ ³´ª²Í#N¼OëGÿœ‡ð(ßéjþéöïÀ! ’„<4 dDb΂%O€‘cpû¤çKÁ¢YZÎY<{Ü­õ¦63áì÷9WŽ–]Qí¶Û<Ó÷xW¸*ÅÛë_¾¹ÁÑÃn³ª³bón®Ô¬yuUfs6ÛÖ /Ç´n¸g›íαí â^_›¹¤ S3]Ö'DXe©—f߀ð’q’(Ž›¬¶ÅæÞ¢%¹¼<å<™}ÐÚ¼Ö*'øhWÜÎcó.×ø‚\²ƒU3‚O>¬ÒĶã뢪Kýá×_vEx~§WÅÚQ4l¨ë\;èˆö]³áU]”•ãôM³Ü<úÜß-ÃÝ®ôÖà†#*@:«pÆ‚o•“ÚŒï^jâʽÀŸ‰TúàÝß(åeUãõìY‡f3æR¦æù³çe«Žæ¦Yÿ¤ÐÛ²XéªBB „kø´kÀ¢t¶ÛTºÌÒ<ûÆ Ày Ä ÞrËû ®›4ÇÉž²à>-ËôÅà”$ÎH-cëƒik}p]ïò:[îÕGi#QG} Ÿ¢êç9£³¢/çˆÞÒJf¦ZÉìØhóÙ:Ýn-H0iц¹¼]§u™}¶T ÷š–ÔO¥Ö^®–¼aéA¡‰˜šˆ#4ðØÃÈLßàé|å§R§5õ¬t$žÒÍ ‘³¸•gSÔ80±ª0ðßëmQeµ^;4¨*êP…A]¦›ÊD -Ld ®²Š5—{ˆ·ä¡LׯGlœ²g‡P›(bç waļ a„àèG)ñî»ÒXC÷L ùáöêßW ÈÑ€Œ%D”R$b,X­¯>~¢Á=<„ý‘ÄÁ³]º$,5¢Ð >\ýú¿ ”JÂ2"Ëa¡p4𤷇ŠqP‹H€– BÄص±©®1Bb3Š:‚$¡šD!8`#ú¢Ü qW"&I”¼»G#@ƒ©‘ZIÃ*•KÅÑ¥HJa({J/ˆ"wи+Š\ƒOŸÖáœ[v9çÅc©n@sö`4TTàX"Vƒ4!VL¢AˆšœIÄ ÷œ*9#Š%@Ó.ZàŠ5I’˜7 €Š0‚ „oà@xýéÓFp1gþ€¦ñ #KÄL1pLa2 ¡F-Žñx#xÈ‹Íà€¨ŽGgé°xuÇŒÐÄ ± :­¿ ø¶úëò-îþu€ú.fìA>ŠHBÅHõ%bÕ’]|ZK<G°%Òx6•««E^ àµíeJëjàìøFiüJíH³zJËtUåœËY{44„ä#Õz9JbÒäݨ)µºb¥ó—9TôP‘ ¥Ô{¶ãR×»rƒã^ÏDºÒÌt}–¨ihuß¿Ë6iéˆ:üí¼•æî³¶“¿à쾿7M˜Mq¢ß®‰ö¹ëPu÷i½3NNùìC¶…g¨Šsíw9=lí˜Î˽â,:Ã6oçU3)NÁQ0w§ëgm‘À·qÐièdÆ_pºxè­c{;÷¨ª¢{³2]ôåüÞN=éÃg–ݾ±ƒÖäÚ3·èÀ0ÚoÇtƒ\¿¨z*Œå>oš&Ña ÙÒØ·±÷Ã{«.lqoã覱#¿ï¢úrº‹$DDÄp¡É)‘\ $±4ÌQ@@§,ž¤‡$¸"”º¼sýضŽö±ñT#‡›€Š&‘\‘$Rõ¥¹9×ÄŠ€âÜÍA$±¸v¹£1–¶=Í®%ØB¢â>ß>§ëmîmœ%¶=s9gB‘³d¤)%bl™Ci£¨Þ ‡ƒ‚¥Œ åß7í7<ßaÂŽƒ—ôN¶g#Á›pô‚ŽøÉ·qp¬g;žÔ  õÓ`¼xMè‰gQ¶AàÏŒž§g´ªþû¯ —nÍãÌ ròpsäa,8Ä7M’Ø9$Ãø•‰}Æm è2ÞÀpž·1÷{O—y ƒzgx`-q µ0Tžé¾¨PéïBÀc):™nÐßÚæˆä_^œv¾ ¶×zŸ[ã‚ýdÜsFÿOYŽÒó;G︻Zrïðâíyœh>²JMÄx ‹!œ„bš¤Ì T*uqRžB†Ö»2ði³ò˜Ó6dûÃöÑÙXñFlü±¢‹ÍŸÐ·+üÕ¥Yçº,‹ò/>?ê¿öí·í{žd7Q2Ÿ‚6žt!0ÞŸV¤Vz)~a#_¨&Ä4쓞¡j€ûRÿA4fÃ髉A—Cr>X |øÃåù4šˆA໡<Q•$”EgcƒÓ¬LŠìag¶MØé²ýÃjñÇÔoÄÑ¢qÄŸzÕØD‡ ¸7ÑáÈx0ÄM°ÿOÌ{ÚðŠ/öä² µÑ"^Üpþ‹wìñ[ !åÈÈh"Æù“„0!'©` ¡‘|•óOÀ¶õý.Ûÿ×#{ý‘ãmÐøÝùšóþ<÷ÖìýY¶þ|äË.y{\º—Ê¿€ûН‹/|!¿xêÅ{9ö±*Ô%.Öû0¢û)AVBa~ CâæWQï«ìâ¿5¹Ü4 endstream endobj 164 0 obj << /Type /ObjStm /N 100 /First 873 /Length 1609 /Filter /FlateDecode >> stream xÚ­X]oT7}ß_áÇö!¾ž/HR „"…eƒhñ@aU¡¢l‚Dÿ}ÏÜ|t7Üìu °¶s<>>ž/Y )Õ ŠŸj ”1"‚_ T¼Ï™ñ+s¤9Hjèç  ˜\ƒ%YPnÁð7*)XƒB! ÌÙí Åí %üæPÉ×(¡škÕæ¸šÒ‚j ­b¼“ VLN°B숭è8?r'­ À†nÎø' >ÎI­.¨a‚ùîÆ]%ØðÝ(ì5ß¶ÿ¹9o-·PÀˆZvŽWñŸ@%¹qf¨Ž@²¤ÿy§ù°&ädhTÉ.+z Í Ñ8ÕÀBê3ÐÀÑ0aT/:±ºA‚eCö…M|¬úlevv˜ž¡>c_\ 3pµ¡Ç„³STRÕ³PQ4 ®sPDÍ~ê0*2Ò¬h˜Ooh@–D¡.ˆ£c`eã¶`ø6épÉNA`9Cx†R\ l@ŠùtX.ÍEB£¢‡}iNC~Æ.€ ‘ÁΪäj©¡a. |ш¡‘úTÆq*Ã? VPa—ÖpFÈw‡×1Öìv°%-Z ?Ôæç Y´©“Çoulv/÷Ù Qcp:4àøWÑÏÏ{4_çF“Åþþb8 g¤o'aøõ·ßC¡X b( V8ÿüñã›Å£G»°X*&¸øN,/ŽûÔáù»ÁÜ4²Ÿzø†SLØoqk鳫5Vº#ÄÑúü2ìï‡ánY®çÁý®Úðf‚‹\uàa¯÷ //Öï–«Ëp†—‡Ga8]}¹ ·¶Oÿù{…?¼ýsµž`Õùå'Y '«OëÏïVŸÆ2½X½ÿðöñúK8Kȩłè+‡¢ô˽½€ ŒðÍ"UÞnv"#}T‚ðüµ.›Ðk]=##‰taAŠl›Až™3%wÙ5£ˆ0Úeöief _“ ®}Bh£hVvc…$&ñÒb›¶"¥zÍV!CN¥­[gŽ·LóYªQr ©NÛºHHN‘tÆ..œ¨Å³½Eª}΃Û#šJ ®5f¤òÝJˆ“@¦Í%Ù}i`#ÂwäÍdá{¹A!åS­JˆÄ» ¢¶ÿ• ˜òÝ ÑRw†Ø„^ \Þ“òn¬ŠFg“àq’»ìÂ}£×f;±ì~n^äIœƒâ–I8˜ ¯4­sv‘žàaYK´Vú <˜hưßIâ wÏs`d–úÀ¨EA5d¤ 6'ÛFbMmŽ1qTö¢ÂtN7óC+}à i‚f4&+{¡†¦îÿ Ã‚Š¥h–kA%4ãÄNÔËÌ¢P¤ÎN^·fSËîƒFÞñ÷ *ÇéæhÀ7[íã@¬Žõo´©ZhÛ…46+ô˜;ÃâôA•“ù«§}·2Š9ÝÍ’^ÚK–ÎÏ×0y6¾cœÓ¥Ç¿/†åç?.Çþñ‡ó¿ÃãõÅûÕŸDz3ü4<žœÑØqRï°­ŠjÚ‚aeõ d­z ãÜÁ(à2 ÏÖ§ëùxy|²÷úùχ¿¼Þ;zõó“å.ЧÃ7WÓ|߂⭬'FžŒÃmpáè/ã.ðMbd¨;Q’maU<ù çD°Í·…[N¸¯eÆ0ІßuaÉbò"²1ªÓÖµ;ƒ"xàîÆâ 3J!ólÐt7˜Ps7 Ã,7ä­Tº°^î&(у½­zqÿå>!wñÔͳ­pßæÏ}øDê#!ˆ‰V¨ ‹w5®´ÒUÁmWm·Éé[³Ž~U›ù³ÿaµ™Nèi¸Zq«ù·¢.¬G4—.¬h‹µöÙe”fi¢xÙÆ^öþù`Ò…&ìŽìœ]E5Tü»!bßì!^qo]ÿ­î‚¿ë.ƽ¤ìjïþQé;^VŒÄÓÉæ±kc‘gã…áßî¿«Nž-÷N?ݼ©xo²×†:PǼ§H¨¤âú º—ËáÁéÁÞÉÓå«ãÓåÞáóÄÜwLºÃm:óÚ ²{!¹÷-4eø¾·ÐÖšÄ<ñ5mk'êÿBÕIjTŠ?¸¥+¸‹6/剔c÷ endstream endobj 267 0 obj << /Length 943 /Filter /FlateDecode >> stream xÚÍX]oÚ0}çWø$ðìëï=nÝ&M{X;´—nM[$>º$];!þûnb@B(Ä&„l‚uϽ'÷;aäŽ0ò©ónØyóQ(â¨Ó Éð–HÎ)wŽÔ* ÃrÝ}Ÿ<iÖ€b]IýøµgY7ÉóñìÎ_¸HŠÄϾ÷8çÝdò˜æ½ŸÃ϶‚û0ìüêpœ2 çŽ*D0ÜRÎ M;×?¹Á??F…³ä©Z:%• p>!ß:—¯Ä(N j¤j ‚ËåZ¬bTüAÈ N LQ#¤çïëÝ·Ë/H±Ý,-³™ŸÒŠŸ-^$fc¢d`¨Ã[Ù\5¡ @.0b t=ä*^Cô4œûÀR`Ùqª–«Vv÷Ãs2}˜ÔT¬VlôÈ5mˆ1œ”íÚPKK ˜æD”¤Œ›ɉE ´ ÛP;F±—*’,Kþî·°ë~ aÅEo ;¿n¸3áÁÕ4Ü.|éIàWm}Ýv{œÿ`Šñ·¶?*'ÐÇNxùõ©g~¼*ÓCœ÷eT¼aäu- ÞWËþBô͇ô5²o—ËåáF?½ÖýF/c(°íL»uJ-ÌPÀþi¬FrÊ´>®¡)Wʳ;šOæù¸h°èØÉ„Ø|W3{­FæËüê¾_±VRgùzÁ]–&åþ]öÐIg°j¤Õþ^Ü'3G€5N…m¬–luêïtT̳ñŸGd½øC"0Y^x}eó¨îSO+̼º²àh>yœÎ›C„ì6æf×Â`ÛÂjÖeV?æ·~ÌGÉ$ÉLáäkôŒ1˜–-M¡mÒ”ÆßÙ(¦ œ¤Úyºó´( -ò{ˆ‘ÅÚÂ,þ•;ð×vx™;œÉc­;„> stream xÚ­]“›Fì=¿Â“—Ã3g‹;i{I§ÍLÒ;ç)édö`mÓb ìríô¿WZ ˜K“iîáÐJZ­¾%{³ÝÌ›½~äñ÷‡Í£'¯D8ž…«p¶ÙÎbß{+‚h¶Igœ÷²2ªž/D¼rB—¾ïuVì|—×2'ø'iäü÷Í/ w=[»ëHD(v»+áÏb âYìUyP&;(=_Âw2ƒ_ád|n´Ú69Á¦$Ú^Î…çÜÌýÐQDÑ „ k|ÚHÓ°œ5"){9zc¯ò” ken•*ˆlnç¾ç”DIdžë¾¾#‰­ªËD¥MÍ ”5Ž]øÂ]‡‚¬´OKGïe­ð± è=„4ÛÎEèlU­ CôN°v‰çâsZÜÓ¡s p¶ÒÍ^B^gyf˜Óê ߤVÒ0ö)“•EwÑú û²©‰åÝ›'—S|2¥wUˆS À¦¹„Üì3M،ٔÔªŽ¸´,a!{EH°Œpö]‹::€e`ÄïlؓƠí QYèÒ¹–ÉŸ9U¤ü jF4ë!‹“1§W+ ©^Õ > —°Wå9`3hqO‡6åæë7KYgò:W,PóÍ$QZgƒcñ9K`óê%mvï§Üfí½JÕ:Ó†Û²fñ{5C*1†Àä­rK_rW¿½! É3›ŽÜ™”E¡lä]"¾äëy¨r5”×psPÒ§sÖõ ŽÉU¥d­éGulYú³ôh‰=$w`‘µ¤Ú¹ºÊ\u§’j¢ã,ZöA{£CCß„Ë]Kœ}°Øc˃C4․h=»ë€E¿Äôl(%¼p¸_aNd9æÄ9ᡆç¾SÓ¡€ŒL™pIŸ¶ÔèôÑ =ÎßIߊ ¼ |Ûbò\—ðji`É>U©Ýò=U*ïJmvµ¢d —}]à„º•¬!š\2ús£êûyÄÁó·,L7×ZÑîR,”峑mÖæÍhäjË—@½=ô•rfXÛ‚b‹LbåÄ[\ñ—1­ÇÀBX®œCY3†\€Pÿgí/øÂn –èžd\iר{:ѬªT¡3|´ûm¤¬ÈL&óì/Þ8I’Eˆ.Âx@5Q*µÂÕiè?H§&7z¨ù AZ °Í´ÎáõoÈ= ¤ç¼BƒZ™ÿ1˜½áDî#CU`Aú`çÛúí¼6ÇÞìÌVUwsÝ”!7˜6ú(Ðÿ>bÄ÷ Äü9½E»¼ÆrV|õT†e¦]}xlJmÊ~¬ ÛSéµóv¨r›ÛfÜäøEýøAŽþfÒœ¸ìaÄÁÚ%ª¿pMyy{tâCJ¼xAßÍåû‹Nl"ãû6sð—¹¾'\áÇmk|þ|"»ý¥@ãevà«—o®.x£1Xœzüô9¨(èö±‰·b×âÑS½XÝeæ{† ~0»Ñ*þ†€uw4‹–àÇ’.\»¢]WÖƒ ›Gÿ®ø6ƒ endstream endobj 288 0 obj << /Length 748 /Filter /FlateDecode >> stream xÚíW[o›0~ϯ@}I£5®/ص}Ø:Rmª6i¥OÛ4QæP$ 8í¤mÿ}›‹Hš¨y˜4° çòùóññ1´" Z£·þèxN¨53†™å/,1`»3Ë!¸[þëËáùmp/x>™b )Píu§‘ê^$ÙM¨þ»@“oþ‡Ô>Žç6²\é€Ù¥ƒ)v@Ž+;6 ÐUr.–yúRå •¬)‚À¡3Ù"À¨£Ç“)ƒð0 ÒhD\î“ü¤RÒ*iÜaΡe²\µ9¿O‚P\,ÓPÄYªG¸Pù×¢%¨B âT¨N ?Œ+F¦ÜÞQùïxNigâÉ'T"§JÀ`ƈ9µÀTÏ,(/Qð´Z…óHÿ@!ä Á"Î !ek¬ÅÁ DK/vs“^)/nóì1ÍDVŽådhÎ3^('¥Ø”³3ÕúŸ¯½ÆNI3mõè¯Rˆ 5ö±ˆl@dD›4Îß\^y:¨°Sˆ1íý¬ØÏXìoÁØ ¶y—±mvQÂOxXÏÕ[èè鞪?è͵ȳ;Õ'}X?~òߟ{¯'rÁ¤L7úÑF2Û3,;½–ÛUz®á6šžmÀŒ÷‡yw:þ¢Ÿkú%˜vöÇ4ûÏti™âšd×iæwmÓêÜ×ÑÓ ¦òyÕ¼xؘ«À?¢¾å_¯‚ûZ¯B†ów™s‰.b²Ç¢{t3÷–õ‘4õ=]ÞÝðüeê¤õõÃÐ!ök¥„ÐK8ªN·ƒUkõùZÅŒîóôá ¨ÚÕK†ü%a¦"ï©l ™m[ èÐc°”2]ýéóÏ“‚Mù¥±É#>Ì–í&µr—ôF¹&[ÃÛŠî¶FÑÚ;ÜÆʸ÷Fpå]zçþP8o*QVÓEkcS~qÚüR?mŠ¡8³'¦Ñºœ¢eðº$¢=’Þ¬Ñçq ktnræUºÀfÒ£6¨¡¡âù£¿µê­m endstream endobj 293 0 obj << /Length 126 /Filter /FlateDecode >> stream xÚ3PHW0Ppçr áÒw36U°Ô³432SIS014Ó3±°T076Ò³05RIQˆÖpÎH,(I-ÒÔ525Ð0ՃСřyé¦{N~Rb„í’X’¨âÅeµF+ê™*èšY˜èm›mhˆ¢Ú5„ k#‚ endstream endobj 297 0 obj << /Length 2264 /Filter /FlateDecode >> stream xÚ­]sã¸í}…n&vëpERÔÇvúÞf¯ÛÉeÓ]ßC§×ÉÐ2mk*K®>6ÉÍýø)KŠvºõ )AÄ,‹`ñÓ›ÀÙ¼yûA¨…X¤µØì1g±ä‹8LÈh±Ù-þ¹üñ¨Ï­©W×"N–£ñ½nõV7†¾n²Ì4 Íu¹£É—î|®pY°lWÿÚü ö¼K”ãû¡+³6¯Ê‘ HºHY‰åc–ô)Èý戻¥ñr_Eµjù”—eÕé7ô¥kG©W°ùW$Õy¡·…'˶rh/6Ì[Ï}w9îUW§ Á¶Ú½Ÿjï·±ÃÃÝÛÏ4;×Ufv]mÖômÕc^zEpÁRÅé`UT $*ÀmjSíß9¥¨™à*D­\{µ„Š ¥huĸ³É}UŸt1¯ü·B¾H@¿Q8Ô¯ œ=ÎÖœsfžM6c‘ˆ³(J@tKûk ‚¶’IÞÓdG]ë =Ç*1 TKƒÔSþ§3õËÌž"fQ({r«>Pžd—0‰Y*%¡oŸW\-MÖµ`'Dàˆ8ªå—¿ß€¶±ÓCŽNñÕ®pdºqËhhÚ¼‹ÑÇ£1uJEP^ÒhÝqî™îÓŒ¥,E÷ÃqëVÖ:oÌÎmõ Ýözä*‚ù”èS¡ÛX„½ï_­”Z6„«MÛÕ%¡Éý‹Î*oì–G˲;míí uh\O×Ë‘Zon@DBî«zÆô"á,Âëãý—ÛÏ››JÁDÜ[~=ç›, #OðËÃû›Ííwð±¢ÍJÆ‹î)ßßÞÝÎ2¼–QÄ„ˆ'w³Õ­9™²mp ÑU·ùÍÔAò=AH£¼÷3‹k§é³kó"o_Ö³f„üø]|f4A[ô·î œïÇYŇ,„Ó“s¹c¹MÕÅ]wÞ=Ý9pTPãD;´*—) \uùxdÑʆPŒz.tF¡½=Ó%}¦OŒ½l_ë“cû”·GÂô;µº^ñdy0íp/•°°!p×ø­t3á@üg.—g%eB¬ÍÿJ·Á\BF½ ô9KY•×p‡LgHûÓ[H50Oc&ƒÞp/gÓÎ{¹Šzßͪ7v2XuãRO`ܯx9­­j/9ºŠôRux²$eK_º(.g 3 ȸ Äù‘™ûã ÅƵ¯$B°M°0$ZDϬ+sSfÆ­pEÁœŸ«êå•áÒÕÞ²ŸQ],X(ÓaÂÚ™&«ó­rk\qI,2N†c·°w23„A÷k¾Ã`íý3#´5 ¿0ÅŽ>ª1ÎÝR;¯MÓ.ûû½î¹»[÷› =_ùº¦Î]]½ NÈf®ñkÈ0 ›ò~%Õòf!#à<žgaðãYŸÎ…y7c <ÆŸ°Ötò ÉÿLºˆ‚ÃØ²ß"¶f„ñª×t0V²¿µF9òÝôÄîd^KÏíºßÓ\6ÅnB¶¹VL¾>~Ïü÷οO¸~ƒÍµûýñúõŒ"&v4i:>¦Pý&*l†fjÅm"¢YrЉ‹ÉÃ-¢K<îZTOWø$¢ÓBÐ ’a%RëV4¥{ ÂzbÎÚ•|0·aÆÏ4Ø” ã8Ь‰õ€ÅËŽc_Œ=TM{¨-Í-ühãÍËTˆ¹üà­Îþ=×Iùð†çc3Q뚃n §5.Rœ!^a­2“I Y ¾§õ‰ÿÏ­Oø?Ê䤯 ò²5ã®çWsI‰£­ÇAßÒŽP)S—ªù:E"XNz¯Òº…TÎ$ôP®ÿFãya|i+mYXÒŒÒ` Mï £4ä;;H ŒàäÊ“=vcŽÔXá lkhgÔyiœ€nG_¤È÷Ž±ÍØ5ãjYWצtiÕú#”:¦œTrxñ$¿œ›/OÚM T©ÑV<—ЇÎv"sï%R9솀ñÓ1ÏŽ4¥"&6%«bgê† NÁ8HWÄIîTÇí3E‘“ê¹)G1­9^ö)i–7.çrô¨I—¤ƒ*5EcÛ–Á‘Sä]¼'òmúš>j³·‚ mE W39ÅYÐÖ-íÙ5/§mU4s%g EdÒ7£?ÌÅX.Yx¹TŒÍŨxßÿPÎq¡ZÁsqß$UÃÛW´F,Žå¸h;• uO|liD «†« ‚…£>uMKdô€‘¾~M¡a9Ñ'ál¨QjÉø€@È2sÑõ‘ôú¸¿™W|Ò_ýlÀãüÒôû6JLŠIë“ÛÊ9¶„[âŸyv´‡XY`¤tF°_8Ñ)òt:¤Ó©»m8B—Q¶¹í!vD³}™ˆB…‚>å;kd¼¥GjjJ¢™¼8 Ÿòlˆ"ªdùSQmñÝPªxÔT4„¶±'Ȩmì@T{Ì5ø%#ä¦Ïé#.Xn¹å:ÂÞ>âZ&•gf?î}[8Ä›<ÜRòóí§ïíSPèk[JÿÔºhC@ª%J^2TÍš`öWnY¦Ïy«‹ÆíB¯ibã¶ió¶£ U3”ŽÍÙâ/JtyÆß-Íå}È¿‚÷>]Tz÷X?ú: ÁàÅ` ÓË…ñ·Ø=CòÈ=™àÌÆ“¦¬æ G7JigÐ3K¿àà=æÞƒVp¬QôG±9‰þ3ÏóÃ6$²½gÿÅ$GÊ$a k±ŸÈ‘)£%·›7ÿ×Ãz“ endstream endobj 334 0 obj << /Length 1586 /Filter /FlateDecode >> stream xÚX[oÛ6~ϯ0Šq¶˜åE¢¤®{pÚ$óÚ&Cêu+Ú"PlÚ Hš$çìÇï’’%›NÒHEQçÆçj:Xèàtïhº÷òDøƒˆD’ËÁt1‚.£A 8 }>˜Î_†o®ã¢VåÁˆût(‰y¾ëø*®”yÏfªªÌ:ÎæfñqUyY›—“U6«“<«¾MÿØ£Ö‚—'„ ^z¨~Ä"F‚ˆFÜ#> þJ¥jb$¥Ã4ç—åeýP¨,¾QÕWêSøc¿¢ØODB‘~`x7é5Ù¨C' Ýhëߦ@Kxþn—4…+ËüBÊ—'<êLõÑds´q–×× ´U¯…ÅëÐéÁĨO*@˜â€Ã¡9àÄãaÃs?=WöW•²×Vçæ™&•µL4‹¢Tsõ•Rž5ħi~§f}{Àýa\&ñUªªW»G,  ’HÑ¿^DUgŸ‰N¨¿þ¬?0JøÐÙ_”ù{—7Œ¸$aõo©¡= Ìÿ¸›'sËjXô„ü²ÓQ¬ç>N'ŽÏ'oA•4ª´Ê€rÍBûÆoÞO¦Çzô܃'£B8Î>/.ÆŸ ípp;84±Ü –=bkÿÑdºMÌ|I]’ÎÏßkjß³'Å0¹#ˆ¾B¾mÅ‘U<½˜œž_l–F.å½;;ÿûÌ…´ï¢ÿ4¾hçñþáøú7¿/\7ã tŸ€´‡Fc~èÿ%n€Ö*xøXšñ£6ÏT$šˆø¡ —)†°ða©êU™™µ Øte?éreN‚ ÍÅ’TEB q©šCF( ò¤2Âcóøw¥Ê³ÔÁó >¯¬&á*Ñv HŒWÕ*`Îj³5‹Ó´jù]©&PI|Xp5•ÌÚ®îÕ¬pX.¡èøíAm¡û¨”C>äˆpM B/w õ)‰hÔP.ò²©’橘?¼oŠTç9ü€p”à ój,Xå K0«Wú.`Ý&çÊ0™Ì &°Ð·nøº³7© Ÿ5v®Ô†€J÷AH”ªl îk„Ud]é\ißC°•º¼…Ž./ݹIŠ6ê7£JPГè-‘nEî âóïó²njGU¢’¸ª\ù]’VøÙØ!  ÞMë.#2ŒžëpaÐâ’,Œú ëþ¸wÛ!FŸPÉúN—aó.ƒm€èžšÀÀÚ4Íå»$[š­$MÁOʸVý,`96 pRN›åàù÷i7hSŽŠŽ”‰õk3c>Rì8ób„ ™íæ…„RàE}˜._Ùñ¦É-X•»°¹FÚŸ]f¥Šk[´0>uS¦ 0gv³ã옡ªú› s •W'ˉɵjhïíÌÛýv’ý–°* Áë×#[Á{×€ŠârÉÍǾŸõhb·ìZ²Ÿ6šÚ¢„Ú€¬/Îß½XT‡9û¶ˆÇÙr/-ûEZî·‚9¶|{¼ßh¿û&´Ãv^3CœÆ¸‹¥ž·p²G¸ƒQ[9üf?±þE:iø~gÀÜîÎ{xæ ;Èïý¥a×õMis®±³ÜᲕª±’™ýY^Οòß`;ÄQ1¼— Òe㸨îpÝÚm~ÿ‰ÆgÔ;?Eõ Ã^²ÐHr¤5”‰Ëñtï  íå endstream endobj 364 0 obj << /Length 665 /Filter /FlateDecode >> stream xÚÍW[OÛ0}ﯰx lÄ8vb'‚=° “†4Ö·1!“º¥RI,Û ñãçÄ&Ûr…‘‡Æ—óÝOZ&ïƒÏÃÁÞÉ@ Š)Ž! Ä´Œ`˜g Gà÷ö— .P;1ÎÐ6…îý•~εp»Ã²Z»5¯Fnñk.e­ŒÛÍ«ÒLëJïüþ ŸÁÞQš€Ü†§i>Nвƒ§0C¹‹¯ÅL”¦±„Aš3›e{û¡½Hdö¢w>VõåNLÚ6B›3-§gâZ”òe(Ò2ÚêéÈ~qm"{˜80×Þ¨Á™)¦#w`Ñ»þÊžVüR¸]³jÌ÷Û<â”@Dr›ab3e.•¾›Û%­Q;êLbÿ|Œ»§…b ó¢±8 ]Û‚Z,Z‚ÑfëqÁ—>ã¦xìpª¾Òm{¼KL I<3J%¸ñ}¨•Ç 9ã¥?û©/ BZPÛ_›ê¢õJ˜¹ªt¯Š`"Q7h&«¥Än!'ÐFM®šá ®&‰ŸÞÏÃÅ´–:$Õ´jç¾ur¼ÕÕ÷Czdä|Íx5™ó‰/6’3í}"ƒ×7!êß,[lAf99k¸³Ò ŸØÕ…PbƒOîuŠqz~coáÜ3²ï¨GòU¾U­€XHê>¡W]ߤéVÒ±r…”äe¤ìÔáVjaêñÝyY«Ñc½c–cdÂî•øËgwÜlÂüÜ0ó6¬¯$—ôuåÒ³0aëöë°V/ï‘Õx?&˜ä]&}–`¾D'ÙóØŠßL'Ù{ÖIúBdOÒIüu’=]'7"ø!ydëÕ‘ýWq|›ß’Š#Ûœ8öþ„Bòf)1Í êK“oÃÁ?=ÌS¾ endstream endobj 264 0 obj << /Type /ObjStm /N 100 /First 884 /Length 1561 /Filter /FlateDecode >> stream xÚ­˜]O\7†ï÷Wø²½ÀÇöøSB‘òÑM#å‘Ò¢\¤ÉªŠ±!RúïûŒ!„eÇ.`}|Þózf<~íqÈbœ )˜MÈÙøØø­½+ädB㯈‘Zxn&…̳3¹€/ÞT¯ï“i©,|ˆÆ;_áW „®ÂXèñ"4* þ…ÒŒAª£‘a¯ÞxñžF ‘à­B£µE¨ÇNÈ«Xùs|jÂîsèÊXE«©+_µ¦ÁÜp.(ΆhP`.&3Œgt¡3èà †Àà^Õ'!‘¨cÂØâ€E 40?â£8Ñ€9ؘrZˆã«ìµ'k#@ý\½ï„%‡¯ôtï‹öõC{Ôü¬=JáÃB8ìjqÖ/=ÿô!ê“â:!fatµI§GpZΞ°[²öÀÕBfMbŠ !ÕB\—ƒ~JƒPK 7«ËæÌlв—NsÑù#S¤zí¹©Q„.ºà HƒT)†1õU¥‘Ô¨FC?ÎÄÀFѨjYÙ$XQŠöDòT½Œ0ÇL4p;&%Œ0'’V"Ì©iÌY½H0çª>Á\ÔpÍ÷¢„ æªÑb†bÍÚssm! æ¦G¬cë‰PMÒ´–Ä:д–ìLòBOö4HibÌÑÐâmêSD¬SÔ!HÀ¤6ïî.¦'æ($]zûfzóÇŸ¦x[4Rl‚æøË§Ootìr}|jvwÍ´d‚}ÿhI\ê9Á ¯¿œ¼_}îºÐ»^¬>||÷hýÕ9:²k¶¦¥6ë¢ËpïNàÐÖñçèï9÷}Ç[U–ê£%Ÿ®qý’#›qØp÷{Pnë-IqÕÛnåíôðøx åQ×MµIuóì×÷ß+¦tüb:øò×i~þñøŸÅôh}òauÒ‡to§ß§gÓã#ßÔÈ÷x‡|YA3³K6©ØºjU§²Ï66÷°ÇðÀLOׇkÃü²÷|ç`ïÙÎþÁë½½Wû‡;Ë×/üªa»›Br6¢9©D[T ¶°VSM–È]k“š±óòá‹g/ŸÞŸ1¾FëUG¼' («8ëui†`¥åkyñêÉëç¿m‡F¸ÈP_…ž¯óâ™"v†±(1SœØ yˆ8Wo+v# „8™¼Íl’CĬ›Áú”l@S޶!Ê#Äh¶-u ËaüCX‡”ÎÙ€¤XÝ4Ø}mAÃGˆCLVÏ?©Ñ×Éò´ì't'ÕªuKµjþ9ÕjîªF×rÞð÷\l²åbówu±…Û»xkG¶÷Ó–îìH–£ËÐ99ºŒõIçü–Kf{âÍ©Y=ò aÅÛ$éfl¶Îd©ÖnËqBýk‰cX¶RŒ¾?¬n=‰h¥T­nû³ÞEαCà ùd“¨ƒ‘H„xnšc`š›zzª˜§b õÃ8q>)nL•` 'ïDǹ´ ¾`Ñ|%Ú39ÏÑf-ô¸4e* ‚âç"—måXA¡Ê¶:6%Qüif5¡}XÚëlcK:03÷† ÎY-úžIœ³V³Œé³>zÙ=–¬C}‡À»u°äcX 6ì!l?dÏ`ƒ'´ýòT“¹ôAU£¯a»Ü^xg 9v¶ßíäfs˜‰[,ÕVNìCàÐOY¯tl½~×:±$}k÷V·ŠlUrZœßmŸÕ«Á}v:³Ïn`õ|I1ŸIFïýoͶ"CØÈTÉõŠ Áê%Xt¬´o{i6ê•P£¼’™H„lm2þv”W‘hñþ°ž™nz¤…Pk3³ "ê;Ö ½GJ”àd üÍ?ýõy ›Ùç¦Z2½qDP8ÑÌ`;›Þ?Ž€}ÕPè%cèÝ Jó¦—Œ#à‹„óøçç3TdžÀBbœÝ¤€u%å> stream xÚÝYKs㸾ϯÐm¨”…!Àw%—ÉŒrÊÙ©µ5§lÊEQÅŠÔðá±óëÓnP$M?6©l¥r±€Ø~}Ý€ÝÅÝÂ]üåÝŸ×ï>\xÁ"I¨ÂÅz·ð<)T˜,"O‰8P‹õvñwçÓ>=¶º^®Tà:¡ ßÏi›nÒFÓìc–馡qZnipÓUÝÒä¢+³6¯Êfùõ_ß¹|‚*ˆ_ÉDŠ(Q‹•òEàÆ$ÿ§¯WW̺^ÊØ¹ëºlYZ³¯º‚nø4Ç´i4ÓRÞ——Û|©ç>ßvi‡øpáËE ²CeË$žTp,ú‘öŒÎ'=¡»ãÙ¥E§{ ô˜íÄÕ‹DâÅý'¸ý¶È›v†yàêýV;+χu%‘‘Gkç™>‚]=W9»ªÆç´{M”K j?EÄ}žíiÈ=ç{§ëG¢Ÿ™ýhWC›×Òš%4G忸®ÒÛ³Kª8*Ь&Ç;Ñs¡tvœQ;ŒDI»Ù¾ª¿ñ)~íÈT`ˆ ±†P" $í.òo¸_Ϲ3žÌœaÎò‰ÑØòn+ß›¸™f]ÝTõmuÔå oø0öBËû7pç«à‰Ý”íÓ:Í0ãžÆS Eœœv’è2=èWÕšóT ’¨xý"KÈUèBUy9ðnôl›ô^ooEZ¾Ò¯žà>­ótShöx±Àx\YÛÜ à•ÿF–?$I "Ç;˜…}—brG‘“âOÈ'R¾…Ôà4 ÕÍ#­ Ü"he9wZbf`3C„Œ,™oë˳­ˆÒduULÛ×Uw·ï?&j­›®h ¾‚z#«U;Ø‚hE?œøJùŽqœ!!» >V]S<ö´#dý–ön,•âž?–K8¼cŠÓð±Ñ–è¸È¥—ÜC8ÊàÕÄŒâÄGX„)7ù!/R®XF2VÆ<çþ<âbö¥4èÖévUõSr—-l5×—† [_b¸Ä‘j08T¨øŽ ¡=®ldL·?­8íF¶E¸xs~uþim¬ ÃPD‘LDUÚðø­¸" òÅõ—¿Y–·Yñ=û)Úe¨ë!#) ¡IµùuöLœ3ç:<ÞéýêÑsŸ$¨¬1b>×µn»º´Z™Æ ]g½A­imeŸ«ðàß9ø„ôåÿY…n¡’!’@¸aø°÷»§Í€«„’¯A{ b7þ̓#ã1ÊÏœš´ÐU/Á«/’¸7¦ª Îu)¾+d_+¡£ø‘ÖÛ9y1 lôfy¨Ýݬ~#yuõ£™¦ ˜eò¨=(kn=v>2Ù+`ˆpðÃÌÞ€ØÇÐOHúH뵉Wk° p¦ßuB_ÍÇÚ3mOtê9Œ°Ë‰A˜.®ÞÒBÞ°ò>öåÉ ××Kßu¾žcËd‹ h`õÅqÞÐï¡B¼78¸%ÒHªaPñ‚É3L[ûyÓN¤”Ýa£Y ü=¹ÂÌô÷.¯­¸Íã„A¿y¦‚B5Ål ´–§bçr) ÇG‚QSEÎÅ2òW7ç4eãÀ’ ƒÞ8Š´©q`i“fßz¼ÍCõÆ8qˆÆêý؇ƒz'úõA€bš/3YÚÚrw*<éC~è4±G0¨ºãò6bsÂ×¹[”ügêäg(“ÿã:f\0`»…ïK M– Ç“ü³õõ×ó³´ …¸*]”ðTK:Žv˜\B«²Mó2/ï&!Á]áì¥F‚\¸Ï¾Pû²¢jôï\ûBáFo¬}òiyP.†Öä¦ö Õx¾çxÒúbÆ@xØcõ%\żX¾Œúp ÞF}_ô?•/Ñ5_f"iœÃsq$cŸ¿Ú*ŸkGð~x*¡È{p³wÇAœ’ɵ ƒ/—Ÿi`0Ò•§Kšäe£¹åw]º ¹à)id/WÀixÕèúoïót®‰€¶&IÔÛ,B 7û~¯ÍqxºB%Þ[ß`üá•þŒ{2Q“‹×nZ:¬¾0¤ò8γ ©Ð«“-vùÓÍùõ2t5Vg¾ƒ¡ÿ.™{Yµg4z¬:Üi–÷O]WÂ:úˆö½«Z]ä8öéo¤~ì ǯ€™7 ¶Ÿh\‘¸}ãzóóÕmÓÖÌ3¾ðÜ™WFÒ¼RŒôøÜ [õ½@Â}·Àn9Uë2³+¦á€_²=m2&àÍc °§i r÷´¥WŠÙ˜·Ã€7ÜÑ ª h^#ÕMÖ{Ó@™Fäq®ËÙ˜îÈãç ™~›t§z=å÷GE²aßðÞ=5\ö%rð¹e|ÊRšÑº^ Fk®™áTb8ãzA%KÞ˜› '~17!µ ;ÝhÒâŽJÀ«x7ÿLå«ñ+–ó^5ÇV _½%úãß+úÞ\/™oò&wÙÁSú1´Üty›nFaµ¥7~/¤¤%ͯ|5­ä¼’–£Øòû÷t”ܧÐFÁ³]?űתíÖÀ z|B"b-RJÿ\Ik&£‡ úÄ­Ò.{Bo r[Ø0£ª\MôÁ=ô‡¹¹ ÁnzŠ7×$o˜}–6z5wEÛU(n4ˆî;çpÿ ½pö¬`Æü’æCçmEM=—çl«nSà…ìšàÑÄ 6ü?ü¬¿?zIL¶øìmÍȧtŸƒ)ºfõ5ßÌìK¢ñ¸­}¹m,'ÁøüÓ¦HøöJ†Ék•>šbÓo‘ÁãFÿ Œ@=(¦ôÜ“É`ôÁùúÝ¿%*w¸ endstream endobj 436 0 obj << /Length 1659 /Filter /FlateDecode >> stream xÚÝYKsÛ6¾ûWè(ÏØ0 €¯Þ?2édZGQOm'‘Í 2iGÿ¾ .D‰2[©3ö$<–Ø×·»X(˜ÜM‚ÉÛ“7ó“‹M2’Å4žÌ—ÆBBãl’0JÒˆNæÅäéå½hZ©OÏiLc‚¿W¢ a$Î~Îsi Ž…*pð±kšZ·8¹éTÞ–µ2§Í9 œ7<œ¤À>æ–ý9 C’„ 8‰‚ù7w¤½×õ£ªÛ2—öû‹šíH$$âÉÿ ¢‰Fg3Âà`G“ß -r«TOšn £€dA¶¡\^âÎÇ•%$޲®¡‡ëyg$Î (É6Ýh$µ®µO!J8}‰Bé«+”î+’sNXšÂ !s*\¯JëYM…ýáÓÛÚ´wZ~üðÞ#k’‘t+쯿Íß]^û$ààýhC¶1Íè¤0 ‹7$׳Ùo3ÏA4#lKåT&>#¦$N;MT¦F͵(4¨¾P¸†.í—òZ¥ÅüO¸µìt{/ݦ< £é×Ó°MóîmM)%1 Çp±g`ÕKü…sp°ta…³r‚ ÂZÉâl/$‡ïòNk©\l¶Z(#¼ç@üÊ‚x ö¡‘pmš’,á¬WÂui†,µXI°cBÓ©Ïy!ž‚š10t6µMcM ʳ @fÙtæ‘1JH%‡„ñ!“”àq‡—ªéÚ3dÐ{Ç.`Ny0}°Ðz£ªp ju®º•ÔeŽæuÕ­”#kkœ4ˆHÈt ¤{š )ÂØÁ’!VM%Ï-þì ·±«}Tö’T›ÖqÖu[·ë¦?ØìLoîþ05ÒÉÅöÌÕ‹ª„rá)'ÎR˜²Z;h£#zso(]¼ì‚ÓÁ¶ö@ùêM`k#ÉBîP¾¸Òåƒôå2AÂÏ~Ìm°xП”?ÏsFöüuS’d|Œ›bqY+%s_ÐD$“䘒 (ÛµÍX{Ú¶bê_:‰IGÛô÷”­ü/²Ýˆ8VûësÊéë³k„1µ.ü®bYòú,ï!ÞÜ@Âì[ìÎ9äðôhT.`r\Ö}œ9Æðø8èûºïÑÔò£ÇókÛõ¤¦ì°«›¡U}Q´ïNFc  ½ ÿUëC'õÚ‰‰ãôÈ0wYæΧïÚp=QÏ]Ž_æKå÷Wø|Ф ŽŠ÷:æ¥lóû­ÙQ¹Ì6“¦«ÚguÐ>ÿÛö3~±ÁìMåÎk.¬àVÿI׿ûËJJIÄ£'e¥’Bïªû»±W0Þ ^L Æx¸— ‹Å[Ù ž¾<ÿÅàáÏÆ…ËOúäz1“¢˜‹E%ÿÿ™ç@%W¦Ã©'&Œ³}ó]•&?xA‹ðÇ~á ^9pfû±ô»ªjQ¼AÿžúÍ;'ø'<æÊ¹óHCá˜dï‘ ZFۇà nÔ!ÂTÕ«RAÿ´Æéãi]«þŒ³ªülçîKè\JÃÙn›Æ²,ÞAÞÖÀ' ÁÎ˾ m¾n„30ø¹©”ŽÞ½+ì÷‡ÔÐö¬lSŸRÙß_ìÂð(gW ÷ÀNp´Ö¾–¸Ûóµë….·Í­v›ÊqÈ·0ë7´¬D»aúA¬€¢Æ}¥å>Å™O…¡õë°]Î<˜žm¶¼‡ù6€ö;È,ŽÔ艴{¬Tõyݲ÷ÏÁø‹4%ŒA⣉íTÂxôÍõüäo¹vTw endstream endobj 367 0 obj << /Type /ObjStm /N 100 /First 875 /Length 1291 /Filter /FlateDecode >> stream xÚ­˜Ën7E÷óüpÈzð^$†v Ç‹$‚‚3R É€ó÷95É,©iG »Ù=·o«.ë!m’JÒ6SI{M•Ú%I5®šÄã9ë¢\=©Å}K:…kO¦¬ûH6ÊNûL.`FIÞ¡5µ÷’Z‹{M½Ä½¥îqï©O¸GKCá= °:FšÒv:fšaÏ,©– šX|¿^káÕ©,,ž‹ ›žªh!0÷Rv†k¤ö(Ìg›Âߥ÷;~ Žwýyà‡Ëß»ýð®înqA‰×wû·‡ÛëO7·ÇHýxøíËï¯?§‹À´2sGx}Ì\¬¾çs—7pÕ(þýÌëtiáhàÏ¿üš¾«9|0ªedpõéãÇ÷OA{Íõ:2 y«êSÈ €‘ÂóàÑòDKàê-ßzÏÖ–,n\ ÙâŰ"š+Y­ùÌ.[àQrÈf ¬æ¹ÕE0bÍ•$¾ž–§-‚«ivŽC³–ò°ä9³Ü皆šN‚X—°>qIYãuïy´Ÿ÷1Zoä_Çàák²pí¯ùrX‘Žg…íËÖ©-Wb·vͯ§æ(K`šÀ¾æ|YŸ<'Úe!%SÈ·2 Bád–9׈)`×BM)Ët%‹XÉQV°´F¹éÚ¹£Fd_Ì„KØ“4•LѽnISs‹Š¼>YÁ)m,b‰ÆØ²wèh­’V‰•,°•áy1È_%6×âFg—½nžåI¡¡és£Œ¶­ãYòT[Ÿ¬Àe²˜0—°t•¹x?ÖÓ辞Sø'ut |²Bjn}í,Ó ç67AÛ—9Ö)œ‘ p¥Ê‘™%fn²æãÚ•†Ì^[)ŸRÃs,Ô{‰ég|²‚“¿˜Z+b›2·sŒÌy–­~‰d=bwŸhË1€‰õ‹}îÇIîÿôë16?è×c€ûš~ÝÅôë1’-öë÷ ýú7c¥Pœži×fçÀ,OV¼½ôtWN;€%𩛥‰"žkØ1ÈcÈ:±ØŸšqîcm7 ¬ªäÞd {²×G.£¿ö¿h<1Z<ªž%ðÆò(ö‰9äÅñq&'!t¦Ïƒ DU_ 3YxTFœ¹a†RzJ©k`acQæ&ı䊧Ƭû»+5Ç_М®ÌË"±•\ÚšÚ{ÇX‹³Q‚§èËak#EÍø›'úÊUòÄ࿱§ endstream endobj 529 0 obj << /Length 1668 /Filter /FlateDecode >> stream xÚ½XmoÛ6þÞ_!l6KJ¢^¶OY–t‚4s\ìC[ªDÇdËÓK³`Øß’%‡Ëš¡XÂäñ!ï…w÷Páν÷¯¸ùýqõêÍ¥+—³@FÒYmœP°ÐNÈ=æz³ÊœÓómrhT5[¸a4 ýÞÎ|>-ëæ¾Rw¿^“ì®=JÄñiC’ËvŸ6y¹¯gŸV¿€®Ø‰Y¸ªòC¹ÂY¸1¨4ªV[%ŸnÊ¢(g®œ>äû{¥ån—쳚fIeÉ Ô}Ah’É爛’~ÛÚò=ýÞ†ùï­ªrUw%y6ÞÕt†õç•sÞõ›¥±¹sö{òÖNÞ>zËÁQ—ÅB’£‡¢ZQU pKhdÌDÁýÈ%‡ÿ΋™+=g!B{.!~ÊëC‘<Ö§}™ 95Zȯ.zÆ+…€?šÕMÁfãlƒD!¥)Í÷u“źJw™Å‡ dÜù`9Øcžè1K4FºŒë3.:Ìr–™²¨ó\æ†ñ@ —à¤×Øò+²œ¼^vÙ•©9 ïsÌ&Š=n©y—"]ÖôI"U*…U#唑ôNiÃûòs>hñ±¼`"mˆMiVc][²;ꫯ«RE™dkL¼]™µ…²Õd3Ï í‰ÆÌçî8ñ.ѲJÑo/ TB%ë›ù’¦úê´`S•;’aÌžz |ÉüPv†p„”Ó(ϱeí¨¦pÞˀܺÄ/Âij?Ï ! 31­i˜&Ãù0Ñí& ŒçTÏ Ön¡œÜêå%TXE+YÒ$$lªž›sŠf[¶÷[³¢ë1I²¹Ò]‹ÝÂÅ[ÙÐ/ŒáÙÚ††‡¤JvŠZB@£á•A¤ºÞñ2 ÝéõNl›®ÏnÞ¾?{k,žœOhðÛÕêç£yïTøCwŠ‹}Ý´Ø]Úœø‰;'[Ïx°â¡¬Šlr<)4il凎õd1þ§’ÁŒúSkkÑaOAhž “«òaÈ!ôt‚¯Å'–­m½µ¤oùÁ£—!Ýä •ÀÓÞ÷|Ø-žjtCøÞñ ñTÏâH¼Œw÷\Ï‘–Ϥ´Ð®ëE,ˆÜ1íÞB¤ôWUìéjý#뢬S£'%=¡C­×uÓÆµ ­èn‡ ºnóÚôwŒ¾è9 '\'^ÅÑ ±®“Žy%†WO;\×]CN„ê†bÀ‹(îZ,Ö¡^õØ7œù úH.‚vòÑN1öVé“Îi>¤JÑ='C>¤^ +"–Áø9/*‡ÕÕó.NðŠ:à]ÓsBŽxa†wq…xGšw{6Bô˜4Ôz;=7‚° ÇÂce½°¨íœ”dÙ3„4x^6¾âúL¶ó™•„ÀOñm‰üï»ýúÿ¥%­}ÌMá7á&÷nÒJqû¿±•‰Ãd[>ÐHÿÙ e;à3Ú±> stream xÚ­XKkG¾Ï¯ècrPO׫ ’…œ€B„­C¡ƒ"/ÁÄhƒ,óïóÕJ£$Æh ¼—žÚ¯¿®WWWÖžJÒ:’jÒVRïxP"<9QówIÌŒ§&® OKB„gMbOÈ MêXõw° üßK2Á{§dÝß9U6<%U,¥]S#,Û-5Ü^S/þÞR×>)téëö‘†`QÒ‡sSa@ÁÒ\"‰ˆ@=ƒÃq£b .i ™tt7Ï%Z)‰”+`vó­€ÙÈ%`¶ C UüXsÕ˜ëp ˜›ŒÉJw‡¹Ì{2s‡†Ñ †˜Gu ¼ZŠKàÖb.1  ¯/̤X˜ºMF!— ã’X 6& ª`À‰µ¸Ì B0» ªp…q#¹1¦ƒ‹{µ‰ü¯YŠIõð 8Ë„“Å$ä‚ÉÀ'>ÁÄ3Àý„ð “ÿÕ0@ Ž)2™ <0D13p‰bª)˜=K ‹Š«kÈ>¤’ƒÁ\ÉÁ`®æ`0WÄÌDi f8_’Ä Ìúš¹#- È€kÌÀ<ªKPñ0piØ|üx5½zõÍX¤`nÈìêLØ›/‚Y4ï +e b‘™F‚µgäi«Es/AbD!UÆ–ÌÅ.&ÙÓM­fæÕ”¬žJ0—–GÁ0Ð32„í–I‚Ä"5{1a­åº£DåNAæ%ïM³¢jì Kiïg€JörºâãŠì¬Ap„ºÅÀ(YZy±O)£î JÆÙ · J óZjJ&¯i!0aS—(³\,ȼ˜Ç=û1³7, Ëì5 µKp¼½¬±"K‹-Ȳ¡­Ù–J•» EQi¬ù˜ÀXƒ`œ"¥·XàÝ1‚Ì‹}…Q¹êþ°ËžF¯Øc{:~ÚÓ!ð²§Cà'û¤\»íK ò† iO«Ç:£«¨1ð¢E«xÊþ°è…smÞëÙ®! er¼hQ%·«,‚Sµ—/öôéöö>¦ù3pü?Î:U¿3ðÓ „ÛÍãØ¼Ó_P8è`œÁ6ŸßmoÞmîÓešÏONÓ|±ù|Ÿžºøû¯ þ¸þc3ͯ±èæöþZ÷Õ4¿Ý|Ú>ÜÝl\ÔE?mÞ¸>Þ~N—‚ZFö{UC ¿Âr×wà^ñG··[P^îî®ÓKïþŸæw¿ßïÞÏ>Üþ9ÍÇÛ»÷›»Ýåjþaþq~}I»WêÖ¸‹;(‚íª­ú|Ü›|gw´sà»4¿Ù^lÜÿÝùÙÛƒ7g?œ]}ïþù78~syÎeÆMÍCþÊ ñ?èSŽ )õe,î¹ãhh8ÜXjˆ¸vÊÝ,†Å÷žÖ;ì¾w¨z:s‹2ŰŒíG¶?ìR¶*BÜVôeïÖ9†]t Îþ%!„E>‚6/É_i´¾ÛZ.‚XÎe…–qBîîøµÀu+>#Ù?íàŽ[QL-ØI¼?,sˆ³ÔЖµÀ-ÇX¼hÆ…MƒXoÒWö±Àk½û—ÎTÖÒ-¤QăG,'Ô¼åéLÔö‡}>¤qÄP])•Kƒ£÷ðO9!°`ëûç¬x±ûYº±œµ¬ø˜šhEu-;VÜ/4;/Ùÿ Ç?Ü=¹Õ endstream endobj 574 0 obj << /Length 1870 /Filter /FlateDecode >> stream xÚ½XYoÛF~÷¯ÐCI€¼æ}´OŽ# Û•e E”¸’ØR$ÁÃŽä¿wfgH‘“:AP½ìîÌp®ývvVÚ`3ÐW'oæ'g—¦=ð…ïÎ`¾˜Ž'|˸¦!<ÛÌÃÁûÑÅ6ÈJ™O [¹‚Æû±§Ò¢ÜäcÓɇßoˆþPeYš—´¸¬’U¥I1þ8w¢±Ù³KK€Ç±Ðæ©aùÂôœ[óÈhç‹ Ïƒ—E°ZU;Tpviø-_=Sèž•üÍÖH¨£Ü¦îÖ2ë8 JïýG’ƒðör–-lÐ΂E”rñÄ•ì1lûBwÓ«–ð=£kµÇ¦i ×il&òS¹±Üɤì1ê@nìv´: AÎ\ð“§»Â7MÞ±\BÅøÔ1Q€ƒ údž=zff–¦U%›ïtØ Ów_éž« o/­{ „_•b‚Ò›h#ŽäöñæFP4wåVæÏÀÐGrB¤¬*¶²è1 92…az#Cø¶þÚ€_Ó¤LÁ†æŽÀ*Nœ‘LB¢¤}¡ºŽp-óGÐ$Hë|Ad-Ö|ŠhÕbd¹ åM3ÉÞŸ°¿«•ÌJö0‘ Í뜣F’f*|žZ–[ãBM1B5¡¡+ø„`ˆ&Ò¹,«<ùÆ—d±1T\Ï1¥8¹ÀÁiE‹Är”4‹vmVQs"µÙ¹Î¾Þ«¢ÄɳZú ÏVPBê*È‚e,i{¨˜”5<ЬbB:ÅÔÐSÄMà H¦|Éd!ˆz9ÖíQÊ"Ÿô~¢)Ì{׉‚·%è©*Žðu«Ê÷ÖÇV 0+` Â'̈’Ò¢Y³Ã_° …œ®Î§Ê¯_{"8õ5¡k„ê8²\¬fÓóù±ªîf4Φ÷7çL¼|¼½˜_ßÝÒê0pEÄê¿@&´ÆiS#1µºpl¶7›Îg·{Aº1‡ÄÎYbøK-Ã(?ÃÃÉðÀü°ïÓ›óÛ«Çó+vx1ü­–2ð>â"]@ñY•½Aa8Xì8ËÀXH‰-T!kYëAÂàôXì´ý;TÅ©ùl_¾ö=ú¤“?yú|”\çUA ?æÄ´¿ JdnOd}ѱ:²=ùîΕ¦§nTæ[USöÝ#¶ÃBŠ“%Ÿ ªë*fє۩ÞÔÍZUE™îøm Šá!ÛŒá–T\°Á’²ÓM Þ+r§Ióú$›Ý#¬*“è;¬:ÄlØÝÎz™p‘/°Ú%Á®¾n»uÇšë¶û²}·â8B·®Êë.È8æ$bEEí´º‹Âv5Ê#,ÚESo¸&©['³†#s¸›|üÉ&N—AÜÎ$±ã"íI€áÁ\k®ñoG팜¦Ú.eœR»¥.ºžäšÐ`XMßf¼ÆD·Sè&Öô…a›ÝľŠ,^Ôçq’<¿a S†|˜aàE´32¬—tsùµ.O%œ8­„ƒ@ÀZ jtAh]X8Ç>C¸Ýž+ÿG€ŒµE&OQž&?5Õ¦Éx4MhM“±ØE#ªÍTÄ* 1X|ÞF«-QùMõ/» (IFW ÒWUžƒŽø…Èy•`G"ˆIEéªì iÉ>ÔeG9–ö¥/”˱õ ‹ ›Y•BÌsCéÁýw}j\ÚtŠL®"ì`V´> ‰T ¢qÅT1¡¡UEÛm#–ÏQ¹¥ÙôéÅ#t =-S&óøÞà\=xž0´ôï±õŽkÉ:¯kìýã››ë‹ïÂL!ËEH»ÝWûàÕ໯x“6Ø*áÒó‚€FÓk™¯Û3=aiÆñ«P7 Õ׌nuy¥:–uÁôôÑÛëh´ 9öèObï"ˆÑ.FuǬÕFc¸£¶adP×­·1Œä=†‘ɰðèêìÙ`…hÏÝ#æðÒ„±~Å*ÒŒD+ŽYœ–$SS Ʋ XÏ:‡¢KS: k y Øê¥‚ßó!óÚ/2åS[ Eq-2ú@«ÿŸ ÝhóàùU…î¿þDY¾”2èC,þ‰Ó> stream xÚ­W_oã6 ï§ð[,q-ÙòŸöÐm±án]Þî†B‰×X"²Ü^ûðE9¶“tá—Rù#E‘´z¥zW¡£¿®®®ï)óh$,cÞjë¥$H#â¥aÐ(ñV…÷Ù¿}æj¾¤iægÒ›rNB¿T¢äZ è¾“]Õ²ÿµúÝç^ä M7NƒŒoIsƒïpoJc>'Ì/çÌ7(í|E±_I¤ŸêV…?ÿøëÈçFÙnX›¯ZȶZïœì¥âÈ8õØßÔû=—E õoµR(¾[àJ×NY { à9H1§Ìu²“P½ª9©Iå’Ð gÕjÌHùZq$ä×[—!\™èiêŽrpb$_ÂJ¾»h¨~ÛˆM5'VW WÏâªi× Cåv6¼íƒ78ãã<^!ÚJY+úu§›N;~‹T[ÿ†9MJ­kC‹j Þ %¤Cتz‚QpÍ{wjRˆÂÀý];õ¿¡(Eãí™Æhª“²’%.ú{2ì DÂwŽ'Nƒ<ŠðÄ&¡Xz|_÷–D®–7_!~pû5Ò¡ÂVX8®°KÉÍ®µá‚§×²7¸ÙVûf'Þ67N16bó‚BØ¢0×w¡p{g,ÌӘ«>ÚXɤ-ÍúI__ lþ˜x™iþ$†æ'YÐ$2þ¬Ÿf§ž¸RüðÄ7›naZd±Ñ{ý/! [a‹ñ8º¼Ïè¼M°HO4ÀàoEâ®ÞžthQH‰d4`4Öüp8,léÊß•&\«à¡Ë`»¨¹~¬¾™€ó”ÞÃ­Õ 8Ú8ÜëÏi.Œ’ !9†Õ×T†¨ÍŽoœpÇn=íEQq ù|Úîj®3ÌÚéN™Ñv°‰,w¢™M ƒ”å&9& æÆøÊUI,¢Íä%Ý‚í¸,;^º(g¦ fúФQ×y·w7«;Ôºyxx¼{8.Ñ+òàûÍðZHêý‚ä¤þÇ^«­Öf êC#&†˜³©~ïåLùé?´·•©ƒ³¸úûy;}Ü‹‰W‚æö«h®kÈÍ6Äe%õÂm¸[×âëQDLJœx‡PÉV(}Ä«Žy)Ú‚S²˜m¸&³ (9‡K¿ŽŽàâ÷G pä6E—¼Ž¢cïÏ]báè[pß]:ÀýˆÃf\Dߨ|ž7LÿH;±Ñ}3,Æ3Åv &#¾J&ÞJUw ²ëô£jUuºõáÍéf„¥&cí|¸4,íï§¥ûYEDÙŠñ ,É …&¼tKª3Í ýpÓáKìÔUýÚö³þäëm\0ó Ýl‚×JÎú'“áÌËÞ-ð¥CÁ…ÇKûûª|Ö¨°î-í˜+œð€´¶ü·=þ%Á%|%{]ëgõOÃŽ_ëM—ÀgŸññ«ãú>bã¿=aÄ d‘E¦÷É'6w««í"Œa endstream endobj 627 0 obj << /Length 1549 /Filter /FlateDecode >> stream xÚ•]s›Fð=¿BéM¬óqIó ;rÆìÊd24“Aè$Ñ"ŽÇ/ýíÝc2N¦OìÝîí÷—ÄG»½Áé{¾8¿îHp6s}wnGžÍ<ÇyÜa™ÂÍè“u¹òRêñDx¾0ü~L²Û®õ€ç«*‹ËDeÅøsø;p F fbf˜N=æ {40'¦÷e¤Ë$Û'ŽíYI¹7o}3<¥.€¢|6=CèNåNËû?n´¨ò\é’$Ní‘gS#Ѧ Ò+ka¯—ïn?hæ¸l:m¨¶­ ¨Ó>‰I©\צ~K6q垀h¤Iùˆd¥ÂË\ê­Ò#Œv83o4± \¢â(«4"i"ð­(Öª¨áÀ*dIÚ"ä p5Ý–û¨¤WZâ•–ÀMnðÖèt„+­eFo¾VR?Ò+d;ž¹Cd¸OHHBŠÅêG:Z§Äë„9H{Ìem*'m´±ÖÝum5ÓFýEWk‰•„apHãZÑ‚o°á$º&h ‰/*b]eiòÏØæÑÑSPDÛ²+ΈM!‘¬9¶‘âä ”5Å °àÜpÁÓFÉ¡Lµ†ãÙqháT{¾k ~'ŠVU^ÇIÖìŠ(%JU•9: åûb´žˆÓ²ŒRH=ÈBš0r„mA deR&²`æBXræ#ë.‹XfÒ8±w{ì'ƒèüd°&ãÌ-æZýP!&ŠcYö 4qƒ<Êðîïª(›;zÚ¤ü@Ðt«¯ãZñ!TÔ²¨Ò’áá^ÊÊ^?‚óFÅÕdRª›+hÖíÀ1:Jñd¦Q=h븖¤:‰q¡âTièê¢(Žò¦3յݼöXà8øúîæ|…ÄG}ÏÑ#kb¿‘q.2Ì@nEƒ ×ñ”ÉÏ®` 2†¯L*‡º&¿G‡<•¯MìYÀ\0b"l6³Q«Å<\Œ'3έÛ~W‹»›ù墵È]>W–—áõí õ-wúK‘ª,uù6UQéŸ!pm1Z-«åý1)Âóû¹‡ä//nßýù²ÆØœynÐçVk€ï›àw9ûØ'ÚFz7¨Þ÷§tbH¯d‹µõYuÐê¡xû6¨­®¥~ì(ÔLA4ÿâç»yþ2Vr»Mâê¢ø$>?çHhD•ÎZî-ÙdÈOGn<1äf¾|ÿaþž2!O5˜ŽoòÞ»‚¹œŠbŽ9.XKÝ/®o¦iD:1݉*§¯ªR™*†Q—Rñ­ T7kÂt…‡œ7ÍR?Ðã¥ÎÁ%R•è,  ØSZ[ ªH ®£‚òpí¶Ò–ƒ¥ÄÜ`Úï m*ø V7§eA»h3æ{³v™jr퇌tßp\þâRé¦©Ì ¨zOìyªÛhà@ ý×1 :z¸‰Êˆ‘VEó8*O&±ëÖ§Ž]Á†|¸Ìõmr ”¦d̵„ »çã°‘:”fÇóÙdÂ3vu`€mÿçxʼv1Þêè í´Ú«Ó×’ú”Zñ9³§m\MӮíb&e]QÃ!N2ï®+˜âÄh{²ŽŠ“è´^ƒÃæg;”'ÿÛµÂõ –DcÝÝ|^×ãcÀðs¥ ^ØG\æ»n?i¨Õàb€¹nf^)ŸŒAšÒ*M)7žk GqB9Ö²ÞÜê&.Í–TCõŠ5Іçh8¿¸Yt/¿`I5Cà飼}”µ]ÓÇvRŸ IÚ&ðéhlɼèÖ§ÁkÎ~ÓpslÑ÷C’R“õú—:¤4­àÇZY­±ú͹3³^ÞZÇ ¨w½¼_¬B¤¹^†·§ÎP÷‹›ÅeعqÍhô¾ÂÝÍÜ_è†÷ç¼]1PMãptŸËÿÄÍ©RÚ"a¯jç6ïäc÷”-¹Ö;Û)ßׯ1&Àª¯ z—DI}¶&¤À´ýâüÊq»“Ç™i¯®Ï8÷Q–ཋðÅn2Y» endstream endobj 657 0 obj << /Length 1431 /Filter /FlateDecode >> stream xÚÅXKoÛ8¾çWøÐƒ¼°Y‰zXÂnn¢d]xíÂqm0í%ƒ’ëdûÛwÈ¡$Ë‘ÑìiOäp>΋ÃáHvoÓ³{7—ï¯]¿‘( Ao¹îyNH±]ÉeH}ÛŠŽ÷}ß·D–䤯÷ÙªyVô,?]ØFÃûkÏé… >ð”ø!BŽ`ôˆo‡(þz1ÿ«? lÛÚðŒKVò‡‚KÁ‹ï¶o}ÛxQ4p€rö¨kEÿ®”¢!u‰ë¸ÆÜE<^Æ/p\ÄŸ§ã˸‚; üÀ¨¿›].'óåƒäùP¤ùŽk5iÎÊp€L$´!‚ñòn1»=†â||Û‚þîãüêë;Íql2ò£¶4mîÿcˆãlÜ¥ö¥ Z3¹qºô=¿ÆÑ.ybí}¶ßÊüP|ø5á/åKƒè03Ý*†ÁüƒÃ³Úþn•óõZ¬ÏÊâýq.’—{™ÕÒkذ+NGa‰g¼ïøÖ3ÛîR>¨x'?ûÔ·˜ì1åÊnUTÇD )èвëÛbˆSaX–t ˆ•ùHý…œUž•Ld'¯öRÂýFBæÊüñ+éÞ×¹zQ¨9Jµ¢ Ó“B&̰ˉ~¼^+óà%w IPê¤V#Ì uá65±4…pÅ uJ˜!²•™fy‡=¾GBÏ{‹=¾ È ¨3dbæïRxÊô×( 6Íx2@Z…¤##:î[»Ñ©fLXeBV YyËKœäk›lÑ”~˜x‚ÔZæÛ–…ð˜@8\7h'¦È²ªy*ö§|U’ºDHäšÊ0Îr¥°‘ê­ ç‚©˜FÁq•@Ä:OScÁ•¥v °"á —´'0~§Ô½ï{6È-r)þ±°äx 2Ç5jEcMI•b#2–"äøfk¦Ò3¨=<Ž…Žë1éö^`àñV¾/ pW\šJÄc¾Ï]ÆŒ8)¶[<—#‰™·9ŽXp¼Ó@ç cÒ<Û dÓqj@ß±Á¤4A²ળ·Û7èØ-?´´·~d Ž]>áÒŽË•ÊÁÔpÐL˜Ô" ê“„u¬—°/BK&œf68ÑÕ²¥‘cø‘[Âs¶D•ÎÐÚHÎÔ·@ÇÙ‚ê Ó¼2ÇnTƯ!'ûl›'BÝxžœìAÍ­ž µ òñ N:Ê‚êèàÑw¢_ h¢ÝýÌåø[ÿT¹I`VŸP^ÐÝ€ÚmœPº"¿í ©‡ÖþÇ›Zk½õL3ýe>/'Óø|kí¶ZëÿÖ¡¶Ž£é¨ë«ùºcmÞv'×ݪÎ4ª£³j•I¯{ŶOomõM&±OÚ@u9Š“KP_›ã¾°«›óxƒêÑ3çÝÕ%@0ýÖÛÂEšî‹R}‰'ääs¾õ·€Rhuïá áu×R¨ÓÚ//þ¯­7u endstream endobj 569 0 obj << /Type /ObjStm /N 100 /First 881 /Length 1497 /Filter /FlateDecode >> stream xÚ­˜Mo7 †ïó+tlÖJ”DI€Àù° m·¶´5|H“E4ðŽ´ÿ¾ÇMk;k¯ïÁÎì;E¾¤È)R]p¥&Cáœ$å]j‘+ϤsµgÂ_uMnNÕÞë®Ú{-¸ZÂTx§v»×2¿·ä¥e×Y©´âºéiÊzÑTe¥Ö\Œ!#t„Ìš= ô4•]”¸ ‚™Õ17 ëôŒ ..æÈJ͹Í%`CGsÉhîh¶u”§Q“LЬìMš«4WÍhnÁÀhn%! ¹u{‚æžͽÙëÝIH¼ñ_¨yÒÄ8 ‚Æ8thÌ%ÌÁpÅ’̰Xœ^ÕˆBspÄùR1*©¹NŠ‘Rñˆ +´ÄÛ‚šF TX¡ ¶ó']Ûª°@Á¼«Ò\ÛÖ¦Ù "-‹Y)¥„û%4Mü”yW!@ MÉ¥‚‘š2B1pqÉœ¦°&)V*""˜Xª¦2)JS…! #R3³ÑË Ä‹©›Ͱ)ʸh.üÓ¬°Â´bÖÊ ¡¶I¡Iö¯lK1•ídvŠ …µ]N„^¹É™uâä ñ´ ÙH¥…j‘`K¹&4ãû\a±ÂÍÜ ®C^²'(ìxV¡IîUab€'Š%{äT6Yb²l¤±ÅiZ®/®Üþ¾[bJµ<6¹;¼~-ã ˆo®oØJd×78œ¬˜ož<™ËËõÛ“Õ•;s‹åóC·8]ýuåÎ'~²…NÿþsÅo~_M‹g,ºº¸úï²½>-ŽWן.ß®>ÎTœ}¿z÷þÍÓõ_î,8ˆî+t­­ûã9˽¹D5á_kTžÍ•Ãl²Êa×;&̸iqòé·«ùþÕû‹?¦ÅÓõå»Õå¼T8_|·x¹xvç3î-»J]}‡ÛÄÔ‡h×ê{³øEß%;˜yâGëÓµ[|8¿Z£¯$jÍ'ªËΰ”*HÈ“”ƒKôVÓ‡À)_ó(¸ogüy˜^]0~=¼;M¾‘4ÚƒÏÄúaƒs…u S÷ÙÎÔZ}Þ¦Þ Ò4fõéº{;¿F<‘¥úòî±p8F#sÇ{³ÀŽ–>Nx|á#•xçØÚ|éƒÐä­MÂfñ³»Ç åœçcØìk«=ÒÈÑ–v‡¥—"•ÄÃà¶%­?¶B›ƒ‰aÙdŒìBem±ì›pòÒûQþ–hp yÎÇ!ìg¨”ÖYa9”Ê{S*^¬_§ú…vGñÿmÏ&æN¯s³ ºÑ÷|e«£tàwZë‰×êX—¾Ã'ÇàÕÚÛé­ÿ,B–ZÏNáÔû[œåÑÉO¯öj)l®l)nA·´ ·°©eßlLÞǽڢoˆ´›9EKÛbC¨s&Zb8¶9†JoÓÇÖ*L«ñ>2õðoÛužÔosYÊWqùÆvE‡)rº"7±Iãž{9²A±R÷â†Nà¶b M6ør¶–!µLÿÞ±Rh´‚}ä 웸·I±ÒÓ¦>„e¼õQÆ N­0÷Œù,U°%ﲂ} RQÆ6—TÈ•1§¥‚ƒ{Ý66›,άÿ•A¯Ñ‚ÇÖv¥MÝt\nÆ’u-i6S/ö‡s!Ž)…©i÷Xáx¯ylsbAÑ-T›çüfߺ²·oyCŠu󴰛ћӣJøŽ?Ãhù²ž—G×ó2^ψÒÄð ÆÒ0RdzËÉÊoܦw‰c`Pl^ÍB'»ÅbºŸ8MF°VÁ0ûŒHê´mFÐïÛ‡ÅðC#9¹éh»­8ÀqJ/óJËczE½Æ!h¬rûhû1}M endstream endobj 674 0 obj << /Length 1268 /Filter /FlateDecode >> stream xÚ•WKsÛ6¾çWð&jF¢Á·˜ôâdœŽ;NÚ‘Õ^šŽ&A S>T'íô¿w P’%»­&°X,¾}| ˆy[yß¿aöû~óæêc”z ²t•z›ÚËà C/gqÅ™·©¼_ý;¾×b˜/£|å‡, Á]Ï+Ùmi²¦Ï§¾¡hÂ5}ï5ǽÌ×ã~þÛæ8²ðŠ È¢ OLò`…Þ2*àd{âOwW`1)2Çr_û}?h’Öý@>ê~Ù8$¨g÷•}%hTô(;ðc?ã .ÊNjÉù'ײïÒºµ§ŒJ({ŒÅ°%h“LóÇF,È¡$ôVàP– CÌ[†QP¤ù²o†‡ÖÆåÜû´Â|{Œîâ”dþÓN–;J f’ûZ­¨Hª{ú–}§¹ìhÒNÁ‡I_Ó¾µS¬D@ÃÛÚÚØI«k *ZW8Š kP‚¬ú†&ÚÞÖ *bÎQ$;¥yÓ¸Þ€" 6~lÆA’åÇh!\ÿ‚Ö2Y€ŠýzlN¢¦¶`kŠzÅA–§§‡v³y³ØöB˜À÷QÐ ÙÄ¢µ¨´,»²©¥â”+%·]+:M»dm­í¸¶­TBÉATI?ô’Ô„ùÖ²i܇“y»Çj­ §ãª¸> stream xÚmUKoÛ0 ¾÷Wø6HTK¶ü¸îÑ¡C1tiníP8¶b{‹¥Ìfý÷£EÚN²\LêERIÙs Çs¾Þx$?nnnï„t„ÇBKg³s"Î"Ÿ;‘ç3á‡Î&wžÝOezèT³X‰(v9g¨¬QÜõ:ë*£qõ=­U»ø¹ù~'aI(ÂÁm±Xpg%pOnï‡3¾pMÛzúñ°DÀh5(ÜMuŽHW*TZðÚnŽ –z³”Ün è[E^v¦Aë¼Ú-„twªQº;w×â2%¹7º8EøœŠîë-w.W\°D ¼˜Ù…ŒÜ´YðØ-ú¢ §eìÚ ` ¼T£ú~P´;çµÒe¸¿^âfi†½£¾o .]° > stream xÚíYKsÛ6¾çWèVj&B€à£=9Žœ¦ã:®£LmIl)Rå#ÿû.^|ÈdO’N¹ˆà\`w?|X¬üÉfâOÞ¾ðÍóõâÅ«+Â&ÄG!‹Ùd±žDEO"Ÿ"BÃÉ"üî]nù¾ÕtF¢ØÃéÆbû^•m¦Ø÷6ÓüÚ!·Õ”ø^¹i[‰zúçâ˜%™$( I(' "<™‘&3“,¦”Iu¥%¤Þ¾ê4¨÷/d#ð–B iD¡_2ó¼½~u‡ô¸Û²n6•øðÛµîªÄ?mÖ©k¶¼Ñ-®‡«ù¦ØK[0Æ« %tG?2³ß–ú¹4#V<ÏEj´ÕV+Ø ^žÃF´‘Mg ó½][7º¥ôÀ3«œWJ¼)Mò©ë¶X5YYè·û¬ÙêVQša°äØÛ´;Q4öË"©¨DÓVFAó°7³–k¢ObQÈQ?ADË/üq,iØIì8¤¬žQˆ°€šá%”šoÍ„Y±.«ïYWåάʎ{м{ÉŒq{^×ÖUMyðyãà2}°sŒ\—y^N -ú,_y•ñe.êΨˆ*´aû j6¨à;áð†&±ž žPߨ œpÀØA„)Û \ÞÍ/óé,ô}oq÷îíÛùcalÂþ›ºáÐAõ3B}c:ާ6»y–ž³ûåò/±2à÷昤ÿ­Œ›Ñ+ÞöQwúê ôË|Ó@…fü[r—H&»ÖßYüµcý?µô~ ôúÌÐÖ°DØHç (Âa‡·×ó«÷wsŸ( ;>)+Ú}u#.®NxÃÙBãnT*ö¢H»^²Àˆ {Z¼Ûw4F>ˆÎËÅg‘?$OôÞÝûO.Í1 éYÏõNù°šøu~³pèb>Jüoï>0+ N÷•ûo„¼w7æw.“)A¤ÇÕK—"”ÄØøxûF²ìy=Ú/Îp0EÂ7óëùâü–øf±ˆÁMqÅ¢÷Oò'É3ªò+!¤Ÿš J>Sñ‡ï“B¤.¯à±Y{'ôQ6¿¸üY·ÜðÄX<ð;ÕÉ\DÊŽÖ•¢`)^•EóByq´Z}öç­0 •> („JŒT·JypŒ&tœïU¥Le¦áœÜA@σ“!ÖCÅ&ŒXòxJMvW)eô ¯¦˜IÝð‚mÜjÝu:`¢4:°SLƒ}×ÅMå¬'ÜE‹£³[¢"B"<²VnÉ ñj!OÚ –çã‰X(•Ù‰n>^_»p9és_¥Vó¨åàÁ¥<}ÛFè.™Ô¦³2²ÆWXúaʘWëžU™·»Bwª/Í—Jnô˜|ÄF#Œmó\‹î3ÛZ”F1 brR±‡[¤~‡y%»xfÎPæéó¸"6> q<à *®á9èÅ,ú \r3ß+âdÌr‘[Ó1â èP\Ñ›“xÒú“!O`ö…{Â¥EÃCÓÁÒ ?`c`O  §~÷O4ÂïFˆ4×H†·íüÁLtàÒÁI neË>•J½u—y׺5cUAÊ|%L£G‚ÒàLæ&O©< ìr» ËÓ>vg0šÄ#†hrpr)ׄÓŽj28êû¬çÖ°t? ÿaA<Ûeej|Ý_<¯®(Ú˜Da³àwl55 FŸÌ/þ!¯§È endstream endobj 671 0 obj << /Type /ObjStm /N 100 /First 874 /Length 1404 /Filter /FlateDecode >> stream xÚ½X[o7~ß_áÇöÏÍÇ–"¤ ­”ª(ä¡mÄ…U…Šv«\$úïû)¡IÈî¸4ôaeÏø›ÏÇçî­^RIÕ,©¥ê’ˆc´ÄÜ %vJXŠ×5IÚ=iQŒ-©vŒ=i—Um%™´T>iŒ?vŒLÇù…q&‡za¢˜!D BSHh æÀ‹øÌêP³€ÙBcP„X*˜+Å0× …„…\Á¯Ž(×ps B(;Äç`î\Vo‘„p -Ah„IÙ“Ð$)…„ØF)$ /ç ´ŠIØÔàÉ\­ž¥„°‡ªýí©j%Þ€Ù ¦Ãöj¡Ã æNQ4ÂÃ+˜ÃDau¯`n¥­VÓ³tV±wI'iúéç_`HÊRÃ={öBisõþý«ÕãÇ3øh»¹Li:‚® öŸ?;‚ áè`;WÌñÑôâ|ûæåú2¥éų£4®?\¦O|§þ±ÆÂëßÖ«é)¸×›Ë ÄœÆç«éd}±½:³¾˜Ãp~õÃúí»×O¶ÒÙœ# d„Ëzë¹(½Âv¯ÏÁðm3þã6qF—Îøˆ2WˆIšá¨·Nxê”Ã÷àôYd{±Ú$—ƒ"™¥#1勽Xh:œ¨Ö’ 7D¬%Ã#öc™-©rÏž1Dª`ZØZîPro¶E½Ï ¡:þ(…†*¤00Ò±ªæˆ«b…®£ Œ`Ù=K[2‰§\5«è®€BZD»BwbëFÔ}ipuþ,¸zù¢àš7›-(ÏRTÅéÎÖóújzyõëåü|ünóûjz²=»>Ÿ·(¯¦ï¦ï§§g4?„Popi0ªƒ9Æ Òrä}k–!p‡³Î^¦éùöt› òo^Ÿ> stream xÚµV[o›0~ï¯@{ h ÅÜ´í!MIÚ©JªŒh“ºj¢à¤¨`1í.ÚŸíc§°åaÓ´‡Æö¹~çô\pŒ½áË“³äätáFdG¡ÉÎð‘c2&žkO×HrãÆœß§ ÃÔ»c"׆KbI‹½…Sþh‰kjùYg8ï¨åMLÜZ·É»G9=]¸QÏãØíx¿øvàLÁå¦x$´Ü¦™)eÁX‰áŽ-˜_Òª‘Ï1³— 8·¡@ ³û”ÁmWÓ k«΂0i ´¹©GË Ì´ì°æP°ôNƒ`5œ2¸ÑHÒìõNP¤«î¸žž1Ïf¤Ó,D=ß1»&O™€èùHäTÄ". ¦<ˆ ç𬉖T|Z ôOV˜6P"¸šÂƒ``K%%Û« -¦ ç¯à©,¢~:¤ØA¼`EZß4‘ !ï(Ä$?"ƒˆD\Œâ óìçP:"qJˆ5¦_YQb<)+jb «§ S^P¡/ Šûp‘¢Hï&ž%±5ž‡íjž\®Wðõ²ëHö¹ªó¬îûäÿCÀÞÄÉv³zÿ,+«C> stream xÚ}UQoâ0 ~߯èc*AHRÚÒñÔM°qÚ1E§éî Mi¥ÒTi8Ä¿¿§ ¸éžlql¶ÓgççåXù”< ¦ÌwÁ?ò$wBŠC:!ñ0ó'ÉœŸè¹HÅ¥ÛgáQƒòVnyÝr÷wòM‰œG LŒaˆGŒ:}éX6†õ~Ôw}‚^o üq©¸lKQÀ@ ²æ.óÑQ'÷}„+”jƒãñèÜÕ¬Ýéí[Ѹ” SÅs5Ø5.Ô¾2jº}âÈ󠜤([2ÔH±“éŒÌ%ç µ"WG3•| ÐI@Ù¦5(’ge«d¹qAe¯– dZgƒ3­ïEVæ§ÛóCq{¬ {W·{okùÝÙË|m^s™~òc8òð[6U¹5ý .ƒ:i ²1mÁ307'D+Sè€ÖVW°gfhB—*=·1€¼Ôw%èwS `ªP¹ÎbKëÙc{ýñIª@×Í–7)É­=),……Îy£Ja]o ÿg<ïj´Ñ·sÍìa hh¥ ï sáÆÉÊcY¹U`l¬Û¡åù¡êY¢ƒñc–¼¾¯0âù‡E]ª}âå2ž'nÄи ® ¡¯~Ñ óÃöº\ohËõ†zñöMU2µ£•i­N€˜)·ï“åó«NèFº’§ÙÛL§ r:Kæ“Õ ¼§ïK@c Sf¼t‚’Ùóú-^‚ßb½\¼¯&ø«­]ÁΑnAˆÝu£Ø]?ŸÛM®·› ¼ûnì…´PÆUZVííðm¾—jòæ9{Ã!ju++Û•"5CöÁ©ä[^~öÔú¥pØ}wÀ‚^>¹°0hÇÂèç •¨w€›wÁÌNÌ.ê¬Ò&«…ê}ÕÓ£,U×Uq×Ýî‘“9¹{ä=gõ[Õ@&nH×eï-ªtË­ÏêpÉíyÄ‚O¢U—€ßc„QJûÔ#!ØëUlÈ\þTƒ©ç_ÿaÈ3?rú> 0e!PeÁÍIòðÔÏ΢ endstream endobj 799 0 obj << /Length1 1410 /Length2 5940 /Length3 0 /Length 6895 /Filter /FlateDecode >> stream xÚTTTk»¦S@qHA†éî abf†¤K:î”nDBZé)•Ž;Æ9çžÿÞµî]³Öžýö÷|ïólvf]}9k¸DCñðó% ZZjâ P ag7€¢!Ü$ìF ‡Iü·„ÂøA(LžPwuð øE$øE%€@€(þW"!P¹A­Z¼u8 ‚$aW€;{" ¶v(̘¿^œ`.¿¸¸èý_å9' ÁZ ”Ä 3 rèÃÁPÊó_-8%íP(g >>www^’ް•æºp‡¢ì!H b ø   r‚üFÆKÂ0°ƒ"ûõá6(wÀ8¡` ‰©p…YCÌp€¾š&@Çû¬ù;á>àÏÝøyùÿn÷§úg#(ìW1 †;9ƒ`žP˜-Àêè(kò¢¿A`nï/ nxÁùG3\€ІcÈ pþÃ}3 0Œyðÿ¿ð«ä#þÏ.ÿ÷ÿó@Ê®ŽŽ¿Âœ¿âÿ# r‚:zþIÀpÙ…Ñ…£Ø¦>‚üÖ²ÄêêôŸQ5£9˜-†ã<üB¼À?· E*C= ÖºPØî7“þÚf†#Ñ…#¡??9˜* ð?bÙ0Ÿ$fc¿C $Fƒ¨_ËýiC0*û÷9”``¸õO9 ‹@È“CŒ% ðâÇèÖâñ‹ð>^…)`0ûlà’ŸkøÄxIþÕìŠ@`Fÿ"fì_ö/ÕC 0ɧ)8øA}UPóq…Ü-wžµaIüÝäccžáÜ'D¨¥1‹å8ýŒô"åOÝüÊOìÛ´å]Ž3¦¿y¡«ïÔx òÜQÞ°½c3uuˆ=ïuÄÈ2EÑ€•ó(QžIâ ¢K÷vøõvbkÛ}v ï»U]ãÝ9¨ ”EÕƒ›µ[Û+ Ò5iŶW¢­ú Ö„¿ÓÝÍZqŠ\0{‘¤Ê¢!ÙzBç^~}©o ޲ûvG¸¿º[ÀÚÛs¥Òƒ~FE!Âr£¹WäçYoܶR©¼¬TnÈnY÷/r%WiØ¡¶Ì™ï¹tgÖÓumçiªÄ=K͉ˆ“Š­øk6U[ öàn“qÈñó(§4‹:yž7,/¨ÁߌžUвm-*ÛA §½Ásä¨8ðèé ,i3¶Y°KÞïµÕ7ãRþèÍÑ÷ä牾×ýìð€1)bý£Ì@]áù²É…MMâL,Æð]¹/$¾V%6…7•°tÐI÷ —ê¦Îð…¸­‘¡_ßÝÖ¢…!fý"¼Þ^Þüˆó,¯ ¨ƒxyiÈËt>îj§Éøj·S¸Îaû3 u€É‘ÕºŒfbžqd¤N†Œ¨Æ}õÖ IuÌðóA(É#'¥N½Ul„ûP8v{,mâáŒúX®Z¼ˆÍûý ¿hV"lVõŽò+)žDw6€^½³wÁîd¶ROHòõŠhŠ˜EÈ;B³LyߘÐ+ÈØ’œó¦²j÷%齆gr±i’'á‘èøãÚYÏÂPr¦°—Kr%·6e7ºv©J=)îžÔi“ÉȲk™4f¤dÐÜZ4çk&›)óÃê?äðU»i£\Î÷xB7u\œË‘`7m]KfƒÞòøýÝÞg…_"2YÀ{àN*?JPxÕÕÔv:µ(ëv'tì h“È+BÕtÐNÛ@—"5iœËÉ.:%wmº·øþ‰@Ý¢"02êC¿('ºžÇN‚®DðqõÉ­P ·Ï;Iã7@n7nR¾Jíyºyá~´åLx>05¨k}j÷›e;ô³ö‹%ˆPü|CUÝWÙ©ýÁʃ´hÁ$)‹ÉûµÃ•«nwZ®(8å~f4÷%²nç®÷¨€#—>ïäê+òŸe4Õ˜Vrë°Ë´*š>ÙXpV¸I©0À»¶=~¦<‚ZlõqºWÂf•îV0¨£ö8QÂ6^:˜v·‹PïSZý[ÏñŽ‹ë°¦0ñ%ë·ŒYs¿‡˜EË$Þé++MUÇbì$ÚfxÏt¹);êÑS³áåBžj´°k§Cé ²Ñ‹ì’e7¥ïJiÔiV݇¼Õôv:L-ƒº3g·ÿ„ g>%[Ü"G)­1¬®€ÿ¾A$… ·ç ל3ËŒõ5pŠ·€”<:¤¸AÖˆ¡ñîHW¸åö:ï±5ÎM2’‡ù/pw.Wb”ç7Z(Ø:ð"! Á¯%9"â1wÓ"÷'‚Ê?ã¾Åö4¨VÕe2¾áœÈÓÓÄt$²SÃçØ‹3´¨ªàxNzá£$Úº cXÇŽÅžKd’Ѓoï÷±`]3Šß:uumáH&—ÅÒñN&†]xTùlG×uX,DíeLþx·èI>N¯ô–S©§øjÁ)Áð´•{#8=¦­ƒ]Ø3Øñ’ˆµ¶×”y¦¥N¥¬;nÐüÅs©j/“9—OvMë}—¹v//ÂÊ`-Mþ|Þ¶RHAõH·€rXÚ8(s5KAZYød²’ÂŒ-jtS#jä]Ÿ@Åæ!â}q4/šèÃB, ÅSû%ý ;–þMu›,䉾­˜k¯=“ýŽíܼҠÂtfŽ«¬«LT,¶YxÉSø*O»FïemÔØd9_‘r·š~â°Á5¼é¨RãálÑŸ ‹õˆ?Ååë{·LLr1˜cªùIÏ}Ž×1ØÐmÏ•#JšýDzœBRŸÌ¯Iã{òÆJª44aBÕW¾M}kTGbg¼Rd§>3>¹j—o²œ³˜¹:Tü û­M:˜äÞMáç±|¹ú.j*7Ø?ö7YÜ„§ë…×Ì‘1Û1¾w1Œ¤ÐM.Âya”aþš`ׯ|­jÝ~Ê?Wévb9‘®¶üCµü}ÈçbÉÍucÝAwÇÒØåôHÎ<Ýš‰pím7îx6v§\…¥KXOñÂJ¢j˜WÖЦ־ ¸¿Bh…ýê6Å—[žóJÆ Ú‡ç õÛÇôL”…² nßrµÅn[fŸ^>ŸzöÔê›+<x"xT&ÁÛõ PB-èO÷Å[1HyÆŠÇÒÛ§´;fÁTžãíè»{ ‰õÂ5*·—#•íjy$ý̈{ÀB¯MüZý³‚?.Ø®VUSŒ½Ö Ãz*!¬1͹߰`ìQoëÞVÁøìÒX fR`-…Vž‡‚ô!ž-íÑÎl—Ûq@ˆkèý]ü!ç^\¢£XÀ•vä¤ðÊ-è‹"=U°}ìê÷ã[™Ó-å? H‚dßÞ÷À D€úª“%ÒîPÒ°li}}âË‘Þâ­{˜\7x|Œ'͈G?vþÔ? NìˆÜsübÞï|í»,jl]ü¡·wCL¡Ä²JCªèrb5¼Œø=‡¥®ùŒ¤­âæʰ l–Ú½e,¢dŽk)9Üо_…¨y¹e¾U ×”¥Îö-1œKîµRÓÆ§·R&¹ˆýûÅÜôǼ%›È™$Fw ¢òé[p'@l$5üÒßGçÒ¹^ó#C6RNG› Ô×®b¹—;.!õQõ ®1Îd&/¾rpu5~¢ážþúííK¬mr?Él‡\áE€T\Õ³wRC¦¼‚À¤ÂQ/õó±ïàtEåÉÅ[ò6E€¡t¸Ð÷€uÜ‚†‡æyHÉÇGЧžyVÉK»ï…—›~ÂgºýTC‚p®¥øn¶=ŽQÄÍÕ ~Ô×mk .ý¤±ý¨v¢`úŽp“Xœ>Õ[¿ÕQÏ™—öô­ä½¶™¹ª¹á¤ßï°!ùÚ´µ'Çeò¹Òâ$d‹éiÊ(O\4"O©Áô»6iä5©ôKÇàxŽûµcT_ecJ®b„ðwµW²ÖdZXCM^ŸÙ=›]•8uÝÿ©ê2-Á‡Ï­ÿƒò«ò {¨]^C„Èb³ªI_Ý=sâ!éóäV6•C„azsi;uTk k@°¤ÄǼSÍA¹·ç7g]Bi+$ëU&Ðz[Úíº'X0±ù±MEá羆&=a6^§¼fjS¯ªyï"£ñ:†r¨‡Š±x‰‹ƒ˜%Iwˆ‚£Ý”hæÞ…5Ž Â·7 QËI µâ<¨¯OÑ?h.êVZ7€¯ iÒ|yê Ò$ë;²Or”?¼~µþн(×›]|!í2¯²š¸oÄ ?Ò>i³2ª“™1qù¹PêG#~‹ˆ#b_|ÜùKŒõ¢RlÚ¦5ß[Å"+o¯8ú…ÙùGb´µ®ÊaH‘¹ Áa"M’×,?8¤­w››BÓí¦§ó<¦ˆ·#Ný–Ý)ü+-×ÈC¯’V<¾2î@²sö“¥˜Ú›ã¯eš‚Šg‹A÷,–ØôùÆ¥ÅYY¯«M{£¹±ôÂ'‹œŽaJ–îN¤“[êiýÞ9¢…ëYìsôkÁä§4 ^z õöÕ~Áz}‡{°y§v**e&"çã! ɤ‰ôÝœ˜­ÖKï+:×q‹‚´ÐÅ<ÉrYçlãe‡ºž"¢ïWï—»Z¨ŽLç?UI½;Þcfc‡>Å]ª¤V±I!vÜWõ×"cypn^öº…F¡èŽ0îlwçqW_"?`ç«T@"x-棚s_¹ c_v|R®Zå ®¶«T•^׃Ôj}‡Gç‰2¢M”šJNoQÔß‘û“hŸPí§Ä¡Fª ¬Ejÿ\®És¥óúÏ~?›êòåLŽ ó‹­û”w´žú‹[“wÞz) ¸S—rÜV¯MÁ7¼arˆNMxeíU w­i /Væ-õvÀE%:B|È”®r¿¼ê3-Ï“op.X[Š 5žèøh½fäv•T/eïf )‘ †žÌs?b–Q[5½Ï[“ QSj¥ëŸëd ŸÐXò­Ê¡5ÔÕrŸõË G‘RŸ‰áíÛçá÷…Œ~ñ½?ÃYXönEi„£IÚfá®àÅÀƒŒ¤®R`?ëÈê5ívjý,RªN¯üiø†êSey—IR¸ É£óôáTTEÇ$O+SƵ²Õ+ɺB«R\µÎ U´ * ß<"!_‰&žŽÝ,9À:“í}[R:;/{€k¡>ô:}ñ[úJ؃?2¦ƒ€’`UœÜ˜KŠ5¸Ü…2(ö¡ï#O’¹q³e—Ë©¼9mê7ÞÌžìøœƒ®%CÞIÓÀÃ}YÌ3c•f.g"¶V¿­Îböø¬#u/2¯ÒÚ·2v[Ãòrl¨5pnÖ¸à­Û`ždŠo„ž ZÌá.)V õU‡³‰C1Ðm¯Aê(?€ÝDMŽC?\l§âžÏ2’À½5I·+_¾ÐY*ب|8§%àwýŠÄB½–¶H¨½JØê0|›JÑFºûõfLè{sªÙ­eÃé XìÒf¯ Ýë‹hª(ys ÂÎ~8s#_怗[Ýà³`ª” ÚÂD%¥Â#ó†üšrõu©Ñ $Aª´«˜ÆöHþðÕN½û®CM1CÙåÉb.Å ÊO«3ï{Ü,÷³9ŠT›™Ñ¸Oƒ¦¢Uw;nF/aƒû.³€>„tNs1ôª¹k6éNss;ëÝÕÀï 'FôiL¼Ý|}©F¼m zªzïéó`×@NÆT½~:ùûDžz3 ŸÁ[Ñ((Ž*(å.JŽÞ+‰ ÑͶ KTÔìý~wdÎé–i¢ì¶Î:ÙûìµsXÙb[ËëÝÆ4I\MmûnÂK7tÔML @Ô—$O«A¢Åùâ‚AoáÍå‡W1Ñâ{ƒffFÖïÓÎÒŠ.oÔŽòHân ¹Éh¯cÿ|Jp§…â ýu£ù‡pW6™æ§7AŸán*º{Õdtf7iúMR7¸c-¥‹ó~®’7j4ëUÀ‰àXÊÀ¾MY¢m,!_Ö=-k?=•rs,©ùØsG‡õmÎ@NF’š÷r@œìaFêuYJƒº¦ÖÎ(#ÖæX!ÇVÜ)çžÔYöÜu# «Å.7®{Qh2…”>œÞ[¯ß&bó Úì|™uW<´LþåèL¡[™þÇ-Ó"¤‘W£Î:N JõÓŽâãõ¹¸.e?‹ëªXÆš8o[ø‚ÓWœ„*>ìpçëÃ>¥»|ñ× Ö÷Zsy§¡O¢Ú1°=ÓiE8Aoß9lŸf©²â±O ×LÖcTö0Z“bÿÜ ¨ÆpÄÞ Už‘Ž^ùªý‰Å‡bgí“.OOãêîþnC÷˜¢ç×Ïßíõ§òÌv½þ0°³Û¹˜ú‰r+ â‡Å§ÅEü÷š;ú“ïLN¼ËI ¨ ÊzAÖwÎÇHäÌ“lIR¥,“Ù¼*á¸ãŠS¬¦Ÿûñx¤¢ôA§åK¿Igy"1Öøl2GÙJ”ø)t¨Ä…E²-(÷L!ëÚŽm;Œ@“<&ÿX¨´m3 ²Üt^3¤Y'rC­tY…;¢’E1±ˆ•n@x±%Œz9 <ÃS~Ï¥u²¤“9ÃKþ¹¬4_ªžZŠ6ñrNEm.6ÃQ·áu˲±Š#­@¾-ŒZJ¥ë`7•ø9Õ>²`»5Äó»”:J{™jH),ØßRŽÖtwáù9Õ‚XæSŽÍ=MeƒC’tÏ Ç­éÏR.¢²”›‡´ó[“³t_DÖ’^DF}¦Ö•"4 bÇÆ“? |?“@o%bŠûú¡YQ'Ô"R€Þ¾§SÀ¤»ÃlxB°ò: ô?¼Ã 5 5 ïb“ºûBe4Oú–ÙŽ"˜M »ø¿Í²Z endstream endobj 801 0 obj << /Length1 1612 /Length2 18729 /Length3 0 /Length 19569 /Filter /FlateDecode >> stream xÚ¬¹ctf]·&ÛvîØFÅvR±+¨àŽmÛ¶í¤b£*¶mÛ6»ž÷íÓ§ÇùúûÓ}~ì1öšs®k^s^s­±ÇØ$Š* ÂÆ¶†@ ['Ff€¼¹µ¡³ãw[9e ©3௑Ž‚BÔhàdnk#fàähb@#++€…››Ž jkçî`njæ VSÖ ¡££ÿOË?!C÷ÿðüÝéhnj üûâ´²µ³Ú8ý…ø¿Þ¨œÌ€s+ @TAQKZ^@-)¯Ú ¬ŠÎ†VæF9s# #`bë°ú÷`dkclþOiŽŒ±„G; ‘ùßm@7# Ý?.z€ÐÁÚÜÑñï;ÀÜ`ê``ãô·N¶s#+gãüµ›Øþ‹ƒíß뿾¿`жŽNŽFævN€¿YÅ$þÍÓÉÌÀéŸÜŽæÝ[“¿‘ƶFÎÿ”ô/ß_˜¿^'sG€ÐÍéŸ\†@€±¹£•ûßÜÁìÌÿEÃÙÑÜÆô?Ѐ¦ÆV@GÇ¿0±ÿéÎÖ øßª7°³³rÿ×nÛEý/æNŽ@+F8Ö¿9œþæ65·cúgP¤mLl,Ìÿ¶;Ûý‡Ïèð¯Qÿ334IÛÚX¹Œ&pLò¶NS¨ÿïTfüïù¿Aâÿÿ[äý÷¿jô¿âÿ×óü_¡%œ­¬ä ¬ÿÀ¿/À߯ øçޱ2pøÿ„X›[¹ÿ6ü×@ à¿IþÿàH;üm†°é_A˜™ÿm4w”0w+š;™L ¬þvê_v5c ƒ•¹ ð¯¢ÿj&€…™ù¿øTÍÌ,mþi=Ç¿]@ãÿJþ¯Hÿ¢Î¤©©!!¬N÷_ïÔE)þÕÞIÕÝî/±ÿYÊw[ãÿµøCDÄÖ àÉð÷2°²}pþMÈÅÂâýÈö/–ÿ\7pr0wüø[23Ë¿ ÿŸÏ®tÿ Œ¸‘­ñ?³¢âd`cüw¼þ—á·‘³ƒÃ_Uÿuâÿüë :è4‚[Y´5â ²HËLwªÅÎûÑÛÍ>lWÚ ZTàWmÛå›¶Íýëç{M0cã$Ïg›û©ÝǾ íÁp7–UW ð2ŸÀ›Œ¦§uƒ²ãÝA“^)bú™F”çռ܄6'³úÁθ’²^É;ád›ÌÕ™Kù£’Qj},æo”F´ÚÂÓ3ÊÄã§Gªþ‘¡Á®Èž}|ºœXX ^lŸäS’$'÷Ÿ÷ FŸ¯.ß\wx•Q*ÁÏ’Z£¼‡ˆ¯´„›Ðˆè³COÎSZÙ_ÄæÆc ¦ýnB°Î—¨xà¢Ñà254åÃ儱Ÿ‡ý’Ä[ÞW!~¢æÏhéïXÙ¡§?} ”2Û¼ ˜aŸnTaÑêíBnNN ß8:>˜¥ÄùÌŠHå ­D æyPe8hÍñL«K©iNéDªÙðÁQ¯ënù¡_jO^Å™Ö$¦P40Õ.¯è&¯,ÁôüˆŠÿp)(™×" ɽf‚ðƴ͇a)¥9ÀeŽxš&þ$nýv­„ò%_©ÛÂô0†¾»øý˜B]ìj:†~',e°%9»NÝ^ &:ýX<"Á|ÈŽZRUo,&Ð2ýØÆ«n0ʃß~ê9&¼Ð{¤¢‘³+ˆŒÊÈ2¸µ|rÞj†O‹°·äqÅ–Û¨vçïõ„Ã@\;Àî ð(ÚÙÖ',â ' ½¡kóH’Úªæ”ËWSgÁJ6?9Ÿ¼HÉ–ööQ8:ãVò§Œý‡BÒµ¡ë›)ßâ:0L¿E>—.\£xÈi%­:ûpùµécƒ[†¹PNqß .®€ ¹ç¥º]?¾©ž‘wÚ?yTlh’œð¾ô—šUYWø¬ú†k»Víd€GCrï'êž§,w3©8VyK{“zó:§¶˜á©;^ͬ¾¹Õ›_%Ú¤LZÏs!ðŸ‰î""'Y§ÑÅ¡:Ò”> RãÕ?UÈ~ÈW«;&`ótŠmE ¥@*Íš™ö¯¸i„ŒA9ù„YÆ[ {EjŠŒöž®9 IEÃY Ž®œäçùí˜K~Šâ¬ j1€{"Oô ãDz c½ `Íż›ç\SgÇ[à HÔ!W oï@£Q¿Ê©ó–Ák¦àUEr´\Ð?þµq 1W3¾ *£<’"èddQê*…]¹Ô£&m_V$B<ØÞs?áVÿpº7©•_ðá  ÄºÚ wp»ËµÝ_,yüôõÝVõÇ(|¨¥OfçÑk”vàË= vþüõm<Ñ®7xn…ð:o§ƒdšô1!ò?æÒVrмQw~)mÎÄݘD"k5úñV[ïOÝRûÚ¢„Üäe®~s¾L³¹›­òÍÔÈœ=•AžOkE¯Ç`ÒΰŸµ€%ƒ ›=DªPz;à­ôû†&(BRõyáf“ð6@÷>|šÒ¸q÷¼b¸úbêëÀ†1š'ð)—ãvAyëËY¶JkK\“‘§ÌÇr^ƒ¢¾_äç¡R ÜhH$VŒüF§ŽÂsuºç¦)U&Šoîy¦,CÚ2ê÷j @•æ«aÄñûõÅ$° ¸œ_a¿ Jm³$9ÃwNË„;ú6[%õ\ßL^ð¹2YOÚì½ÉJ$ °ìëIÁƒ5(µIµ,§@¡„´kÃ3ˆ,ë•cx—ºz)óó2b£ãTƒ+ ‹ÎÔµ¿é©køI¯@ÙGTÜÿ^.=ó#C™s»9õJwrAüy]Ê!VñWM…ò¹>uzmvk‹‚Ä…ÚðÕAÕÇšZs¼t:Ì®½æ÷fªŠŽr91EAôìÒ†G.·Úšëi/¥’‚Œ¶Wˆ€“õZÑ);ì?=¯ÄîíC‹o ùvH_ºæ„˜Žcð%®åu% ýo> µ—¡FÄöâ-(3þÁ ]Á[_"+E¢p±¶²¶V ³ jË+S„R·fÛE™ƒ²cKN °P0ùÝwÙbí+yz½CM§²Rɹ¿`T<×Z"aDÏšÛû4³Z õ7ž‹õ÷Åôö„sƲ{ø2˜Å^•CàmX`T§Î¼ ,$ƒVPß–é-UT&†¾øÛIǦÉÀòß ®Ší3Õg~ùÉXäÀì`Noü–¸ý’V€o{ìv?¨”ñl*RµÍy^‚qdêÀoœÁK"·Û.·Ö œ µÿ°n¨&>aK&´‚ _Ê€:×h¢õoz¤Ö«`ŽH{ÁÐQ§#‘1¸€çYl*:¿’ø<Û,%ôìÃ0a”$3"BfÇ`jæx JOmbCê…$'°»¶àËÁ¦Y†êQhX¿óp©öLé;‚Ȧ®‚n^áoW÷$€‹ð (øé­Òöøe‚1næ$ˆ'ñzl÷ôÉêYÖ)Ê™¦ØdÚ¢(l|Óaí̓V|}Ï#³¹ž–õÙÂ:ƒi™I3¼ú kN™V„©þêšÁq UË×rØe¶"‰k°bNˆ ¨‡±¢lÕu¢¶WyO(ч ÍŠö¤§ªI—ļø\¸Ës×T¨ŸnÙ¬s›Ö¿£—6K]Š»3bv´0]ªÙ7ñÜÔŸÏ9Q’®›ô°¶]MPÒÙdý[bÆ['껾ðmŸ¯ÎˆÇá7‘CñKP*©Ã²ÑæIœ ºñó¿ÛÊ@HÊúJ¹<_ö"]+‚H=ºfr}Ã@§ Ïþ] Å>¨ÇOÅùÕ^é,«g§Ä'“;ô¢¾FQïÍ-W/]ø 7¤ÀL”±Ön«R‰ÏñA+ÛöŠg*$¨¢ÀÀø¥v¸Â¹T_/¥ÐÇ«bÝnË11õM»Ï±$ìóš¤Xd„+@òšÔ6JC&l­mˆ] Ý?ýÛåŸ >j b5¬¬{RŒ?ç{ئYßÁ¾"½deu8Ò­*"ûGL,”‘Ópäß›rT åD"›pÓcâ×vCÓ‚tó«³m„£y!¿ å‰ðܤE±ü%³®õp¹iG¶Õ©’VD±Lá·2>8c×YÞiiÓÖcÉ~“™Ä-§îÂÖ B„’ßW} Ó0*T÷kú°ºlZ‘Ì®&X¾cê¡4ñP“ ª¤Ú\ÜC¬‹¯dó….x¡§rl³ó ¯Ÿˆ¾”ËŠ†ÓCs¹ŽRCœí‚äN úPä©oZuöˆõ¾w§)?4z*LÑ7$Ý—ŒGúùTdÌ/o,cD{núI:Ð׿s›v­+ëã>´¼PˆëØ“³›ôÕÁ¡¥Èt­ˆ¢V^ú-=Wš"ž¡è泯ش ¬ÈNB÷c)„ìŸ_šS} ™Ü ú17mÔö! 3Bà²BÌ룉Móy®Qïx‚]>R $ÃQTÛêÊs}£»c™Ú¢Ùœ¡{t«Å2,¶v|a5!ÖfǪf¬G&Tè“€´ƒ?ÙS—Rª*ñä6îòBkgž}…íò8û¡¿o-øaô.2Ÿ÷à\‡•íi俘bø¯°¥èUÕ6~¾%1¯;žçj¬±LíiÈcƒÈwÚ®€ßœ† ÓÈôÇLg¼ ÏùbïN°áB¸æIÓ*µ:Y M)Ûk'W€Y%ÞIªˆv¤Ø;ó‚AFˆJ5þ2–>Sh4+íp¦ŽÃ{xÙɶ§9+ 7«u&~~óLqÒ™ÂÚËé•ð!¢5Öú´?™q(¦ĉæÅGcÛ²ôÜú¨Z½ŸeÊ ö2±ÒD4Cà‰´š‚ÆQelXh~ÝÒ«”¤žWÔPýT5ž—wâ´ËtÈ…&´,‘¿|--~]#þX¿]H¾Ò°ö.85’ ÃПU‡T)qDoö:z%ýDÉñ]Ý‘wÿFXM{JRò1–<Ý­O;SC–q+‘˜úñš–ÓÚŽ€)L—×£¦ÓùHÑž‰2)*~x"Ýà\NÔ'u‘W;SEQ-Å6&¹rŽÛ(&dí'žf¹܈ƒïgÊ<*çÝÄüò;;PÛˆØê´h ¦()¥ëTœ8” Ú¬LÔꆠ‚=ü(–Q,.9h6¦µô'Õ—úatpˆCõo3Ø;ª€ =³{7SWÆØ•=üÔ‘6B ïѺ#ØÿÖZfUéûƒbü£þ]ø=0AÆ@BÒ[‘¨TyJù<óíÞp†Ž›†XºÚ‰ZJïÜoK›8ª”wULÒÇ”(ô˜Ióµé¥uÌå6—ÆÛ´ô›<%J®3ºKÌ3jô¨Ý›w‚gÁ~ɼ³\ôò)…ýHÓ[…’¾ÙÞ ÏÍ1”ïq¡£V%¸T!“xDt7ðÂÈ Z›»GµßH"p×r9ª'Ä<×ëóóx|qTëËü.Ÿs³Ž'%Ná<Ôpía×ñ…Òrиÿ¤)1æ¨ë…£?1"²¿‘ø Ž¡"xU„‡¦*¤ -zT”ü‡ƒÜ“µy@ ~³?,*Íž‡8Ïߦм]“tn&’W]ö¢£; <›ü8HJ{äföõÜ•>_„@R¢ܰH˜‹V3¤nWãúúxcM ï«wúé?–õŒ'áp¡ê–þŠ!égÒM¨ºƒ{¤c¹BYžd Ž_Eô“ȳ(Cg8[ÅÒ•]øü€\õû–1·ZÃo¢éñã:ûíP`Æ+vgÛ­uZ,#­Êv¥TÅM2Ó‚¬n^ª°;öD @Íun`/)*ø 1M·÷Ͱ ›fY=d fÕ3ÙKhº3äC Ƽºü8ÉÚ`œÌ¥,h nI" j¶mä%¨{xnµƒòbæÕû\ãRÕ÷ëõv¤g"imgO—'¬Ê‚ñÈtãòôI¼¯¥i¹Säu7 ¶cR>B·YÀŸœ³ bÕ©2dFQ9áy—F‘Ò¥Ýæ·D8Æ’q/ ™³æ(ODe«Å¡ü^Í.ꣽá/ûp™ƒJxŒ¡wìôa#®Y…gk>¬S²×íWÈYLr‚ûUùs뉖κ…B¹ÆšdcÅðDŸéyi-Ö'uâ´Ú I˜wI_¼öªr…¦hž©6Q,cé±3C%nÞhdº±CÄ9|LÖ•^mfô‡HØI>>¦º¸q>“jcÌíõ‹wuøiE¬(û@ÎÓ혀4[[ë0_5Œtë„ÔFÇîŸV!™/_@ šG߇›·=™ú)ôëŸÌªÞpëÝj”rw~v‚{¶9ÎF©c/ù@Ëà4¦×Åݰ,ïZm_b×öÃi˺_p§áÍfoŽ¢§j|Ÿ/M0PßÑIü5‚{…F“8gv÷‡JòyÙkÜ5˜Uk¶”_o±šÆ^²Þ(ù4ßNµHÓ‚7™n^*δJ©[®O&2S}—¼è¨?Ü#Á“èñ›(0ø~G^ù¦±ämç;‰2 å“^W¦ä\hy³y2†õÀ^uÐáyA¸MT]Àwbq¤ärN°5*Z¹‘@o_äC;¯Ðåë)¼¶4@1µ÷Ľ<!m]¼.¨šZ¾aÔ/È8q·þ†•8.:±ƒ@MU9ö&ôcýJœìnu؈†Ä,Æ_+qPx ‡–5:cd¢ƒéÀô=:¦ Ü€©Ð67>\s6߃ùnJFÚ¸ü½×v~A Ù”’Èû«Ê¾éàZH=ÿó´TU*ç…qû.'§Jz™3aI‹HÖ­{¬Ùñ.”y·×ÔÀÖÙ‚yβ>ø(Yç#\üÆ:»½ö)yÜú›/l¾o}ßýÆ´>ŸžÏÁ¢BþwBo9…µ¥¾Ü«HÉã¸[Ñmí|ö»>:„x›ž xØêbk˜e d>½Ôj©Õ©[‚ðÄñe®_â‘Ð5 ð`µy‡íφ)fD¥ÊÎ\VVJîHÀþü ·jH¶°-?ØþæÚkí:ÒÜóK¼ê};EºRh;ú;¬2¡ h þÍò”œÄ  =í1!"Ÿ?Ð×ݽÏÎ| ôŒHÈš¦ß¾.Vo¹þ¼.>àÜ—Œžq¢=úÐnÙtºqDdPÝä*oº@! ÝéT„/Φ Yñ9.9hsªæ$‘j¿«õª†N„ð§S„½y¡YÓgmuDz‡(í ‚X‹V!ƒóǫԀ}^jŒ[®&-̺4]ç8é)þVL²;28âÈ”Ÿ+²dœzÞÝß4) ¹^ñ?hãŽN)Lëû\$Áù“'ѽ)û•QðQ+ÂБ™P‹ÙXÕ“,Z–m z‰õm,½"G®¡ ™FÕé×U=ôŒ¼B›-²9n§õ ²óèbºŠ¿œÏúü ƒÿ!Šisoèg¯YL•W9±\W”\ÚÎÖXT¬¶Ÿ4¿ÐJøé¢pYN+xƒõšïiŸnú;â˜VBÏl5£d¹’JC¹ÚWgN—ìê@èAÚ7)‡°&Mßh=%pRÕXW/[‰: ïõ-ç%'êé嬯|ϺàžHÜA|¥I;&Š/AW^í­kô ó±l—÷­ttùé~]Ö7ÆßˆŸ†ßî¢ÂÊF£L`Y“¨LÒÖiuà "ßåçÀ±£í‚WI;W¾½‚ORïµ€­ù ËIÖ£g¨l•›9Öß]ÛŸjõNL ®p´Ä Ì\Ô€Œ°ûN+<"W.ž\!„øq:µ; 5Wú _® [ª—ÑÞÃ0“zƒ,·¿#2Ñ*õw…ZîöKêO0©Ž¯êicè– ®¢Õ‡°Ý å|Ágõ\¥™8¡ÂuÆqä®Tœfö|þQʉ¯¿Ý‘f˾È1—V0Ä…'Ç~¥(~©Lî,EÄx:>9©в‰×èùûa9œ½£Ì¹J‚cáM¹RNöG÷ò#Õ@¼-FPS•™´4“…€]ii½lkUÁÂÿ«e’R¶Í½¯)tKM$‡Û* îyºa› s_]eÿ×½§ÌºÃçZ,J'”ïû˜ÿá×~FŸ`eUT´—”^{Ú­­£.ŸNŒØvœT)»6êþ@,“ÈF"d ›ÁxŒûéÉliêùNv2«f‰žÀH½­üñ—“ʪ<”WYŒŸubš³*vÁ€nš†EæÄŠÑQœÄ¾ ’u't×’¦ãXC 8B0¼Lóx€ ΄øl­FŸ ’ªÕ&zj´ª”:îýæ)¿uJ\­ý;\õ6&÷9ÿO„§ËTg *÷8}´ÎŠRf”•œûÐz ÖãD>ƒ8ÏÏæó+Ä4ÝÀïA ¾¹Û‰ÍŠQ/5…mqËŸºÒð¤Ú·++6šÌÇ™‚ÂÔØ·O•—i²’°t’5£Œ«QQF0»v§·ü‚<РÎhŸæPІA7c64b¯w^LHµeih»–!PgŸoM³:É?ø³òÎy¼’clÍTªq&»û4[ãÇEÒÇIQ^ùö¥0”Y=Ý~žÐðÖÂEThãxÅÆ¹¬rRU­!cÕã9? ñC±Ál4Ëwb¸±ú`á”»j—P†y§,޳sœ[AO&X:N×AEÞ­eKw;D„ÃmŽer¹»Ïx_yÛP˜IÚgçüllJJŠÕ b’Ý?e•ä0G$ÂÄ"è¿‚¶‡%îý­*«3¼X¡ôi”êeÑÚT{ŒÑn׷醃ÇQ¢ŒHÎnáÐÑò‘jš/˜i\ËÒ§Ò=}¨Åk3˜î‡;ß D'¦ŽA÷HGy/âPT“™eºÃ"•¸wß%ô@™‰¿ å¨ÕËv²Wyj02Å=kAãÿöÚ8î)}vcW‚¤x×ëjî0®M£Ù>97®ãžvôDÄW5É`P"5¿ŠÁ@  ~ã%©™KղĹ2<£<ÐÑÃçN™J¤µö44É4ƒUã×"*ìgZï¾Û œ;AœýÂ(¾¾DSΕDZ2XÛûŠÿ¨±'k´yãŒ$Ôë,×ñ›Ü’ÏÁTÆ 2ågýD“{ºÃšÎÌʬ¾~Œ¬fÿ®°X¼–¹õý 0õ(¡’}„°wEê]ty½Ë·@®ö(’? ]Ðl&1©/®ÝûÑ| e)¢ÕWäšÆ¾4V7ÎÑ6ÝnÖ‡"g¼Èø3ÄÜ‘~Í‹¼÷#­(%4|!HÑá$õ©þ^¸ã%P'8̚¦©x˜»·Õ¿>ª1¾f·_ldÅ‘R»¶á_¶Ð,sV ¦üAÔ¿j²î@û>_Âóé‚„#|¹˜@(è:Smk%g-7†£KxÌ“œJsí_—s÷/í„lÜP¶¦:"0qt¨ñb£vEÜLê¢\mó6æ‹T•7Íè­ÜOÐkN†Ý¼ŽáÔ ÍÈb-?Ðwê9½òÖFÇ«¡Ôy%ЗùçØHQ~縨–µRJŸáƒ÷‡Ñ`Ç|¢´¸™ÍÂWgÂÓ©«;!¶÷Fν¾ø«&æ®”CVB›òâqÌñǔ՜Ȧc2ó·ót~°·|«¸ ®ÿ€eO\Ÿˆ+÷%퀷k]%­ÝÝÁCŽº‘£Z|¾ÐÍ7HÖrÞQÝ t&øf!LlWꕼçéÃÍ¿„–ZEÞ‡¼./ÑÛÄÿbùˆÍŠö³û&Ý(g\f Á [s\|‰>‰¾=kíT†,gÁ·Ÿ¤Xt+8‹Á–DÍä?Ñ}õz‘‘­$•Á8—ý2ot ‡daá¬%BønŽÞæŸÉ)rOO a´`³Ñb=6f@b#ºOo³(Y@ýû£÷Õ<%[u¼Ê³ (| –\2¾G¬ÂÈçÜÈõqù`È5úÏ‚3ñÌöÕ#vx³ÆxD}’Šu|±yç P?¤ìÁ\½ÇVcN«¬\H¸$G òz ¬ŠJÁ#½Ç’[ÑJŽ|S3‘Õ²v~SâKßÄÉ…l¶uWMö[À&ëæº|ËjòÃ@¼1lr‘ sç,\Âm0$@3ËÓwœ^;ƒt2Ð%sù ÖÀP`äˆWy‡·dd¬v=çƒÖ—Õ/éMÒk¿‡f='dç;ÿÍ™óuØå%/’ôˆYš¹3åÀ™ú¹‚Rsl¹IƒfY7f§sŠ37Úï“u¶ÇñLEyâ¯q}¢L× g¨Þ£³€V‘1“Ÿuù¿®XÑZƒ?Šßr^V­u޵ìëhWÃ!}¦è’²‡Åíç »ûEŒR1è¾Õ­“Ý/ÊH8ç’U5vì3ª*…ãè pŒ]dØ´OÿÔ©’ZŸ _D 'kFiOn׸ɉ¹C65ASᤱð“\«_[ƒé÷É»žÕÊŒ“!ÍšTy6gÊ=52¯pîö÷­OÅÚ œ[•÷4ÂK%£št‹™׃n[ùk°E˜6¬Êå®…&¹,ý½¯/íßW¶)åá¥î†‘ïÆºÇúDÒúbXÛtÝÁÉ‹íÌ• c"òðýóêb쌖œÂÅa¼¾°6ßSd娬ìC­åý=Õ»¼Ûx•¾9DúkC´g„ 1W•1é^@LVùö §3o$ÈÞ#IWó;Í¥·P;Ù{/éa tÔ¯2‡­*+Q†\+gw7ûÙ,ðf–Z«úæGº·Ñ^mbUÁoøBA…œŸVäïú[Ž=§Åu°î‰Û×­×è† ÞbÜãÊ|AeÍG£´W€Ýy‹ÝÃZÃÁ ÃݸObíúíÐL”±Ã2)qš±Š‰:¾’Zø îÅàÏÖ¯àŸD”G…”ÄQ£<"ˆy™;+8Ñ ’¶,#MÍ=/!é=×dYDj&:9¤mý›¡R<§¬Þ­6Ò›=µÓ_ +—#«ÙÍv¦éˆ7h)ªíUœ¢—ùœêò;ö'g„ß`®Vá•õx&ýN±O+~ÊìTëm–Ê®Û9Ó¾«ÆFòmÿ’}så¢<Àuá£3˜­O«F*ÜöœÓlsë¦U+0¹¦í‹>Ê>Œ(Š}ìr3UïEîœYÃØÒ6g âü>æúSÅèf|{@R5ÔmÞo)¡‹© ×pT"#Œ)xê$6>ÆÔãz0zAR·¢LÞYø :!A^^êMÂ,Æ/ë–Ë«å¿uñ9#AcQR6€¯ø3’nY4 ¹†ó¾gW’—=r2ûPj ›ÓÝs ³·ä;‰¥a«ÅÁzãzž¿?SÈÔÚLk/ŸTYÉ`~žLÁuÒÊ’¶§ðhs„sAüd-@kæÏq7qé³ÏOê²b«Ø§ák(‡I š˜ÝåFÈu£ŽQ%˜P•4`Øf1uäÄw]8r~™ƒ÷ÛÄÒ„[c˧‡·™œBÈ>bl7,6K§šÈt–Îî>[/ªz°µ–j<õ'Íx}™Úý4(•kl·7CÃb®(äðj$­{äéêrÌØ)í©Ú> $ÿ–ˆ=åÀŸ`T<£ššÄô¾É~D̯ CÁé:Ú‹xVú7d¨`P‡Ã`•z®9ûý€£Žú_Ýdës°5‰sׇ—,f@~:é¢üBd;¨æç\.ñÊf[{±)9J2}rvPÌS_XkÕH*¾ÃšrMN¾–ƒ‰ÒPùBbp}g©”Ïo³u·[ñ—³–ñ²P{zPc®ÔŽö8m‚܇h•ZyÎ0U^ÆaWž–Ð? :‘êÙÎ(`ü±Ø8â "Dí÷„Â/cGàý’3tŒÆlú Í&³*Ÿ7U~žä[$”K}h![~´3™.7»8rŒ0M2åêYYÛb7É`Uæk)—~K3µëÛpbqo¿W¬²zk…½µuù‘O„¾Zô…7;’SÍKòÃï‹‘ï5;ÁOUþ.”’2аµdÛ—U˧øýdªyÁqÕV:é¸àË1¯<ãýåôó^ i74—/HHì<Æ;Œ Oda9éq¿Ìô“´{H‚ؼ3(á íÜ_ŒŽÔd™ÉižÎ§¡áÌâºF.tM¡¸!dÀ4ÈÜ¡]  ÿ8”=ÚëD³* ¬ªr´“_»÷yŸxü¢8¶‘á:òh×·äŽÍ˜iÊ…—ZÒ' ¿þf3¡”¢±Ï™Í¡~ûs2hµùß–˜ä«kAì|¼…‘«§A ŒËÁúüzS$ðcZ&o˜^šŠxÂôB¡®¯‘ª$‹oš$4wZ¨QS™½vü[4®wÑòF,ˆ_fjùÔùP31g·”k÷^/ð°ö"K,œMª]!±ñ¿”+tiXˆg}ZJE¦+ž’(ÝÚP3Â$4ö ýU°üØ=|QunÕ°q‘©ŠY„¯Ï:PGÿš(h0ÁŠ\«‡žº.MC¬qàºBÆ4¾ ;ÒïjÜœ «Q»“Ÿ{zÉ[]üH§Ã²*ݲJæH&⻓MÀïxMš}#‹‚׸¦Š´âýe¶RI«Š¼ØªA.º[M¿Œú³¹¸H"’Ž"øò t" `tú(ì|J«VŒãbr²ò÷Dã!x5e ½÷eÑðQË”ÿJç|´ËAvòLw"Xìgy¢ìè¥^6ÅS¯´Yãw|©¤eÂ,)ÆRÌí«xWHÆqéR`üÒ®q'$ë(C䛊kžTb3Œ¹—©‚ ¯Ê1L?¦k°°ý‚¢` æjþ,rôÛyˆ}1ßé…×ëÇzÙ"£àÇ“ª:ä¥sƒ.ó9›I>ôA¨,ãz&±Ÿ}(»—™—Р¶.JÂÁšóÊG,ßd^Ú•I@¤í7p×°¬S?G Õ‰(ígS§ÒŸ _Ï*ÆÍT ÀtÖ‰\®uC¨»4~ˆýý†ƒ Áòr ¯“ó[@aÔÛ|A'†â픲{›xˆ¬Â½˜Ú=Ó›\ÅôÄŸÂÌj•Ϧß?óQ@B2²Sé.68{fãMNtq¬p.;‘ÀÚ‹qARh…ŽZF¿™k,zIç˹Ãb®€¯%æÈUêù³«Rµåˆ¤†yiB¦ù(âû¥ñ;lÃ!ÕbM5š—Œao»Ý:rn#¦Íp&sιh„‹ôRº¥;¼/pR´wP*è |ƒ¯L4²´_Ùh=àANC§ˆ|6!2gï2Íá_ºgsÚÑFÙ0<*Q”¼ûŒƒuKôÕI¥`1$·­h†®Q÷SÊ`$(fðc4d¬ÿ+ LÛoГ¡eñbºë(¾AÜ8|ÐPiwÓ“0ÑDüe«Ðz'ºœys_áÝÕ{$¿!$A—F}ÀÛM!Á!Ý;Ç.¶ÒÒ¾}ŒGÍ"> r)[Yå+ » Á_†€3æ †.e*e©àAÕP›ê«=v¥›p''”$ˆ#WÆÁíêûˆb~f g8ýhïÐ ¼ÒšëÞÑ4Ó=÷QõéÙ@D¢ú¬æGYžsŸŒ´7sƒ²º<Ïx¢ûeS/ZM¸ú¶]*2Ëe˜¿h0èͰÕ$Žq.æ3#ë&Ñà Sl tý¤™,Ÿ¤£Dm·FÁëÀ;éXªÖyÑeâØÙ;†ÂÍ û)É¿”(žü'ÄÂdoËhŽþIò¬dµ¬ÓžŠì zýÄÝñcê´_>¿î¬_tz–Û©æ,rЇëâ¿¶Ôt îVÏ^}ùíZez_z,?»™žß2»~_Æ1ýËOvª;s#)±W§ukkà•©£K0¿»ùRÇ ~\gPˆ9aâ׎«ò+áÃ!)^’²ÃG«œõ·&Ùâeæ Í}¦¡Fó4UNh›'Ekçi_?RŸ!#®¼u:çç ÈýV¡sj’™0¸a Vïw¸6î‡U\G¯æ­M#«æ“€kx>„ÔÕf×) ó€ßXkR¯†XIgmô Åfž¤¶»É÷Öü äu~Õ¡–r»Œ »¡kQ_0](§2]¬³“Ù j&e¾½É­T²SÏÍ?ºÎ<¡ Ë#í-m±ªû¼13˜*+Fq ÎEþxùêzlxQV{ñÉ`‚kOÉY¸!)ªÔ@¡änõžl }^c Ñ‚e×R‘’1¯–F®ã è2n"?í@äa¡ÀFæBÃÜÁç5#¨‘۽Ƙß^ªE³ÓyGå)$¸C3õ¶µœ”Ç^³2-”G~Dú—ûàŸù9Ø´Ÿ?öAš‹jý³¸=ÏÉÄÕßì%Þ²0ST=!7…=v½V"â$dÚàž¤@åf“Nˆ+},Kçå§~ZÒ¡ „¼n»Óél"¨,T§ªT×V2ÕZô&iÔ¿;Ãp8På6¦údûˆ½É^0q®ºÔ€ng¨;ôÚÂ7v¿·Ù==Ÿ°«àÇø.é!èÁA߆µù̓{˜¼ÂGÚCkšžOá@5cX1sð@σÍbtnWš‚ÙÁûÜWÀÝxüÖxRaÑ^XŸ¿[ÚÞ¢³æ‘UÓÍ–q-;ÔTZ^¶ƒËÖ-WÜ×ŒÚ /E"R`þXæIøý;$¡1‘8«Ñœ”+µâÃ÷]l‰Ù.Å߃‹†ÔëKÿä†-vô¬{w„<çû-ÑÈÈ,ó>Bý‰!ÌîÖ®¨²-g=7ÚyŽûª>ïøqÑJïÌã2¬»Ê61›Aº)]{‹]å|tµ¤iêà¦AÐvU¡D Ú&7Bu{Ͳ·ûû{.ç0E¡GÓêA"pV¾a«[°Ðnâø´|ÑA3 ™LcÞëÅà}(ƉS®¹ýЭõf“™q–ü(0Á‹¥,>feÌUæÒÝQ‚—uÇ?¶óÜ1£²sñf•“ƒØ´¼Æåî…HWWUc:ª˜ðQ/Àœ’á#rnÓÝ\ öQPL”äKªžÏ|ÊÉcï3¿ŽwxuYÜÆSªï¹6 Ñ-`*vÄ{Røäk¥Vä¸PÂå,ÏÍÁŒ}–.gSÓ1Ö5T´¹© &ÂM…°ymUAcĺǞ¹F¨^ë%HjÍaÿŽòDÏ«ÙeU ¯ZÈÅ}wÅZò+(†‘TZi‰™WcKA5ÓR þ¹Ë@Œ·è”Ÿ.Âp›µÁ¤G“ŸÐ=X«Z=âÒ÷¿¶j$û—?•Éi‰%$µŒæEóÀ?v¨ê ?#U§ñgÈ©Ãê£ÒU¼=:hÀ™ã&W”b¾æ9õ×cìRƒÁ£[å%º…2ˆçæ>ƒ4g—Ç茆éPA:f«© ¨ùU¨>ú#o2¬]GÐXñ*H§f°;l²Ýâœö£*"•·éÙ—Jú&ƒ"ÅÞº x^>R_ÔçD®.êêA¬XkÿÝ6·O•ÃÚMÂOÞ‹|l}ßõìU’Ú·þã+z½¨­¡1“Ø’“Ë+߯@võZWSÇka²°b­fÒZEÍ:GÊDN~ÅÚ Ië—Þ­Ï¡€a& I˜<*Ö8}àñµc$}³¹©ç¶iŸš-"ç­|Ô»y=\×9®‡js݉ü-/}1¥ZO¦ ñ@A‡2ô˜\ÜUƒÑ¼_`µE|~ÀyÌö¹ƒ¥~º»RËסH…8ÏŒkò¡„ë‘He"ðÙÐGðL]X»á3tøzb'@Ê]2Zõ”V^T¹ÇÉ õJ´:PN4k“*ÕÑ>ª 7î]þÑ÷ Ñðþ½„ÁTÝÁ•“€[Vm X}<î5uAZö?’/ß™͆Hö¬efÓ1äVC c¢wÁ!-ãÖWÖP¢ZŠädܘšV©®¬gÖ^U×%½¼‰¢íØW:ßÀ}FˆÛÑ´³p¾¸`ôàzh èɆ‹›­Ø¾Å“ÒÒ¹BcÇå‹}Ót4n´Œ›žwL‡…aòl5á Î Rm£ ¼Fm»˜’!bz«îé7_Ê‚ø'õG‹åMæÜ‚·Ó6| d¿Ž¢ ñKŒÓO°èUäwÜG¡à¡%ÑaJ&W†Fˆ@>z=àj‰üøØ¥„i7dÇ›ºpÚ覫¢$øØ°]Üè‚O溎u8™÷3¢]!b†Áªžumár¶o­)š-üÌ+ è¸'§ rnÚòôS^§s†è_îÕ±à-ô£›%¬ät[’¬eDmôf“&è èO™SÈG ¶SnÁV{Ÿô‚l¾Ì*4ò¸¿Û&Pjµ®sCœ„½,ÏòäÎêq,[Y*»ËFso¸¹ñ…o¾cä£/ÛëOóalÏtb— ïi™°_rÜÜ>®ûކ’D­ÈÓ€î1ÿV{,‚6æYpoë§Âû6ïu9ЛԧdK´ßÃÒ^Hí›3ØÌÎ2µ†É8¹Q–¬¯tú„ÄÚ–MÞÕØÄÌaùËÛ¹W }¸‡x¿S_áÇÍõë¬ý÷˜šQ1qOnÎ*N·\GP_TSþWàU³ªSª¼’Þ8@Î4kR6K½Kfø{2Öù=+éÄOB„tÃè¶k¹½åmÖXâÞ'Æ]ãAsž´s¬QÄUÌ72~3?^Áø}]R¡l–u±³!‘’/gÅyŠ?sÏ‚"FÒËì]8!uϯdɺÛå­¦­ÆÕÐ_y ޳J‘±¥ç ›í4j7},ã[‘Ü~pUm¦ŸŠºÓ” 5ѨÞU XK©ÏD'ð%‘‰_{_O;¨M&ní(Âù]aS˜¶Ó¬á.{¬Šã*w›‘äSä&PU²Úý„Fd;—äúpÛ”8&»MGPuŽ_­k´Ik¡ Öá2MkÜÁàs¡Àú̾:00ø­’{Z¾ûôrÑìÉ SVGæP’ òãã;;lPPÛÝóëK+Î,Ý%6]w'×K(û1ûuWÎ%r)tú^‰=—ÒuÌ{ײ=Ùç¯&U¤Èù‚uÊëíñ…Òû•â€-®ÖÌ*àA$å—$ºˆþP ¾àÓWåÁðHÁìÑhÑý\®´8òa{ï‹}I&ƒH_Þ CöB·»<¹¼3BÕšePÄà­I^£ jê\æ~½š÷¯ÚKoŠª§ÃyÆ‚±<Í¥,XfQ”ȆÔøTé#Ïxù·}„Ô¦‚ºžhJ è•âPA‡d%þ†‰âÃꤥϱ¤Ïj%F $Wk½]ì=‚Âø‰×¢Ål#qk~Û;¥cEÙËÕ€”~³éþfÍp»ãÒ4×ß{ì—¡¥’„½TÚK1çðÉŸsþÔ^ï‚d¢/ú;”•°±ŽTfåë±EÌ|Æ ¢OM»E…Rù2ÑÚµ`¢Â¥íNº±aÊôߩșV×££"×Á7ê¤v€´Ü3OõbD¢=<—yÃ'ªöw o’-†’Õ¬”¨Œ>G"€*ÌáÍ>—CZQ9‹hüÑ9*d?UBªT²¤¬m,¡ OCâöYß8°¿ªÀ³¡ç4³~¿Ñ&¼ñÍ7õ)žÇ«_Í´T~(|QœÊ*,^À¹žl¡ Š„¥¦Õ ½nŽ~ŠæÚƒ\¢ÎsüxÔÕÆ¹Ô¹Ô1Ð\ ,Mý ׫j”ܽ£iü±MÆ”kg¹b¤0#çÜä[]†zÆÀ¯^o¬Fv¯…BM<Ç?n¯ö½lŒ©–‰3ïë ’˜Àò$\%(e ˆ¼ç’ÿ;(ñåO™Ã“èýµdz²FlUä™ÁWzP<• —¶IÅ(-¼±B7nwˆ*÷ J V``{&ÂÉvÊfÓ¦;,‡÷›œms\ÔJ±;A#ÍM:cYxXJ[# Þº q„9góš“ÄþMhÿdÔzûÔÇ"æ–¥ï;ñµzn§?ÂЉªOV¡¡•ß@b¹²v˜›s9Ï7GÌ”jÛ§w]'ܧ£ø¶1öŽ¡w LZ•™ÒŒGQ·PͳÝú­®ÈEiç€ »DÙ¿l´¢z_“® fGƒtøtpÍ~¼ª©&ZØ$ø30)ûñï‚•Ý÷’wàׂš—ÕGa;"±y¿Ö¤¨¾$…-ÈËpòmúûUŽÚ÷=n%·%¹9‘Úû½¥õÉM­x¢Õ¤•])žh‘²˜©¡`(ØÄ.Ùu“þ¡4e°hèåú`zöÞQØì(éÏ Tß·:O¡È¦oijë/.Á8®Ø6Ë–W tE¯µ¾8ñ(2Шè¹ð׃:× ‡â¨Ëî,:• W,JlT9 Èc.IÃ`‚ÎË‹Ëe 5®ÞM‰§pˆÁ½'!W)19_¸{¨8J3O,7ÞLèÛ™ ŽHqh GF ¯÷i¼(bT·„[[¹ñè«“œÕ[7S©Þ$5â]Ù f¹Cm %›^PT^&]7O4ZÄ ¶ˆª0çæ7žk~¦ ø&ÕÁM£Ð©oØÝå+Dǹ’†3ô“ºk˜Ü§…òë·Y{&yC4µÃBÿÎg7•¶º™tXN¶¦™ñà™iÔ}6Èí¬Ÿ°Ã oõAôôšà»]Ât‡dÅ{)/1zɶUcs”jÔ=J& vnfèHãæ#¡àÓä(XS¤(.µ ›€?áPHq$.…üNh%%„%ªAmæÅކý«:TEàKߤЯß-:¼ÑÉF¬v¢HªOâu¸Jÿ“–ÑöéSfÞsжP1W•:–CÁ÷÷)»Ò/"Ö¶+²@˜)ýåÁ2ãlÁ5\¹¦av.¦dö¹íöÊ¥÷úCëC ù¸É3$»ÚÃWýŒÁ7Î ¬€¶Ü4o¥³bÅË×^?ä|}o‡Ûv}_y† ¹B°JÉ¢§‰ÿ$7‘ðQw{rƒ'––ógÿd\ù8âõ¹Ô"ìuÆþÌ¥£áè2“×U@¦è/Šb¨4×ý‚@¸D,L0ôÿl “ô® Íþ‚jðñº0ЦïQªw'壆RÝ L&Þoë+Ä º>™!ÁÚðÁä9‘Öýp`êõöæUè?G žÞÇLoããô>ÆÝºR K…‘úÆË‚µP«ÇdeÓØçÌÀÆä›âKå<­ÚŒ:ù¨ÚÒüm×Ê®Í g ¥Kç$ž_þÔµDbc‘ÿeÊ©71WØ1øA˜ópzl†ƒ7^®„¾ùog ¢ÛNûÿúý+ÉÀöÍ„¦Ô{G–\c¥9ÂÊÆùôèÆEZê­ó&º,­©p||¯oe䉜lÅŒŽŠeoõÌü‹uèNÓ°L.·*P‡žhèCŒ×h…Þwë|è›ÅÞ~å²\0‰jû*Ë2}XvÀ3)H•3  %±iÉÿ=…Ö­[5ahu›ø°2¼ˆ% ¯ƒhAxg{9„çL'SÁÎØ0¤J2 ºj¬F™‹\üˆË5Øè"B`Ö¸¬.ªå„4õó)÷ B!‡S`‡00&ã{¿ŠìÒÉÈUvå©|(?ÿê÷ËV°SG;å4ÅO@ˆÝP!T·…•Ô0ÓRŠT “pïVæÙ;j&oCBÍÜ©øõàuM[To~æR"ïèN`<ÍÂR½øêVÆ×wû,Þë‘þ÷·f$n€5;׌“g™Cç‰*´ÙM ¶$¢÷¿)ƒ2uù˜~{ KZÙqçá‡åÑpAú^Ðé}H€ýæ!ð­óñóÈwläÒYßãõc$öwXzÊ+:_¼v݈@»—8|èÅ“årHƒ½©¦R—ÉÝÒO™ìðç½z]3G”ˆö8“©™ÜÛŒ‡J/£¼úVÓ ~°Åt*,Š ªæI I?èãÇr¾]Õšoùc‚çyTV2›Ñ"X»4ÍáZMYïóïÑûQ³³œJö¥k}ߣ¨=YÂç|Ÿ(ˆsÅwçBÉ" ~РP>éfo_Å—˜Š•šéûÉÓD75E$#€™‹œƒ?1(^°…[tidĸ#ZÜÃK}Ç&›eÑ3C–å{#rœ,–Øre6'7haºÀFàê÷Ééáý4çbùPÅtÔÏ ÛוÆ×»¿Í#S8JÏоN àعLÚèÚÊr?嬸ã»tƒ¯”kí7Q‡ µÖª‰ 6Àü|â_mOÔóêxÎ>¬òõksæÉ—âÂj÷©kè JÿXÃÆmèÆÝp33«Øhœ»ò<Ë9ïa±ä&Ñ5ú±^9¢T4É~_G¸8C¹• ò_£fXBÛ’¿úïà[µˆ„á&ò«æ Ά^ÚÆ;Z­FþЭðbºu•£Ç8›},åJºªÉò¹¢™êc´³ÂàA$n$1Aêª#VRý¸V4X6¥y@Ù?WænÉyÐí™®ö_…Q KVþ@Qõè:~ît\ ”Îâ’xâþ¾›¡ ·¥U*ˆCî>†Xæ™þ4Bl*#Üä$ˆBB¥ª’§KÐÚ±ï¥âv ~K»ÙëÂ*Ur{ôðÆ¦Ü 7Î"kH0òàOl„£<.kò)ÓHptnÇFʪº¯Èéø…¹Ž¿t»´;þ½óCvÂÛ÷Ëܳ§Ì™ÓÞ‰ßzþµ¾ç+þR¸uZ¶õ"LÒƒ]ˆ®•mVëwæ®Ç2ÇúzîT“á3¶°Å!é—!éëÿÁD9z³Tn3h›ðùCZP ÕjÔt™í_]bwVã‚›gìÚnõ2ÖáUÝ*êÍa/'šUêQ›Í—x>1ó|á6\ïy‚05̾{Ö‡Sù±N[b8ßLÐKK=ÔŽö D–ã”dØ(ão»«¿üeË|ðFðÔj.Xçöpà'ù¹½õM£ºÕw¹ª†‹Ö±Œ Š•Ñ= (ú„h,‡|Q£àûDÌÔÐ ±¨ê?u‹Mc®n…ݾ‚omóùW›«´ÈÙ›{UµÜI›l·:ê?º•MóCI“©” 8nð¤ú2)×eʱyå5Ö;B6Äzê ŠJrÑœRCè¹B)H›)pœ¶°q]'L‚ ÷; Ï…Ô¿(ÖÉá–Øë®¦ÄPg2ë®å›jŸEc¬o:¢Íù…D;Ä^¦_Ì Ü5®'ΣãÖ¾ ?r}ìÔš££ùãÕjtÿ5²âŽV*÷2žFÒbö•ƒ™ry$G»cM‡´>ðQi(Pö¤9CjF·´Ud&µ™â¤-V­S¸Û[Çv¹gB2›_™¢ „5†9”èŠÓÂï}삤P¹¿OsÔ™ÕD 6QçK“Æ_m›6k/˜Ì¡ßû¼Dß莥AÄjq™ÇQ›Ö«Oˆ_X#ÇóvµKV[ºWBw°b+6mmÖ“?Û¨ým/9®,Êô uMwºêª<™?”º9ϯçÜP*WU¶«+ô¶ÛÛbBYVZ±nž¾)½D>]zu¿$4nù£º±ÄÌrQðí<`úDüC+K `¨N¨¯™Þ楴7@—úKÇÚÃyKµk¥æ¸K¤=1Mmòc *46·.¢L÷@¥I׃9ï}³5ÇäM‚ä^¢:pÓOà ^>¼SÞ{¤x¿;ÝyÉç¯XÝ—„¼3ÅÈvFRËF+¬×Ûg™¥öI ý^ñóbÞl2,êEÁ;šs ýÆÅ™½ð£=ÙN|Ø3}ÎíJªÿ,¤Æ`µJTŽ@9´›’NŽh.ÃÞu±Òÿu¥ËÍÏrUFÈIµKÖ¢Öÿ¶Còàð‰ëq$]‘ìN+•…Ža/_DnR|YÅçz(Q=ÝÏ‘/™ºršã)ãè¿§×ô•%Θ½~d  Úš \vþÚ÷mæ™G~Êß?§d ÷´òM'뀞!‚FY²¶26âJŽDjçÿ¯ätäiE[¡ÓôîZƒy¡¾}oWÂà£ïw~iÙ™1´³´öIãÊÁÎ$¥®Äw–0Tùœª(•h këôú=ó¿)õq?ß¶žÊ"daIá&£p†Ç2Ú… ôó l|J``÷MÏÞ9a~åKàe*¡2òvûvˆÇg2lšŽ>~Cãû¥m…)O$¶Ñ~ÍÁ($Ä&bŸIo‰Ùß%é>˶ïùÔª¾¦ïç‹3;"}˜ý}–Uàl3ªÚdN;h}è ¼£ôIrH$;YѰEyGŽÊƪäSdY+­ ïk=õS„ñ¢!3gÔ`í.™ÅÈœ÷-¡¤æ±7z8)kö&T}·x'Æ=¢÷@²˜nO‹uÚp={; 1×Ônuàš(ÌCL»'X¤#ÕŒû£,ŸíÆQoio¨°+¸@èȮׄ"ÅõÒÔàÚHzª\—óÔ/&M}a¨ª]cp×Öh¸Z ìÇzoqÁ»ºá7ìLíB Ÿˆ:ZV»…-Ú b¹Z ¾îæ#ÇÕÓ  AØœ­l° ®©{müdö endstream endobj 803 0 obj << /Length1 1630 /Length2 9014 /Length3 0 /Length 9852 /Filter /FlateDecode >> stream xÚ­veT\m–5w ®…»»»»C€ EE  U…;AƒH 8'Xp×$¸w\ƒËGÞwº{Vók¦T­ûœ}Î>²Ï}Öe¢Ó5à’³sµ)»Bà\|ܼâm°‹­;Lˢɥrp×±už!L&&(Èv…(ÚÀAâ@ðóøÄÄÄ0™ ®nÞP°ƒ#Àj¤oÂÆÁÁù/Ë€­÷?§HØ`~zð9»º¹€ ð'Šÿu €;‚ö`g@AG×LM[Àª¢mPA@Pg€®ûS+@€&‚À@l{W(Àùïè ±ÿi ÆýÄ%Ø`n ø) ä¹ý8n ¨ {z€a¨ þ4¸+ :»Ûý)àÉnïúWAnP×'—'ì‰Lׇ¡`78à)«®¢òßuÂmàrÃÀO0ÀÕþÉÓÎèþ§¥¿°'š'n†ÀpüO.[À ss¶ñ~ÊýDæÿU†; qøWœ(ÈÁjç ‚Ážhž¸ÿLç_}þ[÷6nnÎÞE»þåõÏÀpÈÙž“ÿ)'þ”Û Áäù³,j{Wïßv;w·` è_bý³3lOEØØ¹Bœ½v {LmWøSJëÿNeîÿœÈÿ‰ÿ#ÿGäý¿‰ûïý·—øÿú>ÿ;µ²»³³¶ËÓü}ÉžnW€&àÏ=ãlü¹k^»ƒþ¿0°³÷ÿøïŽ& ¿‹ý/¾‡Õà6OC‘ƒ8< ÃÅÇÏÍû· S{ìtÁp #ÀÞÆùifÙ v ¨3zÒö¯±>ñòþf辂üAèo±û÷òŸäú«x CcŽÿé†ýËS÷ià†Þn À¥1Ñrµûçá¼¼«À—K˜ÀÅ/ ˆòñùÿÿ¢áû×YË{Ìy¹yyùOÿÿøýëdùo4J «ÝŸÍ1€Û@잖ퟆ?0Ð }Òø¯÷ÿ©éœÿZ{È Äœ›qJ„:¥¦§Á«H³¿+šwwò!} s+úbø)/¨Âµ#05rU¬Ìú®2Œ»vDü¡É{z×í~S}ë['‰3KÇ{Ða.•?[WÁs‹ÇVÏË"œ´=“ߣ)Í伯[kÃzú/ ïP©GZ èG—lA yADŒn¸À5ñÄ­øµ„Uù»{Ìï~]^°ôôíë8AéÚ¤äÈŠÇ`’°! HÙ¥K†{[CÏ¿Pnt¨ÕÚïºÕ¯›ÇŽnh2ÉZâÇ+ÁÝô“¦„js‘öœëB§ÚÕ£ À4¯8'Ø*jÔ("ìóšÇÇd „_~ê8l³<(ÒÐÿ¶‡UD­“ƽà) ×(R¯CPå)”º/ ¥lëÕÝ*r͵´/ ‡ƒß0Æ´oQaÓvÐ:3`S¥}ÐÜ—²bÙii îÚ˜½¹ë£WòØÙaÍá~þI=À¿Ú…fþ¢äM]Þ Êw&ÚŸôãd„UDEŽîŒIÔ´Zb]K.QÃÁ‚oÍ•±O`ò_öåÏö¾(ârƒØhè~Ç ’¾“Çïaª¹  Ý FÛêù-½{a¼a“Ìcþcåª.„bàú7×Wr»ìJ‰þÉãpÊX¯¦’åÔ†"”ÖÙõë%?Ø2q }ÙŠOäPo-àk–g–{ðÊV¼ûëÚrÜõ{_ª‚VÄg_̪QB4 üwˆ'ÌÏÕËjzgwsü ÷%X«*m¶K–ð5“ðO .C 0œ*ó·m‰îÓ‰ õ\q=ûŒ%…£ˆXç…qyçÊÇ/%œvÎ?ž¢Ð4™êsm›ç3Úa¹í4=Û¹å¿JîUhà1ñJ·ÍÕ¶Ky.N)A€÷anÜwÒG6K<]¸R§ô€~bKt1?°¡}Ø›ƒÏnƒnmwk<­Ó'ÇÖ°‚Óèn°šï²zzÛfñ0ŒüÛñ¤{bŒ¸*ì|½y`Ûˆ¨ç ýÈæC,Ö'kΆm‡qÏçã`ióò2`áMíN&–“ílƒP[ÁÏçŒó–¿îL^ì*< ‘]ù^COe¹Õ˜ Ó¹\KòMר |ªœ¸<3iz(˃–h“1µMº–ôFÒŸøá¿îì¿{/ øqöéôÄìã³÷+ˆ±l8 6:ÖrxÇxNA“MÛóí‚iûêì‡d­—®_|ùö<YkÈ¢™¿cüt*)ý}µ¬MóHùÀs!èñ-á6…,Ù”Aæ"88ó¡hrèð;Åõ~]µ CÍ-÷/‰"ey>­/ !É„í])£¯ƒ;° 8,„št×Ý[* „?/É ¼™ŠÃ÷·S–@ o°‰ÂÐh¥°H“KF¨Çô¹¼¶ówÙd?ÍüŠm%8j†ÃuëfAµÁ/Ã5Eç¾(ÒéHþ?$e4‰çq&‘銵¶f!עɪO¾ÜQåô uUÅ:ïToíë‹I­ä{=ÅlÂ[k´½>f?Ü &© òåü+~œX ïË“b[IJß~Éj ’…‹¯Ÿ3ìZ…Jç}¯d^Ÿ‹Û·¸P÷UØòk¿x§¤Ûj†³uA]ÞÞÜœ»yË©'Û'}A„„áÞvتk`Ç“¯Ø5³¬ª4©Äc9!7±o{•(ÿûãŠyñØæZÞ>xäÆ~ÿ ¾ò »® …? á|˜]6½^¤¯±õ‚1¸êÚ£ ;y´F/2qŒe4–ÌíVœ\ßvùû؈°ênïÑÍPyW’³Ê±@‰A9ö+µþ°Ö¿ÔöÃQ4° ŒPå§å'âzÏ<|·U(Ï¿¿lkÙ÷³ÚjŸbûyÇRP<ý€5!ÄÄ\›‘ö èÙs'7½ [¢«øúî£[š­#é–AÊ >á*h¡9ï1olË3+žÍ§Þ»E›{§N[H;vëõþG~_,÷¸ü÷âŸx{¯‰nJûm/=Zz Ý*€k³¡¦² ðë̶ï´ô̵@ºçŠ0°©;Abñõi:´×iŠÖÜ5yÿh¬·~Ð*Ž-tDn­ÄÌYzÖ ÅdÄA¿ÑW³^§4è.³„ª)¤ƒZñ¥^£‘Èz·k Ci_¬•·¢eÛæÆ¤òH²X]@]ïêŠâIé§+øÏlÏè&5)wœç«éº]ý<7•™‚^y'WÖG±ºÌÈ$¿ûg#É£vÈ‘_&£ t=ûyñPNjda(<"ùdRMk‚k>;ÆzÖQÅÓ]äÛjQÙX.·ªÛqâö€Ö_$e²û ¤kVÜ$}˜ù£oQª’+Ý×Ãß•òTe!¹4‹Éî´*ìJ¼,–äW?¶ýÈœM5õÛm•AáœÓgÝqe ‚o*‚æM¾Ã.ã­”{Ð1 ­DÒŠ ß··‹9S„p2!®?ž9{—³¸¼¸/k }ÍàØÛÝ?ÔCŸ²Ë?àq­,aËbèU0 ÙŽ{ASPë~+^ôz}*bë}«¨Nw½i·)êWO ÐÛ4å˜ùàcì–€öŽTÑ>î-až ²—ÚéìC„:í3¦Øb3¹¼ÁD”†íOehoÜœg©¡“¼¤óÞÜøúUé EÇë’ñ/õÝÆÄj1¦‘âò6lQÑ:Wo€x?é –ñæ˜AR˜ûû^„§Íæ â¡JBÆ3\môÍp¬R«üdfLÁ÷Ьb9<¨Ñí,â²Uþtå_)\ü¬`ZÂ\«m¬Dâvˆkæ mŠã¼—ï«ëCãÂÁ;Œ³ä¿ç0p¨½*ç?/ E”pÏ2Ùü¤Õ™Ú*¨ ÊÌ’¯Úª•àS¸“UÜ1)’Îñ犕m¼¹7ôýmÄgdÊý² ^̳ÚŠŸ™ÎÅ7~~É=ø‘öBÃK2,žÈ{"Çd‘¢Øhk4Bä¤ZKHš''õ/½FDºÚur1âÐìú–÷Q 9_D’£J¯d]~%/ÇúFol|œ™G9D+OWÄòýI÷ïõW¿£BÑÜ7á²Q‡ñ#þÊ7Õd(Ä,$ªØ¡ÍÏ‹ÄfX}ûúp½Üi°vÇc[Bsy»1Q¬(^‹ çíÝ z%™¯K7qÑ~ó‚÷²°‹x¨—5N\±´&Ô[ýMQÕ»5І~ÐÚ*Qn/†—™.ÇL¡„+Œeîgî4p}XM3‚b*@Š>ãýà쵫p5Ôè!@„štÔ.†(¤·ô¨²ÕZË~ØÛÛ]’{LÙc / ŒLÌ>w™^V¼¹t£Çºâô÷‡yÂÎgRh~ìKp¬‰ºíð÷Õ óëÔCbôrÅ»JqZæŸÆæµ)ÒÍ·”DaWH]_m[á¬oõóh™2½›BNW®…:¢ó¬ÜÓ+͇ŠŽ|1{$í¹‘¶º%Ø oŒ¤EÔö[ØI†éx‘X³tÞøˆcUbC}äÖeráE$×÷¾ Ú4Õ™6™ò̯±™÷zkè¹¼‡ ½t£{È¢ozÜ3»¶eq—×f‚•¹EÐ[~~XèƒÎÒ°~Å$£ïº °¼û Á*®oñ7 ³¡JÙXP¥÷‘Ѝ<ëaù}ôùG¹cñR¨9h½—¯3ŽoyI2‹ÉÈG$ÊšF©”b6þßÉ6á·Ó¢y±z Š­L^œÙxöƒ¤uÉO >À/•ylËäÉž#ŸH–1¤G<øÅ Õ¬þcÝ–¶Ëc$£'Iâíðr@’›m`½ŢÔà çWãe¹y×O„y8ö•IŒ™”u@~r@ûomnܼt¸,¶›`.vË­Ðnkýq‰ èîÃÔ G‡êFàò•( 7}2»¯bÊ-®æ¦C-MgáJ¡úRV°#*Ðã‡C8z¤ÃNœeÒO,lämB½íª‹é.3ÄØ±v—…âKñZPª¼—ªu—÷ô§Ë'ÛCš¥GÚdªJ‘\=³¦.Bh6`Üå†c0£Fˆ‚ ~†ºf§½QŰBŒ-U¢Ð— Âÿ Ð3è¥ä9åŠí]ѵ°v´Ú& §R±æµ,ÝØÉ|+`þˆõ¶ùÄm4ôq]»ÏA7>½u‘ž#ªò"ƒÏWN‰—ÅÑ4m/s;èðÊ‘|Q)éÕoì+™ÞfÓ°/ a©Ñð[¾ìT“Ç=oÍoì_TèçÄw£ñ­#›{…Î6šgÛ›Û-~<’¹¼[~øä^ÑË÷{F¥í[ÅéÔ¨^‹æ75ŠƒÈCÜ¥Ó’44§Þߥ®K±TH„¿mñŽ‹71"ÝNÛN„n¦­kv•~9`—„É4M‰n‡Lš·'qt‡ôL+½ì!mú-ì {è…^V õxð8‚çF×ýÝ&»Ù ׄq/§G]CüîZH$N?€ë”NýHv1Ž”nJ! ˆÃÏÊÃyoðYYÂ3C7_`·¸y°¤øtMå~xŒ®¦测>öÂX)eç&•¿\ºÄHwbæ“P=˜Y!nnö`È•~7'A"…Ž<½ýδ¸z­{¦,‰%°[N!ù˜ƒZ/À"6p0ãïaÈt pfSW¾‹\ÍRßVßÕ›öv+Gï^ûB¡=«Ó_&(¸Y¡jÉ;D—³ÿð|â·6.]ЙB{©t‚åÑ‘ž}'·¼ª‚­•³RœUÍ õ\!€ñú Hª?z±':TlnÚë;2ZÈ¥Ÿ÷ªÛ!Lnaxg3£D€lÇŽ¯“+Ô“ ¸“æ´Ì¿-BvÊ^­Ü‚Tñ«ñóØ“GàŸ%ÿLl+èØZÞD´Ù§"u/Ì¢€ö. ÀPÉÏÇÔ¿ä¥bh4¨Óq}LºÓ;Æ[JºÍˆóa§¤xDïlÚ©Ú43w‡5 ¨ß2‘Fö¹P6L²u<8/¢…¯k]îR+Š\˜Dû Æ{ØpC.Œ® '¸n•B2¸™dµn• ›JLMÛ>gÅÀ©W„à !×á·h¼YæyYÁ”R$ùyþ4Újáï$¿Jë—XÃ_iyVØÝŸÉ$/ÒQÕ %ë“zß"¿,í&|[Yãà¦DMì–:²DõJŒw=5Œ˜*ìjž™z8J&ïkn$}å·î{h· åˆjà [22ÆÃÁw¦`àù~_&ÂÛDعåd´‡+i d\ísyÿ(R¾Ìœ•{Oy2o³¢`w0ôÑBþS›÷|ê¶¢å„íL´ó\ÿÁäfí¯w$©£˜XÉZ“⟚»÷mE9e ÚZtüW ð*èµ»Z÷Gc-oÒðcëšÛ¹&¾S|o‚sÃ1/åÅôÖ“‡)s¬)éÉ;H”¾ÙË..ñ>èJ{ÁÕg/¤¬Ü}š Wæe~ !Šhá«^Œ7S d{^,3]Ÿ¹•Ëçr“² ÞW=^£I#èí‘Òøx^j£«J ¿›3kŒÙ)ûA)|7¬D¢ó9-„?ͧC¦ð]|ó¤Zg‰Õå£Jb)ë{N]ÚÙûÁ¾Ý\:+&ÏXú8y¯FäK"*p ˳E{SsÚ"¯©ÐŠè䎱øœ œa”ZŸä–¾7cM=õ0;fÒ±üóÅ / e¨°ÅJºÿùÇÝ·©…©þÆZ/q¦hc  ûbåX^£Dc^*é«\‘N“µÖíÖÑ“›çë­¯P¥ÙÆis/Ú½>tñdÖ|“ºC|ü2ô°ÈL¬F;¼ý¼#†p?‚·¢'W}ê«E˜æ?¹“d¾o(0 ñ}RÏ«$IòÍ!ö·Ò.¯¼QuNÈ¡olÑ.”¸W?Aôv›¤wíºÁ%˜¤¢ ãfå÷n½Î^ås_*á¿Fdöå Þ—áÚ9ËÑJ¢h¸Ä¶®n¼ ü¤âŒoŠRÍ«T˜a4dXbZ•²'nH$qz1Œ&–°¼¾¥ý>õ(ô[.ãÖHøÒ‘ÈCr—bƒÐÌW8¬ß+Øî¢ ´É“€~ÖLdå KèÎγ² >`VWu«júZJQíöU÷”ñØv.•̪µ–_õÄ”!©©e#¬H®¼5Áš}ñ-p[ x2ÓýR|V‡RÃhC‚ž`Ü f4“¿‚THö§+ë²qÆóîgÌ•$î#C'S£ú§½ðí€Ò‹rמóxšBŽ4UÔ1ÖÔ`BY« Ó–¥ŒV¡*ÂHööUF¿ë¿~º·3•÷÷·áÂ7¿Ñ¥,Å›³3sÂf†ræ?wά4ߘ mo˜Žâ^§[ð{¡^ãÝlº;qi¤°2Ô µ°øoXHŠ5±ËX¨º÷›Ú”nr}ºD)eшw­D…ië€"±1 WÐL…W F,铘GŽÂ‚«x|CRÆÉÛžfÓ³q÷ðÑ/n¼Sù¹,Í£û{NK›ßáTj— ˆ;½:Šðó„U·Mi(ð…mÏÕ¾ ‰¶Z›ºœAÁ³‚ý oÅ÷ªxæ+&LÊ€)sšúšéÀ;À%%Îä…lÖméÖÜÁ£ª¯æfŠŽ(npRø~ØL\ Þ|{Ï:LNåÙsm9KxÓØ[~w´)õ @™7FÌÓ¯qk=Ã^à|%Ü´|”c[†Á>Õ £/‚ÐÕò}9ý9®Ä‰½€š›5áÇÀ¬šö¿ %Vû‹m(-'Jq¨!·l40„Ñë¾ÚÉÃlü[Ä÷LLÒ>uZ¯jùQY=ê³%ƶ…™àñ%;–·x²ó›i›æ“JŠÅ_Äâøhçžô›ÑfxZ¦JAdu}ÙšÏ6^ îÚWE÷QZ^+T~é;LιE³®¬oŒ³’Á¹É~u|Î_– W!Ò‘}“!˜8”^iËdk@|ýº¨ùi„1³éÍø$ŽŠ(±| ‹§¦Ûq˜Ä;³³ ‰²Ÿ8 ÏæN4vmFE«Ž„™—ÊEf)È&µÿbQm̧\ôF–z°ä¾úЮ™ÇrˆÑÔ‘'sVwþ@'É\kÉ ¸ÜÙešÍ7s£ö½¾`F f%lxF«Ê%¾×‹QÖuÆ”/òÎ ï»þ4­7_ lÆÒ¬Ýz{w®Ùòܨåz2¿p@âÄWì‡mt¡coYݹÜm0uþ™cd+‘ÖcOsº:Á+ŒÈ`a_î{|+Ioú1›¯çFø¬gQW†Ñ‡Õ ½øX0f§!±fÉ8¢f.BÏPçf/(û´r% g½ =/Ìó€øq³`Í(%R;­ã«›+ìŽ6w°Y²}Òê «ŸÂOÇ/¶†V³G׈àyT³£^ƒI;îû5Ò>ÓžMM 0rôu¿jÉaèþs@¬vZ—{Kt s4CæY1&~¢À0š€@ç‡Ñûšœïl™„ÏðôI´›Å—16‚à"÷¥Ñ1±+Íó¨ììµõmo÷¸ºB)èWy"ÕËfœP.› 7 Ǥzjɯ?Ô ~˜ÂÌÒ=9u’ÝÁãÈïo»øsŠÙõ¿ ò§ç;×>¨àDÖ«ô*H’б#"Rë¿ý zf³H·~bßòíX¦‚ñR¥Y‰jX7O£š¤ê| ¸H꽋{Êâ¿*OmaßWÒ“Uq)ë)UG>áø"1ÅÇ>œÑÉúVÉ{¿ô7Z–W#±nåêÿö完¶âÑþ'Çi°_=`O]JµòrmÁªÅ‘Š~…¦cóŽùCéûê…3 ?KÀ±²R+ k7V¾¸8ÀäÄ29> ýü«ÚÔPÇhqH¥ !"îsÑT9‡.–Èûl‡²“ãŒÈ7ö X¯nèꮳst>êgRÛ”y]¦Õ4{çÔh®úMu#«NÕ’!σúUQ纕_ÑëV ÒX{·˜zÈÛÏ ?uv†„º©í ç9ÜEãlÆéSvnV© GWƒ#óQaktåÖÁ"#hSµ}9ÑëóÓ>R1%ªÉ™K¿ÕæÞRt»æ²lZ­‘–Óx9O$‹¡³:ïÚa 5ü"já‡;Ïô~ yªê€4âú ¸ \›çŽ‹€È8iêÓŒôÀs i«›NqS)™s±û¿^ük}Àà_„£¾ UÝé‹V¢+Ýü‘ø<ç#aæ¡¡7õ\¿iZp—‘ÖKN/Ä¡¥„(¹‰{ÄI;²V]2¨€ÝÍÿSwÏh°wœM/R˧WÆBfÃÏ Z¯m§YÞ% è*åú,gNN“Å‹R¬n(RAàoħÐIaûn­¿ Y|É(½Rñ4p_EQÃì{žåOxIZë%–ä·A,TZ3¿èÁý¦ÅÖeQÒ i7å™ÌSIwå'´'%},¨»_|²oñ–Ì΢ø×YŠ„Å7(Áx¢,Æ‘M7CŠÅÓßå²G£ÞÛTa2ŽX›/GL WQ½¾ ³‰È1'Éë%ô†VQ:ièH3,ݨ<æuѬ…ãã6H4yq‘[9”".hxNýËØuZ‘wýŽ¢H§!ð½Ù*Dœùã›hhFLwHl1Cͨ{½d19rëœÈì(ÖÙ êv2>t–þk‹9¿N_ÒEgÔ ƒ¬ß¸»cÿ;Ý‘á×\t×Ëž·²)>ïùo­¼ü–`t¾uš:-d:ótØHÀLFÓçw´Ã->»µIœ_G6ô^8Ã¥ö‚Ç4i$÷Û Ô.Ø=òXµG3W⨋FÌšgAnòf`-=âJE9δö̃@«sMoîfWÕ£„ö}f%ñqšæ•ÁgT/Íô·æ==]¥–4ˆÐ„CÞ¶Jn\¶axñc$®§ã¼D$~‰ ›”²¼4£¶BK½ Ê;X2­4ôzƒ‹e‘£ l¡›‡`ÛÝÞ¥¤‹¸·r±I¤Q¶WpöÏÒ”N~õCšuÊДñ¡~wÊ©ÓXÄÉõ©·|-üŠõè]›"^µïÆ¡ŸXxóX›Hãxùä—Ngìó$–͔֯l»Öå "Ý2¾|ŒßŽÒ/ ï1NŽ ±Pµçºö~®»„wjŸf‡¡eK7³œlÉÚ7$•ãZ˜û§’„¨ž5*9NÑl«a<®¶»ýî®æhª:ÑaÏ*BãÊÁ;’Ü·¢9–RS%P<ß¶cœá„ŒµSP°¦›ã]µ‡¸ zÁòìJx^µ¸ÁŠö)N¦Žˆ©‘¨ÖxIí­ª˜m×ÀΧl‚F;ï[ˆÞ¹}•¥[šì74Êà´å³µ!¹’ñL%¦S!PÍŠŽgÉéšoü߽Йuñ±žÿ°ðMèVåWûª¬˜óBGw:»7&ûaÉ™¡œ~UÄLÙ›ßÅ;bú¹J‡=[3ý7{aû)G=LMò>ÄaŸpôA¦H? £e¢SºE볿1€7æÏ)íÃb$V3®š1Á¼Èæn«mCE¶zBngŸ + ñ1»y8–ƒç\ý°¾å‰~Š«»5(dÖŒá ÑMeSNþäÿv¾¯Õ>=Í^£<”<VÔ­û‘oxñ”œšé½RÄ¡¥\ä,[½ä=µ]É4Û2üx‘µ“P}“„œáÂ-8.'¬k’ÿ~Êt1žxG`­ŒÅë’̼SJÂtXýÁÓâHA£ñæg’]Ýø½x"·(³ ÛB°§nmË‚i§'t] ½„¤šAE]wAT—T¹PDŽ޼ËÀ’ãZ† ·ßug|÷êŒÇ,¬…ÙÒ¸ÞeëTTänïǤ]߸¡õ3eü<5³H22)‡Ýœž:˜ív&mÓOºKÎl•ns`,ÜYçMñ0{“•@•ir‹VÃ9uÉϯԛɇ<(²’pP¨   ×Ì=Óhó´[RE»Ü…H:„ÏÀZyIOßhW]wË"YqÑ—j¢M¢‰†ö_p3ÒæãÀäÎDN£]/º+eðÇìÈæ”2Ñį=î&‚K|ÎÎF(“r• ÛÆ^’«µ#µMñØzk]í%}Ä)ÒIåIŽÀÝ®¦a?‡ ‚Þ¢ ŠL¡Ë>x| ñÝl•/æÒJszL}®™ÎÕ5„?—â€ß‹J»Ñ‘2¤R¹èÆ0åQæç4J¾«›ŠHŽð÷Íz\QÿÝcÁ·CW’6¿öII.e‡uÞˆø¥kwÖ@¤¿%AY ØÚ>»­Q e µurl´gžþ!nƒvcÆf|j†,3¹(cù]f KeOš ª‰8¤@ü`˜Ç]»˜zš\<Á˜U:ëñÿâè©U endstream endobj 805 0 obj << /Length1 1608 /Length2 10402 /Length3 0 /Length 11226 /Filter /FlateDecode >> stream xÚ­veTœÝ’5.»‡Æ%8ÁÝÝÝhÜwÜ‚»»;„àîÁ Ü-ûxß;wî¬ûͯ™ùÑk=§ªÎ®]µëÔj U f13°´ƒ½ 3; ?PÙÊÎÄ¢²Wdw°5¾¹44Î`‹•ƒ½$ÈÌÔ›%Á¦@ ;€(áàèéleaé¤×R×axÿžé_–¿B€&žÿô¼Ý„XYØiß>ÜÀ¶Žv`{—7ˆÿñE 0èb š[Ù‚*ªzrÊ2@ze-  Øì ²ªºšØZ™­LÁö0ÐÜÁhûÐÔÁÞÌê¯Ò ,oXb q›Z½]{˜‚ÿr1ÁÎvVÈÛ7Ð ´pÙ»¼õÀÅheojëjö7»¹Ãß„Þ"ìÞ|o`ªˆ©³•£ ð-«ª¤ô?xºX‚\þÊ ±zsÌß"ÍL]ÿ*éoßÌ›×deº€=\þÊešYAmAžo¹ßÀ­þ¦á ±²·ø& 3Øälf †@Þ`Þ°ÿêοêþ—êAŽŽ¶žßvø;ê?9X¹@À¶æ,vŽ·œ¦.o¹-¬ì¬ Šœ½¹ív3WÇúÜÀÎ7ˆþ¯™ax#2s°·õšÍ¬Ê.o)ôÿ3•YþïDþ?øÿDàÿyÿwâþ»Fÿåÿoßó¿CK»ÚÚ*ƒìÞà ø¶a @Eà_;æÿ‹ÙYÙzþ7Ñÿ¨þÃÿDÎôÖ1{‹7)ØXØþa´‚H[y€ÍT­\L-æ Û·ýmײ7;ÛZكߴü»@fv.®óiZZ™ÚØÿÕtn¾¿]`{³gþ&Ïß¼Y%TÄ”dÞÿû6ý;JõMuMOÇ7bÿQ‡’ƒÙþÂwðz3³óp™9ÙxÞ'ïŸï“ïo ö•@.ÎV@ƒ·¢ÙØÿ.ý?~ÿ:ýŒ”½©ƒÙ_s¢á²7{­ÿ4üå6uuv~Sôï×þVò?Ï9ì6üXt0±NûšîRK38.iÐßË;êXÒ Y˜PíÐ㟾ÅWaüTÊÒ8ÉÿÒæ¹päø¼+ϸ7Ü‹oKד>Ë#õ¥bèËÇZ§íày¿Äú±-ýX'Úû|^qNŸ›M{o{\MýcñÙd§3Òù=C•[~.õ#ºŸijý¼NÌF(ìÚ‚£cÚăû;º‘¡Áï=—ð}»$ﳿ Ó€ü’(’\Á1΀×Ù4ÙI~ÖéœTO(¤nÈZºÕ2(DOíÞ†yç¿í^”²/¸Œt¦EP˜1$³@à6&^h“:3³è<ªº×ÒþÎMl]³ñaR_ÝËD—²‰ÊoT;KI¹e4†æ%Ó&Œeqƒê ¢uëÈR_翸¹Î’ÎnKåÎZ ²sw8åþcì- xМR8rñÈÂi’+O ÔÎMÆyþví7ô)¶ ŠOÆQv"´ƒc 8áwâÄØÇÛY×FÚŽQfÔ.ñcoLRÝ >òï 9£>c¾áÍ“ƒ«ˆÙÜ‹N }^ç9%¬%:ëEø~‚h«* æ×çVý“_Añíñ¤äC¢šI)ån5­ö*ë½×ä zŸ¢z»æ*AøâvÎLhtA ’ÉÎ]K)³²uUíû"ýQ+íq¹ëŸÆ§ë1•%ê±ù¸Wï·ÍñK,ìJøÙ l_(Ù‹¶_¬’Y}jRß§n°J›|ÜÅÏ[R¦Ÿ¬'ŽøÆà§?\“RÕ*bŒI†T5Ö­ò.Åf]Z¢ÍŇÌlESÐ~C!ßüørxPyºúÁ!Ö5‰+¢º9ôæ‚(¿Ø±3À­03¨’IŽE·î²È¥Ž€PÜ™o>è|þ²ZM{d²cK e–þ‰‘Cké›,ìm¾ÿŸä–$Þ'Lªœánä›`Ñò ÐÆìö†IëÉOÑÕ™µ¨ÀŒo‡åcöøzTò´¢ÜƒÐÞÒ5É9~:b¡¿¬ùñß’§·ÊYçLUâÈ1¿ˆPô¢’Ís<ªó@# !è9j-ÆAçÊγWÇÕ^P'½Ûe”‹ %öç"öxΘ…ÖòlX*°ïs–^zÒ­Ô¬#m|Z)šM#Áï*lú/K'è<´Ó®l6îRŒOU-ý²”0+tÒQa¶PçÛ…»×¤ò-ÓVªrÒ3 [Îmf¶é•|A™=J“úROYWcÆ{h%Ü“˜é“½JoøÙ*&¶aJw9~_°uqÁ†Ö×Ðyy½Ø"0ïø ®_ˆ¢pbêtmJѼ²é,ñN£‚œ[ÝÖú+s½ïii*=W»ŠÔ:\‰ÇB¦ŽZ«L0v#/4]Êmi7¼m,6ØæO\Ž_OË5k^uú #F8„ë]JHU÷‹è"¢)žÞÐíð$|À\€P‹=•F'9Ú{³JÌÓ.AÝa5#ܬï”îû²Úq9­þ#ðHO„ÑV>ÎÂú$Q³X/„{fÃo75Qò8Õ:ÞÅijø£úɵ„_‡‚CìW†÷¾ [eG Pm\""Ü>ç¿×Ý9š½´²µ_ šØÉ›h#ú~¦ôs3rvÜ*„˜¨PAº˜h$-9Ý.„ŠÜWf3Òa¿ŸåhÊ*e¬ªGŽ‹°tö5>3Ú:#=/Ù-ç×à®b%1Âï`Ù‹V=€ÿ(ŒEGI]/h™Ãâ“ O†Y­$…Ûš|“Ú_â‘Td†&ÕVwg·ýL]ða )xùíŒàjh›¬ˆÚƒÔË5ï.kO¿Jž-›î)ò°n’ÔWýAeXQïÚ ¼ó Ù8KÈP`²*t©×OÿC 9`ÿ¬„4=à’h3¬™UúçúÍmùÞlIA‡gÑöB™ë&|è¬"òø=’­ ñÅ8±¾wŸ°@áÂÓ‰?6£é'^G¹Üoz_Ô-Gò¿(|f8[:(AX3ƒ¼KQ¨Ñšéð#>@‰Í©µJ&ùˆ6-鯈zü‰à#M«|V[ÑòB<Ë¿C¹Ž"6›øAœJh­v7#þ cj·¤U^.Dqº ¼š:·JÈÈÍ;PÒ‘^È}'EZ/ÍyÓ/ÙV¢çTQÞÄéžÍ€Òˆ»ˆé©Î¾óòõ|¡…£ç¬6ÝÚ®SÙ5Þ +IÓqd»”}´bŽÕÁé‚å¦ÿñ fùçe^ö‡®/Ì7“9j‡‹¡Vž[™LIÜä5g4CDŠÌßøé¼× †¿;Þþ–ùü y£¸Z_'!S÷äýŽv¥H!²ÙïhMð?ȰÖðœXŸÜ=ÝcRK÷Ù à:im+½€Í™xAÇ&Ù0ÉóLJLhã]´n[wÇ1Ž@hCÄJt☠iCüe³#Ì­ÌTVj’ÐoÒ‚Zd¹áÔ©tr¯S¥RµÌÅœ€Êðô ´ .Æó©Ußµyì(íhiˆYÚ‹Á Öð/Öt4›‘íp@‚th#ü«xkýmLl¶ƒd„è-ó.øVì§PìJlïnMu¥äH(êkÊÑ©£mSE¸©ò9ÎçßÊœù§£¾<¤s¥m¯–ê’˜ónljFÔÖÝq‡¤ Äël9ðËÒ“Ϭú5Ù­1™þ|°yë@÷®è±‚ $U?‚%AMÔFcò•.¾„£A¾×êµkå"ŽðѬŸ9S"uCVEb'ÈT|¸+ÿ»H¨Tñ†=©·ÔDYa+¶qA5SñìÊCINUY™ rØ \HxƆÙ­–ß ½Û½}ÃÇr¥§Õ?ÚϘó‚/{húed’×Hi2-ÖŒê½ qA×þœÅQõìe:»“ß”tÙ­Hèh~©tWääBËFUZÛ'’3`å5ži³Ø¸''Jøm ÓGÿ*)ë(ÙÔ,L@gúý£jñ”¢¯aÚ»Ò‡ xá,y§3Ëðý3W +Û”kÂ×-ý§œ ]¬ f®ÛÈM–Œäãù£y¹Û';XQÇÐN4‘ó?]Ä™z‰¥¢©Û°Yf³öèNAo]ÃéïŽò^Ù¬àN§æKŠ·Õd[„þ€½À‹ÏȘöP2¹R¬õqÅÚªô/”‚¡lÉäe \VîVz¡ùLŸ¡ƒë…Lðgò¡€Ÿ öåºá6Ó‚³óÒOµ—\ë ÿšàé"ú ÖÇçzFú³`«ì}m\‘+׃Rò"M|Ÿ0úÃóaÊÓÜS„‰ ǦŠIºüH'ªö¨¬Ÿñãç¨FÖì%WÍBø—ÓÊòv“åi@q½@=W¬ èå%­™¾ÈaI_Þ¹¦O<ô1~z^ÆŽŠ{ÚU ya¹J§¸¸Sœq¯3™èWPžÞí=ᆀÔLù1œaßn ŸMCuˆôÌ˪17Ìî*u¿½".4%Ó“ìÁéY[«#_›c:ó{ Ý¥\xgT0µÕ# ¿ptÚlWXõØ©0=odj¾•ñª"¿;^£ñ܆æ½ÒS°ŒF{%åËêãC¦7ƒnIE(_v2³ÑQ›jé%'Ã…QÛÁSÄB• rÒ;Å‹Úã[Z,Sòݾ)Ò¥îÐwªN0˜O “wKwÎÆCDZ1\8M›ðK~oŠT^ >×5ð‡‹__ã÷0Fg‹·z®bWÃøÿîp;,ÊòcqúS. Ð¿ÇYÏ.ñôEs¦¸é“…àáo»]˲:­™'n²Ëpi›Àe-è¢; ^ÚwM U •Â=qƒôþ°že…QQ‹ËGv2FTø½ÓT²L”ÛðÉÂõQç´eÝ•h‡Ó»ûªî|îNiR#ùªÒ5yëSȲÚÍ!CŸ› 郚‡Œì6Oa½¢äK(Äcg<6ÁFú딽ìù¸ÅNôÁä1z—©‹ Èšw+UÄÉq¾-üÈ‘ÆçÔ»l(‹g¾ô-Äö2úè1y©½ŠED#õÊ„¢C/ûèKÞ(¼°©¦NQ ±Ý¡0Ñ#¡ã>ÝÀ§qúN ukÖþ÷ºŽ«–®m´rõok¦-‰X.]|¶¿ñw¦»û’+ü%¶›9ªˆy«ÜIÀ‡¡³ RõJØ&‹<þI–h ÓÀ+ºnÛ×ü8ãbÁÛ}Å4éL––+D|q'wŒ=Z!'9e´1mÀ¾¨ø+Š9wA-uA>±å“;Þ%Û÷ cª7¬Óà¯s1w#©,#F‰]^L¨¶Ïz&µ[šÃßݹ`I¼tgÆC£†ç°8%gÎü±_#ˆ+'¢f)¸$ÛLjI÷«ž7$›@=ĬG×›ŸÖé5Õ;×uX6üÿT­öa¨ œ‹ÍFp"2£ùª9œ‚Z›aÑâ'ijôÞ)ª·Å{Ñù€ мûKHÝ¥tñS¿©¼öT TüDßµ«ä¤œ$'z_vÕ&©-®¦I¯›U]¥äÍõ¾ý¯OàJ;ÃÎSÈ‘s.Íp Q IeŒ]oÌVü!(ÆÞUåÌÄ 0ÅÚ⯸›(ýþ¨c«øïr‡ƒENؽÖSbéñt\"‚#¾K1©§GÿËøOcŸf¢{^VY µì ´™é§[àP&’›<±_a´ëUÎÝ?®ÏÚ¿9ïaQüõÛšlþ¬Í~‡Mèìê™Ö9‘ðô-ƒ¹ç³¼h¥<9ñµ)2—*«•ÁüݶL@eµ–2ºÙdù…©~9VV[á…Êþ™ÐV™˜b‰ëãSþN—?¡Fïd1¶:<ó×Dœ×F¿èåN‰y_»ð~‘›rAü`n¨û[î™GÚò”'û¶šu;f‚Q¸j{*”y™ðBak-ŽT6*, Á€˜ŠWG·XÒÔtkÐßÔ^X7¨  )íäøÂß6» .±Ù3Þ¼ÈJì!~Ïã4­„‡T —ÁA"íøø}Þä‘g”:Õ™ýÇê‘LSr­@pÑrÉQ±Ñ‡þq›ÙuÉHºBQäÄûE€@aý¥Q„èeh_ïÕQGàS¾·ŠR­ó@¦wóñ'^‡,~-å·T2¯Uù¨”åO0^l´>À‘jKÓþèX ºb”°‰qü(Ôì;Ì nš+ œ„R˜¢ ÁgÈZäFyugzq OùwfÌ>é~.ܰ×CoôN½Ÿ§à³q«r?œû½Ù8]¢ò[%·]ôFôתHáÈ ¾…¸ äw‡/ŽÃ&$¤cù½¨Ä¸8!ÿ›lOXLxn“^~~•Û³0üneOìä;öu˜²…/´6 ¤ÒK$Ò*ªƒïÜ6þ;ÿ3ú7VRd*‹ó÷n}Dן÷¡Î~L'[ÿRëm¬¤éma³¹öÈ:±+A}=‰ÖSgúОˆ:9%<®% ã9:x}ná²£ ñÛ‰™fÔˆèí¯v#«IÛ\‚9­’PûÂÌ:uëâ|åÝ;ƒ%Ëô‘ñB*†ž':ØíK€›RÒK¤‹Ã´-Òå§T~õ`¦ßäFæØ÷Ø0,4¿$Í3¡>­hýÀßð¡Þ`³œ÷Íò…ÑA+¹Õ¸cÞ¹:3â¸Jîíõ§I]T~‹2@'CµÚë…Z„C#ñOÊÍH‹‰€ßÕh÷]²mfÀmƒ…ÂßF³Æ) ûÓ·Xgîpl“²ƒJt ða¯ÌÒí>Šü`ßÛ’ÃÔöo9gÚQ˜„ÜndvßIôkGr‚ú4ôý#Ú¦ÄòÌúóá<ÃËa5° ¾³s^/ĉ){IÈÞýGmìx/jY¤n@’Q è“J‡öÙ«aa”¸Œ…ؤamc\—g¡›$'ž®#ËnκaöéßMi‚G²•ºËÍI9Ö]¶üKD—>ºäD€F±™~á]Ïîôãq¨Ÿ¦Þ¡ûª/–ÉafÏd^Uö—s\EÛ„ÇZ&v];À)æîÝ̱…¡ çÔ«=sᥙ6äË]3èn êÊ£¦ñÖŒÖSÛ1‹³3ÏEÝþ¿T¥˜³ù9׊Dš kjà¿ÐŽBüóä˜⬠ø¾!Þ7å¤hÚ$âa—Ck…öïJ–\A×cxx-‘‹ pïƒ~& ñ8Î<6NyhŒÒŒaò||T&RKyˆì$7püÔâê³&â Ðêh.?3&L%o ©f¥v’qp£O5xÑÂïÓ¬—ìÕRxJÈóñn§¢ÅLˆµ>JuÓMl±T·à½b”·¿¯:ÞÔy+íZ|ÑG~ ´;õs/mÜj"d"Ït?qÅqÎYÆ?mx|’㺔á¡ßmæ}ø‡­e¡{äþ 4ž¥M"0& 7÷苵´A3Pô ÖvГBÞ†V}1¦´ä½œ+ZyVµTez&¼ÿ¨Â ã[ÎuÀʉÌe&‡0›àÇHîÙ »-oeºKäó¼¦䓎jU&Ñíq¯¡v DjÈÞ0iJ¸Í0Í´ÊÕð2¡ ú$.Èd,jhéùIófA'< ÖýuÙ¸vƒk5Ç/±IŒ¼Ô”‚Fà(ñfÏ9hÍá¦êø¬$‹)Ðiþ-„4ÙýØ×û¢HpÓªY:°’©»ÿ,‚6‹L…EÌgîÎN'þŠÑIÖ•Ö+iñðs$—W3|KC‹Žî @³žÙþRÇPîîæ:ÑåÔ|ɇ¾ä™ýŽæd‘G ŸŒ5oßm'óœÈ¸Ñ’]h=üŠ8q´Ö©¾¤Ô.”àËQ2 ó!±«Õý>Ø—Áÿm‹Ÿê¹ÒÎÜ#3ÚÐû©8o¾«wÅ#d‹ÍñÐ)ÂÔçw¡ ºQð04äm|Õ]fÆ!ÞdQwbPþÈp™H ¥Ü,¯êž³ DDI3æŸ|et4Ôö¹¢;ož˜AµTRöÞ<©„À«rh]8÷œ{}ouh¾ÆìŒ]^¼»ù‡,(i…©âÜly8«(è}ð¹UvP»ñÀ0«²Z6CĀ͋&m—Z¨ÛE`5שûÛމ-v¾‚mº›ÓÉã¶ðGVÇp|aÚd ñKÀé`Ã~Ýw#ƒ»ì@UÅCB6¹XZլ㚰+¸“‰ÔÆP‡)¢ˆK‚Ì€Sþiý)Ž:ïO}Ŷ—r–y”ö¤•n“!'6Iœ¿•&¬­(aa¸U%-JçÓÔ:?Õø‚Öׄª¹=øùl˜W¼Éôɹ qŠâh(½ –ÎAUy$ªgðêšÕ†/³ìƒ¥nœ…H4%Ï=̤!nU÷ °Œ„ºÅÇý°H6N3Îv¹"ƒLHêÎæâ^ ©C.ýy‡$S¶.°Á˜š¡‰CFÐ]äE‚sêqÙ>¿õ QŠ•mîëúY[ î›âm¥™d€AE ³ Y™$Ig°ÿ¤íDJ÷«¤Êüçt|‰ÕŸ’a›åíyUô‰³ø_#Dy¬¡Õ"´yq¾²°G¿úã vš¦ 2Öö,çYˆ_pƶN!p+N׬-]á^Õ‘Èé+$Aæç—“úЈܣ@HÌ*æ²g.£‘ì[BÜ ýô_§tcÈÈî«·‡²ž¼çÆìêþJ“ã‰+53¹\‰¾$õ›¨Ó˜´íY\нÇäA¦–”èÍõ´ù×@/ˆâ;ƒI5ÂÌpBÏ%î r^ÒFÄRú41–µ¶–j:Ç/M«.\2ŸäM6[y,¹Á?wK¹„–KLG\84£öz3§÷°0[/ñ¡Ôp¦õ¯wuÜXŸ8Vp Éc¸óØŽL¸SÅãØ•c§s™bQüR,A*·‡^G¡}NïPÓc­°û @õ5| ùØÅN³ù5 "­QMiŽ©!{š°ZjȘ2LñíV„dø>áñu’˜ˆ%ôp™0ó$}™Gº©¦dú< ØQú€Ìu "Òn+–þDõg‹ÙŸbAXÑü±ýîRó3¨Ó/Â@P*‰ ««Ð!l̹)t¥i³¸í,$…9óå ¦ë1Á¬ Ù´€Û°PµeÔZ¨¡ZqµXú—çgë+GÞ/’kCxÙÛ¾LLÆlg%Ä&=ê×ÌOúŒ)é"0öòU‰‡‰Wü}Ì$BÄÇÊa¼™v|öL¡ªsSösÁ¢¥#yßd<Ÿ5à¾e¡ì–›Ã½Ú“X|ÇÏfÕsGè€ÀáˆwÍ`ßj>†êAS(Éõ½å úµcêóн](æSaQù9°ÚÍÈîåÂwhÜ(àÉrlæCCg¢² Cz,¦QPå{=l:’–$¬ _«v[‚¤½ÆaÒëûç†èCÙ.½ é ƒNŸ£Í?e¹Üó¼(9K(5/½_Ô)d[~µ¯ú×Ûâ>¶1Žß'rèÿóÁ¢È~ÞŸ¼V–xwì¢1N(Ø|­ŸË,b6˜½¨/ãCš ! µ¼ ý›?,JŒ(÷ÁݵkÁûûîÉ,* vk‹”îáKöD£…v‹sìÒ`ø`©²â}°k‡ºÙÇ…4ç5ÕŽ^ƾ[MÖQÚŠ;¿GC)·½C®ns,sÉ ÅWph[!ˆø¢ÑØÓKÊûÜíhã›ÿÉ üš˜Ñ5ÞeŽºÖ^RÅÝø“‚—mnG>JI¨§4Ûoþ¹Æ¼Ÿá^,}}Ãé;E$¶ú` ¨M¤ÿk¼uMo:[Seº)L0 ì¬â.y˜\ðyÿ,Öy1OÜA¯žKз')a޶—³TŸ"²&5ïZ °ƒÅu†õDÎÅ]‘‚ØI¨ZÉÜ Þ¹®ÁB´xŸzœ–î© ‰ŽhùèÜ-·…­Ú×Ù,:Ðîô||·Û¶‘r€V~I'Š2…ûý5©»‰^'B¢ëÇ߆mw••zÖÚË?ò] CÎÚäüFÄ<50鼃…ÍÆŸn'S¨«[‚” Þ’‘sR¿™£–Ü1‚¿¸ìŽD‘M5@ÿ¼žP½ ø Ížt«j?áü4†,évgá·‹ {¯wéy—ç«C¨Ò$¹õ¯œiŒ7òòõû4>í?‰œOVšxΉ+Ø9ðCñŽ—¢fƒŠ7øñ¼ìºX«;ýÔ&Û’‡r¤DNR)dïa¼O Z\WóÉ ©® à)×E¢,¦×Þ«8Ë7ÒwBÉ|Óˆ‘=iE08ð­«uºŒƒš SrŸñ+çêòõÏH8D=<.düq]…2ß–¢‰Š5ì±rù‹ÌÈfF®n}’&¤Xo´ =…2啈ßL”Õi/†…-,Ç6ÂщŠ?t£(ø´YÊÖŸo´Ý¦]ѵ¸]Xñ¨Πݢ²{gè¾óô ø(üE:¤î*w‹EÓ() -v•žÉ–¿ÇGÒ:*–ÔÇpèi¯ãÞ˽«%å¼]·jSpe¯žÅJ©Îw  ù}ôålgD/ýÜü»fê…å7ï˜B?¢g>Ѫα &)­רú Pœ»læ§ *Ÿÿ=Ë( *–’*@á[HþÝy;Ľ}GLBêI§?ÓÇ ZScœûK½ID­f2/{­"Ï,;ƒ|î‹3¤4¹NÅ QâW?9]0ŒÝR¦]q/%Æé jmoWÑÇÞûFIšüˆý‘"ü+ÖØOR8æƥÿñ¨¢fØöC÷‹W¯ÆÒ†¤¸Kmkެo mR'Y±F»ýÔEZg;žxêáYº¼R}y5WÁg8Ê9@Ÿô8Ýdä+—™"ôpÉ—ËñÊy(<úˆÄbŸjH ÔT7Ñóe,ÄñÏ·BÞ{Å)ݩЦÎröŒ ì;‚±Ñ*’ÔI&P¡øoû2õçÚ;MäǸâŠÜ pÏö li¸€†2¿Ï<¸VÏ …WÙÖâ΄áñ’õ?>˜†Ù¥­ÞN ÛÞ©«Û$¬˜špNèLffÈvI² ô&ÿdýZ¯ÃTˆŒ$«ö‡>î,ðB"B}ÿåθƒú±çs):.*Ÿb›/y®C¹@é.åïýÛ@t ûuQ¨·kÖ>¨ Ì[G?ˆPXwgÆcŽí‡´ÁÍ"û›s–7e_ÜîÏûS¶G¨º½ÊLQ=¶*–¢¦õù–å†WЪ±jÒàëUÏ=ܹŽmìét>6¢càÙ¡¥é`Ÿµ£ƒ©WÓ‚‚*ÞÞ_iïUï'¿ã þuNúç+åûŽí†zöŒýèpé&ÙŒOúš2•C`3D½Ü±_×x±_­â8 pT´¦¯ßwúú=ñù+¬gúªÇæÜpÕüæ÷Ö¬•S¨PWÓ#`P…$~ÒÁI”µ¶$\yÁg··)²qOŠÞ$Ã«Ž¢’#Eej™ñSÊŸªmhøù˜§M@{jS›È›×a@KK—— ¿(IØåL˜ÕÑàšŠ1¼ÄÙdðבͺ»0D))Ù˜bš:D 1rŠßåŽÌ³}:€À Ã°ô³QUÖÉwF›ºÕ8LÃ4±!ð°h~˜½âóÿ=û݈‚_}è"ÆqÒuÉÐoàý<«tbŸÖNÎw]ßÈr[#gά)Æé†ÿ=„ﺸÝÞÊçŸí©&õ¡áט<Ñ3Ç5:ÔeÖ×?4¹dE#ÐÕf”®;S‚†”•ÞK4²Â° ßBiûÌ)7ÃIX00-ÑéŸx˜6–²yêªé%wïF@Ëf¥ò¿Ê*„ÂäëCüôŒíüôÁCâ¥lyÔF£GŸv{§ÜÞ%tÿb.XÄ€ê¼*¬oÙ'uÇýà/åYÛ!æ·ý¥ M€òûõºÝ@t:; “ƒ¦ûÔ"ݽF/rO-{i÷J‰OêÓ³³á¨hm'íÊ=m®Ì«cwŸæ…öo|škC™›¯ó„²7–ÛÍ¬ÅØjGâìm—OÄêi`+xÚjó¤ÁäÒtÕ(ï°ä^¨¼k¥"Nò˜ØÖ¶%êûá4$¤ …Uö¸Ñ¡;…A“ÕÐ"ãO‘Õ˶?ö%h蜙¤~ë\ôpÐûl–H Hº=J¢~L ý°ª— ?W€y½×\ßFðÎÒf o;~,ìÖRÉõl`lŸmð© w0L&Å]´ÂoÁ1÷(ñsls~§[OçØB2çõ¥ç䋸F_A~úÕ;©gÝŸ3ß;t\Ó„1/±J™ïÑÈ4ïéék_º3Íí²|ò1Œw]ù~Ø»s}ºoÎc†B(5âÂseöG¬m’ÁÙ^|g´AU‰|*»ÞïA«wÉIÅÿg§v1t íUicÏv„qßBrã”Å¡iƒßz2At M3¾}§ó±®Ú[áËšA°ÉÎ+lô=Ÿt«ž:¿žÄjõ~bl°`oû¸ßvR¦5û¸,~„7ƒžzžm ´Ñ÷¯Ê”öQ\{βVÄb­E™§¬ÈØUmñÝ¡pŠZö¯:Xð´ð6É=¯¼fEÛOŸ… `‚QçÕˆè0úü¦Î%ùšÐRŸkùZîôÿñ‰fŒ endstream endobj 807 0 obj << /Length1 1166 /Length2 7092 /Length3 0 /Length 7864 /Filter /FlateDecode >> stream xÚuveXÙº5 îîÖ îîîîîÚ45Á ÜÝ‚»;‚C„àî.Aƒ»_fÎ3ß™s¿§~ÔÞk½õÊÚ«ê)ªwªLb–s 4ÄÁ…‰™•  ¶7wuÖ0sPdR‚\¯ —•&ØÅø_ô+!á4sC$Í\^yMkW€’™€ÀÆÊÏÊËÏÅöºfåø+âÄPuÛC>T.@';°Ã+% ±pµ:¸h¸::Ú–ê@gˆ«“Й`õÚÙWH@=À k­–ºãßÀÜó/ tƒÔ¯ 7 ÄñJ¯)d€@§×¦-ÿˆUµ2“²»ü1.€ÖÚÅÅ‘Ÿ…ÅÑÊ øŠ1;[1;]Xè^•r°”€Øÿ‘ÀéÍ$ÁN@‹×¡7¦†eT­¸îõš#Úz¬âæƒ(¶¯Òæ½ÈÊÌ);Ì6T*‚ûřȕ"É<[ì̇³]Ùv5îN:xiü믃{® H(]¿—R:•  Ü©—Q[2¼Ÿ!YE"{ig VGO·#£Ñ± .„^Ê••ÙŸÙŒ¼}×X kôÓ,™Y>åF…A£äÓ(CÖ$pî>W ÷øqÛUè$Qņõ"~":¢ì©KÇU¸rêå0•¿üXjþYHyXZ›¦.ái­Óõ˽p¨#ã J¯†¿ƒh =è¡þ<©u9·õ5âIú$ÜÊXJpN| ¾é'ZÄÜ!ÖO–j4´xO}cŒšP1"›Üð†Òñ'ïîZ¤â7»bãá›á—»ì#b®Ýâzüâ žšYulÆÖ÷‡çø³8l_Ó†šExQàõÜ™[ X¹²p¿´Ô­B{~lpÿÈwœ`£vb×òUh7’9;´1u7hïYy¹–«ÝÆÊFÖ‰u»åÝKÛh,§j½Ìó` W,½%*˜Jv3¿¸¸.E™Ø¦«¼¡¯¦Œmv<™ØÜŠíÖÑæ ìê‰dwž¶”têéÕ!7 ãP˜Ä,Žéj~<¬ZPµ%±O>S+KŒÚ}3]Ã"@‹cÇAýCGiã÷%3æ½µ¿ÉTõÚhViâ”Ú‡¡=UþLU‰ˆY½ó7ûH·H¥O³P1Èž©-­'æ‹*ðcdPYøVç®­0ŽOO“ù%³Ãþ´uí·ï·n`ôø¾W ;wÅ5¾?Æ3)1"õ¬É‚ZŽíti,ÇÚ lÊÚŒ¬dݵ&H”³Í- V½S3 )ÙÜO˜NO`‚¢ùQátðÁ{.{ü´v©œ“Š$"©b®­ží¨¸èãö2ES9ié‚Yì¦5öœ>q±†a¶B3,}c>‹˜´ñTðÐO!d7í"ØZ–­ÉTí ñoç.Æ]/ðHF½v2ㆇ-·è îÚ6ç³äx’Kó7Ô½WrœùýiWÃ[$†ªê›Ø7D– ,Ÿ4½Z ”#ãÚGØyê “ÞØ™¥KåÙî}DÓÚœ ¯¨u¡ËÊSP&ëBjªÿVP…èùó5¯MážÍÃwä¶F'Ö€Gî©8“—ƒÓR›£‚-9Ø{‹Ú©"JŔ΍V5È?¥¹ô$oôxq[÷¥,ÛôöŽº%W#Óf&¿7…œÊ®ñ×3RÂ>LP±ùâ4óàLÄýêý…ܯ¬‚Îæ°£îƒæ™rG@6šœ‘/\ì¼RëgLSˆÜ •¢ô…Š-êíýZ ò Qzwš¬1Ãü[©s¹ß:¼NY vøgK(â ã\ÏüÞß G"Í«!LËÒ-ïæ[Oypµ÷Û‹~Þ?#amï­íZ€²xº4é~Ü›¡£Å¡c€ù±ƒ@8fÇKG»>bŽ[¤¼ÄXh ¡fÁ±x‰‹¼Ü‡Ê›Ô Û>ð¡&I¸ôé²9µÓŠ®¢]þfëÐcñ»#ø]‰Ý—Vß4Nâüqò'¡²QéGt*ÖM 0îQñš— 3ĉûÃîhWè‡B›uPŒÑ3×å·½n‡Š„}QØ“‡«ãî0§éÓ/ç¥U@é=Ù,}tÈx:¿âÞ…GPȱÝa̬ 9\œÓSÁý˜EæˆÆVw?Êk¼{´­”ÇòÅy+å¯YnÔ5𼤸y&‚IÍ›ëÍ’Õs™êdÃHðÄ%ìÐ/b©~GööÝuáR<ê1ÉDZ8”Veã®ó#âj<„ÛµÍ1MICïLå…¼çYX‘ŤÎY’â¯GëÑ/Úݲ«ÔdAÙj©[]è9®‰ka"`W.l0ÓYßôÌø´óÑi¡,*AzLáÂ×Ã?Túf“éI’H“9NƒÕ÷gçŠÑø[Áô œP§bW¡kYrBþèho‰0"IÝLaؽ· Â…Ìg¹X“áöST‚tO†‹ð›Èh=Ì_R‹—i.µyƒw8,ȱ»ñù«¼Þãuh#—ÀÔkl^=yɸ¾_øª¬G\U Û ½¼RÕ¨uX2®|¼«ÆSy<0|{vµäe«v8bÜѶÃï­K ¥³oZ¿ zs)äÈÒ"¡»Úin¿Öbãv¤_Òz äÃ2iÎÈoLž^Xú#ˆRÁBãbkíl®‡&q2l(>¸´a0޵,»]«NĘ?Ky».'ÑêÛWÛÃûŒ%gÕkÁàÝ¢˜uC£wøk¦lÁ…xw’N¸cjj2‚ode Æ/Øi°¿Æ?‘Ó •ò‚yŸü±‡ç[¼÷.(MNl¿hN?¶í(ÿâéå*‡Ý=f穼!å„{ oÂÕÏœÒ )Ê ÷{yËøààáƒAs«Øƒ¦ƒÀ!ø†Î«+B#úÇ϶HÝW™×/Ô¹l¯ñ¼ÞK$¢çT¶ÿSà•Ö=åÏëO£þ3çÈ®'û+$W3‚~Ü#€õSÍ]½N\óªBF³ÍH$¡êòn®Æ¬À±ŠîtQ¸¦"îAÌôU”È&¥ÌæiêЉ;3qO-)ÅDŒ–Ú`‡ÿ¡Ümë’°_!‰eÕ1Æ‘ì²OXýötehšºûŠgðIÈžâ„ý£C÷='Ça‡fϲԣ*ÞóOM™'qßò'/˜€ø¾þµ>DIíìJ>ι°î‘%ÉŸ8õ£{B¨|&¿\ârÅ‹?â£O‰”Ò”„T‹wÀn¢ù·NˆzEÃgö××ðГi‘ðSuªÒJqÖxôT¹LaH{©ž±Pž&›‚/XwSðà9‰Ê+,£š©W÷^ªOã×ׯh4GWl‰u=ú…Î5‚¶6%¦34 Hö®? Ô?ŸŠ¬Îœó”+1MÅR \,’˼l£!Q9„‡ë™žädTò`Ê•ü`€4 Q‡µ7xËq9ŽPn‰t;? If’Ý{/5‘Óõø¾ÊÜtgë})&&8êê7iè7m,NÝnW&3].•@sÛ“çñª nW- ã+WlÉAQAÝ·Ù‡Lcµ Žiƒ‚§"›üôPáµ)(+©X ÷g X$G’2¶ø—í—t+·%énã5£ÞnY‘ÕŸ®0í5ÕhóåÖ‹_/>i±!h‹ñQŽc]øN¹ÔàµEÔ>Ö`ÝŠŸ¸ˆ$×WÞ¤¹±"Œ#ØI¡_PÊí¶§]Ä¡"»#êU|ò _ŒÇûž@h®0ëÍ›D÷,¤açº:¨O@Þíu¾Ò¯Z¸,ý¬Zõ…q@\v®3÷ ER°^h{ ŸQ .ñ+,“È–¶è‚Áb¿'GkhœåÞ0šXoaÏ›ª/„ø©®á þØÃÔFyߨ­´ÌQ„ã#0­æ”ým=މ¤ƒ[Èöéú’876‡JxRø¾Ê›¸·"d~¥J".g#]Ôxå^¼B“ ˜—ËÜ èCÇ‘´B¤ÝÜõ?è2«Žr*b6þ¸ßì÷ÜèŠÈÐ#‡ TØß%D.½A{8g!äÞvXKù~qD:Ïj£«>ÈM ɱMSC%d™•½ÏêüÊd‚|Y=ì× ·Ã«Ÿ|5ñDtqó6˜^Ò®ìæ³µ¬Y4Î g%)ý;‚i¢tÂÙ­9—²Ü쬑w 3/ 4ëK7ØXå²KÎI^Òч_Zý.ƒ”.ÚbQԳ߭¿d±P!z6w¢].ÃJuÐ9»®| CÔѤ]ý}B§×~ÌQæ’^·¬%5F·½ú‚âCãDÖ¹¤…s•–ªïÞLK”W¦>4RÀåA<…2±Êµvsò‡/;³ãƒš;ì‘áKÜýÓ‘[Ý.š ²p%ÞxlœPÞTþª óÁkê™g.«Ïuã¾çÂCo›çOâ6üýûË);åg2õ‚ª6 1isØÏË)d§6Ë”%ZÑr ÆwŸð,ñ3Ðqu»êQ6S'5ÑÈP›×õú8[ÂOœÊB°ChÝX€ƒÜWNgÌp—èmYvk­zã4IÓeR¾&¼‘µ­M&W{aÅÒZÂ~[êž°J¡;å÷âôIàÕ¨»Çä6 àŠWeèü¾+?ˆ Êý@ÍO·¡Ï^‹6gì·žÛ,ÊÃëj‚mXµE{°0å<¡ü ' ~éx–¡ðÂF–ÒZ•µY¨Ç”òÎO|‚%K2ÕÎðNøwÕêðq òõK‚Ë)˜®§fÓ1y‘˜ :??HŸ´œ¨Õ(u¢G¤ÐÀî9ˆÏ™âOS‡ÅB$n~ØV%€BÚS©*H¿WO(é\R <‹?/½(`èÃÞŠÏ¡^KSnÆ®âw§ øŠ–Ü%íÉG!tû»ËŠSúª~7½Q8wàAÒ‰ÅtRšûE" êŸ6ã1ZYB÷ÉÀϧ’é2ô˜µ±ϱ‰Ôu„!óCSø.ˆ=ÃÑÌ8ŽS#¾¬ìÞ:-@4cÛm&~—I ú™cGõã:ÙeÓ¼·$*£{¤˜…¶¡ò¬a#u«$jpDz&¥ÒÈd ÔlèÁm÷ö¤ (c p5ÑÑ$f—QniQs…Kj"é:tâ·|,}ÒèuX ¶–¤nXÔ§Ðw%-Ó–Í÷p¹“[9kžlÅ0Ù=™ÚÁw•Ú€º=…·Ûƒãîë¢È(“—×i¥)uDÖ0ÖþdÁ9çò/{¦cN†›ktÖÂ>Ib’*×ml–RÂäèßÜÚV1îÎ31’yå9è@YÌÁû‡óâÊ|!×4±ÂÝÁn–Á|,ìóºŸð i["Ä` Bæ¯A0~¾(ÍÞØôL%Øü›gÈ»˜é kxÒ,dýÒÇм;.IÖ5,xgè#y‚Ä…L‡Éiqº$×§œa%Ñ‹þU‘+/kSTÞa E×95fnæÞ„ŒÔäpáö‹Ùϵ>3páߢÛ½¹Nh{“J9 ù ï¯Ï&&¸F‡šÍz»LIp`/R„2Î@ùùTÈç±¢©LÁhʉ …5èjÜ`¨$ûîò½Õ$_)Ya„ʺ,ñ.7ÜFœÅgú¬ëy¢ËT³&_ ñ>ã~ã:·ÇÞçr·,ªÉlÞ¨”Ï­®¬Rº%ÿîŽÆfôá= Ÿ/û÷¹«bþFBÅ~×&JDõ¨e :ñËle2¶V~Þëç"óM¶¢GÈŽö‘µß÷OÂ÷‘$T—]D3 bpI¾ïëßÅÞ7´Øsy¼ü–Þ܇KQ¬ ãåGñKâÔ ©3óžvÿÖÏäâ2,Úuùûœøñ{†»ŽmOc%*ãc ZìûC&~ìlt)–Z«õMoɸåO ( v¯N—ô0”}®¸wŠæ*n—â#•<ð ù«óJý…WiƒøÅäåÁÃú(Ògø2¨=âõK’x¸¡Þ×Ozᘊç 9|û§¢‚cMBûõÒʳÍÙä_ßIèÎÇŸ4$:†ó§+[¿$¾"e ñ’5‹‚bú|r¢mM—ôYÒWw·*¢F$-Ÿ{A#g‚ÙžU›š‰ ®ÜãÁ*³¬)é©Ô£ìO $_‚Z_«ƒjõïÆkðè– êAZƒË(Ó8Ì·Ñ]±>Ôá<Y½ô9Þd³õ‡2±s¼pÄŒ¿š%/FXjÀyt’»ÔÝ×5 •µJ׋,˜Â)J’$?p[þCI3cJd¦8wu,CE¤ˆ6ó­ƒOçÔ›ßmŠúbd³B¦È‚Žb…2¡(¸îÔETËÆô›MR ž¤®§ÛOh ¤BÈ‹IfŠÎÖØÂ æB¢gæÚeÞ²ŸõjAÊ@vyu1ÛCJw1uEµVçË Bi3Ú὜ßê£B^ÜʳÑë_9øÓ7d„Ü@œÛA3÷ÞÓ%¶ˆêÄFøNu’™·é".—¢I~~~§±GyÚ»y! ‡ ÝfìŽDš_x ·Ø#RFæ˜`35Ã~gnuÐ ¼<7.¹t…?,X(yЫy†Þb¿ÑÔú߸wÑöªÀž†IÍó†@í9ö½ÞwFŒÿ¥P©\M‰$: ¥{ðR߉ˆÜDÍ1Ž:ž_KpE31÷]º~&ÿí ìªtuRaµýy‘ïm<äCÏFЬO÷›nné½T¨þoip/ ªPi9k¨ 9Lc‹ ÕD –¶ÑimÆÐâܦô¨â©#Ò¦8ŸÅ¡õGŒ»oc¨Éµóáà߉Ó˜2Mq*¸&Êo“gt²ÝJì¡g¢7£èaÔíS"u’9\ûê`Z_$¥‰Œ½Ùx+aø²¥µ³9ÆzÍ6WÌ)N³D‹!r™3·Ë§f.øGøÞØ…›,/’N‰&'¹îÈÜ|Œ€éÿ¥tl™n]8öq옣*¯ì}xSI„¹¦ñø\†)îKÁ/W²_4Òê„›u½Ì";’'•¹ˆáB{ßaæ§»V:¢æ Ê?ßd¦b~ÐW]–Ë1¯‘ÑžÕÉ”ò »- )+Ë?GŠäª¬_*JÎÓgÙ á8&Pt»±[™pûp{©¯o›jœ© åw‚>}DÌß´wm™qMÃC`H]`ü~£„Ãxí Ç :åDæVBýüŸé뎕ážsCù{ÊtÌ1–(Á‚ÇEQ#‰Å¹ª{Õx)kÍñA,;ÍãØè`è” h´HB%ûƒÑøèxFÕã RÑLWÒLm$æ”^Gš*C¢úÜëw,aõ¼ßÓPT%¬šóЭEˆ©Æ÷Èû¦tfU½|§”Dƒ~ÿ¶ƒZDIg¡0Ló#cêŸß°-øô £né÷ýΦ+1Ìt÷«±e|^OyÇJ€%M ×Øæ ¯¡ŸÛ—¹Ä3ß…-Žï‹äŠ\³'̇÷HYæãXPTq&à Ǡ9²ã3Ö7oo¾ÏÝ^ n?ˆW´Ž…‚¥Ù›®è)üÜkÄ(‘8D‡AŸ™öcfM·¨ÿ– µ¢;äøôÉ6É6C:ä1¿”¾»@3ægС«ÖYê'€½\ LCH¯,ê±pG-½¸¾1IÚdõÊF…Ç”;úzIzì_£/ŠŽù ¨KºëH#…­”•¡î:Ä_œiUø+Ỳմà±rx³¢«Eú¶‰æð?£m*H¶÷†µ¥go÷Ìɯ?y ~Yî9½}g3ñöÑ®x÷=èˆW± endstream endobj 809 0 obj << /Length1 1199 /Length2 2416 /Length3 0 /Length 3170 /Filter /FlateDecode >> stream xÚmSy<”í÷NMÈRRJ†<‰Œ,3ƒ‰™’m0YÆ–·¬3Ï0ŒfÁDÊ–­l!KJ$%%D–²FY³V„W…D(|G½½ýÞ~}ž?žû>×9×9çºÏ‘Ûca­¬K¢»€†tK©‚ÀxЧ ›iM ™*[®ì#,à(‚€œÜQ ‹ þÑ… ê3@‹B§a ,®ÏQ76`F`ª‰À 41êî¡öÓ‘ÎÀ Š'ݰY ƒJ¡q!,Èöi,k¶—•’¬@&Í ‚L @æVøçÌ€>݋ฺ±˜Õ1EE¥_$\8? 2)®4`÷àRé^kÙ¸F dp '­ùZ $ k­mæÆbyaàp/2äÚT˜dÈ‚+p‹5 ‘ôéžkL5ý°Hä6ÆÿICÝ—ðGˆL¡‘¾·Gb{Ámho6xûO×$ðËæ ²BFh 7úÝàk©r¼Àï rÍL ‘¼è^™@e‚2Èý 0 > Àb°ÁÀ€ÿ ü÷&€D$ ‘¸€®Ü'ùÅÎ5ƒäw3‹Añì*@¬}ÿž¹K¢Ó¨œ_îx‚'Àÿ³ÁáÿÔÿ¿žzzt.­2RCPVÕTHnŸh”Úï¬ÿêñS‹ïV åŸZ¿(ÐÈtý£%®–?ÛòLü—OgQˆ û5F‚;AÜòãõüCö{C6•ú]ØI®&LÀXS…Ê]œ5e(ÄÿEð¤P9ˆûÝñøc!þ¡ûþÁ®Ks¥‚€2Rõ‡‘Â4¤ø$ ‹èöcv~ÊMú¾  IY[qn ùvÔBô L&÷Q¾C ô[R‘N¢Ð\kwD Ò¿†5˜Èf0¸:})nìÏ;™Â-ý@¢@ox0Ô½8´|¡Hê«<ÚªVsÀf~•-­.Måy«²þ ^Ü#ªž=§™xkÑävø–ý³ <çâ Ñ¾h½ >ÑmgE×ã"$Þ«Ü=„ÇMóÃÚf5ñçÅ“3'ô9õ¸©=ó¶r‡õ[D­ÏÑÅ‚¤ìÆÆ½Íy¡» r 7™w) w,…|4ÇQOYbx;*±÷°dAãÇ%í‹òÆv‚%ï¿l+¬uîìªÕFuœ3`O»@mó50•-U—Ü*Lt*yª”®EfÉÍ›W†öwñŠ_Œ—Ú,.þ<eêy°—ÈMí¼R[ÑkÒìQÖ¥9OºÜö•‰ôÏÏÈÚ+Î6å3~Ó·ð Yµ©»¢‡Nžuu<útû{RG¯]ºáî{ˆŒA¶Þ×·Í¥ï«Àß%~²¤¢ù¬=NÀ¼%úr³äo3ÝÝR€e?ß%ŠC˜Œö…xè¡„2ÂG¥$[wÛ¤®3øÔ7§\*D2v-*I'-…é„°ë1Úé hÝ(Ž7£É8 ecqÞyô—H¨ Në`Ëç|p¯ù[û¥Y™|@Ëý‡Þ”âúKZ!á %2 {’*ÇeûѸlF¨úúÄ%ƾ¨Ð˜1%Ú¦öhAñXh‰ð¦YᙼÙ!Ü󂛪«øÛQŸ'Ëß”&v>µ¼Tö%8”„4[¹ å'J²”ó‡zò[¯f¬™õÂ| F´ºè.ï]O›C _¯¯«OÇY¥‰G£.BN\vä-ލnŽ0ÙÝöP±nx'y±žÕ¤µÕ¯þúݖо‹„'϶‹ØÅ&žƭ13+¡§µOfûgºMžMöŸßö:Mh߃`˜Ê­—Ñb"Zæ»ÅÆ$Eï<„Üë¿‚ÞG™+¡Û–*]Û"Riƒª˜^ÖøXjÖV”ÀÇ”äMÐÒ.†³{ €Ù—U>g•ž>-5si`g¡xâNž+[ˆ¿µ°¥ªÚÞ¸HÅâ†Y\÷.ƶØw¾ÑNÐŒÐHëFÁÜÄFíÓ!Í—qÉc¬Ïeª'ò"®°eÖíßr]¾ö[o ’8ÿ%ÒjûöZ] ¬hyÊÄ­Õß,ÖÞÂ0[ç¶õÅÔ£AL­¶=&Ûé½{MY[x±³Ò.5ÏRÍ2z=Ãé3eZÅ%<ÓüB–>¡rXžTíy©ž·]æ÷K'X:íG€'[cùm+06‡Ø|F­M’&-Òg¶/+Qn%ïÁæN–ºMi€Þ¨Ž’:ä-ùy=éÎMéîû jDzËòõª ZÇ£5uÄá¨÷÷$Dh#'«`ä3¯ÆW¦ ¹u`_®{s¦ÑÇÜêSŸ¦M,¶Î}u% fÅ5óB^û°ø``”ó5ä¦4ê–UÎó½|få¼yä–ÞFd?qoÞçCKs»2žÙÎÙ¸ùW«ø•®0„á þ¬0¢|YÑýÈ•ø}Í‚¢MN §9H&­NêÆEÇ~ËœÔ}fUõÌôƲê o"Bb>VWðT…ÈòËëZ}ñOf¢]ÐÔaVΉ]µõõ­v¿‘øæšU¾!±C«ƒ:þx×Ôáá-;¾vTˆ¦* åaë‹ùݱŽÒa>¨B1ÙîzÁ½æ¾­TýÕ9cƒ : &êEÏŸXz§ßu¦Ê¹BCaS”X°™G˜9…ßÔp‘ó—î”¶óÆÙª 6£ûߟëŒÙ<— yýn/"®n9Õø®«Ø«ÆŸY !ÇéŠOsyC™ô«ÎwX™ëRµ‘8GßÖš‰”e¤\'oE9JVï :í,pEËkî[žñño%£*#>éìû Å{&}Ç“>‘ÆÁ7Ë]Ã9]W…–ZÒÚ,mb{z;K"SwÑïì³®ZŠÊÊ€…ò%oîŽrº¬¡¶ÿjYx³²þh{¾1B Sá,2r_*LÜ Û0}œ`âÛ¶UN¾AyÁYi_*c°—D7ÖÎ/ó‡^])§eÙæsþ^¸&=¸$ZÞn³³ñUqs‡:ÏZ¿Ì!êøñlý#‹ðNEµ Ú%Ñáo /f‘S©Mì2ŸÊ”¯ƒ§…ÙÊŸïP“CÇ´×…«m×\=¿tOë‹ËçJ£/pÁt |³wè:dã²âq¼2gòCL Œép€ú;ÙãöùÅ­þºCϤY+Mü¤ Ïný#½¸§ë]™084äŽhH,¦"-ó„“s‘ìY9}%Œ¸ªÎV)ä¦Â:%Óå² ªƒ'ÕFnÂ?㥠¯ïqYýœCa)7¾^ÍpœPÿëL]Pd±¨hα+ó]6gä˜Þà‹ô»iï 1üe-¨Ü¤´»jßl…ã«;vRâY˜ªØñêäã ½¤íÃíùî®Ä½3ƒå béÝc¦gœì&úr¦•"Þ/Ùî–ùz<1&eÒëÔp;;ìyä2 ~ïzU›6wjC÷”öæ™ÜÓÞQÝ6“·ûºötÌè ãü' âš´K=m>£ïhyµëÖ¥åyíÚ´ÐÖhößBNÑ>²VžJúÞnÎlÒöJθɴRÜs@ÚýElúD|BGö[vZsTåù¬ }¥™†wë/–§çˆ\Ͻ>x¾„¸XISHÜ6—[‹Ý³m¼–r—¦ït¹Rœøú˜@ ÖÅÊ·Ðy÷ ‘šO=¡0ý7ºçùj]¢‘Òë÷w53èöŸéeÆ=mƒoý°ÒÆg‡«Š“eU‡]_¬[:âqBò+Ù­¦ºsóÝå&1þšB¼ñÄF'Á—×¢S‡c<+O—å%O£jZ&p¼ò—íX‰R!G¶s6ò Å=–=|NºGò2N¸ U þiû¨SÒò­é WsBN¦_®Z|v·)Xþ¢ÎS´TðÇm!Rüg…2’¥5àC@Ïhtø£ˆ àÄN»nE-'GYÇYê* Áo ¿ÅÛî9ôØ!Ïz¶Ú8@çU^x¥mñ¸›2é’î "­äçÓ“³Hñê²ZõPC7ü=˜þA}ãC«óò¯ã®]Ë«ŒT•ÐÓj"•@FÚ54Nnyû?RÓ92 endstream endobj 811 0 obj << /Length1 1626 /Length2 13148 /Length3 0 /Length 13995 /Filter /FlateDecode >> stream xÚ­veTœÛ–-Á5@°ÂÝÝÝ ®Á¥€‚ÂÝ îÜÝ!8Hp îîÜ]çܾ}{Ü×ïO¿þQc|{É\s­¹öEIª¬Æ(jfg”²³ufdebá(‚lL\œTílíx?Í@€w;'"%¥¸#ÐØdg+aì ähÍ@S€•——‘ ngïá²°tÐh¨jÑÒÓ3üËòWÀÄ㟞÷L'…-€êýö³·Ú:¿CüÕ€@€³%`âJÊ:²ŠÒiE €4Ðèh (»˜€A¦)ÐÖ H 0·s€ÿq˜ÚÙšþj͉éKÔ ` p²š‚ÞÓ€î¦@û¿\ { £ ÈÉéýrX8Û:¿ÏÀÙ²5»˜ýEàÝnn÷7!{G»÷›wß;˜²“³“©#ÈÞð^UYBê<-ÿªízwìÌß#ÍìL]þjéoß;Ì»×Ùdëpº;ÿUË09Ùƒ=Þk¿ƒÙ;‚þ¦áâ²µø€#ÐÂØÑ trz‡yÇþk:ÿêð_º7¶·{üm÷wÔr9;ÁæLˆ¬lï5Mßk[€l™ÿÚY[s;+Ë?ìf.öÿô¹ÿÍ_;CûNÂØÌÎì0š#2+Ú9¿—ÐüÏTfúßùAâÿÿWäýÿ÷ß5ú/—øÿ÷>ÿ;´” ¬hló¾ÿxc-àý(þzh\lþ¯cØãÿ•ôïÑZÀ°³›ý»OÖÙø}$¢¶ï²°0±üÃr’¹Í”AΦ–scðû¼þ¶kØšÁ [à»®ÀÈÊÂòo>uK©µí_pþô5ûwúïRýMžYR[KZJœþ¿y\ÿT~_guûwnÿÑÊg;³ÿ<ü#&fçðbdåâ0²s°¾ß½wB¼\,>ÿMÉ¿Xÿuþlììrè¾÷ÍÂúw÷ÿñû×Iÿß`$mMíÌþZ5gc[³÷MûOÃ_nSGÇwÿ¾üï]ÿóü÷Îî@SÄÅ9;Sþ «ÔŒ4çï¸9ý#ºÝ¬ÐýÁö%õê…ùþÕv¿üRÃ6x+Œžk‚™Æø^[=fí_väèv;?‚©%Oó}Èi»ò1V©Ú¸éw˜ JPÒŽ´¢¼ÎfÖa¾p±hînލ¨?õ±;"œÝÑú“»æûcSÜÚ£úš¦ÔÅâ´£7@`~/8<¢JÜ¿»¥îèïûuÛµC@Ÿû’ß×7éô›³‡‘ãu½é+ì£+·=„Æ‹ý¹Eq¦x³ÆéŸÍ«Véü2˜{è«´™6gkªo¯l>'ièG‰ÙÜK¨¸ÔìOÕJ;À4÷öÎAÔÇ¥“–Á>jÄuÞE7:ÄíÝ"Np³p2‡•c¯üÞBnщ~ÁHS*ïÎ7ä)ÈÆ™4^øµÖÄ—SñYÈ$}7ØqÝuÉ'Â{£“î¹pþuÍn©H»\á‚$Z²¡mÞo”Ú/45›O!—wÉ“æ|mÐd :Näš?>vH;¦jÄw°è–¬ày-‡±zbÉêƒ"îhi;mw-YûÚ¢’qõMàm>Ÿiø’p¦hRþ„äU MXÁ`xÃò$)HTn‡¢b?LÇk±Ì ÐåAÀL4po†›àmìÂíYý˜ ¹ ¢*HIÍ=II= žaê‘®£s~úÌ¡šÃLÊý³¬àñÕE0£ƒ°O)™ Äabj­AÉ(3âxÏš©_¤Å›ËO„òº¡ÒÒß«ã+¯Ìpõ&BíÉ1Éñô"Sª"^ vƒ“«q©à‰·I}æÞïüqVÓ·RfŸø£™*4e ô¦4’nào»—™xòá㲜ÛÌ‘?tÛþZœ±ÝZ¿…ÐýsßèW³nÎ-ä?¼QÁ,QØ'\—qpiIløjþkÙ>¥ò·MzñuýJãÅê)£Ú§»ß?¨ìž8L«¼ ¦ƒH—ŒàLêÑÝèÝxµr»q'p~¸£Åg/ôÇÑ%Ÿ”²»%X Ó}w¼[úD!ÒòKLm‰ùÀ)Û¾Äï'é8¯‡!û-„‚ÿƇH;ÛÕÌ™ò`]öÝÇ:è¹Ä—·ín¼_× Í|â®Æô5SX ßR,åÆJvíÊ„:áüÏÝaF`Þ„–š,*ïÔ6¶Õ¸KA´F}æ#·°h¢Ça責oƒø 8EÍvòßbë^ø¬db:ÌdŠ·è?yñ†ç‡aí$¯Z¯“°ƒáòº0ÏEñì‹’Y&fö£6êûçßmʽĺy%ØgÑíøKqnC†=¶u=¬Ò8x³2õ©Tri°ý§µA·y‰ùú‹Û ~ÍëÆqíEšPÖ†…^Ĥ1Ï5g8¾VEwû~ë+DÅD§BRRÁŽ÷r`­&úZŒh©¸ü"ŸÖ}ÜáóÍd½Þ¼±™º·dYl¼õ¨Sùl1 € ÇÃÎü>d¥¶d¶_Ôbÿ¢q)Ú¨A:†nìü Ÿ“ avær×ðÓx5`»âŠ*×ló“­W³=éï3J©‡«nÈ\I¦—Jeù—êö•n“‹òªß{ê›hºˆëXBB8o/ñß6'hܨýÙÜîaC8B€-‡EùœG~¾ù° Y†‹-á/—æñ³2.sUõ±g:áÌ#ª=$ØZØ£#Og×Ö©Na^~N¸›^|é°)D‡ŠÔóñz…š$Jê$®¯"×Õ>åíâù,/•¬ëèéͦl˜Ú4DåKd„Ÿ¡ä ¦ D­a‘÷àµ\N Ñg£<ç„®´ ÿÞ˜ìöR›£·üáMÖ$µ—LJjQµE¯EsóP»‡¾èWÉàP`Àyï ÉÍò–ñªÅ炮Š~½Súàä] {"Ȇ~Íü¸Ú:økЊº ó-ƒ7«¶F¾¬È^êÆ@aÜùÊJW¥z,¨oCÞÚ uKùN ãgOA|ÅÅt†RimôjüäpõªÆSñÚ XeÅM¹¤ƒãx]>gÌÔ<èDÎ-á4¢Àr@Qíy$‚í,UvÆ|a¯2+ þR£rfü£ºÄ9úÂpîÊ&˜b µ[\&VÕmqö•ÈתkE[69ôîa²h$µª‡“Ñ›":“®UËk¨p¾r(pÈѧ6Ä‹Ã4¢qR"“­ k›+È(bòèwáoD©9ý L*¸•=KjQ!®—™1„†O’Öö„›'÷q™gXU¢WËF­D#+0ìýHÁ•“·Jí–cŠõvLà¶åŒ«Í«€Ÿ£–,¼]å½Dw ÐÉ7æèÙÙBÿ|#Äã³ÍøáÛíZ»ì$Ï ê E­ë·`3û!El'!™wßçôŸ·T5„‚¡š·¿‰R»â½†”ª &TV“Á½¤ÎKYžœx|°Œb• 4”‡óZ˜OI%ãg·0y‰X‚š+¤þЫèlIPp=ž@|HòÄêó3ŸðÛ9d[Ì”ÏÛÒ õ;ƒ*° +"0kW…üX>¡ú“†°uÆTê9µu Ø-oýn5ªÎÚÐû¸‘ŠÍJOª 3®fŒX_×»n¯ÒFÖ!l÷Ú;éowénÅnqq5h¯(üHŽñ{ UÒŒÇT½ 1Â4?åsd‰ÓAKœt€•pœBMp/½üLÙù9ªæÇU`ö ÓEG,žºŸ Â$J÷™Lé”]RÄëý‰_AË<õ´}MƒFÍÕÈrßÅ0ßO¸J<éû©O†¦²Hµ•Ò ŽO7ILßE·<" †°X—f¦p*–pBw½~®îŒëU^úʤ¿="]dZ–@'-â^bW¤¯4HÅøP(ÌTU»hk̓ØoéµXðËø" {bŠhEÛÚƒ»ÔðìRªw£³žï^{áÊoÃrÍ +ÆAѰtt¨Çhi»‘+åÌñ$jî­+À“(¯&P³¤÷™=Î)g Mø™õ/…K&x¾NTÀKÅÅŒf‘æ•-[-yŽz °õi%Õ¶¸ÀÄ“h—]g˜!] ädËçòQ°ÐZŽé+‰0ÈJ?  3Û'ÏÄÂúwË'‹{<&á,Ò‚ÙÓ` <Ý9h§#&Þ`ZÌÎ6Ò$UÙ$õŽ¥Â'4¹/´ Ûÿ°ÜöøÌcj¬Î$ïÝÛˆ?[4X˜0'}ÐR{ªImc%¸‹êhÆizQ‡ÞA¶Æ=„qÍA4á"3òEB?fÈ:¨” ö=Ï—n&×î;Ý©HoÖÂYU/†Ò¦QD0ÚHûö3º~¤ mõÏSæ ¹ÓC ãÒÇÜy~ÜØæ&'xÊætÞ#B:—b“t?ú]òŒc [uq¬ÑY=‰bLJDãud8†ö¯¼À…ȶKI'‰‚\á¤ÆGâ/9Ëö^Ó2Ùêbêa8Ú¶œî0 •rt OòXV—º‰1&é÷½nnAܵ[ÇCø]ôgäŽÞÁ¹h¼àJðhxå—œ<Ãâ’DæûïǬ­oÄ #íð½hª`ˆhQ™&U6]úZ$EsæÖe •»âÇO úüÓ€Mùj¤ ¼â"\=ÆÎýH…ü«48ð©ƒÇ8¤.À½~ðY_[³wtZƹÌv¸×pÒšü(„ F>ëÕ€g«yiËoÛb5{«ähÎõãÕúòuLý &“sS±"ÿÑòŒ¶ŽXTHyíüànx€mâ±çñUñNÇ5çÁðŠó¾—1§ØMt{„ßMÔdÁ=Ù„|Ë·Pµ}§fGâ*4­‘ªÁÐ}¢Ñû5ozUt;ö[žŽ^û!EŸÏ‡ùçáB_5ï¾–-TüV³Ê’ù‚ŸxÙÄÍ?—ù]F¡„bì a5GõÅ‚*ãåsë*¶›WÞÐĪ‹‚ádÉÒ \].e;)8!òC@õ|_½ï·¬X© ƒÂ?*b(°žÚ¢d˜?_\ ÜÊ$Ó¥ dwè¥iË:·öüÚ=¥¸¢efù¬¼i´ õÉWï Þ’jpGC$ñ«!Æ!N$þL¿”ƒFýÛG‘pÉ‘ ¶XhwxÞÄëC‹ Н•ý% f¾Yµk:H¹±=§:äœÓ-äÖú^”àL ›]ƒb !HíkÒj"×…½4éŸç܉+2¼¨*Ò¨ô=«¥‚º† ³Üª©ŒÞ‡63Ó:¬&CM]cÑ•8Ùl’ï =¦t/eOý– BŠSbŒVE/Äð&ÄÂ(—Æ:rG±v<¦#ÏÚ]©±Zvê>㣾uKëYHné79'§Ù’nt•ÏŽmó "NrÄâ3”„@¯ÆÕõ¬ïÑÈD@¤ß:Íh¿Ë&ãQ ¡fçÿlu¦¾õ^v‰7ƒÂà¢æA·1ã¢ÑqŸŽ õ•ª‰S%ó – þ0Wb/áêÂÛ¿WÝÞ'ló³¦Ô¬ÖŽR&‚[Å;¬WÉ1›„Ñ ¾Êã«{¸0oqnÁø0/ŽÙ*èØpØwÎg]|¨À‹Áº%-›Þ«ÐefZOH…¤Íø»‘ É|=À¥D.ü»»-ØqŒvQìƒWÄecš¯úæ×~kó)wˆm‡‚f¨˜\ü˜¬ª®£IS"Z§»—ñ+aõU%¹VÎéÃú2žj80qp ‚ ÷¦G ¨aû4CN³¢ø £-iþ=kT!R„ÞFù‚-ËŸî¼Rnij˜ùé(”œë%Ø»È#CˆŒ´ÆM,H`×ycj}!?ãu‹ô~x¬>¡ŸÛÿ}Mh¦c{ËF‹à†ç?LOÁ€€ÃÑnU€wÙ­”žŽÁyüÍèxpp7gœÝ“4"¶½F=“Â_ö§ =to—¡áNÖéuuè¡JìçËD÷ê€9îmA'ÒPÞœ¼Ÿ¯‹ P9®›¸–®?}àr£Ó×­,ûñzä+ð• “Þ Ù‰VÜbjú[<2¢E>% tPEùämJ |¿ù-Ö Û8mÄ? 5ŸÿÎc4ħ¸0)<ؼg›ÚØù2èGF(Ë­8[#×ÛîJa*·—»dVP»ÌGzçšâ1¨;Õ·¹l©Öh¿t˜¶_[~JæëñÙI:\¶³ö»ÛëôE]¼ä^>@·½~“ñÛ¾¬;!ŸÞ×Ë+c¤ËyøúugÍ3=,ÎøJ;;—œeI¦GÃgŹáÁï¯Æ eIaòìT"|clf¢©oKK1»F ¼ohޏ2BÀñ†Ú‡zÆ¿\à­z!Â5-$Ì'–.ÈŸ33ó[>æÔOö y³'çeºÕt»Â;E…ÎÒçÝýªL3µ «{®Rvù²í*aív™XXïèµDª¬R¦Ée·¯Ó¼6àÝ"Ðuæ³ÄÑm67Õ9b¯Œ¦¿°xrb% mÛ?$ˆ))°ôð€)ëæ ÙàKB‡Rb-¡È–tùun°Fš7ë,‡:2ý QÉEiš€¸E³rE?LSÂ- €H&ÑØ“ ¼MV™€w¼ï$w˜/ ÝÙT<nb ðõvhq?¬_FL‰vâ|i™r_±§st‡Æ¼Ý¦W³NIÑ[ð¡vSFDú‘»c{­DWIñ àȪ*mÜÿIɽ¹WT°þ5±M¸ÚÏŸ°;‹C÷ ÁÊÛŠeÅ8i£°¹ÇÂ]Sp™K °’Ò`·:ësy<%0èeXí¤(ïÃ.¤WÊ6é]í«<ø’ª¥€Ê¶5 ÐrÙrå³ÐØGô[‹µR„£ µŒ05 «Lð×L.d‡õÃâØí ŠÀã#$49•A­ð`r™“@GNhþÓ… Î ÕØx¤=òA§¨ªƒŠÜx^}UHçjÂö6íxïV½­½Ò¦´’á1㌌ž¶V}hòîÒgßo˜QPìFÜé>¢"£ oD©È®T…#üs1Ò †WÐ5®yàþüìüs鱨ALe'ID6ªÒLÔ %£eßUÒrQÈ|WˆBùmÕ\’Ù JêÎì^Ü…mìÞõ}Þ'^•}¡È*“e\XÛ ›êD¹jÂÈ þ ÷N¡¢glÀ²V ’6Î ¼Jz¹ÏŒ_2MOL„GܼñoÄ!á×ÃMľñY C邊-ëW¾ç\¦»ÐöèÇ£•Ùý–¬›\²¨âû™»}³»Í {žc5"ŠPh`AħPo%¬%¡š{ʃ´JÛN 9³ûÚEfÆ{(\{!aÌiTäœM˜Ó›×rK-\ÓûXŠsÇ×H+BX­o@”Ûhã ÝL‡Óözj‹©0ÒVrú÷–X¸F ûM!°ÊƒˆÔ`¾3•Þ¬Ö8p@•ÿ<²cëëO¡*‚<\fJN¢é´½°)çh(†Yë| ™eX+yüÀ+!p¼å€5Ê¢·ns¯£=Ê#zo’–µþ ,[ÚdÂsPæ(I3eâ 킉5÷^í3fÃ;œ×ú£Ãq* ~X¢flµC»Èíñ§ðSxKm½mh>ÈoôE€ôu²îJÈ]>]@õýA(cú92#Öe]º[^Íy󃂺O úX‡zü{®ýbªÁG¸'pSbþüjÿóدÍvF÷l«QY¹Å—´3Ï¿A73Yöt”fHyl§ù¸^¢ošiñ i–|HÇÒOÍ\£á¡‘49ä¯þÌòß3áo²——³ûÙýâ/R1p~„ñ®ŒÁRD=¯|g¥5Õ/ ŽÐvngÄ=üuӮ󶦶S†¥ú+¿§Z.àzÀ´"¥X‰’žßŸÑ.A-9ú²GÐWª–T81¿3KïA¡®|ÉjL¢š iò”;èrô¬}'>úqð¼h£äs·L3„I—ýcMØþ[³Ox¹t½óT¿©dÔ·ö’¥0ãônPÚ2C5÷íGޤÅÏ–§'](ÿ=Óf‚"&÷îŠ!ÎCÚ F¾¦vŸ°SúT’¼b2 rKŽu!;ÞÀ—ؽw—½ægâܧn/X˜JšœTˈ…øu÷• v)ò“‘’ꉷ‚cÞ†c…Rö ÎåÃ}a]ì/Çd섌gé¼õÈâ«æ¬Œá¤4tÞ-{³“¼ mkŸÁ‡Ûö@¡Ó /ó=鸧¼¤f zQÕÜP–ణܱ`ØK ¨1çl²O1´ø°“p·B1‹ Ë9ª4¥P1£3‘Ò0 IˆrgÞ­ø,ëÎÂu4ÌÍñù'V¥6ë¿ö³ö8³0ÐqÖÚ`òKW„ì2ž##œ[*Uú-$ÈÉ_úe–÷HÅ<=¿Å«ÈÙC¸G KïðÞÍs¬0wu»òšü¬õñì”K+‘HvÉ5¿vé×'²ûâ*ìÖs–‡?´ÈUt«ïÇC¸ Õ'ÈO'ÍaÏä!·¼Ê\m¸£ó/­)ÛFM´A!” }|kº©õ‚DÿÔ´ÃØ¦#ÄækáëØ%~cë¿§ÈÊ7 ù†¢€"ÆÀŽD™ôÌ^5S—sÉ»Ux+lkÞUå»›5Ü^qKSQïI9ëº6Ôýø€]®|Óvô§Ì, Q–ÙI…îmo4?üàE¢jÙݽVXÅXGçåxaÇEµm¥“ÝT°r×Ãsš4ÈÔ°í‡*›EÉ˱ v£]ŒzÝ™ä!HMÿæÔ ¿h=O>ýœ€ QOZýÜZ/jSžš¥­†ƒæúøbî9Ȉ×Ä¢0³zø$Ó§! ç‘æYý")žéVÉÍ +y5}^òU«þM¹Fþ0­IV¶œ3m m¼ñ†;eŒƒvþtu¤ì‹(B¦˜Vþ²@í\]=9±Ëü#ÿZ, ×ð㤪}KÌ ßgOI"éJEÀÚ;ŠQ2“’‡dÏõd‰Å éX³Vlù.0iÁ*‘†^¿eZ^«ásGŸÝÉü[Ä­ã2kªN/5Ì®‘ó(rX]ötÌ2}š'0³ù†oµ‹¶»`>ÕÚgðMqBhëð1y·¢F=ÓŒÑßø; ¢þ¹RsÇ t:óEL ma¼ðsD§×áéC\—£Á¨±ž!»ÂH‘,'0q‹„ìã¿•(n•ôib@ýžzŠP”-O4yðGêåë³u|6Ïÿ,&ÂhÆ#[4بa° Â7C5Ðob8DèBú8§ÇÏ ÷Üïv\8Iú˜$¬ëª«Î”Ú™©axb=u~QÐzS?i4ß·ùÖÏG²¬æ“Ñ´&ãÙ1¸û½ŽôNjP¥PxdLÜ,&Æ–wiàNû¿ÏBæÄ7ÀÅëJ@µ Ýàs0~Ù%ð›¼Ò!5ÆBRL|£®ÃK1;á–CÁ`ß¾eª‡c¼î„aTW|r‰…¹¾ÀÆ’/M{ Q$ûs¸D7ð§A q%*+W´8?êÅ›˜¼È4…íãã/….b¼ £Â·`ß³Ó õŠ»Ú9 ía„hSz‚ƒý2jÁ'ŒSWŽ—߇…þ×eÐGáÂçc’Z[›°K?Ié`Ð~³ýŒ’n •HdK¢! Žu­ð(·×ÔEp l`²í,†7yhΘù0š|þ~þ„¹\ßCýJ¥üæ¶~k²Ò<<Õ–q†)Û'·¸+\X´RÂÔ&§?’ ÷ÍY†•;† ^~:wå«$«ÀN÷XÅÇÀÖ=2ƒ|î[P.T,êô+\ö)\à§~pœkcù~ò7·Ë Û¼Çù£— (ê(û9=‹xe]³Ø,>‡Cð¤õ%'Áf±‰rNíýÂÎn3u AiŠÛ׈uÙô¤ÁÎó½sÊ𱯠Α4ªHi³Å+Wã‰Eè¬*ƒÕ‡ETÿà_ÇÍS§éΛd`²~´ôÅ Šg&ˆCÉG2¯@BÖö3_^b›Ý?¼Ußd`bgǸ^½¹ @ÀOKõèêhD¿?~ù(}÷Ä;|ìÖÀi}OCÂHÿM㣃¯Îý°nã«/B‰‘…÷ãÅLܬw)~Úäÿû·1ÆlÂ5žRE‹l…U4®¾Ä‚Ìc<=îocTÞ`\O¬º2RY) çâVx£oÍ”]4>¢ÅÊñ—9²[7!¤œY´P3ß$„¬KõŸµýT;»ÂéžÃ;‰¢N“`_„™GK#ÇŽ)ít­¹èrìšÀ·è6$œ‘:øe?|²zk)F8(L²„Ùë§ë‘?9$m %ȹ褙oº\Á@lXyb¥Ü™_ÈϘcà%k¨K­-)H4ÂVÈqþPTL+ý ø%¾ ½©Ò1:ñ~~'> y|ú‡øKF‰·¸ô¶~…¼phçÏʪkÙO÷ÆYl–Øy¼Ñ£N3~¾Y-!ô(²heŸË\·¦ô;›ÆS 9F/ó+ï»õ4‚ósâ³×¼uäyèÍl¹>¦ÍÍd“­CBV\#vÏûM*;„…°5² s«èº×ánP{ ;A%}Ü‹ÔnP:˜¹æ"‰~Øìª¶“'˜œ¯ê^×/s®ƒ «–.;÷j®sš9$³¶ªf ,A— ?ã 9‡pr©Ã•ìc~ÇÎÛÒ¥‹d&­² Òæ0áè¬ÚÓFžGgÕ‹J£íF¤_©ruõ8mYž¥w7YlÊ™Qé'œ%óƵ/â]è,ù>¬sýá¼.fÚ„ØpG×Ff¨5ÒçU³H â)‰íJ4´ýŒ¢ÆÉ™ê½•îÖu·ÄEñà½â‚TzOE§ÂÙ!¤êAÓͱq'^gµ¦1?EüÏÛœd³£Õï„™Ž,•/[YýÆåtplÊŽ&å(ײO6×`™?MÛÂÝžÎB.ßUy§¸vúC5ÑÐ?Ô JãØ%/ zÙìacÑÑ5Û—¢cœš‹õÀó<ﲦÂÉ;ÒJ¢go0ÏÑlµæýfÏ@¦¹„óÆ*ƒÀÜL“ðEV±ü,\vôc&qB¥éBed‹p=i…ÎþÚ'¤B²¨çA¨$,r=¨fãämeÙè/‡U­„ŒY^@W¨,0þs?ÇFŒ¢`¨Â®ñ –[ˆ ´hǤÊÓæC„éæò—®‰yóaµ‰­+kÅuÃFi eõ=rb!ãIÇ}Os!å…WY8Ñ_E$ocÕÙŸRÌ?I³Y›"Ìp’UY…ëW ö'~EÁér@ØpÒ±ÀÆRÇ 5EµzÈ3†üoVRåF.uºs†Âr8éóÅ îºýƒ‡„‡³‡}ÎÌè’¤³ü+HáÇ­cš~aµBBä^§?8×ÿ Ý#ï5y÷¸ž„dÿ u´«áÒki*W±f%ëÔµËLºã–7+Œú·”Ùƒ=ôüD¶Q•®Ëµ¸OÛÃ|¶°æƒ˜0 fƒ¨-CºõŒ@‚c+Ã_Á[>¥1Oñ˜xÚÃsc±£êخՌM-Ùb (–ÄmZ{°Ê9ô0’KžZð~‘òv:·§5”¢¯Ä}™ï¯gȆ¨}…±Ì$Úñ-™…„öÀÄ7!¾qêuÇ4u b,B'ë0r£y\/îó‡¶ÈöžÜL*‰52¯¥lYìŠ'ª>@n×Û)ÆjwÝSFkp#¾ç©là Hô[Ù7;‹¶³Y_«—Q>ÿΊ8çà@šŸ[½ßÝfyGG¡éµž^xÕ=ÔO+Ÿï }È<ý%Ÿ·g ŠX¿ ~íYØ×u}ª…9_ZÛ­ìhç´Â΂ïRœÀ‡™lÍïÊ‚9KÐT¾™~J]í¦‡â*9ÇæèÙzgKvË}_e8xtJg2ïXhù%×-v‹X!‘²l™¹ohŠY\¦„øÛü…N­¿º[?]´€Zvê"V[M¸ñ.j1Q{‡tOèvrGÞj)*†)ôº•GäDO.ê¡1+G!y¦ü–Ð…œ«åç‰ÒÆÍîEŽ^½Â¦òÉEÞÁî hôåàšè8ÿ³ÜßCȉõŠÞ$œ MÅašù¯¥ìè£þlY;^ ô(Šbk÷k¼EÈL¢ŸòF¿¨£e]έ=Q6ÐyX "ÞNz·6€”Í'7ê2›ÓzÔÓwšë¾]ù¦Í-ŽLYZ~±Æ`A1¿[ö>Ï‘ ü¾nLk2¨ù¾÷:%Ÿ©jt!µg櫟{õiÓû€æƒ·p=áNÜChÚæ!YÙn"4*Œek=Ñ©q¤œêаë>Ô»«A‘†\gз¤žëy§áyÔÖ,Ý‘Á)m¸7+dû}˜‹FTÇ,_æÌÓã¸LøX³•Óò9 ASû–H¶®$…f#¥A*Ð/a¡Žn¯Üûr½à¤ùÊËwÚ•IØúc¥/Â÷>íϸ”¥g¥E»ÃÜ!J(lð®Êqvû·hX»FÒM´ûûŒ °á¤ß(íǘ!D)<…dËÑÄj#Y‹¢!¤ºÃïA˜øÛ$“ǘVÆEηûŽ;ê­tdïáó„ÙÂFõZYz²®Àï’1+ì`ÊÖX=oÛûQãÆ‰Á3îë/M,˳}®;ºñ’ýÆ¢tò\›ˆ³¥NáQä–\UÛXVaÒà;¼2Œð[†›òî5g’ šºŠ=£4›Â¾ø¼±u_¨»P*”ðúÚ’-ÌâN2Wo,ÙXÁÒJk !0QÛ¡ø¬&]ô)ª{Fd\%§mä ‡UÕoqŠ_W‚&ØšúÂÕî©-‰)²_ûiÄ6¶lŸÖvü §7¡œá.ò÷Sôñk1fuý9>3'Œ¡šû/¦åugUþh‡Dxâ3 N¢0ìv»íyã1uÒ-ñ«“õ¯É+4ÅSR§N‘õÆdÌöç¯ðq¹|ƒ[MÌVï` ýàPb`ý§ „ç$לåAJÁ}?+ä޽ióMË% ^,Ã}öVlGÖD•”‡„‰Ì]!×CÉg”Üå¿°ƾ,|Açɯ’qSÇMX>¦MÌå<;h)ÅdÎðª¾Øbü2V÷r 4ÍÜtÒN!™•Pî ;׎«ÎcßÚFî­½ÚJ¶ÕÔqÁ p»ãožó਱À”jVxSK2զĆÎ*E¼ç¹çÐi8öK;¿®®ddcÓ.âvyÒu95sxϺŸ“ú ¼æ3ãòÚáFvÝIRÃ[¤Ð,¥ú8 }ï“mí°oȲ†Ý V1 .£›|T˜€Òø'óæ*Pò|ò¯Ö<ÄÕÈNX-v–P¦‰«Î8Ì« 4smÒ)o‰ã/V=P8}¼°hšQµýÛ›¦$Cc÷dzªú­Á‰£ü¢’³!×ÅëËf­‹9ÖÆ±ß!×lõ¾éþóÿ'ºV¼¸ùvk×±wœµ²¿)¶7ò‚ÇWÛg‚S"ðYæ.š´¥Òr”oqôO}ÂÚÚnÒöý9º?ŸÄEâÅ”ÌÎw§žR#?Нzã=Î’*Çò)g}·i)„rÜöÏšA¨$îŠÕ*±Û±wkÓïñˆõÑ!„VeÃ$n¹øòá *ŠJÝ2O¡*i•c¬1ðkEõ^‡•¿œ£åv¦qëòQÄf“ÒÛ&É®g×7ºP6ÌBÅ4ç!8oÆc3³Š_Õ a`ô¯x]¼ …%âJoV yøÇм„v娶H|Äóo9§çVÅ+là®’Z~d„EÇÆL§ÿ:u¬q²;‡£þô]"¡¶–óËŠñ³îZ©w…ÒϦÐnȲĩÕÝw‰²âó¥)›¦¦‘žŠÌ,b¨}ëÈJÐ…Š™(f£Ë‹§6¾™ÔŽPÕ¾Xb˜¯Ûâƒ<溙º|cŒ°…ËÚ·µ0ÆEáÖNZFVv©¤8ÑšaÔýc°Gvƒ£¸·Ä¬"·È+» ŸS)Öü$]^4°Ÿ[h'?ʦíç,£ÏOBÒþfDªNâ‡Ôô\²2ý¶(ù[iß²~«y÷¡ Þܶ:š…ÌÜKÓØ–HdöÆÉ±ûvX_z ñŠøŒ¡Žù¨ã‚·M ú­m¯’òœ÷óxÓ³@êˆçíZì‚k(És¼‰còˆõ²ÿSMîDºÊÑ­qÂŽþ…)[äÞjpüÑ© e¼󼋘‘”^•œF…“^r’ÒÕiZØZ*0:ƒ›~š¬ÏvuÁ`íTg¦svž#§ûá~ºulËþùÁ=\Èæ€ÇªK%aÕþ#¤†TžÆ/2-¸-ñ­å{(7häcMp{…Ö œˆ0Ž‘Òs ¼ÖôS8LÐrO!^}u¯.¾18b(v€/¾c)£€²MCÖAýgÀFƬ¹ڑŸdÃ’ZJi\ ãO9',oíF…äΗc±/ëÑ1Ä*˜°zs¬´ƒQð_–^®E#4ÌÂeŸ¦eg¦ïç³§Þ`¯Ðˆf{JKñ³‚¼b²{Ñ^§‰E\oL§zLãöæM ›õÚŠ«åy~íÈøÒÔ§«ü”ŠÌ#9Ž=]œ43žÌ°½­ %R¦À(è’¬KÉòø1L¡"”HpÃQWMäùágã}û:gœe,^;´T›ÜŒÎ­¨»¿½¥K?嘆_–Ó®ÇרûTªô{0¾žW¤>ªZà¹u`ŠaŸ2ïÓ´vR´Õÿ&鯄»±æØºr–[z8âCØNoá=üž2„YSC‰†—,QéÓÝ÷ÂÖæ¹M¥Š?¸nœ&£5㓬7R”õ6/Ý^ØžO6B$næòb|x’w`C€¾c¸ ”™¹ñͰo‹InÂØ D‚ä¯LݺgrŒìo\wi®ý€Ê~S(dž×1ó`ÿ°²×7‚(±f·þ™|_µn©Ü`²u»ö‰1ùn0Ö+ÑW½Ðhs%5öëA1!ªs€ùùöC Ì™UçeñvÌdü£Öe•i`††7‘ÓÓ98ÜÑ&CT¯CÅÜ*ÚüpJу”‰iDÄ*‹iau%õ4{ŸLÍÔIø:¯V¶¬nHŒUK2!·OŸ¬*3^öXVÊ9s%½O¢'Ô°_E:h*±µ‹W~§û'iŸàåNC‹ô)ÔDréÜaˆZ@Ü@P/ìÛ"eÁ„ Nk'Mä£aywG?uRTþNHkBq&)!2ÑcþËMˆsà=,ØÒ?¬ZUKøwq¬ßŠ”„FjžÚ­Â¯›Õ¼@øÛåCÝ ­8l—®‹¿yjòr‹ÏếJªÏÕê4RV¥önSÉþP²3kóq—ºd“&…¶xô£ŒRЬ!còíè¢Q°ž'f˜·%Pqiå+†î~¢ëf„¼®§7ÀÙV[ßšQ²V¿ªÿøx“‡Á–×ÌC QÓÉlá!+§ŽW^=äГl.­m‚î«*XÖ‚ˆo/Mù´Û¿ÿæâÙ„ì£a›Eì £w9àƒf_&<º©¤ØÀ‰ðŒ;u¨üœ"ªåz¡=êI9TË9Aõ‹VͲsÅÛcôe¥º6{`b`6gÃx•þüøÒû*u0_;ÒXéçZ¨†3J£,Y>0ùqxÌš óüI§j†èc©üTㆲ®Äö,±ë3è[“®ÖÁBæ˜èï wHouÙl~r{fÕÙˆµß—ÕR'£)¸2&ܘõª”¬*zãë©#®˜’…{YR_+×d(Æ÷Þ Œ >iµ9OÃO|m(܈Ÿ@? õ s¶I\ÇNÐ*øå’ÄÑUi¾Fòíåª7¤´ƒÄ¬kê%«8j)@ « &±ž¿ǨiÑ/×5´pùâdÖ‡påC}ú OM‘6åxdé«NòÔÖH6H]²î§µ“õ’6{LØ[=É—cõý.-*,…ÀÀtËÇÕÆ'Îb_ŒøÉ?IÆæók¨|¦%¥Ÿµ K=¨‹t8\Fˆjaq÷ýádê¥/'š +s*ƒßð¿4VZžü±ÑG/Ïù6z¢ÎBËë‹/(YG©à¡tƧ=ÂþÒŒ#,=™ý]Mèˉ޶»þ|`”n¸¹·a>5Úʾ×]uø:+ö· æ^?“«q¶}UœÁft}ïæ‹c½ù§eä«GR×rÇÇ‘öùIKi.FÞi¢þ|HÞÃO!ÃØ6k L¡ÖO_ÇÚ,çvö =¢|&cq$éð$A©L®‰|¢±ÿywœNû0~D8Úv4" f¨ šÙdR¬Ÿ€Nƒ-/‚Uã:dâÓP¸!d+b@Ýý΢Eý! ~+Ʊ„Óò®áÕ?Ѧ9áÍ‹uÛwÆ=–[#„q[ÙÎϘ+¸ †¢HòT/ éqíAžQ ½r &#Rµ…clç)`u½~|U¦ÓÛ¹aŸCPë¾”žsåDôTÏ>£‡ÁévŠš‹þ,Œ(ÜL¹Ó¤ñ† @ùCÚ*t4ólº,÷w§H*SH2ÿ ùÎÜ endstream endobj 813 0 obj << /Length1 1630 /Length2 18243 /Length3 0 /Length 19077 /Filter /FlateDecode >> stream xÚ¬¸c”eݶ%¶¶mG†mÛ¶mÛ¶mÛ¶íȰí—ß9uëV»¯êOÕý±[[s ô1ÇZm“È)Òü6²50±µq¢a ¥çÄ—1·6pvT°µ–±å¢Q06uÆÿ+g"!t0Öw2·µÒw2æÄW56Â26ÄgdÄgààà€"Á´µsw075sÂ'WVP¥ ¢¢þOÉ?&øîÿ¡ùëéhnjƒOú÷ÁÅØÊÖÎÚØÆé/Äÿµ£¢±1¾“™1¾‰¹•1¾ ¬œº¸Œ(>¹¨Œ2¾¨±±ƒ¾¾œ³•¹!¾”¹¡±£1¾‰­¾Õ¿ø†¶6Fæÿ”æHûë·#¾>¾£±¡ù_7c7Cc»TÔøvÆÖ掎ŸñÍñMômœþöÀÉßÜÆÐÊÙèŸþÊMlÿ•ƒí_ 뿺¿`r¶ŽNކævNø£Ê ‰ü;O'3}§b;šÿUãÛšüµ4²5tþ§¤éþÂüÕ:é›Û8â;»9ýËÀßÈÜÑÎJßýoì¿`væÿJÃÙÑÜÆô?3 Æw06Õw0²2vtü óûŸîügøÿKõúvvVîÿò¶ý—ÕÿÌÁÜÉÑØÊ„ŠñoLC§¿±MÍm èþ™q[|úËœíþCçbìð¯‘ÿ33“Ð7²µ±rÇ726¢“±uúŸüÿŽeÚÿ>’ÿ(þo!ø¿…Þÿ7rÿ+GÿË%þ½ÏÿZÄÙÊJFßúïü{Çàÿ]2ú6ø÷ ¾þ?‹ÆJßáÿç£omnåþòú¯ÖªÆÿN÷ÿ&î¤ÿ·-¿mLÿRCOKÿo¡¹£ˆ¹›±‘œ¹“¡¾‰¾ÕßžýK®lcdì`encü—ÛµŸ†žþ¿è”ÌÌ -mþ!åß*c£ÿZÁ_ºþ•?’¸¬²*ÕÿfÁþËPîï 8)¹ÛýÍíT#mkô?ÿÀغá{Ò0°²ãÓ0²3ü½â`döþß„üÞ¥õÌÝð5ÿÖMÏð¯êÿÇï?OÚÿFØÆÐÖèŸÑQtÒ·1ú;mÿSðÚÐÙÁá/ÉÿZ«þó¿æÞØØÍØj}ÅÖ+È"-3Ý©=wdJHs x$Ø®´Q©¨À¯Æ¶×7-l£Rï³6˜¶i†ó»Ý}ùÜîëH‚òx¬ÍЬ7Åø:Û›ˆ¢¿q›´“ê8€N§6ýB5ÊófIjDƒ•^åxJ^A§ä g¦“Éâæ…ÂÈ¥À…øÙÎÇ0µ!µ ¡ ©®ðü‚4ñôå™lh|td¸÷´ÿ‹*'’„KÝ'ùœ ÉÉ]Ïá±Ñðô݅ͱj9«Uµ1QÙÕëcÅø)f™!ýŠ ×ôç7à!=ÿŠA¬¤ëuht cQ/5ބ଒„N}׊øÅëÆe/gšeæGŒ9ôŸ¦ÈÑ4¢"–oDr~±¡¥Lx#1zv„tyu•HžY6æú_|$¼p‘üu~ãIûüÅÑ:NÞ¸<=ÕJiƒõÙr4#<æÀ4Ñ \#í¹éùùÕ-B(/¢žÁßÊ™cø¸¥l7¡ TL[T-Œ¬ƒ‚ó¥5Çt#ÖºJ^’0½c†"Šm[7áqF‰ç’éÒ™Ò[IÔ¨A6àsujDbhš4¼æG[ŬíûJ}No ~©ø%UºnåµÛE’’ØBz¹¸d.ÇååV£vã.9÷5{&¢«ÏkÙ5¦Ûmͺ€em¦Ä™XŽÖਦ€"+MóvË7K`•»åº¸)YîvÓ”·ß‚ ’÷R¾Hþg©?_؆· p\F;çL*Xë«íXèOèýAyîZˆÆ’L;… ÜbF_šŽ„;-ZÍ ‡í™ñ–šïäâšéÙÍŽø@à¶ÐSdÑùô•ãÉâK_¶Š†RýgŒOA90†œj&ÐÌ·¾VŒ¡~©ã;­Z €`ñÎg©(\ UÜ)|ÅS¹‡ƒR]<%†Ç E•ÅnQ–·-Ëteb5£2+WÁíVÇÿ{컫èEf3Î4 VŸ#*ÃæÖ¹wƒT0Ðx¸6õ毵H¦¹:*«Ä4Ÿu}6üYªÃz£‘¢BVèGì\Ä…:ûsé ?Ò!Ð/ž> "ý2+(]({i 6"ÊÅí±r7út)x†sÏW„nk·„EPÓ©šÄ¯Í>îdANCýyr÷Õˆ‘vn ß3±\þy½è…0Ì,ÅZË×8]Ć|ùIqJòtéÊ‚?öýÜj}ø‹yÒò Ü'’øî~@6#MŠÙ" èBþ ‚ÍÖS).û+6-Ýdb^÷÷KÔU?j­j #L,s {†G¿§ 05÷ZÈ\Ä £aõñÖ¥þÛ–êk&2D© ÇÖ<\,€Œþ*MÑA­Ë=º}Cc¼pqiðÑUiw$sŠ2&5œ$½}E°ï¦•žÂÎù¢œ>¹‡ž/†OÊȃžßO8Þ¨ë" |ë.„¬”¯4x«Úùtœm“ ïqÑH—ù¦|ä¹–<°´ 3¸˜2¸\chÄ>é!kïÅ}Ä¥ìZàÔßÕCgŠÖžÌ´ä oF3×(ï Ñ=ZÇî\å*­}ÁÀ—¬k¢›ÞÖÙ­›•Ór%9b×<¾#åìQjÝÑ·?t‹½|†Æ¬m=˱ªòfÏß j¬8¾Ð< º8NÆïрʈ"ù ³0~ôḦ ¤AÓ(OÜh'{‚Âu’¡OR¡VXn³à½õ¤ÚD ÑëWKŒ_ƒ¹Ú{Ö/ø>&®—:*³6¨Ÿ9¿€¾”Ix֪Ċ‡nº‘–õM`±Ý›h²½ŸÞØóÈý=€^ Žwkúš*F^õ!˜­‰%‘p‰^>MõÉf~ä,‚NZÍ–{tƒŸh«g¾ƒb¡ä€8sMíÐÓûÉvŒô4Ã.>ó4g¾:‰…Sì$ñAÕKCMÜ:6ªâ5á”pfHw$ ,çɺåqd̳ÄnÉ ko0à“X%‘è|¥Z]9çÑNÁ{¥vKÀ—;d_¸bd<ÚnÈŠì}[®=±Â¥ÇŽêVbL¾‚“G–q)ÿQ¬¬Å:ÚÇve“rÁ£á«î¥!â5í÷—õ„ètå !2Wâ”h³ËÛ•­;í+³=š]”ðØÉ> æ[™³E"1\×ëѹ  ëæOÁøHõÚ_/„½6SW{=è¶¢×;™,œ tL\ù°§Föµ¬lò¼›‚•á·I¼7ø‹Xî'—®N´StÉ) ~”¬ZŒûo&k¦Nݺwi¸uî¨LÕR;ü «¹ò’?J„yrIÿÝaÎÅðõzŒVu——´ ;ÒÏŠŒ}¤ñá(൉ ¿5ÁoÉ “ÕzMcY ÿP‹ïO &ÝØ¦&7ï…¹«ÊONì˜gíý'<½ökŒSÔh4¯„ÒæK|´:ÆýÍ*sIûl§Îȱn›#;0=š* AOùØZ"¶ñ’ùxRJ°¾¾\øÅ~¹w¥¢ͱ<4ývÅ9X˜~‡! RÚJšt™u`°ø×Ê—GQ¥xûÆ£â‡7ÄYÛÌœ2c2áÆ™åœÙÇrK ,ƒO1š—˜QK /ó“¾;¶IiªŠqŸÏ·ÏáÏGÈÈr¦ÖŠ_n%ì "­[XQº0 A+÷„ÓdùÄŸ.]D7ãZ¦ð· ‚òiK,\“OÕÑå:¢>QrÐEå-TÄ»€£Ôg§ûÞÄ[3/Q%OuüâœÎ„G)_SÉ —Ûõd_Ÿ¢Zp,àoož3/—~c”o©žRdŸh=š=Òœ©,î.·FbÇ^¬ÿxÿ†±³‚J/o0yG?·¬|PúÜ¸Ž §Ü¼]ºþþÖW*ùƒXv¾TX–êæš÷âú¶ðœ-©oý síiqû¸IŽŽÜEOðB¬–l =_WxAà?ÕVU:£ób2Q‘,»å)IªqþDÛ÷ûEç^cì××Ã3ÅK lSÔR3'_’&*¥Vô›¿Ð,8¤Äãuj/ðö¦ýq3BÇ„Áb•«Ÿš ¯Œ –'¶:¨ˆ(¨É¸¾ i=‘­lÛ=¿Æ§NVìŠż]œ D!dôŸkfÁ—¡É‚`ÞuÀ°¬VMàˆ¢ÅÚf;F®XK,Ævï{0}EÅ.U¨(-[4¤ìPiÍöѳUv,µPIÙáao¢FáþÑik‚lk­*ñœù¥;G~ꇰˆ9ß!¹ý—¼7Ñ’¥ýς͆iì# ÁÍ•¹°;c¾AŽñ S¤ÀO)ºöVXâ†"ºù¤¤@}D~Œðs,)‰¬K=A#ãŒx@ÉžÙgs ŒsÛìX™Xäd-{8ʳ€êó ½Õוš(©Ÿ ‰ µB‡z²)wu4tð&G^2fÙ&¥×»YtÉ@ïqݲy´ßfÂá!ÅìÐA#òŸ`'Éêv ©›2„yÛeÞvmuZÇÄHi­Äí•ˬÙðÏÒÇg9×Kp£ô£D ¥¤·€C*©±È ÃJ¬‡¨#üLÜ\lñ°­¯[ÇW÷S ÜšÀ¨Îö¤—C¶’ t×.Ô~O]UAêwÒâÓ×éh©n’d;8N®*¨?Rba!—†æI^>ÕF-cÚ\jE$»Xêöål™Ã"Ä”û=å[a}nhímû㯹aã—×Ì£ì#÷ÜYWAIfM°Ò¡8>'Η° 6_…%Ù!ö¨|o>º\Qhƒ SE§u쌌f`>h¾¦ž_$å¿y‘¨ d½•qüüxаYŠ…Í‹³ c…“QÖã@j'Ébp8|Hì¡ù'ÁÞ’À*«+ûÌN\XÈÃÏ``–H©MÇQ9dÁ°Ÿ§§*b14«gyZ)H©ëW7ûœs¡°àp››º§ÒëĤ]vEn»9ÕÕ~ƒ=Gê‚W—:óbRRñc³.‡¢£Ü2uˆª”o¨¢uæø«\[¾§q ™%„)Î\¼ÕδÌ"ƒ‘“ÂÜÈBCW5KéަßÞÌõ¼Ù3(É{ë’z:ó™Lhúh¯ô >eå$ôCðµ÷B¹\\æ(ë2÷-¨s³EE*­ÎèÜ ;ëÎi9BmuLQw ë %±MŽ˜Þ‚ÒÚß7ífPyÔjÖ;UÎÊô‘3?ò‡ÖÃqY€óû N¾S OÅ{»Æ´Ð̉ …‰Ç+YAŒ\›wá­£‘êþùXwð‡ûqîׯŸ¾à»¼æMFðJ>H¶¿24Šž²†»O¢cz*LÁiâFÿØô;”ne½;x†i|mVâð+Dó0±Øw§›Èzqì HL’ªà™[Ìc>Äw¿K€äÚœyÇO#ˆriMÐ ½jéÉt®§„ÈFgÇYôÌØÖ²•’`Í›,,WHß@ðTdàÎqãtXÀç×¾íFV,ÑÒØ»®ñÈgNÙÒâçdE’Rˆ†—9ƒô À™.C‚Æ¡П“à@útòé× ‹_̃ ­ï¿¼¥AÞZ^ÈÎ)g‡Ÿÿsñ‚óV¾U^Vwä=/&S“Bct tã &Ä—uvÞfy€ˆ§Zyë÷Öøhº¾ü«,rí(K¹ ËlÚùà¦_'›GÕŽðî-Œ¸öËL)ëPbû^ù°àÑ¡£á±fÚ3¦ƒ”^¥¹æêëè|b@I‡MÞ`WÅËî~ëà¸`øG•TZØÔ.eêg]Ÿ³oÈ–Ô·ùMåǤzßC¹Õ8öÓhiº|a”æ©_BÓpºòhƒF[–“‰œƒJ—­T5Ió Ã$D¯¬•I5û´âb,7YÐ<‡á QÇM©€N$ù—ü½0é{íL-fý,'äºé…’†qgÊz—¶¤.é´èë4ß$ÒÜTˆ- J'—®} ÁV9pv¢7Ù œ{e€–"‡¼°ìImAÖöMÊ™|EyÛuã[W1eù•ùJ¹ÓJÁP—gâå…¶'÷W mHã¤á¸™ D²VÚƒ°OÕÙ"üܯxrO0´Œ°½±¾Jíö¶ž #úòîåßj?ºÞ/´íY ö ³ìØ ;<­ jëª PÚ$}FB–ÇŠ_„4,¸Ù*6yñé_¯ê!(ÙÁkØpÐêº4Ÿg¨ªäMœGÅi €OÕÀÞ™Ì=S›÷âÞßÛ¤’õ'xÔã_Qb\8cÓÜR‰”É™3ÔÕãðgŒqÛM>Fx´ëp8JˆÑöîë oRí½’˜§tP@'C ÝÉw“€gsœ¯ÛÌt–ó/æì‚Â.±nÖžwUÝò£OýÃyÓ‹ùV£/áÒèvðÒšåóá]1—vñn€ŠaÛ.…÷pߤ€³Å2Z~5­~X·O“°ÐðT•ŒÛÙ2çcä­ £fJ3<ªÂ²?•ûž…QvCG‚w”º[­½v¾AÉ }a¡J ‹ëÛ„> ©ß8!w]Œøážû¢ŠjØÒ`u÷÷å'¸P³‰YL"LJ³ R2µ"z2õšx¥xÓtz‰_v ¼G$’[«gÏûNù]Vâz3.1í­_áÇÈ63üÚØ(·–¦1ûPX‹åÅÒ„Ä×0xs[(JKú f¿ªÐÌùžir€+9¬¦ü¥òËô;u_[eÃÞs­ÈT»*ÌdwF»i8™˜&1½1Lº¤ênæ^H‡·3›„)Æ=]@x«V‹KÄ3úÅNCñ÷ð/ñÍB`~A¯ka~™|!}¬þmБÀK'Ï6ä`ß° ¿ã®¿÷ÂÍÁC˜t90è1Ùº}½ç†¤HÀ-uö…Œƒ7i›ç8¾ÖÜ‚Ví×pr²lê=ÂrSÙt^“VÔ3Þ¯ç™!kt^â*Š_¹kެ· Þmß<«ÄÄÇ`°Ió3]ÈžÊþ/‘ËŽ n¦—K) ùîסRÜø£o¸ƒšnV0%Lò†ck‚Ö¿º/îB Øá¤Ø"BgOä,OŠÔ.lP·]<ÃÖ"çŸ&z|Åå„ú±ˆÎOŸHà»QQømHHGZ™œHÝÆò VSöï ™ñ.ðH¿Á쀟Rã;ª¦Vj– ªV kMOŽÍÿ6”}wæüUø¶†'˜o…£Šz–ëyC¨Ü:ñ¡ÝÓ;ž°‡º±ÓO‰)[Åuiõ±¯0 @š—¦{kЂ)áP_íi8{Îz÷Üýu_?ºš=Ȧsiz)LA«ðœ6²Ë2•öUí•b*Êé"ª<Ó¡5l`Αƈuä³ ‹5U#ô… +Pà«T©ÔwMÓ° Gèì¹g²~ï°å8y«¾PEº<­r©Íj?>‰™¼$Že|ÒoX4Ô–¿Ì ³2Ú–0S7K¡Mýtö0ºå/PO,!'Í9yÎ*@œ¤ ¢á ½ô.lQÛú–ØLÊ}L&u/wc#a—‰…v¸N$«žªŽ'`ú)_Ä0ö4á¬̉"Œµ^Ø ›«Ø •E´¥ƒ=oX8cáË-4Õ nŒ ¿QD„§ÁÔÖ£úÀ›ó¿|¯vçyŽ4êÚ#ÅSøø2Í«ƒKXØÑÑ#ä9?„MH'*YPphhšépi/X*ZˆÍ¿ eFŸ9Å·ÜþzÄË—F¨ 7rœL^AÙEHû!?µƒ#ìm…|5XÌ´tã¡@®¨÷ž‡æ¬¸D†qÖ¿òƒWd&Õ¿À s•$ÍéŒÓ ¤Ë\»šì#‚d"‰b¾¹¢Ž¶…^M’{lŽ<ÖêrAüö½ýx–—çú]ˆæï»Ã?iB`ºÜÙÔONw õÄË;,‡™÷ópðHh7”°e¨ø<0©®6"׫¸"…‡ú,ù¢d½ÂšmDˆDÕ6œqSÈ«ÒÛBéï{¾´©\êö+I5Š?êô,gl¤øPaÛ)}„ +A NÝhLJKtP:P»)±fÖ0\\Àå«(A1g¶àTËR˜ò‘1–\.D—ÏÄZ}¯§4Ò—Rž¢’־Ȋ³d½9nb0Ùs†VZ"+A¤zÔÙ S¦ï·K½’AF)Ì¥d†ð/ÄtÁƒË&zq×mek—)@ÞåCGE:˜ ó*…’°’åY£zTðL£öѰh7žtAبlGäÀÐã¬]›ÕÇ€çgÁÅ»hý•X`„ z¼ð|@«9 ‹<Ö7À"£m1(:¢À \òÅÐ= 鸅ÏÏR29k ôýËC nëtó)þÐØ°bÌßœ½3*õªÕÀÛ”’Û„¯´3jô=al-r¥ŸÄRÉq÷³l·$%C\и"ØJŒc ”! azw÷†Rl‘°Y A¸¥‚”SjÁnÞXVï¼D~~Éë!®‰–,n½‰Q¸¼çAAryPû#PQ¦JR7wÙþ2ŸŠ“-…&Z"®h¹v…4ûfÌ7”3÷™èÞE´áØ ºéþ`™¦ywÚ…“7ÔCÄ:òšGõóNU\4xuŽž Û½Ç?‘OË“˜úÉÏþh±ÄoRóòÓ˜”uoD•UúPåªÊ¤Œ8Xotðu®d޽x«V?Á^¢¥`µŸ $,ÏÒ¬­ký€Rü³Ö\JpæA郲kP)Ÿ÷ÄlªòãŠÇêÌ]dÁ„| YZ¶ÌÈœ|<úÌ«uÓÊ*o„k¬LWÕB@¤*Y¬…gÐZÔ+ü_@Öîl I÷*¤ÏìŒBßáGæÅî„èCÖ„wn‘ƒÍy-{û÷ÖK¼U­†üÁG%šåuáÄ/v.Q,w>ù­Ïž?âùf•ɬ«Çsð8ºwd¡v¾^%Ê@Ap$Èz€Âuûé¸z_ä€ DÑH´ûDÒÆ|‹žÒ30¿: ²sY' ác¸ÚÏF¤ðô»§Pê|Á"ÄŽ¤:ãyG[†FK^P‰ ?kÒ”Ðý¶È”.–dâ˜A¯Ïo¯ ìGÌ¥¾:>‰F¸ÎsOR£Ûp|Ù~ƒÝÖ%ÖKm„x¶¯ul„êU ¢ õk]-šèüTnæò”q%/ZmÕYî§³3:?Z¡'a³ä›èD¾¹ W5všÜ«Æ Š©‰´¬ÂÕ¡ì ·}<Á §s¤”n1Vƒê«F—‰^|„«¿X$<óW.X®,‹ùÝÆ¡V¾u5O;_ íº1cæ”ü™5zDñ¨ƒiÂÈvÒØZ,’vÛüínu ûg^A™²ËhI)›‘ÑÉoŸ«^Ó>p)°ÅôN¡Çu7[p¾3NxØåg)@Luèñ@€Âe„ºV;t ‹9R ¤DPÏÜä\"«Ëâ@¢ˆÊ4ŽmcªƒD<_°¹œ &úrøÜ³u_ÔØù k‘H†Ž†ø×3TÑ%àyú“®Åú¯ŸQVšõ‰nŠN;Ÿt«G Ü*À¢"ŠÝ¹Š›×¥ií<¼<ÝImï…[î§•çÄŒ~›‡…U„áq¿ …ï‘ïsS+ë¦ø‡ž†$öœ·Ïš;³]‰Oï:§¸ÅÚÏá*n¾ ¥!i>9äÕM3UqûnzœQ?#•ŽW Xi1ÀÐÆÝî4L¹ŒÃ4(Qu}úV€˜|©ß¥Ú¿GÛSÿ@m ³Ê`@\¨Y`õç K¹œPâ"ŒåÇ£‡#=V–WÞUŸd°À³LˆîJIY‚ÖfbœN°9¯óÅšØíãj¢£= ì³Ú·=ÒÄ Jˆ>¦óìêî&Ž` gåY, d5„´²÷ap˜-©L«O'ï¶#´°¡NÏ9h-ÛetKokzŒõL¥€ªjë›±, ÌÆÌ¨ì´g @7™WQSoáþVUGÖ±Â-âÍ÷›à|e ¤Öæ¸ÅH%øãb¤l°ÑíÝvòè7§€êG.f”±â¡´&ŠŠz#Ñ:-ˆ]ø¬ò.š¢ghÝùΛ0ù.¤ óR™³GhÂp $ak…‘ð:Rˆ9F›g ¼b™ÿlÈ+)7áñ“µ½ùYËÖAâ×v¾™¼#ecD¹:ŧ"p:Ø:¶ˆ±Jµ/ ñŽ1ÕγËÂi©Uv4Xï.9Ú*¢Ü)àO78Ð^T9Í„ìˆM?ÏÕ¹–¾¿äÔƒBˆ½q8…(c…#Ùÿ 4y%²}MÊ~AM×{;E8ø‰(Û0÷ª) «TÛ;õ˜åm<¾eÆüzHÝ=‘„pÒ änønÍø^Ì‚‰y¼šeÈ©Eç˜ÿ¼ëM7À†(v¿Á%Á|"6ù±çÖÃ|ÜÇ;ç2ù?þÃϹ ùþ²§‡žo¢\›ÚÕ—œå‰!fðÞeŒÝIP ºZÉØ¢Þæº}þu”¶IýY|XfÆY³ìϧå+¶t wèÛ*®k¯ëCK/å(y]èÈa‰×VUƒppíOÍÚÐL’“çüsþè_ ,.ù¢c·M>OĹp@ìOdë™#Ïḛ4EÃf.&wy,å·0ãÎ<¤Ž‰@ÄæAÿw°>6„7k¦•ç&u[߃R?uÄ_Ïv—âwä⬆29WrŽ Ö6;¼äe}`T—¨^1>µ›±9ö‹D3ƒEVš|Kk+Ø^³ÚNÁêÖÎk¨v¥CAtµ@~$º˜Õs¾ÚI•èìÅÕ_­Åw¥0·Ü>ûÎÏgÏ_³v ¦øzäÒÚŽ50ãeº$Åô i€üqvp-Þî™—Xû Ï.PjÍqÑ”8Ý®{[:p¯u.üÛ*¯6BF}Ÿõâ­|ë$šj |f-èx¬—ÈcWóC·–Ñ”PÚÙëòI‰ƒÏ×P2¬@žENk!ÙÂBççmU»I²›FüzÎŒ‘p YQ,[æ(n¨ôÎ<²½1Ô‚ŽuÒ:¾ÈV?0ûÉ~v.ÃfÕçãIÖûly$`áû0²_;0kI`GŒ_*ßwµÛ˜WZ‹&çØ@²c &›ð M޽¨F•tø'ŽZ_’Èe“=ò±ª#f¼ì-íÅéÑ–ꘛ¤d¿ì¾”ñ6tpÂèpÏäPü—™¾3ç´—c~ë[–}ù'?Ë^?dÝï>æpfˆ›²ŸÃqú“Qø¯í‹Wk’«Æ(Ëzo’®º•7å–…À³8Ú”’hûÆrOn}ë·@@l~¢^/DšAÎ3K<,ùXò,$ÉI$,l5å¦h‹ö^õü Nûä#@‰îq+\gåSOÔrA…}ßb°B|ÿ$4lcL¸Ðh|òý©»5Èß{Ið·1Hÿnªô2ïÙ >S? š’õ $m³ÙnT^±å,ça‰b,«ÁÚ Ú@mÝ?¾ãîgíÜY’§ç‘:³§Z›;¥ÕÓc ¸»Ð%¨$xæD¿{³× ðHP*ƒ›-í L— 滩àÄKHfö«b¥¾Ž"sÒ’¬rØx<„'”±ZÚ§û’cnÒŽÈÐåœL ¿WVñ&¤KÁÅjÍÝÍ`ÞoUQm2PÑ´€ejÞ×߆èØ—w½ä®³¨ó–%$‚Õ É(2hü†& Òq$왉Ç:ý±ÕRbÜ,_ߣ_Ê~³w‡y_~jÀ;˜;Jݵö¡Ñi)ê cÁ_TÔ"ìœØß‚Su]v·†ù–w‘ÒA Z>oôÍ’7%jMI‘'® Ö¸Ÿ}½f´ñ2ŠÌ_íµ‡fíf€ý…!!ŽœM¨ªü–›”myÉO íyFPÝÆ8~&Å—HFÚLl”EWœGDŽs9\£D,l¼PÔHðq©'ô¦Ptãšýk‡š¦‡Æ9©kÖ–,±2:”¢3‡$PnºÝNåíû[Áâ/¾&¿Ìµÿð|—ôK÷|Cw›,QI¡k«ó#Gÿ™Ð õ›#ÍÕäp“á¹ê>¨ÿAìh[pÍãd3‘áè oÕh %™Oö ÃÕÏÌßÒm¥ýâTªá˜Ü"wì´ûG„ÍÎÉþãUÁêæô]DÈuMí©¥^Ok¸ç'ÙzUHJ‚JwÞ8‰jìeqµ-tø¨<êJ·qé9û,m‹BIÆÀý€Ouö‰ŸÃ%qÐpi 2+ ó»Â…#™x+Ø\Ó鉽›®…>[{Ä=]¢Žyå,CÚ² lͤ>¨ã¤&V?ôI¨yw’¿7NL]CR•Š/fc3æ 5hœ3u+þ£¢%?pôºFXx…$uº°)Æè–okÍR…hŸÇ'¯Õø¨8ºbãƒN5/ª+nBÄŒOÂEži.dÿä+5jåЈ;üzˆÌáV %5ކ×x»CÐ)\AÖR~B5Žö[¦?[ÕÚš‘Åæ³S‘€Á—.òäÖy&¥˜µ +F’Õ;Ì`¢û½ðËs3°‘!‡Õvi•5£´-„@õ8Ríó¶š©(»ß¨ý$–\ÚÂ3š Rôkz`ÄË4X:òð`Œäh ŒA×Ë?þVkÙׯojÁ[ŠÌ»†Šº ñx½Á¦“Mв표¶ø*ÜgÚ©áà†¡HB]Ì3`BÆYÿˆÄпÆ?ÖÜ$r{jc’¸á[£\ÙŒÃâÝzVÙÓY™‘ýgsƒÈµ×aÁP‹ÛÅ•lœÛq 3¯]XpdŠ‘¿é[PbÊÕê lŠZoŒn߯ÍyµØŠ“{Vǽ‹±Ü[49Ô%s5LÉ!ÿjl®b¸YÇy¯Ú|¬çòvÕ)ôZÍ%ÿÃd†RøûþÁ‰=wŠ0%âUA¦ªô·jÒU™J¶y•»{­IÀj("Éø‰V€vG¾)v>qÍèçªèhCOc?˜ÕI;è1ÈéÊó[‹\ÇSòhåOؘ„Æœó¿UpÁÉRoâñ@.»ðBÚOögLnzLö•Ör ‹;¥ú„“ ššÝbhÅ¥&ë¡™L@^’-â‡}›úS¥õ½¸œ¹YƒŒæ1üZNggL-V/øX˜wô˜è!ûa²>À¯ñy¼þMÀ@à¬âeHžù64‡;[}ÀŸ:×êm]JxwV]¢™ wVÑëJÅ_çvZ‚—3¦Á¹ÖìvÈÑ;Ó¦Õ’­dd1P‘‰€÷åU’Õö‚ϱEîšR…‹Oð§·9:ÚðýH;ö™“¿jr©PX¦ÜY8©’éÐ$×wçÈ«lÕ=§Ïtfxm&ưÊß\kžHc7 H?›AW#pMƲÞ’Ö~`»4þ\’nza)ý<Äž[ûÒÍ g$fPÕ[¦}Äm—Û5ñ×8µ­Å ±SúÉ «Ý«šX€( |*…¯èVüLCº™Ÿ †ƒß–1~ ‹¦ÏÙe'²¼{ù?/“v_ç„™(§RÒ‹BsŠl²©.E =„Ô`¹@¼:ôŽb‘Ó­.±îžyK ÷ômw¶ö¸U‘û‘Ë*¯þ5£-³Áñ/‡+>Ψ™¡-*™XjiOO»uni¥®äH Å¿ø!Í#9<†qK÷¢Äl ;1ÔÚu܈X‹Á„ÚmVíý‚r6ª`}¼¯-“¤r©ND9§˜g9–Û;ã—™ë냿„z=ó[‘º|B™0ð°Î†JôÎéØ)æöa2™—É&X` }oY0ju—9w©VPB #¦Ð)û•cHî÷êU6£Íåc¿ Ø¡Ä¨rD()Aéˆà–÷MÊà •œÑ%ñD€§ åú¨1žÕÅ|í/z¡ˆŸL‹a«ƒ‘ÛEÛxº‚Þ¬îÊ9¤»r÷Øÿõf kú£Då®ÓÌsßFcÜWÁ¤h¿u° ©“È~/pÖÁµ²zS®ÈÇç‘å$× gh~´@åÉ›¦¦ü})à S&ô6ây !ÝY'ÔY¸PaI±Ïh(ËL¦UˆþMÝ)Ôvögq!oFèõ…¦TíWEžR’Ž\Û|«þzÑö*xô‹€êy86Ä@¹r˜ÛÞ6SkCa¿ò+f¶‚½R6Ÿúe1¼JSh”ke¾jû·/Á¬=áµÞLÞ u•%ìLuÖ:pŸüªÀFÀv˜|6 R+ìÌl£zgJ°þ<‡ÆÇb–¡¹c;µ˜¡QXæÐîꘈÝn 0¤{ÑÓ¾Ù¾ŒñݦŒ8ÏÚ¯½§úJ$OnØ)² Òkí}ÈÐ^nH‰*$ ="›‚[îÐ4væžr¬GïõVTúá[,¯?Ý´s7e¥pOcA8gEe´#{Èd¢i„]º!Æ/¨©»wÈÚ3áCÄš›€2<¼iA?`J< Îí¶^u~Ñ \@‘Òf}^Ê6c°«N‘¦'ãû»;#cì|2ì´,•ä_ÄÁ¬uŠŸÝñ•rĂѰ‚cÁµ(¹«nN(<ê§ÝUä&Ò3i®4©ýâfyoäx‚>bUV âqŸd*Å¥„6q‡bktÊÔ’ŽÂ2ü08¯æ¾éæ9ðÙÞ$Z àŽAre‰y™ň(qâÌ„ä£VWìm$¤­÷ Œ¸zÖwh:€ ê7NJM­’Û~ÈT€õN…7VV#žÉÞùJàÀÐâšÎÍFQ{=òNâ•[ãY?öÕ§z€It+d·è‘<`ës¤¹ì’íQš±G€í™cª8Ðú ÑEú;V¼…@Ï…ò‹’Û äp“÷K›·föÏL—K7$eëÅm»`\Ò˜ŸC4ôG7ÀÊn|œŠ°3Ž’*œÜtýzŸ‚×ñÇT)íè°OŠ¥Y@T„ˆî^ +5¹YåR$Q4›é´ Á­ë|¾0QƒTýžÀLÙ Ž—Û2Ç:Lz«ÇÁýJϼ¦}Ú«‹ßqÇa¯’ piÉÁÊ»ŠØ²É¤Ä n-'R7¼ÚRâv¨éZ9Üó¹’@‡Ñí£îA B:OVBg^ëñ2á;4i…²]£..îwf×@‚)ßÏJERŠ×?0œ!ö½ü‹13> q°‚…ÎB¾laºµ›coÒuÉLµ{2œÊçÔmF2¡|†DÊ ÓÄ¢6žYvÒPZúµã‰‚<Òs –ñJºXŸY©øé­üSÈ¢R2Ýú±ýMõEš!ÓÕmHoÀ‚»YA˜IÑ#de€¢ª0H™¬$§°„5[} †äyÖ¯>ÊŠ8ë [{¡{7OGæ’è£eŸ©ð_,Ú*ëy°G-Ÿ@ïL'ÁÙ”½Yw­˜*§•z¶*)K•}ð ‘߯^Ô↯ôÇê [ôá&F`p_'N¥ög#BÙWÙcüÔHÝã›éÔÄìž©±åUÍÅ\ìèu¡Ï¶#‚¥œ×ÙÉ.2o0ðcæjqâ Èa 1$0£š–qù=.Újöóûicèï »¤ÈV§ 5ç¦Ä±ä÷Qºà˜»W–ñ™ý~ º™<œÌ”]02ˆ3Ï1ž¬»}Õ2¤IïYv»LÞÝÒF%×'³:™¬f´ª^¯{‚¼8¡EŒ.ùÓ‚Éw@i,v©žbyI¤WT£$ Eû.6’ѳ xpYªu’ {¹ÃPéH-½ÒêÒáëÈ¢½ß¦é!Ç݇«UX{Çã‹£}õJ‰í‚V;JZn¿”›Ù|†üK]¼•Vi};½Ñh ãpOH3PN$Í>rgM.j=Ž.-ñUcðÑ€mÕ¨C°‹—¢aYê a’ª¤ÐƱd¸jí²Iòôºc›Ï"´Ce s‰i6ÓBMH1r·4!âNQ|ÍÄ…˜^Ù'¿±Ç=íÂÉG8Šþ˜>ÿ/RÄ6g~ø[´þd”´>Å=ßßÕsÖžD7÷ÆÛÔªŽou‘f›Û“h!‚ѳãÎ$²k j×Ãê ‡È”1¹`õY9ôÌöˆ2Ø€3^¢ ÷5@>‡@ˆ•¹µáBïèòÅÒ™ „îV\uQ“"²¥u'{f–8N³4¼À Ào[”ѻˣ;|ÐFÎûL–ô%åò‰üÖ¶H"î;õË+#‹:¼»˜È–×㉺Ò¾õÑZý-…d Ú/›ì'1á‹¿{A tGˆ0´íGy¾P½Huß©“¯8åË'=!ñ+c™rÜåÅÝhŒ¶‘dÍÏçTì'‚ßOÅ~B·>¬6šœÈ‘R,7bW!\DÐM/_#ï·`P©ºSoÌ+Ø«ÿbú[êÓñ¢”ðIûeh6$&h®c–¯‹+;‹92”^¨ â&ÿ5”#>µ¯Ó`¥²µMæðÓ‰%Þáš¾Ïxù4”½P(}a_xD‘¿’Ëadg뀛½ åØkõÚÌ@–ׯÍüY|‡(øMÚ³Ï,»s• Î.¯CboΨš¢yÞ<^F…¶‚O¡³4æ¡ÙCÖù=ý+sðˆ"x$)v†jV¬0,öÍø~sƒWQópJg˜Kp\,ùgÿŸü0y‘réjOÎEc•…‹¦½S}`®Ÿ 7­TÞLùsWTÀOÌ@ÜË(fïè’¹Oz„p{cÛÅ®eÐU±Lù«O ¬•KÏb‰=·gjÍ:¹² ˜å”Æ•bn·f{Êcu; ñÇïÞ@’Ÿ‚ÒÅã.xäåŒüX&ƒNçžÃÉ„ŽŒ-D[4éhÒZɬþ»dG•0IÀ'þ÷ÍnqeëLãókø£ú¬ ˆ5NLÂ@¬–=› `"9)0݃ƒ´’ØA‡Nú_Û‰]qKÞoàȺ¾„6ŸÒÚù¶Ä‡Ó°¿wâx£›ýˆ¾Ógå¦f´ ¹4GA¶Ö%f *NÓ6Oð, QâSË­«¬T1%Ḓd*âʳ#,Âß{ŽN$Ð~g€Ø·\$êZÙ·äÐ[­ÚØ=]GµñC2˜øùÈè7øN±ØÀè2íѶïJãáåŸdóÈZ‘ ŸAAE†ýü™‘Ð Ùåv˜ãc¨Ô w/HaüÉjnö ÷•þq*š½n§€¸Õ¿Á- tW?³m4J ÆLvÝ÷tLÀjþ´*çÏØPZ —€ÌÜcg¥D‘ÛJŠãjµ !º´Ýî2rÄ"]£ ÒùuG‡™y™Ee£ÞaQ¨këÂö 41`»æ—Ïûô¨oÓR™‚3©Šû$Z¹á”“¸@i¦"IÜÈô3-–8Ž&­rÝ‹VRB=†’¾¹}³ ~(„…‰3ÛSmR…˜•“›%»Žôü†EŸ $LL¯v²sWà±¹¯±d}O;7íS¸'Óœ¬\?㟠(‹c×HÊÎ)7Ž—ãgØë¤ŽðEÆJÔE¥\Õ1ä7VùÊ8‰™ü hxŒÄƒ}Ì»?Ë•ØH¿]5Ÿzx|O®¨Q#‚Æž2 yõ#9gºR “¿Z^Uɽ¸ýŠÙÎõ(6õ¢Oae|wáqˆšçï´õ½–YS NVØßN¤Úìš#1l6c3¨;q4 ¼ {‚ _Sèþ²i¿3!u ïÿ…Óá*>Læ“^œìÓ¼€­qÕ“Øå ¢ŒÜoŽÇs-T@yž‘ÈYÆ¥Áƒ2K•*ž:¸‰€“þÇ‚[=ÇfÓ¿6Gq&€ûpã˜Ëµ¸D&Š;÷5%¦jànYìóÄRGÉ®À”6úàmÎñ5ÅŸÒÒ‰™*ÈDågé# K[ˆ›*ÿULjn^dåÕqñzAF(jÃÞÓä"짨ˆ*5HÁñOocö®göq¼r¢VTá’¿‰j>yöe9êÚ*ÅNƒR?B飠¶ŒCn‘©¯¤óFŠ.qƒý0Œ´œ^Ý#(‚ÔÈõd#yQO@‘Ü6Ulƒß7^^~ÑïŒfún½6€ÌÏ0êIEéó«F¡ðÛ3Â_]àÓ¨ÌÎ&ÀÇ«ŒB™w4RNÒêLŒyvÇ‚Ǧ/uÿ_z …ö 途Œ5,5j¶XšÍ €97ÂÌÿéèÍúßh/€D$ö‡ú> Ó›¾f…(ñ¥4M™ÚÄEˆ£ K÷ÅTR4<Å‘sÌTsÃdbUçSçk—gú•ÀåwÚ§ëm¹x¡þϦí/˜/5ù³z"(±âz¹Ðm 5~¡pâ€_vC¯¡xðˆÏd² åÒpŸYg€Ù£kÈLE„ºÜJòWÔµõƒ[ƒ_À‹H¬=v}ò dr+èü"%iÁõƒBm×ìz:‚[} š$· ·¯ó%o „~êÉ '½*ÇMï«í®zê3š,û¯ /¬…ßBûò³å`O«§BÉçs®§9¸À½y5$•|áˆ|3Œír2?“ã܎װj ¥S¶ø\¦´å˜ÄÙ¤J\¼†ËÔù³Q,‹„àÐÂ=eGšY9«Ô?,v‡Ú^@hÅžý2Eå•IIÙc-¯ôs‚Z¤5îØ$ú¥9÷ŠJhD=4hÑb;ù ô?9âz ä©é‰¶­&4¸Ùì^ã®!^Ê”hÞ©]ñÜÊ":…„ïMÅÇZÔôüÁ=‰?·†«£ŒìƒŸíé>Ÿî]r#Úúf…0úÒ§ØM[T •V[-çï±0ˆ¢«ñ;ˆpB²Lç?®—4ˆ4䮋ŸÒx~’¥k m‚$¢sŒjlifÜÒÇã¶\ʼnQ}6ß²O $‹y0‰, Çàçe: S^‹R|ø[8WZÕ íIoþp|:GGßை—ºA€ÆÐ›zõ%Ií H ÈæÌYuh8Ï_ŽT䶭Ș°Ôȇ».;=¤<ª…M'Ñ®ºý-Öß½‰¤Eö”´OQ…^Ò•ç,à-°1ó[ 1<ñ¾o]ð=”8¦[ÿÊúk¼Ay N½W‡ „®î÷üªs¶(‹0òšÿÍl¦²Si‘nW«zêÓUEÚÕß°òU¼[/Åúgb#‘„~ô¦ÙþrÝb†$ðþ¯˜Š%i×®´A1/†¹9{‘Ù¦¤fÙ#÷àSo…sófã Ï6Ö,i½· — b¾_ÇD•6ó‰r’bG¹.½ ‘l‚pNá)z„žÔ‚>p.¼‘áa°öH•ª\ç*h‡¨å§\ЊtˆÄ©âEB†y]³Åè]báq”e™ãÿ±çêèsp¬µÿœ¶e™àô ¢Ü(Ž1ÿü4Ûh×8Cë&é@ˆÝ`}GÌM Àg3Ù§8Ä8Óß·j(ÙHåödf4<ŽW×Çk„vs>àÚ!-J“‚ÒL"duæÖ|)ßÿw»¨ dê~Цn/+îZº ý==¡«cüNôÀôQ’DÞs¾©÷#° ¸ôœ#×og°kLyµøFbfì ŸIŒÈÆÙžÙïà›L:,àÁ¸_S¯¼.Ÿ¯åÙÌ ³ ¥>§üç©p<¹Ü dæ²¹¸3›ðD‡Z|P}óJ%ï²­u¥]÷kÀtWõgI®äõļÂÇAųëãË·'íŽÀâSYbAãöÙÍàê:(Àx¼$jy}xó?Õ<6ú¤Ì\- SœÒþÒß@}‰²”®_ºÛ­ÜO' \§ƒÊÄ¥cy‘½`éW3YÏÙ½N3‰d)Fù—Ɇð_ÊŽƒ|ùn N™*ÖUãKMýмE‚ ‚„óiÐëªr•‚*“ •J×Ð4t¦¨¶Th¯Xs¼5S”ihå/Ê"­7[w2Ô6‹Ã‘(ôðRòÖþ{)Ë/ãÅ¿IÅh»U£Òlàü2ˆƒºò¿ãª‚„Iv¾y1› õ*ÐÂýíZäbÆÒ}<ü3;Ëœz«„ò©ÊôÏ$iÏÓ9isÒI'A#·ç¥…öç,+a‡Ò)Ï„OœÖ àêã€[ù:?I2o«‚ëwÀ8$¹ýN1¥_7‰‡Of_áuò„½  v&f?Iò¸5Ķ]ȺÁO3¿—‡±s™ÐEÍ7QÂ4êY7Bk15ô÷« 'ŧï£ÂXgþ¤‹6hH¼ÆÌ Å,ÁÒ!RÛ#—ߦÙhhÔ²™ÈvjeÙ» äàô‰×.öƒ<ñÚRÇd]R×hxd1ý9VÉ6ß<Ûìu_Q^d —´a9®$Õ³&ÃQ\6›ä6Çš6Ä‘“S€ª?ט~ÆÞ—Z×¢— ®-n2Ý^@Áßj¾˜IÏ6÷MVyPƒP @í¨Álœéʲ[8c𳚰š‡ ij)q½PºêémÈ“wsK¥·d^Ó±€ûóçµ²ô¡÷lô?|šðE “Ǽ*Ú ËôËð§îµ¶DÂÆøŠs¶‚gÑD+ʹŽx@ÔŠmå*µ¸D•ì™îÉ!M/[ɶi€ìªùþ‡¢ºvR‚˜„ýK^|"·‘삨=¶þAÛS i-j˜iÚx¢«© ˆûò—Jðˆ(a0mÓ“Œ‚ï8A;üÀœ¦„¥ñNAléì„ߌâ'úÖ3¶Œ|ž$ïÀu—Ërç^Ç!éÅjŒ¨i–BgYÁ‡Í&zÙrS…›»S;òŒ*v\d‡ôamÚ> stream xÚ­weT]Ý’-‚»ÜÝÝÝ-¸s€Cà@p î®ÁƒKpww×àÜ]BðÇ÷ݾ}{Ü÷úO¿þ±÷Ø«æªYUkÖª3™ª“˜…½PÚìÌÄÆÌÊPÙ™¹8©ÛÛ)Ûó)2©­\äœMmï"•„#ÐÔd–4uò´I 9€ÀÆÇLJH°wðpYY;hµÔµéÿeùk ÀÌãŸÈ»§È  ~ÿpÚÚ;ØÁÎïÿcG àl X‚l U]9e­Œ²@:¾¡êbf 2(‚Ì`' ÀÒÞ`ûÀÜlú«4'æw.1'€)ÀÉhzwº›þ‚@G;“Óû7ä°r4;¿Ÿ³=6·u±ø+w»¥ýß 98Ú¿ï°{ÇÞÉTíœÌA΀÷¨ª’ÒÿÈÓÙÚÔù¯ØN w`où¾ÓÂÞÜ寒þÆÞiÞQgSØ à twþ+–`rr°5õxýNæàú; 'Øê_0V¦Ž¶@'§wšwî¿Nç_uþKõ¦¶{Ûÿ½ë?s9;m-™ÙØßcš;¿Ç¶Yþê9°¥=€õv ‡b®@Ç¿ˆö¯ž¡{OÂÔÂlë°Z"²(Û;¿‡ÐþÏTfþßùAâÿÿWäýÿ÷ß5ú/—øÿ÷>ÿ;µ´‹­­²©Ý{ücÎÞ)ð>kŠ€¿†­©#à¯2ÿ¿\Mí@¶ÿó¿ïÖþ#ëÿàüwø!ÄÀVï 1±q1sýà r’¹-TAÎæÖKSÛ÷ÃûÛ®¶:Ú‚ÀÀw‘ÿ>ßw'VÖÃ4­AæŸÁ©Áõ¶ø÷Þuû»1=9m†ÿfÚþ½Yõ½+œ5=€€ÿˆ¤­doñŸ‹¿¨ÄÅíÝ^LlÜ|&vÖ÷Ëø~ùØ9½ÿaÿ&bû×ZÉÔÙäÐgefee¼¿ÿùükeøo4R`s{‹¿úHÃÙlñÞzÿiø 6wqt|Wüïið^ù?×_ Ðhޏ¼`o.d“š‘æ\›=8.©ßÛÍ=ìP\§YçWißå›¶ÉWfò\Ì\?ÉÿÚâ1ìð²+O¿7ÜcKÓ• <Ï%ò¦ ëÉC_§nãaØ `1*FI;ÑŽòº˜SüõA›õÓÞÖ¸šºQÑ3,ñd‡#üÅ=…kžåo‡>æ)µ±ØíhõÕùÇ'Ô‰‡÷¿iúG†º®`zv ²b¨Lq}¾“%9{˜8ÞÖ™¿Â<ºò¸ ¹¡xa¦½¸PøƒÉSí%jhÇD_Vm! Í ⽤ª§oKÓ„‹ž™q%š…ÍÊêpqë¦g5CàK‰,è•Rðã¬ÃÕP|L†[‘d[æ ÈÚ@ cEúâè7áasþBÔõš ~ˆ]|æGÈ#¬Æë2÷1û(§|$¨­¿öÒ kë;Š4RDVå0òó”¥Ö·u&þÞ9šd¼ dAn£61ˆ°#=ýYˆ}†ù†CéŽÛÈÍâÈI»!ÉþžÊnxï[‡Efi"?«ÃB %7>¨9ÚçÑR•þIá‹)Œ¥g]È*`Y^Gí÷ÉÉB*¥EÞÈyŸ‚+Û94Ñǹ¤ {võÕ]î¤ ØJ”ñ]ys|ðÌQ÷9íA|ü%,ÄU$ +ø«6qh±M‹ÔY¡€åQAè²§^¥ˆÃÄå½’jnDzYßך¹*vÔ›p)i'š‹;Š,b‘ía]ÿ6;¨Dªeÿ¨õˆŸ£Èãr’£‡†>u»;t£ÑÞt\³u(Ì·Ä* sJ̈À„-u–K@î‰Y;íÃŽM¾SõHÂÇG#K´¹ ,>6’'&Á(ð ¨Æ²L€kA ™¤˜TEWngæ3G 媡eOÚo¼?ºš0k‡ßTDE¥† &Ãü£;*îöf]k„žäÿ(û@¨°sÑÙñNŽkõ¹zp¶4½žÿ±™—¶³1• >§)/ÆÎÂ2(!olk]¼d.^giJ|kì8NûسÙ)"š”™áø°Óî] EE¨Ý}èšf[¹nm¹ºIY•M5šz£BŽðM‡›#gªfƒ“Õ8bĨµ!ÿv±°Ht×°(|@>…ÏЧ·X‹'€iš~úÙŽ ô KÆôçZÓõÝ#ÜkkäxhJ&—U0ÞɽíE¾¼/}SD’àˆj+ ˆS˜ÅE ›« ›Ä¹ÏÉ,ZÍi…¹êµ!&¿nö±};§*”¿1äЫþù9<Ù9¢û'Ê·Åàw]zvl;-8· ag«-ŽÄ:jK¿:„u¯>ÉØtúûØâ#M…àÍ$²õ/¡)¾AUÀzôÖrk}Éh¡Äy¡•¬?AÀ+ñŽþÄЩ0Irô«Fdç¦Å}³^ÞhEy=›ÿÁ%}üûŒ‚%ÑÈ,B#ÛÍ#mÍ`#;ÕIüæ‘0)ÛqÊfÒ ÝŠ/ùÇÖ-å @[ü¦£=ÕËdθ“¥T2Aý¸€º¼ë êïÅYq@âÌ ÏrþPI*ž!ídWŽç ÚãxAH)òmŒ;¯ZßÒ¶µ‹9"•8‘í%°ôÙ§ÕO‰#‘_åçŽElÔŸdhˆ\/$cjGP0²‚®4C/®æ×ÃŒýY¸çl¥}ƾGÖËÔØ›¸ WtÜod[‘CSçYÍi»s“$³ ±À«háE;E«é·©[#,ɀ욜À*µ ¸›ÇÄêGQ?…Ð}UÈË¢ð¼†mf£a±Tþsœ?é\:ãRçŒÔüYªU¯Ci²¡*Ѳ H ØÒ݇àv‰B´µû²m=Lϼ_fÌ÷‘væF\Cq Òwì™C…\ÙŸ5«F©¤%å ;šêWB¸‚[ë%ô烮Y"WìòVʧÜñd.ñ;b0ýB­ŒFÀ/ÛSÆðŠ›°yXä²4Ÿ}TÂ)]M_jÙÃD¼f¢c˜²*®Í)÷ƒmÑãÁ :^ò¤ýo9kØýM§†©0˜Ô壵½?Îq›q\¸Ù^†æhïYLåëNvNr†â¸&®ä?™%Y‹òRd’ÂËDbFY2 wCgÄΞi”Ôκ2cêOÂGò*CçOE¾‰±c“`BÄáIÿ¶hUõ$YÅÄÁ!~.q%#ü^ƒÛ‡±ø&ùfvg¥’ÞKhúüÄ@ºý¶p¤—Él¸Þò0þ¤ß&ÍÂßI5ì›Ló­=IC ’V#gdWJôIA0týMM–CìOÏØ.ü?­ß–©,~Á Á¦ÏXŸ† qÂèIˆÿÄGlºÂ ©ª“”û­Ix,Á4B¡ë­X”ÌŸ„N7gpŠì;³Î)m84S“cT[¨¼ Ä§Î²â3m®´äfWZ<¥§CvõfÎ%ÜïiZÑ—´œ¸&çò]ë&Ã_$Šv#ÙiÝ[u6n!Ãz½:Ed¢Àó`x´JݤÿJ/{èx÷ë7€-¸êqö× ¦pàªI©Ãµ‡‚`R@Òæi츬IQ 'Á4Ô9­KEɘ¸»ñNnf×DZ/:.i¡goLj) c ƒ3å´€àÑz0ìáìÀé—©mkË_ÙÎ{UÇã*¥zxËP›ëê†ço_™Ì>aÛ$ŽÝl>¬¼·k‹Ë£?õÏ|)µ£ŠJ”­«â2ï+øl…†jQLº°Ï€TM­:Q?œÜãÜ  F޼e“£WÒÁº†b)óX%¬¹©Zè’ØH€Ø­Çþ Z;thï`.dG~ÿ9ëì„+~Ø—CÜ0™šh'ÉÕù]3u¤[#l1lkXŽt9sR‡jYôe^]Ùm¦×Êœ#:°[+ÂHÈ©îûÆG%Û¥;’º¥Ñíôƒh’ƒlÒ¸e^¤ÌýôÐlªK åÚ(â½ñ¥ššÕº&´ì´*ôùJ_9®.>±NKA£4Ãcs”™ãqWéñœÓ=Õ"ñGŠ^åµ¶Í–žï¶9µ*gÂ,\óNF@ÍŒ™­Å•£¯ì­úÚhmzA)E0žRéK«°Ïçr¾þäåÏ¿&óójÂûy~S ü¼§_^7ÄS8$ˆ‹4_± žöö„*×@;Í“2ü&wýuFóˆÒHfl3t"~hæ÷Dç.™ •ñ™¹8Ç÷ãS=—à©ß1ùLЩӜ6ÜÐiŒñ´º/Kl%!‹6«dÙ.K/¥¸Ëz/{ÜE?åádúõ%œ†ÑÁ4ð"º,J¡Š0¬ZÞàI%Tˆ5”}"Ü ‚g=޹Ìc\yD&w°J7ÓîY£¼ÂsqC؉é-^8 Tû¡~%¡É`’<_òÈíê{„„‰®H!€SM?Ê;¹f§7zÅ´7¾à'è‚æ™!h¼ô~1{Ü.Yà‚ø5‚*wé¹9±öøÕ>3Æ gq ”eõà3ÛØèàвŒÊÒõþo¨×—([»T}§¤ž‡ýÈïÜ­Ááð“Où­§JN1s‘šŸøÅV\' Û²•Ö¬ (d Â`ùƒØÎ¡i%E…7f¢ì_zú\?àà½aH=ðf3àçŽÈY¨R]©±•ÌþÄ]Ø ’3+ änÆ~ýó™þTXK”Šc¶ù Üg½¶·ûÖ(‡+>Éô¤#8ßnp6ÿQ‡þ˜4® î6á¬+”Ê/&³€»;Lú­ÈþhÀKοhríôå“ÝÏøjZ‹|ÂC¶ÜÕŒpX¯X_G8êŠÑ6=Ü ß>È^È’º}½ÂÍYVj]]ê½Ó:âoâ {˨>7¿^i $1`B½TlÐý¦¸P©¡çú"ÝÔßïGw¤j)Œ‚hç2ê±&DIÔ²0L¤”l|Œu˜©Ä¿ò8£›™ïï}¸§òåq HÜ^ƒT^$SNAà‹r™µKñ;b»Ž yé‚Óht›Ë¯FVˆÃO;Yÿ-‚–«qÓå¹I⬢þ9ê•í¨@¥µ9?]%â wYlYgd]…6l¯tñx¯$i+ªžêj']·¨x‹k/¤½G8è#^3š­iÔ~ŠÀ.¶ÆXs„‘vHÚ¡ÙÇÒªßáe+ˆ’È’Ü âÉŸ ºáv?¡0cÓ)Š<Ú›·©P <\(ÂpƶakLÎn(ÛÍ:©xüɲ÷vwstCÀ½©äq jdÅè“îÂke¾°:¾ YFÙÞ¸ÔhH–îˆçÄ °&>¡ÅÔÌ*Lô¾pVy~ð˜@¨¬¦¨S5‰ŠÀ\ÄC= 1l¿Õ)†ÛÀÆw>ã´OõîwÇ¡Òjx$oÞ^¤>Yƒs±¿j-”8âµ}IléX¯w‚PçòŠñÁu‘dúÌl$éñÖ`MèÓö1Œþú-• §Š3%*?üj'u>¤«qk¢£]FìÍ(aÂW²å—wÅÌì6T«j©’>ÝÈÌic„—7 a]]û%Ld!Õ¾6拃ôù#¬!kÚÙL#ä",žìº›zÏ⨇¥ ½“óç$8¹=–ýédÁµl[^)cV=˜ Å'íy¥¢>zTy,-ò\þa;Šr5¼hŠ §¨‹UçÚ®Ó¥-$²lã¼›úPø«_úao•×£íÊWƺTfîÕŠªŠ¦ƒ\U÷%•\©Yvp L9iLD.W#,ÕŽ™ÔE¶mº*_™÷û FN¦rÇ÷(Ũ¼ Юä[Jàw¡›ã˜ˆ+m¬”Òø‚g„FX?%*ò¡³ICjY[k_èl>Rã=ÑðmÄ™M`X†º‡hŒfe´ÔúÊvÙ’”w]zß:LÆ¿o~àžAŹ$ »5œ g«nì×ô­Åß¹Xã¯|bÊŽæ¶¼ø-b­ëÊüº‚ükñ¸Ÿ²ò¤‚|8ʯ¹ ´®â“¤ŠPôüáTèZ]ÖÒÒñC\.e±_˜Ø«ÿÏDÝE´îJf}$&î&$i5KÓé‚y˜ªÙº4d±WÕÍ•AŒL6‚µeñ4‚›«.ÖôY°åüÕdUÄïÉKÎ&½© hG¾Qƒ~UøÆ¯ý•$zš¼¼üÉ©›1+jÖ§zˆ˜ÕÞ5P#Âí)ÎÁK†òŽ‹ÔYßi&:9ÿÄÜï/JÍžÍS>T˜,.ÚgåcIH ¤®Ÿt½å²O»ëL‘DT'<Áì èl§y™‘ÚyâŸðgö®÷ãlËêXi熿ßz@"”„Ŭ$EùžÇÞ$CºóÏô¸Ã¨Gd<íPý ûˆÌd®®ÞÓeMI.de/XQoÞëO˜7o-.z†IY$QëlFùær4i4WQǹáÛ–…M’]ÜsÑ£W}m§­cîLí±Øêqb°Èýg*ûôŸ6J{…L,0Vê`*>ƒd(©¡ºpnw4–æ"aåèˆVNÙ÷¬dÓ6ýYÞN*ùäÊ¿x„Á[Î_%;V­~±YÿAìcÜýD Ÿš¬ >ÃÌyŠŸ‘õ{Æ*m>¢V1:›<9»åE†¡è.¾©2Ü”tAz4Ó(;ý<$Å•’{²Þ'½ÕàªåUñŠø6àb‚á÷É.ñ¬ÎÍJ?j¿è’ÚK©mKpá7¦ÈUéðóñÚÞÙ7Ù ‘p±ƒ þ5['ð©4‘3F”YÖå¡í˜mЕwmXÃ~ýqgVì3ÿOKö3·È’c"±“Wu|sÿxÝûŸ¥bŽÕ)§Íº£ÞËξäxçã‰ÔHÊÕû²³Ô<6ƒÚq+ÃAã K˜Gщí|å¹®qŒ¶1Ž¥‚LËß­2€Jˆ/ýŽözî“…lÈFá^óN¤vÚÔ²Â{¬n•ý nH†‰Ó™Îl×Ër—SiÂW7v?& 2âŲòÅ3Í^“Y³Á½ö _æA;…ê‘êÓÌç8Ÿw¼£C§§m SÊŸµ€Ÿ8.i•ÙK½{œ­®‚ÔO ·àDÙô´3{ÇÄ?l«+àvg*‚ö]KùÎ&AŒ>÷ 4ñ]§_LÖá¬6Z„¨¦yÖI1°;õ ™š ŠÄ$3ïc{m¹bC,Êæ{ÝüÈlIþ&–Äê»;ŸF¨’Ô§4œÓY1«†Z8‡²íçÿ-Ãd§Ü“B|£U„h ?Ðùm¥Á¶Ä:¸ÐT#Å Á(Îi¬ÐÉ»c9ž:œ’—»±Mà>½ ½ü Òe¦æ%¿‡ µÓ”ý±ƒ ùœ÷F'|¾$â®óèTV­? }Kç÷64—qBPÒ¶u1T1ùÃP¥‘nFž…ziÎ —órIL'{õÛŠäÉ‘òŒü+‚éø›»µÓÉÍ=7´±Í°°Õ7vã*/áýù„OŠ¿~Á6 Ÿ…s³”I¥W=«æÚȥͦŸWÚ 9ü€»ÆÙ†È~Õþ=†ÜÄÐ ¾<]gÞYƒö¨+´™Æ ¢k·[þó݃éG©&ãÝþGþ"˜Ã5­²ÎÁ05aéY´é±†.„_ϯÂvö©xcò€5+$¹˜=n. –,û®üVÜwhaPÔŠ²@ ‹º1loârŸŠ¬b¨aÈù…ÎÊtzÏX¶Þf*ÁW³¾ÊW®å<}(ÕkÕ%·ŸÕfHO±Îj%¢iÍ=Ȭz,Æ Šcë7izŸ½ð«Œ+ó€çõP|3bÙP{ÂÙêû‘k~¾OãÆP(“zRó%znp.ï]²Ê‰*û™ð‚H×ÚG‰ÊsÁJtx]»>ù­i;µ'+…Ë2¿*ô©’Hd—ݘ1¢v‡šþ7^3XA¤E¾¨ÇNcÿ¢.ÿ^zÎŒˆ¦ºŽv-‰}luågþ¸¶;%ž‡‚…·¼2+±ÂU"<7݆ëGgì㥘;›¹-BÆœ³’£êùŸd D{#¤rbò_{8|fâ÷ˆézkõ7Ø|‡À‘¹êág”QopPI ر·lƒŒ»Ô';z ¿FU:‰@8®«_ëb™ç>¹s*Å8 Á5ʹ’×Ô»ÅúÌ•à¥Ø5ÞðŠßkÍËS‰ÔV ñÌ7‹ãßf…—´ûš«"G8Þàù#ÞQ î_Êa¤d𪎖¯8+P-¼¬Ë Auö}ˆ¢ìÅ©Hdõ»Wö½½·l?è¿~è0•‡Ø°¦Ò& ÏMÄ®L7Ú V¸aÁ{ÆQòkŠ¿î±!]mù#",Ž¿yËèXq”UB²ðA&ßÿ™ë€ÑZÆ Ý­à'I›1]7š æ×øÇn·.&3;2ˆyw¥¨­øT7ÆÅ¡ GõÇ• ÜCWPÚŒOy$-&ÃTÒ}‘ßD–aîºçV­‰9¦C¡#Ö–I¬yò†ö(÷ý~–«Ô=J â}#ž=F²÷Å)é9†|êzõû5<Õ²—ršem? œ¬-åTÍô݈nüèïE;2]uLKTš&gÁWæiDš h½q Î"UôJœoϸ[rC ¾}¼?z‰^½òÐ7Ö~SBWoº(É?óY¿C§‰Šaz ÒñîÈ£3`–áø1òï„Ó#<ÀÙˇù}Óňгôvõ­æŠ¢Å;m „Üí?ÊÜ?L!<~e%OXÅÒtºž½_ÕÖ­›g»Ç9÷1^ñˆ° I¸2 Aî(‹Åº4IfMÖEj‹”uu” ¡Yy}#œ½ÊŒ'|ëWE;?Ùbx{¬‘ßCFen3¹³®ÚRådsCšdið ‚qõ4)…BJ ó)Ydm‘¬¨2÷ûhñ•OGÏ]"wʺüúÚÁ.3™2=zäš‹‹~ÑzµRf¥öû¬EѺD8¿@÷Y>¥¡#¸(¦ ˆ‡Iëõ“:-·zÚÄž©ÅœQÜP a}·s=Úí.1øÑá²ücrÊ) ®ˆ- šËå¬E&K¯êaÈÉ”PûjŒì²[>YÌ¡á#ŽkkA1úl&À0&u,`Ħ€5G wwõˆ§6‡Ø­Õ¯¤ó{Æ®]a©D.õÓE›8`¬£ùÕʳ£9»¯FÙ¨Õ€ ØKù!ìT¥ÿçÅÿ&(„j:õ&—ùÇüÝ.r°«ŒÊ`6LdJ Õâb+{®":ý•åR}òG>,@×éê#§…“—2!ÇŸ‡|“Ì_,ˆjä05=”Ll©Yr¹Ã=2áÆïGó[Usw9w"µX—üŽ*Ê«„†x"ÍaÏ•7¤îq¥]«QÄPj·l ãÖŸ5TCÒµåÎ ~¾îôZ/Þõ–rV]P¹}ØìØô‘uªíó¡Iµ øWv+Mͧž–;ýš¤Œ¶¾6ÓÎ[ÍjªÁ}ËtznB“ëäú|õ“àLücl[§/!Oj!‹}L$—Æ‚¶d–UÔ°[ž—Á.”Ùc{ŸÜ¶`|º*§Y!ö’QOŒ!ûVÙOÅÉÎÜ5Ö––Š|_P÷ê‚LN •Q¥&!TÞY4ü!ýF*IÐ瀟7êòrkb;øyGOŒcXn|ߺ8‚Êp(ƒsÊÒEaRî¤%‰^ß*JEL™Mðñ9O9QBC`¡cáý†eƒb!¥ù ÉF ÎéWÌÏŸQ=êy¤’ºFÓv,¥ø÷Ú’>TGZ®‰·CžaÓI>é7TmËi6¬Ùö†ùz7úþï[SnÐVrö‘L[^Û]ñY£'7ñµ' wÂâY œ·ïÎ!«(“deþÀ¦åBÚÖ¦¿£[µcÑôžÐvW/RA•,GÍãIy.s«47ñZ €ÞK´œ{ÁƦüø+§¹wmüè •Ï‰{Í/ž‰ÎÄ6Ž—F—gq (±<IÁ%Z3j¢„€-»÷ÚU˜ «‰®Ј¥Ü4ŸQ¼RŠ/¸ÝûÔÖ×GöÉ.ýÅHë#9¬.íØ<…ÌÊ×ú²åz4Òñ !ÁŒ'‘䳟7=ÊڀÕL†Ýª î–èÆ¹‹S7u‰JsjjzºþÍï_$ð¡§, ô³N)˜õHX#©*>B†—³é1ÖÞ Æ’’âq…zμþ “ʆÄ9xôê!M&µÃsDÅéëDµ„!O ŒX£qøq{RqÀK1…”ð Al²NÁä…Žé-ì!±ký'y®ýÏ~@шî³¥Žf4.@(zžñPOçXéaì5#zÆþÕ]±oJ¦¹=é w«Ä¶Ã… ±‘iIuÕÆ¡Ö-2+)ü¹¸KVµ?1 a qsç$o •¶új£b•—ØTÉôj󂛪—hÝ+Ë3HŸšµŒ 1öGfÐ#<ºOÇ®Im\nÚÇf£‹;"‚Ýv7þØ™Àùv‘—¡E‰²¦¶XÕkðkÛ}oK¼¤× KѦo+ñ]¸¿ª?ÅÃîÎ/»V9Å0•´ ÊA¢€†ÁÒ*£†¹·-ñ}ƒgëvÐ`묢ù‹áÔŽÂö nß[& ³ÿ"%F†ÏÓUÒÆN8ÊÍ_à£OÅ–÷زh¯Yõý¿ä2!‡&äãŸFù þ6æ‘)2ÔÁ¢!Z`×áé^æ^nÓuPÐXù®?SÇMxv?¸žýØÚa_Z³Fب{ýxÖt(ü©‡UÊ9”ï¥p7ÑÙ"÷·@êít.öÑ-´È=ˆGsæ;^Ù8Z‘ý@XCÖƒŠš–—ä+ƒòÕhKÞÝî­Vv4¬BR+{cÊà‰²<£äÒɃcz³¦Éc^8œuÑ¿¾>•ˆAn®Ú ­21”þ»_kýv%âbÒZ³% lÔµ ãQj Îhë÷㪼ÔçCrv"Ç˚ƅ&lÇ/C‡$ŸMnÐkxhĬ®~SÄ=T.\?Ì';À=•GrÅ=&&^´_`´¹Iˆ‹:¸d|9ø>ÑÃ!ЯÔâߎ”›¿Ü5¨Ø)7µ2þ(-‹[‰éŸÅ@tùóïó¦§rÏ!V%…ßbãè÷U­W´¡Nb-óuR±’*!?V¬¥Ô@¨Ö˜55ú¾_[Ÿ†ð#´Süê#µ!Á7¥PýµçÖܳ†÷4~[ÊN˜ôÝüT°¾Rd©üÉyp\3~õºš&˺†ý-ÖÖÕŸç˜áj0¿6E§ÞÛ"t‰Faa…Ž«‡ëi,m7}^©z‚]‹ WA½\ÒO¼Ü´‰¹Œ†¥½„˜ºw’ê.‰'ÂcNX‹Ì]¡_B±%ÈQ.£€¨£·+¬§ài­ÍÜiÝD–¢²^]B!ø”™ ![ A<]\jfø˜ÁÞþj÷™aî¶ÙÇ1e-ë_°„C²Ñ÷yaë»Êi=ð÷Å8ØÕ—p€q›s‘rëÁW»lw­ÇnLÔ:îí#.óé`Öt9˜þÞOÇa~>À2é¨ÅÀßÔVWGí3ÍØ‡N3C¡ðQý¸B)¤]áõ–Æ•ÞèÊ£Ê1;f˜´ª^¿×ðz&þ…;ˆ¼!þý·Ý%ÿ¹_»#ÔècÇPP¤Ñ>•ôÁ‚‘¼œìOK¯çWe):¶µnFö»ýËl+8ÜNŸ`ü¤ž6WY· )3ç~køzezU§Õ9×_çÏû ŠŒfaèè€K;?_D3Xm¢SmFàóÂyúûõÊQkj{ò\ $/.a¹@Äg¥›ýÌß–f-º…V‹ËÏ¥jÏÆðõ0c9)ÛgÈkõ¼iÿ-tŸoåŠmFD°'ˆ˜R]Ïs ŽFSdr{ù°gld5üsl»ü ¥J’ò"ÚüS#HM­:w—‡|\c‘šÆñw0ïè k«ÑÚ”Û/4[¬ÕÜ$tTÞïvǘ†»Gw-Ó1¦².ZÊ5ÓG¶€X§==7æðŸ Q3hî-9ÈnÅ>‘…³Ø­4º¶¡ÂÛEÐÛjUÝ: <׫œ¾8ºŽ_Óμb©·8 ˜º Qb5“Ô(í± »õÑ_ßÞd?rÅ™ï“6E}JJêÛw¢oé8{QÑ®2#;*]ÓIäÄÞCUè¡LDž­î^$geÆ'dˆÊ8CqNŠpɸƑËä²_|iE0t÷W¢#M§¾àˆB;VïûVëedÀ>ëMãcÊ„¸:X~©ã èš’››m~™éþìC2i¼wyùqï¡ÝÅ‹’'¹ïÜÐ}¢6Ú[uð¹tµåܺ¤žÐª«ð Ç7­ãH /lÃ~R–ô›hÒ4§×™vÐY‡'H¶5ìÊêp_¤³9œ†ÒÁ1˜~§IßÍvrT&Ʋ‡ÚЮC"Ï{Tx¿øe;?’ºŸŒH™V ¤2Õ$):F> ›|OUµ"dÇ,ñÅ4Š˜oµ§b•Ä{€æíá¶GâãÓ/?†™½¡ø9>SÜ/IÜÝ©G5o¦_çûØù2³÷éF £K!ܪõ³°¨5VoUš›ÈT½‚é44<2#X­ÍSæ;´#¤g =ÜÄ9J($ lxGœ½ôî2‹‹ÁĬ¥®ÇÛ©±±vß4ÛâgÛ½6tJæáVÅd N ÖY|Ç5wöžÖ ¦4úÂÛ}‰œa­ÑB7Næ(r;û; ÈÑ«£Ó¾e—ž…'”‚cb“£Úë×…•¦¤žÌ? ¾zK[.íFƳ­HdòØ’‹VVôBè¦ÈñÌ»]ú[¬?ÂKx…§q]_Iõ‹¼8Ýf+·_äe® „ê,<E¿4fôö×,íh?iëÿ‹¹h6Ñßš«¼ÿ}Á·Y½ýá§à…&ø¶.BKèJöýÙŽ^nŽd½G!jcϳ½B$$vt^ºsªnNeÚŠˆ0Q3ð4G Ÿ]·./¡%¿FœG ´ÇÆìã`¸¸Ã% ÎíÈ‘;já-¢}à™^𹔫$`££êõXÙþÔ}m+Þí´MÒ܉kSºÀ‘Pߪôü:ªáœc+4¶›}_m³éÛxR.ØæŠÂ›&ÿa†"${?ÿ‡çºx–7¥4ÅÈÿíoIt endstream endobj 775 0 obj << /Type /ObjStm /N 100 /First 896 /Length 4040 /Filter /FlateDecode >> stream xÚíZÛrÛ8}÷WðqR[4®US[•Ëd’Ím6“I²›Êƒl3‰6²å‘ä¹}ýöÙ4(RФöi+Å €î>}eŸªº ¡®¬ã›®b⛩4Y¾S¥ú¶2ÆV>¥ÊøÀýP‘ÃóTYoªëÊÕî(_9ËÏ£©¼ÁeÈr/]=ñÝW©fq1TÉi¾Ç*%¶"êJ×”ŽÛ¢µŽUHüDÏ –f-œØ4§Ñ°•NžWñJckŸ|eä&6³ÎËcEÞR뺢ÂQ¬Me5›k[YØk¶½f#c„ól*£ŠšÑ §¦È 怞ÉðÌ+5v×éH[ã`T‚,žÃ¨õÌ$`ÙÍ£s €m‹x$²8Í줚™Ì„f‘†%éȰ¢D<Ïñh²Üð`Ëa¥fú<,gq)0‘,)±-•ç©ëymbÒ”®kFã ÑYÖYk~nÙàÚ˜Xñ4æ"¦œÚtœQí÷1S€ÞKÍ—²ÑʰÁÙø+ÙˆæÚl”S±±;—£yÆjšòג룙éà®7—Å“××›kÌÌ™ëÙàb= öÆ1pm·Ç㻣·¾Æ–ýÿºáÅÌ9‡ƒOÜŽñªÍ.Œ 㸣°È˜\D)€ÚÏE‡ºYX6®º}Ê“õrÀ\<19=Mÿøf§Ç\ä\¯5òÑ ®ÔAü òÜNv‰æsW?ŸeôW>Sp•€2\âÊ}‚üŠ~^Rùy6 Èsùy^×Íë×um‘çb.œ„ÈÞЯ۪v\Öq;tk\v†ÿ‡ÄÿþjÿÝ|Å`ïquï…×¹$l|~si/–)òEÛÈLåäð…l9~“ì/°EuË“¹¡C—c­Ëˆù>79Œ”røu¢•¬ÖæR=¤+¿åØþ^>ï×tí>9É$¯eÅØ09ÈLÉñ’®vr¼—/V|6Çóë5¶#;U}µ%9…ò{D¬AæßtûÏ2ä‚É\¥äÒ‘ÅyÅéÁPïÌ][¶NÖçm,‚¥ßîn]¹‹9Åw»X:»ÜË`èmïÚa·ØXrRdZð6~Ö°ºØ ™‘¯Ù>èJp—{˜eÂV×ên¿¤÷.#0¹½—°zx…¾àsF+7ÿ+‹{ï@EqÇf$Îz²9kûNû’Ú> _;¨áâlr—+Ï}øâð#º»2?źlï?ïŠw"œ¿ï7›“õâb»Z·çñgó3ùçÓ‡¿Ü{õ·{OŸ>Jü|9ÿ°©l;án~3ºÍ§ôÛˆ9Ÿ’‚ã]Rw6'ù½(ñÌ{ó‹‡ÍâÃG¼&¿4íØmÁGÛùrqrçüòá'üàçmsöª ÜzÓ­²¤YÈÇùÇýïÔ²Ùlnµú,xŸöËw¯ÏÁyóæõƒ;¯þölqv|¹yº:rûEóár˜6 ŒxŸðkˆÖ.ãJ\Î…— C\µ ²º@e|‰êŽº«î©ûêõ@ý¨ªGêê±z¢žªgê¹úIýS½P?«—êõJ½VoÔ¿Ô\ÍÏ.šõf~~ªæ›“Åb»Xž6ÜÜ6ëÅæ“:VÇó“O›å|ó‘[ku¼žŸ4Ëæý¶m­aEn~j¶ýcn·'êdµ\óÿggsuªNWË% iT¶^5¿^Ηê½z¿ø­Qïù­Y}PÖÍœu«ê㟛sµPÿQŸÔ2ï˜:Sçê|qÞ¨•Zñÿê¯ÎYqnµjHÄ}±:UËËúUýz¹Ú6§Ç˾ÑNν¶¹Vµiέћæ7V¿Yü¡Zø[µý¸nµý}¥.Õåù)Óv²Z7ê7õ»úCý©þR5ëUéU±Ö7ñªÇ_ß{9òªçÇËÅ´gñkuö,üÊüžÅÚûíõ­'ìC­ÿÌÙ+Nx7yÏxõÌ;´âù5³¹ÝÃÔ$º I÷?¿óôÇŽ¤ŸçLÒÝÕòtOèªnSP8¸hØtEgÒ’¢Üí)2z_ðé2ú™aô]ÅÞ£½Qײ׺Øi à (8]Nø|ëÖ#Ç=ä®=ó#u7!ÿé/ï< ï±WÞÆ¯ûøå¼JŽ òõ|=$Ÿö]Á½¡ÝÌîvÌ_ñ.|ïd ¾ë½Ÿ ÿÝ—X2ó-áÍS>¤8Ü„âWÏ^ÿòðÙ.ÅàcÍ4ãÿ:~ ÍEˆq/ÑÇ™»•Z!Þ¨zþðæõîu_¬Îž­Ò“Ûø‘tBÏ ?Ñâø—üàhPŽè^!¬ÓÞ(®‹<çõГî_+‚‹Ø-#÷:qÛl¶ ŽþaÔŽãu"ZõêÉËGÏïÿòz‡çë³' ÏÆ<‡8àÙé'ùk¬uõçŽ*S„Ë1åø«Ž'«‹?Ûç§§n—Ÿ=ƒô[z~yvÌ!¿øpþÙ“H›0F‡<óxÑ7*²wÿûÑë7žs yàðz×{|xºÅ~”‡\€/òµz\l%Pá1× Ðƒ±y($Ÿ u¢xþp~²:]œ`ˆ‹÷ïvü-è­É~¶¬È^ùBáE]]’“ëÕ¡¼pŠIëOêù”Ûz{給Ög`{Æ 0-¬ÌHæ&»V†Ý–©ß/Ìð6h$@$•qB¸ù»G•ô0|¯^4Š@æŠVx8¿TŽŸ»•ûêäyEî—¡OÞy¸(„ÑY±_¥‘wã@bŸ½<Þæ.²³Þošü©Ý·ßAØåO+òŸ ,Ö›-<¼òœ*ŸÌ‹ÎëÅéö#þ¢¸§ÎR¾÷]u× ³kÙ mã•ɶsÅÙóç7¶ìàûήuv×:ëJëp~ï­Óߺ½/»–ùoi`™.,‹ß²½§ð]Ëâ®ef¯aô- ;xvÝ1N¼>ÅÒ:üŒÓ[g¾…u‡Ž»Æ™Ïx[IÿÆ:«ígn+ªko[ø¶}î4°kß( ¬ìli »ŽøÖbƒ-.qšè?˜À70yõãÅ)—ØÃžÝ>ßt[œñyQ{·í÷Úçþ»/Ñ [ã*Ó}B€°òݵߘVve}±[;Mëô|oe¶á»—{úb–Znœ‰í½µ·òí´Ê›V§wŸåÊíÓáEf›+ùŽI>Ûé>ê8$Û¤~kcÇ{Ço·ø¤/ëh¿œÙ‘õür»äƒÌ¦óĪ 8">ôËVŸ8eå‚#UK-Ÿ_+ßùr±[÷Óºù­òvàªíR×/5‡–vÙï>8ñqBŽ9.ã|)gÂz9öSÊ©'äP/§> ÇÆBNgÜ@Ží©µ‡¨µ¶”c&äô<ÛC¡'V`L pùÚŒôBxë Kd‹‚AO¬„žì@°è ÏÁ¡'<Þ˜çÐ*öSŠ3¨ÞröÒ1¢ˆð;qhÞ ëÖë1ÑžGÇz# jQ ĈZ F€Ò1Â^-;³½£àÉÒóè„b€2‚ñãa(Ó÷ÊÄ{lP‚½ÆŽõ¦[íèXo(#öÍĈF &@41¢‘ J°¾­ÓÅžGGŠsZ“M$´%±/CX?¼Ýë ÷€—‚ô€—FŽ•eçѱÚx)‰à•ÔOHïd{ÅÀk{£€Pò5!sù‘ceá«E!Éé„äM’¡ ¥€¬ Dö'©?„|K6J/›;ò«,=N(&ÉË„¬N’˜ É•$’6I:&djrb0R5µÙv¨ØßjGÇŠ‘ÐIr2!§’$eB¾&ɇ„„M’¥¹’$  ŒÚH(†ô<:¡¨‚ B(QT(^4Áë(Dì)y±3)ŒCxë%À½ÀJËž¦lao,”*B¨daHY8Çj-PHÙ!Ôw’²ÃÞ‹ž€·À$E„=ñAœ(ú‘^›=ËNy–Â(-FAh3&Aˆ‚ÄBdJ™Òxmv,7åX ’@D §$@%ˆ‚JI ¢ZS’ýAµ¦ö—Ÿb—ËM9–ö%ˆOR„±Ûº÷9x+™P^­Tdò=3Ö›ËOœtÈ–DïЈޣ'q°R„ÉGôdƒp0°ã"œ¥çѱbœúø”àEé¶R‘ Û's¬aÂQÀŽ‹0„çÁ µÀ¤{½À$5˜p°Rƒ '+5Q¥ƒLŒÙÀ1ÜkªöSÌ(!j¿•‚L¨ýVj0‡Í­ü½t׃½Rƒ ';®ÁYzP PRƒ‘tŸFPû­é{%™Pû­dJÙÞqmˆÙ±¤öÿ^€b endstream endobj 941 0 obj << /Author()/Title()/Subject()/Creator(LaTeX with hyperref package)/Producer(pdfTeX-1.40.14)/Keywords() /CreationDate (D:20150213064426-08'00') /ModDate (D:20150213064426-08'00') /Trapped /False /PTEX.Fullbanner (This is pdfTeX, Version 3.1415926-2.5-1.40.14 (TeX Live 2013/Debian) kpathsea version 6.1.1) >> endobj 848 0 obj << /Type /ObjStm /N 93 /First 835 /Length 3709 /Filter /FlateDecode >> stream xÚ}ZKo¹¼ëWÌÑ:È>úAÀ0 ]+‚Yr$y÷°Øƒ“}!vù÷aõ°FÒr†È!§«‹.6çój˺xmKÊý¯¬K.­ÿMKïóR õ²HÃߺXÂsY<úéÒmI«¯'Þ_ê†`©[,9-®ë’jE!-I4÷B^’: eI¾–^¨KjOdÉkEA—œM¶äìùÄÕ—\£s[²äº¸ugµvO,-Ù…¼dwí…²”uE¡.%eëYJ®x¢K)Š‚-¥ºœ¸ùR4:·¥Xî_—â°ì}:wwëêxR–šÑÙëRKÆYjκT‰Î¶Tu=q÷¥úÚѽ-µÁr[YáFK‹$tny‘ÜßðÖǸ¢s«‹|n²ˆÖ>ÜM1EÁéVO¼ù¢ktn‹‚`냮¹wnkZ´( yéo·^(‹êŠ'uQ‹Î²¨w7Zg¢˜ÁÖmÙjí¤õ~–º›mm‹•þFKëbµô')-¦}Á´”Ãð·Ôç#õZK}>rŸ‚–ú@ÔÔ-÷ÿ}ytË £ŸêIÃÂñ°ÓÀ¿¿…%×:¹ÖJîM¶úrh¹ôÿÀê3ÝJéí}¬[íæ1Ž­vÞ LÄËIË›=÷§ÖsŒ—noÂ…Vúª[û?XC K_wkj@^Ê‚´—J¯·‚E]S“â(²/ú´J_Ê­®(õ•ùúõÉ«ëO¿~þºüô¢´zº`¬Öåvé5A-±¦¨eÖ µÂZCÍ·Z}¹žö½‚ÊÏ'¯®¾üúåÛn<>yóæ nÅ fãõu…±ÆZ굺²–QK¬Ô2kp¾–?ãÂx4À‚`­|«°‚}š£¶{º•tœ÷VN£q†M XI0 `%!ÁJB‚ îJa îJpSðí­Àà$d˜ÀIÈ0“a'z˜á¯nÛŒk§[댛1kJŠ•3h()fx¨¤˜á“r~úk=ÞN¸0ŽÆ¶Ào%Ý¿•tK¸Dº%\"ÂQW²/u›qKŒso='#ÃNF†£ndXÀÐȰ‚!_ú­&3®žn­3.–b5RÄ$Ö}Waøª‘" ê>ÁóSáýæÆ`XÖ`PtR¬ è¤XAÑIQ@‘$ðÞuÆ…%G K@ÑIQ@ÑIQ@ÑIQ@±‘¢€bãH ¼oy–XY½õ) (6RTPd“‚b#EÅÆ RxßlÆõÓ­uÆUPl¤¨ ØHQ;EYIQ5RTC㮎Ú)a=Z€^!E޲¢‰-¡FŠ–QãYAm•0­3®U¼BŠЉ )(&R4PLœƒ÷iŽ•’Ô[g`E’rPL{ ):(&RtPLœ ‡÷iŽ•1Á~$I†™  3:f2t0ÌdØà.]jp°Ì;ØC’ÚÑNj`Au¯j)»møT8Ý8HáXà eÆ8—yE·ØIí`œ% c~·³à nœÖóºWàîœ}‡ñhq!²*gˆ¬R9±R’«TE…äªîÀð~°­À H!TH®R’«BÄÂÌ£\eR¬Ð;ÕyœazçØåÕÍwçW»£õèÝõÝýùÕž>rìêÝ÷×wpêQß÷7o?^=ŒMyôÂÍ·?¼»øñ4~’±?þpy÷·«³»>ÜÜÞ?ò#RO||öíCzwÞÝN(òàÇÜáìû›÷ÎïÑÏþo¿ë›Û÷ç1>úÐïþöÝååÅ6ä‰G3ÿã»ë·7?> Ò?>ýëóËÞ#îGøÊÄx{ŽÉû¶í ¶%sí ö&s‚íIß …ñ`{ÒwiÑ'OúF)6ÄuïõŒcñƒ{l0><‡¸*}Jétß™°muäKóÊÙ1÷^Çnmiøã±ˆTü‰‘Žóîy{ùÌ7B[Ÿ8òU‹ôœ½ŽÃ}·>ö+îŠC†"¦G"4>îð(™ DêñX•ӽϱCˆ¨O†åË—/Ý%&@ß>ýý—XÉ™'ªí Öš–CHœøÙiÇüë—ö>æÜGÔðAÔGÞã#¨zžK1ë:YûÞÇ~õ±¿}è°î³úæ¸>Ê?X ›#ÔùÑ>6¼èècKy™ËrWJ™m¿†xú8AøÈ/|d>ç%Î`Eg?‡öúÈ#|¨©!õ¡¡>ßœûóïe†É‘ øH|$>.È|œç]ä™ßÂÔyŠÆÑÞ‡ˆúØ—>V”Ó¹ës?G°y8Ç©ÝÇyÝÇH|Ä6gmW;þüä»m¿Æ¯B|œ©}œ¦}œ£Ýžû$÷ø»É°9È>¶˜»1·b>îÃÜÚñ7‘yÒljÝÇm—°éã†ËÇÝ–Ï·ZÛµô“ëCÚ^Cºã¹ÅññmÇ[zæjPgæ#¨ùˆ°>´ÊÇ%˜O5>ÙngždÑ´9üßeÚø"ÓÆ­y±»Í?{ò´àÛ¸kã*±«®6.¹Ú¸tjó×”-I98cË㥻†6’ø6òÞ6RÅ6g]LJ¾IXˆ3Øëm6ÛËm„å6Âra¹åv¼×VR‡‰6Âra¹°Üæ0Û zŽõßmd8mþ-ÃzôöÛÏ_{cÛ8Þÿ÷ÏË«ï?}ûôËïÿ:yõ¡ø×Å·©8yuóŸo¿|ù-žlo ím[ôßú¿ÿýŸŸ_}üú™ãáÕ§¿þåëëׯ®ÿóëןÖ^øð"¾y“¢”{)G jýæMÙÛëÞ.Q*½¤Qª½dQ’^ò(i/µ(lo0Žâ†ÓPÜ€úY°—Px²A%`¥ ,-mp xiL@LdfÚ@Pó ؼÁ&àæ 77o¸¸yPŒ1Øp3p󆛛7Ü Ü¼áfàþÜgíÕÍŸ;ÿÇ·/¿ÿ¶lsù?‘“Þ endstream endobj 942 0 obj << /Type /XRef /Index [0 943] /Size 943 /W [1 3 1] /Root 940 0 R /Info 941 0 R /ID [<3BC38E630FECCF656593190A9085882A> <3BC38E630FECCF656593190A9085882A>] /Length 2040 /Filter /FlateDecode >> stream xÚ%Ø7¬$I€ñ®Ù}»oÍ[ï½½õÞÖzïM­÷þ$@•Àˆ¸„$$P@§ 9'‘ $ÈH€ùýI>UÕë7ÓÓß×=Ý3 ÃðßÑ0Œ†4ÌÿÞ`´m4L›yÕ(ÁnY»b4 ¦C±vÙhfÀ k—ŒfÂä}ƒµ‹¦³`¶µ—Ö.˜Î¹ã·Ÿœcí¼é̳¶ÞÚ9Óù°ÀÚ&kgM¢ñZ}eíŒébX2¿Èik§M—²ñZ>`í”érXaí¤µ“¦+aÕx­MX;aºÖX[n-›®…uÖ6Z;nºâ£Îƒc¦al†íiæÇ!Þ[á#ï„ý¦»`Çx»Ævñ‡½F{ Fû 6>á†#pbb×bŸãÃħŒÇ%XÉ8ÄqìCJØ á7ÄG×à:Ü€Û°; é?±»7í Ïévpú òfÃ:ØÈÛK¢N±°N8¦Ó­‡3bx wÒ0ñ$Þè܇ðÐvÛÁcxâ-#Âgi˜ý*þí%¼‚×ðÞÂ;xü›»ø»ø»ä»ä»ÐûŒ4œúEl²&Ó°ü+1•w¼EÝç”]cµÏ÷ Ý¾Û—€Nû2Pg_šì«`µ—ÚmDm_›†µ?÷]ZëZëZë ë ëQØ£mà0õ˜î„صxQ…u…uòºÂºÂºÂºÂºÂºÂúQ/W¿ÇÓ°åϱCZëZëZëZëZëZëZëZëZëZëZëZëZëZëZëZëZë7Ú~; »ÿotdÖ È¢Ë¢Ë¢?Etùôgª «OÒp°Ä DŠèŠèŠèŠèŠèŠèüÛøêøñ_]$'§Ã( ߯tÌ€™0 Ka" Wÿ¿É,ˆ+ÜÄum>ÄÕl!¸†M.†%ì6£°, wÎÇ«ÄÕç ÑjX™†{ߌ?¬‚‹°& ÷oÇÚZØ›a l… ^~;쀰 vÃØ û`?€xóCpŽÀQ8Ç!à 8 §à4œ³pÎÃx —Òðâ“ØñËp®Â5¸7à&Ü‚ÛpîB{pÀCxá <…èà9Äé%¼‚×ðÆe)öå]Þý;FïáC¾ñwÓjïkJ׿Óè j£N€"ª"ª"ªªK_b¨b¨b¨b¨b¨b¨ñ…&†ºÔT—ÁrE] ÄW1Ô5Àyue­ëýרM ƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒªƒzΕ?6¾†¯mˆ#©âz tPuPuPuPuPuPuPuPuPuPuPuPuPuPuPuPuPuPuPuPuPuPuPÙ¯a_“õ_?ØÓŒ`ø¢šš€0&ă90¦`̇°Ábˆ»–¥àÛoj9¸C™Z îK¦Vƒ»‘©µàdj=l€° 6ÃØ Á6Ø;`'ì‚ݰöÂ>ðu›2û™ýÌ~f?³ŸÝ<þÊÿñÃØ8CÜÈÎ3ç™óÌy柉ÏÄgâ³3¾¿ò÷K¯Òèiã¯ü_}S4ºÝîFw£»ÑÝènt7ºÝî¶Ð9ãH6¦ƒmq~³#^™øFw£»Å“Ým‹·\—†Ï[lÌycº1ݘnL7¦ÓéÆtcº1ÝÜœìóFrs²7'{£»ÑÝb'ént7m´ãÀt‹ugwã¼qÞ8oœ7ÎçóÆyã¼qÞ8oœ7ÎçóÆyã¼qÞ8oœ7ÎçóÆyã¼…s%6çy£»ÑÝènt7ºÝîFw£»ÑÝènÝŒ`L‡‰4úø/ñ×Ù03 ¿ÿQL'a,†9iøÃ§ñ‡¹0@8_qs÷ãKaÄ}Ý X « îôÇwsüG¼ÞøNÿ‹G1Z—Ò³1ZŸÒÓC1ÚÒ·¿£)ýì·1Ú”Ò¯¿£Í)ýíómI£ƒŸÅh+¸¿×áÄC\<ï߆;pâyÿ܇O^à1<§ð žCü$ÏûñþÞÀ[xï…2¤Ñ'Ïíd¡¢PQ¨(TOåeÌ …™â÷ƒâØ]Åcxa¡°PX(,¶ ……ÂBa¡°PX(,Š3¯¬…uà÷ˆâ±´xò/~Š(›a 8°…ßâ7”²v€çø² vƒGä²öÁ~ðËD9‡à0pT8*¾kËqÈpünQN_:Ê8 çà<\€‹p .ø Äâ ñ…øB|!¾_ˆ/Äâ ñ…øB|!¾_ˆ/Äâ ñ…øò2¾¾dlõ;W‡ÿ”GÐ! endstream endobj startxref 165191 %%EOF plr/doc/plr.sgml0000775000000000000000000016650312465736645012641 0ustar rootroot PL/R User's Guide - R Procedural Language 2003-2009 Joseph E Conway Overview PL/R is a loadable procedural language that enables you to write PostgreSQL functions and triggers in the R programming language. PL/R offers most (if not all) of the capabilities a function writer has in the R language. Commands are available to access the database via the PostgreSQL Server Programming Interface (SPI) and to raise messages via elog() . There is no way to access internals of the database backend. However the user is able to gain OS-level access under the permissions of the PostgreSQL user ID, as with a C function. Thus, any unprivileged database user should not be permitted to use this language. It must be installed as an untrusted procedural language so that only database superusers can create functions in it. The writer of a PL/R function must take care that the function cannot be used to do anything unwanted, since it will be able to do anything that could be done by a user logged in as the database administrator. An implementation restriction is that PL/R procedures cannot be used to create input/output functions for new data types. Installation Place source tar file in contrib in the PostgreSQL source tree and untar it. The shared object for the R call handler is built and installed in the PostgreSQL library directory via the following commands (starting from /path/to/postgresql_source/contrib): cd plr make make install As of PostgreSQL 8.0.0, PL/R can also be built without the PostgreSQL source tree. Untar PL/R whereever you prefer. The shared object for the R call handler is built and installed in the PostgreSQL library directory via the following commands (starting from /path/to/plr): cd plr USE_PGXS=1 make USE_PGXS=1 make install Win32 - adjust paths according to your own setup, and be sure to restart the PostgreSQL service after changing: In Windows environment: R_HOME=C:\Progra~1\R\R-2.5.0 Path=%PATH%;C:\Progra~1\R\R-2.5.0\bin In MSYS: export R_HOME=/c/progra~1/R/R-2.5.0 export PATH=$PATH:/c/progra~1/PostgreSQL/8.2/bin USE_PGXS=1 make USE_PGXS=1 make install You can use plr.sql (which is created in contrib/plr) to create the language and support functions in your database of choice: psql mydatabase < plr.sql Alternatively you can create the language manually using SQL commands: CREATE FUNCTION plr_call_handler() RETURNS LANGUAGE_HANDLER AS '$libdir/plr' LANGUAGE C; CREATE LANGUAGE plr HANDLER plr_call_handler; As of PostgreSQL 9.1 you can use the new CREATE EXTENSION command: CREATE EXTENSION plr; This is not only simple, it has the added advantage of tracking all PL/R installed objects as dependent on the extension, and therefore they can be removed just as easily if desired: DROP EXTENSION plr; If a language is installed into template1, all subsequently created databases will have the language installed automatically. In addition to the documentation, the plr.out.* files in plr/expected are a good source of usage examples. R headers are required. Download and install R prior to building PL/R. R must have been built with the --enable-R-shlib option when it was configured, in order for the libR shared object library to be available. Additionally, libR must be findable by your runtime linker. On Linux, this involves adding an entry in /etc/ld.so.conf for the location of libR (typically $R_HOME/bin or $R_HOME/lib), and then running ldconfig. Refer to man ldconfig or its equivalent for your system. R_HOME must be defined in the environment of the user under which PostgreSQL is started, before the postmaster is started. Otherwise PL/R will refuse to load. See plr_environ(), which allows examination of the environment available to the PostgreSQL postmaster process. Functions and Arguments To create a function in the PL/R language, use standard R syntax, but without the enclosing braces or function assignment. Instead of myfunc <- function(arguments) { function body }, the body of your PL/R function is just function body CREATE OR REPLACE FUNCTION funcname (argument-types) RETURNS return-type AS ' function body ' LANGUAGE 'plr'; The body of the function is simply a piece of R script. When the function is called, the argument values are passed as variables arg1 ... argN to the R script. The result is returned from the R code in the usual way. For example, a function returning the greater of two integer values could be defined as: CREATE OR REPLACE FUNCTION r_max (integer, integer) RETURNS integer AS ' if (arg1 > arg2) return(arg1) else return(arg2) ' LANGUAGE 'plr' STRICT; Starting with PostgreSQL 8.0, arguments may be explicitly named when creating a function. If an argument is explicitly named at function creation time, that name will be available to your R script in place of the usual argN variable. For example: CREATE OR REPLACE FUNCTION sd(vals float8[]) RETURNS float AS ' sd(vals) ' LANGUAGE 'plr' STRICT; Starting with PostgreSQL 8.4, a PL/R function may be declared to be a WINDOW. In this case, in addition to the usual argN (or named) variables, PL/R automatically creates several other arguments to your function. For each explicit argument, a corresponding variable called farg1 ... fargN is passed to the R script. These contain an R vector of all the values of the related argument for the moving WINDOW frame within the current PARTITION. For example: CREATE OR REPLACE FUNCTION r_regr_slope(float8, float8) RETURNS float8 AS $BODY$ slope <- NA y <- farg1 x <- farg2 if (fnumrows==9) try (slope <- lm(y ~ x)$coefficients[2]) return(slope) $BODY$ LANGUAGE plr WINDOW; In the preceding example, farg1 and farg2 are R vectors containing the current row's data plus that of related rows. The determination as to which rows qualify as related is determined by the frame specification of the query at run time. The example also illustrates one of two additional autogenerated arguments. fnumrows is the number of rows in the current WINDOW frame. The other (not shown) auto-argument is called prownum. This argument provides the 1-based row offset of the current row in the current PARTITION. See for more information and a more complete example. In some of the the definitions above, note the clause STRICT, which saves us from having to think about NULL input values: if a NULL is passed, the function will not be called at all, but will just return a NULL result automatically. In a non-strict function, if the actual value of an argument is NULL, the corresponding argN variable will be set to a NULL R object. For example, suppose that we wanted r_max with one null and one non-null argument to return the non-null argument, rather than NULL: CREATE OR REPLACE FUNCTION r_max (integer, integer) RETURNS integer AS ' if (is.null(arg1) && is.null(arg2)) return(NULL) if (is.null(arg1)) return(arg2) if (is.null(arg2)) return(arg1) if (arg1 > arg2) return(arg1) arg2 ' LANGUAGE 'plr'; As shown above, to return a NULL value from a PL/R function, return NULL. This can be done whether the function is strict or not. Composite-type (tuple) arguments are passed to the procedure as R data.frames. The element names of the frame are the attribute names of the composite type. If an attribute in the passed row has the NULL value, it will appear as an "NA" in the frame. Here is an example: CREATE TABLE emp (name text, age int, salary numeric(10,2)); INSERT INTO emp VALUES ('Joe', 41, 250000.00); INSERT INTO emp VALUES ('Jim', 25, 120000.00); INSERT INTO emp VALUES ('Jon', 35, 50000.00); CREATE OR REPLACE FUNCTION overpaid (emp) RETURNS bool AS ' if (200000 < arg1$salary) { return(TRUE) } if (arg1$age < 30 && 100000 < arg1$salary) { return(TRUE) } return(FALSE) ' LANGUAGE 'plr'; SELECT name, overpaid(emp) FROM emp; name | overpaid ------+---------- Joe | t Jim | t Jon | f (3 rows) There is also support for returning a composite-type result value: CREATE OR REPLACE FUNCTION get_emps() RETURNS SETOF emp AS ' names <- c("Joe","Jim","Jon") ages <- c(41,25,35) salaries <- c(250000,120000,50000) df <- data.frame(name = names, age = ages, salary = salaries) return(df) ' LANGUAGE 'plr'; select * from get_emps(); name | age | salary ------+-----+----------- Jim | 41 | 250000.00 Joe | 25 | 120000.00 Jon | 35 | 50000.00 (3 rows) An alternative method may be used to create a function in PL/R, if certain criteria are met. First, the function must be a simple call to an existing R function. Second, the function name used for the PL/R function must match that of the R function exactly. If these two criteria are met, the PL/R function may be defined with no body, and the arguments will be passed directly to the R function of the same name. For example: create or replace function sd(_float8) returns float as '' language 'plr'; select round(sd('{1.23,1.31,1.42,1.27}'::_float8)::numeric,8); round ------------ 0.08180261 (1 row) Because the function body is passed as an SQL string literal to CREATE FUNCTION, you have to escape single quotes and backslashes within your R source, typically by doubling them. Passing Data Values The argument values supplied to a PL/R function's script are the input arguments converted to a corresponding R form. See . Scalar PostgreSQL values become single element R vectors. One exception to this are scalar bytea values. These are first converted to R raw type, and then processed by the R unserialize command. One-dimensional PostgreSQL arrays are converted to multi-element R vectors, two-dimensional PostgreSQL arrays are mapped to R matrixes, and three-dimensional PostgreSQL arrays are converted to three-dimensional R arrays. Greater than three-dimensional arrays are not supported. Composite-types are transformed into R data.frames. Function Arguments PostgreSQL type R type boolean logical int2, int4 integer int8, float4, float8, cash, numeric numeric bytea object everything else character
Conversely, the return values are first coerced to R character, and therefore anything that resolves to a string that is acceptable input format for the function's declared return type will produce a result. Again, there is an exception for scalar bytea return values. In this case, the R object being returned is first processed by the R serialize command, and then the binary result is directly mapped into a PostgreSQL bytea datum. Similar to argument conversion, there is also a mapping between the dimensionality of the declared PostgreSQL return type and the type of R object. That mapping is shown in Function Result Dimensionality PgSQL return type R type Result Example scalar array, matrix, vector first column of first row c(1,2,3) in R returns 1 in PostgreSQL setof scalar 1D array, greater than 2D array, vector multi-row, 1 column set array(1:10) in R returns 10 rows in PostgreSQL scalar data.frame textual representation of the first column's vector data.frame(c(1,2,3)) in R returns 'c(1, 2, 3)' setof scalar 2D array, matrix, data.frame #columns > 1, error; #columns == 1, multi-row, 1 column set (as.data.frame(array(1:10,c(2,5))))[,1] in R returns 2 rows of scalar array 1D array, greater than 3D array, vector 1D array array(1:8,c(2,2,2,2)) in R returns {1,2,3,4,5,6,7,8,1,2,3,4,5,6,7,8} array 2D array, matrix, data.frame 2D array array(1:4,c(2,2)) in R returns {{1,3},{2,4}} array 3D array 3D array array(1:8,c(2,2,2)) in R returns {{{1,5},{3,7}},{{2,6},{4,8}}} composite 1D array, greater than 2D array, vector first row, 1 column array(1:8,c(2,2,2)) in R returns 1 row of scalar setof composite 1D array, greater than 2D array, vector multi-row, 1 column set array(1:8,c(2,2,2)) in R returns 8 rows of scalar composite 2D array, matrix, data.frame first row, multi-column array(1:4,c(2,2)) in R returns 1 row of 2 columns setof composite 2D array, matrix, data.frame multi-row, multi-column set array(1:4,c(2,2)) in R returns 2 rows of 2 columns
Using Global Data Sometimes it is useful to have some global status data that is held between two calls to a procedure or is shared between different procedures. Equally useful is the ability to create functions that your PL/R functions can share. This is easily done since all PL/R procedures executed in one backend share the same R interpreter. So, any global R variable is accessible to all PL/R procedure calls, and will persist for the duration of the SQL client connection. An example of using a global object appears in the pg.spi.execp example, in . A globally available, user named, R function (the R function name of PL/R functions is not the same as its PostgreSQL function name; see: ) can be created dynamically using the provided PostgreSQL function install_rcmd(text). Here is an example: select install_rcmd('pg.test.install <-function(msg) {print(msg)}'); install_rcmd -------------- OK (1 row) create or replace function pg_test_install(text) returns text as ' pg.test.install(arg1) ' language 'plr'; select pg_test_install('hello world'); pg_test_install ----------------- hello world (1 row) A globally available, user named, R function can also be automatically created and installed in the R interpreter. See: PL/R also provides a global variable called pg.state.firstpass. This variable is reset to TRUE the first time each PL/R function is called, for a particular query. On subsequent calls the value is left unchanged. This allows one or more PL/R functions to perform a possibly expensive initialization on the first call, and reuse the results for the remaining rows in the query. For example: create table t (f1 int); insert into t values (1); insert into t values (2); insert into t values (3); create or replace function f1() returns int as ' msg <- paste("enter f1, pg.state.firstpass is", pg.state.firstpass) pg.thrownotice(msg) if (pg.state.firstpass == TRUE) pg.state.firstpass <<- FALSE msg <- paste("exit f1, pg.state.firstpass is", pg.state.firstpass) pg.thrownotice(msg) return(0) ' language plr; create or replace function f2() returns int as ' msg <- paste("enter f2, pg.state.firstpass is", pg.state.firstpass) pg.thrownotice(msg) if (pg.state.firstpass == TRUE) pg.state.firstpass <<- FALSE msg <- paste("exit f2, pg.state.firstpass is", pg.state.firstpass) pg.thrownotice(msg) return(0) ' language plr; select f1(), f2(), f1 from t; NOTICE: enter f1, pg.state.firstpass is TRUE NOTICE: exit f1, pg.state.firstpass is FALSE NOTICE: enter f2, pg.state.firstpass is TRUE NOTICE: exit f2, pg.state.firstpass is FALSE NOTICE: enter f1, pg.state.firstpass is FALSE NOTICE: exit f1, pg.state.firstpass is FALSE NOTICE: enter f2, pg.state.firstpass is FALSE NOTICE: exit f2, pg.state.firstpass is FALSE NOTICE: enter f1, pg.state.firstpass is FALSE NOTICE: exit f1, pg.state.firstpass is FALSE NOTICE: enter f2, pg.state.firstpass is FALSE NOTICE: exit f2, pg.state.firstpass is FALSE f1 | f2 | f1 ----+----+---- 0 | 0 | 1 0 | 0 | 2 0 | 0 | 3 (3 rows) create or replace function row_number() returns int as ' if (pg.state.firstpass) { assign("pg.state.firstpass", FALSE, env=.GlobalEnv) lclcntr <- 1 } else lclcntr <- plrcounter + 1 assign("plrcounter", lclcntr, env=.GlobalEnv) return(lclcntr) ' language 'plr'; SELECT row_number(), f1 from t; row_number | f1 ------------+---- 1 | 1 2 | 2 3 | 3 (3 rows) Database Access and Support Functions The following commands are available to access the database from the body of a PL/R procedure, or in support thereof: Normal Support pg.spi.exec (character query) Execute an SQL query given as a string. An error in the query causes an error to be raised. Otherwise, the command's return value is the number of rows processed for INSERT, UPDATE, or DELETE statements, or zero if the query is a utility statement. If the query is a SELECT statement, the values of the selected columns are placed in an R data.frame with the target column names used as the frame column names. However, non-numeric columns are not converted to factors. If you want all non-numeric columns converted to factors, a convenience function pg.spi.factor (described below) is provided. If a field of a SELECT result is NULL, the target variable for it is set to NA. For example: create or replace function test_spi_tup(text) returns setof record as ' pg.spi.exec(arg1) ' language 'plr'; select * from test_spi_tup('select oid, NULL::text as nullcol, typname from pg_type where typname = ''oid'' or typname = ''text''') as t(typeid oid, nullcol text, typename name); typeid | nullcol | typename --------+---------+---------- 25 | | text 26 | | oid (2 rows) The NULL values were passed to R as NA, and on return to PostgreSQL they were converted back to NULL. pg.spi.prepare (character query, integer vector type_vector) Prepares and saves a query plan for later execution. The saved plan will be retained for the life of the current backend. The query may use arguments, which are placeholders for values to be supplied whenever the plan is actually executed. In the query string, refer to arguments by the symbols $1 ... $n. If the query uses arguments, the values of the argument types must be given as a vector. Pass NA for type_vector if the query has no arguments. The argument types must be identified by the type Oids, shown in pg_type. Global variables are provided for this use. They are named according to the convention TYPENAMEOID, where the actual name of the type, in all capitals, is substituted for TYPENAME. A support function, load_r_typenames() must be used to make the predefined global variables available for use: select load_r_typenames(); load_r_typenames ------------------ OK (1 row) Another support function, r_typenames() may be used to list the predefined Global variables: select * from r_typenames(); typename | typeoid -----------------+--------- ABSTIMEOID | 702 ACLITEMOID | 1033 ANYARRAYOID | 2277 ANYOID | 2276 BITOID | 1560 BOOLOID | 16 [...] TRIGGEROID | 2279 UNKNOWNOID | 705 VARBITOID | 1562 VARCHAROID | 1043 VOIDOID | 2278 XIDOID | 28 (59 rows) The return value from pg.spi.prepare is a query ID to be used in subsequent calls to pg.spi.execp. See spi_execp for an example. pg.spi.execp (external pointer saved_plan, variable listvalue_list) Execute a query previously prepared with pg.spi.prepare . saved_plan is the external pointer returned by pg.spi.prepare. If the query references arguments, a value_list must be supplied: this is an R list of actual values for the plan arguments. It must be the same length as the argument type_vector previously given to pg.spi.prepare. Pass NA for value_list if the query has no arguments. The following illustrates the use of pg.spi.prepare and pg.spi.execp with and without query arguments: create or replace function test_spi_prep(text) returns text as ' sp <<- pg.spi.prepare(arg1, c(NAMEOID, NAMEOID)); print("OK") ' language 'plr'; select test_spi_prep('select oid, typname from pg_type where typname = $1 or typname = $2'); test_spi_prep --------------- OK (1 row) create or replace function test_spi_execp(text, text, text) returns setof record as ' pg.spi.execp(pg.reval(arg1), list(arg2,arg3)) ' language 'plr'; select * from test_spi_execp('sp','oid','text') as t(typeid oid, typename name); typeid | typename --------+---------- 25 | text 26 | oid (2 rows) create or replace function test_spi_prep(text) returns text as ' sp <<- pg.spi.prepare(arg1, NA); print("OK") ' language 'plr'; select test_spi_prep('select oid, typname from pg_type where typname = ''bytea'' or typname = ''text'''); test_spi_prep --------------- OK (1 row) create or replace function test_spi_execp(text) returns setof record as ' pg.spi.execp(pg.reval(arg1), NA) ' language 'plr'; select * from test_spi_execp('sp') as t(typeid oid, typename name); typeid | typename --------+---------- 17 | bytea 25 | text (2 rows) create or replace function test_spi_prep(text) returns text as ' sp <<- pg.spi.prepare(arg1); print("OK") ' language 'plr'; select test_spi_prep('select oid, typname from pg_type where typname = ''bytea'' or typname = ''text'''); test_spi_prep --------------- OK (1 row) create or replace function test_spi_execp(text) returns setof record as ' pg.spi.execp(pg.reval(arg1)) ' language 'plr'; select * from test_spi_execp('sp') as t(typeid oid, typename name); typeid | typename --------+---------- 17 | bytea 25 | text (2 rows) NULL arguments should be passed as individual NA values in value_list. Except for the way in which the query and its arguments are specified, pg.spi.execp works just like pg.spi.exec. pg.spi.cursor_open( character cursor_name, external pointer saved_plan, variable list value_list) Opens a cursor identified by cursor_name. The cursor can then be used to scroll through the results of a query plan previously prepared by pg.spi.prepare. Any arguments to the plan should be specified in argvalues similar to pg.spi.execp. Only read-only cursors are supported at the moment. plan <- pg.spi.prepare('SELECT * FROM pg_class'); cursor_obj <- pg.spi.cursor_open('my_cursor',plan); Returns a cursor object that be be passed to pg.spi.cursor_fetch pg.spi.cursor_fetch( external pointer cursor, boolean forward, integer rows) Fetches rows from the cursor object previosuly returned by pg.spi.cursor_open . If forward is TRUE then the cursor is moved forward to fetch at most the number of rows required by the rows parameter. If forward is FALSE then the cursor is moved backrwards at most the number of rows specified. rows indicates the maximum number of rows that should be returned. plan <- pg.spi.prepare('SELECT * FROM pg_class'); cursor_obj <- pg.spi.cursor_open('my_cursor',plan); data <- pg.spi.cursor_fetch(cursor_obj,TRUE,as.integer(10)); Returns a data frame containing the results. pg.spi.cursor_close( external pointercursor) Closes a cursor previously opened by pg.spi.cursor_open plan <- pg.spi.prepare('SELECT * FROM pg_class'); cursor_obj <- pg.spi.cursor_open('my_cursor',plan); pg.spi.cursor_close(cursor_obj); pg.spi.lastoid() Returns the OID of the row inserted by the last query executed via pg.spi.exec or pg.spi.execp, if that query was a single-row INSERT. (If not, you get zero.) pg.quoteliteral (character SQL_string) Duplicates all occurrences of single quote and backslash characters in the given string. This may be used to safely quote strings that are to be inserted into SQL queries given to pg.spi.exec or pg.spi.prepare. pg.quoteident (character SQL_string) Return the given string suitably quoted to be used as an identifier in an SQL query string. Quotes are added only if necessary (i.e., if the string contains non-identifier characters or would be case-folded). Embedded quotes are properly doubled. This may be used to safely quote strings that are to be inserted into SQL queries given to pg.spi.exec or pg.spi.prepare. pg.thrownotice (character message) pg.throwerror (character message) Emit a PostgreSQL NOTICE or ERROR message. ERROR also raises an error condition: further execution of the function is abandoned, and the current transaction is aborted. pg.spi.factor (data.frame data) Accepts an R data.frame as input, and converts all non-numeric columns to factors. This may be useful for data.frames produced by pg.spi.exec or pg.spi.prepare, because the PL/R conversion mechanism does not do that for you. RPostgreSQL Compatibility Support The following functions are intended to provide some level of compatibility between PL/R and RPostgreSQL (PostgreSQL DBI package). This allows, for example, a function to be first prototyped using an R client, and then easily moved to PL/R for production use. dbDriver (character dvr_name) dbConnect (DBIDriver drv, character user, character password, character host, character dbname, character port, character tty, character options) dbSendQuery (DBIConnection conn, character sql) fetch (DBIResult rs, integer num_rows) dbClearResult (DBIResult rs) dbGetQuery (DBIConnection conn, character sql) dbReadTable (DBIConnection conn, character name) dbDisconnect (DBIConnection conn) dbUnloadDriver (DBIDriver drv) These functions nominally work like their RPostgreSQL counterparts except that all queries are performed in the current database. Therefore all driver and connection related parameters are ignored, and dbDriver, dbConnect, dbDisconnect, and dbUnloadDriver are no-ops. PostgreSQL Support Functions The following commands are available to use in PostgreSQL queries to aid in the use of PL/R functions: plr_version() Displays PL/R version as a text string. install_rcmd (text R_code) Install R code, given as a string, into the interpreter. See for an example. reload_plr_modules () Force re-loading of R code from the plr_modules table. It is useful after modifying the contents of plr_modules, so that the change will have an immediate effect. plr_singleton_array (float8 first_element) Creates a new PostgreSQL array, using element first_element. This function is predefined to accept one float8 value and return a float8 array. The C function that implements this PostgreSQL function is capable of accepting and returning other data types, although the return type must be an array of the input parameter type. It can also accept multiple input parameters. For example, to define a plr_array function to create a text array from two input text values: CREATE OR REPLACE FUNCTION plr_array (text, text) RETURNS text[] AS '$libdir/plr','plr_array' LANGUAGE 'C' WITH (isstrict); select plr_array('hello','world'); plr_array --------------- {hello,world} (1 row) plr_array_push (float8[] array, float8 next_element) Pushes a new element onto the end of an existing PostgreSQL array. This function is predefined to accept one float8 array and a float8 value, and return a float8 array. The C function that implements this PostgreSQL function is capable of accepting and returning other data types. For example, to define a plr_array_push function to add a text value to an existing text array: CREATE OR REPLACE FUNCTION plr_array_push (_text, text) RETURNS text[] AS '$libdir/plr','plr_array_push' LANGUAGE 'C' WITH (isstrict); select plr_array_push(plr_array('hello','world'), 'how are you'); plr_array_push ----------------------------- {hello,world,"how are you"} (1 row) plr_array_accum (float8[] state_value, float8 next_element) Creates a new array using next_element if state_value is NULL. Otherwise, pushes next_element onto the end of state_value. This function is predefined to accept one float8 array and a float8 value, and return a float8 array. The C function that implements this PostgreSQL function is capable of accepting and returning other data types. For example, to define a plr_array_accum function to add an int4 value to an existing int4 array: CREATE OR REPLACE FUNCTION plr_array_accum (_int4, int4) RETURNS int4[] AS '$libdir/plr','plr_array_accum' LANGUAGE 'C'; select plr_array_accum(NULL, 42); plr_array_accum ------------- {42} (1 row) select plr_array_accum('{23,35}', 42); plr_array_accum ----------------- {23,35,42} (1 row) This function may be useful for creating custom aggregates. See for an example. load_r_typenames() Installs datatype Oid variables into the R interpreter as globals. See also r_typenames below. r_typenames() Displays the datatype Oid variables installed into the R interpreter as globals. See for an example. plr_environ() Displays the environment under which the Postmaster is currently running. This may be useful to debug issues related to R specific environment variables. This function is installed with EXECUTE permission revoked from PUBLIC. plr_set_display(text display) Sets the DISPLAY environment vaiable under which the Postmaster is currently running. This may be useful if using R to plot to a virtual frame buffer. This function is installed with EXECUTE permission revoked from PUBLIC. plr_get_raw(bytea serialized_object) By default, when R objects are returned as type bytea, the R object is serialized using an internal R function prior to sending to PostgreSQL. This function unserializes the R object using another internal R function, and returns the pure raw bytes to PostgreSQL. This is useful, for example, if the R object being returned is a JPEG or PNG graphic for use outside of R. Aggregate Functions Aggregates in PostgreSQL are extensible via SQL commands. In general, to create a new aggregate, a state transition function and possibly a final function are specified. The final function is used in case the desired output of the aggregate is different from the data that needs to be kept in the running state value. There is more than one way to create a new aggregate using PL/R. A simple aggregate can be defined using the predefined PostgreSQL C function, plr_array_accum (see ) as a state transition function, and a PL/R function as a finalizer. For example: create or replace function r_median(_float8) returns float as ' median(arg1) ' language 'plr'; CREATE AGGREGATE median ( sfunc = plr_array_accum, basetype = float8, stype = _float8, finalfunc = r_median ); create table foo(f0 int, f1 text, f2 float8); insert into foo values(1,'cat1',1.21); insert into foo values(2,'cat1',1.24); insert into foo values(3,'cat1',1.18); insert into foo values(4,'cat1',1.26); insert into foo values(5,'cat1',1.15); insert into foo values(6,'cat2',1.15); insert into foo values(7,'cat2',1.26); insert into foo values(8,'cat2',1.32); insert into foo values(9,'cat2',1.30); select f1, median(f2) from foo group by f1 order by f1; f1 | median ------+-------- cat1 | 1.21 cat2 | 1.28 (2 rows) A more complex aggregate might be created by using a PL/R functions for both state transition and finalizer. Window Functions Starting with version 8.4, PostgreSQL supports WINDOW functions which provide the ability to perform calculations across sets of rows that are related to the current query row. This is comparable to the type of calculation that can be done with an aggregate function. But unlike regular aggregate functions, use of a window function does not cause rows to become grouped into a single output row; the rows retain their separate identities. Behind the scenes, the window function is able to access more than just the current row of the query result. See the PostgreSQL documentation for more general information related to the use of this capability. PL/R functions may be defined as WINDOW. For example: CREATE OR REPLACE FUNCTION r_regr_slope(float8, float8) RETURNS float8 AS $BODY$ slope <- NA y <- farg1 x <- farg2 if (fnumrows==9) try (slope <- lm(y ~ x)$coefficients[2]) return(slope) $BODY$ LANGUAGE plr WINDOW; A number of variables are automatically provided by PL/R to the R interpreter: fargN farg1 and farg2 are R vectors containing the current row's data plus that of the related rows. fnumrows The number of rows in the current WINDOW frame. prownum (not shown) Provides the 1-based row offset of the current row in the current PARTITION. A more complete example follows: -- create test table CREATE TABLE test_data ( fyear integer, firm float8, eps float8 ); -- insert randomly pertubated data for test INSERT INTO test_data SELECT (b.f + 1) % 10 + 2000 AS fyear, floor((b.f+1)/10) + 50 AS firm, f::float8/100 + random()/10 AS eps FROM generate_series(-500,499,1) b(f); CREATE OR REPLACE FUNCTION r_regr_slope(float8, float8) RETURNS float8 AS $BODY$ slope <- NA y <- farg1 x <- farg2 if (fnumrows==9) try (slope <- lm(y ~ x)$coefficients[2]) return(slope) $BODY$ LANGUAGE plr WINDOW; SELECT *, r_regr_slope(eps, lag_eps) OVER w AS slope_R FROM (SELECT firm, fyear, eps, lag(eps) OVER (ORDER BY firm, fyear) AS lag_eps FROM test_data) AS a WHERE eps IS NOT NULL WINDOW w AS (ORDER BY firm, fyear ROWS 8 PRECEDING); In this example, the variables farg1 and farg2 contain the current row value for eps and lag_eps, as well as the preceding 8 rows which are also in the same WINDOW frame within the same PARTITION. In this case since no PARTITION is explicitly defined, the PARTITION is the entire set of rows returned from the inner sub-select. Another interesting example follows. The idea of Winsorizing is to return either the original value or, if that value is outside certain bounds, a trimmed value. So for example winsor(eps, 0.1) would return the value at the 10th percentile for values of eps less that that, the value of the 90th percentile for eps greater than that value, and the unmodified value of eps otherwise. CREATE OR REPLACE FUNCTION winsorize(float8, float8) RETURNS float8 AS $BODY$ library(psych) return(winsor(as.vector(farg1), arg2)[prownum]) $BODY$ LANGUAGE plr VOLATILE WINDOW; SELECT fyear, eps, winsorize(eps, 0.1) OVER (PARTITION BY fyear) AS w_eps FROM test_data ORDER BY fyear, eps; In this example, use of the variable prownum is illustrated. Loading R Modules at Startup PL/R has support for auto-loading R code during interpreter initialization. It uses a special table, plr_modules, which is presumed to contain modules of R code. If this table exists, the modules defined are fetched from the table and loaded into the R interpreter immediately after creation. The definition of the table plr_modules is as follows: CREATE TABLE plr_modules ( modseq int4, modsrc text ); The field modseq is used to control the order of installation. The field modsrc contains the full text of the R code to be executed, including assignment if that is desired. Consider, for example, the following statement: INSERT INTO plr_modules VALUES (0, 'pg.test.module.load <-function(msg) {print(msg)}'); This statement will cause an R function named pg.test.module.load to be created in the R interpreter on initialization. A PL/R function may now simply reference the function directly as follows: create or replace function pg_test_module_load(text) returns text as ' pg.test.module.load(arg1) ' language 'plr'; select pg_test_module_load('hello world'); pg_test_module_load --------------------- hello world (1 row) The table plr_modules must be readable by all, but it is wise to make it owned and writable only by the database administrator. R Function Names In PostgreSQL, one and the same function name can be used for different functions as long as the number of arguments or their types differ. R, however, requires all function names to be distinct. PL/R deals with this by constructing the internal R function names as a concatenation of the string PLR with the object ID of the procedure's pg_proc. Thus, PostgreSQL functions with the same name and different argument types will be different R functions too. This is not normally a concern for a PL/R programmer, but it might be visible when debugging. If a specific, known, function name is needed so that an R function can be referenced by one or more PL/R functions, the install_rcmd(text) command can be used. See . Trigger Procedures triggers in PL/R Trigger procedures can be written in PL/R. PostgreSQL requires that a procedure that is to be called as a trigger must be declared as a function with no arguments and a return type of trigger. The information from the trigger manager is passed to the procedure body in the following variables: pg.tg.name The name of the trigger from the CREATE TRIGGER statement. pg.tg.relid The object ID of the table that caused the trigger procedure to be invoked. pg.tg.relname The name of the table that caused the trigger procedure to be invoked. pg.tg.when The string BEFORE or AFTER depending on the type of trigger call. pg.tg.level The string ROW or STATEMENT depending on the type of trigger call. pg.tg.op The string INSERT, UPDATE, or DELETE depending on the type of trigger call. pg.tg.new When the trigger is defined FOR EACH ROW, a data.frame containing the values of the new table row for INSERT or UPDATE actions. For triggers defined FOR EACH STATEMENT and for DELETE actions, set to NULL. The atribute names are the table's column names. Columns that are null will be represented as NA. pg.tg.old When the trigger is defined FOR EACH ROW, a data.frame containing the values of the old table row for DELETE or UPDATE actions. For triggers defined FOR EACH STATEMENT and for INSERT actions, set to NULL. The atribute names are the table's column names. Columns that are null will be represented as NA. pg.tg.args A vector of the arguments to the procedure as given in the CREATE TRIGGER statement. The return value from a trigger procedure can be NULL or a one row data.frame matching the number and type of columns in the trigger table. NULL tells the trigger manager to silently suppress the operation for this row. If a one row data.frame is returned, it tells PL/R to return a possibly modified row to the trigger manager that will be inserted instead of the one given in pg.tg.new. This works for INSERT and UPDATE only. Needless to say that all this is only meaningful when the trigger is BEFORE and FOR EACH ROW; otherwise the return value is ignored. Here's a little example trigger procedure that forces an integer value in a table to keep track of the number of updates that are performed on the row. For new rows inserted, the value is initialized to 0 and then incremented on every update operation. CREATE FUNCTION trigfunc_modcount() RETURNS trigger AS ' if (pg.tg.op == "INSERT") { retval <- pg.tg.new retval[pg.tg.args[1]] <- 0 } if (pg.tg.op == "UPDATE") { retval <- pg.tg.new retval[pg.tg.args[1]] <- pg.tg.old[pg.tg.args[1]] + 1 } if (pg.tg.op == "DELETE") retval <- pg.tg.old return(retval) ' LANGUAGE plr; CREATE TABLE mytab (num integer, description text, modcnt integer); CREATE TRIGGER trig_mytab_modcount BEFORE INSERT OR UPDATE ON mytab FOR EACH ROW EXECUTE PROCEDURE trigfunc_modcount('modcnt'); Notice that the trigger procedure itself does not know the column name; that's supplied from the trigger arguments. This lets the trigger procedure be reused with different tables. License License: GPL version 2 or newer. http://www.gnu.org/copyleft/gpl.html This program 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. This program 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 this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
plr/plr.control0000664000000000000000000000025312465736645012574 0ustar rootroot# plr extension comment = 'load R interpreter and execute R script from within a database' default_version = '8.3.0.16' module_pathname = '$libdir/plr' relocatable = true plr/sql/0000775000000000000000000000000012465736645011174 5ustar rootrootplr/sql/plr.sql0000775000000000000000000004113712465736645012523 0ustar rootroot-- -- first, define the language and functions. Turn off echoing so that expected file -- does not depend on contents of plr.sql. -- \set ECHO none \i plr.sql \set ECHO all -- check version SELECT plr_version(); -- make typenames available in the global namespace select load_r_typenames(); CREATE TABLE plr_modules ( modseq int4, modsrc text ); INSERT INTO plr_modules VALUES (0, 'pg.test.module.load <-function(msg) {print(msg)}'); select reload_plr_modules(); -- -- plr_modules test -- create or replace function pg_test_module_load(text) returns text as 'pg.test.module.load(arg1)' language 'plr'; select pg_test_module_load('hello world'); -- -- user defined R function test -- select install_rcmd('pg.test.install <-function(msg) {print(msg)}'); create or replace function pg_test_install(text) returns text as 'pg.test.install(arg1)' language 'plr'; select pg_test_install('hello world'); -- -- a variety of plr functions -- create or replace function throw_notice(text) returns text as 'pg.thrownotice(arg1)' language 'plr'; select throw_notice('hello'); create or replace function paste(_text,_text,text) returns text[] as 'paste(arg1,arg2, sep = arg3)' language 'plr'; select paste('{hello, happy}','{world, birthday}',' '); create or replace function vec(_float8) returns _float8 as 'arg1' language 'plr'; select vec('{1.23, 1.32}'::float8[]); create or replace function vec(float, float) returns _float8 as 'c(arg1,arg2)' language 'plr'; select vec(1.23, 1.32); create or replace function echo(text) returns text as 'print(arg1)' language 'plr'; select echo('hello'); create or replace function reval(text) returns text as 'eval(parse(text = arg1))' language 'plr'; select reval('a <- sd(c(1,2,3)); b <- mean(c(1,2,3)); a + b'); create or replace function "commandArgs"() returns text[] as '' language 'plr'; select "commandArgs"(); create or replace function vec(float) returns text as 'c(arg1)' language 'plr'; select vec(1.23); create or replace function reval(_text) returns text as 'eval(parse(text = arg1))' language 'plr'; select round(reval('{"sd(c(1.12,1.23,1.18,1.34))"}'::text[])::numeric,8); create or replace function print(text) returns text as '' language 'plr'; select print('hello'); create or replace function cube(int) returns float as 'sq <- function(x) {return(x * x)}; return(arg1 * sq(arg1))' language 'plr'; select cube(3); create or replace function sd(_float8) returns float as 'sd(arg1)' language 'plr'; select round(sd('{1.23,1.31,1.42,1.27}'::_float8)::numeric,8); create or replace function sd(_float8) returns float as '' language 'plr'; select round(sd('{1.23,1.31,1.42,1.27}'::_float8)::numeric,8); create or replace function mean(_float8) returns float as '' language 'plr'; select mean('{1.23,1.31,1.42,1.27}'::_float8); create or replace function sprintf(text,text,text) returns text as 'sprintf(arg1,arg2,arg3)' language 'plr'; select sprintf('%s is %s feet tall', 'Sven', '7'); -- -- test aggregates -- create table foo(f0 int, f1 text, f2 float8) with oids; insert into foo values(1,'cat1',1.21); insert into foo values(2,'cat1',1.24); insert into foo values(3,'cat1',1.18); insert into foo values(4,'cat1',1.26); insert into foo values(5,'cat1',1.15); insert into foo values(6,'cat2',1.15); insert into foo values(7,'cat2',1.26); insert into foo values(8,'cat2',1.32); insert into foo values(9,'cat2',1.30); create or replace function r_median(_float8) returns float as 'median(arg1)' language 'plr'; select r_median('{1.23,1.31,1.42,1.27}'::_float8); CREATE AGGREGATE median (sfunc = plr_array_accum, basetype = float8, stype = _float8, finalfunc = r_median); select f1, median(f2) from foo group by f1 order by f1; create or replace function r_gamma(_float8) returns float as 'gamma(arg1)' language 'plr'; select round(r_gamma('{1.23,1.31,1.42,1.27}'::_float8)::numeric,8); CREATE AGGREGATE gamma (sfunc = plr_array_accum, basetype = float8, stype = _float8, finalfunc = r_gamma); select f1, round(gamma(f2)::numeric,8) from foo group by f1 order by f1; -- -- test returning vectors, arrays, matricies, and dataframes -- as scalars, arrays, and records -- create or replace function test_vt() returns text as 'array(1:10,c(2,5))' language 'plr'; select test_vt(); create or replace function test_vi() returns int as 'array(1:10,c(2,5))' language 'plr'; select test_vi(); create or replace function test_mt() returns text as 'as.matrix(array(1:10,c(2,5)))' language 'plr'; select test_mt(); create or replace function test_mi() returns int as 'as.matrix(array(1:10,c(2,5)))' language 'plr'; select test_mi(); create or replace function test_dt() returns text as 'as.data.frame(array(1:10,c(2,5)))[[1]]' language 'plr'; select test_dt(); create or replace function test_di() returns int as 'as.data.frame(array(1:10,c(2,5)))[[1]]' language 'plr'; select test_di() as error; create or replace function test_vta() returns text[] as 'array(1:10,c(2,5))' language 'plr'; select test_vta(); create or replace function test_via() returns int[] as 'array(1:10,c(2,5))' language 'plr'; select test_via(); create or replace function test_mta() returns text[] as 'as.matrix(array(1:10,c(2,5)))' language 'plr'; select test_mta(); create or replace function test_mia() returns int[] as 'as.matrix(array(1:10,c(2,5)))' language 'plr'; select test_mia(); create or replace function test_dia() returns int[] as 'as.data.frame(array(1:10,c(2,5)))' language 'plr'; select test_dia(); create or replace function test_dta() returns text[] as 'as.data.frame(array(1:10,c(2,5)))' language 'plr'; select test_dta(); create or replace function test_dta1() returns text[] as 'as.data.frame(array(letters[1:10], c(2,5)))' language 'plr'; select test_dta1(); create or replace function test_dta2() returns text[] as 'as.data.frame(data.frame(letters[1:10],1:10))' language 'plr'; select test_dta2(); -- generates expected error create or replace function test_dia1() returns int[] as 'as.data.frame(array(letters[1:10], c(2,5)))' language 'plr'; select test_dia1() as error; create or replace function test_dtup() returns setof record as 'data.frame(letters[1:10],1:10)' language 'plr'; select * from test_dtup() as t(f1 text, f2 int); create or replace function test_mtup() returns setof record as 'as.matrix(array(1:15,c(5,3)))' language 'plr'; select * from test_mtup() as t(f1 int, f2 int, f3 int); create or replace function test_vtup() returns setof record as 'as.vector(array(1:15,c(5,3)))' language 'plr'; select * from test_vtup() as t(f1 int); create or replace function test_vint() returns setof int as 'as.vector(array(1:15,c(5,3)))' language 'plr'; select * from test_vint(); -- -- try again with named tuple types -- CREATE TYPE dtup AS (f1 text, f2 int); CREATE TYPE mtup AS (f1 int, f2 int, f3 int); CREATE TYPE vtup AS (f1 int); create or replace function test_dtup1() returns setof dtup as 'data.frame(letters[1:10],1:10)' language 'plr'; select * from test_dtup1(); create or replace function test_dtup2() returns setof dtup as 'data.frame(c("c","qw","ax","h","k","ax","l","t","b","u"),1:10)' language 'plr'; select * from test_dtup2(); create or replace function test_mtup1() returns setof mtup as 'as.matrix(array(1:15,c(5,3)))' language 'plr'; select * from test_mtup1(); create or replace function test_vtup1() returns setof vtup as 'as.vector(array(1:15,c(5,3)))' language 'plr'; select * from test_vtup1(); -- -- test pg R support functions (e.g. SPI_exec) -- create or replace function pg_quote_ident(text) returns text as 'pg.quoteident(arg1)' language 'plr'; select pg_quote_ident('Hello World'); create or replace function pg_quote_literal(text) returns text as 'pg.quoteliteral(arg1)' language 'plr'; select pg_quote_literal('Hello''World'); create or replace function test_spi_t(text) returns text as '(pg.spi.exec(arg1))[[1]]' language 'plr'; select test_spi_t('select oid, typname from pg_type where typname = ''oid'' or typname = ''text'''); create or replace function test_spi_ta(text) returns text[] as 'pg.spi.exec(arg1)' language 'plr'; select test_spi_ta('select oid, typname from pg_type where typname = ''oid'' or typname = ''text'''); create or replace function test_spi_tup(text) returns setof record as 'pg.spi.exec(arg1)' language 'plr'; select * from test_spi_tup('select oid, typname from pg_type where typname = ''oid'' or typname = ''text''') as t(typeid oid, typename name); create or replace function fetch_pgoid(text) returns int as 'pg.reval(arg1)' language 'plr'; select fetch_pgoid('BYTEAOID'); create or replace function test_spi_prep(text) returns text as 'sp <<- pg.spi.prepare(arg1, c(NAMEOID, NAMEOID)); print("OK")' language 'plr'; select test_spi_prep('select oid, typname from pg_type where typname = $1 or typname = $2'); create or replace function test_spi_execp(text, text, text) returns setof record as 'pg.spi.execp(pg.reval(arg1), list(arg2,arg3))' language 'plr'; select * from test_spi_execp('sp','oid','text') as t(typeid oid, typename name); create or replace function test_spi_lastoid(text) returns text as 'pg.spi.exec(arg1); pg.spi.lastoid()/pg.spi.lastoid()' language 'plr'; select test_spi_lastoid('insert into foo values(10,''cat3'',3.333)') as "ONE"; -- -- test NULL handling -- CREATE OR REPLACE FUNCTION r_test (float8) RETURNS float8 AS 'arg1' LANGUAGE 'plr'; select r_test(null) is null as "NULL"; CREATE OR REPLACE FUNCTION r_max (integer, integer) RETURNS integer AS 'if (is.null(arg1) && is.null(arg2)) return(NA);if (is.null(arg1)) return(arg2);if (is.null(arg2)) return(arg1);if (arg1 > arg2) return(arg1);arg2' LANGUAGE 'plr'; select r_max(1,2) as "TWO"; select r_max(null,2) as "TWO"; select r_max(1,null) as "ONE"; select r_max(null,null) is null as "NULL"; -- -- test tuple arguments -- create or replace function get_foo(int) returns foo as 'select * from foo where f0 = $1' language 'sql'; create or replace function test_foo(foo) returns foo as 'return(arg1)' language 'plr'; select * from test_foo(get_foo(1)); -- -- test 2D array argument -- create or replace function test_in_m_tup(_int4) returns setof record as 'arg1' language 'plr'; select * from test_in_m_tup('{{1,3,5},{2,4,6}}') as t(f1 int, f2 int, f3 int); -- -- test 3D array argument -- create or replace function arr3d(_int4,int4,int4,int4) returns int4 as ' if (arg2 < 1 || arg3 < 1 || arg4 < 1) return(NA) if (arg2 > dim(arg1)[1] || arg3 > dim(arg1)[2] || arg4 > dim(arg1)[3]) return(NA) return(arg1[arg2,arg3,arg4]) ' language 'plr' WITH (isstrict); select arr3d('{{{111,112},{121,122},{131,132}},{{211,212},{221,222},{231,232}}}',2,3,1) as "231"; -- for sake of comparison, see what normal pgsql array operations produces select f1[2][3][1] as "231" from (select '{{{111,112},{121,122},{131,132}},{{211,212},{221,222},{231,232}}}'::int4[] as f1) as t; -- out-of-bounds, returns null select arr3d('{{{111,112},{121,122},{131,132}},{{211,212},{221,222},{231,232}}}',1,4,1) is null as "NULL"; select f1[1][4][1] is null as "NULL" from (select '{{{111,112},{121,122},{131,132}},{{211,212},{221,222},{231,232}}}'::int4[] as f1) as t; select arr3d('{{{111,112},{121,122},{131,132}},{{211,212},{221,222},{231,232}}}',0,1,1) is null as "NULL"; select f1[0][1][1] is null as "NULL" from (select '{{{111,112},{121,122},{131,132}},{{211,212},{221,222},{231,232}}}'::int4[] as f1) as t; -- -- test 3D array return value -- create or replace function arr3d(_int4) returns int4[] as 'return(arg1)' language 'plr' WITH (isstrict); select arr3d('{{{111,112},{121,122},{131,132}},{{211,212},{221,222},{231,232}}}'); -- -- Trigger support tests -- -- -- test that NULL return value suppresses the change -- create or replace function rejectfoo() returns trigger as 'return(NULL)' language plr; create trigger footrig before insert or update or delete on foo for each row execute procedure rejectfoo(); select count(*) from foo; insert into foo values(11,'cat99',1.89); select count(*) from foo; update foo set f1 = 'zzz'; select count(*) from foo; delete from foo; select count(*) from foo; drop trigger footrig on foo; -- -- test that returning OLD/NEW as appropriate allow the change unmodified -- create or replace function acceptfoo() returns trigger as ' switch (pg.tg.op, INSERT = return(pg.tg.new), UPDATE = return(pg.tg.new), DELETE = return(pg.tg.old)) ' language plr; create trigger footrig before insert or update or delete on foo for each row execute procedure acceptfoo(); select count(*) from foo; insert into foo values(11,'cat99',1.89); select count(*) from foo; update foo set f1 = 'zzz' where f0 = 11; select * from foo where f0 = 11; delete from foo where f0 = 11; select count(*) from foo; drop trigger footrig on foo; -- -- test that returning modifed tuple successfully modifies the result -- create or replace function modfoo() returns trigger as ' if (pg.tg.op == "INSERT") { retval <- pg.tg.new retval$f1 <- "xxx" } if (pg.tg.op == "UPDATE") { retval <- pg.tg.new retval$f1 <- "aaa" } if (pg.tg.op == "DELETE") retval <- pg.tg.old return(retval) ' language plr; create trigger footrig before insert or update or delete on foo for each row execute procedure modfoo(); select count(*) from foo; insert into foo values(11,'cat99',1.89); select * from foo where f0 = 11; update foo set f1 = 'zzz' where f0 = 11; select * from foo where f0 = 11; delete from foo where f0 = 11; select count(*) from foo; drop trigger footrig on foo; -- -- test statement level triggers and verify all arguments come -- across correctly -- create or replace function foonotice() returns trigger as ' msg <- paste(pg.tg.name,pg.tg.relname,pg.tg.when,pg.tg.level,pg.tg.op,pg.tg.args[1],pg.tg.args[2]) pg.thrownotice(msg) return(NULL) ' language plr; create trigger footrig after insert or update or delete on foo for each row execute procedure foonotice(); select count(*) from foo; insert into foo values(11,'cat99',1.89); select count(*) from foo; update foo set f1 = 'zzz' where f0 = 11; select * from foo where f0 = 11; delete from foo where f0 = 11; select count(*) from foo; drop trigger footrig on foo; create trigger footrig after insert or update or delete on foo for each statement execute procedure foonotice('hello','world'); select count(*) from foo; insert into foo values(11,'cat99',1.89); select count(*) from foo; update foo set f1 = 'zzz' where f0 = 11; select * from foo where f0 = 11; delete from foo where f0 = 11; select count(*) from foo; drop trigger footrig on foo; -- Test cursors: creating, scrolling forward, closing CREATE OR REPLACE FUNCTION cursor_fetch_test(integer,boolean) RETURNS SETOF integer AS 'plan<-pg.spi.prepare("SELECT * FROM generate_series(1,10)"); cursor<-pg.spi.cursor_open("curs",plan); dat<-pg.spi.cursor_fetch(cursor,arg2,arg1); pg.spi.cursor_close(cursor); return (dat);' language 'plr'; SELECT * FROM cursor_fetch_test(1,true); SELECT * FROM cursor_fetch_test(2,true); SELECT * FROM cursor_fetch_test(20,true); --Test cursors: scrolling backwards CREATE OR REPLACE FUNCTION cursor_direction_test() RETURNS SETOF integer AS'plan<-pg.spi.prepare("SELECT * FROM generate_series(1,10)"); cursor<-pg.spi.cursor_open("curs",plan); dat<-pg.spi.cursor_fetch(cursor,TRUE,as.integer(3)); dat2<-pg.spi.cursor_fetch(cursor,FALSE,as.integer(3)); pg.spi.cursor_close(cursor); return (dat2);' language 'plr'; SELECT * FROM cursor_direction_test(); --Test cursors: Passing arguments to a plan CREATE OR REPLACE FUNCTION cursor_fetch_test_arg(integer) RETURNS SETOF integer AS 'plan<-pg.spi.prepare("SELECT * FROM generate_series(1,$1)",c(INT4OID)); cursor<-pg.spi.cursor_open("curs",plan,list(arg1)); dat<-pg.spi.cursor_fetch(cursor,TRUE,arg1); pg.spi.cursor_close(cursor); return (dat);' language 'plr'; SELECT * FROM cursor_fetch_test_arg(3); --Test bytea arguments and return values: serialize/unserialize create or replace function test_serialize(text) returns bytea as ' mydf <- pg.spi.exec(arg1) return (mydf) ' language 'plr'; create or replace function restore_df(bytea) returns setof record as ' return (arg1) ' language 'plr'; select * from restore_df((select test_serialize('select oid, typname from pg_type where typname in (''oid'',''name'',''int4'')'))) as t(oid oid, typname name); --Test WINDOW functions -- create test table CREATE TABLE test_data ( fyear integer, firm float8, eps float8 ); -- insert data for test INSERT INTO test_data SELECT (b.f + 1) % 10 + 2000 AS fyear, floor((b.f+1)/10) + 50 AS firm, f::float8/100 AS eps FROM generate_series(-200,199,1) b(f); CREATE OR REPLACE FUNCTION r_regr_slope(float8, float8) RETURNS float8 AS $BODY$ slope <- NA y <- farg1 x <- farg2 if (fnumrows==9) try (slope <- lm(y ~ x)$coefficients[2]) return(slope) $BODY$ LANGUAGE plr WINDOW; SELECT *, round((r_regr_slope(eps, lag_eps) OVER w)::numeric,6) AS slope_R FROM (SELECT firm, fyear, eps, lag(eps) OVER (ORDER BY firm, fyear) AS lag_eps FROM test_data) AS a WHERE eps IS NOT NULL WINDOW w AS (ORDER BY firm, fyear ROWS 8 PRECEDING); plr/Makefile0000775000000000000000000000513612465736645012045 0ustar rootroot# location of R library ifdef R_HOME r_libdir1x = ${R_HOME}/bin r_libdir2x = ${R_HOME}/lib # location of R includes r_includespec = -I${R_HOME}/include rhomedef = ${R_HOME} else R_HOME := $(shell pkg-config --variable=rhome libR) r_libdir1x := $(shell pkg-config --variable=rlibdir libR) r_libdir2x := $(shell pkg-config --variable=rlibdir libR) r_includespec := $(shell pkg-config --cflags-only-I libR) rhomedef := $(shell pkg-config --variable=rhome libR) endif ifneq (,${R_HOME}) EXTENSION = plr MODULE_big = plr PG_CPPFLAGS += $(r_includespec) SRCS += plr.c pg_conversion.c pg_backend_support.c pg_userfuncs.c pg_rsupport.c OBJS := $(SRCS:.c=.o) SHLIB_LINK += -L$(r_libdir1x) -L$(r_libdir2x) -lR DATA_built = plr.sql DATA = plr--8.3.0.16.sql plr--unpackaged--8.3.0.16.sql DOCS = README.plr REGRESS = plr EXTRA_CLEAN = doc/html/* doc/plr-US.aux doc/plr-*.log doc/plr-*.out doc/plr-*.pdf doc/plr-*.tex-pdf ifdef USE_PGXS ifndef PG_CONFIG PG_CONFIG := pg_config endif PGXS := $(shell $(PG_CONFIG) --pgxs) include $(PGXS) else subdir = contrib/plr top_builddir = ../.. include $(top_builddir)/src/Makefile.global include $(top_srcdir)/contrib/contrib-global.mk endif ifeq ($(PORTNAME), darwin) DYSUFFIX = dylib DLPREFIX = libR else ifeq ($(PORTNAME), win32) DLPREFIX = R else DLPREFIX = libR endif endif # we can only build PL/R if libR is available # Since there is no official way to determine this, # we see if there is a file that is named like a shared library. ifneq ($(PORTNAME), darwin) ifneq (,$(wildcard $(r_libdir1x)/$(DLPREFIX)*$(DLSUFFIX)*)$(wildcard $(r_libdir2x)/$(DLPREFIX)*$(DLSUFFIX)*)) shared_libr = yes; endif else ifneq (,$(wildcard $(r_libdir1x)/$(DLPREFIX)*$(DYSUFFIX)*)$(wildcard $(r_libdir2x)/$(DLPREFIX)*$(DYSUFFIX)*)) shared_libr = yes endif endif # If we don't have a shared library and the platform doesn't allow it # to work without, we have to skip it. ifneq (,$(findstring yes, $(shared_libr)$(allow_nonpic_in_shlib))) override CPPFLAGS := -I"$(srcdir)" -I"$(r_includespec)" $(CPPFLAGS) override CPPFLAGS += -DPKGLIBDIR=\"$(pkglibdir)\" -DDLSUFFIX=\"$(DLSUFFIX)\" override CPPFLAGS += -DR_HOME_DEFAULT=\"$(rhomedef)\" else # can't build all: @echo ""; \ echo "*** Cannot build PL/R because libR is not a shared library." ; \ echo "*** You might have to rebuild your R installation. Refer to"; \ echo "*** the documentation for details."; \ echo "" endif # can't build - cannot find libR else # can't build - no R_HOME all: @echo ""; \ echo "*** Cannot build PL/R because R_HOME cannot be found." ; \ echo "*** Refer to the documentation for details."; \ echo "" endif plr/plr.sql.in0000775000000000000000000000552612465736645012333 0ustar rootroot-- keep this in sync with the plr--X.Y.Z.N.sql extension install file CREATE FUNCTION plr_call_handler() RETURNS LANGUAGE_HANDLER AS 'MODULE_PATHNAME' LANGUAGE C; CREATE LANGUAGE plr HANDLER plr_call_handler; CREATE OR REPLACE FUNCTION plr_version () RETURNS text AS 'MODULE_PATHNAME','plr_version' LANGUAGE C; CREATE OR REPLACE FUNCTION reload_plr_modules () RETURNS text AS 'MODULE_PATHNAME','reload_plr_modules' LANGUAGE C; CREATE OR REPLACE FUNCTION install_rcmd (text) RETURNS text AS 'MODULE_PATHNAME','install_rcmd' LANGUAGE C WITH (isstrict); REVOKE EXECUTE ON FUNCTION install_rcmd (text) FROM PUBLIC; CREATE OR REPLACE FUNCTION plr_singleton_array (float8) RETURNS float8[] AS 'MODULE_PATHNAME','plr_array' LANGUAGE C WITH (isstrict); CREATE OR REPLACE FUNCTION plr_array_push (_float8, float8) RETURNS float8[] AS 'MODULE_PATHNAME','plr_array_push' LANGUAGE C WITH (isstrict); CREATE OR REPLACE FUNCTION plr_array_accum (_float8, float8) RETURNS float8[] AS 'MODULE_PATHNAME','plr_array_accum' LANGUAGE C; CREATE TYPE plr_environ_type AS (name text, value text); CREATE OR REPLACE FUNCTION plr_environ () RETURNS SETOF plr_environ_type AS 'MODULE_PATHNAME','plr_environ' LANGUAGE C; REVOKE EXECUTE ON FUNCTION plr_environ() FROM PUBLIC; CREATE TYPE r_typename AS (typename text, typeoid oid); CREATE OR REPLACE FUNCTION r_typenames() RETURNS SETOF r_typename AS ' x <- ls(name = .GlobalEnv, pat = "OID") y <- vector() for (i in 1:length(x)) {y[i] <- eval(parse(text = x[i]))} data.frame(typename = x, typeoid = y) ' language 'plr'; CREATE OR REPLACE FUNCTION load_r_typenames() RETURNS text AS ' sql <- "select upper(typname::text) || ''OID'' as typename, oid from pg_catalog.pg_type where typtype = ''b'' order by typname" rs <- pg.spi.exec(sql) for(i in 1:nrow(rs)) { typobj <- rs[i,1] typval <- rs[i,2] if (substr(typobj,1,1) == "_") typobj <- paste("ARRAYOF", substr(typobj,2,nchar(typobj)), sep="") assign(typobj, typval, .GlobalEnv) } return("OK") ' language 'plr'; CREATE TYPE r_version_type AS (name text, value text); CREATE OR REPLACE FUNCTION r_version() RETURNS setof r_version_type as ' cbind(names(version),unlist(version)) ' language 'plr'; CREATE OR REPLACE FUNCTION plr_set_rhome (text) RETURNS text AS 'MODULE_PATHNAME','plr_set_rhome' LANGUAGE C WITH (isstrict); REVOKE EXECUTE ON FUNCTION plr_set_rhome (text) FROM PUBLIC; CREATE OR REPLACE FUNCTION plr_unset_rhome () RETURNS text AS 'MODULE_PATHNAME','plr_unset_rhome' LANGUAGE C; REVOKE EXECUTE ON FUNCTION plr_unset_rhome () FROM PUBLIC; CREATE OR REPLACE FUNCTION plr_set_display (text) RETURNS text AS 'MODULE_PATHNAME','plr_set_display' LANGUAGE C WITH (isstrict); REVOKE EXECUTE ON FUNCTION plr_set_display (text) FROM PUBLIC; CREATE OR REPLACE FUNCTION plr_get_raw (bytea) RETURNS bytea AS 'MODULE_PATHNAME','plr_get_raw' LANGUAGE C WITH (isstrict); plr/pg_rsupport.c0000775000000000000000000004505712465736645013143 0ustar rootroot/* * PL/R - PostgreSQL support for R as a * procedural language (PL) * * Copyright (c) 2003-2015 by Joseph E. Conway * ALL RIGHTS RESERVED * * Joe Conway * * Based on pltcl by Jan Wieck * and inspired by REmbeddedPostgres by * Duncan Temple Lang * http://www.omegahat.org/RSPostgres/ * * License: GPL version 2 or newer. http://www.gnu.org/copyleft/gpl.html * * This program 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. * * This program 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 this program; if not, write to the Free Software * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA * * pg_rsupport.c - Postgres support for use within plr functions */ #include "plr.h" extern MemoryContext plr_SPI_context; extern char *last_R_error_msg; static SEXP rpgsql_get_results(int ntuples, SPITupleTable *tuptable); static void rsupport_error_callback(void *arg); /* The information we cache prepared plans */ typedef struct saved_plan_desc { void *saved_plan; int nargs; Oid *typeids; Oid *typelems; FmgrInfo *typinfuncs; } saved_plan_desc; /* * Functions used in R *****************************************************************************/ void throw_pg_notice(const char **msg) { /* skip error CONTEXT for explicitly called messages */ SAVE_PLERRCONTEXT; if (msg && *msg) elog(NOTICE, "%s", *msg); else elog(NOTICE, "%s", ""); RESTORE_PLERRCONTEXT; } /* * plr_quote_literal() - quote literal strings that are to * be used in SPI_exec query strings */ SEXP plr_quote_literal(SEXP rval) { const char *value; text *value_text; text *result_text; SEXP result; /* extract the C string */ PROTECT(rval = AS_CHARACTER(rval)); value = CHAR(STRING_ELT(rval, 0)); /* convert using the pgsql quote_literal function */ value_text = PG_STR_GET_TEXT(value); result_text = DatumGetTextP(DirectFunctionCall1(quote_literal, PointerGetDatum(value_text))); /* copy result back into an R object */ PROTECT(result = NEW_CHARACTER(1)); SET_STRING_ELT(result, 0, COPY_TO_USER_STRING(PG_TEXT_GET_STR(result_text))); UNPROTECT(2); return result; } /* * plr_quote_literal() - quote identifiers that are to * be used in SPI_exec query strings */ SEXP plr_quote_ident(SEXP rval) { const char *value; text *value_text; text *result_text; SEXP result; /* extract the C string */ PROTECT(rval = AS_CHARACTER(rval)); value = CHAR(STRING_ELT(rval, 0)); /* convert using the pgsql quote_literal function */ value_text = PG_STR_GET_TEXT(value); result_text = DatumGetTextP(DirectFunctionCall1(quote_ident, PointerGetDatum(value_text))); /* copy result back into an R object */ PROTECT(result = NEW_CHARACTER(1)); SET_STRING_ELT(result, 0, COPY_TO_USER_STRING(PG_TEXT_GET_STR(result_text))); UNPROTECT(2); return result; } /* * plr_SPI_exec - The builtin SPI_exec command for the R interpreter */ SEXP plr_SPI_exec(SEXP rsql) { int spi_rc = 0; char buf[64]; const char *sql; int count = 0; int ntuples; SEXP result = NULL; MemoryContext oldcontext; PREPARE_PG_TRY; /* set up error context */ PUSH_PLERRCONTEXT(rsupport_error_callback, "pg.spi.exec"); PROTECT(rsql = AS_CHARACTER(rsql)); sql = CHAR(STRING_ELT(rsql, 0)); UNPROTECT(1); if (sql == NULL) error("%s", "cannot exec empty query"); /* switch to SPI memory context */ SWITCHTO_PLR_SPI_CONTEXT(oldcontext); /* * trap elog/ereport so we can let R finish up gracefully * and generate the error once we exit the interpreter */ PG_TRY(); { /* Execute the query and handle return codes */ spi_rc = SPI_exec(sql, count); } PLR_PG_CATCH(); PLR_PG_END_TRY(); /* back to caller's memory context */ MemoryContextSwitchTo(oldcontext); switch (spi_rc) { case SPI_OK_UTILITY: snprintf(buf, sizeof(buf), "%d", 0); SPI_freetuptable(SPI_tuptable); PROTECT(result = NEW_CHARACTER(1)); SET_STRING_ELT(result, 0, COPY_TO_USER_STRING(buf)); UNPROTECT(1); break; case SPI_OK_SELINTO: case SPI_OK_INSERT: case SPI_OK_DELETE: case SPI_OK_UPDATE: snprintf(buf, sizeof(buf), "%d", SPI_processed); SPI_freetuptable(SPI_tuptable); PROTECT(result = NEW_CHARACTER(1)); SET_STRING_ELT(result, 0, COPY_TO_USER_STRING(buf)); UNPROTECT(1); break; case SPI_OK_SELECT: ntuples = SPI_processed; if (ntuples > 0) { result = rpgsql_get_results(ntuples, SPI_tuptable); SPI_freetuptable(SPI_tuptable); } else result = R_NilValue; break; case SPI_ERROR_ARGUMENT: error("SPI_exec() failed: SPI_ERROR_ARGUMENT"); break; case SPI_ERROR_UNCONNECTED: error("SPI_exec() failed: SPI_ERROR_UNCONNECTED"); break; case SPI_ERROR_COPY: error("SPI_exec() failed: SPI_ERROR_COPY"); break; case SPI_ERROR_CURSOR: error("SPI_exec() failed: SPI_ERROR_CURSOR"); break; case SPI_ERROR_TRANSACTION: error("SPI_exec() failed: SPI_ERROR_TRANSACTION"); break; case SPI_ERROR_OPUNKNOWN: error("SPI_exec() failed: SPI_ERROR_OPUNKNOWN"); break; default: error("SPI_exec() failed: %d", spi_rc); break; } POP_PLERRCONTEXT; return result; } static SEXP rpgsql_get_results(int ntuples, SPITupleTable *tuptable) { SEXP result; ERRORCONTEXTCALLBACK; /* set up error context */ PUSH_PLERRCONTEXT(rsupport_error_callback, "rpgsql_get_results"); if (tuptable != NULL) { HeapTuple *tuples = tuptable->vals; TupleDesc tupdesc = tuptable->tupdesc; result = pg_tuple_get_r_frame(ntuples, tuples, tupdesc); } else result = R_NilValue; POP_PLERRCONTEXT; return result; } /* * plr_SPI_prepare - The builtin SPI_prepare command for the R interpreter */ SEXP plr_SPI_prepare(SEXP rsql, SEXP rargtypes) { const char *sql; int nargs; int i; Oid *typeids = NULL; Oid *typelems = NULL; FmgrInfo *typinfuncs = NULL; void *pplan = NULL; void *saved_plan; saved_plan_desc *plan_desc; SEXP result; MemoryContext oldcontext; PREPARE_PG_TRY; /* set up error context */ PUSH_PLERRCONTEXT(rsupport_error_callback, "pg.spi.prepare"); /* switch to long lived context to create plan description */ oldcontext = MemoryContextSwitchTo(TopMemoryContext); plan_desc = (saved_plan_desc *) palloc(sizeof(saved_plan_desc)); MemoryContextSwitchTo(oldcontext); PROTECT(rsql = AS_CHARACTER(rsql)); sql = CHAR(STRING_ELT(rsql, 0)); UNPROTECT(1); if (sql == NULL) error("%s", "cannot prepare empty query"); PROTECT(rargtypes = AS_INTEGER(rargtypes)); if (!isVector(rargtypes) || !isInteger(rargtypes)) error("%s", "second parameter must be a vector of PostgreSQL datatypes"); /* deal with case of no parameters for the prepared query */ if (rargtypes == R_MissingArg || INTEGER(rargtypes)[0] == NA_INTEGER) nargs = 0; else nargs = length(rargtypes); if (nargs < 0) /* can this even happen?? */ error("%s", "second parameter must be a vector of PostgreSQL datatypes"); if (nargs > 0) { /* switch to long lived context to create plan description elements */ oldcontext = MemoryContextSwitchTo(TopMemoryContext); typeids = (Oid *) palloc(nargs * sizeof(Oid)); typelems = (Oid *) palloc(nargs * sizeof(Oid)); typinfuncs = (FmgrInfo *) palloc(nargs * sizeof(FmgrInfo)); MemoryContextSwitchTo(oldcontext); for (i = 0; i < nargs; i++) { int16 typlen; bool typbyval; char typdelim; Oid typinput, typelem; char typalign; FmgrInfo typinfunc; typeids[i] = INTEGER(rargtypes)[i]; /* switch to long lived context to create plan description elements */ oldcontext = MemoryContextSwitchTo(TopMemoryContext); get_type_io_data(typeids[i], IOFunc_input, &typlen, &typbyval, &typalign, &typdelim, &typelem, &typinput); typelems[i] = get_element_type(typeids[i]); MemoryContextSwitchTo(oldcontext); /* perm_fmgr_info already uses TopMemoryContext */ perm_fmgr_info(typinput, &typinfunc); typinfuncs[i] = typinfunc; } } else typeids = NULL; UNPROTECT(1); /* switch to SPI memory context */ SWITCHTO_PLR_SPI_CONTEXT(oldcontext); /* * trap elog/ereport so we can let R finish up gracefully * and generate the error once we exit the interpreter */ PG_TRY(); { /* Prepare plan for query */ pplan = SPI_prepare(sql, nargs, typeids); } PLR_PG_CATCH(); PLR_PG_END_TRY(); if (pplan == NULL) { char buf[128]; char *reason; switch (SPI_result) { case SPI_ERROR_ARGUMENT: reason = "SPI_ERROR_ARGUMENT"; break; case SPI_ERROR_UNCONNECTED: reason = "SPI_ERROR_UNCONNECTED"; break; case SPI_ERROR_COPY: reason = "SPI_ERROR_COPY"; break; case SPI_ERROR_CURSOR: reason = "SPI_ERROR_CURSOR"; break; case SPI_ERROR_TRANSACTION: reason = "SPI_ERROR_TRANSACTION"; break; case SPI_ERROR_OPUNKNOWN: reason = "SPI_ERROR_OPUNKNOWN"; break; default: snprintf(buf, sizeof(buf), "unknown RC %d", SPI_result); reason = buf; break; } /* internal error */ error("SPI_prepare() failed: %s", reason); } /* SPI_saveplan already uses TopMemoryContext */ saved_plan = SPI_saveplan(pplan); if (saved_plan == NULL) { char buf[128]; char *reason; switch (SPI_result) { case SPI_ERROR_ARGUMENT: reason = "SPI_ERROR_ARGUMENT"; break; case SPI_ERROR_UNCONNECTED: reason = "SPI_ERROR_UNCONNECTED"; break; default: snprintf(buf, sizeof(buf), "unknown RC %d", SPI_result); reason = buf; break; } /* internal error */ error("SPI_saveplan() failed: %s", reason); } /* back to caller's memory context */ MemoryContextSwitchTo(oldcontext); /* no longer need this */ SPI_freeplan(pplan); plan_desc->saved_plan = saved_plan; plan_desc->nargs = nargs; plan_desc->typeids = typeids; plan_desc->typelems = typelems; plan_desc->typinfuncs = typinfuncs; result = R_MakeExternalPtr(plan_desc, R_NilValue, R_NilValue); POP_PLERRCONTEXT; return result; } /* * plr_SPI_execp - The builtin SPI_execp command for the R interpreter */ SEXP plr_SPI_execp(SEXP rsaved_plan, SEXP rargvalues) { saved_plan_desc *plan_desc = (saved_plan_desc *) R_ExternalPtrAddr(rsaved_plan); void *saved_plan = plan_desc->saved_plan; int nargs = plan_desc->nargs; Oid *typeids = plan_desc->typeids; Oid *typelems = plan_desc->typelems; FmgrInfo *typinfuncs = plan_desc->typinfuncs; int i; Datum *argvalues = NULL; char *nulls = NULL; bool isnull = false; SEXP obj; int spi_rc = 0; char buf[64]; int count = 0; int ntuples; SEXP result = NULL; MemoryContext oldcontext; PREPARE_PG_TRY; /* set up error context */ PUSH_PLERRCONTEXT(rsupport_error_callback, "pg.spi.execp"); if (nargs > 0) { if (!Rf_isVectorList(rargvalues)) error("%s", "second parameter must be a list of arguments " \ "to the prepared plan"); if (length(rargvalues) != nargs) error("list of arguments (%d) is not the same length " \ "as that of the prepared plan (%d)", length(rargvalues), nargs); argvalues = (Datum *) palloc(nargs * sizeof(Datum)); nulls = (char *) palloc(nargs * sizeof(char)); } for (i = 0; i < nargs; i++) { PROTECT(obj = VECTOR_ELT(rargvalues, i)); argvalues[i] = get_datum(obj, typeids[i], typelems[i], typinfuncs[i], &isnull); if (!isnull) nulls[i] = ' '; else nulls[i] = 'n'; UNPROTECT(1); } /* switch to SPI memory context */ SWITCHTO_PLR_SPI_CONTEXT(oldcontext); /* * trap elog/ereport so we can let R finish up gracefully * and generate the error once we exit the interpreter */ PG_TRY(); { /* Execute the plan */ spi_rc = SPI_execp(saved_plan, argvalues, nulls, count); } PLR_PG_CATCH(); PLR_PG_END_TRY(); /* back to caller's memory context */ MemoryContextSwitchTo(oldcontext); /* check the result */ switch (spi_rc) { case SPI_OK_UTILITY: snprintf(buf, sizeof(buf), "%d", 0); SPI_freetuptable(SPI_tuptable); PROTECT(result = NEW_CHARACTER(1)); SET_STRING_ELT(result, 0, COPY_TO_USER_STRING(buf)); UNPROTECT(1); break; case SPI_OK_SELINTO: case SPI_OK_INSERT: case SPI_OK_DELETE: case SPI_OK_UPDATE: snprintf(buf, sizeof(buf), "%d", SPI_processed); SPI_freetuptable(SPI_tuptable); PROTECT(result = NEW_CHARACTER(1)); SET_STRING_ELT(result, 0, COPY_TO_USER_STRING(buf)); UNPROTECT(1); break; case SPI_OK_SELECT: ntuples = SPI_processed; if (ntuples > 0) { result = rpgsql_get_results(ntuples, SPI_tuptable); SPI_freetuptable(SPI_tuptable); } else result = R_NilValue; break; case SPI_ERROR_ARGUMENT: error("SPI_execp() failed: SPI_ERROR_ARGUMENT"); break; case SPI_ERROR_UNCONNECTED: error("SPI_execp() failed: SPI_ERROR_UNCONNECTED"); break; case SPI_ERROR_COPY: error("SPI_execp() failed: SPI_ERROR_COPY"); break; case SPI_ERROR_CURSOR: error("SPI_execp() failed: SPI_ERROR_CURSOR"); break; case SPI_ERROR_TRANSACTION: error("SPI_execp() failed: SPI_ERROR_TRANSACTION"); break; case SPI_ERROR_OPUNKNOWN: error("SPI_execp() failed: SPI_ERROR_OPUNKNOWN"); break; default: error("SPI_execp() failed: %d", spi_rc); break; } POP_PLERRCONTEXT; return result; } /* * plr_SPI_lastoid - return the last oid. To be used after insert queries. */ SEXP plr_SPI_lastoid(void) { SEXP result; PROTECT(result = NEW_INTEGER(1)); INTEGER_DATA(result)[0] = SPI_lastoid; UNPROTECT(1); return result; } /* * Takes the prepared plan rsaved_plan and creates a cursor * for it using the values specified in ragvalues. * */ SEXP plr_SPI_cursor_open(SEXP cursor_name_arg,SEXP rsaved_plan, SEXP rargvalues) { saved_plan_desc *plan_desc = (saved_plan_desc *) R_ExternalPtrAddr(rsaved_plan); void *saved_plan = plan_desc->saved_plan; int nargs = plan_desc->nargs; Oid *typeids = plan_desc->typeids; FmgrInfo *typinfuncs = plan_desc->typinfuncs; int i; Datum *argvalues = NULL; char *nulls = NULL; bool isnull = false; SEXP obj; SEXP result = NULL; MemoryContext oldcontext; char cursor_name[64]; Portal portal=NULL; PREPARE_PG_TRY; PUSH_PLERRCONTEXT(rsupport_error_callback, "pg.spi.cursor_open"); /* Divide rargvalues */ if (nargs > 0) { if (!Rf_isVectorList(rargvalues)) error("%s", "second parameter must be a list of arguments " \ "to the prepared plan"); if (length(rargvalues) != nargs) error("list of arguments (%d) is not the same length " \ "as that of the prepared plan (%d)", length(rargvalues), nargs); argvalues = (Datum *) palloc(nargs * sizeof(Datum)); nulls = (char *) palloc(nargs * sizeof(char)); } for (i = 0; i < nargs; i++) { PROTECT(obj = VECTOR_ELT(rargvalues, i)); argvalues[i] = get_scalar_datum(obj, typeids[i], typinfuncs[i], &isnull); if (!isnull) nulls[i] = ' '; else nulls[i] = 'n'; UNPROTECT(1); } strncpy(cursor_name, CHAR(STRING_ELT(cursor_name_arg,0)), 64); /* switch to SPI memory context */ SWITCHTO_PLR_SPI_CONTEXT(oldcontext); /* * trap elog/ereport so we can let R finish up gracefully * and generate the error once we exit the interpreter */ PG_TRY(); { /* Open the cursor */ portal = SPI_cursor_open(cursor_name,saved_plan, argvalues, nulls,1); } PLR_PG_CATCH(); PLR_PG_END_TRY(); /* back to caller's memory context */ MemoryContextSwitchTo(oldcontext); if(portal==NULL) error("SPI_cursor_open() failed"); else result = R_MakeExternalPtr(portal, R_NilValue, R_NilValue); POP_PLERRCONTEXT; return result; } SEXP plr_SPI_cursor_fetch(SEXP cursor_in,SEXP forward_in, SEXP rows_in) { Portal portal=NULL; int ntuples; SEXP result = NULL; MemoryContext oldcontext; int forward; int rows; PREPARE_PG_TRY; PUSH_PLERRCONTEXT(rsupport_error_callback, "pg.spi.cursor_fetch"); portal = R_ExternalPtrAddr(cursor_in); if(!IS_LOGICAL(forward_in)) { error("pg.spi.cursor_fetch arg2 must be boolean"); return result; } if(!IS_INTEGER(rows_in)) { error("pg.spi.cursor_fetch arg3 must be an integer"); return result; } forward = LOGICAL_DATA(forward_in)[0]; rows = INTEGER_DATA(rows_in)[0]; /* switch to SPI memory context */ SWITCHTO_PLR_SPI_CONTEXT(oldcontext); PG_TRY(); { /* Open the cursor */ SPI_cursor_fetch(portal,forward,rows); } PLR_PG_CATCH(); PLR_PG_END_TRY(); /* back to caller's memory context */ MemoryContextSwitchTo(oldcontext); /* check the result */ ntuples = SPI_processed; if (ntuples > 0) { result = rpgsql_get_results(ntuples, SPI_tuptable); SPI_freetuptable(SPI_tuptable); } else result = R_NilValue; POP_PLERRCONTEXT; return result; } void plr_SPI_cursor_close(SEXP cursor_in) { Portal portal=NULL; MemoryContext oldcontext; PREPARE_PG_TRY; PUSH_PLERRCONTEXT(rsupport_error_callback, "pg.spi.cursor_close"); portal = R_ExternalPtrAddr(cursor_in); /* switch to SPI memory context */ SWITCHTO_PLR_SPI_CONTEXT(oldcontext); PG_TRY(); { /* Open the cursor */ SPI_cursor_close(portal); } PLR_PG_CATCH(); PLR_PG_END_TRY(); /* back to caller's memory context */ MemoryContextSwitchTo(oldcontext); } void plr_SPI_cursor_move(SEXP cursor_in,SEXP forward_in, SEXP rows_in) { Portal portal=NULL; MemoryContext oldcontext; int forward; int rows; PREPARE_PG_TRY; PUSH_PLERRCONTEXT(rsupport_error_callback, "pg.spi.cursor_move"); portal = R_ExternalPtrAddr(cursor_in); if(!IS_LOGICAL(forward_in)) { error("pg.spi.cursor_move arg2 must be boolean"); return; } if(!IS_INTEGER(rows_in)) { error("pg.spi.cursor_move arg3 must be an integer"); return; } forward = LOGICAL(forward_in)[0]; rows = INTEGER(rows_in)[0]; /* switch to SPI memory context */ SWITCHTO_PLR_SPI_CONTEXT(oldcontext); PG_TRY(); { /* Open the cursor */ SPI_cursor_move(portal, forward, rows); } PLR_PG_CATCH(); PLR_PG_END_TRY(); /* back to caller's memory context */ MemoryContextSwitchTo(oldcontext); } void throw_r_error(const char **msg) { if (msg && *msg) last_R_error_msg = pstrdup(*msg); else last_R_error_msg = pstrdup("caught error calling R function"); } /* * error context callback to let us supply a call-stack traceback */ static void rsupport_error_callback(void *arg) { if (arg) errcontext("In R support function %s", (char *) arg); } plr/plr.h0000775000000000000000000004054412465736645011355 0ustar rootroot/* * PL/R - PostgreSQL support for R as a * procedural language (PL) * * Copyright (c) 2003-2015 by Joseph E. Conway * ALL RIGHTS RESERVED * * Joe Conway * * Based on pltcl by Jan Wieck * and inspired by REmbeddedPostgres by * Duncan Temple Lang * http://www.omegahat.org/RSPostgres/ * * License: GPL version 2 or newer. http://www.gnu.org/copyleft/gpl.html * * This program 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. * * This program 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 this program; if not, write to the Free Software * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA * * plr.h */ #ifndef PLR_H #define PLR_H #define PLR_VERSION "08.03.00.16" #include "postgres.h" #include "fmgr.h" #include "funcapi.h" #include "miscadmin.h" #if PG_VERSION_NUM >= 80400 #include "windowapi.h" #endif #include "access/heapam.h" #if PG_VERSION_NUM >= 90300 #include "access/htup_details.h" #else #include "access/htup.h" #endif #include "catalog/catversion.h" #include "catalog/pg_language.h" #include "catalog/pg_namespace.h" #include "catalog/pg_proc.h" #include "catalog/pg_type.h" #include "commands/trigger.h" #include "executor/spi.h" #include "lib/stringinfo.h" #include "nodes/makefuncs.h" #include "optimizer/clauses.h" #include "parser/parse_type.h" #include "storage/ipc.h" #include "tcop/tcopprot.h" #include "utils/array.h" #include "utils/builtins.h" #if PG_VERSION_NUM >= 80500 #include "utils/bytea.h" #endif #include "utils/lsyscache.h" #include "utils/memutils.h" #include "utils/rel.h" #include "utils/syscache.h" #include "utils/typcache.h" #include #include #include #include #include /* * The R headers define various symbols that are also defined by the * Postgres headers, so undef them first to avoid conflicts. */ #ifdef ERROR #undef ERROR #endif #ifdef WARNING #undef WARNING #endif #include "R.h" #include "Rversion.h" /* * R version is calculated thus: * Maj * 65536 + Minor * 256 + Build * 1 * So: * version 1.8.0 results in: * (1 * 65536) + (8 * 256) + (0 * 1) == 67584 * version 1.9.0 results in: * (1 * 65536) + (9 * 256) + (0 * 1) == 67840 */ #if (R_VERSION >= 132096) /* R_VERSION >= 2.4.0 */ #include "Rembedded.h" #endif #if !defined(WIN32) && !defined(WIN64) #include "Rinterface.h" #else extern int R_SignalHandlers; #endif #include "Rinternals.h" #include "Rdefines.h" #if (R_VERSION < 133120) /* R_VERSION < 2.8.0 */ #include "Rdevices.h" #endif /* Restore the Postgres headers */ #ifdef ERROR #undef ERROR #endif #ifdef WARNING #undef WARNING #endif #define WARNING 19 #define ERROR 20 /* starting in R-2.7.0 this defn was removed from Rdevices.h */ #ifndef KillAllDevices #define KillAllDevices Rf_KillAllDevices #endif /* for some reason this is not in any R header files, it is locally defined */ #define INTEGER_ELT(x,__i__) INTEGER(x)[__i__] #ifndef R_HOME_DEFAULT #define R_HOME_DEFAULT "" #endif /* working with postgres 7.3 compatible sources */ #if !defined(PG_VERSION_NUM) || PG_VERSION_NUM < 80200 #error "This version of PL/R only builds with PostgreSQL 8.2 or later" #elif PG_VERSION_NUM < 80300 #define PG_VERSION_82_COMPAT #elif PG_VERSION_NUM < 80400 #define PG_VERSION_83_COMPAT #else #define PG_VERSION_84_COMPAT #endif #ifdef PG_VERSION_84_COMPAT #define HAVE_WINDOW_FUNCTIONS #endif #ifdef DEBUGPROTECT #undef PROTECT extern SEXP pg_protect(SEXP s, char *fn, int ln); #define PROTECT(s) pg_protect(s, __FILE__, __LINE__) #undef UNPROTECT extern void pg_unprotect(int n, char *fn, int ln); #define UNPROTECT(n) pg_unprotect(n, __FILE__, __LINE__) #endif /* DEBUGPROTECT */ #define xpfree(var_) \ do { \ if (var_ != NULL) \ { \ pfree(var_); \ var_ = NULL; \ } \ } while (0) #define freeStringInfo(mystr_) \ do { \ xpfree((mystr_)->data); \ xpfree(mystr_); \ } while (0) #define NEXT_STR_ELEMENT " %s" #if (R_VERSION < 67840) /* R_VERSION < 1.9.0 */ #define SET_COLUMN_NAMES \ do { \ int i; \ char *names_buf; \ names_buf = SPI_fname(tupdesc, j + 1); \ for (i = 0; i < strlen(names_buf); i++) { \ if (names_buf[i] == '_') \ names_buf[i] = '.'; \ } \ SET_STRING_ELT(names, df_colnum, mkChar(names_buf)); \ pfree(names_buf); \ } while (0) #else /* R_VERSION >= 1.9.0 */ #define SET_COLUMN_NAMES \ do { \ char *names_buf; \ names_buf = SPI_fname(tupdesc, j + 1); \ SET_STRING_ELT(names, df_colnum, mkChar(names_buf)); \ pfree(names_buf); \ } while (0) #endif #if (R_VERSION < 67584) /* R_VERSION < 1.8.0 */ /* * See the non-exported header file ${R_HOME}/src/include/Parse.h */ extern SEXP R_ParseVector(SEXP, int, int *); #define PARSE_NULL 0 #define PARSE_OK 1 #define PARSE_INCOMPLETE 2 #define PARSE_ERROR 3 #define PARSE_EOF 4 #define R_PARSEVECTOR(a_, b_, c_) R_ParseVector(a_, b_, c_) /* * See the non-exported header file ${R_HOME}/src/include/Defn.h */ extern void R_PreserveObject(SEXP); extern void R_ReleaseObject(SEXP); /* in main.c */ extern void R_dot_Last(void); /* in memory.c */ extern void R_RunExitFinalizers(void); #else /* R_VERSION >= 1.8.0 */ #include "R_ext/Parse.h" #if (R_VERSION >= 132352) /* R_VERSION >= 2.5.0 */ #define R_PARSEVECTOR(a_, b_, c_) R_ParseVector(a_, b_, (ParseStatus *) c_, R_NilValue) #else /* R_VERSION < 2.5.0 */ #define R_PARSEVECTOR(a_, b_, c_) R_ParseVector(a_, b_, (ParseStatus *) c_) #endif /* R_VERSION >= 2.5.0 */ #endif /* R_VERSION >= 1.8.0 */ /* convert C string to text pointer */ #define PG_TEXT_GET_STR(textp_) \ DatumGetCString(DirectFunctionCall1(textout, PointerGetDatum(textp_))) #define PG_STR_GET_TEXT(str_) \ DatumGetTextP(DirectFunctionCall1(textin, CStringGetDatum(str_))) #define PG_REPLACE_STR(str_, substr_, replacestr_) \ PG_TEXT_GET_STR(DirectFunctionCall3(replace_text, \ PG_STR_GET_TEXT(str_), \ PG_STR_GET_TEXT(substr_), \ PG_STR_GET_TEXT(replacestr_))) /* initial number of hash table entries for compiled functions */ #define FUNCS_PER_USER 64 #define ERRORCONTEXTCALLBACK \ ErrorContextCallback plerrcontext #define PUSH_PLERRCONTEXT(_error_callback_, _plr_error_funcname_) \ do { \ plerrcontext.callback = _error_callback_; \ plerrcontext.arg = (void *) pstrdup(_plr_error_funcname_); \ plerrcontext.previous = error_context_stack; \ error_context_stack = &plerrcontext; \ } while (0) #define POP_PLERRCONTEXT \ do { \ pfree(plerrcontext.arg); \ error_context_stack = plerrcontext.previous; \ } while (0) #define SAVE_PLERRCONTEXT \ ErrorContextCallback *ecs_save; \ do { \ ecs_save = error_context_stack; \ error_context_stack = NULL; \ } while (0) #define RESTORE_PLERRCONTEXT \ do { \ error_context_stack = ecs_save; \ } while (0) #ifndef TEXTARRAYOID #define TEXTARRAYOID 1009 #endif #define TRIGGER_NARGS 9 #define TUPLESTORE_BEGIN_HEAP tuplestore_begin_heap(true, false, work_mem) #define INIT_AUX_FMGR_ATTS \ do { \ finfo->fn_mcxt = plr_caller_context; \ finfo->fn_expr = (Node *) NULL; \ } while (0) #define PROARGTYPES(i) \ procStruct->proargtypes.values[i] #define FUNCARGTYPES(_tup_) \ ((Form_pg_proc) GETSTRUCT(_tup_))->proargtypes.values #define PLR_CLEANUP \ plr_cleanup(int code, Datum arg) #define TRIGGERTUPLEVARS \ HeapTuple tup; \ HeapTupleHeader dnewtup; \ HeapTupleHeader dtrigtup #define SET_INSERT_ARGS_567 \ do { \ arg[5] = DirectFunctionCall1(textin, CStringGetDatum("INSERT")); \ tup = trigdata->tg_trigtuple; \ dtrigtup = (HeapTupleHeader) palloc(tup->t_len); \ memcpy((char *) dtrigtup, (char *) tup->t_data, tup->t_len); \ HeapTupleHeaderSetDatumLength(dtrigtup, tup->t_len); \ HeapTupleHeaderSetTypeId(dtrigtup, tupdesc->tdtypeid); \ HeapTupleHeaderSetTypMod(dtrigtup, tupdesc->tdtypmod); \ arg[6] = PointerGetDatum(dtrigtup); \ argnull[6] = false; \ arg[7] = (Datum) 0; \ argnull[7] = true; \ } while (0) #define SET_DELETE_ARGS_567 \ do { \ arg[5] = DirectFunctionCall1(textin, CStringGetDatum("DELETE")); \ arg[6] = (Datum) 0; \ argnull[6] = true; \ tup = trigdata->tg_trigtuple; \ dtrigtup = (HeapTupleHeader) palloc(tup->t_len); \ memcpy((char *) dtrigtup, (char *) tup->t_data, tup->t_len); \ HeapTupleHeaderSetDatumLength(dtrigtup, tup->t_len); \ HeapTupleHeaderSetTypeId(dtrigtup, tupdesc->tdtypeid); \ HeapTupleHeaderSetTypMod(dtrigtup, tupdesc->tdtypmod); \ arg[7] = PointerGetDatum(dtrigtup); \ argnull[7] = false; \ } while (0) #define SET_UPDATE_ARGS_567 \ do { \ arg[5] = DirectFunctionCall1(textin, CStringGetDatum("UPDATE")); \ tup = trigdata->tg_newtuple; \ dnewtup = (HeapTupleHeader) palloc(tup->t_len); \ memcpy((char *) dnewtup, (char *) tup->t_data, tup->t_len); \ HeapTupleHeaderSetDatumLength(dnewtup, tup->t_len); \ HeapTupleHeaderSetTypeId(dnewtup, tupdesc->tdtypeid); \ HeapTupleHeaderSetTypMod(dnewtup, tupdesc->tdtypmod); \ arg[6] = PointerGetDatum(dnewtup); \ argnull[6] = false; \ tup = trigdata->tg_trigtuple; \ dtrigtup = (HeapTupleHeader) palloc(tup->t_len); \ memcpy((char *) dtrigtup, (char *) tup->t_data, tup->t_len); \ HeapTupleHeaderSetDatumLength(dtrigtup, tup->t_len); \ HeapTupleHeaderSetTypeId(dtrigtup, tupdesc->tdtypeid); \ HeapTupleHeaderSetTypMod(dtrigtup, tupdesc->tdtypmod); \ arg[7] = PointerGetDatum(dtrigtup); \ argnull[7] = false; \ } while (0) #define CONVERT_TUPLE_TO_DATAFRAME \ do { \ Oid tupType; \ int32 tupTypmod; \ TupleDesc tupdesc; \ HeapTuple tuple = palloc(sizeof(HeapTupleData)); \ HeapTupleHeader tuple_hdr = DatumGetHeapTupleHeader(arg[i]); \ tupType = HeapTupleHeaderGetTypeId(tuple_hdr); \ tupTypmod = HeapTupleHeaderGetTypMod(tuple_hdr); \ tupdesc = lookup_rowtype_tupdesc(tupType, tupTypmod); \ tuple->t_len = HeapTupleHeaderGetDatumLength(tuple_hdr); \ ItemPointerSetInvalid(&(tuple->t_self)); \ tuple->t_tableOid = InvalidOid; \ tuple->t_data = tuple_hdr; \ PROTECT(el = pg_tuple_get_r_frame(1, &tuple, tupdesc)); \ ReleaseTupleDesc(tupdesc); \ pfree(tuple); \ } while (0) #define GET_ARG_NAMES \ char **argnames; \ argnames = fetchArgNames(procTup, procStruct->pronargs) #define SET_ARG_NAME \ do { \ if (argnames && argnames[i] && argnames[i][0]) \ { \ appendStringInfo(proc_internal_args, "%s", argnames[i]); \ pfree(argnames[i]); \ } \ else \ appendStringInfo(proc_internal_args, "arg%d", i + 1); \ } while (0) #define SET_FRAME_ARG_NAME \ do { \ appendStringInfo(proc_internal_args, "farg%d", i + 1); \ } while (0) #define SET_FRAME_XARG_NAMES \ do { \ appendStringInfo(proc_internal_args, ",fnumrows,prownum"); \ } while (0) #define FREE_ARG_NAMES \ do { \ if (argnames) \ pfree(argnames); \ } while (0) #define PREPARE_PG_TRY \ ERRORCONTEXTCALLBACK #define SWITCHTO_PLR_SPI_CONTEXT(the_caller_context) \ the_caller_context = MemoryContextSwitchTo(plr_SPI_context) #define CLEANUP_PLR_SPI_CONTEXT(the_caller_context) \ MemoryContextSwitchTo(the_caller_context) #define PLR_PG_CATCH() \ PG_CATCH(); \ { \ MemoryContext temp_context; \ ErrorData *edata; \ SWITCHTO_PLR_SPI_CONTEXT(temp_context); \ edata = CopyErrorData(); \ MemoryContextSwitchTo(temp_context); \ error("error in SQL statement : %s", edata->message); \ } #define PLR_PG_END_TRY() \ PG_END_TRY() /* * structs */ typedef struct plr_func_hashkey { /* Hash lookup key for functions */ Oid funcOid; /* * For a trigger function, the OID of the relation triggered on is part * of the hashkey --- we want to compile the trigger separately for each * relation it is used with, in case the rowtype is different. Zero if * not called as a trigger. */ Oid trigrelOid; /* * We include actual argument types in the hash key to support * polymorphic PLpgSQL functions. Be careful that extra positions * are zeroed! */ Oid argtypes[FUNC_MAX_ARGS]; } plr_func_hashkey; /* The information we cache about loaded procedures */ typedef struct plr_function { char *proname; TransactionId fn_xmin; ItemPointerData fn_tid; plr_func_hashkey *fn_hashkey; /* back-link to hashtable key */ bool lanpltrusted; Oid result_typid; bool result_istuple; FmgrInfo result_in_func; Oid result_elem; FmgrInfo result_elem_in_func; int result_elem_typlen; bool result_elem_typbyval; char result_elem_typalign; int result_natts; Oid *result_fld_elem_typid; FmgrInfo *result_fld_elem_in_func; int *result_fld_elem_typlen; bool *result_fld_elem_typbyval; char *result_fld_elem_typalign; int nargs; Oid arg_typid[FUNC_MAX_ARGS]; bool arg_typbyval[FUNC_MAX_ARGS]; FmgrInfo arg_out_func[FUNC_MAX_ARGS]; Oid arg_elem[FUNC_MAX_ARGS]; FmgrInfo arg_elem_out_func[FUNC_MAX_ARGS]; int arg_elem_typlen[FUNC_MAX_ARGS]; bool arg_elem_typbyval[FUNC_MAX_ARGS]; char arg_elem_typalign[FUNC_MAX_ARGS]; int arg_is_rel[FUNC_MAX_ARGS]; SEXP fun; /* compiled R function */ #ifdef HAVE_WINDOW_FUNCTIONS bool iswindow; #endif } plr_function; /* compiled function hash table */ typedef struct plr_hashent { plr_func_hashkey key; plr_function *function; } plr_HashEnt; /* * external declarations */ /* libR interpreter initialization */ extern int Rf_initEmbeddedR(int argc, char **argv); /* PL/R language handler */ extern Datum plr_call_handler(PG_FUNCTION_ARGS); extern void PLR_CLEANUP; extern void plr_init(void); extern void plr_load_modules(void); extern void load_r_cmd(const char *cmd); extern SEXP call_r_func(SEXP fun, SEXP rargs); /* argument and return value conversion functions */ extern SEXP pg_scalar_get_r(Datum dvalue, Oid arg_typid, FmgrInfo arg_out_func); extern SEXP pg_array_get_r(Datum dvalue, FmgrInfo out_func, int typlen, bool typbyval, char typalign); extern SEXP pg_datum_array_get_r(Datum *elem_values, bool *elem_nulls, int numels, bool has_nulls, Oid element_type, FmgrInfo out_func, bool typbyval); extern SEXP pg_tuple_get_r_frame(int ntuples, HeapTuple *tuples, TupleDesc tupdesc); extern Datum r_get_pg(SEXP rval, plr_function *function, FunctionCallInfo fcinfo); extern Datum get_datum(SEXP rval, Oid typid, Oid typelem, FmgrInfo in_func, bool *isnull); extern Datum get_scalar_datum(SEXP rval, Oid result_typ, FmgrInfo result_in_func, bool *isnull); /* Postgres support functions installed into the R interpreter */ extern void throw_pg_notice(const char **msg); extern SEXP plr_quote_literal(SEXP rawstr); extern SEXP plr_quote_ident(SEXP rawstr); extern SEXP plr_SPI_exec(SEXP rsql); extern SEXP plr_SPI_prepare(SEXP rsql, SEXP rargtypes); extern SEXP plr_SPI_execp(SEXP rsaved_plan, SEXP rargvalues); extern SEXP plr_SPI_cursor_open(SEXP cursor_name_arg,SEXP rsaved_plan, SEXP rargvalues); extern SEXP plr_SPI_cursor_fetch(SEXP cursor_in,SEXP forward_in, SEXP rows_in); extern void plr_SPI_cursor_close(SEXP cursor_in); extern void plr_SPI_cursor_move(SEXP cursor_in, SEXP forward_in, SEXP rows_in); extern SEXP plr_SPI_lastoid(void); extern void throw_r_error(const char **msg); /* Postgres callable functions useful in conjunction with PL/R */ extern Datum plr_version(PG_FUNCTION_ARGS); extern Datum reload_plr_modules(PG_FUNCTION_ARGS); extern Datum install_rcmd(PG_FUNCTION_ARGS); extern Datum plr_array_push(PG_FUNCTION_ARGS); extern Datum plr_array(PG_FUNCTION_ARGS); extern Datum plr_array_accum(PG_FUNCTION_ARGS); extern Datum plr_environ(PG_FUNCTION_ARGS); extern Datum plr_set_rhome(PG_FUNCTION_ARGS); extern Datum plr_unset_rhome(PG_FUNCTION_ARGS); extern Datum plr_set_display(PG_FUNCTION_ARGS); extern Datum plr_get_raw(PG_FUNCTION_ARGS); /* Postgres backend support functions */ extern void compute_function_hashkey(FunctionCallInfo fcinfo, Form_pg_proc procStruct, plr_func_hashkey *hashkey); extern void plr_HashTableInit(void); extern plr_function *plr_HashTableLookup(plr_func_hashkey *func_key); extern void plr_HashTableInsert(plr_function *function, plr_func_hashkey *func_key); extern void plr_HashTableDelete(plr_function *function); extern char *get_load_self_ref_cmd(Oid funcid); extern void perm_fmgr_info(Oid functionId, FmgrInfo *finfo); #endif /* PLR_H */ plr/pg_conversion.c0000775000000000000000000013353412465736645013430 0ustar rootroot/* * PL/R - PostgreSQL support for R as a * procedural language (PL) * * Copyright (c) 2003-2015 by Joseph E. Conway * ALL RIGHTS RESERVED * * Joe Conway * * Based on pltcl by Jan Wieck * and inspired by REmbeddedPostgres by * Duncan Temple Lang * http://www.omegahat.org/RSPostgres/ * * License: GPL version 2 or newer. http://www.gnu.org/copyleft/gpl.html * * This program 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. * * This program 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 this program; if not, write to the Free Software * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA * * pg_conversion.c - functions for converting arguments from pg types to * R types, and for converting return values from R types * to pg types */ #include "plr.h" static void pg_get_one_r(char *value, Oid arg_out_fn_oid, SEXP *obj, int elnum); static SEXP get_r_vector(Oid typtype, int numels); static Datum get_trigger_tuple(SEXP rval, plr_function *function, FunctionCallInfo fcinfo, bool *isnull); static Datum get_tuplestore(SEXP rval, plr_function *function, FunctionCallInfo fcinfo, bool *isnull); static Datum get_simple_array_datum(SEXP rval, Oid typelem, bool *isnull); static Datum get_array_datum(SEXP rval, plr_function *function, int col, bool *isnull); static Datum get_frame_array_datum(SEXP rval, plr_function *function, int col, bool *isnull); static Datum get_md_array_datum(SEXP rval, int ndims, plr_function *function, int col, bool *isnull); static Datum get_generic_array_datum(SEXP rval, plr_function *function, int col, bool *isnull); static Tuplestorestate *get_frame_tuplestore(SEXP rval, plr_function *function, AttInMetadata *attinmeta, MemoryContext per_query_ctx, bool retset); static Tuplestorestate *get_matrix_tuplestore(SEXP rval, plr_function *function, AttInMetadata *attinmeta, MemoryContext per_query_ctx, bool retset); static Tuplestorestate *get_generic_tuplestore(SEXP rval, plr_function *function, AttInMetadata *attinmeta, MemoryContext per_query_ctx, bool retset); static SEXP coerce_to_char(SEXP rval); extern char *last_R_error_msg; /* * given a scalar pg value, convert to a one row R vector */ SEXP pg_scalar_get_r(Datum dvalue, Oid arg_typid, FmgrInfo arg_out_func) { SEXP result; /* add our value to it */ if (arg_typid != BYTEAOID) { char *value; value = DatumGetCString(FunctionCall3(&arg_out_func, dvalue, (Datum) 0, Int32GetDatum(-1))); /* get new vector of the appropriate type, length 1 */ PROTECT(result = get_r_vector(arg_typid, 1)); pg_get_one_r(value, arg_typid, &result, 0); UNPROTECT(1); } else { SEXP s, t, obj; int status; Datum dt_dvalue = PointerGetDatum(PG_DETOAST_DATUM(dvalue)); int bsize = VARSIZE((bytea *) dt_dvalue); PROTECT(obj = get_r_vector(arg_typid, bsize)); memcpy((char *) RAW(obj), VARDATA((bytea *) dt_dvalue), bsize); /* * Need to construct a call to * unserialize(rval) */ PROTECT(t = s = allocList(2)); SET_TYPEOF(s, LANGSXP); SETCAR(t, install("unserialize")); t = CDR(t); SETCAR(t, obj); PROTECT(result = R_tryEval(s, R_GlobalEnv, &status)); if(status != 0) { if (last_R_error_msg) ereport(ERROR, (errcode(ERRCODE_DATA_EXCEPTION), errmsg("R interpreter expression evaluation error"), errdetail("%s", last_R_error_msg))); else ereport(ERROR, (errcode(ERRCODE_DATA_EXCEPTION), errmsg("R interpreter expression evaluation error"), errdetail("R expression evaluation error caught in \"unserialize\"."))); } UNPROTECT(3); } return result; } /* * Given an array pg value, convert to a multi-row R vector. */ SEXP pg_array_get_r(Datum dvalue, FmgrInfo out_func, int typlen, bool typbyval, char typalign) { /* * Loop through and convert each scalar value. * Use the converted values to build an R vector. */ SEXP result; ArrayType *v; Oid element_type; int i, j, k, nitems, nr = 1, nc = 1, nz = 1, ndim, *dim; int elem_idx = 0; Datum *elem_values; bool *elem_nulls; bool fast_track_type; /* short-circuit for NULL datums */ if (dvalue == (Datum) NULL) return R_NilValue; v = DatumGetArrayTypeP(dvalue); ndim = ARR_NDIM(v); element_type = ARR_ELEMTYPE(v); dim = ARR_DIMS(v); nitems = ArrayGetNItems(ARR_NDIM(v), ARR_DIMS(v)); switch (element_type) { case INT4OID: case FLOAT8OID: fast_track_type = true; break; default: fast_track_type = false; } /* * Special case for pass-by-value data types, if the following conditions are met: * designated fast_track_type * no NULL elements * 1 dimensional array only * at least one element */ if (fast_track_type && typbyval && !ARR_HASNULL(v) && (ndim == 1) && (nitems > 0)) { char *p = ARR_DATA_PTR(v); /* get new vector of the appropriate type and length */ PROTECT(result = get_r_vector(element_type, nitems)); /* keep this in sync with switch above -- fast_track_type only */ switch (element_type) { case INT4OID: Assert(sizeof(int) == 4); memcpy(INTEGER_DATA(result), p, nitems * sizeof(int)); break; case FLOAT8OID: Assert(sizeof(double) == 8); memcpy(NUMERIC_DATA(result), p, nitems * sizeof(double)); break; default: /* Everything else is error */ ereport(ERROR, (errcode(ERRCODE_FEATURE_NOT_SUPPORTED), errmsg("direct array passthrough attempted for unsupported type"))); } if (ndim > 1) { SEXP matrix_dims; /* attach dimensions */ PROTECT(matrix_dims = allocVector(INTSXP, ndim)); for (i = 0; i < ndim; i++) INTEGER_DATA(matrix_dims)[i] = dim[i]; setAttrib(result, R_DimSymbol, matrix_dims); UNPROTECT(1); } UNPROTECT(1); /* result */ } else { deconstruct_array(v, element_type, typlen, typbyval, typalign, &elem_values, &elem_nulls, &nitems); /* array is empty */ if (nitems == 0) { PROTECT(result = get_r_vector(element_type, nitems)); UNPROTECT(1); return result; } if (ndim == 1) nr = nitems; else if (ndim == 2) { nr = dim[0]; nc = dim[1]; } else if (ndim == 3) { nr = dim[0]; nc = dim[1]; nz = dim[2]; } else ereport(ERROR, (errcode(ERRCODE_FEATURE_NOT_SUPPORTED), errmsg("greater than 3-dimensional arrays are not yet supported"))); /* get new vector of the appropriate type and length */ PROTECT(result = get_r_vector(element_type, nitems)); /* Convert all values to their R form and build the vector */ for (i = 0; i < nr; i++) { for (j = 0; j < nc; j++) { for (k = 0; k < nz; k++) { char *value; Datum itemvalue; bool isnull; int idx = (k * nr * nc) + (j * nr) + i; isnull = elem_nulls[elem_idx]; itemvalue = elem_values[elem_idx++]; if (!isnull) { value = DatumGetCString(FunctionCall3(&out_func, itemvalue, (Datum) 0, Int32GetDatum(-1))); } else value = NULL; /* * Note that pg_get_one_r() replaces NULL values with * the NA value appropriate for the data type. */ pg_get_one_r(value, element_type, &result, idx); if (value != NULL) pfree(value); } } } pfree(elem_values); pfree(elem_nulls); if (ndim > 1) { SEXP matrix_dims; /* attach dimensions */ PROTECT(matrix_dims = allocVector(INTSXP, ndim)); for (i = 0; i < ndim; i++) INTEGER_DATA(matrix_dims)[i] = dim[i]; setAttrib(result, R_DimSymbol, matrix_dims); UNPROTECT(1); } UNPROTECT(1); /* result */ } return result; } /* * Given an array pg datums, convert to a multi-row R vector. */ SEXP pg_datum_array_get_r(Datum *elem_values, bool *elem_nulls, int numels, bool has_nulls, Oid element_type, FmgrInfo out_func, bool typbyval) { /* * Loop through and convert each scalar value. * Use the converted values to build an R vector. */ SEXP result; int i; bool fast_track_type; switch (element_type) { case INT4OID: case FLOAT8OID: fast_track_type = true; break; default: fast_track_type = false; } /* * Special case for pass-by-value data types, if the following conditions are met: * designated fast_track_type * no NULL elements * 1 dimensional array only * at least one element */ if (fast_track_type && typbyval && !has_nulls && (numels > 0)) { SEXP matrix_dims; /* get new vector of the appropriate type and length */ PROTECT(result = get_r_vector(element_type, numels)); /* keep this in sync with switch above -- fast_track_type only */ switch (element_type) { case INT4OID: Assert(sizeof(int) == 4); memcpy(INTEGER_DATA(result), elem_values, numels * sizeof(int)); break; case FLOAT8OID: Assert(sizeof(double) == 8); memcpy(NUMERIC_DATA(result), elem_values, numels * sizeof(double)); break; default: /* Everything else is error */ ereport(ERROR, (errcode(ERRCODE_FEATURE_NOT_SUPPORTED), errmsg("direct array passthrough attempted for unsupported type"))); } /* attach dimensions */ PROTECT(matrix_dims = allocVector(INTSXP, 1)); INTEGER_DATA(matrix_dims)[0] = numels; setAttrib(result, R_DimSymbol, matrix_dims); UNPROTECT(1); UNPROTECT(1); /* result */ } else { SEXP matrix_dims; /* array is empty */ if (numels == 0) { PROTECT(result = get_r_vector(element_type, 0)); UNPROTECT(1); return result; } /* get new vector of the appropriate type and length */ PROTECT(result = get_r_vector(element_type, numels)); /* Convert all values to their R form and build the vector */ for (i = 0; i < numels; i++) { char *value; Datum itemvalue; bool isnull; isnull = elem_nulls[i]; itemvalue = elem_values[i]; if (!isnull) { value = DatumGetCString(FunctionCall3(&out_func, itemvalue, (Datum) 0, Int32GetDatum(-1))); } else value = NULL; /* * Note that pg_get_one_r() replaces NULL values with * the NA value appropriate for the data type. */ pg_get_one_r(value, element_type, &result, i); if (value != NULL) pfree(value); } /* attach dimensions */ PROTECT(matrix_dims = allocVector(INTSXP, 1)); INTEGER_DATA(matrix_dims)[0] = numels; setAttrib(result, R_DimSymbol, matrix_dims); UNPROTECT(1); UNPROTECT(1); /* result */ } return result; } /* * Given an array of pg tuples, convert to an R list * the created object is not quite actually a data.frame */ SEXP pg_tuple_get_r_frame(int ntuples, HeapTuple *tuples, TupleDesc tupdesc) { int nr = ntuples; int nc = tupdesc->natts; int nc_non_dropped = 0; int df_colnum = 0; int i = 0; int j = 0; Oid element_type; Oid typelem; SEXP names; SEXP row_names; char buf[256]; SEXP result; SEXP fldvec; if (tuples == NULL || ntuples < 1) return R_NilValue; /* Count non-dropped attributes so we can later ignore the dropped ones */ for (j = 0; j < nc; j++) { if (!tupdesc->attrs[j]->attisdropped) nc_non_dropped++; } /* * Allocate the data.frame initially as a list, * and also allocate a names vector for the column names */ PROTECT(result = NEW_LIST(nc_non_dropped)); PROTECT(names = NEW_CHARACTER(nc_non_dropped)); /* * Loop by columns */ for (j = 0; j < nc; j++) { int16 typlen; bool typbyval; char typdelim; Oid typoutput, typioparam; FmgrInfo outputproc; char typalign; /* ignore dropped attributes */ if (tupdesc->attrs[j]->attisdropped) continue; /* set column name */ SET_COLUMN_NAMES; /* get column datatype oid */ element_type = SPI_gettypeid(tupdesc, j + 1); /* * Check to see if it is an array type. get_element_type will return * InvalidOid instead of actual element type if the type is not a * varlena array. */ typelem = get_element_type(element_type); /* get new vector of the appropriate type and length */ if (typelem == InvalidOid) PROTECT(fldvec = get_r_vector(element_type, nr)); else { PROTECT(fldvec = NEW_LIST(nr)); get_type_io_data(typelem, IOFunc_output, &typlen, &typbyval, &typalign, &typdelim, &typioparam, &typoutput); fmgr_info(typoutput, &outputproc); } /* loop rows for this column */ for (i = 0; i < nr; i++) { if (typelem == InvalidOid) { /* not an array type */ char *value; value = SPI_getvalue(tuples[i], tupdesc, j + 1); pg_get_one_r(value, element_type, &fldvec, i); } else { /* array type */ Datum dvalue; bool isnull; SEXP fldvec_elem; dvalue = SPI_getbinval(tuples[i], tupdesc, j + 1, &isnull); if (!isnull) PROTECT(fldvec_elem = pg_array_get_r(dvalue, outputproc, typlen, typbyval, typalign)); else PROTECT(fldvec_elem = R_NilValue); SET_VECTOR_ELT(fldvec, i, fldvec_elem); UNPROTECT(1); } } SET_VECTOR_ELT(result, df_colnum, fldvec); UNPROTECT(1); df_colnum++; } /* attach the column names */ setAttrib(result, R_NamesSymbol, names); /* attach row names - basically just the row number, zero based */ PROTECT(row_names = allocVector(STRSXP, nr)); for (i=0; i use R INTEGER */ PROTECT(result = NEW_INTEGER(numels)); break; case INT8OID: case FLOAT4OID: case FLOAT8OID: case CASHOID: case NUMERICOID: /* * Other numeric types => use R REAL * Note pgsql int8 is mapped to R REAL * because R INTEGER is only 4 byte */ PROTECT(result = NEW_NUMERIC(numels)); break; case BOOLOID: PROTECT(result = NEW_LOGICAL(numels)); break; case BYTEAOID: PROTECT(result = NEW_RAW(numels)); break; default: /* Everything else is defaulted to string */ PROTECT(result = NEW_CHARACTER(numels)); } UNPROTECT(1); return result; } /* * given a single non-array pg value, convert to its R value representation */ static void pg_get_one_r(char *value, Oid typtype, SEXP *obj, int elnum) { switch (typtype) { case OIDOID: case INT2OID: case INT4OID: /* 2 and 4 byte integer pgsql datatype => use R INTEGER */ if (value) INTEGER_DATA(*obj)[elnum] = atoi(value); else INTEGER_DATA(*obj)[elnum] = NA_INTEGER; break; case INT8OID: case FLOAT4OID: case FLOAT8OID: case CASHOID: case NUMERICOID: /* * Other numeric types => use R REAL * Note pgsql int8 is mapped to R REAL * because R INTEGER is only 4 byte */ if (value) NUMERIC_DATA(*obj)[elnum] = atof(value); else NUMERIC_DATA(*obj)[elnum] = NA_REAL; break; case BOOLOID: if (value) LOGICAL_DATA(*obj)[elnum] = ((*value == 't') ? 1 : 0); else LOGICAL_DATA(*obj)[elnum] = NA_LOGICAL; break; default: /* Everything else is defaulted to string */ if (value) SET_STRING_ELT(*obj, elnum, COPY_TO_USER_STRING(value)); else SET_STRING_ELT(*obj, elnum, NA_STRING); } } /* * given an R value, convert to its pg representation */ Datum r_get_pg(SEXP rval, plr_function *function, FunctionCallInfo fcinfo) { bool isnull = false; Datum result; if (function->result_typid != BYTEAOID && (TYPEOF(rval) == CLOSXP || TYPEOF(rval) == PROMSXP || TYPEOF(rval) == LANGSXP || TYPEOF(rval) == ENVSXP)) ereport(ERROR, (errcode(ERRCODE_DATA_EXCEPTION), errmsg("incorrect function return type"), errdetail("R return value type cannot be mapped to PostgreSQL return type."), errhint("Try BYTEA as the PostgreSQL return type."))); if (CALLED_AS_TRIGGER(fcinfo)) result = get_trigger_tuple(rval, function, fcinfo, &isnull); else if (function->result_istuple || fcinfo->flinfo->fn_retset) result = get_tuplestore(rval, function, fcinfo, &isnull); else { /* short circuit if return value is Null */ if (rval == R_NilValue || isNull(rval)) /* probably redundant */ { fcinfo->isnull = true; return (Datum) 0; } if (function->result_elem == 0) result = get_scalar_datum(rval, function->result_typid, function->result_in_func, &isnull); else result = get_array_datum(rval, function, 0, &isnull); } if (isnull) fcinfo->isnull = true; return result; } /* * Similar to r_get_pg, given an R value, convert to its pg representation * Other than scalar, currently only prepared to be used with simple 1D vector */ Datum get_datum(SEXP rval, Oid typid, Oid typelem, FmgrInfo in_func, bool *isnull) { Datum result; /* short circuit if return value is Null */ if (rval == R_NilValue || isNull(rval)) /* probably redundant */ { *isnull = true; return (Datum) 0; } if (typelem == InvalidOid) result = get_scalar_datum(rval, typid, in_func, isnull); else result = get_simple_array_datum(rval, typelem, isnull); return result; } static Datum get_trigger_tuple(SEXP rval, plr_function *function, FunctionCallInfo fcinfo, bool *isnull) { TriggerData *trigdata = (TriggerData *) fcinfo->context; TupleDesc tupdesc = trigdata->tg_relation->rd_att; AttInMetadata *attinmeta; MemoryContext fn_mcxt; MemoryContext oldcontext; int nc; int nr; char **values; HeapTuple tuple = NULL; int i, j; int nc_dropped = 0; int df_colnum = 0; SEXP result; SEXP dfcol; /* short circuit statement level trigger which always returns NULL */ if (TRIGGER_FIRED_FOR_STATEMENT(trigdata->tg_event)) { /* special for triggers, don't set isnull flag */ *isnull = false; return (Datum) 0; } /* short circuit if return value is Null */ if (rval == R_NilValue || isNull(rval)) /* probably redundant */ { /* special for triggers, don't set isnull flag */ *isnull = false; return (Datum) 0; } if (isFrame(rval)) nc = length(rval); else if (isMatrix(rval)) nc = ncols(rval); else nc = 1; PROTECT(dfcol = VECTOR_ELT(rval, 0)); nr = length(dfcol); UNPROTECT(1); if (nr != 1) ereport(ERROR, (errcode(ERRCODE_DATA_EXCEPTION), errmsg("incorrect function return type"), errdetail("function return value cannot have more " \ "than one row"))); /* * Count number of dropped attributes so we can add them back to * the return tuple */ for (j = 0; j < nc; j++) { if (tupdesc->attrs[j]->attisdropped) nc_dropped++; } /* * Check to make sure we have the same number of columns * to return as there are attributes in the return tuple. * Note that we have to account for the number of dropped * columns. * * Note we will attempt to coerce the R values into whatever * the return attribute type is and depend on the "in" * function to complain if needed. */ if (nc + nc_dropped != tupdesc->natts) ereport(ERROR, (errcode(ERRCODE_DATATYPE_MISMATCH), errmsg("returned tuple structure does not match table " \ "of trigger event"))); fn_mcxt = fcinfo->flinfo->fn_mcxt; oldcontext = MemoryContextSwitchTo(fn_mcxt); attinmeta = TupleDescGetAttInMetadata(tupdesc); /* coerce columns to character in advance */ PROTECT(result = NEW_LIST(nc)); for (j = 0; j < nc; j++) { PROTECT(dfcol = VECTOR_ELT(rval, j)); if(!isFactor(dfcol)) { SEXP obj; PROTECT(obj = coerce_to_char(dfcol)); SET_VECTOR_ELT(result, j, obj); UNPROTECT(1); } else { SEXP t; for (t = ATTRIB(dfcol); t != R_NilValue; t = CDR(t)) { if(TAG(t) == R_LevelsSymbol) { PROTECT(SETCAR(t, coerce_to_char(CAR(t)))); UNPROTECT(1); break; } } SET_VECTOR_ELT(result, j, dfcol); } UNPROTECT(1); } values = (char **) palloc((nc + nc_dropped) * sizeof(char *)); for(i = 0; i < nr; i++) { for (j = 0; j < nc + nc_dropped; j++) { /* insert NULL for dropped attributes */ if (tupdesc->attrs[j]->attisdropped) values[j] = NULL; else { PROTECT(dfcol = VECTOR_ELT(result, df_colnum)); if(isFactor(dfcol)) { SEXP t; for (t = ATTRIB(dfcol); t != R_NilValue; t = CDR(t)) { if(TAG(t) == R_LevelsSymbol) { SEXP obj; int idx = INTEGER(dfcol)[i] - 1; PROTECT(obj = CAR(t)); values[j] = pstrdup(CHAR(STRING_ELT(obj, idx))); UNPROTECT(1); break; } } } else { if (STRING_ELT(dfcol, 0) != NA_STRING) values[j] = pstrdup(CHAR(STRING_ELT(dfcol, i))); else values[j] = NULL; } UNPROTECT(1); df_colnum++; } } /* construct the tuple */ tuple = BuildTupleFromCStrings(attinmeta, values); for (j = 0; j < nc; j++) if (values[j] != NULL) pfree(values[j]); } UNPROTECT(1); MemoryContextSwitchTo(oldcontext); if (tuple) { *isnull = false; return PointerGetDatum(tuple); } else { /* special for triggers, don't set isnull flag */ *isnull = false; return (Datum) 0; } } static Datum get_tuplestore(SEXP rval, plr_function *function, FunctionCallInfo fcinfo, bool *isnull) { bool retset = fcinfo->flinfo->fn_retset; ReturnSetInfo *rsinfo = (ReturnSetInfo *) fcinfo->resultinfo; TupleDesc tupdesc; AttInMetadata *attinmeta; MemoryContext per_query_ctx; MemoryContext oldcontext; int nc; /* check to see if caller supports us returning a tuplestore */ if (!rsinfo || !(rsinfo->allowedModes & SFRM_Materialize)) ereport(ERROR, (errcode(ERRCODE_SYNTAX_ERROR), errmsg("materialize mode required, but it is not " "allowed in this context"))); if (isFrame(rval)) nc = length(rval); else if (isList(rval) || isNewList(rval)) nc = length(rval); else if (isMatrix(rval)) nc = ncols(rval); else nc = 1; per_query_ctx = rsinfo->econtext->ecxt_per_query_memory; oldcontext = MemoryContextSwitchTo(per_query_ctx); /* get the requested return tuple description */ tupdesc = CreateTupleDescCopy(rsinfo->expectedDesc); /* * Check to make sure we have the same number of columns * to return as there are attributes in the return tuple. * * Note we will attempt to coerce the R values into whatever * the return attribute type is and depend on the "in" * function to complain if needed. */ if (nc != tupdesc->natts) ereport(ERROR, (errcode(ERRCODE_SYNTAX_ERROR), errmsg("query-specified return tuple and " "function returned data.frame are not compatible"))); attinmeta = TupleDescGetAttInMetadata(tupdesc); /* OK, go to work */ rsinfo->returnMode = SFRM_Materialize; if (isFrame(rval)) rsinfo->setResult = get_frame_tuplestore(rval, function, attinmeta, per_query_ctx, retset); else if (isList(rval) || isNewList(rval)) rsinfo->setResult = get_frame_tuplestore(rval, function, attinmeta, per_query_ctx, retset); else if (isMatrix(rval)) rsinfo->setResult = get_matrix_tuplestore(rval, function, attinmeta, per_query_ctx, retset); else rsinfo->setResult = get_generic_tuplestore(rval, function, attinmeta, per_query_ctx, retset); /* * SFRM_Materialize mode expects us to return a NULL Datum. The actual * tuples are in our tuplestore and passed back through * rsinfo->setResult. rsinfo->setDesc is set to the tuple description * that we actually used to build our tuples with, so the caller can * verify we did what it was expecting. */ rsinfo->setDesc = tupdesc; MemoryContextSwitchTo(oldcontext); *isnull = true; return (Datum) 0; } Datum get_scalar_datum(SEXP rval, Oid result_typid, FmgrInfo result_in_func, bool *isnull) { Datum dvalue; SEXP obj; const char *value; /* * Element type is zero, we don't have an array, so coerce to string * and take the first element as a scalar * * Exception: if result type is BYTEA, we want to return the whole * object in serialized form */ if (result_typid != BYTEAOID) { PROTECT(obj = coerce_to_char(rval)); if (STRING_ELT(obj, 0) == NA_STRING) { UNPROTECT(1); *isnull = true; dvalue = (Datum) 0; return dvalue; } value = CHAR(STRING_ELT(obj, 0)); UNPROTECT(1); if (value != NULL) { dvalue = FunctionCall3(&result_in_func, CStringGetDatum(value), ObjectIdGetDatum(0), Int32GetDatum(-1)); } else { *isnull = true; dvalue = (Datum) 0; } } else { SEXP s, t; int len, rsize, status; bytea *result; char *rptr; /* * Need to construct a call to * serialize(rval, NULL) */ PROTECT(t = s = allocList(3)); SET_TYPEOF(s, LANGSXP); SETCAR(t, install("serialize")); t = CDR(t); SETCAR(t, rval); t = CDR(t); SETCAR(t, R_NilValue); PROTECT(obj = R_tryEval(s, R_GlobalEnv, &status)); if(status != 0) { if (last_R_error_msg) ereport(ERROR, (errcode(ERRCODE_DATA_EXCEPTION), errmsg("R interpreter expression evaluation error"), errdetail("%s", last_R_error_msg))); else ereport(ERROR, (errcode(ERRCODE_DATA_EXCEPTION), errmsg("R interpreter expression evaluation error"), errdetail("R expression evaluation error caught in \"serialize\"."))); } len = LENGTH(obj); rsize = VARHDRSZ + len; result = (bytea *) palloc(rsize); SET_VARSIZE(result, rsize); rptr = VARDATA(result); memcpy(rptr, (char *) RAW(obj), rsize - VARHDRSZ); UNPROTECT(2); dvalue = PointerGetDatum(result); } return dvalue; } static Datum get_array_datum(SEXP rval, plr_function *function, int col, bool *isnull) { SEXP rdims; int ndims; int objlen = length(rval); if (objlen > 0) { /* two supported special cases */ if (isFrame(rval)) return get_frame_array_datum(rval, function, col, isnull); else if (isMatrix(rval)) return get_md_array_datum(rval, 2 /* matrix is 2D */, function, col, isnull); PROTECT(rdims = getAttrib(rval, R_DimSymbol)); ndims = length(rdims); UNPROTECT(1); /* 2D and 3D arrays are specifically supported too */ if (ndims == 2 || ndims == 3) return get_md_array_datum(rval, ndims, function, col, isnull); /* everything else */ return get_generic_array_datum(rval, function, col, isnull); } else { /* create an empty array */ return PointerGetDatum(construct_empty_array(function->result_elem)); } } static Datum get_frame_array_datum(SEXP rval, plr_function *function, int col, bool *isnull) { Datum dvalue; SEXP obj; const char *value; Oid result_elem; FmgrInfo in_func; int typlen; bool typbyval; char typalign; int i; Datum *dvalues = NULL; ArrayType *array; int nr = 0; int nc = length(rval); #define FIXED_NUM_DIMS 2 int ndims = FIXED_NUM_DIMS; int dims[FIXED_NUM_DIMS]; int lbs[FIXED_NUM_DIMS]; #undef FIXED_NUM_DIMS int idx; SEXP dfcol = NULL; int j; bool *nulls = NULL; bool have_nulls = FALSE; if (nc < 1) /* internal error */ elog(ERROR, "plr: bad internal representation of data.frame"); if (function->result_istuple) { result_elem = function->result_fld_elem_typid[col]; in_func = function->result_fld_elem_in_func[col]; typlen = function->result_fld_elem_typlen[col]; typbyval = function->result_fld_elem_typbyval[col]; typalign = function->result_fld_elem_typalign[col]; } else { result_elem = function->result_elem; in_func = function->result_elem_in_func; typlen = function->result_elem_typlen; typbyval = function->result_elem_typbyval; typalign = function->result_elem_typalign; } for (j = 0; j < nc; j++) { if (TYPEOF(rval) == VECSXP) PROTECT(dfcol = VECTOR_ELT(rval, j)); else if (TYPEOF(rval) == LISTSXP) { PROTECT(dfcol = CAR(rval)); rval = CDR(rval); } else /* internal error */ elog(ERROR, "plr: bad internal representation of data.frame"); /* * Not sure about this test. Need to reliably detect * factors and do the alternative assignment ONLY for them. * For the moment this locution seems to work correctly. */ if (ATTRIB(dfcol) == R_NilValue || TYPEOF(CAR(ATTRIB(dfcol))) != STRSXP) PROTECT(obj = coerce_to_char(dfcol)); else PROTECT(obj = coerce_to_char(CAR(ATTRIB(dfcol)))); if (j == 0) { nr = length(obj); dvalues = (Datum *) palloc(nr * nc * sizeof(Datum)); nulls = (bool *) palloc(nr * nc * sizeof(bool)); } for(i = 0; i < nr; i++) { value = CHAR(STRING_ELT(obj, i)); idx = ((i * nc) + j); if (STRING_ELT(obj, i) == NA_STRING || value == NULL) { nulls[idx] = TRUE; have_nulls = TRUE; } else { nulls[idx] = FALSE; dvalues[idx] = FunctionCall3(&in_func, CStringGetDatum(value), (Datum) 0, Int32GetDatum(-1)); } } UNPROTECT(2); } dims[0] = nr; dims[1] = nc; lbs[0] = 1; lbs[1] = 1; if (!have_nulls) array = construct_md_array(dvalues, NULL, ndims, dims, lbs, result_elem, typlen, typbyval, typalign); else array = construct_md_array(dvalues, nulls, ndims, dims, lbs, result_elem, typlen, typbyval, typalign); dvalue = PointerGetDatum(array); return dvalue; } /* return simple, one dimensional array */ static Datum get_simple_array_datum(SEXP rval, Oid typelem, bool *isnull) { Datum dvalue; SEXP obj; SEXP rdims; const char *value; int16 typlen; bool typbyval; char typdelim; Oid typinput, typioparam; FmgrInfo in_func; char typalign; int i; Datum *dvalues = NULL; ArrayType *array; int nitems; int *dims; int *lbs; bool *nulls; bool have_nulls = FALSE; int ndims = 1; dims = palloc(ndims * sizeof(int)); lbs = palloc(ndims * sizeof(int)); /* * get the element type's in_func */ get_type_io_data(typelem, IOFunc_output, &typlen, &typbyval, &typalign, &typdelim, &typioparam, &typinput); perm_fmgr_info(typinput, &in_func); PROTECT(rdims = getAttrib(rval, R_DimSymbol)); if (length(rdims) > 1) ereport(ERROR, (errcode(ERRCODE_FEATURE_NOT_SUPPORTED), errmsg("greater than 1-dimensional arrays are " \ "not supported in this context"))); dims[0] = INTEGER(rdims)[0]; lbs[0] = 1; UNPROTECT(1); nitems = dims[0]; if (nitems == 0) { *isnull = true; return (Datum) 0; } dvalues = (Datum *) palloc(nitems * sizeof(Datum)); nulls = (bool *) palloc(nitems * sizeof(bool)); PROTECT(obj = coerce_to_char(rval)); for (i = 0; i < nitems; i++) { value = CHAR(STRING_ELT(obj, i)); if (STRING_ELT(obj, i) == NA_STRING || value == NULL) { nulls[i] = TRUE; have_nulls = TRUE; } else { nulls[i] = FALSE; dvalues[i] = FunctionCall3(&in_func, CStringGetDatum(value), (Datum) 0, Int32GetDatum(-1)); } } UNPROTECT(1); if (!have_nulls) array = construct_md_array(dvalues, NULL, ndims, dims, lbs, typelem, typlen, typbyval, typalign); else array = construct_md_array(dvalues, nulls, ndims, dims, lbs, typelem, typlen, typbyval, typalign); dvalue = PointerGetDatum(array); return dvalue; } static Datum get_md_array_datum(SEXP rval, int ndims, plr_function *function, int col, bool *isnull) { Datum dvalue; SEXP obj; SEXP rdims; const char *value; Oid result_elem; FmgrInfo in_func; int typlen; bool typbyval; char typalign; int i, j, k; Datum *dvalues = NULL; ArrayType *array; int nitems; int nr = 1; int nc = 1; int nz = 1; int *dims; int *lbs; int idx; int cntr = 0; bool *nulls; bool have_nulls = FALSE; if (ndims > 0) { dims = palloc(ndims * sizeof(int)); lbs = palloc(ndims * sizeof(int)); } else { dims = NULL; lbs = NULL; } if (function->result_istuple) { result_elem = function->result_fld_elem_typid[col]; in_func = function->result_fld_elem_in_func[col]; typlen = function->result_fld_elem_typlen[col]; typbyval = function->result_fld_elem_typbyval[col]; typalign = function->result_fld_elem_typalign[col]; } else { result_elem = function->result_elem; in_func = function->result_elem_in_func; typlen = function->result_elem_typlen; typbyval = function->result_elem_typbyval; typalign = function->result_elem_typalign; } PROTECT(rdims = getAttrib(rval, R_DimSymbol)); for(i = 0; i < ndims; i++) { dims[i] = INTEGER(rdims)[i]; lbs[i] = 1; switch (i) { case 0: nr = dims[i]; break; case 1: nc = dims[i]; break; case 2: nz = dims[i]; break; default: /* anything higher is currently unsupported */ ereport(ERROR, (errcode(ERRCODE_FEATURE_NOT_SUPPORTED), errmsg("greater than 3-dimensional arrays are " \ "not yet supported"))); } } UNPROTECT(1); nitems = nr * nc * nz; dvalues = (Datum *) palloc(nitems * sizeof(Datum)); nulls = (bool *) palloc(nitems * sizeof(bool)); PROTECT(obj = coerce_to_char(rval)); for (i = 0; i < nr; i++) { for (j = 0; j < nc; j++) { for (k = 0; k < nz; k++) { int arridx = cntr++; idx = (k * nr * nc) + (j * nr) + i; value = CHAR(STRING_ELT(obj, idx)); if (STRING_ELT(obj, idx) == NA_STRING || value == NULL) { nulls[arridx] = TRUE; have_nulls = TRUE; } else { nulls[arridx] = FALSE; dvalues[arridx] = FunctionCall3(&in_func, CStringGetDatum(value), (Datum) 0, Int32GetDatum(-1)); } } } } UNPROTECT(1); if (!have_nulls) array = construct_md_array(dvalues, NULL, ndims, dims, lbs, result_elem, typlen, typbyval, typalign); else array = construct_md_array(dvalues, nulls, ndims, dims, lbs, result_elem, typlen, typbyval, typalign); dvalue = PointerGetDatum(array); return dvalue; } static Datum get_generic_array_datum(SEXP rval, plr_function *function, int col, bool *isnull) { int objlen = length(rval); Datum dvalue; SEXP obj; const char *value; Oid result_elem; FmgrInfo in_func; int typlen; bool typbyval; char typalign; int i; Datum *dvalues = NULL; ArrayType *array; #define FIXED_NUM_DIMS 1 int ndims = FIXED_NUM_DIMS; int dims[FIXED_NUM_DIMS]; int lbs[FIXED_NUM_DIMS]; #undef FIXED_NUM_DIMS bool *nulls; bool have_nulls = FALSE; bool fast_track_type; bool has_na = false; if (function->result_istuple) { result_elem = function->result_fld_elem_typid[col]; in_func = function->result_fld_elem_in_func[col]; typlen = function->result_fld_elem_typlen[col]; typbyval = function->result_fld_elem_typbyval[col]; typalign = function->result_fld_elem_typalign[col]; } else { result_elem = function->result_elem; in_func = function->result_elem_in_func; typlen = function->result_elem_typlen; typbyval = function->result_elem_typbyval; typalign = function->result_elem_typalign; } /* * Special case for pass-by-value data types, if the following conditions are met: * designated fast_track_type * no NULL/NA elements */ if (TYPEOF(rval) == INTSXP || TYPEOF(rval) == REALSXP) { switch (TYPEOF(rval)) { case INTSXP: if (result_elem == INT4OID) fast_track_type = true; else fast_track_type = false; for (i = 0; i < objlen; i++) { if (INTEGER(rval)[i] == NA_INTEGER) { has_na = true; break; } } break; case REALSXP: if (result_elem == FLOAT8OID) fast_track_type = true; else fast_track_type = false; for (i = 0; i < objlen; i++) { if (ISNAN(REAL(rval)[i])) { has_na = true; break; } } break; default: fast_track_type = false; has_na = true; /* does not really matter in this case */ } } else { fast_track_type = false; has_na = true; /* does not really matter in this case */ } if (fast_track_type && typbyval && !has_na) { int32 nbytes = 0; int32 dataoffset; if (TYPEOF(rval) == INTSXP) { nbytes = objlen * sizeof(INTEGER_DATA(rval)); dvalues = (Datum *) INTEGER_DATA(rval); } else if (TYPEOF(rval) == REALSXP) { nbytes = objlen * sizeof(NUMERIC_DATA(rval)); dvalues = (Datum *) NUMERIC_DATA(rval); } else elog(ERROR, "attempted to passthrough invalid R datatype to Postgresql"); dims[0] = objlen; lbs[0] = 1; dataoffset = 0; /* marker for no null bitmap */ array = (ArrayType *) palloc0(nbytes + ARR_OVERHEAD_NONULLS(ndims)); SET_VARSIZE(array, nbytes + ARR_OVERHEAD_NONULLS(ndims)); array->ndim = ndims; array->dataoffset = dataoffset; array->elemtype = result_elem; memcpy(ARR_DIMS(array), dims, ndims * sizeof(int)); memcpy(ARR_LBOUND(array), lbs, ndims * sizeof(int)); memcpy(ARR_DATA_PTR(array), dvalues, nbytes); dvalue = PointerGetDatum(array); } else { /* original code */ dvalues = (Datum *) palloc(objlen * sizeof(Datum)); nulls = (bool *) palloc(objlen * sizeof(bool)); PROTECT(obj = coerce_to_char(rval)); /* Loop is needed here as result value might be of length > 1 */ for(i = 0; i < objlen; i++) { value = CHAR(STRING_ELT(obj, i)); if (STRING_ELT(obj, i) == NA_STRING || value == NULL) { nulls[i] = TRUE; have_nulls = TRUE; } else { nulls[i] = FALSE; dvalues[i] = FunctionCall3(&in_func, CStringGetDatum(value), (Datum) 0, Int32GetDatum(-1)); } } UNPROTECT(1); dims[0] = objlen; lbs[0] = 1; if (!have_nulls) array = construct_md_array(dvalues, NULL, ndims, dims, lbs, result_elem, typlen, typbyval, typalign); else array = construct_md_array(dvalues, nulls, ndims, dims, lbs, result_elem, typlen, typbyval, typalign); dvalue = PointerGetDatum(array); } return dvalue; } static Tuplestorestate * get_frame_tuplestore(SEXP rval, plr_function *function, AttInMetadata *attinmeta, MemoryContext per_query_ctx, bool retset) { Tuplestorestate *tupstore; char **values; HeapTuple tuple; TupleDesc tupdesc = attinmeta->tupdesc; int tupdesc_nc = tupdesc->natts; Form_pg_attribute *attrs = tupdesc->attrs; MemoryContext oldcontext; int i, j; int nr = 0; int nc = length(rval); SEXP dfcol; SEXP result; if (nc != tupdesc_nc) ereport(ERROR, (errcode(ERRCODE_DATA_EXCEPTION), errmsg("actual and requested return type mismatch"), errdetail("Actual return type has %d columns, but " \ "requested return type has %d", nc, tupdesc_nc))); /* switch to appropriate context to create the tuple store */ oldcontext = MemoryContextSwitchTo(per_query_ctx); /* initialize our tuplestore */ tupstore = TUPLESTORE_BEGIN_HEAP; MemoryContextSwitchTo(oldcontext); /* * If we return a set, get number of rows by examining the first column. * Otherwise, stop at one row. */ if (retset) { if (isFrame(rval)) { PROTECT(dfcol = VECTOR_ELT(rval, 0)); nr = length(dfcol); UNPROTECT(1); } else if (isList(rval) || isNewList(rval)) nr = 1; } else nr = 1; /* coerce columns to character in advance */ PROTECT(result = NEW_LIST(nc)); for (j = 0; j < nc; j++) { PROTECT(dfcol = VECTOR_ELT(rval, j)); if((!isFactor(dfcol)) && ((attrs[j]->attndims == 0) || (TYPEOF(dfcol) != VECSXP))) { SEXP obj; PROTECT(obj = coerce_to_char(dfcol)); SET_VECTOR_ELT(result, j, obj); UNPROTECT(1); } else if(attrs[j]->attndims != 0) /* array data type */ { SEXP obj; PROTECT(obj = NEW_LIST(nr)); for(i = 0; i < nr; i++) { SEXP dfcolcell; SEXP objcell; PROTECT(dfcolcell = VECTOR_ELT(dfcol, i)); PROTECT(objcell = coerce_to_char(dfcolcell)); SET_VECTOR_ELT(obj, i, objcell); UNPROTECT(2); } SET_VECTOR_ELT(result, j, obj); UNPROTECT(1); } else { SEXP t; for (t = ATTRIB(dfcol); t != R_NilValue; t = CDR(t)) { if(TAG(t) == R_LevelsSymbol) { PROTECT(SETCAR(t, coerce_to_char(CAR(t)))); UNPROTECT(1); break; } } SET_VECTOR_ELT(result, j, dfcol); } UNPROTECT(1); } values = (char **) palloc(nc * sizeof(char *)); for(i = 0; i < nr; i++) { for (j = 0; j < nc; j++) { PROTECT(dfcol = VECTOR_ELT(result, j)); if(isFactor(dfcol)) { SEXP t; /* * a factor is a special type of integer * but must check for NA value first */ if (INTEGER_ELT(dfcol, i) != NA_INTEGER) { for (t = ATTRIB(dfcol); t != R_NilValue; t = CDR(t)) { if(TAG(t) == R_LevelsSymbol) { SEXP obj; int idx = INTEGER(dfcol)[i] - 1; PROTECT(obj = CAR(t)); values[j] = pstrdup(CHAR(STRING_ELT(obj, idx))); UNPROTECT(1); break; } } } else values[j] = NULL; } else { if ((attrs[j]->attndims != 0) || (STRING_ELT(dfcol, i) != NA_STRING)) { if (attrs[j]->attndims == 0) { values[j] = pstrdup(CHAR(STRING_ELT(dfcol, i))); } else /* array data type */ { bool isnull = false; Datum arr_datum; if (TYPEOF(dfcol) != VECSXP) arr_datum = get_array_datum(dfcol, function, j, &isnull); else arr_datum = get_array_datum(VECTOR_ELT(dfcol,i), function, j, &isnull); if (isnull) { values[j] = NULL; } else { FunctionCallInfoData fake_fcinfo; FmgrInfo flinfo; Datum dvalue; MemSet(&fake_fcinfo, 0, sizeof(fake_fcinfo)); MemSet(&flinfo, 0, sizeof(flinfo)); fake_fcinfo.flinfo = &flinfo; flinfo.fn_mcxt = CurrentMemoryContext; fake_fcinfo.context = NULL; fake_fcinfo.resultinfo = NULL; fake_fcinfo.isnull = false; fake_fcinfo.nargs = 1; fake_fcinfo.arg[0] = arr_datum; fake_fcinfo.argnull[0] = false; dvalue = (*array_out)(&fake_fcinfo); if (fake_fcinfo.isnull) values[j] = NULL; else values[j] = DatumGetCString(dvalue); } } } else values[j] = NULL; } UNPROTECT(1); } /* construct the tuple */ tuple = BuildTupleFromCStrings(attinmeta, values); /* switch to appropriate context while storing the tuple */ oldcontext = MemoryContextSwitchTo(per_query_ctx); /* now store it */ tuplestore_puttuple(tupstore, tuple); /* now reset the context */ MemoryContextSwitchTo(oldcontext); for (j = 0; j < nc; j++) if (values[j] != NULL) pfree(values[j]); } UNPROTECT(1); oldcontext = MemoryContextSwitchTo(per_query_ctx); tuplestore_donestoring(tupstore); MemoryContextSwitchTo(oldcontext); return tupstore; } static Tuplestorestate * get_matrix_tuplestore(SEXP rval, plr_function *function, AttInMetadata *attinmeta, MemoryContext per_query_ctx, bool retset) { Tuplestorestate *tupstore; char **values; HeapTuple tuple; MemoryContext oldcontext; SEXP obj; int i, j; int nr; int nc = ncols(rval); /* switch to appropriate context to create the tuple store */ oldcontext = MemoryContextSwitchTo(per_query_ctx); /* * If we return a set, get number of rows. * Otherwise, stop at one row. */ if (retset) nr = nrows(rval); else nr = 1; /* initialize our tuplestore */ tupstore = TUPLESTORE_BEGIN_HEAP; MemoryContextSwitchTo(oldcontext); values = (char **) palloc(nc * sizeof(char *)); PROTECT(obj = coerce_to_char(rval)); for(i = 0; i < nr; i++) { for (j = 0; j < nc; j++) { if (STRING_ELT(obj, (j * nr) + i) != NA_STRING) values[j] = (char *) CHAR(STRING_ELT(obj, (j * nr) + i)); else values[j] = (char *) NULL; } /* construct the tuple */ tuple = BuildTupleFromCStrings(attinmeta, values); /* switch to appropriate context while storing the tuple */ oldcontext = MemoryContextSwitchTo(per_query_ctx); /* now store it */ tuplestore_puttuple(tupstore, tuple); /* now reset the context */ MemoryContextSwitchTo(oldcontext); } UNPROTECT(1); oldcontext = MemoryContextSwitchTo(per_query_ctx); tuplestore_donestoring(tupstore); MemoryContextSwitchTo(oldcontext); return tupstore; } static Tuplestorestate * get_generic_tuplestore(SEXP rval, plr_function *function, AttInMetadata *attinmeta, MemoryContext per_query_ctx, bool retset) { Tuplestorestate *tupstore; char **values; HeapTuple tuple; MemoryContext oldcontext; int nr; int nc = 1; SEXP obj; int i; /* switch to appropriate context to create the tuple store */ oldcontext = MemoryContextSwitchTo(per_query_ctx); /* * If we return a set, get number of rows. * Otherwise, stop at one row. */ if (retset) nr = length(rval); else nr = 1; /* initialize our tuplestore */ tupstore = TUPLESTORE_BEGIN_HEAP; MemoryContextSwitchTo(oldcontext); values = (char **) palloc(nc * sizeof(char *)); PROTECT(obj = coerce_to_char(rval)); for(i = 0; i < nr; i++) { if (STRING_ELT(obj, i) != NA_STRING) values[0] = (char *) CHAR(STRING_ELT(obj, i)); else values[0] = (char *) NULL; /* construct the tuple */ tuple = BuildTupleFromCStrings(attinmeta, values); /* switch to appropriate context while storing the tuple */ oldcontext = MemoryContextSwitchTo(per_query_ctx); /* now store it */ tuplestore_puttuple(tupstore, tuple); /* now reset the context */ MemoryContextSwitchTo(oldcontext); } UNPROTECT(1); oldcontext = MemoryContextSwitchTo(per_query_ctx); tuplestore_donestoring(tupstore); MemoryContextSwitchTo(oldcontext); return tupstore; } static SEXP coerce_to_char(SEXP rval) { SEXP obj = NULL; switch (TYPEOF(rval)) { case LISTSXP: case NILSXP: case SYMSXP: case VECSXP: case EXPRSXP: case LGLSXP: case INTSXP: case REALSXP: case CPLXSXP: case STRSXP: case RAWSXP: PROTECT(obj = AS_CHARACTER(rval)); break; default: ereport(ERROR, (errcode(ERRCODE_DATA_EXCEPTION), errmsg("data type coercion error"), errdetail("R object is not an expected " \ "data type; examine your R code"))); } UNPROTECT(1); return obj; } plr/pg_userfuncs.c0000775000000000000000000003601212465736645013251 0ustar rootroot/* * PL/R - PostgreSQL support for R as a * procedural language (PL) * * Copyright (c) 2003-2015 by Joseph E. Conway * ALL RIGHTS RESERVED * * Joe Conway * * Based on pltcl by Jan Wieck * and inspired by REmbeddedPostgres by * Duncan Temple Lang * http://www.omegahat.org/RSPostgres/ * * License: GPL version 2 or newer. http://www.gnu.org/copyleft/gpl.html * * This program 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. * * This program 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 this program; if not, write to the Free Software * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA * * pg_userfuncs.c - User visible PostgreSQL functions */ #include "plr.h" extern MemoryContext plr_SPI_context; #ifndef WIN32 extern char **environ; #endif static ArrayType *plr_array_create(FunctionCallInfo fcinfo, int numelems, int elem_start); /*----------------------------------------------------------------------------- * plr_version : * output PL/R version string *---------------------------------------------------------------------------- */ PG_FUNCTION_INFO_V1(plr_version); Datum plr_version(PG_FUNCTION_ARGS) { PG_RETURN_TEXT_P(PG_STR_GET_TEXT(PLR_VERSION)); } /*----------------------------------------------------------------------------- * reload_modules : * interface to allow plr_modules to be reloaded on demand *---------------------------------------------------------------------------- */ PG_FUNCTION_INFO_V1(reload_plr_modules); Datum reload_plr_modules(PG_FUNCTION_ARGS) { MemoryContext plr_caller_context = CurrentMemoryContext; if (SPI_connect() != SPI_OK_CONNECT) elog(ERROR, "SPI_connect failed"); plr_SPI_context = CurrentMemoryContext; MemoryContextSwitchTo(plr_caller_context); plr_load_modules(); if (SPI_finish() != SPI_OK_FINISH) elog(ERROR, "SPI_finish failed"); PG_RETURN_TEXT_P(PG_STR_GET_TEXT("OK")); } /*----------------------------------------------------------------------------- * install_rcmd : * interface to allow user defined R functions to be called from other * R functions *---------------------------------------------------------------------------- */ PG_FUNCTION_INFO_V1(install_rcmd); Datum install_rcmd(PG_FUNCTION_ARGS) { char *cmd = PG_TEXT_GET_STR(PG_GETARG_TEXT_P(0)); load_r_cmd(cmd); PG_RETURN_TEXT_P(PG_STR_GET_TEXT("OK")); } /*----------------------------------------------------------------------------- * array : * form a one-dimensional array given starting elements * FIXME: does not handle NULL array elements * this function should be obsoleted by similar * backend functionality *---------------------------------------------------------------------------- */ PG_FUNCTION_INFO_V1(plr_array); Datum plr_array(PG_FUNCTION_ARGS) { ArrayType *result; result = plr_array_create(fcinfo, PG_NARGS(), 0); PG_RETURN_ARRAYTYPE_P(result); } /*----------------------------------------------------------------------------- * array_push : * push an element onto the end of a one-dimensional array * FIXME: does not handle NULL array elements * this function should be obsoleted by similar * backend functionality *---------------------------------------------------------------------------- */ PG_FUNCTION_INFO_V1(plr_array_push); Datum plr_array_push(PG_FUNCTION_ARGS) { ArrayType *v; Datum newelem; int *dimv, *lb, ub; ArrayType *result; int indx; Oid element_type; int16 typlen; bool typbyval; char typalign; v = PG_GETARG_ARRAYTYPE_P(0); newelem = PG_GETARG_DATUM(1); /* Sanity check: do we have a one-dimensional array */ if (ARR_NDIM(v) != 1) ereport(ERROR, (errcode(ERRCODE_FEATURE_NOT_SUPPORTED), errmsg("input must be one-dimensional array"))); lb = ARR_LBOUND(v); dimv = ARR_DIMS(v); ub = dimv[0] + lb[0] - 1; indx = ub + 1; element_type = ARR_ELEMTYPE(v); /* Sanity check: do we have a non-zero element type */ if (element_type == 0) /* internal error */ elog(ERROR, "invalid array element type"); get_typlenbyvalalign(element_type, &typlen, &typbyval, &typalign); result = array_set(v, 1, &indx, newelem, FALSE, -1, typlen, typbyval, typalign); PG_RETURN_ARRAYTYPE_P(result); } /*----------------------------------------------------------------------------- * array_accum : * accumulator to build an array from input values -- when used in * conjunction with plr functions that accept an array, and output * a statistic, this can be used to create custom aggregates. * FIXME: does not handle NULL array elements * this function should be obsoleted by similar * backend functionality *---------------------------------------------------------------------------- */ PG_FUNCTION_INFO_V1(plr_array_accum); Datum plr_array_accum(PG_FUNCTION_ARGS) { Datum v; Datum newelem; ArrayType *result; /* return NULL if both arguments are NULL */ if (PG_ARGISNULL(0) && PG_ARGISNULL(1)) PG_RETURN_NULL(); /* create a new array from the second argument if first is NULL */ if (PG_ARGISNULL(0)) PG_RETURN_ARRAYTYPE_P(plr_array_create(fcinfo, 1, 1)); /* return the first argument if the second is NULL */ if (PG_ARGISNULL(1)) PG_RETURN_ARRAYTYPE_P(PG_GETARG_ARRAYTYPE_P_COPY(0)); v = PG_GETARG_DATUM(0); newelem = PG_GETARG_DATUM(1); result = DatumGetArrayTypeP(DirectFunctionCall2(plr_array_push, v, newelem)); PG_RETURN_ARRAYTYPE_P(result); } /* * actually does the work for array(), and array_accum() if it is given a null * input array. * * numelems and elem_start allow the function to be shared given the differing * arguments accepted by array() and array_accum(). With array(), all function * arguments are used for array construction -- therefore elem_start is 0 and * numelems is the number of function arguments. With array_accum(), we are * always initializing the array with a single element given to us as argument * number 1 (i.e. the second argument). * */ static ArrayType * plr_array_create(FunctionCallInfo fcinfo, int numelems, int elem_start) { Oid funcid = fcinfo->flinfo->fn_oid; Datum *dvalues = (Datum *) palloc(numelems * sizeof(Datum)); int16 typlen; bool typbyval; Oid typinput; Oid element_type; char typalign; int i; HeapTuple tp; Oid functypeid; Oid *funcargtypes; ArrayType *result; if (numelems == 0) ereport(ERROR, (errcode(ERRCODE_FEATURE_NOT_SUPPORTED), errmsg("at least one value required to construct an array"))); /* * Get the type metadata for the array return type and its elements */ tp = SearchSysCache(PROCOID, ObjectIdGetDatum(funcid), 0, 0, 0); if (!HeapTupleIsValid(tp)) /* internal error */ elog(ERROR, "function OID %u does not exist", funcid); functypeid = ((Form_pg_proc) GETSTRUCT(tp))->prorettype; getTypeInputInfo(functypeid, &typinput, &element_type); get_typlenbyvalalign(element_type, &typlen, &typbyval, &typalign); funcargtypes = FUNCARGTYPES(tp); /* * the first function argument(s) may not be one of our array elements, * but the caller is responsible to ensure we get nothing but array * elements once they start coming */ for (i = elem_start; i < elem_start + numelems; i++) if (funcargtypes[i] != element_type) ereport(ERROR, (errcode(ERRCODE_INVALID_PARAMETER_VALUE), errmsg("argument %d datatype not " \ "compatible with return data type", i + 1))); ReleaseSysCache(tp); for (i = 0; i < numelems; i++) dvalues[i] = PG_GETARG_DATUM(elem_start + i); result = construct_array(dvalues, numelems, element_type, typlen, typbyval, typalign); return result; } /*----------------------------------------------------------------------------- * plr_environ : * utility function to display the environment under which the * postmaster is running. *---------------------------------------------------------------------------- */ PG_FUNCTION_INFO_V1(plr_environ); Datum plr_environ(PG_FUNCTION_ARGS) { ReturnSetInfo *rsinfo = (ReturnSetInfo *) fcinfo->resultinfo; Tuplestorestate *tupstore; HeapTuple tuple; TupleDesc tupdesc; AttInMetadata *attinmeta; MemoryContext per_query_ctx; MemoryContext oldcontext; char *var_name; char *var_val; char *values[2]; #ifndef WIN32 char **current_env; #else char *buf; LPTSTR envstr; int count = 0; int i; #endif /* check to see if caller supports us returning a tuplestore */ if (!rsinfo || !(rsinfo->allowedModes & SFRM_Materialize)) ereport(ERROR, (errcode(ERRCODE_SYNTAX_ERROR), errmsg("materialize mode required, but it is not " "allowed in this context"))); per_query_ctx = rsinfo->econtext->ecxt_per_query_memory; oldcontext = MemoryContextSwitchTo(per_query_ctx); /* get the requested return tuple description */ tupdesc = CreateTupleDescCopy(rsinfo->expectedDesc); /* * Check to make sure we have a reasonable tuple descriptor */ if (tupdesc->natts != 2 || tupdesc->attrs[0]->atttypid != TEXTOID || tupdesc->attrs[1]->atttypid != TEXTOID) ereport(ERROR, (errcode(ERRCODE_SYNTAX_ERROR), errmsg("query-specified return tuple and " "function return type are not compatible"))); /* OK to use it */ attinmeta = TupleDescGetAttInMetadata(tupdesc); /* let the caller know we're sending back a tuplestore */ rsinfo->returnMode = SFRM_Materialize; /* initialize our tuplestore */ tupstore = TUPLESTORE_BEGIN_HEAP; #ifndef WIN32 for (current_env = environ; current_env != NULL && *current_env != NULL; current_env++) { Size name_len; var_val = strchr(*current_env, '='); if (!var_val) continue; name_len = var_val - *current_env; var_name = (char *) palloc0(name_len + 1); memcpy(var_name, *current_env, name_len); values[0] = var_name; values[1] = var_val + 1; tuple = BuildTupleFromCStrings(attinmeta, values); tuplestore_puttuple(tupstore, tuple); pfree(var_name); } #else buf = GetEnvironmentStrings(); envstr = buf; while (true) { if (*envstr == 0) break; while (*envstr != 0) envstr++; envstr++; count++; } /* reset pointer to the environment buffer */ envstr = buf; while(*buf == '=') buf++; for (i = 0; i < count; i++) { Size name_len; var_val = strchr(buf, '='); if (!var_val) continue; name_len = var_val - buf; var_name = (char *) palloc0(name_len + 1); memcpy(var_name, buf, name_len); values[0] = var_name; values[1] = var_val + 1; tuple = BuildTupleFromCStrings(attinmeta, values); tuplestore_puttuple(tupstore, tuple); pfree(var_name); while(*buf != '\0') buf++; buf++; } FreeEnvironmentStrings(envstr); #endif /* * no longer need the tuple descriptor reference created by * TupleDescGetAttInMetadata() */ ReleaseTupleDesc(tupdesc); tuplestore_donestoring(tupstore); rsinfo->setResult = tupstore; /* * SFRM_Materialize mode expects us to return a NULL Datum. The actual * tuples are in our tuplestore and passed back through * rsinfo->setResult. rsinfo->setDesc is set to the tuple description * that we actually used to build our tuples with, so the caller can * verify we did what it was expecting. */ rsinfo->setDesc = tupdesc; MemoryContextSwitchTo(oldcontext); return (Datum) 0; } /*----------------------------------------------------------------------------- * plr_set_rhome : * utility function to set the R_HOME environment variable under * which the postmaster is running. *---------------------------------------------------------------------------- */ PG_FUNCTION_INFO_V1(plr_set_rhome); Datum plr_set_rhome(PG_FUNCTION_ARGS) { char *rhome = PG_TEXT_GET_STR(PG_GETARG_TEXT_P(0)); size_t rh_len = strlen(rhome); if (rh_len) { char *rhenv; MemoryContext oldcontext; /* Needs to live until/unless we explicitly delete it */ oldcontext = MemoryContextSwitchTo(TopMemoryContext); rhenv = palloc(8 + rh_len); MemoryContextSwitchTo(oldcontext); sprintf(rhenv, "R_HOME=%s", rhome); putenv(rhenv); } PG_RETURN_TEXT_P(PG_STR_GET_TEXT("OK")); } /*----------------------------------------------------------------------------- * plr_unset_rhome : * utility function to unset the R_HOME environment variable under * which the postmaster is running. *---------------------------------------------------------------------------- */ PG_FUNCTION_INFO_V1(plr_unset_rhome); Datum plr_unset_rhome(PG_FUNCTION_ARGS) { unsetenv("R_HOME"); PG_RETURN_TEXT_P(PG_STR_GET_TEXT("OK")); } /*----------------------------------------------------------------------------- * plr_set_display : * utility function to set the DISPLAY environment variable under * which the postmaster is running. *---------------------------------------------------------------------------- */ PG_FUNCTION_INFO_V1(plr_set_display); Datum plr_set_display(PG_FUNCTION_ARGS) { char *display = PG_TEXT_GET_STR(PG_GETARG_TEXT_P(0)); size_t d_len = strlen(display); if (d_len) { char *denv; MemoryContext oldcontext; /* Needs to live until/unless we explicitly delete it */ oldcontext = MemoryContextSwitchTo(TopMemoryContext); denv = palloc(9 + d_len); MemoryContextSwitchTo(oldcontext); sprintf(denv, "DISPLAY=%s", display); putenv(denv); } PG_RETURN_TEXT_P(PG_STR_GET_TEXT("OK")); } /*----------------------------------------------------------------------------- * plr_get_raw : * utility function to ... *---------------------------------------------------------------------------- */ extern char *last_R_error_msg; PG_FUNCTION_INFO_V1(plr_get_raw); Datum plr_get_raw(PG_FUNCTION_ARGS) { SEXP result; SEXP s, t, obj; int status; bytea *bvalue = PG_GETARG_BYTEA_P(0); int len, rsize; bytea *bresult; char *brptr; PROTECT(obj = NEW_RAW(VARSIZE(bvalue))); memcpy((char *) RAW(obj), VARDATA(bvalue), VARSIZE(bvalue)); /* * Need to construct a call to * unserialize(rval) */ PROTECT(t = s = allocList(2)); SET_TYPEOF(s, LANGSXP); SETCAR(t, install("unserialize")); t = CDR(t); SETCAR(t, obj); PROTECT(result = R_tryEval(s, R_GlobalEnv, &status)); if(status != 0) { if (last_R_error_msg) ereport(ERROR, (errcode(ERRCODE_DATA_EXCEPTION), errmsg("R interpreter expression evaluation error"), errdetail("%s", last_R_error_msg))); else ereport(ERROR, (errcode(ERRCODE_DATA_EXCEPTION), errmsg("R interpreter expression evaluation error"), errdetail("R expression evaluation error caught in \"unserialize\"."))); } len = LENGTH(result); rsize = VARHDRSZ + len; bresult = (bytea *) palloc(rsize); SET_VARSIZE(bresult, rsize); brptr = VARDATA(bresult); memcpy(brptr, (char *) RAW(result), rsize - VARHDRSZ); UNPROTECT(3); PG_RETURN_BYTEA_P(bresult); } plr/plr--unpackaged--8.3.0.16.sql0000664000000000000000000000201312465736645015032 0ustar rootroot/* plr/plr--unpackaged--8.3.0.16.sql */ ALTER EXTENSION plr ADD type plr_environ_type; ALTER EXTENSION plr ADD type r_typename; ALTER EXTENSION plr ADD type r_version_type; ALTER EXTENSION plr ADD function plr_call_handler(); ALTER EXTENSION plr ADD function plr_version(); ALTER EXTENSION plr ADD function reload_plr_modules(); ALTER EXTENSION plr ADD function install_rcmd(text); ALTER EXTENSION plr ADD function plr_singleton_array (float8); ALTER EXTENSION plr ADD function plr_array_push (_float8, float8); ALTER EXTENSION plr ADD function plr_array_accum (_float8, float8); ALTER EXTENSION plr ADD function plr_environ (); ALTER EXTENSION plr ADD function r_typenames(); ALTER EXTENSION plr ADD function load_r_typenames(); ALTER EXTENSION plr ADD function r_version(); ALTER EXTENSION plr ADD function plr_set_rhome (text); ALTER EXTENSION plr ADD function plr_unset_rhome (); ALTER EXTENSION plr ADD function plr_set_display (text); ALTER EXTENSION plr ADD function plr_get_raw (bytea); ALTER EXTENSION plr ADD LANGUAGE plr;