taler-deployment

Deployment scripts and configuration files
Log | Files | Refs | README

procedures.sql (128043B)


      1 BEGIN;
      2 SET search_path TO exchange;
      3 CREATE OR REPLACE FUNCTION create_partitioned_table(
      4    IN table_definition TEXT 
      5   ,IN table_name TEXT 
      6   ,IN main_table_partition_str TEXT 
      7   ,IN partition_suffix TEXT DEFAULT NULL 
      8 )
      9 RETURNS VOID
     10 LANGUAGE plpgsql
     11 AS $$
     12 BEGIN
     13   IF (partition_suffix IS NULL)
     14   THEN
     15     main_table_partition_str = '';
     16   ELSE
     17     IF (partition_suffix::int > 0)
     18     THEN
     19       table_name=table_name || '_' || partition_suffix;
     20     END IF;
     21   END IF;
     22   EXECUTE FORMAT(
     23     table_definition,
     24     table_name,
     25     main_table_partition_str
     26   );
     27 END $$;
     28 COMMENT ON FUNCTION create_partitioned_table
     29   IS 'Generic function to create a table that is partitioned or sharded.';
     30 CREATE OR REPLACE FUNCTION comment_partitioned_table(
     31    IN table_comment TEXT
     32   ,IN table_name TEXT
     33   ,IN partition_suffix TEXT DEFAULT NULL
     34 )
     35 RETURNS VOID
     36 LANGUAGE plpgsql
     37 AS $$
     38 BEGIN
     39   IF ( (partition_suffix IS NOT NULL) AND
     40        (partition_suffix::int > 0) )
     41   THEN
     42     table_name=table_name || '_' || partition_suffix;
     43   END IF;
     44   EXECUTE FORMAT(
     45      'COMMENT ON TABLE %s IS %s'
     46     ,table_name
     47     ,quote_literal(table_comment)
     48   );
     49 END $$;
     50 COMMENT ON FUNCTION comment_partitioned_table
     51   IS 'Generic function to create a comment on table that is partitioned.';
     52 CREATE OR REPLACE FUNCTION comment_partitioned_column(
     53    IN table_comment TEXT
     54   ,IN column_name TEXT
     55   ,IN table_name TEXT
     56   ,IN partition_suffix TEXT DEFAULT NULL
     57 )
     58 RETURNS VOID
     59 LANGUAGE plpgsql
     60 AS $$
     61 BEGIN
     62   IF ( (partition_suffix IS NOT NULL) AND
     63        (partition_suffix::int > 0) )
     64   THEN
     65     table_name=table_name || '_' || partition_suffix;
     66   END IF;
     67   EXECUTE FORMAT(
     68      'COMMENT ON COLUMN %s.%s IS %s'
     69     ,table_name
     70     ,column_name
     71     ,quote_literal(table_comment)
     72   );
     73 END $$;
     74 COMMENT ON FUNCTION comment_partitioned_column
     75   IS 'Generic function to create a comment on column of a table that is partitioned.';
     76 CREATE OR REPLACE FUNCTION exchange_do_create_tables(
     77   num_partitions INTEGER
     78 )
     79   RETURNS VOID
     80   LANGUAGE plpgsql
     81 AS $$
     82 DECLARE
     83   tc CURSOR FOR
     84     SELECT table_serial_id
     85           ,name
     86           ,action
     87           ,partitioned
     88           ,by_range
     89       FROM exchange.exchange_tables
     90      WHERE NOT finished
     91      ORDER BY table_serial_id ASC;
     92 BEGIN
     93   FOR rec IN tc
     94   LOOP
     95     CASE rec.action
     96     WHEN 'create'
     97     THEN
     98       IF (rec.partitioned AND
     99           (num_partitions IS NOT NULL))
    100       THEN
    101         EXECUTE FORMAT(
    102           'SELECT exchange.create_table_%s (%s)'::text
    103           ,rec.name
    104           ,quote_literal('0')
    105         );
    106         IF (rec.by_range OR
    107             (num_partitions = 0))
    108         THEN
    109           IF (rec.by_range)
    110           THEN
    111             EXECUTE FORMAT(
    112               'CREATE TABLE exchange.%s_default'
    113               ' PARTITION OF %s'
    114               ' DEFAULT'
    115              ,rec.name
    116              ,rec.name
    117             );
    118           ELSE
    119             EXECUTE FORMAT(
    120               'CREATE TABLE exchange.%s_default'
    121               ' PARTITION OF %s'
    122               ' FOR VALUES WITH (MODULUS 1, REMAINDER 0)'
    123              ,rec.name
    124              ,rec.name
    125             );
    126           END IF;
    127         ELSE
    128           FOR i IN 1..num_partitions LOOP
    129             EXECUTE FORMAT(
    130                'CREATE TABLE exchange.%I'
    131                ' PARTITION OF %I'
    132                ' FOR VALUES WITH (MODULUS %s, REMAINDER %s)'
    133               ,rec.name || '_' || i
    134               ,rec.name
    135               ,num_partitions
    136               ,i-1
    137             );
    138           END LOOP;
    139         END IF;
    140       ELSE
    141         EXECUTE FORMAT(
    142           'SELECT exchange.create_table_%s ()'::text
    143           ,rec.name
    144         );
    145       END IF;
    146       EXECUTE FORMAT(
    147         'DROP FUNCTION exchange.create_table_%s'::text
    148           ,rec.name
    149         );
    150     WHEN 'alter'
    151     THEN
    152       EXECUTE FORMAT(
    153         'SELECT exchange.alter_table_%s ()'::text
    154         ,rec.name
    155       );
    156       EXECUTE FORMAT(
    157         'DROP FUNCTION exchange.alter_table_%s'::text
    158           ,rec.name
    159         );
    160     WHEN 'constrain'
    161     THEN
    162       ASSERT rec.partitioned, 'constrain action only applies to partitioned tables';
    163       IF (num_partitions IS NULL)
    164       THEN
    165         EXECUTE FORMAT(
    166            'SELECT exchange.constrain_table_%s (NULL)'::text
    167           ,rec.name
    168         );
    169       ELSE
    170         IF ( (num_partitions = 0) OR
    171              (rec.by_range) )
    172         THEN
    173           EXECUTE FORMAT(
    174              'SELECT exchange.constrain_table_%s (%s)'::text
    175             ,rec.name
    176             ,quote_literal('default')
    177           );
    178         ELSE
    179           FOR i IN 1..num_partitions LOOP
    180             EXECUTE FORMAT(
    181               'SELECT exchange.constrain_table_%s (%s)'::text
    182               ,rec.name
    183               ,quote_literal(i)
    184             );
    185           END LOOP;
    186         END IF;
    187       END IF;
    188       EXECUTE FORMAT(
    189         'DROP FUNCTION exchange.constrain_table_%s'::text
    190           ,rec.name
    191         );
    192     WHEN 'foreign'
    193     THEN
    194       IF (num_partitions IS NULL)
    195       THEN
    196         EXECUTE FORMAT(
    197           'SELECT exchange.foreign_table_%s (%s)'::text
    198           ,rec.name
    199           ,NULL
    200         );
    201       END IF;
    202       EXECUTE FORMAT(
    203         'DROP FUNCTION exchange.foreign_table_%s'::text
    204           ,rec.name
    205         );
    206     WHEN 'master'
    207     THEN
    208       EXECUTE FORMAT(
    209         'SELECT exchange.master_table_%s ()'::text
    210         ,rec.name
    211       );
    212       EXECUTE FORMAT(
    213         'DROP FUNCTION exchange.master_table_%s'::text
    214           ,rec.name
    215         );
    216     ELSE
    217       ASSERT FALSE, 'unsupported action type: ' || rec.action;
    218     END CASE; 
    219     UPDATE exchange.exchange_tables
    220        SET finished=TRUE
    221      WHERE table_serial_id=rec.table_serial_id;
    222   END LOOP; 
    223 END $$;
    224 COMMENT ON FUNCTION exchange_do_create_tables
    225   IS 'Creates all tables for the given number of partitions that need creating. Does NOT support sharding.';
    226 CREATE OR REPLACE FUNCTION amount_normalize(
    227     IN amount taler_amount
    228   ,OUT normalized taler_amount
    229 )
    230 LANGUAGE plpgsql
    231 AS $$
    232 BEGIN
    233   normalized.val = amount.val + amount.frac / 100000000;
    234   normalized.frac = amount.frac % 100000000;
    235 END $$;
    236 COMMENT ON FUNCTION amount_normalize
    237   IS 'Returns the normalized amount by adding to the .val the value of (.frac / 100000000) and removing the modulus 100000000 from .frac.';
    238 CREATE OR REPLACE FUNCTION amount_add(
    239    IN a taler_amount
    240   ,IN b taler_amount
    241   ,OUT sum taler_amount
    242 )
    243 LANGUAGE plpgsql
    244 AS $$
    245 BEGIN
    246   sum = (a.val + b.val, a.frac + b.frac);
    247   CALL amount_normalize(sum ,sum);
    248   IF (sum.val > (1<<52))
    249   THEN
    250     RAISE EXCEPTION 'addition overflow';
    251   END IF;
    252 END $$;
    253 COMMENT ON FUNCTION amount_add
    254   IS 'Returns the normalized sum of two amounts. It raises an exception when the resulting .val is larger than 2^52';
    255 CREATE OR REPLACE FUNCTION amount_left_minus_right(
    256   IN l taler_amount
    257  ,IN r taler_amount
    258  ,OUT diff taler_amount
    259  ,OUT ok BOOLEAN
    260 )
    261 LANGUAGE plpgsql
    262 AS $$
    263 BEGIN
    264 IF (l.val > r.val)
    265 THEN
    266   ok = TRUE;
    267   IF (l.frac >= r.frac)
    268   THEN
    269     diff.val = l.val - r.val;
    270     diff.frac = l.frac - r.frac;
    271   ELSE
    272     diff.val = l.val - r.val - 1;
    273     diff.frac = l.frac + 100000000 - r.frac;
    274   END IF;
    275 ELSE
    276   IF (l.val = r.val) AND (l.frac >= r.frac)
    277   THEN
    278     diff.val = 0;
    279     diff.frac = l.frac - r.frac;
    280     ok = TRUE;
    281   ELSE
    282     diff = (-1, -1);
    283     ok = FALSE;
    284   END IF;
    285 END IF;
    286 RETURN;
    287 END $$;
    288 COMMENT ON FUNCTION amount_left_minus_right
    289   IS 'Subtracts the right amount from the left and returns the difference and TRUE, if the left amount is larger than the right, or an invalid amount and FALSE otherwise.';
    290 DROP FUNCTION IF EXISTS exchange_do_withdraw;
    291 CREATE FUNCTION exchange_do_withdraw(
    292   IN in_amount_with_fee taler_amount,
    293   IN in_reserve_pub BYTEA,
    294   IN in_reserve_sig BYTEA,
    295   IN in_now INT8,
    296   IN in_min_reserve_gc INT8,
    297   IN in_planchets_h BYTEA,
    298   IN in_maximum_age_committed INT2, 
    299   IN in_noreveal_index INT2, 
    300   IN in_selected_h BYTEA, 
    301   IN in_denom_serials INT8[],
    302   IN in_denom_sigs BYTEA[],
    303   IN in_blinding_seed BYTEA, 
    304   IN in_cs_r_values BYTEA[], 
    305   IN in_cs_r_choices INT8, 
    306   OUT out_reserve_found BOOLEAN,
    307   OUT out_balance_ok BOOLEAN,
    308   OUT out_reserve_balance taler_amount,
    309   OUT out_age_ok BOOLEAN,
    310   OUT out_required_age INT2, 
    311   OUT out_reserve_birthday INT4,
    312   OUT out_idempotent BOOLEAN,
    313   OUT out_noreveal_index INT2, 
    314   OUT out_nonce_reuse BOOLEAN)
    315 LANGUAGE plpgsql
    316 AS $$
    317 DECLARE
    318   my_reserve RECORD;
    319   my_difference RECORD;
    320   my_balance taler_amount;
    321   my_not_before DATE;
    322   my_earliest_date DATE;
    323 BEGIN
    324 SELECT current_balance
    325       ,birthday
    326       ,gc_date
    327   INTO my_reserve
    328   FROM reserves
    329  WHERE reserve_pub=in_reserve_pub;
    330 out_reserve_found = FOUND;
    331 IF NOT out_reserve_found
    332 THEN
    333   out_age_ok = FALSE;
    334   out_required_age = -1;
    335   out_idempotent = FALSE;
    336   out_noreveal_index = -1;
    337   out_reserve_balance.val = 0;
    338   out_reserve_balance.frac = 0;
    339   out_balance_ok = FALSE;
    340   out_nonce_reuse = FALSE;
    341   RETURN;
    342 END IF;
    343 out_reserve_balance = my_reserve.current_balance;
    344 out_reserve_birthday = my_reserve.birthday;
    345 SELECT noreveal_index
    346   INTO out_noreveal_index
    347   FROM withdraw
    348  WHERE reserve_pub = in_reserve_pub
    349    AND planchets_h = in_planchets_h;
    350 out_idempotent = FOUND;
    351 IF out_idempotent
    352 THEN
    353   out_balance_ok = TRUE;
    354   out_age_ok = TRUE;
    355   out_required_age = -1;
    356   out_nonce_reuse = FALSE;
    357   RETURN;
    358 END IF;
    359 out_noreveal_index = -1;
    360 IF (my_reserve.birthday <> 0)
    361 THEN
    362   my_not_before=date '1970-01-01' + my_reserve.birthday;
    363   my_earliest_date = current_date - make_interval(in_maximum_age_committed);
    364   IF ( (in_maximum_age_committed IS NULL) OR
    365        (my_earliest_date < my_not_before) )
    366   THEN
    367     out_required_age = extract(year FROM age(current_date, my_not_before));
    368     out_age_ok = FALSE;
    369     out_balance_ok = TRUE; 
    370     out_nonce_reuse = FALSE; 
    371     RETURN;
    372   END IF;
    373 END IF;
    374 out_age_ok = TRUE;
    375 out_required_age = 0;
    376 SELECT *
    377   INTO my_difference
    378   FROM amount_left_minus_right(out_reserve_balance
    379                               ,in_amount_with_fee);
    380 out_balance_ok = my_difference.ok;
    381 IF NOT out_balance_ok
    382 THEN
    383   out_nonce_reuse = FALSE; 
    384   RETURN;
    385 END IF;
    386 my_balance = my_difference.diff;
    387 in_min_reserve_gc=GREATEST(in_min_reserve_gc,my_reserve.gc_date);
    388 UPDATE reserves SET
    389   gc_date=in_min_reserve_gc
    390  ,current_balance=my_balance
    391 WHERE
    392   reserve_pub=in_reserve_pub;
    393 IF in_blinding_seed IS NOT NULL
    394 THEN
    395   INSERT INTO unique_withdraw_blinding_seed
    396     (blinding_seed)
    397   VALUES
    398     (in_blinding_seed)
    399   ON CONFLICT DO NOTHING;
    400   IF NOT FOUND
    401   THEN
    402     out_nonce_reuse = TRUE;
    403     RETURN;
    404   END IF;
    405 END IF;
    406 out_nonce_reuse = FALSE;
    407 INSERT INTO withdraw
    408   (planchets_h
    409   ,execution_date
    410   ,max_age
    411   ,amount_with_fee
    412   ,reserve_pub
    413   ,reserve_sig
    414   ,noreveal_index
    415   ,denom_serials
    416   ,selected_h
    417   ,blinding_seed
    418   ,cs_r_values
    419   ,cs_r_choices
    420   ,denom_sigs)
    421 VALUES
    422   (in_planchets_h
    423   ,in_now
    424   ,in_maximum_age_committed
    425   ,in_amount_with_fee
    426   ,in_reserve_pub
    427   ,in_reserve_sig
    428   ,in_noreveal_index
    429   ,in_denom_serials
    430   ,in_selected_h
    431   ,in_blinding_seed
    432   ,in_cs_r_values
    433   ,in_cs_r_choices
    434   ,in_denom_sigs)
    435 ON CONFLICT DO NOTHING;
    436 IF NOT FOUND
    437 THEN
    438   RAISE EXCEPTION 'Conflict on insert into withdraw despite idempotency check for reserve_pub(%) and planchets_h(%)!',
    439     in_reserve_pub,
    440     in_planchets_h;
    441 END IF;
    442 END $$;
    443 COMMENT ON FUNCTION exchange_do_withdraw(
    444   taler_amount,
    445   BYTEA,
    446   BYTEA,
    447   INT8,
    448   INT8,
    449   BYTEA,
    450   INT2,
    451   INT2,
    452   BYTEA,
    453   INT8[],
    454   BYTEA[],
    455   BYTEA,
    456   BYTEA[],
    457   INT8)
    458   IS 'Checks whether the reserve has sufficient balance for an withdraw operation (or the request is repeated and was previously approved) and that age requirements are met. If so updates the database with the result. Includes storing the hashes of all blinded planchets, (separately) the hashes of the chosen planchets and denomination signatures, or signaling idempotency (and previous noreveal_index) or nonce reuse';
    459 DROP FUNCTION IF EXISTS exchange_do_refresh;
    460 CREATE FUNCTION exchange_do_refresh(
    461   IN in_rc BYTEA,
    462   IN in_now INT8,
    463   IN in_refresh_seed BYTEA,
    464   IN in_planchets_h BYTEA,
    465   IN in_amount_with_fee taler_amount,
    466   IN in_blinding_seed BYTEA,
    467   IN in_cs_r_values BYTEA[],
    468   IN in_cs_r_choices INT8,
    469   IN in_selected_h BYTEA,
    470   IN in_denom_sigs BYTEA[],
    471   IN in_denom_serials INT8[],
    472   IN in_old_coin_pub BYTEA,
    473   IN in_old_coin_sig BYTEA,
    474   IN in_noreveal_index INT4,
    475   IN in_zombie_required BOOLEAN,
    476   OUT out_coin_found BOOLEAN,
    477   OUT out_balance_ok BOOLEAN,
    478   OUT out_zombie_bad BOOLEAN,
    479   OUT out_nonce_reuse BOOLEAN,
    480   OUT out_idempotent BOOLEAN,
    481   OUT out_noreveal_index INT4,
    482   OUT out_coin_balance taler_amount)
    483 LANGUAGE plpgsql
    484 AS $$
    485 DECLARE
    486   known_coin RECORD;
    487   difference RECORD;
    488 BEGIN
    489 SELECT known_coin_id
    490      ,remaining
    491   INTO known_coin
    492   FROM known_coins
    493   WHERE coin_pub = in_old_coin_pub;
    494 IF NOT FOUND
    495 THEN
    496   out_coin_found = FALSE;
    497   out_balance_ok = TRUE;
    498   out_zombie_bad = FALSE;
    499   out_nonce_reuse = FALSE;
    500   out_idempotent = FALSE;
    501   out_noreveal_index = -1 ;
    502   out_coin_balance.val = 0;
    503   out_coin_balance.frac = 0;
    504   RETURN;
    505 END IF;
    506 out_coin_found = TRUE;
    507 out_coin_balance = known_coin.remaining;
    508 SELECT TRUE, noreveal_index
    509 INTO out_idempotent, out_noreveal_index
    510 FROM exchange.refresh
    511 WHERE rc=in_rc;
    512 IF out_idempotent
    513 THEN
    514   out_balance_ok = TRUE;
    515   out_zombie_bad = FALSE; 
    516   out_nonce_reuse = FALSE;
    517 RETURN;
    518 END IF;
    519 out_idempotent = FALSE;
    520 out_noreveal_index = in_noreveal_index;
    521 IF in_blinding_seed IS NOT NULL
    522 THEN
    523   INSERT INTO unique_refresh_blinding_seed
    524     (blinding_seed)
    525   VALUES
    526     (in_blinding_seed)
    527   ON CONFLICT DO NOTHING;
    528   IF NOT FOUND
    529   THEN
    530       out_nonce_reuse = TRUE;
    531       out_balance_ok = TRUE;
    532       out_zombie_bad = FALSE; 
    533       RETURN;
    534   END IF;
    535 END IF;
    536 out_nonce_reuse = FALSE;
    537 INSERT INTO exchange.refresh
    538   (rc
    539   ,execution_date
    540   ,old_coin_pub
    541   ,old_coin_sig
    542   ,planchets_h
    543   ,amount_with_fee
    544   ,noreveal_index
    545   ,refresh_seed
    546   ,blinding_seed
    547   ,cs_r_values
    548   ,cs_r_choices
    549   ,selected_h
    550   ,denom_sigs
    551   ,denom_serials
    552   )
    553   VALUES
    554   (in_rc
    555   ,in_now
    556   ,in_old_coin_pub
    557   ,in_old_coin_sig
    558   ,in_planchets_h
    559   ,in_amount_with_fee
    560   ,in_noreveal_index
    561   ,in_refresh_seed
    562   ,in_blinding_seed
    563   ,in_cs_r_values
    564   ,in_cs_r_choices
    565   ,in_selected_h
    566   ,in_denom_sigs
    567   ,in_denom_serials
    568   )
    569   ON CONFLICT DO NOTHING;
    570 IF NOT FOUND
    571 THEN
    572   RAISE EXCEPTION 'Conflict in refresh despite idempotency check for rc(%)!', rc;
    573   RETURN;
    574 END IF;
    575 IF in_zombie_required
    576 THEN
    577   PERFORM
    578    FROM recoup_refresh
    579    WHERE refresh_id IN
    580       (SELECT refresh_id
    581        FROM refresh
    582        WHERE old_coin_pub=in_old_coin_pub);
    583   IF NOT FOUND
    584   THEN
    585     out_zombie_bad=TRUE;
    586     out_balance_ok=FALSE;
    587     RETURN;
    588   END IF;
    589 END IF;
    590 out_zombie_bad=FALSE; 
    591 SELECT *
    592 INTO difference
    593 FROM amount_left_minus_right(out_coin_balance
    594                             ,in_amount_with_fee);
    595 out_balance_ok = difference.ok;
    596 IF NOT out_balance_ok
    597 THEN
    598   RETURN;
    599 END IF;
    600 out_coin_balance = difference.diff;
    601 UPDATE known_coins
    602   SET
    603     remaining = out_coin_balance
    604   WHERE
    605     known_coin_id = known_coin.known_coin_id;
    606 END $$;
    607 DROP FUNCTION IF EXISTS exchange_do_deposit;
    608 CREATE FUNCTION exchange_do_deposit(
    609   IN in_shard INT8,
    610   IN in_merchant_pub BYTEA,
    611   IN in_merchant_sig BYTEA,
    612   IN in_wallet_timestamp INT8,
    613   IN in_exchange_timestamp INT8,
    614   IN in_refund_deadline INT8,
    615   IN in_wire_deadline INT8,
    616   IN in_h_contract_terms BYTEA,
    617   IN in_wallet_data_hash BYTEA, 
    618   IN in_wire_salt BYTEA,
    619   IN in_wire_target_h_payto BYTEA,
    620   IN in_h_normalized_payto BYTEA,
    621   IN in_policy_details_serial_id INT8, 
    622   IN in_policy_blocked BOOLEAN,
    623   IN in_receiver_wire_account TEXT,
    624   IN ina_coin_pub BYTEA[],
    625   IN ina_coin_sig BYTEA[],
    626   IN ina_amount_with_fee taler_amount[],
    627   IN in_total_amount taler_amount,
    628   OUT out_exchange_timestamp INT8,
    629   OUT out_insufficient_balance_coin_index INT4, 
    630   OUT out_conflict BOOL
    631  )
    632 LANGUAGE plpgsql
    633 AS $$
    634 DECLARE
    635   wtsi INT8; 
    636   bdsi INT8; 
    637   i INT4;
    638   ini_amount_with_fee taler_amount;
    639   ini_coin_pub BYTEA;
    640   ini_coin_sig BYTEA;
    641 BEGIN
    642 INSERT INTO wire_targets
    643     (wire_target_h_payto
    644     ,h_normalized_payto
    645     ,payto_uri)
    646   VALUES
    647     (in_wire_target_h_payto
    648     ,in_h_normalized_payto
    649     ,in_receiver_wire_account)
    650   ON CONFLICT DO NOTHING 
    651   RETURNING
    652     wire_target_serial_id
    653   INTO
    654     wtsi;
    655 IF NOT FOUND
    656 THEN
    657   SELECT
    658     wire_target_serial_id
    659   INTO
    660     wtsi
    661   FROM wire_targets
    662   WHERE
    663     wire_target_h_payto=in_wire_target_h_payto;
    664 END IF;
    665 INSERT INTO batch_deposits
    666   (shard
    667   ,merchant_pub
    668   ,merchant_sig
    669   ,wallet_timestamp
    670   ,exchange_timestamp
    671   ,refund_deadline
    672   ,wire_deadline
    673   ,h_contract_terms
    674   ,wallet_data_hash
    675   ,wire_salt
    676   ,wire_target_h_payto
    677   ,policy_details_serial_id
    678   ,policy_blocked
    679   ,total_amount
    680   )
    681   VALUES
    682   (in_shard
    683   ,in_merchant_pub
    684   ,in_merchant_sig
    685   ,in_wallet_timestamp
    686   ,in_exchange_timestamp
    687   ,in_refund_deadline
    688   ,in_wire_deadline
    689   ,in_h_contract_terms
    690   ,in_wallet_data_hash
    691   ,in_wire_salt
    692   ,in_wire_target_h_payto
    693   ,in_policy_details_serial_id
    694   ,in_policy_blocked
    695   ,in_total_amount)
    696   ON CONFLICT DO NOTHING 
    697   RETURNING
    698     batch_deposit_serial_id
    699   INTO
    700     bdsi;
    701 IF NOT FOUND
    702 THEN
    703   SELECT
    704       exchange_timestamp
    705      ,batch_deposit_serial_id
    706    INTO
    707       out_exchange_timestamp
    708      ,bdsi
    709    FROM batch_deposits
    710    WHERE shard=in_shard
    711      AND merchant_pub=in_merchant_pub
    712      AND h_contract_terms=in_h_contract_terms
    713      AND wire_target_h_payto=in_wire_target_h_payto
    714      AND ( (wallet_data_hash=in_wallet_data_hash) OR
    715            (wallet_data_hash IS NULL AND in_wallet_data_hash IS NULL) )
    716      AND wire_salt=in_wire_salt
    717      AND wallet_timestamp=in_wallet_timestamp
    718      AND refund_deadline=in_refund_deadline
    719      AND wire_deadline=in_wire_deadline
    720      AND ( (policy_details_serial_id=in_policy_details_serial_id) OR
    721            (policy_details_serial_id IS NULL AND in_policy_details_serial_id IS NULL) );
    722   IF NOT FOUND
    723   THEN
    724     out_conflict=TRUE;
    725     RETURN;
    726   END IF;
    727 END IF;
    728 out_conflict=FALSE;
    729 FOR i IN 1..array_length(ina_coin_pub,1)
    730 LOOP
    731   ini_coin_pub = ina_coin_pub[i];
    732   ini_coin_sig = ina_coin_sig[i];
    733   ini_amount_with_fee = ina_amount_with_fee[i];
    734   INSERT INTO coin_deposits
    735     (batch_deposit_serial_id
    736     ,coin_pub
    737     ,coin_sig
    738     ,amount_with_fee
    739     )
    740     VALUES
    741     (bdsi
    742     ,ini_coin_pub
    743     ,ini_coin_sig
    744     ,ini_amount_with_fee
    745     )
    746     ON CONFLICT DO NOTHING;
    747   IF FOUND
    748   THEN
    749     UPDATE known_coins kc
    750       SET
    751         remaining.frac=(kc.remaining).frac-ini_amount_with_fee.frac
    752           + CASE
    753               WHEN (kc.remaining).frac < ini_amount_with_fee.frac
    754               THEN 100000000
    755               ELSE 0
    756             END,
    757         remaining.val=(kc.remaining).val-ini_amount_with_fee.val
    758           - CASE
    759               WHEN (kc.remaining).frac < ini_amount_with_fee.frac
    760               THEN 1
    761               ELSE 0
    762             END
    763       WHERE coin_pub=ini_coin_pub
    764         AND ( ((kc.remaining).val > ini_amount_with_fee.val) OR
    765               ( ((kc.remaining).frac >= ini_amount_with_fee.frac) AND
    766                 ((kc.remaining).val >= ini_amount_with_fee.val) ) );
    767     IF NOT FOUND
    768     THEN
    769       out_insufficient_balance_coin_index=i-1;
    770       RETURN;
    771     END IF;
    772   END IF;
    773 END LOOP; 
    774 END $$;
    775 DROP FUNCTION IF EXISTS exchange_do_check_deposit_idempotent;
    776 CREATE FUNCTION exchange_do_check_deposit_idempotent(
    777   IN in_shard INT8,
    778   IN in_merchant_pub BYTEA,
    779   IN in_wallet_timestamp INT8,
    780   IN in_exchange_timestamp INT8,
    781   IN in_refund_deadline INT8,
    782   IN in_wire_deadline INT8,
    783   IN in_h_contract_terms BYTEA,
    784   IN in_wallet_data_hash BYTEA, 
    785   IN in_wire_salt BYTEA,
    786   IN in_wire_target_h_payto BYTEA,
    787   IN in_policy_details_serial_id INT8, 
    788   IN in_policy_blocked BOOLEAN,
    789   IN ina_coin_pub BYTEA[],
    790   IN ina_coin_sig BYTEA[],
    791   IN ina_amount_with_fee taler_amount[],
    792   OUT out_exchange_timestamp INT8,
    793   OUT out_is_idempotent BOOL
    794  )
    795 LANGUAGE plpgsql
    796 AS $$
    797 DECLARE
    798   wtsi INT8; 
    799   bdsi INT8; 
    800   i INT4;
    801   ini_amount_with_fee taler_amount;
    802   ini_coin_pub BYTEA;
    803   ini_coin_sig BYTEA;
    804 BEGIN
    805 out_exchange_timestamp = in_exchange_timestamp;
    806 SELECT wire_target_serial_id
    807   INTO wtsi
    808   FROM wire_targets
    809  WHERE wire_target_h_payto=in_wire_target_h_payto;
    810 IF NOT FOUND
    811 THEN
    812   out_is_idempotent = FALSE;
    813   RETURN;
    814 END IF;
    815 SELECT
    816     exchange_timestamp
    817    ,batch_deposit_serial_id
    818   INTO
    819     out_exchange_timestamp
    820    ,bdsi
    821   FROM batch_deposits
    822  WHERE shard=in_shard
    823    AND merchant_pub=in_merchant_pub
    824    AND h_contract_terms=in_h_contract_terms
    825    AND wire_target_h_payto=in_wire_target_h_payto
    826    AND ( (wallet_data_hash=in_wallet_data_hash) OR
    827          (wallet_data_hash IS NULL AND in_wallet_data_hash IS NULL) )
    828    AND wire_salt=in_wire_salt
    829    AND wallet_timestamp=in_wallet_timestamp
    830    AND refund_deadline=in_refund_deadline
    831    AND wire_deadline=in_wire_deadline
    832    AND ( (policy_details_serial_id=in_policy_details_serial_id) OR
    833          (policy_details_serial_id IS NULL AND in_policy_details_serial_id IS NULL) );
    834 IF NOT FOUND
    835 THEN
    836   out_is_idempotent=FALSE;
    837   RETURN;
    838 END IF;
    839 FOR i IN 1..array_length(ina_coin_pub,1)
    840 LOOP
    841   ini_coin_pub = ina_coin_pub[i];
    842   ini_coin_sig = ina_coin_sig[i];
    843   ini_amount_with_fee = ina_amount_with_fee[i];
    844   PERFORM FROM coin_deposits
    845     WHERE batch_deposit_serial_id=bdsi
    846       AND coin_pub=ini_coin_pub
    847       AND coin_sig=ini_coin_sig
    848       AND amount_with_fee=ini_amount_with_fee;
    849   IF NOT FOUND
    850   THEN
    851     out_is_idempotent=FALSE;
    852     RETURN;
    853   END IF;
    854 END LOOP; 
    855 out_is_idempotent=TRUE;
    856 END $$;
    857 CREATE OR REPLACE FUNCTION exchange_do_melt(
    858   IN in_cs_rms BYTEA,
    859   IN in_amount_with_fee taler_amount,
    860   IN in_rc BYTEA,
    861   IN in_old_coin_pub BYTEA,
    862   IN in_old_coin_sig BYTEA,
    863   IN in_known_coin_id INT8, 
    864   IN in_noreveal_index INT4,
    865   IN in_zombie_required BOOLEAN,
    866   OUT out_balance_ok BOOLEAN,
    867   OUT out_zombie_bad BOOLEAN,
    868   OUT out_noreveal_index INT4)
    869 LANGUAGE plpgsql
    870 AS $$
    871 DECLARE
    872   denom_max INT8;
    873 BEGIN
    874 INSERT INTO exchange.refresh_commitments
    875   (rc
    876   ,old_coin_pub
    877   ,old_coin_sig
    878   ,amount_with_fee
    879   ,noreveal_index
    880   )
    881   VALUES
    882   (in_rc
    883   ,in_old_coin_pub
    884   ,in_old_coin_sig
    885   ,in_amount_with_fee
    886   ,in_noreveal_index)
    887   ON CONFLICT DO NOTHING;
    888 IF NOT FOUND
    889 THEN
    890   out_noreveal_index=-1;
    891   SELECT
    892      noreveal_index
    893     INTO
    894      out_noreveal_index
    895     FROM exchange.refresh_commitments
    896    WHERE rc=in_rc;
    897   out_balance_ok=FOUND;
    898   out_zombie_bad=FALSE; 
    899   RETURN;
    900 END IF;
    901 IF in_zombie_required
    902 THEN
    903   PERFORM
    904     FROM recoup_refresh
    905    WHERE rrc_serial IN
    906     (SELECT rrc_serial
    907        FROM refresh_revealed_coins
    908       WHERE melt_serial_id IN
    909       (SELECT melt_serial_id
    910          FROM refresh_commitments
    911         WHERE old_coin_pub=in_old_coin_pub));
    912   IF NOT FOUND
    913   THEN
    914     out_zombie_bad=TRUE;
    915     out_balance_ok=FALSE;
    916     RETURN;
    917   END IF;
    918 END IF;
    919 out_zombie_bad=FALSE; 
    920 UPDATE known_coins kc
    921   SET
    922     remaining.frac=(kc.remaining).frac-in_amount_with_fee.frac
    923        + CASE
    924          WHEN (kc.remaining).frac < in_amount_with_fee.frac
    925          THEN 100000000
    926          ELSE 0
    927          END,
    928     remaining.val=(kc.remaining).val-in_amount_with_fee.val
    929        - CASE
    930          WHEN (kc.remaining).frac < in_amount_with_fee.frac
    931          THEN 1
    932          ELSE 0
    933          END
    934   WHERE coin_pub=in_old_coin_pub
    935     AND ( ((kc.remaining).val > in_amount_with_fee.val) OR
    936           ( ((kc.remaining).frac >= in_amount_with_fee.frac) AND
    937             ((kc.remaining).val >= in_amount_with_fee.val) ) );
    938 IF NOT FOUND
    939 THEN
    940   out_noreveal_index=-1;
    941   out_balance_ok=FALSE;
    942   RETURN;
    943 END IF;
    944 IF in_cs_rms IS NOT NULL
    945 THEN
    946   SELECT
    947       denominations_serial
    948     INTO
    949       denom_max
    950     FROM exchange.denominations
    951       ORDER BY denominations_serial DESC
    952       LIMIT 1;
    953   INSERT INTO exchange.cs_nonce_locks
    954     (nonce
    955     ,max_denomination_serial
    956     ,op_hash)
    957   VALUES
    958     (in_cs_rms
    959     ,denom_max
    960     ,in_rc)
    961   ON CONFLICT DO NOTHING;
    962   IF NOT FOUND
    963   THEN
    964     SELECT 1
    965       FROM exchange.cs_nonce_locks
    966      WHERE nonce=in_cs_rms
    967        AND op_hash=in_rc;
    968     IF NOT FOUND
    969     THEN
    970        out_balance_ok=FALSE;
    971        out_zombie_bad=FALSE;
    972        out_noreveal_index=42; 
    973        ASSERT false, 'nonce reuse attempted by client';
    974     END IF;
    975   END IF;
    976 END IF;
    977 out_balance_ok=TRUE;
    978 out_noreveal_index=in_noreveal_index;
    979 END $$;
    980 CREATE OR REPLACE FUNCTION exchange_do_select_deposits_missing_wire(
    981   IN in_min_serial_id INT8)
    982 RETURNS SETOF exchange_do_select_deposits_missing_wire_return_type
    983 LANGUAGE plpgsql
    984 AS $$
    985 DECLARE
    986   missing CURSOR
    987   FOR
    988   SELECT
    989     batch_deposit_serial_id
    990    ,wire_target_h_payto
    991    ,wire_deadline
    992     FROM batch_deposits
    993     WHERE batch_deposit_serial_id > in_min_serial_id
    994     ORDER BY batch_deposit_serial_id ASC;
    995 DECLARE
    996   my_total_val INT8; 
    997 DECLARE
    998   my_total_frac INT8; 
    999 DECLARE
   1000   my_total taler_amount; 
   1001 DECLARE
   1002   my_batch_record RECORD;
   1003 DECLARE
   1004   i RECORD;
   1005 BEGIN
   1006 OPEN missing;
   1007 LOOP
   1008   FETCH NEXT FROM missing INTO i;
   1009   EXIT WHEN NOT FOUND;
   1010   SELECT
   1011     SUM((cdep.amount_with_fee).val) AS total_val
   1012    ,SUM((cdep.amount_with_fee).frac::INT8) AS total_frac
   1013     INTO
   1014       my_batch_record
   1015     FROM coin_deposits cdep
   1016     WHERE cdep.batch_deposit_serial_id = i.batch_deposit_serial_id;
   1017   my_total_val=my_batch_record.total_val;
   1018   my_total_frac=my_batch_record.total_frac;
   1019   my_total.val = my_total_val + my_total_frac / 100000000;
   1020   my_total.frac = my_total_frac % 100000000;
   1021   RETURN NEXT (
   1022        i.batch_deposit_serial_id
   1023       ,my_total
   1024       ,i.wire_target_h_payto
   1025       ,i.wire_deadline);
   1026 END LOOP;
   1027 CLOSE missing;
   1028 RETURN;
   1029 END $$;
   1030 CREATE OR REPLACE FUNCTION exchange_do_select_justification_missing_wire(
   1031   IN in_wire_target_h_payto BYTEA,
   1032   IN in_current_time INT8,
   1033   OUT out_payto_uri TEXT, 
   1034   OUT out_kyc_pending TEXT, 
   1035   OUT out_aml_status INT4, 
   1036   OUT out_aml_limit taler_amount) 
   1037 LANGUAGE plpgsql
   1038 AS $$
   1039 DECLARE
   1040   my_required_checks TEXT[];
   1041 DECLARE
   1042   my_aml_data RECORD;
   1043 DECLARE
   1044   satisfied CURSOR FOR
   1045   SELECT satisfied_checks
   1046     FROM kyc_attributes
   1047    WHERE h_payto=in_wire_target_h_payto
   1048      AND expiration_time < in_current_time;
   1049 DECLARE
   1050   i RECORD;
   1051 BEGIN
   1052   out_payto_uri = NULL;
   1053   SELECT payto_uri
   1054     INTO out_payto_uri
   1055     FROM wire_targets
   1056    WHERE wire_target_h_payto=my_wire_target_h_payto;
   1057   my_required_checks = NULL;
   1058   SELECT string_to_array (required_checks, ' ')
   1059     INTO my_required_checks
   1060     FROM legitimization_requirements
   1061     WHERE h_payto=my_wire_target_h_payto;
   1062   SELECT
   1063       new_threshold
   1064      ,kyc_requirements
   1065      ,new_status
   1066     INTO
   1067       my_aml_data
   1068      FROM aml_history
   1069     WHERE h_payto=in_wire_target_h_payto
   1070     ORDER BY aml_history_serial_id 
   1071       DESC LIMIT 1;
   1072   IF FOUND
   1073   THEN
   1074     out_aml_limit=my_aml_data.new_threshold;
   1075     out_aml_status=my_aml_data.kyc_status;
   1076     my_required_checks
   1077        = array_cat (my_required_checks,
   1078                     my_aml_data.kyc_requirements);
   1079   ELSE
   1080     out_aml_limit=NULL;
   1081     out_aml_status=0; 
   1082   END IF;
   1083   OPEN satisfied;
   1084   LOOP
   1085     FETCH NEXT FROM satisfied INTO i;
   1086     EXIT WHEN NOT FOUND;
   1087     FOR i in 1..array_length(i.satisfied_checks)
   1088     LOOP
   1089       my_required_checks
   1090         = array_remove (my_required_checks,
   1091                         i.satisfied_checks[i]);
   1092     END LOOP;
   1093   END LOOP;
   1094   IF ( (my_required_checks IS NOT NULL) AND
   1095        (0 < array_length(my_satisfied_checks)) )
   1096   THEN
   1097     out_kyc_pending
   1098       = array_to_string (my_required_checks, ' ');
   1099   END IF;
   1100   RETURN;
   1101 END $$;
   1102 CREATE OR REPLACE FUNCTION exchange_do_refund(
   1103   IN in_amount_with_fee taler_amount,
   1104   IN in_amount taler_amount,
   1105   IN in_deposit_fee taler_amount,
   1106   IN in_h_contract_terms BYTEA,
   1107   IN in_rtransaction_id INT8,
   1108   IN in_deposit_shard INT8,
   1109   IN in_known_coin_id INT8,
   1110   IN in_coin_pub BYTEA,
   1111   IN in_merchant_pub BYTEA,
   1112   IN in_merchant_sig BYTEA,
   1113   OUT out_not_found BOOLEAN,
   1114   OUT out_refund_ok BOOLEAN,
   1115   OUT out_gone BOOLEAN,
   1116   OUT out_conflict BOOLEAN)
   1117 LANGUAGE plpgsql
   1118 AS $$
   1119 DECLARE
   1120   bdsi INT8; 
   1121 DECLARE
   1122   tmp_val INT8; 
   1123 DECLARE
   1124   tmp_frac INT8; 
   1125 DECLARE
   1126   tmp taler_amount; 
   1127 DECLARE
   1128   deposit taler_amount; 
   1129 BEGIN
   1130 SELECT
   1131    bdep.batch_deposit_serial_id
   1132   ,(cdep.amount_with_fee).val
   1133   ,(cdep.amount_with_fee).frac
   1134   ,bdep.done
   1135  INTO
   1136    bdsi
   1137   ,deposit.val
   1138   ,deposit.frac
   1139   ,out_gone
   1140  FROM batch_deposits bdep
   1141  JOIN coin_deposits cdep
   1142    USING (batch_deposit_serial_id)
   1143  WHERE cdep.coin_pub=in_coin_pub
   1144   AND shard=in_deposit_shard
   1145   AND merchant_pub=in_merchant_pub
   1146   AND h_contract_terms=in_h_contract_terms;
   1147 IF NOT FOUND
   1148 THEN
   1149   out_refund_ok=FALSE;
   1150   out_conflict=FALSE;
   1151   out_not_found=TRUE;
   1152   out_gone=FALSE;
   1153   RETURN;
   1154 END IF;
   1155 INSERT INTO refunds
   1156   (batch_deposit_serial_id
   1157   ,coin_pub
   1158   ,merchant_sig
   1159   ,rtransaction_id
   1160   ,amount_with_fee
   1161   )
   1162   VALUES
   1163   (bdsi
   1164   ,in_coin_pub
   1165   ,in_merchant_sig
   1166   ,in_rtransaction_id
   1167   ,in_amount_with_fee
   1168   )
   1169   ON CONFLICT DO NOTHING;
   1170 IF NOT FOUND
   1171 THEN
   1172    PERFORM
   1173    FROM exchange.refunds
   1174    WHERE coin_pub=in_coin_pub
   1175      AND batch_deposit_serial_id=bdsi
   1176      AND rtransaction_id=in_rtransaction_id
   1177      AND amount_with_fee=in_amount_with_fee;
   1178   IF NOT FOUND
   1179   THEN
   1180     out_refund_ok=FALSE;
   1181     out_conflict=TRUE;
   1182     out_not_found=FALSE;
   1183     RETURN;
   1184   END IF;
   1185   out_refund_ok=TRUE;
   1186   out_conflict=FALSE;
   1187   out_not_found=FALSE;
   1188   out_gone=FALSE;
   1189   RETURN;
   1190 END IF;
   1191 IF out_gone
   1192 THEN
   1193   out_refund_ok=FALSE;
   1194   out_conflict=FALSE;
   1195   out_not_found=FALSE;
   1196   RETURN;
   1197 END IF;
   1198 SELECT
   1199    SUM((refs.amount_with_fee).val) 
   1200   ,SUM(CAST((refs.amount_with_fee).frac AS INT8)) 
   1201   INTO
   1202    tmp_val
   1203   ,tmp_frac
   1204   FROM refunds refs
   1205   WHERE coin_pub=in_coin_pub
   1206     AND batch_deposit_serial_id=bdsi;
   1207 IF tmp_val IS NULL
   1208 THEN
   1209   RAISE NOTICE 'failed to sum up existing refunds';
   1210   out_refund_ok=FALSE;
   1211   out_conflict=FALSE;
   1212   out_not_found=FALSE;
   1213   RETURN;
   1214 END IF;
   1215 tmp.val = tmp_val + tmp_frac / 100000000;
   1216 tmp.frac = tmp_frac % 100000000;
   1217 IF (tmp.val < deposit.val)
   1218 THEN
   1219   out_refund_ok=TRUE;
   1220 ELSE
   1221   IF (tmp.val = deposit.val) AND (tmp.frac <= deposit.frac)
   1222   THEN
   1223     out_refund_ok=TRUE;
   1224   ELSE
   1225     out_refund_ok=FALSE;
   1226   END IF;
   1227 END IF;
   1228 IF (tmp.val = deposit.val) AND (tmp.frac = deposit.frac)
   1229 THEN
   1230   in_amount.frac = in_amount.frac + in_deposit_fee.frac;
   1231   in_amount.val = in_amount.val + in_deposit_fee.val;
   1232   in_amount.val = in_amount.val + in_amount.frac / 100000000;
   1233   in_amount.frac = in_amount.frac % 100000000;
   1234 END IF;
   1235 UPDATE known_coins kc
   1236   SET
   1237     remaining.frac=(kc.remaining).frac+in_amount.frac
   1238        - CASE
   1239          WHEN (kc.remaining).frac+in_amount.frac >= 100000000
   1240          THEN 100000000
   1241          ELSE 0
   1242          END,
   1243     remaining.val=(kc.remaining).val+in_amount.val
   1244        + CASE
   1245          WHEN (kc.remaining).frac+in_amount.frac >= 100000000
   1246          THEN 1
   1247          ELSE 0
   1248          END
   1249   WHERE coin_pub=in_coin_pub;
   1250 out_conflict=FALSE;
   1251 out_not_found=FALSE;
   1252 END $$;
   1253 COMMENT ON FUNCTION exchange_do_refund(taler_amount, taler_amount, taler_amount, BYTEA, INT8, INT8, INT8, BYTEA, BYTEA, BYTEA)
   1254   IS 'Executes a refund operation, checking that the corresponding deposit was sufficient to cover the refunded amount';
   1255 DROP FUNCTION IF EXISTS exchange_do_recoup_to_reserve;
   1256 CREATE FUNCTION exchange_do_recoup_to_reserve(
   1257   IN in_reserve_pub BYTEA,
   1258   IN in_withdraw_id INT8,
   1259   IN in_coin_blind BYTEA,
   1260   IN in_coin_pub BYTEA,
   1261   IN in_known_coin_id INT8,
   1262   IN in_coin_sig BYTEA,
   1263   IN in_reserve_gc INT8,
   1264   IN in_reserve_expiration INT8,
   1265   IN in_recoup_timestamp INT8,
   1266   OUT out_recoup_ok BOOLEAN,
   1267   OUT out_internal_failure BOOLEAN,
   1268   OUT out_recoup_timestamp INT8)
   1269 LANGUAGE plpgsql
   1270 AS $$
   1271 DECLARE
   1272   tmp taler_amount; 
   1273   balance taler_amount; 
   1274   new_balance taler_amount; 
   1275   reserve RECORD;
   1276   rval RECORD;
   1277 BEGIN
   1278 out_internal_failure=FALSE;
   1279 SELECT
   1280    remaining
   1281  INTO
   1282    rval
   1283 FROM exchange.known_coins
   1284   WHERE coin_pub=in_coin_pub;
   1285 IF NOT FOUND
   1286 THEN
   1287   out_internal_failure=TRUE;
   1288   out_recoup_ok=FALSE;
   1289   RETURN;
   1290 END IF;
   1291 tmp := rval.remaining;
   1292 IF tmp.val + tmp.frac = 0
   1293 THEN
   1294   SELECT
   1295     recoup_timestamp
   1296   INTO
   1297     out_recoup_timestamp
   1298     FROM exchange.recoup
   1299     WHERE coin_pub=in_coin_pub;
   1300   out_recoup_ok=FOUND;
   1301   RETURN;
   1302 END IF;
   1303 UPDATE known_coins
   1304   SET
   1305      remaining.val = 0
   1306     ,remaining.frac = 0
   1307   WHERE coin_pub=in_coin_pub;
   1308 SELECT current_balance
   1309   INTO reserve
   1310   FROM reserves
   1311  WHERE reserve_pub=in_reserve_pub;
   1312 balance = reserve.current_balance;
   1313 new_balance.frac=balance.frac+tmp.frac
   1314    - CASE
   1315      WHEN balance.frac+tmp.frac >= 100000000
   1316      THEN 100000000
   1317      ELSE 0
   1318      END;
   1319 new_balance.val=balance.val+tmp.val
   1320    + CASE
   1321      WHEN balance.frac+tmp.frac >= 100000000
   1322      THEN 1
   1323      ELSE 0
   1324      END;
   1325 UPDATE reserves
   1326   SET
   1327     current_balance = new_balance,
   1328     gc_date=GREATEST(gc_date, in_reserve_gc),
   1329     expiration_date=GREATEST(expiration_date, in_reserve_expiration)
   1330   WHERE reserve_pub=in_reserve_pub;
   1331 IF NOT FOUND
   1332 THEN
   1333   RAISE NOTICE 'failed to increase reserve balance from recoup';
   1334   out_recoup_ok=TRUE;
   1335   out_internal_failure=TRUE;
   1336   RETURN;
   1337 END IF;
   1338 INSERT INTO exchange.recoup
   1339   (coin_pub
   1340   ,coin_sig
   1341   ,coin_blind
   1342   ,amount
   1343   ,recoup_timestamp
   1344   ,withdraw_id
   1345   )
   1346 VALUES
   1347   (in_coin_pub
   1348   ,in_coin_sig
   1349   ,in_coin_blind
   1350   ,tmp
   1351   ,in_recoup_timestamp
   1352   ,in_withdraw_id);
   1353 out_recoup_ok=TRUE;
   1354 out_recoup_timestamp=in_recoup_timestamp;
   1355 END $$;
   1356 CREATE OR REPLACE FUNCTION exchange_do_recoup_to_coin(
   1357   IN in_old_coin_pub BYTEA,
   1358   IN in_refresh_id INT8,
   1359   IN in_coin_blind BYTEA,
   1360   IN in_coin_pub BYTEA,
   1361   IN in_known_coin_id INT8,
   1362   IN in_coin_sig BYTEA,
   1363   IN in_recoup_timestamp INT8,
   1364   OUT out_recoup_ok BOOLEAN,
   1365   OUT out_internal_failure BOOLEAN,
   1366   OUT out_recoup_timestamp INT8)
   1367 LANGUAGE plpgsql
   1368 AS $$
   1369 DECLARE
   1370   rval RECORD;
   1371 DECLARE
   1372   tmp taler_amount; 
   1373 BEGIN
   1374 out_internal_failure=FALSE;
   1375 SELECT
   1376    remaining
   1377  INTO
   1378    rval
   1379 FROM exchange.known_coins
   1380   WHERE coin_pub=in_coin_pub;
   1381 IF NOT FOUND
   1382 THEN
   1383   out_internal_failure=TRUE;
   1384   out_recoup_ok=FALSE;
   1385   RETURN;
   1386 END IF;
   1387 tmp := rval.remaining;
   1388 IF tmp.val + tmp.frac = 0
   1389 THEN
   1390   SELECT
   1391       recoup_timestamp
   1392     INTO
   1393       out_recoup_timestamp
   1394     FROM recoup_refresh
   1395     WHERE coin_pub=in_coin_pub;
   1396   out_recoup_ok=FOUND;
   1397   RETURN;
   1398 END IF;
   1399 UPDATE known_coins
   1400   SET
   1401      remaining.val = 0
   1402     ,remaining.frac = 0
   1403   WHERE coin_pub=in_coin_pub;
   1404 UPDATE known_coins kc
   1405   SET
   1406     remaining.frac=(kc.remaining).frac+tmp.frac
   1407        - CASE
   1408          WHEN (kc.remaining).frac+tmp.frac >= 100000000
   1409          THEN 100000000
   1410          ELSE 0
   1411          END,
   1412     remaining.val=(kc.remaining).val+tmp.val
   1413        + CASE
   1414          WHEN (kc.remaining).frac+tmp.frac >= 100000000
   1415          THEN 1
   1416          ELSE 0
   1417          END
   1418   WHERE coin_pub=in_old_coin_pub;
   1419 IF NOT FOUND
   1420 THEN
   1421   RAISE NOTICE 'failed to increase old coin balance from recoup';
   1422   out_recoup_ok=TRUE;
   1423   out_internal_failure=TRUE;
   1424   RETURN;
   1425 END IF;
   1426 INSERT INTO recoup_refresh
   1427   (coin_pub
   1428   ,known_coin_id
   1429   ,coin_sig
   1430   ,coin_blind
   1431   ,amount
   1432   ,recoup_timestamp
   1433   ,refresh_id
   1434   )
   1435 VALUES
   1436   (in_coin_pub
   1437   ,in_known_coin_id
   1438   ,in_coin_sig
   1439   ,in_coin_blind
   1440   ,tmp
   1441   ,in_recoup_timestamp
   1442   ,in_refresh_id);
   1443 out_recoup_ok=TRUE;
   1444 out_recoup_timestamp=in_recoup_timestamp;
   1445 END $$;
   1446 CREATE OR REPLACE PROCEDURE exchange_do_main_gc(
   1447   IN in_ancient_date INT8,
   1448   IN in_now INT8)
   1449 LANGUAGE plpgsql
   1450 AS $$
   1451 DECLARE
   1452   reserve_uuid_min INT8; 
   1453   coin_min INT8; 
   1454   batch_deposit_min INT8; 
   1455   withdraw_min INT8; 
   1456   denom_min INT8; 
   1457 BEGIN
   1458 DELETE FROM prewire
   1459   WHERE finished=TRUE;
   1460 DELETE FROM wire_fee
   1461   WHERE end_date < in_ancient_date;
   1462 DELETE FROM refresh
   1463   WHERE execution_date < in_ancient_date;
   1464 DELETE FROM kycauths_in
   1465   WHERE execution_date < in_ancient_date;
   1466 DELETE FROM reserves_in
   1467   WHERE execution_date < in_ancient_date;
   1468 DELETE FROM batch_deposits
   1469   WHERE wire_deadline < in_ancient_date;
   1470 DELETE FROM reserves
   1471   WHERE gc_date < in_now
   1472     AND current_balance = (0, 0);
   1473 SELECT withdraw_id
   1474   INTO withdraw_min
   1475   FROM withdraw
   1476   ORDER BY withdraw_id ASC
   1477   LIMIT 1;
   1478 DELETE FROM recoup
   1479   WHERE withdraw_id < withdraw_min;
   1480 SELECT reserve_uuid
   1481   INTO reserve_uuid_min
   1482   FROM reserves
   1483   ORDER BY reserve_uuid ASC
   1484   LIMIT 1;
   1485 DELETE FROM reserves_out
   1486   WHERE reserve_uuid < reserve_uuid_min;
   1487 DELETE FROM denominations
   1488   WHERE expire_legal < in_now
   1489     AND denominations_serial NOT IN
   1490       (SELECT DISTINCT denominations_serial
   1491          FROM reserves_out)
   1492     AND denominations_serial NOT IN
   1493       (SELECT DISTINCT denominations_serial
   1494          FROM known_coins
   1495         WHERE coin_pub IN
   1496           (SELECT DISTINCT coin_pub
   1497              FROM recoup))
   1498     AND denominations_serial NOT IN
   1499       (SELECT DISTINCT denominations_serial
   1500          FROM known_coins
   1501         WHERE coin_pub IN
   1502           (SELECT DISTINCT coin_pub
   1503              FROM recoup_refresh));
   1504 DELETE FROM recoup_refresh
   1505   WHERE known_coin_id < coin_min;
   1506 SELECT known_coin_id
   1507   INTO coin_min
   1508   FROM known_coins
   1509   ORDER BY known_coin_id ASC
   1510   LIMIT 1;
   1511 SELECT batch_deposit_serial_id
   1512   INTO batch_deposit_min
   1513   FROM coin_deposits
   1514   ORDER BY batch_deposit_serial_id ASC
   1515   LIMIT 1;
   1516 DELETE FROM refunds
   1517   WHERE batch_deposit_serial_id < batch_deposit_min;
   1518 DELETE FROM aggregation_tracking
   1519   WHERE batch_deposit_serial_id < batch_deposit_min;
   1520 DELETE FROM coin_deposits
   1521   WHERE batch_deposit_serial_id < batch_deposit_min;
   1522 SELECT denominations_serial
   1523   INTO denom_min
   1524   FROM denominations
   1525   ORDER BY denominations_serial ASC
   1526   LIMIT 1;
   1527 DELETE FROM cs_nonce_locks
   1528   WHERE max_denomination_serial <= denom_min;
   1529 END $$;
   1530 CREATE OR REPLACE FUNCTION exchange_do_purse_delete(
   1531   IN in_purse_pub BYTEA,
   1532   IN in_purse_sig BYTEA,
   1533   IN in_now INT8,
   1534   OUT out_decided BOOLEAN,
   1535   OUT out_found BOOLEAN)
   1536 LANGUAGE plpgsql
   1537 AS $$
   1538 DECLARE
   1539   my_deposit record;
   1540 DECLARE
   1541   my_in_reserve_quota BOOLEAN;
   1542 BEGIN
   1543 PERFORM refunded FROM purse_decision
   1544   WHERE purse_pub=in_purse_pub;
   1545 IF FOUND
   1546 THEN
   1547   out_found=TRUE;
   1548   out_decided=TRUE;
   1549   RETURN;
   1550 END IF;
   1551 out_decided=FALSE;
   1552 SELECT in_reserve_quota
   1553   INTO my_in_reserve_quota
   1554   FROM exchange.purse_requests
   1555  WHERE purse_pub=in_purse_pub;
   1556 out_found=FOUND;
   1557 IF NOT FOUND
   1558 THEN
   1559   RETURN;
   1560 END IF;
   1561 INSERT INTO exchange.purse_deletion
   1562   (purse_pub
   1563   ,purse_sig)
   1564 VALUES
   1565   (in_purse_pub
   1566   ,in_purse_sig)
   1567 ON CONFLICT DO NOTHING;
   1568 IF NOT FOUND
   1569 THEN
   1570   RETURN;
   1571 END IF;
   1572 DELETE FROM contracts
   1573   WHERE purse_pub=in_purse_pub;
   1574 INSERT INTO purse_decision
   1575   (purse_pub
   1576   ,action_timestamp
   1577   ,refunded)
   1578 VALUES
   1579   (in_purse_pub
   1580   ,in_now
   1581   ,TRUE);
   1582 IF (my_in_reserve_quota)
   1583 THEN
   1584   UPDATE reserves
   1585     SET purses_active=purses_active-1
   1586   WHERE reserve_pub IN
   1587     (SELECT reserve_pub
   1588        FROM exchange.purse_merges
   1589       WHERE purse_pub=in_purse_pub
   1590      LIMIT 1);
   1591 END IF;
   1592 FOR my_deposit IN
   1593   SELECT coin_pub
   1594         ,amount_with_fee
   1595     FROM exchange.purse_deposits
   1596   WHERE purse_pub = in_purse_pub
   1597 LOOP
   1598   UPDATE known_coins kc SET
   1599     remaining.frac=(kc.remaining).frac+(my_deposit.amount_with_fee).frac
   1600      - CASE
   1601        WHEN (kc.remaining).frac+(my_deposit.amount_with_fee).frac >= 100000000
   1602        THEN 100000000
   1603        ELSE 0
   1604        END,
   1605     remaining.val=(kc.remaining).val+(my_deposit.amount_with_fee).val
   1606      + CASE
   1607        WHEN (kc.remaining).frac+(my_deposit.amount_with_fee).frac >= 100000000
   1608        THEN 1
   1609        ELSE 0
   1610        END
   1611     WHERE coin_pub = my_deposit.coin_pub;
   1612 END LOOP;
   1613 END $$;
   1614 COMMENT ON FUNCTION exchange_do_purse_delete(BYTEA,BYTEA,INT8)
   1615   IS 'Delete a previously undecided purse and refund the coins (if any).';
   1616 CREATE OR REPLACE FUNCTION exchange_do_purse_deposit(
   1617   IN in_partner_id INT8,
   1618   IN in_purse_pub BYTEA,
   1619   IN in_amount_with_fee taler_amount,
   1620   IN in_coin_pub BYTEA,
   1621   IN in_coin_sig BYTEA,
   1622   IN in_amount_without_fee taler_amount,
   1623   IN in_reserve_expiration INT8,
   1624   IN in_now INT8,
   1625   OUT out_balance_ok BOOLEAN,
   1626   OUT out_late BOOLEAN,
   1627   OUT out_conflict BOOLEAN)
   1628 LANGUAGE plpgsql
   1629 AS $$
   1630 DECLARE
   1631   was_merged BOOLEAN;
   1632 DECLARE
   1633   psi INT8; 
   1634 DECLARE
   1635   my_amount taler_amount; 
   1636 DECLARE
   1637   was_paid BOOLEAN;
   1638 DECLARE
   1639   my_in_reserve_quota BOOLEAN;
   1640 DECLARE
   1641   my_reserve_pub BYTEA;
   1642 DECLARE
   1643   rval RECORD;
   1644 BEGIN
   1645 INSERT INTO purse_deposits
   1646   (partner_serial_id
   1647   ,purse_pub
   1648   ,coin_pub
   1649   ,amount_with_fee
   1650   ,coin_sig)
   1651   VALUES
   1652   (in_partner_id
   1653   ,in_purse_pub
   1654   ,in_coin_pub
   1655   ,in_amount_with_fee
   1656   ,in_coin_sig)
   1657   ON CONFLICT DO NOTHING;
   1658 IF NOT FOUND
   1659 THEN
   1660   PERFORM
   1661   FROM purse_deposits
   1662   WHERE purse_pub = in_purse_pub
   1663     AND coin_pub = in_coin_pub
   1664     AND coin_sig = in_coin_sig;
   1665   IF NOT FOUND
   1666   THEN
   1667     out_balance_ok=FALSE;
   1668     out_late=FALSE;
   1669     out_conflict=TRUE;
   1670     RETURN;
   1671   ELSE
   1672     out_late=FALSE;
   1673     out_balance_ok=TRUE;
   1674     out_conflict=FALSE;
   1675     RETURN;
   1676   END IF;
   1677 END IF;
   1678 PERFORM
   1679   FROM exchange.purse_deletion
   1680   WHERE purse_pub = in_purse_pub;
   1681 IF FOUND
   1682 THEN
   1683   out_late=TRUE;
   1684   out_balance_ok=FALSE;
   1685   out_conflict=FALSE;
   1686   RETURN;
   1687 END IF;
   1688 UPDATE known_coins kc
   1689   SET
   1690     remaining.frac=(kc.remaining).frac-in_amount_with_fee.frac
   1691        + CASE
   1692          WHEN (kc.remaining).frac < in_amount_with_fee.frac
   1693          THEN 100000000
   1694          ELSE 0
   1695          END,
   1696     remaining.val=(kc.remaining).val-in_amount_with_fee.val
   1697        - CASE
   1698          WHEN (kc.remaining).frac < in_amount_with_fee.frac
   1699          THEN 1
   1700          ELSE 0
   1701          END
   1702   WHERE coin_pub=in_coin_pub
   1703     AND ( ((kc.remaining).val > in_amount_with_fee.val) OR
   1704           ( ((kc.remaining).frac >= in_amount_with_fee.frac) AND
   1705             ((kc.remaining).val >= in_amount_with_fee.val) ) );
   1706 IF NOT FOUND
   1707 THEN
   1708   out_balance_ok=FALSE;
   1709   out_late=FALSE;
   1710   out_conflict=FALSE;
   1711   RETURN;
   1712 END IF;
   1713 UPDATE purse_requests pr
   1714   SET
   1715     balance.frac=(pr.balance).frac+in_amount_without_fee.frac
   1716        - CASE
   1717          WHEN (pr.balance).frac+in_amount_without_fee.frac >= 100000000
   1718          THEN 100000000
   1719          ELSE 0
   1720          END,
   1721     balance.val=(pr.balance).val+in_amount_without_fee.val
   1722        + CASE
   1723          WHEN (pr.balance).frac+in_amount_without_fee.frac >= 100000000
   1724          THEN 1
   1725          ELSE 0
   1726          END
   1727   WHERE purse_pub=in_purse_pub;
   1728 out_conflict=FALSE;
   1729 out_balance_ok=TRUE;
   1730 SELECT COALESCE(partner_serial_id,0)
   1731       ,reserve_pub
   1732   INTO psi
   1733       ,my_reserve_pub
   1734   FROM purse_merges
   1735  WHERE purse_pub=in_purse_pub;
   1736 IF NOT FOUND
   1737 THEN
   1738   out_late=FALSE;
   1739   RETURN;
   1740 END IF;
   1741 SELECT
   1742     amount_with_fee
   1743    ,in_reserve_quota
   1744   INTO
   1745     rval
   1746   FROM exchange.purse_requests preq
   1747   WHERE (purse_pub=in_purse_pub)
   1748     AND ( ( ( ((preq.amount_with_fee).val <= (preq.balance).val)
   1749           AND ((preq.amount_with_fee).frac <= (preq.balance).frac) )
   1750          OR ((preq.amount_with_fee).val < (preq.balance).val) ) );
   1751 IF NOT FOUND
   1752 THEN
   1753   out_late=FALSE;
   1754   RETURN;
   1755 END IF;
   1756 my_amount := rval.amount_with_fee;
   1757 my_in_reserve_quota := rval.in_reserve_quota;
   1758 INSERT INTO purse_decision
   1759   (purse_pub
   1760   ,action_timestamp
   1761   ,refunded)
   1762 VALUES
   1763   (in_purse_pub
   1764   ,in_now
   1765   ,FALSE)
   1766 ON CONFLICT DO NOTHING;
   1767 IF NOT FOUND
   1768 THEN
   1769   out_late=TRUE;
   1770   RETURN;
   1771 END IF;
   1772 out_late=FALSE;
   1773 IF (my_in_reserve_quota)
   1774 THEN
   1775   UPDATE reserves
   1776     SET purses_active=purses_active-1
   1777   WHERE reserve_pub IN
   1778     (SELECT reserve_pub
   1779        FROM purse_merges
   1780       WHERE purse_pub=my_purse_pub
   1781      LIMIT 1);
   1782 END IF;
   1783 IF (0 != psi)
   1784 THEN
   1785   UPDATE purse_actions
   1786      SET action_date=0 
   1787         ,partner_serial_id=psi
   1788    WHERE purse_pub=in_purse_pub;
   1789 ELSE
   1790   INSERT INTO reserves
   1791     (reserve_pub
   1792     ,current_balance
   1793     ,expiration_date
   1794     ,gc_date)
   1795   VALUES
   1796     (my_reserve_pub
   1797     ,my_amount
   1798     ,in_reserve_expiration
   1799     ,in_reserve_expiration)
   1800   ON CONFLICT DO NOTHING;
   1801   IF NOT FOUND
   1802   THEN
   1803     UPDATE reserves
   1804       SET
   1805        current_balance.frac=(current_balance).frac+my_amount.frac
   1806         - CASE
   1807           WHEN (current_balance).frac + my_amount.frac >= 100000000
   1808             THEN 100000000
   1809           ELSE 0
   1810           END
   1811       ,current_balance.val=(current_balance).val+my_amount.val
   1812         + CASE
   1813           WHEN (current_balance).frac + my_amount.frac >= 100000000
   1814             THEN 1
   1815           ELSE 0
   1816           END
   1817       ,expiration_date=GREATEST(expiration_date,in_reserve_expiration)
   1818       ,gc_date=GREATEST(gc_date,in_reserve_expiration)
   1819       WHERE reserve_pub=my_reserve_pub;
   1820   END IF;
   1821 END IF;
   1822 END $$;
   1823 CREATE OR REPLACE FUNCTION exchange_do_purse_merge(
   1824   IN in_purse_pub BYTEA,
   1825   IN in_merge_sig BYTEA,
   1826   IN in_merge_timestamp INT8,
   1827   IN in_reserve_sig BYTEA,
   1828   IN in_partner_url TEXT,
   1829   IN in_reserve_pub BYTEA,
   1830   IN in_wallet_h_payto BYTEA,
   1831   IN in_expiration_date INT8,
   1832   OUT out_no_partner BOOLEAN,
   1833   OUT out_no_balance BOOLEAN,
   1834   OUT out_conflict BOOLEAN)
   1835 LANGUAGE plpgsql
   1836 AS $$
   1837 DECLARE
   1838   my_amount taler_amount;
   1839 DECLARE
   1840   my_purse_fee taler_amount;
   1841 DECLARE
   1842   my_partner_serial_id INT8;
   1843 DECLARE
   1844   my_in_reserve_quota BOOLEAN;
   1845 DECLARE
   1846   rval RECORD;
   1847 DECLARE
   1848   reserve_bal RECORD;
   1849 DECLARE
   1850   balance taler_amount;
   1851 BEGIN
   1852 INSERT INTO reserves
   1853   (reserve_pub
   1854   ,expiration_date
   1855   ,gc_date)
   1856   VALUES
   1857   (in_reserve_pub
   1858   ,in_expiration_date
   1859   ,in_expiration_date)
   1860   ON CONFLICT DO NOTHING;
   1861 IF in_partner_url IS NULL
   1862 THEN
   1863   my_partner_serial_id=NULL;
   1864 ELSE
   1865   SELECT
   1866     partner_serial_id
   1867   INTO
   1868     my_partner_serial_id
   1869   FROM partners
   1870   WHERE partner_base_url=in_partner_url
   1871     AND start_date <= in_merge_timestamp
   1872     AND end_date > in_merge_timestamp;
   1873   IF NOT FOUND
   1874   THEN
   1875     out_no_partner=TRUE;
   1876     out_conflict=FALSE;
   1877     RETURN;
   1878   END IF;
   1879 END IF;
   1880 out_no_partner=FALSE;
   1881 SELECT amount_with_fee
   1882       ,purse_fee
   1883       ,in_reserve_quota
   1884   INTO rval
   1885   FROM purse_requests pr
   1886   WHERE purse_pub=in_purse_pub
   1887     AND (pr.balance).val >= (pr.amount_with_fee).val
   1888     AND ( (pr.balance).frac >= (pr.amount_with_fee).frac OR
   1889           (pr.balance).val > (pr.amount_with_fee).val );
   1890 IF NOT FOUND
   1891 THEN
   1892   out_no_balance=TRUE;
   1893   out_conflict=FALSE;
   1894   RETURN;
   1895 END IF;
   1896 my_amount := rval.amount_with_fee;
   1897 my_purse_fee := rval.purse_fee;
   1898 my_in_reserve_quota := rval.in_reserve_quota;
   1899 out_no_balance=FALSE;
   1900 INSERT INTO purse_merges
   1901     (partner_serial_id
   1902     ,reserve_pub
   1903     ,purse_pub
   1904     ,merge_sig
   1905     ,merge_timestamp)
   1906   VALUES
   1907     (my_partner_serial_id
   1908     ,in_reserve_pub
   1909     ,in_purse_pub
   1910     ,in_merge_sig
   1911     ,in_merge_timestamp)
   1912   ON CONFLICT DO NOTHING;
   1913 IF NOT FOUND
   1914 THEN
   1915   PERFORM
   1916   FROM purse_merges
   1917   WHERE purse_pub=in_purse_pub
   1918      AND merge_sig=in_merge_sig;
   1919   IF NOT FOUND
   1920   THEN
   1921      out_conflict=TRUE;
   1922      RETURN;
   1923   END IF;
   1924   out_conflict=FALSE;
   1925   RETURN;
   1926 END IF;
   1927 INSERT INTO purse_decision
   1928   (purse_pub
   1929   ,action_timestamp
   1930   ,refunded)
   1931 VALUES
   1932   (in_purse_pub
   1933   ,in_merge_timestamp
   1934   ,FALSE)
   1935 ON CONFLICT DO NOTHING;
   1936 IF NOT FOUND
   1937 THEN
   1938   out_conflict=TRUE;
   1939   RETURN;
   1940 END IF;
   1941 out_conflict=FALSE;
   1942 IF (my_in_reserve_quota)
   1943 THEN
   1944   UPDATE reserves
   1945     SET purses_active=purses_active-1
   1946   WHERE reserve_pub IN
   1947     (SELECT reserve_pub
   1948        FROM purse_merges
   1949       WHERE purse_pub=my_purse_pub
   1950      LIMIT 1);
   1951 END IF;
   1952 INSERT INTO account_merges
   1953   (reserve_pub
   1954   ,reserve_sig
   1955   ,purse_pub
   1956   ,wallet_h_payto)
   1957   VALUES
   1958   (in_reserve_pub
   1959   ,in_reserve_sig
   1960   ,in_purse_pub
   1961   ,in_wallet_h_payto);
   1962 IF (0 != my_partner_serial_id)
   1963 THEN
   1964   UPDATE purse_actions
   1965      SET action_date=0 
   1966         ,partner_serial_id=my_partner_serial_id
   1967    WHERE purse_pub=in_purse_pub;
   1968 ELSE
   1969   my_amount.val = my_amount.val + my_purse_fee.val;
   1970   my_amount.frac = my_amount.frac + my_purse_fee.frac;
   1971   my_amount.val = my_amount.val + my_amount.frac / 100000000;
   1972   my_amount.frac = my_amount.frac % 100000000;
   1973   SELECT current_balance
   1974     INTO reserve_bal
   1975     FROM reserves
   1976    WHERE reserve_pub=in_reserve_pub;
   1977   balance = reserve_bal.current_balance;
   1978   balance.val=balance.val+my_amount.val
   1979      + CASE
   1980        WHEN balance.frac + my_amount.frac >= 100000000
   1981        THEN 1
   1982        ELSE 0
   1983        END;
   1984   balance.frac=balance.frac+my_amount.frac
   1985      - CASE
   1986        WHEN balance.frac + my_amount.frac >= 100000000
   1987        THEN 100000000
   1988        ELSE 0
   1989        END;
   1990   UPDATE reserves
   1991      SET current_balance=balance
   1992    WHERE reserve_pub=in_reserve_pub;
   1993 END IF;
   1994 RETURN;
   1995 END $$;
   1996 COMMENT ON FUNCTION exchange_do_purse_merge(BYTEA, BYTEA, INT8, BYTEA, TEXT, BYTEA, BYTEA, INT8)
   1997   IS 'Checks that the partner exists, the purse has not been merged with a different reserve and that the purse is full. If so, persists the merge data and either merges the purse with the reserve or marks it as ready for the taler-exchange-router. Caller MUST abort the transaction on failures so as to not persist data by accident.';
   1998 CREATE OR REPLACE FUNCTION exchange_do_reserve_purse(
   1999   IN in_purse_pub BYTEA,
   2000   IN in_merge_sig BYTEA,
   2001   IN in_merge_timestamp INT8,
   2002   IN in_reserve_expiration INT8,
   2003   IN in_reserve_gc INT8,
   2004   IN in_reserve_sig BYTEA,
   2005   IN in_reserve_quota BOOLEAN,
   2006   IN in_purse_fee taler_amount,
   2007   IN in_reserve_pub BYTEA,
   2008   IN in_wallet_h_payto BYTEA,
   2009   OUT out_no_funds BOOLEAN,
   2010   OUT out_no_reserve BOOLEAN,
   2011   OUT out_conflict BOOLEAN)
   2012 LANGUAGE plpgsql
   2013 AS $$
   2014 BEGIN
   2015 INSERT INTO purse_merges
   2016     (partner_serial_id
   2017     ,reserve_pub
   2018     ,purse_pub
   2019     ,merge_sig
   2020     ,merge_timestamp)
   2021   VALUES
   2022     (NULL
   2023     ,in_reserve_pub
   2024     ,in_purse_pub
   2025     ,in_merge_sig
   2026     ,in_merge_timestamp)
   2027   ON CONFLICT DO NOTHING;
   2028 IF NOT FOUND
   2029 THEN
   2030   PERFORM
   2031   FROM purse_merges
   2032   WHERE purse_pub=in_purse_pub
   2033      AND merge_sig=in_merge_sig;
   2034   IF NOT FOUND
   2035   THEN
   2036      out_conflict=TRUE;
   2037      out_no_reserve=FALSE;
   2038      out_no_funds=FALSE;
   2039      RETURN;
   2040   END IF;
   2041   out_conflict=FALSE;
   2042   out_no_funds=FALSE;
   2043   out_no_reserve=FALSE;
   2044   RETURN;
   2045 END IF;
   2046 out_conflict=FALSE;
   2047 PERFORM
   2048   FROM exchange.reserves
   2049  WHERE reserve_pub=in_reserve_pub;
   2050 out_no_reserve = NOT FOUND;
   2051 IF (in_reserve_quota)
   2052 THEN
   2053   IF (out_no_reserve)
   2054   THEN
   2055     out_no_funds=TRUE;
   2056     RETURN;
   2057   END IF;
   2058   UPDATE exchange.reserves
   2059      SET purses_active=purses_active+1
   2060    WHERE reserve_pub=in_reserve_pub
   2061      AND purses_active < purses_allowed;
   2062   IF NOT FOUND
   2063   THEN
   2064     out_no_funds=TRUE;
   2065     RETURN;
   2066   END IF;
   2067 ELSE
   2068   IF (out_no_reserve)
   2069   THEN
   2070     IF ( (0 != in_purse_fee.val) OR
   2071          (0 != in_purse_fee.frac) )
   2072     THEN
   2073       out_no_funds=TRUE;
   2074       RETURN;
   2075     END IF;
   2076     INSERT INTO exchange.reserves
   2077       (reserve_pub
   2078       ,expiration_date
   2079       ,gc_date)
   2080     VALUES
   2081       (in_reserve_pub
   2082       ,in_reserve_expiration
   2083       ,in_reserve_gc);
   2084   ELSE
   2085     UPDATE exchange.reserves
   2086       SET
   2087         current_balance.frac=(current_balance).frac-in_purse_fee.frac
   2088          + CASE
   2089          WHEN (current_balance).frac < in_purse_fee.frac
   2090          THEN 100000000
   2091          ELSE 0
   2092          END,
   2093        current_balance.val=(current_balance).val-in_purse_fee.val
   2094          - CASE
   2095          WHEN (current_balance).frac < in_purse_fee.frac
   2096          THEN 1
   2097          ELSE 0
   2098          END
   2099       WHERE reserve_pub=in_reserve_pub
   2100         AND ( ((current_balance).val > in_purse_fee.val) OR
   2101               ( ((current_balance).frac >= in_purse_fee.frac) AND
   2102                 ((current_balance).val >= in_purse_fee.val) ) );
   2103     IF NOT FOUND
   2104     THEN
   2105       out_no_funds=TRUE;
   2106       RETURN;
   2107     END IF;
   2108   END IF;
   2109 END IF;
   2110 out_no_funds=FALSE;
   2111 INSERT INTO account_merges
   2112   (reserve_pub
   2113   ,reserve_sig
   2114   ,purse_pub
   2115   ,wallet_h_payto)
   2116   VALUES
   2117   (in_reserve_pub
   2118   ,in_reserve_sig
   2119   ,in_purse_pub
   2120   ,in_wallet_h_payto);
   2121 END $$;
   2122 COMMENT ON FUNCTION exchange_do_reserve_purse(BYTEA, BYTEA, INT8, INT8, INT8, BYTEA, BOOLEAN, taler_amount, BYTEA, BYTEA)
   2123   IS 'Create a purse for a reserve.';
   2124 CREATE OR REPLACE FUNCTION exchange_do_expire_purse(
   2125   IN in_start_time INT8,
   2126   IN in_end_time INT8,
   2127   IN in_now INT8,
   2128   OUT out_found BOOLEAN)
   2129 LANGUAGE plpgsql
   2130 AS $$
   2131 DECLARE
   2132   my_purse_pub BYTEA;
   2133 DECLARE
   2134   my_deposit record;
   2135 DECLARE
   2136   my_in_reserve_quota BOOLEAN;
   2137 BEGIN
   2138 SELECT purse_pub
   2139       ,in_reserve_quota
   2140   INTO my_purse_pub
   2141       ,my_in_reserve_quota
   2142   FROM purse_requests
   2143  WHERE (purse_expiration >= in_start_time) AND
   2144        (purse_expiration < in_end_time) AND
   2145        NOT was_decided
   2146   ORDER BY purse_expiration ASC
   2147  LIMIT 1;
   2148 out_found = FOUND;
   2149 IF NOT FOUND
   2150 THEN
   2151   RETURN;
   2152 END IF;
   2153 INSERT INTO purse_decision
   2154   (purse_pub
   2155   ,action_timestamp
   2156   ,refunded)
   2157 VALUES
   2158   (my_purse_pub
   2159   ,in_now
   2160   ,TRUE);
   2161 NOTIFY X8DJSPNYJMNZDAP7GN6YQ4EZVSQXMF3HRP4VAR347WP9SZYP1C200;
   2162 IF (my_in_reserve_quota)
   2163 THEN
   2164   UPDATE reserves
   2165     SET purses_active=purses_active-1
   2166   WHERE reserve_pub IN
   2167     (SELECT reserve_pub
   2168        FROM exchange.purse_merges
   2169       WHERE purse_pub=my_purse_pub
   2170      LIMIT 1);
   2171 END IF;
   2172 FOR my_deposit IN
   2173   SELECT coin_pub
   2174         ,amount_with_fee
   2175     FROM purse_deposits
   2176   WHERE purse_pub = my_purse_pub
   2177 LOOP
   2178   UPDATE known_coins kc SET
   2179     remaining.frac=(kc.remaining).frac+(my_deposit.amount_with_fee).frac
   2180      - CASE
   2181        WHEN (kc.remaining).frac+(my_deposit.amount_with_fee).frac >= 100000000
   2182        THEN 100000000
   2183        ELSE 0
   2184        END,
   2185     remaining.val=(kc.remaining).val+(my_deposit.amount_with_fee).val
   2186      + CASE
   2187        WHEN (kc.remaining).frac+(my_deposit.amount_with_fee).frac >= 100000000
   2188        THEN 1
   2189        ELSE 0
   2190        END
   2191     WHERE coin_pub = my_deposit.coin_pub;
   2192   END LOOP;
   2193 END $$;
   2194 COMMENT ON FUNCTION exchange_do_expire_purse(INT8,INT8,INT8)
   2195   IS 'Finds an expired purse in the given time range and refunds the coins (if any).';
   2196 CREATE OR REPLACE FUNCTION exchange_do_reserve_open_deposit(
   2197   IN in_coin_pub BYTEA,
   2198   IN in_known_coin_id INT8,
   2199   IN in_coin_sig BYTEA,
   2200   IN in_reserve_sig BYTEA,
   2201   IN in_reserve_pub BYTEA,
   2202   IN in_coin_total taler_amount,
   2203   OUT out_insufficient_funds BOOLEAN)
   2204 LANGUAGE plpgsql
   2205 AS $$
   2206 BEGIN
   2207 INSERT INTO exchange.reserves_open_deposits
   2208   (reserve_sig
   2209   ,reserve_pub
   2210   ,coin_pub
   2211   ,coin_sig
   2212   ,contribution
   2213   )
   2214   VALUES
   2215   (in_reserve_sig
   2216   ,in_reserve_pub
   2217   ,in_coin_pub
   2218   ,in_coin_sig
   2219   ,in_coin_total
   2220   )
   2221   ON CONFLICT DO NOTHING;
   2222 IF NOT FOUND
   2223 THEN
   2224   out_insufficient_funds=FALSE;
   2225   RETURN;
   2226 END IF;
   2227 UPDATE exchange.known_coins kc
   2228   SET
   2229     remaining.frac=(kc.remaining).frac-in_coin_total.frac
   2230        + CASE
   2231          WHEN (kc.remaining).frac < in_coin_total.frac
   2232          THEN 100000000
   2233          ELSE 0
   2234          END,
   2235     remaining.val=(kc.remaining).val-in_coin_total.val
   2236        - CASE
   2237          WHEN (kc.remaining).frac < in_coin_total.frac
   2238          THEN 1
   2239          ELSE 0
   2240          END
   2241   WHERE coin_pub=in_coin_pub
   2242     AND ( ((kc.remaining).val > in_coin_total.val) OR
   2243           ( ((kc.remaining).frac >= in_coin_total.frac) AND
   2244             ((kc.remaining).val >= in_coin_total.val) ) );
   2245 IF NOT FOUND
   2246 THEN
   2247   out_insufficient_funds=TRUE;
   2248   RETURN;
   2249 END IF;
   2250 out_insufficient_funds=FALSE;
   2251 END $$;
   2252 CREATE OR REPLACE FUNCTION exchange_do_reserve_open(
   2253   IN in_reserve_pub BYTEA,
   2254   IN in_total_paid taler_amount,
   2255   IN in_reserve_payment taler_amount,
   2256   IN in_min_purse_limit INT4,
   2257   IN in_default_purse_limit INT4,
   2258   IN in_reserve_sig BYTEA,
   2259   IN in_desired_expiration INT8,
   2260   IN in_reserve_gc_delay INT8,
   2261   IN in_now INT8,
   2262   IN in_open_fee taler_amount,
   2263   OUT out_open_cost taler_amount,
   2264   OUT out_final_expiration INT8,
   2265   OUT out_no_reserve BOOLEAN,
   2266   OUT out_no_funds BOOLEAN,
   2267   OUT out_reserve_balance taler_amount)
   2268 LANGUAGE plpgsql
   2269 AS $$
   2270 DECLARE
   2271   my_balance taler_amount;
   2272   my_cost taler_amount;
   2273   my_cost_tmp INT8;
   2274   my_years_tmp INT4;
   2275   my_years INT4;
   2276   my_needs_update BOOL;
   2277   my_expiration_date INT8;
   2278   reserve RECORD;
   2279 BEGIN
   2280 SELECT current_balance
   2281       ,expiration_date
   2282       ,purses_allowed
   2283   INTO reserve
   2284   FROM reserves
   2285  WHERE reserve_pub=in_reserve_pub;
   2286 IF NOT FOUND
   2287 THEN
   2288   RAISE NOTICE 'reserve not found';
   2289   out_no_reserve = TRUE;
   2290   out_no_funds = TRUE;
   2291   out_reserve_balance.val = 0;
   2292   out_reserve_balance.frac = 0;
   2293   out_open_cost.val = 0;
   2294   out_open_cost.frac = 0;
   2295   out_final_expiration = 0;
   2296   RETURN;
   2297 END IF;
   2298 out_no_reserve = FALSE;
   2299 out_reserve_balance = reserve.current_balance;
   2300 IF (reserve.expiration_date < in_now)
   2301 THEN
   2302   my_expiration_date = in_now;
   2303 ELSE
   2304   my_expiration_date = reserve.expiration_date;
   2305 END IF;
   2306 my_cost.val = 0;
   2307 my_cost.frac = 0;
   2308 my_needs_update = FALSE;
   2309 my_years = 0;
   2310 IF (my_expiration_date < in_desired_expiration)
   2311 THEN
   2312   my_years = (31535999999999 + in_desired_expiration - my_expiration_date) / 31536000000000;
   2313   reserve.purses_allowed = in_default_purse_limit;
   2314   my_expiration_date = my_expiration_date + 31536000000000 * my_years;
   2315 END IF;
   2316 IF (reserve.purses_allowed < in_min_purse_limit)
   2317 THEN
   2318   my_years = (31535999999999 + in_desired_expiration - in_now) / 31536000000000;
   2319   my_expiration_date = in_now + 31536000000000 * my_years;
   2320   my_years_tmp = (in_min_purse_limit + in_default_purse_limit - reserve.purses_allowed - 1) / in_default_purse_limit;
   2321   my_years = my_years + my_years_tmp;
   2322   reserve.purses_allowed = reserve.purses_allowed + (in_default_purse_limit * my_years_tmp);
   2323 END IF;
   2324 IF (my_years > 0)
   2325 THEN
   2326   my_cost.val = my_years * in_open_fee.val;
   2327   my_cost_tmp = my_years * in_open_fee.frac / 100000000;
   2328   IF (CAST (my_cost.val + my_cost_tmp AS INT8) < my_cost.val)
   2329   THEN
   2330     out_open_cost.val=9223372036854775807;
   2331     out_open_cost.frac=2147483647;
   2332     out_final_expiration=my_expiration_date;
   2333     out_no_funds=FALSE;
   2334     RAISE NOTICE 'arithmetic issue computing amount';
   2335   RETURN;
   2336   END IF;
   2337   my_cost.val = CAST (my_cost.val + my_cost_tmp AS INT8);
   2338   my_cost.frac = my_years * in_open_fee.frac % 100000000;
   2339   my_needs_update = TRUE;
   2340 END IF;
   2341 IF NOT my_needs_update
   2342 THEN
   2343   out_final_expiration = reserve.expiration_date;
   2344   out_open_cost.val = 0;
   2345   out_open_cost.frac = 0;
   2346   out_no_funds=FALSE;
   2347   RAISE NOTICE 'no change required';
   2348   RETURN;
   2349 END IF;
   2350 IF ( (in_total_paid.val < my_cost.val) OR
   2351      ( (in_total_paid.val = my_cost.val) AND
   2352        (in_total_paid.frac < my_cost.frac) ) )
   2353 THEN
   2354   out_open_cost.val = my_cost.val;
   2355   out_open_cost.frac = my_cost.frac;
   2356   out_no_funds=FALSE;
   2357   IF (reserve.expiration_date >= in_desired_expiration)
   2358   THEN
   2359     RAISE NOTICE 'forcing low expiration time';
   2360     out_final_expiration = 0;
   2361   ELSE
   2362     out_final_expiration = reserve.expiration_date;
   2363   END IF;
   2364   RAISE NOTICE 'amount paid too low';
   2365   RETURN;
   2366 END IF;
   2367 IF (out_reserve_balance.val > in_reserve_payment.val)
   2368 THEN
   2369   IF (out_reserve_balance.frac >= in_reserve_payment.frac)
   2370   THEN
   2371     my_balance.val=out_reserve_balance.val - in_reserve_payment.val;
   2372     my_balance.frac=out_reserve_balance.frac - in_reserve_payment.frac;
   2373   ELSE
   2374     my_balance.val=out_reserve_balance.val - in_reserve_payment.val - 1;
   2375     my_balance.frac=out_reserve_balance.frac + 100000000 - in_reserve_payment.frac;
   2376   END IF;
   2377 ELSE
   2378   IF (out_reserve_balance.val = in_reserve_payment.val) AND (out_reserve_balance.frac >= in_reserve_payment.frac)
   2379   THEN
   2380     my_balance.val=0;
   2381     my_balance.frac=out_reserve_balance.frac - in_reserve_payment.frac;
   2382   ELSE
   2383     out_final_expiration = reserve.expiration_date;
   2384     out_open_cost.val = my_cost.val;
   2385     out_open_cost.frac = my_cost.frac;
   2386     out_no_funds=TRUE;
   2387     RAISE NOTICE 'reserve balance too low';
   2388   RETURN;
   2389   END IF;
   2390 END IF;
   2391 UPDATE reserves SET
   2392   current_balance=my_balance
   2393  ,gc_date=reserve.expiration_date + in_reserve_gc_delay
   2394  ,expiration_date=my_expiration_date
   2395  ,purses_allowed=reserve.purses_allowed
   2396 WHERE
   2397  reserve_pub=in_reserve_pub;
   2398 out_final_expiration=my_expiration_date;
   2399 out_open_cost = my_cost;
   2400 out_no_funds=FALSE;
   2401 RETURN;
   2402 END $$;
   2403 CREATE OR REPLACE FUNCTION exchange_do_insert_or_update_policy_details(
   2404   IN in_policy_hash_code BYTEA,
   2405   IN in_policy_json TEXT,
   2406   IN in_deadline INT8,
   2407   IN in_commitment taler_amount,
   2408   IN in_accumulated_total taler_amount,
   2409   IN in_fee taler_amount,
   2410   IN in_transferable taler_amount,
   2411   IN in_fulfillment_state SMALLINT,
   2412   OUT out_policy_details_serial_id INT8,
   2413   OUT out_accumulated_total taler_amount,
   2414   OUT out_fulfillment_state SMALLINT)
   2415 LANGUAGE plpgsql
   2416 AS $$
   2417 DECLARE
   2418     cur_commitment taler_amount;
   2419 DECLARE
   2420     cur_accumulated_total taler_amount;
   2421 DECLARE
   2422     rval RECORD;
   2423 BEGIN
   2424        INSERT INTO policy_details
   2425                (policy_hash_code,
   2426                 policy_json,
   2427                 deadline,
   2428                 commitment,
   2429                 accumulated_total,
   2430                 fee,
   2431                 transferable,
   2432                 fulfillment_state)
   2433        VALUES (in_policy_hash_code,
   2434                 in_policy_json,
   2435                 in_deadline,
   2436                 in_commitment,
   2437                 in_accumulated_total,
   2438                 in_fee,
   2439                 in_transferable,
   2440                 in_fulfillment_state)
   2441        ON CONFLICT (policy_hash_code) DO NOTHING
   2442        RETURNING policy_details_serial_id INTO out_policy_details_serial_id;
   2443        IF FOUND THEN
   2444                out_accumulated_total = in_accumulated_total;
   2445                out_fulfillment_state = in_fulfillment_state;
   2446                RETURN;
   2447        END IF;
   2448        SELECT policy_details_serial_id
   2449          ,commitment
   2450          ,accumulated_total
   2451        INTO rval
   2452        FROM policy_details
   2453        WHERE policy_hash_code = in_policy_hash_code;
   2454        out_policy_details_serial_id := rval.policy_details_serial_id;
   2455        cur_commitment := rval.commitment;
   2456        cur_accumulated_total := rval.accumulated_total;
   2457        out_accumulated_total.val = cur_accumulated_total.val + in_accumulated_total.val;
   2458        out_accumulated_total.frac = cur_accumulated_total.frac + in_accumulated_total.frac;
   2459        out_accumulated_total.val = out_accumulated_total.val + out_accumulated_total.frac / 100000000;
   2460        out_accumulated_total.frac = out_accumulated_total.frac % 100000000;
   2461        IF (out_accumulated_total.val > (1 << 52))
   2462        THEN
   2463                RAISE EXCEPTION 'accumulation overflow';
   2464        END IF;
   2465        IF (out_fullfillment_state = 2) 
   2466        THEN
   2467                IF (out_accumulated_total.val >= cur_commitment.val OR
   2468                        (out_accumulated_total.val = cur_commitment.val AND
   2469                                out_accumulated_total.frac >= cur_commitment.frac))
   2470                THEN
   2471                        out_fulfillment_state = 3; 
   2472                END IF;
   2473        END IF;
   2474        UPDATE exchange.policy_details
   2475        SET
   2476                accumulated = out_accumulated_total,
   2477                fulfillment_state = out_fulfillment_state
   2478        WHERE
   2479                policy_details_serial_id = out_policy_details_serial_id;
   2480 END $$;
   2481 DROP FUNCTION IF EXISTS exchange_do_insert_aml_decision;
   2482 CREATE FUNCTION exchange_do_insert_aml_decision(
   2483   IN in_payto_uri TEXT, 
   2484   IN in_h_normalized_payto BYTEA,
   2485   IN in_h_full_payto BYTEA, 
   2486   IN in_decision_time INT8,
   2487   IN in_expiration_time INT8,
   2488   IN in_properties TEXT, 
   2489   IN in_kyc_attributes_enc BYTEA, 
   2490   IN in_kyc_attributes_hash BYTEA, 
   2491   IN in_kyc_attributes_expiration INT8, 
   2492   IN in_new_rules TEXT,
   2493   IN in_to_investigate BOOLEAN,
   2494   IN in_new_measure_name TEXT, 
   2495   IN in_jmeasures TEXT, 
   2496   IN in_justification TEXT, 
   2497   IN in_decider_pub BYTEA, 
   2498   IN in_decider_sig BYTEA, 
   2499   IN in_notify_s TEXT,
   2500   IN ina_events TEXT[],
   2501   IN in_form_name TEXT, 
   2502   OUT out_invalid_officer BOOLEAN,
   2503   OUT out_account_unknown BOOLEAN,
   2504   OUT out_last_date INT8,
   2505   OUT out_legitimization_measure_serial_id INT8,
   2506   OUT out_payto_uri TEXT)
   2507 LANGUAGE plpgsql
   2508 AS $$
   2509 DECLARE
   2510   my_outcome_serial_id INT8;
   2511   my_legitimization_process_serial_id INT8;
   2512   my_kyc_attributes_serial_id INT8;
   2513   my_rec RECORD;
   2514   my_access_token BYTEA;
   2515   my_i INT4;
   2516   ini_event TEXT;
   2517 BEGIN
   2518 out_account_unknown=FALSE;
   2519 out_legitimization_measure_serial_id=0;
   2520 IF in_decider_pub IS NOT NULL
   2521 THEN
   2522   IF in_justification IS NULL OR in_decider_sig IS NULL
   2523   THEN
   2524     RAISE EXCEPTION 'Got in_decider_sig without justification or signature.';
   2525   END IF;
   2526   PERFORM
   2527     FROM aml_staff
   2528     WHERE decider_pub=in_decider_pub
   2529       AND is_active
   2530       AND NOT read_only;
   2531   IF NOT FOUND
   2532   THEN
   2533     out_invalid_officer=TRUE;
   2534     out_last_date=0;
   2535     RETURN;
   2536   END IF;
   2537 END IF;
   2538 out_invalid_officer=FALSE;
   2539 SELECT decision_time
   2540   INTO out_last_date
   2541   FROM legitimization_outcomes
   2542  WHERE h_payto=in_h_normalized_payto
   2543    AND is_active
   2544  ORDER BY decision_time DESC, outcome_serial_id DESC;
   2545 IF FOUND
   2546 THEN
   2547   IF in_decider_pub IS NOT NULL AND out_last_date > in_decision_time
   2548   THEN
   2549     RETURN;
   2550   END IF;
   2551   UPDATE legitimization_outcomes
   2552      SET is_active=FALSE
   2553    WHERE h_payto=in_h_normalized_payto
   2554      AND is_active;
   2555 ELSE
   2556   out_last_date = 0;
   2557 END IF;
   2558 SELECT access_token
   2559       ,payto_uri
   2560   INTO my_rec
   2561   FROM wire_targets
   2562  WHERE h_normalized_payto=in_h_normalized_payto;
   2563 IF NOT FOUND
   2564 THEN
   2565   IF in_payto_uri IS NULL
   2566   THEN
   2567     out_account_unknown=TRUE;
   2568     RETURN;
   2569   END IF;
   2570   out_payto_uri = in_payto_uri;
   2571   INSERT INTO wire_targets
   2572     (wire_target_h_payto
   2573     ,h_normalized_payto
   2574     ,payto_uri)
   2575     VALUES
   2576     (in_h_full_payto
   2577     ,in_h_normalized_payto
   2578     ,in_payto_uri)
   2579     RETURNING access_token
   2580       INTO my_access_token;
   2581 ELSE
   2582   my_access_token = my_rec.access_token;
   2583   out_payto_uri = my_rec.payto_uri;
   2584 END IF;
   2585 IF in_jmeasures IS NOT NULL
   2586 THEN
   2587   SELECT legitimization_measure_serial_id
   2588     INTO out_legitimization_measure_serial_id
   2589     FROM legitimization_measures
   2590     WHERE access_token=my_access_token
   2591       AND jmeasures=in_jmeasures
   2592       AND NOT is_finished;
   2593   IF NOT FOUND
   2594   THEN
   2595     INSERT INTO legitimization_measures
   2596       (access_token
   2597       ,start_time
   2598       ,jmeasures
   2599       ,display_priority)
   2600       VALUES
   2601       (my_access_token
   2602       ,in_decision_time
   2603       ,in_jmeasures
   2604       ,1)
   2605       RETURNING
   2606         legitimization_measure_serial_id
   2607       INTO
   2608         out_legitimization_measure_serial_id;
   2609   END IF;
   2610 END IF;
   2611 RAISE NOTICE 'marking legi measures of % as finished except for %', my_access_token, out_legitimization_measure_serial_id;
   2612 UPDATE legitimization_measures
   2613   SET is_finished=TRUE
   2614   WHERE access_token=my_access_token
   2615     AND NOT is_finished
   2616     AND legitimization_measure_serial_id != out_legitimization_measure_serial_id;
   2617 UPDATE legitimization_outcomes
   2618    SET is_active=FALSE
   2619  WHERE h_payto=in_h_normalized_payto
   2620    AND expiration_time >= in_decision_time;
   2621 INSERT INTO legitimization_outcomes
   2622   (h_payto
   2623   ,decision_time
   2624   ,expiration_time
   2625   ,jproperties
   2626   ,new_measure_name
   2627   ,to_investigate
   2628   ,jnew_rules
   2629   )
   2630   VALUES
   2631   (in_h_normalized_payto
   2632   ,in_decision_time
   2633   ,in_expiration_time
   2634   ,in_properties
   2635   ,in_new_measure_name
   2636   ,in_to_investigate
   2637   ,in_new_rules
   2638   )
   2639   RETURNING
   2640     outcome_serial_id
   2641   INTO
   2642     my_outcome_serial_id;
   2643 IF in_kyc_attributes_enc IS NOT NULL
   2644 THEN
   2645   IF in_kyc_attributes_hash IS NULL OR in_kyc_attributes_expiration IS NULL
   2646   THEN
   2647     RAISE EXCEPTION 'Got in_kyc_attributes_hash without hash or expiration.';
   2648   END IF;
   2649   IF in_decider_pub IS NULL
   2650   THEN
   2651     RAISE EXCEPTION 'Got in_kyc_attributes_hash without in_decider_pub.';
   2652   END IF;
   2653   INSERT INTO legitimization_processes
   2654     (h_payto
   2655     ,start_time
   2656     ,expiration_time
   2657     ,provider_name
   2658     ,provider_user_id
   2659     ,finished
   2660     ) VALUES
   2661     (in_h_normalized_payto
   2662     ,in_decision_time
   2663     ,in_decision_time
   2664     ,'aml-officer'
   2665     ,in_decider_pub
   2666     ,TRUE
   2667     )
   2668     RETURNING legitimization_process_serial_id
   2669     INTO my_legitimization_process_serial_id;
   2670   INSERT INTO kyc_attributes
   2671     (h_payto
   2672     ,collection_time
   2673     ,expiration_time
   2674     ,form_name
   2675     ,by_aml_officer
   2676     ,encrypted_attributes
   2677     ,legitimization_serial
   2678     ) VALUES
   2679     (in_h_normalized_payto
   2680     ,in_decision_time
   2681     ,in_kyc_attributes_expiration
   2682     ,in_form_name
   2683     ,TRUE
   2684     ,in_kyc_attributes_enc
   2685     ,my_legitimization_process_serial_id
   2686     )
   2687     RETURNING kyc_attributes_serial_id
   2688     INTO my_kyc_attributes_serial_id;
   2689 END IF;
   2690 IF in_decider_pub IS NOT NULL
   2691 THEN
   2692   INSERT INTO aml_history
   2693     (h_payto
   2694     ,outcome_serial_id
   2695     ,justification
   2696     ,decider_pub
   2697     ,decider_sig
   2698     ,kyc_attributes_hash
   2699     ,kyc_attributes_serial_id
   2700     ) VALUES
   2701     (in_h_normalized_payto
   2702     ,my_outcome_serial_id
   2703     ,in_justification
   2704     ,in_decider_pub
   2705     ,in_decider_sig
   2706     ,in_kyc_attributes_hash
   2707     ,my_kyc_attributes_serial_id
   2708   );
   2709 END IF;
   2710 FOR i IN 1..COALESCE(array_length(ina_events,1),0)
   2711 LOOP
   2712   ini_event = ina_events[i];
   2713   INSERT INTO kyc_events
   2714     (event_timestamp
   2715     ,event_type)
   2716     VALUES
   2717     (in_decision_time
   2718     ,ini_event);
   2719 END LOOP;
   2720 INSERT INTO kyc_alerts
   2721   (h_payto
   2722   ,trigger_type)
   2723   VALUES
   2724   (in_h_normalized_payto,1)
   2725  ON CONFLICT DO NOTHING;
   2726 EXECUTE FORMAT (
   2727    'NOTIFY %s'
   2728   ,in_notify_s);
   2729 END $$;
   2730 COMMENT ON FUNCTION exchange_do_insert_aml_decision(TEXT, BYTEA, BYTEA, INT8, INT8, TEXT, BYTEA, BYTEA, INT8, TEXT, BOOLEAN, TEXT, TEXT, TEXT, BYTEA, BYTEA, TEXT, TEXT[], TEXT)
   2731   IS 'Checks whether the AML officer is eligible to make AML decisions and if so inserts the decision into the table';
   2732 DROP FUNCTION IF EXISTS exchange_do_insert_successor_measure;
   2733 CREATE FUNCTION exchange_do_insert_successor_measure(
   2734   IN in_h_normalized_payto BYTEA,
   2735   IN in_decision_time INT8,
   2736   IN in_expiration_time INT8,
   2737   IN in_new_measure_name TEXT, 
   2738   IN in_jmeasures TEXT, 
   2739   OUT out_last_date INT8,
   2740   OUT out_account_unknown BOOLEAN,
   2741   OUT out_legitimization_measure_serial_id INT8
   2742 )
   2743 LANGUAGE plpgsql
   2744 AS $$
   2745 DECLARE
   2746   my_outcome_serial_id INT8;
   2747   my_access_token BYTEA;
   2748 BEGIN
   2749 out_account_unknown=FALSE;
   2750 out_legitimization_measure_serial_id=0;
   2751 SELECT decision_time
   2752   INTO out_last_date
   2753   FROM legitimization_outcomes
   2754  WHERE h_payto=in_h_normalized_payto
   2755    AND is_active
   2756  ORDER BY decision_time DESC, outcome_serial_id DESC;
   2757 IF FOUND
   2758 THEN
   2759   IF out_last_date > in_decision_time
   2760   THEN
   2761     RETURN;
   2762   END IF;
   2763   UPDATE legitimization_outcomes
   2764      SET is_active=FALSE
   2765    WHERE h_payto=in_h_normalized_payto
   2766      AND is_active;
   2767 ELSE
   2768   out_last_date = 0;
   2769 END IF;
   2770 SELECT access_token
   2771   INTO my_access_token
   2772   FROM wire_targets
   2773  WHERE h_normalized_payto=in_h_normalized_payto;
   2774 IF NOT FOUND
   2775 THEN
   2776   IF in_payto_uri IS NULL
   2777   THEN
   2778     out_account_unknown=TRUE;
   2779     RETURN;
   2780   END IF;
   2781   INSERT INTO wire_targets
   2782     (wire_target_h_payto
   2783     ,h_normalized_payto
   2784     ,payto_uri)
   2785     VALUES
   2786     (in_h_full_payto
   2787     ,in_h_normalized_payto
   2788     ,in_payto_uri)
   2789     RETURNING access_token
   2790       INTO my_access_token;
   2791 END IF;
   2792 SELECT legitimization_measure_serial_id
   2793   INTO out_legitimization_measure_serial_id
   2794   FROM legitimization_measures
   2795   WHERE access_token=my_access_token
   2796     AND jmeasures=in_jmeasures
   2797     AND NOT is_finished;
   2798 IF NOT FOUND
   2799 THEN
   2800   INSERT INTO legitimization_measures
   2801     (access_token
   2802     ,start_time
   2803     ,jmeasures
   2804     ,display_priority)
   2805     VALUES
   2806     (my_access_token
   2807     ,in_decision_time
   2808     ,in_jmeasures
   2809     ,1)
   2810     RETURNING
   2811       legitimization_measure_serial_id
   2812     INTO
   2813       out_legitimization_measure_serial_id;
   2814 END IF;
   2815 UPDATE legitimization_measures
   2816   SET is_finished=TRUE
   2817   WHERE access_token=my_access_token
   2818     AND NOT is_finished
   2819     AND legitimization_measure_serial_id != out_legitimization_measure_serial_id;
   2820 UPDATE legitimization_outcomes
   2821    SET is_active=FALSE
   2822  WHERE h_payto=in_h_normalized_payto
   2823    AND expiration_time >= in_decision_time;
   2824 INSERT INTO legitimization_outcomes
   2825   (h_payto
   2826   ,decision_time
   2827   ,expiration_time
   2828   ,jproperties
   2829   ,new_measure_name
   2830   ,to_investigate
   2831   ,jnew_rules
   2832   )
   2833   VALUES
   2834   (in_h_normalized_payto
   2835   ,in_decision_time
   2836   ,in_expiration_time
   2837   ,'{}'
   2838   ,in_new_measure_name
   2839   ,FALSE
   2840   ,NULL
   2841   )
   2842   RETURNING
   2843     outcome_serial_id
   2844   INTO
   2845     my_outcome_serial_id;
   2846 END $$;
   2847 COMMENT ON FUNCTION exchange_do_insert_successor_measure(BYTEA, INT8, INT8, TEXT, TEXT)
   2848   IS 'Checks whether the AML officer is eligible to make AML decisions and if so inserts the decision into the table';
   2849 CREATE OR REPLACE FUNCTION exchange_do_insert_aml_officer(
   2850   IN in_decider_pub BYTEA,
   2851   IN in_master_sig BYTEA,
   2852   IN in_decider_name TEXT,
   2853   IN in_is_active BOOLEAN,
   2854   IN in_read_only BOOLEAN,
   2855   IN in_last_change INT8,
   2856   OUT out_last_change INT8)
   2857 LANGUAGE plpgsql
   2858 AS $$
   2859 BEGIN
   2860 INSERT INTO exchange.aml_staff
   2861   (decider_pub
   2862   ,master_sig
   2863   ,decider_name
   2864   ,is_active
   2865   ,read_only
   2866   ,last_change
   2867   ) VALUES
   2868   (in_decider_pub
   2869   ,in_master_sig
   2870   ,in_decider_name
   2871   ,in_is_active
   2872   ,in_read_only
   2873   ,in_last_change)
   2874  ON CONFLICT DO NOTHING;
   2875 IF FOUND
   2876 THEN
   2877   out_last_change=0;
   2878   RETURN;
   2879 END IF;
   2880 SELECT last_change
   2881   INTO out_last_change
   2882   FROM exchange.aml_staff
   2883   WHERE decider_pub=in_decider_pub;
   2884 ASSERT FOUND, 'cannot have INSERT conflict but no AML staff record';
   2885 IF out_last_change >= in_last_change
   2886 THEN
   2887  RETURN;
   2888 END IF;
   2889 UPDATE exchange.aml_staff
   2890   SET master_sig=in_master_sig
   2891      ,decider_name=in_decider_name
   2892      ,is_active=in_is_active
   2893      ,read_only=in_read_only
   2894      ,last_change=in_last_change
   2895   WHERE decider_pub=in_decider_pub;
   2896 END $$;
   2897 COMMENT ON FUNCTION exchange_do_insert_aml_officer(BYTEA, BYTEA, TEXT, BOOL, BOOL, INT8)
   2898   IS 'Inserts or updates AML staff record, making sure the update is more recent than the previous change';
   2899 DROP FUNCTION IF EXISTS exchange_do_array_reserves_insert;
   2900 CREATE FUNCTION exchange_do_array_reserves_insert(
   2901   IN in_gc_date INT8,
   2902   IN in_reserve_expiration INT8,
   2903   IN ina_reserve_pub BYTEA[],
   2904   IN ina_wire_ref INT8[],
   2905   IN ina_credit taler_amount[],
   2906   IN ina_exchange_account_name TEXT[],
   2907   IN ina_execution_date INT8[],
   2908   IN ina_wire_source_h_payto BYTEA[],
   2909   IN ina_h_normalized_payto BYTEA[],
   2910   IN ina_payto_uri TEXT[],
   2911   IN ina_notify TEXT[])
   2912 RETURNS SETOF exchange_do_array_reserve_insert_return_type
   2913 LANGUAGE plpgsql
   2914 AS $$
   2915 DECLARE
   2916   conflict BOOL;
   2917   dup BOOL;
   2918   uuid INT8;
   2919   i INT4;
   2920   ini_reserve_pub BYTEA;
   2921   ini_wire_ref INT8;
   2922   ini_credit taler_amount;
   2923   ini_exchange_account_name TEXT;
   2924   ini_execution_date INT8;
   2925   ini_wire_source_h_payto BYTEA;
   2926   ini_h_normalized_payto BYTEA;
   2927   ini_payto_uri TEXT;
   2928   ini_notify TEXT;
   2929 BEGIN
   2930   FOR i IN 1..array_length(ina_reserve_pub,1)
   2931   LOOP
   2932     ini_reserve_pub = ina_reserve_pub[i];
   2933     ini_wire_ref = ina_wire_ref[i];
   2934     ini_credit = ina_credit[i];
   2935     ini_exchange_account_name = ina_exchange_account_name[i];
   2936     ini_execution_date = ina_execution_date[i];
   2937     ini_wire_source_h_payto = ina_wire_source_h_payto[i];
   2938     ini_h_normalized_payto = ina_h_normalized_payto[i];
   2939     ini_payto_uri = ina_payto_uri[i];
   2940     ini_notify = ina_notify[i];
   2941     INSERT INTO wire_targets
   2942       (wire_target_h_payto
   2943       ,h_normalized_payto
   2944       ,payto_uri
   2945       ) VALUES (
   2946         ini_wire_source_h_payto
   2947        ,ini_h_normalized_payto
   2948        ,ini_payto_uri
   2949       )
   2950     ON CONFLICT DO NOTHING;
   2951     INSERT INTO reserves
   2952       (reserve_pub
   2953       ,current_balance
   2954       ,expiration_date
   2955       ,gc_date
   2956     ) VALUES (
   2957       ini_reserve_pub
   2958      ,ini_credit
   2959      ,in_reserve_expiration
   2960      ,in_gc_date
   2961     )
   2962     ON CONFLICT DO NOTHING
   2963     RETURNING reserve_uuid
   2964       INTO uuid;
   2965     conflict = NOT FOUND;
   2966     INSERT INTO reserves_in
   2967       (reserve_pub
   2968       ,wire_reference
   2969       ,credit
   2970       ,exchange_account_section
   2971       ,wire_source_h_payto
   2972       ,execution_date
   2973     ) VALUES (
   2974       ini_reserve_pub
   2975      ,ini_wire_ref
   2976      ,ini_credit
   2977      ,ini_exchange_account_name
   2978      ,ini_wire_source_h_payto
   2979      ,ini_execution_date
   2980     )
   2981     ON CONFLICT DO NOTHING;
   2982     IF NOT FOUND
   2983     THEN
   2984       IF conflict
   2985       THEN
   2986         dup = TRUE;
   2987       else
   2988         dup = FALSE;
   2989       END IF;
   2990     ELSE
   2991       IF NOT conflict
   2992       THEN
   2993         EXECUTE FORMAT (
   2994           'NOTIFY %s'
   2995           ,ini_notify);
   2996       END IF;
   2997       dup = FALSE;
   2998     END IF;
   2999     RETURN NEXT (dup,uuid);
   3000   END LOOP;
   3001   RETURN;
   3002 END $$;
   3003 CREATE OR REPLACE FUNCTION exchange_do_batch_reserves_update(
   3004   IN in_reserve_pub BYTEA,
   3005   IN in_expiration_date INT8,
   3006   IN in_wire_ref INT8,
   3007   IN in_credit taler_amount,
   3008   IN in_exchange_account_name TEXT,
   3009   IN in_wire_source_h_payto BYTEA,
   3010   IN in_notify text,
   3011   OUT out_duplicate BOOLEAN)
   3012 LANGUAGE plpgsql
   3013 AS $$
   3014 BEGIN
   3015   INSERT INTO reserves_in
   3016     (reserve_pub
   3017     ,wire_reference
   3018     ,credit
   3019     ,exchange_account_section
   3020     ,wire_source_h_payto
   3021     ,execution_date)
   3022     VALUES
   3023     (in_reserve_pub
   3024     ,in_wire_ref
   3025     ,in_credit
   3026     ,in_exchange_account_name
   3027     ,in_wire_source_h_payto
   3028     ,in_expiration_date)
   3029     ON CONFLICT DO NOTHING;
   3030   IF FOUND
   3031   THEN
   3032     out_duplicate = FALSE;
   3033     UPDATE reserves rs
   3034       SET
   3035          current_balance.frac = (rs.current_balance).frac+in_credit.frac
   3036            - CASE
   3037              WHEN (rs.current_balance).frac + in_credit.frac >= 100000000
   3038                THEN 100000000
   3039              ELSE 1
   3040              END
   3041         ,current_balance.val = (rs.current_balance).val+in_credit.val
   3042            + CASE
   3043              WHEN (rs.current_balance).frac + in_credit.frac >= 100000000
   3044                THEN 1
   3045              ELSE 0
   3046              END
   3047              ,expiration_date=GREATEST(expiration_date,in_expiration_date)
   3048              ,gc_date=GREATEST(gc_date,in_expiration_date)
   3049             WHERE reserve_pub=in_reserve_pub;
   3050     EXECUTE FORMAT (
   3051       'NOTIFY %s'
   3052       ,in_notify);
   3053   ELSE
   3054     out_duplicate = TRUE;
   3055   END IF;
   3056   RETURN;
   3057 END $$;
   3058 CREATE OR REPLACE FUNCTION exchange_do_get_link_data(
   3059   IN in_coin_pub BYTEA
   3060 )
   3061 RETURNS SETOF record
   3062 LANGUAGE plpgsql
   3063 AS $$
   3064 DECLARE
   3065   curs CURSOR
   3066   FOR
   3067   SELECT
   3068    melt_serial_id
   3069   FROM refresh_commitments
   3070   WHERE old_coin_pub=in_coin_pub;
   3071 DECLARE
   3072   i RECORD;
   3073 BEGIN
   3074 OPEN curs;
   3075 LOOP
   3076     FETCH NEXT FROM curs INTO i;
   3077     EXIT WHEN NOT FOUND;
   3078     RETURN QUERY
   3079       SELECT
   3080        tp.transfer_pub
   3081       ,denoms.denom_pub
   3082       ,rrc.ev_sig
   3083       ,rrc.ewv
   3084       ,rrc.link_sig
   3085       ,rrc.freshcoin_index
   3086       ,rrc.coin_ev
   3087       FROM refresh_revealed_coins rrc
   3088        JOIN refresh_transfer_keys tp
   3089          ON (tp.melt_serial_id=rrc.melt_serial_id)
   3090        JOIN denominations denoms
   3091          ON (rrc.denominations_serial=denoms.denominations_serial)
   3092        WHERE rrc.melt_serial_id =i.melt_serial_id
   3093        ORDER BY tp.transfer_pub,
   3094        rrc.freshcoin_index ASC
   3095        ;
   3096 END LOOP;
   3097 CLOSE curs;
   3098 END $$;
   3099 CREATE OR REPLACE FUNCTION exchange_do_batch4_known_coin(
   3100   IN in_coin_pub1 BYTEA,
   3101   IN in_denom_pub_hash1 BYTEA,
   3102   IN in_h_age_commitment1 BYTEA,
   3103   IN in_denom_sig1 BYTEA,
   3104   IN in_coin_pub2 BYTEA,
   3105   IN in_denom_pub_hash2 BYTEA,
   3106   IN in_h_age_commitment2 BYTEA,
   3107   IN in_denom_sig2 BYTEA,
   3108   IN in_coin_pub3 BYTEA,
   3109   IN in_denom_pub_hash3 BYTEA,
   3110   IN in_h_age_commitment3 BYTEA,
   3111   IN in_denom_sig3 BYTEA,
   3112   IN in_coin_pub4 BYTEA,
   3113   IN in_denom_pub_hash4 BYTEA,
   3114   IN in_h_age_commitment4 BYTEA,
   3115   IN in_denom_sig4 BYTEA,
   3116   OUT existed1 BOOLEAN,
   3117   OUT existed2 BOOLEAN,
   3118   OUT existed3 BOOLEAN,
   3119   OUT existed4 BOOLEAN,
   3120   OUT known_coin_id1 INT8,
   3121   OUT known_coin_id2 INT8,
   3122   OUT known_coin_id3 INT8,
   3123   OUT known_coin_id4 INT8,
   3124   OUT denom_pub_hash1 BYTEA,
   3125   OUT denom_pub_hash2 BYTEA,
   3126   OUT denom_pub_hash3 BYTEA,
   3127   OUT denom_pub_hash4 BYTEA,
   3128   OUT age_commitment_hash1 BYTEA,
   3129   OUT age_commitment_hash2 BYTEA,
   3130   OUT age_commitment_hash3 BYTEA,
   3131   OUT age_commitment_hash4 BYTEA)
   3132 LANGUAGE plpgsql
   3133 AS $$
   3134 BEGIN
   3135 WITH dd AS (
   3136 SELECT
   3137   denominations_serial,
   3138   coin
   3139   FROM denominations
   3140     WHERE denom_pub_hash
   3141     IN
   3142      (in_denom_pub_hash1,
   3143       in_denom_pub_hash2,
   3144       in_denom_pub_hash3,
   3145       in_denom_pub_hash4)
   3146      ),
   3147      input_rows AS (
   3148      VALUES
   3149       (in_coin_pub1,
   3150       in_denom_pub_hash1,
   3151       in_h_age_commitment1,
   3152       in_denom_sig1),
   3153       (in_coin_pub2,
   3154       in_denom_pub_hash2,
   3155       in_h_age_commitment2,
   3156       in_denom_sig2),
   3157       (in_coin_pub3,
   3158       in_denom_pub_hash3,
   3159       in_h_age_commitment3,
   3160       in_denom_sig3),
   3161       (in_coin_pub4,
   3162       in_denom_pub_hash4,
   3163       in_h_age_commitment4,
   3164       in_denom_sig4)
   3165       ),
   3166       ins AS (
   3167       INSERT INTO known_coins (
   3168       coin_pub,
   3169       denominations_serial,
   3170       age_commitment_hash,
   3171       denom_sig,
   3172       remaining
   3173       )
   3174       SELECT
   3175         ir.coin_pub,
   3176         dd.denominations_serial,
   3177         ir.age_commitment_hash,
   3178         ir.denom_sig,
   3179         dd.coin
   3180         FROM input_rows ir
   3181         JOIN dd
   3182           ON dd.denom_pub_hash = ir.denom_pub_hash
   3183           ON CONFLICT DO NOTHING
   3184           RETURNING known_coin_id
   3185       ),
   3186        exists AS (
   3187          SELECT
   3188          CASE
   3189            WHEN
   3190              ins.known_coin_id IS NOT NULL
   3191              THEN
   3192                FALSE
   3193              ELSE
   3194                TRUE
   3195          END AS existed,
   3196          ins.known_coin_id,
   3197          dd.denom_pub_hash,
   3198          kc.age_commitment_hash
   3199          FROM input_rows ir
   3200          LEFT JOIN ins
   3201            ON ins.coin_pub = ir.coin_pub
   3202          LEFT JOIN known_coins kc
   3203            ON kc.coin_pub = ir.coin_pub
   3204          LEFT JOIN dd
   3205            ON dd.denom_pub_hash = ir.denom_pub_hash
   3206          )
   3207 SELECT
   3208  exists.existed AS existed1,
   3209  exists.known_coin_id AS known_coin_id1,
   3210  exists.denom_pub_hash AS denom_pub_hash1,
   3211  exists.age_commitment_hash AS age_commitment_hash1,
   3212  (
   3213    SELECT exists.existed
   3214    FROM exists
   3215    WHERE exists.denom_pub_hash = in_denom_pub_hash2
   3216  ) AS existed2,
   3217  (
   3218    SELECT exists.known_coin_id
   3219    FROM exists
   3220    WHERE exists.denom_pub_hash = in_denom_pub_hash2
   3221  ) AS known_coin_id2,
   3222  (
   3223    SELECT exists.denom_pub_hash
   3224    FROM exists
   3225    WHERE exists.denom_pub_hash = in_denom_pub_hash2
   3226  ) AS denom_pub_hash2,
   3227  (
   3228    SELECT exists.age_commitment_hash
   3229    FROM exists
   3230    WHERE exists.denom_pub_hash = in_denom_pub_hash2
   3231  )AS age_commitment_hash2,
   3232  (
   3233    SELECT exists.existed
   3234    FROM exists
   3235    WHERE exists.denom_pub_hash = in_denom_pub_hash3
   3236  ) AS existed3,
   3237  (
   3238    SELECT exists.known_coin_id
   3239    FROM exists
   3240    WHERE exists.denom_pub_hash = in_denom_pub_hash3
   3241  ) AS known_coin_id3,
   3242  (
   3243    SELECT exists.denom_pub_hash
   3244    FROM exists
   3245    WHERE exists.denom_pub_hash = in_denom_pub_hash3
   3246  ) AS denom_pub_hash3,
   3247  (
   3248    SELECT exists.age_commitment_hash
   3249    FROM exists
   3250    WHERE exists.denom_pub_hash = in_denom_pub_hash3
   3251  )AS age_commitment_hash3,
   3252  (
   3253    SELECT exists.existed
   3254    FROM exists
   3255    WHERE exists.denom_pub_hash = in_denom_pub_hash4
   3256  ) AS existed4,
   3257  (
   3258    SELECT exists.known_coin_id
   3259    FROM exists
   3260    WHERE exists.denom_pub_hash = in_denom_pub_hash4
   3261  ) AS known_coin_id4,
   3262  (
   3263    SELECT exists.denom_pub_hash
   3264    FROM exists
   3265    WHERE exists.denom_pub_hash = in_denom_pub_hash4
   3266  ) AS denom_pub_hash4,
   3267  (
   3268    SELECT exists.age_commitment_hash
   3269    FROM exists
   3270    WHERE exists.denom_pub_hash = in_denom_pub_hash4
   3271  )AS age_commitment_hash4
   3272 FROM exists;
   3273 RETURN;
   3274 END $$;
   3275 CREATE OR REPLACE FUNCTION exchange_do_batch2_known_coin(
   3276   IN in_coin_pub1 BYTEA,
   3277   IN in_denom_pub_hash1 BYTEA,
   3278   IN in_h_age_commitment1 BYTEA,
   3279   IN in_denom_sig1 BYTEA,
   3280   IN in_coin_pub2 BYTEA,
   3281   IN in_denom_pub_hash2 BYTEA,
   3282   IN in_h_age_commitment2 BYTEA,
   3283   IN in_denom_sig2 BYTEA,
   3284   OUT existed1 BOOLEAN,
   3285   OUT existed2 BOOLEAN,
   3286   OUT known_coin_id1 INT8,
   3287   OUT known_coin_id2 INT8,
   3288   OUT denom_pub_hash1 BYTEA,
   3289   OUT denom_pub_hash2 BYTEA,
   3290   OUT age_commitment_hash1 BYTEA,
   3291   OUT age_commitment_hash2 BYTEA)
   3292 LANGUAGE plpgsql
   3293 AS $$
   3294 BEGIN
   3295 WITH dd AS (
   3296 SELECT
   3297   denominations_serial,
   3298   coin
   3299   FROM denominations
   3300     WHERE denom_pub_hash
   3301     IN
   3302      (in_denom_pub_hash1,
   3303       in_denom_pub_hash2)
   3304      ),
   3305      input_rows AS (
   3306      VALUES
   3307       (in_coin_pub1,
   3308       in_denom_pub_hash1,
   3309       in_h_age_commitment1,
   3310       in_denom_sig1),
   3311       (in_coin_pub2,
   3312       in_denom_pub_hash2,
   3313       in_h_age_commitment2,
   3314       in_denom_sig2)
   3315       ),
   3316       ins AS (
   3317       INSERT INTO known_coins (
   3318       coin_pub,
   3319       denominations_serial,
   3320       age_commitment_hash,
   3321       denom_sig,
   3322       remaining
   3323       )
   3324       SELECT
   3325         ir.coin_pub,
   3326         dd.denominations_serial,
   3327         ir.age_commitment_hash,
   3328         ir.denom_sig,
   3329         dd.coin
   3330         FROM input_rows ir
   3331         JOIN dd
   3332           ON dd.denom_pub_hash = ir.denom_pub_hash
   3333           ON CONFLICT DO NOTHING
   3334           RETURNING known_coin_id
   3335       ),
   3336        exists AS (
   3337        SELECT
   3338         CASE
   3339           WHEN ins.known_coin_id IS NOT NULL
   3340           THEN
   3341             FALSE
   3342           ELSE
   3343             TRUE
   3344         END AS existed,
   3345         ins.known_coin_id,
   3346         dd.denom_pub_hash,
   3347         kc.age_commitment_hash
   3348         FROM input_rows ir
   3349         LEFT JOIN ins
   3350           ON ins.coin_pub = ir.coin_pub
   3351         LEFT JOIN known_coins kc
   3352           ON kc.coin_pub = ir.coin_pub
   3353         LEFT JOIN dd
   3354           ON dd.denom_pub_hash = ir.denom_pub_hash
   3355      )
   3356 SELECT
   3357  exists.existed AS existed1,
   3358  exists.known_coin_id AS known_coin_id1,
   3359  exists.denom_pub_hash AS denom_pub_hash1,
   3360  exists.age_commitment_hash AS age_commitment_hash1,
   3361  (
   3362    SELECT exists.existed
   3363    FROM exists
   3364    WHERE exists.denom_pub_hash = in_denom_pub_hash2
   3365  ) AS existed2,
   3366  (
   3367    SELECT exists.known_coin_id
   3368    FROM exists
   3369    WHERE exists.denom_pub_hash = in_denom_pub_hash2
   3370  ) AS known_coin_id2,
   3371  (
   3372    SELECT exists.denom_pub_hash
   3373    FROM exists
   3374    WHERE exists.denom_pub_hash = in_denom_pub_hash2
   3375  ) AS denom_pub_hash2,
   3376  (
   3377    SELECT exists.age_commitment_hash
   3378    FROM exists
   3379    WHERE exists.denom_pub_hash = in_denom_pub_hash2
   3380  )AS age_commitment_hash2
   3381 FROM exists;
   3382 RETURN;
   3383 END $$;
   3384 CREATE OR REPLACE FUNCTION exchange_do_batch1_known_coin(
   3385   IN in_coin_pub1 BYTEA,
   3386   IN in_denom_pub_hash1 BYTEA,
   3387   IN in_h_age_commitment1 BYTEA,
   3388   IN in_denom_sig1 BYTEA,
   3389   OUT existed1 BOOLEAN,
   3390   OUT known_coin_id1 INT8,
   3391   OUT denom_pub_hash1 BYTEA,
   3392   OUT age_commitment_hash1 BYTEA)
   3393 LANGUAGE plpgsql
   3394 AS $$
   3395 BEGIN
   3396 WITH dd AS (
   3397 SELECT
   3398   denominations_serial,
   3399   coin
   3400   FROM denominations
   3401     WHERE denom_pub_hash
   3402     IN
   3403      (in_denom_pub_hash1,
   3404       in_denom_pub_hash2)
   3405      ),
   3406      input_rows AS (
   3407      VALUES
   3408       (in_coin_pub1,
   3409       in_denom_pub_hash1,
   3410       in_h_age_commitment1,
   3411       in_denom_sig1)
   3412       ),
   3413       ins AS (
   3414       INSERT INTO known_coins (
   3415       coin_pub,
   3416       denominations_serial,
   3417       age_commitment_hash,
   3418       denom_sig,
   3419       remaining
   3420       )
   3421       SELECT
   3422         ir.coin_pub,
   3423         dd.denominations_serial,
   3424         ir.age_commitment_hash,
   3425         ir.denom_sig,
   3426         dd.coin
   3427         FROM input_rows ir
   3428         JOIN dd
   3429           ON dd.denom_pub_hash = ir.denom_pub_hash
   3430           ON CONFLICT DO NOTHING
   3431           RETURNING known_coin_id
   3432       ),
   3433        exists AS (
   3434        SELECT
   3435         CASE
   3436           WHEN ins.known_coin_id IS NOT NULL
   3437           THEN
   3438             FALSE
   3439           ELSE
   3440             TRUE
   3441         END AS existed,
   3442         ins.known_coin_id,
   3443         dd.denom_pub_hash,
   3444         kc.age_commitment_hash
   3445         FROM input_rows ir
   3446         LEFT JOIN ins
   3447           ON ins.coin_pub = ir.coin_pub
   3448         LEFT JOIN known_coins kc
   3449           ON kc.coin_pub = ir.coin_pub
   3450         LEFT JOIN dd
   3451           ON dd.denom_pub_hash = ir.denom_pub_hash
   3452        )
   3453 SELECT
   3454  exists.existed AS existed1,
   3455  exists.known_coin_id AS known_coin_id1,
   3456  exists.denom_pub_hash AS denom_pub_hash1,
   3457  exists.age_commitment_hash AS age_commitment_hash1
   3458 FROM exists;
   3459 RETURN;
   3460 END $$;
   3461 DROP PROCEDURE IF EXISTS exchange_do_kycauth_in_insert;
   3462 CREATE PROCEDURE exchange_do_kycauth_in_insert(
   3463   IN in_account_pub BYTEA,
   3464   IN in_wire_reference INT8,
   3465   IN in_credit taler_amount,
   3466   IN in_wire_source_h_payto BYTEA,
   3467   IN in_h_normalized_payto BYTEA,
   3468   IN in_payto_uri TEXT,
   3469   IN in_exchange_account_name TEXT,
   3470   IN in_execution_date INT8,
   3471   IN in_notify_s TEXT)
   3472 LANGUAGE plpgsql
   3473 AS $$
   3474 BEGIN
   3475   INSERT INTO kycauths_in
   3476     (account_pub
   3477     ,wire_reference
   3478     ,credit
   3479     ,wire_source_h_payto
   3480     ,exchange_account_section
   3481     ,execution_date
   3482     ) VALUES (
   3483      in_account_pub
   3484     ,in_wire_reference
   3485     ,in_credit
   3486     ,in_wire_source_h_payto
   3487     ,in_exchange_account_name
   3488     ,in_execution_date
   3489     )
   3490     ON CONFLICT DO NOTHING;
   3491   IF NOT FOUND
   3492   THEN
   3493     RETURN;
   3494   END IF;
   3495   UPDATE wire_targets
   3496      SET target_pub=in_account_pub
   3497    WHERE wire_target_h_payto=in_wire_source_h_payto;
   3498   IF NOT FOUND
   3499   THEN
   3500     INSERT INTO wire_targets
   3501       (wire_target_h_payto
   3502       ,h_normalized_payto
   3503       ,payto_uri
   3504       ,target_pub
   3505       ) VALUES (
   3506        in_wire_source_h_payto
   3507       ,in_h_normalized_payto
   3508       ,in_payto_uri
   3509       ,in_account_pub);
   3510   END IF;
   3511   EXECUTE FORMAT (
   3512      'NOTIFY %s'
   3513     ,in_notify_s);
   3514 END $$;
   3515 DROP FUNCTION IF EXISTS exchange_do_trigger_kyc_rule_for_account;
   3516 CREATE FUNCTION exchange_do_trigger_kyc_rule_for_account(
   3517   IN in_h_normalized_payto BYTEA,
   3518   IN in_account_pub BYTEA, 
   3519   IN in_merchant_pub BYTEA, 
   3520   IN in_payto_uri TEXT, 
   3521   IN in_h_full_payto BYTEA,
   3522   IN in_now INT8,
   3523   IN in_jmeasures TEXT,
   3524   IN in_display_priority INT4,
   3525   IN in_notify_s TEXT,
   3526   OUT out_legitimization_measure_serial_id INT8,
   3527   OUT out_bad_kyc_auth BOOL)
   3528 LANGUAGE plpgsql
   3529 AS $$
   3530 DECLARE
   3531   my_rec RECORD;
   3532   my_access_token BYTEA;
   3533   my_account_pub BYTEA;
   3534   my_reserve_pub BYTEA;
   3535 BEGIN
   3536 SELECT
   3537    access_token
   3538   ,target_pub
   3539 INTO
   3540   my_rec
   3541 FROM wire_targets
   3542   WHERE h_normalized_payto=in_h_normalized_payto;
   3543 IF FOUND
   3544 THEN
   3545   my_access_token = my_rec.access_token;
   3546   my_account_pub = my_rec.target_pub;
   3547   out_bad_kyc_auth = COALESCE ((my_account_pub != in_merchant_pub), TRUE);
   3548 ELSE
   3549   INSERT INTO wire_targets
   3550     (payto_uri
   3551     ,wire_target_h_payto
   3552     ,h_normalized_payto
   3553     ,target_pub)
   3554   VALUES
   3555     (in_payto_uri
   3556     ,in_h_full_payto
   3557     ,in_h_normalized_payto
   3558     ,in_account_pub)
   3559   RETURNING
   3560     access_token
   3561   INTO my_access_token;
   3562   out_bad_kyc_auth=TRUE;
   3563 END IF;
   3564 IF out_bad_kyc_auth
   3565 THEN
   3566   PERFORM FROM reserves_in
   3567     WHERE wire_source_h_payto IN (
   3568       SELECT wire_target_h_payto
   3569         FROM wire_targets
   3570        WHERE h_normalized_payto=in_h_normalized_payto
   3571       )
   3572       AND reserve_pub = in_merchant_pub
   3573    ORDER BY execution_date DESC;
   3574   IF FOUND
   3575   THEN
   3576     out_bad_kyc_auth = FALSE;
   3577   END IF;
   3578 END IF;
   3579 UPDATE legitimization_measures
   3580    SET display_priority=GREATEST(in_display_priority,display_priority)
   3581  WHERE access_token=my_access_token
   3582    AND jmeasures=in_jmeasures
   3583    AND NOT is_finished
   3584  RETURNING legitimization_measure_serial_id
   3585   INTO out_legitimization_measure_serial_id;
   3586 IF NOT FOUND
   3587 THEN
   3588   INSERT INTO legitimization_measures
   3589     (access_token
   3590     ,start_time
   3591     ,jmeasures
   3592     ,display_priority)
   3593     VALUES
   3594     (my_access_token
   3595     ,in_now
   3596     ,in_jmeasures
   3597     ,in_display_priority)
   3598     RETURNING
   3599       legitimization_measure_serial_id
   3600     INTO
   3601       out_legitimization_measure_serial_id;
   3602   UPDATE legitimization_measures
   3603     SET is_finished=TRUE
   3604     WHERE access_token=my_access_token
   3605       AND NOT is_finished
   3606       AND legitimization_measure_serial_id != out_legitimization_measure_serial_id;
   3607 END IF;
   3608 EXECUTE FORMAT (
   3609    'NOTIFY %s'
   3610   ,in_notify_s);
   3611 END $$;
   3612 DROP FUNCTION IF EXISTS exchange_do_lookup_kyc_requirement_by_row;
   3613 CREATE FUNCTION exchange_do_lookup_kyc_requirement_by_row(
   3614   IN in_h_normalized_payto BYTEA,
   3615   OUT out_account_pub BYTEA, 
   3616   OUT out_reserve_pub BYTEA, 
   3617   OUT out_access_token BYTEA, 
   3618   OUT out_jrules TEXT, 
   3619   OUT out_payto TEXT, 
   3620   OUT out_not_found BOOLEAN,
   3621   OUT out_rule_gen INT8, 
   3622   OUT out_aml_review BOOLEAN, 
   3623   OUT out_kyc_required BOOLEAN)
   3624 LANGUAGE plpgsql
   3625 AS $$
   3626 DECLARE
   3627   my_wtrec RECORD;
   3628   my_lorec RECORD;
   3629 BEGIN
   3630 SELECT access_token
   3631       ,target_pub
   3632       ,payto_uri
   3633   INTO my_wtrec
   3634   FROM wire_targets
   3635  WHERE h_normalized_payto=in_h_normalized_payto;
   3636 IF NOT FOUND
   3637 THEN
   3638   out_not_found = TRUE;
   3639   out_kyc_required = FALSE;
   3640   RETURN;
   3641 END IF;
   3642 out_not_found = FALSE;
   3643 out_payto = my_wtrec.payto_uri;
   3644 out_account_pub = my_wtrec.target_pub;
   3645 out_access_token = my_wtrec.access_token;
   3646 PERFORM
   3647   FROM legitimization_measures
   3648  WHERE access_token=out_access_token
   3649    AND NOT is_finished
   3650  LIMIT 1;
   3651 out_kyc_required = FOUND;
   3652 SELECT jnew_rules
   3653       ,to_investigate
   3654       ,outcome_serial_id
   3655   INTO my_lorec
   3656   FROM legitimization_outcomes
   3657  WHERE h_payto=in_h_normalized_payto
   3658    AND is_active;
   3659 IF FOUND
   3660 THEN
   3661   out_jrules=my_lorec.jnew_rules;
   3662   out_aml_review=my_lorec.to_investigate;
   3663   out_rule_gen=my_lorec.outcome_serial_id;
   3664 END IF;
   3665 SELECT reserve_pub
   3666   INTO out_reserve_pub
   3667   FROM reserves_in
   3668  WHERE wire_source_h_payto
   3669    IN (SELECT wire_source_h_payto
   3670          FROM wire_targets
   3671         WHERE h_normalized_payto=in_h_normalized_payto)
   3672  ORDER BY execution_date DESC
   3673  LIMIT 1;
   3674 END $$;
   3675 DROP FUNCTION IF EXISTS exchange_do_insert_active_legitimization_measure;
   3676 CREATE FUNCTION exchange_do_insert_active_legitimization_measure(
   3677   IN in_access_token BYTEA,
   3678   IN in_start_time INT8,
   3679   IN in_jmeasures TEXT,
   3680   OUT out_legitimization_measure_serial_id INT8)
   3681 LANGUAGE plpgsql
   3682 AS $$
   3683 BEGIN
   3684 UPDATE legitimization_measures
   3685    SET is_finished=TRUE
   3686  WHERE access_token=in_access_token
   3687    AND NOT is_finished;
   3688 INSERT INTO legitimization_measures
   3689   (access_token
   3690   ,start_time
   3691   ,jmeasures
   3692   ,display_priority)
   3693   VALUES
   3694   (in_access_token
   3695   ,in_start_time
   3696   ,in_jmeasures
   3697   ,1)
   3698   RETURNING
   3699     legitimization_measure_serial_id
   3700   INTO
   3701     out_legitimization_measure_serial_id;
   3702 END $$;
   3703 COMMENT ON FUNCTION exchange_do_insert_active_legitimization_measure(BYTEA, INT8, TEXT)
   3704   IS 'Inserts legitimization measure for an account and marks all existing such measures as inactive';
   3705 CREATE OR REPLACE FUNCTION exchange_do_select_aggregations_above_serial(
   3706   IN in_min_serial_id INT8)
   3707 RETURNS SETOF exchange_do_select_aggregations_above_serial_return_type
   3708 LANGUAGE plpgsql
   3709 AS $$
   3710 DECLARE
   3711   aggregation CURSOR
   3712   FOR
   3713   SELECT
   3714     batch_deposit_serial_id
   3715    ,aggregation_serial_id
   3716     FROM aggregation_tracking
   3717     WHERE aggregation_serial_id >= in_min_serial_id
   3718     ORDER BY aggregation_serial_id ASC;
   3719 DECLARE
   3720   my_total_val INT8; 
   3721 DECLARE
   3722   my_total_frac INT8; 
   3723 DECLARE
   3724   my_total taler_amount; 
   3725 DECLARE
   3726   my_batch_record RECORD;
   3727 DECLARE
   3728   i RECORD;
   3729 BEGIN
   3730 OPEN aggregation;
   3731 LOOP
   3732   FETCH NEXT FROM aggregation INTO i;
   3733   EXIT WHEN NOT FOUND;
   3734   SELECT
   3735     SUM((cdep.amount_with_fee).val) AS total_val
   3736    ,SUM((cdep.amount_with_fee).frac::INT8) AS total_frac
   3737     INTO
   3738       my_batch_record
   3739     FROM coin_deposits cdep
   3740     WHERE cdep.batch_deposit_serial_id = i.batch_deposit_serial_id;
   3741   my_total_val=my_batch_record.total_val;
   3742   my_total_frac=my_batch_record.total_frac;
   3743   my_total.val = my_total_val + my_total_frac / 100000000;
   3744   my_total.frac = my_total_frac % 100000000;
   3745   RETURN NEXT (
   3746        i.batch_deposit_serial_id
   3747       ,i.aggregation_serial_id
   3748       ,my_total
   3749       );
   3750 END LOOP;
   3751 CLOSE aggregation;
   3752 RETURN;
   3753 END $$;
   3754 DROP FUNCTION IF EXISTS exchange_do_persist_kyc_attributes;
   3755 CREATE FUNCTION exchange_do_persist_kyc_attributes(
   3756   IN in_process_row INT8,
   3757   IN in_h_payto BYTEA,
   3758   IN in_birthday INT4,
   3759   IN in_provider_name TEXT,
   3760   IN in_provider_account_id TEXT, 
   3761   IN in_provider_legitimization_id TEXT, 
   3762   IN in_collection_time_ts INT8,
   3763   IN in_expiration_time INT8, 
   3764   IN in_expiration_time_ts INT8, 
   3765   IN in_enc_attributes BYTEA,
   3766   IN in_kyc_completed_notify_s TEXT,
   3767   IN in_form_name TEXT, 
   3768   OUT out_ok BOOLEAN) 
   3769 LANGUAGE plpgsql
   3770 AS $$
   3771 BEGIN
   3772 INSERT INTO kyc_attributes
   3773   (h_payto
   3774   ,collection_time
   3775   ,expiration_time
   3776   ,form_name
   3777   ,by_aml_officer
   3778   ,encrypted_attributes
   3779   ,legitimization_serial
   3780  ) VALUES
   3781   (in_h_payto
   3782   ,in_collection_time_ts
   3783   ,in_expiration_time_ts
   3784   ,in_form_name
   3785   ,FALSE
   3786   ,in_enc_attributes
   3787   ,in_process_row);
   3788 UPDATE legitimization_processes
   3789   SET provider_user_id=in_provider_account_id
   3790      ,provider_legitimization_id=in_provider_legitimization_id
   3791      ,expiration_time=GREATEST(expiration_time,in_expiration_time)
   3792      ,finished=TRUE
   3793  WHERE h_payto=in_h_payto
   3794    AND legitimization_process_serial_id=in_process_row
   3795    AND provider_name=in_provider_name;
   3796 out_ok=FOUND;
   3797 UPDATE reserves
   3798    SET birthday=in_birthday
   3799  WHERE (reserve_pub IN
   3800     (SELECT reserve_pub
   3801        FROM reserves_in
   3802       WHERE wire_source_h_payto IN
   3803         (SELECT wire_source_h_payto
   3804            FROM wire_targets
   3805           WHERE h_normalized_payto=in_h_payto) ) )
   3806   AND ( ((current_balance).frac > 0) OR
   3807         ((current_balance).val > 0 ) )
   3808   AND (expiration_date > in_collection_time_ts);
   3809 EXECUTE FORMAT (
   3810  'NOTIFY %s'
   3811  ,in_kyc_completed_notify_s);
   3812 INSERT INTO kyc_alerts
   3813  (h_payto
   3814  ,trigger_type)
   3815  VALUES
   3816  (in_h_payto,1)
   3817  ON CONFLICT DO NOTHING;
   3818 END $$;
   3819 COMMENT ON FUNCTION exchange_do_persist_kyc_attributes(INT8, BYTEA, INT4, TEXT, TEXT, TEXT, INT8, INT8, INT8, BYTEA, TEXT, TEXT)
   3820   IS 'Inserts new KYC attributes and updates the status of the legitimization process';
   3821 DROP FUNCTION IF EXISTS exchange_do_insert_aml_program_failure;
   3822 CREATE FUNCTION exchange_do_insert_aml_program_failure (
   3823   IN in_legitimization_process_serial_id INT8,
   3824   IN in_h_payto BYTEA,
   3825   IN in_now INT8,
   3826   IN in_error_code INT4,
   3827   IN in_error_message TEXT,
   3828   IN in_kyc_completed_notify_s TEXT,
   3829   OUT out_update BOOLEAN) 
   3830 LANGUAGE plpgsql
   3831 AS $$
   3832 BEGIN
   3833 UPDATE legitimization_processes
   3834    SET finished=TRUE
   3835       ,error_code=in_error_code
   3836       ,error_message=in_error_message
   3837  WHERE h_payto=in_h_payto
   3838    AND legitimization_process_serial_id=in_legitimization_process_serial_id;
   3839 out_update = FOUND;
   3840 IF NOT FOUND
   3841 THEN
   3842   INSERT INTO legitimization_processes
   3843     (finished
   3844     ,error_code
   3845     ,error_message
   3846     ,h_payto
   3847     ,start_time
   3848     ,provider_section
   3849     ) VALUES (
   3850      TRUE
   3851     ,in_error_code
   3852     ,in_error_message
   3853     ,in_h_payto
   3854     ,in_now
   3855     ,'skip'
   3856    );
   3857 END IF;
   3858 EXECUTE FORMAT (
   3859  'NOTIFY %s'
   3860  ,in_kyc_completed_notify_s);
   3861 INSERT INTO kyc_alerts
   3862  (h_payto
   3863  ,trigger_type)
   3864  VALUES
   3865  (in_h_payto,1)
   3866  ON CONFLICT DO NOTHING;
   3867 END $$;
   3868 COMMENT ON FUNCTION exchange_do_insert_aml_program_failure(INT8, BYTEA, INT8, INT4, TEXT, TEXT)
   3869   IS 'Stores information about an AML program run that failed into the legitimization_processes table. Either updates a row of an existing legitimization process, or creates a new entry.';
   3870 DROP FUNCTION IF EXISTS exchange_do_set_aml_lock;
   3871 CREATE FUNCTION exchange_do_set_aml_lock (
   3872   IN in_h_payto BYTEA,
   3873   IN in_now INT8,
   3874   IN in_expiration INT8,
   3875   OUT out_aml_program_lock_timeout INT8) 
   3876 LANGUAGE plpgsql
   3877 AS $$
   3878 BEGIN
   3879 UPDATE wire_targets
   3880    SET aml_program_lock_timeout=in_expiration
   3881  WHERE h_normalized_payto=in_h_payto
   3882    AND ( (aml_program_lock_timeout IS NULL)
   3883       OR (aml_program_lock_timeout < in_now) );
   3884 IF NOT FOUND
   3885 THEN
   3886   SELECT aml_program_lock_timeout
   3887     INTO out_aml_program_lock_timeout
   3888     FROM wire_targets
   3889    WHERE h_normalized_payto=in_h_payto;
   3890 ELSE
   3891   out_aml_program_lock_timeout = 0;
   3892 END IF;
   3893 END $$;
   3894 COMMENT ON FUNCTION exchange_do_set_aml_lock(BYTEA, INT8, INT8)
   3895   IS 'Tries to lock an account for running an AML program. Returns the timeout of the existing lock, 0 if there is no existing lock, and NULL if we do not know the account.';
   3896 DROP FUNCTION IF EXISTS exchange_do_insert_sanction_list_hit;
   3897 CREATE FUNCTION exchange_do_insert_sanction_list_hit(
   3898   IN in_h_normalized_payto BYTEA,
   3899   IN in_decision_time INT8,
   3900   IN in_expiration_time INT8,
   3901   IN in_properties TEXT, 
   3902   IN in_new_rules TEXT, 
   3903   IN in_to_investigate BOOLEAN,
   3904   IN in_notify_s TEXT,
   3905   IN ina_events TEXT[],
   3906   OUT out_outcome_serial_id INT8)
   3907 LANGUAGE plpgsql
   3908 AS $$
   3909 DECLARE
   3910   my_i INT4;
   3911   ini_event TEXT;
   3912 BEGIN
   3913 INSERT INTO legitimization_outcomes
   3914   (h_payto
   3915   ,decision_time
   3916   ,expiration_time
   3917   ,jproperties
   3918   ,to_investigate
   3919   ,jnew_rules
   3920   )
   3921   VALUES
   3922   (in_h_normalized_payto
   3923   ,in_decision_time
   3924   ,in_expiration_time
   3925   ,in_properties
   3926   ,in_to_investigate
   3927   ,in_new_rules
   3928   )
   3929   RETURNING
   3930     outcome_serial_id
   3931   INTO
   3932     out_outcome_serial_id;
   3933 FOR i IN 1..COALESCE(array_length(ina_events,1),0)
   3934 LOOP
   3935   ini_event = ina_events[i];
   3936   INSERT INTO kyc_events
   3937     (event_timestamp
   3938     ,event_type)
   3939     VALUES
   3940     (in_decision_time
   3941     ,ini_event);
   3942 END LOOP;
   3943 EXECUTE FORMAT (
   3944    'NOTIFY %s'
   3945   ,in_notify_s);
   3946 END $$;
   3947 COMMENT ON FUNCTION exchange_do_insert_sanction_list_hit(BYTEA, INT8, INT8, TEXT, TEXT, BOOLEAN, TEXT, TEXT[])
   3948   IS 'Insert result from sanction list check into the table';
   3949 SET search_path TO exchange;
   3950 DROP FUNCTION IF EXISTS interval_to_start;
   3951 CREATE OR REPLACE FUNCTION interval_to_start (
   3952   IN in_timestamp TIMESTAMP,
   3953   IN in_range statistic_range,
   3954   OUT out_bucket_start INT8
   3955 )
   3956 LANGUAGE plpgsql
   3957 AS $$
   3958 BEGIN
   3959   out_bucket_start = EXTRACT(EPOCH FROM DATE_TRUNC(in_range::text, in_timestamp));
   3960 END $$;
   3961 COMMENT ON FUNCTION interval_to_start
   3962  IS 'computes the start time of the bucket for an event at the current time given the desired bucket range';
   3963 DROP PROCEDURE IF EXISTS exchange_do_bump_number_bucket_stat;
   3964 CREATE OR REPLACE PROCEDURE exchange_do_bump_number_bucket_stat(
   3965   in_slug TEXT,
   3966   in_h_payto BYTEA,
   3967   in_timestamp TIMESTAMP,
   3968   in_delta INT8
   3969 )
   3970 LANGUAGE plpgsql
   3971 AS $$
   3972 DECLARE
   3973   my_meta INT8;
   3974   my_range statistic_range;
   3975   my_bucket_start INT8;
   3976   my_curs CURSOR (arg_slug TEXT)
   3977    FOR SELECT UNNEST(ranges)
   3978          FROM exchange_statistic_bucket_meta
   3979         WHERE slug=arg_slug;
   3980 BEGIN
   3981   SELECT bmeta_serial_id
   3982     INTO my_meta
   3983     FROM exchange_statistic_bucket_meta
   3984    WHERE slug=in_slug
   3985      AND stype='number';
   3986   IF NOT FOUND
   3987   THEN
   3988     RETURN;
   3989   END IF;
   3990   OPEN my_curs (arg_slug:=in_slug);
   3991   LOOP
   3992     FETCH NEXT
   3993       FROM my_curs
   3994       INTO my_range;
   3995     EXIT WHEN NOT FOUND;
   3996     SELECT *
   3997       INTO my_bucket_start
   3998       FROM interval_to_start (in_timestamp, my_range);
   3999     UPDATE exchange_statistic_bucket_counter
   4000        SET cumulative_number = cumulative_number + in_delta
   4001      WHERE bmeta_serial_id=my_meta
   4002        AND h_payto=in_h_payto
   4003        AND bucket_start=my_bucket_start
   4004        AND bucket_range=my_range;
   4005     IF NOT FOUND
   4006     THEN
   4007       INSERT INTO exchange_statistic_bucket_counter
   4008         (bmeta_serial_id
   4009         ,h_payto
   4010         ,bucket_start
   4011         ,bucket_range
   4012         ,cumulative_number
   4013         ) VALUES (
   4014          my_meta
   4015         ,in_h_payto
   4016         ,my_bucket_start
   4017         ,my_range
   4018         ,in_delta);
   4019     END IF;
   4020   END LOOP;
   4021   CLOSE my_curs;
   4022 END $$;
   4023 DROP PROCEDURE IF EXISTS exchange_do_bump_amount_bucket_stat;
   4024 CREATE OR REPLACE PROCEDURE exchange_do_bump_amount_bucket_stat(
   4025   in_slug TEXT,
   4026   in_h_payto BYTEA,
   4027   in_timestamp TIMESTAMP,
   4028   in_delta taler_amount
   4029 )
   4030 LANGUAGE plpgsql
   4031 AS $$
   4032 DECLARE
   4033   my_meta INT8;
   4034   my_range statistic_range;
   4035   my_bucket_start INT8;
   4036   my_curs CURSOR (arg_slug TEXT)
   4037    FOR SELECT UNNEST(ranges)
   4038          FROM exchange_statistic_bucket_meta
   4039         WHERE slug=arg_slug;
   4040 BEGIN
   4041   SELECT bmeta_serial_id
   4042     INTO my_meta
   4043     FROM exchange_statistic_bucket_meta
   4044    WHERE slug=in_slug
   4045      AND stype='amount';
   4046   IF NOT FOUND
   4047   THEN
   4048     RETURN;
   4049   END IF;
   4050   OPEN my_curs (arg_slug:=in_slug);
   4051   LOOP
   4052     FETCH NEXT
   4053       FROM my_curs
   4054       INTO my_range;
   4055     EXIT WHEN NOT FOUND;
   4056     SELECT *
   4057       INTO my_bucket_start
   4058       FROM interval_to_start (in_timestamp, my_range);
   4059     UPDATE exchange_statistic_bucket_amount
   4060       SET
   4061         cumulative_value.val = (cumulative_value).val + (in_delta).val
   4062         + CASE
   4063             WHEN (in_delta).frac + (cumulative_value).frac >= 100000000
   4064             THEN 1
   4065             ELSE 0
   4066           END,
   4067         cumulative_value.frac = (cumulative_value).frac + (in_delta).frac
   4068         - CASE
   4069             WHEN (in_delta).frac + (cumulative_value).frac >= 100000000
   4070             THEN 100000000
   4071             ELSE 0
   4072           END
   4073      WHERE bmeta_serial_id=my_meta
   4074        AND h_payto=in_h_payto
   4075        AND bucket_start=my_bucket_start
   4076        AND bucket_range=my_range;
   4077     IF NOT FOUND
   4078     THEN
   4079       INSERT INTO exchange_statistic_bucket_amount
   4080         (bmeta_serial_id
   4081         ,h_payto
   4082         ,bucket_start
   4083         ,bucket_range
   4084         ,cumulative_value
   4085         ) VALUES (
   4086          my_meta
   4087         ,in_h_payto
   4088         ,my_bucket_start
   4089         ,my_range
   4090         ,in_delta);
   4091     END IF;
   4092   END LOOP;
   4093   CLOSE my_curs;
   4094 END $$;
   4095 COMMENT ON PROCEDURE exchange_do_bump_amount_bucket_stat
   4096   IS 'Updates an amount statistic tracked over buckets';
   4097 DROP PROCEDURE IF EXISTS exchange_do_bump_number_interval_stat;
   4098 CREATE OR REPLACE PROCEDURE exchange_do_bump_number_interval_stat(
   4099   in_slug TEXT,
   4100   in_h_payto BYTEA,
   4101   in_timestamp TIMESTAMP,
   4102   in_delta INT8
   4103 )
   4104 LANGUAGE plpgsql
   4105 AS $$
   4106 DECLARE
   4107   my_now INT8;
   4108   my_record RECORD;
   4109   my_meta INT8;
   4110   my_ranges INT8[];
   4111   my_precisions INT8[];
   4112   my_rangex INT8;
   4113   my_precisionx INT8;
   4114   my_start INT8;
   4115   my_event INT8;
   4116 BEGIN
   4117   my_now = ROUND(EXTRACT(epoch FROM CURRENT_TIMESTAMP(0)::TIMESTAMP) * 1000000)::INT8 / 1000 / 1000;
   4118   SELECT imeta_serial_id
   4119         ,ranges AS ranges
   4120         ,precisions AS precisions
   4121     INTO my_record
   4122     FROM exchange_statistic_interval_meta
   4123    WHERE slug=in_slug
   4124      AND stype='number';
   4125   IF NOT FOUND
   4126   THEN
   4127     RETURN;
   4128   END IF;
   4129   my_start = ROUND(EXTRACT(epoch FROM in_timestamp) * 1000000)::INT8 / 1000 / 1000; 
   4130   my_precisions = my_record.precisions;
   4131   my_ranges = my_record.ranges;
   4132   my_rangex = NULL;
   4133   FOR my_x IN 1..COALESCE(array_length(my_ranges,1),0)
   4134   LOOP
   4135     IF my_now - my_ranges[my_x] < my_start
   4136     THEN
   4137       my_rangex = my_ranges[my_x];
   4138       my_precisionx = my_precisions[my_x];
   4139       EXIT;
   4140     END IF;
   4141   END LOOP;
   4142   IF my_rangex IS NULL
   4143   THEN
   4144     RETURN;
   4145   END IF;
   4146   my_meta = my_record.imeta_serial_id;
   4147   my_start = my_start - my_start % my_precisionx; 
   4148   INSERT INTO exchange_statistic_counter_event AS msce
   4149     (imeta_serial_id
   4150     ,h_payto
   4151     ,slot
   4152     ,delta)
   4153    VALUES
   4154     (my_meta
   4155     ,in_h_payto
   4156     ,my_start
   4157     ,in_delta)
   4158    ON CONFLICT (imeta_serial_id, h_payto, slot)
   4159    DO UPDATE SET
   4160      delta = msce.delta + in_delta
   4161    RETURNING nevent_serial_id
   4162         INTO my_event;
   4163   UPDATE exchange_statistic_interval_counter
   4164      SET cumulative_number = cumulative_number + in_delta
   4165    WHERE imeta_serial_id = my_meta
   4166      AND h_payto = in_h_payto
   4167      AND range=my_rangex;
   4168   IF NOT FOUND
   4169   THEN
   4170     INSERT INTO exchange_statistic_interval_counter
   4171       (imeta_serial_id
   4172       ,h_payto
   4173       ,range
   4174       ,event_delimiter
   4175       ,cumulative_number
   4176      ) VALUES (
   4177        my_meta
   4178       ,in_h_payto
   4179       ,my_rangex
   4180       ,my_event
   4181       ,in_delta);
   4182   END IF;
   4183 END $$;
   4184 COMMENT ON PROCEDURE exchange_do_bump_number_interval_stat
   4185   IS 'Updates a numeric statistic tracked over an interval';
   4186 DROP PROCEDURE IF EXISTS exchange_do_bump_amount_interval_stat;
   4187 CREATE OR REPLACE PROCEDURE exchange_do_bump_amount_interval_stat(
   4188   in_slug TEXT,
   4189   in_h_payto BYTEA,
   4190   in_timestamp TIMESTAMP,
   4191   in_delta taler_amount
   4192 )
   4193 LANGUAGE plpgsql
   4194 AS $$
   4195 DECLARE
   4196   my_now INT8;
   4197   my_record RECORD;
   4198   my_meta INT8;
   4199   my_ranges INT8[];
   4200   my_precisions INT8[];
   4201   my_x INT;
   4202   my_rangex INT8;
   4203   my_precisionx INT8;
   4204   my_start INT8;
   4205   my_event INT8;
   4206 BEGIN
   4207   my_now = ROUND(EXTRACT(epoch FROM CURRENT_TIMESTAMP(0)::TIMESTAMP) * 1000000)::INT8 / 1000 / 1000;
   4208   SELECT imeta_serial_id
   4209         ,ranges
   4210         ,precisions
   4211     INTO my_record
   4212     FROM exchange_statistic_interval_meta
   4213    WHERE slug=in_slug
   4214      AND stype='amount';
   4215   IF NOT FOUND
   4216   THEN
   4217     RETURN;
   4218   END IF;
   4219   my_start = ROUND(EXTRACT(epoch FROM in_timestamp) * 1000000)::INT8 / 1000 / 1000; 
   4220   my_precisions = my_record.precisions;
   4221   my_ranges = my_record.ranges;
   4222   my_rangex = NULL;
   4223   FOR my_x IN 1..COALESCE(array_length(my_ranges,1),0)
   4224   LOOP
   4225     IF my_now - my_ranges[my_x] < my_start
   4226     THEN
   4227       my_rangex = my_ranges[my_x];
   4228       my_precisionx = my_precisions[my_x];
   4229       EXIT;
   4230     END IF;
   4231   END LOOP;
   4232   IF my_rangex IS NULL
   4233   THEN
   4234     RETURN;
   4235   END IF;
   4236   my_start = my_start - my_start % my_precisionx; 
   4237   my_meta = my_record.imeta_serial_id;
   4238   INSERT INTO exchange_statistic_amount_event AS msae
   4239     (imeta_serial_id
   4240     ,h_payto
   4241     ,slot
   4242     ,delta
   4243     ) VALUES (
   4244      my_meta
   4245     ,in_h_payto
   4246     ,my_start
   4247     ,in_delta
   4248     )
   4249     ON CONFLICT (imeta_serial_id, h_payto, slot)
   4250     DO UPDATE SET
   4251       delta.val = (msae.delta).val + (in_delta).val
   4252         + CASE
   4253           WHEN (in_delta).frac + (msae.delta).frac >= 100000000
   4254           THEN 1
   4255           ELSE 0
   4256         END,
   4257       delta.frac = (msae.delta).frac + (in_delta).frac
   4258         - CASE
   4259           WHEN (in_delta).frac + (msae.delta).frac >= 100000000
   4260           THEN 100000000
   4261           ELSE 0
   4262         END
   4263     RETURNING aevent_serial_id
   4264          INTO my_event;
   4265   UPDATE exchange_statistic_interval_amount
   4266     SET
   4267       cumulative_value.val = (cumulative_value).val + (in_delta).val
   4268       + CASE
   4269           WHEN (in_delta).frac + (cumulative_value).frac >= 100000000
   4270           THEN 1
   4271           ELSE 0
   4272         END,
   4273       cumulative_value.frac = (cumulative_value).frac + (in_delta).frac
   4274       - CASE
   4275           WHEN (in_delta).frac + (cumulative_value).frac >= 100000000
   4276           THEN 100000000
   4277           ELSE 0
   4278         END
   4279    WHERE imeta_serial_id=my_meta
   4280      AND h_payto=in_h_payto
   4281      AND range=my_rangex;
   4282   IF NOT FOUND
   4283   THEN
   4284     INSERT INTO exchange_statistic_interval_amount
   4285       (imeta_serial_id
   4286       ,h_payto
   4287       ,range
   4288       ,event_delimiter
   4289       ,cumulative_value
   4290       ) VALUES (
   4291        my_meta
   4292       ,in_h_payto
   4293       ,my_rangex
   4294       ,my_event
   4295       ,in_delta);
   4296   END IF;
   4297 END $$;
   4298 COMMENT ON PROCEDURE exchange_do_bump_amount_interval_stat
   4299   IS 'Updates an amount statistic tracked over an interval';
   4300 DROP PROCEDURE IF EXISTS exchange_do_bump_number_stat;
   4301 CREATE OR REPLACE PROCEDURE exchange_do_bump_number_stat(
   4302   in_slug TEXT,
   4303   in_h_payto BYTEA,
   4304   in_timestamp TIMESTAMP,
   4305   in_delta INT8
   4306 )
   4307 LANGUAGE plpgsql
   4308 AS $$
   4309 BEGIN
   4310   CALL exchange_do_bump_number_bucket_stat (in_slug, in_h_payto, in_timestamp, in_delta);
   4311   CALL exchange_do_bump_number_interval_stat (in_slug, in_h_payto, in_timestamp, in_delta);
   4312 END $$;
   4313 COMMENT ON PROCEDURE exchange_do_bump_number_stat
   4314   IS 'Updates a numeric statistic (bucket or interval)';
   4315 DROP PROCEDURE IF EXISTS exchange_do_bump_amount_stat;
   4316 CREATE OR REPLACE PROCEDURE exchange_do_bump_amount_stat(
   4317   in_slug TEXT,
   4318   in_h_payto BYTEA,
   4319   in_timestamp TIMESTAMP,
   4320   in_delta taler_amount
   4321 )
   4322 LANGUAGE plpgsql
   4323 AS $$
   4324 BEGIN
   4325   CALL exchange_do_bump_amount_bucket_stat (in_slug, in_h_payto, in_timestamp, in_delta);
   4326   CALL exchange_do_bump_amount_interval_stat (in_slug, in_h_payto, in_timestamp, in_delta);
   4327 END $$;
   4328 COMMENT ON PROCEDURE exchange_do_bump_amount_stat
   4329   IS 'Updates an amount statistic (bucket or interval)';
   4330 DROP FUNCTION IF EXISTS exchange_statistic_interval_number_get;
   4331 CREATE OR REPLACE FUNCTION exchange_statistic_interval_number_get (
   4332   IN in_slug TEXT,
   4333   IN in_h_payto BYTEA
   4334 )
   4335 RETURNS SETOF exchange_statistic_interval_number_get_return_value
   4336 LANGUAGE plpgsql
   4337 AS $$
   4338 DECLARE
   4339   my_time INT8 DEFAULT ROUND(EXTRACT(epoch FROM CURRENT_TIMESTAMP(0)::TIMESTAMP) * 1000000)::INT8 / 1000 / 1000;
   4340   my_ranges INT8[];
   4341   my_range INT8;
   4342   my_delta INT8;
   4343   my_meta INT8;
   4344   my_next_max_serial INT8;
   4345   my_rec RECORD;
   4346   my_irec RECORD;
   4347   my_i INT;
   4348   my_min_serial INT8 DEFAULT NULL;
   4349   my_rval exchange_statistic_interval_number_get_return_value;
   4350 BEGIN
   4351   SELECT imeta_serial_id
   4352         ,ranges
   4353         ,precisions
   4354     INTO my_rec
   4355     FROM exchange_statistic_interval_meta
   4356    WHERE slug=in_slug;
   4357   IF NOT FOUND
   4358   THEN
   4359     RETURN;
   4360   END IF;
   4361   my_rval.rvalue = 0;
   4362   my_ranges = my_rec.ranges;
   4363   my_meta = my_rec.imeta_serial_id;
   4364   FOR my_i IN 1..COALESCE(array_length(my_ranges,1),0)
   4365   LOOP
   4366     my_range = my_ranges[my_i];
   4367     SELECT event_delimiter
   4368           ,cumulative_number
   4369       INTO my_irec
   4370       FROM exchange_statistic_interval_counter
   4371      WHERE imeta_serial_id = my_meta
   4372        AND range = my_range
   4373        AND h_payto = in_h_payto;
   4374     IF FOUND
   4375     THEN
   4376       my_min_serial = my_irec.event_delimiter;
   4377       my_rval.rvalue = my_rval.rvalue + my_irec.cumulative_number;
   4378       SELECT SUM(delta) AS delta_sum
   4379         INTO my_irec
   4380         FROM exchange_statistic_counter_event
   4381        WHERE imeta_serial_id = my_meta
   4382          AND h_payto = in_h_payto
   4383          AND slot < my_time - my_range
   4384          AND nevent_serial_id >= my_min_serial;
   4385       IF FOUND AND my_irec.delta_sum IS NOT NULL
   4386       THEN
   4387         my_delta = my_irec.delta_sum;
   4388         my_rval.rvalue = my_rval.rvalue - my_delta;
   4389         SELECT nevent_serial_id
   4390           INTO my_next_max_serial
   4391           FROM exchange_statistic_counter_event
   4392          WHERE imeta_serial_id = my_meta
   4393            AND h_payto = in_h_payto
   4394            AND slot >= my_time - my_range
   4395            AND nevent_serial_id >= my_min_serial
   4396          ORDER BY slot ASC
   4397          LIMIT 1;
   4398         IF FOUND
   4399         THEN
   4400           UPDATE exchange_statistic_interval_counter
   4401              SET cumulative_number = cumulative_number - my_delta,
   4402                  event_delimiter = my_next_max_serial
   4403            WHERE imeta_serial_id = my_meta
   4404              AND h_payto = in_h_payto
   4405              AND range = my_range;
   4406         ELSE
   4407           DELETE FROM exchange_statistic_interval_counter
   4408            WHERE imeta_serial_id = my_meta
   4409              AND h_payto = in_h_payto
   4410              AND range = my_range;
   4411         END IF;
   4412         IF (my_i < array_length(my_ranges,1))
   4413         THEN
   4414           UPDATE exchange_statistic_interval_counter AS usic SET
   4415             cumulative_number = cumulative_number + my_delta,
   4416             event_delimiter = LEAST(usic.event_delimiter,my_min_serial)
   4417            WHERE imeta_serial_id = my_meta
   4418              AND h_payto = in_h_payto
   4419              AND range=my_ranges[my_i+1];
   4420           IF NOT FOUND
   4421           THEN
   4422             INSERT INTO exchange_statistic_interval_counter
   4423               (imeta_serial_id
   4424               ,h_payto
   4425               ,range
   4426               ,event_delimiter
   4427               ,cumulative_number
   4428               ) VALUES (
   4429                my_meta
   4430               ,in_h_payto
   4431               ,my_ranges[my_i+1]
   4432               ,my_min_serial
   4433               ,my_delta);
   4434           END IF;
   4435         ELSE
   4436           DELETE FROM exchange_statistic_counter_event
   4437                 WHERE imeta_serial_id = my_meta
   4438                   AND h_payto = in_h_payto
   4439                   AND slot < my_time - my_range;
   4440         END IF;
   4441       END IF;
   4442       my_rval.range = my_range;
   4443       RETURN NEXT my_rval;
   4444     END IF;
   4445   END LOOP;
   4446 END $$;
   4447 COMMENT ON FUNCTION exchange_statistic_interval_number_get
   4448   IS 'Returns deposit statistic tracking deposited amounts over certain time intervals; we first trim the stored data to only track what is still in-range, and then return the remaining value for each range';
   4449 DROP FUNCTION IF EXISTS exchange_statistic_interval_amount_get;
   4450 CREATE OR REPLACE FUNCTION exchange_statistic_interval_amount_get (
   4451   IN in_slug TEXT,
   4452   IN in_h_payto BYTEA
   4453 )
   4454 RETURNS SETOF exchange_statistic_interval_amount_get_return_value
   4455 LANGUAGE plpgsql
   4456 AS $$
   4457 DECLARE
   4458   my_time INT8 DEFAULT ROUND(EXTRACT(epoch FROM CURRENT_TIMESTAMP(0)::TIMESTAMP) * 1000000)::INT8 / 1000 / 1000;
   4459   my_ranges INT8[];
   4460   my_range INT8;
   4461   my_delta_value INT8;
   4462   my_delta_frac INT8;
   4463   my_delta taler_amount;
   4464   my_meta INT8;
   4465   my_next_max_serial INT8;
   4466   my_rec RECORD;
   4467   my_irec RECORD;
   4468   my_jrec RECORD;
   4469   my_i INT;
   4470   my_min_serial INT8 DEFAULT NULL;
   4471   my_rval exchange_statistic_interval_amount_get_return_value;
   4472 BEGIN
   4473   SELECT imeta_serial_id
   4474         ,ranges
   4475         ,precisions
   4476     INTO my_rec
   4477     FROM exchange_statistic_interval_meta
   4478    WHERE slug=in_slug;
   4479   IF NOT FOUND
   4480   THEN
   4481     RETURN;
   4482   END IF;
   4483   my_meta = my_rec.imeta_serial_id;
   4484   my_ranges = my_rec.ranges;
   4485   my_rval.rvalue.val = 0;
   4486   my_rval.rvalue.frac = 0;
   4487   FOR my_i IN 1..COALESCE(array_length(my_ranges,1),0)
   4488   LOOP
   4489     my_range = my_ranges[my_i];
   4490     SELECT event_delimiter
   4491           ,cumulative_value
   4492       INTO my_irec
   4493       FROM exchange_statistic_interval_amount
   4494      WHERE imeta_serial_id = my_meta
   4495        AND h_payto = in_h_payto
   4496        AND range = my_range;
   4497     IF FOUND
   4498     THEN
   4499       my_min_serial = my_irec.event_delimiter;
   4500       my_rval.rvalue.val = (my_rval.rvalue).val + (my_irec.cumulative_value).val + (my_irec.cumulative_value).frac / 100000000;
   4501       my_rval.rvalue.frac = (my_rval.rvalue).frac + (my_irec.cumulative_value).frac % 100000000;
   4502       IF (my_rval.rvalue).frac > 100000000
   4503       THEN
   4504         my_rval.rvalue.frac = (my_rval.rvalue).frac - 100000000;
   4505         my_rval.rvalue.val = (my_rval.rvalue).val + 1;
   4506       END IF;
   4507       SELECT SUM((esae.delta).val) AS value_sum
   4508             ,SUM((esae.delta).frac) AS frac_sum
   4509         INTO my_jrec
   4510         FROM exchange_statistic_amount_event esae
   4511        WHERE imeta_serial_id = my_meta
   4512          AND h_payto = in_h_payto
   4513          AND slot < my_time - my_range
   4514          AND aevent_serial_id >= my_min_serial;
   4515       IF FOUND AND my_jrec.value_sum IS NOT NULL
   4516       THEN
   4517         my_delta_value = my_jrec.value_sum + my_jrec.frac_sum / 100000000;
   4518         my_delta_frac = my_jrec.frac_sum % 100000000;
   4519         my_rval.rvalue.val = (my_rval.rvalue).val - my_delta_value;
   4520         IF ((my_rval.rvalue).frac >= my_delta_frac)
   4521         THEN
   4522           my_rval.rvalue.frac = (my_rval.rvalue).frac - my_delta_frac;
   4523         ELSE
   4524           my_rval.rvalue.frac = 100000000 + (my_rval.rvalue).frac - my_delta_frac;
   4525           my_rval.rvalue.val = (my_rval.rvalue).val - 1;
   4526         END IF;
   4527         SELECT aevent_serial_id
   4528           INTO my_next_max_serial
   4529           FROM exchange_statistic_amount_event
   4530          WHERE imeta_serial_id = my_meta
   4531            AND h_payto = in_h_payto
   4532            AND slot >= my_time - my_range
   4533            AND aevent_serial_id >= my_min_serial
   4534          ORDER BY slot ASC
   4535          LIMIT 1;
   4536         IF FOUND
   4537         THEN
   4538           UPDATE exchange_statistic_interval_amount SET
   4539              cumulative_value.val = (cumulative_value).val - my_delta_value
   4540               - CASE
   4541                   WHEN (cumulative_value).frac < my_delta_frac
   4542                   THEN 1
   4543                   ELSE 0
   4544                 END,
   4545              cumulative_value.frac = (cumulative_value).frac - my_delta_frac
   4546              + CASE
   4547                  WHEN (cumulative_value).frac < my_delta_frac
   4548                  THEN 100000000
   4549                  ELSE 0
   4550                END,
   4551              event_delimiter = my_next_max_serial
   4552            WHERE imeta_serial_id = my_meta
   4553              AND h_payto = in_h_payto
   4554              AND range = my_range;
   4555         ELSE
   4556           DELETE FROM exchange_statistic_interval_amount
   4557            WHERE imeta_serial_id = my_meta
   4558              AND h_payto = in_h_payto
   4559              AND range = my_range;
   4560         END IF;
   4561         IF (my_i < array_length(my_ranges,1))
   4562         THEN
   4563           UPDATE exchange_statistic_interval_amount AS msia SET
   4564             cumulative_value.val = (cumulative_value).val + my_delta_value
   4565               + CASE
   4566                  WHEN (cumulative_value).frac + my_delta_frac > 100000000
   4567                  THEN 1
   4568                  ELSE 0
   4569                END,
   4570             cumulative_value.frac = (cumulative_value).frac + my_delta_value
   4571               - CASE
   4572                  WHEN (cumulative_value).frac + my_delta_frac > 100000000
   4573                  THEN 100000000
   4574                  ELSE 0
   4575                END,
   4576             event_delimiter = LEAST (msia.event_delimiter,my_min_serial)
   4577            WHERE imeta_serial_id = my_meta
   4578              AND h_payto = in_h_payto
   4579              AND range=my_ranges[my_i+1];
   4580           IF NOT FOUND
   4581           THEN
   4582             my_delta.val = my_delta_value;
   4583             my_delta.frac = my_delta_frac;
   4584             INSERT INTO exchange_statistic_interval_amount
   4585               (imeta_serial_id
   4586               ,h_payto
   4587               ,event_delimiter
   4588               ,range
   4589               ,cumulative_value
   4590               ) VALUES (
   4591                my_meta
   4592               ,in_h_payto
   4593               ,my_min_serial
   4594               ,my_ranges[my_i+1]
   4595               ,my_delta);
   4596           END IF;
   4597         ELSE
   4598           DELETE FROM exchange_statistic_amount_event
   4599                 WHERE imeta_serial_id = my_meta
   4600                   AND h_payto = in_h_payto
   4601                   AND slot < my_time - my_range;
   4602         END IF;
   4603       END IF;
   4604       my_rval.range = my_range;
   4605       RETURN NEXT my_rval;
   4606     END IF;
   4607   END LOOP; 
   4608 END $$;
   4609 COMMENT ON FUNCTION exchange_statistic_interval_amount_get
   4610   IS 'Returns deposit statistic tracking deposited amounts over certain time intervals; we first trim the stored data to only track what is still in-range, and then return the remaining value; multiple values are returned, one per range';
   4611 DROP PROCEDURE IF EXISTS exchange_statistic_counter_gc;
   4612 CREATE OR REPLACE PROCEDURE exchange_statistic_counter_gc ()
   4613 LANGUAGE plpgsql
   4614 AS $$
   4615 DECLARE
   4616   my_time INT8 DEFAULT ROUND(EXTRACT(epoch FROM CURRENT_TIMESTAMP(0)::TIMESTAMP) * 1000000)::INT8 / 1000 / 1000;
   4617   my_h_payto BYTEA;
   4618   my_rec RECORD;
   4619   my_sum RECORD;
   4620   my_meta INT8;
   4621   my_ranges INT8[];
   4622   my_precisions INT8[];
   4623   my_precision INT4;
   4624   my_i INT4;
   4625   min_slot INT8;
   4626   max_slot INT8;
   4627   end_slot INT8;
   4628   my_total INT8;
   4629 BEGIN
   4630   FOR my_h_payto IN
   4631     SELECT DISTINCT h_payto
   4632       FROM exchange_statistic_counter_event
   4633   LOOP
   4634   FOR my_rec IN
   4635     SELECT imeta_serial_id
   4636           ,ranges
   4637           ,precisions
   4638           ,slug
   4639       FROM exchange_statistic_interval_meta
   4640   LOOP
   4641     PERFORM FROM exchange_statistic_interval_number_get (my_rec.slug, my_h_payto);
   4642     my_meta = my_rec.imeta_serial_id;
   4643     my_ranges = my_rec.ranges;
   4644     my_precisions = my_rec.precisions;
   4645     FOR my_i IN 1..COALESCE(array_length(my_ranges,1),0)
   4646     LOOP
   4647       my_precision = my_precisions[my_i];
   4648       IF 1 >= my_precision
   4649       THEN
   4650         CONTINUE;
   4651       END IF;
   4652       IF 1 = my_i
   4653       THEN
   4654         min_slot = 0;
   4655       ELSE
   4656         min_slot = my_ranges[my_i - 1];
   4657       END IF;
   4658       end_slot = my_ranges[my_i];
   4659       LOOP
   4660         EXIT WHEN min_slot >= end_slot;
   4661         max_slot = min_slot + my_precision;
   4662         SELECT SUM(delta) AS total,
   4663                COUNT(*) AS matches,
   4664                MIN(nevent_serial_id) AS rep_serial_id
   4665           INTO my_sum
   4666           FROM exchange_statistic_counter_event
   4667          WHERE h_payto=my_h_payto
   4668            AND imeta_serial_id=my_meta
   4669            AND slot >= my_time - max_slot
   4670            AND slot < my_time - min_slot;
   4671         IF FOUND AND my_sum.matches > 1
   4672         THEN
   4673           my_total = my_sum.total;
   4674           DELETE FROM exchange_statistic_counter_event
   4675            WHERE h_payto=my_h_payto
   4676              AND imeta_serial_id=my_meta
   4677              AND slot >= my_time - max_slot
   4678              AND slot < my_time - min_slot
   4679              AND nevent_serial_id > my_sum.rep_serial_id;
   4680           UPDATE exchange_statistic_counter_event SET
   4681             delta = my_total
   4682            WHERE imeta_serial_id = my_meta
   4683              AND h_payto = my_h_payto
   4684              AND nevent_serial_id = my_sum.rep_serial_id;
   4685         END IF;
   4686         min_slot = min_slot + my_precision;
   4687       END LOOP; 
   4688     END LOOP; 
   4689     DELETE FROM exchange_statistic_counter_event
   4690      WHERE h_payto=my_h_payto
   4691        AND imeta_serial_id=my_meta
   4692        AND slot < my_time - my_ranges[array_length(my_ranges,1)];
   4693   END LOOP; 
   4694   END LOOP; 
   4695 END $$;
   4696 COMMENT ON PROCEDURE exchange_statistic_counter_gc
   4697   IS 'Performs garbage collection and compaction of the exchange_statistic_counter_event table';
   4698 DROP PROCEDURE IF EXISTS exchange_statistic_amount_gc;
   4699 CREATE OR REPLACE PROCEDURE exchange_statistic_amount_gc ()
   4700 LANGUAGE plpgsql
   4701 AS $$
   4702 DECLARE
   4703   my_time INT8 DEFAULT ROUND(EXTRACT(epoch FROM CURRENT_TIMESTAMP(0)::TIMESTAMP) * 1000000)::INT8 / 1000 / 1000;
   4704   my_h_payto BYTEA;
   4705   my_rec RECORD;
   4706   my_sum RECORD;
   4707   my_meta INT8;
   4708   my_ranges INT8[];
   4709   my_precisions INT8[];
   4710   my_precision INT4;
   4711   my_i INT4;
   4712   min_slot INT8;
   4713   max_slot INT8;
   4714   end_slot INT8;
   4715   my_total_val INT8;
   4716   my_total_frac INT8;
   4717 BEGIN
   4718   FOR my_h_payto IN
   4719     SELECT DISTINCT h_payto
   4720       FROM exchange_statistic_counter_event
   4721   LOOP
   4722   FOR my_rec IN
   4723     SELECT imeta_serial_id
   4724           ,ranges
   4725           ,precisions
   4726           ,slug
   4727       FROM exchange_statistic_interval_meta
   4728   LOOP
   4729     PERFORM FROM exchange_statistic_interval_amount_get (my_rec.slug, my_h_payto);
   4730     my_meta = my_rec.imeta_serial_id;
   4731     my_ranges = my_rec.ranges;
   4732     my_precisions = my_rec.precisions;
   4733     FOR my_i IN 1..COALESCE(array_length(my_ranges,1),0)
   4734     LOOP
   4735       my_precision = my_precisions[my_i];
   4736       IF 1 >= my_precision
   4737       THEN
   4738         CONTINUE;
   4739       END IF;
   4740       IF 1 = my_i
   4741       THEN
   4742         min_slot = 0;
   4743       ELSE
   4744         min_slot = my_ranges[my_i - 1];
   4745       END IF;
   4746       end_slot = my_ranges[my_i];
   4747       LOOP
   4748         EXIT WHEN min_slot >= end_slot;
   4749         max_slot = min_slot + my_precision;
   4750         SELECT SUM((delta).val) AS total_val,
   4751                SUM((delta).frac) AS total_frac,
   4752                COUNT(*) AS matches,
   4753                MIN(aevent_serial_id) AS rep_serial_id
   4754           INTO my_sum
   4755           FROM exchange_statistic_amount_event
   4756          WHERE imeta_serial_id=my_meta
   4757            AND h_payto=my_h_payto
   4758            AND slot >= my_time - max_slot
   4759            AND slot < my_time - max_slot;
   4760         IF FOUND AND my_sum.matches > 1
   4761         THEN
   4762           my_total_frac = my_sum.total_frac % 100000000;
   4763           my_total_val = my_sum.total_val + my_sum.total_frac / 100000000;
   4764           DELETE FROM exchange_statistic_amount_event
   4765            WHERE imeta_serial_id=my_meta
   4766              AND h_payto=my_h_payto
   4767              AND slot >= my_time - max_slot
   4768              AND slot < my_time - max_slot
   4769              AND aevent_serial_id > my_sum.rep_serial_id;
   4770           UPDATE exchange_statistic_amount_event SET
   4771              delta.val = my_total_value
   4772             ,delta.frac = my_total_frac
   4773            WHERE imeta_serial_id = my_meta
   4774              AND h_payto = my_h_payto
   4775              AND aevent_serial_id = my_sum.rep_serial_id;
   4776         END IF;
   4777         min_slot = min_slot + my_precision;
   4778       END LOOP; 
   4779     END LOOP; 
   4780     DELETE FROM exchange_statistic_amount_event
   4781      WHERE h_payto=my_h_payto
   4782        AND imeta_serial_id=my_meta
   4783        AND slot < my_time - my_ranges[array_length(my_ranges,1)];
   4784     END LOOP; 
   4785   END LOOP; 
   4786 END $$;
   4787 COMMENT ON PROCEDURE exchange_statistic_amount_gc
   4788   IS 'Performs garbage collection and compaction of the exchange_statistic_amount_event table';
   4789 DROP PROCEDURE IF EXISTS exchange_statistic_bucket_gc;
   4790 CREATE OR REPLACE PROCEDURE exchange_statistic_bucket_gc ()
   4791 LANGUAGE plpgsql
   4792 AS $$
   4793 DECLARE
   4794   my_rec RECORD;
   4795   my_range TEXT;
   4796   my_now INT8;
   4797   my_end INT8;
   4798 BEGIN
   4799   my_now = EXTRACT(EPOCH FROM CURRENT_TIMESTAMP(0)::TIMESTAMP); 
   4800   FOR my_rec IN
   4801     SELECT bmeta_serial_id
   4802           ,stype
   4803           ,ranges[array_length(ranges,1)] AS range
   4804           ,ages[array_length(ages,1)] AS age
   4805       FROM exchange_statistic_bucket_meta
   4806   LOOP
   4807     my_range = '1 ' || my_rec.range::TEXT;
   4808     my_end = my_now - my_rec.age * EXTRACT(SECONDS FROM (SELECT my_range::INTERVAL)); 
   4809     IF my_rec.stype = 'amount'
   4810     THEN
   4811       DELETE
   4812         FROM exchange_statistic_bucket_amount
   4813        WHERE bmeta_serial_id = my_rec.bmeta_serial_id
   4814          AND bucket_start >= my_end;
   4815     ELSE
   4816       DELETE
   4817         FROM exchange_statistic_bucket_counter
   4818        WHERE bmeta_serial_id = my_rec.bmeta_serial_id
   4819          AND bucket_start >= my_end;
   4820     END IF;
   4821   END LOOP;
   4822 END $$;
   4823 COMMENT ON PROCEDURE exchange_statistic_bucket_gc
   4824   IS 'Performs garbage collection of the exchange_statistic_bucket_counter and exchange_statistic_bucket_amount tables';
   4825 DROP FUNCTION IF EXISTS exchange_drop_customization;
   4826 CREATE OR REPLACE FUNCTION exchange_drop_customization (
   4827   IN in_schema TEXT,
   4828   OUT out_found BOOLEAN
   4829 )
   4830 LANGUAGE plpgsql
   4831 AS $$
   4832 DECLARE
   4833   my_xpatches TEXT;
   4834 BEGIN
   4835   out_found = FALSE;
   4836   FOR my_xpatches IN
   4837     SELECT patch_name
   4838       FROM _v.patches
   4839      WHERE starts_with(patch_name, in_schema || '-')
   4840   LOOP
   4841     PERFORM _v.unregister_patch(my_xpatches);
   4842     out_found = TRUE;
   4843   END LOOP;
   4844   IF out_found
   4845   THEN
   4846     EXECUTE FORMAT('DROP SCHEMA %s CASCADE'
   4847       ,in_schema);
   4848   END IF;
   4849   DELETE
   4850      FROM exchange_statistic_interval_meta
   4851     WHERE origin=in_schema;
   4852   DELETE
   4853      FROM exchange_statistic_bucket_meta
   4854     WHERE origin=in_schema;
   4855 END $$;
   4856 COMMENT ON FUNCTION exchange_drop_customization
   4857   IS 'Removes all entries related to a particular exchange customization schema';
   4858 CREATE OR REPLACE FUNCTION purse_requests_insert_trigger()
   4859   RETURNS trigger
   4860   LANGUAGE plpgsql
   4861   AS $$
   4862 BEGIN
   4863   INSERT INTO
   4864     exchange.purse_actions
   4865     (purse_pub
   4866     ,action_date)
   4867   VALUES
   4868     (NEW.purse_pub
   4869     ,NEW.purse_expiration);
   4870   RETURN NEW;
   4871 END $$;
   4872 COMMENT ON FUNCTION purse_requests_insert_trigger()
   4873   IS 'When a purse is created, insert it into the purse_action table to take action when the purse expires.';
   4874 CREATE OR REPLACE FUNCTION reserves_out_insert_trigger()
   4875   RETURNS trigger
   4876   LANGUAGE plpgsql
   4877   AS $$
   4878 BEGIN
   4879   INSERT INTO exchange.reserve_history
   4880     (reserve_pub
   4881     ,table_name
   4882     ,serial_id)
   4883   SELECT
   4884      res.reserve_pub
   4885     ,'reserves_out'
   4886     ,NEW.reserve_out_serial_id
   4887   FROM
   4888     exchange.reserves res
   4889   WHERE res.reserve_uuid = NEW.reserve_uuid;
   4890   RETURN NEW;
   4891 END $$;
   4892 COMMENT ON FUNCTION reserves_out_insert_trigger()
   4893   IS 'Replicate reserve_out inserts into reserve_history table.';
   4894 CREATE OR REPLACE FUNCTION reserves_in_insert_trigger()
   4895   RETURNS trigger
   4896   LANGUAGE plpgsql
   4897   AS $$
   4898 BEGIN
   4899   INSERT INTO exchange.reserve_history
   4900     (reserve_pub
   4901     ,table_name
   4902     ,serial_id)
   4903   VALUES
   4904     (NEW.reserve_pub
   4905     ,'reserves_in'
   4906     ,NEW.reserve_in_serial_id);
   4907   RETURN NEW;
   4908 END $$;
   4909 COMMENT ON FUNCTION reserves_in_insert_trigger()
   4910   IS 'Automatically generate reserve history entry.';
   4911 CREATE OR REPLACE FUNCTION purse_decision_insert_trigger()
   4912   RETURNS trigger
   4913   LANGUAGE plpgsql
   4914   AS $$
   4915 BEGIN
   4916   UPDATE exchange.purse_requests
   4917      SET was_decided=TRUE
   4918    WHERE purse_pub=NEW.purse_pub;
   4919   IF NEW.refunded
   4920   THEN
   4921     INSERT INTO exchange.coin_history
   4922       (coin_pub
   4923       ,table_name
   4924       ,serial_id)
   4925     SELECT
   4926       pd.coin_pub
   4927      ,'purse_decision'
   4928      ,NEW.purse_decision_serial_id
   4929     FROM exchange.purse_deposits pd
   4930     WHERE purse_pub = NEW.purse_pub;
   4931   ELSE
   4932     INSERT INTO exchange.reserve_history
   4933       (reserve_pub
   4934       ,table_name
   4935       ,serial_id)
   4936     SELECT
   4937       reserve_pub
   4938      ,'purse_decision'
   4939      ,NEW.purse_decision_serial_id
   4940     FROM exchange.purse_merges
   4941     WHERE purse_pub=NEW.purse_pub;
   4942   END IF;
   4943   RETURN NEW;
   4944 END $$;
   4945 COMMENT ON FUNCTION purse_decision_insert_trigger()
   4946   IS 'Automatically generate coin history entry and update decision status for the purse.';
   4947 DROP PROCEDURE IF EXISTS exchange_do_gc;
   4948 CREATE PROCEDURE exchange_do_gc(
   4949   IN in_ancient_date INT8,
   4950   IN in_now INT8)
   4951 LANGUAGE plpgsql
   4952 AS $$
   4953 BEGIN
   4954   CALL exchange_do_main_gc(in_ancient_date,in_now);
   4955   CALL exchange_statistic_amount_gc ();
   4956   CALL exchange_statistic_bucket_gc ();
   4957   CALL exchange_statistic_counter_gc ();
   4958 END $$;
   4959 COMMENT ON PROCEDURE exchange_do_gc
   4960   IS 'calls all other garbage collection subroutines';
   4961 COMMIT;