Is this something like a lens? (proof search transformers/combinators) - haskell

In automated theorem proving (proof search), I compose transformers of type
t :: Claim -> IO (Maybe (Claim, Proof -> Proof))
such that: when t c returns Just (c', f), then c' implies c and a proof for c is obtained from a proof p' for c' by computing f p'.
Is this a lens, somehow? (If yes, what would it help?)
There's also a more general case (for several, or zero, subgoals)
ts :: Claim -> IO (Maybe ([Claim], [Proof] -> Proof))
The IO part is important because these transformers do substantial work (calling external processes), and I might want to impose timeouts.

I can't readily see how lenses could help with that. However, reordering your monadic stack and using monad transformers should make composition much easier, and also open up the possibility of abstracting from IO in the cases you don't need impurity:
t' :: Claim -> MaybeT IO (Claim, Proof -> Proof)
If you want or need to keep using an existing implementation of t in spite of the more cumbersome type, you can lift its result to MaybeT with:
(MaybeT . return =<<) . lift :: m (Maybe b) -> MaybeT m b
It is worth noting that Claim -> (Claim, Proof -> Proof) is equivalent to State Claim (Proof -> Proof), so it might be possible to go even further:
t'' :: StateT Claim (MaybeT IO) (Proof -> Proof)

Related

What are freer monads?

I heard this term a few times, but I still don't know what exactly is a so-called "Freer Monad". The name makes me think about Free Monads, but I don't see how they are actually related. There is some library I found on hackage: http://hackage.haskell.org/package/freer, but the example out there didn't help me a lot.
I don't understand the idea at all, and therefore I don't see any good usecases for them. I also wonder what advantages they provide over free monads and classic mtl stacks.
I know this is an old thread, but i thought I'd answer it anyway just in case
what [...] is a so-called "Freer Monad"
according to the original paper Freer Monads, More Extensible Effects a "Freer Monad" is essentially a Free Monad without the necessary Functor constraint of a Free Monad.
A free monad is basically the essence of the monadic structure; the "smallest" thing that is still a monad. A very nice practial explanation approach can be found in this article. This article also shows that the "normal" free monad needs a Functor constraint.
However, it is often quite tedious adding the functor constraint in every function (and sometimes maybe even weird to implement), and as it turns out, by "moving the functor functionality" to an argument for the Impure constructor so that the implementing side can alter the type of the output itself (so without a general functor), it is possible to get rid of this constraint. This is done by using GADTs: (example from the Freer Monads paper)
data Free f a = Pure a
| Impure (f (Free f a))
instance Functor f => Monad (Free f) where
becomes
data FFree f a where
Pure :: a → FFree f a
Impure :: f x → (x → FFree f a) → FFree f a
instance Monad (FFree f) where
[...]
Impure fx k’ >>= k = Impure fx (k’ >>> k)
This basically lets the later implementation choose how to perform the fmap operation fixed [pun not intended] to the appropriate "output/wrapped type".
So the fundamental difference is essentially usability and generality.
As there was some confusion: FFree is the Freer monad and corresponds to Eff in the package freer-simple.
good usecases for them
Freer monads, just as well as Free monads lend themselves for constructing DSLs.
consider for example a type
data Lang r where
LReturn :: Var -> Lang Int
LPrint :: IntExpr -> Lang ()
LAssign :: Var -> IntExpr -> Lang ()
LRead :: Var -> Lang Int
this tells me that there are a couple of operations to be performed in Lang: return x print x assign x y read y.
We use GADTs here so that we can also specify what output the individual actions are going to have. This comes in quite handy if we write functions in our DSL, because their output can be tpechecked.
adding some convenience functions (that can acutally be derived):
lReturn :: Member Lang effs
=> Var -> Eff effs Int
lReturn = send . LReturn
lPrint :: Member Lang effs
=> IntExpr -> Eff effs ()
lPrint = send . LPrint
lAssign :: Member Lang effs
=> Var -> IntExpr -> Eff effs ()
lAssign v i = send $ LAssign v i
lRead :: Member Lang effs
=> Var -> Eff effs Int
lRead = send . LRead
(this is already written using freer)
now we can use them like this: (assuming that IntExpr contains Variables and Ints)
someFunctionPrintingAnInt = do
lAssign (Var "a") (IE_Int 12)
lPrint (IE_Var $ Var "a")
these functions now enable you to have a DSL that can be interpreted in different ways. All needed for this is an interpreter with a specific type for effs (which is ~~ a type level list of freer monad "instances)
so freer takes the idea of the freer monads and packs it into an effect system.
this interpreter could look something like this:
runLangPure :: Eff '[Lang] Int -> Either () Int -- [StateMap]
runLangPure program = fst . fst $
run (runWriter (runState empty (runError (reinterpret3 go program))))
where
go :: Lang v -> Eff '[Error (), State StateMap, Writer [String]] v
go (LReturn var) = get >>= go (Eval stmt) >>= tell . []
go (LPrint expr) = do
store <- get
value <- evalM expr
tell [show value]
go (LAssign var expr) = do
value <- evalM expr
--modify state (change var)
go (LRead var) = do
strValue <- getLine
get >>= insert var (stringToInt strValue)
the run... part specifies the initial "state" of the monads. the go part is the interpreter itself, interpreting the different possible actions.
Note that one can use the functions get and tell in the same do block even though they are part of different monads, which brings us to
I also wonder what advantages do they provide over free monads and classic mtl stacks.
the implementation allows to use monadic actions of different parts of the "monad stack" without lifting.
About the implementation:
To understand this, we look at it from a high level of abstraction:
the auxiliary functions of our DSL are send to Eff effs where it is required that Member Lang effs.
So the Member constraint is just a way of declaing that Lang is in the type-level list effs in Member Lang effs. (basically typelevel elem)
The Eff monad has the functionality to "ask" the Members of the type level list of monads whether they can handle the current value (remeber, the operations are just values that are intrepreted subsequently). if so their intrepretation is executed, if not, the question is handed off to the next monad in the list.
This becomes more intuitive and understandable when spending some time in the freer-simple code base.

'ExceptT ResourceT' vs 'ResourceT ExceptT'

Real World Haskell states that "Transformer stacking order is important". However, I can't seem to figure out if there's a difference between ExceptT (ResourceT m) a and ResourceT (ExceptT m) a. Will they interfere with each other?
In this example, there is no real difference between both orders. The reason being: unlike many transformers including ExceptT, the resource transformer does not “inject” its own doings into the base monad you apply it to, but rather start off the entire action with passing in the release references.
If you write out the types (I'll refer to MaybeT instead of ExceptT for the sake of simplicity; they're obviously equivalent for the purpose of this question) then you have basically
type MaybeResourceT m a = MaybeT (IORef RelMap -> m a)
= IORef RelMap -> m (Maybe a)
type ResourceMaybeT m a = ResourceT (m (Maybe a))
= IORef RelMap -> m (Maybe a)
i.e. actually equivalent types. I suppose you could also show that for the operations.

Is Haskell designed to encourage Hungarian Notation?

I'm learning Haskell and started noticing common suffixes in functions like:
debugM
mapM_
mapCE
Which is known as Hungarian Notation. But at the same time I can use type classes to write non-ambiguous code like:
show
return
Since functions like map are so common and used in many contexts, why not let type checker to pick correct polymorphic version of map, fmap, mapM, mapM_ or mapCE?
There's a little bit of "Hungarian notation", but it's quite different. In short, Haskell's type system removes the need for most of it.
The map/mapM thing is a neat example. These two functions confer the exact same concept, but cannot be polymorphically represented because abstracting over the difference would be really noisy. So we pick a Hungarian notation instead.
To be clear, the two types are
map :: (a -> b) -> ([a] -> [b])
mapM :: Monad m => (a -> m b) -> ([a] -> m [b])
These look similar, all mapM does is add the monad, but not the same. The structure is revealed when you make the following synonyms
type Arr a b = a -> b
type Klei m a b = a -> m b
and rewrite the types as
map :: Arr a b -> Arr [a] [b]
mapM :: Monad m => Klei m a b -> Klei m [a] [b]
The thing to note is that Arr and Monad m => Klei m are often extremely similar things. They both form a certain structure known as a "category" which allows us to hoist all kinds of computation inside of it. [0]
What we'd like is to abstract over the choice of category with something like
class Mapping cat where
map :: cat a b -> cat [a] [b]
instance Mapping (->) where map = Prelude.map
instance Monad m => Mapping (Klei m) where map = mapM -- in spirit anyway
but it turns out that there is way more to be gained by abstracting over the list part with Functor [1]
class Functor f where
map :: (a -> b) -> (f a -> f b)
instance Functor [] where
map = Prelude.map
instance Functor Maybe where
map Nothing = Nothing
map (Just a) = Just (f a)
and so for simplicity's sake, we use Hungarian notation to make the difference of category instead of rolling it up into Haskell's polymorphism functionality.
[0] Notably, the fact that Klei m is a category implies m is a monad and the category laws become exactly the monad laws. In particular, that's my favorite way for remembering what the monad laws are.
[1] Technically, the sole method of Functor is called fmap not map, but it could and perhaps should have been called just map. The f was added so that the type signature for map remains simple (specialized to lists) and thus is a little less intimidating to beginners. Whether or not that was the right decision is a debate that continues today.
Your assumption is that all of these do roughly the same thing - they don't. map and fmap are pretty much the same function - map is just fmap specialized to the [] functor (either for historical reasons, or so that beginners would get less confusing type errors - I'm not sure).
mapM and mapM_ on the other hand are like map followed by sequence or sequence_ respectively - while what they're doing may look related, they're doing different things. Incidentally, the function that behaves like fmap for monads is... fmap (which is also aliased with a specialized signature to liftM, for historical reasons), as Monads are, by definition, also Functors; note that this is, right now, not enforced by the standard library - a historical oversight that should be corrected with GHC 7.10 if I'm not mistaken.
I don't know what to tell you about debugM and mapCE as I haven't seen these before.

Transformation under Transformers

I'm having a bit of difficulty with monad transformers at the moment. I'm defining a few different non-deterministic relations which make use of transformers. Unfortunately, I'm having trouble understanding how to translate cleanly from one effectful model to another.
Suppose these relations are "foo" and "bar". Suppose that "foo" relates As and Bs to Cs; suppose "bar" relates Bs and Cs to Ds. We will define "bar" in terms of "foo". To make matters more interesting, the computation of these relations will fail in different ways. (Since the bar relation depends on the foo relation, its failure cases are a superset.) I therefore give the following type definitions:
data FooFailure = FooFailure String
data BarFailure = BarSpecificFailure | BarFooFailure FooFailure
type FooM = ListT (EitherT FooFailure (Reader Context))
type BarM = ListT (EitherT BarFailure (Reader Context))
I would then expect to be able to write the relations with the following function signatures:
foo :: A -> B -> FooM C
bar :: B -> C -> BarM D
My problem is that, when writing the definition for "bar", I need to be able to receive errors from the "foo" relation and properly represent them in "bar" space. So I'd be fine with a function of the form
convert :: (e -> e') -> ListT (EitherT e (Reader Context) a
-> ListT (EitherT e' (Reader Context) a
I can even write that little beast by running the ListT, mapping on EitherT, and then reassembling the ListT (because it happens that m [a] can be converted to ListT m a). But this seems... messy.
There's a good reason I can't just run a transformer, do some stuff under it, and generically "put it back"; the transformer I ran might have effects and I can't magically undo them. But is there some way in which I can lift a function just far enough into a transformer stack to do some work for me so I don't have to write the convert function shown above?
I think convert is a good answer, and using Control.Monad.Morph and Control.Monad.Trans.Either it's (almost) really simple to write:
convert :: (Monad m, Functor m, MFunctor t)
=> (e -> e')
-> t (EitherT e m) b -> t (EitherT e' m) b
convert f = hoist (bimapEitherT f id)
the slight problem is that ListT isn't an instance of MFunctor. I think this is the author boycotting ListT because it doesn't follow the monad transformer laws though because it's easy to write a type-checking instance
instance MFunctor ListT where hoist nat (ListT mas) = ListT (nat mas)
Anyway, generally take a look at Control.Monad.Morph for dealing with natural transformations on (parts of) transformer stacks. I'd say that fits the definition of lifting a function "just enough" into a stack.

What general structure does this type have?

While hacking something up earlier, I created the following code:
newtype Callback a = Callback { unCallback :: a -> IO (Callback a) }
liftCallback :: (a -> IO ()) -> Callback a
liftCallback f = let cb = Callback $ \x -> (f x >> return cb) in cb
runCallback :: Callback a -> IO (a -> IO ())
runCallback cb =
do ref <- newIORef cb
return $ \x -> readIORef ref >>= ($ x) . unCallback >>= writeIORef ref
Callback a represents a function that handles some data and returns a new callback that should be used for the next notification. A callback which can basically replace itself, so to speak. liftCallback just lifts a normal function to my type, while runCallback uses an IORef to convert a Callback to a simple function.
The general structure of the type is:
data T m a = T (a -> m (T m a))
It looks much like this could be isomorphic to some well-known mathematical structure from category theory.
But what is it? Is it a monad or something? An applicative functor? A transformed monad? An arrow, even? Is there a search engine similar Hoogle that lets me search for general patterns like this?
The term you are looking for is free monad transformer. The best place to learn how these work is to read the "Coroutine Pipelines" article in issue 19 of The Monad Reader. Mario Blazevic gives a very lucid description of how this type works, except he calls it the "Coroutine" type.
I wrote up his type in the transformers-free package and then it got merged into the free package, which is its new official home.
Your Callback type is isomorphic to:
type Callback a = forall r . FreeT ((->) a) IO r
To understand free monad transformers, you need to first understand free monads, which are just abstract syntax trees. You give the free monad a functor which defines a single step in the syntax tree, and then it creates a Monad from that Functor that is basically a list of those types of steps. So if you had:
Free ((->) a) r
That would be a syntax tree that accepts zero or more as as input and then returns a value r.
However, usually we want to embed effects or make the next step of the syntax tree dependent on some effect. To do that, we simply promote our free monad to a free monad transformer, which interleaves the base monad between syntax tree steps. In the case of your Callback type, you are interleaving IO in between each input step, so your base monad is IO:
FreeT ((->) a) IO r
The nice thing about free monads is that they are automatically monads for any functor, so we can take advantage of this to use do notation to assemble our syntax tree. For example, I can define an await command that will bind the input within the monad:
import Control.Monad.Trans.Free
await :: (Monad m) => FreeT ((->) a) m a
await = liftF id
Now I have a DSL for writing Callbacks:
import Control.Monad
import Control.Monad.Trans.Free
printer :: (Show a) => FreeT ((->) a) IO r
printer = forever $ do
a <- await
lift $ print a
Notice that I never had to define the necessary Monad instance. Both FreeT f and Free f are automatically Monads for any functor f, and in this case ((->) a) is our functor, so it automatically does the right thing. That's the magic of category theory!
Also, we never had to define a MonadTrans instance in order to use lift. FreeT f is automatically a monad transformer, given any functor f, so it took care of that for us, too.
Our printer is a suitable Callback, so we can feed it values just by deconstructing the free monad transformer:
feed :: [a] -> FreeT ((->) a) IO r -> IO ()
feed as callback = do
x <- runFreeT callback
case x of
Pure _ -> return ()
Free k -> case as of
[] -> return ()
b:bs -> feed bs (k b)
The actual printing occurs when we bind runFreeT callback, which then gives us the next step in the syntax tree, which we feed the next element of the list.
Let's try it:
>>> feed [1..5] printer
1
2
3
4
5
However, you don't even need to write all this up yourself. As Petr pointed out, my pipes library abstracts common streaming patterns like this for you. Your callback is just:
forall r . Consumer a IO r
The way we'd define printer using pipes is:
printer = forever $ do
a <- await
lift $ print a
... and we can feed it a list of values like so:
>>> runEffect $ each [1..5] >-> printer
1
2
3
4
5
I designed pipes to encompass a very large range of streaming abstractions like these in such a way that you can always use do notation to build each streaming component. pipes also comes with a wide variety of elegant solutions for things like state and error handling, and bidirectional flow of information, so if you formulate your Callback abstraction in terms of pipes, you tap into a ton of useful machinery for free.
If you want to learn more about pipes, I recommend you read the tutorial.
The general structure of the type looks to me like
data T (~>) a = T (a ~> T (~>) a)
where (~>) = Kleisli m in your terms (an arrow).
Callback itself doesn't look like an instance of any standard Haskell typeclass I can think of, but it is a Contravariant Functor (also known as Cofunctor, misleadingly as it turns out). As it is not included in any of the libraries that come with GHC, there exist several definitions of it on Hackage (use this one), but they all look something like this:
class Contravariant f where
contramap :: (b -> a) -> f a -> f b
-- c.f. fmap :: (a -> b) -> f a -> f b
Then
instance Contravariant Callback where
contramap f (Callback k) = Callback ((fmap . liftM . contramap) f (f . k))
Is there some more exotic structure from category theory that Callback possesses? I don't know.
I think that this type is very close to what I have heard called a 'Circuit', which is a type of arrow. Ignoring for a moment the IO part (as we can have this just by transforming a Kliesli arrow) the circuit transformer is:
newtype CircuitT a b c = CircuitT { unCircuitT :: a b (c, CircuitT a b c) }
This is basicall an arrow that returns a new arrow to use for the next input each time. All of the common arrow classes (including loop) can be implemented for this arrow transformer as long as the base arrow supports them. Now, all we have to do to make it notionally the same as the type you mention is to get rid of that extra output. This is easily done, and so we find:
Callback a ~=~ CircuitT (Kleisli IO) a ()
As if we look at the right hand side:
CircuitT (Kleisli IO) a () ~=~
(Kliesli IO) a ((), CircuitT (Kleisli IO) a ()) ~=~
a -> IO ((), CircuitT (Kliesli IO) a ())
And from here, you can see how this is similar to Callback a, except we also output a unit value. As the unit value is in a tuple with something else anyway, this really doesn't tell us much, so I would say they're basically the same.
N.B. I used ~=~ for similar but not entirely equivalent to, for some reason. They are very closely similar though, in particular note that we could convert a Callback a into a CircuitT (Kleisli IO) a () and vice-versa.
EDIT: I would also fully agree with the ideas that this is A) a monadic costream (monadic operation expecitng an infinite number of values, I think this means) and B) a consume-only pipe (which is in many ways very similar to the circuit type with no output, or rather output set to (), as such a pipe could also have had output).
Just an observation, your type seems quite related to Consumer p a m appearing in the pipes library (and probably other similar librarties as well):
type Consumer p a = p () a () C
-- A Pipe that consumes values
-- Consumers never respond.
where C is an empty data type and p is an instance of Proxy type class. It consumes values of type a and never produces any (because its output type is empty).
For example, we could convert a Callback into a Consumer:
import Control.Proxy
import Control.Proxy.Synonym
newtype Callback m a = Callback { unCallback :: a -> m (Callback m a) }
-- No values produced, hence the polymorphic return type `r`.
-- We could replace `r` with `C` as well.
consumer :: (Proxy p, Monad m) => Callback m a -> () -> Consumer p a m r
consumer c () = runIdentityP (run c)
where
run (Callback c) = request () >>= lift . c >>= run
See the tutorial.
(This should have been rather a comment, but it's a bit too long.)

Resources