代码之家  ›  专栏  ›  技术社区  ›  leftaroundabout

有双重变焦功能吗?

  •  7
  • leftaroundabout  · 技术社区  · 7 年前

    zoom 允许我们在实际定义了更多变量的上下文中使用仅使用某些状态变量的状态操作。

    {-# 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 = "🌌🌌🌌"}

    但是,如果我想在一个只定义了一些状态变量的环境中做一些事情,然后运行一个包含一些额外的、局部状态变量的计算,会怎么样?就像

    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
    

    我怀疑 spacecraft 实际上需要一些其他的光学设备,但我看不出来。

    1 回复  |  直到 7 年前
        1
  •  4
  •   danidiaz    7 年前

    这个功能怎么样?

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

    “如果你让我相信扩展状态是小状态加上额外的东西,并且你给了我一些初始额外的东西,我可以把扩展状态计算塞进小状态计算中。”

    Iso' Expedition (SolarSystem,Char) .