Re: [Haskell-cafe] Interfacing Java/Haskell

2013-05-10 Thread CJ van den Berg

On 2013-05-09 17:04, Hans Georg Schaathun wrote:
 Does anyone have experience with integrating Haskell and Java?
 I have done some searching, finding a lot of pointers but hardly
 anything in terms of evaluation, successes, or caveats.  
 
 From what I see Frege looks promising, arguably not haskell I suppose,
 but does it work?  Other projects I have seen appear to have reached 
 a stand-still for ages.
 
 The background for the question is that I will contribute some control
 algorithms based on machine learning or AI in a larger project.  It
 would save me a lot of time if I could write in Haskell, but only
 assuming that interfacing with Java afterwards is trivial compared
 to writing everything in java in the first place.  I am, perhaps,
 particularly worried that a Haskell-lookalike for JVM might be
 unable to optimise properly, like not being lazy.  Any advice?

I have successfully written Java/Haskell programs using the Java
Native Interface. You can find my JNI to Haskell binding library at
https://github.com/neurocyte/foreign-jni. I am primarily using it to
write Android Apps with Haskell, but I’ve done a little testing with
the standard JVM and it works fine. There is a bare bones
demonstration of a Java/Haskell application at
https://github.com/neurocyte/android-haskell-activity. That is for
Android, but the basic principals are the same for plain JVM integration.

I am currently working on a tool to generate full (or at least fully
usable) Haskell bindings to Java libraries (using foreign-jni),
including being able to implement Java callback interfaces in
Haskell. That is still a work in progress though and I have not yet
published it to github. The intent is to generate a full set of
bindings to the Android API, but it is pretty generic and should work
for any Java API.

-- 
CJ van den Berg

mailto:c...@vdbonline.com
xmpp:neuroc...@gmail.com

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


[Haskell-cafe] A use case for *real* existential types

2013-05-10 Thread Leon Smith
I've been working on a new Haskell interface to the linux kernel's inotify
system, which allows applications to subscribe to and be notified of
filesystem events.   An application first issues a system call that returns
a file descriptor that notification events can be read from,  and then
issues further system calls to watch particular paths for events.   These
return a watch descriptor (which is just an integer) that can be used to
unsubscribe from those events.

Now,  of course an application can open multiple inotify descriptors,  and
when removing watch descriptors,  you want to remove it from the same
inotify descriptor that contains it;  otherwise you run the risk of
deleting a completely different watch descriptor.

So the natural question here is if we can employ the type system to enforce
this correspondence.   Phantom types immediately come to mind,  as this
problem is almost the same as ensuring that STRefs are only ever used in a
single ST computation.   The twist is that the inotify interface has
nothing analogous to runST,  which does the heavy lifting of the type
magic behind the ST monad.

This twist is very simple to deal with if you have real existential types,
 with the relevant part of the interface looking approximately like

init :: exists a. IO (Inotify a)
addWatch :: Inotify a - FilePath - IO (Watch a)
rmWatch :: Inotify a - Watch a - IO ()

UHC supports this just fine,  as demonstrated by a mockup attached to this
email.  However a solution for GHC is not obvious to me.


inotify.hs
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A use case for *real* existential types

2013-05-10 Thread Andres Löh
Hi.

 So the natural question here is if we can employ the type system to enforce
 this correspondence.   Phantom types immediately come to mind,  as this
 problem is almost the same as ensuring that STRefs are only ever used in a
 single ST computation.   The twist is that the inotify interface has nothing
 analogous to runST,  which does the heavy lifting of the type magic behind
 the ST monad.

 This twist is very simple to deal with if you have real existential types,
 with the relevant part of the interface looking approximately like

 init :: exists a. IO (Inotify a)
 addWatch :: Inotify a - FilePath - IO (Watch a)
 rmWatch :: Inotify a - Watch a - IO ()

You can still do the ST-like encoding (after all, the ST typing trick
is just an encoding of an existential), with init becoming like
runST:

 init :: (forall a. Inotify a - IO b) - IO b
 addWatch :: Inotify a - FilePath - IO (Watch a)
 rmWatch :: Inotify a - Watch a - IO ()

Looking at your inotify.hs, the code of init becomes:

 init :: (forall a. Inotify a - IO b) - IO b
 init k = do
   nextWatchRef_ - newIORef 0
   currentWatchesRef_ - newIORef []
   k $ Inotify {
 nextWatchRef = nextWatchRef_
   , currentWatchesRef = currentWatchesRef_
   }

And the code of main becomes:

 main = init $ \ nd0 - do
   wd0 - addWatch nd0 foo
   wd1 - addWatch nd0 bar
   init $ \ nd1 - do
 wd3 - addWatch nd1 baz
 printInotifyDesc nd0
 printInotifyDesc nd1
 rmWatch nd0 wd0
 rmWatch nd1 wd3
   -- These lines cause type errors:
   --  rmWatch nd1 wd0
   --  rmWatch nd0 wd3
 printInotifyDesc nd0
 printInotifyDesc nd1

Cheers,
  Andres

-- 
Andres Löh, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com

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


Re: [Haskell-cafe] A use case for *real* existential types

2013-05-10 Thread MigMit
Maybe I understand the problem incorrectly, but it seems to me that you're 
overcomplicating things.

With that kind of interface you don't actually need existential types. Or 
phantom types. You can just keep Inotify inside the Watch, like this:

import Prelude hiding (init, map)
import Data.IORef

data Inotify =
Inotify {nextWatchRef :: IORef Int, currentWatchesRef :: IORef 
[(Int,String)]}

data Watch = Watch Int Inotify

init ::IO Inotify
init = do
  nextWatchRef_ - newIORef 0
  currentWatchesRef_ - newIORef []
  return Inotify { 
   nextWatchRef = nextWatchRef_
 , currentWatchesRef = currentWatchesRef_
 }

addWatch :: Inotify - String - IO Watch
addWatch nd filepath = do
  wd - readIORef (nextWatchRef nd)
  writeIORef (nextWatchRef nd) (wd + 1)
  map - readIORef (currentWatchesRef nd)
  writeIORef (currentWatchesRef nd) ((wd,filepath):map)
  return (Watch wd nd)

rmWatch :: Watch - IO ()
rmWatch (Watch wd nd) = do
  map - readIORef (currentWatchesRef nd)
  writeIORef (currentWatchesRef nd) (filter ((/= wd) . fst) map)

printInotifyDesc :: Inotify - IO ()
printInotifyDesc nd = print = readIORef (currentWatchesRef nd)

main :: IO ()
main = do
  nd0 - init
  wd0 - addWatch nd0 foo
  _ - addWatch nd0 bar
  nd1 - init
  wd3 - addWatch nd1 baz
  printInotifyDesc nd0
  printInotifyDesc nd1
  rmWatch wd0
  rmWatch wd3
  printInotifyDesc nd0
  printInotifyDesc nd1

OK, I understand that it might be not what you want. For example, it could be 
that you can combine two different Watches if and only if they refer to the 
same Inotify. Well, then you need existential types. But you almost did it 
right, all you have to do now is to wrap Inotify in another type like that:

{-# LANGUAGE ExistentialQuantification #-}
import Prelude hiding (init, map)
import Data.IORef

data Inotify a = Inotify
{ nextWatchRef  :: IORef Int
, currentWatchesRef :: IORef [(Int,String)]
} 

newtype Watch a = Watch Int

data PolyInotify = forall a. PolyInotify (Inotify a)

init :: IO PolyInotify
init = do
  nextWatchRef_ - newIORef 0
  currentWatchesRef_ - newIORef []
  return $ PolyInotify Inotify { 
   nextWatchRef = nextWatchRef_
 , currentWatchesRef = currentWatchesRef_
 }

addWatch :: Inotify a - String - IO (Watch a)
addWatch nd filepath = do
  wd - readIORef (nextWatchRef nd)
  writeIORef (nextWatchRef nd) (wd + 1)
  map - readIORef (currentWatchesRef nd)
  writeIORef (currentWatchesRef nd) ((wd,filepath):map)
  return (Watch wd)

rmWatch :: Inotify a - Watch a - IO ()
rmWatch nd (Watch wd) = do
  map - readIORef (currentWatchesRef nd)
  writeIORef (currentWatchesRef nd) (filter ((/= wd) . fst) map)

printInotifyDesc :: Inotify a - IO ()
printInotifyDesc nd = print = readIORef (currentWatchesRef nd)

main :: IO ()
main = do
  pnd0 - init
  case pnd0 of
PolyInotify nd0 -
do wd0 - addWatch nd0 foo
   _ - addWatch nd0 bar
   pnd1 - init
   case pnd1 of
 PolyInotify nd1 -
 do wd3 - addWatch nd1 baz
printInotifyDesc nd0
printInotifyDesc nd1
rmWatch nd0 wd0
rmWatch nd1 wd3
-- These lines cause type errors:
--  rmWatch nd1 wd0
--  rmWatch nd0 wd3
printInotifyDesc nd0
printInotifyDesc nd1

You may also choose to employ Rank2Types, which would make this more ST-like, 
with init playing the part of runST:

{-# LANGUAGE Rank2Types #-}
import Prelude hiding (init, map)
import Data.IORef

data Inotify a = Inotify
{ nextWatchRef  :: IORef Int
, currentWatchesRef :: IORef [(Int,String)]
} 

newtype Watch a = Watch Int

init :: (forall a. Inotify a - IO b) - IO b
init action = do
  nextWatchRef_ - newIORef 0
  currentWatchesRef_ - newIORef []
  action Inotify { 
   nextWatchRef = nextWatchRef_
 , currentWatchesRef = currentWatchesRef_
 }

addWatch :: Inotify a - String - IO (Watch a)
addWatch nd filepath = do
  wd - readIORef (nextWatchRef nd)
  writeIORef (nextWatchRef nd) (wd + 1)
  map - readIORef (currentWatchesRef nd)
  writeIORef (currentWatchesRef nd) ((wd,filepath):map)
  return (Watch wd)

rmWatch :: Inotify a - Watch a - IO ()
rmWatch nd (Watch wd) = do
  map - readIORef (currentWatchesRef nd)
  writeIORef (currentWatchesRef nd) (filter ((/= wd) . fst) map)

printInotifyDesc :: Inotify a - IO ()
printInotifyDesc nd = print = readIORef (currentWatchesRef nd)

main :: IO ()
main =
init $ \nd0 -
do wd0 - addWatch nd0 foo
   _ - addWatch nd0 bar
   init $ \nd1 -
   do wd3 - addWatch nd1 baz
  printInotifyDesc nd0
  printInotifyDesc nd1
  rmWatch nd0 wd0
  rmWatch nd1 wd3
-- These lines cause type errors:
--  rmWatch nd1 wd0
--  rmWatch nd0 wd3
  printInotifyDesc nd0
  printInotifyDesc nd1

On May 10, 2013, at 2:17 PM, Leon 

[Haskell-cafe] Typeclass with an ‘or’ restriction.

2013-05-10 Thread Mateusz Kowalczyk
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Greetings,

We can currently do something like
 class (Num a, Eq a) = Foo a where bar :: a - a - Bool bar =
 (==)

This means that our `a' has to be an instance of Num and Eq. Apologies
for a bit of an artificial example.

Is there a way however to do something along the lines of:
 class Eq a = Foo a where bar :: a - a - Bool bar = (==)
 
 class Num a = Foo a where bar :: a - a - Bool bar _ _ = False
This would allow us to make an instance of Num be an instance of Foo
or an instance of Eq to be an instance of Foo.

The compiler currently complains about multiple declarations. Is there
currently a way to achieve this?

The main issue I can see with this is that given an instance of both,
Num and Eq, it wouldn't be possible to pick the correct default
implementation.

Purely a theoretical question.

- -- 
Mateusz K.
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.19 (GNU/Linux)

iQIcBAEBAgAGBQJRjP0hAAoJEM1mucMq2pqX30wP/0d0TQHs4S3G5TBw+T1baI6n
g/5k/YlPmSgS3FaO8JMQsb2uqL8dGPZGUN7d2ohwcigtXS88KWH4u4rTjrs1+p8o
ktS+vIE4kEEedTAX6wmP2Zn+rvK2zFGboCafaX/a/IxT5CbwYZ97RrWCjzz1jlPs
S/VlhNHcTQ7Cf/0pa0xJ1kbao+vBHiWtWjxcdzCT/6zS86+jm9vz8qrYT3TWUd3y
AJXPBjRuXeyz+RDv18yrth7hMlAvaeoWzmC4gbGFHC68/Oq2l8kz+4dt6ApN+mIy
l73wNjrU185YoZ2dkuKTIph8/BadgkD+9ktkgZZ/NlqxElc596BdbOcMfVk4rz4A
0nWqaLa4QctIthghJ1UNfKS8lQzkVVRT6e03LYdgPkqJm1HQxkjHL/WieV2NEoRf
1K9S4SVW8Aq/ML/Gmx782Z3jMECfnYWntf9gSOwFASB64tVej1iUxb7UsfxJAL1t
ysf9MjcbZsHe3M/JAq4f8HtHoZoiIG/TTjD0yo74owssJDfOTDqmYMriyelcnUf6
hDCPZyUqLPMTNVx07T+gwfXJoE1HK20hzVe2o1dPBZ8Kb2KJbNg0+sUSB3/v6O8e
EJ6w7aQ3OnZUACd1i2uLZiphMF8d8va4T8eTFUyROODHvaPv6netzr8gPcIXhpVO
5OwyMfO54cinZYen7+HR
=iAYY
-END PGP SIGNATURE-

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


[Haskell-cafe] Stream processing

2013-05-10 Thread Ertugrul Söylemez
Hello everybody,

I'm trying to formulate the stream processing problem, which doesn't
seem to be solved fully by the currently existing patterns.  I'm
experimenting with a new idea, but I want to make sure that I don't miss
any defining features of the problem, so here is my list.  A stream
processing abstraction should:

  * have a categorically proven design (solved by iteratees, pipes),

  * be composable (solved by all of them),

  * be reasonably easy to understand and work with (solved by conduit,
pipes),

  * support leftovers (solved by conduit and to some degree by
iteratees),

  * be reliable in the presence of async exceptions (solved by conduit,
pipes-safe),

  * hold on to resources only as long as necessary (solved by conduit
and to some degree by pipes-safe),

  * ideally also allow upstream communication (solved by pipes and to
some degree by conduit).

  * be fast (solved by all of them).

Anything else you would put in that list?


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.


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


Re: [Haskell-cafe] Typeclass with an ‘or’ restriction.

2013-05-10 Thread Adam Gundry
Hi Mateusz,

It's not directly possible to write a class with a choice of
superclasses; as you point out, it's not really clear what that would
mean. One workaround, though it might not be sensible in practice, is
the following.

 {-# LANGUAGE ConstraintKinds, GADTs #-}

First, reify the constraints we are interested in as types that pack up
the corresponding dictionary. Thanks to ConstraintKinds, it's possible
to do this once and for all.

 data Dict c where
   Dict :: c = Dict c

Now we can describe types with either Num or Eq dictionaries (or both)
as a class.  The proxy argument makes it easy to specify the type, in
the absence of explicit type application.

 class NumOrEq a where
   numOrEq :: proxy a - Either (Dict (Num a)) (Dict (Eq a))

Something like your Foo class can then be defined like this:

 class NumOrEq a = Foo a where
   bar :: a - a - Bool
   bar x y = case numOrEq [x] of
 Left Dict   - False
 Right Dict  - x == y

When giving an instance for NumOrEq, you must choose which dictionary to
pack up if both are available.

 instance NumOrEq Int where
   numOrEq _ = Left Dict

 instance NumOrEq Bool where
   numOrEq _ = Right Dict

 instance Foo Int
 instance Foo Bool

And with all that, we have:

 bar 3 (3 :: Int) == False
 bar True True == True

Now I'm wondering why we would want that in the first place.

Hope this helps,

Adam


On 10/05/13 14:58, Mateusz Kowalczyk wrote:
| Greetings,
|
| We can currently do something like
| class (Num a, Eq a) = Foo a where bar :: a - a - Bool bar =
| (==)
|
| This means that our `a' has to be an instance of Num and Eq. Apologies
| for a bit of an artificial example.
|
| Is there a way however to do something along the lines of:
| class Eq a = Foo a where bar :: a - a - Bool bar = (==)
|
| class Num a = Foo a where bar :: a - a - Bool bar _ _ = False
| This would allow us to make an instance of Num be an instance of Foo
| or an instance of Eq to be an instance of Foo.
|
| The compiler currently complains about multiple declarations. Is there
| currently a way to achieve this?
|
| The main issue I can see with this is that given an instance of both,
| Num and Eq, it wouldn't be possible to pick the correct default
| implementation.
|
| Purely a theoretical question.


-- 
The University of Strathclyde is a charitable body, registered in
Scotland, with registration number SC015263.

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


Re: [Haskell-cafe] Constrained Category, Arrow, ArrowChoice, etc?

2013-05-10 Thread Sjoerd Visscher

On May 9, 2013, at 10:36 PM, Conal Elliott co...@conal.net wrote:
 BTW, have you see the new paper The constrained-monad problem? I want to 
 investigate whether its techniques can apply to Category  friends for linear 
 maps and for circuits. Perhaps you’d like to give it a try as well. I got to 
 linear maps as an elegant formulation of timing analysis for circuits.
 
I have implemented the normal form for categories. The normal form is like the 
type-threaded lists from the thrist package:
https://gist.github.com/sjoerdvisscher/5554910

Evaluating the normal form works fine even for your original :-* datatype.

But I got stuck trying to expand this to categories with products, as I'm not 
sure what the normal form should be. But I guess you might have good ideas 
about that?

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


Re: [Haskell-cafe] A use case for *real* existential types

2013-05-10 Thread Leon Smith
On Fri, May 10, 2013 at 9:00 AM, Andres Löh and...@well-typed.com wrote:


  This twist is very simple to deal with if you have real existential
 types,
  with the relevant part of the interface looking approximately like
 
  init :: exists a. IO (Inotify a)
  addWatch :: Inotify a - FilePath - IO (Watch a)
  rmWatch :: Inotify a - Watch a - IO ()

 You can still do the ST-like encoding (after all, the ST typing trick
 is just an encoding of an existential), with init becoming like
 runST:

  init :: (forall a. Inotify a - IO b) - IO b
  addWatch :: Inotify a - FilePath - IO (Watch a)
  rmWatch :: Inotify a - Watch a - IO ()


Right, but my interface the Inotify descriptor has an indefinite extent,
 whereas your interface enforces a dynamic extent.   I'm not sure to what
degree this would impact use cases of this particular library,  but in
general moving a client program from the the first interface to the second
can require significant changes to the structure of the program,   whereas
moving a client program from the second interface to the first is trivial.
   So I'd say my interface is more expressive.

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


Re: [Haskell-cafe] A use case for *real* existential types

2013-05-10 Thread Leon Smith
On Fri, May 10, 2013 at 9:04 AM, MigMit miguelim...@yandex.ru wrote:

 With that kind of interface you don't actually need existential types. Or
 phantom types. You can just keep Inotify inside the Watch, like this:


Right, that is an alternative solution,  but phantom types are a relatively
simple and well understood way of enforcing this kind of property in the
type system without incurring run-time costs.   My inotify binding is
intended to be as thin as possible,  and given my proposed interface,   you
could implement your interface in terms of mine,  making the phantom types
disappear using the restricted existentials already available in GHC,   and
such a wrapper should be just as efficient as if you had implemented your
interface directly.

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


Re: [Haskell-cafe] A use case for *real* existential types

2013-05-10 Thread Alexander Solla
I'm not sure if it would work for your case, but have you considered using
DataKinds instead of phantom types?  At least, it seems like it would be
cheap to try out.

http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/kind-polymorphism-and-promotion.html


On Fri, May 10, 2013 at 12:52 PM, Leon Smith leon.p.sm...@gmail.com wrote:

 On Fri, May 10, 2013 at 9:04 AM, MigMit miguelim...@yandex.ru wrote:

 With that kind of interface you don't actually need existential types. Or
 phantom types. You can just keep Inotify inside the Watch, like this:


 Right, that is an alternative solution,  but phantom types are a
 relatively simple and well understood way of enforcing this kind of
 property in the type system without incurring run-time costs.   My inotify
 binding is intended to be as thin as possible,  and given my proposed
 interface,   you could implement your interface in terms of mine,  making
 the phantom types disappear using the restricted existentials already
 available in GHC,   and such a wrapper should be just as efficient as if
 you had implemented your interface directly.

 Best,
 Leon


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


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


Re: [Haskell-cafe] A use case for *real* existential types

2013-05-10 Thread Leon Smith
On Fri, May 10, 2013 at 5:49 PM, Alexander Solla alex.so...@gmail.comwrote:

 I'm not sure if it would work for your case, but have you considered using
 DataKinds instead of phantom types?  At least, it seems like it would be
 cheap to try out.


 http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/kind-polymorphism-and-promotion.html


I do like DataKinds a lot,  and I did think about them a little bit with
respect to this problem,  but a solution isn't obvious to me,  and perhaps
more importantly I'd like to be able to support older versions of GHC,
 probably back to 7.0 at least.

The issue is that every call to init needs to return a slightly different
type,  and whether this is achieved via phantom types or datakinds,  it
seems to me some form of existential typing is required.  As both Andres
and MigMit pointed out,  you can sort of achieve this by using a
continuation-like construction and higher-ranked types (is there a name for
this transform?  I've seen it a number of times and it is pretty well
known...),  but this enforces a dynamic extent on the descriptor whereas
the original interface I proposed allows an indefinite extent.

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


Re: [Haskell-cafe] A use case for *real* existential types

2013-05-10 Thread Alexander Solla
On Fri, May 10, 2013 at 3:31 PM, Leon Smith leon.p.sm...@gmail.com wrote:

 On Fri, May 10, 2013 at 5:49 PM, Alexander Solla alex.so...@gmail.comwrote:

 I'm not sure if it would work for your case, but have you considered
 using DataKinds instead of phantom types?  At least, it seems like it would
 be cheap to try out.


 http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/kind-polymorphism-and-promotion.html


 I do like DataKinds a lot,  and I did think about them a little bit with
 respect to this problem,  but a solution isn't obvious to me,  and perhaps
 more importantly I'd like to be able to support older versions of GHC,
  probably back to 7.0 at least.

 The issue is that every call to init needs to return a slightly different
 type,  and whether this is achieved via phantom types or datakinds,  it
 seems to me some form of existential typing is required.  As both Andres
 and MigMit pointed out,  you can sort of achieve this by using a
 continuation-like construction and higher-ranked types (is there a name for
 this transform?  I've seen it a number of times and it is pretty well
 known...),  but this enforces a dynamic extent on the descriptor whereas
 the original interface I proposed allows an indefinite extent.


I know what extensions (of predicates and the like) are, but what exactly
does dynamic and indefinite mean in this context?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Where is haskell-platform?

2013-05-10 Thread Clark Gaebel
I'm looking for the version of haskell platform that was supposed to be
released May 6. It seems like it isn't out yet. What's preventing this from
happening, and is there anything I can do to help?

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


Re: [Haskell-cafe] A use case for *real* existential types

2013-05-10 Thread Leon Smith
A value has an indefinite extent if it's lifetime is independent of any
block of code or related program structure,  think malloc/free or new/gc.
 A value has a dynamic extent if is lifetime is statically determined
relative to the dynamic execution of the program (e.g. a stack variable):
 in this case the type system ensures that no references to the inotify
descriptor can exist after the callback returns.

Best,
Leon


On Fri, May 10, 2013 at 6:52 PM, Alexander Solla alex.so...@gmail.comwrote:




 On Fri, May 10, 2013 at 3:31 PM, Leon Smith leon.p.sm...@gmail.comwrote:

 On Fri, May 10, 2013 at 5:49 PM, Alexander Solla alex.so...@gmail.comwrote:

 I'm not sure if it would work for your case, but have you considered
 using DataKinds instead of phantom types?  At least, it seems like it would
 be cheap to try out.


 http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/kind-polymorphism-and-promotion.html


 I do like DataKinds a lot,  and I did think about them a little bit with
 respect to this problem,  but a solution isn't obvious to me,  and perhaps
 more importantly I'd like to be able to support older versions of GHC,
  probably back to 7.0 at least.

 The issue is that every call to init needs to return a slightly different
 type,  and whether this is achieved via phantom types or datakinds,  it
 seems to me some form of existential typing is required.  As both Andres
 and MigMit pointed out,  you can sort of achieve this by using a
 continuation-like construction and higher-ranked types (is there a name for
 this transform?  I've seen it a number of times and it is pretty well
 known...),  but this enforces a dynamic extent on the descriptor whereas
 the original interface I proposed allows an indefinite extent.


 I know what extensions (of predicates and the like) are, but what exactly
 does dynamic and indefinite mean in this context?

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


Re: [Haskell-cafe] Stream Processing

2013-05-10 Thread Gabriel Gonzalez
As far as I can tell, the only thing on that list not solved currently 
by `pipes` is leftovers, but I will be releasing that very soon.

Hello everybody,

I'm trying to formulate the stream processing problem, which doesn't
seem to be solved fully by the currently existing patterns.  I'm
experimenting with a new idea, but I want to make sure that I don't miss
any defining features of the problem, so here is my list.  A stream
processing abstraction should:

   * have a categorically proven design (solved by iteratees, pipes),

   * be composable (solved by all of them),

   * be reasonably easy to understand and work with (solved by conduit,
 pipes),

   * support leftovers (solved by conduit and to some degree by
 iteratees),

   * be reliable in the presence of async exceptions (solved by conduit,
 pipes-safe),

   * hold on to resources only as long as necessary (solved by conduit
 and to some degree by pipes-safe),

   * ideally also allow upstream communication (solved by pipes and to
 some degree by conduit).

   * be fast (solved by all of them).

Anything else you would put in that list?


Greets,
Ertugrul
   



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


[Haskell-cafe] Typeclass with an `or' restriction.

2013-05-10 Thread oleg

Mateusz Kowalczyk wrote:
 Is there a way however to do something along the lines of:
  class Eq a = Foo a where bar :: a - a - Bool bar = (==)
 
  class Num a = Foo a where bar :: a - a - Bool bar _ _ = False
 This would allow us to make an instance of Num be an instance of Foo
 or an instance of Eq to be an instance of Foo.

GADTs are a particular good way to constraint disjunction, if you can live
with the closed universe. (In the following example I took a liberty
to replace Int with Ord, to make the example crispier.)

 {-# LANGUAGE GADTs #-}

 data OrdEq a where
 Ord :: Ord a = OrdEq a -- representation of Ord dict
 Eq  :: Eq a  = OrdEq a -- representation of Eq dict

 bar :: OrdEq a - a - a - Bool
 bar Ord x y = x  y
 bar Eq  x y = x == y

The function bar has almost the desired signature, only (OrdEq a -)
has the ordinary arrow rather than the double arrow. We can fix that:

 class Dict a where
 repr :: OrdEq a

 -- We state that for Int, we prefer Ord
 instance Dict Int where
 repr = Ord

 bar' :: Dict a = a - a - Bool
 bar' = bar repr

 test = bar' (1::Int) 2

I can see the utility of this: something like C++ STL iterators and
algorithms? An algorithm could test if a bidirectional iterator is
available, or it has to do, less efficiently, with unidirectional. Of
course we can use ordinary type classes, at the cost of the
significant repetition. In the OrdEq example above, there are only two
choices of the algorithm for Bar: either the type supports Ord, or the
type supports Eq. So the choice depends on wide sets of types rather
than on types themselves.



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


Re: [Haskell-cafe] Reinventing a solution to configuration problem

2013-05-10 Thread oleg

I guess you might like then
http://okmij.org/ftp/Haskell/types.html#Prepose
which discusses implicit parameters and their drawbacks (see Sec 6.2).





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


[Haskell-cafe] A use case for *real* existential types

2013-05-10 Thread oleg

But Haskell (and GHC) have existential types, and your prototype code
works with GHC after a couple of trivial changes:

 main = do
   W nd0 - init
   wd0 - addWatch nd0 foo
   wd1 - addWatch nd0 bar
   W nd1 - init
   wd3 - addWatch nd1 baz
   printInotifyDesc nd0
   printInotifyDesc nd1
   rmWatch nd0 wd0
   rmWatch nd1 wd3
 -- These lines cause type errors:
 --  rmWatch nd1 wd0
 --  rmWatch nd0 wd3
   printInotifyDesc nd0
   printInotifyDesc nd1

The only change is that you have to write
  W nd - init
and that's all. The type-checker won't let the user forget about the
W. The commented out lines do lead to type errors as desired.

Here is what W is

 data W where
 W :: Inotify a - W
 init :: IO W
  [trivial modification to init's code]

I must say though that I'd rather prefer Adres solution because his
init
 init :: (forall a. Inotify a - IO b) - IO b

ensures that Inotify does not leak, and so can be disposed of at the
end. So his init enforces the region discipline and could, after a
trivial modification to the code, automatically do a clean-up of
notify descriptors -- something you'd probably want to do.



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


[Haskell-cafe] Stream processing

2013-05-10 Thread oleg

I'm a bit curious
   * be reliable in the presence of async exceptions (solved by conduit,
 pipes-safe),
  
   * hold on to resources only as long as necessary (solved by conduit
 and to some degree by pipes-safe),

Are you aware of
http://okmij.org/ftp/Streams.html#regions
which describes both resource deallocation and async signals. Could
you tell what you think is deficient in that code?

   * ideally also allow upstream communication (solved by pipes and to
 some degree by conduit).

Are you aware (of, admittedly) old message whose title was specifically
  ``Sending messages up-and-down the iteratee-enumerator chain''
http://www.haskell.org/pipermail/haskell-cafe/2011-May/091870.html
(there were several messages in that thread). Here is the code for
those messages
http://okmij.org/ftp/Haskell/Iteratee/UpDown.hs



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