$TITLE Appendix E: OLG production model -- period by period govt budget

$ONTEXT

The benchmark social accounting matrix:

      | Output| Income categories    |  Consumption categories
      | OUT   | CAP     LAB     TAX  |  CON     INV     GOV     ROW
---------------------------------------------------------------------
OUT   |                                 5,397   1,786   1,474     802
CAP   | 3,521
LAB   | 5,041
TAX   |           779   1,491
CON   |         2,742   3,550                             995
INV   |                                 1,890            -199      95
GOV   |                         2,270
ROW   |   897
---------------------------------------------------------------------
Note: Based on 1996 IO tables for USA. Numbers in 1996 USD billion.

$OFFTEXT

*=====================================================================
* Introduce intertemporal sets
*=====================================================================

* The model captures all generations alive in the first model period
* (year 0) and all those born in the span of the subsequent 150
* years, where generations are labeled according to the year in which
* they are born. The model is solved in 5-year intervals with each
* new generation being born at the start of a period and living to
* the age of 55.

SCALARS TIMINT  Single period time interval                     /5/,
        INIYEAR Year in with oldest generation was born         /-50/;

SETS
        G Generations in the model /
        "-50","-45","-40","-35","-30","-25","-20","-15","-10","-5",
        0,5,10,15,20,25,30,35,40,45,50,55,60,65,70,75,80,85,90,95,
        100,105,110,115,120,125,130,135,140,145,150/,
        T(G) Time periods in the model /
        0,5,10,15,20,25,30,35,40,45,50,55,60,65,70,75,80,85,90,95,
        100,105,110,115,120,125,130,135,140,145,150/,
        A(T)   Typical life-cycle / 0,5,10,15,20,25,30,35,40,45,50/;

* We need some special sets to identify key time periods and generations.

SETS    TFIRST(T)       First period in the model,
        TLAST(T)        Last period in the model,
        ATGEN(G)        Generations with terminal assets;

* These special sets are identified by their order in the declaration.

TFIRST(A)       = YES$(ORD(A) EQ 1);
TLAST(T)        = YES$(ORD(T) EQ CARD(T));
ATGEN(G)        = YES$((CARD(G)-CARD(A)+1) LT ORD(G));

* Aliases used to manipulate sets.

ALIAS (G,GG,YR), (T,TT), (A,AA);

*=====================================================================
* Introduce fundamental parameters
*=====================================================================

SCALARS RBAR_A          Annual interest rate                    /0.05/,
        GAMMA_A         Annual population growth rate           /0.01/,
        DELTA_A         Annual depreciation rate                /0.07/,
        THETA           Inverse intertemporal elasticity        /4.00/,
        SIGMA_CL        Elasticity of substitution (C vs L)     /0.8/,
        PHI             Consumption share parameter             /0.4/,
        ETADX           Elasticity of transformation D vs. X    /4/,
        SIGMA           Armington elasticity on imports         /4/;

* Modify annual rates of change to 5-year interval between solution
* periods

SCALARS RBAR            Periodic interest rate,
        GAMMA           Periodic population growth rate,
        DELTA           Periodic depreciation rate,
        RHO_CL          Exponent in intratemporal utility;

RBAR    = (1+RBAR_A)**TIMINT  - 1;
GAMMA   = (1+GAMMA_A)**TIMINT - 1;
DELTA   = 1 - (1-DELTA_A)**TIMINT;
RHO_CL  = 1 - 1/SIGMA_CL;

*=====================================================================
* Time profiles
*=====================================================================

* Declare variables relating values to intertemporal sets and use
* annual growth and interest rates to create time profiles consistent
* with the 5-year interval between solution periods.

PARAMETERS
        YEAR(G)         Point in time,
        AGE(A)          Age at a given point in the life cycle,
        PREF(G)         Reference price path (present value index),
        QREF(G)         Reference quantity path (index),
        PSHR(A)         Population share for agents of age A,
        PI(A)           Productivity index;

* Time periods and ages can be identified by the order of the
* relevant set using the fact that each period has a length of 5
* years, and that generations are labeled according to the year they
* are born and live for 55 years.

YEAR(G)         = INIYEAR + TIMINT * (ORD(G)-1);
AGE(A)          = TIMINT * (ORD(A)-1);

* Declare indices for population size and present value prices.

QREF(G)         = (1+GAMMA_A)**YEAR(G);
PREF(G)         = 1 /(1+RBAR_A)**YEAR(G);

* Age group A share in total polutation

PSHR(A) = (1/QREF(A)) / SUM(AA, (1/QREF(AA)));

* Productivity index as in Auerbach and Kotlikoff (1987)

PI(A) = EXP(4.47 + 0.033*AGE(A) - 0.00067*(AGE(A))**2) / EXP(4.47);

* Use ages and years to set up correspondence between generations,
* age, and year.

SET MAPG(G,A,YR)    Assignment from generation and age to time period;

MAPG(G,A,YR)    = YES$(YEAR(G)+AGE(A) EQ YEAR(YR));

*=====================================================================
* Read benchmark data
*=====================================================================

SCALARS C0      Benchmark private consumption           /5.397/,
        I0      Benchmark investment                    /1.786/,
        G0      Benchmark government consumption        /1.474/,
        X0      Benchmark exports                       /0.802/,
        M0      Benchmark imports                       /0.897/,
        R0      Benchmark capital earnings (net of tax) /2.742/,
        L0      Benchmark labor earnings (net of tax)   /3.550/,
        S0      Benchmark savings                       /1.890/,
        T0      Benchmark transfers  to households      /0.995/,
        D0      Benchmark government budget deficit     /0.199/,
        B0      Benchmark trade deficit                 /0.095/,
        Y0      Benchmark output                        /8.562/,
        TR0     Benchmark tax rate on capital income
        TL0     Benchmark tax rate on labor income;

TR0     = 779  / 2742;
TL0     = 1491 / 3550;

* Infer capital stock from earnings and the steady-state return:

SCALAR        K0      Initial capital stock;

K0      = R0 / (RBAR+DELTA);

*=====================================================================
* Modify benchmark data to represent a consistent steady-state
*=====================================================================

* Modify investment level and revise consumption accordingly to keep
* total demand constant:

C0      = C0 + I0 - (GAMMA+DELTA)*K0;
I0      = (GAMMA+DELTA)*K0;
S0      = R0 + L0 + T0 - C0;

*=====================================================================
* Calibration model: Solve for benchmark steady state of reference
* generation
*=====================================================================

* Find utility discount rate, RHO, and time endowment, OMEGA, to set
* implied aggregate values at the benchmark level. Government
* transfers to households, T0, are modeled as exogenous lump-sum
* payments and are added to household incomes according to each
* generation's share in the total population. We use the equations
* arising from the household utility maximization problem to set up
* an mixed complementarity problem (MCP) and use the solver to find
* the value of RHO that satisfies all the equations in the system.

VARIABLES
        CA(A)           Present value of assets over the life cycle,
        CMA(A)          Value of assets held by age,
        CCMA            Aggregate value of assets held by age,
        RHO             Period utility discount rate,
        OMEGA           Scaling factor on time endowment;

POSITIVE VARIABLES
        CZ(A)           Full consumption,
        CC(A)           Consumption,
        CCC             Aggregate consumption,
        CELL(A)         Leisure time,
        CL(A)           Labor time,
        CPZ(A)          Price of full consumption (present value),
        ETA(A)          Price of time (present value utils),
        LAMDA           Price of income (present value utils);

EQUATIONS
        EQZ(A)          Definition of consumption,
        EQPZ(A)         Definition of price of full consumption,
        EQC(A)          FOC for consumption,
        EQS(A)          FOC for leisure time,
        EQL(A)          FOC for labor time,
        EQETA(A)        FOC for price of time,
        EQLAMDA         FOC for price of income,
        EQCA(A)         Present value assets over the life cycle,
        EQCMA(A)        Value of assets held by age,
        EQCCC           Aggregate consumption,
        EQCCMA          Aggregate value of assets,
        EQCCCLEV        Fix level of aggregate consumption,
        EQCCMALEV       Fix level of aggregate assets;

* Equation definitions:

EQZ(A)..        CZ(A) =E= ( PHI*CC(A)**RHO_CL
                +(1-PHI)*CELL(A)**RHO_CL )**(1/RHO_CL);

* First order conditions:

EQC(A)..        LAMDA*PREF(A) =E= (1+RHO)**(1-ORD(A))
                * CZ(A)**(1-RHO_CL-THETA)
                * PHI*CC(A)**(RHO_CL-1);

EQS(A)..        ETA(A) =E= (1+RHO)**(1-ORD(A))
                * CZ(A)**(1-RHO_CL-THETA)
                * (1-PHI)*CELL(A)**(RHO_CL-1);

EQL(A)..        ETA(A)=G=LAMDA*PREF(A)*PI(A);

EQLAMDA..        SUM(A,PREF(A)*CC(A)) =E=
                SUM(A,PREF(A)*(PI(A)*CL(A) + PSHR(A)*QREF(A)*T0));

EQETA(A)..      OMEGA =E= CELL(A) + CL(A);

* Price indices:

EQPZ(A)..       CPZ(A) =E=
                (PHI**SIGMA_CL*PREF(A)**(1-SIGMA_CL) + (1-PHI)**SIGMA_CL
                * (ETA(A)/LAMDA)**(1-SIGMA_CL))**(1/(1-SIGMA_CL));

* Asset positions:

EQCA(A)..        CA(A) =E= SUM(AA$(ORD(AA) LT ORD(A)),
                 PREF(AA)*(PI(AA)*CL(AA)
                 + PSHR(AA)*QREF(AA)*T0-CC(AA)));

EQCMA(A)..      CMA(A) =E= CA(A)/(QREF(A)*PREF(A));

* Aggregate values:

EQCCC..         CCC =E= SUM(A,CC(A)/QREF(A));
EQCCMA..        CCMA =E= SUM(A,CMA(A));

* Fix aggregate level of consumption and assets at benchmark level:

EQCCCLEV..      CCC =E= C0;
EQCCMALEV..     CCMA =E= (1+RBAR)*K0 + (B0-D0)*(1+RBAR)/(RBAR-GAMMA);

* Associate variables with equations:

MODEL BENCH     /EQZ.CZ, EQPZ.CPZ, EQCA.CA, EQCMA.CMA, EQC.CC,
                EQS.CELL,EQL.CL, EQETA.ETA, EQLAMDA.LAMDA, EQCCC.CCC,
                EQCCMA.CCMA, EQCCCLEV.RHO, EQCCMALEV.OMEGA/;

* Set bounds to prevent operation errors:

RHO.LO          = -0.99;
CZ.LO(A)        = 1E-5;
CC.LO(A)        = 1E-5;
CELL.LO(A)      = 1E-5;
LAMDA.LO        = 1E-5;

* Initialize variables:

RHO.L           = 0.01;
CZ.L(A)         = 0.5;
CC.L(A)         = 0.5;
CELL.L(A)       = 0.5;
CL.L(A)         = 0.5;
CPZ.L(A)        = 0.5;
ETA.L(A)        = 0.5;
LAMDA.L         = 0.5;
CCC.L           = 0.5;

* Solve calibration model:

BENCH.ITERLIM=50000;
SOLVE BENCH USING MCP;

* Calibration results

PARAMETERS      RHO_A           Annual utility discount rate,
                PELLRATIO(A)    Ratio of reservation to market wage;

RHO_A           = (1+RHO.L)**(1/TIMINT) - 1;
PELLRATIO(A)    = 100 * ETA.L(A)/(PREF(A)*PI(A)*LAMDA.L);

*=====================================================================
* Use endowments and the calibrated consumption and leisure time
* profiles for generation 0 to install baseline values for all
* generations
*=====================================================================

PARAMETERS
        PIREF(G,T)      Baseline productivity profile,
        EREF(G,T)       Baseline endowment profile,
        CREF(G,T)       Baseline consumption profile,
        ELLREF(G,T)     Baseline leisure time profile,
        LREF(G,T)       Baseline labor time profile,
        ZREF(G,T)       Baseline full consumption profile,
        TREF(G,T)       Baseline transfers to households,
        PELLREF(G,T)    Baseline reservation wage,
        PZREF(G,T)      Baseline price of full consumption,
        ZREF_T(G,A)     Baseline post-terminal consumption profile,
        PREF_T(A)       Baseline post-terminal price path,
        PZREF_T(G,A)    Baseline post-terminal full consumption,
        MREF(G)         Baseline present value of consumption;

* We assign demand and income profiles for generation G at time T
* based on endowments and the calibrated consumption profile for
* generation 0. The trick here is to use a GAMS loop over the mapping
* which relates generations (G), ages (A) and time periods (T).

LOOP(MAPG(G,A,T),
        PIREF(G,T)      = PI(A);
        EREF(G,T)       = QREF(G) * OMEGA.L;
        CREF(G,T)       = QREF(G) * CC.L(A);
        ELLREF(G,T)     = QREF(G) * CELL.L(A);
        LREF(G,T)       = QREF(G) * CL.L(A);
        ZREF(G,T)       = QREF(G) * CZ.L(A);
        PELLREF(G,T)    = PREF(G) * ETA.L(A)/LAMDA.L;
        TREF(G,T)       = QREF(G) * PSHR(A)*T0*QREF(A);
        PZREF(G,T)      = PREF(G) * CPZ.L(A);   );

* The last model generation is born in year 150 which means that in
* order to capture the full life cycle of all model generations we
* need to cover a 50-year "post-terminal" period. We index these
* post-terminal periods by the same index (A) that we use to index
* ages in a life cycle.

* Consumption profiles in post-terminal periods for generation G at
* age A are inferred from the consumption levels in the initial
* period of generations that have the same age.

LOOP((G,A,TLAST)$(YEAR(G)+AGE(A) GT YEAR(TLAST)),
        ZREF_T(G,AA)$(AGE(AA)+YEAR(TLAST) EQ AGE(A)+YEAR(G))
        = QREF(G) * CZ.L(A); );

* Present value prices in post-terminal periods are extrapolated from
* the value of the reference price index in the terminal period.

LOOP((A,TLAST)$AGE(A), PREF_T(A) = PREF(TLAST) / (1 + RBAR_A)**AGE(A); );

LOOP((G,A,TLAST)$(YEAR(G)+AGE(A) GT YEAR(TLAST)),
        PZREF_T(G,AA)$(AGE(AA)+YEAR(TLAST) EQ AGE(A)+YEAR(G))
        = CPZ.L(A)*PREF(G); );

* Present value of consumption by generation, including post-terminal
* consumption by generations who live beyond the model horizon.

MREF(G) = SUM(T,  ZREF(G,T)*PZREF(G,T))
        + SUM(A, PZREF_T(G,A)*ZREF_T(G,A));

*=====================================================================
* Distribute assets holdings by type
*=====================================================================

SCALARS THETAC          Ratio of capital stock to assets,
        THETAD          Ratio of government deficit to assets,
        THETAB          Ratio of trade deficit to assets;

PARAMETERS
        A0REF(G)        Baseline initial asset holdings,
        ATREF(G)        Baseline terminal asset holdings;

* Value shares of the different asset types as implied by benchmark
* value flows.

THETAC  = (1+RBAR)*K0 / CCMA.L;
THETAB  = (B0*(1+RBAR)/(RBAR-GAMMA)) / CCMA.L;
THETAD  = (-D0*(1+RBAR)/(RBAR-GAMMA)) / CCMA.L;

* Distribute asset types by assuming that all age groups hold the
* different types in same proportion. Use mapping to identify
* generation at time zero from age of reference generation.

A0REF(G)        = SUM(MAPG(G,A,"0"), CMA.L(A));

* Assets left at end of terminal period for generation G are inferred
* from inital assets.

LOOP((G,GG),    ATREF(G)$(ORD(G) EQ (ORD(GG) + (CARD(G) + 1 - CARD(A))))
                = A0REF(GG) * (1+GAMMA)**CARD(T) / (1+RBAR); );

*=====================================================================
* Parameters for counterfactual experiments
*=====================================================================

PARAMETERS
        TAXR    Model tax rate on capital earnings,
        TAXL    Model tax rate on labor earnings;

* Initialize model tax rates at benchmark values:

TAXR    = TR0;
TAXL    = TL0;

*=====================================================================
* Define share parameters
*=====================================================================

PARAMETER       ALPHAC  Goods share of full consumption;

ALPHAC(G,T)$ZREF(G,T) = CREF(G,T)*PREF(T) / (ZREF(G,T)*PZREF(G,T));

*=====================================================================
* Model in GAMS/MCP. This model solves for the equilibrium transition
* path subject to terminal conditions that assume the presence of a
* steady state. If there are no exogenous changes the model
* replicates the calibrated consumption profiles. We use this feature
* to check the calibrations and then solve for the results of
* fundamental tax reform
*=====================================================================

POSITIVE VARIABLES

* Activity levels. These determine how inputs are converted into
* outputs according to the technology implied by functional forms and
* the benchmark data. The variables here are activity levels and an
* equilibrium requires that each active sector earns zero profit.

        QY(T)           Domestic production,
        QA(T)           Supply of Armington composite,
        QK(T)           Capital stock,
        QI(T)           Investment,
        QL(G,T)         Labor supply,
        QZ(G,T)         Full consumption,
        QU(G)           Utility,

* Prices. The variables here are the prices that are associated with
* each commodity. An equilibrium requires that prices are such that
* supply equals demand.

        PH(T)           Price of output for domestic use,
        PFX             Price of foreign exchange,
        PY(T)           Composite price of output,
        PA(T)           Price of Armington composite,
        PL(T)           Wage rate (labor in efficiency units),
        PR(T)           Rental rate,
        PK(T)           Price of capital,
        PU(G)           Price of intertemporal utility,
        PKT             Price of post-terminal capital,
        PELL(G,T)       Reservation wage (leisure in units of time),
        PZ(G,T)         Price of full consumption (current value),
        PZT(G,A)        Price of full consumption (current value),

* Incomes. These are agents that receive income from endowments or
* taxes and spend it to maximize utility. The variables here are
* income levels and an equilibrium requires that total income equals
* total expenditure.

        RA(G)           Representative agents by generation,
        GOVT(T)         Government with period-by-period budget,

* Auxiliary variables. These are endogenous variables associated with
* model constraints that relate the transition to the steady state.
* The replacement tax is varying over time to ensure government
* budget balance period by period.

        KT              Terminal capital,
        ZT(G,A)         Post-terminal consumption of goods,
        AT(G)           Terminal bonds,
        TAU(T)          Replacement tax in counterfactual;

EQUATIONS

* Equations asscociated with model variables. These fall into three
* classes. PRF which ensure zero profit in each activity, MKT which
* ensure no excess demand for each commodity, and DEF which ensure
* income balance for each agent.

        PRF_QY(T)       Domestic production,
        PRF_QA(T)       Supply of Armington composite,
        PRF_QK(T)       Capital stock,
        PRF_QI(T)       Investment,
        PRF_QL(G,T)     Labor supply,
        PRF_QZ(G,T)     Full consumption,
        PRF_QU(G)       Utility,
        MKT_PH(T)       Price of output for domestic use,
        MKT_PFX         Pice of foreign exchange,
        MKT_PA(T)       Price of Armington composite,
        MKT_PL(T)       Wage rate (labor in efficiency units),
        MKT_PR(T)       Rental rate,
        MKT_PK(T)       Price of capital,
        MKT_PU(G)       Price of intertemporal utility,
        MKT_PKT         Price of post-terminal capital,
        MKT_PELL(G,T)   Reservation wage (leisure in units of time),
        MKT_PZ(G,T)     Price of full consumption (current value),
        MKT_PZT(G,A)    Price of full consumption (current value),
        DEF_RA(G)       Representative agents by generation,
        DEF_GOVT(T)     Government - period-by-period balancing,

* Equations associated with auxilliary variables used to impose
* steady-state restrictions on the values of terminal period
* variables, and with simplyfying terms.

        EQ_KT           Terminal capital,
        EQ_ZT(G,A)      Post-terminal consumption of goods,
        EQ_AT(G)        Terminal bonds,
        EQ_TAU(T)       Replacement tax in counterfactual
        EQ_PY(T)        Defines PY to simplify algebra;

*=====================================================================
* The following equations define zero profit conditions for each
* activity.
*=====================================================================

PRF_QY(T)..
        (PR(T)*(1+TAXR)/(PREF(T)*(1+TR0)))**(R0*(1+TR0)/Y0)*
        (PL(T)*(1+TAXL)/(PREF(T)*(1+TL0)))**(L0*(1+TL0)/Y0)
        =E= PY(T)/PREF(T);

EQ_PY(T)..
        Y0 * (PY(T)/PREF(T))**(1+ETADX)
        =E= X0 * PFX**(1+ETADX)
        + (Y0-X0) * (PH(T)/PREF(T))**(1+ETADX);

PRF_QA(T)..
        (M0 / (C0+I0+G0)) * PFX**(1-SIGMA)
        + ((Y0-X0)/(C0+I0+G0)) * (PH(T)/PREF(T))**(1-SIGMA)
        =E= (PA(T)/PREF(T))**(1-SIGMA);

PRF_QK(T)..
        PK(T)*K0
        =E= PR(T)*R0 + (PK(T+1)+PKT$TLAST(T))*K0*(1-DELTA);

PRF_QI(T).. PA(T) =E= PK(T+1) + PKT$TLAST(T);

PRF_QL(G,T)$CREF(G,T).. PELL(G,T) =G= PL(T) * PIREF(G,T);

PRF_QZ(G,T)$ZREF(G,T)..
        ALPHAC(G,T) * (PA(T)*(1+TAU(T))/PREF(T))**(1-SIGMA_CL) +
        (1-ALPHAC(G,T)) * (PELL(G,T)/PELLREF(G,T))**(1-SIGMA_CL)
        =E= (PZ(G,T)/PZREF(G,T))**(1-SIGMA_CL);

PRF_QU(G)..
        SUM(T, PZREF(G,T)*ZREF(G,T)*(PZ(G,T)/PZREF(G,T))**(1-1/THETA))
        +SUM(A, PZREF_T(G,A)*ZREF_T(G,A)
        *(PZT(G,A)/PZREF_T(G,A))**(1-1/THETA))
        =E= MREF(G) * PU(G)**(1-1/THETA);

*=====================================================================
* The following define market clearance by ensuring no excess demand
* for each commodity
*=====================================================================

MKT_PA(T)..
        QA(T) * (Y0-X0+M0) =E= QI(T) * I0
        + SUM(G, CREF(G,T) * QZ(G,T)
        * (PZ(G,T)*PREF(T)/(PA(T)*(1+TAU(T))*PZREF(G,T)))**SIGMA_CL)
        + GOVT(T)/PA(T);

MKT_PELL(G,T)$CREF(G,T)..
        EREF(G,T) =E= QL(G,T) +
        ELLREF(G,T)*QZ(G,T)*(PZ(G,T)*PELLREF(G,T)
        / (PELL(G,T)*PZREF(G,T)))**SIGMA_CL;

MKT_PL(T)..
        SUM(G, QL(G,T) * PIREF(G,T))
        =E= L0 * QY(T) * ((PY(T)*(1+TL0)) / (PL(T)*(1+TAXL)));

MKT_PR(T)..
        QK(T)*R0 =E= R0 * QY(T) * ((PY(T)*(1+TR0)) / (PR(T)*(1+TAXR)));

MKT_PK(T)..
        QK(T-1)*K0*(1-DELTA) + QI(T-1)*I0
        + SUM(G,THETAC*A0REF(G)/(1+RBAR))$TFIRST(T)
        =E= QK(T)*K0;

MKT_PH(T)..
        QY(T) * (PH(T)/PY(T))**ETADX
        =E= QA(T) * (PA(T)/PH(T))**SIGMA;

MKT_PFX..
        SUM(T, PREF(T) * X0 * QY(T) * (PFX*PREF(T)/PY(T))**ETADX)
        + SUM((G,T), PREF(T)*TREF(G,T))
        + SUM(G, (1-THETAC)*A0REF(G))
        + SUM(T, PREF(T)*QREF(T)*(D0-T0))
        =E= SUM(T, PREF(T) * M0 * QA(T) * (PA(T)/(PREF(T)*PFX))**SIGMA)
        + SUM((G,TLAST), AT(G)*PREF(TLAST)*(1-THETAC)*ATREF(G));

MKT_PKT..
        SUM(TLAST, QK(TLAST)*K0*(1-DELTA) + QI(TLAST)*I0)
        =E= SUM(ATGEN, THETAC * ATREF(ATGEN) * KT);

MKT_PZ(G,T)$ZREF(G,T)..
        QZ(G,T) =E= QU(G) * (PU(G)*PZREF(G,T)/PZ(G,T))**(1/THETA);

MKT_PZT(G,A)$ZREF_T(G,A)..
        ZT(G,A) =E= QU(G) * (PU(G)*PZREF_T(G,A)/PZT(G,A))**(1/THETA);

MKT_PU(G).. QU(G)*PU(G)*MREF(G) =E= RA(G);

*=====================================================================
* The following equations define income balance for households and
* government
*=====================================================================

DEF_RA(G)..
        RA(G) =E= SUM(T, PELL(G,T) * EREF(G,T))
        + PFX * SUM(T,PREF(T)*TREF(G,T))
        + SUM(TFIRST, PK(TFIRST) * THETAC * A0REF(G)/(1+RBAR))
        + PFX * (1-THETAC)*A0REF(G)
        + SUM(A, PZT(G,A)*ZREF_T(G,A)*ZT(G,A))
        + AT(G) * PFX * (-SUM(TLAST, PREF(TLAST)*(1-THETAC)*ATREF(G)))
        + KT * PKT * (-THETAC*ATREF(G));

DEF_GOVT(T)..
        GOVT(T) =E= PREF(T)*QREF(T)*(D0-T0) * PFX
        + TAXL * PL(T) * L0 * QY(T) * ((PY(T)*(1+TL0)) / (PL(T)*(1+TAXL)))
        + TAXR * PR(T) * R0 * QY(T) * ((PY(T)*(1+TR0)) / (PR(T)*(1+TAXR)))
        + SUM(G, CREF(G,T)* QZ(G,T)
        * (PZ(G,T)*PREF(T)/(PA(T)*(1+TAU(T))*PZREF(G,T)))**SIGMA_CL
        * PA(T) * TAU(T));

*=====================================================================
* The following equations describe additional constraints used to
* close the model and select the level of endogenous taxes.
*=====================================================================

* Set the endogenous tax to balance the government budget to balance
* period by period.

EQ_TAU(T).. PA(T) * QREF(T) * G0 =E= GOVT(T);

* Select terminal capital stocks so that all generations living past
* the terminal period achieve the same equivalent variation.

EQ_AT(G)$ATGEN(G).. QU(G) - QU(G-1) =E= 0;

* Select the levels of post-terminal consumption of goods and leisure
* so that the present value price declines with the steady-state
* interest rate.

EQ_ZT(G,A)$ZREF_T(G,A)..
        SUM(TLAST, PZ(G-(ORD(A)-1),TLAST))
        =E= PZT(G,A) * (1+RBAR)**(ORD(A)-1);

* Scale the level of the terminal capital staock to achieve
* steady-state growth in last period investment.

EQ_KT.. SUM(TLAST(T), QI(T)/QI(T-1)) =E= 1 + GAMMA;

*=====================================================================
* Assign initial values and bounds for activity levels, prices, and
* auxiliary variables:
*=====================================================================

QY.L(T)         = QREF(T);
QA.L(T)         = QREF(T);
QK.L(T)         = QREF(T);
QI.L(T)         = QREF(T);
QL.L(G,T)       = LREF(G,T);
PY.L(T)         = PREF(T);
PH.L(T)         = PREF(T);
PFX.L           = 1;
PA.L(T)         = PREF(T);
PL.L(T)         = PREF(T);
PZ.L(G,T)       = PZREF(G,T);
PZT.L(G,A)      = PZREF_T(G,A);
PR.L(T)         = PREF(T);
PK.L(T)         = PREF(T)*(1+RBAR);
PELL.L(G,T)     = PELLREF(G,T);
PZT.L(G,A)      = PZREF_T(G,A);
LOOP(TLAST, PKT.L= PK.L(TLAST) / (1+RBAR));
KT.L            = 1;
KT.LO           = -INF;
AT.L(G)         = 1;
AT.LO(G)        = -INF;
ZT.L(G,A)       = 1$ZREF_T(G,A);
TAU.LO(T)       = -INF;
TAU.L(T)        = 0;
QU.L(G)         = 1;
PU.L(G)         = 1;
QZ.L(G,T)       = 1$ZREF(G,T);
GOVT.L(T)       = PREF(T) * QREF(T) * G0;
RA.L(G)         = MREF(G);

* Numeraire:

PA.FX(TFIRST)   = 1;

MODEL OLG /     PRF_QY.QY,PRF_QA.QA,PRF_QK.QK,PRF_QI.QI,
                PRF_QL.QL,PRF_QZ.QZ,PRF_QU.QU,MKT_PH.PH,
                MKT_PFX.PFX,MKT_PA.PA,MKT_PL.PL,MKT_PR.PR,
                MKT_PK.PK,MKT_PU.PU,MKT_PKT.PKT, MKT_PELL.PELL,
                MKT_PZ.PZ,MKT_PZT.PZT,DEF_RA.RA,DEF_GOVT.GOVT,
                EQ_KT.KT,EQ_ZT.ZT,EQ_AT.AT,EQ_TAU.TAU,EQ_PY.PY /;

*=====================================================================
* Replicate the benchmark equilibrium:
*=====================================================================

OLG.ITERLIM=0;
SOLVE OLG USING MCP;

*=====================================================================
* Run counterfactual: reduce taxes on capital and labor income:
*=====================================================================

* Parameters for reporting results from counterfactual experiment:

PARAMETERS
        WCHANGE Welfare change (% equivalent variation by year of birth),
        WGAIN   Base year total welfare gain (1996 USD billion),
        TDEF    Trade deficit (% of baseline level),
        KSTOCK  Capital stock (% change from baseline level),
        LSUPPLY Aggregate labor supply (% change from baseline level),
        CONSTAX Consumption tax rate (%);

* Reduce tax on capital income or tax on labor income by $100 billion:

SETS    SCENARIO                /CAPITAL,LABOR/,
        CAPTAX(SCENARIO)        /CAPITAL/
        LABTAX(SCENARIO)        /LABOR/;

LOOP(SCENARIO,

        TAU.L(T)        = 0;
        TAXR            = TR0;
        TAXL            = TL0;

        IF (CAPTAX(SCENARIO), TAXR = TR0 - 100*1E-3/R0; );
        IF (LABTAX(SCENARIO), TAXL = TL0 - 100*1E-3/L0; );

* Solve the model

        OLG.ITERLIM=10000;
        SOLVE OLG USING MCP;

*=====================================================================
* Report results from tax reform
*=====================================================================

        WCHANGE(G,SCENARIO)     = 100 * (QU.L(G) - 1);
        WGAIN(SCENARIO)
        = SUM(G$(ORD(G) EQ CARD(G)),(QU.L(G)-1))
        * SUM(A, (CC.L(A)+(ETA.L(A)/LAMDA.L)*CELL.L(A)/
        PREF(A))/QREF(A)) / 1E-3;

        TDEF(T,SCENARIO)
        = 100 * (( M0 * QA.L(T) * (PA.L(T)/(PREF(T)*PFX.L))**SIGMA
        - X0 * QY.L(T) * (PFX.L*PREF(T)/PY.L(T))**ETADX)
        / (QREF(T)*B0) -1);
        KSTOCK(T,SCENARIO)      = 100 * (QK.L(T) / QREF(T) - 1);
        LSUPPLY(T,SCENARIO)
        = 100 * (L0 * QY.L(T) * ((PY.L(T)*(1+TL0)) / (PL.L(T)*(1+TAXL)))
        / (L0*QREF(T)) - 1);
        CONSTAX(T,SCENARIO)     = 100 * TAU.L(T);

* End scenario loop
);

DISPLAY PSHR,QREF,PREF,TR0,TL0,K0,PIREF,EREF,CREF,ELLREF,LREF,ZREF,
        TREF,PELLREF,PZREF,ZREF_T,PREF_T,PZREF_T,MREF,RHO.L,RHO_A,
        OMEGA.L,PELLRATIO,THETAC,THETAD,THETAB,WCHANGE,WGAIN,TDEF,
        KSTOCK,LSUPPLY,CONSTAX;