Re: [Haskell-cafe] displaying conetents of a list

2009-05-12 Thread Daniel Peebles
Even more succinctly:

sequence_ . map is mapM_, and putStrLn . show is print, so you get:

mapM_ print films

Dan

On Sun, May 10, 2009 at 9:59 PM, Alex MDC alex@gmail.com wrote:
 2009/5/11 applebiz89 applebi...@hotmail.com

 I know to use show and putStrLn but I just don't know how to put them into
 the function correctly

 Well I hope we're not doing your homework for you but...

 As putStrLn is in the IO monad, listFilms should at least have a signature
 like this:

 listFilms :: [Film] - IO ()

 Now you know you want to call putStrLn on each item in the list. That means
 you want to join a bunch of functions return IO (). That sounds like a job
 for sequence_:

 listFilms films = sequence_ $ map (putStrLn.show) films

 Or the same thing more verbosely:

 listFilms [] = return ()
 listFilms (film:films)
  = do putStrLn (show film)
   listFilms films

 Hope that helps,
 Alex


 ___
 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] [ANNOUNCE] Bindings for libguestfs

2009-05-12 Thread Richard W.M. Jones
I added some partial bindings for libguestfs[1] here:

http://git.et.redhat.com/?p=libguestfs.git;a=blob;f=haskell/Guestfs.hs;hb=HEAD

Some very simple example programs which use these bindings:

http://git.et.redhat.com/?p=libguestfs.git;a=tree;f=haskell;hb=HEAD

Any comments welcome.  My Haskell skills are pretty terrible, so I'm
sure there are many ways these can be improved.

If someone wants to look at binding the rest of the API, then please
send me some patches.  (Note that the Guestfs.hs file is automatically
generated).

BTW, I found the documentation on writing FFIs very contradictory and
incomplete.  For example, I was completely defeated trying to find
ways to do simple stuff like passing in integers or returning
booleans.  *Potentially* Haskell's FFI seems like it might be one of
the best out of the languages I've used so far, but it needs way more
documentation and examples.

Rich.

[1] http://et.redhat.com/~rjones/libguestfs/

-- 
Richard Jones, Emerging Technologies, Red Hat  http://et.redhat.com/~rjones
virt-df lists disk usage of guests without needing to install any
software inside the virtual machine.  Supports Linux and Windows.
http://et.redhat.com/~rjones/virt-df/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Decoupling OpenAL/ALUT packages from OpenGL

2009-05-12 Thread Neil Brown

Sven Panne wrote:
Regarding Functor/Applicative: The obvious instances for e.g. a 2-dimensional 
vertex are:


   data Vertex2 a = Vertex2 a a

   instance Functor Vertex2 where
  fmap f (Vertex2 x y) = Vertex2 (f x) (f y)

   instance Applicative Vertex2 where
  pure a = Vertex2 a a
  Vertex2 f g * Vertex2 x y = Vertex2 (f x) (g y)

They fulfill all required laws, but are these the only possible instances? If 
not, are they at least the most canonical ones in a given sense? And 
finally: Does somebody have a real-world example where the Applicative 
instance is useful? Usages of the Functor instance are much more obvious for 
me.
  
I'd say those are the right instances.  Some obvious uses (perhaps more 
useful for Vector2 than Vertex2, but still) are:


liftA2 (+) (Vertex2 1 3) (Vertex2 4 5) == Vertex2 5 8
pure 0 == Vertex2 0 0

The latter being a useful shorthand to get a vertex for the origin.  
Also, if you define Foldable:


foldl1 (+) . liftA2 (*) v w == dotProduct v w

The useful thing being that that definition of dotProduct is the same 
for 2-, 3- and 4- dimensional things, and for vertexes and vectors.  So 
possible additions to your type-class list are Foldable and maybe 
Traversable (no harm, although I'd have to reach further for an example 
for this).  I guess the tricky decision might be whether to provide a 
Num instance  (again, probably more suitable for Vector2)?


instance Num a = Num (Vertex2 a) where
 (+) = liftA2 (+)
 (-) = liftA2 (-)
 (*) = liftA2 (*)
 abs = fmap abs
 signum = fmap signum
 negate = fmap negate
 fromInteger = pure . fromInteger

Even if you don't want to define Num, note how easy having the 
Applicative instance makes defining some of the operators :-)


Thanks,

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


Re: [Haskell-cafe] Classes: functional dependency (type - value)

2009-05-12 Thread Jason Dusek
2009/05/10 Belka lambda-be...@yandex.ru:
 Some real code using wished feature:

  This code has multiple issues:

 .  It is nearly unreadable as formatted.

 .  There are actual errors that would prevent it from compiling
(pattern match on `Left` and `Just` in the same `case`
expression!).

  Please amend the code so it is easier to read and test.

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


Re: [Haskell-cafe] Decoupling OpenAL/ALUT packages from OpenGL

2009-05-12 Thread David Duke


Sven,

Am Montag, 4. Mai 2009 13:33:33 schrieb David Duke:
  

Decoupling basic primitives for geometric modelling from OpenGL would be
useful. [...]
Even just data constructors and instances of these within Functor and
Applicative are a useful starting point. [...]

This leads me to the conclusion that I should only lift the data types for 
vectors and matrices out of the OpenGL package, including only instances for 
standard type classes like Eq, Ord, Functor, etc. This means that the new 
package will *not* include type classes for things like scalars, vector 
spaces, etc. These can be defined by the other packages in their own type 
class language. 
That seems a reasonable step.  If and when consensus does emerge on 
packaging vector  matrix operations, that could be added as a further 
package.  
Regarding Functor/Applicative: The obvious instances for e.g. a 2-dimensional 
vertex are:


   data Vertex2 a = Vertex2 a a

   instance Functor Vertex2 where
  fmap f (Vertex2 x y) = Vertex2 (f x) (f y)

   instance Applicative Vertex2 where
  pure a = Vertex2 a a
  Vertex2 f g * Vertex2 x y = Vertex2 (f x) (g y)

They fulfill all required laws, but are these the only possible instances? If 
not, are they at least the most canonical ones in a given sense? And 
finally: Does somebody have a real-world example where the Applicative 
instance is useful? Usages of the Functor instance are much more obvious for 
me.
  
The Vertex constructor and Applicative operators don't seem to admit 
anything different that is also sensible (unless someone has a use for 
* with function and/or args permuted).  As to real-world example, if 
you interpret a vertex as a (position) vector and want to apply that to 
another vertex, liftA2 (+) is neat.  For working with sampled data, we 
have something like


class Interp b where
 interpolate :: Float - b - b - b

with suitable instances for types in the numeric hierarchy, and then

instance (Interp a, Applicative f) = Interp (f a) where
 interp t = liftA2 (interp t)

If vertex is an instance of applicative, we then immediately have 
interpolation between coordinates (we use it in contour and surface 
extraction, others may find it useful in animation or distortion).


   David

--
Dr. David Duke  E: d...@comp.leeds.ac.uk
School of Computing W: www.comp.leeds.ac.uk/djd/
University of Leeds T: +44 113 3436800
Leeds, LS2 9JT, U.K.

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


[Haskell-cafe] Re[2]: [Gtk2hs-users] ANN: Gtk2HS 0.10.1 released

2009-05-12 Thread Bulat Ziganshin
Hello Peter,

Monday, May 11, 2009, 5:40:20 PM, you wrote:

 GHC 6.10.1 is now supported.

 6.10.2/6.10.3?

 Yes, those versions are supported as well. GHC 6.10.1 changed the way
 finalizers are handled, and as a result, Gtk2HS programs were
 crashing.  I don't think anything that affects Gtk2HS was changed in
 GHC 6.10.[23].

no, you mixed things a bit :)

6.10.1 was out in Nov 2008. gtk2hs 0.10 supports it

the change in finalizers was made in 6.10.2, issued in Apr 2009


and BIG THANKS to entire gtk2hs team: i'm really happy to finally get
production-level ghc 6.10 together with new gtk2hs



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


[Haskell-cafe] Data.Map lookup signature

2009-05-12 Thread Nico Rolle
Hi everyone.

The docs in the web on http://www.haskell.org/ghc/docs
define Data.Map.lookup as follows:
http://www.haskell.org/ghc/docs
lookup :: Ord k = k - Map k a - Maybe a
but my version of ghci does i like that:
Data.Map.lookup :: (Ord k, Monad m) = k - Data.Map.Map k a - m a
but i need the 1. one.
my version of ghci is 6.8.2
regards
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANN: Gtk2HS 0.10.1 released

2009-05-12 Thread Andy Stewart
Peter Gavin pga...@gmail.com writes:

 Hi everyone,

 I'd like to announce the release of Gtk2HS 0.10.1!  This release
 includes mostly bug fixes and other small improvements. Most notably,
 GHC 6.10.1 is now supported.

 The source tarball may be downloaded from:

 http://sourceforge.net/project/showfiles.php?group_id=49207package_id=42440

 A Windows installer will be provided soon.

 Thanks to all the contributors!
Now i use gtk2hs develop GUI program, and it's very nice integrate GTK
and Haskell.

Thanks gtk2hs team! :)

Hope gtk2hs will support *all* functional of GTK (newest version) in the 
feature.

  -- Andy

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


[Haskell-cafe] Fundep Curiosity

2009-05-12 Thread Christopher Lane Hinson


I've noticed that a large majority of fundeps I see in other people's 
libraries are written:


class C a b | b - a

Where the dependent parameter appears first in the MPTC.  Is there a 
reason for this?


AFAIK, there isn't any semantic significance to the order of parameters in 
an MPTC.  Why do many haskellers find this configuration more intuitive?


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


Re: [Haskell-cafe] Re: ANN: Gtk2HS 0.10.1 released

2009-05-12 Thread Daniel Peebles
I vaguely remember there being some finalizer behavior that changed in
6.10.2 that might affect this package. Not sure though.

On Sun, May 10, 2009 at 12:10 PM, Andy Stewart
lazycat.mana...@gmail.com wrote:
 Bulat Ziganshin bulat.zigans...@gmail.com writes:

 Hello Peter,

 Sunday, May 10, 2009, 7:43:38 PM, you wrote:

 I'd like to announce the release of Gtk2HS 0.10.1!  This release
 includes mostly bug fixes and other small improvements. Most notably,
 GHC 6.10.1 is now supported.

 6.10.2/6.10.3?
 I think 6.10.1 compatible with 6.10.2/6.10.3

 6.10.2/6.10.3 just fix some bug of 6.10.1

  -- Andy


 ___
 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] Re: Data.Map lookup signature

2009-05-12 Thread Nico Rolle
Oh sorry.
It was probalby changed in one of the latest versions
I downloaded the latest and now i'm finde.

2009/5/11 Nico Rolle nro...@web.de:
 Hi everyone.

 The docs in the web on http://www.haskell.org/ghc/docs
 define Data.Map.lookup as follows:
 http://www.haskell.org/ghc/docs
 lookup :: Ord k = k - Map k a - Maybe a
 but my version of ghci does i like that:
 Data.Map.lookup :: (Ord k, Monad m) = k - Data.Map.Map k a - m a
 but i need the 1. one.
 my version of ghci is 6.8.2
 regards

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


Re: [Haskell-cafe] Hoogle: converting binary .hoo into text?

2009-05-12 Thread Peter Verswyvelen
On Mon, May 11, 2009 at 10:25 AM, Neil Mitchell ndmitch...@gmail.comwrote:

 Hi Peter,

  I would like to use the Hoogle text format in C#.

 Out of curiosity, why? I'm just interested to know what work you're doing.


Sure. We're building with a graphical representation of a Haskellish
language (a tiny subset of Haskell actually). The target audience is
graphical artists and designers. For testing, I would like to populate the
library with primitives taken from the Haskell base libraries.  I tried
using the GHC API for it, but got stuck. I got the advice in #haskell to
parse the Hoogle format, which indeed looks simple enough for the task.

 Hoogle on Hackage comes with a bunch of binary *.hoo files. Can these be
  converted to text/xml? If not, is the binary format documented?

 The binary format is documented in the code, and there is a show command.
 Try:

 hoogle +base --dump

 However the binary format is not an encoding of the text format, it
 throws away lots of data, and precomputes interesting tables etc. If
 you want the original, the binary is probably not that useful.

 I do have a complete set of text files though. I can upload them to
 the Hoogle website, or I can distribute them with the hackage package.
 I could just email them to you privately. What seems the best option
 for everyone?


I'm not everyone but I guess it would be useful in general. From within
Haskell, ideally one would just use the GHC API (or Cabal API) to extract
all information I guess, but for usage in other languages, an easy to parse
format is better no? (maybe even XML, but that is bulky :-)

 I know I can build hoo files using cabal haddock --hoogle. But doing
 this
  on the BASE package (which I need) from Hackage fails (I'm on Windows,
 using
  MSYS):
  configure: creating ./config.status
  config.status: error: cannot find input file: include/HsBaseConfig.h.in
  Does anyone have an easy solution? Maybe I just need to switch to Linux
 to
  get this working? :-)

 I have a small pile of hacks to get the base library building with
 Hoogle. You are welcome to look at them (data/generate in the Hoogle
 repo). Caution: these hacks may make your eyes bleed, and certainly
 won't work for anything but the GHC/base version pair that I last did
 it on.

 Thanks

 Neil

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


Re: [Haskell-cafe] Hoogle: converting binary .hoo into text?

2009-05-12 Thread Neil Mitchell
Hi

 Sure. We're building with a graphical representation of a Haskellish
 language (a tiny subset of Haskell actually). The target audience is
 graphical artists and designers. For testing, I would like to populate the
 library with primitives taken from the Haskell base libraries.  I tried
 using the GHC API for it, but got stuck. I got the advice in #haskell to
 parse the Hoogle format, which indeed looks simple enough for the task.

You might be able to use haskell-src-exts (plus a little bit of
preprocessing) to parse the declarations. I deliberately tried to
follow Haskell syntax where possible.

  Hoogle on Hackage comes with a bunch of binary *.hoo files. Can these be
  converted to text/xml? If not, is the binary format documented?

 The binary format is documented in the code, and there is a show command.
 Try:

 hoogle +base --dump

 However the binary format is not an encoding of the text format, it
 throws away lots of data, and precomputes interesting tables etc. If
 you want the original, the binary is probably not that useful.

 I do have a complete set of text files though. I can upload them to
 the Hoogle website, or I can distribute them with the hackage package.
 I could just email them to you privately. What seems the best option
 for everyone?

 I'm not everyone but I guess it would be useful in general. From within
 Haskell, ideally one would just use the GHC API (or Cabal API) to extract
 all information I guess, but for usage in other languages, an easy to parse
 format is better no? (maybe even XML, but that is bulky :-)

Writing a converting from text files to XML is fine by me - Hoogle
already has the textual format parser, so if you add a patching adding
a dump XML option I'll happily apply.

I'll send you the .txt files by private email. It seems like you want
them now, but don't care about keeping them up to date, since it's
only a demo. Hence fast and quick, but not long term provided, seems a
good short-term compromise.

Thanks

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


[Haskell-cafe] caml build

2009-05-12 Thread Vasili I. Galchin
Hello,

  I have forgotten whether I sent this posting out. Sorry if I did (I
didn't  see on Haskell cafe archive).

  I am building Swish and getting an error. I want to follow the
progress of swish build ... I don't see an additional parameter like
verbose mode that will tell which swish component is being built. ???


Regards,

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


[Haskell-cafe] Kind of confusing

2009-05-12 Thread Anton van Straaten

GHC amused me today with this error (context omitted):

Couldn't match kind `(* - *) - * - *' against `?? - ? - *'
When matching the kinds of `t :: (* - *) - * - *' and
   `(-) :: ?? - ? - *'

It was a silly mistake: I had used 'lift' where I intended to use 'liftM'.

But I'm thinking Haskell compilers should have some sort of option 
which, when the ratio of punctuation to alphanumerics in an error 
message exceeds a certain level, just responds to the user with a more 
readily comprehensible message such as WTF, dude?


Serious question: what is the significance of the question mark and 
double question marks in those signatures, or better yet, where can I 
read about it?


Anton

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


[Haskell-cafe] Developing 3 dimensional interactive environments/functional objects

2009-05-12 Thread paulfrancis
 Does any programmer on this mailing list have experience with developing 3 dimensional interactive environments/functional objects within them, au Second Life? Is Haskell useful for such an endeavor? With best wishes,  Paul
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: OT: Languages

2009-05-12 Thread wren ng thornton

Tillmann Rendel wrote:

wren ng thornton wrote:
 Indeed. The proliferation of compound words is noteworthy, but it's 
 not generally considered an agglutinative language. From what (very 
 little) German I know compounds tend to be restricted to nouns, as 
 opposed to languages like Turkish, Japanese, Korean,...


Yes, compounds are restricted to nouns in German. But as I understand 
it, agglutinative relates more to the inflection system than to the 
lexicon anyway.


In general, I'm not sure I draw a distinction there. What belongs in the 
grammar vs what belongs in the lexicon is rather fluid and depends on 
both the language and the theory in question; whereas the phenomenon is, 
I think, easily identifiable (if not always easily definable). That is, 
the distinction between agglutinative vs fusional is typological rather 
than theoretical.


The distinction has to do with information content per morpheme (or 
compositional vs idiomatic information construction). For determining 
this, root/base morphemes are included just as much as inflectional 
morphemes. The distinction between what is root vs what is 
inflection is a spectrum and not always clear cut, especially in 
agglutinative languages. In languages like Japanese which lacks spaces, 
this difficulty is highlighted by the fact that it's not always clear 
whether something is a word or a phrase (and hence whether the 
latter major segment contains base morphemes, or is only inflection).


Though yes, the distinction is most clearly observed by looking at 
verbal inflections. And now we're really far off topic :)


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Stream-fusion without the lists

2009-05-12 Thread Reiner Pope
Hi everyone,

With stream-fusion, we can write functions which construct and
destruct lists, such as (this is the main example from the Stream
Fusion paper[1])
  f :: Int - Int
  f n = sum [k * m | k - [1..n], m - [1..k]]
and the rewrite rules in stream-fusion replace these operations on
lists with fusible operations on the Stream (non-recursive) datatype.

In this example, the domain and codomain of the function don't mention
the list datatype. There seem to be many functions like this: the
lists are being used internally as composable loops rather than as
data-structures.

The Stream datatype seems to be much better suited to representing
loops than the list datatype is. So, instead of programming with the
lists, why don't we just use the Stream datatype directly?

For example:
In Data.Stream (from the stream-fusion package) we can find most of
the Prelude list functions but with Stream in all the types instead of
[]. For example,

Data.Stream.sum :: Num a = S.Stream a - a

Using this module, we can rewrite f without mentioning lists. We first
need a Monad instance for Data.Stream.Stream:

 import qualified Data.List.Stream as S

 instance Monad S.Stream where
return = S.return
(=) = S.concatMap

Now we can write
 f :: Int - Int
 f n = S.sum $ do
k - S.enumFromToInt 1 n
m - S.enumFromToInt 1 k
return (k*m)

which is essentially the same as the original f, although lacking the
syntactic sugar of the list comprehension.

To me, it seems that Stream is more sensible data type to use than []
when the algorithm being expressed is just a loop (rather than
something which needs a [] as a cache/buffer), for the following
reasons:

1. If I am programming with lists and I need some function which I
can't express with Prelude functions, I have to write it myself. I
will probably lose fusion in this case, because I will write it
recursively in terms of lists. On the other hand, if I am programming
with Streams, I will write it myself in terms of Streams, and it
should be easier to maintain fusion because it won't be recursive.

2. Holding on to a [] too long can cause a space leak. This is not the
case for Stream, because a Stream only ever contains one state. More
generally, the memory use of Stream is more easily predictable than
that of [], since running a Stream only holds on to one state at a
time, and we often know how big the state is.

3. Fusion doesn't rely on rewrite rules firing. I consider this point
less significant than the other two.

So, thoughts? Do people program with Streams directly? What have I not
considered?

Cheers,
Reiner

[1] http://www.cse.unsw.edu.au/~dons/papers/stream-fusion.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Inferred typing?

2009-05-12 Thread michael rice
In the code below, is the type returned by the return functions inferred from 
the result type in the function type signature, i.e., just change the result
type to Maybe Int and the code will return a Maybe monad, (Just 4), instead of
a List monad?

Michael

=

import Monad

fn :: [Int] - [Int]
fn l = mzero `mplus` (return (head l)) `mplus` (return (last l))



*Main :l test5
[1 of 1] Compiling Main ( test5.hs, interpreted )
Ok, modules loaded: Main.
*Main fn [4,5,6,7,8]
[4,8]
*Main 



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


[Haskell-cafe] OT: Is conference dead?

2009-05-12 Thread Dušan Kolář

Hello all,

 I'm sorry for the OT post, is the conference dead? I've got no mail 
since yeasterday afternoon. And that is quite unusual.


 Best regards,

   Dusan

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


Re: [Haskell-cafe] Classes: functional dependency (type - value)

2009-05-12 Thread Daniel Schüssler
Hello!

The problem is that it's impossible to infer the SomeClass instance from the 
type SomeRole. If you do print role, which instance should it use?

I can think of two ways around it:

-- 1. (dummy parameter)
--
data SomeRole a = Role1 | Role2 | Role3 deriving Show

class SomeClass a where
role :: SomeRole a
   
data Foo = Foo
data Bar = Bar
   
instance SomeClass Foo where role = Role1

instance SomeClass Bar where role = Role2

main = do
  print (role :: SomeRole Foo)
  print (role :: SomeRole Bar)


-- 2. (dummy argument)
--
data SomeRole = Role1 | Role2 | Role3 deriving Show

class SomeClass a where
role :: a - SomeRole
   
data Foo = Foo
data Bar = Bar
   
instance SomeClass Foo where role _ = Role1

instance SomeClass Bar where role _ = Role2

main = do
  print (role (undefined :: Foo))
  print (role (undefined :: Bar))

--


On Sunday 10 May 2009 15:21:39 Belka wrote:
 Hello, communion people!

 I seek for your advice in a matter, where it's really hard for me to
 determine a good programming style.
 Here's the problem. I'm generalizing multiple authorization procedures to
 one, using class definition. (if of any interest, the code is in the end.)
 The problem essense is folowing:
 
 data SomeRole = Role1 | Role2 | Role3

 class SomeClass a b c | a - b, c where
   f1 :: ...
   f2 :: ...
   ...
   fn :: ...
   role :: SomeRole -- -- here is the problem

 I want to have a fuctional dependency from a type a on a value of *role*,
 so that I could easily inspect the *role* from within any other class
 members.
 Is it possible? Or do I rougly violate some style traditions?

 Some real code using wished feature:
 ---
 data AuthentificationPurpose = JustValidateInput | JustGenerateForOutput |
 ValidateInputAndGenerateForOutput
 type AuthSucceded = Bool

 class AuthentificationStructure t_env t_realInput t_assumption t_keySet |
 t_realInput - t_assumptionInput, t_keySet where
 authentificationPurpose :: AuthentificationPurpose
 makeAssumption  :: t_env - t_realInput - IO (Either ErrorMessage
 t_assumption)
 makeFinalKeySet :: (t_realInput, t_assumption) - t_keySet
 validateRealKeySet_with_Assumed :: t_realInput - t_keySet - Maybe
 ErrorMessage
 tryLogTheValidKey :: t_env - (t_realInput, t_assumption)
 - IO (Maybe ErrorMessage)
 tryLogTheAuthTry  :: t_env - (t_realInput, t_assumption,
 AuthSucceded) - IO (Maybe ErrorMessage)

 authentificate :: AuthentificationStructure t_env t_realInput
 t_assumptionInput t_keySet = t_env - t_businessInput - IO (Either
 ErrorMessage (t_assumption, t_keySet))
 authentificate env realInput = do err_or_assumption - makeAssumption env
 realInput
   case err_or_assumption of
   Left err_msg - return $ Left Error!
 Assumption maker failed. Lower level error message:  ++ err_msg
   Just assumption - do
   key_set -
 makeFinalKeySet (realInput, assumption)
   err_or_keyset1 - case
 authentificationPurpose of

 JustGenerateForOutput - return $ Right key_set

 JustValidateInput - do

 mb_failure - validateRealKeySet_with_Assumed t_realInput key_set

 case mb_failure of

 Just err_msg - return $ Left Error! Invalid set of auth keys. Lower level
 error message:  ++ err_msg

 Nothing - return $ Right key_set

 ValidateInputAndGenerateForOutput
   err_or_keyset2 - case
 err_or_keyset1 of

 Left err_msg - return err_or_keyset1

 Right key_set - do

 mb_failure - tryLogTheValidKey env (realInput, assumption)

 case mb_failure of

 Just err_msg - return $ Left Error! Could not log valid key. Lower level
 error message:  ++ err_msg

 Nothing  - return err_or_keyset1
   mb_failure -
 tryLogTheAuthTry env (realInput, assumption, isRight err_or_keyset2)
   case mb_failure of
   Just err_msg1 - case
 err_or_keyset2 of

 Left err_msg2 - return $ Left (1.  ++ err_msg2 ++ \n2.  ++ err_msg1)

 Right   _ - return $ Left err_msg1
   Nothing   - case
 err_or_keyset2 of

 Left  err_msg - return $ Left err_msg

 Right key_set - return $ Right (assumption, key_set)
 -

 Best regards, Belka
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org

[Haskell-cafe] Re: [Gtk2hs-users] ANN: Gtk2HS 0.10.1 released

2009-05-12 Thread Peter Gavin
On Sun, May 10, 2009 at 11:52 AM, Bulat Ziganshin
bulat.zigans...@gmail.com wrote:
 Hello Peter,

 Sunday, May 10, 2009, 7:43:38 PM, you wrote:

 I'd like to announce the release of Gtk2HS 0.10.1!  This release
 includes mostly bug fixes and other small improvements. Most notably,
 GHC 6.10.1 is now supported.

 6.10.2/6.10.3?


Yes, those versions are supported as well. GHC 6.10.1 changed the way
finalizers are handled, and as a result, Gtk2HS programs were
crashing.  I don't think anything that affects Gtk2HS was changed in
GHC 6.10.[23].

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


[Haskell-cafe] ANN: AAIP Workshop on ICFP Deadline Extension

2009-05-12 Thread Martin Hofmann
AAIP Workshop on ICFP Deadline Extension

Please note that the submission deadline for the 3rd Workshop on
Approaches and Applications of Inductive Programming has been extended 
to May 25.

The workshop takes place for the first time at the
14th ACM SIGPLAN International Conference on Functional Programming 
(ICFP 2009) in Edinburgh, Scotland.

If a sufficient number of high quality papers is submitted, there will 
be a Post-Workshop Proceedings Volume published at Springer LNCS.

The workshop will present three invited speakers from the research area 
of functional programming who have done excellent work to make use of 
inductive programming techniques.

The full Call for Papers and further information are available at
http://www.cogsys.wiai.uni-bamberg.de/aaip09/

Submit to the workshop and help to tighten the link between the 
functional programming and the inductive programming community!

Best regards,

Ute Schmid, Rinus Plasmeijer and Emanuel Kitzelmann



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


[Haskell-cafe] Re: OT: Is conference dead?

2009-05-12 Thread Simon Marlow

On 12/05/2009 08:04, Dušan Kolář wrote:


I'm sorry for the OT post, is the conference dead? I've got no mail
since yeasterday afternoon. And that is quite unusual.


We had a full disk on haskell.org over the weekend.  We freed up some 
space yesterday, but it seems the lists were still stuck.  I've 
restarted mailman and the mail now seems to be flowing, but there's a 
large backlog.


Cheers,
Simon

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


Re: [Haskell-cafe] Kind of confusing

2009-05-12 Thread Max Bolingbroke
Hi Anton,

AFAIK the only place this is documented is in GHC source code. Please
see the section called Main data types representing Kinds at
http://hackage.haskell.org/packages/archive/ghc/6.10.2/doc/html/Type.html.

Basically, they are all members of GHC's internal subkind hierarchy,
which is used to distinguish between the representation of types.

For example, the error function can be instantiated to have the type
String - Int# - Int# whereas every polymorphic function you write
will only be able to be instantiated at lifted types like Int. This
reflects the fact that internally the type variable in the type of
error has (IIRC) kind ?. I don't know why they showed up in your
error message!

Cheers,
Max

2009/5/12 Anton van Straaten an...@appsolutions.com:
 GHC amused me today with this error (context omitted):

    Couldn't match kind `(* - *) - * - *' against `?? - ? - *'
    When matching the kinds of `t :: (* - *) - * - *' and
                               `(-) :: ?? - ? - *'

 It was a silly mistake: I had used 'lift' where I intended to use 'liftM'.

 But I'm thinking Haskell compilers should have some sort of option which,
 when the ratio of punctuation to alphanumerics in an error message exceeds a
 certain level, just responds to the user with a more readily comprehensible
 message such as WTF, dude?

 Serious question: what is the significance of the question mark and double
 question marks in those signatures, or better yet, where can I read about
 it?

 Anton

 ___
 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: [darcs-users] [Haskell-cafe] Darcs as undo/redo system?

2009-05-12 Thread Wolfgang Jeltsch
Am Freitag, 8. Mai 2009 18:43 schrieb Jason Dagit:
 If you wanted to work on this, I would encourage you to read more
 about patch theory[1,2,3,4] and also try out libdarcs[5].

Is libdarcs the same as the darcs library package on Hackage (which exports 
the darcs API)?

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


[Haskell-cafe] Re: OT: Languages

2009-05-12 Thread Achim Schneider
wren ng thornton w...@freegeek.org wrote:

 That is, the distinction between agglutinative vs
 fusional is typological rather than theoretical.
 
 Though yes, the distinction is most clearly observed by looking at 
 verbal inflections. And now we're really far off topic :)

No, we aren't. A couple of days ago, I considered replacing a couple of
highly regular function definitions by three lists and two calls to
*, but didn't do it as I would still have to name the resulting
functions by hand, to use them, and TH seemed utter overkill.

-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


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


[Haskell-cafe] Re: Inferred typing?

2009-05-12 Thread Achim Schneider
michael rice nowg...@yahoo.com wrote:

 In the code below, is the type returned by the return functions
 inferred from the result type in the function type signature, i.e.,
 just change the result type to Maybe Int and the code will return a
 Maybe monad, (Just 4), instead of a List monad?
 
Yes.

Prelude :m Control.Monad
Prelude Control.Monad let fn l = mzero `mplus` (return (head l))
  `mplus` (return (last l)) 
Prelude Control.Monad fn [1,3] :: Maybe Int 
Just 1
Prelude Control.Monad fn [1,3] :: Maybe Float
Just 1.0
Prelude Control.Monad fn [1,2,3] :: [Int]
[1,3]

-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


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


[Haskell-cafe] Re: Classes: functional dependency (type - value)

2009-05-12 Thread Heinrich Apfelmus
Belka wrote:
 Hello, communion people!
 
 I seek for your advice in a matter, where it's really hard for me to
 determine a good programming style.
 Here's the problem. I'm generalizing multiple authorization procedures to
 one, using class definition. (if of any interest, the code is in the end.) 
 The problem essense is folowing:
 
 data SomeRole = Role1 | Role2 | Role3
 
 class SomeClass a b c | a - b, c where
   f1 :: ...
   f2 :: ...
   ...
   fn :: ...
   role :: SomeRole -- -- here is the problem
 
 I want to have a fuctional dependency from a type a on a value of *role*,
 so that I could easily inspect the *role* from within any other class
 members.
 Is it possible? Or do I rougly violate some style traditions?

The problem is that when you write

   role

there is no way to choose the right instance? That is, where does the
compiler get  a, b, c  from when looking just at an invocation of  role
? Therefore, the type of  role  has to involve  a  , for example as in

   class SomeClass a b c ... where
...
role :: a - SomeRole

and used as

   role (undefined :: Foo)



That being said, I think that type classes are not what you want here. I
suggest to simply use a regular data type

   data SomeThing a b c = SomeThing {
 f1   :: ...
   , f2   :: ...
 ...
   , fn   :: ...
   , role :: SomeRole
   }

Remember that  f1, f2, ...  can be functions, this is a functional
language, after all! Instances are then simply a concrete value, like
for example

   thething :: SomeThing Foo Bar Baz
   thething = SomeThing {
f1 = id
 ,  f2 = filter (3) . map length
 ,  ...
 ,  role = Role1
 }


Regards,
apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] Stream-fusion without the lists

2009-05-12 Thread Roman Leshchinskiy

On 12/05/2009, at 14:45, Reiner Pope wrote:


The Stream datatype seems to be much better suited to representing
loops than the list datatype is. So, instead of programming with the
lists, why don't we just use the Stream datatype directly?


I think the main reason is that streams don't store data and therefore  
don't support sharing. That is, in


let xs = map f ys in (sum xs, product xs)

the elements of xs will be computed once if it is a list but twice if  
it is a stream.


Roman


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


Re: [Haskell-cafe] commending Design concepts in programming languages

2009-05-12 Thread Wolfgang Jeltsch
Am Freitag, 8. Mai 2009 14:31 schrieb Daniel Fischer:
 Though I had no contact with algebraists in the 1980s,

I also hadn’t. However, nowadays I have contact with someone who was an 
algebraist in the 1980s. It’s my boss (professor), by the way. :-) 

  I think, also category theorists often wrote (write?) composition with
  the first morphism on the left, i.e., “the other way round”.

 Yeah, I heard that, too. It's a field where the advantages of postfix
 notation show clearly and a young one, so for them it was relatively easy
 to switch.

However, I fear that all those other mathematicians who define
f . g = \x - f(g(x), have made the category theorists switch to this 
suboptimal notation (first morphism on the right). At least, I cannot 
remember seeing the other notation (first morphism on the left) in category 
theory literature so far. It’s just that my above-mentioned professor told me 
that category theorists would use the first-morphism-on-the-left notation.

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


Re: [Haskell-cafe] Inferred typing?

2009-05-12 Thread Brent Yorgey
On Mon, May 11, 2009 at 10:59:01PM -0700, michael rice wrote:
 In the code below, is the type returned by the return functions inferred from 
 the result type in the function type signature, i.e., just change the result
 type to Maybe Int and the code will return a Maybe monad, (Just 4), instead of
 a List monad?

Indeed, it is.  Try it! =)

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


[Haskell-cafe] Haskell Weekly News: Issue 117 - May 12, 2009

2009-05-12 Thread Brent Yorgey
---
Haskell Weekly News
http://sequence.complete.org/hwn/20090512
Issue 117 - May 12, 2009
---

   Welcome to issue 117 of HWN, a newsletter covering developments in the
   [1]Haskell community.

   The Haskell Platform is here!

Announcements

   The Haskell Platform. Don Stewart [2]announced the first release of the
   [3]Haskell Platform: a single, standard Haskell distribution for every
   system. The Haskell Platform is a blessed library and tool suite for
   Haskell culled from Hackage, along with installers for a wide variety
   of systems. It saves developers work picking and choosing the best
   Haskell libraries and tools to use for a task.

   GHC version 6.10.3. Ian Lynagh [4]announced the release of [5]GHC
   6.10.3. This release contains a handful of bugfixes relative to 6.10.2
   and better line editing support in GHCi, so updating is recommend. See
   the [6]release notes for more details.

   Bindings for libguestfs. Richard W.M. Jones [7]announced some
   [8]partial bindings for [9]libguestfs.

   Heads up: Conflicting versions of network-2.2.1. Johan Tibell
   [10]announced a heads-up that the version of network-2.2.1 that shipped
   with GHC 6.10 differs from the one on Hackage. If you want the API
   additions that are present in network-2.2.1 on Hackage, be sure to use
   network-2.2.1.1 instead.

   hpc-strobe-0.1: Hpc-generated strobes for a running Haskell program.
   Thorkil Naur [11]announced the initial release of [12]hpc-strobe, a
   rudimentary library that demonstrates the possibility of using Hpc
   (Haskell Program Coverage) to inspect the state of a running Haskell
   program. hpc-strobe uses the basic machinery provided by Hpc to produce
   multiple tix files, also called strobes, representing the coverage at
   different times while the program is running. By subtracting such two
   tix files, again using Hpc machinery, a tix file representing the
   expressions used between the times of recording the subtracted tix
   files is produced. This may be used, for example, to get a better idea
   of what a long-running program is doing. It could also be used as a
   profiling tool, getting information about how many times individual
   expressions are used.

   BUG FIX release of regex-tdfa-1.1.2. ChrisK [13]announced version 1.1.2
   of [14]regex-tdfa, a bug-fix release.

   Silkworm game. Duane Johnson [15]announced the release of [16]Silkworm,
   a game written in Haskell using [17]Hipmunk and GLFW.

Discussion

   Platform policy question: API compatibility in minor releases. Duncan
   Coutts began a [18]discussion on versioning policies for major and
   minor releases, for packages included in the Haskell Platform. See also
   the [19]newly started discussion on the purpose of Haskell Platform
   releases.

Blog noise

   [20]Haskell news from the [21]blogosphere. Blog posts from people new
   to the Haskell community are marked with , be sure to welcome them!
 * Magnus Therning: [22]Vim haskellmode packaged for Arch.
 * Manuel M T Chakravarty: [23]Instant Generics: Fast and Easy..
 * Bjorn Buckwalter: [24]May 2009 HCAR Submissions.
 * Gtk2HS: [25]Gtk2HS 0.10.1 Released.
 * Magnus Therning: [26]Arch and Haskell, on little snag.
 * Mikael Vejdemo Johansson (DrSyzygy): [27]Gröbner bases for operads
   - Or What I did in my vacation.
 * Mads Lindstrøm: [28]WxGeneric 0.6.0.
 * Osfameron: [29]Is currying monadic?.
 * James Iry: [30]A Brief, Incomplete, and Mostly Wrong History of
   Programming Languages.
 * Duane Johnson: [31]Visualizing Typed Functions.
 * Well-Typed.Com: [32]Next steps for the Haskell Platform.
 * Don Stewart (dons): [33]The Haskell Platform.
 * Luke Palmer: [34]Lazy Partial Evaluation.
 * Christopher Lane Hinson: [35]Vec is Good.
 * LHC Team: [36]Constructor specialization and laziness..
 * Lee Pike: [37]An Atomic Fibonacci Server: Exploring the Atom
   (Haskell) DSL.
 * John Van Enk: [38]Atom  Arduino :: First Program (pt. 2).
 *  Chris Forno: [39]Is Haskell a Good Choice for Web
   Applications?.
 *  Sparky: [40]Haskell and Eclipse [Part 2].
 *  Brit Butler: [41]Playing with Haskell.
 * Duane Johnson: [42]Silkworm Game written in Haskell.
 * Matthew Podwysocki: [43]Functional Composition and Partial
   Application .
 *  Takashi: [44]A Prolog In Haskell.
 *  mokehehe: [45]Using DirectX from Haskell.
 *  mokehehe: [46]AO bench in Haskell.

Quotes of the Week

 * jfredett: My haskell-spider senses were tingling, I just overshot
   RT and went for the Halting Problem.
 * NeilBrown: I heard that if you chant I don't think this can be
   done in Haskell three times in front of a text editor, Don Stewart
   appears and implements it in one line...
 * bos: The last couple

Re: [Haskell-cafe] caml build

2009-05-12 Thread Nicolas Pouillard
Excerpts from Vasili I. Galchin's message of Tue May 12 00:27:26 +0200 2009:
 Hello,
 
   I have forgotten whether I sent this posting out. Sorry if I did (I
 didn't  see on Haskell cafe archive).
 
   I am building Swish and getting an error. I want to follow the
 progress of swish build ... I don't see an additional parameter like
 verbose mode that will tell which swish component is being built. ???

I don't get the relation with the subject of your post, can you elaborate?

Best regards,

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


Re: [Haskell-cafe] Fundep Curiosity

2009-05-12 Thread Daniel Fischer
Am Montag 11 Mai 2009 18:36:54 schrieb Christopher Lane Hinson:
 I've noticed that a large majority of fundeps I see in other people's
 libraries are written:

 class C a b | b - a

 Where the dependent parameter appears first in the MPTC.  Is there a
 reason for this?

Yes. Generalised newtype deriving (perhaps others, but that's what jumped at 
me).

Consider

class MonadState s m | m - s where ...

newtype State s a = State { runState :: s - (a,s) }

instance Monad (State s) where ...

instance MonadState s (State s) where ...

newtype MySpecialState s a = MSS (State (s,Int) a)
deriving (Monad, MonadState (s,Int))


 AFAIK, there isn't any semantic significance to the order of parameters in
 an MPTC.  Why do many haskellers find this configuration more intuitive?

 Friendly,
 --Lane

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


Re: [Haskell-cafe] Inferred typing?

2009-05-12 Thread Daniel Fischer
Am Dienstag 12 Mai 2009 07:59:01 schrieb michael rice:
 In the code below, is the type returned by the return functions inferred
 from the result type in the function type signature, i.e., just change the
 result type to Maybe Int and the code will return a Maybe monad, (Just 4),
 instead of a List monad?

You can find out such things yourself, just remove the type signature and ask 
ghci/hugs 
what they think:

*MType :t fn
fn :: (MonadPlus m) = [a] - m a


 Michael

 =

 import Monad

 fn :: [Int] - [Int]
 fn l = mzero `mplus` (return (head l)) `mplus` (return (last l))

 

 *Main :l test5
 [1 of 1] Compiling Main ( test5.hs, interpreted )
 Ok, modules loaded: Main.
 *Main fn [4,5,6,7,8]
 [4,8]
 *Main

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


Re: [Haskell-cafe] OT: Is conference dead?

2009-05-12 Thread Daniel Fischer
Am Dienstag 12 Mai 2009 09:04:46 schrieb Dušan Kolář:
 Hello all,

   I'm sorry for the OT post, is the conference dead? I've got no mail
 since yeasterday afternoon. And that is quite unusual.

I didn't get anything yesterday afternoon either. On Saturday, posts reached my 
mailbox 
typically one hour after sending, Sunday it was 2+ hours, yesterday noon I got 
what was 
sent up to 8am GMT, nothing after that. Today things are much delayed again.

It seems the mail server at haskell.org is seriously acting up.
Does anybody know whom one can ask to look into it?


   Best regards,

 Dusan



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


Re: [Haskell-cafe] Kind of confusing

2009-05-12 Thread Philippa Cowderoy
On Mon, 2009-05-11 at 20:43 -0400, Anton van Straaten wrote:
 Serious question: what is the significance of the question mark and 
 double question marks in those signatures, or better yet, where can I 
 read about it?
 

I've forgotten where to find the details (try the GHC manual if you
haven't already?), but IIRC they're part of how GHC handles boxing.

-- 
Philippa Cowderoy fli...@flippac.org

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


[Haskell-cafe] List of exports of a module - are there alternatives?

2009-05-12 Thread Maurício
Hi,

When we want to list which declarations are exported by a module
we do:

module Mod ( list of exports ) where ...

Are there propositions to alternatives to that (I could not
find one)? Like, say, add a do export or do not export
tag to declarations we want to (not) export?

(I think something like that could be nice when we have modules
with 200 declarations and just a few are (not) going to be
exported.)

Thanks,
Maurício


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


[Haskell-cafe] Problem with text and text-icu packages

2009-05-12 Thread David Carter
Hi,

I'm struggling with text-0.1 and text-icu-0.1, as announced at

http://www.serpentine.com/blog/2009/02/27/finally-fast-unicode-support-for-haskell/

The code in

http://pastebin.com/m7d8d9f91

is intended to read in a UTF-8 file a1.txt, reverse it twice, and
write it out to another UTF-8 file a2.txt, which I would have thought
should make a2.txt identical to a1.txt. Mostly it is, but sometimes it
isn't, e.g.:

% echo a  a1.txt
% tryicu   # - my code
% cat a2.txt
ࠋ퐤

Specifically, a1.txt contains bytes 97 and 10, while a2.txt contains
bytes 224 160 139 237 144 164.

Have I misconstrued things, or is this a bug?

I am running ghc 6.10.2 and ICU 4.0.1 on SuSE.

Thanks for any help

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


Re: [Haskell-cafe] Fundep Curiosity

2009-05-12 Thread Tillmann Rendel

Christopher Lane Hinson wrote:
I've noticed that a large majority of fundeps I see in other people's 
libraries are written:


class C a b | b - a

Where the dependent parameter appears first in the MPTC.  Is there a 
reason for this?


AFAIK, there isn't any semantic significance to the order of parameters 
in an MPTC.  Why do many haskellers find this configuration more intuitive?


The order of parameters in an MPTC is significant if you want to use 
newtype deriving, which can only be used with the last parameter, by 
explicitly providing all other parameters.


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


Re: [Haskell-cafe] [ANNOUNCE] Bindings for libguestfs

2009-05-12 Thread Don Stewart
rjones:
 I added some partial bindings for libguestfs[1] here:
 
 http://git.et.redhat.com/?p=libguestfs.git;a=blob;f=haskell/Guestfs.hs;hb=HEAD
 
 Some very simple example programs which use these bindings:
 
 http://git.et.redhat.com/?p=libguestfs.git;a=tree;f=haskell;hb=HEAD
 
 Any comments welcome.  My Haskell skills are pretty terrible, so I'm
 sure there are many ways these can be improved.
 
 If someone wants to look at binding the rest of the API, then please
 send me some patches.  (Note that the Guestfs.hs file is automatically
 generated).

Very cool. Are you likely to upload to hackage?
  
 BTW, I found the documentation on writing FFIs very contradictory and
 incomplete.  For example, I was completely defeated trying to find
 ways to do simple stuff like passing in integers or returning
 booleans.  *Potentially* Haskell's FFI seems like it might be one of
 the best out of the languages I've used so far, but it needs way more
 documentation and examples.

Perhaps read the FFI chapter of RWH (online?)

What resources were you using to grok the FFI?

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


[Haskell-cafe] International Summer School on Advances in Programming Languages (precedes ICFP'09)

2009-05-12 Thread Matthew Fluet (ICFP Publicity Chair)
   International Summer School on Advances in Programming Languages
25th-28th August, 2009
 Heriot-Watt University, Edinburgh, Scotland
   http://www.macs.hw.ac.uk/~greg/ISS-AiPL


Overview


This four-day residential International Summer School on Advances in
Programming Languages has a major theme of Concurrency, Distribution,
and Multicore. Intended primarily for postgraduate research students,
the School offers lectures and practical sessions on an engaging blend
of cutting edge theoretical and practical techniques from
international experts.

The Summer School is supported by the Scottish Informatics and
Computer Science Alliance (http://www.sicsa.ac.uk/), a Scottish
Funding Council Research Pool. Participants from SICSA member
institutions may attend at no cost.

Confirmed Topics/Speakers

* Static and dynamic languages,
  Prof Philip Wadler, University of Edinburgh
* Compiler technology for data-parallel languages,
  Dr Sven-Bodo Scholz, University of Hertfordshire
* New applications of parametricity,
  Dr Janis Voigtlander, Technical University of Dresden
* Automatic vectorising compilation,
  Dr Paul Cockshott, University of Glasgow
* Foundational aspects of size analysis,
  Prof Marko van Eekelen / Dr Olha Shakaravska, Radboud University Nijmegen
* Context oriented programming,
  Dr Pascal Costanza, Vrije Universiteit Brussels
* Multi-core programming,
  Dr Phil Trinder, Heriot-Watt University
* Multi-core compilation,
  Dr Alastair Donaldson, Codeplay Software Ltd
* Principles and Applications of Refinement Types,
  Dr Andrew D. Gordon, Microsoft Research, Cambridge
* Resource aware programming in Hume,
  Prof Greg Michaelson, Heriot-Watt University / Prof Kevin Hammond,
University of St Andrews
* Haskell concurrency  parallelism,
  Dr Satnam Singh, Microsoft Research, Cambridge


Location


The Summer School is at Heriot-Watt University's Riccarton campus, set
in pleasant parkland to the west of Edinburgh, with easy access to the
airport, city and central Scotland
(http://www.hw.ac.uk/welcome/directions.htm).

The Summer School immediately precedes the 2009 International
Conference on Functional Programming
(http://www.cs.nott.ac.uk/~gmh/icfp09.html) and takes place during the
Edinburgh International Festival (http://www.eif.co.uk/) , and the
associated Edinburgh Festival Fringe (http://www.edfringe.com/) and
Edinburgh International Book Festival (http://www.edbookfest.co.uk/)


Steering Committee
~~

Prof Prof Greg Michaelson, Heriot-Watt University (Convenor),
g.michael...@hw.ac.uk
Prof Kevin Hammond, University of St Andrews
Dr Patricia Johann, University of Strathclyde
Prof Philip Wadler, University of Edinburgh


Fee
~~~

Full rate: £400; (free for SICSA students)
Includes: four nights single room, en-suite accommodation with
breakfast, lunch and dinner, plus coffee breaks and session materials.

Day rate: £200; (free for SICSA students)
Includes: lunch, coffee breaks, session materials


Registration of Interest


If you are interested in attending the International Summer School,
please complete the form available from
(http://www.macs.hw.ac.uk/~greg/ISS-AiPL/ISS-AiPL%20register.doc) or
below, and return it to: iss-aipl-regis...@macs.hw.ac.uk


**
International Summer School on Advances in Programming Languages
25th-28th August, 2009
Heriot-Watt University, Edinburgh, Scotland

Registration of Interest

Name:
Address:
Email:
Phone:
SICSA Uni: Yes / No
Rate: Full / Day
Accessibility requirements:
Dietary requirements:

Return to: iss-aipl-regis...@macs.hw.ac.uk
**
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Developing 3 dimensional interactive environments/functional objects

2009-05-12 Thread Don Stewart
paulfrancis:
Does any programmer on this mailing list have experience with developing 3
 dimensional interactive environments/functional objects within them, au Second
 Life? Is Haskell useful for such an endeavor?

Mm..

Anygma
http://www.anygma.com/JobOfferA.html

gamr7
http://www.gamr7.com/

Both use Haskell to some extent.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [ANNOUNCE] Bindings for libguestfs

2009-05-12 Thread Richard W.M. Jones
On Tue, May 12, 2009 at 08:18:08AM -0700, Don Stewart wrote:
 rjones:
  I added some partial bindings for libguestfs[1] here:
  
  http://git.et.redhat.com/?p=libguestfs.git;a=blob;f=haskell/Guestfs.hs;hb=HEAD
  
  Some very simple example programs which use these bindings:
  
  http://git.et.redhat.com/?p=libguestfs.git;a=tree;f=haskell;hb=HEAD
  
  Any comments welcome.  My Haskell skills are pretty terrible, so I'm
  sure there are many ways these can be improved.
  
  If someone wants to look at binding the rest of the API, then please
  send me some patches.  (Note that the Guestfs.hs file is automatically
  generated).
 
 Very cool. Are you likely to upload to hackage?

I think it should be a bit more complete before uploading it.  It only
covers about half the interface.

  BTW, I found the documentation on writing FFIs very contradictory and
  incomplete.  For example, I was completely defeated trying to find
  ways to do simple stuff like passing in integers or returning
  booleans.  *Potentially* Haskell's FFI seems like it might be one of
  the best out of the languages I've used so far, but it needs way more
  documentation and examples.
 
 Perhaps read the FFI chapter of RWH (online?)

 What resources were you using to grok the FFI?

Well, Real World Haskell was one of the resources:

http://book.realworldhaskell.org/read/interfacing-with-c-the-ffi.html

(And it's fine, one of the better resources as an introduction.  But
not thorough enough to cover the booleans / returning complex structs
problems I had).

The others, as I remember it, were:

http://www.haskell.org/haskellwiki/FFI_Introduction
http://www.haskell.org/haskellwiki/FFICookBook

(Made me think it was simple, but doesn't really cover much once I got
down to the details)

http://www.cse.unsw.edu.au/~chak/haskell/ffi/

 the documentation for 'Foreign' etc in the Haddock-generated library
docs.

Rich.

-- 
Richard Jones, Emerging Technologies, Red Hat  http://et.redhat.com/~rjones
virt-df lists disk usage of guests without needing to install any
software inside the virtual machine.  Supports Linux and Windows.
http://et.redhat.com/~rjones/virt-df/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [ANNOUNCE] Bindings for libguestfs

2009-05-12 Thread Don Stewart
rjones:
 On Tue, May 12, 2009 at 08:18:08AM -0700, Don Stewart wrote:
  rjones:
   I added some partial bindings for libguestfs[1] here:
   
   http://git.et.redhat.com/?p=libguestfs.git;a=blob;f=haskell/Guestfs.hs;hb=HEAD
   
   Some very simple example programs which use these bindings:
   
   http://git.et.redhat.com/?p=libguestfs.git;a=tree;f=haskell;hb=HEAD
   
   Any comments welcome.  My Haskell skills are pretty terrible, so I'm
   sure there are many ways these can be improved.
   
   If someone wants to look at binding the rest of the API, then please
   send me some patches.  (Note that the Guestfs.hs file is automatically
   generated).
  
  Very cool. Are you likely to upload to hackage?
 
 I think it should be a bit more complete before uploading it.  It only
 covers about half the interface.
 
   BTW, I found the documentation on writing FFIs very contradictory and
   incomplete.  For example, I was completely defeated trying to find
   ways to do simple stuff like passing in integers or returning
   booleans.  *Potentially* Haskell's FFI seems like it might be one of
   the best out of the languages I've used so far, but it needs way more
   documentation and examples.
  
  Perhaps read the FFI chapter of RWH (online?)
 
  What resources were you using to grok the FFI?
 
 Well, Real World Haskell was one of the resources:
 
 http://book.realworldhaskell.org/read/interfacing-with-c-the-ffi.html
 
 (And it's fine, one of the better resources as an introduction.  But
 not thorough enough to cover the booleans / returning complex structs
 problems I had).
 
 The others, as I remember it, were:
 
 http://www.haskell.org/haskellwiki/FFI_Introduction
 http://www.haskell.org/haskellwiki/FFICookBook
 
 (Made me think it was simple, but doesn't really cover much once I got
 down to the details)
 
 http://www.cse.unsw.edu.au/~chak/haskell/ffi/
 
  the documentation for 'Foreign' etc in the Haddock-generated library
 docs.

Very good.

I wonder if /you/ could note down (maybe on the wiki) the things you
need to work out - then we would have a tutorial from someone learning
on the job. That could then be fleshed out into a fuller tutorial?

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


RE: [darcs-users] [Haskell-cafe] Darcs as undo/redo system?

2009-05-12 Thread Sittampalam, Ganesh
Wolfgang Jeltsch wrote:
 Am Freitag, 8. Mai 2009 18:43 schrieb Jason Dagit:
 If you wanted to work on this, I would encourage you to read more
 about patch theory[1,2,3,4] and also try out libdarcs[5].
 
 Is libdarcs the same as the darcs library package on Hackage (which
 exports the darcs API)? 

Yes.

Ganesh

=== 
 Please access the attached hyperlink for an important electronic 
communications disclaimer: 
 http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html 
 
=== 
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] haskell cuda?

2009-05-12 Thread Dan

Hi,

Does anyone know if there's a compiler from Data-Parallel Haskell to GPU 
code?  I saw a paper on it a while back, but Google hasn't turned up any 
code.


Cheers,
- Dan
begin:vcard
fn:Daniel K. Cook
n:Cook;Daniel K.
email;internet:danielkc...@gmail.com
tel;cell:+44 (0) 7949 125 491
x-mozilla-html:TRUE
version:2.1
end:vcard

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


[Haskell-cafe] Structural sharing in haskell data structures?

2009-05-12 Thread Andrew Wagner
So I've been reading a lot about a (relatively) new language called Clojure.
One of its goals is to make concurrency easier via a built-in home-grown
STM. Anyway, one of the ways it tries to do this is to have completely
immutable data structures. Every time I read a tutorial about this in
Clojure, it says ...yes, it sounds awful to think that your whole data
structure gets copied every time you want to make a change to it, but it's
sane because of a technique called structural sharing. Yet every time I
hear immutability talked about in Haskell, what I hear is ...yes, it sounds
awful to think that your whole data structure gets copied every time you
want to make a change to it, but it's sane because of laziness...unless you
need the whole data structure So I'm just curious, does GHC use
structural sharing or something similar? Do other implementations? Does it
matter?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Main function error

2009-05-12 Thread applebiz89

I have compiled each function independently and they have compiled the only
problem is the main function..

I keep getting the error 'films not defined' and I am not sure why

[code]

type Title = String
type Director = String
type Year = Int
type Fan = String

data Film = Film Title Director Year [Fan] deriving Show

-- List of films

testDatabase :: [Film]
testDatabase = [ (Film Casino Royale Martin Campbell 2006 [Garry,
Dave, Zoe])]

-- Function 

filmsInGivenYear :: Year - [Film] - [String]
filmsInGivenYear year' films = [ title | (Film title director year fans) -
films, year == year']

doFilmsInGivenYear :: [Film] - IO ()
doFilmsInGivenYear films  = do putStrLn which year?
   text - getLine
   let year' = read text :: Int
   let answer = filmsInGivenYear year' films
   print answer

main :: IO ()
main = do 
 doFilmsInGivenYear films
 main

[/code]

if the other functions are compiling without this error im not sure as to
why the main function does not compile because of the films...any light on
this?

Thanks
-- 
View this message in context: 
http://www.nabble.com/Main-function-error-tp23506481p23506481.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Stream-fusion without the lists

2009-05-12 Thread Don Stewart
rl:
 On 12/05/2009, at 14:45, Reiner Pope wrote:

 The Stream datatype seems to be much better suited to representing
 loops than the list datatype is. So, instead of programming with the
 lists, why don't we just use the Stream datatype directly?

 I think the main reason is that streams don't store data and therefore  
 don't support sharing. That is, in

 let xs = map f ys in (sum xs, product xs)

 the elements of xs will be computed once if it is a list but twice if it 
 is a stream.


The other issue is reminding developers to preserve stream invariants,
so as not to break the heavy duty rewriting that's going to happen to
their code.

Still, if someone finds a use for it, proceed!

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


Re: [Haskell-cafe] Stream-fusion without the lists

2009-05-12 Thread Max Rabkin
On Tue, May 12, 2009 at 1:39 PM, Roman Leshchinskiy r...@cse.unsw.edu.au 
wrote:
 let xs = map f ys in (sum xs, product xs)

 the elements of xs will be computed once if it is a list but twice if it is
 a stream.

If you're using lists for loops rather than data, that's what you want
(what you probably really want is cfoldl' ((,) $ sumF * productF)
xs, in terms of combinable folds).

 Roman

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


Re: [Haskell-cafe] commending Design concepts in programming languages

2009-05-12 Thread Max Rabkin
On Tue, May 12, 2009 at 1:41 PM, Wolfgang Jeltsch
g9ks1...@acme.softbase.org wrote:
 At least, I cannot
 remember seeing the other notation (first morphism on the left) in category
 theory literature so far. It’s just that my above-mentioned professor told me
 that category theorists would use the first-morphism-on-the-left notation.

I've seen the notation f;g for g.f somewhere (and Wikipedia mentions
it). I think it's less ambiguous than just fg (which I've seen for f.g
too), but in Haskell we have the option of . A flipped application
might be nice to go with it. How about $ ?

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


Re: [Haskell-cafe] Inferred typing?

2009-05-12 Thread michael rice
I was looking at some code and couldn't figure out how it was returning a list 
since there were no list constructors present.

Thanks!

Michael

--- On Tue, 5/12/09, Brent Yorgey byor...@seas.upenn.edu wrote:

From: Brent Yorgey byor...@seas.upenn.edu
Subject: Re: [Haskell-cafe] Inferred typing?
To: haskell-cafe@haskell.org
Date: Tuesday, May 12, 2009, 7:50 AM

On Mon, May 11, 2009 at 10:59:01PM -0700, michael rice wrote:
 In the code below, is the type returned by the return functions inferred from 
 the result type in the function type signature, i.e., just change the result
 type to Maybe Int and the code will return a Maybe monad, (Just 4), instead of
 a List monad?

Indeed, it is.  Try it! =)

-Brent
___
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] Stream-fusion without the lists

2009-05-12 Thread Andrew Coppin

Roman Leshchinskiy wrote:

On 12/05/2009, at 14:45, Reiner Pope wrote:


The Stream datatype seems to be much better suited to representing
loops than the list datatype is. So, instead of programming with the
lists, why don't we just use the Stream datatype directly?


This is more or less the conclusion I came to myself the other day when 
I sat down and tried to implement stream fusion myself (just for giggles).


I think the main reason is that streams don't store data and therefore 
don't support sharing. That is, in


let xs = map f ys in (sum xs, product xs)

the elements of xs will be computed once if it is a list but twice if 
it is a stream.


...and I hadn't thought of this part! ;-)

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


Re: [Haskell-cafe] [ANNOUNCE] Bindings for libguestfs

2009-05-12 Thread John Dorsey
Richard,

 I added some partial bindings for libguestfs[1] here:
 http://git.et.redhat.com/?p=libguestfs.git;a=blob;f=haskell/Guestfs.hs;hb=HEAD

Terrific!  Partial bindings are great.  Thanks for releasing it.  I haven't
taken the time to look at your code, but...

 BTW, I found the documentation on writing FFIs very contradictory and
 incomplete.  For example, I was completely defeated trying to find
 ways to do simple stuff like passing in integers or returning
 booleans.  *Potentially* Haskell's FFI seems like it might be one of
 the best out of the languages I've used so far, but it needs way more
 documentation and examples.

Can you be more specific about what needs improvement?

I wrote a partial Haskell binding for Net-SNMP recently, and I got along
pretty well using the API docs at
http://www.haskell.org/ghc/docs/latest/html/libraries/index.html, and an
example in RWH using hsc2hs.

What did you see that was contradictory?

Regards,
John

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


Re: [Haskell-cafe] List of exports of a module - are there alternatives?

2009-05-12 Thread Miguel Mitrofanov
I think that it's not nice to export 200 declarations from a single  
module.


On 12 May 2009, at 18:05, Maurício wrote:


Hi,

When we want to list which declarations are exported by a module
we do:

module Mod ( list of exports ) where ...

Are there propositions to alternatives to that (I could not
find one)? Like, say, add a do export or do not export
tag to declarations we want to (not) export?

(I think something like that could be nice when we have modules
with 200 declarations and just a few are (not) going to be
exported.)

Thanks,
Maurício


___
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] List of exports of a module - are there alternatives?

2009-05-12 Thread Andrew Wagner
On Tue, May 12, 2009 at 10:05 AM, Maurício briqueabra...@yahoo.com wrote:
snip

 (I think something like that could be nice when we have modules
 with 200 declarations and just a few are (not) going to be
 exported.)

 Thanks,
 Maurício


Uh, show me such a module, and I'll show you a module that's quite bloated
and desperately needs to be refactored.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Map lookup signature

2009-05-12 Thread Ryan Ingram
Maybe is an instance of Monad; the second signature is just more
general than the first.

class Monad m where
return :: a - m a
(=) :: m a - (a - m b) - m b
fail :: String - m a

Map lookup only uses return and fail; for Maybe these are defined
as follows:
   return x = Just x
   fail s = Nothing

So it's really the same thing.

  -- ryan

On Mon, May 11, 2009 at 8:37 AM, Nico Rolle nro...@web.de wrote:
 Hi everyone.

 The docs in the web on http://www.haskell.org/ghc/docs
 define Data.Map.lookup as follows:
 http://www.haskell.org/ghc/docs
 lookup :: Ord k = k - Map k a - Maybe a
 but my version of ghci does i like that:
 Data.Map.lookup :: (Ord k, Monad m) = k - Data.Map.Map k a - m a
 but i need the 1. one.
 my version of ghci is 6.8.2
 regards
 ___
 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] Stream-fusion without the lists

2009-05-12 Thread Ryan Ingram
Sure, but this definition leaks space, which I think is one of the
points that Reiner made.

  -- ryan

On Tue, May 12, 2009 at 5:39 AM, Roman Leshchinskiy r...@cse.unsw.edu.au 
wrote:
 On 12/05/2009, at 14:45, Reiner Pope wrote:

 The Stream datatype seems to be much better suited to representing
 loops than the list datatype is. So, instead of programming with the
 lists, why don't we just use the Stream datatype directly?

 I think the main reason is that streams don't store data and therefore don't
 support sharing. That is, in

 let xs = map f ys in (sum xs, product xs)

 the elements of xs will be computed once if it is a list but twice if it is
 a stream.

 Roman


 ___
 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] IO trouble

2009-05-12 Thread Xiao-Yong Jin
Hi,

I can't really describe it in the subject.  So let me try to
do it here.

I have two functions

 f :: a - b
 g :: (a - b) - c - d

and I use them as

 gf :: c - d
 gf = g f

Now I want to handle exceptions in f and redefine f as in f'

 f' :: a - IO (Either e b)

So my question is how to define gf' now to use f' instead of
f?

 gf' :: c - IO (Either e d)

Thanks in advance.
Xiao-Yong
-- 
c/*__o/*
\ * (__
*/\  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] haskell cuda?

2009-05-12 Thread Don Stewart
Lee, Chakravarty et al

Data Parallelism in Haskell : ICFP PC Portland 2009
http://bit.ly/17EQcl

The other thing to look for is Obsidian, from Chalmers

danielkcook:
 Hi,

 Does anyone know if there's a compiler from Data-Parallel Haskell to GPU  
 code?  I saw a paper on it a while back, but Google hasn't turned up any  
 code.

 Cheers,
 - Dan

 begin:vcard
 fn:Daniel K. Cook
 n:Cook;Daniel K.
 email;internet:danielkc...@gmail.com
 tel;cell:+44 (0) 7949 125 491
 x-mozilla-html:TRUE
 version:2.1
 end:vcard
 

 ___
 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] caml build

2009-05-12 Thread Vasili I. Galchin
Hi Nicolas,

  I am starting a caml build. I want line by line which module is
being built so when I get an error I have a context to reason about to fix
the problem. Got it?

Regards,

Vasili

On Tue, May 12, 2009 at 7:23 AM, Nicolas Pouillard 
nicolas.pouill...@gmail.com wrote:

 Excerpts from Vasili I. Galchin's message of Tue May 12 00:27:26 +0200
 2009:
  Hello,
 
I have forgotten whether I sent this posting out. Sorry if I did (I
  didn't  see on Haskell cafe archive).
 
I am building Swish and getting an error. I want to follow the
  progress of swish build ... I don't see an additional parameter like
  verbose mode that will tell which swish component is being built. ???

 I don't get the relation with the subject of your post, can you elaborate?

 Best regards,

 --
 Nicolas Pouillard

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


Re: [Haskell-cafe] Structural sharing in haskell data structures?

2009-05-12 Thread Don Stewart
wagner.andrew:
 So I've been reading a lot about a (relatively) new language called Clojure.
 One of its goals is to make concurrency easier via a built-in home-grown STM.
 Anyway, one of the ways it tries to do this is to have completely immutable
 data structures. Every time I read a tutorial about this in Clojure, it says
 ...yes, it sounds awful to think that your whole data structure gets copied
 every time you want to make a change to it, but it's sane because of a
 technique called structural sharing. Yet every time I hear immutability 
 talked
 about in Haskell, what I hear is ...yes, it sounds awful to think that your
 whole data structure gets copied every time you want to make a change to it,
 but it's sane because of laziness...unless you need the whole data
 structure So I'm just curious, does GHC use structural sharing or
 something similar? Do other implementations? Does it matter?


Purity allows our data structures to have a lot of sharing.
This is separate to laziness.

Laziness lets us build up interesting structures that have unusual
sharing.

Actually, what kind of persistant structures does Clojure have at this
stage? I was under the impression they were reusing Java data
structures. E.g. some of the nicer ones on hackage are zippers, patricia
tries, finger trees, which I can't imaging have been ported.

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


Re: [Haskell-cafe] haskell cuda?

2009-05-12 Thread Scott A. Waterman

Try reaching Manuel Chakravarty,  http://justtesting.org/
and his colleague Sean Lee at Galois.

Slides from his talk on GPU.gen :
  Just gave my talk on Data Parallelism in Haskell at PSU; here the  
slides: http://bit.ly/17EQcl


and slides from an earlier Galois talk:
http://www.galois.com/blog/2008/08/29/gpugen-bringing-the-power-of-gpus-into-the-haskell-world/


--ts

On May 12, 2009, at 9:18 AM, Dan wrote:


Hi,

Does anyone know if there's a compiler from Data-Parallel Haskell to  
GPU code?  I saw a paper on it a while back, but Google hasn't  
turned up any code.


Cheers,
- Dan
danielkcook.vcf___
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] Main function error

2009-05-12 Thread Jochem Berndsen
applebiz89 wrote:
 main :: IO ()
 main = do
  doFilmsInGivenYear films
  main

You pass as argument to 'doFilmsInGivenYear' the value 'films', which is
not defined. Instead, I think you meant 'testDatabase'.

All the best,

-- 
Jochem Berndsen | joc...@functor.nl
GPG: 0xE6FABFAB
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with text and text-icu packages

2009-05-12 Thread Bryan O'Sullivan
On Tue, May 12, 2009 at 7:16 AM, David Carter david.m.car...@gmail.comwrote:

 Specifically, a1.txt contains bytes 97 and 10, while a2.txt contains
 bytes 224 160 139 237 144 164.

 Have I misconstrued things, or is this a bug?


It's probably a bug, and it has (I hope) already been found and fixed.
Please try the darcs version of text instead:  http://code.haskell.org/text/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] haskell cuda?

2009-05-12 Thread Scott A. Waterman

Sean and Manuel are both at Univ. New South Wales
 http://www.cse.unsw.edu.au/~seanl/
 http://www.cse.unsw.edu.au/~chak/


On May 12, 2009, at 2:36 PM, Scott A. Waterman wrote:


Try reaching Manuel Chakravarty,  http://justtesting.org/
and his colleague Sean Lee at Galois.

Slides from his talk on GPU.gen :
 Just gave my talk on Data Parallelism in Haskell at PSU; here the  
slides: http://bit.ly/17EQcl


and slides from an earlier Galois talk:
http://www.galois.com/blog/2008/08/29/gpugen-bringing-the-power-of-gpus-into-the-haskell-world/


--ts

On May 12, 2009, at 9:18 AM, Dan wrote:


Hi,

Does anyone know if there's a compiler from Data-Parallel Haskell  
to GPU code?  I saw a paper on it a while back, but Google hasn't  
turned up any code.


Cheers,
- Dan
danielkcook.vcf___
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 cuda?

2009-05-12 Thread Dan
Doesn't look like there's code out there - will try e-mailing the 
authors of the various papers/presentations.


This e-mail also counts as an open plea to those compiler wizards 
working on this stuff: feel free to put beta buggy versions of your code 
online :)


Thanks,
- Dan

Scott A. Waterman wrote:

Try reaching Manuel Chakravarty,  http://justtesting.org/
and his colleague Sean Lee at Galois.

Slides from his talk on GPU.gen :
  Just gave my talk on Data Parallelism in Haskell at PSU; here the 
slides: http://bit.ly/17EQcl


and slides from an earlier Galois talk:
http://www.galois.com/blog/2008/08/29/gpugen-bringing-the-power-of-gpus-into-the-haskell-world/ 




--ts

On May 12, 2009, at 9:18 AM, Dan wrote:


Hi,

Does anyone know if there's a compiler from Data-Parallel Haskell to 
GPU code?  I saw a paper on it a while back, but Google hasn't turned 
up any code.


Cheers,
- Dan
danielkcook.vcf___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe




begin:vcard
fn:Daniel K. Cook
n:Cook;Daniel K.
email;internet:danielkc...@gmail.com
tel;cell:+44 (0) 7949 125 491
x-mozilla-html:TRUE
version:2.1
end:vcard

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


Re: [Haskell-cafe] Structural sharing in haskell data structures?

2009-05-12 Thread Andrew Wagner

 Purity allows our data structures to have a lot of sharing.
 This is separate to laziness.


Ah, so haskell does do it. Interesting that it so rarely comes up, whereas
it's frequently mentioned in clojure.



 Laziness lets us build up interesting structures that have unusual
 sharing.

 Actually, what kind of persistant structures does Clojure have at this
 stage? I was under the impression they were reusing Java data
 structures. E.g. some of the nicer ones on hackage are zippers, patricia
 tries, finger trees, which I can't imaging have been ported.


It has some built-in persistent data structures: lists, vectors (arrays),
maps, and sets. It also has strong interoperability with Java, so that any
existing Java library can easily be used in Clojure code. In some ways, that
makes it a VERY mature language already.


 -- Don

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


Re: [Haskell-cafe] Structural sharing in haskell data structures?

2009-05-12 Thread Don Stewart
wagner.andrew:
 Purity allows our data structures to have a lot of sharing.
 This is separate to laziness.
 
 
 Ah, so haskell does do it. Interesting that it so rarely comes up, whereas 
 it's
 frequently mentioned in clojure.

I think it is just assumed, since that's been the case for 20 years or
more now. Sharing is kind of exciting to the ex-Java people looking at
Clojure, I guess, since it's a new idea. So they talk about it.

 Laziness lets us build up interesting structures that have unusual
 sharing.
 
 Actually, what kind of persistant structures does Clojure have at this
 stage? I was under the impression they were reusing Java data
 structures. E.g. some of the nicer ones on hackage are zippers, patricia
 tries, finger trees, which I can't imaging have been ported.
 
 It has some built-in persistent data structures: lists, vectors (arrays), 
 maps,
 and sets. It also has strong interoperability with Java, so that any existing
 Java library can easily be used in Clojure code. In some ways, that makes it a
 VERY mature language already.

Certainly the JVM and its libraries are mature.

Looks like yet another example of tech incubation in Haskell, then
dispersal outwards to other langs. The more the better.

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


Re: [Haskell-cafe] Main function error

2009-05-12 Thread John Van Enk
What would you expect the program to output? You probably mean
'testDatabase' instead of 'films'.
/jve


On Tue, May 12, 2009 at 12:59 PM, applebiz89 applebi...@hotmail.com wrote:


 I have compiled each function independently and they have compiled the only
 problem is the main function..

 I keep getting the error 'films not defined' and I am not sure why

 [code]

 type Title = String
 type Director = String
 type Year = Int
 type Fan = String

 data Film = Film Title Director Year [Fan] deriving Show

 -- List of films

 testDatabase :: [Film]
 testDatabase = [ (Film Casino Royale Martin Campbell 2006 [Garry,
 Dave, Zoe])]

 -- Function

 filmsInGivenYear :: Year - [Film] - [String]
 filmsInGivenYear year' films = [ title | (Film title director year fans) -
 films, year == year']

 doFilmsInGivenYear :: [Film] - IO ()
 doFilmsInGivenYear films  = do putStrLn which year?
   text - getLine
   let year' = read text :: Int
   let answer = filmsInGivenYear year' films
   print answer

 main :: IO ()
 main = do
 doFilmsInGivenYear films
 main

 [/code]

 if the other functions are compiling without this error im not sure as to
 why the main function does not compile because of the films...any light on
 this?

 Thanks
 --
 View this message in context:
 http://www.nabble.com/Main-function-error-tp23506481p23506481.html
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

 ___
 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] Main function error

2009-05-12 Thread Alexander Dunlap
On Tue, May 12, 2009 at 9:59 AM, applebiz89 applebi...@hotmail.com wrote:

 I have compiled each function independently and they have compiled the only
 problem is the main function..

 I keep getting the error 'films not defined' and I am not sure why

 [code]

 type Title = String
 type Director = String
 type Year = Int
 type Fan = String

 data Film = Film Title Director Year [Fan] deriving Show

 -- List of films

 testDatabase :: [Film]
 testDatabase = [ (Film Casino Royale Martin Campbell 2006 [Garry,
 Dave, Zoe])]

 -- Function

 filmsInGivenYear :: Year - [Film] - [String]
 filmsInGivenYear year' films = [ title | (Film title director year fans) -
 films, year == year']

 doFilmsInGivenYear :: [Film] - IO ()
 doFilmsInGivenYear films  = do putStrLn which year?
                               text - getLine
                               let year' = read text :: Int
                               let answer = filmsInGivenYear year' films
                               print answer

 main :: IO ()
 main = do
         doFilmsInGivenYear films
         main

 [/code]

 if the other functions are compiling without this error im not sure as to
 why the main function does not compile because of the films...any light on
 this?

 Thanks

When you say 'doFilmsInGivenYear films', where does the variable
'films' come from? It's not defined anywhere in your program. That's
what the compiler is complaining about.

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


Re: [Haskell-cafe] Main function error

2009-05-12 Thread Daniel Fischer
Am Dienstag 12 Mai 2009 18:59:47 schrieb applebiz89:
 I have compiled each function independently and they have compiled the only
 problem is the main function..

 I keep getting the error 'films not defined' and I am not sure why

 [code]

 type Title = String
 type Director = String
 type Year = Int
 type Fan = String

 data Film = Film Title Director Year [Fan] deriving Show

 -- List of films

 testDatabase :: [Film]
 testDatabase = [ (Film Casino Royale Martin Campbell 2006 [Garry,
 Dave, Zoe])]

 -- Function

 filmsInGivenYear :: Year - [Film] - [String]
 filmsInGivenYear year' films = [ title | (Film title director year fans) -
 films, year == year']

 doFilmsInGivenYear :: [Film] - IO ()
 doFilmsInGivenYear films  = do putStrLn which year?
text - getLine
let year' = read text :: Int
let answer = filmsInGivenYear year' films
print answer



 main :: IO ()
 main = do
  doFilmsInGivenYear films
  main

There is no top level definition of films in your module, main doesn't take any 
parameter, 
so films is not in scope in main. You probably meant testDatabase.

However, main is not good even if you fix that, because every iteration of 
main, you work 
on the same database, you can't add new films or fans to films.
You should do something like

main :: IO ()
main = loop testDatabase

loop db = do
actionToRun - selectAction
newDB - actionToRun db
loop newDB

selectAction = do
putStrLn $ Select action to run:\n 1-print films from given year\n 2-add 
fan for some 
film\n ...
ln - getLine
let n = read ln
act = case n of
1 - doFilmsInGivenYear
2 - becomeFan

return act

doFilmInGivenYear :: [Film] - IO [Film]
doFilmInGivenYear films = do
 (your code)
return films

becomeFan :: [Film] - IO [Film]
becomeFan films = do
who - ask for name of fan
whichFilm - ask for film
let newFilms = makeFan who whichFilm films
return newFilms

then you can alter your database and have the modified database available in 
the next 
iteration of loop.

 [/code]

 if the other functions are compiling without this error im not sure as to
 why the main function does not compile because of the films...any light on
 this?

The other functions receive films as a parameter.


 Thanks

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


Re: [Haskell-cafe] Developing 3 dimensional interactive environments/functional objects

2009-05-12 Thread Peter Verswyvelen
You might want to contact the author of RogueStar GL
http://roguestar.downstairspeople.org/



On Tue, May 12, 2009 at 5:21 PM, Don Stewart d...@galois.com wrote:

 paulfrancis:
 Does any programmer on this mailing list have experience with
 developing 3
  dimensional interactive environments/functional objects within them, au
 Second
  Life? Is Haskell useful for such an endeavor?

 Mm..

Anygma
http://www.anygma.com/JobOfferA.html

gamr7
http://www.gamr7.com/

 Both use Haskell to some extent.
 ___
 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] Removing mtl from the Haskell Platform

2009-05-12 Thread roconnor
I wanted to pass this idea around the cafe to get some thoughts before 
submitting a trac on this topic.


I'd like to see the mtl removed from the Haskell Platform.

The mtl was a tremendous step forward when it was developed.  However, we 
have learned a few things about monad transformers since the development 
of the mtl, and it is time that we moved forward.


There are at least 3 significant problem with the mtl.

1) `pass' should not be a member functions of the MonadWriter class.  It 
is my understanding that there is no `MonadWriter w m = MonadWriter w 
(ContT s m)' instance because the `pass' function cannot be implemented. 
I'm also highly suspicious of some other methods too (I'm looking at you 
`local').


2) The `StateT s (Cont r a)' instance of callCC is wrong.  The paper on 
modular monad transformers 
http://www.cs.nott.ac.uk/~mjj/pubs/mmt/mmt.pdf describes why this is 
wrong.


3) I am told by many people that the order of the state and value pair in 
`State' is backwards.  Actually, I'm not entirely sure what the issue is 
here, but I trust the people who say this.


I think that use of the mtl should be deprecated so that we move on to 
improved monad transformer libraries.  Having the mtl in the Haskell 
Platform does the opposite by further entrenching its use, possibly to the 
point where we may not be able to get rid of it for years.


If I had to recommend a replace library, I would pick monadLib.  However, 
there are other libraries, such as the mmtl and transformers and it's 
related packages that I haven't looked at, and may also make fine 
replacements for the mtl.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] List of exports of a module - are there alternatives?

2009-05-12 Thread Daniel Peebles
I would like to see this too. Maybe just a private keyword that would
make everything after it invisible to the outside (or until a public
keyword appeared)?

On Tue, May 12, 2009 at 10:05 AM, Maurício briqueabra...@yahoo.com wrote:
 Hi,

 When we want to list which declarations are exported by a module
 we do:

 module Mod ( list of exports ) where ...

 Are there propositions to alternatives to that (I could not
 find one)? Like, say, add a do export or do not export
 tag to declarations we want to (not) export?

 (I think something like that could be nice when we have modules
 with 200 declarations and just a few are (not) going to be
 exported.)

 Thanks,
 Maurício


 ___
 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] Structural sharing in haskell data structures?

2009-05-12 Thread Tillmann Rendel

Hi,

Andrew Wagner wrote:

So I'm just curious, does GHC use
structural sharing or something similar? 


Structural sharing is not a feature of implementations, but of 
libraries. Consider this example:


  -- a function to change the head of a list
  replaceHead y xs = y : tail xs

  -- a big list
  xs = [1..1]

  -- two new list with changed head
  ys = replaceHead 42 xs
  zs = replaceHead 27 xs

  -- the length of our lists
  n = length xs + length ys + length zs

In this example, n will be 3, but even after evaluation xs, ys and 
zs, we have only 10002 cons cells allocated, because  cons cells are 
shared between xs, ys and zs. This happens automatically in every 
language with references or pointers. However, it is only sane to do 
with immutable data structures, so programmers have to add extra code to 
explicitly avoid structural sharing in impure languages.


Another example:

  xs = 1 : xs

This list is infinite, but we have only one cons cell allocated.

  Tillmann


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


Re: [Haskell-cafe] Main function error

2009-05-12 Thread Tillmann Rendel

applebiz89 wrote:

I have compiled each function independently and they have compiled the only
problem is the main function..

I keep getting the error 'films not defined' and I am not sure why


Well, because it is not defined :)


type Title = String
type Director = String
type Year = Int
type Fan = String

data Film = Film Title Director Year [Fan] deriving Show

-- List of films

testDatabase :: [Film]
testDatabase = [ (Film Casino Royale Martin Campbell 2006 [Garry,
Dave, Zoe])]

-- Function 


filmsInGivenYear :: Year - [Film] - [String]
filmsInGivenYear year' films = [ title | (Film title director year fans) -
films, year == year']

doFilmsInGivenYear :: [Film] - IO ()
doFilmsInGivenYear films  = do putStrLn which year?
   text - getLine
   let year' = read text :: Int
   let answer = filmsInGivenYear year' films
   print answer

main :: IO ()
main = do 


At this point, the following names are defined:
  - testDatabase
  - filmsInGivenYear
  - doFilmsInGivenYear
  - main
  - (and names from libraries)


 doFilmsInGivenYear films
 main


Here you use three names:

  - doFilmsInGivenYear (ok, is defined)
  - films (oups, not defined)
  - main (ok, is defined)

So ghc tries to figure out what you mean with films, and fails, because 
it was not defined. Try using one of the defined names instead of films.


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


Re: [Haskell-cafe] IO trouble

2009-05-12 Thread Lauri Alanko
On Tue, May 12, 2009 at 04:59:36PM -0400, Xiao-Yong Jin wrote:
  f :: a - b
  g :: (a - b) - c - d

  gf :: c - d
  gf = g f
 
 Now I want to handle exceptions in f and redefine f as in f'
 
  f' :: a - IO (Either e b)
 
 So my question is how to define gf' now to use f' instead of
 f?
 
  gf' :: c - IO (Either e d)

Use Control.Monad.Error.ErrorT, it's exactly for this. You have to
monadize g to be able to pass f' as an argument to it.

f' :: a - ErrorT e IO b
g' :: Monad m = (a - m b) - c - m d
gf' :: c - ErrorT e IO d
gf' = g' f'

Here e should be some fixed instance of Error.

HTH.


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


Re: [Haskell-cafe] Darcs as undo/redo system?

2009-05-12 Thread Trent W. Buck
Wolfgang Jeltsch g9ks1...@acme.softbase.org writes:

 Am Freitag, 8. Mai 2009 18:43 schrieb Jason Dagit:
 If you wanted to work on this, I would encourage you to read more
 about patch theory[1,2,3,4] and also try out libdarcs[5].

 Is libdarcs the same as the darcs library package on Hackage (which exports 
 the darcs API)?

The Darcs package (both on Hackage and elsewhere) builds two things: the
darcs(1) binary, and libHSdarcs.  The latter is what Jason was referring
to.  Note that currently it just exposes all our internal functions,
rather than providing a coherent (or stable!) API.

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


Re: [Haskell-cafe] Kind of confusing

2009-05-12 Thread Derek Elkins
On Tue, 2009-05-12 at 14:09 +0100, Philippa Cowderoy wrote:
 On Mon, 2009-05-11 at 20:43 -0400, Anton van Straaten wrote:
  Serious question: what is the significance of the question mark and 
  double question marks in those signatures, or better yet, where can I 
  read about it?
  
 
 I've forgotten where to find the details (try the GHC manual if you
 haven't already?), but IIRC they're part of how GHC handles boxing.
 

http://hackage.haskell.org/trac/ghc/wiki/IntermediateTypes

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


[Haskell-cafe] forall vs =

2009-05-12 Thread Daryoush Mehrtash
What is the difference between forall as in:

runSThttp://www.haskell.org/ghc/docs/6.10-latest/html/libraries/base/Control-Monad-ST.html#v%3ArunST::
(
forall s. 
SThttp://www.haskell.org/ghc/docs/6.10-latest/html/libraries/base/Control-Monad-ST.html#t%3ASTs
a) - a

and the = as in

evalStateThttp://www.haskell.org/ghc/docs/6.6/html/libraries/mtl/Control-Monad-State.html#v%3AevalStateT::
Monadhttp://www.haskell.org/ghc/docs/6.6/html/libraries/base/Control-Monad.html#t%3AMonadm
=
StateThttp://www.haskell.org/ghc/docs/6.6/html/libraries/mtl/Control-Monad-State.html#t%3AStateTs
m a - s - m a

thanks

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