Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Is there a “dual” to zooming?

zoom allows us to use a state action that only uses some state variables, in a context where more variables are actually defined.

{-# LANGUAGE TemplateHaskell #-}

import Control.Lens

import Control.Monad.Trans.State
import Control.Monad.IO.Class

data Galaxy = Galaxy {
    _solarSys :: SolarSystem
  , _otherStars :: String
  } deriving (Show)
data SolarSystem = SolarSystem {
    _sun :: Float
  , _planets :: Int
  } deriving (Show)

makeLenses ''SolarSystem
makeLenses ''Galaxy

main = (`runStateT`Galaxy (SolarSystem 2e+30 8) "🌌🌌🌌") $ do
   zoom solarSys $ do
      sun -= 1e+23
      planets += 1
   liftIO . print =<< get
Galaxy {_solarSys = SolarSystem {_sun = 1.9999999e30, _planets = 9}, _otherStars = "🌌🌌🌌"}

But what if I want to do some stuff in an environment with only some state variables defined, and then run a computation that has some extra, local state-variables? Like

data Expedition = Expedition {
    _environment :: SolarSystem
  , _spacecraft :: Char
  } deriving (Show)
makeLenses ''Exploration

main = (`runStateT`Galaxy (SolarSystem 2e+30 8) "Milky") $ do
   zoom solarSys $ do
      spectralFilter environment (spacecraft ???~= '🚀') $ do
         spacecraft .= '🛰️'
         environment . planets -= 1
   liftIO . print =<< get

I suspect the initialisation of spacecraft would actually require some other optic, but I can't see which.

like image 784
leftaroundabout Avatar asked Aug 16 '18 11:08

leftaroundabout


People also ask

Can you zoom on 2 screens with one person?

Hosts using the Zoom desktop client can allow multiple participants share their screens simultaneously during a meeting. This can be useful for a real-time comparison of documents or other materials by participants. To make full use of this feature, enable the dual monitors option in the Zoom client settings.

Can u split screen zoom?

Click your profile picture, then click Settings. Click the Share Screen tab. Click the Side-by-Side Mode check box. Zoom will automatically enter side-by-side mode when a participant starts sharing their screen.

How do you zoom in on 3 monitors?

Using Presenter View in a Zoom meeting with 3 screensDrag the videos panel to screen #2. Make sure the Zoom controls are on your laptop screen and drag them there from another screen if needed. Use the Zoom controls to open the chat window and pop it out from the controls if needed.


1 Answers

How about this function?

cram :: Monad m => Iso' s' (s,x) -> x -> StateT s' m r -> StateT s m r
cram someiso extra action =
    StateT (\small0 -> do let big0 = view (from someiso) (small0,extra)
                          (r,big) <- runStateT action big0
                          let (small,_) = view someiso big
                          pure (r,small))

"If you convince me that the expanded state is the small state plus extra stuff, and you give me some initial extra stuff, I can cram the expanded-state computation into the small-state one."

You would have to write an Iso' Expedition (SolarSystem,Char).

like image 189
danidiaz Avatar answered Oct 25 '22 05:10

danidiaz