پرونده:CAPM-SML.svg

Page contents not supported in other languages.
از ویکی‌پدیا، دانشنامهٔ آزاد

پروندهٔ اصلی(پروندهٔ اس‌وی‌جی، با ابعاد ۷۲۳ × ۵۷۸ پیکسل، اندازهٔ پرونده: ۱۱ کیلوبایت)

توضیح dow jones index and it's 30 stocks: the CAPM and the security market line (purple). the grey line is the linear model. mean yield is assumed to be 2.9%
تاریخ
منبع data by quote.yahoo, atomatically retrieved with GNU R, see graph source below
پدیدآور Thomas Steiner
اجازه‌نامه
(استفادهٔ مجدد از این پرونده)
Thomas Steiner put it under the CC-by-SA 2.5.
w:fa:کرییتیو کامنز
انتساب انتشار مشابه
این پرونده با اجازه‌نامهٔ کریتیو کامانز Attribution-Share Alike 2.5 عمومی منتشر شده است.
شما اجازه دارید:
  • برای به اشتراک گذاشتن – برای کپی، توزیع و انتقال اثر
  • تلفیق کردن – برای انطباق اثر
تحت شرایط زیر:
  • انتساب – شما باید اعتبار مربوطه را به دست آورید، پیوندی به مجوز ارائه دهید و نشان دهید که آیا تغییرات ایجاد شده‌اند یا خیر. شما ممکن است این کار را به هر روش منطقی انجام دهید، اما نه به هر شیوه‌ای که پیشنهاد می‌کند که مجوزدهنده از شما یا استفاده‌تان حمایت کند.
  • انتشار مشابه – اگر این اثر را تلفیق یا تبدیل می‌کنید، یا بر پایه‌ آن اثری دیگر خلق می‌کنید، می‌‌بایست مشارکت‌های خود را تحت مجوز یکسان یا مشابه با ا اصل آن توزیع کنید.

R source:

library(tseries)
library(RSvgDevice)

quote<-function(inst, nDs) {
  if(!inherits(try(open(url("http://quote.yahoo.com")), silent = TRUE), "try-error")) {
    start <- strftime(as.POSIXlt(Sys.time() - nDs*24*3600), format="%Y-%m-%d") 
    end <- strftime(as.POSIXlt(Sys.time()), format = "%Y-%m-%d") 
    x <- get.hist.quote(instrument=inst, start=start, end=end, quote = c("AdjClose"), compression="m",  quiet=T, retclass="zoo")
  }
  return(x)
}

yield=2.9
nDays=1042
comp<-c("^DJI", "AA", "AIG", "AXP", "BA", "C", "CAT", "DD", "DIS", "GE", "GM", "HD", "HON", "HPQ", "IBM", "INTC", "JNJ", "JPM", "KO", "MCD", "MMM", "MO", "MRK", "MSFT", "PFE", "PG", "T", "UTX", "VZ", "WMT", "XOM")

comp.quote<-quote(comp[1],nDays)
from= as.Date(index(comp.quote[1,1]),format="%Y-%m-%d")
to=   as.Date(index(comp.quote[length(comp.quote[,1]),1]),format="%Y-%m-%d")

for (c in 2:length(comp)) {
  comp.quote<-merge(comp.quote,quote(comp[c],nDays))
}

rdt<-12*diff(comp.quote)/comp.quote*100

points=array(NA,dim=c(length(comp),2))
for (p in 1:length(comp)) {
  points[p,1]= cov(rdt[,1],rdt[,p])/var(rdt[,1])
  points[p,2]=mean(rdt[,p])
}

devSVG(file="CAPM-SML.svg", width=10, height=8, bg="transparent", fg="black", onefile=TRUE, xmlHeader=TRUE)

par(lwd=2)
plot(points[2:length(comp),],type="p",col="blue",xlab="beta",ylab="return (in % p.a.)",main="CAPM: Security Market Line",xlim=range(0,points[,1]))
lines(points[1,1],points[1,2],col="red",type="p")
abline(a=yield,b=points[1,2]-yield,col="purple")
text(points[2:length(comp),1],points[2:length(comp),2],comp,pos=3,col="blue")
text(points[1,1],             points[1,2],           comp[1],pos=3,col="red")

lm1<-lm(points[,2]~points[,1])
abline(lm1,col="darkgrey",lwd=1)
 
text(x=par("usr")[2], y=par("usr")[3]+0.5, labels=paste("Dow Jones monthly data from", format.Date(from,"%d %b %Y"), "to", format.Date(to,"%d %b %Y"),""), col="grey",adj=c(1,0) )
grid(lwd=1)

dev.off()
 
این نمودار با کد نامشخص از لحاظ W3C با R ساخته شده است.

عنوان

شرحی یک‌خطی از محتوای این فایل اضافه کنید

آیتم‌هایی که در این پرونده نمایش داده شده‌اند

توصیف‌ها

checksum انگلیسی

d8332e6c26cf2fa1d2b0308dcca9328b675998bb

۱۱٬۴۷۵ بایت

۵۷۸ پیکسل

۷۲۳ پیکسل

تاریخچهٔ پرونده

روی تاریخ/زمان‌ها کلیک کنید تا نسخهٔ مربوط به آن هنگام را ببینید.

تاریخ/زمانبندانگشتیابعادکاربرتوضیح
کنونی‏۸ نوامبر ۲۰۰۶، ساعت ۱۴:۰۸تصویر بندانگشتی از نسخهٔ مورخ ‏۸ نوامبر ۲۰۰۶، ساعت ۱۴:۰۸۷۲۳ در ۵۷۸ (۱۱ کیلوبایت)Thire{{Information| |Description = dow jones index and it's 30 stocks: the CAPM and the security market line (purple). the grey line is the linear model. mean yield is assumed to be 2.9% |Source = data by quote.yahoo, atomatically retrieved with GNU R, see gra

صفحه‌های زیر از این تصویر استفاده می‌کنند:

کاربرد سراسری پرونده

ویکی‌های دیگر زیر از این پرونده استفاده می‌کنند:

فراداده