The Perl Toolchain Summit needs more sponsors. If your company depends on Perl, please support this very important event.

NAME

Statistics::SDT - Signal detection theory (SDT) measures of sensitivity and bias in frequency data

VERSION

This is documentation for Version 0.07 of Statistics::SDT.

SYNOPSIS

 use Statistics::SDT 0.07;
 use feature qw{say};

 my $sdt = Statistics::SDT->new(
  correction => 1,
  precision_s => 2,
 );

 $sdt->init(
  hits => 50,
  signal_trials => 50, # or misses => 0,
  false_alarms => 17,
  noise_trials => 25, # or correct_rejections => 8
 ); # or init these into 'new' &/or pass their values as 2nd arg. hashrefs in calling the following methods

 say 'Hit rate = ',            $sdt->rate('hr'); # or 'far', 'mr', 'crr'
 say 'Sensitivity d = ',       $sdt->sens('d');  # or 'Ad', 'A'
 say 'Bias beta = ',           $sdt->bias('b');  # or 'log', 'c', 'griers'
 say 'Criterion k = ',         $sdt->crit();            # -0.47
 say 'Hit rate by d & c = ',  $sdt->dc2hr();            # .99
 say 'FAR by d & c = ',       $sdt->dc2far();           # .68
 say 'LogBeta by d & c = ',   $sdt->dc2logbeta();       # -2.60

 # m-AFC:
 say 'd_fc = ', $sdt->sens('f' => {hr => .866, alternatives => 3, correction => 0, method => 'alexander'})); # or 'smith'

DESCRIPTION

This module implements algorithms for Signal Detection Theory (SDT) measures of sensitivity and response-bias, e.g., d', A', c, as based on frequency data. These are largely as defined in Stanislav & Todorov (1999; see REFERENCES), as well as other sources including Alexander (2006). Output from this module per method are tested for agreement with example data and calculation from those sources.

For any particular analysis, (1) create the SDT object with new, (2) initialise the object with relevant data with init, and then (3) call the measure wanted.

For those measures that involve Z-score transformation of probabilities, this is made via the ndtri function in Math::Cephes, and this is denoted in the equations below by the Greek letter phi^-1 (for inverse phi). The function can be directly accessed by the present module as "Statistics::SDT::ndtri()". The complementary ndtr for converting Z-scores into probabilities is also used/available in this way.

Most methods assume a yes/no rather than m-AFC design. For m-AFC designs, only sensitivity measures are offered/relevant, approximated from the hit-rate for the given number of hits and signal trials, which are assumed to indicate all trials.

PARAMETERS

The following named parameters need to be given as a hash or hash-reference: either to the new constructor method, init, or into each measure-function. To calculate the hit-rate, provide the (i) count of hits and signal-trials, (ii) the counts of hits and misses, or (iii) the count of signal-trials and misses. To calculate the false-alarm-rate, provide (i) the count of false-alarms and noise-trials, (ii) the count of false-alarms and correct-rejections, or (iii) the count of noise-trials and correct-rejections. Or supply the hit-rate and false-alarm-rate. Or see dc2hr and dc2far to get back the rates via given/calculated sensitivity and criterion. If a method depends on these counts/rates and they are not provided, or what it depends on cannot be calculated from the provided values, the methods will generally return an empty string.

hits => POSINT

The number of hits.

false_alarms => POSINT

The number of false alarms.

signal_trials => POSINT

The number of signal trials. The hit-rate is derived by dividing the number of hits by the number of signal trials.

noise_trials => POSINT

The number of noise trials. The false-alarm-rate is derived by dividing the number of false-alarms by the number of noise trials.

hr => FLOAT [0 .. 1]

The hit-rate -- instead of passing the number of hits and signal trials, give the hit-rate directly.

far => FLOAT [0 .. 1]

The false-alarm-rate -- instead of passing the number of false alarms and noise trials, give the false-alarm-rate directly.

alternatives => POSINT

The number of response alternatives; when estimating for a forced-choice rather than yes/no design. If defined (and greater than or equal to 2), then, by default, Smith's (1982) estimate of d' is used; otherwise Alexander's.

correction => POSINT [0, 1, 2, undef]

Indicate whether or not to perform a correction on the number of hits and false-alarms when the hit-rate or false-alarm-rate equals 0 or 1 (due, e.g., to strong inducements against false-alarms, or easy discrimination between signals and noise). This is relevant to all functions that make use of the inverse phi function (all except aprime option with sens, and the griers option with bias). As ndtri must die with an error if given 0 or 1, there is a default correction.

If correction = 0, no correction is performed to calculation of rates. This should only be used when (1) using the parametric measures and the rates will never be at the extremes of 0 and 1; or (2) using only the nonparametric measures (aprime and griers).

If correction = 1 (default), extreme rates (of 0 and 1) are corrected: 0 is replaced with 0.5 / n; 1 is replaced with (n - 0.5) / n, where n = number of signal or noise trials. This is the most common method of handling extreme rates (Stanislav and Todorov, 1999) but it might bias sensitivity measures and not be as satisfactory as the loglinear transformation applied to all hits and false-alarms, as follows.

If correction > 1, the loglinear transformation is applied to all values: 0.5 is added to both the number of hits and false-alarms, and 1 is added to the number of signal and noise trials.

If correction is undefined: To avoid errors thrown by the ndtri function, any values that equal 1 or 0 will be corrected as if it equals 1.

precision_s => POSINT

Precision (n decimal places) of any of the statistics. Default = 0 to have all possible decimals returned.

method => STR ['smith', 'alexander']

Method for estimating d' for forced-choice design. Default is smith; otherwise alexander.

SUBROUTINES/METHODS

new

Creates the class object that holds the values of the parameters, as above, and accesses the following methods (without having to pass the all values again).

As well as storing parameter values, the class-object returned by new will stores hr, the hit-rate, and far, the false-alarm-rate. These can be specifically given as named arguments to the method (ensuring that they do not equal zero or 1 in order to avoid errors thrown by the inverse-phi function). Otherwise, calculation of the hit-rate and false-alarm-rate from the given number of signal/noise trials, and hits/misses (etc., as defined above) corrects for this limitation; i.e., correction can only be done by supplying the relevant counts, not just the rate - see the notes on the |<correction|Statistics::SDT/correction> option.

init

 $sdt->init(...)

Instead of passing the number of hits, signal-trials, etc., with every call to the measure-functions, or creating a new class object for every set of data, initialise the class object with the values for parameters, key => value pairs, as defined above. This method is called by new (if the parameter values are passed to it). The hit-rates and false-alarm rates are always calculated anew from the hits and signal trials, and the false-alarms and noise trials, respectively; unless a value for one or the other, or both (as hr and far) is passed in a call to init.

Each init replaces the values only of those attributes passed to it - any values set in previous inits are retained for those attributes that are not set in a call to init. To reset everything, first use clear

The method also stores any given values for alternatives, correction, precision_s and method.

clear

 $sdt->clear()

Sets all attributes to undef: hits, false_alarms, signal_trials, noise_trials, hr, far, alternatives, correction, and method.

rate

 $sdt->rate('hr|far|mr|crr') # return the indicated rate
 $sdt->rate(hr => PROB, far => PROB, mr => PROB, crr => PROB) # set 1 or more rate => probability pairs
 $sdt->rate('hr' => {signal_trials => INT, hits => INT}) # or misses instead of hits
 $sdt->rate('far' => {noise_trials => INT, false_alarms => INT}) # or correct_rejections instead of false_alarms
 $sdt->rate('mr' => {signal_trials => INT, misses => INT})  # or hits instead of misses
 $sdt->rate('crr' => {noise_trials => INT, correct_rejections => INT})  # or false_alarms instead of correct_rejections

Generic method to get or set the conditional response proportions:

  HR (hit-rate) = N(Rs|Ss) / N(Ss)

  FAR (false-alarm-rate) = N(Rs|Sn) / N(Sn)

  MR (miss-rate) = N(Rn|Ss) / N(Ss)

  CRR (correct-rejection-rate) = N(Rn|Sn) / N(Sn)

where S = stimulus (trial-type, expected response), R = response, subscript s indicates signal-plus-noise trials and n indicates noise-only trials.

To get a rate, these string abbreviations do the trick; the method only checks the first letter, so any passable abbreviation will do, case-insensitively. The rate is returned to the precision indicated by the optional precision_s argument (given here or in init).

To set a rate for use by other methods (such as for sensitivity or bias), either give the actual proportion as key => value pairs, e.g., HR => .7, or a hashref giving sufficient info to calculate the rate (if this has not already been paased to init).

Also performs any required or requested corrections, depending on value of correction (given here or in init).

Unless the values of the rates are directly given, then they will be calculated from the presently passed counts and trial-numbers, or whatever has been cached of these values. For the hit-rate, there must be a value for hits and signal_trials, and for the false-alarm-rate, there must be a value for false_alarms and noise_trials. If these values are not passed, they will be taken from any prior value, unless this has been cleared or never existed - in which case expect a croak.

zrate

 $z = $sdt->zrate('hr'); # or 'far', 'mr', 'crr'

Returns the Z-transformation of the given rate using the inverse-phi function (ndtri from Math::Cephes).

dc2hr

 $sdt->dc2hr() # assume d' and c can be calculated from already inited param values
 $sdt->dc2hr(d => FLOAT, c => FLOAT)

Returns the hit-rate estimated from given values of sensitivity d' and bias c, viz.:

  HR = φ(d’ / 2 – c)

dc2far

 $sdt->dc2far() # assume d' and c can be calculated from already inited param values
 $sdt->dc2far(d => FLOAT, c => FLOAT)

Returns the false-alarm-rate estimated from given values of sensitivity d' and bias c, viz.:

  FAR = φ(–d’ / 2 – c)

sens

 $s = $sdt->sens('dprime'); # or 'aprime', 'adprime'
 $s = $sdt->sens('dprime', { signal_trials => POSINT }); # set args, optionally
 $s = $sdt->sens('d_a', { stdev_n => POS_FLOAT, stdev_s => POS_FLOAT }); # required args

Alias: sensitivity

Returns one of the sensitivity measures, as indicated by the first argument string, optionally updating any of the measure variables and options with a subsequent hashref. The measures are as follows, accessed by giving the name (or at least its first two letters) as the first argument.

dprime

Returns the index of standard deviation units of sensitivity, or discrimination, d' (d prime). Assuming equal variances for the noise and signal+noise distributions, this is estimated by subtracting the z-score units of the false-alarm rate (or 1 - the correct-rejection-rate) from the z-score units of the hit rate:

  d’ = φ–1(HR) – φ–1(FAR)
      = φ–1(HR) + φ–1(CR)

Larger positive values indicate greater sensitivity. If both HR and FAR are either 0 or 1, then sensitivity returns 0, indicating no sensitivity; the signal cannot be discriminated from noise. Values less than 0 (more false-alarms than hits) indicate a lack of sensitivity that might result from a consistent reponse-confusion or -inhibition.

For estimating dprime for m-AFC tasks, the forced-choice design, there are two methods, as set by the method parameter in init or sensitivity. The default method is smith, the method cited by Stanislav & Todorov (1999); and there is the more generally applicable alexander method.

The present interface to these methods is limited in that they are given, for proportion-correct, the hit-rate as for the yes/no design: as the count of hits divided by number of signal trials. Rather than give these methods a value for hr, the init method could be used setting the number of hit and signal trials as appropriate, and setting the number of false alarms and noise trials to zero. This is not optimal (intuitive) as the proportion correct is something else in the yes/no design (see pcorrect), but simply works by present limitations). So, in what follows, for HR, one should really read proportion-correct.

Smith (1982) method: satisfies "the 2% bound for all M [alternatives] and all percentiles and, except for M = 3 or 4, satisfies a 1% error bound" (p. 95). The specific algorithm used depends on number of alternatives:

Smith's d* applies when n alternatives < 12:

  d’ = Kln( [ (n – 1)HR ] / [ 1 – HR ] )

where

    K = .86 – .085 * ln(n – 1).

Smith's d** applies when n >= 12:

    d’ = (A + B)φ–1(HR)

where

    A = (–4 + sqrt[16 + 25 * ln(n – 1)]) / 3

and

    B = sqrt( [ln(n – 1) + 2] / [ln(n – 1) + 1] )

The limits of the method can be noted in that, when n >= 14, d' does not equal zero when the proportion correct (HR) is simply 1/n.

Alexander (2006/1990) method (which never fails the latter elementary test): "gives values of d' with an error of less than 2% (mostly less than 1%) from those obtained by integration for the range d' = 0 (or 1% correct for n [alternatives] > 1000) to 75% correct and an error of less than 4% up to 95% correct for n up to at least 10000, and slightly greater maximum errors for n = 100000. This approximation is comparable to the accuracy of Elliott's table (0.02 in proportion correct) but can be used for any n." (Elliott's table being that in Swets, 1964, pp. 682-683). The estimation is offered by:

          d’ = [ φ–1(HR) – φ–1(1/n) ] / An

where n is the number of alternatives, and An is estimated by:

          An = 1 - 1 / (1.93 + 4.75 * log10(n) + .63[log10(n)]2)

d_a

Returns estimate of SDT sensitivity for without assuming equal variances, given values of stdev_n for standard deviation of the noise distribution, and stdev_s for standard deviation of the signal-plus-noise distribution.

  d’ = sqrt[ 2 / (1 + b2) ][φ–1(HR) – bφ–1(FAR)]

where

  b = σ(N) / σ(S)

aprime

Returns the nonparametric index of sensitivity, A', a.k.a. Ag (e.g., Pastore & Scheirer, Eq. 6). It makes no assumption about the homogeneity of variances of the underlying distributions, and is the average of the maximum and minimum possible areas under the receiver-operating-characteristic curve (based on one ROC point).

  a’ = [ .5 + d(1 + d) ] / 4j

where, if HR >= FAR, d = (HR - FAR), and j = HR(1 - FAR), otherwise d = (FAR - HR) and j = FAR(1 - HR).

Ranges from 0 to 1. Values greater than 0.5 indicate positive discrimination (1 = perfect performance); a value of 0.5 indicates no sensitivity to the presence of the signal (it cannot be discriminated from noise); and values less than 0.5 indicate negative discrimination (perhaps given consistent response confusion or inhibition).

adprime

Returns Ad', the area under the receiver-operator-characteristic (ROC) curve, estimating the proportion of correct responses for the task as a two-alternative forced-choice task.

  Ad = φ(d’ / sqrt(2))

Ranges between 0 and 1, with a value of 0.5 reflecting no discriminative ability when comparing two stimuli. If both the hit-rate and false-alarm-rate are either 0 or 1, then the returned value of sensitivity is 0.5.

bias

 $b = $sdt->bias('likelihood|loglikelihood|decision|griers') # based on values of the measure variables already inited or otherwise set 
 $b = $sdt->bias('likelihood' => { signal_trials => INT}) # pass to any of the measure variables

Returns an estimate of the SDT decision threshold/response-bias. The particular estimate is named by the first argument string (or at least its first two letters), as below. optionally updating any of the measure variables and options with a subsequent hashref (as given by example for signal_trials).

With a yes response indicating that the decision variable exceeds the criterion, and a no response indicating that the decision variable is less than the criterion, the measures indicate if there is a bias toward the yes response, and so a liberal/low criterion, or a bias toward the no response, and so a conservative/high criterion.

beta, likelihood_bias

Returns the paramteric beta measure of response bias, based on the ratio of the likelihood the decision variable obtains a certain value on signal trials, to the likelihood that it obtains the value on noise trials.

          β = exp( [φ–1(FAR)2 – φ–1(HR)2] / 2 )

Values less than 1 indicate a bias toward the yes response (more hits and FAs than misses and CRs), values greater than 1 indicate a bias toward the no response (more misses and CRs than hits and FAs), and the value of 1 indicates no bias toward yes or no.

log_likelihood_bias

Returns the natural logarithm of the likelihood bias, beta.

          lnβ = [ φ–1(FAR)2 – φ–1(HR)2 ] / 2

Ranges from -1 to +1, with values less than 0 indicating a bias toward the yes response (more hits and FAs than misses and CRs), values greater than 0 indicating a bias toward the no response (more misses and CRs than hits and FAs), and a value of 0 indicating no response bias.

c, distance

Returns the c parametric measure of response bias (Macmillan & Creelman, 1991, Eq. 12), defined as the distance between the criterion and the point where beta = 1 (crossing-point of the noise and signal distributions, with neither response favoured; where signal+noise is as likely as noise-only, and so how different the response criterion is from an unbiased criterion).

          c = –[ φ–1(HR) + φ–1(FAR) ] / 2

Ranges from -1 to +1, with deviations from zero, measured in standard deviation units. Values less than 0 indicate a bias toward the yes response (more hits and FAs than misses and CRs); values greater than 0 indicate a bias toward the no response (more misses and CRs than hits and FAs); and a value of 0 indicates unbiased responding.

griers

Returns Griers B'' nonparametric measure of response bias. Defining a = HR(1 - HR) and b = FAR(1 - FAR) if HR >= FAR, otherwise a = FAR(1 - FAR) and b = HR(1 - HR), then B'' = ( a - b ) / ( a + b ); or, summarily:

          B” = sign(HR – FAR)[ HR(1 – HR) – FAR(1 – FAR) ] / [ HR(1 – HR) + FAR(1 – FAR) ]

Ranges from -1 to +1, with values less than 0 indicating a bias toward the yes response (more hits and FAs than misses and CRs), values greater than 0 indicating a bias toward the no response (more misses and CRs than hits and FAs), and a value of 0 indicating no response bias.

dc2logbeta

 $sdt->dc2logbeta() # assume d' and c can be calculated from already inited param values
 $sdt->dc2logbeta(d => FLOAT, c => FLOAT)

Returns the log-likelihood (beta) bias estimated from given values of sensitivity d' and bias c, viz.:

  lnβ = dc

criterion

 $sdt->criterion() # from FAR or from d' and c from already inited param values
 $sdt->criterion(far => PROPORTION) # from FAR or from d' and c from already inited param values
 $sdt->criterion(d => FLOAT, c => FLOAT)

Alias: crit

Returns the value of the decision criterion (critical output value of the input process) on the basis of either:

(1) the false-alarm-rate:

  xc = –φ–1(FAR)

or (2) both sensitivity d' and bias c as:

  xc = d’ / 2 + c

The method firstly checks if FAR can be calculated from given data or specific argument far, or similarly by d' and c.

REFERENCES

Alexander, J. R. M. (2006). An approximation to d' for n-alternative forced choice. From http://eprints.utas.edu.au/475/.

Lee, M. D. (2008). BayesSDT: Software for Bayesian inference with signal detection theory. Behavior Research Methods, 40, 450-456. doi: 10.3758/BRM.40.2.450

Macmillan, N. A. & Creelman, C. D. (1991). Detection theory: A user's guide. Cambridge, UK: Cambridge University Press.

Pastore, R. E., & Scheirer, C. J. (1974). Signal detection theory: Considerations for general application. Psychological Bulletin, 81, 945-958. doi: 10.1037/h0037357

Smith, J. E. K. (1982). Simple algorithms for M-alternative forced-choice calculations. Perception and Psychophysics, 31, 95-96. doi: 10.3758/BF03206208

Stanislaw, H., & Todorov, N. (1999). Calculation of signal detection theory measures. Behavior Research Methods, Instruments, and Computers, 31, 137-149. doi: 10.3758/bf03207704

Swets, J. A. (1964). Signal detection and recognition by human observers. New York, NY, US: Wiley.

DIAGNOSTICS

Number of hits/false-alarms and signal/noise trials needed to calculate rate

Croaked when using init or rate and the given arguments are insufficient (as indicated) to calculate hit-rate and/or false-alarm-rate.

Uninitialised counts for calculating MR [or CRR]

Croaked if a method depends on calculating the miss-rate (MR) or correct-rejection-rate (CRR) and the necessary counts of signal or noise trials (respectively), or number of misses or correct-rejections (respectively) have not been provided, cannot be inferred, or are not numeric (is_float check). To avoid this error, try to ensure that if there are no trials of these kinds, that their given values are zero and not just empty.

DEPENDENCIES

List::AllUtils : all and any methods

Math::Cephes : ndtr (phi), ndtri (inverse phi) and log10 functions

String::Numeric : is_int and is_float methods

String::Util : hascontent and nocontent methods

SEE ALSO

Statistics::Contingency : Measure of accuracy for data in the form of hits, misses, correct rejections and false alarms.

Statistics::ROC : Receiver-operator characteristic curves.

BUGS AND LIMITATIONS

Expects counts, not raw observations, let alone ratings, limiting the measures implemented.

Most methods assume yes/no design, not m-AFC. The interface for the two m-AFC methods is not optimal - HR in their case stands for "percent correct" and is calculated as N(hits) / N(signal trials). This might have to change but fits with present limitations.

Smith (1982) method: his term "N^-1(Pc)" is defined as "the unit normal deviate corresponding to the right tail area P" (p. 95) rather than the left. This suggests using, for inverse-phi, ndtri(1 - Pc) rather than ndtri(Pc), which satisfies his example that "N^-1(.1586) = +1", which is equal to ndtri(1 - .1586), not ndtri(.1586). But to use ndtri(1 - Pc) would produce sensitivity in the wrong direction, even negative (smaller probabilities, larger z-scores); e.g., d' = -.37 when Pc = .96 and m = 13. So ndtri(Pc) (or, rather HR, see above) is used.

SUPPORT

You can find documentation for this module with the perldoc command.

    perldoc Statistics::SDT

You can also look for information at:

AUTHOR

Roderick Garton, <rgarton at cpan.org>

LICENSE AND COPYRIGHT

This program is free software. It may be used, redistributed and/or modified under the same terms as Perl-5.6.1 (or later) (see http://www.perl.com/perl/misc/Artistic.html).

Disclaimer

To the maximum extent permitted by applicable law, the author of this module disclaims all warranties, either express or implied, including but not limited to implied warranties of merchantability and fitness for a particular purpose, with regard to the software and the accompanying documentation.