[Haskell-cafe] ANNOUNCE: xournal-convert-0.1

2011-12-27 Thread Ian-Woo Kim
Hi, all,

I have uploaded a utility program xournal-convert which is a
command-line utility for changing xournal file format to various other
formats. Currently, converting xournal file format (xoj) to several
SVG files for each page and index.html for navigating all those pages
are implemented. I will support more output formats as I implement. I
think that SVG/html support must be useful to some people as it is
now.
This program depends on xournal-types, xournal-render and
xournal-parser libraries which are also used for hxournal program ( a
notetaking program written in haskell. similar to xournal)

Installation should be simple.
Just type
 cabal update
 cabal install xournal-convert

In command line, you can run the program like
 xournal-convert makesvg --dest=[destination folder] xojfilename
Currently, this program only accepts gunzipped xoj file. For xoj file
you generated from xournal program, you need to rename the file as
xxx.xoj.gz (xxx is some filename) and gunzip xxx.xoj.gz to make
gunzipped xoj format file. For files from hxournal, you can just use
the file directly.

By this program, you can simply generate static webpages for each
xournal file. I personally found this useful for reading my notes on
the web.

Note:
As for hxournal, the current version is 0.6.1.0. It currently supports
pdf background and has undo/redo and smoother scrolling (not completed
yet though). If you are interested, please try the latest version.

Thank you for your interest. Happy holidays.

best regards,
Ian-Woo Kim

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


Re: [Haskell-cafe] Reifying case expressions [was: Re: On stream processing, and a new release of timeplot coming]

2011-12-27 Thread Sebastian Fischer
On Tue, Dec 27, 2011 at 5:35 AM, Eugene Kirpichov ekirpic...@gmail.comwrote:

  I wonder if now this datatype of yours is isomorphic to StreamSummary b
 r - StreamSummary a r.

 Not sure what you mean here. StreamSummary seems to be the same as
 ListConsumer but I don't see how functions from consumers to consumers are
 list transformers, i.e., functions from lists to lists.

 Well. They are isomorphic, if list transformers are represented as
 functions from lists. I'm assuming they could be with the other
 representation too.

 type ListT a b = forall r . ([b] - r) - ([a] - r)


I see! I think the type

type ContListTransformer a b = forall r . ListConsumer b r -
ListConsumer a r

is isomorphic to `ListConsumer a [b]`. Here are the isomorphisms (I did not
check whether they are indeed isomorphisms):

clt2lc :: ContListTransformer a b - ListConsumer a [b]
clt2lc clt = clt idC

lc2clt :: ListConsumer a [b] - ContListTransformer a b
lc2clt _   (Done r)   = Done r
lc2clt (Done [])   (Continue r _) = Done r
lc2clt (Done (b:bs))   (Continue _ f) = lc2clt (Done bs) (f b)
lc2clt (Continue bs f) c  =
  Continue (consumeList c bs) (\a - lc2clt (f a) c)

However, `ListTransformer a b` is less expressive because of it's
incremental nature. Every list transformer `t` satisfies the following
property for all `xs` and `ys`:

transformList t xs `isPrefixOf` transformList t (xs++ys)

List *consumers* don't need to follow this restriction. For example, the
consumer

Continue [1] (\_ - Done [])

which represents the function

nonIncr [] = [1]
nonIncr _  = []

is not incremental in the sense above, because

not (nonIncr [] `isPrefixOf` nonIncr ([]++[0]))

I think it is the incremental nature of list transformers that allows them
to be composed in lock-step in the Category instance. `lc2clt` above is
sequential composition for list *consumers* but it applies the second
consumer only after executing the first completely.

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


Re: [Haskell-cafe] MIDI-controlled application

2011-12-27 Thread Tim Baumgartner
Hi Stephen,

2011/12/27 Stephen Tetley stephen.tet...@gmail.com

 Hi Tim

 More problematic is that FRP models hybrid (continuous and discrete)
 systems. For me at least, MIDI seems essentially discrete - a stream
 of control events. In MIDI files control events are twinned with a
 time stamp so they can be played. Presumably events are instantaneous
 in real-time interactive MIDI - not something I've looked at.


The events all feature a time stamp and my drum set produces lots of
CRTClock events for synchronization. I didn't use the time stamps in my
Java application but I would have to for recording/recognizing rhythms.


 Working with an FRP system like Yampa might add a lot of complexity,
 which admittedly you should be able to ignore


Yes, I'm a bit afraid of that.


 but initially it might
 be difficult to identify what parts are needed for a mostly discrete
 system like MIDI. (If you are time-stamping MIDI events yourself you
 will presumably need to sample a running clock which seems like a
 continuous behaviour...)

 Unfortunately I can't think of any systems in Haskell that are more
 discrete than continuous so you might have to choose a FRP system
 anyway.


I just had a glance at Peakachu. It seemed easier than Yampa to me. I liked
the Program abstraction. Perhaps I can use this...


 Incidentally, I've been working on a MIDI animation language for the
 last couple of days based on the animation language in Paul Hudak's
 book. I've wanted continuous behaviours to model modulating volumes
 (crescendos, decrescendos) and panning, but I've found the work tough
 going for modelling the note lists where I want the system discrete in
 both input (specification) and output.


This reminds me of the Yampa based synthesizer from the paper Switched-On
Yampa. I just looked into it.


 Best wishes

 Stephen


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


Re: [Haskell-cafe] Reifying case expressions [was: Re: On stream processing, and a new release of timeplot coming]

2011-12-27 Thread Heinrich Apfelmus

Sebastian Fischer wrote:

Heinrich Apfelmus wrote:

Likewise, each function from lists can be represented in terms of our new
data type [...]

   length' :: ListTo a Int
   length' = CaseOf
   (0)
   (\x - fmap (1+) length')

   length = interpret length'


This version of `length` is tail recursive while the previous version is
not. In general, all functions defined in terms of `ListTo` and `interpret`
are spine strict - they return a result only after consuming all input list
constructors.

This is what Eugene observed when defining the identity function as

idC = CaseOf [] (\x - (x:) $ idC)

This version does not work for infinite lists. Similarly, `head` and `take`
cannot be defined as lazily as in the standard libraries.


Indeed, the trouble is that my original formulation cannot return a 
result before it has evaluated all the case expressions. To include 
laziness, we need a way to return results early.


Sebastian's  ListTransformer  type does precisely that for the special 
case of lists as results, but it turns out that there is also a 
completely generic way of returning results early. In particular, we can 
leverage lazy evaluation for the result type.


The idea is, of course, to reify another function. This time, it's going 
to be  fmap


data ListTo a b where
Fmap   :: (b - c) - ListTo a b - ListTo a c
CaseOf :: b - (a - ListTo a b) - ListTo a b

(GADT syntax due to the existential quantification implied by Fmap ). To 
see why this works, have a look at the interpreter


interpret :: ListTo a b - ([a] - b)
interpret (Fmap f g)= fmap f (interpret g)
interpret (CaseOf nil cons) = \ys - case ys of
[] - nil
(x:xs) - interpret (cons x) xs

In the case of functions, fmap  is simply function concatenation

fmap f (interpret g) = f . interpret g

Now, the point is that our interpretation returns part of the result 
early whenever  the function  f  is lazy and returns part of the result 
early. For instance, we can write the identity function as


idL :: ListTo a [a]
idL = CaseOf [] $ \x - Fmap (x:) idL

When interpreted, this function will perform a pattern match on the 
input list first, but then the  Fmap  will ensure that we return the 
first element of the result. This seems incredible, so I encourage the 
reader to check this by looking at the reduction steps for the expression


interpret idL (1:⊥)

To summarize, we do indeed have  id = interpret idL .


Of course, the result type is not restricted to lists, any other type 
will do. For instance, here the definition of a short-circuiting  and


andL :: ListTo Bool Bool
andL = CaseOf True $ \b - Fmap (\c - if b then c else False) andL

testAnd = interpret andL (True:False:undefined)
-- *ListTo testAnd
-- False

With the right applicative instance, it also possible to implement  take 
and friends, see also the example code at


  https://gist.github.com/1523428

Essentially, the  Fmap  constructor also allows us to define a properly 
lazy function  const .




To avoid confusion, I chose new names for my new types.

data ListConsumer a b
  = Done !b
  | Continue !b (a - ListConsumer a b)


I know that you chose these names to avoid confusion, but I would like 
to advertise again the idea of choosing the *same* names for the 
constructors as the combinators they represent


data ListConsumer a b
= Const b
| CaseOf b (a - ListConsumer a b)

interpret :: ListConsumer a b - ([a] - b)
interpret (Const b) = const b
interpret (CaseOf nil cons) = \ys - case ys of
[] - nil
(x:xs) - interpret (const x) xs

This technique for designing data structures has the huge advantage that 
it's immediately clear how to interpret it and which laws are supposed 
to hold. Especially in the case of lists, I think that this approach 
clears up a lot of confusion about seemingly new concepts like Iteratees 
and so on: Iteratees are just ordinary functions [a] - b, albeit with a 
slightly different representation in terms of familiar combinators like 
 case of, const, or fmap.


The turn combinators into constructors technique is the staple of 
designing combinator libraries and goes back to at least Hughes' famous 
paper


  John Hughes. The Design of a Pretty-printing Library. (1995)
  http://citeseer.ist.psu.edu/viewdoc/summary?doi=10.1.1.38.8777


Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


[Haskell-cafe] GHC 7.4: Expected behavior or bug?

2011-12-27 Thread Michael Snoyman
Thanks to Mark Wright for pointing this out[1].

We have the equivalent of the following code in persistent:

{-# LANGUAGE MultiParamTypeClasses #-}
data Key backend entity = Key

class Monad (b m) = Foo b m where
func :: b m (Key b m)

This code works fine with GHC 7.0, but I get the following message from GHC 7.4:

Expecting two more arguments to `b'
In the type `b m (Key b m)'
In the class declaration for `Foo'

Is this expected behavior, or a bug? If the former, what would be a
possible workaround?

Thanks,
Michael

[1] https://github.com/yesodweb/persistent/issues/31

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


Re: [Haskell-cafe] GHC 7.4: Expected behavior or bug?

2011-12-27 Thread Bas van Dijk
On 27 December 2011 17:38, Michael Snoyman mich...@snoyman.com wrote:
 Thanks to Mark Wright for pointing this out[1].

 We have the equivalent of the following code in persistent:

 {-# LANGUAGE MultiParamTypeClasses #-}
 data Key backend entity = Key

 class Monad (b m) = Foo b m where
    func :: b m (Key b m)

 This code works fine with GHC 7.0, but I get the following message from GHC 
 7.4:

    Expecting two more arguments to `b'
    In the type `b m (Key b m)'
    In the class declaration for `Foo'

 Is this expected behavior, or a bug? If the former, what would be a
 possible workaround?

 Thanks,
 Michael

 [1] https://github.com/yesodweb/persistent/issues/31

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

I fixed a similar breakage in the hmatrix library:

https://github.com/AlbertoRuiz/hmatrix/commit/a4f38eb196209436f72b938f6355f6e28474bef3

I don't know if it's a bug in GHC, but the workaround is to add an
explicit kind signature:

{-# LANGUAGE KindSignatures, MultiParamTypeClasses #-}
data Key (backend :: * - * - *) entity = Key

class Monad (b m) = Foo b m where
   func :: b m (Key b m)

Cheers,

Bas

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


Re: [Haskell-cafe] MIDI-controlled application

2011-12-27 Thread Yves Parès
If you're afraid of Yampa (I was ;p), Ertugrul Söylemez released recently
the Netwire http://hackage.haskell.org/package/netwire-3.1.0 library on
hackage.
I went through its internals and I find it simpler to grasp and to use than
Yampa as Ertugrul chose to replace the switch functions by the use of
ArrowChoice. Yet I don't know if the latter wholly supersedes the former.
Plus I like the fact it doesn't depend on IO (you can handle automatons in
pure code).

And if you're to stick with Yampa, you might wanna look at
Animas.http://hackage.haskell.org/package/Animas-0.2
It's a fork of Yampa. I don't the advantages it brings or what I changes,
but its documentation on hackage is far more complete.

2011/12/27 Tim Baumgartner baumgartner@googlemail.com

 Hi Haskellers!

 I'm writing my first non-trivial Haskell application. I have an electronic
 drum set that generates MIDI events that I process with Haskell. A simple
 application of this kind might have fixed drums associated with fixed
 commands (I've done that). The next step would be to display menus (with
 very large font...) that show commands and the associated drums. The menu
 structure should be derived from the commands active in each context. Up to
 this point, I implemented this already in Java. But now after some
 successful attempts in Haskell, I plan for more features: the user should
 ultimately be able to record his own triggers, i.e. short drum rhythms,
 and associate them with actions. Since I'm still a beginner with only some
 basic experience in Monads, Arrows and their transformers, there is
 infinite knowledge to be gained by working on this problem (both library
 and concrete apps).

 Currently I'm using a monad that combines Parsec (with MIDI event stream)
 and a Writer (that writes commands that should result in IO). It's done in
 a way that during running the monad, many parses can be done and failing
 parses roll back the parser state so that a new parse can be tried.

 Now my questions:
 I have read about Yampa, but I have not mastered it yet. E.g. I don't
 understand switches. Could my triggers be realized with Yampa's events
 and switches?
 Would you recommend any other approach?
 Is there something similar somewhere?

 Regards
 Tim


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


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


Re: [Haskell-cafe] MIDI-controlled application

2011-12-27 Thread Stephen Tetley
Hi Tim

Events in FRP / Yampa are typically key presses / mouse movement, so a
MIDI controller generating Note-on / Note-off events would be a direct
analogue to key presses.

More problematic is that FRP models hybrid (continuous and discrete)
systems. For me at least, MIDI seems essentially discrete - a stream
of control events. In MIDI files control events are twinned with a
time stamp so they can be played. Presumably events are instantaneous
in real-time interactive MIDI - not something I've looked at.

Working with an FRP system like Yampa might add a lot of complexity,
which admittedly you should be able to ignore - but initially it might
be difficult to identify what parts are needed for a mostly discrete
system like MIDI. (If you are time-stamping MIDI events yourself you
will presumably need to sample a running clock which seems like a
continuous behaviour...)

Unfortunately I can't think of any systems in Haskell that are more
discrete than continuous so you might have to choose a FRP system
anyway.


Incidentally, I've been working on a MIDI animation language for the
last couple of days based on the animation language in Paul Hudak's
book. I've wanted continuous behaviours to model modulating volumes
(crescendos, decrescendos) and panning, but I've found the work tough
going for modelling the note lists where I want the system discrete in
both input (specification) and output.

Best wishes

Stephen

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


Re: [Haskell-cafe] GHC 7.4: Expected behavior or bug?

2011-12-27 Thread Michael Snoyman
On Tue, Dec 27, 2011 at 6:47 PM, Bas van Dijk v.dijk@gmail.com wrote:
 On 27 December 2011 17:38, Michael Snoyman mich...@snoyman.com wrote:
 Thanks to Mark Wright for pointing this out[1].

 We have the equivalent of the following code in persistent:

 {-# LANGUAGE MultiParamTypeClasses #-}
 data Key backend entity = Key

 class Monad (b m) = Foo b m where
    func :: b m (Key b m)

 This code works fine with GHC 7.0, but I get the following message from GHC 
 7.4:

    Expecting two more arguments to `b'
    In the type `b m (Key b m)'
    In the class declaration for `Foo'

 Is this expected behavior, or a bug? If the former, what would be a
 possible workaround?

 Thanks,
 Michael

 [1] https://github.com/yesodweb/persistent/issues/31

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

 I fixed a similar breakage in the hmatrix library:

 https://github.com/AlbertoRuiz/hmatrix/commit/a4f38eb196209436f72b938f6355f6e28474bef3

 I don't know if it's a bug in GHC, but the workaround is to add an
 explicit kind signature:

 {-# LANGUAGE KindSignatures, MultiParamTypeClasses #-}
 data Key (backend :: * - * - *) entity = Key

 class Monad (b m) = Foo b m where
   func :: b m (Key b m)

 Cheers,

 Bas

Thanks Bas, that seems to solve the problem.

Michael

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


Re: [Haskell-cafe] ANNOUNCE: hxournal-0.5.0.0 - A pen notetaking

2011-12-27 Thread Ian-Woo Kim
Hi, Greg,

Sorry that I just missed to read your reply.
Since hxournal has a configuration file to specify input device and
also is activated on the toggle menu item Use X Input, you should be
able to experiment pen drawing now.

Did you succeed in using the latest version of hxournal?
I appreciate your report.

Thanks very much.

best,
Ian-Woo

On Tue, Dec 13, 2011 at 5:22 AM, Greg Weber g...@gregweber.info wrote:
 I got the program installed after creating the libstdc++.so symlink.
 No ink shows up from my drawing though. I am on a Thinkpad X201 Tablet and
 xournal works.

 I am glad you are experimenting with window splits. I think the worst part
 of xournal is it constrains you to a notebook-width piece of paper.

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


Re: [Haskell-cafe] ANNOUNCE: hxournal-0.5.0.0 - A pen notetaking

2011-12-27 Thread Greg Weber
yes it worked after your updates shortly after this. Thank you very much
for checking up, and also for continuing to develop this - I may be able to
replace xournal with it now.

On Tue, Dec 27, 2011 at 10:03 AM, Ian-Woo Kim ianwoo...@gmail.com wrote:

 Hi, Greg,

 Sorry that I just missed to read your reply.
 Since hxournal has a configuration file to specify input device and
 also is activated on the toggle menu item Use X Input, you should be
 able to experiment pen drawing now.

 Did you succeed in using the latest version of hxournal?
 I appreciate your report.

 Thanks very much.

 best,
 Ian-Woo

 On Tue, Dec 13, 2011 at 5:22 AM, Greg Weber g...@gregweber.info wrote:
  I got the program installed after creating the libstdc++.so symlink.
  No ink shows up from my drawing though. I am on a Thinkpad X201 Tablet
 and
  xournal works.
 
  I am glad you are experimenting with window splits. I think the worst
 part
  of xournal is it constrains you to a notebook-width piece of paper.

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


[Haskell-cafe] MIDI-controlled application

2011-12-27 Thread Tim Baumgartner
Hi Haskellers!

I'm writing my first non-trivial Haskell application. I have an electronic
drum set that generates MIDI events that I process with Haskell. A simple
application of this kind might have fixed drums associated with fixed
commands (I've done that). The next step would be to display menus (with
very large font...) that show commands and the associated drums. The menu
structure should be derived from the commands active in each context. Up to
this point, I implemented this already in Java. But now after some
successful attempts in Haskell, I plan for more features: the user should
ultimately be able to record his own triggers, i.e. short drum rhythms,
and associate them with actions. Since I'm still a beginner with only some
basic experience in Monads, Arrows and their transformers, there is
infinite knowledge to be gained by working on this problem (both library
and concrete apps).

Currently I'm using a monad that combines Parsec (with MIDI event stream)
and a Writer (that writes commands that should result in IO). It's done in
a way that during running the monad, many parses can be done and failing
parses roll back the parser state so that a new parse can be tried.

Now my questions:
I have read about Yampa, but I have not mastered it yet. E.g. I don't
understand switches. Could my triggers be realized with Yampa's events
and switches?
Would you recommend any other approach?
Is there something similar somewhere?

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


Re: [Haskell-cafe] If you'd design a Haskell-like language, what would you do different?

2011-12-27 Thread Miguel Mitrofanov
27.12.2011, 07:30, "Alexander Solla" alex.so...@gmail.com:And why exactly should we limit ourselves to some theory you happen to like?Because the question was about MY IDEAL.  You're right. I'm confusing two different threads. My apologies.But (_|_) IS a concrete value.Um, perhaps in denotational semantics.  But even in that case, it is not a HASKELL value. Could you please clarify the meaning of "HASKELL value"? Does it mean something that can be represented in memory, fully evaluated? If so, infinite lists like [1..] aren't HASKELL value's either, which is rather limiting. Or is it something else?  You seem to be mixing up syntax and semantics. Unlikely. But, in case I'm wrong, I'd like to know what makes you think that I put any attention on syntax...But they ARE very similar to other values. They can be members of otherwise meaningful structures, and you can do calculations with these structures. "fst (1, _|_)" is a good and meaningful calculation. Mere syntax.So what?  ...except for this. See, I didn't want to argue about definitions here, so I didn't ask you why do you think of that as a syntactic issue. That was a mistake. So: what is the reason for you to say that "fst (1, _|_)" is a "mere syntax"? I am proposing we give Haskell bottoms semantics that bring it in line with the bottoms from various theories including lattice theory, the theory of sets, the theory of logic, as opposed to using denotational semantics' bottom semantic, which is unrealistic for a variety of reasons. Erm... but denotational semantics IS based on lattice theory (which, in turn, is based on the theory of sets). So how on Earth can they be "opposed" to each other?   Haskell bottoms can't be compared, due to Rice's theorem.  Haskell bottoms cannot be given an interpretation as a Haskell value. Well, lots of things can't be compared. Functions, for example. Do you mean that functions like "id" are not what you call "Haskell value"?  What happens to referential transparency when distinct things are all defined by the same equation?... = let x = x in xundefined, seq, unsafeCoerce, and many other "primitives" are defined using that equation.  (See GHC.Prim)  The Haskell definition for these distinct things /does nothing/.  It loops.  The semantics we get for them (an error message if we use undefined, a causal side-effect if we use seq, type coercion if we use unsafeCoerce) is done /magically/ by the compiler.  As far as Haskell, as a language, is concerned, all of these are bottom, and they are all /equal/, because of referential transparency/substitutionality. No. The mere fact that Prim.hs contains some stub doesn't mean anything. In fact, the Prim.hs header states: "It is not code to actually be used. Its only purpose is to be consumed by haddock." "seq" has a very clear semantics - and yes, I do mean denotational semantics here - which has nothing to do with Prim.hs "definition". Oops.  Indeed.Well, that's a different story.No, it's the same story that I've been telling. Yes, and again, I'm sorry for that. It is clear that denotational semantics is a Platonic model of constructive computation. Could you please stop offending abstract notions?What?  Platonic does not mean "bad". The way I see it, phylosphical notions are all offensive.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC 7.4: Expected behavior or bug?

2011-12-27 Thread Bas van Dijk
On 27 December 2011 17:47, Bas van Dijk v.dijk@gmail.com wrote:
 I fixed a similar breakage in the hmatrix library:

 https://github.com/AlbertoRuiz/hmatrix/commit/a4f38eb196209436f72b938f6355f6e28474bef3

GHC-7.4.1-rc1 also reported another type error in code that was
accepted by GHC = 7.2.2. These were the type errors I got:

[24 of 36] Compiling Numeric.LinearAlgebra.Algorithms (
lib/Numeric/LinearAlgebra/Algorithms.hs,
dist/build/Numeric/LinearAlgebra/Algorithms.o )

lib/Numeric/LinearAlgebra/Algorithms.hs:576:23:
No instance for (RealFrac (RealOf t0))
  arising from a use of `floor'
Possible fix:
  add an instance declaration for (RealFrac (RealOf t0))
In the expression: floor
In the second argument of `($)', namely
  `floor $ logBase 2 $ pnorm Infinity m'
In the expression: max 0 $ floor $ logBase 2 $ pnorm Infinity m

lib/Numeric/LinearAlgebra/Algorithms.hs:576:31:
No instance for (Floating (RealOf t0))
  arising from a use of `logBase'
Possible fix:
  add an instance declaration for (Floating (RealOf t0))
In the expression: logBase 2
In the second argument of `($)', namely
  `logBase 2 $ pnorm Infinity m'
In the second argument of `($)', namely
  `floor $ logBase 2 $ pnorm Infinity m'

lib/Numeric/LinearAlgebra/Algorithms.hs:576:39:
No instance for (Num (RealOf t0))
  arising from the literal `2'
Possible fix: add an instance declaration for (Num (RealOf t0))
In the first argument of `logBase', namely `2'
In the expression: logBase 2
In the second argument of `($)', namely
  `logBase 2 $ pnorm Infinity m'

lib/Numeric/LinearAlgebra/Algorithms.hs:576:43:
No instance for (Normed Matrix t0)
  arising from a use of `pnorm'
Possible fix: add an instance declaration for (Normed Matrix t0)
In the second argument of `($)', namely `pnorm Infinity m'
In the second argument of `($)', namely
  `logBase 2 $ pnorm Infinity m'
In the second argument of `($)', namely
  `floor $ logBase 2 $ pnorm Infinity m'

lib/Numeric/LinearAlgebra/Algorithms.hs:593:19:
No instance for (Container Vector t0)
  arising from a use of `add'
Possible fix: add an instance declaration for (Container Vector t0)
In the expression: add
In an equation for `|+|': |+| = add
In an equation for `expGolub':
expGolub m
  = iterate msq f !! j
  where
  j = max 0 $ floor $ logBase 2 $ pnorm Infinity m
  a = m */ fromIntegral ((2 :: Int) ^ j)
  q = geps eps
  eye = ident (rows m)
  

lib/Numeric/LinearAlgebra/Algorithms.hs:599:1:
Couldn't match type `t0' with `t'
  because type variable `t' would escape its scope
This (rigid, skolem) type variable is bound by
  the type signature for expm :: Field t = Matrix t - Matrix t
The following variables have types that mention t0
  expGolub :: Matrix t0 - Matrix t0
(bound at lib/Numeric/LinearAlgebra/Algorithms.hs:575:1)

Note that RealOf is a type family:

type family RealOf x

type instance RealOf Double = Double
type instance RealOf (Complex Double) = Double

type instance RealOf Float = Float
type instance RealOf (Complex Float) = Float

Adding the following explicit type signature fixed it:

expGolub :: ( Fractional t, Element t, Field t
, Normed Matrix t
, RealFrac (RealOf t)
, Floating (RealOf t)
) = Matrix t - Matrix t

I have no idea if this should be considered a bug.

Regards,

Bas

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


[Haskell-cafe] [ANNOUNCEMENT] github 0.1.1

2011-12-27 Thread Mike Burns
The Github API now has a fancy Haskell library for accessing it, and
this library is named: github.

  http://hackage.haskell.org/package/github
  https://github.com/mike-burns/github

The module structure reflects the Github API v3 documentation.

It currently only supports the non-authenticated parts of the API.

It does not support a few API endpoints which are documented by Github
but which don't work under a command-line curl.

I love pull requests, so send 'em!

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


Re: [Haskell-cafe] Composing Enumeratees in enumerator

2011-12-27 Thread Michael Craig
Thanks for the replies, all. It's good to see that the other iteratee
packages out there are addressing this issue.

I still don't get why it's an issue in the first place. It seems to me like
a pretty simple thing to implement:

(=$=) :: (Monad m)
  = Enumeratee a0 a1 m (Step a2 m b) - Enumeratee a1 a2 m b
  - Enumeratee a0 a2 m b
(=$=) e01 e12 step = Iteratee $ do
step' - runIteratee $ e12 step
runIteratee . joinI $ e01 step'

This puts a type restriction on the LHS enumeratee, but enumeratees are
generally polymorphic in the last type param anyway. (And joinE has a
similar restriction when composing an enumerator with an enumeratee.)

Is there a good reason why enumerator doesn't export this or something
analogous?

Mike Craig


On Sun, Dec 25, 2011 at 10:20 PM, Conrad Parker con...@metadecks.orgwrote:

 On 24 December 2011 05:47, Michael Craig mks...@gmail.com wrote:
  I've been looking for a way to compose enumeratees in the enumerator
  package, but I've come up with nothing so far. I want this function
 
  (=$=) :: Monad m = Enumeratee a0 a1 m b - Enumeratee a1 a2 m b -
  Enumeratee a0 a2 m b
 
  I'm building a modular library on top of enumerator that facilitates
 reading
  time series data from a DB, applying any number of transformations to it,
  and then writing it back / doing something else with it. I'd like to be
 able
  to write simple transformations (enumeratees) and compose them without
  binding them to either a db reader (enumerator) or db writer (iteratee).
 
  I've been looking at the iterIO package as a possible alternative,
 because
  it seems to allow easy composition of Inums (enumeratees). I'm a little
  skittish of it because it seems unpopular next to enumerator.

 Hi Michael,

 You could also look at the iteratee package. This is the signature of
 the () operator:

 () :: (Nullable s1, Monad m) = (forall x. Enumeratee s1 s2 m x) -
 Enumeratee s2 s3 m a - Enumeratee s1 s3 m a

 it's quite useful for composing enumeratees, likewise its friend ()
 swims the other way.


 http://hackage.haskell.org/packages/archive/iteratee/0.8.7.5/doc/html/Data-Iteratee-Iteratee.html

 cheers,

 Conrad.

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


[Haskell-cafe] Haskell Platform and Windows - where's 2011.4?

2011-12-27 Thread Steve Horne


On haskell.org, the 2011.4.0.0 version is shown as the current stable 
release - but the most recent download link is for the 2011.2.0.0 version.


This is bugging me a little because the documentation in the 2011.2 
Haskell Platform download for Windows is broken - there's at least one 
bug report about this already. There's online documentation, but it's 
(1) online, where I need something I can read on an old no-internet 
laptop, and (2) I assume for the most recent version, and therefore it 
potentially misleading.


I already fixed the online side - sorry, I know slurping a whole site 
is evil but I had little choice. The fact that the docs relate to a 
version of the platform that I can't access remains. I just have to hope 
that the changes are few and won't affect me.


Extra annoying - there's no mention of why 2011.4 is missing from the 
Windows download page - no temporarily delayed or skipped due to an 
awkward technical issue or not enough Windows developers 
volunteering. For all I know, it could just be an oversight updating 
haskell.org itself, but I think that's unlikely.


So... what's the situation with the Haskell Platform on Windows? - both 
WRT my specific bit of whinging and whining, and in general?


Is Windows a low priority niche from the Haskell POV? If I intend to 
take Haskell more seriously, do I need to make Linux or some other *nix 
my primary OS?


Please say no - I've been an on-and-off Linux user for around 10 years, 
with the most recent 2 years on ending around May this year. For all the 
pros, the cons of endless graphics card driver issues, awkward 
configuration hassles and so on have defeated me yet again.



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


Re: [Haskell-cafe] Haskell Platform and Windows - where's 2011.4?

2011-12-27 Thread Bas van Dijk
On 27 December 2011 19:13, Steve Horne sh006d3...@blueyonder.co.uk wrote:
 On haskell.org, the 2011.4.0.0 version is shown as the current stable
 release - but the most recent download link is for the 2011.2.0.0 version.

What download link are you referring to? I see that:
http://hackage.haskell.org/platform/windows.html correctly points to
the 2011.4.0.0 release.

Bas

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


Re: [Haskell-cafe] GHC 7.4: Expected behavior or bug?

2011-12-27 Thread José Pedro Magalhães
Hi,

This is a change in behavior. Previously GHC was more liberal than Haskell
98 prescribed, and would not default the kind of otherwise unconstrained
type variables to *. 7.4 does default to *, so you have to provide kind
signatures when you want another kind (particularly in phantom type
variables).


Cheers,
Pedro

On Tue, Dec 27, 2011 at 16:47, Bas van Dijk v.dijk@gmail.com wrote:

 On 27 December 2011 17:38, Michael Snoyman mich...@snoyman.com wrote:
  Thanks to Mark Wright for pointing this out[1].
 
  We have the equivalent of the following code in persistent:
 
  {-# LANGUAGE MultiParamTypeClasses #-}
  data Key backend entity = Key
 
  class Monad (b m) = Foo b m where
 func :: b m (Key b m)
 
  This code works fine with GHC 7.0, but I get the following message from
 GHC 7.4:
 
 Expecting two more arguments to `b'
 In the type `b m (Key b m)'
 In the class declaration for `Foo'
 
  Is this expected behavior, or a bug? If the former, what would be a
  possible workaround?
 
  Thanks,
  Michael
 
  [1] https://github.com/yesodweb/persistent/issues/31
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe

 I fixed a similar breakage in the hmatrix library:


 https://github.com/AlbertoRuiz/hmatrix/commit/a4f38eb196209436f72b938f6355f6e28474bef3

 I don't know if it's a bug in GHC, but the workaround is to add an
 explicit kind signature:

 {-# LANGUAGE KindSignatures, MultiParamTypeClasses #-}
 data Key (backend :: * - * - *) entity = Key

 class Monad (b m) = Foo b m where
   func :: b m (Key b m)

 Cheers,

 Bas

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

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


Re: [Haskell-cafe] Haskell Platform and Windows - where's 2011.4?

2011-12-27 Thread Don Stewart
All versions went live last week. Are you perhaps looking at an expired or
cached page?

On Tuesday, December 27, 2011, Bas van Dijk v.dijk@gmail.com wrote:
 On 27 December 2011 19:13, Steve Horne sh006d3...@blueyonder.co.uk
wrote:
 On haskell.org, the 2011.4.0.0 version is shown as the current stable
 release - but the most recent download link is for the 2011.2.0.0
version.

 What download link are you referring to? I see that:
 http://hackage.haskell.org/platform/windows.html correctly points to
 the 2011.4.0.0 release.

 Bas

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

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


Re: [Haskell-cafe] Haskell Platform and Windows - where's 2011.4?

2011-12-27 Thread Steve Horne

On 27/12/2011 18:36, Bas van Dijk wrote:

On 27 December 2011 19:13, Steve Hornesh006d3...@blueyonder.co.uk  wrote:

On haskell.org, the 2011.4.0.0 version is shown as the current stable
release - but the most recent download link is for the 2011.2.0.0 version.

What download link are you referring to? I see that:
http://hackage.haskell.org/platform/windows.html correctly points to
the 2011.4.0.0 release.

Bas


From http://hackage.haskell.org/platform/

Click Windows to reach http://hackage.haskell.org/platform/windows.html

Seems to be the same page you're referring to, but no 2011.4 link.

Just in case, I forced a page refresh - and got a surprise when that 
fixed it.


OK - I really should have tried that before. But... why would an old 
page hang around in my Firefox cache so long and not get updated? I've 
not had this on any other sites.



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


Re: [Haskell-cafe] Haskell Platform and Windows - where's 2011.4?

2011-12-27 Thread Steve Horne

On 27/12/2011 18:57, Steve Horne wrote:
OK - I really should have tried that before. But... why would an old 
page hang around in my Firefox cache so long and not get updated? I've 
not had this on any other sites.

I still should be doing more checking before posting.

A look in the source for the page doesn't show any odd metadata or 
anything. Whatever the issue is, it's my end.


Sorry everyone.


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


Re: [Haskell-cafe] GHC 7.4: Expected behavior or bug?

2011-12-27 Thread Michael Snoyman
Thanks for the explanation.

2011/12/27 José Pedro Magalhães j...@cs.uu.nl:
 Hi,

 This is a change in behavior. Previously GHC was more liberal than Haskell
 98 prescribed, and would not default the kind of otherwise unconstrained
 type variables to *. 7.4 does default to *, so you have to provide kind
 signatures when you want another kind (particularly in phantom type
 variables).


 Cheers,
 Pedro


 On Tue, Dec 27, 2011 at 16:47, Bas van Dijk v.dijk@gmail.com wrote:

 On 27 December 2011 17:38, Michael Snoyman mich...@snoyman.com wrote:
  Thanks to Mark Wright for pointing this out[1].
 
  We have the equivalent of the following code in persistent:
 
  {-# LANGUAGE MultiParamTypeClasses #-}
  data Key backend entity = Key
 
  class Monad (b m) = Foo b m where
     func :: b m (Key b m)
 
  This code works fine with GHC 7.0, but I get the following message from
  GHC 7.4:
 
     Expecting two more arguments to `b'
     In the type `b m (Key b m)'
     In the class declaration for `Foo'
 
  Is this expected behavior, or a bug? If the former, what would be a
  possible workaround?
 
  Thanks,
  Michael
 
  [1] https://github.com/yesodweb/persistent/issues/31
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe

 I fixed a similar breakage in the hmatrix library:


 https://github.com/AlbertoRuiz/hmatrix/commit/a4f38eb196209436f72b938f6355f6e28474bef3

 I don't know if it's a bug in GHC, but the workaround is to add an
 explicit kind signature:

 {-# LANGUAGE KindSignatures, MultiParamTypeClasses #-}
 data Key (backend :: * - * - *) entity = Key

 class Monad (b m) = Foo b m where
   func :: b m (Key b m)

 Cheers,

 Bas

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



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


[Haskell-cafe] GHC 7.4 and binutils-gold

2011-12-27 Thread Michael Snoyman
Hi all,

One other little GHC 7.4 note. When I first tried building code with
it, I got the following error message:

/usr/bin/ld: --hash-size=31: unknown option

Once I uninstalled binutils-gold, everything went just fine. Has
anyone else experienced this? I'm running Ubuntu Oneiric.

Michael

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


Re: [Haskell-cafe] How hard is it to start a web startup using Haskell?

2011-12-27 Thread Martin DeMello
A good compromise might be opa (not used it myself, but I've been
reading up on it as a possible candidate for any personal web projects
I might want to do). It is not haskell, but it is ML-derived, and
specifically for webapps. It has some example apps available, though
nothing near the volume of apps rails or django would have.

martin

On Mon, Dec 26, 2011 at 6:17 PM, Haisheng Wu fre...@gmail.com wrote:

 Turns out that those guys doing start-up with Haskell are already expert at
 Haskell.
 Hence choosing Haskell is more straightforward.

 I'm thinking of using Haskell since it looks cool and beautiful.
 However I have little experience and will move slowly at certain begging
 period.
 This sounds not good to a startup company.

 Comparing with Django in Python, Rails in Ruby, yesod and snap looks not
 that mature.
 Also, for instance, I'd like to build up a CRM application company, I
 could leverage some open source projects in other languages.  In Haskell, we
 need to build from scratch basically.

 Appreciate your suggestions/comments.

 -Simon



 On Wed, Dec 21, 2011 at 2:30 AM, David Pollak
 feeder.of.the.be...@gmail.com wrote:



 On Mon, Dec 19, 2011 at 2:36 PM, Yves Parès limestr...@gmail.com wrote:

  Haskell is a mature platform that provides lots of goodies that I might
  otherwise have to write (like the goodies I wrote in Lift including an
  Actors library)

 I don't get it: Actors are at the core of Scala concurrency model,


 Actors as implemented in the Scala distribution were (and probably still
 are) horrid.  They have poor performance, memory retention issues, and an
 overall poor design.  When Lift relied on Scala's Actors, a Lift-comet site
 needed to be restarted every few weeks because of pent-up memory issues.  On
 the other hand, with Lift Actors, http://demo.liftweb.net has been running
 since July 7th.


 and are expanded for distributed programming through Akka for instance.


 Actually, no.  Scala's Actors are not expanded by Akka (although Akka
 Actors may replace the existing Actor implementation in the Scala library).
  Akka is yet another replacement for Scala's Actor library and Akka's
 distributed capabilities are weak and brittle.  Also, Lift's Actor library
 and Martin Odersky's flames about it paved the way for Akka because I took
 the heat that might have driven Jonas out of the Scala community when Akka
 was a small project.


 To me it'd be the other way around: you'd have to develop Actors in
 Haskell, don't you?


 I've come to understand that Actors are a weak concurrency/distribution
 paradigm.  Anything that has a type signature Any = Unit is not composable
 and will lead to the same kinds of issues that we're looking for the
 compiler in Haskell to help us with (put another way, if you like Smalltalk
 and Ruby, then Actors seem pretty cool.)

 On the other hand, many of Haskell's libraries (STM, Iteratees, etc.) have
 a much more composable set of concurrency primitives.


 Or maybe you don't mean the same thing by 'Actor'?


 2011/12/19 David Pollak feeder.of.the.be...@gmail.com

 On Mon, Dec 19, 2011 at 2:04 AM, Ivan Perez
 ivanperezdoming...@gmail.com wrote:

 I'm actually trying to make a list of companies and people using
 Haskell
 for for-profit real world software development.

 I'd like to know the names of those startups, if possible.


 I am building http://visi.pro on Haskell.  I am doing it for a number of
 reasons:

 Haskell is a mature platform that provides lots of goodies that I might
 otherwise have to write (like the goodies I wrote in Lift including an
 Actors library)
 Haskell allows a lot of nice things that make building a language and
 associated tools easier (like laziness)
 Haskell is a filter for team members. Just like Foursquare uses Scala as
 a filter for candidates in recruiting, I'm using Haskell as a filter... if
 you have some good Haskell open source code, it's a way to indicate to me
 that you're a strong developer.




 -- Ivan

 On 18 December 2011 18:42, Michael Snoyman mich...@snoyman.com wrote:
  On Sun, Dec 18, 2011 at 6:57 PM, Gracjan Polak
  gracjanpo...@gmail.com wrote:
 
  Hi all,
 
  The question 'How hard is it to start a technical startup with
  Haskell?'
  happened a couple of times on this list. Sometimes it was in the
  form 'How hard
  is to find Haskell programmers?' or 'Are there any Haskell jobs?'.
 
  I'd like to provide one data point as an answer:
 
 
  http://www.reddit.com/r/haskell/comments/ngbbp/haskell_only_esigning_startup_closes_second_angel/
 
  Full disclosure: I'm one of two that founded this startup.
 
  How are others doing businesses using Haskell doing these days?
 
  I don't run a startup myself, but I know of at least three startups
  using Haskell for web development (through Yesod), and my company is
  basing its new web products on Yesod as well. I think there are
  plenty
  of highly qualified Haskell programmers out there, especially if
  you're willing to let someone work 

Re: [Haskell-cafe] MIDI-controlled application

2011-12-27 Thread Heinrich Apfelmus

Stephen Tetley wrote:

Events in FRP / Yampa are typically key presses / mouse movement, so a
MIDI controller generating Note-on / Note-off events would be a direct
analogue to key presses.

More problematic is that FRP models hybrid (continuous and discrete)
systems. For me at least, MIDI seems essentially discrete - a stream
of control events. In MIDI files control events are twinned with a
time stamp so they can be played. Presumably events are instantaneous
in real-time interactive MIDI - not something I've looked at.

Working with an FRP system like Yampa might add a lot of complexity,
which admittedly you should be able to ignore - but initially it might
be difficult to identify what parts are needed for a mostly discrete
system like MIDI. (If you are time-stamping MIDI events yourself you
will presumably need to sample a running clock which seems like a
continuous behaviour...)

Unfortunately I can't think of any systems in Haskell that are more
discrete than continuous so you might have to choose a FRP system
anyway.


Concerning FRP, I would like to advertise my reactive-banana library
here, which tries to follow Conal Elliott's semantics with behaviors and 
events.


  http://www.haskell.org/haskellwiki/Reactive-banana

I intend to do audio / MIDI programming in the future, so it's going to
be well-supported for your particular purpose, even. That said, I
haven't started to use it for MIDI myself yet, so I appreciate any kind
of feedback!

If you want to learn reactive-banana, I recommend that you have a look
at the source code of the model implementation in Reactive.Banana.Model.
It's intended to be really simple to understand and it's the
authoritative reference for the semantics of the actual implementation
(which is far from simple to understand). As you can see, the model uses
infinite lists. The advantage of the actual implementation, especially
for MIDI, is that it is *real-time*, something which is tricky to do 
with infinite lists. Still, you could probably use the model as a guide 
for cooking up your own FRP library.




Incidentally, I've been working on a MIDI animation language for the
last couple of days based on the animation language in Paul Hudak's
book. I've wanted continuous behaviours to model modulating volumes
(crescendos, decrescendos) and panning, but I've found the work tough
going for modelling the note lists where I want the system discrete in
both input (specification) and output.


Consider me interested. How does your approach compare to
Conal-style FRP with behaviors and events?


Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


Re: [Haskell-cafe] GHC 7.4 and binutils-gold

2011-12-27 Thread austin seipp
I encountered this problem approximately a month ago building HEAD and
reported it to Ian:

http://www.haskell.org/pipermail/cvs-ghc/2011-November/068562.html

His fix worked - but I was doing a build from source. The problem now
is that this is a -build-time- option, not a runtime option, but
you're using pre-built binaries: ones that were built on Linux systems
using GNU ld, not gold. So removing gold is basically your only hope
for the 7.4.1 RC.

Alternatively, you could probably tell GHC which ld to use by aliasing
GHC to something like 'ghc -pgml ld.ld' - Oneiric installs gold under
'ld.gold' and moves GNU ld to 'ld.ld' so you still have both
installed. It just updates the ld symlink to point to the gold binary
by default.

So if 7.4.1 final wants to support gold, this logic needs to be moved
to runtime somehow.

This should probably be discussed on cvs-ghc or glasgow-haskell-users
with Ian et al.

On Tue, Dec 27, 2011 at 4:00 PM, Michael Snoyman mich...@snoyman.com wrote:
 Hi all,

 One other little GHC 7.4 note. When I first tried building code with
 it, I got the following error message:

 /usr/bin/ld: --hash-size=31: unknown option

 Once I uninstalled binutils-gold, everything went just fine. Has
 anyone else experienced this? I'm running Ubuntu Oneiric.

 Michael

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



-- 
Regards,
Austin

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


[Haskell-cafe] Conduits: Is Source a valid instance of Monad?

2011-12-27 Thread Aristid Breitkreuz
Hi all,

As you may have noticed, Michael Snoyman has been working on an
alternative approach to I/O, called conduits. You can find it here:

https://github.com/snoyberg/conduit

When looking at the Source type (explained here:
http://www.yesodweb.com/blog/2011/12/conduits), I noticed that they
seem to behave like lists, and naturally wondered if I could write a
Monad instance for them. But first, let's have a brief look at the
definition of Source:

data SourceResult a = Open a | Closed

data PreparedSource m a = PreparedSource
{ sourcePull :: ResourceT m (SourceResult a)
, sourceClose :: ResourceT m ()
}

newtype Source m a = Source { prepareSource :: ResourceT m
(PreparedSource m a) }

ResourceT deals with resource acquisition and releasing (making sure
that all resources are released), and provides a an abstraction over
IORef/STRef. For our purposes here, ResourceT is probably close enough
to IO.


So now the question again is, can we write a Monad instance for this?
I have been able to write join (concatenate) and return (a source with
a single non-repeated) element.

https://gist.github.com/1525471

I _think_ it behaves properly like a Monad, but I'm not quite sure,
and neither was Michael. Greg Weber then suggested bringing the
question to this forum. What made the question difficult for me is
that this would be a stateful Monad transformer, so I'm not quite sure
how to test the Monad laws properly.


There's a second part to this question: If Source turns out not to be
a Monad, is it possibly a ZipList-like Applicative? And either way,
which is more useful: The list-like or the ziplist-like instances (of
Applicative/Monad)?



Thank you,

Aristid

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


Re: [Haskell-cafe] MIDI-controlled application

2011-12-27 Thread Tom Murphy
On Tue, Dec 27, 2011 at 3:54 AM, Tim Baumgartner 
baumgartner@googlemail.com wrote:

 Hi Haskellers!

 I'm writing my first non-trivial Haskell application. I have an
electronic drum set that generates MIDI events that I process with Haskell.
A simple application of this kind might have fixed drums associated with
fixed commands (I've done that).

[...]


 Currently I'm using a monad that combines Parsec (with MIDI event stream)
and a Writer (that writes commands that should result in IO). It's done in
a way that during running the monad, many parses can be done and failing
parses roll back the parser state so that a new parse can be tried.



Care to share your code?

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