Finance-Treasury-0.1.2: Obtain Treasury yield curve dataSource codeContentsIndex
Finance.Treasury
Stabilityexperimental
MaintainerSteve lihn <stevelihn@gmail.com>
Contents
Yield curve storage
Yield curve maturity
Fetching yield curve data
Printing yield curve data
Description

Tested with: GHC 6.6.1

Finance.Treasury is a module to obtain yield curve data from Department of Treasury website.

Error reporting is somewhat of a mixed model in this module. More improvement is desired in future releases.

Here is a small complete program illustrating the use of this module:

    module Main where
    import Finance.Treasury
    import qualified Data.Map as M
    import Data.List (sort)
    import Text.Printf
    main = do
        putStrLn "**************************************"
        m <- getYieldCurveThisMonth 
        putStrLn "*** pretty print 10y rates for all dates"
        prettyYieldCurve m (Just "10y")
        --
        d <- getLatestYieldCurve 
        putStrLn "*** pretty print the latest daily yield curve"
        prettyYieldCurve (M.fromList [d]) Nothing
        --
        putStrLn "*** show some yield curves of past year"
        h <- getYieldCurveHist
        prettyYieldCurve (minmax h) (Just "10y")
        mapM_ prt yrs 
        putStrLn "**************************************"
        return ()
        where minmax h = M.fromList [ M.findMin h, M.findMax h ]
              yrs = reverse [ 1992..2007 ]
              prt :: Int -> IO ()
              prt yr = do putStrLn $ "*** show some yield curves of "++(show yr)
                          yc <- getYieldCurveYyyy yr
                          prettyYieldCurve (minmax yc) (Just "10y")
                          return ()

License info: The license is a simple BSD3-style license.

Synopsis
type YieldCurveMap = Map Day DailyYieldCurve
type DailyYieldCurve = Map String Float
type DailyYieldCurveList = [(String, Float)]
yieldCurveHash :: Map String String
getLatestYieldCurve :: IO (Day, DailyYieldCurve)
getYieldCurveThisMonth :: IO YieldCurveMap
getYieldCurveHist :: IO YieldCurveMap
getYieldCurveYyyy :: Int -> IO YieldCurveMap
prettyYieldCurve :: YieldCurveMap -> Maybe String -> IO ()
Yield curve storage
type YieldCurveMap = Map Day DailyYieldCurveSource
a Map storing all the daily yield curves
type DailyYieldCurve = Map String FloatSource
a Map storing the assoc array of maturity to interest rate (in percent)
type DailyYieldCurveList = [(String, Float)]Source
a List storing the tuple of maturity and interest rate (in percent)
Yield curve maturity
yieldCurveHash :: Map String StringSource
translates maturity from XML names to abbreviations. E.g. BC_1MONTH becomes 1m. List of all maturities: 1m 3m 6m 1y 2y 3y 5y 7y 10y 20y 30y. However, 30y data may be lacking for some years when the bond was not in circulation.
Fetching yield curve data
getLatestYieldCurve :: IO (Day, DailyYieldCurve)Source
fetch the latest daily yield curve from the monthly data.
getYieldCurveThisMonth :: IO YieldCurveMapSource
fetch the latest monthly data. There is no reason to fail, so it is an error if there is no XML returned
getYieldCurveHist :: IO YieldCurveMapSource
fetch the latest yearly data (excluding current month). There is no reason to fail, so it is an error if there is no XML returned
getYieldCurveYyyy :: Int -> IO YieldCurveMapSource
fetch the historical yearly data (excluding current year). If YYYY is not in range (since 1992), this call may fail. Otherwise, there is no reason to fail.
Printing yield curve data
prettyYieldCurve :: YieldCurveMap -> Maybe String -> IO ()Source
print yield curve data in a csv format for storage or testing.
Produced by Haddock version 2.3.0