Skip to content

Instantly share code, notes, and snippets.

@mmakowski
Last active December 10, 2015 22:48
Show Gist options
  • Save mmakowski/4504744 to your computer and use it in GitHub Desktop.
Save mmakowski/4504744 to your computer and use it in GitHub Desktop.
module Lenses where
import Prelude hiding ((.), id)
import Control.Category
data Lens s a = Lens (s -> a) ((a -> a) -> s -> s)
instance Category Lens where
id = Lens id id
(Lens lg lm) . (Lens rg rm) = Lens (lg . rg) (rm . lm)
(^.) :: s -> Lens s a -> a
s ^. (Lens f _) = f s
(%=) :: Lens s a -> (a -> a) -> s -> s
(Lens _ m) %= f = m f
(^=) :: Lens s a -> a -> s -> s
l ^= a = l %= (const a)
infixl 8 ^.
infixr 4 %=
infixr 4 ^=
data Point = Point { x :: Double, y :: Double }
deriving (Eq, Show)
xLens :: Lens Point Double
xLens = Lens x (\f p -> p { x = f (x p) })
yLens :: Lens Point Double
yLens = Lens y (\f p -> p { y = f (y p) })
data Circle = Circle { origin :: Point
, radius :: Double
}
deriving (Eq, Show)
originLens :: Lens Circle Point
originLens = Lens origin (\f c -> c { origin = f (origin c) })
radiusLens :: Lens Circle Double
radiusLens = Lens radius (\f c -> c { radius = f (radius c) })
doubleX = (xLens . originLens) %= (*2)
{-
Kmett's lenses:
Store comonad
Store: a pair of:
- value (from a structure)
- an updater, that given a value will produce an updated structure (structure doesn't have to be supplied!)
not very clear why comonad.
van Laarhoven lenses: just a type synonym, so we can use standard fn composition
-}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment