Cogs and Levers A blog full of technical stuff

A Quick Lap with Lens

Introduction

When working with complex data structures in Haskell, burying down to observe a piece of information can be tedious. The Lens library has been created to ease this problem. From the Lens wiki page:

Lenses are composable functional references. They allow you to access and modify data potentially very deep within a structure!

The Lens library allows you to interact with your data structures in a composable manner, making your code easier to understand - and more fun to write.

Key Points

  • Whilst there are a lot of different functions, (^.) allows you to get some data and (.~) allows you to set some data
  • makeLenses is what does all the magic of creating your accessors
  • I haven’t found anywhere that specifically says this, but it seems that your fields in a record structure need to be preceded with an underscore

An Example

{-# LANGUAGE TemplateHaskell #-}

import Control.Lens

data Ball = Ball { _position :: (Double, Double), _velocity :: (Double, Double) }
	deriving (Show)

-- create the accessors for the Ball type
makeLenses ''Ball

-- | Animates a ball's position with respect to a timestep.
-- Takes a ball's existing position and velocity and animates it
-- by the time step provided
--
animate :: Ball -> Double -> Ball
animate b t = do
	position .~ (px + vx * t, py + vy * t) $ b
  where (px, py) = b ^. position
		(vx, vy) = b ^. velocity

main :: IO ()
main = do
	-- the original ball
	let b = Ball { _position = (4.5, 6.2), _velocity = (-0.3, 1.2) }
	-- animate the ball by 1 full timestep
	let b' = animate b 1

	putStrLn $ "Initial ball : " ++ (show b)
	putStrLn $ "Animated ball: " ++ (show b')

cabal sandbox ghci

A very quick post that is based on the information from this stack overflow article on how to get a GHCi session up and running with the libraries referenced that you’ve installed using your cabal sandbox.

cd $YOUR_PACKAGE_DIR
 
# For GHC >= 7.6
ghci -no-user-package-db -package-db .cabal-sandbox/i386-linux-ghc-7.6.1-packages.conf.d
 
# For GHC < 7.6
ghci -no-user-package-conf -package-conf .cabal-sandbox/i386-linux-ghc-7.4.2-packages.conf.d

A Quick Lap with the Writer Monad

Introduction

The Writer monad allows functions to accumulate information as functions execute. According to the Hackage page:

A writer monad parameterized by the type w of output to accumulate.

Perhaps not the most verbose of descriptions, however this is rather simple to explain with a well known example. In previous programming disciplines you would have needed to log information out of your code as your program “did things”. The Writer monad allows you to write out information in a log form. This doesn’t necessarily have to be in textual log format; an example I have seen recently is to keep track of calculations used to come to a final result. The calculations put into that log sped up calculations on other figures.

The idea here is to not clutter your code having to support things like logging/tracing, etc. Employing this monad gives your code the ability to produce this output on the side without getting in the way.

Key Pieces

  • Functions in the Writer monad are decorated with Writer l r. l in this case is the type that you’ll be logging out where r is the result being returned from your function.
  • The function tell is what’s used to push another value into the log/trace/writer.
  • Operations in the Writer monad can be chained together using >>=
  • runWriter is what you’ll use to run something in the Writer monad to get your result back.

An Example

import Control.Monad.Writer

-- | Starts a value off.
-- This function doesn't perform any calculation at all, it just prepares an
-- initial value to start in the calculation pipeline
--
start :: Int -> Writer [String] Int
start x = do
  tell (["Starting with " ++ show x])
  return x

-- | Halve a value
-- Any value passed into this function gets halved
--
half :: Int -> Writer [String] Int
half x = do
  tell (["Halving " ++ show x])
  return (x `div` 2)

-- | Squares a value
-- Any value passed into this function gets squared
--
sqr :: Int -> Writer [String] Int
sqr x = do
  tell (["Squaring " ++ show x])
  return (x * x)

main :: IO ()
main = do
  let work = runWriter $ start 10 >>= half >>= sqr >>= half
  let ans  = fst work
  let log  = snd work

  putStrLn $ "Answer: " ++ show ans
  putStrLn ""
  putStrLn " ==== Log ==== "

  mapM_ putStrLn log

A Quick Lap with the State Monad

Introduction

The State monad gives functionality of both the Reader monad and Writer monad in one. When using the State monad you’re able to read the state at any time and then set it back again, providing read/write access.

Key Points

  • The function get is used to read the current state
  • The function put is used to set the state
  • runState is used to manage execution of functions that run in the State monad
  • Operations in the State monad can use >>= to be chained together
  • Functions in the State monad are decorated with State s v. Where s is the type of the state and v is the return type from the function<

An Example

import Control.Monad.State

-- | Starts a value off.
-- This function doesn't perform any calculation at all, it just prepares an
-- initial value to start in the calculation pipeline
--
start :: Int -> State [String] Int
start x = do
  put ["Starting with " ++ show x]
  return x

-- | Halve a value
-- Any value passed into this function gets halved
--
half :: Int -> State [String] Int
half x = do
  s <- get
  let ns = s ++ ["Halving " ++ show x]
  put ns
  return (x `div` 2)

-- | Squares a value
-- Any value passed into this function gets squared
--
sqr :: Int -> State [String] Int
sqr x = do
  s <- get
  let ns = s ++ ["Squaring " ++ show x]
  put ns
  return (x * x)

main :: IO ()
main = do
  let c = runState $ start 10 >>= half >>= sqr >>= half
  let work = c [""]
  let ans  = fst $ work
  let log  = snd $ work

  putStrLn $ "Answer: " ++ show ans
  putStrLn ""
  putStrLn " ==== Log ==== "

  mapM_ putStrLn log

A Quick Lap with the Reader Monad

Introduction

The Reader monad allows functions to use shared state (or a shared environment) to operate with. According to the Hackage page:

The Reader monad (also called the Environment monad). Represents a computation, which can read values from a shared environment, pass values from function to function, and execute sub-computations in a modified environment.

If many of your functions require the same shared values (think like a config file, application settings or just shared state), rather than adding a new parameter to all of your functions that require this information you can put your functions into the Reader monad which will give you access to this state.

Key Pieces

  • The Reader constructor takes the form of Reader s v where s is your state type and v is your function return type.
  • The ask function is what you’ll use to retrieve the state value for use in your own functions.
  • To run the Reader monad you use the runReader function.

An Example

import Control.Monad.Reader

-- | Shared configuration for this application.
-- Rather trivial (and useless), it just configures how our application will
-- address the user 
--
data SalutationConfig = SalutationConfig { formal :: Bool }

-- | Returns a greeting
-- Takes in someone's name and returns a greeting string
--
greeter :: String -> Reader SalutationConfig String
greeter name = do
  -- grab the configuration out
  cfg <- ask
  -- grab the "formal" setting from the config
  let f = formal cfg
  
  -- send out the value
  return (makeSalutation f ++ name)

-- | Makes a salutation for a "formal" setting
makeSalutation :: Bool -> String
makeSalutation True = "Good day, "
makeSalutation False = "Wasaaaaaaaap, "

main :: IO ()
main = do
  -- create the configuration
  let cfg = SalutationConfig { formal = False}
  -- run the reader with the configuration for a guy named "Michael"
  let msg = runReader (greeter "Michael") $ cfg

  -- "Wasaaaaaaaaaap, Michael"
  putStrLn msg