Instances for partial conversion functions

Hello,

In a project, I have some universal type Object for which conversion functions to “more concrete” types can be implemented. Parsers, in a sense.

A basic parser into type a would be a function of type Object -> Maybe a, but so these can be combined, a Parser a is really a [Object -> Maybe a] where, when executed on some Object, the first Just value “wins” (see code below). This allows for definitions like

intParser :: Parser Int = _
floatParser :: Parser Float = _

intOrFloatParser :: Parser (Either Int Float)
intOrFloatParser = fmap Left intParser <|> fmap Right floatParser

Note in the above I used fmap (Functor) and <|> (Alternative). Indeed, instances for these typeclasses seem quite straight-forward, and I believe the implementations are law-abiding. However, Alternative has an Applicative constraint, and that’s where I’m stuck: where pure is easy to define, I’m unable to figure out what a sensible implementation of <*> (or liftA2) would look like, given the semantics of a Parser (and what the effects of such implementation would be). Similarly, a MonadPlus instance seems straight-forward given the Alternative instance, but there as well I don’t see what Monad's >>= would be.

Does the [T -> Maybe a] type ring any bells, and/or does anyone see if/which sensible implementations for <*> and >>= could be provided?

For reference, some code to make the idea more concrete:

module Parser where

import Control.Applicative (Alternative(..))
import Control.Monad (MonadPlus(..))
import Data.Monoid (First(..))

data Object

-- | A 'Parser a' is a list of functions which may be able to convert an
--  'Object' into an 'a'. When executed using 'runParser', the first
--  successful conversion result is returned.
newtype Parser a = Parser [Object -> Maybe a]

runParser :: Parser a -> Object -> Maybe a
runParser (Parser a) obj = getFirst $ foldMap (First . ($ obj)) a

instance Functor Parser where
    fmap f (Parser a) = Parser $ fmap (fmap f .) a

instance Applicative Parser where
    pure a = Parser $ pure (const $ Just a)
    a <*> b = _ -- ???

instance Alternative Parser where
    empty = Parser mempty
    Parser a <|> Parser b = Parser (a <> b)

instance Monad Parser where
    a >>= k = _ -- ???

instance MonadPlus Parser where
    -- Could rely on default implementations, but to be more explicit...
    mzero = empty
    mplus = (<|>)

instance Semigroup (Parser a) where
    (<>) = (<|>)

instance Monoid (Parser a) where
    mempty = empty

Thanks in advance!

Your parser type is a composition of functors, all of which are monads:

import GHC.Generics ((:.:))
type Parser = [] :.: (((->) Object) :.: Maybe)

so you can at least get an Applicative instance for free, since Applicative functors are closed under composition. Since the outermost Functor is an Alternative, the whole composition is. The Generics module provides the necessary derivation.
Not all compositons of monads are monads, though. Especially [] is hard to deal with since it is a non-commutative monad.

Thanks for this. I was looking into the instances of [] and a -> b earlier, but got quite confused by the [] one in this context: in essence, my Parser type “behaves” much more as a function than as a list, hence ziping seems not to make much sense? Or maybe I’m missing something/confusing things?

The inner Applicative ((->) Object) :.: Maybe is actually a monad, a.k.a. ReaderT Object Maybe. Hence the question about the entire thing being a monad boils down to a monad instance for types like [] :.: m for m some monad. We already have pure so only >>= remains to be defined, or equivalently a

join :: [m [m a]] -> [m a]

This join you could get by virtue of a distributive law

m [a] -> [m a]

but in our case I think we are out of luck: I can not imagine a sensible function

(Object -> Maybe [a]) -> [Object -> Maybe a]

That is because the list is only making choices explicit.
Why not:

import Control.Monad.Reader (ReaderT)
type Parser = ReaderT Object Maybe

which is already an Alternative because Maybe is. Its implementation does what you want, I think: p <|> q applies both p and q to the same object and combines both results using the Alternative instance of Maybe which chooses the first Just result if any.

Agreed, a Monad instance is likely not possible because there’s likely no sensible “and then” operation, given there’s only a single input value.

The actual code is quite a bit more elaborate, where the base parsers are not simple Object -> Maybe a functions, and I need all possible parser functions in a list eventually for further processing. The code above is an oversimplification. So reusing ReaderT as-is won’t fly (it definitely would in the demo code, though, thanks for pointing that out!)

If you really need list choices embedded, consider a proper ListT transformer.

That seems to resemble how these work:

Functional Pearl: Parallel Parsing Processes (2004)

…but looking at that type declaration again:

has got me thinking - if all the list’s elements are being applied to the same Object, then:

could be a simpler option.

Can you elaborate on this? I anticipate that there’s a way to twiddle your data structures to capture what you want without mixing the list and the type parameter (which is what prevents this from being a relatively straightforward monad transformer stack—even a correct ListT can have some surprising behavior, and I generally advise people to avoid it when something simpler will do).

My first feeling is that you’d wrap what you’re interested in a type.

data ObjectValue = ObjInt Int | ObjFloat Float ...
type Parser = Object -> Maybe ObjectValue 

And then you could combine all your parsers with asum

numParsers :: [ Object -> Maybe ObjectValue ]
numParsers = [intParser, floatParser ... ]

runNumParsers :: Object -> Maybe ObjectValue
runNumParsers = asum numParsers 

First one succeeds, no success returns Nothing.

Then you would unwrap your types and values as needed.

My apologies if I have misunderstood the question.

Edit: I think you’re trying to write a generalized instance for the more complicated [Object → Maybe a] type. And I think that’s way above my skill level.

Thanks again for all insights. I guess I got confused mainly by the use of a list (which is needed because of implementation detail reasons only, heck, the actual code isn’t even Haskell…), but failed to realize this thing is defined not by its implementation, but by its behaviour, which is in a sense fully dictated by runParser.

Thanks to some of the comments here, I started to realize the actual type is a bit like newtype Parser a b = Parser (a -> Alt Maybe b), and the Applicative, Monad and other instances of a -> b can be reused (in spirit).

I actually defined it as newtype Parser a b = Parser [a -> Maybe b] not to get confused by this Object thing, with (next to the one above) the following instances:

instance Applicative (Parser a) where
    pure a = Parser [\_ -> Just a]
    pf <*> pa = Parser [\a -> case runParser pf a of
      Nothing -> Nothing
      Just f -> case runParser pa a of
        Nothing -> Nothing
        Just v -> Just (f v)]

instance Monad (Parser a) where
    f >>= k = Parser [\a -> case runParser f a of
      Nothing -> Nothing
      Just a' -> runParser (k a') a]

instance MonadFail (Parser a) where
    fail _ = Parser []

Then, I wanted to check whether laws hold. Since my datatype contains functions, it’s not obvious how to achieve this (since it’d essentially mean I’d need to prove equality of functions, at some point). However, using the excellent quickcheck-higherorder library I was able to express the Functor/Applicative/Alternative/Monad/MonadFail/MonadPlus laws, a bit as is done in quickcheck-classes (which can’t handle higher-order types), and at least QuickCheck seems to believe my instances are OK, when both side of the Equations (expressions of laws) are QuickCheck’ed themselves over runParser for some random instantiation of a and b.

1 Like

I it suspicious that in all your definitions you use the idiom
[\a -> case runParser ... ] so every usage of <*> or >>= will collapse the list layer into a singleton. That may also be the reason why your QuickCheck tests succeed. Are you sure you want this?
The law m >>= return = m ought to be violated. Please check with a list input of length > 1.

Typically, transformer stacks including a list layer tend to obey all the laws except that the list order is not respected. As long as you don’t care about the order of options, then you may be fine. But since your runParser tries all choices from left to right, list order is actually important.

As an example, consider finite probability distributions.

import Data.Monoid (Product(..))
type Dist a = [(Product Double,a)]
dirac = pure . pure :: a -> Dist a
bind :: Dist a -> (a -> Dist b) -> Dist b
bind dx k = do
    (p,a) <- dx
    map ((p,id) <*>) (k a)

prob :: (a -> Bool) -> Dist a -> Product Double
prob event = foldMap (\(p,a) -> if event a then p else mempty)

This is a lawful monad by virtue of return = dirac, (>>=) = bind but only disregarding the list order, that is, w.r.t the semantics given by prob.

2 Likes

I believe the list is a red herring. Indeed, m >>= return = m doesn’t hold at a structural level, but does at the effects/interpretation level: imagine the type itself is abstract, you don’t know about the list layer (which is only used by/because of <|>), then it’s fully isomorphic to Object -> Maybe a (also witnessed by runParsers type). Basically, if I wouldn’t use the list and instead actually use Object -> Maybe a as the type, then <|> would be implemented more “directly” of course, and <*> and bind would be ± what my implementation does, without wrapping the resulting function in a singleton list.

As for the correctness of the Applicative and Monad instances: the version abstracting over the input type, hence type Parser a b = a -> Maybe b (or, in my case, with the list but “abstract”) is a profunctor, and looking into the profunctors package I came by Star, which is newtype Star f d c = Star (d -> f c), i.e., my Parser a is Star (Alt Maybe) Object a, and Star f ds Applicative, Monad and other instances are very much alike the ones I have for Parser a.

Finally, I found this blog post: looks like I’m not the first exploring this area.

Yeah I guess in the end you have choices of which composing library (mtl, Compose, Generic :.:) you use to build your result functor and whether to wrap the parser in a Star, Kleisli or similar. The class instances provided by each library will likely give you slightly different ergonomics.

At least Applicative and Alternative are a no-brainer but since the Monad instance is unlawful you should be careful whether GHC uses the monad laws to optimize your code while changing the semantics. I’m unsure whether that is actually a real danger.