7

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.

leftaroundabout
  • 117,950
  • 5
  • 174
  • 319
  • Why does it need an optic at all as opposed to a plain function of type `SolarSystem -> Expedition`? You don't appear to be doing anything interesting with the updated context once the nested action is done (unlike `zoom`, which uses both directions of its optic argument). – Daniel Wagner Aug 16 '18 at 12:26
  • @DanielWagner because the state updates to the `SolarSystem` portion of the local action should also propagate outwards. – leftaroundabout Aug 16 '18 at 12:27
  • Oh, of course. Well now I just feel silly. – Daniel Wagner Aug 16 '18 at 12:28

1 Answers1

4

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).

danidiaz
  • 26,936
  • 4
  • 45
  • 95