Skip to content

Evaluator

Evaluator.hs
module Evaluator where


import Chess ( display, Board(..), SquareState(HasPiece) )
import Control.Monad.Except ( MonadError(throwError) )
import Control.Monad.State ( MonadState(put, get), gets, modify ) 
import Data.Text ( Text ) 
import Parser ( Instruction(..), ChessError(ReplError, Exit) )

evaluate :: (MonadError ChessError m, MonadState Board m) => 
  Instruction -> m Text
evaluate instr = case instr of
  ReplInstruction "quit" -> throwError Exit -- (1)!
  ReplInstruction "display" -> gets display -- (2)!
  Set file rank piece -> do
    (Board boardFunc) <- get -- (3)!
    let newBoard =
          Board -- (4)!
            ( \f r ->
                if f == file && r == rank
                  then HasPiece piece
                  else boardFunc f r
            )
    put newBoard -- (5)!
    return $ display newBoard
  ReplInstruction _ -> throwError $ ReplError "no such instruction"
  1. Throw an error of type ChessError. This is what requires the MonadError ChessError constraint.
  2. gets display is the same as fmap display get: it accesses the state (of type Board), which requires the MonadState Board constraint, and applies display to it, to return a Text value.
  3. get is the local state. It takes no arguments.
  4. Recall that a Board value represents the board as a function from a File and Rank to a square state, so this function is what we need to change, when updating the Board.
  5. put takes an argument and sets the state to that argument.

Analysis

MonadError and MonadState are typeclasses for types with the ability to throw errors and mutate local state respectively. See the monad transformer library (mtl) for more.

With that in mind, read the type signature of evaluate as follows: evaluate is a function that takes an Instruction and returns Text, but with the possibility of throwing an error of type ChessError, and of changing the state (of type Board).

We can think of evaluate as taking a synactic description of an Instruction and evaluating it into a result. For example ReplInstruction "quit" is a description of an instruction, but throwError Exit is the actually "program" that will quit the repl.

evaluate

evaluate :: (MonadError ChessError m, MonadState Board m) => 
    Instruction -> m Text
evaluate instr = case instr of
    ReplInstruction "quit" -> throwError Exit
    ReplInstruction "display" -> gets display
    Set file rank piece -> do
        (Board boardFunc) <- get
        let newBoard =
            Board
                ( \f r ->
                    if f == file && r == rank
                    then HasPiece piece
                    else boardFunc f r
                )
        put newBoard
        return $ display newBoard
    ReplInstruction _ -> throwError $ ReplError "no such instruction"
evaluate' :: (MonadError ChessError m, MonadState Board m) => 
    Instruction -> m Text
evaluate' = \case
    ReplInstruction "quit" -> throwError Exit
    ReplInstruction "display" -> gets display
    Set file rank piece -> do
        (Board boardFunc) <- get
        let newBoard =
            Board
                ( \f r ->
                    if f == file && r == rank
                    then HasPiece piece
                    else boardFunc f r
                )
        put newBoard
        return $ display newBoard
    ReplInstruction _ -> throwError $ ReplError "no such instruction"
evaluate :: (MonadError ChessError m, MonadState Board m) => 
    Instruction -> m Text
evaluate instr = case instr of
    ReplInstruction "quit" -> throwError Exit
    ReplInstruction "display" -> gets display
    Set file rank piece -> do
        let updateBoard (Board boardFunc) = Board ( \f r ->
            if f == file && r == rank
                then HasPiece piece
                else boardFunc f r)
        modify updateBoard
        gets display
    ReplInstruction _ -> throwError $ ReplError "no such instruction"

Last update: February 14, 2023
Created: August 18, 2022

Comments