Re: [Haskell-cafe] Superset of Haddock and Markdown

2011-11-18 Thread Ertugrul Soeylemez
Ivan Lazar Miljenovic  wrote:

> Wasn't there talk at one stage of integrating pandoc into haddock?

I wouldn't mind Haddock depending on Pandoc, at least optionally
(-fmarkdown-comments).  Taking this to its conclusion you could easily
have syntax-highlighted code examples in Haddock documentations and
allow alternative output formats.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] A Mascot

2011-11-16 Thread Ertugrul Soeylemez
John Meacham  wrote:

> People tend to concentrate on the lambda which cooresponds to the
> functional aspect of haskell when designing logos. Not nearly enough
> attention is paid to the other striking feature, the laziness. The
> 'bottom' symbol _|_ should feature prominently. The two most defining
> features of haskell are that it is purely functional and _|_ inhabits
> every type. The combination of which is very powerful.

I like the idea, even though personally I don't care that much.

I think the phrase "being lazy with class" could be put into the design
of a mascot.  For Haskell (forgive me for that term) marketing purposes
a mascot would definitely help.

But I think, despite the well-founded denotational semantics of Haskell,
bottom does not play that much of a role.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANN: Netwire 2.0.0

2011-11-14 Thread Ertugrul Soeylemez
Ozgur Akgun  wrote:

> Compilation problems here:
>
> [...]
>
> This build was trying to use deepseq-1.2.0.1. It builds fine with
> deepseq-1.1.0.2 though.

It should be fixed now.  Thanks for your report!


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


[Haskell-cafe] ANN: Netwire 2.0.0

2011-11-14 Thread Ertugrul Soeylemez
Hello everybody,

it's finally done.  I have just released Netwire 2.0.0, which is a
complete rewrite from scratch.  It has been generalized to arbitrary
automata with inhibition, so FRP is now just a special use case.

First of all the top module is now:

import Control.Wire

Wire is now an arrow transformer instead of an arrow-to-monad
transformer and the inhibition type is polymorphic instead of the
hard-coded SomeException type:

Wire e (>~) a b

Wire represents the following underlying type:

a >~ (Either e b, Wire e (>~) a b)

Inhibition uses any monoid 'e'.  To get the old behaviour, you can use
Last SomeException as 'e'.  One significant change is that all features
which were builtin in Netwire 1 are now addons, including even time and
random number generation.  These addons are available in the form of
type classes (Control.Wire.Classes) for the underlying arrow, including
for example:

  * ArrowIO,
  * ArrowRandom,
  * ArrowTime.

Also there are no explicit sessions anymore.  The current state of a
wire is simply the wire itself.  Everything else is captured by the
underlying arrow (>~), which you can construct the way you like.  There
is no hard-coded WireState anymore.

To get going really fast, just use the following type:

type SimpleWire = Wire () (Kleisli IO)

with the testWire function.  You can find a small demo here:



There are instances for all addon classes for Kleisli IO, so you can
write your first application very quickly.  For more serious
applications, you would usually write or compose your own underlying
arrow or even leave it polymorphic.

Please don't hesitate to give me feedback.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] German names for kinds and sorts

2011-11-14 Thread Ertugrul Soeylemez
Daniel Schoepe  wrote:

> > Most time, it is not really difficult to find an appropriate term
> > for concepts of Haskell, like types (Typen) or type classes
> > (Typklassen).  But I really don't know how to call kinds and sorts
> > in German. Any ideas?
>
> I'd go with "Arten" and "Sorten" respectively.

I agree.  I find myself talking about "Typarten":  "Der Typ Maybe ist
von der Art * -> *."

Often it's also sufficient to differentiate between concrete types and
type constructors:  "Maybe ist ein Typenkonstruktor."


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/


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


Re: [Haskell-cafe] How do you describe systems in general with Haskell?

2011-11-05 Thread Ertugrul Soeylemez
Grigory Sarnitskiy  wrote:

> If you are to describe a system, which consists of several subsystems,
> how do you approach the problem? What types, classes, functions
> whatever do you introduce?
>
> I guess it is a common problem, is there a general method? Just to
> describe, not to solve (though if the description implies the solution
> then it is wonderful).
>
> Obviously this is not just a haskell-specific problem, but I think
> there might be people who are aware of the best current solution
> (category theory?).

In general I view the subsystems as completely separate, as far as
possible.  Then I write a library for each of them, combining them later
in a program.

Also I try to find a design pattern for the general problem at hand,
although I almost always end up using FRP.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] arr considered harmful

2011-11-02 Thread Ertugrul Soeylemez
Ryan Ingram  wrote:

> I know it's a bit of an 'intentionally provocative' title, but with
> the recent discussions on Arrows I thought it timely to bring this up.
>
> Most of the conversion from arrow syntax into arrows uses 'arr' to
> move components around. However, arr is totally opaque to the arrow
> itself, and prevents describing some very useful objects as arrows.

I can totally understand your frustration, but on the other hand I have
to say that /not/ having 'arr' would break a lot of useful things at
least for me and probably for most programmers using AFRP.

One possible compromise is to move it into its own type class and also
offer specialized versions of it for plumbing in a yet simpler class.

class Arrow (>~) => ArrowPair (>~)
dup  :: a >~ (a, a)
swap :: (a, b) >~ (b, a)
...

class Arrow (>~) => ArrowArr (>~) where
arr :: (a -> b) -> (a >~ b)

This would enable some interesting optimization opportunities.  Perhaps
it also makes sense to turn ArrowArr into a subclass of ArrowPair.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] A catch-all MonadIO instance

2011-10-28 Thread Ertugrul Soeylemez
Bas van Dijk  wrote:

> I understand, portability is important for transformers. For
> monad-control it's less of an issue because I already use other
> language extensions (incl. RankNTypes).
>
> So I think I go ahead and add a catch-all instance for MonadControlIO
> to monad-control.

I'm not sure whether this will work well.  You will get overlapping
instances, and I don't see a way to hide instances when importing.
Perhaps the OverlappingInstances extension could help here.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Reminder Munich Haskell

2011-10-28 Thread Ertugrul Soeylemez
Heinrich Hördegen  wrote:

> We would appreciate, if more people from outside Munich could join us,
> but I understand if it is too far.

The problem is that all the meetings seem to be planned in the middle of
the week.  If you could throw in some more convenient dates in the
weekend or before holidays, I would certainly join.

Another idea is to create a similar meeting in or near Stuttgart.  If
any Haskellers from Baden-Württemberg are interested, I would be happy
to arrange a meeting.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Reminder Munich Haskell

2011-10-27 Thread Ertugrul Soeylemez
Heinrich Hördegen  wrote:

> this evening, Haskeller meet at Cafe Puck at 19h30:
> www.haskell-munich.de

May I ask how the evening went?  I would love to join, but it's just too
far away from here (Ludwigsburg near Stuttgart) for work days.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Is it possible to get the information of instances of a type?

2011-10-26 Thread Ertugrul Soeylemez
Magicloud Magiclouds  wrote:

>   If this was in ruby or other languages that support reflection, it
> won't be a question.
>   But in Haskell, could I write a code to list the classes that a type
> instanced?

In regular Haskell, type information is completely lost after
compilation, so you can't recover any of that.  There is no run-time
type information like in languages with OO inheritance.

However, types can choose to provide type information through the
Typeable type class (Data.Typeable).  Generally you wouldn't want to use
it, if you write Haskell properly (i.e. if you don't try to write Ruby
in Haskell).


>   TemplateHaskell as well.

I'm not sure about that one.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Data.Vector.Mutable.mapM

2011-10-20 Thread Ertugrul Soeylemez
Joachim Breitner  wrote:

> I’m consdering to change some performance critical code from Vector to
> MVector, hopefully avoiding a lot of copying and garbage collecting. But
> it seems that the Data.Vector.Mutable interface at
> http://hackage.haskell.org/packages/archive/vector/0.9/doc/html/Data-Vector-Mutable.html
>   is quite limited; e.g. I am missing simple functions having type
> modifyM :: PrimMonad m => (a -> m a) -> MVector (PrimState m) a -> m 
> ()
> that would do something with each element in the vector.
>
> Is this an indication that such use is actually not desired, or is it
> just the case that nobody has developed that yet?

In general you should try to work with immutable vectors as much as
possible.  Done properly you shouldn't lose much performance that way.

However, sometimes an operation is just much easier to express and
faster with the MVector interface.  In these cases you can escape to the
mutable interface using 'create', 'modify', 'thaw' and 'freeze'.  Don't
forget that you lose fusion that way, though.

In other words:  Don't use MVector exclusively.  Use it only when you
really need it.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/


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


Re: [Haskell-cafe] Waiting on input with `hWaitForInput' or `threadWaitRead'

2011-10-18 Thread Ertugrul Soeylemez
Michael Orlitzky  wrote:

> > I have uploaded a simple concurrent echo server implementation to
> > hpaste [1].  It uses one thread for the stdout logger, one thread
> > for the server, one thread for each client and finally a main thread
> > waiting for you to hit enter to quit the application.
> >
> > [1] http://hpaste.org/52742 - Concurrent echo server with logger
>
> This is a good example; you should stick it on the wiki somewhere so
> it isn't lost.

It is a good example for concurrent programming, but not a good example
for server programming.  By putting it into the wiki I would discourage
some programmers from using more suitable I/O abstractions/mechanisms.

Better let's keep it away from the wiki.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Waiting on input with `hWaitForInput' or `threadWaitRead'

2011-10-18 Thread Ertugrul Soeylemez
Jason Dusek  wrote:

> > I don't think you want either of the functions you mentioned.  What
> > you probably want instead is to do concurrent programming by
> > creating Haskell threads.  A hundred Haskell threads reading from
> > Handles are translated to one or more OS threads using whatever
> > polling mechanism (select(), poll(), epoll) your operating system
> > supports.
> >
> > I have uploaded a simple concurrent echo server implementation to
> > hpaste [1]. It uses one thread for the stdout logger, one thread for
> > the server, one thread for each client and finally a main thread
> > waiting for you to hit enter to quit the application.
> >
> > [1] http://hpaste.org/52742 - Concurrent echo server with logger
>
> I am not sure how to apply the principle you mention to a proxy, which
> must read from and write to both handles in turn (or, ideally, as
> needed).

A proxy server acts a lot like an echo server.  The difference is that
usually before the actual proxying starts you have a negotiation phase,
and instead of echoing back to the same socket, you just write it to a
different one.  Here is an (untested) example:

(clientH, clientHost, clientPort) <- accept serverSock
destH <- negotiate clientH
doneVar <- newEmptyMVar

forkIO (hGetContents clientH >>= hPutStr destH >>= putMVar doneVar)
forkIO (hGetContents destH >>= hPutStr clientH >>= putMVar doneVar)
replicateM_ 2 (takeMVar doneVar)
mapM_ hClose [clientH, destH]

Of course this code is going to bite you in production for two reasons:
First of all it has no error handling.  If the 'negotiate' function
throws an exception, then nobody will close the client handle.  So view
this is a highly simplified example!

The second reason is that in this lazy I/O framework it is
extraordinarily difficult to write the 'negotiate' function in the first
place, unless you allow yourself to put stuff back into the handle or
process only one byte at a time.  Both options are bad.  A better option
is to use a proper I/O abstraction suitable for protocol processing.
Iteratees [1] come to mind.  They solve this problem elegantly and let
you really just use the parser style "destH <- negotiate".

My usage of the MVar is actually kind of an abuse.  I just use it to
allow the two forwarder threads to signal their completion.  The main
thread just waits for the two to complete and then closes both handles.
The word "abuse" is perhaps too strong, because there is essentially
nothing wrong with the approach.  The standard concurrency library
doesn't provide an event primitive, so the more general MVar is often
used for this.

[1] http://www.yesodweb.com/book/enumerator


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-17 Thread Ertugrul Soeylemez
Christian Maeder  wrote:

> > So please, please, please, if you decide to use a newtype, do /not/
> > hide the constructor.
>
> The better alternative to "not hiding the constructor" is to supply
> conversion functions that may or may not do more than the constructor
> and selector and are named accordingly. (This just disallows pattern
> matching.)

Except annoying library users, what would be the point of that?

Please understand that as a middle level developer (abstractions,
protocol implementations, frameworks, etc.) I am sometimes annoyed by
the idealism of some library interfaces, and I find myself reinventing
the wheel very often, because the closed interfaces of some existing
libraries just don't support what I need, even though the technical
basis would be there, or because of the abstraction forest I'm unable to
guarantee or even get good performance.

I could totally understand having a black box interface for some higher
level stuff, but ByteString is still low/middle level and should support
me as a developer on that level.

Unifying vector and bytestring sounds like a great step, and I would
find it ruined already by wrapping it up in a newtype.  Hiding the
constructor would make this even worse.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


[Haskell-cafe] ANN: netwire 1.2.7

2011-10-17 Thread Ertugrul Soeylemez
Hello fellows,

netwire 1.2.7 is out.  Summary of the changes from netwire 1.2.5 (my
last announcement):

  * Events:  Added 'periodically' event generator.

  * Manager:  Added the 'manager' wire, which is sort of a
generalization of the various context wires and should be useful for
highly dynamic applications like games.

  * FRP.NetWire now also exports mkGen, toGen and the WireState type.
Furthermore I have added mkFix to ease writing stateless wires.
Right now this just translates to mkGen, but might make use of a
special Wire constructor in the future.

  * Added appFirst, appFrozen, appEvent and an ArrowApply instance based
on appFrozen.  All these allow you to embed a wire network into the
running network.  The embedded network is allowed to be a signal
itself, which technically turns Wire into a monad.

  * Added testWire and testWireStr to ease writing wire test programs.

  * The FRP.NetWire.Concurrent module is gone for now.  I'm performing a
lot of research regarding embedded concurrent wire sessions, but I
have not reached a point where I can provide a stable implementation
yet.

  * Lots of documentation improvements.

Please keep the feedback coming.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-17 Thread Ertugrul Soeylemez
Christian Maeder  wrote:

> I think the cleanest solution (just from a theoretical point of view)
> is to use a newtype for your byte strings.
>
> - it should have the same performance
> - allows to make ByteString really abstract when hiding the newtype
> constructor
> - is portable and supplies control over all other instances (not just
> Show)
>
> I'm not sure if one could make really bad thinks to your ByteString by
> using the Vector interface, but one would want to disallow vector
> operations just for compatible with other byte strings.
>
> It would require more work just on your side, though.

Also such an implementation wouldn't be big news.  You would get stream
fusion as news, but I'm specifically excited about the idea that I can
use the vector interface.

I see no need to restrict the ByteString interface, since it is a pretty
low level data structure anyway.  You use it to process raw ByteStrings
and as such should get maximum flexibility in doing so.  Every
restriction means that in a certain edge case you can't get high
performance, because the author decided that you aren't smart enough to
use the underlying interface, something which I always found annoying
about some of the Haskell libraries.

So please, please, please, if you decide to use a newtype, do /not/ hide
the constructor.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Waiting on input with `hWaitForInput' or `threadWaitRead'

2011-10-17 Thread Ertugrul Soeylemez
Jason Dusek  wrote:

> I would like to use evented I/O for a proxying application. My present
> thinking is to fork a thread for each new connection and then to wait
> for data on either socket in this thread, writing to one or the other
> socket as needed.
>
> [...]
>
> Ideally, I'd get something like select() on handles, just saying
> whether there are bytes or not. However, I haven't managed to find
> anything like that in the standard libraries.

I don't think you want either of the functions you mentioned.  What you
probably want instead is to do concurrent programming by creating
Haskell threads.  A hundred Haskell threads reading from Handles are
translated to one or more OS threads using whatever polling mechanism
(select(), poll(), epoll) your operating system supports.

I have uploaded a simple concurrent echo server implementation to hpaste
[1].  It uses one thread for the stdout logger, one thread for the
server, one thread for each client and finally a main thread waiting for
you to hit enter to quit the application.

[1] http://hpaste.org/52742 - Concurrent echo server with logger


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-16 Thread Ertugrul Soeylemez
Felipe Almeida Lessa  wrote:

> > Although I don't have a problem with using language extensions the
> > vector package, as it is a commonly used tool, shouldn't require me
> > to use an extension just to be able to debug my code.  This would be
> > particularly annoying when using GHCi, because you would always have
> > to start it with an extension option.
>
> You don't need it.  The OverlappingInstances extension needs to be
> enabled only where the ovarlapping instances are defined, *not* where
> they're used. =)

I see.  Then I'm totally fine with it. =)


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-16 Thread Ertugrul Soeylemez
Bas van Dijk  wrote:

> On 15 October 2011 23:17, Ertugrul Soeylemez  wrote:
> > Both instances are valid here, and there is no mechanism to choose
> > one of them.
>
> There is: OverlappingInstances[1] chooses the most specific instance.
> So in case someVector :: Vector Word8 the instance Show (Vector Word8)
> is chosen because it's the most specific.

Although I don't have a problem with using language extensions the
vector package, as it is a commonly used tool, shouldn't require me to
use an extension just to be able to debug my code.  This would be
particularly annoying when using GHCi, because you would always have to
start it with an extension option.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Question, re: using Automaton

2011-10-16 Thread Ertugrul Soeylemez
Captain Freako  wrote:

> Encapsulating an automaton by running it on a stream of inputs,
> obtaining a stream of outputs.
>
> Typical usage in arrow notation:
>
>   proc p -> do
>   ...*ys <- (|runAutomaton (\x -> ...)|) xs*
>
> Here xs refers to the input stream and x to individual elements of
> that stream. ys is bound to the output stream.  Could someone replace
> the ellipses w/ an expression that would compile and make sense?
> (I'm really struggling, trying to understand this example.)

Your expression should in fact compile and run out of the box.  I
haven't tried your example, but I use the (| |) syntax form frequently.
See the GHC manual [1] to see how it is translated.

Example:

proc x -> do
y <- trans subArrow -< (f x, g x)
someComp3 -< f y

where
subArrow = proc (x1, x2) -> do
someComp1 -< x1
y <- someComp2 -< x2
returnA -< h y

The (| |) notation can be used to write this more concisely:

proc x ->
y <- (| trans (do
someComp1 -< f x
y <- someComp2 -< g x
returnA -< h y |)
someComp3 -< f y

It basically allows you to construct an arrow computation (subArrow) to
be passed to an arrow function (trans) using the outer computation's
bound variables without having to construct tuples to pass them around.
Under the hood this is translated to passing tuples.

Note:  I'm assuming GHC.

[1] 


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-15 Thread Ertugrul Soeylemez
Bas van Dijk  wrote:

> > My suggestion was to remove the generic Show instance and add only
> > specialized instances.  This is more work, but will also yield
> > better results.  In particular, it allows specialized string
> > representations for other types, too.
>
> What exactly is the problem with using OverlappingInstances to define
> specialized Show and Read instances for Vectors with certain element
> types (Char, Word8, Bool)?
>
> Am I missing something dangerous here?

Consider having the following instances:

instance Show a => Show (Vector a)
instance Show (Vector Word8)

How could the compiler determine, which instance you want, when saying

show someVector

where someVector :: Vector Word8?  Both instances are valid here, and
there is no mechanism to choose one of them.  You can only write a
generic instance, where you can rule out the specialized instances.  I
don't think that's possible in this case.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-15 Thread Ertugrul Soeylemez
Roman Leshchinskiy  wrote:

> > Personally, I think that ByteString and especially Vector Word8
> > aren't strings and shouldn't be treated as such. But I wouldn't be
> > strongly against showing them as strings. However, I *am* strongly
> > against using UndecidableInstances in vector and I don't see how to
> > implement this without using them.
>
> I meant OverlappingInstances, of course. To clarify, I would still
> consider it if everybody thinks it's a really good idea.

My suggestion was to remove the generic Show instance and add only
specialized instances.  This is more work, but will also yield better
results.  In particular, it allows specialized string representations
for other types, too.  For example the way values of type Vector Bool
are printed is extremely useless.  I always find myself writing my own
debugging output functions for boolean vectors.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-15 Thread Ertugrul Soeylemez
Joachim Breitner  wrote:

> > So what do other people think about this?
>
> having a human-readable Show instance for ByteStrings is definitely a
> great plus when debugging code.

I agree and would even go as far as saying that it's generally useful,
even if the data is not guaranteed to be text.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/


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


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-14 Thread Ertugrul Soeylemez
Max Rabkin  wrote:

> > Though I would argue that unless you're trying to actually use for
> > Show/Read for serialisation, does it really matter what the
> > Show/Read instances for Bytestring are?
>
> Convenient debugging and REPL interaction certainly matter!

On the other hand, having a separate Show instance for Vector Word8
would require either writing all Show instances explicitly or keeping
two separate packages.  I would prefer to have the two packages merged
into one.

But since I find a useful Show instance for ByteString useful, too, I
would go with the first variant of providing a few default instances
instead of a generic Show a => Show (Vector a) instance.  That way you
can write nicer instances for some other element types, too.  For
example I can imagine how a much nicer Vector Bool instance would look
like:

fromBoolString "1.1..111..1"


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] A question about causality in FRP

2011-10-14 Thread Ertugrul Soeylemez
David Barbour  wrote:

> > The usual model for arrowized FRP is based on this type:
> >
> >newtype Auto a b = Auto (a -> (b, Auto a b))
> >
> > I would be very interested in how you would write an ArrowApply
> > instance for such a type.  So far my conclusion is:  It's
> > impossible.
>
> Interesting claim. The implementation is obvious enough:
>   runAuto (Auto f) = f
>   app = Auto $ \ (f,x) -> let (x',f') = runAuto f x in (x',app)
>
> Which arrow laws does this violate? Or is your concern that a fresh
> arrow supplied to `app` at each instant obviously cannot accumulate
> state?

It's not about the laws, it's about losing state.


> Yampa AFRP model chooses to model products using the `Either` type -
> i.e.  indicating that either element can be updated independently.
> Using this, one could accumulate state in the captured arrow, though
> there'd be a funky reset whenever the arrow is updated.

Of course you can make a trade-off, but I don't think it's possible to
solve this in a clean way in the automaton model.


> The reactive model I'm developing, Reactive Demand Programming, is
> actually anti-causal: behavior at any given instant may depend only
> upon its present and future inputs (anticipation), but never the
> past. State is treated as an external service, part of an abstract
> machine, orchestration of registers or a database. I think this setup
> works better than FRP, e.g. for controlling space-leaks, supporting
> smooth transitions and upgrades of dynamic behavior, modeling the app
> as a whole as dynamic, and orthogonal persistence.

I would be very interested in such a model.  Are there any resources
online?


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] A question about causality in FRP

2011-10-14 Thread Ertugrul Soeylemez
David Barbour  wrote:

> If you want first-class behaviors or behavior transformers, those will
> need a different abstraction than 'nested' behaviors. Nested != First
> Class.  You'd have special functions to lift a first-class behavior as
> an argument (e.g. add a phantom type to prohibit non-causal
> observation), and to lower it into the main system for sampling
> (e.g. ArrowApply).

The usual model for arrowized FRP is based on this type:

newtype Auto a b = Auto (a -> (b, Auto a b))

I would be very interested in how you would write an ArrowApply instance
for such a type.  So far my conclusion is:  It's impossible.

Do you have a different AFRP model in mind?


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Up and Down the Latter of Abstraction

2011-10-12 Thread Ertugrul Soeylemez
Lyndon Maydwell  wrote:

> I came across an interesting page about interactive abstraction called
> "Up and Down the Latter of Abstraction" [1] while browsing
> hacker-news.
>
> Under the appendix "Tools & Implementation" Bret Victor ponders:
>
>   "Perhaps language theorists will stop messing around with arrows and
> dependent types, and start inventing languages suitable for
> interactive development and discovery."
>
> I don't subscribe to the idea that static guarantees and functional
> characteristics are mutually exclusive to interactive development and
> discovery and I think they may actually complement each other
> extremely well, but this page certainly does sell the interactive
> aspect very effectively.
>
> The closest I've seen to this proces from Haskell seems to have come
> from "luite" and co (correct me if I'm wrong) and their work on the
> Diagrams package and its surrounding infrastructure [2], however,
> their interactive demonstrations no longer seem to be online. Still,
> the dominant interface seems to be web-based, and I feel that a native
> environment for this kind of explorative interactive programming would
> be more effective.
>
> Other languages that seem to be especially effective at this kind of
> development are Processing [3] and Mathematica [4].
>
> Has anyone had experience with interactive development in Haskell?

I wouldn't say that the author is entirely wrong in that there is a need
for such tools.  I just don't like the way he presents us statically
typed functional programmers.  There is absolutely no reason to believe
that this kind of programming is difficult or even impossible in
Haskell.

Quite the contrary:  As we like to write our algorithms purely,
interactive visualization becomes almost trivial, once you have a useful
library for doing it.  The Gloss library is a good start for visualizing
pure algorithms.  Unfortunately you cannot write GUIs with sliders and
input fields very well, and you cannot control the parameters via the
console, because Gloss forces your entire application into the pure
framework.  You can only write pure keyboard and mouse handlers, so
Gloss is generally very limited for real world applications, unless you
abuse laziness to deal with it.

I think the true source code solution to this problem is an FRP-based
graphics library with some simple controllable UI elements.  This is
very well possible in Haskell.  We have powerful abstractions with
powerful implementations ready to use.

You could go further by writing an editor with a builtin interpreter,
which can visualize pure Haskell functions automatically, as long as the
types are in certain type classes.  As a programmer you wouldn't have to
do anything other than perhaps specifying parameter bounds for the
sliders.

In other words:  In contrast to Bret Victor I think the statically
typed, pure Haskell with arrows and a lot of theoretic background is the
best language for this way of programming.  It's just that apparently
nobody has written the tools yet.  The editor-builtin visualizer would
indeed be a great feature.

As an amusing fact (regarding the author's call you quoted) arrows are
exactly the one abstraction, which would make this also accessible to
impure or automaton-style computations.  A type class ArrowAnimation
could enable visualization of nonstatic computations like automata, FRP
systems, impure operations, nondeterministic computations, etc.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Haskell vs. Dart

2011-10-11 Thread Ertugrul Soeylemez
Heinrich Apfelmus  wrote:

> I didn't look very carefully, but from a Haskeller's point of view, I
> can't see any significant difference between Dart and JavaScript,
> except perhaps for the name. By comparison, CoffeeScript is a way more
> innovative venture.

If you want a useful client-side browser language, which is not just the
same as JavaScript with a different syntax, look into Haxe [1].

That one is a statically, strongly typed language, which can be compiled
down to JavaScript and other targets (PHP, ActionScript, SWF, C++,
etc.).  Some of the interesting features of it are algebraic data types,
pattern matching, a module system and a rich standard library with lots
of functionality which you always missed in JavaScript.

It is also a great alternative, if you are forced to deploy PHP code
and, like me, can't even find words strong enough to express the
intensity of your absolute hate against that "programming language".

[1] http://haxe.org/


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANN: ircbot 0.1.1

2011-10-11 Thread Ertugrul Soeylemez
Jeremy Shaw  wrote:

> 1. The library is based around the old String based irc library. Would
> be nice to upgrade to something that used ByteStrings+Text+Builder.
> Practically speaking.. it's IRC. The maximum line length is 510
> characters, and the bot typically needs to handle, at most, a few
> messages per second. So, space and time issues would only be a
> practical concern if your bot is joining hundreds of channels. But,
> that is no excused not to use Text :) Perhaps the fastirc library?

Hello there,

I'm the author of the fastirc library.  Even though it does address the
problem of the old String-based 'irc' library, I wouldn't say that I'm
very happy with the way it works.

The library is a product of my early attempts to write fast, secure
networking code in Haskell back in spring 2010.  The protocol parser is
based on attoparsec and is fast, but it doesn't work the way I would
like it to work.  It has a somewhat fragile way to ensure that lines
don't get too long.  Another shortcoming is the very weak session code,
so if you want to use fastirc, you should only use the parser.

I have started a new library based on attoparsec and the enumerator
library, which is faster and handles line splitting properly with an
enumeratee (that one is already on Hackage in the 'netlines' package).
Also it will have good support for sessions using an FRP approach with
the netwire library.

However, be prepared to wait one or two weeks, until I have time to
reach a point, where I can make an official release.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] haskell i18n best practices

2011-09-30 Thread Ertugrul Soeylemez
Paulo Pocinho  wrote:

> I don't know if this is a bad habit, but I had already separated the
> dialogue text in the code with variables holding the respective
> strings. At this time, I thought there could be some other way than
> gettext. Then I figured how to import localisation data, that the
> program loads, from external files. The data type is basically a tuple
> with variable-names associated with strings. This is bit like the
> file-embed package [3].
>
> Still uncomfortable with i18n, I learned about the article "I18N in
> Haskell" in yesod blog [4]. I'd like to hear more about it.
>
> What is considered the best practice for localisation?

I can't help you with best practice for Haskell, and I don't think there
is any.  Gettext is probably the easiest approach, because it integrates
nicely with the rest of the environment.  It automatically uses the
usual LANG and LC_* variables, which are used in Unix-like systems.

An even simpler (but not necessarily easier) approach is to hard-code
the languages in a Map and just look up the string you need.  In this
case you have to code the integration yourself.  It somewhat sounds like
you are targetting the Windows platform anyway.  Personally I'd likely
prefer Gettext for its integration and all the existing translation
tools.

In either case, the best practice is not to work with variables, but
with a default language.  You write your text strings in your default
language (usually English), but wrap them in a certain function call.
The function will try to look up a translated message for the current
language.  This makes both programming and translating easier.  This is
how I imagine it works (or should work):

main :: IO ()
main = do
tr <- getTranslator
putStrLn (tr "This is a test.")

The 'tr' function is called just '_' in other languages, but you can't
use the underscore in Haskell.  A translater (person) would use a
program to search your entire source code for those translatable
strings, then they would use a translation program, which shows an
English string and asks them to enter the translated string over and
over, until all strings are translated.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Much faster complex monad stack based on CPS state

2011-09-28 Thread Ertugrul Soeylemez
Bas van Dijk  wrote:

> Because of this reason I don't provide a MonadTransControl instance
> for ContT in monad-control[2].

Is that even possible?  I tried hard to come up with just a MonadFix
instance for CPS-based monads, and I failed.  I would think that
MonadTransControl is just as hard, if not even harder.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Proposal: Subcomputations in arrow notation

2011-09-22 Thread Ertugrul Soeylemez
"Paterson, Ross"  wrote:

> See the GHC Arrow notation documentation for more about the banana
> brackets, which let you use user-defined control structures like
> event.

I have reread the documentation now.  It seems that there are a lot of
syntactic constructs, which I've missed.  Particularly the banana
bracket notation does exactly what I want.  Thanks a lot!


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


[Haskell-cafe] Proposal: Subcomputations in arrow notation

2011-09-21 Thread Ertugrul Soeylemez
Hello fellow Haskellers,

this is a proposal to extend the arrow notation (-XArrows).  I find
myself writing the following very often:

system :: Wire IO () String
system =
proc _ -> do
botAddPeriod <- succ ^<< noise -< ()
botAddSpeed <- noise1 -< ()
botAddStart <- noise1 -< ()
botMsg <- event addBot -< (botAddPeriod, botAddSpeed, botAddStart)

bots <- manager -< ((), maybe MgrNop id botMsg)
let botStr = concatMap (printf "%8.2") . M.elems $ bots :: String
identity -< printf "Bot positions: %s" botStr

where
addBot :: Wire IO (Double, Double, Double) (MgrMsg Int IO () Double)
addBot =
proc (addPeriod, addSpeed, addStart) -> do
periodically -< addPeriod
botId <- identifier -< ()
identity -< MgrAdd botId (constant addSpeed >>> integral 
addStart)

The relevant part is the first paragraph of the first arrow computation:

botAddPeriod <- succ ^<< noise -< ()
botAddSpeed <- noise1 -< ()
botAddStart <- noise1 -< ()
botMsg <- event addBot -< (botAddPeriod, botAddSpeed, botAddStart)

This line should generate a message for the bot manager at random
intervals.  The actual event generator is in the second arrow
computation 'addBot'.  I would like to be able to write this more in
line with the rest of the code.  The following is possible:

system :: Wire IO () String
system =
proc _ -> do
botAddPeriod <- succ ^<< noise -< ()
botAddSpeed <- noise1 -< ()
botAddStart <- noise1 -< ()

botMsg <- event (proc (addPeriod, addSpeed, addStart) -> do
periodically -< addPeriod
botId <- identifier -< ()
identity -< MgrAdd botId (constant addSpeed >>> integral 
addStart))
-< (botAddPeriod, botAddSpeed, botAddStart)

bots <- manager -< ((), maybe MgrNop id botMsg)
let botStr = concatMap (printf "%8.2") . M.elems $ bots :: String
identity -< printf "Bot positions: %s" botStr

This is probably not a big improvement.  It's more concise, but also
harder to understand.  My proposal is to add syntax to allow the
following notation:

system :: Wire IO () String
system =
proc _ -> do
botAddPeriod <- succ ^<< noise -< ()
botAddSpeed <- noise1 -< ()
botAddStart <- noise1 -< ()

botMsg <- event $ do
periodically -< addPeriod
botId <- identifier -< ()
identity -< MgrAdd botId (constant addSpeed >>> integral 
addStart)

bots <- manager -< ((), maybe MgrNop id botMsg)
let botStr = concatMap (printf "%8.2") . M.elems $ bots :: String
identity -< printf "Bot positions: %s" botStr

Again the relevant part is the event generator in the middle.  In this
hypothetical syntax, the compiler would figure out from the inner
computation, which variables from the outer scope are used and pass them
automatically in an appropriate tuple.  You wouldn't need any explicit
passing anymore.

If others like the idea, too, and there is nobody to implement it, then
I would be willing to get in touch with the GHC code and implement this
as a patch myself.

What do you think?


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Animas/Yampa - Using Zip as a Routing Function in a Parallel Switch with Feedback

2011-09-20 Thread Ertugrul Soeylemez
"M. George Hansen"  wrote:

> I've been playing around with functional reactive programming using
> Animas/Yampa and ran into a strange situation. I'm using a parallel
> switch to route input to a collection of signal functions and using
> the output as feedback (to simulate state). Everything works as
> expected until I attempt to use zip as a routing function (i.e. pair
> each element of input with a signal function). Using zip as a routing
> function causes the program to enter an infinite loop when it
> evaluates the output from the parallel switch.

I'm not totally sure, but I sense that you may need a one-instant delay
in your looping code here:


> rec
> let senses = map (\state -> (inputEvents, state)) states
> states <- par route activities -< senses

Try adding a one-instant delay by passing the output of your parallel
switch through the iPre signal function:

states <- iPre [] <<< par route activities -< senses

Hope that helps.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANN: Webwire 0.1.0, netwire 1.2.5

2011-09-16 Thread Ertugrul Soeylemez
Daniel Patterson  wrote:

> I'm also excited to see examples. Even simple ones!

Alright, I have written some examples:




> Based on my understanding of FRP (which may have little bearing on
> what webwire actually does, just what I hope it does), what makes it
> really different is that it is relatively stateless itself - that's
> kind of the point, that you model your system as a bunch of data
> sources, and you can change them with pure functions, and when you do
> that they will be updated anywhere you are using them without any
> explicit imperative stuff. I'm not sure how that translates to a
> server-side applications (the only web examples I know of have been
> javascript-based), or webwire itself so I'm curious to see how this
> works.

Interestingly it's quite the opposite.  Wires in netwire are inherently
stateful, but offer an interface, which hides that state almost
completely.  Wires are essentially time-varying functions.  In fact, a
stateless wire is simply a function or a computation in the underlying
monad.

What makes FRP so great is that you observe this statefulness in terms
of data dependencies.  Very little imperative programming, yet high
performance and an incredible expressivity.  See in the examples how
quickly I was able to write an application, which limits the average
request rate over the last ten requests for every session individually.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/


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


Re: [Haskell-cafe] Karatsuba Multiplication Parallel

2011-09-16 Thread Ertugrul Soeylemez
Burak Ekici  wrote:

> I am trying to parallelize the below Karatsuba multiplication
> code. However, at each trial of mine the error message speaking of
> "incorrect indentation" is returned. I could not come up with ideas to
> solve the problem.

I didn't read enough of the code to help you with your actual issue, but
I'd like to point out that you have to use sharing for the parallel
processing to be effective.  In other words, this is wrong:

3^1 `par` 5^1 `pseq` 3^1 * 5^1

and this is right:

let x = 3^1
y = 5^1
in x `par` y `pseq` x * y


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANN: Webwire 0.1.0, netwire 1.2.5

2011-09-16 Thread Ertugrul Soeylemez
Michael Snoyman  wrote:

> I'm not sure what you mean by runtime-only, could you clarify?

The session is inherently bound to its current continuation, and the
continuation is a function, i.e. cannot be serialized.  This is a
generalization, which comes with the price that sessions are lost, as
soon as you quit the program.

In other words:  Applications desiring to save the state need to capture
it as something serializable to be able to restore sessions (at least
partly) later on.


> The reason I'm wary of continuation-based frameworks is that (at least
> from what I've seen) they are purposely non-RESTful. I know REST is a
> buzzword, but the other way to put it is: you're going to end up
> working against most of what HTTP is doing. There are good reasons why
> HTTP is stateless, and that shouldn't be circumvented lightly.

Yes, this is indeed a problem with the traditional explicit continuation
approach.  However, webwire solves this problem mostly, because
continuations are implicit and bound to the current resource.  You will
see the effect of continuations mostly in global or resource-specific
stuff like authentication, forms, sessions, etc.

In other words:  What FRP buys you here is that you can write your
applications in a dialog style.  Resource URIs need to be managed by the
application developer and are not in any way dealt with by webwire.


> I don't want to go too far on this right now, as I'm not an expert on
> cont-based frameworks, and I'm certainly not sure how webwire works.
> But from what I've seen in the past, you end up with ugly URLs and bad
> caching behavior. I think web developers *should* have to think about
> the fact that a page request is an inherently stateless operations,
> and storing state data should be a huge exception[1], not the norm.

As noted above, the URI problem is not an issue in webwire.  And as for
the caching, one really great thing about the FRP approach is that you
can actually infer the change rate of a resource to some extent.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANN: Webwire 0.1.0, netwire 1.2.5

2011-09-16 Thread Ertugrul Soeylemez
Michael Snoyman  wrote:

> Nice to see another project taking advantage of WAI and Shakespeare. I
> look forward to seeing some example code as well, though I personally
> am very wary of continuation-based frameworks.

AFRP uses continuations under the hood, so you can view webwire as
continuation-based to some extent.  But out of interest, why are you
wary?  This is highly experimental work, and I see some problems coming:

  * Lower performance, though that can be fixed.  Right now I'm getting
up to about 8000 requests per second using apachebench with -n 1
and -c 1000, which is probably not enough for high volume sites.

  * Sessions are a runtime-only phenomenon.  This is a more serious
problem, for which I don't currently have a general solution, though
for most applications specialized solutions can be written.

  * FRP and netwire in particular have a steep learning curve.

If you see any further potential problems, I'd be very grateful, if
you'd let me know.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANN: Webwire 0.1.0, netwire 1.2.5

2011-09-16 Thread Ertugrul Soeylemez
Christopher Done  wrote:

> > webwire is an experimental web framework based on the functional
> > reactive programming library netwire.  It uses WAI under the hood
> > and right now features only a subset of the very basics of what you
> > need to write web sites
>
> Are you going to provide any examples?

Soon, yes.  Right now I'm focussing on finishing the basics.  As soon as
I have preliminary form support, I'm going to write an example
application.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANN: Webwire 0.1.0, netwire 1.2.5

2011-09-15 Thread Ertugrul Soeylemez
Ertugrul Soeylemez  wrote:

> webwire is [...]

stupid me. =)  As always I forgot to link them:

<http://hackage.haskell.org/package/webwire>
<http://hackage.haskell.org/package/netwire>


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


[Haskell-cafe] ANN: Webwire 0.1.0, netwire 1.2.5

2011-09-15 Thread Ertugrul Soeylemez
Hello fellow Haskellers,

webwire is an experimental web framework based on the functional
reactive programming library netwire.  It uses WAI under the hood and
right now features only a subset of the very basics of what you need to
write web sites.  Features:

  * Reactive programming of web sites.
  * Stick together subapplications similar to Happstack.
  * Build web pages piece by piece using Yesod-inspired widgets.
  * Builtin support for "shakespearean" templates.
  * Builtin support for selecting output types (like HTML/JSON).
  * Simple Happstack-style routing functionality.
  * Very simple overall design.
  * And as always:  100% Haddock documentation coverage.

Its aim is to combine all the good features of continuation-based web
frameworks by hiding as much as possible of the stateless nature of
HTTP.  Through the netwire library it introduces some new design
patterns, which appear to work amazingly well for web applications:

  * Powerful new design pattern for sessions:  Through netwire's
context-sensitive wires it becomes almost trivial to have separate
subwires for every user.  This way you can write your applications
like you were in a dialog with the user.  I'm planning to implement
forms based on the same design pattern.

  * Feedback and choice make it easy to express complicated
inter-request data dependencies.

And together with webwire I have also released a new version of netwire.
Changes include:

  * Generalized context wire transformers.
  * Generalized session functions.
  * Signal injection (reinject exhibited signals).

Thanks go to:  Cale Gibbard for support with AFRP, the Yesod team for
lots of useful libraries.

Keep the feedback coming!


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


[Haskell-cafe] ANN: Netwire 1.2.4

2011-09-11 Thread Ertugrul Soeylemez
Hello there,

version 1.2.4 of netwire is out.  Major changes:

  * Changed the semantics of time.  Previously if a wire was not run
(because of an earlier inhibiting wire), then its local time was
suspended.  Example:

proc _ -> do
t1 <- time -< ()
fps1 <- avgFps 1000 -< ()

require_ <<< wackelkontakt -< ()
t2 <- time -< ()
fps2 <- avgFps 1000 -< ()

identity -<
printf "Time: %8.2f %8.2f\nFPS : %8.2f %8.2f"
   t1 t2 fps1 fps2

In the previous version t2 would be about half of t1, because the
{require_ <<< wackelkontakt} wire inhibits for about half of all
instances.  Further fps1 and fps2 would be about equal.  In other
words, time was local, while FPS were global.  This is not very
useful in practical applications.

With the new semantics t1 and t2 will be equal.  Instead the
framerate will drop after the inhibiting wire, such that fps2 will
be about half of fps1.  So now time is global and FPS are local.

This is useful e.g. in a stateless network application (like a web
app) to ban users, who are trying logins too fast.  The following
wire allows one login trial per second in average over the last 10
trials (the faster you try the longer you have to wait):

login :: Wire MyApp IpAddress User
login = context $ proc ipAddr -> do
fps <- avgFps 10 -< ()
require_ -< fps < 1
{- login procedure -}

Used with ArrowPlus this easily lets you fetch the currently logged
in user from the session, and if there is none, request a login:

getUser :: Wire MyApp IpAddress User
getUser = getCurrentUser <+> login

  * Context-sensitive wires.  There is now a new wire transformer called
'context', which is essentially a context switcher establishing
multiple wire threads of control:

context :: (Ord a, Monad m) => Wire m a b -> Wire m a b

It takes a base wire and evolves it individually for each possible
input value.  This is a very convenient alternative to parallel
routing switches.

The 'context' wire transformer never forgets a context.  For many
applications (like sessions in a web application) this is not
desirable.  For them there is an alternative transformer
'contextLimited', which allows you to garbage-collect.

Minor changes:

  * More responsive calculus wires.  Reflect changes immediately without
the one-instant delay.  If you need the delay for feedback, use
'delay' explicitly.

  * New analysis wires 'collect' and 'lastSeen'.

  * New inhibition wires 'forbid_', 'inhibit_' and 'require_'.

  * Separate session starting/cleaning functions in FRP.NetWire.Session.
However, the exception-safe withWire function is the preferred way.

  * Optimized internal representation.  There are now only two
constructors WGen and WArr for the Wire type instead of four.  I
dropped WConst and WId, because they are representable as special
cases of WArr without noticable performance loss.  This improves
overall performance, because now there are only two constructors to
pattern-match against.

Right now I'm working intensively on netwire, so if you have any feature
requests, just mail me.  There is a good chance to find your desired
feature implemented quickly.

Note:  I have been too quick with version numbers.  Major version 2 will
be the one with the stabilized API, so for now with increasing minor
version numbers (but not patch levels!) you have to be prepared for API
changes, although I don't expect big changes anymore.

Enjoy and keep the feedback coming!


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] mapM is supralinear?

2011-09-09 Thread Ertugrul Soeylemez
Roman Cheplyaka  wrote:

> > In general it's a bad idea to use mapM over IO.
>
> Could you explain why?

Most applications don't require loading the entire result into memory,
so a combinator like foldM is more appropriate.  You should use mapM
over IO only, when the list is short, or when there is really no way
around loading everything into memory.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] mapM is supralinear?

2011-09-07 Thread Ertugrul Soeylemez
Travis Erdman  wrote:

> The performance of mapM appears to be supralinear in the length of the
> list it is mapping on.  Does it need to be this way?  As a comparison,
> both mapM_ and map are linear in the length of the list.

It needs to be this way in most monads.  It's not a problem of mapM
itself, but of its definition in the particular monad.  In general it's
a bad idea to use mapM over IO.  For [] it will eat lots of memory
quickly and by its mere definition there is nothing you can do about
that.

mapM_ is linear, because it can throw away the results, so no
complicated accumulation occurs.  map is usually linear, because used
properly it will be optimized away leaving just a loop, which doesn't
produce any data structures in memory and is just run element by
element.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANN: Netwire 1.2.0

2011-09-06 Thread Ertugrul Soeylemez
Ertugrul Soeylemez  wrote:

> version 1.2.1 of netwire is out.

It's actually 1.2.2 now, because had forgotten something in the .cabal
file.


Greets
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/

-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


[Haskell-cafe] ANN: Netwire 1.2.0

2011-09-06 Thread Ertugrul Soeylemez
Hello there,

version 1.2.1 of netwire is out.  New features include:

  * Completely reworked event system.  Events are now solely based on
signal inhibition, which turns out to be much more convenient and
faster than AFRP's traditional approach using Maybe-wrapped values.

Now instead of checking for the presence of an event, you simply
assume that it happened.  If it didn't happen, then the signal is
inhibited and your wire is not run.  This makes your code much
simpler, because you get along almost entirely without switches.
Example displaying a discrete clock updated at intervals of half a
second:

system :: forall m. Monad m => Wire m () String
system =
proc _ -> printf "%8.2f" ^<< hold discreteClock -< ()

where
discreteClock :: Wire m () Double
discreteClock =
proc _ -> do
t <- time -< ()
repeatedly -< (0.5, t)

By using ArrowPlus or Alternative, you can handle the case, where
the event did not happen, listening for alternative events or simply
having a fallback.  By using the various wire combinators you can
hold, sample, keep or exhibit event values as shown above.

  * Lots and lots of Haddock documentation improvements.  Now the
inhibition and feedback behaviour of every builtin wire is
documented.

  * Apropos feedback:  Finally added an ArrowLoop instance, so you can
now have recursive values in your wires.  There is a catch though:
Right now wires which produce values used recursively must not
inhibit.  There is an inherent problem handling the inhibition case,
which you will observe as a pattern match error.

Right now I don't have a solution for this problem, but I'm working
on it.  However, it may well be that it simply cannot be solved with
my current internal wire representation.  This is the price to pay
for signal inhibition.

To prevent (or rather catch) inhibition you can use the 'exhibit' or
'event' combinators.

  * Many small performance improvements.  Simple signal networks go well
beyond 35000 frames per second on my mobile Intel i7 with 1.7 GHz
and their executables cost well less than 5 MiB RAM.  The
performance passes the 50k FPS mark on my i5 with 2.8 GHz at home.
This is more than a 10x speedup compared to my last benchmark on the
initial release of version 1.0.0

  * Removed some of variations of existing wires and replaced them by
wire combinators instead.  For example 'executeOnce' and
'executeEvery' are gone.  Instead you should use the normal
'execute' wire together with 'swallow', 'sample', 'hold' or other
combinators.

  * Changed the semantics of all wires to support feedback.  Now some
wires support feedback right away, while for others you need a
one-instant delay.  The feedback behaviour of all wires is
Haddock-documented, as noted.

Enjoy and please give me as much feedback as possible. =)


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] How to make callCC more dynamic

2011-08-25 Thread Ertugrul Soeylemez
bob zhang  wrote:

>   I was curious that we could bring really continuations into haskell,
> the traditional callCC brings a lot of unnecessary type restrictions

That's where the misconception lies.  The type parameter /is/ necessary
for delimited continuations in Haskell.  By the way, I don't see how
these continuations would be in any way not "real" or how the type
parameter places any "restrictions", unless of course you want dynamic
typing.

The only operations I can imagine, which really restrict the type
parameter, are the operation of aborting the entire computation and
manipulating the result of it:

abort:: a -> ContT a m a
mapContT :: (r -> r) -> ContT r m ()

You can have undelimited CPS without the type parameter, but then you
won't get any CPS effects.  As noted, you will just have an
IdentityT-like monad transformer, which can at best improve the
semantics of the underlying monad.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] haskell or lazy functional as procedure language

2011-08-25 Thread Ertugrul Soeylemez
Permjacov Evgeniy  wrote:

> Ok, I know, I want something strange. But consider situation, when one
> is starting a project and finds, that he need s
>
> 1) ACID relational storage
> 2) Power of good RDBMS system (postgresql for example)
> 3) Power of some very hight level language and compiled (haskell for
> example) for stored procedures
> 4) And all data processing MUST be performed inside RDBMS
> 5) And does not have enough money to by Oracle ore other commercial RDBMS.
>
> I already considered using ghc with postgresql. It could be very, very
> good pair, but ghc runtime cannot be re-initialized, and reqular
> way for stored procedures in postgresql is calling function from
> shared object (meaning, I have to shut down ghc runtime each time
> stored procedure ended).
>
> What other options do you see?

I'm using a Haskell + PostgreSQL combination a lot.  For access to the
database I mostly use the HDBC library.  In general much if not most of
my data processing is written in the database language PL/PgSQL, which
has a very low barrier and can really do most of what you need easily,
likely much more easily than an interface to an external PL could do.

However, in my case the Haskell application is still the main program.
You can exploit the full power of both without moving everything into
the database, and honestly I wouldn't do that, because it would make
things more complex.  I also believe it's not really possible without
writing a full-fledged Haskell extension for PostgreSQL, because just
running programs cannot do long term concurrency well, for example.

Rather I have the view that the database should do the data logic and
the data logic only.  But it should do it so well that you can easily
access the database from multiple programs without problems.  As soon as
that goal is reached (though you can use PostgreSQL rules to some
extent, in general you will want to write real procedures), there is
really little reason not to let the Haskell program be primary.

If by some policy you are forced to have the database primary, then you
are pretty lost with Haskell.  You should consider following A.M.'s
advice or just use one of the built-in PLs like Python.  As said, when
it comes to data logic, PL/PgSQL performs very well and can express many
things concisely, so in many cases you won't even need an external
language.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] How to make callCC more dynamic

2011-08-24 Thread Ertugrul Soeylemez
bob zhang  wrote:

> I thought the right type for ContT should be
> newtype ContT m a = ContT {runContT :: forall r. (a-> m r) -> m r}

No, that will effectively make it impossible to make use of CPS effects,
hence turning your ContT into an IdentityT-like monad transformer, which
can only change the semantics of the underlying monad.  More concretely
what you are implementing here is a codensity as you can find it in the
monad-ran package by Edward K.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Function composition in run-time?

2011-08-24 Thread Ertugrul Soeylemez
dokondr  wrote:

> This is a nice one, looks already like tiny DSL )
>
> I think I've got the main idea - enumerate in my program all function
> compositions in some data structure for Haskell to compile, and the
> associate these with parameter values in external file.

In Haskell you get a not-even-too-tiny DSL for free for composing
functions in arbitrary, dynamic ways.  Hint:  (a ->) is a monad and (->)
is an ArrowChoice and an ArrowApply.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


[Haskell-cafe] ANN: Netwire 1.1.0 and instinct 0.1.0

2011-08-22 Thread Ertugrul Soeylemez
Hello there,

today I have released one new library 'instinct' for neural networks as
well as a new revision of my AFRP library 'netwire', which comes along
with many new features, but also with largely incompatible changes.

Instinct is a library for neural networks, which currently features:

  * High performance,
  * arbitrary network models, as long as they don't loop,
  * reasonably compact memory representation,
  * backpropagation learning.

Netwire is an arrowized functional reactive programming library written
with networking applications in mind.  Changes include:

  * Inhibiting signals now contain a SomeException value,
  * the Wire type has been generalized over the underlying monad.

The second change brings up two new features:

  * Wires over arbitrary monads, hence
  * pure wires.

I appreciate constructive feedback.  Enjoy!


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Problem with types

2011-08-19 Thread Ertugrul Soeylemez
Anupam Jain  wrote:

> However, if I try to parameterise over the function 'f' it does not
> work!  -
>
> p f = (m1',m2') where
>   m1 = M ("1", ())
>   m2 = M ("2", True)
>   m1' = f m1
>   m2' = f m2
>
> It doesn't even typecheck, producing the error - "Couldn't match
> expected type 'Bool' with actual type '()'"
>
> Is there a particular reason for this? How can I define a function
> like 'p' within Haskell?

Try to write the type signature for 'p'.

And as a general advice:  Always write type signatures.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] why is Random in System?

2011-08-17 Thread Ertugrul Soeylemez
Ryan Newton  wrote:

> I'm the maintainer of random.  If people could decide on what the
> alternative name would be we could put it through the library proposal
> process.  It seems that one problem at this moment is the lack of a
> single, clear "right" answer.  Replacing one debatable not-quite-right
> choice with another may not be satisfying ;-).
>
> Also, what Thomas says is right.  The current implementation is SLOW
> and WEAK, which would not seem to make a good default implementation.
> The goal is to replace it with something better so that the default
> random package is strong in at least one dimension.  I think this is
> important because I imagine many people use the default package, for
> example because they don't want to scour hackage and try all the
> alternatives.
>
> My proposal for this has been to use AES based crypto-prng.  I think
> that is fast enough (i.e. faster than what's currently there), very
> strong, and splittable.  New Intel and AMD hardware has hardware
> support for AES which makes it even faster.  The intel-aes package
> provides this functionality, with and without hardware support.  But
> there's work left to do in terms of testing, making sure its cross
> platform, etc.  Anyone who's interested in helping (especially with
> Windows support) would be warmly welcomed!

Using a cryptographically strong random number generator here is
probably a very bad idea.  Two reasons:

Firstly while being faster than the current implementation an AES-based
implementation will still be considerably slower than the Mersenne
Twister algorithm.  This may or may not be true, if hardware AES support
is there, but don't just assume that everybody has AES instructions now.
For example I don't have them.

Secondly there is no standard requiring that the default random number
generator is cryptographically safe.  Changing this particular
implementation, which is the one most people use, to a CSPRNG will make
people take for granted that System.Random is safe to use in
security-related products, because it would be very convenient.  This
will render strong security products trivially weak, when compiled with
the wrong Haskell distribution, and you will find packages with
statements like:  "We assume that you use Ryan Newton's distribution of
the random package."

I would rather propose the Mersenne Twister as the default random number
generator.  You could add AES as a secondary generator for people
requiring cryptographic strength, but then do it properly, i.e. impure,
because most people, when reading about a PRNG with "AES" anywhere in
its name, will just assume that it's a CSPRNG.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] why is Random in System?

2011-08-17 Thread Ertugrul Soeylemez
Brandon Allbery  wrote:

> > > I've noticed there's a convention to put modules having to deal
> > > with randomness into System.Random.  I thought System was for OS
> > > interaction?  Granted getting a random seed usually means going to
> > > the OS, but isn't the rest of it, like generating random
> > > sequences, distributions, selecting based on probability,
> > > shuffling, etc. all non-OS related algorithms?
> >
> > System definitely does seem like an odd choice.  In most cases the
> > only interaction any PRNG, even when accessed via the FFI, has with
> > the "system" is - as you say - to get an initial seed value for a
> > global instance.
>
> I'd be tempted to guess that the whole reason it's under System is the
> IO component.

That's not really valid, is it?  After all the new 'time' package is
also stationed under the Data tree, and it has a similarly large IO
component.  I have to say, it seems very intuitive to me to look for it
under Data, even though I'm not sure why.  Probably I'm just used to it.
Time has a strong connection to the operating system and the hardware,
so it could just as well go into the System tree.  For
(non-cryptographic) randomness however we are dealing with numerical
data, for which the connection to the system is mere convenience, so I
wouldn't mind finding it under Data at all.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


[Haskell-cafe] ANN: Netwire AFRP library

2011-08-07 Thread Ertugrul Soeylemez
Hi there,

after a few weeks of development time, I have released the first
official version of my arrowized FRP library called Netwire:

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

I have written it with networking applications in mind, but it is a
general purpose library, so it can be used in all of the classic fields
like gaming, animation, user interfaces and others.

Its basic idea is the same as in Yampa, but its internal structure is
much simpler and hence it's easier to extend.  Also like in most of my
libraries I have specifically decided to expose the internals, so you
can extend Netwire without having to fork.

Features not found in Yampa/Animas:

  * switching by ArrowChoice,
  * suspended signal transformers,
  * signal inhibition,
  * combination through ArrowZero and ArrowPlus,
  * impure signal transformers.

There exists a wiki page, which should give you a quickstart:

http://haskell.org/haskellwiki/Netwire

I would be grateful for any constructive feedback.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


[Haskell-cafe] Animas/Yampa: ArrowChoice?

2011-07-14 Thread Ertugrul Soeylemez
Hello all,

I really like the way Animas (fork of Yampa) represents reactive
systems, and I would love to write some of my simulations using it.
Unfortunately most of what I want to do requires dynamic systems, which
can be boiled down to me believing to need an ArrowChoice instance for
the SF arrow, because I have to choose between different signal paths
depending on the input signal or events.

Animas appears to be only suitable for robot-like systems with specific,
predefined actors.

Is there anything I can do about it?  Is it difficult to write the
ArrowChoice instance?  Or is there a different solution, which I
overlooked?


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Paid work available in functional web programming

2011-07-13 Thread Ertugrul Soeylemez
Christopher Done  wrote:

> > I write to mention briefly that I'm looking for people interested in
> > writing Ur/Web programs for pay.  Ur/Web is a DSL for building
> > modern web applications, and I believe it is truly a secret weapon
> > for that domain, and one that should appeal to many Haskell fans.  I
> > have one customer now for whom I'm leading a project to develop a
> > particular web application, and I'd like to have more.  The current
> > project would benefit from more programming help, and I would also
> > like to develop a network of people interested in future projects.
>
> I would like to see a real application in Ur/Web. There are many
> simple examples. I don't and wouldn't want to develop like that,
> writing raw HTML and SQL seems going backwards despite the incredible
> advances in consistency and correctness that Ur/Web offers.

I agree about the HTML part, but not so much about the SQL part.
Personally I went back from all the nice abstractions to writing raw
SQL, because I realized that this is the only way to really exploit the
power of my database system (PostgreSQL) [1].

[1] http://coder.mx/journal/yesod-persistent-vs-sql


> I also find it hard to understand the type system in a non-superficial
> level because the related paper was very hard to grok. I tried to get
> it running a while ago and could not get it to compile. I would also
> like to see how it handles non-web stuff as inevitably IME web
> applications involve more than merely reading and writing to a
> database.
>
> I like the idea, please keep us posted about it.

I like the continuation part about it.  If there were a web framework in
Haskell similar to the continuation-based framework in Racket or Ur/Web,
I would most certainly switch to it (from Yesod), given that it's mature
enough.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] compare iteratee with python's yield

2011-07-01 Thread Ertugrul Soeylemez
yi huang  wrote:

> I just read several tutorials on iteratee, i find that iteratee is
> similar to python's generator, both allow streamlined data
> processing. For example, i can implement enumFile and printChunks in
> python like this:
>
> EOF = None
> def enum_file(bufsize, filename):
> with open(filename) as input:
> while True:
> data = input.read(bufsize)
> if not data:
> break
> yield data
> yield EOF
>
> def print_chunks(print_empty, generator):
> for chunk in generator:
> if chunk==EOF:
> print 'EOF'
> return
> if len(chunk)==0 and not print_empty:
> continue
> print chunk
>
> print_chunks(True, enum_file(2, "data"))
>
> But i find iteratee far more complicated than python's generator, is
> that because iteratee can do something python's generator can't, or i
> simply need to be more familar with functional programming style.

I don't know Python very well, but I suspect that its generators are
really a sort of coroutines.  Iteratees are also coroutines, but their
architecture is quite different.

The difference is that conceptually an iteratee does not know about its
input.  In Python the generator stops to wait for the iterator to
request more input:  The consumer talks to the producer.  This control
flow is turned inside out in iteratees, where the iteratee stops to wait
for the enumerator to provide more input.  The producer talks to the
consumer in iteratees.  This is a conceptual difference, so what's the
advantage?

The main advantage of iteratees, compared to generators, can be seen in
a statically typed language such as Haskell.  Let's say that instead of
printing the input lines your consumer would instead just calculate its
length and return it.  Let's call this consumer 'length'.  If you would
translate generators to Haskell, you would find that your 'length'
consumer would suddenly include a MonadIO constraint, even though it
doesn't need it.

With iteratees' inversion of control only the part which needs the
MonadIO constraint really has it.  An enumerator is really a function
from an iteratee to an iteratee.  It converts an arbitrary iteratee to
an iteratee with additional input, adding the constraints necessary to
fulfill this task.  While with the generator concept you apply a
producer to a consumer, with iteratees you apply a consumer to an
producer.

Hope that helps.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] what if two package contains same module?

2011-06-30 Thread Ertugrul Soeylemez
吴兴博  wrote:

> it seems that cabal install different into different folders.  if two
> package contains same module name, can they all exist?  since cabal
> have no "remvoe" or "uninstall". how can I hide some packages?

Alternatively for small programs for which you don't use a Cabal file
you can use the PackageImports extension (-XPackageImports) and import
modules from specific packages.  For example both the 'pool' and the
'resource-pool' packages provide a Data.Pool module.  You can choose to
import the one from 'resource-pool' using this:

import "resource-pool" Data.Pool


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Enumerators, Enumeratees and Iterators

2011-06-28 Thread Ertugrul Soeylemez
Sævar Berg  wrote:

> The first question is, I think, to be solved with enumeratees but I can't
> really grok how.
> Let's say I have an iteratee that consumes all input. Is it possible to
> implement an enumeratee or something else to stick between the enumerator
> and the iteratee to basically modify the input to the iteratee to only be a
> part of the input?

Yes, this is an enumeratee.  An enumeratee is neither a data producder
nor a consumer.  It is an iteratee, which feeds another iteratee with
input based on its own input, so it acts like a kind of map operation.


> enumFile "someFile" && printFileLines -- prints file with prepended line
> numbers
> enumFile "someFile" ?? onlyGet10Lines && printFileLines -- print only 10
> lines

In fact an enumeratee can split the input stream into lines.  Another
one can zip the stream with a list.  A final one can take 10 lines from
the stream.  The code would look like this (in the 'enumerator'
package):

enumFile "myFile.txt" $$
lines =$
zipWithList [1..] =$
take 10 =$
printLines

where

lines   :: Monad m => Enumeratee Text Text m b
zipWithList :: Monad m => [a'] -> Enumeratee a (a, a') m b
take:: Monad m => Int -> Enumeratee a a m b
printLines  :: MonadIO m => Iteratee (Int, Text) m ()

This is how I would do it.


> The second question could actually have an application in the server
> I'm writing. I was wondering if it was possible to write
> iteratees/enumerators that would only generate/consume when a certain
> something was the next chunk to be processed?

You want concurrent iteratees here.  As far as I know in the
'enumerator' package there is no builtin way to do it (you may be
luckier in the 'iteratee' package, but I don't know).  However, I think
it should be possible to write a 'concurrent' function, if the iteratees
in question all have the same input type:

concurrent :: Monad m => [Step a m b] -> Iteratee a m [b]

A version, which doesn't collect the results is probably much easier to
write:

concurrent_ :: Monad m => [Step a m b] -> Iteratee a m ()


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] toSql and fromSql, for Algebraic Data Type

2011-06-27 Thread Ertugrul Soeylemez
Tom Murphy  wrote:

>  The title is self-explanatory. I'd like to store information from
> an algebraic data type in an SQL database, but the type signature of
> toSql (toSql
>   :: Data.Convertible.Base.Convertible a SqlValue => a -> SqlValue)
> doesn't make sense to me.
>  How is this done (how do I make an instance of a typeclass like that?)

My answer is:  This is tiring, redundant work.  Honestly, don't do it,
if you can avoid it.  Rather find a type with a ready-made Convertible
instance, which can represent the values of your type and convert to and
from that one instead.

By the way, if your type is just an enumeration of nullary constructors,
note that most database systems support efficient 'ENUM' types.  For
example in PostgreSQL you can do this:

CREATE TYPE server_status AS ENUM(
'online',
'offline',
'not available');

According to the documentation columns of type "server_status" will use
a compact, efficient 32 bit integer representation, but on the interface
you can work with regular strings, so you can just convert your
algebraic type to and from strings.

Even better, if you don't mind being tied to the particular database
system, you can abstract away such types by using stored procedures.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://coder.mx/
http://ertes.de/



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


Re: [Haskell-cafe] Data.Enumerator question

2011-06-23 Thread Ertugrul Soeylemez
David Place  wrote:

> I can see that an Enumeratee can produce fewer outputs than it
> receives as inputs.  For example, this GroupBy Enumeratee.
>
> > http://hpaste.org/47916
>
> Can an Enumeratee produce more outputs than inputs?  For instance,
> take a Data.Text and send each character to the inner Iteratee
> individually.  I feels this can be done, but don't see how to do it.

Yes.  Just look at the definition of Enumeratee.  It is an iteratee
function, which takes an iteratee (by its Step value) and produces
another iteratee, possibly with additional input.  It can pass the
iteratee any input it wants, possibly dependent on the outer input
stream.

In other words, the enumeratee is an iteratee, which consumes an input
stream and derives from it the input stream of another iteratee.  It is
well possible to simply ignore the outer input stream (in which case you
have about the same functionality as a regular enumerator).


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


[Haskell-cafe] pool: Why doesn't it block?

2011-06-12 Thread Ertugrul Soeylemez
Hello Michael, hello fellow haskellers,

there is something, which has bothered me for quite a while, but now it
has become a serious problem for me, because I see it as a bug, and
there is no elegant way to work around it.

I wonder if it's the right semantics for Data.Pool to simply fail with
an exception, if the pool is exhausted.  It would be much more
appropriate, if it would just block, until a resource becomes available.
Otherwise it's just /safe/ for multi-threading, but not really /useful/
for it.

I noticed this when I launched 512 worker threads, but my pool had only
16 database connections.  I need the pool to block, until a resource is
available.

It's also common that my Yesod site just returns an internal server
error, when the pool is exhausted, so you can only handle as many
connections successfully as there are database connections.  I would
expect Yesod to wait for a connection to become available instead of
simply blowing the request.

Blocking should at least be an option and be somehow reachable from
Yesod/persistent.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


[Haskell-cafe] Yesod: How safe are forms?

2011-06-11 Thread Ertugrul Soeylemez
Hello fellow haskellers,

how far does Yesod.Form protect you from invalid input?  I'm
particularly interested in what happens, when you submit invalid data to
select fields or radio groups.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Proposal: remove "Stability" from haddock documentation on hackage

2011-06-08 Thread Ertugrul Soeylemez
Chris Smith  wrote:

> I got asked a question today about why Control.Applicative is labeled
> as "experimental" on Hackage.  Perhaps that field is something of a
> failed experiment, and it remaining there is likely to confuse people.
>
> Just a thought... not sure of the best place to mention it.

I don't think that's a proper rationale to remove the feature, because
every feature can be used in a wrong way.  It appears to be quite
natural to me that people forget to update their module headers, but
there are also programmers, who manage their comments very responsibly,
including the module header.

Personally I used to use the feature, but at some point I abandoned it,
because although I always update the comments associated with
definitions, I tend to forget the module's head comment.  Also since my
modules are mostly very related, the stability is a package property for
me rather than a module property.

If you are serious about removing failed experiments, there are more
important places to get started at. ;)


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] *GROUP HUG*

2011-06-04 Thread Ertugrul Soeylemez
Yves Parès  wrote:

> From from what I see here, Haskell at work seems to target web
> development.  I should try this soon...

That's one of the main use cases for Haskell in real world projects (in
my opinion).  However, I also use Haskell for network servers.


> What is everyone using? Yesod?

Personally I use Yesod, but that's mainly a matter of taste.  I think,
the other big framework is Happstack.  There is also a framework called
Salvia.  It comes with a very nice AJAX wiki/blog demo.  You should
check it out.

The reason why I use Yesod is twofold:  Firstly and mainly because I'm
used to it.  Secondly because I didn't like Happstack that much.  I'm
amazed by how you can get very productive with very little code, but
that reasoning probably also holds for the other frameworks.

One important note about Yesod, however:  To really exploit it to its
full power you should understand very well and be willing to use some of
the Haskell extensions, most notably type families, quasiquoting and
Template Haskell.  Many people view this as a downside.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] *GROUP HUG*

2011-06-02 Thread Ertugrul Soeylemez
Yves Parès  wrote:

> > I cannot agree with this for practical reasons.  I'm using Haskell
> > for real world commercial applications, and I'm very productive with
> > it.
>
> I wish so much I could say that... Out of curiosity, what are you
> using Haskell for?

I use the Yesod web framework for web development and a combination of
many libraries for network servers.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] *GROUP HUG*

2011-06-02 Thread Ertugrul Soeylemez
Ivan Tarasov  wrote:

> myFoldr :: (a -> b -> b) -> b -> [a] -> b
> myFoldr f z xs = foldl' (\s x v -> s (x `f` v)) id xs $ z

That's not foldr.  It's a function similar to foldr in Haskell and equal
to foldr in a different language, which lacks bottom.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] *GROUP HUG*

2011-06-02 Thread Ertugrul Soeylemez
"Alberto G. Corona "  wrote:

> Haskell is an academic asset as well as a fun asset.

I cannot agree with this for practical reasons.  I'm using Haskell for
real world commercial applications, and I'm very productive with it.

There is however a variation of this statement, with which I could
agree, namely:  Learning Haskell will pay off much less than learning
PHP, if your goal is to find a job.  It takes a lot longer and there are
a lot less companies in need of Haskell programmers.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] [Maybe Int] sans Nothings

2011-05-23 Thread Ertugrul Soeylemez
Gregory Crosswhite  wrote:

> Or even better,
>
>  filter isJust

To make it worse again the original function can be generalized in a few
ways.  Here is a generalization from the inner Maybe type:

import Data.Foldable as F

catFoldables :: Foldable t => [t a] -> [a]
catFoldables = concatMap F.toList

Here is a generalization from the outer list type:

joinMaybes :: (Alternative m, Monad m) => m (Maybe a) -> m a
joinMaybes = (>>= maybe empty pure)

And finally the generalization from everything:

import Data.Foldable as F

joinFoldables :: (Alternative m, Foldable t, Monad m) => m (t a) -> m a
joinFoldables = (>>= F.foldr (\x _ -> pure x) empty)

The final function looks a bit scary, but is actually surprisingly easy
to understand, once you realize that 'foldr' is just a generalization of
the 'maybe' function.  The structure of Maybe is a list structure with
at most one element after all.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/

-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Random thoughts about typeclasses

2011-05-16 Thread Ertugrul Soeylemez
Robert Clausecker  wrote:

> I found out, that GHC implements typeclasses as an extra argument, a
> record that stores all functions of the typeclass. So I was wondering,
> is there a way (apart from using newtype) to pass a custom record as
> the typeclass record, to modify the behavior of the typeclass? I
> thought about something like this:
>
> f :: Show a => [a] -> String
> f = (>>= show)
>
> -- So, f becomes something like this?
> __f :: ClassShow a -> [a] -> String
> __f (ClassShow __show) x = x >>= __show
>
> -- And if I call the function, it looks somewhat like this:
> g :: [Int] -> String
> g = f
>
> __g = __f instanceShowInt
>
> -- But is it possible to do something like this?
> g2 = __f (ClassShow (return . fromEnum))
>
> Tis is just a random thought, some compilers like JHC implement them
> by another way. But would this theoretically be possible?

If I understand you right, you would like to decide about the instance
at run-time instead of at compile-time.  This is actually possible in
practice.  A suitable search term is "implicit configurations", in
particular "reification".


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANNOUNCE: iterIO-0.1 - iteratee-based IO with pipe operators

2011-05-06 Thread Ertugrul Soeylemez
David Mazieres  wrote:

> Hi, everyone.  I'm pleased to announce the release of a new iteratee
> implementation, iterIO:
>
>   http://hackage.haskell.org/package/iterIO
>
> IterIO is an attempt to make iteratees easier to use through an
> interface based on pipeline stages reminiscent of Unix command
> pipelines.  Particularly if you've looked at iteratees before and been
> intimidated, please have a look at iterIO to see if it makes them more
> accessible.
>
> [...]
>
> Please enjoy.  I'd love to hear feedback.

Thanks a lot, David.  This looks like really good work.  I'm using the
'enumerator' package, and looking at the types your library seems to use
a similar, but more complicated representation.  Is there any particular
reason, why you didn't base your library on an existing iteratee package
like 'enumerator'?


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Python is lazier than Haskell

2011-04-29 Thread Ertugrul Soeylemez
Chris Smith  wrote:

> > > Sometimes I wish for a -fphp flag that would turn some type errors
> > > into warnings. Example:
> > >
> > > v.hs:8:6:
> > > Couldn't match expected type `[a]' against inferred type `()'
> > > In the first argument of `a', namely `y'
> > > In the expression: a y
> > > In the definition of `c': c = a y
> > >
> > > GHC could substitute 'y = error "Couldn't match expected type
> > > `[a]' against inferred type `()'"' and compile anyway.
> > >
> > > Would that bring Haskell closer to Python?
> >
> > It would make people abuse that feature.  I don't want it.
>
> I do, particularly in GHCi.  I don't mind if Haskell refuses to build
> a binary, but having to comment out coded in order to load bits in
> GHCi is definitely a pain.

I wonder why I don't have to do that.  You may be thinking in a
different language.  With the semantics of Haskell also comes a certain
programming style, I think.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Python is lazier than Haskell

2011-04-28 Thread Ertugrul Soeylemez
Gracjan Polak  wrote:

> Ketil Malde  malde.org> writes:
>
> > In Haskell, I often need to add stubs of "undefined" in order to do
> > this.  I don't mind, since it is often very useful to say
> > *something* about the particular piece - e.g. I add the type
> > signature, establishing the shape of the missing piece without
> > bothering with the actual implementation just yet.
>
> Seconded.

I don't see any problem with this.  Although I usually have a bottom-up
approach, so I don't do this too often, it doesn't hurt, when I have to.


> Sometimes I wish for a -fphp flag that would turn some type errors
> into warnings. Example:
>
> v.hs:8:6:
> Couldn't match expected type `[a]' against inferred type `()'
> In the first argument of `a', namely `y'
> In the expression: a y
> In the definition of `c': c = a y
>
> GHC could substitute 'y = error "Couldn't match expected type `[a]'
> against inferred type `()'"' and compile anyway.
>
> Would that bring Haskell closer to Python?

It would make people abuse that feature.  I don't want it.  Haskell is
so difficult to abuse compared to other languages, and I'd like to keep
it that way.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] There is no null; Maybe/Option types

2011-04-26 Thread Ertugrul Soeylemez
wren ng thornton  wrote:

> But the greatest thing about Maybe is that you don't *have* to write
> code in monadic style. Because Maybe makes explicit the null-pointer
> shenanigans in other languages, you can simply unwrap the Maybe and
> pass around the raw value instead of letting Nothing permeate your
> whole program. Spending all your time in the Maybe monad is just as
> bad as spending all your time in the IO monad.

Unless you're saying that I'm one of the worst Haskell programmers in
the world, you are totally wrong.  Monads are an abstraction for
convenience and beauty in expression, not for encapsulating bad habits.
Particularly there is nothing wrong with writing 90% of your code in
monadic style, which is what I do, often combining three or more monads.

And even if I don't use Maybe in monadic style, I often use combinators
like 'maybe'.  Monadic style to avoid explicit wrapping, and combinators
to avoid explicit unwrapping.

What exactly is wrong with that?  Why would you /not/ use (>=>) to
calculate the fourth root from a monadic square root function?

  fourthRoot :: (Alternative f, Integral i, Monad f) => i -> f i
  fourthRoot = mSqrt >=> mSqrt


> Purity begets clarity!

All Haskell code is pure (in the sense of referential transparency),
including monadic code, even in the IO monad.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] select(2) or poll(2)-like function?

2011-04-18 Thread Ertugrul Soeylemez
Don Stewart  wrote:

> Redirecting to haskell-cafe@, where this kind of long discussion belongs.

Answering to Mike Meyer here, because it has been requested multiple
times that we move the discussion to the cafe.

What you described about Eiffel didn't sound very different from what
Haskell does, but in Haskell the OOP part is missing.  You can very well
pass MVars as arguments to a concurrent thread.  This is the usual way
to tell a thread to do something and wait for its answer.  Of course you
don't have to wait right away.  You can command multiple threads to do
something and then collect the answers pretty straightforwardly both
with little programming and with little execution overhead.

However, as STM gains more popularity you generally don't use the old
fashioned command/wait concept.  You would rather have a certain number
of threads running all the time and communicating through transactions
in variables.  Threads with shorter lifetimes (for example for client
connections) would not know about the other threads.  They just know
about the variables they need to use.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Stateful iteratees

2011-04-12 Thread Ertugrul Soeylemez
Maciej Marcin Piechotka  wrote:

> > Does someone know a cleaner, more elegant solution?  Encapsulating the
> > state in the iteratee's input type is not an option.
>
> The first thing that come to my mind.
>
> runWithState :: Iteratee a (StateT s m) b -> s -> Iteratee a m (b, s)
> runWithState i s = do
> let onDone v st = return (Right (v, st))
> onCont c err = return (Left (c, err))
> (i', s') <- runStateT (runIter i onDone onCont) s
> case i' of
>   Left (c, err) -> icont (\str -> runWithState (c str) s') err
>   Right (v, st) -> idone (v, s') st
>
> I believe it is equivalent to:
>
> runWithState :: Iteratee a (StateT s m) b -> s -> Iteratee a m (b, s)
> runWithState i s = do
> let onDone v st = do
> s' <- get
> return (idone (v, s') st)
> onCont c err = do
> s' <- get
> return (icont (\str -> runWithState (c str) s') err)
> joinIM $ evalStateT (runIter i onDone onCont) s

Thanks for the code.  It might come in handy, but for the current
implementation I decided not to use this approach, but instead to
generalize over 'm', which gives me better composability, for example:

  MailMonad m => Iteratee SmtpResponse m ()

Library users can write their own monads and make them instances of
MailMonad, which is very easy, because there is only one function to
implement.  This seems to solve my original problem.


> I haven't tested but it compiles so it should work.

I loved that statement -- specifically because it's not far-fetched in
Haskell.  You wouldn't dare to write anything like that in any of the
more commonly used languages. =)


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Stateful iteratees

2011-04-07 Thread Ertugrul Soeylemez
Gregory Collins  wrote:

> On Thu, Apr 7, 2011 at 7:35 PM, Ertugrul Soeylemez  wrote:
>
> > > Why can't you use #1 and do this when you call "run_"?
> >
> > Because that runs the iteratee and leaves me with a StateT.  Even
> > though I use a CPS-based StateT, I doubt that it can be converted
> > back to Iteratee easily.
> >
> > With the first variant, I would need a function like this:
> >
> >    runMyApp :: Iteratee a (StateT MyConfig m) b -> Iteratee a m b
>
> Let me rephrase my question: why do you need a function like this?

Because I have multiple, independent libraries, which use a stateful
iteratee.  They work perfectly well, as long as you don't try to combine
them.  I have found a solution now, which seems to solve the problems.
I have described it in my last post.


> Anyways, something like this is definitely doable (using enumerator
> formulation, sorry), but your type needs to be this:
>
> runStateIteratee :: Monad m => Iteratee a (StateT s m) r -> s ->
> Iteratee a m (r, s)

Well, yes, but that's only part of the problem.  After doing this, I
need to put the iteratee on top of another monad transformer, while
remembering the state to (again) change the underlying state type.  All
in all it would become very complicated.  The solution I'm working on
seems to solve this more nicely and keeps the iteratees clean.

But it's good to know that such a transformation is possible.  It may
help out later.  Thanks.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Stateful iteratees

2011-04-07 Thread Ertugrul Soeylemez
Gregory Collins  wrote:

> > I'm trying to solve a very practical problem:  I need a stateful
> > iteratee monad transformer.  Explicit state passing is very
> > inconvenient and would destroy the elegance of my library.
> >
> > There are two approaches to this:
> >
> >   1. type MyT a m = Iteratee a (StateT MyConfig m)
> >   2. type MyT a m = StateT MyConfig (Iteratee a m)
> >
> > Both work well except in two very specific corner cases:
> >
> >   - I need to convert the transformer to 'Iteratee a m', i.e. remove
> > the state layer.  This is obviously trivial with the second
> > variant, but seems very difficult with the first one, if it's
> > possible at all.
>
> Why can't you use #1 and do this when you call "run_"?

Because that runs the iteratee and leaves me with a StateT.  Even though
I use a CPS-based StateT, I doubt that it can be converted back to
Iteratee easily.

With the first variant, I would need a function like this:

runMyApp :: Iteratee a (StateT MyConfig m) b -> Iteratee a m b

I think, this function is impossible to write.  The reason behind this
requirement is that I have multiple monad transformers of this kind,
each in different libraries, each with different state types, and I need
to compose them.

But I have another idea in mind.  I could do the following instead:

-- First library.
class Monad m => OneStateMonad m where
mapOneConfig :: (OneConfig -> OneConfig) -> m OneConfig

oneComp :: OneStateMonad m => Iteratee Input m Output

-- Second library.
class TwoStateMonad m where
mapTwoConfig :: (TwoConfig -> TwoConfig) -> m TwoConfig

twoComp :: TwoStateMonad m => Iteratee Input m Output

Then the user of the library has to build the monad transformer stack by
themselves, like this:

instance Monad m => OneStateMonad (StateT (OneConfig, TwoConfig) m)
instance Monad m => TwoStateMonad (StateT (OneConfig, TwoConfig) m)

appComp :: Monad m =>
   Iteratee Input (StateT (OneConfig, TwoConfig) m) Output

That might work, but it seems to be cumbersome.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


[Haskell-cafe] Stateful iteratees

2011-04-07 Thread Ertugrul Soeylemez
Hello fellow Haskellers,

I'm trying to solve a very practical problem:  I need a stateful
iteratee monad transformer.  Explicit state passing is very inconvenient
and would destroy the elegance of my library.

There are two approaches to this:

  1. type MyT a m = Iteratee a (StateT MyConfig m)
  2. type MyT a m = StateT MyConfig (Iteratee a m)

Both work well except in two very specific corner cases:

  - I need to convert the transformer to 'Iteratee a m', i.e. remove the
state layer.  This is obviously trivial with the second variant, but
seems very difficult with the first one, if it's possible at all.

  - I need to use control structures of Iteratee like catchError.  This
is obviously trivial with the first variant, but very inconvenient
with the second, because I would need to reinvent many wheels.

Does someone know a cleaner, more elegant solution?  Encapsulating the
state in the iteratee's input type is not an option.

Many thanks in advance.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] 'Progress bar' enumeratee

2011-04-06 Thread Ertugrul Soeylemez
"David Hotham"  wrote:

> The desired behaviour (certainly my desired behaviour, but I think
> also the most useful behaviour generally) is that the enumeratee
> passes n bytes to its iteratee, prints a dot, and repeats.
>
> Given that, printing the dots all in one bunch after passing bytes to
> the iteratee isn't any improvement over printing the dots all in one
> bunch before passing them to the iteratee.
>
> I think that mostly I want it the way that I want it because that's
> the bit that I struggled most over and I'm now reluctant to give it
> up!  However this might actually make a useful difference to behaviour
> in the case of an iteratee that did very expensive processing, or that
> itself performed IO.  In such cases, my behaviour could be expected to
> give a more accurate indication of how far through processing we'd
> actually got.

If you're talking about my code, you must have misunderstood something.
It does not print the dots all in one bunch, but prints them as input is
requested from the enumerator.  The last version I posted prints the
dots after the iteratee has consumed the input.  That difference is
noticable, when your iteratee does complex computations before it goes
back to the Continue state.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] 'Progress bar' enumeratee

2011-04-06 Thread Ertugrul Soeylemez
As a side note, even though GHC seems to handle this properly, I would
force the value of 'i' before passing data to the continuation.
Otherwise a less smart compiler may eat memory.  I believe, it can only
eat memory proportional to 'n', but nevertheless real constant space is
better:

seq i $ k ch >>== (\step -> printDots >> loop i step)


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] 'Progress bar' enumeratee

2011-04-06 Thread Ertugrul Soeylemez
"David Hotham"  wrote:

> I did have a version along those lines at some point, but I felt it
> was cheating rather to print the dots not at the correct point in the
> stream.
>
> Perhaps I've over-complicated for the sake of the learning experience,
> but I do like to have a version that passes on the correct number of
> bytes, then prints the ".", and then continues.

Well, then just do the printing after calling the continuation:

dotsAt :: forall b m. MonadPeelIO m => Int ->
  Enumeratee ByteString ByteString m b
dotsAt n =
loop 0

where
loop :: Int -> Enumeratee ByteString ByteString m b
loop i' step@(Continue k) =
continue go

where
go :: Stream ByteString ->
  Iteratee ByteString m (Step ByteString m b)
go EOF = return step
go ch@(Chunks strs) = do
let (numDots, i) = divMod (i' + sum (L.map BC.length strs)) n
printDots = tryIO $ BC.putStr (BC.replicate numDots '.') >>
hFlush stdout
k ch >>== (\step -> printDots >> loop i step)
loop i' step = return step

By the way, after trying out the code, I found that you should use
hFlush after printing.  Otherwise you may see the dots delayed.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] 'Progress bar' enumeratee

2011-04-06 Thread Ertugrul Soeylemez
"David Hotham"  wrote:

> I've spent some time over the last couple of days trying to write an
> enumeratee that prints a "." every n bytes (with obvious intended use
> as a progress tracker).  Seems like it oughtn't be hard, but it has
> been a steep learning curve...
>
> I have come up with something that seems to do the job but I don't
> know that I'm completely happy with it (or even that I completely
> understand it, to be honest).
>
> If anyone more expert would be kind enough either to reassure me that
> I'm doing it right or - more likely - to offer improvements /
> suggestions on what obvious simplifications I have overlooked, I'd be
> grateful.

I think that using lazy bytestrings does not have any advantage here,
since the enumerator creates the strict bytestrings at some point, then
your enumeratee converts them into lazy ones just for counting.  Just
use the straightforward approach:  Take the chunks and count the bytes
like here:

{-# LANGUAGE ScopedTypeVariables #-}

dotsAt :: forall b m. MonadPeelIO m =>
  Int -> Enumeratee ByteString ByteString m b
dotsAt n =
loop 0

where
loop :: Int -> Enumeratee ByteString ByteString m b
loop i' step@(Continue k) =
continue go

where
go :: Stream ByteString ->
  Iteratee ByteString m (Step ByteString m b)
go EOF = return step
go ch@(Chunks strs) = do
let (numDots, i) = divMod (i' + sum (L.map BC.length strs)) n
tryIO $ BC.putStr (BC.replicate numDots '.')
k ch >>== loop i
loop i' step = return step

I think, this is about the most straightforward and also the fastest
approach.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


[Haskell-cafe] Ann: contstuff, dnscache, ihttp, ismtp, netlines, yesod-tableview

2011-04-03 Thread Ertugrul Soeylemez
Hello fellow Haskellers,

(once again posted to the cafe, because the Haskell mailing list rejects
my mails.)

I have released quite a few libraries over time on Hackage.  I feel they
are stable enough now to announce them here.

  * contstuff: Fast and flexible monad transformers based on the CPS
concept.  Mainly it helps getting rid of large transformer stacks,
because it unifies some monad transformers (like StateT and ContT),
and it is also faster than the naive approach.

This library is comparable to a combination of the transformers
package with Edward Kmett's monad-ran package, but without hiding
the CPS transformation.  In early benchmarks ChoiceT turned out to
be twice as fast as normal Haskell lists, and it is also a proper
list monad transformer.

Finally in the Control.ContStuff.Classes module you find lots of
useful utility classes, which seem to be unique to contstuff.

  * dnscache: Handy DNS caching library.  This library automatically
manages a set of resolver threads for you, which share a reply
cache.  This allows very fast mass-resolution.

The library also comes with a handy command line utility called
'massdns' for quick resolution of even very large lists of entities.
Call massdns without arguments to get usage help.

  * ihttp: This is an HTTP library based on enumerators giving you
maximum flexibility and control over the connection.  Using proper
iteratees you can simply implement e.g. proxy clients (my main use
case), but also HTTP servers.  Using proper enumeratees you can also
encapsulate the connection in an SSL/TLS layer, but unfortunately
there doesn't seem to be such an SSL/TLS implementation yet.

  * ismtp: This is an advanced ESMTP library, which allows you to
structure your sessions as you like.  It also features an automated
resolver for MX records using the dnscache library.  Right now there
is support for most of the base functionalities of the protocol as
specified in RFC 821 (SMTP) and RFC 1425 (service extensions).

An update to RFC 2821 is planned, but is not necessary for practical
purposes.  The new RFC mainly removes some unneeded features and
unifies the two mentioned RFCs.

Right now there is no support for SMTL (SASL) authentication, but it
is planned for a near future release.  For the time being you can
implement your own iteratees for this purpose, if you depend on
authentication.

  * netlines: This is a library for writing implementations of
text-based protocols.  In particular it allows reading lines safely
from untrusted sources with a maximum length in constant space.

  * yesod-tableview: For web applications using Michael Snoyman's Yesod
web framework this library implements an easy to use table renderer
mainly for database records.  It is in an early stage of development
right now, but as the need arises, I will extend it.

To use the networking libraries, you should be familiar with John
Millikin's 'enumerator' package.  If you're not, I recommend studying
it, because it is a useful library for all kinds of stream processing
like network connections, files and concurrent channels.

All mentioned libraries have been tested extensively for correctness and
safety.  Especially the networking libraries have undergone a lot of
penetration testing.  However, I'm only one developer, so I would be
glad to hear about any vulnerabilities and other shortcomings you find.
Usually I have a very short response time to bugs in these libraries, so
please don't hesitate to contact me.  Feature requests are also welcome,
of course. =)

Please note that major version numbers specify interface versions in my
libraries.  In other words, a new major version of a package usually
means that the API has changed in a way, which is likely to break
dependent packages.

I would like to use this opportunity to thank a few people in particular
(alphabetically):

- Cale Gibbard,
- Edward Kmett,
- John Millikin,
- Bryan O'Sullivan and
- Michael Snoyman.

I appreciate your efforts both in libraries and support.  Many thanks,
guys!  Thanks also to the rest of the innovative and helpful Haskell
community.


Greets,
Ertugrul


-- 
Key-ID: E5DD8D11 "Ertugrul Soeylemez "
FPrint: 0F12 0912 DFC8 2FC5 E2B8  A23E 6BAC 998E CE40 2012
Keysrv: hkp://subkeys.pgp.net/


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] pool, persistent, persistent-sqlite: Space leak

2011-04-02 Thread Ertugrul Soeylemez
Michael Snoyman  wrote:

> Good catch, that was most definitely a space leak in pool. I've
> uploaded version 0.0.1.1, would you mind testing?

Great!  I will test it and report back, as soon as I'm at home.  Many
thanks.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] using IO monad in Iteratee

2011-04-02 Thread Ertugrul Soeylemez
Bas van Dijk  wrote:

> On 1 April 2011 21:59, Dmitry Olshansky  wrote:
> > Is it possible to change enumFile to using MonadIO class?
>
> No because it uses the control operation Control.Exception.finally ::
> IO a -> IO b -> IO a internally. You can't lift control operations
> with liftIO :: MonadIO m => IO a -> m a.
>
> However if you are able to define a MonadTransControl and
> MonadControlIO instance (from the monad-control package[1]) for
> Iteratee and use Control.Exception.Control.finally instead of the
> regular finally, you can use your MyMonad with the modified enumFile.

I don't think that's possible, because Iteratee is based on CPS.  I
think, so far nobody has come up with an instance definition for
monad-peel or monad-control for CPS-based monads like ContT or Iteratee.

However, it is easy to write an own handle enumerator, which uses
monad-peel or monad-control exception handling to convert errors to
iteratee exceptions.  On the other hand, as has been noted, there is
enumHandle, which does that by itself.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


[Haskell-cafe] pool, persistent, persistent-sqlite: Space leak

2011-03-30 Thread Ertugrul Soeylemez
Hello Michael, hello fellow Haskellers,

there seems to be a space leak in either 'pool', 'persistent' or
'persistent-sqlite'.  From the behaviour I suspect the bug to be in
'pool'.  When I run a transaction in an infinite loop, my program keeps
eating more and more memory, even if the transaction itself doesn't do
anything:

forever $ runSqlPool (return ()) pool

This doesn't happen for non-pooled connections, i.e. the following code
runs in constant space as expected:

forever $ runSqlConn (return ()) conn

Versions are pool-0.0.1, persistent-0.4.2, persistent-sqlite-0.4.0.  It
happens for both file and in-memory databases.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANNOUNCE: enumerator 0.4.8

2011-03-29 Thread Ertugrul Soeylemez
Antoine Latter  wrote:

> It looks like we can't quite fit Enumeratee into the Category
> typeclass (without newtypes, at least). That's a shame.

Yeah.  Intuitively it looks like iteratees and enumeratees are excellent
candidates for Category and even Arrow.  Unfortunately they can either
be monad transformers or arrows.  You can't mix without, as you said, a
newtype.  That's very unfortunate.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANNOUNCE: enumerator 0.4.8

2011-03-29 Thread Ertugrul Soeylemez
Hello John,

Sorry that I'm late.  And honestly one day for request submissions is a
bit narrow.

I have a request, too:  Right now it is difficult to compose
enumeratees.  An equivalent of (.) for enumeratees would be great.  So
instead of:

joinI $ e1 $$ joinI $ e2 $$ iter

one could write

let e = e1 .= e2 in e =$ iter

I would appreciate a 0.4.10 with such a composition operator.


Greets,
Ertugrul


John Millikin  wrote:

> Since the release, a couple people have sent in feature requests, so I'm 
> going to put out 0.4.9 in a day or so.
> 
> New features will be:
> 
> - tryIO: runs an IO computation, and converts any exceptions into 
> ``throwError`` calls (requested by Kazu Yamamoto)
> 
> - checkContinue: encapsulates a common pattern (loop (Continue k) = ...) 
> when defining enumerators
> 
> - mapAccum and mapAccum: sort of like map and mapM, except the step function 
> is stateful (requested by Long Huynh Huu)
> 
> Anyone else out there sitting on a request? Please send them in -- I am 
> always happy to receive them, even if they must be declined.
> 
> ---
> 
> Also, I would like to do a quick poll regarding operators.
> 
> 1. It has been requested that I add operator aliases for joinI and joinE.
> 
> 2. There have been complaints that the library defines too many operators 
> (currently, 5).
> 
> Do any existing enumerator users, or anyone for that matter, have an opinion 
> either way?
> 
> The proposed operators are:
> 
> --
> infixr 0 =$
> infixr 0 $=
> 
> (=$) :: Monad m => Enumeratee ao ai m b -> Iteratee ai m b -> Iteratee ao m 
> b
> enum =$ iter = joinI (enum $$ iter)
> 
> ($=) :: Monad m => Enumerator ao m (Step ai m b) -> Enumeratee ao ai m b -> 
> Enumerator ai m b
> ($=) = joinE
> --
> 
> 


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANNOUNCE: enumerator 0.4.8

2011-03-27 Thread Ertugrul Soeylemez
John Millikin  wrote:

> Good idea -- I've added an ``enumSocketTimed`` and ``iterSocketTimed``
> to the network-enumerator package at <
> http://hackage.haskell.org/package/network-enumerator
> >. ``enumSocketTimed`` is equivalent to your ``enumHandleTimeout``,
> but instead of Handle uses the more efficient Socket type.

For simple applications working with handles is much more convenient, so
I decided to implement a timed handle enumerator instead of a socket
enumerator.

Perhaps it would be a good idea to add your 'enumSocketTimed' and
'iterSocketTimed' to my netlines package, too.  Also I should add
'iterHandleTimeout'.


> For setting a global timeout on an entire session, it's better to wrap
> the ``run_`` call with ``System.Timeout.timeout`` -- this is more
> efficient than testing the time on every chunk, and does not require a
> specialised enumerator.

It may be more efficient, but I don't really like it.  I like robust
applications, and to me killing a thread is always a mistake, even if
the thread is kill-safe.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANNOUNCE: enumerator 0.4.8

2011-03-26 Thread Ertugrul Soeylemez
Hello John,

great stuff!  Many thanks.  I can't await the 0.5 release of your
library.  By the way, I believe that the 'enumHandleSession' and
'enumHandleTimeout' enumerators from the 'netlines' library really
belong into this one.  You will want to have timeout support, when
reading from a network handle.

Keep up the good work!


Greets,
Ertugrul


John Millikin  wrote:

> -
> Enumerators are an efficient, predictable, and safe alternative to
> lazy I/O. Discovered by Oleg Kiselyov, they allow large datasets to be
> processed in near–constant space by pure code. Although somewhat more
> complex to write, using enumerators instead of lazy I/O produces more
> correct programs.
> 
> http://hackage.haskell.org/package/enumerator
> http://john-millikin.com/software/enumerator/
> -
> 
> Hello -cafe,
> 
> It's been a while since the last point release of enumerator. This one
> is sufficiently large that I think folks might want to know about it,
> and since I try not to spam too many announcements, I'll give a quick
> rundown on major changes in other 0.4.x versions as well.
> 
> First, most of what I call "list analogues" -- enumerator-based
> versions of 'head', 'take', 'map', etc -- have been separated into
> three modules (Data.Enumerator.List, .Binary, and .Text) depending on
> what sorts of data they operate on. This separation has been an
> ongoing process throughout 0.4.x releases, and I think it's now
> complete. The old names in Data.Enumerator will continue to exist in
> 0.4.x versions, but will be removed in 0.5.
> 
> Second, Gregory Collins and Ertugrul Soeylemez found a space leak in
> Iteratee's (>>=), which could cause eventual space exhaustion in some
> circumstances. If you use enumerators to process very large or
> infinite streams, you probably want to upgrade to version 0.4.7 or
> higher.
> 
> Third, the source code PDF has seen some substantial improvement -- if
> you're interested in how the library is implemented, or have insomnia,
> read it at < http://john-millikin.com/software/enumerator/enumerator_0.4.8.pdf
> >
> 
> Finally, there is a known issue in the current encoding of iteratees
> -- if an iteratee yields extra data but never consumed anything, that
> iteratee will violate the monad law of associativity. Oleg has updated
> his implementations to fix this problem, but since it would break a
> *lot* of dependent libraries, I'm holding off until the vague future
> of version 0.5. Since iteratees that yield extra data they didn't
> consume are invalid anyway, I hope this problem will not cause too
> much inconvenience.
> 
> New features
> -
> 
> * Range-limited binary file enumeration (requested + initial patch by
> Bardur Arantsson).
> 
> * splitWhen , based on the "split" package <
> http://hackage.haskell.org/package/split >
> 
> * 0.4.6: Typeable instances for most types (requested by Michael Snoyman)
> 
> * 0.4.5: joinE , which simplifies enumerator/enumeratee composition
> (requested by Michael Snoyman)
> 
> ___
> Libraries mailing list
> librar...@haskell.org
> http://www.haskell.org/mailman/listinfo/libraries



-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Question on a common pattern

2011-03-15 Thread Ertugrul Soeylemez
Hello tsuraan,

Most often, when we multi-pattern-match on the return value of a monadic
computation, we talk about Maybe or Either or [], and I often find
myself doing this:

someIO1 :: IO (Maybe A)
someIO2 :: IO (Either A B)

result1 <- someIO1 >>= maybe ...
result2 <- someIO2 >>= either ...

There are many ways of encoding this more nicely.  My personal way is to
use the proper monad transformers for the purpose.  For many of these
situations I have written convenient combinators in the 'contstuff'
package.  I found especially the 'liftF' function very useful in these
cases:

liftF :: (LiftFunctor t, Monad m) => m (InnerFunctor t a) -> t m a

Example instances:

liftF :: Monad m => m [a] -> ChoiceT r i m a
liftF :: Monad m => m (Either e a) -> EitherT r e m a
liftF :: Monad m => m (Maybe a) -> MaybeT r m a

That way instead of checking each return value individually you would
just write:

result <- evalMaybeT $ do
x <- liftF someMaybeIO
y <- liftF (someOtherMaybeIO x x)
return (Result x y)


Greets,
Ertugrul


tsuraan  wrote:

> In my code, I'm doing this quite a lot:
> 
> x <- someIO
> case x of
>   Opt1 -> ...
> 
> Having a line for extracting the value from the IO (or STM) and then
> acting on the value seems unnatural.  Is there a more concise way to
> do this?  This code:
> 
> case someIO of
>   Opt1 -> ...
> 
> Doesn't work, but is there something like that, that is valid?



-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] Yesod 0.7.1 using GHC 7.0.2 on Arch Linux

2011-03-13 Thread Ertugrul Soeylemez
I know, but at least I can go on with development.  I hope, the problem
will be fixed soon.


vagif.ve...@gmail.com wrote:

> No, it is not solved.
> With -fproduction flag you are loosing devel-server functionality.
> 
> On Saturday, March 12, 2011 02:45:11 PM Ertugrul Soeylemez wrote:
> > Oh, I just noticed the other thread about this issue.  Compiling Yesod
> > with the -fproduction flag solved it.
> > 
> > Thanks to Michael for that.
> > 
> > 
> > Greets,
> > Ertugrul
> > 
> > Ertugrul Soeylemez  wrote:
> > > Hello Ryan,
> > > 
> > > thanks a lot.
> > > 
> > > Is there a workaround for this, until it's fixed?
> > > 
> > > 
> > > Greets,
> > > Ertugrul
> > > 
> > > Ryan Yates  wrote:
> > > > Looks to be reported here:
> > > > 
> > > > http://hackage.haskell.org/trac/ghc/ticket/5004
> > > > 
> > > > 
> > > > <http://hackage.haskell.org/trac/ghc/ticket/5004>Ryan
> > > > 
> > > > On Sat, Mar 12, 2011 at 3:26 PM, Ertugrul Soeylemez  
> > > > wrote:
> > > > > Hello there,
> > > > > 
> > > > > today I have upgraded to GHC 7.0.2 by doing a system update on my
> > > > > Arch Linux box (x86, 32 bits), and I'm having difficulties to
> > > > > install Yesod. Its dependencies seem to have been installed without
> > > > > problems, but the
> > > > > 
> > > > > Yesod package itself fails.  The complete build log follows:
> > > > >% cabal install yesod
> > > > >Resolving dependencies...
> > > > >Configuring yesod-0.7.1...
> > > > >Preprocessing library yesod-0.7.1...
> > > > >Preprocessing executables for yesod-0.7.1...
> > > > >Building yesod-0.7.1...
> > > > >[1 of 1] Compiling Yesod( Yesod.hs, dist/build/Yesod.o
> > > > >) Registering yesod-0.7.1...
> > > > >[1 of 2] Compiling CodeGen  ( CodeGen.hs,
> > > > > 
> > > > > dist/build/yesod/yesod-tmp/CodeGen.o )
> > > > > 
> > > > >[2 of 2] Compiling Main ( scaffold.hs,
> > > > > 
> > > > > dist/build/yesod/yesod-tmp/Main.o )
> > > > > 
> > > > >Loading package ghc-prim ... linking ... done.
> > > > >Loading package integer-gmp ... linking ... done.
> > > > >Loading package base ... linking ... done.
> > > > >Loading package bytestring-0.9.1.10 ... linking ... done.
> > > > >Loading package base64-bytestring-0.1.0.2 ... linking ... done.
> > > > >Loading package array-0.3.0.2 ... linking ... done.
> > > > >Loading package containers-0.4.0.0 ... linking ... done.
> > > > >Loading package cereal-0.3.0.0 ... linking ... done.
> > > > >Loading package filepath-1.2.0.0 ... linking ... done.
> > > > >Loading package old-locale-1.0.0.2 ... linking ... done.
> > > > >Loading package old-time-1.0.0.6 ... linking ... done.
> > > > >Loading package unix-2.4.2.0 ... linking ... done.
> > > > >Loading package directory-1.1.0.0 ... linking ... done.
> > > > >Loading package binary-0.5.0.2 ... linking ... done.
> > > > >Loading package data-default-0.2.0.1 ... linking ... done.
> > > > >Loading package tagged-0.2 ... linking ... done.
> > > > >Loading package crypto-api-0.5.2 ... linking ... done.
> > > > >Loading package pureMD5-2.1.0.3 ... linking ... done.
> > > > >Loading package pretty-1.0.1.2 ... linking ... done.
> > > > >Loading package template-haskell ... linking ... done.
> > > > >Loading package transformers-0.2.2.0 ... linking ... done.
> > > > >Loading package deepseq-1.1.0.2 ... linking ... done.
> > > > >Loading package text-0.11.0.5 ... linking ... done.
> > > > >Loading package blaze-builder-0.2.1.4 ... linking ... done.
> > > > >Loading package blaze-html-0.4.1.0 ... linking ... done.
> > > > >Loading package file-embed-0.0.3.1 ... linking ... done.
> > > > >Loading package time-1.2.0.3 ... linking ... done.
> > > > >Loading package unix-compat-0.2.1.1 ... linking ... done.
> > > > >Loading package enumer

Re: [Haskell-cafe] Yesod 0.7.1 using GHC 7.0.2 on Arch Linux

2011-03-12 Thread Ertugrul Soeylemez
Oh, I just noticed the other thread about this issue.  Compiling Yesod
with the -fproduction flag solved it.

Thanks to Michael for that.


Greets,
Ertugrul


Ertugrul Soeylemez  wrote:

> Hello Ryan,
> 
> thanks a lot.
> 
> Is there a workaround for this, until it's fixed?
> 
> 
> Greets,
> Ertugrul
> 
> 
> Ryan Yates  wrote:
> 
> > Looks to be reported here:
> > 
> > http://hackage.haskell.org/trac/ghc/ticket/5004
> > 
> > 
> > <http://hackage.haskell.org/trac/ghc/ticket/5004>Ryan
> > 
> > On Sat, Mar 12, 2011 at 3:26 PM, Ertugrul Soeylemez  wrote:
> > 
> > > Hello there,
> > >
> > > today I have upgraded to GHC 7.0.2 by doing a system update on my Arch
> > > Linux box (x86, 32 bits), and I'm having difficulties to install Yesod.
> > > Its dependencies seem to have been installed without problems, but the
> > > Yesod package itself fails.  The complete build log follows:
> > >
> > >% cabal install yesod
> > >Resolving dependencies...
> > >Configuring yesod-0.7.1...
> > >Preprocessing library yesod-0.7.1...
> > >Preprocessing executables for yesod-0.7.1...
> > >Building yesod-0.7.1...
> > >[1 of 1] Compiling Yesod( Yesod.hs, dist/build/Yesod.o )
> > >Registering yesod-0.7.1...
> > >[1 of 2] Compiling CodeGen  ( CodeGen.hs,
> > > dist/build/yesod/yesod-tmp/CodeGen.o )
> > >[2 of 2] Compiling Main ( scaffold.hs,
> > > dist/build/yesod/yesod-tmp/Main.o )
> > >Loading package ghc-prim ... linking ... done.
> > >Loading package integer-gmp ... linking ... done.
> > >Loading package base ... linking ... done.
> > >Loading package bytestring-0.9.1.10 ... linking ... done.
> > >Loading package base64-bytestring-0.1.0.2 ... linking ... done.
> > >Loading package array-0.3.0.2 ... linking ... done.
> > >Loading package containers-0.4.0.0 ... linking ... done.
> > >Loading package cereal-0.3.0.0 ... linking ... done.
> > >Loading package filepath-1.2.0.0 ... linking ... done.
> > >Loading package old-locale-1.0.0.2 ... linking ... done.
> > >Loading package old-time-1.0.0.6 ... linking ... done.
> > >Loading package unix-2.4.2.0 ... linking ... done.
> > >Loading package directory-1.1.0.0 ... linking ... done.
> > >Loading package binary-0.5.0.2 ... linking ... done.
> > >Loading package data-default-0.2.0.1 ... linking ... done.
> > >Loading package tagged-0.2 ... linking ... done.
> > >Loading package crypto-api-0.5.2 ... linking ... done.
> > >Loading package pureMD5-2.1.0.3 ... linking ... done.
> > >Loading package pretty-1.0.1.2 ... linking ... done.
> > >Loading package template-haskell ... linking ... done.
> > >Loading package transformers-0.2.2.0 ... linking ... done.
> > >Loading package deepseq-1.1.0.2 ... linking ... done.
> > >Loading package text-0.11.0.5 ... linking ... done.
> > >Loading package blaze-builder-0.2.1.4 ... linking ... done.
> > >Loading package blaze-html-0.4.1.0 ... linking ... done.
> > >Loading package file-embed-0.0.3.1 ... linking ... done.
> > >Loading package time-1.2.0.3 ... linking ... done.
> > >Loading package unix-compat-0.2.1.1 ... linking ... done.
> > >Loading package enumerator-0.4.7 ... linking ... done.
> > >Loading package mtl-2.0.1.0 ... linking ... done.
> > >Loading package parsec-3.1.1 ... linking ... done.
> > >Loading package network-2.2.1.10 ... linking ... done.
> > >Loading package wai-0.3.2 ... linking ... done.
> > >Loading package utf8-string-0.3.6 ... linking ... done.
> > >Loading package web-routes-0.23.4 ... linking ... done.
> > >Loading package wai-app-static-0.0.1.1 ... linking ... done.
> > >Loading package random-1.0.0.3 ... linking ... done.
> > >Loading package clientsession-0.4.1 ... linking ... done.
> > >Loading package cookie-0.0.0 ... linking ... done.
> > >Loading package failure-0.1.0.1 ... linking ... done.
> > >Loading package extensible-exceptions-0.1.1.2 ... linking ... done.
> > >Loading package QuickCheck-2.4.0.1 ... linking ... done.
> > >Loading package blaze-builder-enumerator-0.2.0.1 ... linking ... done.
> > >Loading package json-types-0.1 ... linking ... done.
> > >Loading package json-enumerator-0.0.1 ..

Re: [Haskell-cafe] Yesod 0.7.1 using GHC 7.0.2 on Arch Linux

2011-03-12 Thread Ertugrul Soeylemez
Hello Ryan,

thanks a lot.

Is there a workaround for this, until it's fixed?


Greets,
Ertugrul


Ryan Yates  wrote:

> Looks to be reported here:
> 
> http://hackage.haskell.org/trac/ghc/ticket/5004
> 
> 
> <http://hackage.haskell.org/trac/ghc/ticket/5004>Ryan
> 
> On Sat, Mar 12, 2011 at 3:26 PM, Ertugrul Soeylemez  wrote:
> 
> > Hello there,
> >
> > today I have upgraded to GHC 7.0.2 by doing a system update on my Arch
> > Linux box (x86, 32 bits), and I'm having difficulties to install Yesod.
> > Its dependencies seem to have been installed without problems, but the
> > Yesod package itself fails.  The complete build log follows:
> >
> >% cabal install yesod
> >Resolving dependencies...
> >Configuring yesod-0.7.1...
> >Preprocessing library yesod-0.7.1...
> >Preprocessing executables for yesod-0.7.1...
> >Building yesod-0.7.1...
> >[1 of 1] Compiling Yesod( Yesod.hs, dist/build/Yesod.o )
> >Registering yesod-0.7.1...
> >[1 of 2] Compiling CodeGen  ( CodeGen.hs,
> > dist/build/yesod/yesod-tmp/CodeGen.o )
> >[2 of 2] Compiling Main ( scaffold.hs,
> > dist/build/yesod/yesod-tmp/Main.o )
> >Loading package ghc-prim ... linking ... done.
> >Loading package integer-gmp ... linking ... done.
> >Loading package base ... linking ... done.
> >Loading package bytestring-0.9.1.10 ... linking ... done.
> >Loading package base64-bytestring-0.1.0.2 ... linking ... done.
> >Loading package array-0.3.0.2 ... linking ... done.
> >Loading package containers-0.4.0.0 ... linking ... done.
> >Loading package cereal-0.3.0.0 ... linking ... done.
> >Loading package filepath-1.2.0.0 ... linking ... done.
> >Loading package old-locale-1.0.0.2 ... linking ... done.
> >Loading package old-time-1.0.0.6 ... linking ... done.
> >Loading package unix-2.4.2.0 ... linking ... done.
> >Loading package directory-1.1.0.0 ... linking ... done.
> >Loading package binary-0.5.0.2 ... linking ... done.
> >Loading package data-default-0.2.0.1 ... linking ... done.
> >Loading package tagged-0.2 ... linking ... done.
> >Loading package crypto-api-0.5.2 ... linking ... done.
> >Loading package pureMD5-2.1.0.3 ... linking ... done.
> >Loading package pretty-1.0.1.2 ... linking ... done.
> >Loading package template-haskell ... linking ... done.
> >Loading package transformers-0.2.2.0 ... linking ... done.
> >Loading package deepseq-1.1.0.2 ... linking ... done.
> >Loading package text-0.11.0.5 ... linking ... done.
> >Loading package blaze-builder-0.2.1.4 ... linking ... done.
> >Loading package blaze-html-0.4.1.0 ... linking ... done.
> >Loading package file-embed-0.0.3.1 ... linking ... done.
> >Loading package time-1.2.0.3 ... linking ... done.
> >Loading package unix-compat-0.2.1.1 ... linking ... done.
> >Loading package enumerator-0.4.7 ... linking ... done.
> >Loading package mtl-2.0.1.0 ... linking ... done.
> >Loading package parsec-3.1.1 ... linking ... done.
> >Loading package network-2.2.1.10 ... linking ... done.
> >Loading package wai-0.3.2 ... linking ... done.
> >Loading package utf8-string-0.3.6 ... linking ... done.
> >Loading package web-routes-0.23.4 ... linking ... done.
> >Loading package wai-app-static-0.0.1.1 ... linking ... done.
> >Loading package random-1.0.0.3 ... linking ... done.
> >Loading package clientsession-0.4.1 ... linking ... done.
> >Loading package cookie-0.0.0 ... linking ... done.
> >Loading package failure-0.1.0.1 ... linking ... done.
> >Loading package extensible-exceptions-0.1.1.2 ... linking ... done.
> >Loading package QuickCheck-2.4.0.1 ... linking ... done.
> >Loading package blaze-builder-enumerator-0.2.0.1 ... linking ... done.
> >Loading package json-types-0.1 ... linking ... done.
> >Loading package json-enumerator-0.0.1 ... linking ... done.
> >Loading package hamlet-0.7.2 ... linking ... done.
> >Loading package monad-peel-0.1 ... linking ... done.
> >Loading package zlib-0.5.3.1 ... linking ... done.
> >Loading package zlib-bindings-0.0.0 ... linking ... done.
> >Loading package wai-extra-0.3.3 ... linking ... done.
> >Loading package web-routes-quasi-0.6.3.1 ... linking ... done.
> >Loading package yesod-core-0.7.0.1 ... linking ... done.
> >Loading package yesod-static-0.0.0.1 ... linking ... done.
> >Loading package SHA-1.4.1.3

[Haskell-cafe] Yesod 0.7.1 using GHC 7.0.2 on Arch Linux

2011-03-12 Thread Ertugrul Soeylemez
Hello there,

today I have upgraded to GHC 7.0.2 by doing a system update on my Arch
Linux box (x86, 32 bits), and I'm having difficulties to install Yesod.
Its dependencies seem to have been installed without problems, but the
Yesod package itself fails.  The complete build log follows:

% cabal install yesod
Resolving dependencies...
Configuring yesod-0.7.1...
Preprocessing library yesod-0.7.1...
Preprocessing executables for yesod-0.7.1...
Building yesod-0.7.1...
[1 of 1] Compiling Yesod( Yesod.hs, dist/build/Yesod.o )
Registering yesod-0.7.1...
[1 of 2] Compiling CodeGen  ( CodeGen.hs, 
dist/build/yesod/yesod-tmp/CodeGen.o )
[2 of 2] Compiling Main ( scaffold.hs, 
dist/build/yesod/yesod-tmp/Main.o )
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package bytestring-0.9.1.10 ... linking ... done.
Loading package base64-bytestring-0.1.0.2 ... linking ... done.
Loading package array-0.3.0.2 ... linking ... done.
Loading package containers-0.4.0.0 ... linking ... done.
Loading package cereal-0.3.0.0 ... linking ... done.
Loading package filepath-1.2.0.0 ... linking ... done.
Loading package old-locale-1.0.0.2 ... linking ... done.
Loading package old-time-1.0.0.6 ... linking ... done.
Loading package unix-2.4.2.0 ... linking ... done.
Loading package directory-1.1.0.0 ... linking ... done.
Loading package binary-0.5.0.2 ... linking ... done.
Loading package data-default-0.2.0.1 ... linking ... done.
Loading package tagged-0.2 ... linking ... done.
Loading package crypto-api-0.5.2 ... linking ... done.
Loading package pureMD5-2.1.0.3 ... linking ... done.
Loading package pretty-1.0.1.2 ... linking ... done.
Loading package template-haskell ... linking ... done.
Loading package transformers-0.2.2.0 ... linking ... done.
Loading package deepseq-1.1.0.2 ... linking ... done.
Loading package text-0.11.0.5 ... linking ... done.
Loading package blaze-builder-0.2.1.4 ... linking ... done.
Loading package blaze-html-0.4.1.0 ... linking ... done.
Loading package file-embed-0.0.3.1 ... linking ... done.
Loading package time-1.2.0.3 ... linking ... done.
Loading package unix-compat-0.2.1.1 ... linking ... done.
Loading package enumerator-0.4.7 ... linking ... done.
Loading package mtl-2.0.1.0 ... linking ... done.
Loading package parsec-3.1.1 ... linking ... done.
Loading package network-2.2.1.10 ... linking ... done.
Loading package wai-0.3.2 ... linking ... done.
Loading package utf8-string-0.3.6 ... linking ... done.
Loading package web-routes-0.23.4 ... linking ... done.
Loading package wai-app-static-0.0.1.1 ... linking ... done.
Loading package random-1.0.0.3 ... linking ... done.
Loading package clientsession-0.4.1 ... linking ... done.
Loading package cookie-0.0.0 ... linking ... done.
Loading package failure-0.1.0.1 ... linking ... done.
Loading package extensible-exceptions-0.1.1.2 ... linking ... done.
Loading package QuickCheck-2.4.0.1 ... linking ... done.
Loading package blaze-builder-enumerator-0.2.0.1 ... linking ... done.
Loading package json-types-0.1 ... linking ... done.
Loading package json-enumerator-0.0.1 ... linking ... done.
Loading package hamlet-0.7.2 ... linking ... done.
Loading package monad-peel-0.1 ... linking ... done.
Loading package zlib-0.5.3.1 ... linking ... done.
Loading package zlib-bindings-0.0.0 ... linking ... done.
Loading package wai-extra-0.3.3 ... linking ... done.
Loading package web-routes-quasi-0.6.3.1 ... linking ... done.
Loading package yesod-core-0.7.0.1 ... linking ... done.
Loading package yesod-static-0.0.0.1 ... linking ... done.
Loading package SHA-1.4.1.3 ... linking ... done.
Loading package RSA-1.0.6.1 ... linking ... done.
Loading package data-object-0.3.1.6 ... linking ... done.
Loading package attoparsec-0.8.5.0 ... linking ... done.
Loading package bytestring-nums-0.3.2 ... linking ... done.
Loading package bytestring-trie-0.2.3 ... linking ... done.
Loading package JSONb-1.0.3 ... linking ... done.
Loading package attempt-0.3.0 ... linking ... done.
Loading package convertible-text-0.3.0.9 ... linking ... done.
Loading package data-object-json-0.3.1.5 ... linking ... done.
Loading package attoparsec-enumerator-0.2.0.3 ... linking ... done.
Loading package network-bytestring-0.1.3.4 ... linking ... done.
Loading package asn1-data-0.4.6 ... linking ... done.
Loading package certificate-0.7.0 ... linking ... done.
Loading package primitive-0.3.1 ... linking ... done.
Loading package vector-0.7.0.1 ... linking ... done.
Loading package cryptocipher-0.2.6 ... linking ... done.
Loading package cryptohash-0.6.3 

Re: [Haskell-cafe] On hGetContents semi-closenesscloseness

2011-02-16 Thread Ertugrul Soeylemez
-BEGIN PGP SIGNED MESSAGE-
Hash: RIPEMD160

Brandon S Allbery KF8NH  wrote:

> Haskell is actually what manufacturing folks call "just in time";
> things are evaluated when they are needed.  Usually this means that
> when you output something, anything needed to compute that output will
> be done then.  The exceptions are things like
> Control.Exception.evaluate (which you can treat as doing output but
> without *actually* outputting anything), mentioned above, plus you can
> indicate that some computation must be evaluated before another by
> means of Prelude.seq.  You can also declare a type as being strict by
> prefixing an exclamation mark (so the runtime will always evaluate a
> computation before binding it), and with the BangPatterns extension
> you can also declare a pattern match binding as strict the same way.

Note that pattern matches are strict by default.  In fact, a pattern
match is the preferred way to force evaluation.  Bang patterns only make
sure that variables (i.e. wildcards, which wouldn't be evaluated
otherwise) in a pattern match are evaluated to WHNF:

  case expr of
Just x  -> ...
Nothing ->

This is strict in the Maybe constructors, but non-strict in the argument
of Just.  When using a bang pattern,

  Just (!x) -> ...

the match is also strict in the argument of Just.  A bang pattern is
really just a shortcut for using 'seq':

  Just x -> seq x $ ...

or as some people prefer to write it:

  Just x | seq x True -> ...


Greets,
Ertugrul


- -- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.11 (GNU/Linux)

iQIcBAEBAwAGBQJNW6RSAAoJENVqN/rl3Y0RpmcQAI8no1y9NopXHKx0zCV+xV4W
R2i2JdkPl8s7z+BpQLFqdKk+y9CfhqDLTwE+v8ek7fhnJXFWHqvGpi/1p6u3DRuO
/ho8YNrzp8gKj0EF0Dn0VCwZ7qdmDBtmNXdHlMUzz2pTd968/9tK0FyUSb20qiBT
Suv8lPv8shsGfYX29apo1JCcHRplfeS9wJpIk0/J5xaddTDElL0CBMWkehRFFlHi
MVB3KS/6VnCqTCd8RtykzzmxtN2d+sf4a96h9RQWFt/62UPGfH04l2kY+1YiP6fK
OaV0iqHyM1TLKT/tzp+duZ57TJ2MX5h00WczHduE01Y+7nnB8b67TAvUXJI21IwA
loh1rHlqSoPI/lF1Ti5iJEF2K74waONtl7AM+lmOQZDVuipALQvesXSWTEvS18Mm
fo052MUwzWgAXU4hwod5ZvjUNR92Z9vL5JAb1MP7DShE+sLJiXYDAD381XKU6FSi
0C4rMo553JXJcMNrnJhzdxDrfJCzcHIdePG6XOkH+EzRIUPs+mYlHuNTrFbZtyzC
LzqfIwDMRQLo0f3KT5cj+6eDV/sUELW3seaTFUSCfIQhJ3molsimQHQy7YsJvvp7
fkcxpAfnAegiTQydfvUFFsdW+ZELeZTyW06iedMisUx1Lhww4Butee8PTZex3jHV
qH/RghfnSK3w/cwiZez2
=ecix
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Yesod and concurrency

2011-02-03 Thread Ertugrul Soeylemez
Michael Snoyman  wrote:

> On Mon, Jan 31, 2011 at 1:09 PM, Ertugrul Soeylemez  wrote:
>
> > how well do WAI, Yesod and the 'persistent' package play with
> > concurrency?  For example, I'd like to write a program, which
> > concurrently provides two related sites as well as a few background
> > workers, which do something with the database.  My idea would look
> > something like this:
> >
> >  main :: IO ()
> >  main =
> >    withMyAppPool $ \pool -> do
> >      forkIO $ worker1 ...   -- background worker
> >      forkIO $ worker2 ...   -- background worker
> >      forkIO $ worker3 ...   -- background worker
> >      forkIO $ toWaiApp ...  -- site 1
> >      forkIO $ toWaiApp ...  -- site 2
> >
> > Will I run into problems with this?
>
> There should not be any issues, just make sure you compile with
> -threaded. The persistent database connection pool should work just
> fine for this. If you find any issues, please let me know, but I have
> not had trouble in the past.

I've run into the first problem with this.  Without having to use
subsites, what's an easy method to use wai-handler-devel with such a
setup?


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


  1   2   3   >