1{-# LANGUAGE CPP #-}
2{-# LANGUAGE Rank2Types #-}
3{-# LANGUAGE MultiParamTypeClasses #-}
4{-# LANGUAGE FlexibleInstances #-}
5{-# LANGUAGE Trustworthy #-}
6
7#if __GLASGOW_HASKELL__ && __GLASGOW_HASKELL__ >= 704
8{-# LANGUAGE NoPolyKinds #-}
9{-# LANGUAGE NoDataKinds #-}
10#endif
11
12-- Disable the warnings generated by 'to', 'ito', 'like', 'ilike'.
13-- These functions are intended to produce 'Getters'. Without this constraint
14-- users would get warnings when annotating types at uses of these functions.
15#if __GLASGOW_HASKELL__ >= 711
16{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}
17#endif
18
19-------------------------------------------------------------------------------
20-- |
21-- Module      :  Control.Lens.Getter
22-- Copyright   :  (C) 2012-16 Edward Kmett
23-- License     :  BSD-style (see the file LICENSE)
24-- Maintainer  :  Edward Kmett <ekmett@gmail.com>
25-- Stability   :  provisional
26-- Portability :  Rank2Types
27--
28--
29-- A @'Getter' s a@ is just any function @(s -> a)@, which we've flipped
30-- into continuation passing style, @(a -> r) -> s -> r@ and decorated
31-- with 'Const' to obtain:
32--
33-- @type 'Getting' r s a = (a -> 'Const' r a) -> s -> 'Const' r s@
34--
35-- If we restrict access to knowledge about the type 'r', we could get:
36--
37-- @type 'Getter' s a = forall r. 'Getting' r s a@
38--
39-- However, for 'Getter' (but not for 'Getting') we actually permit any
40-- functor @f@ which is an instance of both 'Functor' and 'Contravariant':
41--
42-- @type 'Getter' s a = forall f. ('Contravariant' f, 'Functor' f) => (a -> f a) -> s -> f s@
43--
44-- Everything you can do with a function, you can do with a 'Getter', but
45-- note that because of the continuation passing style ('.') composes them
46-- in the opposite order.
47--
48-- Since it is only a function, every 'Getter' obviously only retrieves a
49-- single value for a given input.
50--
51-- A common question is whether you can combine multiple 'Getter's to
52-- retrieve multiple values. Recall that all 'Getter's are 'Fold's and that
53-- we have a @'Monoid' m => 'Applicative' ('Const' m)@ instance to play
54-- with. Knowing this, we can use @'Data.Semigroup.<>'@ to glue 'Fold's
55-- together:
56--
57-- >>> (1, 2, 3, 4, 5) ^.. (_2 <> _3 <> _5)
58-- [2,3,5]
59--
60-------------------------------------------------------------------------------
61module Control.Lens.Getter
62  (
63  -- * Getters
64    Getter, IndexedGetter
65  , Getting, IndexedGetting
66  , Accessing
67  -- * Building Getters
68  , to
69  , ito
70  , like
71  , ilike
72  -- * Combinators for Getters and Folds
73  , (^.)
74  , view, views
75  , use, uses
76  , listening, listenings
77  -- * Indexed Getters
78  -- ** Indexed Getter Combinators
79  , (^@.)
80  , iview, iviews
81  , iuse, iuses
82  , ilistening, ilistenings
83  -- * Implementation Details
84  , Contravariant(..)
85  , getting
86  , Const(..)
87  ) where
88
89import Prelude ()
90
91import Control.Lens.Internal.Indexed
92import Control.Lens.Internal.Prelude
93import Control.Lens.Type
94import Control.Monad.Reader.Class as Reader
95import Control.Monad.State        as State
96import Control.Monad.Writer (MonadWriter (..))
97
98-- $setup
99-- >>> :set -XNoOverloadedStrings
100-- >>> import Control.Lens
101-- >>> import Data.List.Lens
102-- >>> import Debug.SimpleReflect.Expr
103-- >>> import Debug.SimpleReflect.Vars as Vars hiding (f,g)
104-- >>> let f :: Expr -> Expr; f = Debug.SimpleReflect.Vars.f
105-- >>> let g :: Expr -> Expr; g = Debug.SimpleReflect.Vars.g
106
107infixl 8 ^., ^@.
108
109-------------------------------------------------------------------------------
110-- Getters
111-------------------------------------------------------------------------------
112
113-- | Build an (index-preserving) 'Getter' from an arbitrary Haskell function.
114--
115-- @
116-- 'to' f '.' 'to' g ≡ 'to' (g '.' f)
117-- @
118--
119-- @
120-- a '^.' 'to' f ≡ f a
121-- @
122--
123-- >>> a ^.to f
124-- f a
125--
126-- >>> ("hello","world")^.to snd
127-- "world"
128--
129-- >>> 5^.to succ
130-- 6
131--
132-- >>> (0, -5)^._2.to abs
133-- 5
134--
135-- @
136-- 'to' :: (s -> a) -> 'IndexPreservingGetter' s a
137-- @
138to :: (Profunctor p, Contravariant f) => (s -> a) -> Optic' p f s a
139to k = dimap k (contramap k)
140{-# INLINE to #-}
141
142-- |
143-- @
144-- 'ito' :: (s -> (i, a)) -> 'IndexedGetter' i s a
145-- @
146ito :: (Indexable i p, Contravariant f) => (s -> (i, a)) -> Over' p f s a
147ito k = dimap k (contramap (snd . k)) . uncurry . indexed
148{-# INLINE ito #-}
149
150
151-- | Build an constant-valued (index-preserving) 'Getter' from an arbitrary Haskell value.
152--
153-- @
154-- 'like' a '.' 'like' b ≡ 'like' b
155-- a '^.' 'like' b ≡ b
156-- a '^.' 'like' b ≡ a '^.' 'to' ('const' b)
157-- @
158--
159-- This can be useful as a second case 'failing' a 'Fold'
160-- e.g. @foo `failing` 'like' 0@
161--
162-- @
163-- 'like' :: a -> 'IndexPreservingGetter' s a
164-- @
165like :: (Profunctor p, Contravariant f, Functor f) => a -> Optic' p f s a
166like a = to (const a)
167{-# INLINE like #-}
168
169-- |
170-- @
171-- 'ilike' :: i -> a -> 'IndexedGetter' i s a
172-- @
173ilike :: (Indexable i p, Contravariant f, Functor f) => i -> a -> Over' p f s a
174ilike i a = ito (const (i, a))
175{-# INLINE ilike #-}
176
177-- | When you see this in a type signature it indicates that you can
178-- pass the function a 'Lens', 'Getter',
179-- 'Control.Lens.Traversal.Traversal', 'Control.Lens.Fold.Fold',
180-- 'Control.Lens.Prism.Prism', 'Control.Lens.Iso.Iso', or one of
181-- the indexed variants, and it will just \"do the right thing\".
182--
183-- Most 'Getter' combinators are able to be used with both a 'Getter' or a
184-- 'Control.Lens.Fold.Fold' in limited situations, to do so, they need to be
185-- monomorphic in what we are going to extract with 'Control.Applicative.Const'. To be compatible
186-- with 'Lens', 'Control.Lens.Traversal.Traversal' and
187-- 'Control.Lens.Iso.Iso' we also restricted choices of the irrelevant @t@ and
188-- @b@ parameters.
189--
190-- If a function accepts a @'Getting' r s a@, then when @r@ is a 'Data.Monoid.Monoid', then
191-- you can pass a 'Control.Lens.Fold.Fold' (or
192-- 'Control.Lens.Traversal.Traversal'), otherwise you can only pass this a
193-- 'Getter' or 'Lens'.
194type Getting r s a = (a -> Const r a) -> s -> Const r s
195
196-- | Used to consume an 'Control.Lens.Fold.IndexedFold'.
197type IndexedGetting i m s a = Indexed i a (Const m a) -> s -> Const m s
198
199-- | This is a convenient alias used when consuming (indexed) getters and (indexed) folds
200-- in a highly general fashion.
201type Accessing p m s a = p a (Const m a) -> s -> Const m s
202
203-------------------------------------------------------------------------------
204-- Getting Values
205-------------------------------------------------------------------------------
206
207-- | View the value pointed to by a 'Getter', 'Control.Lens.Iso.Iso' or
208-- 'Lens' or the result of folding over all the results of a
209-- 'Control.Lens.Fold.Fold' or 'Control.Lens.Traversal.Traversal' that points
210-- at a monoidal value.
211--
212-- @
213-- 'view' '.' 'to' ≡ 'id'
214-- @
215--
216-- >>> view (to f) a
217-- f a
218--
219-- >>> view _2 (1,"hello")
220-- "hello"
221--
222-- >>> view (to succ) 5
223-- 6
224--
225-- >>> view (_2._1) ("hello",("world","!!!"))
226-- "world"
227--
228--
229-- As 'view' is commonly used to access the target of a 'Getter' or obtain a monoidal summary of the targets of a 'Fold',
230-- It may be useful to think of it as having one of these more restricted signatures:
231--
232-- @
233-- 'view' ::             'Getter' s a     -> s -> a
234-- 'view' :: 'Data.Monoid.Monoid' m => 'Control.Lens.Fold.Fold' s m       -> s -> m
235-- 'view' ::             'Control.Lens.Iso.Iso'' s a       -> s -> a
236-- 'view' ::             'Lens'' s a      -> s -> a
237-- 'view' :: 'Data.Monoid.Monoid' m => 'Control.Lens.Traversal.Traversal'' s m -> s -> m
238-- @
239--
240-- In a more general setting, such as when working with a 'Monad' transformer stack you can use:
241--
242-- @
243-- 'view' :: 'MonadReader' s m             => 'Getter' s a     -> m a
244-- 'view' :: ('MonadReader' s m, 'Data.Monoid.Monoid' a) => 'Control.Lens.Fold.Fold' s a       -> m a
245-- 'view' :: 'MonadReader' s m             => 'Control.Lens.Iso.Iso'' s a       -> m a
246-- 'view' :: 'MonadReader' s m             => 'Lens'' s a      -> m a
247-- 'view' :: ('MonadReader' s m, 'Data.Monoid.Monoid' a) => 'Control.Lens.Traversal.Traversal'' s a -> m a
248-- @
249view :: MonadReader s m => Getting a s a -> m a
250view l = Reader.asks (getConst #. l Const)
251{-# INLINE view #-}
252
253-- | View a function of the value pointed to by a 'Getter' or 'Lens' or the result of
254-- folding over the result of mapping the targets of a 'Control.Lens.Fold.Fold' or
255-- 'Control.Lens.Traversal.Traversal'.
256--
257-- @
258-- 'views' l f ≡ 'view' (l '.' 'to' f)
259-- @
260--
261-- >>> views (to f) g a
262-- g (f a)
263--
264-- >>> views _2 length (1,"hello")
265-- 5
266--
267-- As 'views' is commonly used to access the target of a 'Getter' or obtain a monoidal summary of the targets of a 'Fold',
268-- It may be useful to think of it as having one of these more restricted signatures:
269--
270-- @
271-- 'views' ::             'Getter' s a     -> (a -> r) -> s -> r
272-- 'views' :: 'Data.Monoid.Monoid' m => 'Control.Lens.Fold.Fold' s a       -> (a -> m) -> s -> m
273-- 'views' ::             'Control.Lens.Iso.Iso'' s a       -> (a -> r) -> s -> r
274-- 'views' ::             'Lens'' s a      -> (a -> r) -> s -> r
275-- 'views' :: 'Data.Monoid.Monoid' m => 'Control.Lens.Traversal.Traversal'' s a -> (a -> m) -> s -> m
276-- @
277--
278-- In a more general setting, such as when working with a 'Monad' transformer stack you can use:
279--
280-- @
281-- 'views' :: 'MonadReader' s m             => 'Getter' s a     -> (a -> r) -> m r
282-- 'views' :: ('MonadReader' s m, 'Data.Monoid.Monoid' r) => 'Control.Lens.Fold.Fold' s a       -> (a -> r) -> m r
283-- 'views' :: 'MonadReader' s m             => 'Control.Lens.Iso.Iso'' s a       -> (a -> r) -> m r
284-- 'views' :: 'MonadReader' s m             => 'Lens'' s a      -> (a -> r) -> m r
285-- 'views' :: ('MonadReader' s m, 'Data.Monoid.Monoid' r) => 'Control.Lens.Traversal.Traversal'' s a -> (a -> r) -> m r
286-- @
287--
288-- @
289-- 'views' :: 'MonadReader' s m => 'Getting' r s a -> (a -> r) -> m r
290-- @
291views :: MonadReader s m => LensLike' (Const r) s a -> (a -> r) -> m r
292views l f = Reader.asks (getConst #. l (Const #. f))
293{-# INLINE views #-}
294
295-- | View the value pointed to by a 'Getter' or 'Lens' or the
296-- result of folding over all the results of a 'Control.Lens.Fold.Fold' or
297-- 'Control.Lens.Traversal.Traversal' that points at a monoidal values.
298--
299-- This is the same operation as 'view' with the arguments flipped.
300--
301-- The fixity and semantics are such that subsequent field accesses can be
302-- performed with ('Prelude..').
303--
304-- >>> (a,b)^._2
305-- b
306--
307-- >>> ("hello","world")^._2
308-- "world"
309--
310-- >>> import Data.Complex
311-- >>> ((0, 1 :+ 2), 3)^._1._2.to magnitude
312-- 2.23606797749979
313--
314-- @
315-- ('^.') ::             s -> 'Getter' s a     -> a
316-- ('^.') :: 'Data.Monoid.Monoid' m => s -> 'Control.Lens.Fold.Fold' s m       -> m
317-- ('^.') ::             s -> 'Control.Lens.Iso.Iso'' s a       -> a
318-- ('^.') ::             s -> 'Lens'' s a      -> a
319-- ('^.') :: 'Data.Monoid.Monoid' m => s -> 'Control.Lens.Traversal.Traversal'' s m -> m
320-- @
321(^.) :: s -> Getting a s a -> a
322s ^. l = getConst (l Const s)
323{-# INLINE (^.) #-}
324
325-------------------------------------------------------------------------------
326-- MonadState
327-------------------------------------------------------------------------------
328
329-- | Use the target of a 'Lens', 'Control.Lens.Iso.Iso', or
330-- 'Getter' in the current state, or use a summary of a
331-- 'Control.Lens.Fold.Fold' or 'Control.Lens.Traversal.Traversal' that points
332-- to a monoidal value.
333--
334-- >>> evalState (use _1) (a,b)
335-- a
336--
337-- >>> evalState (use _1) ("hello","world")
338-- "hello"
339--
340-- @
341-- 'use' :: 'MonadState' s m             => 'Getter' s a     -> m a
342-- 'use' :: ('MonadState' s m, 'Data.Monoid.Monoid' r) => 'Control.Lens.Fold.Fold' s r       -> m r
343-- 'use' :: 'MonadState' s m             => 'Control.Lens.Iso.Iso'' s a       -> m a
344-- 'use' :: 'MonadState' s m             => 'Lens'' s a      -> m a
345-- 'use' :: ('MonadState' s m, 'Data.Monoid.Monoid' r) => 'Control.Lens.Traversal.Traversal'' s r -> m r
346-- @
347use :: MonadState s m => Getting a s a -> m a
348use l = State.gets (view l)
349{-# INLINE use #-}
350
351-- | Use the target of a 'Lens', 'Control.Lens.Iso.Iso' or
352-- 'Getter' in the current state, or use a summary of a
353-- 'Control.Lens.Fold.Fold' or 'Control.Lens.Traversal.Traversal' that
354-- points to a monoidal value.
355--
356-- >>> evalState (uses _1 length) ("hello","world")
357-- 5
358--
359-- @
360-- 'uses' :: 'MonadState' s m             => 'Getter' s a     -> (a -> r) -> m r
361-- 'uses' :: ('MonadState' s m, 'Data.Monoid.Monoid' r) => 'Control.Lens.Fold.Fold' s a       -> (a -> r) -> m r
362-- 'uses' :: 'MonadState' s m             => 'Lens'' s a      -> (a -> r) -> m r
363-- 'uses' :: 'MonadState' s m             => 'Control.Lens.Iso.Iso'' s a       -> (a -> r) -> m r
364-- 'uses' :: ('MonadState' s m, 'Data.Monoid.Monoid' r) => 'Control.Lens.Traversal.Traversal'' s a -> (a -> r) -> m r
365-- @
366--
367-- @
368-- 'uses' :: 'MonadState' s m => 'Getting' r s t a b -> (a -> r) -> m r
369-- @
370uses :: MonadState s m => LensLike' (Const r) s a -> (a -> r) -> m r
371uses l f = State.gets (views l f)
372{-# INLINE uses #-}
373
374-- | This is a generalized form of 'listen' that only extracts the portion of
375-- the log that is focused on by a 'Getter'. If given a 'Fold' or a 'Traversal'
376-- then a monoidal summary of the parts of the log that are visited will be
377-- returned.
378--
379-- @
380-- 'listening' :: 'MonadWriter' w m             => 'Getter' w u     -> m a -> m (a, u)
381-- 'listening' :: 'MonadWriter' w m             => 'Lens'' w u      -> m a -> m (a, u)
382-- 'listening' :: 'MonadWriter' w m             => 'Iso'' w u       -> m a -> m (a, u)
383-- 'listening' :: ('MonadWriter' w m, 'Monoid' u) => 'Fold' w u       -> m a -> m (a, u)
384-- 'listening' :: ('MonadWriter' w m, 'Monoid' u) => 'Traversal'' w u -> m a -> m (a, u)
385-- 'listening' :: ('MonadWriter' w m, 'Monoid' u) => 'Prism'' w u     -> m a -> m (a, u)
386-- @
387listening :: MonadWriter w m => Getting u w u -> m a -> m (a, u)
388listening l m = do
389  (a, w) <- listen m
390  return (a, view l w)
391{-# INLINE listening #-}
392
393-- | This is a generalized form of 'listen' that only extracts the portion of
394-- the log that is focused on by a 'Getter'. If given a 'Fold' or a 'Traversal'
395-- then a monoidal summary of the parts of the log that are visited will be
396-- returned.
397--
398-- @
399-- 'ilistening' :: 'MonadWriter' w m             => 'IndexedGetter' i w u     -> m a -> m (a, (i, u))
400-- 'ilistening' :: 'MonadWriter' w m             => 'IndexedLens'' i w u      -> m a -> m (a, (i, u))
401-- 'ilistening' :: ('MonadWriter' w m, 'Monoid' u) => 'IndexedFold' i w u       -> m a -> m (a, (i, u))
402-- 'ilistening' :: ('MonadWriter' w m, 'Monoid' u) => 'IndexedTraversal'' i w u -> m a -> m (a, (i, u))
403-- @
404ilistening :: MonadWriter w m => IndexedGetting i (i, u) w u -> m a -> m (a, (i, u))
405ilistening l m = do
406  (a, w) <- listen m
407  return (a, iview l w)
408{-# INLINE ilistening #-}
409
410-- | This is a generalized form of 'listen' that only extracts the portion of
411-- the log that is focused on by a 'Getter'. If given a 'Fold' or a 'Traversal'
412-- then a monoidal summary of the parts of the log that are visited will be
413-- returned.
414--
415-- @
416-- 'listenings' :: 'MonadWriter' w m             => 'Getter' w u     -> (u -> v) -> m a -> m (a, v)
417-- 'listenings' :: 'MonadWriter' w m             => 'Lens'' w u      -> (u -> v) -> m a -> m (a, v)
418-- 'listenings' :: 'MonadWriter' w m             => 'Iso'' w u       -> (u -> v) -> m a -> m (a, v)
419-- 'listenings' :: ('MonadWriter' w m, 'Monoid' v) => 'Fold' w u       -> (u -> v) -> m a -> m (a, v)
420-- 'listenings' :: ('MonadWriter' w m, 'Monoid' v) => 'Traversal'' w u -> (u -> v) -> m a -> m (a, v)
421-- 'listenings' :: ('MonadWriter' w m, 'Monoid' v) => 'Prism'' w u     -> (u -> v) -> m a -> m (a, v)
422-- @
423listenings :: MonadWriter w m => Getting v w u -> (u -> v) -> m a -> m (a, v)
424listenings l uv m = do
425  (a, w) <- listen m
426  return (a, views l uv w)
427{-# INLINE listenings #-}
428
429-- | This is a generalized form of 'listen' that only extracts the portion of
430-- the log that is focused on by a 'Getter'. If given a 'Fold' or a 'Traversal'
431-- then a monoidal summary of the parts of the log that are visited will be
432-- returned.
433--
434-- @
435-- 'ilistenings' :: 'MonadWriter' w m             => 'IndexedGetter' w u     -> (i -> u -> v) -> m a -> m (a, v)
436-- 'ilistenings' :: 'MonadWriter' w m             => 'IndexedLens'' w u      -> (i -> u -> v) -> m a -> m (a, v)
437-- 'ilistenings' :: ('MonadWriter' w m, 'Monoid' v) => 'IndexedFold' w u       -> (i -> u -> v) -> m a -> m (a, v)
438-- 'ilistenings' :: ('MonadWriter' w m, 'Monoid' v) => 'IndexedTraversal'' w u -> (i -> u -> v) -> m a -> m (a, v)
439-- @
440ilistenings :: MonadWriter w m => IndexedGetting i v w u -> (i -> u -> v) -> m a -> m (a, v)
441ilistenings l iuv m = do
442  (a, w) <- listen m
443  return (a, iviews l iuv w)
444{-# INLINE ilistenings #-}
445
446------------------------------------------------------------------------------
447-- Indexed Getters
448------------------------------------------------------------------------------
449
450-- | View the index and value of an 'IndexedGetter' into the current environment as a pair.
451--
452-- When applied to an 'IndexedFold' the result will most likely be a nonsensical monoidal summary of
453-- the indices tupled with a monoidal summary of the values and probably not whatever it is you wanted.
454iview :: MonadReader s m => IndexedGetting i (i,a) s a -> m (i,a)
455iview l = asks (getConst #. l (Indexed $ \i -> Const #. (,) i))
456{-# INLINE iview #-}
457
458-- | View a function of the index and value of an 'IndexedGetter' into the current environment.
459--
460-- When applied to an 'IndexedFold' the result will be a monoidal summary instead of a single answer.
461--
462-- @
463-- 'iviews' ≡ 'Control.Lens.Fold.ifoldMapOf'
464-- @
465iviews :: MonadReader s m => IndexedGetting i r s a -> (i -> a -> r) -> m r
466iviews l f = asks (getConst #. l (Const #. Indexed f))
467{-# INLINE iviews #-}
468
469-- | Use the index and value of an 'IndexedGetter' into the current state as a pair.
470--
471-- When applied to an 'IndexedFold' the result will most likely be a nonsensical monoidal summary of
472-- the indices tupled with a monoidal summary of the values and probably not whatever it is you wanted.
473iuse :: MonadState s m => IndexedGetting i (i,a) s a -> m (i,a)
474iuse l = gets (getConst #. l (Indexed $ \i -> Const #. (,) i))
475{-# INLINE iuse #-}
476
477-- | Use a function of the index and value of an 'IndexedGetter' into the current state.
478--
479-- When applied to an 'IndexedFold' the result will be a monoidal summary instead of a single answer.
480iuses :: MonadState s m => IndexedGetting i r s a -> (i -> a -> r) -> m r
481iuses l f = gets (getConst #. l (Const #. Indexed f))
482{-# INLINE iuses #-}
483
484-- | View the index and value of an 'IndexedGetter' or 'IndexedLens'.
485--
486-- This is the same operation as 'iview' with the arguments flipped.
487--
488-- The fixity and semantics are such that subsequent field accesses can be
489-- performed with ('Prelude..').
490--
491-- @
492-- ('^@.') :: s -> 'IndexedGetter' i s a -> (i, a)
493-- ('^@.') :: s -> 'IndexedLens'' i s a  -> (i, a)
494-- @
495--
496-- The result probably doesn't have much meaning when applied to an 'IndexedFold'.
497(^@.) :: s -> IndexedGetting i (i, a) s a -> (i, a)
498s ^@. l = getConst $ l (Indexed $ \i -> Const #. (,) i) s
499{-# INLINE (^@.) #-}
500
501-- | Coerce a 'Getter'-compatible 'Optical' to an 'Optical''. This
502-- is useful when using a 'Traversal' that is not simple as a 'Getter' or a
503-- 'Fold'.
504--
505-- @
506-- 'getting' :: 'Traversal' s t a b          -> 'Fold' s a
507-- 'getting' :: 'Lens' s t a b               -> 'Getter' s a
508-- 'getting' :: 'IndexedTraversal' i s t a b -> 'IndexedFold' i s a
509-- 'getting' :: 'IndexedLens' i s t a b      -> 'IndexedGetter' i s a
510-- @
511getting :: (Profunctor p, Profunctor q, Functor f, Contravariant f)
512        => Optical p q f s t a b -> Optical' p q f s a
513getting l f = rmap phantom . l $ rmap phantom f
514