States, histories and histograms

Haskell implementation of the Overview/States, histories and histograms

Sections

Variables, values and systems

States

Histories

Histograms

Independent Histograms

Substrate structures

Example - a weather forecast

Variables, values and systems

The set of all variables is $\mathcal{V}$. The Variable type is usually defined with a String, an Integer or a pair of Variable,

data Variable = VarStr String | VarInt Integer | VarPair (Variable,Variable) | ...

For example,

let suit = VarStr "suit"
    rank = VarStr "rank"

:t suit
suit :: Variable

let vv = Set.fromList [suit, rank]

rp vv
"{rank,suit}"

The set of all values is $\mathcal{W}$. The Value type is usually defined with a String, an Integer or a Double,

data Value  = ValStr String | ValInt Integer | ValDouble Double | ...

For example,

let [hearts,clubs,diamonds,spades] = map ValStr ["hearts","clubs","diamonds","spades"] 

:t spades
spades :: Value

let wws = Set.fromList [hearts, clubs, diamonds, spades]

:t wws
wws :: Set.Set Value

rp wws
"{clubs,diamonds,hearts,spades}"

let [jack,queen,king,ace] = map ValStr ["J","Q","K","A"] 

:t ace
ace :: Value

let wwr = Set.fromList $ [jack,queen,king,ace] ++ map ValInt [2..10]

rp wwr
"{A,J,K,Q,2,3,4,5,6,7,8,9,10}"

A system $U \in \mathcal{V} \to \mathrm{P}(\mathcal{W})$ is a functional mapping between variables and non-empty sets of values, $\forall (v,W) \in U~(|W|>0)$. The System type is defined with a Map.Map from Variable to a set of Value,

newtype System = System (Map.Map Variable (Set.Set Value)) 

A System can be constructed from a list of pairs of Variable and Value sets,

listsSystem :: [(Variable, Set.Set Value)] -> Maybe System
systemsList :: System -> [(Variable, Set.Set Value)]

For example,

let uu = fromJust $ listsSystem [(suit,wws), (rank,wwr)]

rp uu
"{(rank,{A,J,K,Q,2,3,4,5,6,7,8,9,10}),(suit,{clubs,diamonds,hearts,spades})}"

rpln $ systemsList uu
"(rank,{A,J,K,Q,2,3,4,5,6,7,8,9,10})"
"(suit,{clubs,diamonds,hearts,spades})"

The Variable set accessor is

systemsVars :: System -> Set.Set Variable

For example,

let uvars = systemsVars

rp $ uvars uu
"{rank,suit}"

The Value set accessor is

systemsVarsSetValue :: System -> Variable -> Maybe (Set.Set Value)

For example,

let uat uu v = fromJust $ systemsVarsSetValue uu v

rp $ uu `uat` suit
"{clubs,diamonds,hearts,spades}"

The valency of a variable $v$ is the cardinality of its values, $|U_v|$,

Set.size $ uu `uat` suit
4

Set.size $ uu `uat` rank
13

The volume of a set of variables in a system $V \subseteq \mathrm{vars}(U)$ is the product of the valencies, $\prod_{v \in V} |U_v| \geq 1$,

systemsSetVarsVolume :: System -> Set.Set Variable -> Maybe Integer

For example

let vol uu vv = fromJust $ systemsSetVarsVolume uu vv

vol uu vv 
52

vol uu $ Set.singleton suit 
4

vol uu $ Set.singleton rank 
13

The volume of an empty set of variables is defined as $1$,


vol uu $ Set.empty
1

A regular system $U’$ of dimension $n$ cardinal variables $\{1 \ldots n\}$ each of valency $d$ cardinal values $\{1 \ldots d\}$ is constructed

systemRegular :: Integer -> Integer -> Maybe System

For example,

let sysreg d n = fromJust $ systemRegular d n

let uu' = sysreg 3 2

rp $ uu'
"{(1,{1,2,3}),(2,{1,2,3})}"

vol uu' $ uvars uu'
9

States

The set of states is the set of value valued functions of variable, $\mathcal{S} = \mathcal{V} \to \mathcal{W}$. The State type is defined with a Map.Map from Variable to Value,

newtype State = State (Map.Map Variable Value)

A State can be constructed from a list of pairs of Variable and Value,

listsState :: [(Variable, Value)] -> State
statesList :: State -> [(Variable, Value)]

The variables of a state $S \in \mathcal{S}$ is the function domain, $\mathrm{vars}(S) := \mathrm{dom}(S)$,

statesVars :: State -> Set.Set Variable

For example,

let llss = listsState
    ssll = statesList

let ss = llss [(suit,spades),(rank,ace)]

rp ss
"{(rank,A),(suit,spades)}"

rpln $ ssll ss
"(rank,A)"
"(suit,spades)"

let svars = statesVars

rp $ svars ss
"{rank,suit}"

The Value accessor is

statesVarsValue :: State -> Variable -> Maybe Value

For example,

let sat ss v = fromJust $ statesVarsValue ss v

rp $ ss `sat` suit
"spades"

The empty state, $\{\}$, has no variables,

stateEmpty :: State

For example,

rp $ svars stateEmpty
"{}"

The state, $S$, is in a system $U$ if (i) the variables of the state are variables of the system, $\mathrm{vars}(S) \subseteq \mathrm{vars}(U)$, and (ii) the value of each variable in the state is in the system, $\forall v \in \mathrm{vars}(S)~(S_v \in U_v)$,

systemsStatesIs :: System -> State -> Bool

For example,

systemsStatesIs uu ss
True

svars ss `Set.isSubsetOf` uvars uu
True

(ss `sat` suit) `Set.member` (uu `uat` suit)
True

(ss `sat` rank) `Set.member` (uu `uat` rank)
True

systemsStatesIs uu' ss
False

Given a set of variables in a system $V \subseteq \mathrm{vars}(U)$, the cartesian set of all possible states is $\prod_{v \in V} ({v} \times U_v)$,

systemsSetVarsSetStateCartesian :: System -> Set.Set Variable -> Maybe (Set.Set State)

which has cardinality equal to the volume $\prod_{v \in V} |U_v|$,

let cart uu vv = fromJust $ systemsSetVarsSetStateCartesian uu vv

rpln $ Set.toList $ cart uu vv 
"{(rank,A),(suit,clubs)}"
"{(rank,A),(suit,diamonds)}"
"{(rank,A),(suit,hearts)}"
"{(rank,A),(suit,spades)}"
"{(rank,J),(suit,clubs)}"
"{(rank,J),(suit,diamonds)}"
...
"{(rank,9),(suit,hearts)}"
"{(rank,9),(suit,spades)}"
"{(rank,10),(suit,clubs)}"
"{(rank,10),(suit,diamonds)}"
"{(rank,10),(suit,hearts)}"
"{(rank,10),(suit,spades)}"

Set.size $ cart uu vv 
52

vol uu vv
52

The variables $V = \mathrm{vars}(S)$ of a state $S$ may be reduced to a given subset $K \subseteq V$ by taking the subset of the variable-value pairs, \[ S~\%~K := \{(v,u) :(v,u) \in S,~v \in K\} \]

setVarsStatesStateFiltered :: Set.Set Variable -> State -> State 

For example,

let sred ss vv = setVarsStatesStateFiltered vv ss

rp $ ss `sred` svars ss
"{(rank,A),(suit,spades)}"

rp $ ss `sred` Set.empty
"{}"

rp $ ss `sred` Set.singleton suit
"{(suit,spades)}"

rp $ ss `sred` Set.singleton rank
"{(rank,A)}"

A set of states $Q \subset \mathcal{S}$ in the same variables $\forall S \in Q~(\mathrm{vars}(S)=V)$ may be split into a subset of its variables $K \subseteq V$ and the complement $V \setminus K$, \[ \mathrm{split}(K,Q) = \{(S~\%~K,~S~\%~(V \setminus K)) :S \in Q\} \]

setVarsSetStatesSplit :: Set.Set Variable -> Set.Set State -> Set.Set (State,State) 

For example,

let ssplit = setVarsSetStatesSplit 

rpln $ Set.toList $ ssplit (Set.singleton suit) (cart uu vv)
"({(suit,clubs)},{(rank,A)})"
"({(suit,clubs)},{(rank,J)})"
"({(suit,clubs)},{(rank,K)})"
"({(suit,clubs)},{(rank,Q)})"
"({(suit,clubs)},{(rank,2)})"
...
"({(suit,spades)},{(rank,6)})"
"({(suit,spades)},{(rank,7)})"
"({(suit,spades)},{(rank,8)})"
"({(suit,spades)},{(rank,9)})"
"({(suit,spades)},{(rank,10)})"

Two states $S,T \in \mathcal{S}$ are said to join if their union is also a state, $S \cup T \in \mathcal{S}$,

pairStatesIsJoin :: State -> State -> Bool
pairStatesUnionLeft :: State -> State -> State

For example,

let sjoin = pairStatesUnionLeft

let colour = VarStr "colour"
    red = ValStr "red"; black = ValStr "black"

let tt = llss [(suit,spades),(colour,black)]

pairStatesIsJoin ss tt
True

rp $ ss `sjoin` tt
"{(colour,black),(rank,A),(suit,spades)}"

let qq = llss [(suit,hearts),(colour,red)]

pairStatesIsJoin ss qq
False

let rr = llss [(suit,spades),(rank,king)]

pairStatesIsJoin ss rr
False

pairStatesIsJoin ss ss
True

Histories

The set of event identifiers is the universal set $\mathcal{X}$. The Id type is usually defined with a String, an Integer, a pair of Id or a null,

data Id = IdStr String | IdInt Integer | IdPair (Id,Id) | IdNull | ...

An event $(x,S)$ is a pair of an event identifier and a state, $(x,S) \in \mathcal{X} \times \mathcal{S}$. A history $H$ is a state valued function of event identifiers, $H \in \mathcal{X} \to \mathcal{S}$, such that all of the states of its events share the same set of variables, $\forall (x,S),(y,T) \in H~(\mathrm{vars}(S)=\mathrm{vars}(T))$. The set of histories is denoted $\mathcal{H} \subset \mathcal{X} \to \mathcal{S}$. The History type is defined with a Map.Map from Id to State,

newtype History = History (Map.Map Id State) 

A History can be constructed from a list of pairs of Id and State,

listsHistory :: [(Id, State)] -> Maybe History
historyToList :: History -> [(Id, State)]

For example, if a deck of cards happens to be dealt in alphanumeric order the history is

let suit = VarStr "suit"
    rank = VarStr "rank"
    vv = Set.fromList [suit, rank]
    [hearts,clubs,diamonds,spades] = map ValStr ["hearts","clubs","diamonds","spades"]
    wws = Set.fromList [hearts, clubs, diamonds, spades]
    [jack,queen,king,ace] = map ValStr ["J","Q","K","A"]
    wwr = Set.fromList $ [jack,queen,king,ace] ++ map ValInt [2..10]
    uu = fromJust $ listsSystem [(suit,wws), (rank,wwr)]

let llhh = fromJust . listsHistory
    hhll = historyToList

let hh = llhh $ zip (map IdInt [1..]) (Set.toList (cart uu vv))

rpln $ hhll hh
"(1,{(rank,A),(suit,clubs)})"
"(2,{(rank,A),(suit,diamonds)})"
"(3,{(rank,A),(suit,hearts)})"
"(4,{(rank,A),(suit,spades)})"
"(5,{(rank,J),(suit,clubs)})"
"(6,{(rank,J),(suit,diamonds)})"
...
"(47,{(rank,9),(suit,hearts)})"
"(48,{(rank,9),(suit,spades)})"
"(49,{(rank,10),(suit,clubs)})"
"(50,{(rank,10),(suit,diamonds)})"
"(51,{(rank,10),(suit,hearts)})"
"(52,{(rank,10),(suit,spades)})"

The set of variables of a history is the set of the variables of any of the events of the history, $\mathrm{vars}(H) = \mathrm{vars}(S)$ where $(x,S) \in H$,

historiesSetVar :: History -> Set.Set Variable

For example,

let hvars = historiesSetVar

rp $ hvars hh
"{rank,suit}"

The inverse of a history, $H^{-1}$, is called the classification. So a classification is an event identifier set valued function of state, $H^{-1} \in \mathcal{S} \to \mathrm{P}(\mathcal{X})$. The Classification type is defined with a Map.Map from State to a set of Id,

newtype Classification = Classification (Map.Map State (Set.Set Id)) 

A Classification can be constructed from a History and vice-versa,

historiesClassification :: History -> Classification
classificationsHistory :: Classification -> History

For example,

let hhgg = historiesClassification
    gghh = classificationsHistory
    ggll = classificationsList

rpln $ ggll $ hhgg hh
"({(rank,A),(suit,clubs)},{1})"
"({(rank,A),(suit,diamonds)},{2})"
"({(rank,A),(suit,hearts)},{3})"
"({(rank,A),(suit,spades)},{4})"
"({(rank,J),(suit,clubs)},{5})"
"({(rank,J),(suit,diamonds)},{6})"
...
"({(rank,9),(suit,diamonds)},{46})"
"({(rank,9),(suit,hearts)},{47})"
"({(rank,9),(suit,spades)},{48})"
"({(rank,10),(suit,clubs)},{49})"
"({(rank,10),(suit,diamonds)},{50})"
"({(rank,10),(suit,hearts)},{51})"
"({(rank,10),(suit,spades)},{52})"

gghh (hhgg hh) == hh
True

The reduction of a history is the reduction of its events, $H\%V := \{(x,S\%V) : (x,S) \in H\}$,

setVarsHistoriesReduce :: Set.Set Variable -> History -> History 

For example,

let hred hh vv = setVarsHistoriesReduce vv hh

rpln $ hhll $ hh `hred` Set.singleton suit
"(1,{(suit,clubs)})"
"(2,{(suit,diamonds)})"
"(3,{(suit,hearts)})"
"(4,{(suit,spades)})"
"(5,{(suit,clubs)})"
"(6,{(suit,diamonds)})"
...
"(47,{(suit,hearts)})"
"(48,{(suit,spades)})"
"(49,{(suit,clubs)})"
"(50,{(suit,diamonds)})"
"(51,{(suit,hearts)})"
"(52,{(suit,spades)})"

rpln $ ggll $ hhgg $ hh `hred` Set.singleton suit
"({(suit,clubs)},{1,5,9,13,17,21,25,29,33,37,41,45,49})"
"({(suit,diamonds)},{2,6,10,14,18,22,26,30,34,38,42,46,50})"
"({(suit,hearts)},{3,7,11,15,19,23,27,31,35,39,43,47,51})"
"({(suit,spades)},{4,8,12,16,20,24,28,32,36,40,44,48,52})"

rpln $ ggll $ hhgg $ hh `hred` Set.singleton rank
"({(rank,A)},{1,2,3,4})"
"({(rank,J)},{5,6,7,8})"
"({(rank,K)},{9,10,11,12})"
"({(rank,Q)},{13,14,15,16})"
"({(rank,2)},{17,18,19,20})"
"({(rank,3)},{21,22,23,24})"
"({(rank,4)},{25,26,27,28})"
"({(rank,5)},{29,30,31,32})"
"({(rank,6)},{33,34,35,36})"
"({(rank,7)},{37,38,39,40})"
"({(rank,8)},{41,42,43,44})"
"({(rank,9)},{45,46,47,48})"
"({(rank,10)},{49,50,51,52})"

The size of a history is its cardinality,

historiesSize :: History -> Integer

For example,

let hsize = historiesSize

hsize hh
52

fromInteger (hsize hh) == length (hhll hh)
True

The addition operation of histories is defined as the disjoint union of the events if both histories have the same variables, \[ H_1 + H_2~:=~\{((x,\cdot),S) : (x,S) \in H_1\}~\cup~\{((\cdot,y),T) : (y,T) \in H_2\} \] where $\mathrm{vars}(H_1) = \mathrm{vars}(H_2)$,

pairHistoriesAdd :: History -> History -> Maybe History

For example,

let hadd hh gg = fromJust $ pairHistoriesAdd hh gg

rpln $ hhll $ hh `hadd` hh
"((1,_),{(rank,A),(suit,clubs)})"
"((2,_),{(rank,A),(suit,diamonds)})"
"((3,_),{(rank,A),(suit,hearts)})"
"((4,_),{(rank,A),(suit,spades)})"
"((5,_),{(rank,J),(suit,clubs)})"
"((6,_),{(rank,J),(suit,diamonds)})"
...
"((50,_),{(rank,10),(suit,diamonds)})"
"((51,_),{(rank,10),(suit,hearts)})"
"((52,_),{(rank,10),(suit,spades)})"
"((_,1),{(rank,A),(suit,clubs)})"
"((_,2),{(rank,A),(suit,diamonds)})"
"((_,3),{(rank,A),(suit,hearts)})"
...
"((_,48),{(rank,9),(suit,spades)})"
"((_,49),{(rank,10),(suit,clubs)})"
"((_,50),{(rank,10),(suit,diamonds)})"
"((_,51),{(rank,10),(suit,hearts)})"
"((_,52),{(rank,10),(suit,spades)})"

hsize $ hh `hadd` hh
104

The size of the sum equals the sum of the sizes, $|H_1 + H_2| = |H_1| + |H_2|$,

hsize (hh `hadd` hh) == hsize hh + hsize hh
True

The multiplication operation of histories is defined as the product of the events where the states join, \[ \begin{eqnarray} H_1 * H_2 &:=& \{((x,y),S \cup T) : (x,S) \in H_1,~(y,T) \in H_2,\\ & &\hspace{5em}\forall v \in \mathrm{vars}(S) \cap \mathrm{vars}(T)~(S_v = T_v)\} \end{eqnarray} \]

pairHistoriesMultiply :: History -> History -> History

For example,

let hmul = pairHistoriesMultiply

rpln $ hhll $ hh `hmul` hh
"((1,1),{(rank,A),(suit,clubs)})"
"((2,2),{(rank,A),(suit,diamonds)})"
"((3,3),{(rank,A),(suit,hearts)})"
"((4,4),{(rank,A),(suit,spades)})"
"((5,5),{(rank,J),(suit,clubs)})"
"((6,6),{(rank,J),(suit,diamonds)})"
...
"((47,47),{(rank,9),(suit,hearts)})"
"((48,48),{(rank,9),(suit,spades)})"
"((49,49),{(rank,10),(suit,clubs)})"
"((50,50),{(rank,10),(suit,diamonds)})"
"((51,51),{(rank,10),(suit,hearts)})"
"((52,52),{(rank,10),(suit,spades)})"

hsize $ hh `hmul` hh
52

let coin = VarStr "coin"
    heads = ValStr "heads"; tails = ValStr "tails"

let gg = llhh $ [(IdInt 1, llss [(coin,heads)]), (IdInt 2, llss [(coin,tails)])]

rpln $ hhll $ gg
"(1,{(coin,heads)})"
"(2,{(coin,tails)})"

rpln $ hhll $ hh `hmul` gg
"((1,1),{(coin,heads),(rank,A),(suit,clubs)})"
"((1,2),{(coin,tails),(rank,A),(suit,clubs)})"
"((2,1),{(coin,heads),(rank,A),(suit,diamonds)})"
"((2,2),{(coin,tails),(rank,A),(suit,diamonds)})"
"((3,1),{(coin,heads),(rank,A),(suit,hearts)})"
"((3,2),{(coin,tails),(rank,A),(suit,hearts)})"
...
"((50,1),{(coin,heads),(rank,10),(suit,diamonds)})"
"((50,2),{(coin,tails),(rank,10),(suit,diamonds)})"
"((51,1),{(coin,heads),(rank,10),(suit,hearts)})"
"((51,2),{(coin,tails),(rank,10),(suit,hearts)})"
"((52,1),{(coin,heads),(rank,10),(suit,spades)})"
"((52,2),{(coin,tails),(rank,10),(suit,spades)})"

hsize $ hh `hmul` gg
104

The size of the product equals the product of the sizes if the variables are disjoint, $\mathrm{vars}(H_1) \cap \mathrm{vars}(H_2) = \emptyset \implies |H_1 * H_2| = |H_1| \times |H_2|$,

hsize (hh `hmul` gg) == hsize hh * hsize gg
True

The variables of the product is the union of the variables if the size is non-zero, $H_1 * H_2 \neq \emptyset \implies \mathrm{vars}(H_1 * H_2) = \mathrm{vars}(H_1) \cup \mathrm{vars}(H_2)$,

hvars (hh `hmul` gg) == hvars hh `Set.union` hvars gg
True

Histograms

The set of all histograms $\mathcal{A}$ is a subset of the positive rational valued functions of states, $\mathcal{A} \subset \mathcal{S} \to \mathbf{Q}_{\geq 0}$, such that each state of each histogram has the same set of variables, $\forall A \in \mathcal{A}~\forall S,T \in \mathrm{dom}(A)~(\mathrm{vars}(S)=\mathrm{vars}(T))$. The Histogram type is defined with a Map.Map from State to Rational,

newtype Histogram = Histogram (Map.Map State Rational)

A Histogram can be constructed from a list of pairs of State and Rational,

listsHistogram :: [(State, Rational)] -> Maybe Histogram
histogramsList :: Histogram -> [(State, Rational)]

For example, the histogram of a deck of cards is

let suit = VarStr "suit"
    rank = VarStr "rank"
    vv = Set.fromList [suit, rank]
    [hearts,clubs,diamonds,spades] = map ValStr ["hearts","clubs","diamonds","spades"]
    wws = Set.fromList [hearts, clubs, diamonds, spades]
    [jack,queen,king,ace] = map ValStr ["J","Q","K","A"]
    wwr = Set.fromList $ [jack,queen,king,ace] ++ map ValInt [2..10]
    uu = fromJust $ listsSystem [(suit,wws), (rank,wwr)]

let llaa = fromJust . listsHistogram
    aall = histogramsList

let aa = llaa $ zip (Set.toList (cart uu vv)) (repeat 1)

rpln $ aall aa
"({(rank,A),(suit,clubs)},1 % 1)"
"({(rank,A),(suit,diamonds)},1 % 1)"
"({(rank,A),(suit,hearts)},1 % 1)"
"({(rank,A),(suit,spades)},1 % 1)"
"({(rank,J),(suit,clubs)},1 % 1)"
"({(rank,J),(suit,diamonds)},1 % 1)"
...
"({(rank,9),(suit,hearts)},1 % 1)"
"({(rank,9),(suit,spades)},1 % 1)"
"({(rank,10),(suit,clubs)},1 % 1)"
"({(rank,10),(suit,diamonds)},1 % 1)"
"({(rank,10),(suit,hearts)},1 % 1)"
"({(rank,10),(suit,spades)},1 % 1)"

The set of variables of a histogram $A \in \mathcal{A}$ is the set of the variables of any of the elements of the histogram, $\mathrm{vars}(A) = \mathrm{vars}(S)$ where $(S,q) \in A$,

histogramsSetVar :: Histogram -> Set.Set Variable

For example,

let vars = histogramsSetVar

rp $ vars aa
"{rank,suit}"

Given a variable map, a histogram may be reframed,

histogramsMapVarsFrame :: Histogram -> Map.Map Variable Variable -> Maybe Histogram

For example,

let reframe aa mm = fromJust $ histogramsMapVarsFrame aa (Map.fromList mm) 

rpln $ aall $ aa `reframe` [(suit, VarStr "S"), (rank, VarStr "R")]
"({(R,A),(S,clubs)},1 % 1)"
"({(R,A),(S,diamonds)},1 % 1)"
"({(R,A),(S,hearts)},1 % 1)"
"({(R,A),(S,spades)},1 % 1)"
"({(R,J),(S,clubs)},1 % 1)"
"({(R,J),(S,diamonds)},1 % 1)"
...
"({(R,9),(S,hearts)},1 % 1)"
"({(R,9),(S,spades)},1 % 1)"
"({(R,10),(S,clubs)},1 % 1)"
"({(R,10),(S,diamonds)},1 % 1)"
"({(R,10),(S,hearts)},1 % 1)"
"({(R,10),(S,spades)},1 % 1)"

rp $ vars $ aa `reframe` [(suit, VarStr "S"), (rank, VarStr "R")]
"{R,S}"

The dimension of a histogram is the cardinality of its variables, $|\mathrm{vars}(A)|$,

Set.size $ vars aa
2

The states of a histogram is the domain, $A^{\mathrm{S}} := \mathrm{dom}(A)$,

histogramsStates :: Histogram -> Set.Set State

For example,

let states = histogramsStates

rpln $ Set.toList $ states aa
"{(rank,A),(suit,clubs)}"
"{(rank,A),(suit,diamonds)}"
"{(rank,A),(suit,hearts)}"
"{(rank,A),(suit,spades)}"
"{(rank,J),(suit,clubs)}"
"{(rank,J),(suit,diamonds)}"
...
"{(rank,9),(suit,hearts)}"
"{(rank,9),(suit,spades)}"
"{(rank,10),(suit,clubs)}"
"{(rank,10),(suit,diamonds)}"
"{(rank,10),(suit,hearts)}"
"{(rank,10),(suit,spades)}"

The count accessor is

histogramsStatesCount :: Histogram -> State -> Maybe Rational

For example,

let aat aa ss = fromJust $ histogramsStatesCount aa ss

let ss = llss [(suit,spades),(rank,ace)]

rp ss
"{(rank,A),(suit,spades)}"

aa `aat` ss
1 % 1

The size of a histogram is the sum of the counts, $\mathrm{size}(A) := \mathrm{sum}(A)$,

histogramsSize :: Histogram -> Rational

For example,

let size = histogramsSize

size aa
52 % 1

If the size is non-zero the normalised histogram has a size of one, $\mathrm{size}(A) > 0 \implies \mathrm{size}(\hat{A}) = 1$,

histogramsResize :: Rational -> Histogram -> Maybe Histogram

For example,

let norm aa = fromJust $ histogramsResize 1 aa

rpln $ aall $ norm aa
"({(rank,A),(suit,clubs)},1 % 52)"
"({(rank,A),(suit,diamonds)},1 % 52)"
"({(rank,A),(suit,hearts)},1 % 52)"
"({(rank,A),(suit,spades)},1 % 52)"
"({(rank,J),(suit,clubs)},1 % 52)"
"({(rank,J),(suit,diamonds)},1 % 52)"
"({(rank,J),(suit,hearts)},1 % 52)"
...
"({(rank,9),(suit,hearts)},1 % 52)"
"({(rank,9),(suit,spades)},1 % 52)"
"({(rank,10),(suit,clubs)},1 % 52)"
"({(rank,10),(suit,diamonds)},1 % 52)"
"({(rank,10),(suit,hearts)},1 % 52)"
"({(rank,10),(suit,spades)},1 % 52)"

size $ norm aa
1 % 1

The volume of a histogram $A$ of variables $V$ in a system $U$ is the volume of the variables, $\prod_{v \in V} |U_v|$,

vol uu $ vars aa
52

A histogram with no variables is called a scalar. The scalar of size $z$ is $\{(\emptyset,z)\}$. Define $\mathrm{scalar}(z) := \{(\emptyset,z)\}$.

histogramScalar :: Rational -> Maybe Histogram

For example,

let scalar q = fromJust $ histogramScalar q

rp $ scalar 52
"{({},52 % 1)}"

rp $ vars $ scalar 52
"{}"

scalar 52 == llaa [(stateEmpty,52)]
True

A singleton is a histogram with only one state, $\{(S,z)\}$,

histogramsIsSingleton :: Histogram -> Bool
histogramSingleton :: State -> Rational -> Maybe Histogram

For example,

let single ss c = fromJust $ histogramSingleton ss c

let ss = llss [(suit,spades),(rank,ace)]

let rr = llss [(suit,hearts),(rank,queen)]

let bb =  llaa [(ss,1)]

rp bb
"{({(rank,A),(suit,spades)},1 % 1)}"

histogramsIsSingleton bb
True

bb == single ss 1
True

let cc =  llaa [(ss,1),(rr,1)]

rp cc
"{({(rank,A),(suit,spades)},1 % 1),({(rank,Q),(suit,hearts)},1 % 1)}"

histogramsIsSingleton cc
False

histogramsIsSingleton $ scalar 1
True

A uniform histogram $A$ has unique non-zero count, $|\{c : (S,c) \in A,~c>0\}|=1$,

histogramsIsUniform :: Histogram -> Bool

For example,

histogramsIsUniform aa
True

histogramsIsUniform bb
True

histogramsIsUniform cc
True

histogramsIsUniform $ scalar 1
True

let dd =  llaa [(ss,1),(rr,2)]

rp dd
"{({(rank,A),(suit,spades)},1 % 1),({(rank,Q),(suit,hearts)},2 % 1)}"

histogramsIsUniform dd
False

The set of integral histograms is the subset of histograms which have integal counts $\mathcal{A}_{\mathrm{i}} = \mathcal{A}~\cap~(\mathcal{S} \to \mathbf{N})$,

histogramsIsIntegral :: Histogram -> Bool

For example,

histogramsIsIntegral `map` [aa,bb,cc,dd,scalar 1]
[True,True,True,True,True]

histogramsIsIntegral $ norm aa
False

A unit histogram is a special case of an integral histogram in which all its counts equal one, $\mathrm{ran}(A)=\{1\}$,

histogramsIsUnit :: Histogram -> Bool

For example,

histogramsIsUnit `map` [aa,bb,cc,dd,scalar 1,norm aa]
[True,True,True,False,True,False]

The size of a unit histogram equals its cardinality, $\mathrm{size}(A)=|A|$,

size `map` [aa,bb,cc,scalar 1]
[52 % 1,1 % 1,2 % 1,1 % 1]

(length . aall) `map` [aa,bb,cc,scalar 1]
[52,1,2,1]

A set of states $Q \subset \mathcal{S}$ in the same variables may be promoted to a unit histogram, $Q^{\mathrm{U}} := Q \times {1} \in \mathcal{A}_{\mathrm{i}}$,

setStatesHistogramUnit :: Set.Set State -> Maybe Histogram

For example,

let unit qq = fromJust $ setStatesHistogramUnit qq

let cart uu vv = fromJust $ systemsSetVarsSetStateCartesian uu vv

aa == unit (cart uu vv)
True

cc == unit (Set.fromList [ss,rr])
True

The effective states of a histogram are those where the count is non-zero. A histogram may be trimmed to its effective states, $\{(S,c) : (S,c) \in A,~c>0\}$,

histogramsTrim :: Histogram -> Histogram

For example,

let trim = histogramsTrim

rpln $ aall $ trim $ llaa [(ss,3),(rr,0)]
"({(rank,A),(suit,spades)},3 % 1)"

rpln $ aall $ trim $ llaa [(ss,3),(rr,5)]
"({(rank,A),(suit,spades)},3 % 1)"
"({(rank,Q),(suit,hearts)},5 % 1)"

trim (llaa [(ss,0),(rr,0)]) == histogramEmpty
True

The unit effective histogram of a histogram is the unit histogram of the effective states, $A^{\mathrm{F}} := \{(S,1) : (S,c) \in A,~c>0\} \in \mathcal{A}_{\mathrm{i}}$,

histogramsEffective :: Histogram -> Histogram

For example,

let eff = histogramsEffective

let ee = llaa [(ss,3),(rr,0)]

rp ee
"{({(rank,A),(suit,spades)},3 % 1),({(rank,Q),(suit,hearts)},0 % 1)}"

rp $ eff ee
"{({(rank,A),(suit,spades)},1 % 1)}"

[xx == eff xx | xx <- [aa,bb,cc,dd,scalar 1,norm aa,ee]]
[True,True,True,False,True,False,False]

Given a system $U$ define the cartesian histogram of the set of variables $V$ as $V^{\mathrm{C}} := \big(\prod_{v \in V} ({v} \times U_v)\big) \times {1} \in \mathcal{A}_{\mathrm{i}}$,

let vvc = unit (cart uu vv)

aa == vvc
True

The size of the cartesian histogram equals its cardinality which is the volume of the variables, $\mathrm{size}(V^{\mathrm{C}})=|V^{\mathrm{C}}| = \prod_{v \in V} |U_v|$,

size vvc
52 % 1

length $ aall vvc
52

vol uu vv
52

The unit effective histogram is a subset of the cartesian histogram of its variables, $A^{\mathrm{F}} \subseteq V^{\mathrm{C}}$, where $V = \mathrm{vars}(A)$,

let aaqq = Set.fromList . aall

[aaqq (eff xx) `Set.isSubsetOf` aaqq vvc | xx <- [aa,bb,cc,dd,scalar 1,norm aa,ee]]
[True,True,True,True,False,True,True]

A partition $P$ is a partition of the cartesian states, $P \in \mathrm{B}(V^{\mathrm{CS}})$. The partition is a set of disjoint components, $\forall C,D \in P~(C \neq D \implies C \cap D = \emptyset)$, that union to equal the cartesian states, $\bigcup P = V^{\mathrm{CS}}$. The Component type is a set of State,

type Component = Set.Set State

The Partition type is a set of Component,

newtype Partition = Partition (Set.Set Component)

A Partition can be constructed from a set of Component,

setComponentsPartition :: Set.Set Component -> Maybe Partition
partitionsSetComponent :: Partition -> Set.Set Component

For example,

let qqpp qq = fromJust $ setComponentsPartition qq
    ppqq = partitionsSetComponent

let c = Set.fromList $ take 13 $ Set.toList $ states vvc

Set.size c
13

let d = Set.fromList $ drop 13 $ Set.toList $ states vvc

Set.size d
39

c `Set.intersection` d == Set.empty
True

c `Set.union` d == states vvc
True

let pp = qqpp $ Set.fromList [c,d]

and [c `Set.intersection` d == Set.empty | c <- Set.toList (ppqq pp), d <- Set.toList (ppqq pp), c /= d]
True

let bigcup =  setSetsUnion

and [c `Set.union` d == bigcup (ppqq pp) | c <- Set.toList (ppqq pp), d <- Set.toList (ppqq pp), c /= d]
True

The unary partition is $\{V^{\mathrm{CS}}\}$,

systemsSetVarsPartitionUnary :: System -> Set.Set Variable -> Maybe Partition

For example,

let unary uu vv = fromJust $ systemsSetVarsPartitionUnary uu vv

ppqq (unary uu vv) == Set.singleton (states vvc)
True

The self partition is $V^{\mathrm{CS}\{\}} = \{\{S\} : S \in V^{\mathrm{CS}}\}$,

systemsSetVarsPartitionSelf :: System -> Set.Set Variable -> Maybe Partition

For example,

let self uu vv = fromJust $ systemsSetVarsPartitionSelf uu vv

ppqq (self uu vv) == Set.fromList [Set.singleton ss | ss <- Set.toList (states vvc)]
True

A partition variable $P \in \mathrm{vars}(U)$ in a system $U$ is such that its set of values equals its set of components, $U_P = P$. So the valency of a partition variable is the cardinality of the components, $|U_P| = |P|$. The Variable type can be constructed with a Partition,

data Variable = ... | VarPartition Partition | ...

Similarly, the Value type can be constructed with a Component,

data Value = ... | ValComponent Component | ...

For example,

:t pp
pp :: Partition

let uu' = fromJust $ listsSystem [(VarPartition pp, Set.fromList [ValComponent c,ValComponent d])]

let uat uu v = fromJust $ systemsVarsSetValue uu v

Set.size (uu' `uat` VarPartition pp)
2

Set.size (uu' `uat` VarPartition pp) == Set.size (ppqq pp)
True

A regular histogram $A’$ of variables $V’$ in system $U’$ has unique valency of its variables, $|\{|U’_v| : v \in V’\}|=1$. The volume of a regular histogram is $d^n = |{V’}^{\mathrm{C}}| = \prod_{v \in V’} |U’_v|$, where valency $d$ is such that $\{d\} = \{|U’_v| : v \in V’\}$ and dimension $n = |V’|$. For example,

let sysreg d n = fromJust $ systemRegular d n

let uu' = sysreg 3 2

rp $ uu'
"{(1,{1,2,3}),(2,{1,2,3})}"

vol uu' $ uvars uu'
9

let aa' = llaa [(llss [(VarInt 1, ValInt 1),(VarInt 2, ValInt 1)], 1)]

rp aa'
"{({(1,1),(2,1)},1 % 1)}"

rp $ vars aa'
"{1,2}"

vol uu' $ vars aa'
9

let d = Set.size $ uu' `uat` VarInt 1

let n = Set.size $ vars aa'

d^n
9

A regular cartesian histogram of cardinal variables $\{1 \ldots n\}$ and cardinal values $\{1 \ldots d\}$ is constructed,

histogramRegularCartesian :: Integer -> Integer -> Maybe Histogram

For example,

let regcart d n = fromJust $ histogramRegularCartesian d n

rpln $ aall $ regcart 3 2
"({(1,1),(2,1)},1 % 1)"
"({(1,1),(2,2)},1 % 1)"
"({(1,1),(2,3)},1 % 1)"
"({(1,2),(2,1)},1 % 1)"
"({(1,2),(2,2)},1 % 1)"
"({(1,2),(2,3)},1 % 1)"
"({(1,3),(2,1)},1 % 1)"
"({(1,3),(2,2)},1 % 1)"
"({(1,3),(2,3)},1 % 1)"

let uu' = sysreg 3 2

regcart 3 2 == unit (cart uu' (uvars uu'))
True

A regular unit singleton histogram of cardinal variables $\{1 \ldots n\}$ and cardinal values $\{1 \ldots d\}$ is constructed,

histogramRegularUnitSingleton :: Integer -> Integer -> Maybe Histogram

For example,

let regsing d n = fromJust $ histogramRegularUnitSingleton d n

rpln $ aall $ regsing 3 2
"({(1,1),(2,1)},1 % 1)"

A regular unit diagonal histogram of cardinal variables $\{1 \ldots n\}$ and cardinal values $\{1 \ldots d\}$ is constructed,

histogramRegularUnitDiagonal :: Integer -> Integer -> Maybe Histogram

For example,

let regdiag d n = fromJust $ histogramRegularUnitDiagonal d n

rpln $ aall $ regdiag 3 2
"({(1,1),(2,1)},1 % 1)"
"({(1,2),(2,2)},1 % 1)"
"({(1,3),(2,3)},1 % 1)"

A histogram may be reframed to a list of cardinal variables by transposition,

let cdtp aa ll = reframe aa (zip (Set.toList (vars aa)) (map VarInt ll))

rpln $ aall $ regcart 2 2 `cdtp` [3,4]
"({(3,1),(4,1)},1 % 1)"
"({(3,1),(4,2)},1 % 1)"
"({(3,2),(4,1)},1 % 1)"
"({(3,2),(4,2)},1 % 1)"

rpln $ aall $ regsing 2 2 `cdtp` [3,2]
"({(2,1),(3,1)},1 % 1)"

A unit histogram of cardinal variables and cardinal values may be constructed from a list of states which are in turn constructed from lists of integers,

let cdaa ll = llaa [(llss [(VarInt i, ValInt j) | (i,j) <- (zip [1..] ss)],1) | ss <- ll]

cdaa [[1,1],[1,2],[2,1],[2,2]] == regcart 2 2
True

cdaa [[1,1,1]] == regsing 2 3
True

The counts of the integral histogram $A \in \mathcal{A}_{\mathrm{i}}$ of a history $H \in \mathcal{H}$ are the cardinalities of the event identifier components of its classification, $A = \mathrm{histogram}(H)$ where $\mathrm{histogram}(H) := \{(S,|X|) : (S,X) \in H^{-1}\}$,

historiesHistogram :: History -> Histogram

For example,

let llhh = fromJust . listsHistory
    hhll = historyToList

let hhaa = historiesHistogram

let hh = llhh $ zip (map IdInt [1..]) (Set.toList (cart uu vv))

let aa = llaa $ zip (Set.toList (cart uu vv)) (repeat 1)

hhaa hh == aa
True

let hhgg = historiesClassification
    gghh = classificationsHistory
    ggll = classificationsList

gghh (hhgg hh) == hh
True

llaa [(ss, toRational (Set.size xx)) | (ss,xx) <- ggll (hhgg hh)] == aa
True

Given an integral histogram $A \in \mathcal{A}_{\mathrm{i}}$, a history $H$ can be constructed by creating an event identifier for each element of each component of the classification, $H = \mathrm{history}(A)$ where $\mathrm{history}(A) := \bigcup \{\{((S,i),S) : i \in \{1 \ldots q\}\} : (S,q) \in A\}$,

histogramsHistory :: Histogram -> Maybe History

For example,

let aahh = fromJust . histogramsHistory

hhaa (aahh aa) == aa
True

rpln $ hhll $ aahh $ regdiag 3 2 
"(({(1,1),(2,1)},1),{(1,1),(2,1)})"
"(({(1,2),(2,2)},1),{(1,2),(2,2)})"
"(({(1,3),(2,3)},1),{(1,3),(2,3)})"

rpln $ hhll $ aahh $ regdiag 3 2 `mul` scalar 3
"(({(1,1),(2,1)},1),{(1,1),(2,1)})"
"(({(1,1),(2,1)},2),{(1,1),(2,1)})"
"(({(1,1),(2,1)},3),{(1,1),(2,1)})"
"(({(1,2),(2,2)},1),{(1,2),(2,2)})"
"(({(1,2),(2,2)},2),{(1,2),(2,2)})"
"(({(1,2),(2,2)},3),{(1,2),(2,2)})"
"(({(1,3),(2,3)},1),{(1,3),(2,3)})"
"(({(1,3),(2,3)},2),{(1,3),(2,3)})"
"(({(1,3),(2,3)},3),{(1,3),(2,3)})"

Note that multiplication of histograms is described below.

A sub-histogram $B$ of a histogram $A$ is such that the effective states of $B$ are a subset of the effective states of $A$ and the counts of $B$ are less than or equal to those of $A$, $B \leq A := B^{\mathrm{FS}} \subseteq A^{\mathrm{FS}}~\wedge~\forall S \in B^{\mathrm{FS}}~(B_S \leq A_S)$,

pairHistogramsLeq :: Histogram -> Histogram -> Bool

For example,

let leq = pairHistogramsLeq

rp bb
"{({(rank,A),(suit,spades)},1 % 1)}"

bb `leq` aa
True

[xx `leq` aa | xx <- [aa,bb,cc,dd,scalar 1,norm aa,ee]]
[True,True,True,False,False,True,False]

The reduction of a histogram is the reduction of its states, adding the counts where two different states reduce to the same state, \[ A\%V := \{(R, \sum (c : (T, c) \in A,~T \supseteq R)) : R \in \{S\%V : S \in A^{\mathrm{S}}\}\} \]

setVarsHistogramsReduce :: Set.Set Variable -> Histogram -> Histogram 

For example,

let ared aa vv = setVarsHistogramsReduce vv aa

rpln $ aall $ aa `ared` Set.singleton suit
"({(suit,clubs)},13 % 1)"
"({(suit,diamonds)},13 % 1)"
"({(suit,hearts)},13 % 1)"
"({(suit,spades)},13 % 1)"

rpln $ aall $ aa `ared` Set.singleton rank
"({(rank,A)},4 % 1)"
"({(rank,J)},4 % 1)"
"({(rank,K)},4 % 1)"
"({(rank,Q)},4 % 1)"
"({(rank,2)},4 % 1)"
"({(rank,3)},4 % 1)"
"({(rank,4)},4 % 1)"
"({(rank,5)},4 % 1)"
"({(rank,6)},4 % 1)"
"({(rank,7)},4 % 1)"
"({(rank,8)},4 % 1)"
"({(rank,9)},4 % 1)"
"({(rank,10)},4 % 1)"

rp $ aa `ared` Set.empty
"{({},52 % 1)}"

aa `ared` vars aa == aa
True

The reduction to the empty set is a scalar, $A\%\emptyset = \{(\emptyset,z)\}$, where $z = \mathrm{size}(A)$,

aa `ared` Set.empty == scalar (size aa)
True

Reduction leaves the size of a histogram unchanged,

size `map` [aa, aa `ared` Set.singleton suit, aa `ared` Set.singleton rank, aa `ared` Set.empty]
[52 % 1,52 % 1,52 % 1,52 % 1]

The histogram of a reduction of a history equals the reduction of the histogram of the history, \[ \mathrm{histogram}(H~\%~V) = \mathrm{histogram}(H)~\%~V \]

let vs = Set.singleton suit

hhaa (hh `hred` vs) == hhaa hh `ared` vs
True

The addition of histograms $A$ and $B$ is defined, \[ \begin{eqnarray} A + B &:=& \{ (S, c) : (S,c) \in A,~S \notin B^{\mathrm{S}} \}~\cup\\ & & \{ (S, c + d) : (S,c) \in A,~(T,d) \in B,~S = T \}~\cup \\ & & \{ (T, d) : (T,d) \in B,~T \notin A^{\mathrm{S}} \} \end{eqnarray} \] where $\mathrm{vars}(A) = \mathrm{vars}(B)$.

pairHistogramsAdd :: Histogram -> Histogram -> Maybe Histogram

For example,

let add xx yy = fromJust $ pairHistogramsAdd xx yy

rp bb
"{({(rank,A),(suit,spades)},1 % 1)}"

rp cc
"{({(rank,A),(suit,spades)},1 % 1),({(rank,Q),(suit,hearts)},1 % 1)}"

rp dd
"{({(rank,A),(suit,spades)},1 % 1),({(rank,Q),(suit,hearts)},2 % 1)}"

rp $ bb `add` cc
"{({(rank,A),(suit,spades)},2 % 1),({(rank,Q),(suit,hearts)},1 % 1)}"

rp $ cc `add` dd
"{({(rank,A),(suit,spades)},2 % 1),({(rank,Q),(suit,hearts)},3 % 1)}"

rp $ bb `add` cc `add` dd
"{({(rank,A),(suit,spades)},3 % 1),({(rank,Q),(suit,hearts)},3 % 1)}"

The sizes add, $\mathrm{size}(A+B) = \mathrm{size}(A) + \mathrm{size}(B)$,

size bb + size cc + size dd == size (bb `add` cc `add` dd)
True

The histogram of an addition of histories equals the addition of the histograms of the histories, \[ \mathrm{histogram}(H_1+H_2) = \mathrm{histogram}(H_1) + \mathrm{histogram}(H_2) \]

let hh = aahh aa

let gg = aahh bb

hhaa (hh `hadd` gg) == hhaa hh `add` hhaa gg
True

The multiplication of histograms $A$ and $B$ is the product of the counts where the states join, \[ A*B := \{ (S \cup T, cd) : (S,c) \in A,~(T,d) \in B,~\forall v \in \mathrm{vars}(S) \cap \mathrm{vars}(T)~(S_v = T_v)\} \]

pairHistogramsMultiply :: Histogram -> Histogram -> Histogram

For example,

let mul = pairHistogramsMultiply

let colour = VarStr "colour"
    red = ValStr "red"; black = ValStr "black"

let bb = llaa [(llss [(suit, u),(colour, w)],1) | (u,w) <- [(hearts, red), (clubs, black), (diamonds, red), (spades, black)]]

rpln $ aall bb
"({(colour,black),(suit,clubs)},1 % 1)"
"({(colour,black),(suit,spades)},1 % 1)"
"({(colour,red),(suit,diamonds)},1 % 1)"
"({(colour,red),(suit,hearts)},1 % 1)"

rpln $ aall $ aa `mul` bb
"({(colour,black),(rank,A),(suit,clubs)},1 % 1)"
"({(colour,black),(rank,A),(suit,spades)},1 % 1)"
"({(colour,black),(rank,J),(suit,clubs)},1 % 1)"
"({(colour,black),(rank,J),(suit,spades)},1 % 1)"
"({(colour,black),(rank,K),(suit,clubs)},1 % 1)"
"({(colour,black),(rank,K),(suit,spades)},1 % 1)"
...
"({(colour,red),(rank,8),(suit,diamonds)},1 % 1)"
"({(colour,red),(rank,8),(suit,hearts)},1 % 1)"
"({(colour,red),(rank,9),(suit,diamonds)},1 % 1)"
"({(colour,red),(rank,9),(suit,hearts)},1 % 1)"
"({(colour,red),(rank,10),(suit,diamonds)},1 % 1)"
"({(colour,red),(rank,10),(suit,hearts)},1 % 1)"

rpln $ aall $ aa `mul` bb `ared` Set.fromList [rank,colour]
"({(colour,black),(rank,A)},2 % 1)"
"({(colour,black),(rank,J)},2 % 1)"
...
"({(colour,black),(rank,9)},2 % 1)"
"({(colour,black),(rank,10)},2 % 1)"
"({(colour,red),(rank,A)},2 % 1)"
"({(colour,red),(rank,J)},2 % 1)"
...
"({(colour,red),(rank,9)},2 % 1)"
"({(colour,red),(rank,10)},2 % 1)"

rpln $ aall $ aa `mul` bb `ared` Set.singleton colour
"({(colour,black)},26 % 1)"
"({(colour,red)},26 % 1)"

If the variables are disjoint, the sizes multiply, $\mathrm{vars}(A) \cap \mathrm{vars}(B) = \emptyset \implies \mathrm{size}(A*B) = \mathrm{size}(A) \times \mathrm{size}(B)$,

let coin = VarStr "coin"
    heads = ValStr "heads"; tails = ValStr "tails"

let cc = llaa [(llss [(coin,heads)], 1),(llss [(coin,tails)], 1)]

rpln $ aall cc
"({(coin,heads)},1 % 1)"
"({(coin,tails)},1 % 1)"

rpln $ aall $ aa `mul` cc
"({(coin,heads),(rank,A),(suit,clubs)},1 % 1)"
"({(coin,heads),(rank,A),(suit,diamonds)},1 % 1)"
"({(coin,heads),(rank,A),(suit,hearts)},1 % 1)"
"({(coin,heads),(rank,A),(suit,spades)},1 % 1)"
"({(coin,heads),(rank,J),(suit,clubs)},1 % 1)"
"({(coin,heads),(rank,J),(suit,diamonds)},1 % 1)"
...
"({(coin,heads),(rank,9),(suit,hearts)},1 % 1)"
"({(coin,heads),(rank,9),(suit,spades)},1 % 1)"
"({(coin,heads),(rank,10),(suit,clubs)},1 % 1)"
"({(coin,heads),(rank,10),(suit,diamonds)},1 % 1)"
"({(coin,heads),(rank,10),(suit,hearts)},1 % 1)"
"({(coin,heads),(rank,10),(suit,spades)},1 % 1)"
"({(coin,tails),(rank,A),(suit,clubs)},1 % 1)"
"({(coin,tails),(rank,A),(suit,diamonds)},1 % 1)"
"({(coin,tails),(rank,A),(suit,hearts)},1 % 1)"
"({(coin,tails),(rank,A),(suit,spades)},1 % 1)"
"({(coin,tails),(rank,J),(suit,clubs)},1 % 1)"
"({(coin,tails),(rank,J),(suit,diamonds)},1 % 1)"
...
"({(coin,tails),(rank,9),(suit,hearts)},1 % 1)"
"({(coin,tails),(rank,9),(suit,spades)},1 % 1)"
"({(coin,tails),(rank,10),(suit,clubs)},1 % 1)"
"({(coin,tails),(rank,10),(suit,diamonds)},1 % 1)"
"({(coin,tails),(rank,10),(suit,hearts)},1 % 1)"
"({(coin,tails),(rank,10),(suit,spades)},1 % 1)"

size aa
52 % 1

size cc
2 % 1

size (aa `mul` cc) == size aa * size cc
True

rpln $ aall $ aa `mul` cc `ared` Set.singleton coin
"({(coin,heads)},52 % 1)"
"({(coin,tails)},52 % 1)"

Multiplication by a scalar scales the size, $\mathrm{size}(\mathrm{scalar}(z)*A) = z \times \mathrm{size}(A)$,

size $ scalar 2
2 % 1

size $ scalar 2 `mul` aa
104 % 1

The histogram of a multiplication of histories equals the multiplication of the histograms of the histories, \[ \mathrm{histogram}(H_1*H_2) = \mathrm{histogram}(H_1) * \mathrm{histogram}(H_2) \]

let hh = aahh aa

let gg = aahh bb

hhaa (hh `hmul` gg) == hhaa hh `mul` hhaa gg
True

The reciprocal of a histogram is $1/A := \{(S, 1/c) : (S, c) \in A,~c>0\}$,

histogramsReciprocal :: Histogram -> Histogram

Define histogram division as $B/A := B*(1/A)$,

pairHistogramsDivide :: Histogram -> Histogram -> Histogram

For example,

let recip = histogramsReciprocal
    divide = pairHistogramsDivide

scalar (1 % 2) == recip (scalar 2)
True

aa `divide` scalar 52 == norm aa
True

scalar (1 % 2) == scalar 1 `divide` scalar 2
True

A histogram $A$ is causal in a subset of its variables $K \subset V$ if the reduction of the effective states to the subset, $K$, is functionally related to the reduction to the complement, $V \setminus K$, \[ \{(S~\%~K,~S~\%~(V \setminus K)) : S \in A^{\mathrm{FS}}\} \in K^{\mathrm{CS}} \to (V \setminus K)^{\mathrm{CS}} \] or \[ \mathrm{split}(K,A^{\mathrm{FS}}) \in K^{\mathrm{CS}} \to (V \setminus K)^{\mathrm{CS}} \]

histogramsIsCausal :: Histogram -> Bool

In the example, the histogram of the deck of cards, $A$, is cartesian and not causal,

let iscausal = histogramsIsCausal 

iscausal aa
False

The histogram of the colours of the suits, $B$, however, is causal from suit to colour,

rpln $ aall bb
"({(colour,black),(suit,clubs)},1 % 1)"
"({(colour,black),(suit,spades)},1 % 1)"
"({(colour,red),(suit,diamonds)},1 % 1)"
"({(colour,red),(suit,hearts)},1 % 1)"

iscausal bb
True

let ssplit = setVarsSetStatesSplit 

rpln $ Set.toList $ ssplit (Set.singleton suit) (states (eff bb))
"({(suit,clubs)},{(colour,black)})"
"({(suit,diamonds)},{(colour,red)})"
"({(suit,hearts)},{(colour,red)})"
"({(suit,spades)},{(colour,black)})"

rpln $ Set.toList $ ssplit (Set.singleton colour) (states (eff bb))
"({(colour,black)},{(suit,clubs)})"
"({(colour,black)},{(suit,spades)})"
"({(colour,red)},{(suit,diamonds)})"
"({(colour,red)},{(suit,hearts)})"

iscausal $ aa `mul` bb
True

rpln $ Set.toList $ ssplit (Set.fromList [suit,rank]) (states (eff (aa `mul` bb)))
"({(rank,A),(suit,clubs)},{(colour,black)})"
"({(rank,A),(suit,diamonds)},{(colour,red)})"
"({(rank,A),(suit,hearts)},{(colour,red)})"
"({(rank,A),(suit,spades)},{(colour,black)})"
"({(rank,J),(suit,clubs)},{(colour,black)})"
"({(rank,J),(suit,diamonds)},{(colour,red)})"
...
"({(rank,9),(suit,hearts)},{(colour,red)})"
"({(rank,9),(suit,spades)},{(colour,black)})"
"({(rank,10),(suit,clubs)},{(colour,black)})"
"({(rank,10),(suit,diamonds)},{(colour,red)})"
"({(rank,10),(suit,hearts)},{(colour,red)})"
"({(rank,10),(suit,spades)},{(colour,black)})"

A histogram $A$ is diagonalised if no pair of effective states shares any value, $\forall S,T \in A^{\mathrm{FS}}~(S \neq T \implies S \cap T = \emptyset)$,

histogramsIsDiagonal :: Histogram -> Bool

For example,

let isdiag = histogramsIsDiagonal

isdiag aa
False

isdiag bb
False

isdiag $ aa `mul` bb
False

In a diagonalised histogram the causality is bijective or equational, \[ \forall u,w \in V~(\{(S\%{u},S\%{w}) : S \in A^{\mathrm{FS}}\}~\in~\{u\}^{\mathrm{CS}} \leftrightarrow \{w\}^{\mathrm{CS}}) \]

let saturation = VarStr "saturation"
    white = ValStr "white"; grey = ValStr "grey"; black = ValStr "black"

let dd = llaa [(llss [(colour, u),(saturation, w)],1) | (u,w) <- [(red, grey), (black, black)]]

rpln $ aall dd
"({(colour,black),(saturation,black)},1 % 1)"
"({(colour,red),(saturation,grey)},1 % 1)"

isdiag dd
True

Similarly for a regular unit histograms,

rpln $ aall $ regdiag 3 2
"({(1,1),(2,1)},1 % 1)"
"({(1,2),(2,2)},1 % 1)"
"({(1,3),(2,3)},1 % 1)"

iscausal $ regdiag 3 2
True

isdiag $ regdiag 3 2
True

iscausal $ regcart 3 2
False

isdiag $ regcart 3 2
False

iscausal $ regsing 3 2
True

isdiag $ regsing 3 2
True

iscausal $ regdiag 3 2 `add` regcart 3 2 
False

isdiag $ regdiag 3 2 `add` regcart 3 2 
False

iscausal $ regdiag 3 2 `add` regsing 3 2 
True

isdiag $ regdiag 3 2 `add` regsing 3 2 
True

Given some slice state $R \in K^{\mathrm{CS}}$, where $K \subset V$ and $V = \mathrm{vars}(A)$, the slice histogram, $A * \{R\}^{\mathrm{U}} \subset A$, is said to be contingent on the incident slice state,

let rr = llss [(suit,spades)]

rpln $ aall $ aa `mul` unit (Set.singleton rr)
"({(rank,A),(suit,spades)},1 % 1)"
"({(rank,J),(suit,spades)},1 % 1)"
"({(rank,K),(suit,spades)},1 % 1)"
"({(rank,Q),(suit,spades)},1 % 1)"
"({(rank,2),(suit,spades)},1 % 1)"
"({(rank,3),(suit,spades)},1 % 1)"
"({(rank,4),(suit,spades)},1 % 1)"
"({(rank,5),(suit,spades)},1 % 1)"
"({(rank,6),(suit,spades)},1 % 1)"
"({(rank,7),(suit,spades)},1 % 1)"
"({(rank,8),(suit,spades)},1 % 1)"
"({(rank,9),(suit,spades)},1 % 1)"
"({(rank,10),(suit,spades)},1 % 1)"

For example, if the slice histogram is diagonalised, $\mathrm{diagonal}(A * \{R\}^{\mathrm{U}}~\%~(V \setminus K))$, then the histogram, $A$, is said to be contingently diagonalised,

let ee = (cdaa [[1]] `mul` (regdiag 2 2 `cdtp` [2,3])) `add` (cdaa [[2]] `mul` (regcart 2 2 `cdtp` [2,3]))

rpln $ aall $ ee
"({(1,1),(2,1),(3,1)},1 % 1)"
"({(1,1),(2,2),(3,2)},1 % 1)"
"({(1,2),(2,1),(3,1)},1 % 1)"
"({(1,2),(2,1),(3,2)},1 % 1)"
"({(1,2),(2,2),(3,1)},1 % 1)"
"({(1,2),(2,2),(3,2)},1 % 1)"

rpln $ aall $ ee `mul` cdaa [[1]]
"({(1,1),(2,1),(3,1)},1 % 1)"
"({(1,1),(2,2),(3,2)},1 % 1)"

let vk = Set.fromList (map VarInt [2,3])

isdiag $ ee `mul` cdaa [[1]] `ared` vk
True

rpln $ aall $ ee `mul` cdaa [[2]]
"({(1,2),(2,1),(3,1)},1 % 1)"
"({(1,2),(2,1),(3,2)},1 % 1)"
"({(1,2),(2,2),(3,1)},1 % 1)"
"({(1,2),(2,2),(3,2)},1 % 1)"

isdiag $ ee `mul` cdaa [[2]] `ared` vk
False

Independent Histograms

The perimeters of a histogram $A \in \mathcal{A}$ is the set of its reductions to each of its variables, $\{A\%\{w\} : w \in V\}$, where $V = \mathrm{vars}(A)$,

rpln $ aall $ aa `ared` Set.singleton suit
"({(suit,clubs)},13 % 1)"
"({(suit,diamonds)},13 % 1)"
"({(suit,hearts)},13 % 1)"
"({(suit,spades)},13 % 1)"

rpln $ aall $ aa `ared` Set.singleton rank
"({(rank,A)},4 % 1)"
"({(rank,J)},4 % 1)"
"({(rank,K)},4 % 1)"
"({(rank,Q)},4 % 1)"
"({(rank,2)},4 % 1)"
"({(rank,3)},4 % 1)"
"({(rank,4)},4 % 1)"
"({(rank,5)},4 % 1)"
"({(rank,6)},4 % 1)"
"({(rank,7)},4 % 1)"
"({(rank,8)},4 % 1)"
"({(rank,9)},4 % 1)"
"({(rank,10)},4 % 1)"

The independent of a histogram is the product of the normalised perimeters scaled to the size, \[ A^{\mathrm{X}} := Z * \prod_{w \in V} \hat{A}\%\{w\} \] where $z = \mathrm{size}(A)$ and $Z = \mathrm{scalar}(z) = A\%\emptyset$,

histogramsIndependent :: Histogram -> Histogram

For example,

let ind = histogramsIndependent

ind aa == scalar (size aa) `mul` (norm aa `ared` Set.singleton suit) `mul` (norm aa `ared` Set.singleton rank)
True

The size is unchanged, $\mathrm{size}(A^{\mathrm{X}}) = \mathrm{size}(A)$,

size (ind aa) == size aa
True

A histogram is said to be independent if it equals its independent, $A = A^{\mathrm{X}}$,

aa == ind aa
True

regdiag 2 2 == ind (regdiag 2 2)
False

Scalar histograms are independent, $\{(\emptyset,z)\} = \{(\emptyset,z)\}^{\mathrm{X}}$,

scalar 52 == ind (scalar 52)
True

Singleton histograms, $|A^{\mathrm{F}}| = 1$, are independent, $\{(S,z)\} = \{(S,z)\}^{\mathrm{X}}$,

regsing 2 2 == ind (regsing 2 2)
True

If the histogram is mono-variate, $|V|=1$, then it is independent $A = A \% \{w\} = A^{\mathrm{X}}$ where $\{w\} = V$,

regdiag 2 2 `ared` Set.singleton (VarInt 1) == ind (regdiag 2 2 `ared` Set.singleton (VarInt 1))
True

Cartesian histograms are independent, $V^{\mathrm{C}} = V^{\mathrm{CX}}$,

regcart 2 2 == ind (regcart 2 2)
True

aa == ind aa
True

The independent of a uniform fully diagonalised histogram equals the sized cartesian,

norm (ind (regdiag 2 2)) == norm (regcart 2 2)
True

A completely effective pluri-variate independent histogram, $A^{\mathrm{XF}} = V^{\mathrm{C}}$ where $|V|>1$, for which all of the variables are pluri-valent, $\forall w \in V~(|U_w| > 1)$, must be non-causal,

iscausal (ind (regdiag 2 2))
False

iscausal (regdiag 2 2)
True

Substrate structures

The set of substrate histories $\mathcal{H}_{U,V,z}$ is the set of histories having event identifiers $\{1 \ldots z\}$, fixed size $z$ and fixed variables $V$, \[ \begin{eqnarray} \mathcal{H}_{U,V,z} &:=& \{1 \ldots z\} :\to V^{\mathrm{CS}}\\ &=& \{H : H \subseteq \{1 \ldots z\} \times V^{\mathrm{CS}},~\mathrm{dom}(H) = \{1 \ldots z\},~|H|=z\} \end{eqnarray} \]

systemsSetVarsSizesHistorySubstrate :: System -> Set.Set Variable -> Integer -> Maybe (Set.Set History)

For example,

let uu' = sysreg 2 2

let hhvvz uu z = fromJust $ systemsSetVarsSizesHistorySubstrate uu (uvars uu) z

rpln $ Set.toList $ hhvvz uu' 3
"{(1,{(1,1),(2,1)}),(2,{(1,1),(2,1)}),(3,{(1,1),(2,1)})}"
"{(1,{(1,1),(2,1)}),(2,{(1,1),(2,1)}),(3,{(1,1),(2,2)})}"
"{(1,{(1,1),(2,1)}),(2,{(1,1),(2,1)}),(3,{(1,2),(2,1)})}"
"{(1,{(1,1),(2,1)}),(2,{(1,1),(2,1)}),(3,{(1,2),(2,2)})}"
"{(1,{(1,1),(2,1)}),(2,{(1,1),(2,2)}),(3,{(1,1),(2,1)})}"
"{(1,{(1,1),(2,1)}),(2,{(1,1),(2,2)}),(3,{(1,1),(2,2)})}"
...
"{(1,{(1,2),(2,2)}),(2,{(1,2),(2,1)}),(3,{(1,1),(2,2)})}"
"{(1,{(1,2),(2,2)}),(2,{(1,2),(2,1)}),(3,{(1,2),(2,1)})}"
"{(1,{(1,2),(2,2)}),(2,{(1,2),(2,1)}),(3,{(1,2),(2,2)})}"
"{(1,{(1,2),(2,2)}),(2,{(1,2),(2,2)}),(3,{(1,1),(2,1)})}"
"{(1,{(1,2),(2,2)}),(2,{(1,2),(2,2)}),(3,{(1,1),(2,2)})}"
"{(1,{(1,2),(2,2)}),(2,{(1,2),(2,2)}),(3,{(1,2),(2,1)})}"
"{(1,{(1,2),(2,2)}),(2,{(1,2),(2,2)}),(3,{(1,2),(2,2)})}"

The cardinality of the substrate histories is $|\mathcal{H}_{U,V,z}| = v^z$ where $v = |V^{\mathrm{C}}|$,

Set.size $ hhvvz uu' 3
64

(2^2)^3
64

Set.size $ hhvvz uu' 7
16384

(2^2)^7
16384

The corresponding set of integral substrate histograms $\mathcal{A}_{U,\mathrm{i},V,z}$ is the set of complete integral histograms in variables $V$ with size $z$, \[ \begin{eqnarray} \mathcal{A}_{U,\mathrm{i},V,z} &:=& \{\mathrm{histogram}(H) : H \in \mathcal{H}_{U,V,z}\}\\ &=& \{A : A \in V^{\mathrm{CS}} :\to \{0 \ldots z\},~\mathrm{size}(A) = z\} \end{eqnarray} \]

systemsSetVarsSizesHistogramSubstrate :: System -> Set.Set Variable -> Integer -> Maybe (Set.Set Histogram)

For example,

let uu' = sysreg 2 2

let aavvz uu z = fromJust $ systemsSetVarsSizesHistogramSubstrate uu (uvars uu) z

rpln $ Set.toList $ aavvz uu' 3
"{({(1,1),(2,1)},0 % 1),({(1,1),(2,2)},0 % 1),({(1,2),(2,1)},0 % 1),({(1,2),(2,2)},3 % 1)}"
"{({(1,1),(2,1)},0 % 1),({(1,1),(2,2)},0 % 1),({(1,2),(2,1)},1 % 1),({(1,2),(2,2)},2 % 1)}"
"{({(1,1),(2,1)},0 % 1),({(1,1),(2,2)},0 % 1),({(1,2),(2,1)},2 % 1),({(1,2),(2,2)},1 % 1)}"
...
"{({(1,1),(2,1)},2 % 1),({(1,1),(2,2)},0 % 1),({(1,2),(2,1)},1 % 1),({(1,2),(2,2)},0 % 1)}"
"{({(1,1),(2,1)},2 % 1),({(1,1),(2,2)},1 % 1),({(1,2),(2,1)},0 % 1),({(1,2),(2,2)},0 % 1)}"
"{({(1,1),(2,1)},3 % 1),({(1,1),(2,2)},0 % 1),({(1,2),(2,1)},0 % 1),({(1,2),(2,2)},0 % 1)}"

The cardinality of integral substrate histograms is the cardinality of weak compositions, \[ \begin{eqnarray} |\mathcal{A}_{U,\mathrm{i},V,z}| &=& \frac {(z + v -1)!}{z!~(v -1)!} \end{eqnarray} \] where the factorial function is $n! := 1 \cdot 2 \cdot 3 \cdots n$. The function compositionWeak is defined in AlignmentUtil,

compositionWeak :: Integer -> Integer -> Integer

So

Set.size $ aavvz uu' 3
20

compositionWeak 3 (2^2)
20

Set.size $ Set.map hhaa $ hhvvz uu' 3
20

Set.size $ aavvz uu' 7
120

compositionWeak 7 (2^2)
120

Set.size $ Set.map hhaa $ hhvvz uu' 7
120

Example - a weather forecast

Some of the concepts above regarding histories and histograms can be demonstrated with a sample of some weather measurements. Let system $U$ consist of four variables, (i) pressure, having values low, medium and high, (ii) cloud, having values none, light and heavy, (iii) wind, having values none, light and strong, and (iv) rain, having values none, light and heavy,

let [pressure,cloud,wind,rain] = map VarStr ["pressure","cloud","wind","rain"]

let [low,medium,high,none,light,heavy,strong] = map ValStr ["low","medium","high","none","light","heavy","strong"]

let lluu ll = fromJust $ listsSystem [(v,Set.fromList ww) | (v,ww) <- ll]

let uu = lluu [
      (pressure, [low,medium,high]),
      (cloud,    [none,light,heavy]),
      (wind,     [none,light,strong]),
      (rain,     [none,light,heavy])]

rp uu
"{(cloud,{heavy,light,none}),(pressure,{high,low,medium}),(rain,{heavy,light,none}),(wind,{light,none,strong})}"

rp $ uvars uu
"{cloud,pressure,rain,wind}"

let vv = uvars uu

vol uu vv 
81

3^4
81

Now let history $H$ be constructed from the following sample,

event pressure cloud wind rain
1 high none none none
2 medium light none light
3 high none light none
4 low heavy strong heavy
5 low none light light
6 medium none light light
7 low heavy light heavy
8 high none light none
9 medium light strong heavy
10 medium light light light
11 high light light heavy
12 medium none none none
13 medium light none none
14 high light strong light
15 medium none light light
16 low heavy strong heavy
17 low heavy light heavy
18 high none none none
19 low light none light
20 high none none none
let llhh vv ev = fromJust $ listsHistory [(IdInt i, llss (zip vv ll)) | (i,ll) <- ev]

let hh = llhh [pressure,cloud,wind,rain] [
      (1,[high,none,none,none]),
      (2,[medium,light,none,light]),
      (3,[high,none,light,none]),
      (4,[low,heavy,strong,heavy]),
      (5,[low,none,light,light]),
      (6,[medium,none,light,light]),
      (7,[low,heavy,light,heavy]),
      (8,[high,none,light,none]),
      (9,[medium,light,strong,heavy]),
      (10,[medium,light,light,light]),
      (11,[high,light,light,heavy]),
      (12,[medium,none,none,none]),
      (13,[medium,light,none,none]),
      (14,[high,light,strong,light]),
      (15,[medium,none,light,light]),
      (16,[low,heavy,strong,heavy]),
      (17,[low,heavy,light,heavy]),
      (18,[high,none,none,none]),
      (19,[low,light,none,light]),
      (20,[high,none,none,none])]

rpln $ hhll hh
"(1,{(cloud,none),(pressure,high),(rain,none),(wind,none)})"
"(2,{(cloud,light),(pressure,medium),(rain,light),(wind,none)})"
"(3,{(cloud,none),(pressure,high),(rain,none),(wind,light)})"
"(4,{(cloud,heavy),(pressure,low),(rain,heavy),(wind,strong)})"
"(5,{(cloud,none),(pressure,low),(rain,light),(wind,light)})"
"(6,{(cloud,none),(pressure,medium),(rain,light),(wind,light)})"
"(7,{(cloud,heavy),(pressure,low),(rain,heavy),(wind,light)})"
"(8,{(cloud,none),(pressure,high),(rain,none),(wind,light)})"
"(9,{(cloud,light),(pressure,medium),(rain,heavy),(wind,strong)})"
"(10,{(cloud,light),(pressure,medium),(rain,light),(wind,light)})"
"(11,{(cloud,light),(pressure,high),(rain,heavy),(wind,light)})"
"(12,{(cloud,none),(pressure,medium),(rain,none),(wind,none)})"
"(13,{(cloud,light),(pressure,medium),(rain,none),(wind,none)})"
"(14,{(cloud,light),(pressure,high),(rain,light),(wind,strong)})"
"(15,{(cloud,none),(pressure,medium),(rain,light),(wind,light)})"
"(16,{(cloud,heavy),(pressure,low),(rain,heavy),(wind,strong)})"
"(17,{(cloud,heavy),(pressure,low),(rain,heavy),(wind,light)})"
"(18,{(cloud,none),(pressure,high),(rain,none),(wind,none)})"
"(19,{(cloud,light),(pressure,low),(rain,light),(wind,none)})"
"(20,{(cloud,none),(pressure,high),(rain,none),(wind,none)})"

rp $ hvars hh
"{cloud,pressure,rain,wind}"

hsize hh
20

The event identifiers are classified,

let hhgg = historiesClassification
    gghh = classificationsHistory
    ggll = classificationsList

rpln $ ggll $ hhgg hh
"({(cloud,heavy),(pressure,low),(rain,heavy),(wind,light)},{7,17})"
"({(cloud,heavy),(pressure,low),(rain,heavy),(wind,strong)},{4,16})"
"({(cloud,light),(pressure,high),(rain,heavy),(wind,light)},{11})"
"({(cloud,light),(pressure,high),(rain,light),(wind,strong)},{14})"
"({(cloud,light),(pressure,low),(rain,light),(wind,none)},{19})"
"({(cloud,light),(pressure,medium),(rain,heavy),(wind,strong)},{9})"
"({(cloud,light),(pressure,medium),(rain,light),(wind,light)},{10})"
"({(cloud,light),(pressure,medium),(rain,light),(wind,none)},{2})"
"({(cloud,light),(pressure,medium),(rain,none),(wind,none)},{13})"
"({(cloud,none),(pressure,high),(rain,none),(wind,light)},{3,8})"
"({(cloud,none),(pressure,high),(rain,none),(wind,none)},{1,18,20})"
"({(cloud,none),(pressure,low),(rain,light),(wind,light)},{5})"
"({(cloud,none),(pressure,medium),(rain,light),(wind,light)},{6,15})"
"({(cloud,none),(pressure,medium),(rain,none),(wind,none)},{12})"

The history can be reduced to a subset of the variables,

let hred hh vv = setVarsHistoriesReduce (Set.fromList vv) hh

rpln $ hhll $ hh `hred` [pressure,rain]
"(1,{(pressure,high),(rain,none)})"
"(2,{(pressure,medium),(rain,light)})"
"(3,{(pressure,high),(rain,none)})"
...
"(18,{(pressure,high),(rain,none)})"
"(19,{(pressure,low),(rain,light)})"
"(20,{(pressure,high),(rain,none)})"

rpln $ ggll $ hhgg $ hh `hred` [pressure,rain]
"({(pressure,high),(rain,heavy)},{11})"
"({(pressure,high),(rain,light)},{14})"
"({(pressure,high),(rain,none)},{1,3,8,18,20})"
"({(pressure,low),(rain,heavy)},{4,7,16,17})"
"({(pressure,low),(rain,light)},{5,19})"
"({(pressure,medium),(rain,heavy)},{9})"
"({(pressure,medium),(rain,light)},{2,6,10,15})"
"({(pressure,medium),(rain,none)},{12,13})"

Let the sample histogram be constructed from the history, $A = \mathrm{histogram}(H)$,

let aa = hhaa hh

rpln $ aall aa
"({(cloud,heavy),(pressure,low),(rain,heavy),(wind,light)},2 % 1)"
"({(cloud,heavy),(pressure,low),(rain,heavy),(wind,strong)},2 % 1)"
"({(cloud,light),(pressure,high),(rain,heavy),(wind,light)},1 % 1)"
"({(cloud,light),(pressure,high),(rain,light),(wind,strong)},1 % 1)"
"({(cloud,light),(pressure,low),(rain,light),(wind,none)},1 % 1)"
"({(cloud,light),(pressure,medium),(rain,heavy),(wind,strong)},1 % 1)"
"({(cloud,light),(pressure,medium),(rain,light),(wind,light)},1 % 1)"
"({(cloud,light),(pressure,medium),(rain,light),(wind,none)},1 % 1)"
"({(cloud,light),(pressure,medium),(rain,none),(wind,none)},1 % 1)"
"({(cloud,none),(pressure,high),(rain,none),(wind,light)},2 % 1)"
"({(cloud,none),(pressure,high),(rain,none),(wind,none)},3 % 1)"
"({(cloud,none),(pressure,low),(rain,light),(wind,light)},1 % 1)"
"({(cloud,none),(pressure,medium),(rain,light),(wind,light)},2 % 1)"
"({(cloud,none),(pressure,medium),(rain,none),(wind,none)},1 % 1)"

rp $ vars aa
"{cloud,pressure,rain,wind}"

size aa
20 % 1

histogramsIsUniform aa
False

histogramsIsIntegral aa
True

histogramsIsUnit aa
False

size $ unit (cart uu vv)
81 % 1

eff aa `leq` unit (cart uu vv)
True

rpln $ aall $ norm aa
"({(cloud,heavy),(pressure,low),(rain,heavy),(wind,light)},1 % 10)"
"({(cloud,heavy),(pressure,low),(rain,heavy),(wind,strong)},1 % 10)"
"({(cloud,light),(pressure,high),(rain,heavy),(wind,light)},1 % 20)"
"({(cloud,light),(pressure,high),(rain,light),(wind,strong)},1 % 20)"
"({(cloud,light),(pressure,low),(rain,light),(wind,none)},1 % 20)"
"({(cloud,light),(pressure,medium),(rain,heavy),(wind,strong)},1 % 20)"
"({(cloud,light),(pressure,medium),(rain,light),(wind,light)},1 % 20)"
"({(cloud,light),(pressure,medium),(rain,light),(wind,none)},1 % 20)"
"({(cloud,light),(pressure,medium),(rain,none),(wind,none)},1 % 20)"
"({(cloud,none),(pressure,high),(rain,none),(wind,light)},1 % 10)"
"({(cloud,none),(pressure,high),(rain,none),(wind,none)},3 % 20)"
"({(cloud,none),(pressure,low),(rain,light),(wind,light)},1 % 20)"
"({(cloud,none),(pressure,medium),(rain,light),(wind,light)},1 % 10)"
"({(cloud,none),(pressure,medium),(rain,none),(wind,none)},1 % 20)"

Now consider the relationships (a) between pressure and rain,

histogramsIsDiagonal aa
False

histogramsIsCausal aa
False

let red aa ll = setVarsHistogramsReduce (Set.fromList ll) aa
    ssplit ll aa = Set.toList (setVarsSetStatesSplit (Set.fromList ll) (states aa))

rpln $ aall $ aa `red` [pressure,rain]
"({(pressure,high),(rain,heavy)},1 % 1)"
"({(pressure,high),(rain,light)},1 % 1)"
"({(pressure,high),(rain,none)},5 % 1)"
"({(pressure,low),(rain,heavy)},4 % 1)"
"({(pressure,low),(rain,light)},2 % 1)"
"({(pressure,medium),(rain,heavy)},1 % 1)"
"({(pressure,medium),(rain,light)},4 % 1)"
"({(pressure,medium),(rain,none)},2 % 1)"

rpln $ ssplit [pressure] (aa `red` [pressure,rain])
"({(pressure,high)},{(rain,heavy)})"
"({(pressure,high)},{(rain,light)})"
"({(pressure,high)},{(rain,none)})"
"({(pressure,low)},{(rain,heavy)})"
"({(pressure,low)},{(rain,light)})"
"({(pressure,medium)},{(rain,heavy)})"
"({(pressure,medium)},{(rain,light)})"
"({(pressure,medium)},{(rain,none)})"

histogramsIsCausal $ aa `red` [pressure,rain]
False

and (b) between (i) cloud and wind, and (ii) rain,

rpln $ aall $ aa `red` [cloud,wind,rain]
"({(cloud,heavy),(rain,heavy),(wind,light)},2 % 1)"
"({(cloud,heavy),(rain,heavy),(wind,strong)},2 % 1)"
"({(cloud,light),(rain,heavy),(wind,light)},1 % 1)"
"({(cloud,light),(rain,heavy),(wind,strong)},1 % 1)"
"({(cloud,light),(rain,light),(wind,light)},1 % 1)"
"({(cloud,light),(rain,light),(wind,none)},2 % 1)"
"({(cloud,light),(rain,light),(wind,strong)},1 % 1)"
"({(cloud,light),(rain,none),(wind,none)},1 % 1)"
"({(cloud,none),(rain,light),(wind,light)},3 % 1)"
"({(cloud,none),(rain,none),(wind,light)},2 % 1)"
"({(cloud,none),(rain,none),(wind,none)},4 % 1)"

rpln $ ssplit [cloud,wind] (aa `red` [cloud,wind,rain])
"({(cloud,heavy),(wind,light)},{(rain,heavy)})"
"({(cloud,heavy),(wind,strong)},{(rain,heavy)})"
"({(cloud,light),(wind,light)},{(rain,heavy)})"
"({(cloud,light),(wind,light)},{(rain,light)})"
"({(cloud,light),(wind,none)},{(rain,light)})"
"({(cloud,light),(wind,none)},{(rain,none)})"
"({(cloud,light),(wind,strong)},{(rain,heavy)})"
"({(cloud,light),(wind,strong)},{(rain,light)})"
"({(cloud,none),(wind,light)},{(rain,light)})"
"({(cloud,none),(wind,light)},{(rain,none)})"
"({(cloud,none),(wind,none)},{(rain,none)})"

histogramsIsCausal $ aa `red` [cloud,wind,rain]
False

Although the sample histogram is neither diagonal nor causal, it is not independent, $A \neq A^{\mathrm{X}}$,

aa == ind aa
False

The perimeters are

rpln $ aall $ aa `red` [pressure]
"({(pressure,high)},7 % 1)"
"({(pressure,low)},6 % 1)"
"({(pressure,medium)},7 % 1)"

rpln $ aall $ aa `red` [cloud]
"({(cloud,heavy)},4 % 1)"
"({(cloud,light)},7 % 1)"
"({(cloud,none)},9 % 1)"

rpln $ aall $ aa `red` [wind]
"({(wind,light)},9 % 1)"
"({(wind,none)},7 % 1)"
"({(wind,strong)},4 % 1)"

rpln $ aall $ aa `red` [rain]
"({(rain,heavy)},6 % 1)"
"({(rain,light)},7 % 1)"
"({(rain,none)},7 % 1)"

The sample independent is

rpln $ aall $ ind aa
"({(cloud,heavy),(pressure,high),(rain,heavy),(wind,light)},189 % 1000)"
"({(cloud,heavy),(pressure,high),(rain,heavy),(wind,none)},147 % 1000)"
"({(cloud,heavy),(pressure,high),(rain,heavy),(wind,strong)},21 % 250)"
"({(cloud,heavy),(pressure,high),(rain,light),(wind,light)},441 % 2000)"
...
"({(cloud,none),(pressure,medium),(rain,light),(wind,strong)},441 % 2000)"
"({(cloud,none),(pressure,medium),(rain,none),(wind,light)},3969 % 8000)"
"({(cloud,none),(pressure,medium),(rain,none),(wind,none)},3087 % 8000)"
"({(cloud,none),(pressure,medium),(rain,none),(wind,strong)},441 % 2000)"

The weather forecast example continues in Entropy and alignment.


top