![]() |
![]() |
"Black-Scholes" in Multiple Languages January 2008: After studying the literature (something many of the famous academics themselves obviously not have done properly) it is obvious that we option traders never have used the Black-Scholes-Merton formula in practice.( see also article in Frobes ) Only if you use close to continuous time delta hedging to remove close to all the risk all the time you are actually using the Black-Scholes (or the Black-Scholes-Merton) version of the option formula. The only problem this is impossible in practice. If you remove most risk by hedging options with options, get immune for blow up risk by the way you construct your option portfolio then you are using the traders formula/method that was discovered before Black-Scholes-Merton by a series of traders and researchers, the first contribution form Bachelier 1900 and the last by Thorp 1969, so this is why we think it should be called the Bachelier-Thorp formula. In practice you can remove risk with discrete delta hedging (known long before Black-Scholes and Merton), but you can not remove enough risk to argue for risk-neutral valuation (and this is the main argument of Black-Scholes-Merton). See Chapter 2 in my book Derivatives Models on Models for a detailed discussion on how to hedge options in practice.
![]() ![]() ![]() ![]() ![]()
(in that case try to use the same symbols and the setup as below)
![]()
In the different implementations below we will use the symbols:
S= Stock price X=Strike price T=Years to maturity r= Risk-free rate v=Volatility
Black-Scholes Directly
in a Excel Sheet If you are afraid of programing languages you can start with doing Black-Scholes directly in an Excel sheet, just type in what you see below. If you are using the Norwegian or French version of Excel you have to do some translation yourself:
![]()
Are you too lazy to type in what you see above? Okay download me here
Black-Scholes in Visual Basic By Espen Gaarder Haug Visual Basic: easy to program but quite slow! '// The Black and Scholes
(1973) Stock option formula '// The cumulative normal
distribution function
Black-Scholes in By Espen Gaarder Haug C++: a bit harder than most other languages but very fast and powerful. After my opinion the Rolls Royce computer language for mathematical models where you need speed (for closed form solutions like Blacks-Scholes you are naturally doing fine in almost any language, but when it comes to large scale Monte Carlo C++ is really a plus). #ifndef Pi // The Black and Scholes
(1973) Stock option formula
// The cumulative normal
distribution function double L, K, w ; double const a1 = 0.31938153, a2 = -0.356563782,
a3 = 1.781477937; L = fabs(X); if (X < 0 ){
Black-Scholes in
JAVA By Espen Gaarder Haug Easy to program, can be used to build JAVA applets or large standalone systems. Much faster than Java Script and VBA but still slower than C/C++
// The Black and Scholes (1973) Stock option formula public double
BlackScholes(char CallPutFlag, double S, double X, double T, double r, double v) // The cumulative normal
distribution function L = Math.abs(X); if (X < 0.0)
Check also out Wenhua Wang excellent Java Option Pricer of first edtion of my book!
Black-Scholes in Java Script By Espen Gaarder Haug (thanks to Kurt Hess at University of Waikato for finding a bug in my code) Easy to program, can be used directly on the web, but quite slow! /* The Black and Scholes (1973) Stock option formula */ function BlackScholes(PutCallFlag, S, X, T, r, v) { var d1, d2;
} /* The cummulative Normal distribution function: */ function CND(x){ var a1, a2, a3, a4 ,a5, k ; a1 = 0.31938153, a2 =-0.356563782, a3 = 1.781477937, a4= -1.821255978 , a5= 1.330274429; if(x<0.0) }
By Jerome V. Braun Perl is the "Swiss Army chainsaw" of languages that naturally also can be used for Black-Scholes: =head2 BlackScholes Routine to implement the Black and Scholes (1973) option pricing formula. # usage Here C<$call_put_flag> is either 'c' or 'p' for a call or put respectively, =cut sub BlackScholes { # calculate some auxiliary
values if ($call_put_flag
eq 'c') { } =head2 CND Approximate the cumulative
normal distribution. That is, the value # usage =cut sub CND { # the percentile under consideration my $Pi = 3.141592653589793238; # Taylor series coefficients # use symmetry to perform
the calculation to the right of 0 my $k = 1/( 1 + 0.2316419*$L); my $CND = 1 - 1/(2*$Pi)**0.5
* exp(-$L**2/2) # then return the appropriate
value }
By Espen Gaarder Haug Easy to program, nice for testing and understanding option models, but quite slow. >with(stats); The cummulative Normal
distribution function: The Balck-Scholes (1973)
stock put option formula.
By Espen Gaarder Haug Easy to program, nice for testing and understanding option models. Mathematica 3.0 was quite slow, but Mathematica 4.0 is pretty fast (Mathematica 4.0 on a 266MHz Power Mac G3 beat MATLAB 5.2 on a 300MHz Pentium II system by an average factor of 4.3. MacWorld 10-99). What will then happen if you put Mathematica 4.0 on a Mac G4, oh my God. (thanks to Wolfram and Steve Jobs life is worth living). The cummulative Normal distribution function: cnd[z_] := (1 + Erf[z/Sqrt[2]])/2; The Balck-Scholes (1973) stock option formula: d1[S_,X_,T_,r_,v_]=(Log[S/X]+(r+v*v/2)*T)/(v*Sqrt[T]); d2[S_,X_,T_,r_,v_]= (Log[S/X]+(r-v*v/2)*T)/(v*Sqrt[T]); BlackScholesCall[S_,X_,T_,r_,v_]= BlackScholesPut[S_,X_,T_,r_,v_]=
By Espen Gaarder Haug If you have a background from Engineering you probably know Matlab. Easy to program, nice for proto modelling, quite fast but still slow compared with JAVA and C/C++. (The code below should be saved as a Matlab M file): %Black and Scholes in Matlab function BlackScholes(CP,S,X,T,r,v) d1=(log(S/X)+(r+v^2/2)*T)/(v*sqrt(T));
Black-Scholes in S-PLUS By Trygve Nilsen, University of Bergen Norway and Gene D. Felber, Talus Solutions Inc S-Plus is the favorite tool for many people working with mathematical statistics. S-Plus is also a great tool for modeling financial derivatives . The code below will also run under the free software R. call.value <-
function(S,X,t,r,v) Important: S-PLUS has a built-in internal functions for "T" and "call". Assigning a value to these in a function creates a conflict and the formula will return an incorrect value.
By Goran Gasparovic, The Johns Hopkins University, Baltimore, Maryland (U.S.A.) IDL; the Interactive Data Language (available from www.rsinc.com, very expensive but useful software). The basic routines are bs2 and cnd2. However, most IDL routines are made so they can handle whole arrays of data at once, so routines bs and cnd are extensions to include that features. They first check whether input variable is a number or array (either strike price, or time) and then react correspondingly, using basic routines to preform calculation. pro bs,c,p,s,x,r,t,v ; c=call price ; p=put price ; s=strike price ; r=interest rate ; t=time in years ; v=volatility x1=double(x) t1=double(t) ss=0 if ((size(x))(0) eq 1) then begin ss=(size(x))(1) t1=dblarr(ss)+t end if ((size(t))(0) eq 1) then begin ss=(size(t))(1) x1=dblarr(ss)+x end if ss eq 0 then begin bs2,c,p,s,x1,r,t1,v endif else begin c=dblarr(ss) p=dblarr(ss) for i=0,ss-1 do begin bs2,c1,p1,s,x1(i),r,t1(i),v c(i)=c1 p(i)=p1 end endelse end pro bs2,c,p,s,x,r,t,v d1 = (alog(s/x) + (r+v^2/2.d0)*t) / (v*sqrt(t)) d2 = d1-v*sqrt(t) c = s*cnd(d1) - x*exp(-r*t)*cnd(d2) p = x*exp(-r*t)*cnd(-d2) - s*cnd(-d1) end function cnd2,x a1 = double(0.31938153) a2 = double(-0.356563782) a3 = double(1.781477937) a4 = double(-1.821255978) a5 = double(1.330274429) l=abs(double(x)) k=1.0 / (1.0 + 0.2316419 * L) w = 1.0 - 1.0 / sqrt(2 * !dPi) * exp(-L *L / 2) * $ (a1*K + a2*K^2 + a3*K^3 + $ a4*K^4 + a5*K^5) if (x lt 0) then w = 1.d0 - w return,w end function cnd,x if ((size(x))(0) eq 0) then begin return,cnd2(x) endif $ else begin s=(size(x))(1) r=dblarr(s) for i=0,s-1 do r(i)=cnd2(x(i)) return,r endelse end
To test out how this code works go to Xavier's php option calculator.
Black-Scholes in Haskell By Karl M. Syring from Germany {- The Black and Scholes (1973) Stock option formula in Haskell. Haskell a polymorphically typed, lazy, purely functional Black-Scholes in Icon By Bill Trost Icon developed by the University of Arizona procedure BlackSholes(CallPutFlag, S, X, T, r, v) d1 := (log(S/X) + (r + v * v / 2.) * T) / (v * sqrt(T)) d2 := d1 - v * sqrt(T) if CallPutFlag == "c" then return S * CND(d1) - X * exp(-r * T) * CND(d2) return X * exp(-r * T) * CND(-d2) - S * CND(-d1) end procedure CND(X) a := [0.31938153, -0.356563782, 1.781477937, -1.821255978, 1.330274429] L := abs(X) K := 1 / (1 + 0.2316419 * L) w := 1.0 - 1.0 / sqrt(2.*&pi) * exp(-L * L / 2.) * (a[1] * K + a[2] *
'From Squeak2.8 of 13 June 2000 [latest update: #2359] on 10 June 2001 at 7:40:05 pm'! Object subclass: #BlackScholes "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BlackScholes class !BlackScholes class methodsFor: 'computing' stamp: 'WRT 6/10/2001 19:39'! isCall: isCall S: s X: x T: t r: r v: v
!BlackScholes class methodsFor: 'private' stamp: 'WRT 6/10/2001 16:53'! CND: x
By Espen Gaarder Haug Very easy to program, with the push of a button the code can be compiled to Pc or Mac. Everything naturally looks ugly on a PC (even the machine), the result on a Mac Carbon X is just amazing! fast and fancy! Even better you can easily port your VBA code into a blistering fast and fancy application. Simple Example: Black-Scholes in Carbon (For Mac X freeks only) Download here First define a constant PI (under Constants) Pi=3.14159265358979 Function GBlackScholes(CallPutFlag as string, S as double, X as double, T as double,
Black-Scholes in
Don't worry we will give you some Black-Scholes REBOL code so you can survive judgment day. REBOL is an interesting and expressive programming language well
suited for internet and cross-platform use. REBOL Home Distributed Network
Applications for the X Internet. Purpose: {Provide a Rebol function for computing the Black-Scholes (1973) formula for determining an European style Option Price.} cum-normal-dist: func [ set [a a1 a2 a3 a4 a5] [0.2316419 0.31938153 (- 0.356563782) 1.781477937
(- 1.821255978) 1.330274429]
black-scholes: func [ either (not put) [
Here is the implementation of Black-Scholes in O'Caml language. This is a very powerful and extremely fast language. It's a programmers dream language! (* Objective Caml is a fast modern type-inferring functional programming
Thanks for providing all those Black Schole calculations in different --Black Scholes Function: create Function BlackScholes(@CallPutFlag varchar(100), @S float, @X float,
Before becoming a financial engineer I used to be a real engineer, so I naturally implemented BS on my calculator, using the reverse-polish notation (aka RPN). << -> S X r v T 'BlackScholes' STO Note: It computes both call and put values, leaving tagged names on the stack. |
![]() |
Black-Scholes in C# By Robert Derby using System; namespace BlackScholes { /// <summary> /// Summary description for BlackSholes. /// </summary> public class BlackSholes { public BlackSholes() { // // TODO: Add constructor logic here // } /* The Black and Scholes (1973) Stock option formula * C# Implementation * uses the C# Math.PI field rather than a constant as in the C++ implementaion * the value of Pi is 3.14159265358979323846 */ public double BlackScholes(string CallPutFlag, double S, double X, double T, double r, double v) { double d1 = 0.0; double d2 = 0.0; double dBlackScholes = 0.0; d1 = (Math.Log(S / X) + (r + v * v / 2.0) * T) / (v * Math.Sqrt(T)); d2 = d1 - v * Math.Sqrt(T); if (CallPutFlag == "c") { dBlackScholes = S * CND(d1) - X * Math.Exp(-r * T) * CND(d2); } else if (CallPutFlag == "p") { dBlackScholes = X * Math.Exp(-r * T) * CND(-d2) - S * CND(-d1); } return dBlackScholes; } public double CND(double X) { double L = 0.0; double K = 0.0; double dCND = 0.0; const double a1 = 0.31938153; const double a2 = -0.356563782; const double a3 = 1.781477937; const double a4 = -1.821255978; const double a5 = 1.330274429; L = Math.Abs(X); K = 1.0 / (1.0 + 0.2316419 * L); dCND = 1.0 - 1.0 / Math.Sqrt(2 * Convert.ToDouble(Math.PI.ToString())) * Math.Exp(-L * L / 2.0) * (a1 * K + a2 * K * K + a3 * Math.Pow(K, 3.0) + a4 * Math.Pow(K, 4.0) + a5 * Math.Pow(K, 5.0)); if (X < 0) { return 1.0 - dCND; } else { return dCND; } } } }
Black-Scholes in K By Tom Messmore, Germany // Black Scholes European Call & Put in k // Tom Messmore tom.messmore@zurich.com .pi : 3.14159265358979323846 // .pi .cnd: {t:%1+.2316419*_abs x // .cnd[0.5] // cumulative (std.) normal distribution function s:t*.31938153+t*-.356563782+t*1.781477937+t*-1.821255978+1.330274429*t _abs(-x>0)+(%_sqrt 2*.pi)*(_exp -.5*x*x)*s} // Abramowitz & Stegun 26.2.17 (from stat.k) .bsfast: {[x;s;v;t;r;opt] // example call is .bsfast[100.;90;.30;90.%365;.03;0] if[~opt _lin (0 1); : `"bad opt" ] // opt 0=EurCall 1=EurPut if[t < 0.; : `"bad time to expiration"] // t is in years; must be non-negative h:(_log[s%x]+(r+(v*(v%2.)))*t)%(v*t^.5); // for subsequent calcs of Eur Put Pr and Eur Call Pr :[opt;:(-s*.cnd[-h])+(+x*(_exp(-r*t)))*.cnd[((v*t^.5)-h)];:(s*.cnd[h])+(-x*(_exp(-r*t)))*.cnd[h+(-v*t^.5)]]} // Description of k language ![]() Black-Scholes in ColdFusion By Alex For more information on ColdFusion (a web language) go to http://www.macromedia.com <cfscript>
By Donsyah Yudistira I myself am a big fan of Black Scholes Option Pricing Formula. The beauty
of the derivation has encouraged many people, including you and me, to
write it in a few languages as seen in your page. function m=bs(cp,s,x,t,r,v) Black-Scholes in PL/SQL By Fernardo Casteras, Bunos
Aires, Argentina Electrical engineer Fernardo Casteras gives us the Black-Scholes formula
written in PL/SQL. PL/SQL is the programming languague used to write stored
procedures in ORACLE relational databases and front-end tools, a widely
used enviroment in corporations. CREATE OR REPLACE FUNCTION BLACKSCHOLES ( CALLPUTFLAG IN VARCHAR2,
By Lou Odette, MA USA I tested it in Arity Prolog, but it should work in any standard Prolog. % black_scholes(+Type,+Spot,+Strike,+Expiry,+RiskFreeRate,+Volatily,-Price)
By Robert Brown I started with your C version. Once my Lisp code was producing the same (declaim (optimize (debug 0) (safety 0) (speed 3)))
Black-Scholes in Ruby ># by Michael Neumann, Germany# one-to-one translation from Python example # Cumulative normal distribution def cnd(x) a1, a2, a3, a4, a5 = 0.31938153, -0.356563782, 1.781477937, -1.821255978, 1.330274429 l = x.abs k = 1.0 / (1.0 + 0.2316419 * l) w = 1.0 - 1.0 / Math.sqrt(2*Math::PI)*Math.exp(-l*l/2.0) * (a1*k + a2*k*k + a3*(k**3) + a4*(k**4) + a5*(k**5)) w = 1.0 - w if x < 0 return w end def BlackScholes(callPutFlag, s, x, t, r, v) d1 = (Math.log(s/x)+(r+v*v/2.0)*t)/(v*Math.sqrt(t)) d2 = d1-v*Math.sqrt(t) if callPutFlag == 'c' s*cnd(d1)-x*Math.exp(-r*t)*cnd(d2) else x*Math.exp(-r*t)*cnd(-d2)-s*cnd(-d1) end end
By Isaac Gouy module BlackScholes
Black-Scholes in VB.NET By Marco Sturlese, '// The Black and Scholes (1973) Stock option formula Black-Scholes in Postscript Language By Dr. Jose Gomes, %! Black-Scholes in MEL By James D. Polk, MEL; Maya's Embedded Language. Maya is a 3D animation global float $PI;
Black-Scholes on TI-89 calculator By Warren Severin, 1) This has been developed on a TI-89 calculator. It should work on many TI-8x models with minor tweaking. Black-Scholes in J By Eugene McDonell, I wrote an article on Black-Scholes for the British publication Vector, 19.3, January 2003. I have a regular column there called "At Play With J", that deals in things having to do with J, a language developed by the late Ken Iverson and Roger Hui, as a successor to Ken's APL. My article is online at : Here is a way to implement it in J: ***************************************************
Black-Scholes in Mathcad v11 By Stuart Bruff, It's written in Mathcad v11 (although it should work in v6 to v13). There is real equivalent of a text source code, as you just type the equations in, using a palette for such things as the square root operator (although there are keyboard shortcuts for most common operators, such as integrals and derivatives). See also http://www.mathcad.com Black-Scholes in SAS By Fabrice Douglas Rouah, * For SAS Release 6.12 or higher; Black-Scholes in APL By Nick Lobachevsky, APL has the undeserved reputation of being unreadable code. Usually, it has a lot more to do with the program author than the language itself. The code is written in a "dyalect" called Dyalog APL. www.dyalog.com Black-Scholes in Lua By Thomas Munro, -- "Lua is a powerful light-weight programming language designed for Black-Scholes in Fortress By Thomas Munro (* Black-Scholes in AutoIt By Russell Lazarus |
![]() |
AutoIt is a freeware Windows automation language which is particularly adept at manipulation of GUI windows and controls. AutoIt scripts can be 'compiled' with a run-time interpreter that allows users to run on most Windows platforms without requiring software installation. For more information, visit the AutoIt web sit at: http://www.autoitscript.com. ;BlackScholes stock option function Black-Scholes in GNU By Dave Prashant /*
EndFunc ;==>_CND
Black-Scholes in gnuplot By Dave Prashant
# Prashant Dave, Ph.D. [prashant dot dave at alumni dot purdue dot edu] Black-Scholes in F# By Michael de la Maza #light Black-Scholes in Objective-C/iPhone By Paul J. Sholtz Objective-C is the programming language used for iPhones. With this code as inspiration to thet started I hope we will see a lot of great option software fro iPhones. HEADER FILE/DECLARATION: -(double)BlackSholes:(char)CallPutFlag: (double)S: (double)X: (double)T: (double)r: (double)v; -(double)CND:(double)X; IMPLEMENTATION: #ifndef Pi #define Pi 3.141592653589793238462643 #endif -(double)BlackSholes:(char)CallPutFlag: (double)S: (double)X: (double)T: (double)r: (double)v { double d1, d2; d1=(log(S/X)+(r+v*v/2)*T)/(v*sqrt(T)); d2=d1-v*sqrt(T); if(CallPutFlag == 'c') return S *[self CND:d1]-X * exp(-r*T)*[self CND:d2]; if(CallPutFlag == 'p') return X * exp(-r * T) * [self CND:-d2] - S * [self CND:-d1]; // error flag; [NSException raise:@"Call/Put Error" format:@"Option must be either a call or put"]; } -(double)CND:(double)X { double L, K, w ; double const a1 = 0.31938153, a2 = -0.356563782, a3 = 1.781477937; double const a4 = -1.821255978, a5 = 1.330274429; L = fabs(X); K = 1.0 / (1.0 + 0.2316419 * L); w = 1.0 - 1.0 / sqrt(2 * Pi) * exp(-L *L / 2) * (a1 * K + a2 * K *K + a3 * pow(K,3) + a4 * pow(K,4) + a5 * pow(K,5)); if (X < 0 ){ w= 1.0 - w; } return w; } INVOCATION (LOGGING ANSWER TO CONSOLE): (models a call option, equity price 50, strike price 45, time to expiry 1/3 of a year, 8% risk free rate and 30% volatility) char flag = 'p'; double S = 50.0; double X = 45.0; double T = 1./3.; double r = 0.08; double v = 0.3; double option_value = [self BlackSholes:flag :S :X :T :r :v]; NSLog(@"option value: %f",option_value); For a detailed description of the Black-Scholes-Merton formula see: Haug, E. G. and Taleb, N.N. (2008): "Why We Have Never Used the Black-Scholes-Merton formula" Haug, E. G. (2007): "Derivatives Models on Models" Wiley Publishing, see Chapter 2 in particular Black,F. and Scholes, M. (1973): "The Pricing of Options and Corporate Liabilities," Journal of Political Economy, 81, 637-654 Merton, R. C. (1973): "Theory of Rational Option Pricing," Bell Journal of Economics and Management Science, 4, 141-144 For a description of many different option pricing formulas see: Haug, E. G. 2007: The Complete Guide to Option Pricing Formulas, McGraw-Hill New York If you hate computers and computer languages don't give up it's still hope! What about taking Black-Scholes in your head instead? If the option is about at-the-money-forward and it is a short time to maturity then you can use the following approximation: call = put = StockPrice * 0.4 * volatility * Sqrt( Time ) |
![]() |
|
![]() |
|
Copyright Espen Haug 1998- 2009 all rights reserved, Feel free to use the code on this page as long as you clearly refer to the programmers.
|