Trying to compose the non-composable: docking schemes

Introduction



In Haskell, it is customary to work with effects as functors whose objects are some expressions that we are interested in at the moment.



When we see the type of expression Maybe a , we abstract from the actual existence of some a , concentrating all our attention on this a . The same story with List a - plural values ​​of a ; State sa - a , depending on some current state; Either ea - a , which may return some error e .



Before continuing, the article will use several definitions:



type (:=) ta = ta -- |   type (:.) tua = t (ua) -- |   type (~>) tu = forall a . ta -> ua -- |  
      
      





For example: List:. Maybe: = a - this expression is easy to imagine, this is a list of values ​​whose existence is in question.



Further, as an example, we will use four common types: Reader , State , Either , Maybe .



Compositions and Transformers



The most obvious way to apply more than one effect to an expression is to simply embed one into the other, this is the usual composition of functors. In compositions, effects do not affect each other in any way (unless Traversable methods are used over them). And in order to merge many effects into one, transformers are used. Each method has its advantages and disadvantages:



Compositions:





Transformers:





Transformers are different from clutch compositions (I don’t know what to call it differently). Having some composition, you can turn it into a transformer and vice versa. Docking schemes will help us with this.



Docking Schemes



If we take a closer look at the types for monad transformers, we can identify some patterns:



 newtype ReaderT rma = ReaderT { runReaderT :: r -> ma } newtype MaybeT ma = MaybeT { runMaybeT :: m (Maybe a) } newtype ExceptT ema = ExceptT { runExceptT :: m (Either ea)) } newtype StateT sma = StateT { runStateT :: s -> m (a,s) }
      
      





Transformers describe a special case of how the current definite and indefinite effect should mesh.



Let t be definite and u be indefinite, try:



 Reader: r -> ua ===> (->) r :. u := a ===> t :. u := a -- t ~ (->) r Maybe: u (Maybe a) ===> u :. Maybe := a ===> u :. t := a -- t ~ Maybe Either: u (Either ea) ===> u :. Either e := a ===> u :. t := a -- t ~ Either e
      
      





Some effects are quite complex and can be defined through the composition of other, simpler effects:



 State: s -> u (a, s) ===> (->) s :. (,) s := a ==> t :. u :. t' := a -- t ~ (->) s, t' ~ (,) s newtype State sa = State ((->) s :. (,) s := a)
      
      





If we take a closer look at the first 3 examples, we can notice common patterns: if in Reader , a certain effect wraps up an indefinite one (takes it into brackets, becomes an object of a functor), then with Either and Maybe it’s the opposite - an indefinite effect wraps up a specific one. In the case of State, we even place the functor between two simpler defined effects.



Let's try to express these patterns in types:



 newtype TU tua = TU (t :. u := a) newtype UT tua = UT (u :. t := a) newtype TUT tut' a = TUT (t :. u :. t' := a)
      
      





We just defined docking schemes - this is a composition of functors in a wrapper that indicates the position of a specific and indefinite effect.



In fact, methods for transformers whose names begin with run simply remove the wrapper of the transformer, returning the composition of the functors. We describe such a class of types:



 class Composition t where type Primary ta :: * run :: ta -> Primary ta
      
      





Now we have a universal way to run these circuits:



 instance Composition (TU tu) where type Primary (TU tu) a = t :. u := a run (TU x) = x instance Composition (UT tu) where type Primary (UT tu) a = u :. t := a run (UT x) = x instance Composition (TUT tu t') where type Primary (TUT tu t') a = t :. u :. t' := a run (TUT x) = x
      
      





What about transformers? Here, you will also need a type class in which a docking scheme is prescribed for a particular type, the embed method is declared to raise the indefinite effect to the level of the transformer and build to construct a certain effect in the transformer:



 class Composition t => Transformer t where type Schema (t :: * -> *) (u :: * -> *) = (r :: * -> *) | r -> tu embed :: Functor u => u ~> Schema tu build :: Applicative u => t ~> Schema tu type (:>) tua = Transformer t => Schema tua
      
      





Now it remains to declare the instances, let's start with Maybe and Either :



 instance Transformer Maybe where type Schema Maybe u = UT Maybe u embed x = UT $ Just <$> x build x = UT . pure $ x instance Transformer (Either e) where type Schema (Either e) u = UT (Either e) u embed x = UT $ Right <$> x build x = UT . pure $ x
      
      





We will create our own type for Reader , since it is not in the base . And he also needs an instance of the Composition class, since it is a wrapper for the arrow functor:



 newtype Reader ea = Reader (e -> a) instance Composition (Reader e) where type Primary (Reader e) a = (->) ea run (Reader x) = x instance Transformer (Reader e) where type Schema (Reader e) u = TU ((->) e) u embed x = TU . const $ x build x = TU $ pure <$> run x
      
      





We do something similar with State :



 newtype State sa = State ((->) s :. (,) s := a) instance Composition (State s) where type Primary (State s) a = (->) s :. (,) s := a run (State x) = x instance Transformer (State s) where type Schema (State s) u = TUT ((->) s) u ((,) s) embed x = TUT $ \s -> (s,) <$> x build x = TUT $ pure <$> run x
      
      





As an example



It remains to test this on the problems of the real world - as an example, we will write a program that calculates the correct placement of various types of brackets.



Define types for parentheses: they can be opening and closing; and also have different styles:



 data Shape = Opened | Closed data Style = Round | Square | Angle | Curly
      
      





Other symbols of our program are not interesting:



 data Symbol = Nevermind | Bracket Style Shape
      
      





We also define a list of errors that our program may encounter:



 data Stumble = Deadend (Int, Style) --     | Logjam (Int, Style) --     | Mismatch (Int, Style) (Int, Style) --      
      
      





What effects do our program need? We need to keep a list of brackets awaiting verification and we need to stop at the first error encountered. We make a transformer:



 State [(Int, Style)] :> Either Stumble := ()
      
      





The algorithm is simple: we go through the structure with indexed brackets, if after the passage we did not encounter an error and we still have the brackets in the state, then the open bracket does not have a closed one:



 checking :: Traversable t => t (Int, Symbol) -> Either Stumble () checking struct = run (traverse proceed struct) [] >>= \case (s : _, _) -> Left . Logjam $ s where ([], _) -> Right ()
      
      





We remember any open bracket, compare any closed with the last remembered open:



 proceed :: (Int, Symbol) -> State [(Int, Style)] :> Either Stumble := () proceed (_, Nevermind) = pure () proceed (n, Bracket style Opened) = build . modify . (:) $ (n, style) procceed (n, Bracket closed Closed) = build get >>= \case []-> embed $ Left . Deadend $ (n, closed) ((m, opened) : ss) -> if closed /= opened then embed . Left $ Mismatch (m, opened) (n, closed) else build $ put ss where
      
      





Conclusion



Using docking schemes, having some composition of functors, we can turn them into transfomers and vice versa. Unfortunately, such a trick will not work with the mother of monads - sequels. And all because they cannot be imagined as a composition of functors, but it is possible as a composition of profunctors ... And yet, this is a completely different story.



Library Code on Github | Hackage Documentation | Parenthesis example



All Articles