Henry Laxen
November 27, 2011

I wanted to take a look at lenses the other day, since I haven't used them before, and I thought while I was at it I might as well write it up in case you, gentle reader, find yourself in the same position. I found a couple of excellent resources online, one on stackoverflow, and some cs notes from Stanford. If you really want a good understanding of the how and why's of lenses, take a look at the Stanford lecture mentioned above. If you just want to use lenses and understand what they do, not how they do it, read on.

This file should load under ghci and you are encouraged to do so and play around. First some imports. We need TemplateHaskell because we are going to be lazy, just like the language, and let it define the lenses for us.

> {-# LANGUAGE TemplateHaskell #-}
> import Data.Lens.Lazy
>     ( (~=), access, (%=), mapLens, (^=), (^.), (^%=), (^%%=), (^$) )
> import Data.Lens.Template ( makeLenses )
> import Data.Char ( toUpper )
> import Data.Map ( Map, fromList )
> import Control.Monad.State.Lazy ( Monad(return), State, runState )
Next we define the all too familiar Person data type, which has an Address data type as one of its fields
> data Person = Person {
>   _fullName :: String,
>   _familiarName :: String,
>   _surName  :: String,
>   _address  :: Address } 
>              
> data Address = Address {
>   _which :: String,
>   _street :: String,
>   _city :: String,
>   _state :: String,
>   _zip  :: String }
I don't really like the default version of show for Person and Address, and it is easy enough to define your own.
> showsPerson :: Person -> String -> String
> showsPerson (Person s1 s2 s3 a1) x =
>   concat ["\n",s1,"\n",s2," ",s3,"\n",show a1,x]
> showsAddress :: Address -> String -> String
> showsAddress (Address s1 s2 s3 s4 s5) x = 
>   concat [s1, ": ",
>           s2, "\n      ",
>           s3, " ",
>           s4, " ",
>           s5, "\n",
>           x]
> instance Show Person where     
>   showsPrec _ = showsPerson
> instance Show Address where     
>   showsPrec _ = showsAddress
Here we make TemplateHaskell do the dirty work, of defining the Lenses for us using the above field names.
> $( makeLenses [''Person, ''Address] )
Here is some sample data
> henry = Person
>   "Henry Herman Laxen"
>   "Henry"
>   "Laxen"
>   (Address 
>     "home"
>     "Via Alta #6"
>     "Chapala"
>     "Jalisco"
>     "45900")
running henry in ghci results in:
Henry Herman Laxen
Henry Laxen
home: Via Alta #6
      Chapala Jalisco 45900

Define upper convert a string to upper case, just so we have a nice function of type (a -> a) lying around

> upper :: String -> String
> upper = Prelude.map toUpper
Now lets see what these things do:
> test1 = address ^$ henry
*Main> test1
home: Via Alta #6
Chapala Jalisco 45900
> test2 = henry ^. address
*Main> test2
home: Via Alta #6
      Chapala Jalisco 45900
> test3 = street ^$ address ^$ henry
*Main> test3
"Via Alta #6"
> test4 = (henry ^. address) ^. street
*Main> test4
"Via Alta #6"
whereas
> -- test4a = henry ^. address ^. street 
results in
    Couldn't match expected type `Data.Lens.Common.Lens Person Address'
                with actual type `Address'
    Expected type: Data.Lens.Common.Lens
                     (Data.Lens.Common.Lens Person Address)
                     (Data.Lens.Common.Lens Person b0)
      Actual type: Data.Lens.Common.Lens Address String
    In the second argument of `(^.)', namely `street'
    In the second argument of `(^.)', namely `address ^. street'
so if we want to drill down to a specific field, we had better use the (^$) version of the getter

That's all for getters, now let's look at setters and modifiers.

> test5 = fullName ^= "Henry H. Laxen" $ henry
*Main> test5

Henry H. Laxen
Henry Laxen
home: Via Alta #6
      Chapala Jalisco 45900
> test6 = fullName ^%= upper   $ henry
*Main> test6

HENRY HERMAN LAXEN
Henry Laxen
home: Via Alta #6
      Chapala Jalisco 45900
> test7 = fullName ^%= upper   $ test5
*Main> test7

HENRY H. LAXEN
Henry Laxen
home: Via Alta #6
      Chapala Jalisco 45900
To do more interesting things, I always need my wife.
> nadine = Person
>   "Nadine Callaway Laxen"
>   "Nadine"
>   "Laxen"
>   (address ^$ henry)
Another way of creating nadine, since she lives at the same address, and has the same last name.
> nadineAgain :: Person
> nadineAgain = (fullName ^= "Nadine Callaway Laxen") .
>               (familiarName ^= "Nadine") $ henry
A silly example of using fmap.
> addMister :: String -> Maybe String
> addMister x = Just ( "Mr. " ++ x )
> mister :: Maybe Person
> mister = fullName ^%%= addMister $ henry
*Main> mister
Just 
Mr. Henry Herman Laxen
Henry Laxen
home: Via Alta #6
      Chapala Jalisco 45900
There is also a Lenses way of manipulating Maps
> type ByFamiliarName = Map String Person
> justHenry :: ByFamiliarName
> justHenry = fromList [("Henry",henry)]
> addNadine :: ByFamiliarName -> ByFamiliarName
> addNadine = mapLens "Nadine" ^= Just nadine
> removeHenry :: ByFamiliarName -> ByFamiliarName
> removeHenry = mapLens "Henry" ^= Nothing    
> test8 = addNadine justHenry
*Main> test8
fromList [("Henry",
Henry Herman Laxen
Henry Laxen
home: Via Alta #6
      Chapala Jalisco 45900
),("Nadine",
Nadine Callaway Laxen
Nadine Laxen
home: Via Alta #6
      Chapala Jalisco 45900
)]
> test9 = removeHenry (addNadine justHenry)
*Main> test9
fromList [("Nadine",
Nadine Callaway Laxen
Nadine Laxen
home: Via Alta #6
      Chapala Jalisco 45900
)]
I also wanted to try out the Stateful operators
> changeFamiliarWithState :: State Person String
> changeFamiliarWithState = do
>   x <- access familiarName
>   if x == "Nadine" then familiarName ~= "Sweetie"
>                   else familiarName %= upper     
>   return x
> test10 = runState changeFamiliarWithState henry
*Main> test10
("Henry",
Henry Herman Laxen
HENRY Laxen
home: Via Alta #6
      Chapala Jalisco 45900
)
You'll notice that runState :: State s a -> s -> (a, s) so that the first part of the tuple returned is "Henry", because of the return x, and the second part is the updated state, which in this case since the familiarName wasn't Nadine is changed to upper case.
> test11 = runState changeFamiliarWithState nadine
*Main> test11
("Nadine",
Nadine Callaway Laxen
Sweetie Laxen
home: Via Alta #6
      Chapala Jalisco 45900
)
In this test, since the familiar name was Nadine, we change it to Sweetie in the state, and return it unchanged as the result.

So I would say, there are just a few things you should have at your fingertips when using lenses, namely:
to get something:
      drill ^$ down ^$ to   ^$ theData 
      Lens     Lens    Lens    Top Level Data
to set something:
       (field ^=  newValue) :: DataType -> DataType 
       Lens      value
to modify something:
       (field ^%=  function) :: DataType -> DataType 
        Lens       function :: (value -> value)
The rest you can look up and figure out.

Quote of the day:
Ninety percent of the politicians give the other ten percent a bad reputation.
Henry Kissinger

Sitemap
Go up to Haskell Go up to Home Page of Nadine Loves Henry
Go back to A look at Heist, MVars and Anansi Continue with Nadine and Henry's Calcudoku Solver