Re: [Haskell-cafe] Netwire bouncing ball

2013-07-11 Thread Ertugrul Söylemez
Just hask...@justnothing.org wrote:

 Thank you very much, this works as expected and is easy to understand.
 However a complete example of a bouncing ball would be super awesome
 since I have trouble to get it work with integralLim_.

 My first try was to use object_ from Control.Wire.Prefab.Move but got
 stuck very quickly.

object_ is a generalization of integralLim_.  It pretty much allows you
to encode any moving behavior you want.  In general I recommend going
with the integral* wires as far as possible.


 I think this would be a good addition to the quickstart tutorial.

Thanks for your feedback.  I should write a complete example application
in the next revision.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread Ertugrul Söylemez
o...@okmij.org wrote:

 Hear, hear! In OCaml, I can (and often do) write

 let (x,s) = foo 1 [] in
 let (y,s) = bar x s in
 let (z,s) = baz x y s in ...

 In Haskell I'll have to uniquely number the s's:

 let (x,s1)  = foo 1 [] in
 let (y,s2)  = bar x s1 in
 let (z,s3)  = baz x y s2 in ...

This isn't a case for non-recursive let.  It is one of the rare cases
where you might actually consider using a state monad.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-10 Thread Ertugrul Söylemez
Michael Snoyman mich...@snoyman.com wrote:

 shouldBeCaught :: SomeException - Bool

 One first stab at such a function would be to return `False` for
 AsyncException and Timeout, and `True` for everything else, but I'm
 not convinced that this is sufficient. Are there any thoughts on the
 right approach to take here?

I think there is no one right approach.  However, if you add such a
function to the exception library, it really belongs into the Exception
type class with the following type:

shouldBeCaught :: (Exception e) = e - Bool

However, a better approach is to have exception tags.  In most cases you
don't want to catch killThread's or timeout's exception, but you do want
to catch all error exceptions:

data Tag = Error | Abort | TryAgain | {- ... -} | Other String
deriving (Data, Eq, Ord, Read, Show, Typeable)

instance IsString Tag where
fromString t = Other t

This could then manifest in the following two functions in the Exception
type class:

hasTag :: (Exception e) = Tag - e - Bool
tagsOf :: (Exception e) = e - [Tag]

Then exception catchers (functions that risk swallowing important
exceptions) could filter by type and tag.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread Ertugrul Söylemez
o...@okmij.org wrote:

  If you would like to write
 
  let (x,s) = foo 1 [] in
  let (y,s) = bar x s in
  let (z,s) = baz x y s in
 
  instead, use a state monad.

 Incidentally I did write almost exactly this code once. Ironically, it
 was meant as a lead-on to the State monad.

 But there have been other cases where State monad was better
 avoided. For instance, functions like foo and bar are already written
 and they are not in the state monad.

It's fine to use `state` or the StateT constructor here.


 For example, foo may take a non-empty Set and return the minimal
 element and the set without the minimal element. There are several
 such handy functions in Data.Set and Data.Map. Injecting such
 functions into a Set monad for the sake of three lines seems overkill.

Not a Set monad, but a state monad.  Other examples include 'random' and
'randomR', where you can just apply 'state':

getRandom  = state random
getRandomR = state . randomR

I do this a lot.


 Also, in the code above s's don't have to have the same type.

For this purpose we have indexed state monads.


 I particularly like repeated lets when I am writing the code to apply
 transformations to it. Being explicit with state passing improves the
 confidence. It is simpler to reason with the pure code.

Really?  I'm more confident that I got the updates right when I use a
state monad, possibly together with lenses.  The idea is to disallow
`get` and only allow `modify` and `put`.

The thing is, your code is really imperative, and it exhibits all the
usual effects of imperative programming:  If you mess up the order of
things, you get wrong results.  In fact the let-style makes things worse
by requiring you to renumber your variables all the time.  A
non-recursive let would really just cover up this problem by imposing an
arbitrary constraint on you.  I think we are all aware that shadowing is
a bad idea, no matter whether you do it through Identity or
non-recursive let.

Also if you are serious about this, you would have to make non-recursive
let the default to get OCaml-style behavior, which would be an extremely
invasive change.  We would have to fix pretty much all packages, all
tutorials, all books, all wiki pages, etc.  Otherwise just like you may
forget to renumber your variables, you may just as well forget to add
the norec keyword or whatever the syntax would be.

State monads are actually a nice abstraction to limit the number of
things that could go wrong in this setting.  I suggest using them
instead of changing the language.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-10 Thread Ertugrul Söylemez
Michael Snoyman mich...@snoyman.com wrote:

 Any thoughts on this? I'm not sure exactly what would be the right
 method to add to the Exception typeclass, but if we can come to
 consensus on that and there are no major objections to my separate
 package proposal, I think this would be something moving forward on,
 including a library proposal.

Just a minor note:  Add both `hasTag` and `tagsOf` to the type class,
because `hasTag` may use something much more efficient than `elem` like
pattern matching or `Data.Set.member`.  I'm not even sure we really need
`tagsOf`.


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guardsloops]

2013-07-10 Thread Ertugrul Söylemez
Donn Cave d...@avvanta.com wrote:

  Let is recursive because, unlike in the case of other languages,
  variables are not locations for storing values, but the expressions
  on the right side of the equality themselves. And obviously it is
  not possible for a variable-expression to be two expressions at the
  same time. The recursiveness is buildt-in. It comes from its pure
  nature.

 I'm surprised that it would come down to purity.  It looks to me like
 simply a question of scope.  I had to write an example program to see
 what actually happens, because with me it isn't intuitive at all
 that the name bound to an expression would be visible from within
 the expression itself.  I suppose this is considered by some to be a
 feature, obviously to others it's a bug.

In a non-strict-by-default language like Haskell it's certainly a
feature.  A sufficiently smart compiler can figure out whether a
definition is recursive or not and apply the proper transformation, so
from a language-theoretic standpoint there is really no reason to have a
non-recursive let.

I think the proper solution is to identify the underlying problem:
general recursion.  Haskell does not enforce totality.  I'd really love
to see some optional totality checking in Haskell.  If Oleg decides not
to use a state monad, he will still have to be careful not to confuse
the numbers, but if he does, then the compiler will reject his code
instead of producing looping code.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-10 Thread Ertugrul Söylemez
Ezra e. k. Cooper e...@ezrakilty.net wrote:

 As starter suggestions for the keyword or syntax, I submit:

   let new x = expr in body   -- Not the old x!

It's not the old x in either case (recursive and non-recursive).


   let shadowing x = expr in body

   shadow x = expr in body

It's shadowing in either case.


   let x =! expr in body  -- The explosive bang gives an imperative
   flavor.

(=!) is a valid operator name.


 Other suggestions would be welcome.

My suggestion:  Don't add a non-recursive let.  See my other post about
general recursion and totality checking.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Netwire bouncing ball

2013-07-10 Thread Ertugrul Söylemez
Just hask...@justnothing.org wrote:

 I'm trying to get a grasp of netwire by implementing a bouncing ball
 simulation and I'm failing.
 The ball starts from the ground with a given velocity and when hitting
 the ground the wire inhibits successfully. Now I'm kinda stuck.

 How can I make the ball bounce?

A very simple way to do this is to use integralLim_ instead of
integral_.  It allows the ball itself to handle the bouncing.  A less
invasive way (i.e. you can add it to your example) is to use the (--)
combinator:

ball = integral_ 0 . integral_ 40 . (-9.8)

aboveGround = require (= 0)

bouncingBall = aboveGround . ball -- bouncingBall

While this gives you a bouncing ball, the ball will not follow real
physics.  Once the ball hits the ground, it will just start over with
its original velocity.  integralLim_ is the correct solution.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Best practices for Arrows?

2013-06-23 Thread Ertugrul Söylemez
Tom Ellis tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:

 Unfortunately my type doesn't have a Monad instance.

If you could reveal the type, we could give more precise suggestions.


  In most cases when you expose an `Arrow` interface you can also
  expose a `Category`+`Applicative` interface, which is pretty much
  equivalent (except for a few extra laws):
 
  proc x - do
  y1 - a1 - x
  y2 - a2 - x
  id - x + y1 + y2^2
 
  Is equivalent to:
 
  liftA3 (\x y1 y2 - x + y1 + y2^2) id a1 a2

 Yes, I can see how that would be useful.  My question is: are you
 talking about this Applicative instance:

 data MyArr a b = ...

 instance Arrow MyArr where
 ...

 instance Functor (MyArr a) where
   fmap f = (arr f )

 instance Applicative (MyArr a) where
   pure = arr . const
   f * g = arr (uncurry ($))  (f  g)

Yes, that seems right.


 I think I will be able to make my Arrow an ArrowLoop, but I haven't
 checked.

It's not that your type may have a useful or even sensible ArrowLoop
notion, but if it does, then arrow notation is very useful.  Also as
Ross noted it gives you access to some additional convenience syntax, in
particular if your type is an ArrowChoice.  Those combinators are
extremely awkward to use directly, but proc notation allows you to use
regular if/case syntax.

However, even then sometimes it can be beneficial to use composition of
small self-contained arrow formulas.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Best practices for Arrows?

2013-06-22 Thread Ertugrul Söylemez
Tom Ellis tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:

 Are there any best-practices I should be aware of with Arrows?  Or is
 it just a case of getting on with it?

The best practice is probably to avoid them.  If your type is a monad,
there is little reason to use the awkward arrow interface.  In some
cases the arrow interface can improve the asymptotic performance though,
for example in the case of `Auto` (which is actually a monad, but the
monadic interface introduces a space leak).

In most cases when you expose an `Arrow` interface you can also expose a
`Category`+`Applicative` interface, which is pretty much equivalent
(except for a few extra laws):

proc x - do
y1 - a1 - x
y2 - a2 - x
id - x + y1 + y2^2

Is equivalent to:

liftA3 (\x y1 y2 - x + y1 + y2^2) id a1 a2

All arrows give rise to a [Profunctor] instance, so instead of `arr` you
can use `lmap` and `rmap`/`fmap`:

arr f . c = fmap f c
c . arr f = lmap f c

If the interface is not under your control, make yourself comfortable
with the complete arrow syntax, most notably how it handles operators,
combinators and the `(| banana bracket notation |)`.  This is very
valuable information.

Try to separate individual computations as much as possible and compose
using `(.)` (or `()`/`()` if you prefer).  This makes your code
much more readable:

c = a . b . c
where
a = {- ... -}
b = {- ... -}
c = {- ... -}

There is one case where the arrow notation is really indispensable:
value recursion via `ArrowLoop`:

proc _ - do
rec v - integral - x + 1
x - integral - v
id - (x, v)

Here the position x is the integral of the velocity, which is itself the
integral of the position + 1.  This is awkward to express in terms of
`loop`, so arrow notation is really a big helper here.

[Profunctor]: http://hackage.haskell.org/package/profunctors


Greets,
Ertugrul

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


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


[Haskell-cafe] Ann: Cascading 0.1.0, DSL for Cascading Style Sheets

2013-06-20 Thread Ertugrul Söylemez
Hi there,

I've just released the first version of [cascading], library for
writing/generating Cascading Style Sheets (CSS) in Haskell.  The API
design is inspired by many other projects, including blaze-html, HSP and
Yesod's Lucius.

[cascading]: http://hackage.haskell.org/package/cascading

Features:

  * Style sheets are monoids and can be MonadWritered.

  * All non-appendix properties of CSS level 2.1 are implemented and
exposed through a type-safe API.  It's easy enough to set properties
for which no type-safe API exists.  See the example below.

  * Easy to integrate into all monadic web frameworks, easy to
interleave stylesheets with framework operations.

  * Builtin support for web-routes.

  * Color space awareness through the colour library.

  * Fully encoding-aware with one caveat:  If you bypass PropValue and
use ByteStrings as property values directly, then UTF-8 is assumed.

Example:

stylesheet :: (MonadWriter CSS m) = m ()
stylesheet =
onAll $ do
select [p] $ do
margin . Edges $ [zeroLen]
padding . Edges $ [_Em # 1, _Ex # 2]

select [em] $ do
fontWeight BolderWeight

select [ul, ol] . below [li] $ do
borderColor (LeftEdge green)
borderWidth (LeftEdge ThickWidth)
vendors $ borderRadius $= (3mm :: PropValue)

This results in the following stylesheet:

p { margin: 0;
padding: 1em 2ex }

em { font-weight: bolder }

ul li, ol li {
border-left-color: #008000;
border-left-width: thick;
border-radius: 3mm;
-moz-border-radius: 3mm;
-ms-border-radius: 3mm;
-o-border-radius: 3mm;
-webkit-border-radius: 3mm
}

Please visit the [homepage].  Feedback is always welcome.  If you find
bugs, please don't hesitate to [report] them.

[homepage]: http://hub.darcs.net/ertes/cascading
[report]:   http://hub.darcs.net/ertes/cascading/issues


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Ann: Cascading 0.1.0, DSL for Cascading Style Sheets

2013-06-20 Thread Ertugrul Söylemez
Ertugrul Söylemez e...@ertes.de wrote:

 vendors $ borderRadius $= (3mm :: PropValue)

Typo: vendors $ border-radius $= (3mm :: PropValue)


Greets,
Ertugrul

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


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


[Haskell-cafe] Only vaporware needs promises

2013-06-10 Thread Ertugrul Söylemez
Tom Ellis tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:

 Hear hear!  Hopefully we, the Haskell community, will be able to
 support this endevour with our time and efforts.

Every Haskell user does this in their own way by use, feedback, uploads
to Hackage, authoring wiki articles or blog articles or simply by
helping people.  The Haskell community has a huge momentum right now and
the language is developed by smart people.

What does /not/ help is a thread like this.  If you want to support the
development of Haskell, don't unsafeCoerce people into making useless
promises.  Instead grab your web browser, text editor or whiteboard and
do your part!


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Stream processing

2013-05-11 Thread Ertugrul Söylemez
o...@okmij.org wrote:

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

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

Conceptually all of them could solve that in some way.  After all they
all have an underlying monad, which could implement that.  In fact
that's what conduit does:  it uses ResourceT.


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

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

Same here.  Conceptually you could solve it in all stream processing
abstractions by small adjustments.

However, my real question hasn't been answered so far.  Is my
formulation of the stream processing problem accurate/complete?


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


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


Re: [Haskell-cafe] Stream processing

2013-05-11 Thread Ertugrul Söylemez
Michael Snoyman mich...@snoyman.com wrote:

 In conduit, this use case is addressed by connect-and-resume, which
 essentially allows you to escape the inversion of control normally
 introduced by the conduit pattern.

Indeed, but this isn't even an extra feature in my case.  It follows
naturally from the automaton design.  Thanks for pointing it out,
though.  I need to think about how to expose this feature.


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


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


[Haskell-cafe] Stream processing

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

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

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

  * be composable (solved by all of them),

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

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

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

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

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

  * be fast (solved by all of them).

Anything else you would put in that list?


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Backward compatibility

2013-05-03 Thread Ertugrul Söylemez
Adrian May adrian.alexander@gmail.com wrote:

 I really don't know why somebody can't make a simple and well
 intentioned point without getting attacked by people who feel
 threatened over every little thing.

It's because we're failing to see the problem.  I mean, if you can
pinpoint the source of your problems we could work on a solution, and we
would be happy to do that.  However, it is important to keep in mind
that Haskell is very active and things change a lot.  This is not a
problem, it's the mindset of this community.  If you are turning it into
a problem, feel free, but then the only suggestion I can make here is
that Haskell is probably not the right choice for your particular
development strategy.

In other words, for Haskell it's simply wrong to assume that you can use
legacy code that hasn't been maintained for many years.  Regardless of
whether you like it, this is the way to go.  If you want to use Haskell,
be prepared to maintain your code.  This usually boils down to making
small adjustments.  When the big breaking change in the base library
came I had to adjust a number of type signatures in my projects and I
was done.  These adjustments become necessary from time to time, and you
should be ready to perform them.


 I said from the start that I think Haskell is cool.

Unfortunately that doesn't really help.  What you are trying to achieve
is a shift in our fundamental philosophy, which is very unlikely to
happen, even if the shift is small.  Using Haskell is great, but does
require you to keep up to date.

The other option is to go with old compiler and library versions.  They
are all available, if you need them for your project, but this is a bad
solution.


 I'd just like it to pay a bit more attention to practical issues
 whilst making progress with its theoretical ones.

It's very difficult to combine those.  Communities solve these problems
differently.  Most communities try to keep compatible at the expense of
eliminating much of the potential for innovation.  The Haskell community
prefers to go the innovation route and is prepared to repair occasional
breakages.  They do occur, and we fix them.


 Why don't you just put it in the forum rules that nobody is ever
 allowed to criticise anything?

Because that's wrong.  I criticize things a lot, sometimes with a much
stronger tone than you did. =)


 At the end of the day, I'm just a typical manager who's atypical in
 wishing he could tell his programmers to study a bit of Haskell
 without making it a synch for the manager next door to knife him in
 the back for suggesting something that looks this unstable. This is
 the real deal on how Haskell looks out there in the mass market. You
 can lead a horse to water...

If it's your decision, you shouldn't be afraid to make it.  You are the
manager of your team!  Don't let yourself be stabbed by another manager.
Recognize that your choice can lead to higher productivity, if you don't
let yourself be distracted by this pointless matter.  And yes, it is
pointless.  If you simply move on and get to productive Haskell work,
you will find that this is a non-issue.

In particular, you want to make educated decisions, which means that you
should probably research the current standards in the Haskell community.
If you would have performed that research from the beginning, you would
have come to the conclusion that WASH was a bad choice to begin with,
which leads me to another very important point:

I have worked in many SCRUM-based teams.  While I could question the
general usefulness of this paradigm, I have to say that it has taught me
a number of very important things, and one thing in particular:
Programmer choices should be made by programmers.  You shouldn't have
made the decision about the web framework in the first place.  Get a
team of Haskell programmers and let them choose the best tool for the
job.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Backward compatibility

2013-05-03 Thread Ertugrul Söylemez
Raphael Gaschignard dasur...@gmail.com wrote:

 I'm pretty sure most of us have experienced some issue with
 dependencies breaking , and its probably the most frustrating problem
 we can have have in any language. It's hard not to take this all a bit
 personally. Maybe if we think more about how to solve this (getting
 people to maintain their stuff, for example) we can make the world a
 better place instead of bickering about issues that are more or less
 language-agnostic really.

The problem can't be solved technically.  It's a human problem after all
and it's amplified by the experimentalism in this community.  I think
the best we can do is to acknowledge its existence, which places us way
ahead of mainstream programming communities.

We don't pretend that type X in lib-0.1.0 is the same as type X in
lib-0.2.0.  What we need to work on is the ability to actually combine
multiple versions of the same package conveniently, i.e. we shouldn't
view this combination as an error.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Backward compatibility

2013-05-03 Thread Ertugrul Söylemez
Adrian May adrian.alexander@gmail.com wrote:

 How about this: can you guys give me a detailed example of a justified
 deprecation: one so extremely obviously called for that even I would
 agree. I just want to understand the kind of logic that's applied over
 these things.

Changes already made in the base library or in one of the platform
libraries:

  * base: Eq and Show independent of Num.  Broke a lot of code.  Reason:
Makes function-like numeric types possible.

  * base: Deprecated and finally removed the old exception system.
Replaced by extensible exceptions, added new masking system.  Broke
a lot of code.  Reason:  Makes the whole exception handling more
sensible.

  * mtl: Unified transformer and Identity variants.  Broke some code.
Reason:  Makes the internals much more maintainable and the whole
library design more sensible.

  * Haskell: Changed the type specializing behavior in local bindings.
Broke a lot of code.  Reason:  Makes type inference infer more
specialized types, makes code more concise, but occasionally
requires a type signature when you specifically want more
polymorphic types.

Often demanded changes that may or may not happen in the future:

  * base: Make Functor a superclass of Monad.  One of the two most
commonly demanded change to the base library.  Will break lots and
lots of code.  Reason:  Would greatly simplify a lot of code.

  * base: Fix the numeric type classes.  The other most commonly
demanded change.  Will break lots and lots of code, including most
of the base library.  Reason:  Would make numeric code much more
sensible and algebraic.

My personal demands.  Unlikely to happen in the near future:

  * Add RankNTypes, ScopedTypeVariables, TupleSections and TypeFamilies
to standard Haskell.  Shouldn't break any existing code.

  * Replace all special arrow classes by category classes, i.e. turn
ArrowChoice and ArrowLoop into CategoryChoice and CategoryLoop.
Introduce ApplicativeFix.  Will break some existing code.

  * Factor Applicative and Alternative into four classes:
  - (Functor f) = Apply f  (*)
  - (Apply f)   = Applicative fpure
  - (Functor f) = Plus f   (|)
  - (Plus f)= Alternative  empty
Would break everything.  Everything.

I could go on.  The point is that you are probably the first person to
complain about those changes. =)


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Backward compatibility

2013-05-03 Thread Ertugrul Söylemez
Neil Davies semanticphilosop...@gmail.com wrote:

 Isn't this a problem of timescale?

 Nothing can be backward compatible for ever (or at least nothing that
 is being developed or maintained)

I was referring to the Dependency Hell.  I don't consider breaking
changes a problem.


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


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


Re: [Haskell-cafe] Backward compatibility

2013-05-03 Thread Ertugrul Söylemez
Adrian May adrian.alexander@gmail.com wrote:

  Changes already made in the base library or in one of the platform
  libraries:

 So could you pick the most unassailable and tell me more about it
 please?

I'll just pick a random example:  Eq and Show are no longer superclasses
of Num.  I'm the author of the Netwire library, a library for functional
reactive programming.  Before that change you would write the following
code to express a clock that runs twice as fast as the real time clock
and oscillates up and down while gradually increasing:

liftA2 (\t o - 2*t + sin o) time (integral_ 0 . v)

Thanks to the change you can now write it as:

2*time + sin (integral_ 0 . v)


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


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


Re: [Haskell-cafe] remote-build-reporting: cabal phoning home?!

2013-05-02 Thread Ertugrul Söylemez
Scott Lawrence byt...@gmail.com wrote:

 I think (and a quick reading of source seems to bear this out) that
 that only happens when you run cabal report. Which isn't quite
 undocumented - see cabal report --help.

That's reassuring.  Thanks a lot!


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


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


Re: [Haskell-cafe] Backward compatibility

2013-05-02 Thread Ertugrul Söylemez
Adrian May adrian.alexander@gmail.com wrote:

 Please don't interpret this as a rant: I'm just feeling a bit
 disappointed about probably having to give up on Haskell.

 [rant that update broke stuff]

Well, it is a rant, so you can just as well concede it. =)

The Haskell community and its descendants (Agda, Disciple, Idris, ...)
differ from all other developer communities I know in one point:  We
don't fear change.  There is a reason why other communities do:
Non-downward-compatible changes will break stuff.  We are aware of that.

Occasionally things will break, when they worked perfectly before an
update.  Does that mean that Haskell sucks?  Not really.  It means that
some library developers will have to get rid of their old bad habits.
This is unlikely to happen for unmaintained projects like WASH.  So the
question you should be asking yourself is:  Do you really want to use
WASH?  I'm surprised that you could build it with any GHC 7.x at all.

If you don't like this experimentalism and the rigor with which we get
rid of old problems (which isn't even that rigorous -- Functor and Monad
are still independent classes even today), then Haskell may indeed be
the wrong choice for you.  However, you should always ask yourself:  Who
is the one with bad habits?

Consider PHP:  It was broken since the beginning and is still broken
today.  The developers carefully make sure that it stays broken, because
fixing it would break applications.  They don't want them to break.
That means that you can rely on all of your old bad habits, keep your
SQL injection vulnerabilities, your broken program logic, etc.  Is this
good or bad?

Consider Debian, the PHP of Linux distributions:  Their philosophy is
never to touch a running system, so instead of employing architectural
changes they keep the old code bases as long as possible and follow a
rigorous backporting policy.  They don't want you to have to rewrite
your configuration files or update your shell scripts or whatever
at-most-five-minutes steps would usually be necessary after an update.
It should Just Work.  Is this good or bad?

To express this question in a broader context:  Are you leaving a broken
tool and replacing it with a new shiny one?  Or are you really just
replacing a small problem by a big one?  Haskell's change policy is a
small problem that prevents you from big problems.  PHP is a big problem
all by itself.  Do you really want to leave this wonderful realm just
because of one setback?  Keep in mind that this setback is an integral
part of why Haskell shines where PHP sucks.

Think about it. ;)


 In principle this is the best language on the planet, but with all
 these version gotchas I don't know that I can use it anymore. What a
 tragedy. I can't even think of a suggestion as to how Haskell should
 try to get out of this mess now.

We all have to deal with these gotchas.  However, I'm still much more
productive with Haskell than with any other language.  When I go to a
new GHC major version I always expect some old packages to fail, and I'm
often surprised by the small number of packages that actually do.

So my closing comment is:  Haskell is one of the best languages, but
that greatness comes at a price.  Deal with it.  Going back to PHP is
not the answer.

Instead you should recognize that now is the time to look into one of
the big three web frameworks of today:  Happstack, Snap and Yesod.  The
tool that is broken and needs to be replaced is WASH, not Haskell.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Backward compatibility

2013-05-02 Thread Ertugrul Söylemez
Adrian May adrian.alexander@gmail.com wrote:

 [...] If you'd rather see more using Haskell, I strongly suggest you
 get a grip on what real companies actually have to worry about. It
 ain't mathematical rigour. Backward compatibility is a big chunk of
 it.

I'm not saying that you are wrong, but you may be looking at it from the
wrong angle:  Unmaintained projects depending on one of the major web
frameworks still compile today.  The strong version constraints used by
packages and taught by the package versioning policy makes this
possible.  When you install it, it does the right thing.

WASH on the other hand is really a legacy from the stone age of real
world development in Haskell.  As said, I'm surprised that you could
even compile it today.  I consider it a proof of concept that web
application development is very possible with Haskell and the community
has moved on to implement real web frameworks made for production use.

This happens for all languages, not only Haskell.  You may find that one
or the other C/C++ package breaks with GCC 4 when it compiled just fine
with GCC 2.  This is why we have the major/minor/patch-level split in
the first place.  You can't expect that nothing will break when you
update from GCC 3 to GCC 4.  The same holds for GHC and even for
strongly keep-being-retarded language implementations like PHP.

At some (quite recent) point in time the whole language was revised and
is called Haskell 2010 now.  You can still compile with Haskell 98 and
many old packages should still work, unless they are broken by the new
base library.  With the new language it's simply that the type system
has changed in an incompatible way.  It's not that features have been
removed, but simply that you have to express them differently now.  This
is most noticable for local bindings, but you will also find that the
base library has undergone some breaking changes.  This was the most
legacy-breaking change I can remember, but it was necessary.  We all
suffered from bad decisions made in the old days.  This is also likely
the change that broke WASH.

Other than this the Haskell ecosystem is actually comparatively stable.
It is so stable that actually we run into another problem, which we
refer to as the Cabal Dependency Hell.  Semisolutions like cabal-dev are
available, but we really need to do some work here.  This is probably
the weakest part of the Haskell ecosystem right now.  However, it's also
actually a very hard problem.  Other languages have the same problem,
but they fix it by ignoring it.  Programmers in those languages just
pretend that it's impossible to install multiple versions of the same
package, but if operating systems like NixOS gain more popularity they
will have to reconsider their philosophy when they face sudden
segfaults.  Haskell's Cabal would have warned them.  They don't have
such a tool.

In other words, you are likely suffering from the one big breaking
change made in Haskell's modern history (i.e. post 1998).  Don't be
discouraged by that and enjoy the improved language and base library.
Enjoy an ecosystem that acknowledges the existence of problems and the
tools you get to find a solution that fits you.  You are going into the
right direction now. =)


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Backward compatibility

2013-05-02 Thread Ertugrul Söylemez
John Lato jwl...@gmail.com wrote:

 I don't think there's anything wrong with moving at a fast pace, nor
 do I think backwards compatibility should be maintained in perpetuity.

I think this statement pretty much covers the mindset of the Haskell
community and also explains the higher breakage rate of Haskell packages
when compared to other languages, in particular non-static ones:  We
move at a very fast pace.  Innovations are made all the time.  Without
this feature we wouldn't be where we are today.

Of course Haskell, being a rigorously static and correct language and a
community that equally rigorously insists on correctness of design
patterns we have to live with the fact that we need to fix the breakages
we introduce, and we do that.  This is a good thing.


 Unfortunately this leaves a lot of scope for migrations to be handled
 poorly, and for unintended consequences of shiny new systems.  IMHO
 both have caused issues for Haskell developers and users in the recent
 and more distant past.  This is an issue where I think the community
 should continually try to improve, and if a user calls out a
 difficulty we should at least try to learn from it and not repeat the
 same mistake.

I think we do that.  The most severe breakages are introduced by new GHC
versions.  That's why there is the Haskell Platform.  If users decide to
move to new versions sooner they should be prepared to handle the
breakages.  In particular a Haskell beginner simply shouldn't use
GHC-HEAD.  Our type system makes us aware of the breakages we introduce
and gives us the opportunity to fix them properly before exposing them
to the users.

With this in mind I don't think there is anything to learn from this
particular case.  You wouldn't use WASH today for the same reasons you
wouldn't use Linux 0.x.  It's a legacy, and the ideas from it have
inspired the more recent web frameworks, which are more convenient,
faster, more real-world-oriented.  In fact I totally expect a new
generation of web frameworks to pop up in the future, more categorical,
even more convenient and less error-prone.


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


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


Re: [Haskell-cafe] Backward compatibility

2013-05-02 Thread Ertugrul Söylemez
Adrian May adrian.alexander@gmail.com wrote:

 I attached the tarball. Don't say you got it from me, OK.

That's a weird thing to demand in a public mailing list with public
search-engine-locatable archives. =)


Greets,
Ertugrul

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


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


[Haskell-cafe] remote-build-reporting: cabal phoning home?!

2013-04-30 Thread Ertugrul Söylemez
Hello there,

could somebody please shed some light on the following line that
appeared in my ~/.cabal/config?

remote-build-reporting: anonymous

The option doesn't seem to be documented anywhere, and I'm very nervous
about undocumented remote reporting features.  I expect cabal-install
to communicate only to fetch the latest package index and to upload and
download packages, the former only when i actually use the upload
command.

If it performs any other communication, please tell me how to disable
it.  In that case I'd also be interested in an explanation for why this
was enabled in the first place.  I certainly didn't enable it myself,
because it would be a serious security breach in my case.

Thank you.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Instances for continuation-based FRP

2013-04-25 Thread Ertugrul Söylemez
Conal Elliott co...@conal.net wrote:

 I first tried an imperative push-based FRP in 1998, and I had exactly
 the same experience as Heinrich mentions. The toughest two aspects of
 imperative implementation were sharing and event merge/union/mappend.

This is exactly why I chose not to follow the imperative path from the
very beginning and followed Yampa's example instead.  Currently the
denotational semantics of Netwire are only in my head, but the following
is planned for the future:

  * Take inspiration from 'pipes' and find a way to add push/pull
without giving up ArrowLoop.  This has the highest priority, but
it's also the hardest part.

  * Write down the denotational semantics as a specification.
Optionally try to prove them in a theorem prover.

  * Engage more with you guys.  We all have brilliant ideas and more
communication could help us bringing FRP to the masses.

I also plan to expose an opaque subset of Netwire which strictly
enforces the traditional notion of FRP, e.g. continuous time.  Netwire
itself is really a stream processing abstraction and doesn't force you
program in a reactive style.  This is both a strength and a weakness.
There is too much potential for abuse in this general setting.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Announcement - HGamer3D - 0.2.1 - why netwire

2013-03-29 Thread Ertugrul Söylemez
Heinrich Apfelmus apfel...@quantentunnel.de wrote:

 In the case of HGamer3D, the sink combinator would replace the need to
 declare a final wire which runs all the wires at each step.  It
 feels a bit weird to me to have wires like guiSetPropW that perform
 side effects, i.e. where it makes a different whether you observe
 their results or not. That's a complexity where I feel that something
 has been swept under the rug.

I did not review the interface of HGamer3D, mostly because it's
Windows-only.  But I'd like to point out that you would prefer a non-IO
monad for wires.  In most cases I would recommend a monad for which ()
is commutative like a reader and/or a commutative writer.  The purpose
of the underlying monad is to allow some event wires to be written more
cleanly.  Without the monad:

keyPressed :: (Monad m, Monoid e)
  = SDL.Keysym
  - Wire e m SDL.Event SDL.Event

With the monad:

keyPressed :: (SDLMonad m, Monoid e)
  = SDL.Keysym
  - Wire e m a a

In particular imperative wires like guiSetPropW (or anything for which
*set* is a sensible name) are simply wrong.  A widget, e.g. a button,
should look like this:

type MyWire= WireM (Reader MyConfig)
type MyEvent a = MyWire a a

button :: MyEvent Button

This wire takes a button configuration describing the current state of
the button.  Given an IsString Button instance and OverloadedStrings a
GUI with a button could look like this:

numberField =
label 
textField  | errorLabel . Please enter a valid number

dialog = proc _ - do
n1 - numberField - Number 1
n2 - numberField - Number 2

let s = n1 + n2 :: Integer
label - Sum:  ++ show s

button - Okay
id - s

As most event wires the button wire acts like identity when the button
is pressed, so it would return back the button configuration.  I hope
this sheds some light onto what GUI code in Netwire /should/ (in fact
/will/) look like.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Announcement - HGamer3D - 0.2.1 - why netwire

2013-03-25 Thread Ertugrul Söylemez
Peter Althainz altha...@gmail.com wrote:

 Its simply the types are more cumbersome, now. In netwire you
 basically have one type, which is Wire  with some type
 parameters (underlying monad, inhibition type, in-type, out-type),
 When underlying monad and inhibition type is choosen, you can define a
 type synonym and all boils done to GameWire a b in all types, events
 (GameWire a a), behaviours (GameWire a b), what you want.  Signal
 inhibition makes Events and Behviours looks equal. Also the overall
 network has this type. And by the way, no generalized datatypes
 (forall t. ), which I'm also not too comfortable with.

Actually for the higher rank types there is a rationale: safety.  In
fact I first had this:

type Event e m = forall a. Wire e m a a

However, this turned out to be too restrictive, when I decided to
simplify it:

type Event e m a = Wire e m a a

The reason is that many events like 'require', even though they still
act like identities, have to examine the input value to make decisions.

Also you can expect that there will be at least one higher rank type in
all libraries I release based on Netwire, for example my upcoming
Vty-based text UI library:

simpleUI ::
(Monad m)
= (forall a. m a - IO a)
- UI m () b
- IO b

The first argument is a monad morphism.  It would be totally fine for it
to be less restrictive for this case, but I want to stick with
categorical concepts as far as possible.  This makes it easier to reason
about the code.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Announcement - HGamer3D - 0.2.1 - why netwire

2013-03-24 Thread Ertugrul Söylemez
Heinrich Apfelmus apfel...@quantentunnel.de wrote:

 I concur that chaining wires with the andThen combinator is very
 slick, I like it a lot. Wolfgang Jeltsch recently described a similar
 pattern for classical FRP, namely a behavior that doesn't live
 forever, but actually ends at some point in time, which can be
 interpreted as an event occurrence. (It ends with a bang!)

Well, that would work, but I wonder why then you wouldn't want to go all
the way to signal inhibition.  You don't need AFRP to have it.  It's
actually quite a light-weight change.  Allow behaviors not to produce a
value, i.e. somewhere in your library replace a by Maybe a.


 However, do note that the andThen combinator in netwire can only be so
 slick because switching restarts time (as the documentation puts
 it). I don't see a nice way to switch between wires that have
 accumulated state.

Time doesn't necessarily restart.  This choice is left to the (--)
combinator.  I've decided for that one to restart time, because it
more closely resembles the behavior of other libraries.  As a
counterexample consider this:

time . holdFor 0.5 (periodically 1) | 2*time

This wire will switch back and forth between the two wires 'time' and
'2*time' filling the gap between the inactive times of each.  Unlike
(--), the (|) combinator keeps state.  This is also true for the
context wires (see below).


 How would you express the TwoCounters example [1] using dynamic event
 switching in netwire? (The example can be implemented without dynamic
 event switching, but that's not what I mean.) What about the BarTab
 example [2]?

I've been asked that via private mail.  Let me just quote my answer:

This is a misconception caused by the very different nature of
Netwire.  In Netwire everything is dynamic.  What really happens in
w1 -- w2 is that at the beginning only w1 exists.  When it inhibits
it is removed from the network and w2 takes its place.  The missing
ingredient is that w2 is not actually produced by a wire, but this
is equally easy and natural.  Just consider the context wires:

context id w

This wire will dynamically create a version of 'w' for every
different input, so it acts like a router that will create wires if
they don't already exist.  Deletion works similarly:

contextLatest id 1000 w

This is a version that only keeps the 1000 latest contexts.  There
is also the classic dynamic switcher called 'switch':

switch nw w

This wire acts like 'w' until 'nw' produces a new wire, then
switches to that one.  Indeed 'nw' is of type Wire e m a (Wire e m a
b).

Really nothing is static in Netwire.  It's actually very easy to
write combinators like 'switch' and 'context' yourself.  In fact you
can even write a sensible ArrowApply instance.  The problem is that
it would have linear time complexity with respect to the number of
instants that have passed, so it's not exactly useful.

Notice that wires (just like all other arrowic automata in Haskell)
switch all the time.  Moving forward in time involves switching, so it's
their very nature to do it.  They could decide to switch to anything
(provided the types fit) and they can observe the switching of other
wires.  There is no need for special library support for wires that
manage a set of wires.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Announcement - HGamer3D - 0.2.1 - why netwire

2013-03-24 Thread Ertugrul Söylemez
Heinrich Apfelmus apfel...@quantentunnel.de wrote:

 So context has the same purpose as Conal's trim combinator [1].
 However, I believe that it is too inconvenient for managing very
 dynamic collections that need to keep track of state, as the context
 function significantly limits the scope of the stateful wire. That's
 why I've opted for a more flexible approach in Reactive.Banana.Switch
 , even if that introduces significant complexity in the type
 signatures.

Again you are thinking in primitive combinators.  Keep in mind that
context is nothing primitive.  In earlier releases of Netwire I had a
manager wire that allowed to manage a set of running wires by message
passing.  However, that wire turned out to be either too generic or too
specific.  There was no good balance, so I decided to get rid of it
altogether.

Now every library layer or application would write its own
application-specific manager wire.


 Again, I would be interested in an implementation of the BarTab
 example [2] to compare the two approaches.

I'm happy to provide one.  Please be patient until I release
netwire-vty, a terminal UI library based on Netwire.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Announcement - HGamer3D - 0.2.1 - why netwire

2013-03-23 Thread Ertugrul Söylemez
Heinrich Apfelmus apfel...@quantentunnel.de wrote:

 You said that reactive-banana didn't feel as simple after the
 introduction of dynamic event switching, though. Could you pinpoint
 some particular thing that made you feel like that? Maybe a type
 signature or a tutorial or something else? I took great care trying to
 make the dynamic event switching stuff entirely optional, so you can
 use reactive-banana without understanding it at all, but I'm not sure
 if I succeeded.

I think this is less of an issue with reactive-banana than with classic
FRP in general.  The type signatures of Netwire can be scary at first
sight, but they are consistent throughout the entire library.  Once you
understand one of these type signatures you understand all of them.
Once you know how to use one wire, you know how to use all others.

Let me pinpoint something in particular: events.  In reactive-banana
events are special, in Netwire they are not.  This makes dynamic
switching special in reactive-banana and natural in Netwire.  Let me
show you an example:  You want to dispaly one for ten seconds, then
two for twelve seconds, then start over:

myWire =
one . for 10 --
two . for 12 --
myWire

Events and particularly dynamic event switching is one of the main
problems Netwire solves elegantly.  You can add this to reactive-banana,
too, but it would require changing almost the entire event interface.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Announcement - HGamer3D - 0.2.1 - featuring FRP based GUI and more

2013-03-22 Thread Ertugrul Söylemez
Peter Althainz altha...@gmail.com wrote:

 you are right all libraries could be compiled at least on Linux
 (maybe even Mac OS) and the bindings could be too. I simply have no
 time currently to mainain another platform. I started on Windows,
 because I like it and I thought its the platform with the most
 gamers. I got in troubles with the linux toolchain on Windows (gcc
 with Mingw) for Ogre and switched to the MSVC based Ogre libraries,
 not considering that possibly the Ogre Linux libraries directly on
 Linux might work well. If there is time or sombody volunteers a Linux
 version can be built, I'm quite sure.

Haskell is very good at writing portable code, but there are some things
to keep in mind:

  * Use System.FilePath instead of string operations,
  * use a portable media library like SDL,
  * when using System.IO or Control.Concurrent modules, pay attention to
the Haddock documentation.

That should make your library portable enabling you to reach a much
larger portion of the Haskell community.


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] Announcement - HGamer3D - 0.2.1 - why netwire

2013-03-22 Thread Ertugrul Söylemez
Peter Althainz altha...@gmail.com wrote:

 - What struck me was introduction of netwire author Ertugrul Söylemez
 on Arrows and the explanations of local state, which can be kept into
 an arrow. Since I was also curious on OOP and FP and game state
 handling, actually this raised some interest. So I think this Arrows
 keep local state argument was the killer feature. But also behaviours
 keep local state and maybe I got misguided here.

It's not arrows that keep local state, but it's specifically the
automaton arrows, in particular Auto and Wire.  Both are automaton
arrows.  One way to express Auto is the following:

data Auto a b = forall s. Auto s ((a, s) - (b, s))

Similarly Wire can be expressed like that (simplified):

data Wire a b = forall s. Wire s ((a, s) - (Maybe b, s))

Both contain a local state value and a transition function.  That's why
they are called automaton arrows.


 - I then did some trials with netwire and I felt it's a quite
 comprehensive and nice API, so I got started with that.

Thanks. =)


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] Future of MonadCatchIO

2013-03-03 Thread Ertugrul Söylemez
Arie Peterson ar...@xs4all.nl wrote:

 Would anyone have a problem with a deprecation of
 MonadCatchIO-transformers, and a failure to update it to work with a
 base without 'block' and 'unblock'?

Yes.  This is a simplified variant of a monad I use:

newtype Continue f m a = Continue (m (Maybe a, f (Continue f a)))

It's related to Cofree and has a valid and very straightforward
MonadCatchIO instance.  However, it's probably impossible to write a
valid MonadTransControl/MonadBaseControl instance for it.

So I kindly ask you not to deprecate MonadCatchIO.  The reason I'm
hesitant about moving to monad-control is that it's hard to understand
and also very difficult to define for CPS monads.  It is commonly
believed to be impossible.

Also I've seen at least one article about the incorrectness of
monad-control.  That's one further reason I like to avoid it.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Proposal: TypeDirectedNameResolution

2013-03-03 Thread Ertugrul Söylemez
Enrique enriqu...@gmail.com wrote:

 So, I think that it was not a good design decision not to use RPN as
 the basic notation for Haskell, but it is late for changing it :( .

I don't think you want that anyway.  First of all, meet van Laarhoven
lenses [1]:

x ^. field . subfield

This has the order you know from OOP, so the basic syntactic support for
quick method auto-suggestion is there.  You don't even need
Control.Category, because the (.) is actually the regular function
composition operator.  So where to go from here?

One advantage of Haskell is that there is no such thing as a method.
It's all functions and values, and you can actually establish a measure
for how exactly a type captures another.  Now just auto-suggest /all/
functions in scope sorted by how exactly their type matches.  You can do
that without lenses, if you have a smart editor:

stdout `

Now it might display something like this:

stdout `[hPutStrLn]
[hSetBuffering]
[hClose   ]
[...  ]
[const]
[id   ]

Finally when you select one of the functions it rewrites it to:

hPutStrLn stdout

Of course in a real editor you would also show the type signature and
probably also the module from where it was imported.

I consider the record problem solved in Haskell.


Greets,
Ertugrul

[1]: http://hackage.haskell.org/package/lens

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


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


Re: [Haskell-cafe] Future of MonadCatchIO

2013-03-03 Thread Ertugrul Söylemez
Ertugrul Söylemez e...@ertes.de wrote:

 newtype Continue f m a = Continue (m (Maybe a, f (Continue f a)))

Typo:

newtype Continue f m a = Continue (m (Maybe a, f (Continue f m a)))

Sorry.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-03-01 Thread Ertugrul Söylemez
Joe Quinn headprogrammingc...@gmail.com wrote:

 Additionally, you can change the session hash with every page hit, to
 some other totally random hash. If someone steals your session, they
 had better act on it immediately, lest you visit another page and it
 changes completely. If your session gets hijacked, you get logged
 out. When you log in again the attacker loses access.

That will likely cause trouble with concurrent connections aka
pipelining:

  * Client sends request 1 with session id A.

  * Server receives request 1, verifies A = A, handles the request, sets
new hash to B, sends response.

  * Client sends request 2 with session id A.

  * Server rejects request 2, because session id mismatch (A /= B).

  * Client receives response to request 1, sets session id to B.

Don't change the session id in the middle of the session.  To prevent
session hijacking you need to use SSL.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] FunPtr to C function with #arguments determined atruntime?

2013-02-19 Thread Ertugrul Söylemez
Ryan Newton rrnew...@gmail.com wrote:

 My problem is that I can't create a type representing what I want at
 the Haskell type-check time, and I need such a type for either
 casting or a foreign import.  For example, let's say the function
 takes a number of Int arguments between 1 and 1000.  If I find out at
 runtime that I need a function with 613 Int arguments, I would need
 to create the type (Int - Int ... - IO ()) to cast to.  I suppose
 there may be some way to create such a dependent type with
 Typeable/Data.Dynamic, since it's monomorphic. Or in theory you could
 dynamically generate new Haskell code to create the type
 (System.Eval.Haskell)...

Simpler.  This is our goal:

main :: IO ()
main = withFunction (push 3 $ push 4 $ done)

The withFunction function constructs a function at run-time, say, by
reading a file, yet this is completely type-safe, statically checked
code and also looks quite nice.

First make a clear separation between the producer and consumer of a
type.  The producer constructs the type, the consumer uses it.  Then you
can use either existentials or higher-rank types.  Let's say the user
enters a number, and we want to treat it as Integer if possible,
otherwise as Double.  This is the traditional approach:

withNum :: String - b - (Integer - b) - (Double - b) - b
withNum str none ki kd
| [(x, _)] - reads str = ki x
| [(x, _)] - reads str = kd x
| otherwise = none

Here is an improved variant:

withNum :: String - b - (forall a. (Num a) = a - b) - b
withNum str none k
| [(x, _)] - reads str = k (x :: Integer)
| [(x, _)] - reads str = k (x :: Double)
| otherwise = none

This is almost the same function, but with an important difference.  For
both cases the same continuation is called, because withNum accepts only
functions that can promise to work for all numeric types.  In other
words, the function must be polymorphic enough.  What really happens
here is that I determine the type at run-time depending on the string.
That's how lightweight dependent types work.  Meet withFunction from the
teaser.  It reveals only its type signature for now:

withFunction ::
(forall a. (Push a) = a - IO b)
- IO b

The withFunction function lifts something from value level and
constructs a function of the correct type from it.  Whatever the
continuation receives is a function of the proper type.  However, you
can't just call the function yet, because withFunction's argument
promises that it works for every type 'a'.  So it can't just pass it an
Int.  That's where the Push class comes in.  Here is a very simple,
non-fancy Int-only way to define it:

class Push a where
push :: Int - (forall b. (Push b) = b - IO c) - a - IO c
done :: a - IO ()

instance (Push a) = Push (Int - a) where
push x k f = k (f x)
done _ = throwIO (userError Messed up my arguments, sorry)

instance Push (IO ()) where
push _ _ _ = throwIO (userError Messed up my arguments, sorry)
done = id

Don't worry about the scary types.  They are actually pretty simple:
The push function, if possible, applies the given Int (first argument)
to the given function (third argument).  It passes the result to the
continuation (second argument), which again promises to work for every
Push.  For non-functions a run-time exception is raised (obviously you
can't do that at compile time, so this is the best we can get).  Here is
an example withFunction together with its application:

withFunction k =
let f :: Int - Int - IO ()
f x y = print x  print y
in k f

main :: IO ()
main = withFunction (push 3 $ push 4 $ done)

Ain't that nice?

Of course the FunPtr is now implicit in whatever withFunction constructs
it from.  While you still need the foreign declaration you now get
type-safety for types determined at run-time.  If the constructed
function takes another Int argument, push is the way to apply it.

I hope this helps.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] What is a Haskell way to implement flags?

2013-02-19 Thread Ertugrul Söylemez
Brandon Allbery allber...@gmail.com wrote:

  In C usual way is to set some bit in integer variable by shifting or
  oring, and than check flag integer variable by anding with
  particular flag value. What is Haskell way?

 You can do that, but a somewhat more idiomatic way would be a list
 (or, slightly less conveniently but more accurately, a Data.Set) of
 constructors from a flags ADT.

The Set way is the one I would prefer.  In fact together with lenses you
even get the boolean interface and a nice interface in general.  Define
your option types:

data Flag =
Debug | Verbose
deriving (Ord)

data Options =
Options {
  _optFiles :: Set FilePath,
  _optFlags :: Set Flag
}

makeLenses ''Options

The fun starts when you have a state monad around Options, because then
you can use lenses very easily.  Let's add a file:

optFiles . contains blah.txt .= True

Let's set the Verbose flag:

optFlags . contains Verbose .= True

Let's flip the Verbose flag:

optFlags . contains Verbose %= not

Are we verbose?

verbose - use (optFlags . contains Verbose)

Have fun. =)


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Netwire, keyboard events, and games

2013-02-16 Thread Ertugrul Söylemez
Patrick Hurst lightqu...@amateurtopologist.com wrote:

 I'm using netwire to build a game; one of the things the player can do
 is move around using WASD. I want to use key *events* as the 'basis'
 of my wires, not the entire state vector of the keyboard so that, for
 example, a press event on D increments the velocity by (200, 0) and a
 release event decrements it by that much. However, this has the
 problem that I can't actually get the velocity unless I have an event
 to feed into the wires, which means I can only update the screen when
 the user presses or releases a key. While this might make for
 interesting gameplay, it's not what I want.

 is the right thing to do to make the input something like a Maybe
 KeyEvent instead, and pass in Nothing whenever I want to get output
 without an event for, e.g., a render?

That highly depends on how you want to process the keys.  For real-time
games you probably want continuous key held events instead of
instantaneous key down and key up events.  The nicest way here is to
use a reader monad below the wire with a set of currently pressed keys:

data GameState =
GameState {
  gsKeyDown :: Set Key
  {- ... -}
}

type GameWire = WireM (Reader GameState)

That way you can write your event wires like identity wires, which makes
using them much more convenient.  Here is one way to write such an event
wire:

keyDown :: Key - GameWire a a
keyDown key =
mkFixM $ \_ x - do
pressed - asks (S.member key . gsKeyDown)
return (if pressed then Right x else Left mempty)

This wire acts like the identity wire when the key is pressed and
inhibits otherwise.  From such a wire you can easily construct a
velocity wire for one direction:

direction :: Key - Double - GameWire a Double
direction key speed =
pure speed . keyDown key | 0

When the key is held down, this wire has the 'speed' value, otherwise it
has the value 0.  A one-dimensional velocity is thus just the sum of two
of these directions:

velocity1 :: Key - Key - Double - GameWire a Double
velocity1 upKey downKey speed =
direction upKey speed +
direction downKey (-speed)

A two-dimensional velocity is just a pair of one-dimensional velocities:

velocity2 speed =
velocity1 W S speed 
velocity1 A D speed

Finally all you need is to turn the velocity into a position.  So
integrate it:

position = integral_ (x0, y0) . velocity2 1

I hope this helps.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Netwire, keyboard events, and games

2013-02-16 Thread Ertugrul Söylemez
Kata Recurse lightqu...@amateurtopologist.com wrote:

 This is the approach that I currently use; it was pointed out to me
 that polling the state of the keys on every input is considered bad
 practice since it means that key clicks that happen in between physics
 updates don't get registered at all, hence why I wanted to use a more
 event-driven approach.

The idea of this approach is that the set of currently pressed keys is
constructed by the application loop, not the wire itself.  Every event
triggers another step of the wire.

One problem with that approach is that the rendering may be much slower
than a wire step, so you get event congestion and thus delayed
responses.  This suggests that it would pay off to handle all events in
a single instant, but that is much more difficult than it sounds.  What
should a wire do, if in a single instant a key is pressed and released,
or if it is pressed multiple times?

A simple solution exists:  Wires can deal with a time delta of 0, so
step the wire with dt = 0 for all queued events before you render the
next frame.  There is nothing wrong with mixing this with sessions.  In,
say, SDL terms, if the event is NoEvent, use stepSession* and render.
If it's any other event, use stepWire* and don't render.


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


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


Re: [Haskell-cafe] arrow notation

2013-02-11 Thread Ertugrul Söylemez
Ross Paterson r...@soi.city.ac.uk wrote:

  Many computations ignore their input value.  You can recognize them
  by their type:  [...]

 Inspection of types is not allowed with GHC's constraint-based type
 checker, which rules out things like this.

Too bad.  Would it be possible to get rid of - ()?


  ## returnA
 
  We don't need it anymore, and it has quite a stupid definition.  Get
  rid of it in favor of 'id'.

 It would be reasonable to redefine returnA = id

Yes, that would be a good start.  For many applications using 'id'
instead of 'arr id' gives a huge performance boost.  In my particular
case (I'm doing wire-based FRP (WFRP)) I often start with a complex
sum network of categorical computations:

c1 . c2 | c3 . c4 . (c5 | c6) | c7

The distinguishing feature of WFRP, what makes it so fast, is that you
can get rid of complexity by recognizing 'id' and 'empty' when they pop
up.  The component computations can morph into them over time, for
example

for 3

is identity-like for three seconds and then switches to 'empty'.  You
can recognize and discard entire subnetworks quickly.


  ## Operators
 
  I often need to mix regular arguments with computation arguments in
  banana notation:
 
  let f c = f' x y c z
  (| f (comp - v) |)

 This wouldn't be legal if f was defined inside the proc.  If the
 arguments come from outside the proc, you could write (permuting the
 arguments)

  (| (f x y z) (comp - v) |)

 If they're defined inside the proc, you'd have something like

  (| f (comp - v) |) x y z

Of course, and that's the inconvenient part.  You have to write wrapper
functions.  It would be nice, if the bananas would consider
unparenthesized expressions as regular arguments.


  ## PreArrow
 
  All sensible arrows form a family of functors:
 
  instance (Arrow a) = Functor (a b) where
  fmap f = (arr f .)
 
  But they do more:  Every arrow is a profunctor as defined in the
  'profunctors' package:
 
  instance (Arrow a) = Profunctor a where
  lmap f = (. arr f)
  rmap = fmap
 
  That's just what you called PreArrow,

 Not so: every arrow has lmap and rmap, but not everything that has an
 lmap also has an rmap.

I see.  You want to get rid of 'arr' altogether.  On one hand that is
desirable.  On the other hand for arrows lmap and rmap are equivalent.
You can define 'arr' given 'lmap':

arr f = lmap f id

From that you can define fmap.  This leads to the conclusion that as
soon as the arrow notation does more than simple composition you need a
functor anyway.


  ## Applicative
 
  One of the main bottlenecks of arrows is the heavy tuple handling,
  but most (if not all) arrows form a family of applicative functors.
  I noticed a huge speedup by moving from arrow style to applicative
  style where possible:
 
  liftA2 (+) (lmap f c) (fmap g d)
 
  is often much faster than:
 
  arr (uncurry (+)) . (c . arr f  arr g . d)
 
  Besides being more readable it sometimes improved the performance of
  my code by an order of magnitude.  So perhaps check to see if the
  category forms an applicative functor.  If it does, you can get
  along without Arrow entirely.
 
  In fact I propose to generalize all the Arrow* classes to Category*
  classes.

 That sounds reasonable.  It's convenient to use simpler classes
 instead of Arrow where possible, but it's not always possible.

The idea is this:  If there are both Arrow and Applicative instances
(can you check this?), the arrow notation could use applicative
combinators instead of arrowic ones where possible:

proc x' - do
f - comp1 - x'
x - comp2 - x'
comp3 - f x

If this is possible, arrow notation would likely rewrite it to

comp3 . ((\f x - f x) $ comp1 * comp2)

and, as a nice bonus, recognize that \f x - f x is really just id and
optimize the fmap away:

comp3 . (comp1 * comp2)

The pattern is:  A computation composed of subcomputations where each of
them takes the same arrow variable as input.  The corresponding arrow
version is unnecessarily expensive because of the tuple wrapping and
unwrapping,

comp3 . arr (\(f, x) - f x) . comp1  comp2

whereas the applicative version is really straightforward and fast.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] arrow notation

2013-02-11 Thread Ertugrul Söylemez
Petr Pudlák petr@gmail.com wrote:

 class Arrow a = ArrowDelay a where
 delay :: a b c - a () (b - c)

 force :: Arrow a = a () (b - c) - a b c

 Perhaps it would be convenient to have ArrowDelay and the
 corresponding conversions included in the library so that defining and
 using Applicative instances for arrows would become more
 straightforward.

I appreciate the idea from a theoretical standpoint, but you don't
actually have to define an ArrowDelay instance for the notation to work.
The compiler can't check the laws anyway.


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


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


Re: [Haskell-cafe] arrow notation

2013-02-10 Thread Ertugrul Söylemez
Ross Paterson r...@soi.city.ac.uk wrote:

 I'd like to hear from anyone who's using arrow notation as supported
 by GHC, because I'm planning a couple of changes to parts of it.

I'm making heavy use of arrow notation, so I'd like to propose a set of
small improvements, not only syntactical.


## Ignored input values

Many computations ignore their input value.  You can recognize them by
their type:  If the input type is fully polymorphic and the output type
is unrelated, the computation cannot use its input value.  In that case
it would make sense to just pass whatever is the cheapest thing you
could pass without requiring me to spell it out:

comp1 :: Arr a Int
comp2 :: Arr a Double

Before:

proc x1 - do
x2 - comp1 - x1
x3 - comp2 - x2
id - (x2, x3)

After:

proc _ - do
x1 - comp1
x2 - comp2
id - (x1, x2)

Then the arrow notation compiler could just pass whatever is most
convenient at that spot.  In this case it would just compose with
'':

comp1  comp2


## returnA

We don't need it anymore, and it has quite a stupid definition.  Get rid
of it in favor of 'id'.


## Operators

I often need to mix regular arguments with computation arguments in
banana notation:

let f c = f' x y c z
(| f (comp - v) |)

Since parentheses are required for computation arguments you could relax
the syntax to allow regular arguments in simple cases as well:

(| f' x y (comp - v) z |)


## PreArrow

All sensible arrows form a family of functors:

instance (Arrow a) = Functor (a b) where
fmap f = (arr f .)

But they do more:  Every arrow is a profunctor as defined in the
'profunctors' package:

instance (Arrow a) = Profunctor a where
lmap f = (. arr f)
rmap = fmap

That's just what you called PreArrow, so there is no need to reinvent
the wheel.  Get Profunctor into base.


## Applicative

One of the main bottlenecks of arrows is the heavy tuple handling, but
most (if not all) arrows form a family of applicative functors.  I
noticed a huge speedup by moving from arrow style to applicative style
where possible:

liftA2 (+) (lmap f c) (fmap g d)

is often much faster than:

arr (uncurry (+)) . (c . arr f  arr g . d)

Besides being more readable it sometimes improved the performance of my
code by an order of magnitude.  So perhaps check to see if the category
forms an applicative functor.  If it does, you can get along without
Arrow entirely.

In fact I propose to generalize all the Arrow* classes to Category*
classes.  The ultimate goal is to get rid of arrows.  We don't really
need them anymore.  I'd rather like to see SHE's idiom brackets in
Haskell and use a more lightweight syntax for stuff like ArrowChoice and
ArrowLoop (or CategoryChoice and CategoryLoop), although I don't yet
know what it would look like.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] FFI - Approaches to C/C++

2013-02-04 Thread Ertugrul Söylemez
kudah kudahkuka...@gmail.com wrote:

 I'd object to your implication that Haskell is completely ready for
 use in general soft real-time systems. I was unable to implement a
 multi-threaded application which does a some IO-work in background
 threads in a way so that its GUI won't die. Worker threads simply
 starve the GUI, because Haskell doesn't have thread priorities. And
 even if it had, it would still lag on Windows, due to lack of IO
 manager. Ezyang had, in fact, made a new scheduler, which seems to
 address the problem; and joeyadams tries to make IO-manager for
 windows, but all this isn't going to see the light of day for a while,
 at least until 7.8.1.

Be sure to compile with -threaded.  Also note that GUI libraries often
want to run in a bound thread.


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


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


Re: [Haskell-cafe] FFI - Approaches to C/C++

2013-01-31 Thread Ertugrul Söylemez
Casey Basichis caseybasic...@gmail.com wrote:

 I'm not entirely sure what you mean.

 I'm intending on using Ogre for GUI - for which there is the Hogre
 bindings, but after emailing the DEV about it, I didn't get the
 impression from his advice that I should be using it for production
 code.  Here is what he suggested:

 It depends, really. Hogre is good for running Ogre from within
 Haskell, but it has its limitations. The number one thing people have
 been struggling with is handling input with hogre - there's Hois
 (Haskell wrapper for OIS) but it's not perfect (it misses input
 events), and the other option is having to write some C++ glue. Hogre
 is a solid proof of concept and you can do some demos with it, but if
 you're e.g. writing a game it might be a bit of a struggle. In the end
 it's about how much you value being able to write code in Haskell (or
 how allergic to C++ you are).

 I'm on iOS so I imagine those difficulties are compounded.

 I am using several other C++ libraries for which there are no existing
 bindings and no Haskell alternative packages that are even remotely
 close.

 Are you suggesting it would be better to write all my own FFI bindings
 for all the needed libraries?

That's not what I'm suggesting.  It was just too little information to
properly judge the difficulty of doing everything in Haskell.

Binding to Ogre (or C++ in general) is indeed difficult.  If Hogre
doesn't work or is too limited, your best option might be to write a C
wrapper around the Hogre functionality you need.  Another option is to
use SDL/OpenGL directly, which may be easier or harder depending on your
application.

However, if you can build the bridge between your rendering library and
Haskell, then Haskell is certainly the better choice.


 Everything I read suggests that Haskells strengths are in
 transformation and that interaction is not its strong suit.

 I am interested in your thoughts and I am open to whatever, but you
 are the first to suggest that the mix is a bad idea.

That used to be true, but the reason has nothing to do with the
language.  The problem was that the libraries weren't there.  Nowadays
you can write all sorts of interactive applications in Haskell,
including GUIs, TUIs, games, simulations and web applications.  However,
I've long been waiting for useful bindings to Ogre or Irrlicht, but I'm
afraid that it's not going to happen any time soon.

Ultimately it's your choice.  Let me summarize the possiblities:

  * C wrapper around Ogre.  Easy integration, but need to write the
rendering code in C/C++.

  * Full FFI bindings to Ogre.  Difficult integration, but you can write
your rendering code in Haskell.

  * Partial FFI bindings to Ogre.  Integration may be somewhat easy, if
you do the initialization in Haskell and the actual rendering in
C/C++.  However, this again requires to write the rendering in
C/C++.

  * Using SDL/OpenGL directly:  Everything available for Haskell.  May
be difficult, because you need to write OpenGL code.

I hope, this helps.


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


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


Re: [Haskell-cafe] Ticking time bomb

2013-01-31 Thread Ertugrul Söylemez
Vincent Hanquez t...@snarc.org wrote:

 I agree this is terrible, I've started working on this, but this is
 quite a bit of work and other priorities always pop up.

 https://github.com/vincenthz/cabal
 https://github.com/vincenthz/cabal-signature

 My current implementation generate a manifest during sdist'ing in
 cabal, and have cabal-signature called by cabal on the manifest to
 create a manifest.sign.

 The main issue i'm facing is how to create a Web of Trust for doing
 all the public verification bits.

You don't need it yet.  See my other post.  Once the basic
infrastructure for signatures is established, you can allow the user to
have a set of trusted keys.  The idea is that users can ask for keys
and/or import keys from key servers.  In the worst case they accept keys
when installing a package.  Once you have such a trust database you can
allow users to select, whether a key is to be trusted for signing other
keys.  Then you have basically everything to establish both hierarchial
trust relationships (like CAs) and webs of trust.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Ticking time bomb

2013-01-31 Thread Ertugrul Söylemez
Vincent Hanquez t...@snarc.org wrote:

 For example, previous maintainer might be away from email for a long
 time potentially leaving a trojan version for days/weeks, or changed
 email address..

And that may even be more harmful, because an insecure system with a
false sense of security is worse than an insecure system alone.

Let's do it properly.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Ticking time bomb

2013-01-31 Thread Ertugrul Söylemez
Joachim Breitner m...@joachim-breitner.de wrote:

  And that may even be more harmful, because an insecure system with a
  false sense of security is worse than an insecure system alone.
 
  Let's do it properly.

 but don’t overengineer it either. Simply adding to hackage the
 possibility to store a .asc file next to the tar.gz file that contains
 the cryptographic signature would be a great start, and allow us to
 develop a WoT model later on.

 (I try to resist from wondering whether this could go into hackage1 or
 only hackage2, and in the latter case, whether that means that we
 actually have the time to overengineer the system.)

 In fact, a lot would already be gained by a simple „warn if foo-2.0 is
 signed with a different key than the version of foo already installed“
 on cabal-install and people having a closer look at uploads from
 different people. Not much infrastructure needed there.

That was exactly my suggestion actually.  It requires the ability to
make and check signatures.  The making can be done with external tools
like GnuPG, but the checking has to be done by cabal-install.  To detect
changed keys there also needs to be a trust database, which can be a
simple directory in ~/.cabal/ where files are named after the
fingerprint of the key it contains.

The most important part is a sensible user interface.  The whole process
should be invisible to the user, until there is a signature error.  The
first installation of a package will actually generate a handful of
signature errors, because the keys are not known yet.

This shouldn't be too hard to implement and requires only a small change
to Hackage and cabal-install's upload command to begin.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Monadic parser vs. combinator parser

2013-01-31 Thread Ertugrul Söylemez
Jan Stolarek jan.stola...@p.lodz.pl wrote:

 Thanks for replies guys. I indeed didn't notice that there are monads
 and applicatives used in this parser. My thought that monadic parsers
 are more verbose came from Hutton's paper where the code is definitely
 less readable than in example I provided.

 There is one more thing that bothers me. It is easy to write a parser
 that returns Nothing when parsing fails. But I can't figure out a way
 to add meaningful error messages so that the user knows where did the
 parsing fail. I experimented with using Either so that I can use Left
 to pass error messages but this turned out to be inflexible and
 clutered the code. I will be greatful for any ideas.

Remember that 'Either e' is also a monad. =)


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


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


Re: [Haskell-cafe] Ticking time bomb

2013-01-31 Thread Ertugrul Söylemez
Vincent Hanquez t...@snarc.org wrote:

  That was exactly my suggestion actually.  It requires the ability to
  make and check signatures.  The making can be done with external
  tools like GnuPG, but the checking has to be done by cabal-install.
  To detect changed keys there also needs to be a trust database,
  which can be a simple directory in ~/.cabal/ where files are named
  after the fingerprint of the key it contains.
 
  The most important part is a sensible user interface.  The whole
  process should be invisible to the user, until there is a signature
  error.  The first installation of a package will actually generate a
  handful of signature errors, because the keys are not known yet.
 
  This shouldn't be too hard to implement and requires only a small
  change to Hackage and cabal-install's upload command to begin.

 That's not a proper solution, and definitively in the warm fuzzy
 feeling department.

 What if you install a package for the first time and this package has
 just been re-uploaded maliciously with a different key and a payload ?
 What if you're relying on hackage mirrors, what stop this mirror to
 regenerate all signatures with a new key ?

 It also make maintainers change difficult, and doing genuine
 non-maintainer upload.

See the last point of my post.  The last step is to implement proper web
of trust functionality, so that some keys can be declared to be signing
keys.  Then a set of trusted keys can be shipped together with
cabal-install.

That step is optional, because at least now I can fetch developer keys
by other means like a key server.

According to my solution Cabal warns for new and changed keys and asks
whether to trust them showing a fingerprint.


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


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


Re: [Haskell-cafe] Monadic parser vs. combinator parser

2013-01-30 Thread Ertugrul Söylemez
Jan Stolarek jan.stola...@p.lodz.pl wrote:

 I will be writing a parser in Haskell and I wonder how to approach the
 problem. My first thought was to use monadic parser, e.g. like the one
 described by Hutton and Meijer in Monadic Parsing in Haskell
 functional pearl. But then I stumbled upon this:

 https://github.com/alephnullplex/cradle/tree/master/code/src/Lbach/Parser

 Monadic parser seems extremely verbose and not very straightforward
 compared to this one. I started to wonder whether I should use monadic
 parser for the sake of it being monadic or should I just go with the
 combinator approach? Any thoughts will be appreciated before I shoot
 myself in the foot :)

A monadic parser /is/ a combinator parser.  The code you linked just
doesn't go as far as wrapping it up with a newtype and providing a monad
instance.

Monadic parsers aren't verbose, because there is the applicative style.
Let's rewrite this noisy example (assuming automatic backtracking):

inParens c = do
char '('
x - c
char ')'
return x

All monads are also applicative functors, which means that you can use
applicative style to write this one more nicely:

inParens c = char '(' * c * char ')'

If your parser is also an IsString you could even write:

inParens c = ( * c * )

If that's not nice and concise I don't know what is. =)


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Ticking time bomb

2013-01-30 Thread Ertugrul Söylemez
Ramana Kumar ramana.ku...@cl.cam.ac.uk wrote:

 But if you keep calling cabal a package manager, eventually you'll
 have to write the patches to make it one.

The combination of Cabal, cabal-install and Hackage is a package
distribution system.  As such, it needs the necessary cryptographic
support.  I don't view them as a package management system.

What's important is that many programmers blindly trust the code they
download, install and run from Hackage.  Yes, it's a bad habit, but
seriously, that's the alternative?  Distributions are often some linear
combination of outdated and broken with coefficients near 1.  Let me
restate the important fact with more emphasis:

People are using Hackage!

In any case there is no valid excuse for the lack of crypto.  It's too
easy to attack Hackage, so we need some crypto regardless of what we
interpret it as.

My proposal is:

  1. Build the necessary machinery into Cabal to allow signing keys and
 packages and verifying the signatures, ideally through GnuPG.
 Cabal would benefit from that even without cabal-install and
 Hackage.

  2. Update Hackage to allow uploading signatures along with packages.

  3. Update cabal-install to allow signing packages and optionally
 checking the signatures.  Do not allow signature chains.  Do not
 support CAs for now.

 Have a database of trusted keys.  Could be a directory below
 ~/.cabal with keys as files.

 More detailed (skip to next step, if you're not going to implement
 this):  Before installing anything, build a map from maintainers
 from whom we would be installing packages to the packages they
 maintain.  Maintainers are identified by their keys, not their
 usernames.  If any of the keys is not trusted yet, then print this
 list as readable as possible.  Use colors, etc.  Hypothetical
 example:

 % cabal install diagrams
 Resolving dependencies...
 The following maintainers are untrusted:

 Diagrams Project ...@... [ABCD1234]:
 FP:           
 monoid-extras-0.2.2.2
 dual-tree-0.1.0.1
 diagrams-core-0.6.0.1
 diagrams-lib-0.6.0.1
 diagrams-svg-0.6.0.1
 diagrams-contrib-0.6.0.1
 diagrams-0.6

 Trust them (?/y/n/t)? ?
   y: yes
   n: no (default)
   t: temporarily

 Trust them (?/y/n/t)? y
 Adding to trust db: Diagrams Project ...@... [ABCD1234]

 [install]

 Cabal should ignore the Maintainer field in the Cabal file.  Only
 the signature counts here.  Cabal must report a changed maintainer:

 % cabal install diagrams
 Resolving dependencies...
 WARNING: Package 'diagrams-core' has changed maintainer.
 [old key info]
 [new key info]
 Install anyway (y/n)? y
 The following maintainers are untrusted:

 [...]

  4. Announce the change and urge maintainers to update their packages
 to include signatures.

  5. Wait a few weeks.

  6. Make signature verification the default in cabal-install.

  7. Optionally implement CA support and establish a CA outside and
 offsite of Hackage.  Someone with a good understanding of server
 security and cryptography should do that.  They could be added to
 ~/.cabal/config to make package installations easier.

Steps 1..6 should be done with high priority, otherwise they will never
be finished.  Step 7 is optional.  If you're indeed considering this,
I'm happy to turn this into a set of bug tracker issues and possibly
help with the development.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] FFI - Approaches to C/C++

2013-01-30 Thread Ertugrul Söylemez
Casey Basichis caseybasic...@gmail.com wrote:

 I'm working on a project in Haskell and C++ where the former is the
 brains and the latter is for UI, interaction etc.

That's a rather odd choice.  Not exactly answering your question, but
questioning your project decisions, why would you do UI and interaction
in C++?  You have the necessary Haskell bindings and libraries to write
everything cleanly in Haskell.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] ANN: monad-bool 0.1

2013-01-26 Thread Ertugrul Söylemez
wren ng thornton w...@freegeek.org wrote:

  Yes.  There is no reason to put up a second Hackage for that one.
  Without changing anything in the current system, packages can just
  update their categories, so that they will be displayed below
  Defunct or something like that.  This is fine, as only the
  categories of the latest version are significant.
 
  If you think this is a good idea, I will start with some of my
  packages. =)

 We've had package deprecation for a while, so the big trick IMO is the
 documentation. Good descriptions of why the package is defunct and
 suggestions on how people can do things better.

 If we're going to do it on Hackage itself, I think the big question is
 one of style: should the documentation be all in the cabal file (i.e.,
 on the package description page, with no modules in the package); or
 should we put the documentation into modules?

I think the package should be included in full, and the package
documentation should clarify why the package shouldn't be used.  The
idea is that people can still download the code and see how not to do
it.  It also helps to keep legacy code working, because bad idea
doesn't necessarily mean, you could die if you use this.

You might go as far as implementing special support for this in the
cabal-install tool in the form of a flag like --allow-defunct.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Suggestiong for inter-thread communication

2013-01-26 Thread Ertugrul Söylemez
Erik de Castro Lopo mle...@mega-nerd.com wrote:

  Do you need advice on what? I didn't understand your last phrase.

 Well I have data from two sources, stdin and the calculation
 thread. If I was doing this in C, I'd probably use a pipe for the
 calculation data and then do select on the two file descriptors.

 There is a select package:

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

 but I was wondering if there was a more idiomatic Haskell way of
 dealing with inputs from more than one source.

Of course.  Threads communicate through MVars, Chans and other
abstractions.  If you have more complicated scenarios like one thread
communicating with multiple other threads in a selective fashion you may
also be interested in software transactional memory (STM).

If you are using separate threads to perform calculations, you should
make sure that you only pass fully evaluated values.  In many cases it
suffices to evaluate to WHNF, in which case you can simply write:

putMVar var $! x

This writes the WHNF of 'x' to the MVar 'var'.  If the values you pass
around are of more complicated data types with non-strict parts (like
(Integer, Integer) instead of just Integer), you can also evaluate to
NF:

import Control.DeepSeq

putMVar var $!! x

Another option is go without concurrency entirely.  Since this is about
parallel calculations, I suppose that your computations are actually
pure.  Let me give you an example:

let xs :: [Integer]
xs = map (^100) [2..1000]
mapM_ print xs

To parallelize this you can simply use parallel strategies:

import Control.Parallel.Strategies

let xs :: [Integer]
xs = parMap rseq (^100) [2..1000]
mapM_ print xs

This calculates the list values in parallel and is as simple as
replacing map by parMap rseq or parMap rdeepseq (if the elements
have non-strict parts like (Integer, Integer) instead of just Integer).

Remember that for pure values you can always just say, please evaluate
this in parallel.  No need at all to mess around with threads.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] ANN: monad-bool 0.1

2013-01-23 Thread Ertugrul Söylemez
David Thomas davidleotho...@gmail.com wrote:

  We could even set up NotOnHackage: a package repository just like
  Hackage, except the packages are just documentation on why there is
  no such package. Implementation-wise it's just a wiki; but the idea
  is about how to organize the wiki. NotOnHackage should be organized
  and searchable similar to Hackage itself, so that people can look
  there when nothing looks promising on Hackage.

 Couldn't this be actually on hackage, so one search turns up what you
 want?

Yes.  There is no reason to put up a second Hackage for that one.
Without changing anything in the current system, packages can just
update their categories, so that they will be displayed below Defunct
or something like that.  This is fine, as only the categories of the
latest version are significant.

If you think this is a good idea, I will start with some of my
packages. =)


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] ANN: monad-bool 0.1

2013-01-22 Thread Ertugrul Söylemez
Roman Cheplyaka r...@ro-che.info wrote:

 - what do you need unsafeCoerce for?

The unsafeCoerce is needed because the library is severely broken.
Consider this:

do onlyIf False
   x - c
   onlyIf True
   return x

There is a good reason why Haskell's type system would never have
allowed to write this library.  I recommend the author to try again
without unsafeCoerce.  It won't work.

Also I'm quite sure that the monads don't have associative () either.
Consider this:

yes = onlyIf True
no  = onlyIf False

yes  x  no  y

According to the intended semantics this should result in 'x', but what
does

yes  (x  no)  y

result in?


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] ANN: monad-bool 0.1

2013-01-22 Thread Ertugrul Söylemez
John Wiegley jo...@fpcomplete.com wrote:

 And poof, all my code just disappeared...

Welcome to Haskell. =)


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Container libraries

2013-01-20 Thread Ertugrul Söylemez
Alexander Solla alex.so...@gmail.com wrote:

 What is the state of container libraries?  I am looking for a library
 which provides:

 * unordered containers (for operational type safety, I don't want to
 impose orders on things that don't have them -- unordered containers
 does this)

You are imposing an order.


 * can handled nested containers (containers does that)
 * can be serialized easily, or better yet, has Generic instances

 Does such a library exist?  What are you using for Set and Map needs?

What's wrong with 'containers' itself?  I prefer Map/Set over
HashMap/HashSet, because the speed difference is small and only
noticable for large maps/sets.  If you need multiple indices, there is
IxSet.

The advantage of those is that their speed and memory behavior is more
predictable, and they're not subject to hash collision attacks.

Serializing them is done by importing your favorite serialization
package, be it binary, cereal or safecopy/acid-state.  They all have the
necessary instances.

For all these reasons I'm not a big fan of hash-based data structures,
particularly hash tables.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] ANNOUNCE: MFlow 0.2

2013-01-18 Thread Ertugrul Söylemez
Heinrich Apfelmus apfel...@quantentunnel.de wrote:

 For some reason, your blog posts are not displayed in my browser
 (Chrome). I block all cookies and I'm using adblock, though.

Blogger.com blogs often need JavaScript to display anything at all.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] ANN: crypto-pubkey: all your public key crypto algorithms belong to us.

2013-01-15 Thread Ertugrul Söylemez
Vincent Hanquez t...@snarc.org wrote:

 Yes, the performance are terrible in term of integers. As the library
 is specific to public key algorithm, i just can't reasonable work on
 64 bits integer :-), and multiprecision integers is the only way to
 go.

 I'm on-and-off working on some mutable mpi library to be able to
 define pure function that do the necessary stuff (i.e. expmod, mulmod,
 etc..)

 I'm hoping this could be reasonably competitive with a C mpi library,
 but time will tell.

It's a waste of time.  In my benchmarks Haskell Integer outperformed
equivalent (sane) C implementations using GMP's mpz_* interface.  You
would be reinventing GMP's mpn_* interface and a custom memory manager
to be able to match the speed of Integer.

The things that were slower than equivalent C code were not related to
Integer, but mostly to data structures like Set in my case, which was
the motivation for me to write the 'quickset' library.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] ANN: crypto-pubkey: all your public key crypto algorithms belong to us.

2013-01-14 Thread Ertugrul Söylemez
Vincent Hanquez t...@snarc.org wrote:

  Also for the particular purpose of generating safe primes I have
  written a blazingly fast implementation that uses intelligent
  sieving and finds even large primes (= 4096 bits) within seconds or
  minutes.  It's on hpaste [2].  I might turn this into a library at
  some point.

 Seconds or minutes ? that's very different :-)
 But in any case, it would be a nice addition i think.

 My safe prime generation function is probably the most naive possible.

Ok, let me give you an actual number.  I want, for an integer b  3, the
smallest integer d such that 2^b - d is a safe prime.  Let's find all
safe primes for b - [100..399]:

% time ./primes {100..399}
2^100 - 12389
2^101 - 9009
...
2^398 - 128981
2^399 - 191301
 ** timings:  real 32.355  user 32.105  krnl 0.113  cpu% 99%

But of course I have four cores, and as a Haskell programmer I feel that
I should use them:

% time ./primes {100..399} +RTS -N
2^100 - 12389
2^101 - 9009
...
2^398 - 128981
2^399 - 191301
 ** timings:  real 11.047  user 38.194  krnl 3.833  cpu% 380%

At some point I'm going to parallelize even individual prime
searches. =)


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


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


Re: [Haskell-cafe] ANN: crypto-pubkey: all your public key crypto algorithms belong to us.

2013-01-12 Thread Ertugrul Söylemez
Vincent Hanquez t...@snarc.org wrote:

 I've recently released crypto-pubkey [1][2], which provide a
 comprehensive solution for public key cryptography.

 Most known RSA modes (PKCS15, OAEP, PSS) are supported, and there's
 also DSA and ElGamal signature support. Most of the code originally
 lived in cryptocipher, but have now been made better and safer, and
 support more modes.

This seems like a very useful library.  Thanks for that!


 I've spend some good chunk of time adding KATs and tests,
 documentation, and making sure the performance was ahead of other
 haskell implementations.

I suggest looking at Daniel Fischer's arithmoi [1] library, which
implements very fast Integer operations and should provide most
functionality needed.  However, beware of timing attacks.

Also for the particular purpose of generating safe primes I have written
a blazingly fast implementation that uses intelligent sieving and finds
even large primes (= 4096 bits) within seconds or minutes.  It's on
hpaste [2].  I might turn this into a library at some point.

[1]: http://hackage.haskell.org/package/arithmoi
[2]: http://hpaste.org/79286


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Example programs with ample use of deepseq?

2013-01-08 Thread Ertugrul Söylemez
Joachim Breitner m...@joachim-breitner.de wrote:

 I’m wondering if the use of deepseq to avoid unwanted lazyness might
 be a too large hammer in some use cases. Therefore, I’m looking for
 real world programs with ample use of deepseq, and ideally easy ways
 to test performance (so preferably no GUI applications).

 I’ll try to find out, by runtime observerations, which of the calls ot
 deepseq could be replaced by id, seq, or „shallow seqs“ that, for
 example, calls seq on the elements of a tuple.

Now that you know when /not/ to use deepseq, let me tell you when it's
appropriate: parallelization via parallel strategies.  It's not exactly
necessary to use deepseq (or rdeepseq in this case), but it's often very
easy to express your algorithms in the usual way and then just change
some of the 'map' applications to 'parMap rdeepseq'.

When your algorithm is written with parallelization in mind this often
gives you an amazingly parallel program by changing only a few words in
your source code.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-19 Thread Ertugrul Söylemez
Mark Flamer m...@flamerassoc.com wrote:

 I have also become intrigued and confused by this category theory
 and how it relates to Haskell. It has been stated many times that you
 don't need to understand category theory to utilize the Haskell
 language but all the concepts, patterns and every paper describing
 them seems to be written by someone who understands it. It really
 appears that to innovate in this community it helps to at least have
 a basic understanding of the theory. I have started working through
 this book Conceptual Mathematics, A first introduction to categories
 and so far it seems very understandable and interesting for mere
 mortals like myself.

My experience is that you can very well innovate in this community
without understanding anything of category theory (CT).  The fun starts
when you realize that your concept, when sound, can most often be
expressed in the categorical framework, and if not, then your concept is
either unsound or can be improved by CT.

In other words, you can learn it along the way, and you do that best by
writing software and using well designed libraries.

For understanding CT itself my suggestion is that you don't try too
hard.  The human mind is used to visualizing things, and except for an
abstract directed graph this fails terribly for CT.  That means, when
you feel stuck, chances are that's just a false feeling.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-18 Thread Ertugrul Söylemez
Christopher Howard christopher.how...@frigidcode.com wrote:

 Since I received the two responses to my question, I've been trying to
 think deeply about this subject, and go back and understand the core
 ideas. I think the problem is that I really don't have a clear
 understanding of the basics of category theory, and even less clear
 idea of the connection to Haskell programming. I have been reading
 every link I can find, but I'm still finding the ideas of objects
 and especially morphisms to be quite vague.

It's vague on purpose, or in better words it's abstract.  A category C
is a collection of objects called ob(C) and a collection of morphisms
hom(C) together with morphism composition that satisfies a few laws.
That's it.  It's up to you to interpret the objects and morphisms.
Different categories give rise to completely different interpretations.

What makes category theory interesting for programming is the set of
laws, because unlike the unspecified nature of objects and morphisms,
the laws are very specific.  They establish a rigorous notion of
soundness and locality.  Let's review these laws:

  * For all f : A - B, g : B - A:
id A . g = g
f . id A = f

This law is often understated.  It means that identity morphisms are
free of effects that could disturb composition.  It also means that the
composition does not change the nature of the component morphisms and is
free of effects that could disturb the neutrality of identity morphisms.

  * f . (g . h) = (f . g) . h

Not much to be said about this one, except that it makes composition
'lightweight' in a sense.  This basically means that you don't care how
compositions are grouped.

These laws make morphisms isolated and composition lightweight as well
as undisturbing.  Now try to transfer these notions to a concrete
category, for example the category of web servers:  The objects are sets
and a morphism f : A - B is a function from A × Request to B.


 The original link I gave
 http://www.haskellforall.com/2012_08_01_archive.html purposely
 skipped over any discussion of objects, morphisms, domains, and
 codomains. The author stated, in his first example, that Haskell
 functions are a category, and proceeded to describe function
 composition. But here I am confused: If functions are a category,
 this would seem to imply (by the phrasing) that functions are the
 objects of the category. However, since we compose functions, and only
 morphisms are composed, it would follow that functions are actually
 morphisms. So, in the function category, are functions objects or
 morphisms? If they are morphisms, then what are the objects of the
 category?

You are absolutely right there.  The category is common called Hask, the
category of types and functions in Haskell.  It is strongly related to
the category of sets and functions, because Haskell types are actually
just sets, where every set has one additional member: bottom.  We say
that the set is 'lifted'.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-17 Thread Ertugrul Söylemez
Christopher Howard christopher.how...@frigidcode.com wrote:

 Say you created a type called Component (C for short), the idea
 being to compose Components out of other Components. Every C has zero
 or more connectors on it. Two Cs can be connected to form a new C
 using some kind of composition operator (say, .), provided there are
 enough connectors (one on each). Presumably you would need a Fail
 constructor of some kind to represent the situation when there is not
 enough connectors.

 Say you had a C (coupler) with two connectors, a C (thing) with one
 connector, and a C (gadget) with one connector.

 So you could have...

 (coupler . thing) . gadget

 Because the coupler and the thing would combine to create a component
 with one spare connector. This would then combine with the gadget to
 make the final component. However, if you did...

 coupler . (thing . gadget)

 Then thing and gadget combine to make a component with no spare
 connectors. And so the new component and the coupler then fail to
 combine. Associativity law broken.

 So, can I adjust my idea to fit the category concept? Or is it just
 not applicable here? Or am I just misunderstanding the whole concept?

You are not misunderstanding the concept.  You just need to learn how to
apply it in this situation.  Pluggable components with multiple slots
are still modelled by regular categories.  Let's say that Comp is such a
component category (I'm using Haskell syntax):

Comp :: * - * - *

To model a component that takes two inputs you just write a component
that takes one (!) tuple of inputs:

myComp :: Comp (X, Y) Z

For partial application of your component you need a bit more than the
basic category pattern.  Most categories form a family of applicative
functors:

instance Applicative (Comp a)

Then partial application is really just this:

partialMyComp :: X - Comp Y Z
partialMyComp x = myComp . fmap (\y - (x, y)) id

Every category that forms such a family of applicative functors is a
profunctor (see the 'profunctors' package by Edward Kmett):

instance Profunctor Comp

That makes expressing partialMyComp slightly more pleasing:

partialMyComp x = lmap (\y - (x, y)) myComp

Finally to save even more keystrokes enable the TupleSections extension:

partialMyComp x = lmap (x,) myComp

You can get similar description through the Arrow interface:

instance Arrow Comp

partialMyComp x = myComp . arr (x,)

However, often the applicative interface is much more pleasing.

Now to the theory:  What does an applicative functor give you?  It
basically extends a categorical concept by the ability to combine
multiple morphisms to a single one.  Given two morphisms,

c1 :: Comp A B
c2 :: Comp A C

and a function

f :: B - C - D

an applicative functor gives you a well-defined way to combine c1 and c2
into another morphism of type

c3 :: Comp A D

An applicative functor provides about the same theoretical soundness as
a category in that such a combination of multiple Comp morphisms is
itself always a Comp morphism, and that the combination operator itself
cannot introduce unwanted effects because of the Applicative laws:

pure f * x = fmap f x
f * pure x = fmap ($ x) f

pure f * pure x = pure (f x)

In other words, all effects are introduced by primitive components.  I
call them atoms.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Predicates in data types

2012-12-12 Thread Ertugrul Söylemez
Navid Hallajian navi...@gmail.com wrote:

 I'm a beginner in Haskell, so forgive me if this is a basic question,
 but I'd like to know if it's possible to have a predicate as part of a
 data type, so that when the data type is created, it can only be done
 if it satisfies the predicate else a type error is thrown.

 For instance, a matrix with integer elements could be modelled as
 [[Int]], given the restrictions that

- it must have at least one column and one row (so there must be at
least one list), and
- every list must have the same length

 so that when a matrix is created, the type system wont allow it if the
 predicates aren't met.

You should model your data type such that it doesn't allow invalid
values to be created in the first place.  This is actually easy with the
DataKinds and GADTs extensions since GHC 7.6.  First, as almost always,
we need type-level naturals.  We will not use the predefined from
GHC.TypeLits, because we need natural numbers with structure:

data Nat :: * where
Z :: Nat
S :: Nat - Nat

Now we define a type-indexed list type that encodes its length in the
type, commonly called 'Vec':

data Vec :: Nat - * - * where
Nil  :: Vec Z a
(:.) :: a - Vec n a - Vec (S n) a

infixr 5 :.

Unlike the regular list type this one does not give rise to a monad (I'm
lying on purpose here, but disregard that).  However, it gives you a
very useful applicative functor:

import Control.Applicative

instance Functor (Vec n) where
fmap f Nil = Nil
fmap f (x :. xs) = f x :. fmap f xs

instance Applicative (Vec Z) where
pure = const Nil
_ * _ = Nil

instance (Applicative (Vec n)) = Applicative (Vec (S n)) where
pure x = x :. pure x
f :. fs * x :. xs = f x :. (fs * xs)

These instances give you an arbitrary-arity zipWith, where liftA2 is
equivalent to zipWith and liftA3 is equivalent to zipWith3.  Using these
we can write a type-correct matrix transposition function:

transposeMat ::
(Applicative (Vec w))
= Vec h (Vec w a)
- Vec w (Vec h a)
transposeMat Nil = pure Nil
transposeMat (xs :. xss) = liftA2 (:.) xs (transposeMat xss)

We have had to use two extensions which I don't like, FlexibleContexts
and FlexibleInstances.  This is because of the Applicative class.  To
get rid of those instances you can write this in terms of a custom
class:

class ZipV (n :: Nat) where
pureV :: a - Vec n a
zipV  :: Vec n (a - b) - Vec n a - Vec n b

infixl 4 `zipV`

instance ZipV Z where
pureV= const Nil
zipV _ _ = Nil

instance (ZipV n) = ZipV (S n) where
pureV x = x :. pureV x
zipV (f :. fs) (x :. xs) = f x :. zipV fs xs

transposeMat :: (ZipV w) = Vec h (Vec w a) - Vec w (Vec h a)
transposeMat Nil = pureV Nil
transposeMat (xs :. xss) =
pureV (:.)
`zipV` xs
`zipV` transposeMat xss

There is only one issue left:  How do we actually get these values from
the outside world?  For example how do we read such a vector from the
user?  There are two (and I think only two) ways to do it:  Higher-rank
types or existential types.  The first one is the simpler one:

fromList :: [a] - (forall n. Vec n a - b) - b
fromList [] k  = k Nil
fromList (x:xs') k = fromList xs' (\xs - k (x :. xs))

The point of the higher rank type is that the second argument to
fromList promises that it can handle vectors of any length.  It's a
function that works for all n.  This can be extended to actually read
such a vec from the user:

getVec :: (Read a) = (forall n. Vec n a - IO b) - IO b
getVec k = fmap read getLine = \xs - fromList xs k

You can't pass a function that handles only non-empty lists to getVec,
because that function cannot handle any 'n'.  This lets the type system
force you to handle empty lists:

nonEmpty :: Vec n a - b - (forall n'. Vec (S n') a - b) - b

I invite you to write this function as an exercise and hope that this
mail helped.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Can cabal be turned into a package manager?

2012-12-12 Thread Ertugrul Söylemez
Janek S. fremenz...@poczta.onet.pl wrote:

 In the recent months there was a lot of dicussion about cabal,
 dependency hell and alike. After reading some of these discussions
 there is a question I just have to ask:

 Why not create a package manager (like rpm or apt) for Haskell
 software?

There is no need to reinvent that.  See below.


 I've been using Linux for years. Software for Linux is mostly written
 in C and C++. There are thousands of libraries with lots of
 dependencies and yet: a) Linux distributions manage to have package
 repositories that are kept in a consistent state b) Linux package
 managers can avoid dependency hell, automatically update to new
 packages, etc. Linux people did it! Is there any technical issue that
 prevents Haskell people from doing exactly the same thing? Or are we
 just having non-technical problems like lack of money or developers?

Actually Linux distributions do all the hard work for you.  Package
maintainers know what I'm talking about.  It's a difficult task to
specify correct dependencies, tedious to negotiate with all the other
developers and all in all provide a consistent system.  But that's only
half of the story.

The problem starts with the File Hierarchy Standard (FHS), which
essentially doesn't allow you to employ a more useful concept.  That's
why an experimental (yet quite usable) Linux distribution called NixOS
[1] has established.  It recognizes the problems of the FHS.  The
solution is simple and radical:  the FHS sucks, so ignore it.

NixOS uses the Nix package manager, which you can also use for your
Haskell packages to escape from the dependency hell.  With Nix you can
even allow all users to install arbitrary packages without interfering
with other users, even the same packages with different versions.  Two
programs can depend on different versions of the same library, etc.
It's the package manager of the future.  Unfortunately the concept is
new and different enough that it will be difficult to convince a large
portion of the Linux community to employ it.  It's the same issue
Haskell has in the programming language world.

There is no need to switch to NixOS to use Nix.  You can even install it
in your home directory.

[1]: http://nixos.org/


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Can cabal be turned into a package manager?

2012-12-12 Thread Ertugrul Söylemez
Rustom Mody rustompm...@gmail.com wrote:

 On Wed, Dec 12, 2012 at 11:25 PM, Ertugrul Söylemez e...@ertes.de
 wrote:

  Janek S. fremenz...@poczta.onet.pl wrote:
 
   In the recent months there was a lot of dicussion about cabal,
   dependency hell and alike. After reading some of these discussions
   there is a question I just have to ask:
  
   Why not create a package manager (like rpm or apt) for Haskell
   software?
 
  There is no need to reinvent that.  See below.
 
 
   I've been using Linux for years. Software for Linux is mostly
   written in C and C++. There are thousands of libraries with lots
   of dependencies and yet: a) Linux distributions manage to have
   package repositories that are kept in a consistent state b) Linux
   package managers can avoid dependency hell, automatically update
   to new packages, etc. Linux people did it! Is there any technical
   issue that prevents Haskell people from doing exactly the same
   thing? Or are we just having non-technical problems like lack of
   money or developers?
 
  Actually Linux distributions do all the hard work for you.  Package
  maintainers know what I'm talking about.  It's a difficult task to
  specify correct dependencies, tedious to negotiate with all the
  other developers and all in all provide a consistent system.  But
  that's only half of the story.
 
  The problem starts with the File Hierarchy Standard (FHS), which
  essentially doesn't allow you to employ a more useful concept.
  That's why an experimental (yet quite usable) Linux distribution
  called NixOS [1] has established.  It recognizes the problems of the
  FHS.  The solution is simple and radical:  the FHS sucks, so ignore
  it.
 
  NixOS uses the Nix package manager, which you can also use for your
  Haskell packages to escape from the dependency hell.  With Nix you
  can even allow all users to install arbitrary packages without
  interfering with other users, even the same packages with different
  versions.  Two programs can depend on different versions of the same
  library, etc. It's the package manager of the future.  Unfortunately
  the concept is new and different enough that it will be difficult to
  convince a large portion of the Linux community to employ it.  It's
  the same issue Haskell has in the programming language world.
 
  There is no need to switch to NixOS to use Nix.  You can even
  install it in your home directory.
 
  [1]: http://nixos.org/

 Thanks Ertugrul for mentioning nix.  My initial study of nix looked
 very promising as a solution to cabal-hell[2] but it seemed to suggest
 that one needs to change the whole OS!

 I must say that I am still dilly-dallying between cabal-dev
 virthualenv and nix and would appreciate a push!

I'm afraid the burden is that you would have to write the necessary Nix
expressions for your Haskell packages, so until we create a real Nix
channel for Hackage the barrier to entry is high.  But it's certainly
possible as a community project.

By the way, the Nix expressions can be derived from the Cabal
descriptions, at least for packages with the build type Simple.  Even
for more complicated packages it should be very well possible.


 [2] I believe that saying cabal-hell is part of the problem with
 cabal-hell.  A more correct phrase may be
 Haskell-has-no-standardized-package-manager-hell (which is a bit
 long!)

It's commonly referred to as the dependency hell.


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


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 to start with GHC development?

2012-12-11 Thread Ertugrul Söylemez
Eric Rochester eroch...@gmail.com wrote:

 Another idea is to have a list of open tasks grouped by how difficult
 they will be and how much knowledge of Haskell and GHC will be
 required. This is somewhat at odds with the earlier suggestion to have
 domains in codebase, with separate de facto maintainers for
 each. However, it would make it easier for others to contribute. I
 could also see where the domain maintainers could put simpler tasks
 into a global index. That might mix the best of both.

It doesn't have to be at odds with the domain suggestion.  In fact they
can be combined neatly.  The maintainer of a domain is the best person
to judge the difficulty of a task, so they can assign the difficulty
levels.  A new GHC developer can then view all tasks from all domains
sorted by difficulty and start with the easiest ones.

To me this sounds like a great idea to encourage people to join GHC
development.  I'm very interested myself, as I actually have some
experience writing compilers for statically typed lazy languages
(including STG compilation), but unfortunately my spare time is very
limited.  However, I would like to solve at least some easy tasks to get
going.

As for Simon Marlow's legacy perhaps this is the opportunity to
reevaluate the current run-time system and make it more transparent,
more modular as well as easier to substitute/customize.  This could open
the doors to using GHC for low level systems programming up to the point
where you can write kernels in Haskell.  This is something I am
particularly interested in.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Observer pattern in haskell FRP

2012-12-11 Thread Ertugrul Söylemez
Nathan Hüsken nathan.hues...@posteo.de wrote:

  Actually it is very scalable, as the same map is passed to every
  object. It can even live in the underlying monad, which means that
  you could even use a mutable vector, if you wish; however, I don't
  recommend that.
 
  Remember that a map is immutable and shared, so passing the same map
  to multiple objects is in fact the same as passing a pointer in
  C++. Lookups in and updates to the map are of logarithmic
  complexity, so this scales well.  Only doubling the number of nodes
  actually adds one full step to lookups and updates.
 
  If you're dealing with millions of objects you may want to use the
  vector solution mentioned earlier.  This requires an imperative
  underlying monad, but you would get about the same speed as in C++.

 I might just not be used enough to functional data structures, Purely
 functional data structures is on my reading list :).

 I was thinking, in the asteroids example the only reason why the view
 needs more input than the models output, is that it needs to be
 informed of creation and destruction of asteroids.

Why would the view need to be informed?


 So, in the model one could habe a signal

 asteroidsModel :: Signal Input [Just AsteroidModel]

 which outputs Nothing for asteroids that have been destroyed.
 Then, in the view this would be taken for as input for

 asteroidsView :: Signal [Just AsteroidModel] [Picture]

 asteroidsView would have to do the following:
 * route the input list to a list of asteroidView signals.
 * When there is a Nothing in the input list, the corresponding (now
 exploding) view is moved to a list of zombie asteroids where it
 remains until its explosion animation is over.
 * When the input list is longer than the list of current astroidView
 signals, the list is extended.

 This would avoid the need for bookkeeping ids.

This is a very complicated way to do it.  I would simply regard the
zombie asteroids as regular objects.  That way you don't need a
special case in the view.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Observer pattern in haskell FRP

2012-12-10 Thread Ertugrul Söylemez
Nathan Hüsken nathan.hues...@posteo.de wrote:

 I put a pseudo C++ example below the mail. I use the terms model and
 view for the game logic and rendering respectively.
 The example is a little different. Asteroids explode when they
 collide. The moment asteroids explode, they are removed from the model
 (the game logic) while in the view (rendering) they still exist until
 the explosion animation is over.

 As you said, this basically is sending messages from the Model (in the
 observer pattern called Observable) to the view (Observer). The main
 difficulty I have is how to send the messages from the correct model
 to the correct view.
 In C++ this is done by keeping pointers.
 Simply assigning IDs would work, but than I would have to always pass
 a map from the model to the view, and I feel like (also I have little
 experience with this), that this approach is not very scalable.

Actually it is very scalable, as the same map is passed to every object.
It can even live in the underlying monad, which means that you could
even use a mutable vector, if you wish; however, I don't recommend that.

Remember that a map is immutable and shared, so passing the same map to
multiple objects is in fact the same as passing a pointer in C++.
Lookups in and updates to the map are of logarithmic complexity, so this
scales well.  Only doubling the number of nodes actually adds one full
step to lookups and updates.

If you're dealing with millions of objects you may want to use the
vector solution mentioned earlier.  This requires an imperative
underlying monad, but you would get about the same speed as in C++.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Simple GUI Form

2012-11-29 Thread Ertugrul Söylemez
Hi there Rune,

if you want to get started with declarative GUI programming in Haskell,
I really recommend taking the FRP route.  Check out the
reactive-banana-wx [1] library instead of using wxHaskell directly.  If
you manage to get wxHaskell working on Windows, then reactive-banana
will work as well.

[1]: http://www.haskell.org/haskellwiki/Reactive-banana


Greets,
Ertugrul


Rune Harder Bak r...@bak.dk wrote:

 I have some input parameters
 data Input = ...
 that I need the user to enter in a gui pop-up. (windows people...)
 The rest of the app is not gui (or perhaps progress could be displayed
 in a log-window)
 
 What is the easiest way to make such a GUI form?
 
 It need to compile for both Linux and Windows, so I though WxWidgets
 was ideal, and I got wx[1]  0.90 to install (using wxWidgets2.8) on
 both windows and linux.
 
 Now I just need to create the form, but how do you do that?
 Any clues or links to examples? I have never used wxwidgets on any
 platform or done any other form of GUI before for that matters.
 (apart from some Visual Basic ten years ago, and html).
 
 I tried looking at wx examples, but I couldn't find this simple use
 case explained anywhere.
 
 I installed wx in the first place because WxGeneric[2] seemed exactly
 what I needed,
 but I can't get it to compile using ghc7.4.2 from haskell-platform.
 Anybody got that working or have some other simple method?
 
 Help much appreciated!
 
 -Rune
 
 [1] http://hackage.haskell.org/package/wx-0.13.2.3
 [2] http://hackage.haskell.org/package/WxGeneric

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


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


Re: [Haskell-cafe] Simple GUI Form

2012-11-29 Thread Ertugrul Söylemez
Rune Harder Bak r...@bak.dk wrote:

 I'm very interested in FRP, but all the examples I could see was forms
 with live feedback gui like a real-time calculator.
 This is a one-time form where the user fills everything in, clicks on
 a button, where after the computations might take a long time, perhaps
 display some console-info.
 But maybe this is a good use-case for reactive-banana as well?

Of course.  There is no reason to think that FRP is limited to real-time
applications with complicated interactions.


 Do you have any good examples in this regard?

Not myself, but there is a somewhat comprehensive tutorial [1] as well
as lots of examples [2] linked from the wiki.

I just want to stress the importance of the last tutorial section:  FRP
is not a concrete design pattern, but rather a family of them.  The
tutorial explains FRP as understood and implemented specifically by
reactive-banana.  There are a number of other practical libraries that
use different notions, in particular of events.

[1]: http://www.haskell.org/haskellwiki/
  FRP_explanation_using_reactive-banana
[2]: http://www.haskell.org/haskellwiki/Reactive-banana/Examples


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


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


Re: [Haskell-cafe] Observer pattern in haskell FRP

2012-11-27 Thread Ertugrul Söylemez
Nathan Hüsken nathan.hues...@posteo.de wrote:

  In fact it could be a (free) monad:
 
  myApp :: MyWire a (GameDelta ())
 
  someDelta :: GameDelta ()
  someDelta = do
  randomPos - liftA2 (,) getRandom getRandom
  replicateM_ 4 (addCreature randomPos)
  getPlayerPos = centerCamOver
 
  Then you could perform that monadic action as part of the rendering
  process.

 That sound like a good Idea. But I still have the problem of
 connection game logic objects with rendering objects, or am I
 missing something? Implementing addCreature is fine, but when I want
 a removeCreature, it has to remove the correct creature from a
 potentially very large list/set of creatures.
 How can I efficiently build this connections (which corresponds to a
 pointer in other languages, I guess)?

That was a simplified example.  In the real world it depends on what
generates your creatures.  If they can be generated all over the code
then you need some form of identifier generation.  This can be done by
the wire's underlying monad:

type Identifier = Int

type Game = WireM (StateT Identifier ((-) AppConfig))

A creature then may look something like this:

creature :: Game World (Creature, GameDelta ())

The wire produces a creating action at the first instant, then switches
to the creature's regular wire.  The various GameDelta actions form at
least a monoid under (), and depending on your design even a group:

rec (creature1, gd1) - creature - w
(creature2, gd2) - creature - w
(creature3, gd3) - creature - w
w - delay (World []) - World [c1, c2, c3]
id - (gd1  gd2  gd3)

That's the basic idea.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Can a GC delay TCP connection formation?

2012-11-26 Thread Ertugrul Söylemez
Jeff Shaw shawj...@gmail.com wrote:

 I've run into an issue that makes me think that when the GHC GC runs
 while a Snap or Warp HTTP server is serving connections, the GC
 prevents or delays TCP connections from forming. My application
 requires that TCP connections form within a few tens of milliseconds.
 I'm wondering if anyone else has run into this issue, and if there are
 some GC flags that could help. I've tried a few, such as -H and -c,
 and haven't found anything to help. I'm using GHC 7.4.1.

When you compile with -threaded and run on multiple threads, then the
runtime uses parallel GC.  Did you try that?


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] code length in Haskell, a comparison

2012-11-19 Thread Ertugrul Söylemez
Darren Grant therealklu...@gmail.com wrote:

 I find myself wondering where Rebol would stand in this.

Or APL.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Computed promoted natural

2012-11-08 Thread Ertugrul Söylemez
Arie Peterson ar...@xs4all.nl wrote:

 I'm trying to use data kinds, and in particular promoted naturals, to
 simplify an existing program.

 The background is as follows: I have a big computation, that uses a
 certain natural number 'd' throughout, which is computed from the
 input. Previously, this number was present as a field in many of my
 data types, for instance

  data OldA = OldA Integer …

 . There would be many values of this type (and others) floating
 around, with all the same value of 'd'. I would like to move this
 parameter to the type level, like this:

  data NewA (d :: Nat) = NewA …

 The advantage would be, that the compiler can verify that the same
 value of 'd' is used throughout the computation.

 Also, it would then be possible to make 'NewA' a full instance of
 'Num', because 'fromInteger :: Integer - NewA d' has a natural
 meaning (where the value of 'd' is provided by the type, i.e. the
 context in which the expression is used), while 'fromInteger ::
 Integer - OldA' does not, because it is not possible to create the
 right value of 'd' out of thin air.

 Is this a sane idea? I seem to get stuck when trying to /use/ the
 computation, because it is not possible to create 'd :: Nat', at the
 type level, from the computed integer.

This is a known and nice way to do it, and not just possible, but
actually quite beautiful.  It all revolves around two related concepts
called reflection and reification, the latter allowing precisely what
you think is impossible:

{-# RankNTypes, ScopedTypeVariables #-}

reflectNum :: (Num a, ReflectNum n) = proxy n - a

reifyNum ::
(Num a)
= a
- (forall n. (ReflectNum n) = Proxy n - b)
- b


 Can one somehow instantiate the type variable 'd :: Nat' at an
 integer that is not statically known?

The idea is that reifyNum takes a polymorphic (!) function in 'n', such
that the function can guarantee that it can handle any 'n', as long as
it's an instance of ReflectNum.  Now since the argument function is
polymorphic, the reifyNum function itself can choose the type based on
whatever value you pass as the first argument:

reifyNum 0 k = k (Proxy :: Proxy Z)
reifyNum n k =
reifyNum (n - 1) (\(_ :: Proxy n) -
  k (Proxy :: Proxy (S n)))

Reflection and reification together are part of a larger concept called
implicit configurations, and there is a paper about it.


 Formulated this way, it sounds like this should not be possible,
 because all types are erased at compile time.

The types are, but the type class dictionaries remain.

Of course there is no reason to reinvent the wheel here.  Check out the
'reflection' library, which even uses some magic to make this as
efficient as just passing the value right away (without
Peano-constructing it).


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Why Kleisli composition is not in the Monad signature?

2012-10-15 Thread Ertugrul Söylemez
damodar kulkarni kdamodar2...@gmail.com wrote:

 The Monad class makes us define bind (=) and unit (return) for our
 monads.

 Why the Kleisli composition (=) or (=) is not made a part of Monad
 class instead of bind (=)?

 Is there any historical reason behind this?

 The bind (=) is not as elegant as (=), at least as I find it.

 Am I missing something?

Try to express

do x - getLine
   y - getLine
   print (x, y)

using only Kleisli composition (without cheating).  Through cheating
(doing non-categorical stuff) it's possible to implement (=) in terms
of (=), but as said that's basically breaking the abstraction.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Explicitly passing an argument to an arrow

2012-10-03 Thread Ertugrul Söylemez
Alfredo Di Napoli alfredo.dinap...@gmail.com wrote:

 Thanks Brent, this should do the trick, although what I was asking was
 something more general:

 For explicitly pass I meant passing them without the eta reduce, in
 other terms:

 swapA' :: (Arrow a) = a ((b,c), (b,c)) (c,b)
 swapA'  t = () swapFirst  swapSecond (???)
   where
 swapFirst  = first $ arr snd
 swapSecond = second $ arr fst

  where the question marks indicate that I don't know how to tell
 swapFirst hey, even though from the outside
 I'm passing you a tuple *t*, you have to take as input a (t,t).

 Hope this is clearer or it has some sense at all, maybe I'm not
 getting correctly the way arrows work!

Perhaps arrow notation (Arrows extension) is what you want:

swapA' :: (Arrow a) = a ((b, c), (b, c)) (c, b)
swapA' =
proc ((_, x), (y, _)) - id - (x, y)

But I really don't understand why you're implementing this as an arrow
computation.  A simple function would do the trick, and should you
really want to use it in an arrow you can just lift it by applying
'arr'.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] simple servers

2012-09-19 Thread Ertugrul Söylemez
Kazu Yamamoto (山本和彦) k...@iij.ad.jp wrote:

  One last question. When writing C code, using epoll apis explicitly
  can impose some blocking. Is the same to be said for GHC.Event?

 I don't understand your question.

 All system calls issued from the network package use non-blocking.
 You don't have to worry about blocking at all.

Almost.  Especially when interfacing with C code you should include the
-threaded option to GHC to link against the multi-threaded run-time
system.  Otherwise your Haskell code will block your C code and
vice-versa.  Also some concurrency features don't work properly in the
single-threaded run-time.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] guards in applicative style

2012-09-12 Thread Ertugrul Söylemez
Brent Yorgey byor...@seas.upenn.edu wrote:

 However, guardA is not as useful as guard, and it is not possible to
 do the equivalent of the example shown using a list comprehension with
 a guard.  The reason is that whereas monadic computations can make use
 of intermediate computed values to decide what to do next, Applicative
 computations cannot.  So there is no way to generate values for x and
 y and then pass them to 'guardA' to do the filtering.  guardA can only
 be used to conditionally abort an Applicative computation using
 information *external* to the Applicative computation; it cannot
 express a condition on the intermediate values computed by the
 Applicative computation itself.

To continue this story, from most applicative functors you can construct
a category, which is interesting for non-monads.  Let's examine the
SparseStream functor, which is not a monad:

data SparseStream a =
SparseStream {
  headS :: Maybe a,
  tailS :: SparseStream a
}

This is an applicative functor,

instance Applicative SparseStream where
pure x = let str = SparseStream (Just x) str in str

SparseStream f fs * SparseStream x xs =
SparseStream (f * x) (fs * xs)

but with a little extension it becomes a category, the wire category:

newtype Wire a b = Wire (a - (Maybe b, Wire a b))

This is like SparseStream, but for each head/tail pair it wants an
argument.  Given a Category instance you can now actually make use of
guardA without resorting to monadic combinators:

guardA p . myStream

This is conceptually how Netwire's applicative FRP works and how events
are implemented.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] How to simplify the code of Maybe within a monad?

2012-08-16 Thread Ertugrul Söylemez
Magicloud Magiclouds magicloud.magiclo...@gmail.com wrote:

   Since Maybe is a monad, I could write code like 'maybeA  maybeB 
 maybeC' to check if all these are not Nothing. Or 'liftM foo maybeD'
 to avoid ugly 'case of'.

Also check out the somewhat cleaner Functor class with its liftM
equivalent called 'fmap', for which you don't need to import
Control.Monad.  For monads fmap = liftM.


   But how if here maybe[ABC] are like 'IO (Maybe Int)', or foo is type
 of 'Int - IO Int'?

Well, this is Haskell, so you can always write your own higher order
functions:

(~=) :: (Monad m) = m (Maybe a) - (a - m (Maybe b)) - m (Maybe b)
c ~= f = c = maybe (return Nothing) f

(~) :: (Monad m) = m (Maybe a) - m (Maybe b) - m (Maybe b)
c ~ d = c = maybe (return Nothing) (const d)

infixl 1 ~=
infixl 1 ~

However in the second case of course there is no Maybe, but then notice
that IO itself acts like Maybe through its exceptions.  In fact Maybe is
a transparent exception monad.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] 'let' keyword optional in do notation?

2012-08-08 Thread Ertugrul Söylemez
Vo Minh Thu not...@gmail.com wrote:

 This is not a parsing problem, but a scoping one: try to run this
 program:

 main = do
   let x = y
   y = 5
   let a = b
   let b = 6
   print (x, y, a, b)

 Cheers,
 Thu

Martijn has actually covered this question:

  Where each sequence of let-less bindings is put in a separate
  binding group. I'm no parsing wizard, but I couldn't come up with
  any situations in which this would cause ambiguity. To me, the
  let-less version is easier on the eyes, more consistent with -
  bindings, and also makes it less of a hassle to move stuff around.

The suggestion seems sound to me, and the additional 'let' can really be
annoying in cases where you have a lot of 'let' bindings among very few
monadic actions.  My current way to deal with this is to move the stuff
to separate computations, but it's certainly not a nice solution:

myComp = c = f
where
f x = ...
where
a = ...
b = ...


Greets
Ertugrul

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


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


Re: [Haskell-cafe] 3 level hierarchy of Haskell objects

2012-08-08 Thread Ertugrul Söylemez
Patrick Browne patrick.bro...@dit.ie wrote:

 Gast [1] describes a 3 level hierarchy of Haskell objects using
 elementOf from set theory:

 value  *elementOf*  type  *elementOf*  class

This hierarchy is pretty arbitrary and quickly runs into problems with
some type system extensions.  You can find out whether the barber of
Seville shaves himself.

A better hierarchial model is related to universes and uses type
relations (assuming a right-associative ':'):

value : type : kind : sort : ...
value : type : universe 0 : universe 1 : universe 2 : ...

A value is of a type.  A type is of the first universe (kind).  An n-th
universe is of the (n+1)-th universe.

Type classes can be modelled as implicit arguments.


 If we include super-classes would the following be an appropriate
 mathematical representation?

What is a superclass?  What are the semantics?


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] 3 level hierarchy of Haskell objects

2012-08-08 Thread Ertugrul Söylemez
Patrick Browne patrick.bro...@dit.ie wrote:

   If we include super-classes would the following be an appropriate
   mathematical representation?
 
  What is a superclass?  What are the semantics?

 I assume that like a normal class a super-class *defines* a set
 operations for types, but it is not *a set* of types. A sub-class can
 use the signature and default methods of its super-class. I have no
 particular super-class in mind.

So you basically just mean

class (Functor f) = Applicative f

where Functor is a superclass of Applicative?  There is really nothing
special about that.  Notice that type classes are a language feature
that is translated to a core language, which is essentially an extended
System F_omega.  See below.


 Rather I am trying to make sense of how these Haskell objects are
 mathematically related.

They are mainly related by logic, in particular type theory.  You may be
interested in System F_omega [1].

[1]: http://en.wikipedia.org/wiki/System_F#System_F.CF.89


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


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


Re: [Haskell-cafe] Benchmark of DFT libraries in Haskell

2012-08-06 Thread Ertugrul Söylemez
Scott Michel scooter@gmail.com wrote:

 I might be missing something in translation, but if I understand
 Takayuki's message's intent, everything needs to be calculated because
 the C-based FFTW library is called (eventually). Laziness doesn't
 really have an impact.

 The choice of underlying data structure and whether FFTW wisdom is
 used clearly has a significant impact.

If the Haskell wrapper library is a thick enough, lazy layer around
FFTW, the size of the result vector may not at all depend on any FFTW
computation.

Again, I have no experience at all with FFTW or any Haskell bindings to
it.  This is just a general remark that is worth keeping in mind.


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


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


Re: [Haskell-cafe] Benchmark of DFT libraries in Haskell

2012-08-05 Thread Ertugrul Söylemez
Takayuki Muranushi muranu...@gmail.com wrote:

 * vector-fftw with wisdom was more than 1/2 times faster than fftw in
 C with wisdom (and with communication overhead.)
 * vector-fftw without wisdom was significantly _faster_ than fftw in C
 without wisdom. I wonder why.
 * vector-fftw over vector was faster than fft over CArray.
 * any library that doesn't use fftw is much slower than those that
 does.

I have no experience with FFTW, but in general a result like this often
means that you may not have actually calculated the values themselves.
One easy way to ensure this is to print out the whole result.  If you
feel like printing takes too much CPU time for comparison, you need to
force deeply like with deepseq.

Notably Data.Vector is a lazy data structure.  If you force the vector
itself, you are not forcing the individual values.  For FFT I would
assume that the length of the resulting vector does not depend on any
values.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] specifying using type class

2012-07-31 Thread Ertugrul Söylemez
Patrick Browne patrick.bro...@dit.ie wrote:

 Thanks for all the very useful feed back on this thread.
 I would like to present my possibly incorrect summarized  view:
 Class signatures can contain placeholders for constructors.
 These place-holder-constructors cannot be used in the class to define
 functions (I assume other in-scope constructors can be used). In the
 instance a real constructor can be substituted for the
 place-holder-constructor. Does this restrict the type of equation
 that can be used in a type class? It seems that some equations
 respecting the constructor discipline are not allowed.

Your intuition seems to be near the truth, although your terminology is
currently wrong.  Let's look at an example:

class Functor f where
fmap :: (a - b) - (f a - f b)

The 'f' in the class header is probably what you call a placeholder for
constructors.  This is not a placeholder, but a type variable.  It
represents a type.  Incidentally in this case it indeed represents a
constructor, namely a /type/ constructor (like Maybe).  This is an
important distinction, because generally when we talk about
constructors, we mean /value/ constructors (like Just or Nothing):

data Maybe a = Just a | Nothing

Here Maybe is a type constructor.  This is because it's not a type in
its own right, but is applied to another type (like Int) to yield an
actual type (Maybe Int).  The type Maybe is applied to is represented
by the type variable 'a' in the code above.  To simplify communication
we often call Maybe itself also a type, but it's really not.

Let's write the Functor instance for Maybe.  It is common to use a
helper function (a so-called fold function), which allows us to express
many operations more easily.  It's called 'maybe' for Maybe:

maybe :: b - (a - b) - Maybe a - b
maybe n j (Just x) = j x
maybe n j Nothing  = n

instance Functor Maybe where
fmap f = maybe Nothing (Just . f)

This is the instance for Maybe.  The type variable 'f' from the class
now becomes a concrete type constructor Maybe.  In this instance you
have f = Maybe, so the type of 'fmap' for this particular instance
becomes:

fmap :: (a - b) - (Maybe a - Maybe b)

The notable thing here is that this is really not a
placeholder/replacement concept, but much more like a function and
application concept.  There is nothing that stops you from having type
variables in an instance:

instance Functor (Reader e) where

As you can see there is still what you called a placeholder in this
instance, so the placeholder concept doesn't really make sense here.
The declaration can be read as:

For every type 'e' the type 'Reader e' is an instance of the
Functor type class.


 I appreciate that in Haskell the most equations occur in the
 instances, [...]

Not at all.  When programming Haskell you write lots and lots of
equations outside of class instances.  Whenever you write = you
introduce an equation, for example in top-level definitions and in 'let'
and 'where' bindings.


 [...] but from my earlier post: I merely wish to identify the
 strengths and weakness of *current Haskell type classes* as a pure
 *unit of specification*

I think you will be interested in this Stack Overflow answer:

http://stackoverflow.com/a/8123973

Even though the actual question answered is different, it does give a
nice overview of the strengths and weaknesses of type classes.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] specifying using type class

2012-07-23 Thread Ertugrul Söylemez
Patrick Browne patrick.bro...@dit.ie wrote:

 Thank you for your clear an detailed reply, the work on dependent
 types seems to address my needs. However it is beyond my current
 research question, which is quite narrow(see[1]). I merely wish to
 identify the strengths and weakness of *current Haskell type classes*
 as a pure *unit of specification*. I do not wish to address any
 perceived weakness, I merely wish to identify them (if there are
 ant). Of course my question may be ill conceived, in that type classes
 were intended to specify interfaces and not algebraic types.

Oh, now I get what you really want.  You want to specify not only the
captured operations, but also assumptions about them.  This is not
impossible in Haskell, but in most cases you will need at least some
form of lightweight dependent types.  However, this can only prove
certain properties, which are not dependent on the functions themselves,
but only their types.  Here is a variant of Stacklike that does static
length checks (GHC 7.4 required):

{-# LANGUAGE DataKinds, GADTs, KindSignatures, RankNTypes #-}

data Nat = Z | S Nat

data Stack :: Nat - * - * where
Empty :: Stack Z a
Push  :: a - Stack n a - Stack (S n) a

class Stacklike (s :: Nat - * - *) where
emptyStack :: s Z a
pop:: s (S n) a - (a, s n a)
push   :: a - s n a - s (S n) a
size   :: s n a - Nat
toList :: s n a - [a]

fromList :: [a] - (forall n. s n a - b) - b
fromList [] k = k emptyStack
fromList (x:xs) k = fromList xs (k . push x)

instance Stacklike Stack where
emptyStack  = Empty
pop (Push x xs) = (x, xs)
push= Push

size Empty = Z
size (Push _ xs) = S (size xs)

toList Empty = []
toList (Push x xs) = x : toList xs

Here it is statically proven by Stacklike that the following length
preserving property holds:

snd . pop . push x :: (Stacklike s) = s n a - s n a

The way Stack is defined makes sure that the following holds:

(snd . pop . push x) emptyStack = emptyStack

These are the things you can prove.  What you can't prove is properties
that require lifting the class's functions to the type level.  This
requires real dependent types.  You can replicate the functions on the
type level, but this is not lifting and can introduce errors.

Also for real proofs your language must be total.  Haskell isn't, so you
can always cheat by providing bottom as a proof.  You may want to check
out Agda.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] specifying using type class

2012-07-22 Thread Ertugrul Söylemez
Patrick Browne patrick.bro...@dit.ie wrote:

 {-
 Below is a *specification* of a queue.
 If possible I would like to write the equations in type class.
 Does the type class need two type variables?
 How do I represent the constructors?
 Can the equations be written in the type class rather than the
 instance? -}

(Side note:  When opening a new topic, please don't /reply/ to a post,
but post it separately by creating a new mail.)

The type class needs to know the element type, so your observation is
correct.  Usually, as in your case, the element type follows from the
data structure type, and you will want to inform the type system about
this connection.  There are basically three ways to do it.  The first is
using MultiParamTypeClasses and FunctionalDependencies:

class Stacklike a s | s - a where
empty :: s a
null  :: s a - Bool
push  :: a - s a - s a
pop   :: s a - Maybe a
size  :: s a - Int
tail  :: s a - Maybe (s a)

Another way is using an associated type (TypeFamilies).  This is
cleaner, but much more noisy in the type signatures:

class Stacklike s where
type StackElement s

empty :: s (StackElement s)
null  :: s (StackElement s) - Bool
push  :: StackElement s - s (StackElement s) - s (StackElement s)
pop   :: s (StackElement s) - Maybe (StackElement s)
size  :: s (StackElement s) - Int
tail  :: s (StackElement s) - Maybe (s (StackElement s))

Finally once you realize that there is really no need to fix the element
type in the type class itself, you can simply write a type class for the
type constructor, similar to how classes like Functor are defined:

class Stacklike s where
empty :: s a
null  :: s a - Bool
push  :: a - s a - s a
pop   :: s a - Maybe a
size  :: s a - Int
tail  :: s a - Maybe (s a)

The big question is whether you want to write a class at all.  Usually
classes are used to capture patterns, not operations.


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] specifying using type class

2012-07-22 Thread Ertugrul Söylemez
Hi there Patrick,

Patrick Browne patrick.bro...@dit.ie wrote:

 Thanks for you very clear explanation.
 Without committing to some concrete representation such as list I do
 not know how to specify constructors in the class (see below). As you
 point out a class may not be appropriate for an actual application,
 but I am investigating the strengths and weaknesses of class as a unit
 of *specification*. Regards, Pat

 -- Class with functional dependency
 class QUEUE_SPEC_CLASS2 a q | q - a where
    newC2 :: q a -- ??
    sizeC2  :: q a - Int
    restC2  :: q a - Maybe (q a)
    insertC2 :: q a - a - q a
 -- Without committing to some concrete representation such as list I
 do not know how to specify constructor for insertC2 ?? =  ??
 insertC2  newC2 a = newC2 -- wrong isEmptyC2  :: q a - Bool
    isEmptyC2 newC2  = True
 --   isEmptyC2 (insertC2 newC2 a) = False wrong

You are probably confusing the type class system with something from
OOP.  A type class captures a pattern in the way a type is used.  The
corresponding concrete representation of that pattern is then written in
the instance definition:

class Stacklike s where
emptyStack :: s a
push   :: a - s a - s a
rest   :: s a - Maybe (s a)
top:: s a - Maybe a

pop :: s a - Maybe (a, s a)
pop s = liftA2 (,) (top s) (rest s)

instance Stacklike [] where
emptyStack = []
push   = (:)
top= foldr (\x _ - Just x) Nothing
rest []  = Nothing
rest (Push _ xs) = Just xs

data MyStack a = Empty | Push a (MyStack a)

instance Stacklike MyStack where
emptyStack = Empty
push   = Push

top Empty  = Nothing
top (Push x _) = Just x

rest Empty   = Nothing
rest (Push _ xs) = Just xs


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Relational Algebra library: first version on GitHub

2012-07-21 Thread Ertugrul Söylemez
Hello there Paul,

Paul Visschers m...@paulvisschers.net wrote:

 A couple of weeks ago I asked if there was interest in a library that
 implements a type-safe relational algebra. The response was positive,
 so I have spruced up the code I had a bit and created a repository on
 GitHub at:

 https://github.com/PaulVisschers/relational-algebra

 It is a very rudimentary version. The code is not documented and there
 is only a very basic example database in Test.hs. It might be helpful
 to look at HaskellDB's PrimQuery and PrimExpr, as this library is
 mostly a direct copy from that (but typed). I will add some decent
 examples of expressions and queries shortly.

 If you check it out, please comment on it and let me know if you want
 to contribute. Since this is going to be my first release, any
 feedback is welcome.

Well, the demonstration could be a bit more comprehensive.  I would be
very interested in seeing queries, especially nontrivial ones with joins
and such.

Would you mind writing a more comprehensive demonstration?


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] What is the surefire way to handle all exceptions and make sure the program doesn't fail?

2012-07-17 Thread Ertugrul Söylemez
Hello there Yifan,

exception handling should be done on a per-context basis, where the
developer establishes the notion of context.  Most of the time this
boils down to releasing resources:

forkIO (doStuffWith h `finally` hClose h)

In more complicated scenarios, where you actually need to /handle/ the
exception you should probably wrap some control concept around it.
There are many options.  You could just catch and handle the exception.
Other options include a resumable monad (like monad-coroutine) that
brings everything back into a consistent state.

Exception handling is convenient in Haskell.  You should probably just
try to enforce some of the exception cases by using the server in a
wrong way.  Close the connection prematurely or send Unix signals.  Note
that you need to handle signals separately.  In particular by default a
SIGPIPE, which can in fact be thrown by the networking system, needs to
be ignored:

import System.Posix.Signal

main :: IO ()
main =
withSocketsDo $ do
installHandler sigPIPE Ignore Nothing

Finally for both efficiency and safety make use of a stream processing
abstraction like conduit, enumerator or pipes.


Greets,
Ertugrul


Yifan Yu yvi...@gmail.com wrote:

 First of all, apologise if the question is too broad. The background
 goes like this: I've implemented a server program in Haskell for my
 company intended to replace the previous one written in C which
 crashes a lot (and btw the technology of the company is exclusively
 C-based).  When I chose Haskell I promised my manager (arrogantly - I
 actually made a bet with him), it won't crash. Now it has been
 finished (with just a few hundred LOC), and my test shows that it is
 indeed very stable. But by looking at the code again I'm a little
 worried, since I'm rather new to exception handling and there're many
 networking-related functions in the program. I was tempted to catch
 (SomeException e) at the very top-level of the program and try to
 recursively call main to restart the server in case of any exception
 being thrown, but I highly doubt that is the correct and idiomatic
 way. There are also a number of long-running threads launched from the
 main thread, and exceptions thrown from these threads can't be caught
 by the top-level `catch' in the main thread. My main function looks
 like this:

 main :: IO ()
 main = withSocketsDo $ do
 sCameraU - socketNewPassive False 6000
 sStunU   - socketNewPassive False 3478
 sCmdT- socketNewPassive True  7000
 mvarCam  - newMVar M.empty
 mvarLog  - newMVar []

 forkIO $ regCamera sCameraU mvarCam mvarLog
 forkIO $ updCamera mvarCam mvarLog
 forkIO $ stun sCameraU sStunU mvarCam mvarLog

 listen sCmdT 128
 processCmd sCmdT mvarCam mvarLog

 sClose sCameraU
 sClose sStunU
 sClose sCmdT

 I find that I can't tell whether a function will throw any exception
 at all, or what exceptions will be thrown, by looking at their
 documentation. I can only tell if I browse the source code. So the
 question is, how can I determine all the exceptions that can be thrown
 by a given function? And what is the best way to handle situations
 like this, with both the long-running threads and main thread need to
 be restarted whenever exceptions happen.


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


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


Re: [Haskell-cafe] Plain lambda inside banana brackets in the arrow notation

2012-07-15 Thread Ertugrul Söylemez
Ross Paterson r...@soi.city.ac.uk wrote:

 Though one possibility that might get us most of the way there would
 be to refactor the Arrow class as

   class PreArrow a where
 premap :: (b - b') - a b' c - a b c

Note that you are reinventing the 'profunctors' package here.  Every
arrow forms a profunctor with the following identities:

lmap = flip (^)
rmap = fmap

or alternatively:

rmap = (^)


Greets,
Ertugrul

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


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


Re: [Haskell-cafe] Interest in typed relational algebra library?

2012-07-07 Thread Ertugrul Söylemez
Paul Visschers m...@paulvisschers.net wrote:

 I've been out of the Haskell game for a bit, but now I'm back. A
 couple of years ago I made a small library that implements relational
 algebra with types so that malformed queries and other operations are
 caught at compile time. It is heavily based off of the internals of
 HaskellDB (see
 http://hackage.haskell.org/packages/archive/haskelldb/2.1.1/doc/html/Database-HaskellDB-PrimQuery.html),
 but types so that it can actually be used directly instead of having
 to use HaskellDB's query monad. Besides the joy of using relational
 algebra directly in your code, this also means that you can make
 query-optimizing code in a type-safe way, you can subquery results
 returned by the database directly without accessing the database again
 and you have more options when converting from relation algebra to SQL
 or another query language. The library isn't quite ready for release,
 but I might want to work on it a bit and then release it. Is anyone
 interested in such a library?

As someone who enjoyed the HaskellDB library I'm very interested in such
a library, even though nowadays I mostly use acid-state.


Greets,
Ertugrul

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


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


  1   2   >