*  This model is the same as that in Appendix D except for:
*  1. MPSGE representation of the transition model. 

*=====================================================================
* 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.

SCALAR
	TIMINT		Single period time interval		/3/,
	INIYEAR		Year in with oldest generation was born /-54/;
SETS
	G		Generations in the model		/
	"-54","-51","-48","-45","-42","-39","-36","-33","-30",
	"-27","-24","-21","-18","-15","-12","-9","-6","-3",
	0,3,6,9,12,15,18,21,24,27,30,33,36,39,42,45,48,51,54,57,
	60,63,66,69,72,75,78,81,84,87,90,93,96,99,
	102,105,108,111,114,117,120,123,126,129,132,
	135,138,141,144,147,150/,
	T(G) Time periods in the model / 
	0,3,6,9,12,15,18,21,24,27,30,33,36,39,42,45,48,51,54,57,
	60,63,66,69,72,75,78,81,84,87,90,93,96,99,102,105,108,111,
	114,117,120,123,126,129,132,135,138,141,144,147,150/,
	A(T) Life-cycle /0,3,6,9,12,15,18,21,24,27,
			 30,33,36,39,42,45,48,51,54/;
SETS	ALABELS(T)	Labels for plots /0,12,24,36,48/,
	GLABELS(G)	Labels for plots /"-30",0,30,60,90,120,150/,
	TLABELS(G)	Labels for plots /0,30,60,90,120,150/;

*  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));

* There are three types of households:
 
SET     H       Households / patient, impatient, wealthy /;

* Aliases used to manipulate sets.

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

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

SCALARS RBAR_A          Annual interest rate                    /0.05/,
        GAMMA_A         Annual population growth rate           /0.01/,
        THETA           Exponent in intertemporal utility       /4.00/;

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

SCALARS RBAR            Periodic interest rate,
        GAMMA           Periodic population growth rate;

RBAR    = (1+RBAR_A)**TIMINT  - 1;
GAMMA   = (1+GAMMA_A)**TIMINT - 1;

PARAMETER       NUMBER(H)       Relative numbers of households  
                                /WEALTHY 1, PATIENT 2, IMPATIENT 10/;

SCALAR          CAD0            Current account deficit (calibrated);

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

*  Declare parameters relating values to intertemporal sets and use
*  annual growth and interest rates to create time profiles consistent
*  with the 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 price index),
	QREF(G)         Reference quantity path (index of population size),
	CONSUM(A,H)     Consumption profile
	BQDISTR(A)      Bequest distribution
	ENDOW(A,H)      Endowment profile
	BEQUEST(G,GG,H) Bequest (present value) by household H generation G,
	BQR(A,H)        Period 0 bequest receipts 
	BQV(H)          Bequestion value for household H
	PVBQ(G,H)       Present value bequest
	BQN(H)          Net bequests received by period 0 generation
	ESUBB(G,H)      Top-level elasticity bw consumption and bequests,
	BETA_B(A,H)     Average bequest as fraction of residual income          
	BETA(H)         Average bequest (fraction of wealth)  /WEALTHY 0.01/
	XI(H)           Bequest elasticity wrt income /WEALTHY 2/;

BEQUEST(G,GG,H) = 0;
ESUBB(G,H) = 0;

*  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);

SCALAR LIFESPAN;  LIFESPAN = SMAX(A, YEAR(A)) - YEAR("0");

* Declare indices for population size and present value prices.

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

*  Use ages and years to set up correspondence from generations, life
*  cycle 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));

* Endowment profile for rich as in Auerbach and Kotlikoff (1987):

ENDOW(A,"WEALTHY") = EXP(4.47 + 0.033*AGE(A) - 0.00067 * AGE(A)**2);
ENDOW(A,"PATIENT") = EXP(4.47 + 0.033*AGE(A) - 0.00067 * AGE(A)**2);
ENDOW(A,"IMPATIENT") = SQRT(ENDOW(A,"PATIENT"));

*  Endowment profiles are scaled to an economy-wide level of 1 in the
*  base year.

ENDOW(A,H) = NUMBER(H) * ENDOW(A,H) / 
	SUM((AA,HH), (1+GAMMA)**(1-ORD(AA)) * NUMBER(HH) * ENDOW(AA,HH));

*  Define bequest distribution. This is the fraction of a $ of bequests
*  in a given year recieved by genereations as defined by their age in
*  that year. It is assumed that only those between the age of 10 and
*  20 recieve bequests according to the following formula.

BQDISTR(A)$((10 LE AGE(A)) AND (AGE(A) LE 20)) =
	  0.14 + AGE(A)*0.038 + AGE(A)*AGE(A)*(-0.002);

* Scale these to sum to unity.

BQDISTR(A) = BQDISTR(A) / SUM(AA, BQDISTR(AA));

*  Compute the base year bequest. The bequest given by households in
*  generation 0 is related to labor income and the level of bequests
*  they receive during the their lifetime.

BQV(H) = BETA(H) * SUM(A, PREF(A)*ENDOW(A,H)) 
	/ (1-BETA(H)*SUM(A,BQDISTR(A)*PREF(A)*QREF(A)));

*  Compute beqeust receipts for the generations alive in period 0.
*  Bequests are distributed in the final period of economic activity for
*  a given generation, so period 0 bequests are distributed by the
*  oldest generation.

BQR(A,H) = BQDISTR(A) *  BQV(H) * ((1+RBAR)/(1+GAMMA))**(CARD(A)-1);

* Net bequest receipts for generation 0 households.

BQN(H) = SUM(A, BQR(A,H)*QREF(A)*PREF(A)) - BQV(H);

*  Infer present value of bequest receipts to generation G from
*  generation GG for all generations from the bequest receipts in year
*  zero.

LOOP((G,GG,A,TLAST)$((YEAR(G)+LIFESPAN EQ YEAR(GG)+AGE(A)) 
	and (YEAR(G)+LIFESPAN LE YEAR(TLAST))),
    BEQUEST(G,GG,H)$BETA(H) = BQDISTR(A) * BQV(H) * QREF(G) * PREF(G););

*  The present value bequest by generation G is the sum of all bequests
*  to generations GG.

PVBQ(G,H) = SUM(GG, BEQUEST(G,GG,H));

* Impose exogenous consumption profiles.

CONSUM(A,"WEALTHY") =  1 + AGE(A) * (1.2620/1E2 
		+ AGE(A) * (4.8180/1E4 + AGE(A) * (-9.5569)/1E6));
CONSUM(A,"PATIENT") =  CONSUM(A,"WEALTHY");
CONSUM(A,"IMPATIENT") =  1;

* Scale consumption for budget balance.

CONSUM(A,H) = CONSUM(A,H)*(SUM(AA, ENDOW(AA,H)*PREF(AA))+BQN(H)) / 
		SUM(AA, CONSUM(AA,H)*PREF(AA));

* Compute bequest as shares of remaining life time income for
* generations in year zero.

BETA_B(A,H) = BQV(H)
	/ (BQV(H)+SUM(AA$(AGE(AA) GE AGE(A)), PREF(AA) * CONSUM(AA,H)));

* Compute elasticity of substitution between top level consumption
* index and bequests.
* 
ESUBB(G,H)$XI(H) = (1-BETA(H)*XI(H)) / (XI(H)*(1-BETA(H)));

LOOP(MAPG(G,A,TFIRST), ESUBB(G,H)$XI(H) = (1-BETA(H)*XI(H)) 
	/ (XI(H)*(1-BETA(H))););

*       Calibrate the current account deficit as a residual: 

CAD0 = SUM((A,H), (CONSUM(A,H)-ENDOW(A,H))/QREF(A));

*=====================================================================
*  Use endowments and the calibrated consumption profiles for generation
*  0 to to back out the evolution of asset holdings and distinguish
*  between domestic and foreign debt
*=====================================================================

PARAMETERS
	ASSETS(A,H)     Present value of assets over the lifecycle,
	MA(A,H)         Current assets by age in period 0,
	ASSETH          Positive asset holdings by age in period 0,
	DEBT            Net Debt by age in period 0;

SCALARS
	DEFICIT         Gross deficit among domestic households,
	SURPLUS         Gross surplus among domestic households,
	THETAD          Domestic share of domestic debt         /1/,
	THETAA          Domestic share of domestic assets       /1/;

*  The present value of assets equals the sum of the value of endowments
*  less consumption in all previous periods of the life cycle. The asset
*  profile of the representative generation can then be used to find the
*  distribution of asset holdings accross generations alive in the base
*  year.

ASSETS(A,H)     = SUM(AA$(ORD(AA) LT ORD(A)), 
	PREF(AA)*(ENDOW(AA,H) + QREF(AA)*BQR(AA,H) - CONSUM(AA,H)));
MA(A,H)         = ASSETS(A,H)/(QREF(A)*PREF(A));

*  We assume that negative asset positions reflect holdings of both
*  domestic and foreign debt, while positive asset positions reflect
*  holdings of domestic assets. We assume that all age groups with
*  negative assets hold foreign and domestic debt in the same proportion
*  which means * that we can use the ratio of total assets to total debt
*  to decompose the asset holdings by * type.

DEFICIT         = -SUM((A,H)$(MA(A,H) LT 0), MA(A,H));
SURPLUS         = SUM((A,H)$(MA(A,H) GT 0),  MA(A,H));

THETAD$DEFICIT  = MIN(1, SURPLUS / DEFICIT);
THETAA$SURPLUS  = MIN(1, DEFICIT / SURPLUS);

ASSETH(A,H,"DOMESTIC")$(MA(A,H) GT 0) = MA(A,H)  * THETAA;
ASSETH(A,H,"FOREIGN")$(MA(A,H) GT 0)  = MA(A,H)  * (1-THETAA);

DEBT(A,H,"DOMESTIC")$(MA(A,H) LT 0)   = -MA(A,H) * THETAD;
DEBT(A,H,"FOREIGN")$(MA(A,H) LT 0)    = -MA(A,H) * (1-THETAD);

*  We model baseline assets and debt positions as inital endowments for
*  generations alive in year 0.

PARAMETERS      DASSET(*,H)     Domestic asset initial endowments
                FASSET(*,H)     Foreign asset intiial endowments;

DASSET(G,H)     = SUM(MAPG(G,A,"0"), 
			ASSETH(A,H,"DOMESTIC") - DEBT(A,H,"DOMESTIC"));
FASSET(G,H)     = SUM(MAPG(G,A,"0"), 
			ASSETH(A,H,"FOREIGN")  - DEBT(A,H,"FOREIGN"));
DASSET("TOTAL",H) = SUM(G, DASSET(G,H));
FASSET("TOTAL",H) = SUM(G, FASSET(G,H));

*=====================================================================
*  Use solution for reference generation to install baseline values for
*  all generations
*=====================================================================

PARAMETERS
	EREF(G,H,T)             Baseline endowment profile,
	CREF(G,H,T)             Baseline consumption profile,
	BREF(G,H,T)             Time path of bequest receipts,
	PREF_T(A)               Baseline post-terminal price path,
	CREF_T(G,H,A)           Baseline post-terminal consumption profile,
	MREF(G,H)               Baseline present value of consumption,
	RAREF(G,H)              Baseline aggregate income including bequest;

*  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),
        EREF(G,H,T) = QREF(G) * ENDOW(A,H);
        BREF(G,H,T) = QREF(T) * BQR(A,H);
        CREF(G,H,T) = QREF(G) * CONSUM(A,H);  );

*  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.

*  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); );

*  Consumption profiles in post-terminal periods for generation G at age
*  AA 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)),
        CREF_T(G,H,AA)$(AGE(AA)+YEAR(TLAST) EQ AGE(A)+YEAR(G))  
		= CONSUM(A,H) * QREF(G); );

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

MREF(G,H) = SUM(T, PREF(T)*CREF(G,H,T)) + 
			SUM(A,  PREF_T(A)*CREF_T(G,H,A)); 
RAREF(G,H) = MREF(G,H) + SUM(GG, BEQUEST(G,GG,H));

*=====================================================================
* Import and export price levels for counterfactual
*=====================================================================

PARAMETERS      PX(T)                   Export price,
                PM(T)                   Import price;

PX(T) = 1;
PM(T) = 1;

*=====================================================================
* Model in MPSGE. This model solves for the equilibrium transition path 
* subject to terminal conditions that assume the pressence 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 an exogenous change 
* in the price of foreign exchange
*=====================================================================

*	Shift compiler from GAMS to MPSGE and set model name:

$ONTEXT
$MODEL:EXCHANGE

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

$SECTORS:
	U(G,H)		! Utility
	X(T)		! Export
	M(T)		! Import

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

$COMMODITIES:
  PC(T)			   ! Price of private consumption
  PCT(G,H,A)$CREF_T(G,H,A) ! Price of post-terminal consumption of goods
  PU(G,H)		   ! Price of intertemporal utility
  PB(G,H)$PVBQ(G,H)	   ! Price index for bequests 
  PFX			   ! Price of foreign exchange

* Declare consumers. 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.

$CONSUMERS:
  RA(G,H)		   ! Representative agents by generation

* Declare auxiliary variables. These are endogenous variables 
* associated with model constraints that relate the transition to the
* steady state.

$AUXILIARY:
  CT(G,H,A)$CREF_T(G,H,A)  ! Post-terminal consumption of goods
  AT(G,H)$ATGEN(G)         ! Terminal assets 

*=====================================================================
* $PROD blocks describe the production activities using the benchmark 
* data and exogenous elasticities. I: fields denote inputs, O: fields 
* denote outputs, P: fields denote the reference price level, and the 
* s: fields denotes the elasticity of substitution
*=====================================================================

* Utility is treated of as a commodity demanded by the different 
* generations which implies that the utility function is modeled as 
* any other production activity. The activity level here is initialized
* at unity implying an overall output level equal to the present value of
* consumption, MREF(G).

$PROD:U(G,H)  s:(1/THETA)
  O:PU(G,H)	 Q:MREF(G,H)
  I:PC(T)	 Q:CREF(G,H,T)		P:PREF(T)
  I:PCT(G,H,A)	 Q:CREF_T(G,H,A)	P:PREF_T(A)

* This block models the level of imports in each year. The assumption 
* of a small open economy and perfect capital mobility implies that the 
* price of imports is constant in current value terms. We therefore do 
* not need to distinguish between years, but only operate with a single 
* present value price for foreign exchange. This activity is initialized
* at the reference quantity path implying an overall output level equal
* to the baseline trade deficit.

$PROD:M(T)
  O:PC(T)	 Q:1
  I:PFX		 Q:(PM(T)*PREF(T))
 
* There are no exports in the baseline so this activity is initialized 
* at zero.

$PROD:X(T)
  O:PFX		 Q:(PX(T)*PREF(T))
  I:PC(T)	 Q:1

*=====================================================================
* $REPORT blocks recover the level of inputs (I: fields) in production 
* activities (PROD: fields). V: fields declare the variables
*=====================================================================

* Store consumption in year T by generation G.

$REPORT:
  V:C(G,H,T)$CREF(G,H,T)	 I:PC(T)		PROD:U(G,H)

*=====================================================================
* $DEMAND blocks represent demands (D: fields) and endowments (E: fields) 
* of the consumers in the model. Endowments may be associated with 
* endogenous auxiliary variables (R: fields)
*=====================================================================

* Each generation demands "consumption utility" and is endowed with 
* an amount of the consumption good in each period. Bequests enter as a 
* demand for the bequest transfer good representing a desire to give 
* bequests in the last period of the life cycle and a corresponding 
* endowments of this good refelecting receipts of bequests. In addition,
* generations alive in the initial period are endowed with domestic and 
* foreign assets. To terminate the model generations alive
* in the terminal period are required to leave an amount of assets and 
* are also endowed with goods for consumption in the post-terminal periods.

$DEMAND:RA(G,H)  s:ESUBB(G,H)
  D:PU(G,H)		Q:MREF(G,H)
  D:PB(G,H)		Q:PVBQ(G,H)
  E:PB(GG,H)		Q:BEQUEST(GG,G,H)
  E:PC(T)		Q:EREF(G,H,T)
  E:PC(TFIRST)		Q:DASSET(G,H)
  E:PFX			Q:FASSET(G,H)
  E:PCT(G,H,A)		Q:CREF_T(G,H,A)		R:CT(G,H,A)
  E:PFX$ATGEN(G)	Q:1			R:AT(G,H)	

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

$CONSTRAINT:AT(G,H)$ATGEN(G)
    U(G,H) - U(G-1,H) =E= 0;

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

$CONSTRAINT:CT(G,H,A)$CREF_T(G,H,A)
  SUM(TLAST, PC(TLAST)) =E= PCT(G,H,A)*(1+RBAR)**(ORD(A)-1);

*=====================================================================
* End model declaration and shift compiler back to GAMS:
*=====================================================================

$OFFTEXT
$SYSINCLUDE MPSGESET EXCHANGE

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

X.L(T)		= 0;
M.L(T)		= QREF(T)*CAD0;
PC.L(T)		= PREF(T);
PCT.L(G,H,A)	= PREF_T(A);
CT.L(G,H,A)	= 1$CREF_T(G,H,A);
AT.L(G,H)	= SUM(T, CREF(G,H,T)*PREF(T)) 
		- SUM(T, (EREF(G,H,T)+BREF(G,H,T))*PREF(T))$ATGEN(G);
AT.LO(G,H)	= -INF;

* Numeraire:

PC.FX(TFIRST)	= 1;

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

EXCHANGE.WORKSPACE=20;
EXCHANGE.ITERLIM=0;
$INCLUDE EXCHANGE.GEN
SOLVE EXCHANGE USING MCP;
DISPLAY "Benchmark tolerance CHK:",EXCHANGE.OBJVAL;

* Parameters for reporting results from counterfactual experiment:

PARAMETER
  WCHANGE	Welfare change (% EV by year of birth),
  CADEF		Current account deficit (% of benchmark consumption);

CADEF(T,"BMK")	
= 100 * SUM((G,H), (C.L(G,H,T)-EREF(G,H,T)))/SUM((G,H),C.L(G,H,T));

*=====================================================================
* Run counterfactual:
*=====================================================================

* Change the exchange rate as reflected in the price of imports and 
* exports. Initial holdings of foreign assets are fixed so this 
* represents a sudden fall in the price of foreign assets 
* which helps the poor who have negative assets, but hurts the rich.

PM(T)$(YEAR(T) GT 10) = 1.25;
PX(T)$(YEAR(T) GT 10) = 1.25;

OPTION SYSOUT=ON;
EXCHANGE.ITERLIM=10000;
$INCLUDE EXCHANGE.GEN
SOLVE EXCHANGE USING MCP;

* Compute welfare changes and current account deficit:

WCHANGE(G,H)		= 100 * (U.L(G,H) - 1);
CADEF(T,"bequest")	= 100 * SUM((G,H), (C.L(G,H,T)-EREF(G,H,T)))
			/SUM((G,H),C.L(G,H,T));

*=====================================================================
* Display statements
*=====================================================================

DISPLAY YEAR,AGE,PREF,QREF,ATGEN,BQV,BQR,BQN,BEQUEST,PVBQ,ESUBB,CAD0;
DISPLAY EREF,CREF,CREF_T,MREF,ASSETS,MA,ASSETH,DEBT,DASSET,FASSET;
DISPLAY WCHANGE,CADEF;

*=====================================================================
* Graphics:
*=====================================================================

$IF NOT EXIST '%gams.sysdir%\wgnupl32.exe' $exit

*	Reinstall benchmark endowments for the plot:

ENDOW(A,"WEALTHY") = EXP(4.47 + 0.033*AGE(A) - 0.00067 * AGE(A)**2);
ENDOW(A,"PATIENT") = EXP(4.47 + 0.033*AGE(A) - 0.00067 * AGE(A)**2);
ENDOW(A,"impatient") = SQRT(ENDOW(A,"wealthy"));
ENDOW(A,H) = NUMBER(H)*ENDOW(A,H) 
	/ SUM((AA,HH), (1+GAMMA)**(1-ORD(AA))*NUMBER(HH)*ENDOW(AA,HH));

* Convert to per-capita:

ENDOW(A,H) = ENDOW(A,H) / NUMBER(H);
CONSUM(A,H) = CONSUM(A,H) / NUMBER(H);
ASSETS(A,H) = ASSETS(A,H) / NUMBER(H);
ASSETS(A,H) = 100 * ASSETS(A,H) / CONSUM("0",H);
DISPLAY ASSETS;

$SETGLOBAL domain A
$SETGLOBAL labels ALABELS
$LIBINCLUDE PLOT ENDOW
$LIBINCLUDE PLOT CONSUM
$SETGLOBAL gp_opt1 "set xlabel 'Age in life-cycle (beginning of period)'"
$SETGLOBAL gp_opt2 "set ylabel '% of base year consumption'"
$SETGLOBAL gp_opt3 "set yrange [-20:70]"
$LIBINCLUDE PLOT ASSETS

$SETGLOBAL gp_opt3 

$SETGLOBAL domain g
$SETGLOBAL labels glabels
$SETGLOBAL gp_opt1 "set xlabel 'Generation'"
$SETGLOBAL gp_opt2 "set ylabel 'Hicksian equivalent variation (%)'"
$LIBINCLUDE PLOT WCHANGE
$SETGLOBAL gp_opt2 

$SETGLOBAL domain t
$SETGLOBAL labels tlabels
$SETGLOBAL gp_opt1 "set xlabel 'Year'"
$LIBINCLUDE PLOT CADEF