def. Optics are a family of inter-composable combinators for building bidirectional data transformations
type Lens s t a b = forall f. Functor f => (a -> f b) -> (s -> f t)
lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b
makeLenses
makeLensesFor
view ^.
set .~
over %~
+~, -~, *~, //~
^~, ^^~, **~
||~, &&~
<>~
<+~, <<+~, ...
- You get what you set
- Setting back what you got doesn't do anything
- Setting twice is the same as setting on
type Fold s a = forall f (Contravariant f, Applicative f) => (a -> f b) -> (s -> f t)
toListOf ^..
maximumOf, minimumOf
maximumByOf, minimumByOf
elemOf
anyOf
allOf
findOf
has, hasn't
sumOf, productOf
firstOf, preview, ^?
lastOf
traverseOf, traverseOf_
forOf, forOf_
foldOf, foldByOf
foldMapOf, foldMapByOf
foldrOf, foldlOf
folded
both
each
folding
to
taking, takingWhile
dropping, droppingWhile
filtered
filteredBy (>=4.18.0)
backwards
only :: Eq a => a -> Fold a ()
-- Word with most consonants
maximumByOf
worded
(compare `on` (length . filter (`elem` "aeiou")))
"Do or do not, there is no try."
type Traversal s t a b = forall f. Applicative f => (a -> f b) -> (s -> f t)
traverseOf, %%~
forOf
sequenceAOf
A lot of our Folds were Traversal in disguise.
traversed
worded, lined
beside :: Traversal s t a b -> Traversal s' t' a b -> Traversal (s, s') (t, t') a b
element :: Traversable f => Int -> Traversal' (f a) a
elementOf :: Traversal' s a -> Int -> Traversal' s a
_head
_tail
- Respect Purity
traverseOf myTraversal pure x == pure x
- Consistent Focuses
fmap (traverseOf myTrav f) . traverseOf myTrav g $ x
==
getCompose . traverseOf myTrav (Compose . fmap f . g) $ x
class Ixed where ix :: Index m -> Traversal' m (IxValue m)
class At where at :: Index m -> Lens' m (Maybe (IxValue m))
(?~) :: Traversal s t a (Maybe b) -> b -> s -> t
sans :: At m => Index m -> m -> m
Recall the example: newtype Cycled a = Cycled [a]
Recall the example: record and creating a data type over the fields.
Recall the example: newtype CaseInsensitive v = CaseInsensitive (Map.Map String v)
makePrisms
prism :: (b -> t) -> (s -> Either t a) -> Prism s t a b
prims' :: (b -> s) -> (s -> Maybe a) -> Prism s s a b
review, #
_Left, _Right
_Nothing, _Just
has, ins't :: Prism s t a b -> s -> Bool
class Cons where _Cons :: Prism s t (a, s) (b, t)
class AsEmpty where _Empty :: Prism' a ()
_Show :: (Read a, Show a) => Prism' String a
Recall the example: _Prefix :: String -> Prism' String String
Recall the example: _Factor :: Int -> Prism' Int Int
Recall the example: _ListCons :: Prism [a] [b] (a, [a]) (b, [b])
Recall the example: _Cycles :: (Eq a) => Int -> Prism' [a] [a]
Recall the simple server example:
_PathPrefix :: String -> Prism' Request Request
oustide :: Prism s t a b -> Lens (t -> r) (s -> r) (b -> r) (a -> r)
safeTail :: [a] -> [a]
safeTail = tail & outside _Empty .~ const []
- review-preview
preview p (review p value) == Just value
- prism complement
let Just a = preview myPrism s
s'= review myPrism a
in s == s'
- pass-through reversion
If the prism fails to match and we type cast the structure into a new type; that we can use the same prism to type cast it back into its original type."
>>> let Left t = matching l s
>>> let Left s' = matching l t
s == s'
iso :: (s -> a) -> (b -> t) -> Iso s t a b
involuted :: (a -> a) -> Iso' a a
-- makeLenses on a newtype creates an Iso!
newtype Email = Email { _email :: Text }
makeLenses ''Email
- converting between encodings
- text formats
- strict <-> lazy representations
- data structures with different performance: List <-> Vector
- more
from :: Iso' s a -> Iso' a s
Data.Text.Lens.packed
Data.Text.Lens.unpacked
reversed :: Iso' [a] [a]
swapped :: Iso' (a, b) (b, a)
flipped :: Iso' (a -> b -> c) (b -> a -> c)
curried :: Iso' ((a, b) -> c) (a -> b -> c)
uncurried :: Iso' (a -> b -> c) ((a, b) -> c)
import Numeric.Lens
>>> 10 ^. negated
>>> 30 & negated %~ (+ 10)
>>> 100 ^. adding 50
>>> 100.0 ^. dividing 10
>>> 0 & multiplying 4 +~ 12
Recall the fahrenheit iso
mapping' :: Functor f => Iso' s a -> Iso' (f s) (f a)
-- >>> ("Beauty", "Age") ^. mapping reversed . swapped
contramapping :: (Contravariant f) => Iso' s a -> Iso (f a) (f s)
bimapping :: (Bifunctor f) => Iso' s a -> Iso' s' a' -> Iso' (f s s') (f a a')
dimapping :: (Profunctor p) => Iso' s a -> Iso' s' a' -> Iso' (p a s') (p s a')
-- ^^^ functions, ..
textToYamlList :: [Text] -> Text
textToYamlList = toYamlList ^. dimapping (mapping unpacked) packed
enum :: Enum a -> Iso' Int a
coerced :: (Coercible s a, Coercible t b) => Iso s t a b
makeWrapped ''Email
_Wrapped' :: Wrapped s => Iso' s (Unwrapped s)
_Unwrapped' :: Wrapped s => Iso' (Unwrapped s) s
- Reversability
myIso . from myIso == id
from myIso . myIso == id
Indexed optics compose just fine with indexed and non-indexed optics alike
-- Just prefix an 'i' ('@' for infix form)
itoListOf (^@..)
iover (%@~)
itraverseOf (%%@~)
...
-- >>> itraverseOf_
-- itraversed
-- (\i s -> putStrLn (replicate i ' ' <> s))
-- ["one", "two", "three"]
-- Index composition
(<.), (<.>), (.>)
(.>) == (.)
icompose :: (i -> j -> k)
-> IndexedOptics i s t a b
-> IndexedOptics j a b c d
-> IndexedOptics k s t c d
-- >>> board ^@.. icompose showCoordinates itraversed itraversed
-- If you use it a lot, better define an operator:
(<symbol>) :: (Indexed <indexTypeA> s t -> r)
-> (Indexed <indexTypeB> a b -> s -> t)
-> Indexed <combinedType> a b -> r
(<symbol>) = icompose <combinationFunction>
-- Filtering by indices
indices :: (Indexable i p, Applicative f)
=> (i -> Bool) -> Optical' p (Indexed i) f a a
-- Target an exact index
index :: (Indexable i p, Eq i, Applicative f)
=> i -> Optical' p (Indexed i) f a a
-- >>> sumOf (itraversed . indices (== "Wednesday") . traversed) exercises
-- >>> exercises ^@.. (itraversed <. itraversed . indices (== "pushups"))
indexing :: Traversal s t a b -> IndexedTraversal Int s t a b
indexing :: Lens s t a b -> IndexedLens Int s t a b
indexing :: Fold s a -> IndexedFold Int s a
indexing :: Getter s a -> IndexedGetter Int s a
-- >>> ("hello" :: Text) ^@.. indexing each
-- [(0,'h'),(1,'e'),(2,'l'),(3,'l'),(4,'o')]
reindexed :: Indexable j p => (i -> j) -> (Indexed i a b -> r) -> p a b -> r
-- >>> toMapOf (reindexed show itraversed) ['a'..'c']
selfIndex :: Indexable a p => p a fb -> a -> fb
-- invertedIndex :: IndexedTraversal Int [a] [b] a b
-- invertedIndex =
-- reindexed
-- (\(xs, i) -> (length xs - 1) - i)
-- (selfIndex <.> itraversed)
-- Index-preserving optics
cloneIndexPreservingLens :: Lens s t a b
-> IndexPreservingLens s t a b
cloneIndexPreservingTraversal :: Traversal s t a b
-> IndexPreservingTraversal s t a b
cloneIndexPreservingSetter :: Setter s t a b
-> IndexPreservingSetter s t a b
-- >>> let _1' = cloneIndexPreservingLens _1
-- >>> [('a', True), ('b', False), ('c', True)] ^@.. itraversed <. _1'
Custom indexed:
slotsFold :: IndexedFold (Position, Position) (Board a) a
slotsFold =
ifolding $ \board ->
zip [(x, y) | y <- [I, II, III], x <- [I, II, III]]
(toList board)
pair :: IndexedFold Bool (a, a) a
pair = ifolding $ \(a, b) -> [(False, a), (True, b)]
pair' :: IndexedTraversal Bool (a, a) (b, b) a b
pair' p (a, a1) = liftA2 (,) (indexed p False a) (indexed p True a1)
There are operators to work with ReaderT and StateT.
view :: MonadReader s m => Getting a s a -> m a
-- getUserPassword :: ReaderT Env IO ()
-- getUserPassword = do
-- userName <- view currentUser
-- maybePassword <- preview (users . ix userName)
-- liftIO $ print maybePassword
(.=) :: MonadStates m=> Lens s s a b -> b -> m ()
use :: MonadStates m=> Lens's a -> m a
(<>=) = <>~ but for MonadState
uses :: MonadState s m => Lens' s a -> (a -> r) -> m r
(<~) :: MonadState s m => Lens s s a b -> m b -> m b -> m ()
(<+=), (<<+=), (<<~), ...
-- saleCalculation :: StateT Till IO ()
-- saleCalculation = do
-- total .= 0
-- total += 8.55
-- total += 7.36
-- totalSale <- use total
-- liftIO $ printf "Total sale: $%.2f\n" totalSale
-- sales <>= [totalSale]
-- total <~ uses taxRate (totalSale *)
-- taxIncluded <- use total
-- liftIO $ printf "Tax included: $%.2f\n" taxIncluded
-- Magnify & Zoom
magnify :: Lens' s a -> ReaderT a m r -> ReaderT s m r
zoom :: Monad m => Lens' s a -> StateT a m r -> StateT s m r
Classy Lenses is a design pattern that solves one of the following design needs:
- Polymorphism over specific record fields
- Separating layers of logic without cross-dependencies
- Isolating the 'knowledge' of a given module of code
makeFields, makeFieldsNoPrefix, makeClassy
-- makeFields
data Person =
Person { _personName :: String
} deriving Show
data Pet =
Pet { _petName :: String
} deriving Show
makeFields ''Person
makeFields ''Pet
-- generates
class HasName s a | s -> a where
name :: Lens' s a
{-# MINIMAL name #-}
instance HasName Person String
instance HasName Pet String
-- makeFields will look for the appropiate Has* class in scope, if it exists already it will
-- just implement an instance. If it can't find an existing instance it will both define the class AND
-- implement an instance.
--
-- This means that if you have two isolated modules which each define HasName classes but neither of the
-- imports each-other, that they'll inadvertently define two separate and incompatible versions of the HasName.
--
-- You can define a separate module just for that field which calls makeFields on a dummy record, then export
-- only the field typeclass for other modules to import.
-- Example
initialize :: ( MonadIO m
, HasHostName e String
, HasPortNumber e Int
, MonadReader e m
)
=> m ()
initialize = do
port <- view portNumber
host <- view hostName
liftIO $ putStrLn ("initializing server at: " <> host <> ":" <> show port)
-}
-- makeClassy
data Person' =
Person' { _name :: String
, _favouriteFood :: String
} deriving Show
makeClassy ''Person
-- generates
class HasPerson c where
person :: Lens' c Person
favouriteFood :: Lens' c String
name :: Lens' c String
{-# MINIMAL person #-}