Skip to content

Instantly share code, notes, and snippets.

@robrix
Created October 3, 2020 19:30
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save robrix/01de8b44f93bff13d6ac6a5331dd9cc9 to your computer and use it in GitHub Desktop.
Save robrix/01de8b44f93bff13d6ac6a5331dd9cc9 to your computer and use it in GitHub Desktop.
What do we gain and what do we break by distributing f over -> in Selective?
class Applicative f => Selective f where
branch :: f (Either a b) -> f (a -> c) -> f (b -> c) -> f c
branch ab f g = fmap (fmap Left) ab `select` fmap (fmap Right) f `select` g
select :: f (Either a b) -> f (a -> b) -> f b
select ab f = branch ab f (pure id)
{-# MINIMAL branch | select #-} -- Defining in terms of both to double-check my work
filteredBy :: (Alternative f, Selective f) => f a -> (a -> Bool) -> f a -- from Staged Selective Parser Combinators
filteredBy f p = select (p' <$> f) empty
where
p' x
| p x = Right x
| otherwise = Left ()
selectA :: Applicative f => f (Either a b) -> f (a -> b) -> f b -- Perhaps slow, but it gets the job done
selectA x y = (\e f -> either f id e) <$> x <*> y
-- per the selective package, we can also implement select with the desired behaviour for any Monad using >>=
selectM :: Monad f => f (Either a b) -> f (a -> b) -> f b
selectM x y = x >>= \e -> case e of Left a -> ($a) <$> y -- execute y
Right b -> pure b -- skip y
class Applicative f => Selective2 f where
-- f (a -> c) has become (f a -> f c)
-- f (b -> c) has become (f b -> f c)
branch2 :: f (Either a b) -> (f a -> f c) -> (f b -> f c) -> f c
branch2 ab f g = fmap (fmap Left) ab `select2` fmap (fmap Right) f `select2` g
-- f (a -> b) has become (f a -> f b)
select2 :: f (Either a b) -> (f a -> f b) -> f b
select2 ab f = branch2 ab f id
{-# MINIMAL branch2 | select2 #-}
-- we can still implement this
filteredBy2 :: (Alternative f, Selective2 f) => f a -> (a -> Bool) -> f a
filteredBy2 f p = select2 (p' <$> f) (const empty)
where
p' x
| p x = Right x
| otherwise = Left ()
-- …but not selectA2!
-- we need to switch on the Either, so we have to use fmap/<*>
-- our higher-order function takes its argument in f, so we can lift it in the Left case with pure
-- but then what?
-- 1. y returns in f, resulting in f (f b), and Applicative doesn’t give us any way to eliminate this nested f; Monad, ahoy
-- 2. we gain nothing from always using pure inputs that we couldn’t have done without Selective2
selectA2 :: Applicative f => f (Either a b) -> (f a -> f b) -> f b
selectA2 x y = ⁉️
-- by contrast, we _can_ implement our desired identifier-parsing, error-with-dependency behaviour:
-- A generalization of the unexpected method in Parsing from String -> p a to p String -> p a, so we don’t have to bind.
-- note that we can’t obtain the desired behaviour (failing with a given error message) with the signature p (String -> a);
-- in fact, that signature can _only_ fail without using the argument
class Alternative p => ParseFail p where
unexpected :: p String -> p a
-- | Like filteredBy2, but it errors with the shown result
filteredBy2Fail :: (ParseFail f, Selective2 f, Show a) => f a -> (a -> Bool) -> f a
filteredBy2Fail f p = select2 (p' <$> f) (unexpected . fmap show)
where
p' x
| p x = Right x
| otherwise = Left x
-- hooray, we can implement this with a Monad!
-- but note we’re not doing anything clever like e.g. selecting _some_ effects to replay; we can’t, generically
-- thus far, it’s not clear that this is much of a win
selectM2 :: Monad f => f (Either a b) -> (f a -> f b) -> f b
selectM2 x y = x >>= \e -> case e of Left a -> y (pure a) -- execute y
Right b -> pure b -- skip y
-- we can analyze Selective programs statically because there aren’t any
-- continuations doing god-knows-what to worry about
-- what about Selective2?
-- anecdotally, I used this signature in a one-off to add “parse any identifier,
-- and then let me parse _the same identifier_ an arbitrary number of times further”
-- to a deterministic parser. it worked, tho it was a bit strange; in particular,
-- it didn’t sacrifice the ability to calculate the nullability or the first set for
-- the parsers.
-- but characterizing which effects get performed is where this gets weird.
-- replaying the effects (but not the choices) made sense in a parser, but does it
-- make sense _anywhere_ else?
-- finally, we’ve seen that we have something like Applicative < Selective2 < Monad,
-- but we further have Selective < Selective2, because you can relate select and
-- select2 via <*>. that is, given y :: f (a -> b), we obtain y' (f a -> f b) by
-- y' = (y <*>).
-- what does that mean?
-- who knows!
@robrix
Copy link
Author

robrix commented Oct 3, 2020

Functor < Applicative ≤ Selective < Selective2 < Monad is kind of an appealing sequence, but I had better come up with a better name if I’m gonna think about this further

@snowleopard
Copy link

snowleopard commented Oct 4, 2020

Here is a variation on the theme:

class Applicative f => FailWith f where
    failWith :: (a -> String) -> f (a -> b)

-- compute: sqrt(x) * y
-- if x < 0 then skip the effect in y and fail with an error
example :: (Selective f, FailWith f) => f Double -> f Double -> f Double
example x y =
    branch (check <$> x) (compute <$> y) (failWith errorHandler)
  where
    check x | x >= 0     = Left x
            | otherwise  = Right x
    errorHandler x = "Can't sqrt this: " ++ show x
    compute y = \x -> sqrt x * y

-- A selective functor with failures
data F a where
    Id        :: a -> F a
    Io        :: IO a -> F a
    Ap        :: F (a -> b) -> F a -> F b
    Select    :: F (Either a b) -> F (a -> b) -> F b
    FailWith  :: (a -> String) -> F (a -> b)

-- The instances below are pretty dubious, e.g. `fmap id` is not `id` at all but I think we can fix this, I was just lazy
instance Functor F where
    fmap f x = pure f <*> x

instance Applicative F where
    pure  = Id
    (<*>) = Ap

instance Selective F where
    select = Select

instance FailWith F where
    failWith = FailWith

data Result a where
    Result       :: a -> Result a
    Error        :: String -> Result a
    ErrorHandler :: (a -> String) -> Result (a -> b)

instance Show a => Show (Result a) where
    show (Result a)       = show a
    show (Error m)        = m
    show (ErrorHandler _) = "<error handler>"

instance Functor Result where
    fmap f x = pure f <*> x

instance Applicative Result where
    pure = Result
    f <*> x = case (f, x) of
                  (Error m, _)               -> Error m
                  (_, Error m)               -> Error m
                  (Result f, Result x)       -> Result (f x)
                  (ErrorHandler f, Result x) -> Error (f x)
                  (_, ErrorHandler _)        -> Error "misplaced error handler"

interpret :: F a -> IO (Result a)
interpret = \case
    Id a       -> pure (Result a)
    Io a       -> Result <$> a
    Ap f x     -> liftM2 (<*>) (interpret f) (interpret x)
    FailWith f -> pure (ErrorHandler f)
    Select f x -> interpret f >>= \case
                      Error m          -> pure (Error m)
                      Result (Right b) -> pure (Result b)
                      Result (Left a)  -> liftM2 (<*>) (interpret x) (pure (Result a))

Now you can have the following ghci session:

> let get = Io (putStr "enter a number: " >> read <$> getLine)
> x <- interpret (example get get)
enter a number: 100
enter a number: 3
> x
30.0
> x <- interpret (example get get)
enter a number: -100
> x
Can't sqrt this: -100.0

Note that the second effect was skipped in the second scenario and that we can still statically analyse F.

@robrix
Copy link
Author

robrix commented Oct 4, 2020

Nice! Thanks for sharing such a complete example ❤️

@robrix
Copy link
Author

robrix commented Oct 4, 2020

That’s super interesting—if I’m following correctly, it holds onto the function to show the invalid value with, and then when interpretation proceeds as far as the error, it’s the application of that to the result which collapses it from ErrorHandler into Error. It reminds me a little bit of how the derivative of parser combinators with respect to an input character operates when iterated over an entire string; building up results (even ambiguous ones) character by character and pruning when sequencing with an empty parser.

Furthermore, it seems like the application of the error handler to the erroring value is guaranteed by the select laws (its type, even); we can’t accidentally end up with a final result in ErrorHandler and which we thus can’t print. Would certainly be nice if the types knew that as well, but this is a really cool demonstration of the approach!

@snowleopard
Copy link

if I’m following correctly, it holds onto the function to show the invalid value with, and then when interpretation proceeds as far as the error, it’s the application of that to the result which collapses it from ErrorHandler into Error.

Yes, exactly!

The name "error handler" is not ideal though: ErrorHandler seems to have nothing to do with effect handlers, so it might just confuse readers.

One problem with this approach I forgot to mention is that it's pretty brittle: if you swap the branches in the example, it stops working, because the implementation of branch based on select needs to do an fmap on the left branch, which hits the "misplaced error handler" case. This seems to suggest that we want the branch-based version of selective functors. Or we need to figure out less brittle Functor/Applicative instances.

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment