Data.RandProc
Description
RandProc.hs - a Haskell library for working with random processes in a mathematically rigorous way
(Concepts taken from Random Processes - a Mathematical Approach for Engineers by:
- Robert M. Gray
- Lee D. Davisson
Prentice-Hall Information and System Sciences Series, Thomas Kailath, Series Editor)
$Id: RandProc.hs 31 2011-06-22 13:49:48Z dbanas $
David Banas
12 March 2011
Copyright (c) 2011 by David Banas; All rights reserved World wide.
Revision History:
Date SVN #
- Description
2011-03-13 3
- Data structures stabilized.
isSigma
working under minimal, discrete sample testing. 2011-03-18 4
- Added
isProbMeas
, as well as monadic debugging versions of both it andisSigma
. Added an example probability space representing a fair die. 2011-03-29 7
- Custom intersection functions added and briefly tested.
2011-04-02 8
- Custom union functions added and briefly tested. Solution is crude: it is O(N^2), and requires 2 passes over the sample list every time a join is successful. Perhaps, a pre-sort?
2011-06-06 9
- Attempted fix of
getCompEvent
AddedsmplComp
function, as helper to revisedgetCompEvent
. ChangedPoint
to accept Double. Moved all sample spaces to new file,Main.hs
. Added input sorting torange
. Changed Ranges to be open intervals, in order to allow for complementing out a Point from them. 2011-06-11 10
- Major re-write.
getCompEvent
fixed. All 5 test spaces checking out ok. 2011-06-18 21
- Removed sample set order dependency from
checkSigma
. All 7 test spaces checking out ok. 2011-06-19 22
- Added 'union of events is an event' test to
checkSigma
. 2011-06-20 23
- Changed
Event
from data constructor to type alias, in order to eliminate many instances of 'Event . f . getSamps' code. 2011-06-20 25
- Modified
smpsSetInt
to use a fold. 2011-06-20 26
- Defined public interface.
2011-06-21 27
- Modified comments for Haddock, and generated HTML docs.
2011-06-22 31
- Moved into
Data
directory. - End of Subversion revision history
- This source has been moved to darcs.
2011-06-27
- Made
smplSetUnion
more efficient, and tuned remaining performance bottlenecks.
To Do:
- data ProbSpace = ProbSpace [Sample] [Measure]
- data Measure = Measure Event Double
- data Sample = Empty
- data TestResult
- data ErrType
- checkProbMeas :: ProbSpace -> TestResult
- point :: Double -> Sample
- range :: (Double, Double) -> Sample
- makeProbSpace :: [(Sample, Double)] -> ProbSpace
- rangeBegin :: Sample -> Double
- rangeEnd :: Sample -> Double
- getProb :: Measure -> Double
- getEvent :: Measure -> Event
- getCompEvent :: [Sample] -> Event -> Event
- eventInt :: Event -> Event -> Event
- smplComp :: Sample -> Sample -> [Sample]
- isElem :: [Sample] -> Sample -> Bool
- noDupEvents :: [Measure] -> Bool
- smplInt :: Sample -> Sample -> Sample
- smplSetInt :: [Sample] -> Sample
- smplUnion :: Sample -> Sample -> [Sample]
- smplSetUnion :: [Sample] -> [Sample]
- checkSigma :: ProbSpace -> TestResult
- getRsltStr :: TestResult -> String
Documentation
We take a probability space to consist of the following:
- an 'abstract space' composed of either discrete or continuous (or a mix) samples
- an 'event space', which must be a Sigma field defined over the abstract space
- a 'probability measure' defined over the event space
- Note:
- For the sake of efficient coding, the event space and the probability measure are combined in the Haskell data structure, below. This is permissable, because there has to be a 1:1 correspondance between them anyway. And it is preferable, because it:
- keeps the probabilities more closely associated w/ the events, and
- avoids duplication of code (i.e. - the list of events).
Measure has 2 fields:
- event - a list of samples from the space, and
- prob - a number between 0 and 1 giving the events probability of occurence.
This is our abstract data type, which represents a sample in the abstract space.
It has a constructor representing every possible element in the abstract space we're modeling. (Currently, just points and ranges of Doubles.)
Normally, none of the constructors of this type will be called directly.
Instead, helper functions are provided, such as point
and range
, which
hide the implementation details from the user, and present a stable interface.
Currently, the sole exception to the above is the Empty constructor, which is really just a hack intended to put off the job of making the functions in this library more intelligent, with regard to their handling of empty lists.
Constructors
Empty |
Custom data type for reporting different errors
checkProbMeas :: ProbSpace -> TestResultSource
Checks a value of type ProbSpace
for correctness, and returns a value of
type TestResult
.
point :: Double -> SampleSource
This is the helper function intended to be used for constructing a point sample.
range :: (Double, Double) -> SampleSource
This is the helper function intended to be used for constructing a range sample. The range is considered open. That is, its end points are not included.
makeProbSpace :: [(Sample, Double)] -> ProbSpaceSource
This helper function generates a complete and valid probability space, given a discrete sample space and set of probabilities.
rangeBegin :: Sample -> DoubleSource
Gets the beginning point of a range, which is not included in the range, since ranges are considered to be open.
rangeEnd :: Sample -> DoubleSource
Gets the ending point of a range, which is not included in the range,
getCompEvent :: [Sample] -> Event -> EventSource
Get the complement of an event from the sample space.
eventInt :: Event -> Event -> EventSource
Calculates the intersection of 2 events (i.e. - list of samples).
smplComp :: Sample -> Sample -> [Sample]Source
Returns that portion of the first sample that is disjoint from the second.
isElem :: [Sample] -> Sample -> BoolSource
Determine if a sample is an element of a space.
(Need this, as opposed to just using elem
, in order to accomodate ranges.)
noDupEvents :: [Measure] -> BoolSource
Checks a list of measures against duplicate events.
smplSetInt :: [Sample] -> SampleSource
Reduces a list of samples to a single sample representing their intersection.
smplUnion :: Sample -> Sample -> [Sample]Source
Returns the union of 2 samples.
Unlike smplInt
, smplUnion must return a list since, if the 2 input
samples aren't adjacent or overlapping, the union of them is a list
containing both.
smplSetUnion :: [Sample] -> [Sample]Source
Collapses a list of samples down to the maximally reduced set, which still composes a proper union of the input.
checkSigma :: ProbSpace -> TestResultSource
Checks whether event space is actually a Sigma field over the sample space.
getRsltStr :: TestResult -> StringSource
Turns a value of type TestResult into a human readable string.