[Haskell-cafe] ANN: data-textual: Human-friendly textual representations

2013-04-23 Thread Mikhail Vorozhtsov

Hello lists,

I'm pleased to announce the first release of data-textual[1], a library 
that provides human-friendly counterparts (called Printable/Textual) of 
the compiler-friendly Show/Read type classes. The library is intended to 
be used for printing and parsing of non-compound and non-polymorphic 
compound data (e.g. numbers, network and hardware addresses, date/time, 
etc).


A quick example (vs network-ip[2] library):

λ> import Data.Maybe (fromJust)
λ> import Data.Textual
λ> import Network.IP.Addr

λ> let x = fromString "[dead::b:e:e:f]:123" :: Maybe Inet6Addr
λ> x
Just (InetAddr {inetHost = ip6FromWords 0xdead 0x0 0x0 0x0 0xb 0xe 0xe 
0xf, inetPort = 123})

λ> toString (fromJust x)
"[dead::b:e:e:f]:123"

λ> let y = fromStringAs aNet4Addr "192.168.100.1/24"
λ> y
Just (netAddr (ip4FromOctets 192 168 100 1) 24)
λ> toText (netPrefix $ fromJust y)
"192.168.100.0"

[1] http://hackage.haskell.org/package/data-textual
[2] http://hackage.haskell.org/package/network-ip

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: text-printer - abstract interface for text builders/printers

2013-03-22 Thread Mikhail Vorozhtsov

Hello,

I was writing a library for working with IP addresses when I found 
myself puzzled with the number of contexts in which the textual 
representation of an address could be used: plain strings, bytestring 
builders (ASCII/UTF8), text builders, pretty printers, etc. I could've 
just written an `addressToString :: Address -> String` function, but 
that would be suboptimal: (a) namespace pollution (that's a lot of 
*ToString's if you count IPv4/6, network addresses, socket addresses, 
etc) and (b) some contexts can take advantage of the fact that textual 
representations are ASCII (e.g. UTF8 bytestring builder).


And so the text-printer[1] was born. It is mainly two type classes. One 
for injecting text into a monoid, with special methods for ASCII and 
UTF-8 characters/strings. The other provides the default injection for 
values of a type (think of the `Pretty` type class in pretty printing 
libraries), the textual representation is supposed to be simple 
(single-line). Plus some convenient combinators and number formatters.


[1] http://hackage.haskell.org/package/text-printer

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-dword: Long binary words from short ones

2012-10-11 Thread Mikhail Vorozhtsov

On 10/11/2012 06:09 PM, Henning Thielemann wrote:


On Thu, 11 Oct 2012, Mikhail Vorozhtsov wrote:


I'm pleased to announce my new little library, data-dword[1]. It
provides Template Haskell utilities for defining binary word data
types from low and high halves, e.g.

data Word96 = Word96 Word32 Word64 -- strictness is configurable
data Int96 = Int96 Int32 Word64


What is the advantage over 'largeword' which does the same with plain
Haskell 98?

http://hackage.haskell.org/package/largeword

1) Control over strictness of the halves
2) Signed types
3) Extra instances/operations
4) Probably faster, due to specialization/inlining/rewrite rules.
5) Test suite


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: data-dword: Long binary words from short ones

2012-10-10 Thread Mikhail Vorozhtsov

Hi.

I'm pleased to announce my new little library, data-dword[1]. It 
provides Template Haskell utilities for defining binary word data types 
from low and high halves, e.g.


data Word96 = Word96 Word32 Word64 -- strictness is configurable
data Int96 = Int96 Int32 Word64

-- All instances are fully implemented (including `quotRem`, etc)
instance Bounded, Enum, Eq, Integral, Num, Ord, Read,
 Real, Show, Ix, Bits, Hashable

-- Extra bit-manipulating functions, unwrapped addition and
-- multiplication, etc.
instance BinaryWord, DoubleWord

-- Rewrite rules for converting to/from the standard integral types
{-# RULES "fromIntegral/..." ... #-}

The library comes with a pretty thorough test suite (that ATM has some 
failures on x86-32 due to bug #7233[2] in the base library).


[1] http://hackage.haskell.org/package/data-dword
[2] http://hackage.haskell.org/trac/ghc/ticket/7233

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call to arms: lambda-case is stuck and needs your help

2012-07-16 Thread Mikhail Vorozhtsov
Good news everyone. LambdaCase and MultiWayIf are now in HEAD. Thanks
for participating in the final push!

On Thu, Jul 5, 2012 at 9:42 PM, Mikhail Vorozhtsov
 wrote:
>
> Hi.
>
> After 21 months of occasional arguing the lambda-case proposal(s) is in 
> danger of being buried under its own trac ticket comments. We need fresh 
> blood to finally reach an agreement on the syntax. Read the wiki page[1], 
> take a look at the ticket[2], vote and comment on the proposals!
>
> P.S. I'm CC-ing Cafe to attract more people, but please keep the discussion 
> to the GHC Users list.
>
> [1] http://hackage.haskell.org/trac/ghc/wiki/LambdasVsPatternMatching
> [2] http://hackage.haskell.org/trac/ghc/ticket/4359

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Call to arms: lambda-case is stuck and needs your help

2012-07-05 Thread Mikhail Vorozhtsov

Hi.

After 21 months of occasional arguing the lambda-case proposal(s) is in 
danger of being buried under its own trac ticket comments. We need fresh 
blood to finally reach an agreement on the syntax. Read the wiki 
page[1], take a look at the ticket[2], vote and comment on the proposals!


P.S. I'm CC-ing Cafe to attract more people, but please keep the 
discussion to the GHC Users list.


[1] http://hackage.haskell.org/trac/ghc/wiki/LambdasVsPatternMatching
[2] http://hackage.haskell.org/trac/ghc/ticket/4359

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: exists-0.1

2012-02-07 Thread Mikhail Vorozhtsov

On 02/07/2012 04:05 PM, Gábor Lehel wrote:

On Tue, Feb 7, 2012 at 7:23 AM, Mikhail Vorozhtsov
  wrote:

Even better, you can write

type ExistentialWith c e = (Existential e, c ~ ConstraintOf e)

instead of

class(Existential e, c ~ ConstraintOf e) =>  ExistentialWith c e
instance (Existential e, c ~ ConstraintOf e) =>  ExistentialWith c e

and drop UndecidableInstances.


I actually mentioned this in the preceding point of the [snip]. The
problem is that it's not even better because you can't partially apply
it.
Ah, sorry, I got sloppy. Have you encountered situations where partial 
application of such "constraint aliases" becomes a problem?


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: exists-0.1

2012-02-07 Thread Mikhail Vorozhtsov

On 02/07/2012 06:49 PM, Yves Parès wrote:

Are there documentation on constraints being types, how they can be
declared/handled and what are the interests?

The GHC User's Guide has (somewhat short) section
http://www.haskell.org/ghc/docs/latest/html/users_guide/constraint-kind.html

Blog posts:
http://blog.omega-prime.co.uk/?p=127
http://comonad.com/reader/2011/what-constraints-entail-part-1/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: exists-0.1

2012-02-06 Thread Mikhail Vorozhtsov

On 02/06/2012 03:32 AM, Gábor Lehel wrote:

There's a common pattern in Haskell of writing:

data E where E :: C a =>  a ->  E
also written
data E = forall a. C a =>  E a

I recently uploaded a package to Hackage which uses the new
ConstraintKinds extension to factor this pattern out into an Exists
type parameterized on the constraint, and also for an Existential type
class which can encompass these kind of types:

http://hackage.haskell.org/package/exists

My motivation was mostly to play with my new toys, if it turns out to
be useful for anything that's a happy and unexpected bonus.

Some interesting things I stumbled upon while writing it:


[snip]

- One of the advantages FunctionalDependencies has over TypeFamilies
is that type signatures using them tend to be more readable and
concise than ones which have to write out explicit equality
constraints. For example, foo :: MonadState s m =>  s ->  m () is nicer
than foo :: (MonadState m, State m ~ s) =>  s ->  m (). But with
equality superclass constraints (as of GHC 7.2), it's possible to
translate from TF-form to FD-form (but not the reverse, as far as I
know): class (MonadStateTF m, s ~ State m) =>  MonadStateFDish s m;
instance (MonadStateTF m, s ~ State m) =>  MonadStateFDish s m.

Even better, you can write

type ExistentialWith c e = (Existential e, c ~ ConstraintOf e)

instead of

class(Existential e, c ~ ConstraintOf e) => ExistentialWith c e
instance (Existential e, c ~ ConstraintOf e) => ExistentialWith c e

and drop UndecidableInstances.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad-control rant

2012-01-31 Thread Mikhail Vorozhtsov

On 01/29/2012 11:55 PM, Edward Z. Yang wrote:

Excerpts from Mikhail Vorozhtsov's message of Sun Jan 29 05:34:17 -0500 2012:

[snip]

I think it is one of the simplest layouts one can some up with. I'll try
to explain the motivation behind each inclusion.

ABORTS(μ) ⊆ RECOVERABLE_ZEROS(μ)


I'm sorry, I cannot understand the discussion below because you haven't
defined precisely what ABORTS means.  (See also below; I think it's
time to write something up.)

ABORTS(μ) = { abort e | e ∷ e }


Why are they not equal? After all we can always write `recover weird $
\e → abort e`, right? But zeros from `RECOVERABLE_ZEROES \ ABORTS` may
have additional effects. For example, recoverable interruptions could
permanently disable blocking operations (you can close a socket but you
can't read/write from it). Why the inclusion is not the other way
around? Well, I find the possibility of `abort e1` and `abort e2` having
different semantics (vs `recover` or `finally`) terrifying. If you can
throw unrecoverable exceptions, you should have a different function for
that.

RECOVERABLE_ZEROS(μ) ⊆ FINALIZABLE_ZEROS(μ)

If a zero is recoverable, we can always "finalize" it (by
catch-and-rethrow).

FINALIZABLE_ZEROS(μ) ⊆ ZEROS(μ)

This one is pretty obvious. One example of non-finalizable zeros is
bottoms in a non-MonadUnbottom monad (e.g. my X monad). Another would be
`System.Posix.Process.exitImmediately`.


Ugh, don't talk to me about the exit() syscall ;-)


[snip]

Yes, I think for some this is the crux of the issue. Indeed, it is why
monad-control is so appealing, it dangles in front of us the hope that
we do, in fact, only need one API.

But, if some functions in fact do need to be different between the two
cases, there's not much we can do, is there?

Yes, but on the other hand I don't want to reimplement ones that are the
same. I want to have a modular solution precisely because it allows both
sharing and extensibility.


The cardinal sin of object oriented programming is building abstractions in
deference of code reuse, not the other way around.

Stepping back a moment, I think the most useful step for you is to write up
a description of your system, incorporating the information from this 
discussion,
and once we have the actual article in hand we can iterate from there.
I'll probably release an updated (and documented) version of 
monad-abort-fd when I have enough time. At the moment I'm just 
overloaded with work.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad-control rant

2012-01-29 Thread Mikhail Vorozhtsov

On 01/24/2012 10:56 PM, Edward Z. Yang wrote:

Excerpts from Mikhail Vorozhtsov's message of Tue Jan 24 07:26:35 -0500 2012:

Sure, but note that evaluate for IO is implemented with seq# under the hood,
so as long as you actually get ordering in your monad it's fairly 
straightforward
to implement evaluate.  (Remember that the ability to /catch/ an error
thrown by evaluate is separate from the ability to /evaluate/ a thunk which
might throw an error.)

Yes, of course. The purpose of MonadUnbottom is to guarantee that
`Control.Exception.throw e ∷ μ α = abort (toException e)`. The choice of
a class method is somewhat arbitrary here (one could go with 'α → μ
(Either SomeException α)` or with no methods at all).


I want to highlight the strangeness of "exception-like" monads that don't have
a MonadUnbottom instance (for concreteness, let's assume that there are no
methods associated with it.  What would you expect this code to do?

 catch (throw (UserError "Foo")) (putStrLn "caught")>>  putStrLn "ignored 
result"

If we don't have ordering, the monad is permitted to entirely ignore the thrown
exception. (In fact, you can see this with the lazy state monad, so long as you
don't force the state value.) Just like in lazy IO, exceptions can move around
to places you don't expect them.
You are trying to make bottoms a new null pointers. Sometimes it just 
doesn't worth the effort (or depends on the interpreter you use). I want 
to have the option to say: sorry, in this particular case (monad) I 
don't distinguish `error` from non-termination, so `catch ⊥ h = ⊥`.


[snip]

Stepping back for a moment, I think the conversation here would be helped if we
dropped loaded terms like "general" and "precise" and talked about concrete
properties:

  - A typeclass has more/less laws (equivalently, the typeclass constrains
what else an object can do, outside of an instance),
  - A typeclass requires an instance to support more/less operations,
  - A typeclass can be implemented for more/less objects

One important point is that "general" is not necessarily "good".  For example,
imagine I have a monad typeclass that has the "referential transparency" law
(why are you using a monad?! Well, never mind that for now.)  Obviously, the IO
monad cannot be validly be an instance of this typeclass. But despite only
admitting instances for a subset of monads, being "less general", I think most
people who've bought into Haskell agree, referentially transparent code
is good code!  This is the essential tension of generality and specificity:
if it's too general, "anything goes", but if it's too specific, it lacks 
elegance.

So, there is a definitive and tangible difference between "all bottoms are 
recoverable"
and "some bottoms are recoverable."  The former corresponds to an extra law
along the lines of "I can always catch exceptions."  This makes reduces the
number of objects the typeclass can be implemented for (or, if you may,
it reduces the number of admissible implementations for the typeclass), but
I would like to defend this as good, much like referential transparency
is a good restriction.

OK, what MonadUnrecoverableException exactly do you have in mind?


I don't know, I've never needed one! :^)


I was thinking about something like (no asynchronous exceptions for now):

-- ABORTS(μ) ⊆ RECOVERABLE_ZEROS(μ) ⊆ FINALIZABLE_ZEROS(μ) ⊆ ZEROS(μ)


Do you have a motivation behind this division?  Are there non-finalizable
but recoverable zeros? Why can't I use aborts to throw non-recoverable
or non-finalizable zeros? Maybe there should be a hierarchy of recoverability,
since I might have a top-level controller which can "kill and spawn" processes?
Maybe we actually want a lattice structure?
I think it is one of the simplest layouts one can some up with. I'll try 
to explain the motivation behind each inclusion.


ABORTS(μ) ⊆ RECOVERABLE_ZEROS(μ)

Why are they not equal? After all we can always write `recover weird $ 
\e → abort e`, right? But zeros from `RECOVERABLE_ZEROES \ ABORTS` may 
have additional effects. For example, recoverable interruptions could 
permanently disable blocking operations (you can close a socket but you 
can't read/write from it). Why the inclusion is not the other way 
around? Well, I find the possibility of `abort e1` and `abort e2` having 
different semantics (vs `recover` or `finally`) terrifying. If you can 
throw unrecoverable exceptions, you should have a different function for 
that.


RECOVERABLE_ZEROS(μ) ⊆ FINALIZABLE_ZEROS(μ)

If a zero is recoverable, we can always "finalize" it (by 
catch-and-rethrow).


FINALIZABLE_ZEROS(μ) ⊆ ZEROS(μ)

This one is pretty obvious. One example of non-finalizable zeros is 
bottoms in a non-MonadUnbottom monad (e.g. my X monad). Another would be 
`System.Posix.Process.exitImmediately`.



Someone has put a term for this problem before: it is an "embarassment of 
riches".
There is so much latitude of choice here that it's hard to know what the 

Re: [Haskell-cafe] Monad-control rant

2012-01-24 Thread Mikhail Vorozhtsov

On 01/22/2012 02:47 AM, Edward Z. Yang wrote:

Excerpts from Mikhail Vorozhtsov's message of Sat Jan 21 09:25:07 -0500 2012:

But I also believe that you can't use this as justification to stick your
head in the sand, and pretend bottoms don't exist (regardless of whether or
not we'rd talking about asynchronous exceptions.)  The reason is that
understanding how code behaves in the presence of bottoms tells you
some very important information about its strictness/laziness, and this
information is very important for managing the time and space usage of your 
code.

I totally agree with you. My point is that things like `evaluate` and
`try undefined = return (Left (ErrorCall "Prelude.undefined"))` are
magic and should not be taken for granted. Bottoms are everywhere, but
the ability to distinguish them from normal values is special. We could
have a separate abstraction for this ability:

class MonadAbort SomeException μ ⇒ MonadUnbottom μ where
-- evaluate a = abort (toException e), if WHNF(a) = throw e
--  return WHNF(a), otherwise
-- join (evaluate m) = m, ensures that `undefined ∷ μ α = abort ...`
evaluate ∷ α → μ α

or something like that.


Sure, but note that evaluate for IO is implemented with seq# under the hood,
so as long as you actually get ordering in your monad it's fairly 
straightforward
to implement evaluate.  (Remember that the ability to /catch/ an error
thrown by evaluate is separate from the ability to /evaluate/ a thunk which
might throw an error.)
Yes, of course. The purpose of MonadUnbottom is to guarantee that 
`Control.Exception.throw e ∷ μ α = abort (toException e)`. The choice of 
a class method is somewhat arbitrary here (one could go with 'α → μ 
(Either SomeException α)` or with no methods at all).



The identity monad for which error "FOO" is a left zero is a legitimate monad:
it's the strict identity monad (also known as the 'Eval' monad.)  Treatment
of bottom is a part of your abstraction!

(I previously claimed that we could always use undefined :: m a as a left zero,
I now stand corrected: this statement only holds for 'strict' monads, a moniker 
which
describes IO, STM and ST, and any monads based on them. Indeed, I'll stick my 
neck
out and claim any monad which can witness bottoms must be strict.)

Bottoms may be zeros in strict monads, but they are not necessarily
recoverable. `runX (recover (True<$ undefined) (const $ return False))`
may be equivalent to `undefined`, not to `runX (return False)`. See my
example of such "IO based" X below. I want to have options.


I think this touches on a key disagreement, which is that I think that in 
IO-like
monads you need to be able to recover from bottoms. See below.


Let's consider the following X (using the `operational` library):

data Command α where
-- Note that we do not employ exceptions here. If command stream
-- transport fails, the interpreter is supposed to start the
-- appropriate emergency procedures (or switch to a backup channel).
-- Sending more commands wouldn't help anyway.
AdjustControlRods ∷ Height → Command Bool
AdjustCoolantFlow ∷ ...
AdjustSecondaryCoolantFlow ∷ ...
RingTheAlarm ∷ ...
-- We could even add an unrecoverable (/in the Controller monad/)
-- error and the corresponding "finally" command.
...
ReadCoolantFlow ∷ ...
...

type Controller = Program Command

-- Run a simulation
simulate ∷ PowerPlantState → Controller α → (α, PowerPlantState)
-- Run for real
run ∷ Controller α → IO α

type X = ErrorT SomeException Controller

So the effects here are decoupled from control operations. Would you
still say that finalizers are useless here because exception handling is
implemented by pure means?


I think your simulation is incomplete. Let's make this concrete: suppose I'm
running one of these programs, and I type ^C (because I want to stop the
program and do something else.)  In normal 'run' operation, I would expect
the program to run some cleanup operations and then exit.  But there's
no way for the simulation to do that! We've lost something here.
I'm not sure I would want to go ^C on a power plant controlling 
software, but OK. We could accommodate external interruptions by:


1. Adding `Finally ∷ Controller α → (Maybe α → Controller β) → Command 
(α, β)` and a `MonadFinally Controller` instance (and modifying 
interpreters to maintain finalizer stacks):


instance MonadFinally Controller where
  finally' m = singleton . Finally m

2. Writing more simulators with different interruption strategies (e.g. 
using StdGen, or `interrupt ∷ PowerPlantState → Bool`, etc).



You are free to create another interface that supports "unrecoverable"
exceptions, and to supply appropriate semantics for this more complicated
interface. However, I don't think it's appropriate to claim this interface
is appropriate for IO style exceptions, which are (and users expect) to always
be recoverable.

Why exactly not? I think that everything usefu

Re: [Haskell-cafe] Monad-control rant

2012-01-21 Thread Mikhail Vorozhtsov

On 01/18/2012 10:43 PM, Edward Z. Yang wrote:

Excerpts from Mikhail Vorozhtsov's message of Wed Jan 18 08:47:37 -0500 2012:

Well, that's the kind of language we live in.  The denotation of our language
always permits for bottom values, and it's not a terribly far jump from there
to undefined and error "foo".  I don't consider the use of these facilities
to be a trap door.

Non-termination is a bug (when termination is expected) and I wish that
`undefined` and `error` would be interpreted as bugs too (when a value
is expected). Putting asynchronous exceptions aside, in some situations
it might be useful to recover from bugs, but they should not be treated
like /errors/, something that is expected to happen. At least I like to
think this way when `error`s meet monads. For example, what is the
meaning of `error` in this piece:

nasty ∷ Monad μ ⇒ μ ()
nasty = error "FOO">>  return ()

runIdentity nasty ~>  () -- error is not necessarily a left zero!
runIdentity $ runMaybeT nasty ~>  error

It's just slipping through abstraction and doing what it wants.


I can't argue with "error should be used sparingly, and usually in cases
where there is an indication of developer error, rather than user error."
It's good, sound advice.

But I also believe that you can't use this as justification to stick your
head in the sand, and pretend bottoms don't exist (regardless of whether or
not we'rd talking about asynchronous exceptions.)  The reason is that
understanding how code behaves in the presence of bottoms tells you
some very important information about its strictness/laziness, and this
information is very important for managing the time and space usage of your 
code.
I totally agree with you. My point is that things like `evaluate` and 
`try undefined = return (Left (ErrorCall "Prelude.undefined"))` are 
magic and should not be taken for granted. Bottoms are everywhere, but 
the ability to distinguish them from normal values is special. We could 
have a separate abstraction for this ability:


class MonadAbort SomeException μ ⇒ MonadUnbottom μ where
  -- evaluate a = abort (toException e), if WHNF(a) = throw e
  --  return WHNF(a), otherwise
  -- join (evaluate m) = m, ensures that `undefined ∷ μ α = abort ...`
  evaluate ∷ α → μ α

or something like that.



The identity monad for which error "FOO" is a left zero is a legitimate monad:
it's the strict identity monad (also known as the 'Eval' monad.)  Treatment
of bottom is a part of your abstraction!

(I previously claimed that we could always use undefined :: m a as a left zero,
I now stand corrected: this statement only holds for 'strict' monads, a moniker 
which
describes IO, STM and ST, and any monads based on them. Indeed, I'll stick my 
neck
out and claim any monad which can witness bottoms must be strict.)
Bottoms may be zeros in strict monads, but they are not necessarily 
recoverable. `runX (recover (True <$ undefined) (const $ return False))` 
may be equivalent to `undefined`, not to `runX (return False)`. See my 
example of such "IO based" X below. I want to have options.


[snip]

  - We only have three magical base monads: IO, ST and STM.  In
  ST we do not have any appreciable control over traditional IO exceptions,
  so the discussion there is strictly limited to pure mechanisms of failure.

Why is this distinction necessary? Why are you trying to tie exception
handling idioms to the particular implementation in RTS?


The distinction I'm trying to make is between code that is pure (and cannot
witness bottoms), and code that is impure, and *can* witness bottoms.
It is true that I need language/RTS support to do the latter, but I'm
in no way tying myself to a particular implementation of an RTS: the semantics
are independent (and indeed are implemented in all of the other Haskell 
implementations.)


  - Finalizing "mutable state" is a very limited use-case; unlike C++
  we can't deallocate the state, unlike IO there are no external scarce
  resources, so the only thing you really might see is rolling back the
  state to some previous version, in which case you really ought not to
  be using ST for that purpose.

Maybe. But you can. And who said that we should consider only IO, ST and
STM? Maybe it is a mysterious stateful monad X keeping tabs on
god-knows-what. Also, even though we do not deallocate memory directly,
having a reference to some gigantic data structure by mistake could hurt
too.


Claim: such a mysterious monad would have to be backed by IO/ST. (In the
case of a pure State monad, once we exit the monad all of that gets garbage
collected.)

Let's consider the following X (using the `operational` library):

data Command α where
  -- Note that we do not employ exceptions here. If command stream
  -- transport fails, the interpreter is supposed to start the
  -- appropriate emergency procedures (or switch to a backup channel).
  -- Sending more commands wouldn't help anyway.
  AdjustControlRods ∷ 

Re: [Haskell-cafe] Monad-control rant

2012-01-18 Thread Mikhail Vorozhtsov

On 01/18/2012 02:45 AM, Edward Z. Yang wrote:

Excerpts from Mikhail Vorozhtsov's message of Tue Jan 17 06:29:12 -0500 2012:

The vehicle of implementation here is kind of important.  If they are 
implemented
as asynchronous exceptions, I can in fact still throw in this universe: I just
attempt to execute the equivalent of 'undefined :: m a'.  Since asynchronous 
exceptions
can always be thrown from pure code, I can /always/ do this, no matter how you
lock down the types.  Indeed, I think implementing this functionality on 
asynchronous
exceptions is a good idea, because it lets you handle nonterminating pure code 
nicely,
and allows you to bail out even when you're not doing monadic execution.

I don't like there this is going. Arguments like this destroy the whole
point of having abstract interfaces. I took liftBase from you and now
you are picking lock on my back door with raise#. I can deny this by
hiding the constructor of the asynchronous exception I use for passing
`lavel` in my implementation. But seriously. Next thing I know you will
be sneaking down my chimney with `unsafePerformIO` in your hands. It is
no question that the type system cannot protect us from all the tricks
RTS provides, but we still can rely on conventions of use.

Personally I'm not a fan of exceptions in pure code. If something can
fail it should be reflected in its type, otherwise I consider it a bug.
The only scenario I'm comfortable with is using asynchronous exceptions
to interrupt some number crunching.


Well, that's the kind of language we live in.  The denotation of our language
always permits for bottom values, and it's not a terribly far jump from there
to undefined and error "foo".  I don't consider the use of these facilities
to be a trap door.
Non-termination is a bug (when termination is expected) and I wish that 
`undefined` and `error` would be interpreted as bugs too (when a value 
is expected). Putting asynchronous exceptions aside, in some situations 
it might be useful to recover from bugs, but they should not be treated 
like /errors/, something that is expected to happen. At least I like to 
think this way when `error`s meet monads. For example, what is the 
meaning of `error` in this piece:


nasty ∷ Monad μ ⇒ μ ()
nasty = error "FOO" >> return ()

runIdentity nasty ~> () -- error is not necessarily a left zero!
runIdentity $ runMaybeT nasty ~> error

It's just slipping through abstraction and doing what it wants.


Hm, are you against splitting MonadPlus too?


The problem with MonadPlus is not the fact that it has mplus/mzero, but that
there are in fact multiple disjoint sets of laws that instances obey.  The only
other point of order is that MonadZero is a useful abstraction by itself,
and that's the point of debate.

What is the "usefulness" here? Is being precise not enough?

contract ∷ MonadZero μ ⇒ (α → Bool) → (β → Bool) → (α → μ β) → α → μ β
contract pre post body x = do
  unless (pre x) mzero
  y ← body x
  unless (post y) mzero
  return y

Why would I drag `mplus` here? `contract` is useful regardless of 
whether you have a choice operation or not.





You are forgetting about `ST`. For example, in `ErrorT SomeException ST`
finalizers /do/ make sense. It's not about having IO, it is about having
some sort of state(fulness).


Conceded. Although there are several responses:

 - We only have three magical base monads: IO, ST and STM.  In
 ST we do not have any appreciable control over traditional IO exceptions,
 so the discussion there is strictly limited to pure mechanisms of failure.
Why is this distinction necessary? Why are you trying to tie exception 
handling idioms to the particular implementation in RTS?


 - Finalizing "mutable state" is a very limited use-case; unlike C++
 we can't deallocate the state, unlike IO there are no external scarce
 resources, so the only thing you really might see is rolling back the
 state to some previous version, in which case you really ought not to
 be using ST for that purpose.
Maybe. But you can. And who said that we should consider only IO, ST and 
STM? Maybe it is a mysterious stateful monad X keeping tabs on 
god-knows-what. Also, even though we do not deallocate memory directly, 
having a reference to some gigantic data structure by mistake could hurt 
too.



I think that's incoherent. To draw out your MaybeT IO example to its logical 
conclusion,
you've just created two types of zeros, only one of which interacts with 
'recover' but
both of which interact with 'finally'. Down this inconsistency lies madness!  
Really,
we'd like 'recover' to handle Nothing's: and actually we can: introduce a 
distinguished
SomeException value that corresponds to nothings, and setup abort to transform 
that not
into an IO exception but a pure Nothing value. Then 'finally' as written works.

I see no inconsistency here. I just give implementers an opportunity to
decide which failures are recoverable (with `recover`) and which are
no

Re: [Haskell-cafe] Monad-control rant

2012-01-18 Thread Mikhail Vorozhtsov

On 01/18/2012 01:52 AM, Brandon Allbery wrote:

On Tue, Jan 17, 2012 at 06:29, Mikhail Vorozhtsov
mailto:mikhail.vorozht...@gmail.com>> wrote:

I wouldn't be too optimistic about convincing GHC HQ. Even making
Applicative a superclass of Monad can make Haskell98 nazis come
after you in ninja suits.


What?!  The only significant complaint I've seen here is that the
necessary language support for doing so without breaking more or less
every Haskell program currently in existence is difficult to achieve.
This is a /big/ exaggeration. What libraries exactly are going to be 
broken? Bytestring/Text (and all other data-structures-related libraries 
for that matter)? I don't think so. Network? Wouldn't be surprised if it 
goes without even a single patch. (Atto)Parsec/Binary/Cereal/*-Builder 
or Enumerator? A few type signatures (mainly contexts) and/or instances 
would need to be changed. Transformers? Some instances again. MTL? Looks 
surprisingly good.


I think with some coordinated effort we could switch the core libraries 
withing a week. On the client side of things I expect the change to go 
unnoticed by most people: by now virtually every custom monad has an 
Applicative instance. Personally, I wouldn't mind being hit by this 
hierarchy transformation, it is totally worth an hour of adjusting type 
contexts in my code (I'm currently maintaining ~17KLOC and I think I 
would need to touch only a handful of places).


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad-control rant

2012-01-17 Thread Mikhail Vorozhtsov

On 01/17/2012 03:00 AM, Edward Z. Yang wrote:
[snip]

I don't think it makes too much sense have thing pick off a menu of
Abort/Recover/Finally from a semantics perspective:


It's easy to imagine monads that have an instance of one of the classes but
not of the others


I'd like to see some examples.  I hypothesize that most of such monads are
incoherent, semantically speaking.  For example, what does it mean to have a
monad that can recover exceptions, but for which you can't throw exceptions?

Imagine a monad that disallows lifting of arbitrary IO actions, but can
receive asynchronous events (which would probably be /implemented/ on
top of asynchronous exceptions, but that's not important here) that
behave like runtime-inserted left zeros.

COMPUTATIONALLY_HEAVY_CODE `recover` \level →
GIVE_AN_APPROXIMATION_INSTEAD(level)


The vehicle of implementation here is kind of important.  If they are 
implemented
as asynchronous exceptions, I can in fact still throw in this universe: I just
attempt to execute the equivalent of 'undefined :: m a'.  Since asynchronous 
exceptions
can always be thrown from pure code, I can /always/ do this, no matter how you
lock down the types.  Indeed, I think implementing this functionality on 
asynchronous
exceptions is a good idea, because it lets you handle nonterminating pure code 
nicely,
and allows you to bail out even when you're not doing monadic execution.
I don't like there this is going. Arguments like this destroy the whole 
point of having abstract interfaces. I took liftBase from you and now 
you are picking lock on my back door with raise#. I can deny this by 
hiding the constructor of the asynchronous exception I use for passing 
`lavel` in my implementation. But seriously. Next thing I know you will 
be sneaking down my chimney with `unsafePerformIO` in your hands. It is 
no question that the type system cannot protect us from all the tricks 
RTS provides, but we still can rely on conventions of use.


Personally I'm not a fan of exceptions in pure code. If something can 
fail it should be reflected in its type, otherwise I consider it a bug. 
The only scenario I'm comfortable with is using asynchronous exceptions 
to interrupt some number crunching.


But, for the sake of argument, so let's suppose that they're not done as
asynchronous exceptions; essentially, you define some 'safe points' which have
the possibility to raise exceptions.  In this case, I claim there will never be
a *technical* difficulty against implementing manually thrown exceptions; the
concern here is "you don't want the user to do that."  With some sets of
operations, this isn't a very strong injunction; if there is a deterministic
set of operations that results in an error, the user can make a gadget which is
semantically equivalent to a thrown exception.  I don't think I can argue 
anything
stronger here, so I concede the rest of the point.

So, to summarize, such an interface (has recovery but not masking or throwing)
always has a trivial throw instance unless you are not implementing it on top
of asynchronous exceptions.

Your example reminds me of what happens in pure code. In this context, we have
the ability to throw errors and map over errors (although I'm not sure how 
people
feel about that, semantically), but not to catch them or mask them.  But I don't
think we need another typeclass for that.

Hm, are you against splitting MonadPlus too?

[snip]

The purpose of monad-abort-fd is to provide a generic API for handling errors
that have values attached to them and for guarding actions with finalizers
(as the notion of failure can include more things besides the errors).


Here's the reason I'm so fixated on IO: There is a very, /very/ bright line
between code that does IO, and pure code.  You can have arbitrary stacks of
monads, but at the end of the day, if IO is not at the end of the line, your
code is pure.

If your code is pure, you don't need finalizers. (Indeed, this is the point
of pure code...)  I can abort computations willy nilly.  I can redo them willy
nilly.  You get a lot of bang for your buck if you're pure.

I don't understand what the "too much IO" objection is about.  If there is no
IO (now, I don't mean a MonadIO instance, but I do mean, in order to interpret
the monad), it seems to me that this API is not so useful.
You are forgetting about `ST`. For example, in `ErrorT SomeException ST` 
finalizers /do/ make sense. It's not about having IO, it is about having 
some sort of state(fulness).



No, you can't. MonadFinally instances must (I really should write
documentation) handle /all/ possible failures, not just exceptions. The
naive

finally ∷ MonadRecover e μ ⇒ μ α → μ β → μ α
finally m f = do
a ← m `recover` \e → f>>  abort e
void $ f
return a

wouldn't work in `MaybeT IO`, just consider `finally mzero f`.


I think that's incoherent. To draw out your MaybeT IO example to its logical 
conclusion,
you've just created two types of zeros, on

Re: [Haskell-cafe] Monad-control rant

2012-01-16 Thread Mikhail Vorozhtsov

On 01/16/2012 02:15 PM, Edward Z. Yang wrote:

Hello Mikhail,

Hi.


Sorry, long email. tl;dr I think it makes more sense for throw/catch/mask to
be bundled together, and it is the case that splitting these up doesn't address
the original issue monad-control was designed to solve.

 ~ * ~

Anders and I thought a little more about your example, and we first wanted to
clarify which instance you thought was impossible to write.

For example, we think it should be possible to write:

 instance MonadBaseControl AIO AIO

Notice that the base monad is AIO: this lets you lift arbitrary AIO
operations to a transformed AIO monad (e.g. ReaderT r AIO), but no more.
If this is the instance you claimed was impossible, we'd like to try 
implementing
it.  Can you publish the full example code somewhere?

However, we don't think it will be possible to write:

 instance MonadBaseControl IO AIO

Because this lets you leak arbitrary IO control flow into AIO (e.g. forkIO, with
both threads having the ability to run the current AIO context), and as you 
stated,
you only want to allow a limited subset of control flow in.  (I think this was
the intent of the original message.)
I was talking about the latter instance. And I don't want to lift IO 
control to AIO, I want an API that works with both IO and AIO.


The real problem with `MonadBaseControl IO AIO` is that the interpreter 
cuts actions into smaller pieces (at blocking operations) and then 
reschedules them in some order. For example, consider the following 
piece of code:


(`catch` \e → HANDLER) $ do
  FOO
  -- wait until the state satisfies the condition
  aioCond STATE_CONDITION
  BAR

The interpreter installs HANDLER and executes FOO. Then it restores 
exception handlers of some other program and executes a piece of it. 
Eventually, when the state satisfies STATE_CONDITION, the interpreter 
restores HANDLER and executes BAR. It's impossible to implement `catch` 
by some sort of straightforward delegation to `Control.Exception.catch`, 
you can't inject you logic into IO (at least without some bizarre 
inversion of control).


I don't see why functions like `throwIO`, `catch`, `finally`, `bracket`, 
etc should be tied to IO or monads that allow lifting of IO actions. The 
functions make perfect sense in `ErrorT SomeException Identity` and in 
many other monads that have nothing to do with IO, why restrict 
ourselves? It's like exporting custom named `<|>` and friends for each 
parser combinator library and then reimplementing common Alternative 
idioms again and again.




Maybe client code doesn't want to be attached to AIO base monads, though;
that's too restrictive for them. So they'd like to generalize a bit.  So let's
move on to the issue of your typeclass decomposition.

 ~ * ~

I don't think it makes too much sense have thing pick off a menu of
Abort/Recover/Finally from a semantics perspective:


It's easy to imagine monads that have an instance of one of the classes but
not of the others


I'd like to see some examples.  I hypothesize that most of such monads are
incoherent, semantically speaking.  For example, what does it mean to have a
monad that can recover exceptions, but for which you can't throw exceptions?
Imagine a monad that disallows lifting of arbitrary IO actions, but can 
receive asynchronous events (which would probably be /implemented/ on 
top of asynchronous exceptions, but that's not important here) that 
behave like runtime-inserted left zeros.


COMPUTATIONALLY_HEAVY_CODE `recover` \level →
  GIVE_AN_APPROXIMATION_INSTEAD(level)


There only a few options:

 - You have special primitives which throw exceptions, distinct from
   Haskell's IO exceptions.  In that case, you've implemented your own
   homebrew exception system, and all you get is a 'Catch MyException'
   which is too specific for a client who is expecting to be able
   to catch SomeExceptions.

 - You execute arbitrary IO and allow those exceptions to be caught.
   But then I can implement Throw: I just embed an IO action that
   is throwing an exception.

 - You only execute a limited subset of IO, but when they throw exceptions
   they throw ordinary IO exceptions.  In this case, the client doesn't
   have access to any scarce resources except the ones you provided,
   so there's no reason for him to even need this functionality, unless
   he's specifically coding against your monad.
As I said, you think of IO too much. The purpose of monad-abort-fd is to 
provide a generic API for handling errors that have values attached to 
them and for guarding actions with finalizers (as the notion of failure 
can include more things besides the errors).


What does it mean to not have a Finally instance, but a Recover and Throw
instance?  Well, I can manually reimplement finally in this case (with or
without support for asynchronous exceptions, dependin

Re: [Haskell-cafe] Monad-control rant

2012-01-14 Thread Mikhail Vorozhtsov

On 01/10/2012 11:12 PM, Edward Z. Yang wrote:

Excerpts from Mikhail Vorozhtsov's message of Tue Jan 10 09:54:38 -0500 2012:

On 01/10/2012 12:17 AM, Edward Z. Yang wrote:

Hello Mikhail,

Hi.


(Apologies for reviving a two month old thread). Have you put some thought into
whether or not these extra classes generalize in a way that is not /quite/ as
general as MonadBaseControl (so as to give you the power you need) but still
allow you to implement the functionality you are looking for? I'm not sure but
it seems something along the lines of unwind-protect ala Scheme might be
sufficient.

I'm not sure I'm following you. The problem with MonadBaseControl is
that it is /not/ general enough.


Sorry, I mispoke.  The sense you are using it is "the more general a type class
is, the more instances you can write for it." I think the design goal I'm going
for here is, "a single signature which covers MonadAbort/Recover/Finally in a
way that unifies them."  Which is not more general, except in the sense that it
"contains" more type classes (certainly not general in the mathematical sense.)
Hm, MonadAbort/Recover/Finally are independent (I made MonadAbort a 
superclass of MonadRecover purely for reasons of convenience). It's easy 
to imagine monads that have an instance of one of the classes but not of 
the others.



It assumes that you can eject/inject
all the stacked effects as a value of some data type. Which works fine
for the standard transformers because they are /implemented/ this way.
But not for monads that are implemented in operational style, as
interpreters, because the interpreter state cannot be internalized. This
particular implementation bias causes additional issues when the lifted
operation is not fully suited for ejecting/injecting. For example the
`Control.Exception.finally` (or unwind-protect), where we can neither
inject (at least properly) the effects into nor eject them from the
finalizer. That's why I think that the whole "lift operations from the
bottom" approach is wrong (the original goal was to lift
`Control.Exception`). The right way would be to capture the control
semantics of IO as a set of type classes[1] and then implement the
general versions of the operations you want to lift. That's what I tried
to do with the monad-abord-fd package.


I think this is generally a useful goal, since it helps define the semantics
of IO more sharply.  However, the exceptions mechanism is actually fairly
well specified, as far as semantics go, see "A Semantics for Imprecise
Exceptions" and "Asynchronous Exceptions in Haskell."  So I'm not sure if
monad-abort-fd achieves the goal of expressing these interfaces, in
typeclass form, as well as allowing users to interoperate cleanly with
existing language support for these facilities.
I certainly didn't do that in any formal way. I was thinking something 
like this: if we identify the basic IO-specific control operations, 
abstract them but make sure they interact in the same way they do in IO, 
then any derivative IO control operation (implemented on top of the 
basic ones) could be lifted just by changing the type signature. The key 
words here are of course "interact in the same way".



[1] Which turn out to be quite general: MonadAbort/Recover/Finally are
just a twist of MonadZero/MonadPlus


Now that's interesting! Is this an equivalence, e.g. MonadZero/MonadPlus
imply MonadAbort/Recover/Finally and vice-versa, or do you need to make
some slight modifications?  It seems that you somehow need support for
multiple zeros of the monad, as well as a way of looking at them.
Yes, something along those lines. MonadAbort is a generalization of 
MonadZero, MonadRecover is a specialization of the "left catch" version 
of MonadPlus (aka MonadOr). MonadFinally is about adopting


finally0 m f = do
  r ← m `morelse` (f Nothing >> mzero)
  (r, ) <$> f (Just r)

to the notion of failure associated with a particular monad.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad-control rant

2012-01-10 Thread Mikhail Vorozhtsov

On 01/10/2012 12:17 AM, Edward Z. Yang wrote:

Hello Mikhail,

Hi.


(Apologies for reviving a two month old thread). Have you put some thought into
whether or not these extra classes generalize in a way that is not /quite/ as
general as MonadBaseControl (so as to give you the power you need) but still
allow you to implement the functionality you are looking for? I'm not sure but
it seems something along the lines of unwind-protect ala Scheme might be
sufficient.
I'm not sure I'm following you. The problem with MonadBaseControl is 
that it is /not/ general enough. It assumes that you can eject/inject 
all the stacked effects as a value of some data type. Which works fine 
for the standard transformers because they are /implemented/ this way. 
But not for monads that are implemented in operational style, as 
interpreters, because the interpreter state cannot be internalized. This 
particular implementation bias causes additional issues when the lifted 
operation is not fully suited for ejecting/injecting. For example the 
`Control.Exception.finally` (or unwind-protect), where we can neither 
inject (at least properly) the effects into nor eject them from the 
finalizer. That's why I think that the whole "lift operations from the 
bottom" approach is wrong (the original goal was to lift 
`Control.Exception`). The right way would be to capture the control 
semantics of IO as a set of type classes[1] and then implement the 
general versions of the operations you want to lift. That's what I tried 
to do with the monad-abord-fd package.


Hopefully this makes sense to you.

[1] Which turn out to be quite general: MonadAbort/Recover/Finally are 
just a twist of MonadZero/MonadPlus; MonadMask is expectedly more 
specific, but permits a nice no-op implementation.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: data-timeout - 64-bit timeouts of nanosecond precision

2011-12-01 Thread Mikhail Vorozhtsov

Hi.

I grew up tired of counting milliseconds, so I wrote a small library[1] 
that allows me to specify time units for timeouts and convert between 
them. The library also provides wrapped versions of 'timeout' and 
'threadDelay' functions:


> threadDelay $ 1 # Minute + 30 # Second

Nanosecond precision seems to be enough for RTS and POSIX calls and it 
also provides a good range for 64-bit representation:


> maxBound :: Timeout
30500 w 3 d 23 h 34 m 33 s 709 ms 551 us 615 ns

One thing that might disappoint some people is that I chose unsigned 
underlying type (Word64), which means that "infinite" timeouts cannot be 
represented. I think "negative" timeouts essentially are performance 
warts (a way of packing `Maybe Word63` into Word64) that muddle equality 
and I recommend using `Maybe Timeout` whenever timeout is optional.


[1] http://hackage.haskell.org/package/data-timeout

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad-control rant

2011-11-13 Thread Mikhail Vorozhtsov

On 11/14/2011 06:55 AM, Bas van Dijk wrote:

Hi Mikhail,

your type class:

class MonadAbort e μ ⇒ MonadRecover e μ | μ → e where
   recover ∷ μ α → (e → μ α) → μ α

looks a lot like the MonadCatchIO type class from MonadCatchIO-transformers:

class MonadIO m =>  MonadCatchIO m where
   catch   :: E.Exception e =>  m a ->  (e ->  m a) ->  m a

I haven't looked at your code in detail but are you sure your
continuation based AIO monad doesn't suffer from the same unexpected
behavior as the ContT monad transformer with regard to catching and
handling exceptions?
Yes, I'm sure. The reason why it works is because finally/bracket/etc 
are not implemented on top of 'recover' (i.e. they don't assume that 
throwing an exception is the only reason control can escape). The 
following class takes care of it:


class (Applicative μ, Monad μ) ⇒ MonadFinally μ where
  finally' ∷ μ α → (Maybe α → μ β) → μ (α, β)
  finally ∷ μ α → μ β → μ α
  finally m = fmap fst . finally' m . const

Finalizers have type 'Maybe α → μ β' so we can

(a) Thread transformer side effects properly:

instance MonadFinally μ ⇒ MonadFinally (L.StateT s μ) where
  finally' m f = L.StateT $ \s → do
~(~(mr, _), ~(fr, s'')) ← finally' (L.runStateT m s) $ \mbr → do
  let ~(a, s') = case mbr of
 Just ~(x, t) → (Just x, t)
 Nothing → (Nothing, s)
  L.runStateT (f a) s'
return ((mr, fr), s'')

(b) Detect that control escaped computation before producing a result 
(finalizer will be called with 'Nothing' in that case).


instance (MonadFinally μ, Error e) ⇒ MonadFinally (ErrorT e μ) where
  finally' m f = ErrorT $ do
~(mr, fr) ← finally' (runErrorT m) $ \mbr →
  runErrorT $ f $ case mbr of
Just (Right a) → Just a
_ → Nothing
return $ (,) <$> mr <*> fr

That of course does not mean that I can use 'finally' and friends with 
ContT, but I can use them with monads which are carefully /implemented/ 
on top of ContT but do not expose it's full power to the users.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Monad-control rant

2011-11-12 Thread Mikhail Vorozhtsov

On 11/12/2011 07:34 AM, Bas van Dijk wrote:

Are you going to release a new version of monad-control right away


Not just yet. I've split `monad-control` into two packages:

* `monad-control`: just exports `Control.Monad.Trans.Control`. This part is 
finished.
* `lifted-base`: wraps all modules of the `base` package which export `IO` 
computations and provides
  lifted version instead. For example we have `Control.Exception.Lifted`, 
`Control.Concurrent.Lifted`, etc.

As you can imagine the latter is a lot of boring work. Fortunately it's easy to 
do so will probably
not take a lot of time. BTW if by any chance you want to help out, that will be 
much appreciated!

The repos can be found [here](https://github.com/basvandijk/lifted-base)


Maybe I should elaborate on why I stopped using monad-control and rolled 
out my own version of lifted Control.Exception in monad-abort-fd 
package. I'm CC-ing the Cafe just in case someone else might be 
interested in the matter of IO lifting.


Imagine we have a monad for multiprogramming with shared state:

-- ContT with a little twist. Both the constructor and runAIO
-- are NOT exported.
newtype AIO s α =
  AIO { runAIO ∷ ∀ β . (α → IO (Trace s β)) → IO (Trace s β) }

runAIOs ∷ MonadBase IO μ
⇒ s -- The initial state
→ [AIO s α] -- The batch of programs to run.
-- If one program exits normally (without using
-- aioExit) or throws an exception, the whole batch
-- is terminated.
→ μ (s, Maybe (Attempt α)) -- The final state and the result.
   -- "Nothing" means deadlock or that
   -- all the programs exited with
   -- aioExit.
runAIOs = liftBase $ mask_ $ ... bloody evaluation ...

data Trace s α where
  -- Finish the program (without finishing the batch).
  TraceExit ∷ Trace s α
  -- Lift a pure value.
  TraceDone ∷ α → Trace s α
  -- A primitive to execute and the continuation.
  TraceCont ∷ Prim s α → (α → IO (Trace s β)) → Trace s β

-- Primitive operations
data Prim s α where
  -- State retrieval/modification
  PrimGet  ∷ Prim s s
  PrimSet  ∷ s → Prim s ()
  -- Scheduling point. The program is suspended until
  -- the specified event occurs.
  PrimEv   ∷ Event e ⇒ e → Prim s (EventResult e)
  -- Scheduling point. The program is suspended until the state
  -- satisfies the predicate.
  PrimCond ∷ (s → Bool) → Prim s ()
  -- Run computation guarded with finalizer.
  PrimFin  ∷ IO (Trace s α) → (Maybe α → AIO s β) → Prim s (α, β)
  -- Run computation guarded with exception handler.
  PrimHand ∷ IO (Trace s α) → (SomeException → AIO s α) → Prim s α

aioExit ∷ AIO s α
aioExit = AIO $ const $ return TraceExit

aioAfter ∷ (s → Bool) → AIO s ()
aioAfter cond = AIO $ return . TraceCont (PrimCond cond)

aioAwait ∷ Event e ⇒ e → AIO s (EventResult e)
aioAwait e = AIO $ return . TraceCont (PrimEv e)

runAIOs slices the programs at scheduling points and enqueues the 
individual pieces for execution, taking care of saving/restoring the 
context (finalizers and exception handlers).


The Functor/Applicative/Monad/MonadBase/etc instances are pretty trivial:

instance Functor (AIO s) where
  fmap f (AIO g) = AIO $ \c → g (c . f)

instance Applicative (AIO s) where
  pure a = AIO ($ a)
  (<*>) = ap

instance Monad (AIO s) where
  return = pure
  AIO g >>= f = AIO $ \c → g (\a → runAIO (f a) c)

instance MonadBase IO (AIO s) where
  liftBase io = AIO (io >>=)

instance MonadState s (AIO s) where
  get   = AIO $ return . TraceCont PrimGet
  put s = AIO $ return . TraceCont (PrimSet s)

instance MonadAbort SomeException (AIO s) where
  abort = liftBase . throwIO

trace ∷ AIO s α → IO (Trace s α)
trace (AIO g) = g (return . TraceDone)

instance MonadRecover SomeException (AIO s) where
  recover m h = AIO $ return . TraceCont (PrimHand (trace m) h)

instance MonadFinally (AIO s) where
  finally' m f = AIO $ return . TraceCont (PrimFin (trace m) f)
  -- finally m = fmap fst . finally' m . const

-- No async exceptions in AIO
instance MonadMask () (AIO s) where
  getMaskingState = return ()
  setMaskingState = const id

Now we have a problem: we can throw/catch exceptions and install 
finalizers in AIO, but we can't use Control.Exception.Lifted because we 
can't declare a MonadBaseControl instance for our "ContT with limited 
interface".


So now, instead of trying to wrap IO control operations uniformly, I 
just reimplement them in terms of the classes I mentioned above 
(MonadAbort+MonadRecover+MonadFinally+MonadMask), for example:


bracket ∷ (MonadFinally μ, MonadMask m μ)
⇒ μ α → (α → μ β) → (α → μ γ) → μ γ
bracket acq release m = mask $ \restore → do
  a ← acq
  finally (restore $ m a) (release a)

It requires more typing (more classes => more instances), but it works 
for a broader class of monads and I get proper side affects in 
finalizers for a bonus.


The code is on Hackage (monad-abort-fd)

[Haskell-cafe] [ANN] transformers-base, transformers-abort, monad-abort-fd

2011-11-10 Thread Mikhail Vorozhtsov

Hi Cafe.

I've been using these three small transformer libraries for awhile, so 
it's probably time to announce them.


transformers-base[1] introduces a generalized version of MonadIO, 
MonadBase (BaseM in monadLib terms). It's very useful when you are 
trying to make a stateful API work in both IO and STM (and all 
transformer stacks on top of them).


transformers-abort[2] basically gives you two versions of EitherT, one 
for errors and one for short-circuiting. Includes instances for 
semigroupoids and monad-control classes.


monad-abort-fd[3] is a typical companion auto-lifter package for 
transformers-abort. But it also provides a generalized version[4] of 
Control.Exception which tries to thread effects properly (e.g. 
finalizers can read (if control didn't escape) and modify the state in 
StateT).


[1] http://hackage.haskell.org/package/transformers-base
[2] http://hackage.haskell.org/package/transformers-abort
[3] http://hackage.haskell.org/package/monad-abort-fd
[4] 
http://hackage.haskell.org/packages/archive/monad-abort-fd/0.3/doc/html/src/Control-Monad-Exception.html


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Indexed monads and MonoLocalBinds

2011-04-21 Thread Mikhail Vorozhtsov

Hi Cafe,

Here is another example of why 'let' should be sometimes generalised.
I've been recently playing with indexed monads (for JSON processing) and 
found out that the following code fails to typecheck:


>{-# LANGUAGE MonoLocalBinds #-}

>data M t t' a = M

>ipure :: a -> M t t a
>ipure a = M
>iseq :: M t t' a -> M t' t'' b -> M t t'' b
>iseq a b = M

>np :: M () Bool ()
>np = M

>test = p `iseq` np `iseq` p
>  where p = ipure ()

Test.hs:13:27:
Couldn't match expected type `Bool' with actual type `()'
Expected type: M Bool t''0 b0
  Actual type: M () () ()
In the second argument of `iseq', namely `p'
In the expression: p `iseq` np `iseq` p

In practice that means that I need to provide a signature for almost 
every monadic local binding that is used more than once, which is 
unbearable, especially when monad transformers and complex indices are 
used.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe