Keeping IO lazy under append

前端 未结 2 1110
天命终不由人
天命终不由人 2021-01-19 03:42

I may have been under the false impression that Haskell is lazier than it is, but I wonder if there\'s a way to get the best of both worlds...

Data.Monoid

相关标签:
2条回答
  • 2021-01-19 04:06

    The Alternative instance for the MaybeT monad transformer returns the first successful result, and does not execute the rest of the operations. In combination with the asum function, we can write something like:

    import Data.Foldable (asum)
    import Control.Applicative
    import Control.Monad.Trans.Maybe
    
    action :: Char -> IO Char
    action c = putChar c *> return c
    
    main :: IO ()
    main = do
        result <- runMaybeT $ asum $ [ empty
                                     , MaybeT $ action 'x' *> return Nothing
                                     , liftIO $ action 'v'
                                     , liftIO $ action 'z'
                                     ]
        print result
    

    where the final action 'z' won't be executed.

    We can also write a newtype wrapper with a Monoid instance which mimics the Alternative:

    newtype FirstIO a = FirstIO (MaybeT IO a)
    
    firstIO :: IO (Maybe a) -> FirstIO a
    firstIO ioma = FirstIO (MaybeT ioma)
    
    getFirstIO :: FirstIO a -> IO (Maybe a)
    getFirstIO (FirstIO (MaybeT ioma)) = ioma
    
    instance Monoid (FirstIO a) where
        mempty = FirstIO empty
        FirstIO m1 `mappend` FirstIO m2 = FirstIO $ m1 <|> m2
    

    The relationship between Alternative and Monoid is explained in this other SO question.

    0 讨论(0)
  • 2021-01-19 04:18

    Is there a way that I can retain the Semigroup or Monoid abstraction, while still get lazy IO?

    Somewhat, but there are drawbacks. The udnerlying problem for our instances is that a generic instance for an Applicative will look like

    instance Semigroup a => Semigroup (SomeApplicative a) where
        x <> y = (<>) <$> x <*> y
    

    We're here at the mercy of (<*>), and usually the second argument y will be at least in WHNF. For example in Maybe's implementation the first line will work fine and the second line will error:

    liftA2 (<>) Just (First 10) <> Just (error "never shown")
    liftA2 (<>) Just (First 10) <> error "fire!"
    

    IO's (<*>) is implemented in terms of ap, so the second action will always be executed before <> is applied.

    A First-like variant is possible with ExceptT or similar, essentially any data type that has a Left k >>= _ = Left k like case so that we can stop the computation at that point. Although ExceptT is meant for exceptions, it may work well for your use-case. Alternatively, one of the Alternative transformers (MaybeT, ExceptT) together with <|> instead of <> might suffice.


    A almost completely lazy IO type is also possible, but must be handled with care:

    import Control.Applicative (liftA2)
    import System.IO.Unsafe (unsafeInterleaveIO)  
    
    newtype LazyIO a = LazyIO { runLazyIO :: IO a }
    
    instance Functor LazyIO where
      fmap f = LazyIO . fmap f . runLazyIO
    
    instance Applicative LazyIO where
      pure    = LazyIO . pure
      f <*> x = LazyIO $ do
                  f' <- unsafeInterleaveIO (runLazyIO f)
                  x' <- unsafeInterleaveIO (runLazyIO x)
                  return $ f' x'
    
    instance Monad LazyIO where
      return  = pure
      f >>= k = LazyIO $ runLazyIO f >>= runLazyIO . k
    
    instance Semigroup a => Semigroup (LazyIO a) where
      (<>) = liftA2 (<>)
    
    instance Monoid a => Monoid (LazyIO a) where
      mempty  = pure mempty
      mappend = liftA2 mappend
    

    unsafeInterleaveIO will enable the behaviour you want (and is used in getContents and other lazy IO Prelude functions), but it must be used with care. The order of IO operations is completely off at that point. Only when we inspect the values we will trigger the original IO:

    ghci> :module +Data.Monoid Control.Monad
    ghci> let example = fmap (First . Just) . LazyIO . putStrLn $ "example"
    ghci> runLazyIO $ fmap mconcat $ replicateM 100 example
    First {getFirst = example
    Just ()}
    

    Note that we only got our example once in the output, but at a completely random place, since the putStrLn "example" and print result got interleaved, since

    print (First x) = putStrLn (show (First x))
                    = putStrLn ("First {getFirst = " ++ show x ++ "}")
    

    and show x will finally put the IO necessary to get x in action. The action will get called only once if we use the result multiple times:

    ghci> :module +Data.Monoid Control.Monad
    ghci> let example = fmap (First . Just) . LazyIO . putStrLn $ "example"
    ghci> result <- runLazyIO $ fmap mconcat $ replicateM 100 example
    ghci> result
    First {getFirst = example
    Just ()}
    ghci> result
    First {getFirst = Just ()}
    

    You could write a finalizeLazyIO function that either evaluates or seq's x though:

    finalizeLazyIO :: LazyIO a -> IO a
    finalizeLazyIO k = do
      x <- runLazyIO k
      x `seq` return x
    

    If you were to publish a module with this functions, I'd recommend to only export the type constructor LazyIO, liftIO :: IO a -> LazyIO a and finalizeLazyIO.

    0 讨论(0)
提交回复
热议问题