45
HASKELL LENSES SIVA JAYARAMAN [2014-10-29 WED] 0

San diego hug lens presentation

Embed Size (px)

Citation preview

Page 1: San diego hug lens presentation

HASKELLLENSES

SIVA JAYARAMAN[2014-10-29 WED]

0

Page 2: San diego hug lens presentation

WHAT?Lenses (as a concept) are a way to focus and accessdeeply into a complex structure.

"poking around inside things""access" here means read, write, modify, fold, traverse,etc

lens is a package which provides an implementation ofthe concept of lenses or functional references.

Availble through cabal: cabal install lensThere are many other lens packages but this is the onewe're going to look at today

We will only cover a subset in this sessionLens is a vast topic and needs a lot of time tounderstand and useBasic usage can be learnt quickly and the payoff isworth it

Page 3: San diego hug lens presentation

WHY?Convenience - will see later with an examplelens forms a combinator library and providescomposition, multiplicity, etc.

We'll see some of these behaviours hereIt also provides a number of generalizations of lensesincluding Prism, Traversal, Iso and Fold.Can be used on many data types.

We'll see a few here such as record syntax, lists, etc

Page 4: San diego hug lens presentation

MOTIVATING SIMPLEEXAMPLE

Time to look at some code

Page 5: San diego hug lens presentation

SOME BASIC IDEAS OF NOTEA lens is a first class value that can be passed around likeany other data structurelenses compose. We've seen in the example code wherewe drill two levels down in a data structure throughcompositon

The fact that they compose is very powerful and cangive rise to succint code that is more understandable

This is akin to 'dotted' notation in OO languagesalthough we're not quite modifying state

Some of the basic uses of lenses do not need the use ofthis library

The lens library, of course, provides a lot of valueaddition

So, how might we create a lens without using this library?

Page 6: San diego hug lens presentation

HOW MIGHT I CREATE ALENS

We saw an example of a simple usage of lensIn order to better understand lenses, let's try reinvent asmall part of the lens library

Page 7: San diego hug lens presentation

OUR OWN BASIC LENS

Page 8: San diego hug lens presentation

STARTING OUTFor this purpose, we'll treat a Lens as a combination of agetter/setter

data NaiveLens s a = NaiveLens { getL :: s -> a, setL :: a -> s -> s}

-- view function to focus on a particular part of the data structureview :: NaiveLens s a -> s -> a

-- set function to set a particular part of the data structureset :: NaiveLens s a -> a -> s -> s

-- composing two lenses:{let composeNaiveLenses :: NaiveLens s1 s2 -> NaiveLens s2 a -> NaiveLens s1 a composeNaiveLenses (NaiveLens getter1 setter1) (NaiveLens getter2 setter2) = NaiveLens (getter2 . getter1) (\a s -> setter1 (setter2 a (getter1 s)) s):}

Page 9: San diego hug lens presentation

USAGEtype TimeStamp = Integer

data FrameHeader = FrameHeader { _frameNum :: FrameNumber, _ts :: TimeStamp } deriving Show

type FramePayload = String

data Frame = Frame {_header :: FrameHeader, _payload :: FramePayload} deriving Show

-- lens for each fieldfheader :: NaiveLens Frame FrameHeaderftimestamp :: NaiveLens FrameHeader TimeStamp

-- composed 'timestamp' lensftimestamp :: NaiveLens Frame TimeStampftimestamp = fheader `composeNaiveLenses` ftimestamp

Page 10: San diego hug lens presentation

EXTENDINGWhat if we want to update a value instead of get or set?

We could implement it in terms of a get and then a set,but that would be inefficientWe could add a function for update as part of the lensdefinition!

data NaiveLens s a = NaiveLens { getL :: s -> a, setL :: a -> s -> s, updateL :: (a -> a) -> s -> s}

updateL :: NaiveLens s a -> (a -> a) -> s -> s

Page 11: San diego hug lens presentation

What if the function (a -> a) can fail, or need to do someIO to get the new value?We could then update NaiveLens with:

data NaiveLens s a = NaiveLens { getL :: s -> a, setL :: a -> s -> s, updateL :: (a -> a) -> s -> s updateM :: (a -> Maybe a) -> s -> Maybe s updateL :: (a -> IO a) -> s -> IO s}

Page 12: San diego hug lens presentation

Or, even generalize:data NaiveLens s a = NaiveLens { getL :: s -> a, setL :: a -> s -> s, updateL :: (a -> a) -> s -> s updateF :: Functor f => (a -> f a) -> s -> f s}

Page 13: San diego hug lens presentation

AND, NOW FOR SOMETHINGCOMPLETELY DIFFERENT

Page 14: San diego hug lens presentation

EVEN MORE GENERALIZATIONWhat if, we could turn this:

into this:

Note: I've not understood yet why we need the forall hereas the type compile even without it

data NaiveLens s a = NaiveLens { getL :: s -> a, setL :: a -> s -> s, updateL :: (a -> a) -> s -> s updateF :: Functor f => (a -> f a) -> s -> f s}

:set -XRankNTypes -- forall needs 'RankNTypes' language extensiontype BetterLens s a = forall f . Functor f => (a -> f a) -> s -> f s

Page 15: San diego hug lens presentation

HOW DOES BETTERLENS WORK?How is the type alias BetterLens even able to do thethings NaiveLens was doing?What we need is a function like this for a setter

:{-- Simply convert BetterLens to something that has the type of setLlet set :: BetterLens s a -> (a -> s -> s) set lns a s = undefined:}

Page 16: San diego hug lens presentation

type BetterLens s a = forall f . Functor f => (a -> f a) -> s -> f s

By selecting functor for f above,Identity:{let set :: BetterLens s a -> (a -> s -> s) set lns a s = runIdentity $ -- To unwrap the Identity functor. -- Note that BetterLens gives f s -- and we need s lns (\x -> Identity a) s -- Note how we ignore the current value and wrap 'a' -- into Identity -- set lns a = runIdentity . lns (Identity . const a):}

Page 17: San diego hug lens presentation

type BetterLens s a = forall f . Functor f => (a -> f a) -> s -> f s

By selecting functor for f above,Identity:{-- The lens library calls 'modify' as 'over'let over :: BetterLens s a -> (a -> a) -> s -> s over lns f = runIdentity . lns (Identity . f):}

Page 18: San diego hug lens presentation

type BetterLens s a = forall f . Functor f => (a -> f a) -> s -> f s

Now, how can this be useful for view?view is of the type BetterLens s a -> (s -> a)BetterLens is a type alias for a function that returns fs)

What we need is aSo, we need something that goes from f s to aHow are we going to achieve that?Can we somehow encode a into f?

Page 19: San diego hug lens presentation

INTRODUCING THE CONST FUNCTORtype BetterLens s a = forall f . Functor f => (a -> f a) -> s -> f s

Remember the const function we saw earlier?const :: x -> y -> x-- a function that takes two values, ignores the second and-- gives back the first

The ( Functor is a functor that ignores its argument,just like the const function did

Const v)

newtype Const x y = Const x

getConst :: Const x y -> xgetConst (Const x) = x

instance Functor (Const v) where fmap f (Const x) = Const x -- note that f is unused

We can use the Const functor to encode a into f

Page 20: San diego hug lens presentation

type BetterLens s a = forall f . Functor f => (a -> f a) -> s -> f s

By selecting Const functor for f above,:{let view :: BetterLens s a -> (s -> a) view lns s = getConst $ lns Const s -- here, Const has type a -> Const a a -- So, if Const a a is being used as the first argument -- of lns, it must be of type f a, with f being Const a:}

Page 21: San diego hug lens presentation

HOW TO MAKE A LENS?So far, we've been tiptoeing around the actualimplementation of the lensesNow, let's do it

Page 22: San diego hug lens presentation

LENS FOR THE FRAMEHEADER CLASS WESAW BEFORE

type BetterLens s a = forall f . Functor f => (a -> f a) -> s -> f s

type FrameNumber = Integertype TimeStamp = Integerdata FrameHeader = FrameHeader { _frameNum :: FrameNumber, _ts :: TimeStamp } deriving Show

frameNum :: BetterLens FrameHeader FrameNumber-- frameNum :: Functor f => (FrameNumber -> f FrameNumber) ->-- (FrameHeader -> f FrameHeader)

frameNum fn (FrameHeader frameNum' ts') = fmap (\frameNum'' -> FrameHeader frameNum'' ts') (fn frameNum')

Page 23: San diego hug lens presentation

SOME NOTESThe getConst doesn't have runtime cost

True given that the lens impl. (e.g. frameNum) and vieware inlined

Note that lenses do compose

Page 24: San diego hug lens presentation

COMPOSING LENSEStype BetterLens s a = forall f . Functor f => (a -> f a) -> s -> f s

composeL :: BetterLens w1 w2 -> BetterLens w2 a -> BetterLens w1 a

We can rewrite this-- lens1 :: (w2 -> f w2> -> (w1 -> f w1)type lens1 = BetterLens w1 w2-- lens2 :: (a -> f a> -> (w2 -> f w2)type lens2 = BetterLens w2 a

-- tadalens1 . lens2 :: (a -> f a) -> (w1 -> f w1)

So, lens composition is simply function composition

Page 25: San diego hug lens presentation

WHAT'S IN A NAMELet's change our type synonym's name to

type Lens' s a = forall f . Functor f => (a -> f a) -> s -> f s

This version of lens that takes two type variables asparameters is defined in Lens library

There is also another versiontype Lens s t a b = forall f . Functor f => (a -> f b) -> s -> f t

we won't go much into this

Page 26: San diego hug lens presentation

HELPER TO CREATE LENSESIf we look at the lens we created above:

frameNum :: Lens' FrameHeader FrameNumberframeNum fn (frameNum' ts') = fmap (\frameNum'' -> FrameHeader frameNum'' ts') (fn frameNum')

it can also be created using the lens helper functionlens :: (s -> a) -> (s -> b -> t) -> Lens s t a b-- for the case where type of a & b are same and type of s & t are samelens :: (s -> a) -> (s -> a -> s) -> Lens s s a a-- or lens :: (s -> a) -> (s -> a -> s) -> Lens' s a

frameNum = lens (\(FrameHeader fnum _) -> fnum) (\(FrameHeader _ ts') newFnum -> FrameHeader newFnum ts)

Page 27: San diego hug lens presentation

AUTOMATIC CREATION OF LENSESIf we look at the lens we created above:

frameNum :: Lens' FrameHeader FrameNumberframeNum fn (frameNum' ts') = fmap (\frameNum'' -> FrameHeader frameNum'' ts') (fn frameNum')

-- or

frameNum = lens (\(FrameHeader fnum _) -> fnum) (\(FrameHeader _ ts') newFnum -> FrameHeader newFnum ts)

the implementation of frameNum is just boiler-plate code.lens library comes with template haskell code to automate

thisimport Control.Lens.TH

data FrameHeader = FrameHeader { _frameNum :: FrameNumber, _ts :: TimeStamp } deriving Show

makeLenses ''FrameHeader

This creates two lenses frameNum and ts like the onesdiscussed previously

Page 28: San diego hug lens presentation

AUTOMATIC CREATION OF LENSESWITHOUT APPENDAGES

What if you don't like the underscores in field names that THrequires?

There are many variations of TH code that you can use tomake these lenses

One variation is something likeimport Control.Lens.TH

data FrameHeader = FrameHeader { frameNum :: FrameNumber, ts :: TimeStamp } deriving Show

makeLensesFor [("frameNum", "frameNumLens"), ("ts", "tsLens")] ''FrameHeader

which creates lenses frameNumLens and tsLens from theabove data structure

Page 29: San diego hug lens presentation

SHORTHANDThe lens library contains many `infix` versions of functions

such as set and view to make it look more imperative.We're not going over those in this session

Page 30: San diego hug lens presentation

A SIMPLE TWIST TO LENSEStype Lens' s a = forall f . Functor f => (a -> f a) -> s -> f s

What if, we change f from a Functor to an Applicative?type Traversal' s a = forall f . Applicative f => (a -> f a) -> s -> f s

We get an entirely different thing which can 'focus' onmultiple things of type a

Page 31: San diego hug lens presentation

REMINDER OF A LENStype Lens' s a = forall f . Functor f => (a -> f a) -> s -> f s

data Person = Person { firstName :: String, lastName :: String, age :: Integer }fnLens :: Lens' Person StringfnLens fn (fname' lname' age') = fmap (\fname'' -> Person fname'' lname' age') (fn fname')

Page 32: San diego hug lens presentation

A TRAVERSALtype Lens' s a = forall f . Functor f => (a -> f a) -> s -> f s

type Traversal' s a = forall f . Applicative f => (a -> f a) -> s -> f s

nTraversal :: Traversal' Person String-- nTraversal :: Applicative f => (String -> f String) -> (Person -> f Person)nTraversal fn (Person fname' lname' age') = ... -- What can this be? (\fname'' lname'' -> Person fname'' lname'' age') ... -- What can this be? (fn fname') ... -- what can this be? (fn lname')

Page 33: San diego hug lens presentation

AHA!type Lens' s a = forall f . Functor f => (a -> f a) -> s -> f s

type Traversal' s a = forall f . Applicative f => (a -> f a) -> s -> f s

nTraversal :: Traversal' Person String-- nTraversal :: Applicative f => (String -> f String) -> (Person -> f Person)nTraversal fn (Person fname' lname' age') = pure (\fname'' lname'' -> Person fname'' lname'' age') <*> (fn fname') <*> (fn lname')

Page 34: San diego hug lens presentation

WHAT CAN WE USETRAVERSALS FOR?

Remember over? over can be used on traversals as welltype Traversal' s a = forall f . Applicative f => (a -> f a) -> s -> f sover lns f = runIdentity . lns (Identity . f)nTraversal :: Traversal' Person String

example:-- Returns a Person with both firstName and lastName capitalizedover nTraversal (map toUpper) :: Person -> Person

Page 35: San diego hug lens presentation

WHAT CAN WE USETRAVERSALS FOR?

Of course, Traversals can be used for anythingTraversableExamples: changing all elements of a list, maps, trees

Page 36: San diego hug lens presentation

PRISMSLens focuses on a single element of a complex data typeTraversal focuses on multiple elemnts of a complex datatype

the focussed elements are all of the same typeBut, what if we have an algebriac data type that has manyconstructors?

This is where Prism comes in

Page 37: San diego hug lens presentation

PRISMSPrisms are like

_left :: Lens' (Either a b) a

>> view _left $ Left ()()

>> view _left $ Right ()error!

if the above is possible. Of course it is not possible.

Page 38: San diego hug lens presentation

PRISMSSo, can we use Maybe?

_left :: Lens' (Either a b) (Maybe a)

>> view _left $ Left ()Just ()

>> view _left $ Right ()Nothing

The problem is if we try to compose another Lens with it.How can we?

Page 39: San diego hug lens presentation

PRISMSSo, we should not encode a Maybe into a Lens. This is why

Prism existsLet's look at two functions that operate over prisms:

preview :: Prism' s a -> s -> Maybe areview :: Prism' s a -> a -> s

Let's look at a built-in prism _Left_Left :: Prism' (Either a b) a

>> preview _Left $ Left 10Just 10

>> preview _Left $ Right "oops"Nothing

Page 40: San diego hug lens presentation

A PRISM USAGEdata CruelData = CruelData {_cruelData :: String} deriving Show

data Greet = Hello Integer | Cruel CruelData | World String deriving Show

data Overall = Overall {_greet :: Greet} deriving Show

makeLenses ''CruelDatamakeLenses ''Overall-- THmakePrisms ''Greet

-- only upcases if Greet is Cruel. Otherwise returns Overall as isupcaseCruelty :: Overall -> OverallupcaseCruelty = (greet . _Cruel . cruelData) %~ (map toUpper)

Page 41: San diego hug lens presentation

CONTROL.LENS OPERATORSThere are tons of operators (over 100) in the Control.Lens

library. Here's a general navigation rule:Those that begin with ^ are view-likeThose that begin with ~ are over-like or set-likeThose that contain . are somehow basic (like view)Those that contain % take functions (like over)Those that begin with = are like the ones that have ~ butapply modifications to a State monad

Page 42: San diego hug lens presentation

SOME CONTROL.LENSFUNCTIONS

We've seen the following before:view, set, over, traverse. There are others that areusefultoListOf, preview, _1, … _9, _head, _tail, _init, etc

Page 43: San diego hug lens presentation

SOME EXAMPLE USAGE:import Data.Treelet t1 = Node 1 [Node 2 [Node 3 [], Node 4 []], Node 5 []]let t2 = Node 6 [Node 7 [Node 8 [], Node 9 []], Node 10 []]let t3 = Node 11 []

toListOf (traverse . traverse) [t1, t2, t3]

[1,2,3,4,5,6,7,8,9,10,11]

Page 44: San diego hug lens presentation

SOME EXAMPLE USAGE:import Data.Treelet t1 = Node 1 [Node 2 [Node 3 [], Node 4 []], Node 5 []]let t2 = Node 6 [Node 7 [Node 8 [], Node 9 []], Node 10 []]let t3 = Node 11 []

toListOf (traverse . traverse) [t1, t2, t3]

[1,2,3,4,5,6,7,8,9,10,11]

Page 45: San diego hug lens presentation

CREDITS

Several StackOverflow questions

Simon Peyton Jones's talk on LensesLens starter tutorial in FPCompleteTalk on Lenses, Folds and Traversals by Edward Kmett,author of the lens library