Challenge

Let’s draw out what we expect the model to look like

These two questions have something in common. They are asking for Markov Models.
Let’s try to represent these models as objects.

set.seed(42) # For reproducibility
MarkovModel <- setClass(
  "MarkovModel",
  
  slots = c(
    model.name = "character",
    transition.matrix = "data.frame",
    initial.probabilities = "numeric",
    num.transitions = "numeric",
    output = "character"
    ), # end of slots
  
  prototype = list(
    model.name = "", 
    transition.matrix = data.frame(),
    initial.probabilities = 0,
    num.transitions = 0,
    output = ""
    ), # end of prototype
  
  validity =  function(object) {}
)

Now that we’ve made our MarkovModel class, let’s create the parameters for Q1

transition.matrix <- data.frame("A" = c(0, 1), "B" = c(1, 0))
rownames(transition.matrix) <- c("A", "B")

initial.probabilities <- c("A" = 1, "B" = 0)


Q1 <- MarkovModel(model.name = "Q1", 
            transition.matrix = transition.matrix,
            initial.probabilities = initial.probabilities,
            num.transitions = 10
)

Great. Object Q1 of class MarkovModel now exists.
Let’s create some functions that will do the predicting for us.

state_prob <- function(trans.mat, from_state) {
  # Indexes through a dataframe by row and slices for the matching state.
  # Returns a named vector of that row
  return(unlist(trans.mat[from_state, ]))
}
transition <- function(state_change_prob) {
  # Takes named vector as input and returns name of starting option 
  # based on state change probability
  sample(x = names(state_change_prob), size =  1, prob = state_change_prob)
}

From here, we can use the functions we made to step through

# Get starting state (in this case, will always be A)
starting_state <- transition(Q1@initial.probabilities)

# Look at object transition matrix, get new probabilities
new_prob <- state_prob(Q1@transition.matrix, starting_state)

# State transition (B)
second_state <- transition(new_prob)

# Repeat
new_prob <- state_prob(Q1@transition.matrix, second_state)

# State transition (A)
third_state <- transition(new_prob)

# Repeat as desired
c(starting_state, second_state, third_state)
## [1] "A" "B" "A"

Although the logic is there, this was a pain to write. Let’s automate it!
Let’s turn it into a function that calls the previous functions.

automate_markov_transitions <- function(MarkovModel) {
  # Automates the Markov process.
  
  # Set starting state
  state <- transition(MarkovModel@initial.probabilities)
  
  # Will return the series of state changes
  total_states <- c(state)
    
  transition_count <- 0
  
  while (transition_count < MarkovModel@num.transitions) {
    new_prob <- state_prob(MarkovModel@transition.matrix, state)
    state <- transition(new_prob)
    total_states <- append(total_states, state)
    transition_count <- transition_count + 1
  }
  
  return(total_states)
}
automate_markov_transitions(Q1)
##  [1] "A" "B" "A" "B" "A" "B" "A" "B" "A" "B" "A"

Wow! Amazing!

Let’s see if this works with Q2

transition.matrix <- data.frame("A" = c(0, 0, 0, 0, 0.25),
                                "B" = c(0, 0, 0, 0, 0.25),
                                "C" = c(0, 0, 0, 0, 0.25), 
                                "D" = c(0, 0, 0, 0, 0.25), 
                                "E" = c(1, 1, 1, 1, 0)
                                )
rownames(transition.matrix) <- c("A", "B", "C", "D", "E")

initial.probabilities <- c("A" = 0.25, "B" = 0.25, "C" = 0.25, "D" = 0.25, "E" = 0)


Q2 <- MarkovModel(model.name = "Q2", 
            transition.matrix = transition.matrix,
            initial.probabilities = initial.probabilities,
            num.transitions = 10
)

automate_markov_transitions(Q2)
##  [1] "C" "E" "B" "E" "C" "E" "B" "E" "B" "E" "A"

Looks like it works! Let’s build this into our class using methods.

setGeneric(name = "doMarkovThing", function(theObject, transition_num) standardGeneric("doMarkovThing"))
## [1] "doMarkovThing"
setMethod(f = "doMarkovThing",
          signature = "MarkovModel",
          def=function(theObject)
            {
            theObject@output <- automate_markov_transitions(theObject)
            validObject(theObject)
            return(theObject)
            }
          )
Q1 <- doMarkovThing(Q1); Q2 <- doMarkovThing(Q2);

Q1@output; Q2@output
##  [1] "A" "B" "A" "B" "A" "B" "A" "B" "A" "B" "A"
##  [1] "A" "E" "B" "E" "C" "E" "A" "E" "C" "E" "B"