Re: [Haskell-cafe] How to catch exception within the Get monad (the Binary package)

2010-09-05 Thread Victor Gorokhov
 If however something goes wrong, and prs fails, the whole function
 fails (error is thrown). Since [a] (result of decoding) is a lazy
 list, actual exception may be thrown at any moment the list is being
 processed, and exception handler may not be properly set.

 True - return (reverse a)
 False - many' (s:a)

Lazy lists are built in left to right order, but Yours is right to left.


 Is there any way to catch/detect failures inside the Get monad?
lookAhead, lookAheadM, etc
___
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 Ben Lippmeier

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.

Ben.

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


Re: [Haskell-cafe] How to catch exception within the Get monad (the Binary package)

2010-09-05 Thread Henning Thielemann


On Sun, 5 Sep 2010, Dimitry Golubovsky wrote:


Hi,

The following function* is supposed to decode a list of some
serialized objects following each other in a lazy Bytestring:

many :: Get a - Get [a]

many prs = many' [] where
 many' a = do
   s - prs
   r - isEmpty
   case r of
 True - return (reverse a)
 False - many' (s:a)

prs is a parser to decode a single object.


It is more efficient to call
   fmap (s:) (many prs)
 in the recursion in order to avoid the final 'reverse'. The way you have 
implemented the loop, the complete list must be hold in memory, even if it 
is consumed lazily.


The trick to catch exceptions lazily is to make them explicit, either by 
using
  http://hackage.haskell.org/packages/archive/capped-list/1.2/doc/html/Data-CappedList.html 
or

  
http://hackage.haskell.org/packages/archive/explicit-exception/0.1.5/doc/html/Control-Monad-Exception-Asynchronous.html
 with an enclosed list. The latter solution is the more general one, but 
unfortunately it causes a space leak in GHC.

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


Re: [Haskell-cafe] How to catch exception within the Get monad (the Binary package)

2010-09-05 Thread Stephen Tetley
Also any half decent binary format should tell you how long the list
is *before* you parse it, either:

1) How many elements it has - for this you just need a counting
version of the many combinator.

2) The length of bytes that the flattened list takes. In this case the
repeating combinator has to test length remaining before deciding
whether to parse the next element.

Neither should need exceptions.
___
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


[Haskell-cafe] Re: Crypto-API is stabilizing

2010-09-05 Thread Marcel Fourné
Thomas DuBuisson wrote:

There is a blog on this [1], but the main points about the new class
are:

1) Generates bytestrings, not Ints

I like this one because it's semantically truer (tm). ;-)

2) Generalized PRNG construction and reseeding

...which takes the great burden off it's users shoulders, nice!

3) 'split' is in a different class.

Is it necessary for crypto-use? I have never used it for that and I
don't know if somebody other did, but I just ask myself the question.

4) Clean failure via Either (RandomGen forced you to use exceptions)

This is much better and fits nicely into the generateKeyPair of
AsymCipher with a minimum of effort.

What can you do?  Accept this API, help improve the API, or argue that
we should stick with RandomGen (despite short-comings noted on the
blog).  Please pick one and get to it!

I plan to use this (genInteger looks just too convenient), but
RandomGenerator looks nice enough to use it in other
crypto-projects (just my RNG-output consumers view)!

Marcel

-- 
Marcel Fourné
OpenPGP-Key-ID: 0x74545C72
A good library is preferable to a tool, except when you just need that
one tool.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] autocomplete using hoogle

2010-09-05 Thread Yuras Shumovich
Hello,

Just want to share some results of my weekend hacking.

It is clear that haskell type checker can help to build a list of
suggestions for autocomplete (very old idea). I tried to create a very basic
prototype to play with the idea.

The approach I used:
The task can be divided into the next two parts:
  - find the most general type of the word we are trying to complete
that will satisfy the type checker
  - find all the symbols that match the found type
The first task can be solved using ghc. Just replace the word with () and
ghc will tell you something like
  Couldn't match expected type `m String' against inferred type `()'
The second task can be solved using hoogle. Just ask it to find everything
that matches base :: type, where base -- already known part of the word;
type -- the type that ghc expects.

Source code is attached (linux only at a moment)
haskell.vim -- very basic ftplugin for vim
Place it into your ~/.vim/ftplugin directory (don't forget to backup
an existent file if any)
complete.hs -- simple script that does actual work.

How to use it.
cd to the cabal package you are working on at a moment
mkdir dist/hscomplete
copy complete.hs file to the dist/hscomplete
edit complete.hs (at least change the package name, it is hard coded)
create hoogle database for your package:
  cabal haddock --hoogle
  hoogle --convert=dist/doc/html/packageName/packageName.hoo +base
+directory +... (all packages you depend on)
start vim (you should be in the directory where package.cabal file is placed!)
Use C-X C-O to auto complete

Example:
cabalized package tmp contains two modules Data.Tmp and Data.Tmp1
Data.Tmp1 imports Data.Tmp
Data/Tmp.hs contains
  veryLongLongName1 :: Int
  veryLongLongName1 = 1

  veryLongLongName2 :: Char
  veryLongLongName2 = 'c'

  veryLongLongName3 :: String
  veryLongLongName3 = Hello

vim src/Data/Tmp1.hs

  import Data.Tmp

  tmp1 :: Monad m = [a] - m Int
  tmp1 a = veryC-x C-O suggests veryLongLongName1

  tmp2 :: Monad m = [a] - m Char
  tmp2 a = veryC-x C-O suggests veryLongLongName2 and veryLongLongName3

  tmp3 :: Monad m = [a] - m String
  tmp3 a = veryC-x C-O suggests veryLongLongName3


Warning: not ready for real use (no error handling, a lot of hard
codes, slow, etc). Just for playing

Yuras


haskell.vim
Description: Binary data

module Main
where

import System.IO
import System.Process
import System.Environment
import Text.Regex
import Data.Maybe
import Debug.Trace

basedir = dist/hscomplete
logfile = basedir ++ /log
inputfile = basedir ++ /haskell.hs
outputfile = basedir ++ /results
hssourcedir = src
packagename = tmp
hooglepackages = +base +directory +process

main :: IO ()
main = withFile logfile WriteMode complete

complete :: Handle - IO ()
complete log = do
  hPutStrLn log log
  [line', col', base] - getArgs
  let line = read line' :: Int
  let col = read col' :: Int
  hPutStrLn log $ show line ++ : ++ show col ++ : ++ base
  content - fmap (fixContent line col) $ readFile inputfile
  writeFile (basedir ++ /main.hs) content
  (ec, _, stderr) - readProcessWithExitCode ghc [--make, basedir ++ /main.hs, -i ++ hssourcedir] []
  hPutStr log stderr
  let re1 = mkRegex Couldn't match expected type `([^']*)'
  let re2 = mkRegex against inferred type `\\(\\)'
  let m1 = matchRegex re1 stderr
  let m2 = matchRegex re2 stderr
  hPutStrLn log $ match:  ++ show m1 ++   ++ show m2
  if isJust m1  isJust m2  length (fromJust m1) == 1
then do
  (ec, stdout, _) - readProcessWithExitCode hoogle (hoogleOpts ++ [base ++  ::  ++ (head $ fromJust m1)]) []
  let ls = map (head . drop 1 . take 2 . words) $ lines stdout
  hPutStrLn log (show ls)
  hPutStrLn log $ show (filter (filterBase base) ls)
  withFile outputfile WriteMode (\h - mapM_ (hPutStrLn h) $ filter (filterBase base) ls)
else writeFile outputfile 
  hPutStrLn log OK

hoogleOpts = [--data=dist/doc/html/ ++ packagename ++ / ++ packagename ++ .hoo] ++ [hooglepackages]

--XXX
fixContent :: Int - Int - String - String
fixContent line col cont = trace (show ln) $ concat $ map (++ \n) $ pre ++ post
  where
  ls = lines cont
  pre = take (line - 1) ls ++ [ln']
  post = tail post'
  post' = drop (line - 1) ls
  ln = head post'
  ln' = take (col - 1) ln ++ ()  ++ drop col ln

filterBase :: String - String - Bool
filterBase base str = ls  lb  str' == base
  where
  lb = length base
  ls = length str
  str' = take lb str

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


Re: [Haskell-cafe] Announce: lhae

2010-09-05 Thread abau
Serguey Zefirov sergu...@gmail.com wrote:
 You had selected wxWidgets because of what?

Because of the neat grid class in wxWidgets. I did not find
anything comparable in gtk.

 Also, how long did it took (especially GUI part)?

Hard to say, because I work on that project on irregular times in my
spare time. But the GUI part was not the big deal, because wxhaskell
is such a handy library.

[1] http://docs.wxwidgets.org/stable/wx_wxgrid.html



_
HTWK Leipzig FIMN Webmail
 https://webmail.imn.htwk-leipzig.de/nocc/



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


Re: [Haskell-cafe] Announce: lhae

2010-09-05 Thread abau
 Seems cool, but I do not really get it : why write it in haskell ? I
 thought at first that your formula language was haskell, but it
 looks more like a php derivative.

This formula language is just a very simple language to insert formulas into 
cells. It has nothing to do with haskell.

 Does it do more than the spreadsheet thing in openoffice ?

I don't know the spreadsheet in openoffice, but I don't think that lhae does 
anything more or better than openoffice.

 Also, maybe you could do the same with gnuplot, it would be really
 cool to be able to use a friendlier language for defining functions
 other than polynomials or the few standard floating point functions.

Sorry, but I don't understand this point. I thought gnuplot is just for 
plotting graphs. But lhae is a (low level) spreadsheet application. But I may 
got something wrong on your question?

_
HTWK Leipzig FIMN Webmail
 https://webmail.imn.htwk-leipzig.de/nocc/



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


Re: [Haskell-cafe] Restricted type classes

2010-09-05 Thread John Lato
On Fri, Sep 3, 2010 at 12:01 PM, C. McCann c...@uptoisomorphism.net wrote:

 On Fri, Sep 3, 2010 at 11:47 AM, John Lato jwl...@gmail.com wrote:
  On Fri, Sep 3, 2010 at 1:29 PM, Ivan Lazar Miljenovic 
 ivan.miljeno...@gmail.com wrote:
  On 3 September 2010 22:23, John Lato jwl...@gmail.com wrote:
   Do you have a kind * implementation of Foldable?  I'd be interested in
   seeing it, because I was unable to create a usable implementation
 (based
   upon the RMonad scheme) on my last attempt.
 
  I was going to make it a subset of Foldable: fold, foldr, foldl, etc.
 
  So you don't have a working implementation yet?  I ended up thinking this
 is
  impossible, although I don't remember the reasoning that led me to that
  conclusion (and I could very well be wrong).
  I would suggest that you check this before going too far along the
  restricted-monad path.

 This sounds odd to me. An RMonad-style version of Foldable is
 straightforward:

class RFoldable t where
rfold :: Control.RMonad.Suitable t a = (a - b - b) - b - t a -
 b

instance RFoldable Data.Set.Set where
rfold = Data.Set.fold

 A similar class for types of kind * is also straightforward:

class Reduce t where
type Elem t
reduce :: (Elem t - r - r) - r - t - r

instance Reduce Data.ByteString.ByteString where
type Elem Data.ByteString.ByteString = Word8
reduce = Data.ByteString.foldr

 Both seem to work as I'd expect. Am I missing something? Foldable is
 pretty trivial--perhaps it was Traversable that you found problematic?


This certainly does seem to work just fine in ghc-6.12, but not 6.10.4.  I
wonder if that was the source of my problems last time.

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


Re: [Haskell-cafe] Restricted type classes

2010-09-05 Thread John Lato
On Sat, Sep 4, 2010 at 12:34 PM, David Menendez d...@zednenem.com wrote:


 On Fri, Sep 3, 2010 at 8:23 AM, John Lato jwl...@gmail.com wrote:

  +1 for using the proper constraints, and especially for bringing over
  Pointed (and anything else that applies).

 What's the argument for Pointed? Are there many types which are
 instances of Pointed but not Applicative? Are there many algorithms
 which require Pointed but not Applicative?


Having Pointed is categorically the right thing to do, which is why I argue
for its inclusion.  Also, I think it would be prudent to avoid a situation
with the possibility of turning into a rehash of the
Functor/Applicative/Monad mess.

Are there any good reasons for not including it?  Just because we don't have
a use now doesn't mean it might not be useful in the future.

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


Re: [Haskell-cafe] Restricted type classes

2010-09-05 Thread Ivan Lazar Miljenovic
On 5 September 2010 22:40, John Lato jwl...@gmail.com wrote:

 Having Pointed is categorically the right thing to do, which is why I argue
 for its inclusion.  Also, I think it would be prudent to avoid a situation
 with the possibility of turning into a rehash of the
 Functor/Applicative/Monad mess.

 Are there any good reasons for not including it?  Just because we don't have
 a use now doesn't mean it might not be useful in the future.

Only reason I can think of: it's a pain to make useless class
instances when there is no reason why they can't be combined (since
you never make an instance of one without an instance of the other).

I _can_ think of a data type that could conceivably be an instance of
Pointed but not Applicative: a BloomFilter (though there's not really
any point in having a BloomFilter with only one value that I can see,
but maybe someone can since there's the singletonB function).

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Restricted type classes

2010-09-05 Thread John Lato
On Sun, Sep 5, 2010 at 7:47 AM, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:

 On 5 September 2010 22:40, John Lato jwl...@gmail.com wrote:
 
  Having Pointed is categorically the right thing to do, which is why I
 argue
  for its inclusion.  Also, I think it would be prudent to avoid a
 situation
  with the possibility of turning into a rehash of the
  Functor/Applicative/Monad mess.
 
  Are there any good reasons for not including it?  Just because we don't
 have
  a use now doesn't mean it might not be useful in the future.

 Only reason I can think of: it's a pain to make useless class
 instances when there is no reason why they can't be combined (since
 you never make an instance of one without an instance of the other).


It's a one-time cost, though, so to me at least it's not a big deal.


 I _can_ think of a data type that could conceivably be an instance of
 Pointed but not Applicative: a BloomFilter (though there's not really
 any point in having a BloomFilter with only one value that I can see,
 but maybe someone can since there's the singletonB function).


Thanks for mentioning this.  Bloom filters certainly are an interesting
structure, in many ways.

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


Re: [Haskell-cafe] Restricted type classes

2010-09-05 Thread Sebastian Fischer

Just because we don't have
a use now doesn't mean it might not be useful in the future.


I am suspicious about complicating a design for potential future  
benefits.


However, difference lists provide an example of a type that support  
Pointed more naturally than Applicative: the dlist package [1]  
provides Applicative and Monad instances but only by converting to  
normal lists in between.


Note that even fmap cannot be defined without converting difference  
lists to normal lists in between. The natural interface to difference  
lists would be Pointed (without a Functor superclass) and Monoid.


Sebastian

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


--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


Re: [Haskell-cafe] Restricted type classes

2010-09-05 Thread Ivan Lazar Miljenovic
On 6 September 2010 00:11, Sebastian Fischer
s...@informatik.uni-kiel.de wrote:
 Just because we don't have
 a use now doesn't mean it might not be useful in the future.

 I am suspicious about complicating a design for potential future benefits.

 However, difference lists provide an example of a type that support Pointed
 more naturally than Applicative: the dlist package [1] provides Applicative
 and Monad instances but only by converting to normal lists in between.

 Note that even fmap cannot be defined without converting difference lists to
 normal lists in between. The natural interface to difference lists would be
 Pointed (without a Functor superclass) and Monoid.

Hmmm is there any reason for Functor to be a superclass of
Pointed?  I understand Functor and Pointed being superclasses of
Applicative (which in turn is a superclass of Monad), but can't see
any relation between Pointed and Functor...

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Unnecessarily strict implementations

2010-09-05 Thread Daniel Fischer
On Saturday 04 September 2010 00:21:39, Jan Christiansen wrote:
 On 03.09.2010, at 14:38, Daniel Fischer wrote:
  I can't reproduce that. For me, it leaks also with profiling.

 Have you used optimizations?

Of course. Always do :)

 It disappears if I compile the program with -O2.

Yeah, without optimisations and with profiling, it runs in small memory.
Without optimisations, it also uses less than half the memory it uses with 
optimisations when compiled without profiling (it does still leak, just 
less badly).

___
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 Donn Cave
Quoth Ben Lippmeier b...@ouroborus.net,
...
 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.

Though, I think those sentiments can be appreciated when expressed 
properly.  I mean, I can talk about how nice it is when my programs
work the first time I run them, without necessarily being grandiose
or trying to ram something down anyone's throat.

I guess everyone's different - some Perl programmers might really
respond to a nice Haskell program, if it isn't gratuitously
incomprehensible.  Others may be more interested in the rationale
behind the language's features, and only from there find any motivation
to try to understand the syntax.

Of course it's a good idea to feign interest in their views on
software engineering, etc., but mostly it comes down to your charisma.
Never worked for me, but good luck!

Donn Cave, d...@avvanta.com
___
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 Don Stewart
Gaius:
 My usual rhetoric is that one-off, throwaway scripts never are, and
 not only do they tend to stay around but they take on a life of their
 own. Today's 10-line file munger is tomorrow's thousand-line ETL batch
 job on which the business depends for some crucial data - yet the
 original author is long gone and no-one dares modify in case it
 breaks. So it is just good sense to use sound practices from the very
 beginning. 

I gave a tech talk recently on using Haskell for scripting -- and it is
built on the idea that today's throw away script is tomorrow's key piece
of infrastructure -- so you better get the maintainance and safety story
right:

http://donsbot.wordpress.com/2010/08/17/practical-haskell/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to catch exception within the Get monad (theBinary package)

2010-09-05 Thread Donn Cave
Quoth Dimitry Golubovsky golubov...@gmail.com,

 Is there any way to catch/detect failures inside the Get monad? It is
 not an instance of MonadError, so catchError does not work.

 Ideally, the function would keep decoding as long as it is possible,
 and upon the first failure of the parser, return whatever has been
 decoded.

I believe it can't be done.  (I've seen three responses that seemed
to be proposing some course of action, but ... correct me if I'm wrong,
nothing that would allow you to use Get in Data.Binary this way.)

The key point is the use of `throw', via `error', in Get's `fail'.
`throw' raises an exception that can be caught only in IO, so you
can't catch it inside Get.  So ... while `fail' is a Monad function,
it isn't implemented here in a way you could use, like it is in Maybe
for example.  Nor could it be, I think, which is kind of unfortunate.

Donn Cave, d...@avvanta.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to catch exception within the Get monad (theBinary package)

2010-09-05 Thread Don Stewart
donn:
 Quoth Dimitry Golubovsky golubov...@gmail.com,
 
  Is there any way to catch/detect failures inside the Get monad? It is
  not an instance of MonadError, so catchError does not work.
 
  Ideally, the function would keep decoding as long as it is possible,
  and upon the first failure of the parser, return whatever has been
  decoded.
 
 I believe it can't be done.  (I've seen three responses that seemed
 to be proposing some course of action, but ... correct me if I'm wrong,
 nothing that would allow you to use Get in Data.Binary this way.)
 
 The key point is the use of `throw', via `error', in Get's `fail'.
 `throw' raises an exception that can be caught only in IO, so you
 can't catch it inside Get.  So ... while `fail' is a Monad function,
 it isn't implemented here in a way you could use, like it is in Maybe
 for example.  Nor could it be, I think, which is kind of unfortunate.

For strict, checked binary parsing, use the cereal package. For lazy
binary parsing with async errors, use binary.

They're the main two points in the design space. The other is to tag the
lazy stream, and insert failure tags in the structure.

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


Re: [Haskell-cafe] Restricted type classes

2010-09-05 Thread David Menendez
On Sun, Sep 5, 2010 at 8:40 AM, John Lato jwl...@gmail.com wrote:


 On Sat, Sep 4, 2010 at 12:34 PM, David Menendez d...@zednenem.com wrote:

 On Fri, Sep 3, 2010 at 8:23 AM, John Lato jwl...@gmail.com wrote:

  +1 for using the proper constraints, and especially for bringing over
  Pointed (and anything else that applies).

 What's the argument for Pointed? Are there many types which are
 instances of Pointed but not Applicative? Are there many algorithms
 which require Pointed but not Applicative?

 Having Pointed is categorically the right thing to do, which is why I argue
 for its inclusion.

Why is it categorically the right thing to do?

When Conor McBride was promoting the use of Applicative (then called
Idiom), he provided several instances and algorithms showing that it
was a useful generalization of Monad, and it still took several years
and a few papers[1] before Applicative found its way into the standard
library.

In other words, we didn't add Applicative and then discover
Traversable later. Traversable was a big part of the argument for why
Applicative is useful.

  [1] Idioms: applicative programming with effects
  http://www.cs.nott.ac.uk/~ctm/Idiom.pdf

 Also, I think it would be prudent to avoid a situation
 with the possibility of turning into a rehash of the
 Functor/Applicative/Monad mess.

Granted, but let's not rush blindly in the opposite direction.

 Are there any good reasons for not including it?  Just because we don't have
 a use now doesn't mean it might not be useful in the future.

This is an argument for putting every member of the container API into
its own independent class. Why make things more complicated for little
or no benefit?

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Restricted type classes

2010-09-05 Thread David Menendez
On Sun, Sep 5, 2010 at 8:47 AM, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 I _can_ think of a data type that could conceivably be an instance of
 Pointed but not Applicative: a BloomFilter (though there's not really
 any point in having a BloomFilter with only one value that I can see,
 but maybe someone can since there's the singletonB function).

Do Bloom filters have a Functor instance?

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to catch exception within the Get monad (theBinary package)

2010-09-05 Thread Alexey Khudyakov

On 05.09.2010 22:02, Don Stewart wrote:

For strict, checked binary parsing, use the cereal package. For lazy
binary parsing with async errors, use binary.

Unfortunately cereal is too slow. I got ~5x slowdown with cereal and had 
to patch binary in order to incorporated error handling (essentially 
same as in cereal but simpler).



They're the main two points in the design space. The other is to tag the
lazy stream, and insert failure tags in the structure.

It won't help againist not enough input errors. Sometimes fragments of 
data I process are damaged they are too short, some bits are flipped 
etc. There is no way to guard againist beforementioned errors but to 
constantly check that there is enough data in stream. Also error 
handling is very useful in signalling that data is malformed. It's 
possible to use cereal but it's too slow and it's inconvenient to have 
both Binary and Serialize instances.


Also beginnig from 0.5.0.2 Get monad is strict and consume all required 
input at once. And therefore isn't suitable for lazy parsing unless 
lazyness is introduced manually.

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


[Haskell-cafe] ANNOUNCE: darcs 2.5 beta 5

2010-09-05 Thread Reinier Lamers
The darcs team would like to announce the immediate availability of darcs 2.5
beta 5 (also known as darcs 2.4.98.5 due to Cabal restrictions). Important 
changes since darcs 2.4.4 are:

   * trackdown can now do binary search with the --bisect option
   * darcs always stores patch metadata encoded with UTF-8
   * diff now supports the --index option
   * amend-record now supports the --ask-deps option
   * apply now supports the --match option
   * amend-record has a new --keep-date option
   * inventory-changing commands (like record and pull) now operate in
 constant time with respect to the number of patches in the repository
   * the push, pull, send and fetch commands no longer set the default
 repository by default
   * the --edit-description option is now on by default for the send command

Changes since the last beta release are:
   * document that GHC 6.10 is required to build darcs 2.5
   * the --index flag is now disabled for amend-record because it was broken
   * clean up documentation for trackdown
   * no longer require a specific version of the hashed-storage package

If you have installed the Haskell Platform or cabal-install, you can install
this beta release by doing:

  $ cabal update
  $ cabal install darcs-beta

Alternatively, you can download the tarball from 
http://darcs.net/releases/darcs-2.4.98.5.tar.gz and build it by hand as 
explained in the README file.

Kind Regards,
the darcs release manager,
Reinier Lamers  


signature.asc
Description: This is a digitally signed message part.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to catch exception within the Get monad (the Binary package)

2010-09-05 Thread Victor Gorokhov
 If however something goes wrong, and prs fails, the whole function
 fails (error is thrown). Since [a] (result of decoding) is a lazy
 list, actual exception may be thrown at any moment the list is being
 processed, and exception handler may not be properly set.

 True - return (reverse a)
 False - many' (s:a)
Lazy lists are built in left to right order, but this one is right to left.


 Is there any way to catch/detect failures inside the Get monad?
lookAhead, lookAheadM, etc
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] variable definition according to input

2010-09-05 Thread Maria Merit
Hello,

Is it possible to define variable names according to input data? For
instance:

input = I k = Int k
input = I m= Int m
input = S s= String s

Of course, the real application is much more complicated, but the basic
question is the same.

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


Re: [Haskell-cafe] variable definition according to input

2010-09-05 Thread Tobias Brandt
On 5 September 2010 21:04, Maria Merit mariam627...@gmail.com wrote:
 Is it possible to define variable names according to input data? For
 instance:

You can do arbitrary IO in TemplateHaskell. So, theoretically yes, you
can define variables depending on input. But it has to be input during
compilation/interpretation.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] variable definition according to input

2010-09-05 Thread Henning Thielemann


On Sun, 5 Sep 2010, Maria Merit wrote:


Hello,
 
Is it possible to define variable names according to input data? For instance:
 
input = I k    = Int k
input = I m= Int m
input = S s    = String s


No this is not possible. However you can use
 Data.Map String Object
with
 data Object = Int Int | String String
in order to manage a set of variables, that is their names and their 
values.___
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 Andrew Coppin

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


Rather than how can I convince them to use Haskell for everything?, 
how about just convincing them to use it on a case-by-case basis. It's 
plausible there are scenarios where Haskell is *not* the best thing to 
use. And if you just tirelessly evangelize Haskell, them one has to 
wonder who's the bigot. ;-)


(That said, I really hate Perl...)

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


Re: [Haskell-cafe] Unnecessarily strict implementations

2010-09-05 Thread Henning Thielemann
Daniel Fischer schrieb:

 Yes. Ordinarily, lines in text files aren't longer than a few hundred 
 characters, leaking those, who cares?

I got several space leaks of this kind in the past. They are very
annoying. They are especially annoying if input comes from the outside
world, where people can attack them to crash your program because of
memory exhaustion.

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


Re: [Haskell-cafe] Re: base-3 -gt; base-4

2010-09-05 Thread Bertram Felgenhauer
Johannes Waldmann wrote:
 Ivan Lazar Miljenovic ivan.miljenovic at gmail.com writes:
 
  ... the only thing that changed of significance was the
  exception handling: Control.Exception now uses extensible exceptions

base-4 also introduced the Control.Category.Category class and
restructured Control.Arrow to use that.

 I'm pretty sure ghc-6.12.3 gives warnings this will not work with base-4
 in some more places. I was hoping there is a comprehensive list somewhere.

There's

  http://www.haskell.org/haskellwiki/Upgrading_packages

but it's not up-to-date, probably because updating to ghc-6.12
was comparatively painless.

And of course there are the ghc-6.10.1 release notes which also
cover the changes in base-4:

  http://www.haskell.org/ghc/docs/6.10.1/html/users_guide/release-6-10-1.html

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


[Haskell-cafe] Ord instances (Was: Unnecessarily strict implementations)

2010-09-05 Thread Henning Thielemann
Neil Brown schrieb:
 On 03/09/10 11:11, Henning Thielemann wrote:

 E.g. I wanted to have a Set of Gaussian (complex) integers, but I did
 not want to define an Ord instance for them, because writing
   a  (b :: Gaussian)
 is a bug with high probability.
 
 Isn't this what newtype is good for?  Instead of declaring Ord Gaussian
 to get Set Gaussian and risking the bug you describe, create newtype
 GaussianInSet = G Gaussian, declare Ord GaussianInSet and use Set
 GaussianInSet.

If I use a newtype then I need to lift the numeric operations to that
newtype, and then chances are great that I use () with wrong
expectations on the newtyped Gaussians.


My concrete application was an implementation of partial fractions,
where I used a Map from a root and its multiplicity in the denominator
to the numerator. E.g.

(3x+1)/(x+4)^2 + 5/(x-7)

is represented by

{(4,2) - polynomial [1,3], (-7,1) - polynomial [5]}

In order to support complex numbers (in this case not only Gaussian
integers) and not forcing an Ord instance, I introduced a new type
class, like ArbitraryOrdered, used a newtype to map this class to Ord
and used this for the Map that represents the partial fraction.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Unnecessarily strict implementations

2010-09-05 Thread Daniel Fischer
On Sunday 05 September 2010 21:52:44, Henning Thielemann wrote:
 Daniel Fischer schrieb:
  Yes. Ordinarily, lines in text files aren't longer than a few hundred
  characters, leaking those, who cares?

 I got several space leaks of this kind in the past. They are very
 annoying. They are especially annoying if input comes from the outside
 world, where people can attack them to crash your program because of
 memory exhaustion.

That would likely be the case of long lines, wouldn't it?
I have trouble imagining a scenario where `lines' holding on to a few 
hundred characters which could already be released causes a noticeable 
space leak, let alone memory exhaustion.
If you have a case where leaking a few KB creates a serious problem, I'd 
like to learn about it.

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


[Haskell-cafe] Proposal: Form a haskell.org committee

2010-09-05 Thread Ian Lynagh

Dear Haskellers,

In recent years, haskell.org has started to receive assets, e.g. money
from Google Summer Of Code, donations for Hackathons, and a Sparc
machine for use in GHC development. We have also started spending this
money: on the community server, on a server to take over hosting
haskell.org itself, and on the haskell.org domain name. There is also
interest in running fundraising drives for specific things such as
Hackathon sponsorship and hosting fees.

However, it is not currently clear who is responsible for determining
what the haskell.org money should be spent on, or what are and are not
acceptable uses of the domain name and hardware.

To fix this problem, we propose that we create a haskell.org
committee, which is responsible for answering these sorts of questions,
although for some questions they may choose to poll the community at
large if they think appropriate.

We suggest that the committee be composed of 5 representatives from the
community, with committee members standing down after at most 3 years.
Each year the committee will appoint one of their members to be the chair.

As membership of the Haskell community is not well-defined, and voting
would potentially be open to abuse if anyone were able to vote, we
propose that the committee should choose their replacements from open
nominations.

Unfortunately, this gives us a bootstrapping problem, so we suggest that
the initial committee be chosen from open nominations by some of the
people who currently de-facto end up making the decisions currently:
Duncan Coutts, Isaac Jones, Ian Lynagh, Don Stewart and Malcolm Wallace.
These 5 would still be elligible to nominate themselves. Two of the
initial members will stand down after one year, and two after two years,
in order to bootstrap rolling membership turnover.


We would love to hear feedback from you about this proposal,
so that we can see whether the proposal, or something similar,
has consensus amongst the community!


A related issue is that haskell.org does not currently exist as a legal
entity. We also hope to solve that problem, but we are still gathering
information so that the community can make an informed decision, so I
won't say more about that for now.


Thanks
Ian

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


[Haskell-cafe] Graphics.Drawing

2010-09-05 Thread han
I think there should be Graphics.Drawing (along with Graphics.Rendering) and
many graphics packages should go into it.

So

* Graphics.Rendering will contain more technical and rendering-engine-level
packages (OpenGL, GD, ...)
* while Graphics.Drawing will be for higher-level and user-friendlier
drawing tools. (gloss, graphics-drawingcombinators, hieroglyph, Chart, ...)

Currently most graphics packages are thrown into Graphics.Rendering or even
Graphics. I think we all agree that having a standalone package right under
Graphics is undesirable. There needs to be at least one subcategory. (which
is why I also think Win32 and X11 should be moved from Graphics to
Graphics.UI.)

What do you think?
___
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 Mathew de Detrich
If they are perl programmers, they (should) understand perl very well. I
would suggest to try explaining to them the obvious disadvantages of perl
and the way that Haskell can cover those disadvantages without (much) of a
compromise.

Perl programs are either ones that are ridiculously short/concise, these are
one off scripts that become impossible to maintain (and even to read apart
from whoever coded the script). These perl scripts are typically shorter
then the equivalent Haskell ones. The other type of Perl scripts are the
ones that are fairly concise, and at least more maintainable/scalable. These
perl scripts tend to be the same size as the Haskell ones, except the
Haskell ones are type safe, have error checking and are much more
maintainable/scalable (the slideshow earlier with DonS shows this). Odds are
that the company probably has the latter of Perl scripts, so if you can show
them how Haskell can be just as excise (but not as extremely concise)
however have a lot more other benefits that will help a lot.

Another thing you can say is that Perl is a very extreme language in design
where as Haskell is more general. This means the one thing Perl does, it
does very well (expressing programming problems in the most concise/short
possible way) but it has to sacrifice for it massively in other areas which
end up costing much more in the long run. Most 'real' world problems do not
require that amount of brevity, considering the massive cost that Perl
brings for such a thing.

Also show them quickcheck as well

On Sun, Sep 5, 2010 at 2:38 AM, Michael Litchard mich...@schmong.orgwrote:

 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.
 ___
 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] Proposal: Form a haskell.org committee

2010-09-05 Thread Manuel M T Chakravarty
Ian Lynagh:
 To fix this problem, we propose that we create a haskell.org
 committee, which is responsible for answering these sorts of questions,
 although for some questions they may choose to poll the community at
 large if they think appropriate.
[..]
 Unfortunately, this gives us a bootstrapping problem, so we suggest that
 the initial committee be chosen from open nominations by some of the
 people who currently de-facto end up making the decisions currently:
 Duncan Coutts, Isaac Jones, Ian Lynagh, Don Stewart and Malcolm Wallace.
 These 5 would still be elligible to nominate themselves. Two of the
 initial members will stand down after one year, and two after two years,
 in order to bootstrap rolling membership turnover.

Good plan!

Manuel

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


Re: [Haskell-cafe] Restricted type classes

2010-09-05 Thread Ivan Lazar Miljenovic
On 6 September 2010 04:25, David Menendez d...@zednenem.com wrote:
 On Sun, Sep 5, 2010 at 8:47 AM, Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com wrote:
 I _can_ think of a data type that could conceivably be an instance of
 Pointed but not Applicative: a BloomFilter (though there's not really
 any point in having a BloomFilter with only one value that I can see,
 but maybe someone can since there's the singletonB function).

 Do Bloom filters have a Functor instance?

Nope; once something is in the bloom filter you can't change it (you
can't even apply an a - a map if I understand correctly).

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Graphics.Drawing

2010-09-05 Thread Ivan Lazar Miljenovic
On 6 September 2010 10:09, han e...@xtendo.org wrote:
 I think there should be Graphics.Drawing (along with Graphics.Rendering) and
 many graphics packages should go into it.

Why?

 So
 * Graphics.Rendering will contain more technical and rendering-engine-level
 packages (OpenGL, GD, ...)
 * while Graphics.Drawing will be for higher-level and user-friendlier
 drawing tools. (gloss, graphics-drawingcombinators, hieroglyph, Chart, ...)
 Currently most graphics packages are thrown into Graphics.Rendering or even
 Graphics. I think we all agree that having a standalone package right under
 Graphics is undesirable.

Why is it undesirable?  Henning Thielmann's gnuplot package for
example uses Graphics.Gnuplot.*.  Whilst we could make that
Graphics.Plotting.Gnuplot.*, the module names are getting a little
unwieldy then.

 There needs to be at least one subcategory. (which
 is why I also think Win32 and X11 should be moved from Graphics to
 Graphics.UI.)
 What do you think?

I fail to see a reason for this (well, I can see why it might be
desirable from an hierarchical point of view, but not how it will help
from a usage point of view since we don't really look for packages
based upon the module hierarchy but rather on package name,
descriptions and categories on Hackage).

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: Form a haskell.org committee

2010-09-05 Thread Jason Dagit
On Sun, Sep 5, 2010 at 3:40 PM, Ian Lynagh ig...@earth.li wrote:

 Dear Haskellers,

 In recent years, haskell.org has started to receive assets, e.g. money
 from Google Summer Of Code, donations for Hackathons, and a Sparc
 machine for use in GHC development. We have also started spending this
 money: on the community server, on a server to take over hosting
 haskell.org itself, and on the haskell.org domain name. There is also
 interest in running fundraising drives for specific things such as
 Hackathon sponsorship and hosting fees.

 However, it is not currently clear who is responsible for determining
 what the haskell.org money should be spent on, or what are and are not
 acceptable uses of the domain name and hardware.

The darcs project uses the Software Freedom Conservancy as a sort of
legal entity to hold on to funds and also to help in case anyone takes
legal action against darcs or darcs needs to take legal action.

You might consider joining the SFC as haskell.org.  I don't know
enough about the SFC or haskell.org to know if it would be beneficial,
so I'm just sort of throwing it out there as something to investigate.
 You might talk to Eric Kow if you're interested.  I believe he
coordinated the process.

http://conservancy.softwarefreedom.org/

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


[Haskell-cafe] ANNOUNCE: secure-sockets version 1.0

2010-09-05 Thread David Anderson
Hi,

I'm happy to announce the first release of secure-sockets, a library which
aims to simplify the task of communicating securely between two
authenticated peers.


-- What it is


The API mimicks that of Network.Socket, and introduces the additional notion
of peer identity, which is distinct from the endpoint address (host and
port). Connections can only be established between two peers who know and
expect to be communicating with each other.

Transport security is implicitly taken care of: an established
Network.Secure.Connection implies that each end of the connection
successfully authenticated to the other, and that they have setup strong
encryption for your data.


-- What it isn't


The library leans towards the zero configuration end of the spectrum, and
basically Just Works. This means that if you know exactly what you want and
need for the cipher, authentication algorithm, key type and length, key
exchange protocol, HMAC algorithm, rekeying intervals, random number
source... Then secure-sockets is not for you.

If on the other hand you just want to replace your current cleartext
cipher and faith-based authentication code with something that gives you
a good chance of being secure (see caveats in docs), without diving into the
rich madness that is full blown SSL, then you might want to take a look.

This library assumes that both ends of a connection are using it. The goal
of secure-sockets is not to allow you to connect to any SSL-enabled server,
or to speak a particular standard flavor of authentication protocol.
Internally, secure-sockets uses SSL to achieve its goals, so you might get
lucky if you do it just right, but that is an implementation detail. The
library is designed to help you easily secure communications between two
programs whose implementation you control, not between you and anything out
there.


-- Links


Homepage: http://secure-hs.googlecode.com/

Hackage page: http://hackage.haskell.org/package/secure-sockets

Bug tracker: http://code.google.com/p/secure-hs/issues/list

Code repository: https://secure-hs.googlecode.com/hg


-- Thanks


I'd like to thank my employer, Google. Not only did they not get mad at the
idea that I might want to hack on Haskell during working hours (as my 20%
project), they also made it very painless for me to open source this code
when the time came.


-- Questions?


Questions, comments, suggestions and patches can be filed in the issue
tracker, emailed directly to me, or thrown out on haskell-cafe.

Hope you find this code useful!
- Dave
___
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 Alexander Solla


On Sep 5, 2010, at 7:46 PM, Mathew de Detrich wrote:

Another thing you can say is that Perl is a very extreme language in  
design where as Haskell is more general. This means the one thing  
Perl does, it does very well (expressing programming problems in the  
most concise/short possible way) but it has to sacrifice for it  
massively in other areas which end up costing much more in the long  
run. Most 'real' world problems do not require that amount of  
brevity, considering the massive cost that Perl brings for such a  
thing.


That doesn't sound right to me.  Perl's biggest weaknesses are  
traditionally:  (i) the syntax:  but those $'s and @'s are actually  
type annotations;  and (ii) There's More Then One Way to Do It:  the  
existence of multiple approaches to solving a problem, instead of an  
official obvious choice.  This means that every programmer on the  
team either has to KNOW all the possible ways to solve a problem with  
Perl, or the programming team has to CHOOSE one and make it policy  
-- effectively picking out the nicest bits and sticking to that sub- 
language.


Depending on your point of view, Haskell does not compare particularly  
favorably with respect to TMTOWTDI.  The whole Control.* hierarchy  
is the construction of custom control structures.  That's the whole  
point of glue languages.  You write custom control structures to  
support the chosen normal forms for expressing data and computations.

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