box-0.6.0: boxes

Safe HaskellNone
LanguageHaskell2010

Box

Description

Effectful, profunctor boxes designed for concurrency.

This library follows the ideas and code from pipes-concurrency and mvc but with some polymorphic tweaks and definitively more pretentious names.

Synopsis

Documentation

>>> :set -XOverloadedStrings
>>> :set -XGADTs
>>> :set -XNoImplicitPrelude
>>> :set -XFlexibleContexts
>>> import NumHask.Prelude
>>> import qualified Prelude as P
>>> import Data.Functor.Contravariant
>>> import Box
>>> import Control.Monad.Conc.Class as C
>>> import Control.Lens

Continuations are very common in the API with Cont as an inhouse type.

>>> :t fromListE [1..3::Int]
fromListE [1..3::Int] :: MonadConc m => Cont m (Emitter m Int)

The applicative is usually the easiest way to think about and combine continuations with their unadorned counterparts.

>>> let box' = Box <$> pure toStdout <*> fromListE ["a", "b" :: Text]
>>> :t box'
box' :: Cont IO (Box IO Text Text)

The two basic ways of connecting up a box are related as follows:

glue c e == glueb (Box c e)
glueb == fuse (pure . pure)
>>> fromToList_ [1..3] glueb
[1,2,3]
>>> fromToList_ [1..3] (fuse (pure . pure))
[1,2,3]
  1. glue: direct fusion of committer and emitter
>>> runCont $ glue <$> pure toStdout <*> fromListE (show <$> [1..3])
1
2
3

Variations to the above code include:

Use of continuation applicative operators:

  • the '(*.)' operator is short hand for runCont $ xyz '(*)' zy.
  • the '($.)' operator is short hand for runCont $ xyz '($)' zy.
glue <$> pure toStdout <*.> fromListE (show <$> [1..3])
glue toStdout <$.> fromListE (show <$> [1..3])

Changing the type in the Emitter (The double fmap is cutting through the Cont and Emitter layers):

glue toStdout <$.> fmap (fmap show) (fromListE [1..3])

Changing the type in the committer (which is Contrvariant so needs to be a contramap):

glue (contramap show toStdout) <$.> fromListE [1..3]

Using the box version of glue:

glueb <$.> (Box <$> pure toStdout <*> (fmap show <$> fromListE [1..3]))
  1. fusion of a box, with an (a -> m (Maybe b)) function to allow for mapping, filtering and simple effects.
>>> let box' = Box <$> pure toStdout <*> fromListE (show <$> [1..3])
>>> fuse (\a -> bool (pure $ Just $ "echo: " <> a) (pure Nothing) (a==("2"::Text))) <$.> box'
echo: 1
echo: 3
>>> commit toStdout "I'm committed!"
I'm committed!
True

Use mapC to modify a Committer and introduce effects.

>>> let c = mapC (\a -> if a==2 then (sleep 0.1 >> putStrLn "stole a 2!" >> sleep 0.1 >> pure (Nothing)) else (pure (Just a))) (contramap (show :: Int -> Text) toStdout)
>>> glueb <$.> (Box <$> pure c <*> fromListE [1..3])
1
stole a 2!
3

The monoid instance of Committer sends each commit to both mappended committers. Because effects are also mappended together, the committed result is not always what is expected.

>>> let cFast = mapC (\b -> pure (Just b)) . contramap ("fast: " <>) $ toStdout
>>> let cSlow = mapC (\b -> sleep 0.1 >> pure (Just b)) . contramap ("slow: " <>) $ toStdout
>>> (glueb <$.> (Box <$> pure (cFast <> cSlow) <*> fromListE (show <$> [1..3]))) <* sleep 1
fast: 1
slow: 1
fast: 2
slow: 2
fast: 3
slow: 3

To approximate what is intuitively expected, use concurrentC.

>>> runCont $ (fromList_ (show <$> [1..3]) <$> (concurrentC cFast cSlow)) <> pure (sleep 1)
fast: 1
fast: 2
fast: 3
slow: 1
slow: 2
slow: 3

This is all non-deterministic, hence the necessity for messy delays and heuristic avoidance of console races.

>>> ("I'm emitted!" :: Text) & Just & pure & Emitter & emit >>= print
Just "I'm emitted!"
>>> with (fromListE [1]) (\e' -> (emit e' & fmap show :: IO Text) >>= putStrLn & replicate 3 & sequence_)
Just 1
Nothing
Nothing
>>> toListE <$.> (fromListE [1..3])
[1,2,3]

The monoid instance is left-biased.

>>> toListE <$.> (fromListE [1..3] <> fromListE [7..9])
[1,2,3,7,8,9]

Use concurrentE to get some nondeterministic balance.

let es = (join $ concurrentE <$> (fromListE [1..3]) <*> (fromListE [7..9]))
glue (contramap show toStdout) <$.> es

1 2 7 3 8 9

State committers and emitters are related as follows:

>>> runIdentity $ fmap (reverse . fst) $ flip execStateT ([],[1..4]) $ glue (hoist (zoom _1) stateC) (hoist (zoom _2) stateE)
[1,2,3,4]

For some reason, related to a lack of an MFunctor instance for Cont, but exactly not yet categorically pinned to a wall, the following compiles but is wrong.

>>> flip runStateT [] $ runCont $ glue <$> pure stateC <*> fromListE [1..4]
((),[])

Most committers and emitters will run forever until:

  • the glued or fused other-side returns.
  • the Transducer, stream or monadic action returns.

Finite ends (collective noun for emitters and committers) can be created with sink and source eg

>>> glue <$> contramap (show :: Int -> Text) <$> (sink 5 putStrLn) <*.> fromListE [1..]
1
2
3
4
5

Two infinite ends will tend to run infinitely.

glue <$> pure (contramap show toStdout) <*.> fromListE [1..]

1 2 ... 💁 ∞

Use glueN to create a finite computation.

>>> glueN 4 <$> pure (contramap show toStdout) <*.> fromListE [1..]
1
2
3
4

module Box.Box

module Box.Cont

module Box.IO

module Box.Queue

module Box.Time