Re: [Haskell-cafe] Inverse of HaskellDB

2010-09-29 Thread Chris Eidhof
On 28 sep 2010, at 17:33, Ozgur Akgun wrote:

 How do you define relationships between data types?
 
 Well, why is it any different from other fields? From one of your examples 
 [1], I'd expect you to have a list of questions in the Quiz data type, and if 
 necessary, a quiz field in the Question data type. This might be a bit tricky 
 but certainly achievable [2].

This is really tricky. For example, consider storing a large tree in the 
database:

 data Tree = Node Int Tree Tree | Leaf Int

This means you need to read the entire tree from the database. Or consider 
cyclic datastructures (such as the example you gave). How do you store this? 
The only way to inspect this is using a library like data-reify [1].

I think the problem might be a bit harder than you suspect.

Another way to solve it is using Sebastiaan Visser's framework, described in 
his paper [2], but that's also rather complicated.

-chris

[1]: http://hackage.haskell.org/package/data-reify
[2]: 
http://github.com/downloads/sebastiaanvisser/msc-thesis/wgp10-genstorage.pdf___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Inverse of HaskellDB

2010-09-28 Thread Chris Eidhof
Hey Jonathan,

I've done some work on this. The hard part is defining relationships between 
datatypes: how do you model this in Haskell? I've some code on github: 
http://github.com/chriseidhof/persist, you might be interested in that.

-chris

On 25 sep 2010, at 21:31, Jonathan Geddes wrote:

 Cafe,
 
 HaskellDB takes a database schema and produces Haskell data structures
 (plus some other query-related stuff for its EDSL query language).
 
 What I'm looking for is the inverse of this functionality. I want to
 create tables based on a Haskell data structure with a few simple
 rules. These rules include: if a field is not of the form `Maybe a'
 then it can't be nullable in the database. If a field is not a
 primitive (in the database) then it is actually stored in another
 table and a reference id is stored in the table. Tables are produced
 recursively, unless they already exist, etc.
 
 The HaskellDB approach is great for interfacing with existing tables,
 but in my case I already have data structures and now I would like a
 quick way to create tables to persist them.
 
 Does such a thing exist? If not, would you find it useful? I may take
 this up as a side project if it does not already exist and others
 would find it useful.
 
 Thanks,
 
 --Jonathan
 ___
 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] record update

2010-09-13 Thread Chris Eidhof
For completeness, using fclabels (yet another record package) you can write it 
like this:


 {-# LANGUAGE TemplateHaskell #-}
 module Records where
 
 import Data.Record.Label
 
 data MyRecord = MyRecord { _field1 :: String, _field2 :: Int, _field3 :: Bool 
 }
 
 $(mkLabels [''MyRecord])
 
 modifyThree f g h = modL field1 f
   . modL field2 g
   . modL field3 h

-chris

On 11 sep 2010, at 19:21, Jonathan Geddes wrote:

 I know that record updates is a topic that has become a bit of a dead
 horse, but here I go anyway:
 
 I find that most of the record updates I read and write take the form
 
 someUpdate :: MyRecord - MyRecord
 someUpdate myRecord = myRecord
{ field1 = f $ field1 myRecord
, field2 = g $ field2 myRecord
, field3 = h $ filed3 myRecord
}
 
 I find myself wishing I could write something more like
 
 someUpdate :: MyRecord - MyRecord
 someUpdate myRecord = myRecord
{ field1 = f
, field2 = g
, field3 = h
}
 
 with equivalent semantics. Here = reads is transformed by. Operator
 = could still be used for assignment as in current record updates.
 
 The best part about such an extension, in my opinion, is that it would
 open the door for anonymous lambda record updates. Something like:
 
 someUpdate :: MyRecord - MyRecord
 someUpdate = \{field1 = f, field2 = g, field3 = h}
 
 again, with the same semantics. This becomes possible because you no
 longer need to refer to the record within the {} part of the update.
 
 This would be useful, for example, in the State monad. We could write:
 
 someStateTransform :: State MyRecord ()
 someStateTransform = do
modify $ \{field1 = (++!)}
...
 
 where currently we see code like
 
 someStateTransform :: State MyRecord ()
 someStateTransform = do
modify $ \record-record{field1 = (++!) $ field1 record}
...
 
 which repeats the record name 3 times and the field name twice. The
 repetition just feels out of place next to all the other terse,
 readable Haskell code in the program.
 
 So what do my fellow haskellers think? Is this idea worth writing up a
 proposal for?
 
 Alternatively, can you offer me some advice on writing code in Haskell
 2010 that avoids the ugly, repetitive style of record update?
 
 --Jonathan
 ___
 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] help me evangelize haskell.

2010-09-05 Thread Chris Eidhof
On 5 sep 2010, at 09:28, Ben Lippmeier wrote:

 
 On 05/09/2010, at 2:38 AM, Michael Litchard wrote:
 
 I'll be starting a new job soon as systems tool guy. The shop is a
 perl shop as far as internal automation tasks go. But I am fortunate
 to not be working with bigots. If they see a better way, they'll take
 to it. So please give me your best arguments in favor of using haskell
 for task automation instead of perl, or awk or any of those scripting
 lanugages.
 
 Try to avoid religious arguments like by using Perl you're living in a state 
 of sin, and focus on look how much easier it is to do X in Haskell. 
 
 Grandiose, hand-wavy assertions like strong typing leads to shorter 
 development times and more reliable software don't work on people that 
 haven't already been there and done that. When you try to ram something down 
 someone's throat they tend to resist. However, if you can provide something 
 tasty and appealing they'll eat it themselves. Write a nice program, show it 
 to your Perl programmer, and if they also think it's nice -- then you've 
 already won.

I've had success in situations with tight deadlines: the only way I got it done 
quickly and without bugs is by using Haskell (as opposed to PHP). Another place 
where you might have success is by writing a small compiler or interpreter for 
an internal language. Start small (in a niche, if you will) and expand upon 
that.

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


Re: [Haskell-cafe] Statically tracking validity - suggestions?

2010-08-31 Thread Chris Eidhof
On 31 aug 2010, at 08:24, strejon wrote:

 
 Hello. I'm using Haskell to write a specification for some software. The
 software uses certificates (standard X.509 certificates) and stores user
 name information in the Subject's CommonName field.
 
 The X.509 standard doesn't actually require the presence of a CommonName
 field so the contents of the Subject section (with the rest of the fields
 omitted) are just represented by a Maybe User_Name.
 
 import Data.List (find, concat)
 import Data.Maybe (fromJust, isJust)
 
 type User_Name= String
 type Public_Key   = Integer
 data Subject_Name = Subject_Name (Maybe User_Name) deriving (Show, Eq)
 
 data Certificate = Certificate {
  certificate_subject :: Subject_Name,
  certificate_key :: Public_Key,
  certificate_issuer  :: String,
  certificate_serial  :: Integer
 } deriving (Show, Eq)
 
 This is all well and good, but the problem is that the validity of
 certificates isn't tracked statically and I have to use the following
 as guards on all functions that only expect valid certificates (and
 inevitably handle cases that I know can't actually happen but
 have to be handled in pattern matching and the like, bloating
 the specification):
 
 user_name :: Subject_Name - Maybe User_Name
 user_name (Subject_Name name) = name
 
 is_valid :: Certificate - Bool
 is_valid = isJust . user_name . certificate_subject
 
 I'm aware of phantom types and the like, but I've been unable to
 work out how to use them (or another type system extension)
 to properly track validity on the type level. I'd want something
 like:
 
 validate :: Certificate Possibly_Valid - Maybe (Certificate Valid)
 
 With later functions only accepting values of type Certificate Valid.
 
 Is there a simple way to do this?

Yes. Introduce a wrapper datatype, ValidCertificate. Create a module and export 
only the wrapper datatype and a way to construct ValidCertificates in a safe 
way:

 module ValidateCertificate 
   ( ValidCertificate,
 fromValidCertificate,
 createValidCertificate
   ) where
 
 data ValidCertificate = ValidCertificate {fromValidCertificate :: Certificate}
 
 createValidCertificate :: Certificate - Maybe ValidCertificate
 createValidCertificate c | is_valid c = Just (ValidCertificate c)
  | otherwise  = Nothing
 
 is_valid :: Certificate - Bool
 is_valid = isJust . user_name . certificate_subject

The trick is not to export the constructor, but only a verified way to 
construct values of ValidCertificate.

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


Re: [Haskell-cafe] ANNOUNCE: DSTM 0.1.1

2010-08-04 Thread Chris Eidhof
This looks very cool! It would be nice to put the pdf online somewhere, and add 
a link from the package documentation. Also, the chat client seems to have some 
problems with output buffering on my system (OS X, GHC 6.12).

-chris

On 3 aug 2010, at 10:35, Frank Kupke wrote:

 Hi,
 DSTM is an implementation of a robust distributed Software Transactional 
 Memory (STM) library for Haskell. Many real-life applications are distributed 
 by nature. Concurrent applications may profit from robustness added by 
 re-implementation as distributed applications. DSTM extends the STM 
 abstraction to distributed systems and presents an implementation efficient 
 enough to be used in soft real-time applications. Further, the implemented 
 library is robust in itself, offering the application developer a high 
 abstraction level to realize robustness, hence, significantly simplifying 
 this, in general, complex task.
 The DSTM package consists of the DSTM library, a name server application, and 
 three sample distributed programs using the library. Provided are a simple 
 Dining Philosophers, a Chat, and a soft real-time Bomberman game application. 
 Distributed communication is transparent to the application programmer. The 
 application designer uses a very simple name server mechanism to set up the 
 system. The DSTM library includes the management of unavailable process nodes 
 and provides the application with abstract error information thus 
 facilitating the implementation of robust distributed application programs.
 For usage please look into the documentation file: DSTMManual.pdf.
 
 
 The package including the documentation can be found on:
 
 http://hackage.haskell.org/package/DSTM-0.1.1
 
 Best regards,
 Frank Kupke
 
 
 ___
 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] Software architecture

2010-08-04 Thread Chris Eidhof
I think the general process is the same. You define your components, try to 
decouple them as much as possible and implement them. One thing that is 
different from other languages: try to write as much pure code as possible. 
This is great for creating composable components.

There are several different ways to structure your programs. The Utrecht 
Haskell Compiler is structured using attribute grammars, which is (similar to) 
aspect-oriented programming.

Another architectural pattern you see a lot is that a program is provided as a 
library and a very small main function. A very good example of this is XMonad.

You could also look at http://www.haskell.org/haskellwiki/Haskell_in_industry, 
which gives some pointers to commercial projects and how they are structured.

-chris

On 4 aug 2010, at 13:07, Charles-Pierre Astolfi wrote:

 Hey there,
 
 I'm searching for software designs in Haskell ; for example, I have a
 pretty good ideo of how I would arrange my modules/classes (in
 ocaml/(java/c++)) and how they would all fit together to create, say,
 a website aspirator. But I don't have any clue of the right way to do
 it with Haskell.
 
 I don't need a solution for this example, I'd just like to see how to
 manage non-trivial code. I haven't found any pointers on the
 interwebs.
 
 On an unrelated note, what is the simplest way to get the llvm
 bitcode? I understand I can compile myself ghc but it there an easier
 way?
 
 Thanks a lot!
 --
 Cp
 ___
 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] [C Binding] Turning the mutable to immutable?

2010-07-07 Thread Chris Eidhof
On 5 jul 2010, at 23:48, Yves Parès wrote:

 Hello,
 
 I don't know if some of you are familiar with the SFML library (stands for 
 Simple and Fast Multimedia Library) -- http://sfml-dev.org
 As SDL, SFML is a 2D graphics library, but conversely to SDL it provides a 
 hardware-accelerated drawing, through OpenGL.
 Well, I'm currently writing its Haskell binding, and I'm stuck with design 
 issues.
 What I'm heading to is a full IO binding, and that's what I'd like to avoid.

Have you considered writing a low-level binding and building a high-level 
library on top of that?

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


Re: [Haskell-cafe] [C Binding] Turning the mutable to immutable?

2010-07-07 Thread Chris Eidhof
I think it might influence performance, but it doesn't have to be that much. 
There are some optimization tricks you can apply to deal with this. Premature 
optimization is the root of all evil ;)

-chris

On 7 jul 2010, at 11:40, Yves Parès wrote:

 That's indeed an advice I've read [1].
 But wouldn't it damage the performances, since code will have to go through 
 an extra layer?
 
 [1] http://blog.ezyang.com/2010/06/principles-of-ffi-api-design
 
 2010/7/7 Chris Eidhof ch...@eidhof.nl
 On 5 jul 2010, at 23:48, Yves Parès wrote:
 
  Hello,
 
  I don't know if some of you are familiar with the SFML library (stands for 
  Simple and Fast Multimedia Library) -- http://sfml-dev.org
  As SDL, SFML is a 2D graphics library, but conversely to SDL it provides a 
  hardware-accelerated drawing, through OpenGL.
  Well, I'm currently writing its Haskell binding, and I'm stuck with design 
  issues.
  What I'm heading to is a full IO binding, and that's what I'd like to avoid.
 
 Have you considered writing a low-level binding and building a high-level 
 library on top of that?
 
 -chris
 

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


Re: [Haskell-cafe] learning advanced haskell

2010-06-14 Thread Chris Eidhof
On 14 jun 2010, at 07:42, Aran Donohue wrote:

 Hi Cafe,
 
 I've been doing Haskell for a few months, and I've written some mid-sized 
 programs and many small ones. I've read lots of documentation and many 
 papers, but I'm having difficulty making the jump into some of the advanced 
 concepts I've read about.
 
 How do people build intuitions for things like RankNTypes and arrows? (Is the 
 answer Get a PhD in type theory?) Normally I learn by coding up little 
 exercise programs, but for these I don't have good intuitions about the kinds 
 of toy problems I ought to try to solve that would lead me to understand 
 these tools better. 

I learned my advanced stuff in two ways:

1. I followed excellent courses at Utrecht University, where they teach (among 
other things) advanced functional programming.
2. I just read a lot, which is a lot slower than 1.
3. By building my own programs, I inevitably find my self stuck and while 
searching for a solution, sometimes these concepts are the answer. For example, 
once I had a monadic program and I wanted to serialize/inspect the program, 
which turned out to be impossible in my case. The solution was to write it down 
using arrows (thus I had to learn arrows and also arrow-notatation). I think 
(for me) this is the most powerful way to learn new advanced concepts. I need 
practical problems to keep myself motivated.

 For systems like Template Haskell and SYB, I have difficulty judging when I 
 should use Haskell's simpler built-in semantic abstractions like functions 
 and typeclasses and when I should look to these other mechanisms.

Sometimes Template Haskell or SYB is the answer, and it's a matter of style, 
but I try to avoid them as much as possible. I find that generic programming in 
the style of regular [1] or emgm [2] is often much simpler.

Some more tips: subscribe to planet haskell, if you haven't done that already. 
Try to find ICFP/JFP/etc papers online that interest you.

-chris

[1]: http://hackage.haskell.org/package/regular
[2]: 
http://hackage.haskell.org/package/emgm___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Steven S. Skiena of The Algorithm Design Manual, Second Edition, 2008 has sent me a message that if there is a Haskell page of algorithms he will link to it.

2010-05-28 Thread Chris Eidhof
Nhe most important reference in literature might be Okasaki's Purely functional 
data structures:

@book{okasaki1999purely,
  title={{Purely functional data structures}},
  author={Okasaki, C.},
  year={1999},
  publisher={Cambridge Univ Pr}
}

-chris

On 28 mei 2010, at 05:23, Casey Hawthorne wrote:

 Hi:
 
 Steven S. Skiena of The Algorithm Design Manual, Second Edition,
 2008 has sent me a message that if there is a Haskell page of
 algorithms he will link to it.
 
 So, is there such a page and/or is there some collection(s) of
 algorithms and data structures some where that I can massage into the
 shape of his book?
 
 :)
 
 --
 Regards,
 Casey
 ___
 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] [ANNOUNCE] First Public Release of the Snap Framework

2010-05-22 Thread Chris Eidhof
Awesome! Congratulations on the first release, I look forward to working with 
it. Also, the web design is great, possibly the best designed Haskell library 
website I've seen so far.

-chris

On 22 mei 2010, at 07:25, Gregory Collins wrote:

 Hello all,
 
 To coincide with Hac Phi 2010
 (http://www.haskell.org/haskellwiki/Hac_%CF%86), the Snap team is happy
 to announce the first public release of the Snap Framework, a simple and
 fast Haskell web programming server and library for unix systems. For
 installation instructions, documentation, and more information, see our
 website at http://snapframework.com/.
 
 Snap is well-documented and has a test suite with a high level of code
 coverage, but it is early-stage software with still-evolving interfaces. Snap
 is therefore most likely to be of interest to early adopters and potential
 contributors.
 
 Snap is BSD-licensed and currently only runs on Unix platforms; it has been
 developed and tested on Linux and Mac OSX Snow Leopard.
 
 Snap Features:
 
 * A simple and clean monad for web programming, similar to happstack's but
   simpler.
 
 * A *fast* HTTP server library with an optional high-concurrency backend
   (using libev).
 
 * An XML-based templating system for generating xhtml that allows you to bind
   Haskell functionality to XML tags in your templates.
 
 * Some useful utilities for web handlers, including gzip compression and
   fileServe.
 
 * Iteratee-based I/O, allowing composable streaming in O(1) space without any
   of the unpredictable consequences of lazy I/O.
 
 If you have questions or comments, please contact us on our mailing list
 (http://mailman-mail5.webfaction.com/listinfo/snap) or in the
 #snapframework channel on the freenode IRC network.
 
 Cheers,
 G
 -- 
 Gregory Collins g...@gregorycollins.net
 ___
 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] cabal problem on OS X

2010-05-22 Thread Chris Eidhof
I have a different problem (also after doing a cabal update): I get a bus 
error. I just created this ticket for it: 
http://hackage.haskell.org/trac/hackage/ticket/691

-chris

On 22 mei 2010, at 13:20, Bill Atkins wrote:

 When I run cabal update on my Mac (Snow Leopard, Intel), I get:
 
 % cabal update
 Downloading the latest package list from hackage.haskell.org
 cabal: Codec.Compression.Zlib: incompatible zlib version
 
 Anyone else seeing this?  Reinstalling the Haskell Platform hasn't helped.
 
 Thanks!
 ___
 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] polyvariadic function for Applicative instances

2010-05-10 Thread Chris Eidhof
Maybe this is what you are looking for: 
http://www.haskell.org/haskellwiki/Idiom_brackets

-chris

On 9 mei 2010, at 18:39, Xiao-Yong Jin wrote:

 Hi,
 
 Is it possible to have a function accept variable number of
 arguments, such that 'f' can be instantiated to different
 concrete types as
 
 f :: Applicative a = (e1 - f) - a e1 - A f
 f g a = pure g * a
 
 f :: Applicative a = (e1 - e2 - f) - a e1 - a e2 - A f
 f g a b = pure g * a * b
 
 Thanks,
 Xiao-Yong
 -- 
 Jc/*__o/*
 X\ * (__
 Y*/\  
 ___
 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] How efficient is read?

2010-05-10 Thread Chris Eidhof
There is the ChristmasTree package 
(http://hackage.haskell.org/package/ChristmasTree) which provides a very fast 
read alternative by deriving grammars for each datatype. If you want to know 
the speed differences, see http://www.cs.uu.nl/wiki/bin/view/Center/TTTAS for 
more information (it's in the Haskell Do You Read Me paper, see section 5 for a 
comparison of efficiency).

-chris

On 9 mei 2010, at 05:32, Tom Hawkins wrote:

 I have a lot of structured data in a program written in a different
 language, which I would like to read in and analyze with Haskell.  And
 I'm free to format this data in any shape or form from the other
 language.
 
 Could I define a Haskell type for this data that derives the default
 Read, then simply print out Haskell code from the program and 'read'
 it in?  Would this be horribly inefficient?  It would save me some
 time of writing a parser.
 
 -Tom
 ___
 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] Re: lhs2TeX - lhs2TeX.fmt missing

2010-05-05 Thread Chris Eidhof
I've generated large LaTeX documents with several modules without too much 
hassle. The key was to use %include a lot, as well as conditionals. Lots of %if 
False around import statements.

-chris

On 5 mei 2010, at 20:18, Pierre-Etienne Meunier wrote:

 By the way, if someone on this list has got too much time, he could write 
 something that would fulfill the goals of literate programming -- à la web 
 and cweb.
 Knuth was able to make books with his source code. I believe that lhs2tex is 
 great for classes about haskell or fp, but I never found it satisfying for 
 programs with several modules, for instance.
 
 
 
 El 05/05/2010, a las 12:42, Ozgur Akgun escribió:
 
 OK, I've found them!
 
 They were under /Users/username/.cabal/share/lhs2tex-1.15 and this path 
 was not in the search path of lhs2TeX.
 I'm using Snow Leoprad. This might be a bug I guess?
 
 Anyway, problem solved for me.
 
 Best,
 
 On 5 May 2010 16:03, Ozgur Akgun ozgurak...@gmail.com wrote:
 Hi all,
 
 I am trying to get lhs2TeX to work. I installed the package using cabal, and 
 now I try to run it on a very simple *.lhs file.
 
 But it blames me and says user error, cannot find lhs2TeX.fmt:
 
 lhs2TeX: user error (File `lhs2TeX.fmt' not found in search path:
 
 And, when I check the search path, there really is no lhs2TeX.fmt file. 
 Should I download it separately or something like that?
 
 PS: Thanks for the great package to the authors!
 
 Best,
 Ozgur Akgun
 
 
 
 -- 
 Ozgur Akgun
 ___
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Cabal-install: bus error

2010-05-03 Thread Chris Eidhof
Hey everyone,

After I upgraded to a newer cabal-install my cabal-install broke again: I get a 
Bus Error when doing cabal update or cabal install something. The version 
that was bundled with the Haskell platform worked fine, but now it's broken 
again. I'm not sure what it was that went wrong or how to debug this.

The previous time I had Bus Errors I upgraded to the newest available Haskell 
Platform release and started from scratch. I would prefer not to do that again. 
However, I don't really know how to solve the Bus Error. Does anyone have a 
clue where to start? Or is there a way to undo my cabal-install upgrade?

-chris

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


Re: [Haskell-cafe] Re: FRP for game programming / artifical life simulation

2010-04-28 Thread Chris Eidhof
I agree. This would be an extremely useful feature, not only for game 
development, but also for web development. We often use continuations as a way 
to add state to the web, but this fails for two reasons: whenever the server 
restarts, or when we scale to multiple machines.

However, I think it is not easy to do this: traversing the heap should be 
relatively simple, however: what if a function implementation changes?

An interesting approach is taken by the Clean guys: they use dynamics, which 
can store a function, a type representation and the heap to disk. See also this 
old thread: http://www.mail-archive.com/haskell-cafe@haskell.org/msg34054.html

-chris

On 28 apr 2010, at 19:50, Peter Verswyvelen wrote:

 Interesting topic. I find it a bit annoying that Haskell doesn't
 provide support to save functions. I understand this is problematic,
 but it would be very nice if the Haskell runtime provided a way to
 serialize (part of) the heap, making sure that pointers to compiled
 functions get resolved correctly.
 
 
 
 On Wed, Apr 28, 2010 at 6:42 PM, Christopher Lane Hinson
 l...@downstairspeople.org wrote:
 
 On Wed, 28 Apr 2010, Ben wrote:
 
 I want to save the state of the system to disk, I want to be able to
 play the game, pick a point to stop, freeze it and turn off the
 computer, and then come back later and resume.  Why is that unwise?
 What are the alternatives?
 
 B
 
 On Tue, 27 Apr 2010, Ben wrote:
 
 slightly off topic, but how does one handle pausing / saving /
 restarting in the FRP framework, especially the arrowized version?
 
 If we're about Arrow FRP, remember that the arrow typeclass includes a
 function, 'arr', that admits any function as a parameter, and these are in
 general impossible to serialize to disk. Since Arrow FRP ends up roughly in
 a form of: FRP a b c = a b (c, FRP a b c), an Arrow instance is actually the
 state of the system.  There are a few tactics that would get us around this
 limitation, but they are rather severe.   You could render 'arr' useless in
 several ways, or you could save all the input to a system and replay it.
 
 But I would argue that even if you wanted to do this, saving an FRP system
 is, to me, like saving a system in the IO monad, (which, there are tactics
 that would let you do this, too).  It's probablematic in part because the
 FRP system probably has active hooks into the user interface, such as
 windows and other widgits that it owns, and possibly other devices (such as
 physical rocket engines).  Even if the FRP system is completely pure and can
 be referenced by a single pointer, it is easily and rightfully aware of
 specific details of the hardware it is embedded in.
 
 So it seems to me that what we actually want, to do complex simulations with
 persistance, is not an FRP system that interacts with the outside world, but
 a self-contained, self-interacting, differential equation hairball.  Such
 a system would be very cool, but I think that the numerical algorithms
 needed exceed what an FRP system should try to provide.
 
 Friendly,
 --Lane
 ___
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GSOC idea: Haskell JVM bytecode library

2010-03-26 Thread Chris Eidhof
We've used this library to generate a prototype JVM backend for UHC about a 
year ago, and it Just Worked. That was probably on 6.10 or 6.8.

-chris

On 26 mrt 2010, at 21:33, Brian Alliet wrote:

 On Fri, Mar 26, 2010 at 08:01:57PM +, Alexandru Scvortov wrote:
 I'm thinking of writing a library for analyzing/generating/manipulating JVM 
 bytecode.  To be clear, this library would allow one to load and work with 
 JVM 
 classfiles; it wouldn't be a compiler, interpretor or a GHC backend.
 
 I wrote a JVM classfile library as part of LambdaVM (which is actually
 a JVM backend for GHC, it is a bit bit-rotted though, I need to get
 back into it):
 
 http://darcs.brianweb.net/hsjava/
 
 It requires my hsutils library (also available on darcs.brianweb.net).
 I haven't touched the code in a while and it might need a tweak or two
 with recent GHC versions. Drop me a line if you have any trouble
 getting it working (and patches are certainly welcome).
 
 There isn't much documentation, besides the code and a few example
 programs that dump a pretty printed version of the data structure. I'd
 be more than happy to give anybody who is interested in using it some
 pointers though.
 
 -Brian
 ___
 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] GSOC idea: Haskell JVM bytecode library

2010-03-26 Thread Chris Eidhof
On 26 mrt 2010, at 22:37, Alexandru Scvortov wrote:

 How stable is it?

I don't know. I remember that we didn't have to change anything and that 
everything just worked.

 Was it easy to use?

Actually yes, because:

 Did it have enough documentation?

I think we used the Java documentation. The nice thing about the hsjava library 
is that it provides datatypes that closely match assembly.

 Do you think it could use a rewrite?  If so, what should be done differently?
 
 Could it be extended into something more?

I guess it could be double-checked and released on hackage. Maybe add tail-call 
support to the library?

 (sorry for the barrage of questions, but you're the one person I've seen so 
 far, apart from the original programmer, that has experience with this)

Only very little experience. It was a project of a couple of weeks.

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


Re: [Haskell-cafe] derivable type classes

2010-03-23 Thread Chris Eidhof
No. A solution for this (depending on the type class you want to derive) is 
Generic Programming. Using Generic Programming, you can define functions that 
work on the structure of the type.

For example, take a look at the regular package [1]. It provides all the 
functionality to write your own generic functions.

-chris

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

On 23 mrt 2010, at 11:52, Ozgur Akgun wrote:

 Can a user define a derivable type class of her own? If yes, how?
 
 Cheers,
 
 -- 
 Ozgur Akgun
 ___
 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] ANN: Salvia-1.0.0

2010-03-23 Thread Chris Eidhof
On 23 mrt 2010, at 14:27, Bas van Dijk wrote:

 On Tue, Mar 23, 2010 at 2:13 PM, Sebastiaan Visser sfvis...@cs.uu.nl wrote:
 Nice! This is certainly worth it.
 
 BTW What's the git equivalent of 'darcs send -o filename' which
 saves the patches to filename? I would rather send my patches as
 email attachements instead of copying my repository to my webserver.
 (Note this is the first time I used git)

The way I like to work is forking the repository on github (you need an account 
for that, though). Then you can push the changes to your forked repository and 
the original author will see it.

Have a look at http://book.git-scm.com/5_git_and_email.html to see how you can 
send changes by email.

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


[Haskell-cafe] ANN: regular-web 0.1 | generic web programming in Haskell

2010-03-21 Thread Chris Eidhof
From the ZuriHac hackathon, I am happy to announce the first release of the 
regular-web package [1]. The package contains functions for generic web 
programming: generating HTML, JSON and Formlets. It is based on the regular 
generic programming library [2].

Generic HTML and forms are often not sufficient for real purposes, so we 
encourage the use of regular-web in combination with the fclabels package [3].  
There is an example in the documentation of the Formlets module. Furthermore, 
there is a slightly larger example [4] on github that shows off some more 
features of the package.

This is a preliminary release and the API will probably change. I am interested 
to see what other people think of this. So please send me your comments or fork 
the project on github.  

[1]: http://hackage.haskell.org/package/regular-web
[2]: http://hackage.haskell.org/package/regular
[3]: http://hackage.haskell.org/package/fclabels
[4]: http://github.com/chriseidhof/regular-web/blob/master/Example.lhs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Code that doesn't compile - but should :)

2010-03-16 Thread Chris Eidhof
What about this?

 {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances,
  UndecidableInstances, FlexibleContexts, EmptyDataDecls, ScopedTypeVariables,
  TypeOperators, TypeSynonymInstances #-}
 
 data Data k = Pair Integer (() - k)
 data RecData = RecData (Data RecData)
 mk_data x = RecData(Pair x (\() - mk_data (x+1)))
 

The I had to change the type of the Converter typeclass

 class Converter a f where convert :: f a - a
 
 -- instance Converter RecData Data where
 --  convert (RecData r) = r
 
 class Selector s a where select :: s - a
 

And explicitly quantify the type variables:

 f :: forall f s a . (Selector s (a-f a), Converter a f) = s - (a-a)
 f s =
  let method = select s :: a - f a
  in (\x -
let res = method x
in convert res)

-chris

On 16 mrt 2010, at 10:36, Giuseppe Maggiore wrote:

 The error message (obtained by loading the file with ghci) is:
 GHCi, version 6.10.4: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.
 [1 of 1] Compiling Main ( 
 C:\Users\pulcy\Desktop\Papers\Monads\Objec
 tiveMonad\HObject\Experiments\FunctorsProblems.hs, interpreted )
 
 C:\Users\pulcy\Desktop\Papers\Monads\ObjectiveMonad\HObject\Experiments\Functors
 Problems.hs:18:15:
 Could not deduce (Selector s (f a - a))
   from the context (Selector s (a1 - f1 a1), Converter a1 f1)
   arising from a use of `select'
at 
 C:\Users\pulcy\Desktop\Papers\Monads\ObjectiveMonad\HObjec
 t\Experiments\FunctorsProblems.hs:18:15-22
 Possible fix:
   add (Selector s (f a - a)) to the context of
 the type signature for `f'
   or add an instance declaration for (Selector s (f a - a))
 In the expression: select s
 In the definition of `method': method = select s
 In the expression:
 let method = select s in (\ x - let res = ... in convert res)
 
 C:\Users\pulcy\Desktop\Papers\Monads\ObjectiveMonad\HObject\Experiments\Functors
 Problems.hs:21:11:
 Couldn't match expected type `a1' against inferred type `f a'
   `a1' is a rigid type variable bound by
the type signature for `f'
  at 
 C:\Users\pulcy\Desktop\Papers\Monads\ObjectiveMonad\HObject\Expe
 riments\FunctorsProblems.hs:16:18
 In the expression: convert res
 In the expression: let res = method x in convert res
 In the expression: (\ x - let res = method x in convert res)
 Failed, modules loaded: none.
 Prelude
 
  
 On Tue, Mar 16, 2010 at 2:31 AM, Ivan Lazar Miljenovic 
 ivan.miljeno...@gmail.com wrote:
 Giuseppe Maggiore giuseppe...@gmail.com writes:
 
  Hi! Can anyone tell me why this code does not work? I cannot seem to
  figure why it is broken...
 
 The error message (and how you got it) would help...
 
  {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, 
  FlexibleInstances,
UndecidableInstances, FlexibleContexts, EmptyDataDecls, 
  ScopedTypeVariables,
TypeOperators, TypeSynonymInstances #-}
 
 You sure you have enough language extensions there? ;-)
  
 Barely :)
  
 
 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 IvanMiljenovic.wordpress.com
 
 
 
 -- 
 Giuseppe Maggiore
 Ph.D. Student (Languages and Games)
 Microsoft Student Partner
 Mobile: +393319040031
 Office: +390412348444
 
 
 ___
 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] Code that doesn't compile - but should :)

2010-03-16 Thread Chris Eidhof
On 16 mrt 2010, at 10:58, Giuseppe Maggiore wrote:

 Well, first of all thanks!
 Second, why the need for explicit quantification?

I'm not sure, but I think it has to do with ambiguity. I think it's similar to 
the problem:

 readShow :: (Read a, Show a) - String - String
 readShow = show . read

We need to explicitly quantify over the type variables so that we can give an 
explicit type signature on the following line:

 let method = select s :: a - f a

There might be an easier way to do this, but I'm not sure how exactly.

-chris


 
 On Tue, Mar 16, 2010 at 2:39 AM, Chris Eidhof ch...@eidhof.nl wrote:
 What about this?
 
  {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, 
  FlexibleInstances,
   UndecidableInstances, FlexibleContexts, EmptyDataDecls, 
  ScopedTypeVariables,
   TypeOperators, TypeSynonymInstances #-}
 
  data Data k = Pair Integer (() - k)
  data RecData = RecData (Data RecData)
  mk_data x = RecData(Pair x (\() - mk_data (x+1)))
 
 
 The I had to change the type of the Converter typeclass
 
  class Converter a f where convert :: f a - a
 
  -- instance Converter RecData Data where
  --  convert (RecData r) = r
 
  class Selector s a where select :: s - a
 
 
 And explicitly quantify the type variables:
 
  f :: forall f s a . (Selector s (a-f a), Converter a f) = s - (a-a)
  f s =
   let method = select s :: a - f a
   in (\x -
 let res = method x
 in convert res)
 
 -chris
 
 On 16 mrt 2010, at 10:36, Giuseppe Maggiore wrote:
 
  The error message (obtained by loading the file with ghci) is:
  GHCi, version 6.10.4: http://www.haskell.org/ghc/  :? for help
  Loading package ghc-prim ... linking ... done.
  Loading package integer ... linking ... done.
  Loading package base ... linking ... done.
  [1 of 1] Compiling Main ( 
  C:\Users\pulcy\Desktop\Papers\Monads\Objec
  tiveMonad\HObject\Experiments\FunctorsProblems.hs, interpreted )
 
  C:\Users\pulcy\Desktop\Papers\Monads\ObjectiveMonad\HObject\Experiments\Functors
  Problems.hs:18:15:
  Could not deduce (Selector s (f a - a))
from the context (Selector s (a1 - f1 a1), Converter a1 f1)
arising from a use of `select'
 at 
  C:\Users\pulcy\Desktop\Papers\Monads\ObjectiveMonad\HObjec
  t\Experiments\FunctorsProblems.hs:18:15-22
  Possible fix:
add (Selector s (f a - a)) to the context of
  the type signature for `f'
or add an instance declaration for (Selector s (f a - a))
  In the expression: select s
  In the definition of `method': method = select s
  In the expression:
  let method = select s in (\ x - let res = ... in convert res)
 
  C:\Users\pulcy\Desktop\Papers\Monads\ObjectiveMonad\HObject\Experiments\Functors
  Problems.hs:21:11:
  Couldn't match expected type `a1' against inferred type `f a'
`a1' is a rigid type variable bound by
 the type signature for `f'
   at 
  C:\Users\pulcy\Desktop\Papers\Monads\ObjectiveMonad\HObject\Expe
  riments\FunctorsProblems.hs:16:18
  In the expression: convert res
  In the expression: let res = method x in convert res
  In the expression: (\ x - let res = method x in convert res)
  Failed, modules loaded: none.
  Prelude
 
 
  On Tue, Mar 16, 2010 at 2:31 AM, Ivan Lazar Miljenovic 
  ivan.miljeno...@gmail.com wrote:
  Giuseppe Maggiore giuseppe...@gmail.com writes:
 
   Hi! Can anyone tell me why this code does not work? I cannot seem to
   figure why it is broken...
 
  The error message (and how you got it) would help...
 
   {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, 
   FlexibleInstances,
 UndecidableInstances, FlexibleContexts, EmptyDataDecls, 
   ScopedTypeVariables,
 TypeOperators, TypeSynonymInstances #-}
 
  You sure you have enough language extensions there? ;-)
 
  Barely :)
 
 
  --
  Ivan Lazar Miljenovic
  ivan.miljeno...@gmail.com
  IvanMiljenovic.wordpress.com
 
 
 
  --
  Giuseppe Maggiore
  Ph.D. Student (Languages and Games)
  Microsoft Student Partner
  Mobile: +393319040031
  Office: +390412348444
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 
 -- 
 Giuseppe Maggiore
 Ph.D. Student (Languages and Games)
 Microsoft Student Partner
 Mobile: +393319040031
 Office: +390412348444
 
 

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


Re: [Haskell-cafe] references for compiler optimizations for functional languages

2010-03-03 Thread Chris Eidhof
I'd like to add Urban Boquist's thesis to that list:

http://www.cs.chalmers.se/~boquist/phd/index.html

(I've added it to the wiki page as well).

-chris

On 1 mrt 2010, at 22:26, Don Stewart wrote:

 mvanier42:
 Hi everyone,
 
 I'm interested in collecting good references for compiler optimizations  
 for functional languages (lazy, strict, statically-typed or not).  Any  
 suggestions?
 
 
 There's lots for what GHC implements on SimonPJ's site:
 
http://www.research.microsoft.com/~simonpj/Papers/inlining/index.htm
 
http://research.microsoft.com/en-us/um/people/simonpj/papers/cpr/index.htm
 

 http://research.microsoft.com/en-us/um/people/simonpj/papers/usage-types/usage.htm
 

 http://research.microsoft.com/en-us/um/people/simonpj/papers/comp-by-trans-scp.ps.gz
 

 http://research.microsoft.com/en-us/um/people/simonpj/papers/andy-thesis.ps.gz
 

 http://research.microsoft.com/en-us/um/people/simonpj/papers/deforestation-short-cut.ps.Z
 
http://www.cse.unsw.edu.au/~dons/papers/CLS07.html :)
 
 I've collected many of them here:
 

 http://haskell.org/haskellwiki/Research_papers/Compilation#Compiler_Analyses
 
 -- Don
 ___
 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] using haskell to serve with apache

2010-03-03 Thread Chris Eidhof
We run a couple of Happstack processes with FastCGI, and it works like a charm. 
We even wrote a module for it:

http://hackage.haskell.org/package/happstack-fastcgi

-chris

On 1 mrt 2010, at 20:19, Yitzchak Gale wrote:

 brad clawsie wrote:
 should i just try out something based on fastcgi?
 
 Obviously it depends on exactly what you want to do.
 
 For a simple very low volume page, even cgi should be
 just fine. I use it all the time.
 
 Regards,
 Yitz
 ___
 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] Two GET HTTP requests

2010-02-10 Thread Chris Eidhof
Hi nwn,

I had the following error:

Run: Network/Socket/Internal.hsc:(298,2)-(314,60): Non-exhaustive patterns in 
case. The code for those lines look like this:

 peekSockAddr p = do
   family - (#peek struct sockaddr, sa_family) p
   case family :: CSaFamily of
 #if defined(DOMAIN_SOCKET_SUPPORT)
 (#const AF_UNIX) - do
 str - peekCString ((#ptr struct sockaddr_un, sun_path) p)
 return (SockAddrUnix str)
 #endif
 (#const AF_INET) - do
 addr - (#peek struct sockaddr_in, sin_addr) p
 port - (#peek struct sockaddr_in, sin_port) p
 return (SockAddrInet (PortNum port) addr)
 #if defined(IPV6_SOCKET_SUPPORT)
 (#const AF_INET6) - do
 port - (#peek struct sockaddr_in6, sin6_port) p
 flow - (#peek struct sockaddr_in6, sin6_flowinfo) p
 addr - (#peek struct sockaddr_in6, sin6_addr) p
 scope - (#peek struct sockaddr_in6, sin6_scope_id) p
 return (SockAddrInet6 (PortNum port) flow addr scope)
 #endif


Thanks for all your help. I'll first upgrade to a new GHC and then try again.

-chris

On 9 feb 2010, at 06:41, Yusaku Hashimoto wrote:

 Try to reinstall HTTP package also. I think your HTTP package is still
 linked with old broken network package.
 
 HTTP depends on network. And network is a binding for network API of
 OS. These API is for C-language. When ghc builds such binding
 packages, It runs gcc for some purpose. gcc thinks you need 64bit
 binary (from SL, I believe.) and works for 64bit environment. But ghc
 on Mac can only build 32bit binaries. So it causes the problem.
 
 You can check if network package was correctly built by running this.
 This takes a host name, and gets the root document of the host via
 HTTP using a socket. Build and try `./this_program haskell.org`
 
 import Network.Socket
 import System.IO
 import System.Environment
 
 getAddr :: HostName - IO AddrInfo
 getAddr host = head `fmap`
   (getAddrInfo (Just defaultHints { addrSocketType = Stream })
(Just host)
(Just http))
 
 connected :: HostName - IO Socket
 connected host = do
addrinfo - getAddr host
sock - socket (addrFamily addrinfo)
   (addrSocketType addrinfo)
   (addrProtocol addrinfo)
connect sock (addrAddress addrinfo)
return sock
 
 httpGet :: HostName - IO String
 httpGet host = do
h - flip socketToHandle ReadWriteMode = connected host
hSetBuffering h NoBuffering
hPutStr h GET / HTTP/1.0\r\n\r\n
hGetContents h
 
 main = fmap head getArgs = httpGet = putStr
 
 I should have mentioned them in my last mail. Sorry.
 
 By the way, ghc-6.12 on Mac still can not build 64bit binaries. So
 upgrading ghc won't solve it.
 
 --nwn
 
 On Mon, Feb 8, 2010 at 12:50 AM, Chris Eidhof ch...@eidhof.nl wrote:
 Thanks. Unfortunately, it didn't help. The thing that frustrates me is that 
 it's quite hard to debug. I guess I'll upgrade my GHC to 6.12, hopefully 
 that'll solve it.
 
 -chris
 
 On 7 feb 2010, at 16:07, Yusaku Hashimoto wrote:
 
 Hello,
 
 On Sat, Feb 6, 2010 at 2:51 AM, Chris Eidhof ch...@eidhof.nl wrote:
 Approach 3: I used the simpleHTTP function from the HTTP package. This 
 crashed, after I dug a little deeper into the code, it threw an error on 
 calling the parseURI function (openFile: no such file exists). I installed 
 the latest network package and upgraded my HTTP package, and the parseURI 
 error went away. I felt like I was almost there, and tried the following:
 
 simpleHTTP (getRequest http://haskell.org;)
 
 This failed with just the text Bus error. I searched the HTTPBis git 
 repository, but couldn't find the text Bus error. I don't have a clue of 
 how to fix this.
 
 Try reinstall network package with `cabal install --reinstall
 --hsc2hs-options=--cflag=-m32 --lflag=-m32`.
 
 See also: http://hackage.haskell.org/trac/ghc/ticket/3681
 
 Hope this helps.
 --nwn
 
 

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


Re: [Haskell-cafe] Lazy language on JVM/CLR

2010-02-09 Thread Chris Eidhof
I don't think it's pure. I would definitely use a pure language on the JVM, but 
IIRC Open Quark / Cal is an impure language. For example, from the library 
documentation: printLine :: String - ().

-chris

On 9 feb 2010, at 15:31, Tim Wawrzynczak wrote:

 Perhaps this is similar to what you're looking for.
 
 http://openquark.org/Open_Quark/Welcome.html
 
 It's a pure, lazy language for the JVM.  I haven't used it myself, but I 
 would imagine that 
 it would have a Java FFI.
 
 Cheers,
  - Tim
 
 On Mon, Feb 8, 2010 at 6:42 PM, Tony Morris tonymor...@gmail.com wrote:
 I have hypothesised a pure, lazy language on the JVM and perhaps the
 .NET CLR with FFI to .NET/Java libraries. I foresee various problems but
 none that are catastrophic; just often requiring a compromises,
 sometimes very unattractive compromises. I have authored several
 libraries in the same vain as pure, lazy programming to run on the JVM
 in Java and Scala programming languages.
 
 I expect others have forethought and perhaps even experimented with such
 a language. Are there any dangers to be wary of that undo the entire
 endeavour?
 
 Thanks for any insights.
 
 --
 Tony Morris
 http://tmorris.net/
 
 ___
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Two GET HTTP requests

2010-02-08 Thread Chris Eidhof
On 7 feb 2010, at 19:52, Lars Viklund wrote:

 On Sun, Feb 07, 2010 at 05:12:23PM +, Ben Millwood wrote:
 This failed with just the text Bus error. I searched the HTTPBis git 
 repository, but couldn't find the text Bus error. I don't have a clue of 
 how to fix this.
 Bus error is a message generated by the operating system. On OS X,
 it can mean a null dereference, which is very unusual.
 
 You did not mention whether the machine running your OS X was a PowerPC
 or an Intel machine.
 
 On non-x86 platforms, a bus error is usually caused by misaligned memory
 accesses. Unlike the x86 which silently and expensively fixes any
 misaligned accesses, sane processors kick and scream, resulting in a bus
 error.
 
 Such things tend to happen quite often when development of a software
 mainly takes place on x86 family chips, and are revealed when some poor
 soul on an UltraSparcIII tries to run them.

I'm on X86, Snow Leopard. I'm running GHC 6.10.2.

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


Re: [Haskell-cafe] Two GET HTTP requests

2010-02-08 Thread Chris Eidhof
I should add that I was able to work around the issue by using Michael 
Snoyman's http-wget [1] package. It uses the command-line version of wget, 
which does work on my machine.

-chris

[1]: http://hackage.haskell.org/package/http-wget

On 7 feb 2010, at 16:50, Chris Eidhof wrote:

 Thanks. Unfortunately, it didn't help. The thing that frustrates me is that 
 it's quite hard to debug. I guess I'll upgrade my GHC to 6.12, hopefully 
 that'll solve it.
 
 -chris
 
 On 7 feb 2010, at 16:07, Yusaku Hashimoto wrote:
 
 Hello,
 
 On Sat, Feb 6, 2010 at 2:51 AM, Chris Eidhof ch...@eidhof.nl wrote:
 Approach 3: I used the simpleHTTP function from the HTTP package. This 
 crashed, after I dug a little deeper into the code, it threw an error on 
 calling the parseURI function (openFile: no such file exists). I installed 
 the latest network package and upgraded my HTTP package, and the parseURI 
 error went away. I felt like I was almost there, and tried the following:
 
 simpleHTTP (getRequest http://haskell.org;)
 
 This failed with just the text Bus error. I searched the HTTPBis git 
 repository, but couldn't find the text Bus error. I don't have a clue of 
 how to fix this.
 
 Try reinstall network package with `cabal install --reinstall
 --hsc2hs-options=--cflag=-m32 --lflag=-m32`.
 
 See also: http://hackage.haskell.org/trac/ghc/ticket/3681
 
 Hope this helps.
 --nwn
 
 ___
 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] Two GET HTTP requests

2010-02-07 Thread Chris Eidhof
Thanks. Unfortunately, it didn't help. The thing that frustrates me is that 
it's quite hard to debug. I guess I'll upgrade my GHC to 6.12, hopefully 
that'll solve it.

-chris

On 7 feb 2010, at 16:07, Yusaku Hashimoto wrote:

 Hello,
 
 On Sat, Feb 6, 2010 at 2:51 AM, Chris Eidhof ch...@eidhof.nl wrote:
 Approach 3: I used the simpleHTTP function from the HTTP package. This 
 crashed, after I dug a little deeper into the code, it threw an error on 
 calling the parseURI function (openFile: no such file exists). I installed 
 the latest network package and upgraded my HTTP package, and the parseURI 
 error went away. I felt like I was almost there, and tried the following:
 
 simpleHTTP (getRequest http://haskell.org;)
 
 This failed with just the text Bus error. I searched the HTTPBis git 
 repository, but couldn't find the text Bus error. I don't have a clue of 
 how to fix this.
 
 Try reinstall network package with `cabal install --reinstall
 --hsc2hs-options=--cflag=-m32 --lflag=-m32`.
 
 See also: http://hackage.haskell.org/trac/ghc/ticket/3681
 
 Hope this helps.
 --nwn

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


[Haskell-cafe] Two GET HTTP requests

2010-02-05 Thread Chris Eidhof
Hi everyone,

I'm trying to do a number of successive HTTP requests in one program. Here's 
what I tried:

Approach 1: I used the 'download' package, which failed to install on OS X. It 
fails with error: libio.h: No such file or directory.

Approach 2: I installed the 'download-curl' package, and tried again. This 
seems to fail on the following example:

 import Network.Curl.Download
 
 main = do x - openURI http://haskell.org;
   y - openURI http://haskell.org/hoogle;
   return ()

If I put a print statement around the second line of the do-statement it looks 
like openURI never returns.

Approach 3: I used the simpleHTTP function from the HTTP package. This crashed, 
after I dug a little deeper into the code, it threw an error on calling the 
parseURI function (openFile: no such file exists). I installed the latest 
network package and upgraded my HTTP package, and the parseURI error went away. 
I felt like I was almost there, and tried the following:

 simpleHTTP (getRequest http://haskell.org;)

This failed with just the text Bus error. I searched the HTTPBis git 
repository, but couldn't find the text Bus error. I don't have a clue of how 
to fix this.

I'm a bit stuck here, I would love to help fix the errors, but don't know what 
would be the best place to begin. If anyone can point me in the right 
direction, I will try to patch at least one of these packages.

Thanks,

-chris

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


Re: [Haskell-cafe] Determining application directory

2010-01-27 Thread Chris Eidhof
Hi Matveev,

You might be interested in the System.Directory module:

http://hackage.haskell.org/packages/archive/directory/1.0.0.3/doc/html/System-Directory.html

HTH,

-chris

On 27 jan 2010, at 18:06, Matveev Vladimir wrote:

 Hi,
 I'm writing cross-platform application in Haskell which should be
 running under Windows and Linux. Under Linux configuration is stored
 in the /etc directory, and under Windows configuration is meant to be in
 the application directory. So, is there a way to get an application
 directory path under Windows? I remember that there is a way to do this
 using WinAPI, but how to do this Haskell?
 ___
 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] HTML - based GUIs - follow up

2010-01-21 Thread Chris Eidhof
Formlets themselves don't require a server. You can use them from the 
commandline. However, formlets do have a limitation: they are not interactive. 
I would really like a library that does something like formlets (compositional 
web forms) but with a FRP-style of writing. A contrived example:

Suppose I have a page with a label that displays a number, and a slider. When I 
change the slider, the number in the label has to change accordingly.

The example above is currently not possible with formlets.

-chris

On 20 jan 2010, at 18:30, Colin Paul Adams wrote:

 Günther == Günther Schmidt gue.schm...@web.de writes:
 
Günther My question is: do formlets only work server based or is it
Günther also possible to use formlet sans happs?
 
 Yes (I think) and yes.
 -- 
 Colin Adams
 Preston Lancashire
 ___
 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] Compiling a shared library on MacOS X

2010-01-04 Thread Chris Eidhof
I'm not sure if it is of any help, but at the haskell-wiki there's an article 
about how to communicate between Haskell and Objective-C using XCode: 
http://haskell.org/haskellwiki/Using_Haskell_in_an_Xcode_Cocoa_project

-chris

On 4 jan 2010, at 00:36, Ivan Miljenovic wrote:

 If I recall correctly, dynamic linking/shared library support is not
 yet available for OSX, as the Industrial Haskell Group does not have
 any knowledge of OSX (but is willing to pay someone who does to do the
 work).
 
 2010/1/4 Jean-Denis Koeck jdko...@gmail.com:
 Hello,
 I'm using the following cabal file to build a shared library with ghc:
 
 Build-Type:Simple
 Executable libmylibrary.dll
   If os(windows)
 CPP-Options:-DWIN32
   Extensions:   ForeignFunctionInterface
   Build-Depends:...
   Main-Is:  libmylibrary.hs
   Ghc-Options:  -W --make -no-hs-main -optl-shared -optl-s -O2
 
 The resulting library is called from a C++ graphical user interface (using
 Qt),
 which worked great so far on Windows and Linux.
 
 However, the compilation fails on MacOS X:
 
 Undefined symbols:
   _ZCMain_main_closure, referenced from:
   _ZCMain_main_closure$non_lazy_ptr in libHSrts.a(Main.o)
   ___stginit_ZCMain, referenced from:
   ___stginit_ZCMain$non_lazy_ptr in libHSrts.a(Main.o)
 ld: symbol(s) not found
 collect2: ld returned 1 exit status
 
 I don't know much about shared libraries, even less about them on MacOS X :(
 Any idea ?
 
 Jean-Denis Koeck
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 
 
 
 -- 
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 IvanMiljenovic.wordpress.com
 Joan Crawford  - I, Joan Crawford, I believe in the dollar.
 Everything I earn, I spend. -
 http://www.brainyquote.com/quotes/authors/j/joan_crawford.html
 ___
 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] diff implementation in haskell

2009-12-09 Thread Chris Eidhof

Also, there is a paper about doing a type-safe diff in Agda, 
http://portal.acm.org/citation.cfm?id=1596614.1596624

I heard rumors that the library will be ported to Haskell.

-chris

On 8 dec 2009, at 15:20, Bayley, Alistair wrote:


From: haskell-cafe-boun...@haskell.org
[mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Ketil Malde

Don Stewart d...@galois.com writes:



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


Wherein we can read:

| This is an implementation of the O(ND) diff algorithm
[...]. It is O(mn)
| in space.

At first I thought 'N' and 'M' would be the lengths of the lists, and
'D' is the number of differences, but then the space bound
doesn't make
sense.  I tried to find the reference, but Citeseer is down
(again. sigh).

Anybody know what the bounds really are?



I think the space bounds are O(M+N). Section 4b. A Linear Space
Refinement concludes with Unfortunately, the input sequences A and B
must be kept in memory, implying that a total of O(M+N) space is
needed.

BTW, there is a minor improvement to this algorithm (claims to be
faster, same space usage):
 http://research.janelia.org/myers/Papers/np_diff.pdf

found via:

http://scholar.google.com/scholar?q=%22An+O(NP)+Sequence+Comparison+Algo
rithm.%22

I thought this paper was easier to understand.

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*

___
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] Bulding a library for C users on OS X

2009-11-02 Thread Chris Eidhof

On 2 nov 2009, at 03:30, Manuel M T Chakravarty wrote:


Chris Eidhof:
I'm trying to call a Haskell function from C, on OS X. There's an  
excellent post [1] by Tomáš Janoušek that explains how to do this  
on Linux. However, on OS X, it's different. First of all, it looks  
like the -no-hs-main flag is ignored, because I get the following  
error:


 ghc -O2 --make   -no-hs-main -optl '-shared' -optc '- 
DMODULE=Test'   -o Test.so Test.hs module_init.c

 [1 of 1] Compiling Main ( Test.hs, Test.o )

 Test.hs:1:0: The function `main' is not defined in module `Main'''


The flag -no-hs-main is a link-time flag that allows you to link  
without a main function, but you are getting a compile time error.   
It's as if you try to export main, but don't define it.


Have you had a look at http://www.haskell.org/ghc/docs/latest/html/users_guide/ffi-ghc.html#foreign-export-ghc 
 ?



Interesting! I didn't see that section before, thanks a lot.

-chris

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


Re: [solved] Re: [Haskell-cafe] Calling Haskell from C, Linking with gcc?

2009-11-01 Thread Chris Eidhof
I can confirm that, if you follow the steps on the wiki, you'll end up  
with a working Mac application. Excellent work John, thanks very much!


-chris

On 30 okt 2009, at 00:53, John Velman wrote:

It's taken 21 days with interruptions, but I finally posted a  
tutorial with

details of what I did on the Haskel Wiki.  Category:Tutorials,
title: Using Haskell in an Xcode Cocoa project

Hope it's clear.  Please send comments and suggestions.

John V.


On Thu, Oct 08, 2009 at 10:34:07AM +0200, Wouter Swierstra wrote:


On 7 Oct 2009, at 23:39, John Velman wrote:

For anyone following this:  The XCode ld script is complex, and  
has mac
specific defaults early in the search path specification, and I  
probably
don't want to change these.  A library in a default path is the  
wrong

libgmp.[dylib | a].


Is there any chance you'll write up exactly what you needed to do  
on a
blog/TMR article/Haskell wiki page? I've tried doing something  
similar, ran
into linking problems, and gave up my fight with XCode. I think  
this would
be a really useful resource for both Obj-C programmers looking into  
Haskell

and Haskell programmers who want to have a fancy Cocoa GUI. Thanks!

 Wouter

___
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] Bulding a library for C users on OS X

2009-10-31 Thread Chris Eidhof

Hey all,

I'm trying to call a Haskell function from C, on OS X. There's an  
excellent post [1] by Tomáš Janoušek that explains how to do this on  
Linux. However, on OS X, it's different. First of all, it looks like  
the -no-hs-main flag is ignored, because I get the following error:


 ghc -O2 --make   -no-hs-main -optl '-shared' -optc '- 
DMODULE=Test'   -o Test.so Test.hs module_init.c

 [1 of 1] Compiling Main ( Test.hs, Test.o )

 Test.hs:1:0: The function `main' is not defined in module `Main'

Second, I learned [2] that I have to pass in different flags on OS X,  
but unfortunately, GHC still wants me to have main. I'm probably doing  
something wrong here, is there anyone who can give me some pointers?  
(no pun intended).


I'm running GHC 6.10.2 on Leopard.

Thanks,
-chris

[1]: http://blog.haskell.cz/pivnik/building-a-shared-library-in-haskell/
[2]: 
http://www.mail-archive.com/haskell-cafe@haskell.org/msg51303.html___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] dsl and gui toolkit

2009-10-05 Thread Chris Eidhof
That sounds really interesting, it would be great if you could share  
some of your work by putting it on hackage or posting a link to the  
repository!


-chris

On 5 okt 2009, at 12:42, Andrew U. Frank wrote:

writing a gui is a mess (independent of wx or gtk) - too much detail  
is shown

and not enough abstraction is done. haskell can help.

i have written an experimental way of producing the GUI   
automatically with a
description of the semantics of the types and operations involved (a  
la

ontology, evnetually comparable what protege produces).
the input is a descriptionof the entity ypes, the fields used, the  
functional

dependencies between the fiels, plus the operations used.
the division in screens and their layout.

the rest ist automatic.
the result is a GUI (with preferably gtk but i had also a wx version  
running).


the ideas were inspired by eliot conal's work and wxgeneric, which  
seemed for

administrative applications either too restricted or to specific.

if somebody wants to try it out for his application, please write
fr...@geoinfo.tuwien.ac.at

(there is not much documentation and the code is not yet completely  
clean -

testing by somebody else would be very valuable!)

andrew

___
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: Multiple-selection formlet?

2009-09-23 Thread Chris Eidhof

Hey Colin,

Currently, I don't think this is supported. It would help a lot if you  
could send me a dumbed-down version of your code, I'll file an issue  
for it on github.


Thanks,
-chris

On 23 sep 2009, at 14:35, Colin Adams wrote:


Just in case you missed it on the cafe.

-- Forwarded message --
From: Colin Adams colinpaulad...@googlemail.com
Date: 2009/9/21
Subject: Multiple-selection formlet?
To: Haskell Cafe haskell-cafe@haskell.org


I can't work out how to get multiple selections delivered from a
formlet. I can add the multiple attribute to get the formlet to allow
the user to make multiple selections, but I only get a single answer
back. This seems inevitable from the type of rawSelect (or select) -
since the list of values to select from is of type [(a, h)] and the
result type is a.

Am I missing something?

--
Colin Adams
Preston,
Lancashire,
ENGLAND



--
Colin Adams
Preston,
Lancashire,
ENGLAND


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


Re: [Haskell-cafe] Problem with Text.XHtml.Strict.Formlets.file on Mac OSX

2009-09-23 Thread Chris Eidhof

Hey Colin,

The code looks OK to me. Are you sure you are setting the right method  
for your form? It's the third component of the tuple returned by the  
runFormState.


Thanks,

-chris

On 22 sep 2009, at 08:56, Colin Adams wrote:


I'm writing a form that involves picking a file to upload, and so uses
Text.XHtml.Strict.Formlets.file. The form displays OK, but when I
click the Browse button, and select a file from the dialog (no matter
what the file type), and then click on the Submit button, I get an
error:

fval[2] is not a file

I haven't added any validation yet.

The generated html looks ok to me:

input type=file name=fval[2] id=fval[2]

This is on my laptop running Mac OSX. I can't test it on Linux until I
get home at the weekend, so I don't know if I've made a silly error in
my coding, but it is very simple:

imageInputForm = F.plug (\xhtml - X.p  (X.label  Image file:)
+++ xhtml) F.file

Are there any known problems with the file formlet? Might it be OSX  
specific?

--
Colin Adams
Preston,
Lancashire,
ENGLAND
___
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] Problem with Text.XHtml.Strict.Formlets.file on Mac OSX

2009-09-23 Thread Chris Eidhof
OK, the trick is to set the attribute enctype=multipart/form-data on  
the form whenever your form contains a file upload item. Using the  
third parameter you can detect if this is the case. This is typical of  
using file-upload fields in web programming and independent of the  
formlets. It's also covered in the Happstack tutorial [1] and in the  
HTML form spec [2].


Good luck,

-chris

[1] http://tutorial.happstack.com/tutorial/file-uploads
[2] http://www.w3.org/TR/html401/interact/forms.html#h-17.13.4

On 23 sep 2009, at 15:35, Colin Adams wrote:


I'm not sure, but the other components of the form work (before I
added the file bit, that is), so they will all be using the same
method.

I'm using a generic form-handling function named withForm that I got
from one of the examples - this code appears to ignore the third
component of the tuple.

Note that I don't really understand all of this yet.

2009/9/23 Chris Eidhof ch...@eidhof.nl:

Hey Colin,

The code looks OK to me. Are you sure you are setting the right  
method for

your form? It's the third component of the tuple returned by the
runFormState.

Thanks,

-chris

On 22 sep 2009, at 08:56, Colin Adams wrote:

I'm writing a form that involves picking a file to upload, and so  
uses

Text.XHtml.Strict.Formlets.file. The form displays OK, but when I
click the Browse button, and select a file from the dialog (no  
matter

what the file type), and then click on the Submit button, I get an
error:

fval[2] is not a file

I haven't added any validation yet.

The generated html looks ok to me:

input type=file name=fval[2] id=fval[2]

This is on my laptop running Mac OSX. I can't test it on Linux  
until I
get home at the weekend, so I don't know if I've made a silly  
error in

my coding, but it is very simple:

imageInputForm = F.plug (\xhtml - X.p  (X.label  Image file:)
+++ xhtml) F.file

Are there any known problems with the file formlet? Might it be OSX
specific?
--
Colin Adams
Preston,
Lancashire,
ENGLAND
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe







--
Colin Adams
Preston,
Lancashire,
ENGLAND


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


Re: [Haskell-cafe] Problem with monadic formlets

2009-08-30 Thread Chris Eidhof

Hey everybody,

I've just uploaded formlets 0.6.1 to Hackage, which should fix this  
bug. Thanks for letting me know!


-chris

On 29 aug 2009, at 13:22, Jeremy Shaw wrote:


Hello,

Yeah, it seems that checkM in formlets 0.6 broken. I reported the  
bug to MightByte as well.


- jeremy

At Fri, 28 Aug 2009 12:49:08 +0100,
Colin Paul Adams wrote:



Colin == Colin Paul Adams co...@colina.demon.co.uk writes:



Jeremy == Jeremy Shaw jer...@n-heptane.com writes:


   Colin apparent data corruprion is occurring. I am suspecting a
   Colin bug in the formlets library (I have version 0.6).

   Colin So I have created a slightly cut-down (no database
   Colin involved) complete working program. Can you see if this
   Colin works ok with your version of formlets:

I managed to uninstall formlets-0.6 myself, and then installed 0.5
instead. After adding the necessary extra argument to runFormletState
(an empty string), the test program works fine. So this seems to be a
bug in formlets-0.6.
--
Colin Adams
Preston Lancashire

___
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] [ann] formlets 0.6

2009-08-24 Thread Chris Eidhof

Hey everyone,

I wanted to let you know that the formlets team has released a new  
version of the formlets [1] on hackage, a library to build type-safe,  
composable web forms. Most notably, Mightybyte and I worked on the  
massInput functionality, which is now ready for use! Mightybyte has an  
excellent article [2] on how to use the massInput to build dynamic  
forms on the client side. If you're building web apps with Haskell,  
make sure you check it out.


-chris

[1]: http://hackage.haskell.org/package/formlets
[2]: 
http://softwaresimply.blogspot.com/2009/08/dynamic-list-formlets-in-haskell.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Are GADTs what I need?

2009-07-13 Thread Chris Eidhof

Hey Kev,

The types are thrown away during compile time. Therefore, if you  
have a constructor VWrapper :: a - Value nothing is known about  
that a when you scrutinize it.


What you could do, however, is something like this:


data Value a where
  VInt :: Integer - Value Integer
  ...
  VWrapper :: a - Value a


And then you can write a function doSomething:


doSomething :: Value String - String
doSomething (VWrapper s) = s


HTH,

-chris

On 13 jul 2009, at 12:41, Kev Mahoney wrote:


Hi there,

I'm currently writing an interpreter that I would like to be able to
use with other haskell programs. I would like to be able to pass along
arbitrary types though the interpreter. I've seen hints that GADTs can
do this, but I am having trouble understanding them.

So far, I've learnt you can do this:

data Value where
VInt :: Integer - Value
...
VWrapper :: a - Value

which can let you encode arbitrary 'dynamic' types into Value. I was
hoping to be able to pattern match to get the value out again e.g.

doSomething :: Value - 
doSomething (VWrapper String s) = .

Also, anything that can help me out with GADTs in general will be much
appreciated.

Thanks,
Kevin.
___
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] Are GADTs what I need?

2009-07-13 Thread Chris Eidhof
Then you could add a specific constructor for String. The main point  
is: the case construct only works for values, not for types. There is  
no typecase construct. If you want to have certain restrictions on the  
'a', such as the Show class, you could also do something like this:


 data Value where
   VWrapper :: (Show a) = a - Value

If you could elaborate a bit on what you're trying to accomplish (from  
a higher viewpoint) then maybe we can help you   some more.


-chris

On 13 jul 2009, at 17:42, Kev Mahoney wrote:


Thanks, that helps.

I was hoping to not have to parametrize Value as there is a fair bit
of code to change, and it cascades down through the data structures
(maybe a forall a . Value a will help here?)

I will have a go at this approach. In case anyone is interested the
code is at http://github.com/KMahoney


2009/7/13 Chris Eidhof ch...@eidhof.nl:

Hey Kev,

The types are thrown away during compile time. Therefore, if you  
have a
constructor VWrapper :: a - Value nothing is known about that  
a when

you scrutinize it.

What you could do, however, is something like this:


data Value a where
 VInt :: Integer - Value Integer
 ...
 VWrapper :: a - Value a


And then you can write a function doSomething:


doSomething :: Value String - String
doSomething (VWrapper s) = s


HTH,

-chris

On 13 jul 2009, at 12:41, Kev Mahoney wrote:


Hi there,

I'm currently writing an interpreter that I would like to be able to
use with other haskell programs. I would like to be able to pass  
along
arbitrary types though the interpreter. I've seen hints that GADTs  
can

do this, but I am having trouble understanding them.

So far, I've learnt you can do this:

data Value where
VInt :: Integer - Value
...
VWrapper :: a - Value

which can let you encode arbitrary 'dynamic' types into Value. I was
hoping to be able to pattern match to get the value out again e.g.

doSomething :: Value - 
doSomething (VWrapper String s) = .

Also, anything that can help me out with GADTs in general will be  
much

appreciated.

Thanks,
Kevin.
___
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] DHUG: meeting tomorrow (July 7th) in Utrecht

2009-07-07 Thread Chris Eidhof

Hi everyone,

The Dutch HUG [1] will meet again tomorrow. This time we'll meet in  
Utrecht again, at the Stairway To Heaven. The meeting will start at  
19h. The venue is a sometimes a bit noisy, but there's beer and nice  
big tables. If you want to hear everything about the Dutch HUG  
straight from the horse's mouth: make sure you're at the meetings and  
subscribed to the mailing list [2]. We already have more than 40  
members after two meetings!


See you tomorrow!

-chris

[1]: http://www.haskell.org/haskellwiki/Dutch_HUG
[2]: http://groups.google.com/group/dutch-hug
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to pretty print code efficiently

2009-07-05 Thread Chris Eidhof

On 4 jul 2009, at 05:13, Alexander Dunlap wrote:


On Fri, Jul 3, 2009 at 6:45 PM, John Kynewho...@gmail.com wrote:

Hi,

Currently I'm pretty printing code by building arrays of strings  
and calling

indent.  For example:

instance JavaPrintableNamed AST.EnumeratedType where
   javaLinesNamed parentName (AST.EnumeratedType memberDefinitions) =
  [ public enum  ++ asJavaId(parentName)
  , {
  ] ++ memberCodeLines ++
  [ }
  , 
  ]
  where
 memberCodeLines = indent $ javaLines memberDefinitions

The indent function takes a list of strings and adds an indent to the
beginning of every line.

I can imagine this to be very inefficient as it builds many strings  
and

concatenates them.

In Ruby, I might do the same thing like this:

class EnumeratedType  JavaPrintableNamed
   def writeTo(writer)
  writer.print public enum 
  writer.puts self.asJavaId
  writer.puts {
  writer.indent do
 self.memberDefinitions.writeTo(writer)
 writer.puts
  end

where above, the writer.indent takes care of the indent, and  
everything is
appended to a stream, which doesn't seem so bad in terms of  
efficiency.


I'm looking for a way to do something similar in Haskell.

Anyone can give me a hand?

Thanks

-John


___


You may want to investigate the standard module
Text.PrettyPrint.HughesPJ, which contains a number of (I assume fairly
efficient) combinators for pretty printing.


I second that. Also, there is uulib which has a pretty printing module  
that's quite similar:


http://hackage.haskell.org/packages/archive/uulib/0.9.10/doc/html/UU-PPrint.html

I think both packages are based on the paper The Design of a Pretty- 
printing Library which can be found at http://www.cs.chalmers.se/~rjmh/Papers/pretty.ps


Not only do they provide abstractions for things like indentation,  
concatenation in different forms, etc., but they also are  more  
efficient than a naive implementation using lists.


-chris

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


Re: [Haskell-cafe] ORM for haskell?

2009-07-03 Thread Chris Eidhof

On 3 jul 2009, at 11:28, Jochem Berndsen wrote:


Chris Eidhof wrote:
I've something working that sort of does this. You define your  
model in

the following way:

data User = User {name :: String, password :: String, age :: Int,  
post

:: BelongsTo Post}
data Post = Post {title :: String, body :: String}

Then there's some boilerplate code (that ultimately will be  
generated by

TH), and from that moment on you can do things like this:

test = do
 conn - connectSqlite3 example.sqlite3
 runDB conn $ do
   user - fromJust $ find typeUser 1
   user' - fillBelongsTo user relPost
   return (post user')



By default, no relations will be fetched, but by doing the  
fillBelongsTo
the user will be updated. I currently have support for new, update  
and

find. All of this code is very alpha, and only works using HDBC and
Sqlite3, but still.


So in this example, both user and user' are of type User, but if I ask
for post user, this is undefined?
I have done something similar as you, except that I filled the related
field with an unsafePerformIO fetching the related data from the  
database.


No, it will never be undefined. The BelongsTo datatype is defined as  
following:


data BelongsTo a = BTNotFetched | BTId Int | BTFetched (Int, a)
So either there is no information available (BTNotFetched), we know  
the id (the foreign key, BTId) or we know the id and the value  
(BTFetched). It is currently just a proof of concept, but for me, an  
extend version of this will do. I think that almost every mapping from  
Haskell datatypes to a RDBMS will be slightly awkward, this is my way  
to find a balance ;)


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


Re: [Haskell-cafe] ORM for haskell?

2009-07-01 Thread Chris Eidhof

Hey Marc,

On 30 jun 2009, at 19:52, Marc Weber wrote:


Is there anyone interested in helping building a library which
a) let's you define kind of model of you data
b) let's you store you model in any backend (maybe a relational
   database)
c) does static checking of your queries at compilation time?

[...]



Maybe this does already exist and I've missed it?


I've something working that sort of does this. You define your model  
in the following way:


data User = User {name :: String, password :: String, age :: Int,  
post :: BelongsTo Post}

data Post = Post {title :: String, body :: String}

Then there's some boilerplate code (that ultimately will be generated  
by TH), and from that moment on you can do things like this:


test = do
  conn - connectSqlite3 example.sqlite3
  runDB conn $ do
user - fromJust $ find typeUser 1
user' - fillBelongsTo user relPost
return (post user')

By default, no relations will be fetched, but by doing the  
fillBelongsTo the user will be updated. I currently have support for  
new, update and find. All of this code is very alpha, and only works  
using HDBC and Sqlite3, but still.


You can find and fork my code on http://github.com/chriseidhof/ 
generics. I'll be happy to answer any questions about the code or the  
ideas behind it.


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


Re: [Haskell-cafe] Logo

2009-06-16 Thread Chris Eidhof

Hey all,

On 15 jun 2009, at 08:39, Ashley Yakeley wrote:


Thomas Davie wrote:
We had a lot of fun deciding Haskell's new logo, and while I  
don't agree with the final result, it would be nice if we could now  
start consistently using it.  With that in mind, I realised that  
the Haskell Platform's logo is totally different, and did a quick  
mock up of a version reflecting the current Haskell logo.  It needs  
someone with the original vector graphics to have a play and  
improve it a little bit, but hopefully you'll se a concept you like.


I rather like the fact that the Haskell Platform logo is distinct  
from the Haskell logo. I think it helps prevent confusion (even  
though the Platform logo is based on one of the Haskell logo  
competition entrants).


For new users, when they install Haskell they will install the  
Haskell Platform. I don't think we need to have a big distinction  
between that. Therefore, I think that the Haskell Platform should  
share the Haskell logo. I think the Haskell platform is an excellent  
name for internal communication, but to the outside world, it *is*  
Haskell. This is what you get when you install Haskell. Otherwise it  
will probably only confuse users.


I think a typical new user would do something along the following  
lines: I want to play around with Haskell. I'll google for install  
Haskell or download Haskell (here, the Haskell Platform download  
page should be the #1 hit). There, the user sees the Haskell logo and  
doesn't have to know *anything* about the platform effort, cabal, ghc  
or whatever. Therefore, I think it should have the Haskell logo, not  
the platform logo.


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


[Haskell-cafe] Dutch HUG meeting tonight in Amsterdam

2009-06-09 Thread Chris Eidhof

Hi everyone,

Tonight there will be another meeting of the Dutch Haskell Users'  
Group! This time we'll meet in Amsterdam, in the library. On the wiki  
[1] you can find the details of how to reach it. We'll be at the top  
floor and shouldn't be hard to recognize. The meeting is set to begin  
at 19:30.


Everybody's welcome, from beginners to advanced haskellers. Even if  
you never programmed in Haskell before it'll probably be a lot of fun.  
See you tonight! There are a lot of international people joining, so  
no knowledge of Dutch is necessary.


If you're joining, also be sure to subscribe to our mailinglist [2].

See you tonight!

-chris

[1]: http://www.haskell.org/haskellwiki/Dutch_HUG
[2]: http://groups.google.com/group/dutch-hug
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANNOUNCE: gitit 0.2 release - wiki using HAppS, git, pandoc

2008-11-09 Thread Chris Eidhof
If anyone else has problems installing gitit, try updating your cabal- 
install (and cabal). I had old versions on my computer, and updating  
them solved my gitit build-problems.


-chris

On 9 nov 2008, at 22:41, John MacFarlane wrote:

I've just uploaded a new version (0.2.1) that requires HAppS =  
0.9.3 
 0.9.4. (There are small API changes from 0.9.2 to 0.9.3, so I  
thought

it best not to allow 0.9.2.x, even though it still compiles with a
warning.)

+++ Hugo Pacheco [Nov 09 08 20:41 ]:
  a new HAppS version [1]0.9.3.1 has been released, and gitit  
requires

  HApps==[2]0.9.2.1. should ti be ok just to relax the dependency?

  On Sat, Nov 8, 2008 at 8:32 PM, John MacFarlane [EMAIL PROTECTED] 


  wrote:

I've uploaded an early version of gitit, a Haskell wiki  
program, to

HackageDB. Gitit uses HAppS as a webserver, git for file storage,
pandoc for rendering the (markdown) pages, and highlighting- 
kate for

highlighted source code.

Some nice features of gitit:

 - Pages and uploaded files are stored in a git repository and  
may

   be added, deleted, and modified directly using git.
 - Pages may be organized into subdirectories.
 - Pandoc's extended version of markdown is used, so you can do  
tables,
   footnotes, syntax-highlighted code blocks, and LaTeX math.  
(And

   you can you pandoc to convert pages into many other formats.)
 - Math is rendered using jsMath (which must be installed
   separately).
 - Source code files in the repository are automatically  
rendered with

   syntax highlighting (plain/text version is also available).

You can check it out on my webserver: [4]http://johnmacfarlane.net:5001/
Or try it locally:

   cabal update
   cabal install pandoc -fhighlighting
   cabal install gitit
   gitit  # note: this will create two subdirectories in the  
working

directory
   # then browse to [5]http://localhost:5001.

There's a git repository at [6]http://github.com/jgm/gitit/tree/master 
.

Comments and patches are welcome.

John
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
[8]http://www.haskell.org/mailman/listinfo/haskell-cafe

  --
  [9]www.di.uminho.pt/~hpacheco

References

  Visible links
  1. http://0.9.3.1/
  2. http://0.9.2.1/
  3. mailto:[EMAIL PROTECTED]
  4. http://johnmacfarlane.net:5001/
  5. http://localhost:5001/
  6. http://github.com/jgm/gitit/tree/master
  7. mailto:Haskell-Cafe@haskell.org
  8. http://www.haskell.org/mailman/listinfo/haskell-cafe
  9. http://www.di.uminho.pt/~hpacheco



___
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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Probably a trivial thing for people knowing Haskell

2008-10-20 Thread Chris Eidhof
I think it might be more appropriate to move this discussion to  
haskell-cafe.


On 19 okt 2008, at 17:24, Friedrich wrote:

Learn to love types:  one of the neat things about Haskell is that if
you can write down the type of a function then you have usually done
90% of the work of writing the code for it.

Well I disagree. But that's another story.


Well, it's definitely not true when you're starting out with Haskell.  
The thing is: once you start to think in types it does work like this.  
You just think: what do I need as my input and what's my output.  
That's what you write down as your type and you're almost done! It's  
very similar to test-driven development; the point with TDD is not so  
much about making sure your program is correct: the big win (for me)  
is that it helps you think about the design of your program. The same  
holds for types.






Another is that in
general, if you can't express the type of a function, it means you
haven't thought through what you're trying to do.


No  that's not true. The use implies that. However I'm not advice
resistant and will see if I use types. But IMHO that's should be job
of the environment  to figure out  correctly and most of the time
Haskell does guess right. And I surely can ask for the types.


I agree. However, sometimes, when things get really complex, you can't  
figure out a way to write down the code. That's when it can be handy  
to start out from the types and slowly work towards the definition.


At first, you'll think that types are there to make your life harder.  
After a while, you'll start to love them and to be honest: I feel  
quite uncomfortable programming in an untyped language these days ;).


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


Re: [Haskell-cafe] Updated formlets sample?

2008-09-22 Thread Chris Eidhof
Ah yes, I just adjusted the code until it compiled, I must confess I  
didn't check whether it actually worked ;). Thanks for the wiki-update!


-chris

On 22 sep 2008, at 09:47, Martin Huschenbett wrote:


Hi Chris,

you're absolutely right. The mistake was in the where-part of  
withForm. The function handleOk' gets an environment d as argument  
but uses an extractor that was created without passing d to  
runFormState. I've put a corrected version on hpaste [1] and also  
posted it to the wiki on haskell.org [2]. Hope this is ok for you?


Regards,

Martin.

[1] http://hpaste.org/10568#a1
[2] http://haskell.org/haskellwiki/Formlets

Chris Eidhof schrieb:
That means that you don't have input0 in your environment, maybe  
you're passing in an empty environment?

-chris
On 21 sep 2008, at 12:11, Martin Huschenbett wrote:

Hi Chris,

thanks for the updated example. Compiling works now. But when I  
try to run it I alway get error messages like


[input0 is not in the data,input1 is not in the data]

Regards,

Martin.

Chris Eidhof schrieb:

Hey Martin,
On 19 sep 2008, at 04:14, Martin Huschenbett wrote:
I found a blog post concerning formlets [1] in the web. Since  
looks very interesting I tried to compile the sample code with  
recent versions of HAppS and formlets from hackage. But this  
didn't work as the API of formlets has changed since this post.


I tried to adopt the code to the new API but I was unable to  
finish this since there is a new monadic context I don't know to  
handle in the right way.


So my question is, is there an updated version of this sample  
code in the web or has anybody tried to adopt it and can send me  
the results?
Yes, I'm sorry for that. The API is still very immature and due  
to changes, that's also why it hasn't been officially announced  
yet. I've just put an updated example at http://hpaste.org/10568,  
hope that'll work for you. I guess we should build a small  
homepage / wikipage that always has an up-to-date example.

-chris


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


Re: [Haskell-cafe] Updated formlets sample?

2008-09-20 Thread Chris Eidhof

Hey Martin,

On 19 sep 2008, at 04:14, Martin Huschenbett wrote:

I found a blog post concerning formlets [1] in the web. Since looks  
very interesting I tried to compile the sample code with recent  
versions of HAppS and formlets from hackage. But this didn't work as  
the API of formlets has changed since this post.


I tried to adopt the code to the new API but I was unable to finish  
this since there is a new monadic context I don't know to handle in  
the right way.


So my question is, is there an updated version of this sample code  
in the web or has anybody tried to adopt it and can send me the  
results?



Yes, I'm sorry for that. The API is still very immature and due to  
changes, that's also why it hasn't been officially announced yet. I've  
just put an updated example at http://hpaste.org/10568, hope that'll  
work for you. I guess we should build a small homepage / wikipage that  
always has an up-to-date example.


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


[Haskell-cafe] Type family fun

2008-08-23 Thread Chris Eidhof

Hey all,

I was playing around with type families, and I have a strange problem.

Suppose we have an alternative to an Either datatype:

 data (:|:) a b = Inl a | Inr b

and a class Ix:

 class Ix i where
   type IxMap i :: * - *
   empty  :: IxMap i [Int]

Now I want to give an instance for (a :|: b):

 instance (Ix l, Ix r) = Ix (l :|: r) where
   type IxMap (l :|: r) = BiApp (IxMap l) (IxMap r)
   empty = BiApp empty empty

BiApp is defined as following:

 data BiApp a b c = BiApp (a c) (b c)

However, it looks like the recursive calls to empty can't be unified,  
I get the following error message:


Couldn't match expected type `IxMap l'
   against inferred type `IxMap i'
  Expected type: IxMap (l :|: r) [Int]
  Inferred type: BiApp (IxMap i) (IxMap i1) [Int]
In the expression: BiApp empty empty
In the definition of `empty': empty = BiApp empty empty

In the inferred type, there should be IxMap l instead of IxMap i, does  
anybody know what I'm doing wrong?


Thanks,

-chris

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


Re: [Haskell-cafe] Re: [Haskell] Compiler Construction course using Haskell?

2008-08-20 Thread Chris Eidhof

I plan to give a course in compiler construction,
using Haskell as the implementation language
(not as source or target language).

Something along these lines:
1. combinator parsers (Parsec),
2. simple interpreter (arithmetical expressions)
3. add algebraic data types, functions
4. type checker
5. code generator.
Ideally, 2..5 would be using the very same tree traversal code
and just change the monad for evaluation.

Any comments appreciated. Have you given such a course? Taken?


At Utrecht University, they teach excellent courses on exactly this  
subject, using Haskell. The course webpage [1] is probably a useful  
resource for you, as it shows exactly what we were thought (I  
participated in the course last year). We made heavy use of Utrecht's  
Attribute Grammar Compiler [2], which is a pre-processor for Haskell  
that allows you to very easily build programs using an attribute  
grammar. This proved to be a really nice way to do the tree  
transformations. I very much liked the idea of attribute grammars, but  
I personally don't like pre-processors very much.


Also, we targeted Simple Stack Machine as a platform. This is an  
assembly-like language that has a graphical interpreter, so you can  
actually see your code, do single-stepping, see your stack, etc. It  
proved to be quite useful. As a student, I it added a lot of  
educational value, but a real language would also be cool (e.g. Harpy  
[4]).


HTH,
-chris

[1]: http://www.cs.uu.nl/docs/vakken/ipt/
[2]: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/uuagc
[3]: http://people.cs.uu.nl/atze/SSM/index.html
[4]: http://uebb.cs.tu-berlin.de/harpy/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Sphinx full-text searching client on Hackage

2008-07-14 Thread Chris Eidhof

Hey everyone,

We started working on a client [1] for the sphinx full-text search  
engine [2], which is a very fast full-text search engine that has  
either SQL or XML as a backend. While our version is far from done (it  
only supports the query command, and a limited number of parameters),  
we still think that it might be useful for other people as well. If  
you want to help us hacking on it, testing it or improving  
documentation, you're more than welcome.


The communication with Sphinx is done using a quite low-level binary  
protocol, but Data.Binary saved the day: it made it very easy for us  
to parse all the binary things. Especially the use of the Get and Put  
monads are a big improvement over the manual reading and keeping track  
of positions, as is done in the PHP/Python clients.


Thanks,
-chris

[1]: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/sphinx
[2]: http://www.sphinxsearch.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Compiling GHC 6.8.3 on OS X with readline support

2008-07-07 Thread Chris Eidhof

Hey all,

When compiling GHC 6.8.3 on OS X, I ended up with a GHCi without  
readline support. That makes interacting quite hard, especially  
because the Backspace-key didn't even work. With some help on irc from  
Baughn and by reading a blog post from Paul Brown, I managed to get  
readline working after all.


After installing readline from fink, I had to pass the following  
options to configure:


./configure --with-readline-includes=/sw/include/readline --with- 
readline-libraries=/sw/lib


After that make and sudo make install worked just fine, and I had  
readline again! I wrote this down in case anybody else has had the  
same problems.


-chris

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


[Haskell-cafe] The state of database libraries

2008-07-04 Thread Chris Eidhof

Hey everyone,

I'm figuring out how to do databases in Haskell (on OS X). So far,  
I've tried the following approaches:


1. hdbc. I'd like to connect to MySQL, so I need the ODBC backend. I  
couldn't get this to work under OS X, while I installed myodbc, which  
seems to be broken.


2. hsql. The packages on hackage don't compile, so I grabbed the darcs  
version. hqsl itself installed perfectly, but when I try to compile  
hsql-mysql, it does not recognize that hsql is already installed and  
tries to recompile. Compiling fails, so I generated a .tar.gz of hsql  
using cabal sdist, put it in the .cabal/packages directory in the  
right place, and finally, it does compile. Now hsql-mysql starts  
compiling, but it finally fails with:


MySQL.hsc:270:0:
 error: ‘MYSQL_NO_DATA’ undeclared (first use in this function)

MySQL.hsc:270:0:
 error: (Each undeclared identifier is reported only once

MySQL.hsc:270:0:  error: for each function it appears in.)

So what is the state of hsql? And haskelldb? Are they actively  
maintained?


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


Re: [Haskell-cafe] IMAP and NNTP libraries

2008-06-23 Thread Chris Eidhof

On 23 jun 2008, at 22:26, Spencer Janssen wrote:


On Sun, Jun 22, 2008 at 02:52:33AM -0300, Maurí cio wrote:

Hi,

Are there mature libraries for IMAP and NNTP
available to Haskell?

Thanks,
Maurício


There is the haskellnet project:

   http://darcs.haskell.org/SoC/haskellnet/

I'm not sure whether it is mature or maintained.
I don't think it's maintained or mature: last time I checked, I  
couldn't get it to work (probably due to library changes), and there  
is not a lot of documentation nor comments.


I was actually thinking of writing a binding myself, to libEtPan!,  
which seems to have a well-documented and clean interface. I'm not  
sure how hard this is though. I've also looked a bit at the UW c- 
client, but I haven't seen any good examples of how to use it.


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


Re: [Haskell-cafe] wanted: Network.Curl examples

2008-06-11 Thread Chris Eidhof

Hey Brad,

I wrote a blog-post with some curl-examples in there, it's a small  
mashup of last.fm and upcoming, check it at


http://tinyurl.com/5d8jx7

Enjoy,
-chris

On 11 jun 2008, at 07:51, brad clawsie wrote:


-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

in search of some trivial examples using Network.Curl, preferrably
posted here:

http://haskell.org/haskellwiki/Network.Curl

some of this stuff i can figure out, but setting the curl
WriteFunction, as discussed here:

http://code.haskell.org/~dons/docs/curl/Network-Curl-Opts.html#t%3AWriteFunction

is nonobvious.

any info would be useful, curl is a great library and it would be nice
if using it were more straightforward

thanks
brad
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.9 (FreeBSD)

iEYEARECAAYFAkhPaAAACgkQxRg3RkRK91OQrQCfTt+xzvqIAxDkqq8/P85ZZjON
HWgAoK3L/1JUQjdaWHcHfutKvI3nPJUc
=BfuR
-END PGP SIGNATURE-
___
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] Simple list processing

2008-06-11 Thread Chris Eidhof

Hey Andrew,

On 11 jun 2008, at 20:17, Andrew Coppin wrote:
According to the theory, anything that consumes a list and produces  
a value is some kind of fold. [Assuming it traverses the list in a  
sensible order!] So it looks like you could implement this as a  
fold. But should that be a LEFT-fold or a RIGHT-fold? (I always get  
confused between the two!)

Check out http://foldl.com/ and http://foldr.com ;)

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


[Haskell-cafe] [ANN] Twitter Client

2008-05-09 Thread Chris Eidhof

Hey everyone,

I was tired of all those graphical Twitter clients that aren't usable  
from my Terminal, so I wrote my own. It's still very much alpha, but  
comments or improvements are more than welcome. You can install it by  
downloading the twitter-package from hackage.


In order to get it to work, create a file ~/.twitter with the  
contents username:password, and you should be set.


The source code isn't polished yet, but it makes heavy use of the new  
curl, json and xml libraries from Galois, so it might be interesting  
to browse the source.


-chris

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


Re: [Haskell-cafe] parser

2007-12-07 Thread Chris Eidhof


On 7 dec 2007, at 22:55, Ryan Bloor wrote:


hi

The thing is... it will be a simple parser really. The expressions  
are already defined and we can't use parsec imports. Below is the  
types I have.
I have a function that removes initial spaces from the start of a  
string. A function that checks if a substring is part of another  
string, which use the remove space function also.

The next function is: which uses the type:

type Parser = String - [(Expr,String)]
So what does this type really mean? You give it a string, and it will  
return a list of (Expr, String). I would guess that the list is all  
possible outcomes, and the String in (Expr, String) is probably the  
rest of the parsed data. If you want to find a correct parse, you  
probably want to select the first element from that list that has an  
empty rest.


You could write a parser that parses single digits:

parseDigit :: String - [(Int, String)]
parseDigit (x:xs) | isDigit x = [read x]

Of course you have to define the other cases for parseDigit. If you  
had a parseMany function that parses many things of the same type, you  
could combine that with parseDigit to parse natural numbers. The other  
thing you are really going to need is a choice-operator. In your  
example, you want to parse terms that are either numbers or term +  
term:


parseTerm = parseNaturalNumber `parseOr` parseAddition

It's probably best to read a good book or tutorial on parsers. There  
is an excellent textbook on grammars and parsing in Haskell [1], it  
probably explains exactly what you want.


-chris

[1] Johan Jeuring, Doaitse Swierstra: Grammars and Parsing: 
http://www.cs.uu.nl/docs/vakken/gont/diktaat.pdf




readExpression :: String - Expr

e.g. readExpression True = EBool True
e.g. readExpression (23 + 67) = EAdd (EInt 23) (EInt 67)


 
Types--


data Type = TNone -- badly typed values
| TInt -- integer values
| TBool -- boolean values
deriving Show
data Expr = EInt {vInt :: Int} -- integer values
| EBool {vBool :: Bool} -- boolean values
| EAdd Expr Expr -- (e1 + e2)
| EMin Expr Expr -- (e1 - e2)
| EMul Expr Expr -- (e1 * e2)
| EAnd Expr Expr -- (e1  e2)
| EOr Expr Expr -- (e1 || e2)
| ENot Expr -- not e1
| EComp Expr Expr -- (e1 == e2)
| ETest Expr Expr Expr -- if e1 then e2 else e3
| ENone -- badly formed expressions






 CC: haskell-cafe@haskell.org
 From: [EMAIL PROTECTED]
 To: [EMAIL PROTECTED]
 Subject: Re: [Haskell-cafe] parser
 Date: Fri, 7 Dec 2007 22:17:54 +0100


 On 6 dec 2007, at 18:06, Ryan Bloor wrote:
  Can anyone advise me on how to check whether a string contains  
ints,

  chars, bools, etc
 
  2345 + 6767 shoudl give IntAdd (2345) (6767)
  2345 should give IntT 2345
 You need to write a parser. There are a lot of libraries that will
 help you write a parser. One library that is often used for writing
 parsers in Haskell is called Parsec [1]. There's good  
documentation on

 that site on how to use it. Parsec is already included in you
 distribution. Good luck!

 -chris

 [1]: http://legacy.cs.uu.nl/daan/parsec.html


Get closer to the jungle… I'm a Celebrity Get Me Out Of Here!


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


Re: [Haskell-cafe] parser

2007-12-07 Thread Chris Eidhof

On 7 dec 2007, at 23:51, Ryan Bloor wrote:
i am using hugs and the isDigit and anything 'is' doesn't work...  
they must have forgot to add them in! Does GHC work with them.
Yes, it's in base. Alternatively, you could write the functions  
yourself, they're not that hard.
p.s... that book looks fantastic... bette than the ones i got from  
the library; too specific.
also... when and where do i use my predetermined types(EBool) and  
how...?
I think that is explained in the book. It's also not too hard to  
figure out yourself. A good strategy for writing Haskell programs in  
general is to think of the types first: what types should your  
functions have? Often this will help you in thinking of a good  
implementation.


The first thing you want to do, is parametrize the return-type of your  
parser. Instead of having type Parser = [(ETerm, String)] you probably  
want: type Parser a = String - [(a, String)]. With that type, you  
could do something like:


parseDigit :: Parser Int
parseMany :: Parser a - Parser [a]
parseOr :: Parser a - Parser a - Parser a

You can use these types to come up with the functions.

-chris




Ryan





 CC: haskell-cafe@haskell.org
 From: [EMAIL PROTECTED]
 To: [EMAIL PROTECTED]
 Subject: Re: [Haskell-cafe] parser
 Date: Fri, 7 Dec 2007 23:31:38 +0100


 On 7 dec 2007, at 22:55, Ryan Bloor wrote:

  hi
 
  The thing is... it will be a simple parser really. The expressions
  are already defined and we can't use parsec imports. Below is the
  types I have.
  I have a function that removes initial spaces from the start of a
  string. A function that checks if a substring is part of another
  string, which use the remove space function also.
  The next function is: which uses the type:
 
  type Parser = String - [(Expr,String)]
 So what does this type really mean? You give it a string, and it  
will

 return a list of (Expr, String). I would guess that the list is all
 possible outcomes, and the String in (Expr, String) is probably the
 rest of the parsed data. If you want to find a correct parse, you
 probably want to select the first element from that list that has an
 empty rest.

 You could write a parser that parses single digits:

 parseDigit :: String - [(Int, String)]
 parseDigit (x:xs) | isDigit x = [read x]

 Of course you have to define the other cases for parseDigit. If you
 had a parseMany function that parses many things of the same type,  
you
 could combine that with parseDigit to parse natural numbers. The  
other

 thing you are really going to need is a choice-operator. In your
 example, you want to parse terms that are either numbers or term +
 term:

 parseTerm = parseNaturalNumber `parseOr` parseAddition

 It's probably best to read a good book or tutorial on parsers. There
 is an excellent textbook on grammars and parsing in Haskell [1], it
 probably explains exactly what you want.

 -chris

 [1] Johan Jeuring, Doaitse Swierstra: Grammars and Parsing: 
http://www.cs.uu.nl/docs/vakken/gont/diktaat.pdf

 
 
  readExpression :: String - Expr
 
  e.g. readExpression True = EBool True
  e.g. readExpression (23 + 67) = EAdd (EInt 23) (EInt 67)
 
 
  
  Types--
 
  data Type = TNone -- badly typed values
  | TInt -- integer values
  | TBool -- boolean values
  deriving Show
  data Expr = EInt {vInt :: Int} -- integer values
  | EBool {vBool :: Bool} -- boolean values
  | EAdd Expr Expr -- (e1 + e2)
  | EMin Expr Expr -- (e1 - e2)
  | EMul Expr Expr -- (e1 * e2)
  | EAnd Expr Expr -- (e1  e2)
  | EOr Expr Expr -- (e1 || e2)
  | ENot Expr -- not e1
  | EComp Expr Expr -- (e1 == e2)
  | ETest Expr Expr Expr -- if e1 then e2 else e3
  | ENone -- badly formed expressions
 
 
 
 
 
 
   CC: haskell-cafe@haskell.org
   From: [EMAIL PROTECTED]
   To: [EMAIL PROTECTED]
   Subject: Re: [Haskell-cafe] parser
   Date: Fri, 7 Dec 2007 22:17:54 +0100
  
  
   On 6 dec 2007, at 18:06, Ryan Bloor wrote:
Can anyone advise me on how to check whether a string contains
  ints,
chars, bools, etc
   
2345 + 6767 shoudl give IntAdd (2345) (6767)
2345 should give IntT 2345
   You need to write a parser. There are a lot of libraries that  
will
   help you write a parser. One library that is often used for  
writing

   parsers in Haskell is called Parsec [1]. There's good
  documentation on
   that site on how to use it. Parsec is already included in you
   distribution. Good luck!
  
   -chris
  
   [1]: http://legacy.cs.uu.nl/daan/parsec.html
 
 
  Get closer to the jungle… I'm a Celebrity Get Me Out Of Here!



Can you guess the film? Search Charades!


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


Re: [Haskell-cafe] parser

2007-12-07 Thread Chris Eidhof


On 6 dec 2007, at 18:06, Ryan Bloor wrote:
Can anyone advise me on how to check whether a string contains ints,  
chars, bools, etc


2345 + 6767 shoudl give IntAdd (2345) (6767)
2345 should give IntT 2345
You need to write a parser. There are a lot of libraries that will  
help you write a parser. One library that is often used for writing  
parsers in Haskell is called Parsec [1]. There's good documentation on  
that site on how to use it. Parsec is already included in you  
distribution. Good luck!


-chris

[1]: http://legacy.cs.uu.nl/daan/parsec.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] return in Monad class necessary?

2007-11-27 Thread Chris Eidhof

On 27 nov 2007, at 10:14, Reinier Lamers wrote:

Chris Eidhof wrote:


On 26 nov 2007, at 19:48, Henning Thielemann wrote:


I wonder whether it is a typical mistake of beginners
to write 'return' within a do-block (that is, not at the end)
and if it is possible to avoid this mistake by clever typing.
In a proper monad 'return' can be fused with subsequent actions,
and thus it is not necessary within a sequence of actions.
However, although sensible, 'return' is also not required at the  
end  of a block.

Has someone already thought about a replacement for monads?


I also made that mistake in the beginning, I used return instead  
of  lets. I don't think it's a big problem, most users will find  
out once  they've got some more experience, and it doesn't really  
do any harm.


It might be possible for the compiler to emit a warning when a  
return is used in the middle of a do block as the top level operator  
on a line. OTOH, that still wouldn't catch something like when (x  
== 0) (return ()) which doesn't do what an imperative programmer  
expects.

Well, there are two things about the return:

First, some people want to use return just as an imperative programmer  
would use it: to exit from a function. So the programmer doesn't  
expect the commands after that return are executed.


Second, the problem I had was that I didn't know how to do  
computations with the data I got from the monad, for example:


 main = do
   myLine - getLine
   reversed - return $ unwords $ reverse $ words myLine
   putStrLn reversed

Instead of the 3rd line I could have written
 let reversed = unwords $ reverse $ words myLine

This is another problem, but it doesn't affect the computation,  
whereas the first problem is more serious.


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


Re: [Haskell-cafe] return in Monad class necessary?

2007-11-26 Thread Chris Eidhof

On 26 nov 2007, at 19:48, Henning Thielemann wrote:

I wonder whether it is a typical mistake of beginners
to write 'return' within a do-block (that is, not at the end)
and if it is possible to avoid this mistake by clever typing.
In a proper monad 'return' can be fused with subsequent actions,
and thus it is not necessary within a sequence of actions.
However, although sensible, 'return' is also not required at the end  
of a block.

Has someone already thought about a replacement for monads?
I also made that mistake in the beginning, I used return instead of  
lets. I don't think it's a big problem, most users will find out once  
they've got some more experience, and it doesn't really do any harm.


-chris

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


[Haskell-cafe] RLE in Haskell: why does the type variable get instantiated?

2007-07-31 Thread Chris Eidhof

Hey Haskell-Cafe,

I was trying out the code in Dons's article [1], and I noticed a  
weird thing when doing it in GHCi. When binding the function  
composition to a variable, the type suddenly changes. I'm not  
completely sure why this happens. Is this because GHCi is in a monad  
and wants to find an instance for the type variable? Here's my GHCi  
session:


Prelude :m +Control.Arrow
Prelude Control.Arrow :m + List
Prelude Control.Arrow List :t map (length  head) . group
map (length  head) . group :: (Eq a) = [a] - [(Int, a)]
Prelude Control.Arrow List let encode = map (length  head) . group
Prelude Control.Arrow List :t encode
encode :: [Integer] - [(Int, Integer)]

Thanks,
-chris

[1]: http://cgi.cse.unsw.edu.au/~dons/blog/2007/07/31
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Silly mail client

2007-05-06 Thread Chris Eidhof
One thing I did was replacing the Reply button in my toolbar with  
Reply All. The only problem is that I always use Cmd+R instead of  
clicking a button, but I'm at least a little bit closer.


-chris

On 6-mei-2007, at 15:21, [EMAIL PROTECTED] wrote:



Andrew Coppin [EMAIL PROTECTED] writes:

OK, this is hacking me off now... Does ANYBODY know how I can  
convince

Thunderbird to send replies to Haskell Cafe rather than sending them
to the original poster? This is really becoming tiresome...


My best approach to that has been to explicitely rewrite the Reply-To
with procmail when the mail arrives at my place. The problem is, that
the 'List-Id' tag will only work, if all clients stick to the implied
rules (which they don't) and if you don't have a MTA or mailbox
storage (like cyrus) which eliminates duplicates (then answers copied
to you arrive earlier, leading to elimination of the copy with the
List-Id tag). After long and careful study I've come to the conclusion
that every magic based on headers inserted by the mailing list and
based on all participants mail clients sticking to some rules won't
work.

Originally, as I understand it, the Mail-Followup-To field had been
intended to indicate an address for reply to list. But most mail
clients don't support it. I'm not sure wether Thunderbird supports it,
but I've heard a reply all would reply to the address indicated in
Mail-Followup-To. The problem is anyway (a) Haskell Cafe does not
provide the field and (b) duplicate elimination would quite possibly
kick the wrong mail copy (that which has Mail-Followup-To set).

So my suggestion:

 1) Use procmail
 2) Detect haskell-cafe in the headers
 3) Add the List-Id and Mail-Followup-To at you side.

 4) If you have client which doesn't respect Mail-Followup-To (try
reply all), then also add a Reply-To header.

(4) means, if you wan't to reply by mail to the individual author,
you'll have to edit the receiver address by hand.

Regards -- Markus

___
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] Why the Prelude must die

2007-03-24 Thread Chris Eidhof


On Mar 24, 2007, at 2:36 AM, Sebastian Sylvan wrote:


On 3/24/07, Chris Eidhof [EMAIL PROTECTED] wrote:

 Given all these issues, I consider the only reasonable option is to
 discard the Prelude entirely.  There will be no magic modules.
 Everything will be an ordinary library.  HOFs like (.) are  
available

 from Control.Function.  List ops come from Data.List.  Any general
 abstractions can be added in abstract Sequence, Monad, etc.  
modules.

 Haskell will regain the kind of organic evolution whose lack
 currently causes Haskell to lose its lead over Python et al by the
 day.
I basically agree with a lot of the things you say. The only thing
is: it's so convenient to have the Prelude. I can just start writing
my haskell programs and don't have to worry about all kinds of
imports. And you'll end up being repetitive: you'll import (.) and
stuff like that in _every_ file. Yeah, this will definitely be more
modular, but if we go for it, it's going to be so much more (tedious)
work to create a new program.


The solution is simple:

* If there is a module M where clause in the beginning of the file,
then it's a proper module and shouldn't import the Prelude.
* If there is no module declaration then it's a quick'n dirty script
and should have the Prelude implicitly imported.
* Interactive interpreters should probably import the Prelude.
So if I'm writing a script, which has been working, then import  
Control.Monad, it all suddenly stops working?


I also think that you want to minimize the differences between an  
interpreted (interactive) version and a compiled version. It would be  
very weird for first-time users if their scripts work in ghci but  
break when they compile them.


I'm sorry for being so negative. I like the idea, but I don't like it  
from a newbie-standpoint. The thing is: this is mostly handy for  
power-users, maybe we should do it for power-users only? We can still  
change the prelude to have no more code in there, but make it only a  
bunch of imports?


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


Re: [Haskell-cafe] Why the Prelude must die

2007-03-23 Thread Chris Eidhof

Given all these issues, I consider the only reasonable option is to
discard the Prelude entirely.  There will be no magic modules.
Everything will be an ordinary library.  HOFs like (.) are available
from Control.Function.  List ops come from Data.List.  Any general
abstractions can be added in abstract Sequence, Monad, etc. modules.
Haskell will regain the kind of organic evolution whose lack
currently causes Haskell to lose its lead over Python et al by the
day.
I basically agree with a lot of the things you say. The only thing  
is: it's so convenient to have the Prelude. I can just start writing  
my haskell programs and don't have to worry about all kinds of  
imports. And you'll end up being repetitive: you'll import (.) and  
stuff like that in _every_ file. Yeah, this will definitely be more  
modular, but if we go for it, it's going to be so much more (tedious)  
work to create a new program.


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


Re: [Haskell-cafe] XML Validation and Digestion in Haskell

2007-03-22 Thread Chris Eidhof
Don't spend too much time on the various libraries though. I tried  
some simple things with Haskell and XML, but I found it really hard  
to actually parse a simple document. You really don't want to write  
your own parser.


The only tool that worked for me was HXT, which is based on arrows.  
These are pretty hard to grasp right away, but really powerful. I  
really like the way they are used in HXT, but it still feels a bit  
weird sometimes.


Good luck, and keep us posted.

-chris

On Mar 22, 2007, at 7:52 AM, Andrew Wagner wrote:


Hi Arun,
Your problem description seems a little vague - which is
understandable, considering how embedded in your business model it is.
As for general recommendations, I'm no guru, but I would suggest
looking at the existing XML libraries in Haskell [1], and if that's
not powerful enough, check out parsec[2] for building a custom parser.
I think to get more specific recommendations, you would need to give
more details about the problem. Hope this helps somewhat. Andrew

[1]: http://www.haskell.org/haskellwiki/Libraries_and_tools/ 
Web_programming#XML_2

[2]: http://www.cs.uu.nl/people/daan/download/parsec/parsec.html


On 3/22/07, Arun Suresh [EMAIL PROTECTED] wrote:

Hi..

I am currently working on a project where basically we do a lot of  
XML

validation and digestion. For example :
We recieve an XML document A, if the document passes schema  
validation, we
do some business level validations, then from A, we create XML  
digests B, C

and D.
Our code-base is written completely in Java. We had earlier tried  
using
XSLT, but it became too unwieldy to manage (we ended up making  
calls to

other Java classes from the XSLT engine)

The problem we are facing right now is that we have huge  
hierarchies of
Validators, Digestors and Contexts. It just doesnt look right. I  
just cant

help but wonder if theres a better way of doing this...

I have been trying to get my hands dirty with Haskell for a couplo  
weeks
now. all the while keeping the problem at hand in the back of my  
mind.. I
just dont seem to be see how applying functional programming  
concepts can
help in this scenario.. Was wondering if somebody could probably  
give me

some pointers..

Regards
Arun






___
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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] XML Validation and Digestion in Haskell

2007-03-22 Thread Chris Eidhof

Hey Aron,

I think you intended to CC Haskell Café as well. HaXml has support  
for DtdToHaskell, but HXT supports validating with a Relax NG  
validator. I guess the best way to figure it out is thoroughly read  
the documentation.


-chris

On Mar 22, 2007, at 10:40 PM, Arun Suresh wrote:


thanks for the feedback you guyz..

First off.. I went through the HaXml documentation.. It looks  
pretty promising..
and as far as HXT is concerned.. I guess ill be spending the  
weekend grappling with the concept of Arrows and monads in general :)


I dont know if HXT or HaXml offers it.. but I was wondering if  
either of them provides some sort of schema compilation facility..  
(a la XmlBeans.. for those from the Java world).. basically I was  
wondering if given an XML schema, is there a utility that will  
generate a Haskell type hierarchy from the same ??


regards
Arun


On 3/23/07, Chris Eidhof  [EMAIL PROTECTED] wrote:Don't spend too  
much time on the various libraries though. I tried

some simple things with Haskell and XML, but I found it really hard
to actually parse a simple document. You really don't want to write
your own parser.

The only tool that worked for me was HXT, which is based on arrows.
These are pretty hard to grasp right away, but really powerful. I
really like the way they are used in HXT, but it still feels a bit
weird sometimes.

Good luck, and keep us posted.

-chris

On Mar 22, 2007, at 7:52 AM, Andrew Wagner wrote:

 Hi Arun,
 Your problem description seems a little vague - which is
 understandable, considering how embedded in your business model  
it is.

 As for general recommendations, I'm no guru, but I would suggest
 looking at the existing XML libraries in Haskell [1], and if that's
 not powerful enough, check out parsec[2] for building a custom  
parser.

 I think to get more specific recommendations, you would need to give
 more details about the problem. Hope this helps somewhat. Andrew

 [1]: http://www.haskell.org/haskellwiki/Libraries_and_tools/
 Web_programming#XML_2
 [2]: http://www.cs.uu.nl/people/daan/download/parsec/parsec.html


 On 3/22/07, Arun Suresh  [EMAIL PROTECTED] wrote:
 Hi..

 I am currently working on a project where basically we do a lot of
 XML
 validation and digestion. For example :
 We recieve an XML document A, if the document passes schema
 validation, we
 do some business level validations, then from A, we create XML
 digests B, C
 and D.
 Our code-base is written completely in Java. We had earlier tried
 using
 XSLT, but it became too unwieldy to manage (we ended up making
 calls to
 other Java classes from the XSLT engine)

 The problem we are facing right now is that we have huge
 hierarchies of
 Validators, Digestors and Contexts. It just doesnt look right. I
 just cant
 help but wonder if theres a better way of doing this...

 I have been trying to get my hands dirty with Haskell for a couplo
 weeks
 now. all the while keeping the problem at hand in the back of my
 mind.. I
 just dont seem to be see how applying functional programming
 concepts can
 help in this scenario.. Was wondering if somebody could probably
 give me
 some pointers..

 Regards
 Arun






 ___
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A real Haskell Cookbook

2007-02-25 Thread Chris Eidhof

Hey everyone,

we added some examples to this page. There are some topics that don't  
have any examples, notably:

# 11 Network Programming
# 12 XML
* 12.1 Parsing XML
# 13 Databases
* 13.1 MySQL
* 13.2 PostgreSQL
* 13.3 SQLite
# 14 FFI
* 14.1 How to interface with C

If anyone feels like filling up some of those sections, that would be  
great.


-chris

On 21 Feb, 2007, at 20:17 , Martin Bishop wrote:

I made a preliminary page, and fleshed out some of the headers/sub- 
headers on the wiki page for a good Haskell Cookbook (aka NOT a  
PLEAC clone).  Please contribute and/or fix the examples and  
explanations so we can make a really nice Cookbook for newbies. :)


 http://haskell.org/haskellwiki/Cookbook

___
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] Hi can u explain me how drop works in Haskell

2007-02-25 Thread Chris Eidhof

Hey,

you're almost there:

drop :: Integer - [a] - [a]
drop 0 xs = xs
drop n (x:xs) = drop (n-1) xs

Your version fails when trying to do drop 10 [1..10]. My version  
fails when trying to do drop 10 [1..9], so you might want to try to  
see if you can come up with a solution for that!


Good luck,
-chris

On 25 Feb, 2007, at 18:43 , iliali16 wrote:



Hi I am trying to implement the function drop in haskell the thing  
is that I
I have been trying for some time and I came up with this code where  
I am

trying to do recursion:

drop :: Integer - [Integer] - [Integer]
drop 0 (x:xs) = (x:xs)
drop n (x:xs)
|n  lList (x:xs) = dropN (n-1) xs :
|otherwise = []

So I want to understand how would this work and what exacttly  
should I put
as an answer on line 4 couse that is where I am lost. I know I  
might got the
base case wrong as well but I don't know what to think for it. I  
have done
the lList as a function before writing this one. Thanks to those  
who can

help me understand this. Thanks alot in advance! Have a nice day!
--
View this message in context: http://www.nabble.com/Hi-can-u- 
explain-me-how-drop-works-in-Haskell-tf3290490.html#a9152251
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] Recursion in Haskell

2007-02-17 Thread Chris Eidhof

The definition of myLen says:

 myLen [] = 0
The length for an empty list is zero

 myLen (x:xs) = 1 + myLen xs
The length of a list containing x and some other stuff (xs) is 1 +  
(the length of the other stuff).


So basically, if you've got a list [1,2,3], it will try to do this:

 myLen (1:[2,3]) = 1 + myLen [2,3]
The length of [1,2,3] is 1 + the length of [2,3]

 myLen (2:[3]) = 1 + myLen [3]
The length of [2,3] = 1 + the length of [3]

 myLen (3:[]) = 1 + myLen []
This is the tricky part, now the other case of myLen is being called:

 myLen [] = 0
Here you can see that it won't recurse anymore. Now there is going to  
be some replacement:


 myLen (3:[])
can now be calculated, because myLen [] is now known (0). Because  
we know this,


 myLen (2:[3])
can now be calculated too, because we know that myLen [3] is 1. And  
so on.


I think the trick here is to see that [1] is exactly the same as 1: 
[]. Once you grasp this, the rest will probably easy.


Good luck!

-chris

On 17 Feb, 2007, at 19:32 , P. R. Stanley wrote:


Hi
I understand the basic principle of recursion but have difficulty  
with the following:

-- a recursive function
-- for calculating the length of lists
myLen [] = 0
myLen (x:xs) = 1 + myLen xs
What's happening here?
Top marks for a comprehensive jargon-free explanation.
Thanks in advance
Paul

___
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] Is Excel the most used -- and fucntional -- programming lanuage on Earth?

2007-01-30 Thread Chris Eidhof
The cool thing about Excel is that it's like Function Reactive  
Programming. When you update the value of a cell, all the other cells  
that reference to it get updated too. That's pretty cool to have in  
GUI's as well, and Haskell has that too. See [1].


-chris

[1]: http://www.haskell.org/frp/

On 30 Jan, 2007, at 22:46 , Alexy Khrabrov wrote:


Heard that statement recently -- that Excel is a functional
programming language, and the most used one -- of any programming
languages -- on Earth!  Is it true?  Are there good examples of
typical FP style in Excel?

Cheers,
Alexy
___
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] Channel9 Interview: Software Composability and theFu ture of Languages

2007-01-28 Thread Chris Eidhof

Haskell is _not_ inherently hard - any more than any other
programming language. But it is different. So right now,
Haskell is hard only because we need more
documentation that is designed to make Haskell
seem easy.
Well, I think it's harder to get a program compiled in Haskell than  
in Java, for example. It's not too hard, although debugging might be  
a little difficult. I think this has to do with the type system.  
Althought it sounds bad, it's actually a good thing. Once you get a  
Haskell program compiled, chances are much higher that it's correct.  
You do a bit more work up front, but chances of a bug are way lower.


The way I see it, programming in Haskell is an investment. If you're  
from a OOP-background, some (trivial) things might take a lot more  
time. But in the end, it does make you more productive. You spend  
less time tracking bugs, and it's easier to refactor. Not everybody  
is willing to make an investment when they've got something that works.


For example, if you know one imperative language, you can switch to  
another without taking too much risk. On the other hand, if you  
switch to a language that is completely different, you don't know if  
it will get your job done. It doesn't feel safe.


-chris

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


Re: [Haskell-cafe] Concurrency in Haskell

2007-01-25 Thread Chris Eidhof
Yes, I'm curious too. For example, it would be great if we could  
change a function that uses map almost automatically to a function  
that does the map in parallel. Ofcourse it should be in the IO monad,  
so maybe mapM would be a better choice to start with.


-chris

On 25 Jan, 2007, at 21:13 , Alexy Khrabrov wrote:


What's the state of concurrency in Haskell?  If Erlang's main strength
is light-weight parallelism, can something like that be done in
Haskell?

Are there good examples of useful code employing GHC concurrency
features one can play with?

Cheers,
Alexy
___
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] Currying

2007-01-18 Thread Chris Eidhof

what is so great about currying?

What are its uses, apart from letting one define functions with less
parentheses?
Well, from an academic viewpoint, it's very interesting to see a  
function defined as a composition of functions. From a practical  
viewpoint, it's just really handy. It saves you a lot of tedious  
typing, and that's basically what progamming languages are supposed  
to do. That's exactly what I love about haskell: it saves me from a  
lot of unnecessary typing. After all, I'm a lazy programmer ;)


-chris

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


Re: [Haskell-cafe] MissingH: profiler support?

2007-01-12 Thread Chris Eidhof
Thanks, this works! I had to build all the other libraries that are  
required with profiling support too. I also  wrote it down on the  
MissingH wiki, see http://software.complete.org/missingh/wiki/Profiling


-chris

On 12 Jan, 2007, at 4:08 , Spencer Janssen wrote:

The typical way to add profiling support to a Cabal lib is to add - 
p at configure time (ie runhaskell Setup.hs configure -p).  Have  
you tried this?



Cheers,
Spencer Janssen

On Jan 8, 2007, at 4:13 PM, Chris Eidhof wrote:


Hey all,

I'm trying to profile my application, which makes use of MissingH.  
But when compiling with -prof -auto-all, I get the following error:



Language.hs:8:7:
Could not find module `Data.String':
  Perhaps you haven't installed the profiling libraries for  
package MissingH-0.18.0?

  Use -v to see a list of the files searched for.


When compiling without those options, everything works just fine.  
I built missingh from source, and added -prof -auto-all to  
GHCPARMS, and did a ./setup configure,make,install and still no  
result. Does anyone know what could be wrong? I'd really like to  
keep using MissingH and having profiling support at the same time.


Thanks,
-chris

___
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


Resending: [Haskell-cafe] MissingH: profiler support?

2007-01-11 Thread Chris Eidhof

Hey,

does anyone know about this? Resending as I got no replies (yet) ;)

Thanks,
-chris

On 8 Jan, 2007, at 23:13 , Chris Eidhof wrote:


Hey all,

I'm trying to profile my application, which makes use of MissingH.  
But when compiling with -prof -auto-all, I get the following error:



Language.hs:8:7:
Could not find module `Data.String':
  Perhaps you haven't installed the profiling libraries for  
package MissingH-0.18.0?

  Use -v to see a list of the files searched for.


When compiling without those options, everything works just fine. I  
built missingh from source, and added -prof -auto-all to GHCPARMS,  
and did a ./setup configure,make,install and still no result. Does  
anyone know what could be wrong? I'd really like to keep using  
MissingH and having profiling support at the same time.


Thanks,
-chris

___
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] MissingH: profiler support?

2007-01-08 Thread Chris Eidhof

Hey all,

I'm trying to profile my application, which makes use of MissingH.  
But when compiling with -prof -auto-all, I get the following error:



Language.hs:8:7:
Could not find module `Data.String':
  Perhaps you haven't installed the profiling libraries for  
package MissingH-0.18.0?

  Use -v to see a list of the files searched for.


When compiling without those options, everything works just fine. I  
built missingh from source, and added -prof -auto-all to GHCPARMS,  
and did a ./setup configure,make,install and still no result. Does  
anyone know what could be wrong? I'd really like to keep using  
MissingH and having profiling support at the same time.


Thanks,
-chris

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


[Haskell-cafe] Re: SYB and/or HList for XML, deserialization and collections

2006-12-26 Thread Chris Eidhof

== Deserialization ==

HAppS periodically checkpoints application state to disk.   
Developers may want to add or remove fields from their state types  
for from data types used by their state types.  The current  
solution is to have the developer assign a version number to  
state.  If state changes then the developer provides dispatch to a  
deserialization function based on that version number.
Well, it is indeed a fact of life that apps get updated, and data- 
models change. I think Ruby on Rails has implemented this quite good,  
using migrations. Basically, when you're using a migration, you  
specify the differences between two datatypes (or in their case,  
tables). If we found some way to determine those diffs automatically,  
and then require a function that maps the old types to the new  
types... but maybe I'm thinking too difficult. Just thinking out  
loud, really. We could encode the structure of the used datatypes  
into the state, and let HAppS automatically check if it needs to  
migrate...


One of the concepts that I also like about RoR is that they have 3  
modes, development, production and test. Three different databases  
are used for the three modes, so you're not messing in your  
production database. Maybe this is something to think about, too.


-chris

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


Re: [Haskell-cafe] Composing monads (sort of)

2006-12-16 Thread Chris Eidhof

Hey Mark,

How can I concisely compose these functions without having to write  
a cascade of case statements such as:


case f1 rec1 of
Nothing - return Nothing
Just id1 - do
rec2 - f2 id2
return $ case rec2 of
Nothing - return Nothing
Just rec2' - case f3 rec2' of

I understand that if I was just dealing with Maybe I could use the  
fact that Maybe is a monad.

Yes, you can write like this:


id2 - f1 rec1
rec2 - f2 id2
rec3 - f3 rec2
return rec3

or, even shorter:

id2 - f1 rec1
rec2 - f2 id2
f3 rec2


The cool thing of the Maybe monad is that it combines a result in  
such a way that it removes the plumbing of constantly checking for  
Nothing. I can definitely recommand you the following tutorials:


http://www.nomaware.com/monads/html/index.html
http://uebb.cs.tu-berlin.de/~magr/pub/Transformers.en.html

Those two tutorials really helped me.

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