[Haskell-cafe] How to determine if a FilePath is a directory name or regular file?

2009-06-22 Thread Colin Paul Adams
I've been hoogling like bad to try to determine if a function like
this exists.

getDirectoryContents returns sub-directories as well as file names. I
want only the latter, so I'm looking for a suitable filter.
-- 
Colin Adams
Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to determine if a FilePath is a directory name or regular file?

2009-06-22 Thread Judah Jacobson
On Sun, Jun 21, 2009 at 11:12 PM, Colin Paul
Adamsco...@colina.demon.co.uk wrote:
 I've been hoogling like bad to try to determine if a function like
 this exists.

 getDirectoryContents returns sub-directories as well as file names. I
 want only the latter, so I'm looking for a suitable filter.

Use System.Directory.doesDirectoryExist/doesFileExist.

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


Re: [Haskell-cafe] How to determine if a FilePath is a directory name or regular file?

2009-06-22 Thread Erik de Castro Lopo
Colin Paul Adams wrote:

 I've been hoogling like bad to try to determine if a function like
 this exists.
 
 getDirectoryContents returns sub-directories as well as file names. I
 want only the latter, so I'm looking for a suitable filter.

The first example in this chapter of Real World Haskell uses the
doesDirectoryExist function :


http://book.realworldhaskell.org/read/io-case-study-a-library-for-searching-the-filesystem.html

HTH,
Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to determine if a FilePath is a directory name or regular file?

2009-06-22 Thread Bulat Ziganshin
Hello Colin,

Monday, June 22, 2009, 10:12:57 AM, you wrote:

 I've been hoogling like bad to try to determine if a function like
 this exists.

 getDirectoryContents returns sub-directories as well as file names. I
 want only the latter, so I'm looking for a suitable filter.

isdir - withFileStatus isdir? filename isDirectory


module System.Directory
  withFileStatus :: String - FilePath - (Ptr CStat - IO a) - IO a
  isDirectory :: Ptr CStat - IO Bool


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

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


Re: [Haskell-cafe] How to determine if a FilePath is a directory name or regular file?

2009-06-22 Thread Colin Paul Adams
 Judah == Judah Jacobson judah.jacob...@gmail.com writes:

Judah On Sun, Jun 21, 2009 at 11:12 PM, Colin Paul
Judah Adamsco...@colina.demon.co.uk wrote:
 I've been hoogling like bad to try to determine if a function
 like this exists.
 
 getDirectoryContents returns sub-directories as well as file
 names. I want only the latter, so I'm looking for a suitable
 filter.

Judah Use System.Directory.doesDirectoryExist/doesFileExist.

Thanks.

it seems it's time i went to the optician again.
-- 
Colin Adams
Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cross platform getProcessID

2009-06-22 Thread John Lask

The short anser is...you need to make a ffi call to getCurrentProcessId

unfortunately there is no binding to this function in System.Win32.Process
which is the natural home for it.

Perhaps you could submit a patch for Win32 package, once you have created 
the binding the signature for the function is quite simple, so there should 
be no problem with the ffi call


DWORD GetCurrentProcessId(VOID)


- Original Message - 
From: John Van Enk vane...@gmail.com

To: Haskell Cafe haskell-cafe@haskell.org
Sent: Monday, June 22, 2009 1:43 PM
Subject: [Haskell-cafe] Cross platform getProcessID



In the unix package, we have getProcessID. Is there a corresponding
method for finding the process ID in Windows?

/jve
___
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 to determine if a FilePath is a directory name or regular file?

2009-06-22 Thread Deniz Dogan
2009/6/22 Colin Paul Adams co...@colina.demon.co.uk:
 Judah == Judah Jacobson judah.jacob...@gmail.com writes:

    Judah On Sun, Jun 21, 2009 at 11:12 PM, Colin Paul
    Judah Adamsco...@colina.demon.co.uk wrote:
     I've been hoogling like bad to try to determine if a function
     like this exists.
    
     getDirectoryContents returns sub-directories as well as file
     names. I want only the latter, so I'm looking for a suitable
     filter.

    Judah Use System.Directory.doesDirectoryExist/doesFileExist.

 Thanks.

 it seems it's time i went to the optician again.

I'm not surprised that anyone would make the mistake. I think that the
two functions should be named isDirectory and isFile, but it seems
that isDirectory was already taken by another function in
System.Directory, which is quite unfortunate. does goes against the
intuition one gets from pretty much everything else in Haskell, where
is seems to be the convention. In fact, Hoogle only knows about
three functions which start with does.

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


Re: [Haskell-cafe] Suggestion for Network.Socket in regards to PortNumber

2009-06-22 Thread Johan Tibell
On Mon, Jun 22, 2009 at 1:22 AM, Thomas DuBuisson 
thomas.dubuis...@gmail.com wrote:

 I'm in favor of the entire Network library being reworked with an
 improved API that is higher level and type-safe instead of a direct
 translation/FFI of Berkeley sockets.   I also would like the Network
 package to export Data instances for headers while taking advantage of
 pretty, prettyclass, and parsec.  I started such work with
 network-data but never really got off the ground with it.


I've given this some thought. There are a few different things that would be
nice to have in a new API:

* Use a binary type (e.g. ByteString) instead of Strings. (see
network-bytestring)
* Encoding more things in the type system, in particular the socket state
(opened, closed, connected, etc). I would like to avoid a very heavyweight
encoding though.
* Allow folds over the input i.e. foldSocket :: (a - ByteString - a) - a
- Socket - IO a

I'm all for having a higher level API but I would like to keep the Berkeley
socket interface. The reason is the following: If we provide a higher level
API that does not expose the whole underlying OS API there will be some
users who can't use the library and will have to resort to writing their own
bindings. I've seen this problem in a few other libraries. The reasoning
often goes something like this: This interface will cover 90% (or 95%) of
all the use cases so its sufficient for most people. The problem with this
kind of reasoning is that I have to write my own OS bindings for every ten
libraries I use (on average).

Perhaps we should start a wiki page where we can take some notes on things
that could be improved in the style of Haskell' discussions (i.e. outlines
of the problem together possible solutions together with their trade-offs.
Python's PEPs are a good model here)?

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


Re: [Haskell-cafe] ANNOUNCE fmlist

2009-06-22 Thread Sebastian Fischer


On Jun 19, 2009, at 7:12 PM, Sjoerd Visscher wrote:

I see you did performance tests. How does your current version  
compare to f.e. one based on DiffLists?


The current versions (0.4) of bfs and idfs based on FMList (0.5) use  
the same amount of memory and are about 10-15% slower than  
corresponding versions of breadth-first search and iterative deepening  
depth-first search based on CPS and DiffList when enumerating  
pythagorean triples without an upper bound (I didn't check other  
examples).


I wonder though, aren't you worried that updated versions of FMList  
might use the monoid laws to rewrite certains bits, and your code  
would break? Essentially you are using FMLists as a tree structure,  
which isn't possible when you abide by the monoid laws.


Manipulating w.r.t. monoid laws may change the order in which results  
are computed by bfs and idfs. However, I won't consider this breaking  
the code. The important property of bfs and idfs is that all results  
are eventually computed and I happily abstract from their order when  
enumerating results of non-deterministic computations. Other people  
may disagree though, so I should mention something about it in the docs.


If rewriting FMList w.r.t. monoid laws would break the completeness of  
the strategies I would be concerned. But currently I have the  
impression that parametricity ensures that I will always be able to  
convert an FMList into the (implicit) tree structures that I use for  
complete search.


I think you should be able to do the same thing in as many lines,  
using f.e. the ChoiceT type from MonadLib, where bfs and idfsBy are  
variations on runChoiceT.


I think so too. With a monad instance for a tree structure one can  
implement both strategies as well. However, the continuation-based  
implementation of monadic bind is more efficient when nested left  
associatively [1]. One could regain the asymptotic improvement of  
monadic bind by wrapping ChoiceT under ContT but that seems inelegant  
as it uses more monads than necessary.


By using a free representation of a pointed monoid one could use  
fmlists to generate the tree structure of a search space:


  data PMonoid a = Point a | Empty | Append (PMonoid a) (PMonoid a)

  instance Monoid PMonoid where
mempty  = Empty
mappend = Append

  treeSearch :: FMList a - PMonoid a
  treeSearch l = unFM l Point

Just like this monoid instance violates the monoid laws, the monad  
ChoiceT m violates corresponding laws of MonadPlus:


mzero `mplus` return 42
  = Choice NoAnswer (Answer 42)
 /= Answer 42
  = return 42

a `mplus` (b `mplus` c)
  = Choice a (Choice b c)
 /= Choice (Choice a b) c
  = (a `mplus` b) `mplus` c

So also w.r.t. laws there is no advantage in using a tree monad  
explicitly. Manipulating a non-deterministic computation w.r.t. these  
laws will change the order of computed results.


Mike Spivey gets by without breaking these laws by introducing an  
additional combinator 'wrap' to increase the depth of the search [2].  
However, this additional combinator prevents the use of (only)  
MonadPlus and whether all results of a non-deterministic computation  
are eventually enumerated depends on appropriate use of 'wrap'.


Cheers,
Sebastian


[1]: J. Voigtländer, Asymptotic Improvement of Computations over Free  
Monads

  http://wwwtcs.inf.tu-dresden.de/~voigt/mpc08.pdf

[2]: Michael Spivey, Algebras for Combinatorial Search
  http://spivey.oriel.ox.ac.uk/mike/search-jfp.pdf

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





PGP.sig
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] Optimizing spelling correction program

2009-06-22 Thread Ketil Malde
Kamil Dworakowski ka...@dworakowski.name writes:

 Right... Python uses hashtables while here I have a tree with log n
 access time. I did not want to use the Data.HashTable, it would
 pervade my program with IO. The alternative is an ideal hashmap that never
 gets changed. This program creates a dictionary at start which then is only
 being used to read from: an ideal application for the Data.PerfectHash
 by Mark Wotton available on Hackage [3].

If you are considering alternative data structures, you might want to
look at tries or Bloom filters, both have O(n) lookup, both have
Haskell implementations.  The latter is probably faster but
probabilistic (i.e. it will occasionally fail to detect a
misspelling - which you can of course check against a real
dictionary).

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] coding standard question

2009-06-22 Thread Jules Bean

Magnus Therning wrote:
Also from experience, I get a good feeling about software that compiles 
without warnings.  It suggests the author cares and is indicative of 
some level of quality.


In contrast, I find almost all the GHC warnings to be useless, and 
therefore turn them off. I don't find they have a significant 
correlation with code quality.


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


Re: [Haskell-cafe] coding standard question

2009-06-22 Thread Miguel Mitrofanov

I so don't want to be the one supporting your code...

Jules Bean wrote on 22.06.2009 13:00:

Magnus Therning wrote:
Also from experience, I get a good feeling about software that 
compiles without warnings.  It suggests the author cares and is 
indicative of some level of quality.


In contrast, I find almost all the GHC warnings to be useless, and 
therefore turn them off. I don't find they have a significant 
correlation with code quality.


YMMV :)
___
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] Optimizing spelling correction program

2009-06-22 Thread Eugene Kirpichov
Hey, you're using String I/O!

nWORDS - fmap (train . map B.pack . words) (readFile big.txt)

This should be

WORDS - fmap (train . B.words) (B.readFile big.txt)

By the way, which exact file do you use as a misspellings file? The
corpus linked to at Norvig's page has many.
And do you have a driver program that I could run and obtain your timings?

2009/6/22 Kamil Dworakowski ka...@dworakowski.name:
 Hi all,

 I want to learn how to optimize Haskell code on the Norvig's spelling
 correction program [1]. Peter Norvig has written the program in
 Python,
 quite a literate translation to Haskell (thanks to Grzegorz Chrupala)
 [2] was also available.

 Both versions are about 23 LOCs, and Haskell version is four times
 slower, 2m25s versus 36s. All the numbers I give come from running the
 program on a list of 806 misspellings, Haskell version compiled with -
 O2
 and -fforce-recomp flags.

 I started with trial and error approach. Just preventing a repetitive
 call to keysSet brought the running time down to 1m48s. I also
 restructured the edits1 function and dropped all uses of sets, which
 haven't been pulling their own weight. This brought the running time
 down to 55s. Not quite there yet but close.

 Reading the Profiling chapter in the RWH book enabled me to do some
 more
 informed optimizing. At this point the GC time was about 2% of the
 overall runnig time, Grzegorz has done a good job of using strict
 versions of functions where necessary. The timing per expression
 however
 showed something useful, 70% of the time was being spent around
 determining membership in the known words dictionary (Data.Map). There
 are about 30 000 items in the dictionary.

 Right... Python uses hashtables while here I have a tree with log n
 access time. I did not want to use the Data.HashTable, it would
 pervade
 my program with IO. The alternative is an ideal hashmap that never
 gets
 changed. This program creates a dictionary at start which then is only
 being used to read from: an ideal application for the Data.PerfectHash
 by Mark Wotton available on Hackage [3].

 The PerfectHash is a dictionary keyed by ByteStrings, so I had to
 migrate the program to use these instead of Strings. Sadly it
 increased
 the running time to 59s. Adding PerfectHash brought the running time
 down to 39s. I have done some code restructuring with the view to
 publishing it, which brought the running time up to 45s. The code is
 available on patch-tag [4] for anyone to scrutinize and hopefully
 point
 out mistakes (it uses big.txt and misspellings file which are linked
 to
 from Norvig's page [1]).

 At this point [5] I don't know how to proceed. The program is still
 slower than Python. The -ddump-simpl dump does not give me any clues,
 there is too much of it and I don't understand most of it. The GC time
 is about 10% of the total, and according to the profiler almost half
 the
 time is spent in the member function, and almost all the rest in
 edits1.
 Shouldn't it run much faster than the interpreted Python?

 Frankly, I am not impressed with the PerfectHash performance; It looks
 as if it is only two times faster than Data.Map. Is this because of
 the
 number of elements?

 1. http://www.norvig.com/spell-correct.html
 2. 
 http://pitekus.blogspot.com/2007/04/norvigs-spelling-corrector-in-haskell.html
 3. http://hackage.haskell.org/package/PerfectHash
 4. http://patch-tag.com/r/spellcorrect/
 5.
 http://patch-tag.com/r/spellcorrect/snapshot/hash/20090621192727-a99e5-fed48a7ccf07b79c572fddb0304648fe80d39904/content/pretty/SpellingCorrection.hs
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] coding standard question

2009-06-22 Thread Erik de Castro Lopo
Magnus Therning wrote:

 Speaking from experience it's good to fix all warnings,

This was may experience from the C programming language.

 since otherwise there 
 will be enough of them to cause a few terminal pages to scroll by when you 
 compile and then there's a real danger of not noticing real errors.  I'd pass 
 '-Wall -Werror' to ghc to force myself to do this :-)

I usually add  -fwarn-tabs to -Wall -Werror.

Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] coding standard question

2009-06-22 Thread Jules Bean

Miguel Mitrofanov wrote:

I so don't want to be the one supporting your code...


Well, that's lucky. Because you aren't.

However, that's an easy arrow to fling. I say I don't find warnings 
useful so you suggest my code is unmaintainable. Is that based on any 
knowledge of my code, or the GHC warnings?


I've been using GHC for years and my honest opinion is that the warnings 
very rarely flag an actual maintainability problem in the code I write, 
and very frequently annoying highlight something I knew I was doing, and 
did quite deliberately - most often inexhaustive patterns or shadowing.


Maybe there are mistakes which you can make which the warnings usefully 
highlight, and maybe I just never make that kind of mistake.


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


[Haskell-cafe] rewrite rules

2009-06-22 Thread Sjoerd Visscher

Hi all,

I have a rewrite rule as follows:

{-# RULES
transform/transform forall (f::forall m. Monoid m = (a - m) - (b - 
 m))
 (g::forall m. Monoid m = (b - m) - (c  
- m))
 (l::FMList c). transform f (transform g  
l) = transform (g.f) l

  #-}

It fires on this code:

  print $ transform (. (*2)) (transform (. (+1)) (upto 10))

But it doesn't fire on this code:

  print $ map (*2) (map (+1) (upto 10)))

with

  map g x = transform (. g) x

and with or without {-# INLINE map #-}.

What am I doing wrong?

--
Sjoerd Visscher
sjo...@w3future.com



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


Re: [Haskell-cafe] coding standard question

2009-06-22 Thread Miguel Mitrofanov



Jules Bean wrote on 22.06.2009 13:09:

Miguel Mitrofanov wrote:

I so don't want to be the one supporting your code...


Well, that's lucky. Because you aren't.


Exactly.



However, that's an easy arrow to fling. I say I don't find warnings 
useful so you suggest my code is unmaintainable. Is that based on any 
knowledge of my code, or the GHC warnings?


First of all, I never said that your code is unmaintainable. And, if it's not, i still don't want to maintain it, since we clearly have very 
different approaches to programming - which is, actually, a good thing (except that mine is obviously good and yours is obviously bad).


I've been using GHC for years and my honest opinion is that the warnings 
very rarely flag an actual maintainability problem in the code I write, 
and very frequently annoying highlight something I knew I was doing, and 
did quite deliberately - most often inexhaustive patterns or shadowing.


Maintainability is (mostly) NOT about how good are YOU in supporting your own 
code.

Maybe there are mistakes which you can make which the warnings usefully 
highlight, and maybe I just never make that kind of mistake.


It's a kind of mistakes that I can make maintaining your code, that's all. That 
doesn't imply that it's your fault (except that it certainly is).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Optimizing spelling correction program

2009-06-22 Thread Ketil Malde
Johan Tibell johan.tib...@gmail.com writes:

 Typo? Bloom filters have O(1) lookup and tries O(m) lookup where m is the
 number of characters in the string.

Typically you need to examine the (whole) search string in order to
compute the hash function, so I think it is fair to consider them both 
O(m).

(Sorry about the alphabet confusion, I should of course have made it
clear that I referred to search pattern size, not the data size.)

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: [Haskell-cafe] coding standard question

2009-06-22 Thread Malcolm Wallace
Erik de Castro Lopo mle...@mega-nerd.com wrote:

 Vasili I. Galchin wrote:
 
   where/let functions use the
  same name for function parameters as the outer function and hence
  there is a shadow warning from the compiler.
 
 In Haskell there is an easy way around this. Variables can
 be name a, a', a'' and so on. ...
 ... its a good idea to fix these warnings.

I would _strongly_ advise not to do that.  By trying to silence the
spurious warning about shadowing, there is enormous potential to
introduce new bugs that were not there before.

Example:

  f a b = g (a+b) (b-a)
where g a c = a*c

ghc warns that g's parameter a shadows the parameter to f.  So we
introduce a primed identifier to eliminate the warning:

  f a b = g (a+b) (b-a)
where g a' c = a*c

Now, no warnings!  But, oops, this function does not do the same thing.
We forgot to add a prime to all occurrences of a on the right-hand-side.

Particularly in larger examples, it can be remarkably easy to miss an
occurrence of the variable whose name you are refactoring.  The key
point is that in this situation, unlike most refactorings, the compiler
_cannot_ help you find the mistake with useful error messages or
warnings.

When I write code that shadows variable names, it is always deliberate.
In fact, the language's lexical rules encourage shadowing, otherwise why
have scopes at all?  I think bug-introduction by the elimination of
shadowing is much more common than bug-elimination by the same route.

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


Re: [Haskell-cafe] coding standard question

2009-06-22 Thread Neil Brown

Jules Bean wrote:
I've been using GHC for years and my honest opinion is that the 
warnings very rarely flag an actual maintainability problem in the 
code I write, and very frequently annoying highlight something I knew 
I was doing, and did quite deliberately - most often inexhaustive 
patterns or shadowing.
I would agree to a certain extent about the warnings.  Name shadowing is 
not really a problem, and it's often hard to avoid shadowing names that 
already exist in an imported module (why shouldn't I have a variable 
named lines?).  It's also usually the case that when I write 
inexhaustive pattern matches, it's because I know that the function (in 
a where clause) cannot be called with the missing pattern.  Type 
defaulting and monomorphism bits may be useful to some, but I only 
usually fix them to get rid of the warning, not because they cause a 
problem.


The ones I find useful are unused imports (handy for tidying up the 
import list), overlapping patterns, missing fields, warnings about tabs 
and a few others.


Of course, you can easily customise which warnings are on and which are 
off, so we can all have different preferences.  It would be nice to be 
able to set some warnings to be errors though, while leaving others as 
warnings, or turned off (don't think GHC can do this?).


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


Re: [Haskell-cafe] Creating a new Haskell mailing list

2009-06-22 Thread Ryan Trinkle
I'm interested in creating a list for iPhone development.  While I also have
an ongoing iPhone build target project, which I will be open-sourcing very
soon, I'd like the list to be about Haskell on iPhone without regard to
whether it has anything to do with my project.


Ryan

On Fri, Jun 19, 2009 at 03:06, Wolfgang Jeltsch
g9ks1...@acme.softbase.orgwrote:

 Am Donnerstag, 18. Juni 2009 16:21 schrieb Henning Thielemann:
  Ryan Trinkle schrieb:
   Hi all,
  
   I'm interested in starting a mailing list on haskell.org
   http://haskell.org.  Who should I talk to about such things?
 
  Is it a mailing list related to a project? Then you may request a
  project on community.haskell.org, then you can start a mailing list at
  yourproj...@project.haskell.org

 See http://community.haskell.org/.

 Best wishes,
 Wolfgang
 ___
 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: Creating a new Haskell mailing list

2009-06-22 Thread Benjamin L . Russell
On Wed, 17 Jun 2009 20:38:54 -0400, Ryan Trinkle ryant5...@gmail.com
wrote:

Hi all,

I'm interested in starting a mailing list on haskell.org.  Who should I talk
to about such things?

One way is to propose the mailing list on the Haskell mailing list
(see the Haskell Info Page at
http://www.haskell.org/mailman/listinfo/haskell and The Haskell
Archives at http://www.haskell.org/pipermail/haskell/), and then move
the discussion, after a few rounds, to this mailing list (the
Haskell-Cafe mailing list).  (Haskell-Beginners was created in this
manner, for example.)

-- Benjamin L. Russell
-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
Furuike ya, kawazu tobikomu mizu no oto. 
-- Matsuo Basho^ 

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


Re: [Haskell-cafe] Optimizing spelling correction program

2009-06-22 Thread Johan Tibell
On Mon, Jun 22, 2009 at 12:05 PM, Ketil Malde ke...@malde.org wrote:

 Johan Tibell johan.tib...@gmail.com writes:

  Typo? Bloom filters have O(1) lookup and tries O(m) lookup where m is the
  number of characters in the string.

 Typically you need to examine the (whole) search string in order to
 compute the hash function, so I think it is fair to consider them both
 O(m).


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


[Haskell-cafe] STM/Data Invariant related Segfault with GHC 6.10.3

2009-06-22 Thread Jan Schaumlöffel
Hello,

I just discovered that programs compiled with GHC 6.10.3 segfault when
accessing a TVar created under certain conditions.  This happens when
the TVar is created and a data invariant is added (using
alwaysSucceeds) in the same atomic block.  The invariant does not
necessarily have to read the TVar in question, a mere
alwaysSucceeds (return ()) is enough.

It looks like by adding the invariant the TVar allocation is not kept
after the block.  The appended code snippets show how to reproduce
this behaviour.  IMHO the first version should work, too.

Is there anything one can do to (reliably) work around this problem?
Is there maybe an underlying problem that causes this?

Regards,
Jan



module Main where
import GHC.Conc

-- this segfaults:
main = do { t - atomically
   (do { t1 - newTVar 0
   ; alwaysSucceeds (readTVar t1)
   ; return t1 })
  ; atomically $ readTVar t }

-- it works if written like this:
main2 = do { t - newTVarIO 0
   ; atomically $ alwaysSucceeds (readTVar t)
   ; atomically $ readTVar t }

-- works also if no invariant is added: 
main3 = do { t - atomically
(do { t1 - newTVar 0
; return t1 })
   ; atomically $ readTVar t }

-- works also if invariant is added later:
main4 = do { t - atomically
(do { t1 - newTVar 0
; return t1 })
   ; atomically $ alwaysSucceeds (readTVar t)
   ; atomically $ readTVar t }

-- 
If you're happy and you know it, syntax error!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] coding standard question

2009-06-22 Thread Johan Tibell
On Mon, Jun 22, 2009 at 12:06 PM, Malcolm Wallace 
malcolm.wall...@cs.york.ac.uk wrote:

 Erik de Castro Lopo mle...@mega-nerd.com mle%2...@mega-nerd.com wrote:

  Vasili I. Galchin wrote:
 
where/let functions use the
   same name for function parameters as the outer function and hence
   there is a shadow warning from the compiler.
 
  In Haskell there is an easy way around this. Variables can
  be name a, a', a'' and so on. ...
  ... its a good idea to fix these warnings.

 I would _strongly_ advise not to do that.  By trying to silence the
 spurious warning about shadowing, there is enormous potential to
 introduce new bugs that were not there before.

 Example:

  f a b = g (a+b) (b-a)
where g a c = a*c

 ghc warns that g's parameter a shadows the parameter to f.  So we
 introduce a primed identifier to eliminate the warning:

  f a b = g (a+b) (b-a)
where g a' c = a*c

 Now, no warnings!  But, oops, this function does not do the same thing.
 We forgot to add a prime to all occurrences of a on the right-hand-side.


Actually there's a warning:

ghci let f a b = g (a+b) (b-a) where g a' c = a*c

interactive:1:34: Warning: Defined but not used: `a''

Cheers,

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


Re: [Haskell-cafe] How to determine if a FilePath is a directory name or regular file?

2009-06-22 Thread Duncan Coutts
On Mon, 2009-06-22 at 08:53 +0200, Deniz Dogan wrote:
 2009/6/22 Colin Paul Adams co...@colina.demon.co.uk:
  Judah == Judah Jacobson judah.jacob...@gmail.com writes:
 
 Judah On Sun, Jun 21, 2009 at 11:12 PM, Colin Paul
 Judah Adamsco...@colina.demon.co.uk wrote:
  I've been hoogling like bad to try to determine if a function
  like this exists.
 
  getDirectoryContents returns sub-directories as well as file
  names. I want only the latter, so I'm looking for a suitable
  filter.
 
 Judah Use System.Directory.doesDirectoryExist/doesFileExist.
 
  Thanks.
 
  it seems it's time i went to the optician again.
 
 I'm not surprised that anyone would make the mistake. I think that the
 two functions should be named isDirectory and isFile, but it seems
 that isDirectory was already taken by another function in
 System.Directory, which is quite unfortunate. does goes against the
 intuition one gets from pretty much everything else in Haskell, where
 is seems to be the convention. In fact, Hoogle only knows about
 three functions which start with does.

One explanation is that isBlah asks is this thing a blah, but we're
not asking that because there is an indirection via the filepath. We're
asking does this filepath refer to a directory not is this filename a
directory. The latter could be a function:

isDirectory :: FileInfo - Bool

along with a hypothetical

getFileInfo :: FilePath - IO FileInfo

Duncan

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


[Haskell-cafe] Re: Creating a new Haskell mailing list

2009-06-22 Thread Benjamin L . Russell
Most likely, if you propose your new mailing list (on the Haskell
mailing list), the discussion will focus on whether it will be likely
to gather enough posts to stay reasonably active.  While the
definition of reasonably active differs depending on the individual,
it is likely to mean somewhere between an average of several posts per
week to one or two per day.  Your proposal will be more likely to pass
if you can demonstrate a reasonably strong demand for active
discussion in the Haskell community.

Alternatively, it is possible to create a Haskell-related mailing list
that is not hosted at haskell.org.  Haskell-Art (see the haskell-art
Info Page at http://lists.lurk.org/mailman/listinfo/haskell-art and
The haskell-art Archives at
http://lists.lurk.org/pipermail/haskell-art/) is one example of such a
list.

You may wish to see the following sites for reference:

haskell.org Mailing Lists
http://haskell.org/mailman/listinfo

Mailing lists - HaskellWiki
http://haskell.org/haskellwiki/Mailing_lists

-- Benjamin L. Russell

On Mon, 22 Jun 2009 07:16:14 -0400, Ryan Trinkle ryant5...@gmail.com
wrote:

I'm interested in creating a list for iPhone development.  While I also have
an ongoing iPhone build target project, which I will be open-sourcing very
soon, I'd like the list to be about Haskell on iPhone without regard to
whether it has anything to do with my project.


Ryan

On Fri, Jun 19, 2009 at 03:06, Wolfgang Jeltsch
g9ks1...@acme.softbase.orgwrote:

 Am Donnerstag, 18. Juni 2009 16:21 schrieb Henning Thielemann:
  Ryan Trinkle schrieb:
   Hi all,
  
   I'm interested in starting a mailing list on haskell.org
   http://haskell.org.  Who should I talk to about such things?
 
  Is it a mailing list related to a project? Then you may request a
  project on community.haskell.org, then you can start a mailing list at
  yourproj...@project.haskell.org

 See http://community.haskell.org/.

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

-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
Furuike ya, kawazu tobikomu mizu no oto. 
-- Matsuo Basho^ 

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


Re: [Haskell-cafe] coding standard question

2009-06-22 Thread Erik de Castro Lopo
Malcolm Wallace wrote:

 When I write code that shadows variable names, it is always deliberate.
 In fact, the language's lexical rules encourage shadowing, otherwise why
 have scopes at all?  I think bug-introduction by the elimination of
 shadowing is much more common than bug-elimination by the same route.

I would almost agree that blindly eliminating shadowing will lead  to 
bugs, but they will be shallow bugs detected almost immediately.

The bugs I am particularly interested in avoiding are the difficult bugs
that seem to be intermittent, that only hit in certain rare situations
and that take ages to find.

I will gladly trade you a hundred of the first for one of the second :-).

Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cross platform getProcessID

2009-06-22 Thread John Van Enk
Hi John,

 The short anser is...you need to make a ffi call to getCurrentProcessId

 unfortunately there is no binding to this function in System.Win32.Process
 which is the natural home for it.

 Perhaps you could submit a patch for Win32 package, once you have created
 the binding the signature for the function is quite simple, so there should
 be no problem with the ffi call

 DWORD GetCurrentProcessId(VOID)


I think I'll do just that. Thanks. :)

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


Re: [Haskell-cafe] Documentation on hackage

2009-06-22 Thread Duncan Coutts
On Mon, 2009-06-15 at 06:49 -0700, Don Stewart wrote:
 si:
  Dear Haskellers,
  
  who needs this kind of documentation?
  
  http://hackage.haskell.org/packages/archive/tfp/0.2/doc/html/Types-Data-Num-Decimal-Literals.html
  
  isn't this a kind of spam?
  
 
 Seems like a good case for the haddock -hide option.

Note that this can be added to the module itself:

{-# OPTIONS_HADDOCK prune #-}

From the user guide[1]:

prune

Omit definitions that have no documentation annotations from the
generated documentation.

hide 

Omit this module from the generated documentation, but
nevertheless propagate definitions and documentation from within
this module to modules that re-export those definitions.


Duncan


[1] http://haskell.org/haddock/doc/html/module-attributes.html

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


Re: [Haskell-cafe] Suggestion for Network.Socket in regards to PortNumber

2009-06-22 Thread Thomas DuBuisson
Johan - glad you chimed in!

I'm all in favor of keeping a low level interface and don't have an
issue with Network.Socket existing,  I additionally really like the
suggestion of moving from the ML to a wiki in the same style as
Haskell'.

I'll port these comments to the wiki if that is whats agreed on and
hold off on other thoughts for now.

* ByteStrings! Absolutely.  The one issue is I feel network packets
should be represented as strict bytestrings and any encode/decode
issues resulting in a 'Left err' via binary-strict or some beefed up
version of that package.

* Avoiding a 'heavy weight' solution for socket state might get ugly
fast with all the 'Either a b' results that we'll need - also a socket
can close at any time so a socket in 'Connected' state might not
actually be connected.  I understand the attraction to a light
solution using existential types but Tim Sheard sketched for me a
reasonable alternative which I invite him to restate here, if he has
the time.

Thomas

On Mon, Jun 22, 2009 at 12:16 AM, Johan Tibelljohan.tib...@gmail.com wrote:
 On Mon, Jun 22, 2009 at 1:22 AM, Thomas DuBuisson
 thomas.dubuis...@gmail.com wrote:

 I'm in favor of the entire Network library being reworked with an
 improved API that is higher level and type-safe instead of a direct
 translation/FFI of Berkeley sockets.   I also would like the Network
 package to export Data instances for headers while taking advantage of
 pretty, prettyclass, and parsec.  I started such work with
 network-data but never really got off the ground with it.

 I've given this some thought. There are a few different things that would be
 nice to have in a new API:

 * Use a binary type (e.g. ByteString) instead of Strings. (see
 network-bytestring)
 * Encoding more things in the type system, in particular the socket state
 (opened, closed, connected, etc). I would like to avoid a very heavyweight
 encoding though.
 * Allow folds over the input i.e. foldSocket :: (a - ByteString - a) - a
 - Socket - IO a

 I'm all for having a higher level API but I would like to keep the Berkeley
 socket interface. The reason is the following: If we provide a higher level
 API that does not expose the whole underlying OS API there will be some
 users who can't use the library and will have to resort to writing their own
 bindings. I've seen this problem in a few other libraries. The reasoning
 often goes something like this: This interface will cover 90% (or 95%) of
 all the use cases so its sufficient for most people. The problem with this
 kind of reasoning is that I have to write my own OS bindings for every ten
 libraries I use (on average).

 Perhaps we should start a wiki page where we can take some notes on things
 that could be improved in the style of Haskell' discussions (i.e. outlines
 of the problem together possible solutions together with their trade-offs.
 Python's PEPs are a good model here)?

 -- Johan



 ___
 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] Suggestion for Network.Socket in regards to PortNumber

2009-06-22 Thread John Van Enk
Moving off list to the Wiki has my vote.

On Mon, Jun 22, 2009 at 7:52 AM, Thomas
DuBuissonthomas.dubuis...@gmail.com wrote:
 Johan - glad you chimed in!

 I'm all in favor of keeping a low level interface and don't have an
 issue with Network.Socket existing,  I additionally really like the
 suggestion of moving from the ML to a wiki in the same style as
 Haskell'.

 I'll port these comments to the wiki if that is whats agreed on and
 hold off on other thoughts for now.

 * ByteStrings! Absolutely.  The one issue is I feel network packets
 should be represented as strict bytestrings and any encode/decode
 issues resulting in a 'Left err' via binary-strict or some beefed up
 version of that package.

 * Avoiding a 'heavy weight' solution for socket state might get ugly
 fast with all the 'Either a b' results that we'll need - also a socket
 can close at any time so a socket in 'Connected' state might not
 actually be connected.  I understand the attraction to a light
 solution using existential types but Tim Sheard sketched for me a
 reasonable alternative which I invite him to restate here, if he has
 the time.

 Thomas

 On Mon, Jun 22, 2009 at 12:16 AM, Johan Tibelljohan.tib...@gmail.com wrote:
 On Mon, Jun 22, 2009 at 1:22 AM, Thomas DuBuisson
 thomas.dubuis...@gmail.com wrote:

 I'm in favor of the entire Network library being reworked with an
 improved API that is higher level and type-safe instead of a direct
 translation/FFI of Berkeley sockets.   I also would like the Network
 package to export Data instances for headers while taking advantage of
 pretty, prettyclass, and parsec.  I started such work with
 network-data but never really got off the ground with it.

 I've given this some thought. There are a few different things that would be
 nice to have in a new API:

 * Use a binary type (e.g. ByteString) instead of Strings. (see
 network-bytestring)
 * Encoding more things in the type system, in particular the socket state
 (opened, closed, connected, etc). I would like to avoid a very heavyweight
 encoding though.
 * Allow folds over the input i.e. foldSocket :: (a - ByteString - a) - a
 - Socket - IO a

 I'm all for having a higher level API but I would like to keep the Berkeley
 socket interface. The reason is the following: If we provide a higher level
 API that does not expose the whole underlying OS API there will be some
 users who can't use the library and will have to resort to writing their own
 bindings. I've seen this problem in a few other libraries. The reasoning
 often goes something like this: This interface will cover 90% (or 95%) of
 all the use cases so its sufficient for most people. The problem with this
 kind of reasoning is that I have to write my own OS bindings for every ten
 libraries I use (on average).

 Perhaps we should start a wiki page where we can take some notes on things
 that could be improved in the style of Haskell' discussions (i.e. outlines
 of the problem together possible solutions together with their trade-offs.
 Python's PEPs are a good model here)?

 -- Johan



 ___
 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




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


Re: [Haskell-cafe] Suggestion for Network.Socket in regards to PortNumber

2009-06-22 Thread Johan Tibell
On Mon, Jun 22, 2009 at 1:52 PM, Thomas DuBuisson 
thomas.dubuis...@gmail.com wrote:

 Johan - glad you chimed in!

 I'm all in favor of keeping a low level interface and don't have an
 issue with Network.Socket existing,  I additionally really like the
 suggestion of moving from the ML to a wiki in the same style as
 Haskell'.

 I'll port these comments to the wiki if that is whats agreed on and
 hold off on other thoughts for now.


Yes, please start a new wiki page. We can still discuss issues here and add
things to the wiki as different solutions materialize.


 * Avoiding a 'heavy weight' solution for socket state might get ugly
 fast with all the 'Either a b' results that we'll need - also a socket
 can close at any time so a socket in 'Connected' state might not
 actually be connected.  I understand the attraction to a light
 solution using existential types but Tim Sheard sketched for me a
 reasonable alternative which I invite him to restate here, if he has
 the time.


Good point. The encodings using existential types are not very lightweight
in my opinion. I'd love to hear Tim's alternative.

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


Re: [Haskell-cafe] How to determine if a FilePath is a directory name or regular file?

2009-06-22 Thread Deniz Dogan
2009/6/22 Duncan Coutts duncan.cou...@worc.ox.ac.uk:
 On Mon, 2009-06-22 at 08:53 +0200, Deniz Dogan wrote:
 2009/6/22 Colin Paul Adams co...@colina.demon.co.uk:
  Judah == Judah Jacobson judah.jacob...@gmail.com writes:
 
     Judah On Sun, Jun 21, 2009 at 11:12 PM, Colin Paul
     Judah Adamsco...@colina.demon.co.uk wrote:
      I've been hoogling like bad to try to determine if a function
      like this exists.
     
      getDirectoryContents returns sub-directories as well as file
      names. I want only the latter, so I'm looking for a suitable
      filter.
 
     Judah Use System.Directory.doesDirectoryExist/doesFileExist.
 
  Thanks.
 
  it seems it's time i went to the optician again.

 I'm not surprised that anyone would make the mistake. I think that the
 two functions should be named isDirectory and isFile, but it seems
 that isDirectory was already taken by another function in
 System.Directory, which is quite unfortunate. does goes against the
 intuition one gets from pretty much everything else in Haskell, where
 is seems to be the convention. In fact, Hoogle only knows about
 three functions which start with does.

 One explanation is that isBlah asks is this thing a blah, but we're
 not asking that because there is an indirection via the filepath. We're
 asking does this filepath refer to a directory not is this filename a
 directory. The latter could be a function:

 isDirectory :: FileInfo - Bool

 along with a hypothetical

 getFileInfo :: FilePath - IO FileInfo

 Duncan



I think see what you mean, but I find the argument more of an excuse
to the poor naming than a solid argument for it. Following the
convention and intuition that most users have should be more important
than making the (sometimes unnecessary) distinction between a
directory and the path to it.

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


[Haskell-cafe] Re: Optimizing spelling correction program

2009-06-22 Thread Kamil Dworakowski
On Jun 22, 10:03 am, Eugene Kirpichov ekirpic...@gmail.com wrote:
 Hey, you're using String I/O!

 nWORDS - fmap (train . map B.pack . words) (readFile big.txt)

 This should be

 WORDS - fmap (train . B.words) (B.readFile big.txt)

 By the way, which exact file do you use as a misspellings file? The
 corpus linked to at Norvig's page has many.
 And do you have a driver program that I could run and obtain your timings?

Yep, Don pointed that out and I have changed the program accordingly.
It didn't make any difference though. The time spent on building the
dictionary is a small portion of the overall run time.

Please see the repository contents for the current version of the
program:
http://patch-tag.com/r/spellcorrect/snapshot/current/content/pretty

The eval-bytestring.hs there is the program I used for timing. Inside
of it you will find the name of the misspellings file needed.

Thanks all for the suggestions. I'll try them when I get home tonight.

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


Re: [Haskell-cafe] How to determine if a FilePath is a directory name or regular file?

2009-06-22 Thread Max Rabkin
On Mon, Jun 22, 2009 at 2:09 PM, Deniz Dogandeniz.a.m.do...@gmail.com wrote:
 I think see what you mean, but I find the argument more of an excuse
 to the poor naming than a solid argument for it. Following the
 convention and intuition that most users have should be more important
 than making the (sometimes unnecessary) distinction between a
 directory and the path to it.

I disagree. (isDirectory /no/such/directory/) should equal true: the
given FilePath is a directory path (on Unix), since it ends with a
slash. However (doesDirectoryExist /no/such/directory) should return
false, since there is no such directory.

 --
 Deniz Dogan

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


Re: [Haskell-cafe] coding standard question

2009-06-22 Thread Malcolm Wallace
Johan Tibell johan.tib...@gmail.com wrote:

  Example:
   f a b = g (a+b) (b-a)
 where g a c = a*c
  
   f a b = g (a+b) (b-a)
 where g a' c = a*c
 
 Actually there's a warning:
 interactive:1:34: Warning: Defined but not used: `a''

Clearly I simplified the example too far.  Try this, only slightly more
complex, example instead.  Remember, the larger the example, the more
likely you are to miss an occurrence.

 f a b = g (a+b) (b-a)
   where g a c = a*(c-a)

 f a b = g (a+b) (b-a)
   where g a' c = a'*(c-a)


Perhaps I should advocate for a new warning in GHC to cover this case:
-fwarn-mixed-scopes, which could flag the use of the unprimed a, due to
being bound at an outer scope.

Because warn-mixed-scopes is almost the opposite of warn-name-shadowing,
then the only way to avoid warnings would be to manually lambda-lift all
functions.  :-)

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


Re: [Haskell-cafe] Suggestion for Network.Socket in regards to PortNumber

2009-06-22 Thread Thomas DuBuisson
All,
I've started to add to the network trac [1] - its just framework for
now.  Please do add proposals, organized comments, and feel free to
alter the framework.  I'm not sure how formal we'd like to make this
so I haven't even tried to make guidelines for proposals.  I'll add
proposals and perhaps try my hand at guidelines throughout this week.

Thomas

[1] http://trac.haskell.org/network/wiki/WikiStart

Possible proposal guidelines:
[2] http://hackage.haskell.org/trac/haskell-prime/wiki/CreateProposal
[3] http://www.python.org/dev/peps/

On Mon, Jun 22, 2009 at 5:03 AM, Johan Tibelljohan.tib...@gmail.com wrote:
 On Mon, Jun 22, 2009 at 1:52 PM, Thomas DuBuisson
 thomas.dubuis...@gmail.com wrote:

 Johan - glad you chimed in!

 I'm all in favor of keeping a low level interface and don't have an
 issue with Network.Socket existing,  I additionally really like the
 suggestion of moving from the ML to a wiki in the same style as
 Haskell'.

 I'll port these comments to the wiki if that is whats agreed on and
 hold off on other thoughts for now.

 Yes, please start a new wiki page. We can still discuss issues here and add
 things to the wiki as different solutions materialize.


 * Avoiding a 'heavy weight' solution for socket state might get ugly
 fast with all the 'Either a b' results that we'll need - also a socket
 can close at any time so a socket in 'Connected' state might not
 actually be connected.  I understand the attraction to a light
 solution using existential types but Tim Sheard sketched for me a
 reasonable alternative which I invite him to restate here, if he has
 the time.

 Good point. The encodings using existential types are not very lightweight
 in my opinion. I'd love to hear Tim's alternative.

 -- Johan


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


Re: [Haskell-cafe] How to determine if a FilePath is a directory name or regular file?

2009-06-22 Thread Deniz Dogan
2009/6/22 Max Rabkin max.rab...@gmail.com:
 On Mon, Jun 22, 2009 at 2:09 PM, Deniz Dogandeniz.a.m.do...@gmail.com wrote:
 I think see what you mean, but I find the argument more of an excuse
 to the poor naming than a solid argument for it. Following the
 convention and intuition that most users have should be more important
 than making the (sometimes unnecessary) distinction between a
 directory and the path to it.

 I disagree. (isDirectory /no/such/directory/) should equal true: the
 given FilePath is a directory path (on Unix), since it ends with a
 slash. However (doesDirectoryExist /no/such/directory) should return
 false, since there is no such directory.

Are you saying that when a function is named isDirectory you expect
it to only check for a trailing forward slash character?

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


[Haskell-cafe] Re: coding standard question

2009-06-22 Thread Christian Maeder
Malcolm Wallace wrote:
 Johan Tibell johan.tib...@gmail.com wrote:
 
 Example:
  f a b = g (a+b) (b-a)
where g a c = a*c

The proper way to avoid shadowing in this simple case would be to make g
global (and don't export it).

 f a b = g (a+b) (b-a)
 g a c = a*c

 
  f a b = g (a+b) (b-a)
where g a' c = a*c
 Actually there's a warning:
 interactive:1:34: Warning: Defined but not used: `a''
 
 Clearly I simplified the example too far.  Try this, only slightly more
 complex, example instead.  Remember, the larger the example, the more
 likely you are to miss an occurrence.
 
  f a b = g (a+b) (b-a)
where g a c = a*(c-a)
 
  f a b = g (a+b) (b-a)
where g a' c = a'*(c-a)
 
 
 Perhaps I should advocate for a new warning in GHC to cover this case:
 -fwarn-mixed-scopes, which could flag the use of the unprimed a, due to
 being bound at an outer scope.

The main reason for let and where are such mixed scopes. (And maybe
you should get a warning if the scope is not mixed, as in the initial
example.)

In any case I think, it does make sense to avoid name shadowing in the
same way as it make sense to avoid shadowing of imported (or declared)
global names by local variables (i.e. by using pi or id as variables).

Surely, it may be convenient to reuse names in local scopes, but it is
as hard to read such code as it is to replace shadowed variables
consistently by hand. (A refactoring tool could rename shadowed
variables as reliable as the compiler treats them.)

Surely there's no help against mixing up names with the same type.

Cheers Christian

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


Re: [Haskell-cafe] How to determine if a FilePath is a directory name or regular file?

2009-06-22 Thread Ketil Malde
Deniz Dogan deniz.a.m.do...@gmail.com writes:

 One explanation is that isBlah asks is this thing a blah, but we're
 not asking that because there is an indirection via the filepath. We're
 asking does this filepath refer to a directory not is this filename a
 directory.

 I think see what you mean, but I find the argument more of an excuse
 to the poor naming than a solid argument for it. Following the
 convention and intuition that most users have should be more important
 than making the (sometimes unnecessary) distinction between a
 directory and the path to it.

It is more important to be consistent and logical than to follow
conventions and intuitions.

And at any rate, convention is that 'isFoo' is a pure function with the
type 'FooType - Bool', clearly different from 'doesDirectoryExist', which
returns an IO action. 

So IMO 'isDirectory /foo/bar/' should always return false, since it is
a string, not a directory. 

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to determine if a FilePath is a directory name or regular file?

2009-06-22 Thread Max Rabkin
On Mon, Jun 22, 2009 at 2:54 PM, Deniz Dogandeniz.a.m.do...@gmail.com wrote:
 Are you saying that when a function is named isDirectory you expect
 it to only check for a trailing forward slash character?

No. I'm saying that *if* isDirectory existed, then (isDirectory
/no/such/directory/) should equal true on Unix. I'm saying
isDirectory should not *exist*, because it cannot do what it says on
Unix or Windows. There are OSes where it can do what it says (i.e., it
is possible to tell whether a path points at a directory or a file).

 --
 Deniz Dogan


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


Re: [Haskell-cafe] coding standard question

2009-06-22 Thread Jochem Berndsen
Jules Bean wrote:
 Magnus Therning wrote:
 Also from experience, I get a good feeling about software that
 compiles without warnings.  It suggests the author cares and is
 indicative of some level of quality.
 
 In contrast, I find almost all the GHC warnings to be useless, and
 therefore turn them off. I don't find they have a significant
 correlation with code quality.
 
 YMMV :)

I strongly disagree with this.
There is a huge difference between

f (x:xs) = ...

and

f (x:xs) = ...
f [] = error f: we expect a nonempty list

The reason for this is that in the second case you express to somebody
who reads your code (including yourself) that this omission was intentional.

The same holds for other warnings (although I sometimes am annoyed by
the shadowing warnings, I agree :).

My default is to start developing, then adding -Wall -Werror and make it
compile again.

Regards,

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


[Haskell-cafe] Re: haskelldb + sqlite problem.

2009-06-22 Thread GüŸnther Schmidt

Hi Cloud,

this often occurs when the path to the database includes a non-ascii 
character.


In my dev environment, the path to the database deliberately contains an 
umlaut and the original code base of hdbc.sqlite3 from John Goerzen, 
version 2.0  version 2.1 thus does not work.


John Goerzen, the author of HDBC has considerably rewritten some parts 
of his hdbc package to use utf8-string wrapping, which includes wrapping 
 the connection string, and in my case caused considerable problems, it 
just wouldn't work. So my solution was to rollback all these changes 
where he used the utf8-wrapping, which was quite a lot of work. I did 
communicate this to John, but he insists that his current solution is 
correct, and I'm not going to argue with him.


Anyway what you can do, for now, is to put your sqlite3 database file 
into a location where the path contains no non-ascii characters, that 
should fix the problem.



You may experience other, utf8-wrapping related problems, for instance 
when you want to insert non-ascii strings into varchar columns. They may 
not come back as you put them in.


HTH

Günther

Magicloud Magiclouds schrieb:

Hi,
  I am using haskelldb and haskelldb-hdbc-sqlite3. Well, I finally got
the source compiled and ran, I got this error:
App: user error (SQL error: SqlError {seState = , seNativeError =
21, seErrorMsg = prepare 74: SELECT subject,\n   timestamp\nFROM
notes as T1\nORDER BY timestamp DESC: library routine called out of
sequence})
  Any clue what I should check? Thanks.



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


Re: [Haskell-cafe] Suggestion for Network.Socket in regards to PortNumber

2009-06-22 Thread Johan Tibell
On Mon, Jun 22, 2009 at 2:46 PM, Thomas DuBuisson 
thomas.dubuis...@gmail.com wrote:

 All,
 I've started to add to the network trac [1] - its just framework for
 now.  Please do add proposals, organized comments, and feel free to
 alter the framework.  I'm not sure how formal we'd like to make this
 so I haven't even tried to make guidelines for proposals.  I'll add
 proposals and perhaps try my hand at guidelines throughout this week.


Lets just get some concrete proposals up there and see if we need some kind
of guidelines and what those guidelines should be. FWIW I like the PEP
style.

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


[Haskell-cafe] ICFP09 Call for Participation

2009-06-22 Thread Matthew Fluet (ICFP Publicity Chair)
=
Call for Participation

The 14th ACM SIGPLAN International Conference
on Functional Programming (ICFP 2009)

  http://www.cs.nott.ac.uk/~gmh/icfp09.html

  Edinburgh, Scotland, 31 August - 2 September 2009
=

ICFP 2009 provides a forum for researchers and developers to hear
about the latest work on the design, implementations, principles, and
uses of functional programming. The conference covers the entire
spectrum of work, from practice to theory, including its peripheries.

Preliminary program:
 * Accepted papers:
  + http://web.cecs.pdx.edu/~apt/icfp09_accepted_papers/accepted.html
 * Invited speakers:
   + Guy Steele -- Organizing Functional Code for Parallel Execution:
 or, foldl and foldr Considered Slightly Harmful
   + Benjamin Pierce -- Lambda, the Ultimate TA: Using a Proof
 Assistant to Teach Programming Language Foundations
   +Dan Piponi -- Commutative Monads, Diagrams and Knots


Schedule including related workshops:
 * Aug 30: ACM SIGPLAN Workshop on ML
 * Aug 30: ACM SIGPLAN Workshop on Generic Programming
 * Aug 31-Sep 2: ICFP09
 * Sep  3: ACM SIGPLAN Haskell Symposium
 * Sep  3: ACM SIGPLAN Developer Tracks on Functional Programming
 * Sep  4: Commercial Users of Functional Programming
 * Sep  4: ACM SIGPLAN Workshop on Mechanizing Metatheory
 * Sep  4: ACM SIGPLAN Workshop on Approaches and Applications of
   Inductive Programming
 * Sep  5: ACM SIGPLAN Erlang Workshop
 * Sep  5: ACM SIGPLAN Developer Tracks on Functional Programming
 * Sep  5: ACM SIGPLAN Haskell Implementors Workshop


Registration information:
 * http://www.regmaster.com/conf/icfp2009.html
 * Early registration deadline: July 30, 2009


Local arrangements (including travel and accommodation):
 * http://www.haskell.org/haskellwiki/ICFP_2009_Local_Arrangements
 * Conference reservation/rate deadline: July 20, 2009
 * ICFP09 coincides with the final week of the Edinburgh International
   Festival, one of the premier arts and cultural festivals in the
   world.  The opportunity to attend the Festival is a plus!  Due to
   the popularity of Edinburgh during the festival period, we
   strongly recommend booking accommodation early.


Conference organizers:
 * General Chair: Graham Hutton (University of Nottingham)
 * Program Chair: Andrew Tolmach (Portland State University)
 * Local Arrangements Chairs: Philip Wadler (University of Edinburgh),
   Kevin Hammond (University of St Andrews), and
   Gregory Michaelson (Heriot-Watt University)
 * Workshop Co-Chairs: Christopher Stone (Harvey Mudd College), and
   Michael Sperber (DeinProgramm)
 * Programming Contest Chair: Andrew Gill (University of Kansas)
 * Publicity Chair: Matthew Fluet (Toyota Technological Institute at Chicago)


=
=

And, don't forget about the ICFP Programming Contest this weekend!!

 * http://www.icfpcontest.org
 * Friday, June 26 to Monday, June 29
 * Organizers: Computer Systems Design Laboratory (University of Kansas)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type system trickery

2009-06-22 Thread Brent Yorgey
On Sun, Jun 21, 2009 at 09:16:12PM +0100, Andrew Coppin wrote:
 Niklas Broberg wrote:
 That's what GADTs are for:

 data Flag = HasZoo | NoZoo

 data Foobar a where
   Foo :: Foobar a - Foobar a
   Bar :: Foobar a - Foobar a
   Zoo :: Foobar a - Foobar HasZoo
   

 Ouch #1: This appears to instantly disable deriving the Eq, Ord and Show 
 instances I want. :-/

Ah, yes, that is a pain.  Maybe try playing around with tools like
Data.Derive?  I haven't played with them much myself so I don't know
if they will help.

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


Re: [Haskell-cafe] rewrite rules

2009-06-22 Thread Daniel Schüssler
Hi Sjoerd,

I don't know the cause of the problem, but if I add this rule, it works:

{-# RULES
   inline_map forall g x. map g x = transform (. g) x
 -#}

maybe, for whatever reason, the 'map' is inlined too late for the 
transform/transform rule to see it?


Greetings,
Daniel

On Monday 22 June 2009 11:41:33 Sjoerd Visscher wrote:
 Hi all,

 I have a rewrite rule as follows:

 {-# RULES
 transform/transform forall (f::forall m. Monoid m = (a - m) - (b -

   m))

   (g::forall m. Monoid m = (b - m) - (c
 - m))
   (l::FMList c). transform f (transform g
 l) = transform (g.f) l
#-}

 It fires on this code:

print $ transform (. (*2)) (transform (. (+1)) (upto 10))

 But it doesn't fire on this code:

print $ map (*2) (map (+1) (upto 10)))

 with

map g x = transform (. g) x

 and with or without {-# INLINE map #-}.

 What am I doing wrong?

 --
 Sjoerd Visscher
 sjo...@w3future.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] rewrite rules

2009-06-22 Thread Sjoerd Visscher


On Jun 22, 2009, at 6:38 PM, Ryan Ingram wrote:


Not 100% sure (especially without source/core), but my guess is that
the higher-rank types make the rule unlikely to fire.

Try -ddump-simpl to see the core output, and look for places where you
expect the rule to fire.  I suspect you will find that the types of f
and g are not forall at that point in the code, but have already
been specialized.

Is there a reason you cannot use this simpler rule?

{-# RULES transform/tranform forall f g l. transform f (transform g
l) = transform (g.f) l #-}



Yes, this is the reason:

Inferred type is less polymorphic than expected
  Quantified type variable `m' is mentioned in the environment:
f :: (a - m) - b - m (bound at Data/FMList.hs:124:29)
In the first argument of `transform', namely `f'
In the expression: transform f (transform g l)
When checking the transformation rule transform/transform

This is the function:

transform :: (forall m. Monoid m = (a - m) - (b - m)) - FMList b - 
 FMList a

transform t l = FM $ \f - unFM l (t f)

I'll have to clean things up before the core output becomes manageable.

Sjoerd


 -- ryan

On Mon, Jun 22, 2009 at 2:41 AM, Sjoerd  
Visschersjo...@w3future.com wrote:

Hi all,

I have a rewrite rule as follows:

{-# RULES
transform/transform forall (f::forall m. Monoid m = (a - m) -  
(b - m))
(g::forall m. Monoid m = (b - m) -  
(c - m))
(l::FMList c). transform f (transform g  
l) =

transform (g.f) l
 #-}

It fires on this code:

 print $ transform (. (*2)) (transform (. (+1)) (upto 10))

But it doesn't fire on this code:

 print $ map (*2) (map (+1) (upto 10)))

with

 map g x = transform (. g) x

and with or without {-# INLINE map #-}.

What am I doing wrong?

--
Sjoerd Visscher
sjo...@w3future.com



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





--
Sjoerd Visscher
sjo...@w3future.com



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


Re: [Haskell-cafe] Getting my mind around UArray - STUArray conversion

2009-06-22 Thread Scott Michel
On Fri, Jun 19, 2009 at 7:08 PM, Dan Doeldan.d...@gmail.com wrote:
 Oops, I replied too hastily.

 What I wrote in my first mail is a problem, as witnessed by the ix and ix1
 in the error message. However, it isn't the main error. The main error is that
 you have a monadic expression, with type something like:

    ST s (UArray ix e)

 but the return type of your function is:

    UArray ix e

 To make a no-op you need to add a runST, something like:

    runST (unsafeThaw mem = unsafeFreeze)

Actually, I probably wanted runSTUArray. :-)

But even then, I can't manage to get wombat to compile correctly. I'm
starting to think that MArray is itself a WOMBAT (waste of money,
brains and time), for three reasons:

a) Overly restrictive Monads in which implementation is supported
(i.e., ST and IO)
b) The triviality of the examples gives no insight as to how they
could be used, other than a create array, do something completely
trivial and freeze.
c) They are evidently very hard to use in a general sense.

Even google-ing for examples just comes up with trivial examples of
MArray usage.

You might ask why I might need a MArray? I'm investigating the
feasibility of building a cycle accurate PPC750 emulator. Memory
emulates better as a mutable array. I'd like to be somewhat more
general because the various systems with which I deal aren't
necessarily 32-bit, sometimes they are 16-bit and sometimes they
aren't PPC750 (different systems hooked to a common bus.) Classes with
rank-n types looked like a good approach to solving this particular
design problem, with a default implementation.

I did try out your suggestions and here's what the code looks like now.

{-# LANGUAGE FlexibleContexts, RankNTypes, ScopedTypeVariables #-}
module Wombat where

import Control.Monad.ST;
import Data.Array.ST;
import Data.Array.Unboxed;
import Data.Array.MArray;

wombat :: forall e ix s. (IArray UArray e, Ix ix, MArray (STUArray s)
e (ST s)) = e - ix - UArray ix e - UArray ix e
wombat val idx mem = runSTUArray (unsafeThaw mem = return)


GHCi says:
[1 of 1] Compiling Wombat   ( wombat.hs, interpreted )

wombat.hs:11:34:
Could not deduce (MArray (STUArray s1) e (ST s1))
  from the context ()
  arising from a use of `unsafeThaw'
   at wombat.hs:11:34-47
Possible fix:
  add (MArray (STUArray s1) e (ST s1)) to the context of
the polymorphic type `forall s. ST s (STUArray s ix e)'
  or add an instance declaration for (MArray (STUArray s1) e (ST s1))
In the first argument of `(=)', namely `unsafeThaw mem'
In the first argument of `runSTUArray', namely
`(unsafeThaw mem = return)'
In the expression: runSTUArray (unsafeThaw mem = return)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules

2009-06-22 Thread Ryan Ingram
Not 100% sure (especially without source/core), but my guess is that
the higher-rank types make the rule unlikely to fire.

Try -ddump-simpl to see the core output, and look for places where you
expect the rule to fire.  I suspect you will find that the types of f
and g are not forall at that point in the code, but have already
been specialized.

Is there a reason you cannot use this simpler rule?

{-# RULES transform/tranform forall f g l. transform f (transform g
l) = transform (g.f) l #-}

  -- ryan

On Mon, Jun 22, 2009 at 2:41 AM, Sjoerd Visschersjo...@w3future.com wrote:
 Hi all,

 I have a rewrite rule as follows:

 {-# RULES
 transform/transform forall (f::forall m. Monoid m = (a - m) - (b - m))
                             (g::forall m. Monoid m = (b - m) - (c - m))
                             (l::FMList c). transform f (transform g l) =
 transform (g.f) l
  #-}

 It fires on this code:

  print $ transform (. (*2)) (transform (. (+1)) (upto 10))

 But it doesn't fire on this code:

  print $ map (*2) (map (+1) (upto 10)))

 with

  map g x = transform (. g) x

 and with or without {-# INLINE map #-}.

 What am I doing wrong?

 --
 Sjoerd Visscher
 sjo...@w3future.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] Type system trickery

2009-06-22 Thread Andrew Coppin

Brent Yorgey wrote:

On Sun, Jun 21, 2009 at 09:16:12PM +0100, Andrew Coppin wrote:
  

Niklas Broberg wrote:


That's what GADTs are for:

data Flag = HasZoo | NoZoo

data Foobar a where
  Foo :: Foobar a - Foobar a
  Bar :: Foobar a - Foobar a
  Zoo :: Foobar a - Foobar HasZoo
  
  
Ouch #1: This appears to instantly disable deriving the Eq, Ord and Show 
instances I want. :-/



Ah, yes, that is a pain.  Maybe try playing around with tools like
Data.Derive?  I haven't played with them much myself so I don't know
if they will help.
  


Not nearly as annoying as this:

 data Foobar a where
   Foo :: X - Y - Foobar NoZoo
   Bar :: X - Y - Foobar NoZoo
   Zoo :: Foobar NoZoo - Foobar Zoo

For some reason, if I do this I get endless type check errors. I have to 
change the top two back to Foobar a before it will work. *sigh*


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


Re: [Haskell-cafe] Getting my mind around UArray - STUArray conversion

2009-06-22 Thread Don Stewart
scooter.phd:
 On Fri, Jun 19, 2009 at 7:08 PM, Dan Doeldan.d...@gmail.com wrote:
  Oops, I replied too hastily.
 
  What I wrote in my first mail is a problem, as witnessed by the ix and 
  ix1
  in the error message. However, it isn't the main error. The main error is 
  that
  you have a monadic expression, with type something like:
 
     ST s (UArray ix e)
 
  but the return type of your function is:
 
     UArray ix e
 
  To make a no-op you need to add a runST, something like:
 
     runST (unsafeThaw mem = unsafeFreeze)
 
 Actually, I probably wanted runSTUArray. :-)
 
 But even then, I can't manage to get wombat to compile correctly. I'm
 starting to think that MArray is itself a WOMBAT (waste of money,
 brains and time), for three reasons:
 
 a) Overly restrictive Monads in which implementation is supported
 (i.e., ST and IO)
 b) The triviality of the examples gives no insight as to how they
 could be used, other than a create array, do something completely
 trivial and freeze.
 c) They are evidently very hard to use in a general sense.
 
 Even google-ing for examples just comes up with trivial examples of
 MArray usage.


Can you just use STUArrays directly without worrying about MArray
overloading? writeArray/readArray on ST is just type safe raw memory
access, so should be easy.

 wombat :: forall e ix s. (IArray UArray e, Ix ix, MArray (STUArray s)
 e (ST s)) = e - ix - UArray ix e - UArray ix e
 wombat val idx mem = runSTUArray (unsafeThaw mem = return)

Argh. That type is scary overloaded. 

-- Don

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


Re: [Haskell-cafe] Type system trickery

2009-06-22 Thread Niklas Broberg
 Not nearly as annoying as this:

  data Foobar a where
   Foo :: X - Y - Foobar NoZoo
   Bar :: X - Y - Foobar NoZoo
   Zoo :: Foobar NoZoo - Foobar Zoo

 For some reason, if I do this I get endless type check errors. I have to
 change the top two back to Foobar a before it will work. *sigh*

Well, that means something very different obviously. It means Zoo
constructors can never take Zoo arguments, so you could only have at
most one Zoo constructor at the outermost level, having either a Foo
or a Bar inside it. Why would that give you type check errors? If it
does, you're doing something else wrong.

Cheers,

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


Re: [Haskell-cafe] Type system trickery

2009-06-22 Thread Thomas DuBuisson
Andrew Coppin said:
  data Foobar a where
   Foo :: X - Y - Foobar NoZoo
   Bar :: X - Y - Foobar NoZoo
   Zoo :: Foobar NoZoo - Foobar Zoo

 For some reason, if I do this I get endless type check errors. I have to
 change the top two back to Foobar a before it will work. *sigh*

That code snippet works for me, so I think you're doing something else
wrong or I transcribed wrong

My code in full:
-
{-# LANGUAGE GADTs, EmptyDataDecls #-}

data NoZoo
data Zoo

data Place a where
Office :: String - Int - Place NoZoo
Home   :: String - Int - Place NoZoo
Zoo:: Place NoZoo - Place Zoo
-

It works fine (but I absolutely agree the lack of deriving is frustrating):
-
*Main let x = Zoo (Office 9th street 3342)
*Main let y = Home Friends House 4422
*Main :t x
x :: Place Zoo
*Main :t y
y :: Place NoZoo
*Main



And if you want to change it wrt Niklas's comments:
---
{-# LANGUAGE GADTs, EmptyDataDecls #-}

data NoZoo
data Zoo

data Place a where
Office :: String - Int - Place NoZoo
Home   :: String - Int - Place NoZoo
Zoo:: Place a - Place Zoo
---

Which works:
---
*Main let x = Zoo (Zoo (Office 9th street 3342))
*Main let y = Home Friends House 4422
*Main :t x
x :: Place Zoo
*Main :t y
y :: Place NoZoo
-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: hledger 0.6.1 released

2009-06-22 Thread Simon Michael
I have released hledger 0.6.1 which fixes a build problem with ghc  
6.8. You can ignore this release if you use a newer ghc or if one of  
the http://hledger.org/binaries works for you.


Thanks to Andreas Reuleaux for the report. More reports welcome on  
irc, list or http://code.google.com/p/hledger/issues .


Best,
-Simon (sm)

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


Re[2]: [Haskell-cafe] Getting my mind around UArray - STUArray conversion

2009-06-22 Thread Bulat Ziganshin
Hello Scott,

Monday, June 22, 2009, 10:23:42 PM, you wrote:

 wombat :: forall e ix s. (IArray UArray e, Ix ix, MArray (STUArray s)
e (ST s)) = e - ix - UArray ix e - UArray ix e

http://haskell.org/haskellwiki/Library/ArrayRef#Reimplemented_Arrays_library

Unboxed arrays now can be used in polymorphic functions...



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

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


[Haskell-cafe] Re: Optimizing spelling correction program

2009-06-22 Thread Kamil Dworakowski

On Jun 22, 6:46 am, Bulat Ziganshin bulat.zigans...@gmail.com wrote:
 Hello Kamil,

 Monday, June 22, 2009, 12:01:40 AM, you wrote:

  Right... Python uses hashtables while here I have a tree with log n

 you can try this pure hashtable approach:

 import Prelude hiding (lookup)
 import qualified Data.HashTable
 import Data.Array
 import qualified Data.List as List

 data HT a b = HT (a-Int) (Array Int [(a,b)])

 -- size is the size of array (we implent closed hash)
 -- hash is the hash function (a-Int)
 -- list is assoclist of items to put in hash
 create size hash list = HT hashfunc
                            (accumArray (flip (:))
                                        []
                                        (0, arrsize-1)
                                        (map (\(a,b) - (hashfunc a,b)) list)
                            )

   where arrsize     =  head$ filter (size)$ iterate (\x-3*x+1) 1
         hashfunc a  =  hash a `mod` arrsize

 lookup a (HT hash arr) = List.lookup a (arr!hash a)

 main = do let assoclist = [(one, 1), (two, 2), (three, 3)]
               hash = create 10 (fromEnum . Data.HashTable.hashString) 
 assoclist
           print (lookup one hash)
           print (lookup zero hash)

It does not compile:

No instance for (Num (String, b))
  arising from the literal `3' at foo.hs:23:61
Possible fix: add an instance declaration for (Num (String, b))
In the expression: 3
In the expression: (three, 3)
In the expression: [(one, 1), (two, 2), (three, 3)]


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


Re: [Haskell-cafe] Type system trickery

2009-06-22 Thread Andrew Coppin

Niklas Broberg wrote:

Not nearly as annoying as this:

 data Foobar a where
  Foo :: X - Y - Foobar NoZoo
  Bar :: X - Y - Foobar NoZoo
  Zoo :: Foobar NoZoo - Foobar Zoo

For some reason, if I do this I get endless type check errors. I have to
change the top two back to Foobar a before it will work. *sigh*



Well, that means something very different obviously. It means Zoo
constructors can never take Zoo arguments.


...which would be precisely what I want, yes. :-)


Why would that give you type check errors? If it
does, you're doing something else wrong.
  


I think (I'm not sure) it's because of stuff like this:

 foobar :: Foobar a - X
 foobar f = case f of
   Foo x y - ...
   Zoo g - foobar g

The first case implies that f :: Foobar NoZoo, while the second implies 
that f :: Foobar Zoo. Apparently this seemingly reasonable construct 
does not type-check...


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


Re: [Haskell-cafe] Type system trickery

2009-06-22 Thread Ross Mellgren

This works for me:

{-# LANGUAGE EmptyDataDecls, GADTs #-}
module Main where

data NoZoo
data Zoo

newtype X = X Int deriving (Show)
newtype Y = Y Char deriving (Show)

data Foobar a where
Foo :: X - Y - Foobar NoZoo
Bar :: X - Y - Foobar NoZoo
Zoo :: Foobar NoZoo - Foobar Zoo

foobar :: Foobar a - X
foobar f = case f of
 Foo x _ - x
 Zoo g   - foobar g

main :: IO ()
main = putStrLn . show $ foobar (Zoo $ Foo (X 1) (Y 'a'))


Could you post a test case?


On Jun 22, 2009, at 3:34 PM, Andrew Coppin wrote:


Niklas Broberg wrote:

Not nearly as annoying as this:

data Foobar a where
 Foo :: X - Y - Foobar NoZoo
 Bar :: X - Y - Foobar NoZoo
 Zoo :: Foobar NoZoo - Foobar Zoo

For some reason, if I do this I get endless type check errors. I  
have to

change the top two back to Foobar a before it will work. *sigh*



Well, that means something very different obviously. It means Zoo
constructors can never take Zoo arguments.


...which would be precisely what I want, yes. :-)


Why would that give you type check errors? If it
does, you're doing something else wrong.



I think (I'm not sure) it's because of stuff like this:

foobar :: Foobar a - X
foobar f = case f of
  Foo x y - ...
  Zoo g - foobar g

The first case implies that f :: Foobar NoZoo, while the second  
implies that f :: Foobar Zoo. Apparently this seemingly reasonable  
construct does not type-check...


___
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: Optimizing spelling correction program

2009-06-22 Thread Daniel Fischer
Am Montag 22 Juni 2009 21:31:50 schrieb Kamil Dworakowski:
 On Jun 22, 6:46 am, Bulat Ziganshin bulat.zigans...@gmail.com wrote:
  Hello Kamil,
 
  Monday, June 22, 2009, 12:01:40 AM, you wrote:
   Right... Python uses hashtables while here I have a tree with log n
 
  you can try this pure hashtable approach:
 
  import Prelude hiding (lookup)
  import qualified Data.HashTable
  import Data.Array
  import qualified Data.List as List
 
  data HT a b = HT (a-Int) (Array Int [(a,b)])
 
  -- size is the size of array (we implent closed hash)
  -- hash is the hash function (a-Int)
  -- list is assoclist of items to put in hash
  create size hash list = HT hashfunc
                             (accumArray (flip (:))
                                         []
                                         (0, arrsize-1)
                                         (map (\(a,b) - (hashfunc a,b))

Typo: should be

map (\(a,b) - (hashfunc a, (a,b))


  list) )
 
    where arrsize     =  head$ filter (size)$ iterate (\x-3*x+1) 1
          hashfunc a  =  hash a `mod` arrsize
 
  lookup a (HT hash arr) = List.lookup a (arr!hash a)
 
  main = do let assoclist = [(one, 1), (two, 2), (three, 3)]
                hash = create 10 (fromEnum . Data.HashTable.hashString)
  assoclist print (lookup one hash)
            print (lookup zero hash)

 It does not compile:

 No instance for (Num (String, b))
   arising from the literal `3' at foo.hs:23:61
 Possible fix: add an instance declaration for (Num (String, b))
 In the expression: 3
 In the expression: (three, 3)
 In the expression: [(one, 1), (two, 2), (three, 3)]



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


[Haskell-cafe] Re: Optimizing spelling correction program

2009-06-22 Thread Kamil Dworakowski
On Jun 22, 9:10 am, Ketil Malde ke...@malde.org wrote:
 Kamil Dworakowski ka...@dworakowski.name writes:
  Right... Python uses hashtables while here I have a tree with log n
  access time. I did not want to use the Data.HashTable, it would
  pervade my program with IO. The alternative is an ideal hashmap that never
  gets changed. This program creates a dictionary at start which then is only
  being used to read from: an ideal application for the Data.PerfectHash
  by Mark Wotton available on Hackage [3].

 If you are considering alternative data structures, you might want to
 look at tries or Bloom filters, both have O(n) lookup, both have
 Haskell implementations.  The latter is probably faster but
 probabilistic (i.e. it will occasionally fail to detect a
 misspelling - which you can of course check against a real
 dictionary).

Using Bryan O'Sullivan's fantastic BloomFilter I got it down below
Python's run time! Now it is 35.56s, 28% of the time is spent on GC,
which I think means there is still some room for improvement.

Do you say that PerfectHash runs with a penalty of calling into c
library?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Optimizing spelling correction program

2009-06-22 Thread Kamil Dworakowski


On Jun 22, 9:06 pm, Daniel Fischer daniel.is.fisc...@web.de wrote:
 Am Montag 22 Juni 2009 21:31:50 schrieb Kamil Dworakowski:



  On Jun 22, 6:46 am, Bulat Ziganshin bulat.zigans...@gmail.com wrote:
   Hello Kamil,

   Monday, June 22, 2009, 12:01:40 AM, you wrote:
Right... Python uses hashtables while here I have a tree with log n

   you can try this pure hashtable approach:

   import Prelude hiding (lookup)
   import qualified Data.HashTable
   import Data.Array
   import qualified Data.List as List

   data HT a b = HT (a-Int) (Array Int [(a,b)])

   -- size is the size of array (we implent closed hash)
   -- hash is the hash function (a-Int)
   -- list is assoclist of items to put in hash
   create size hash list = HT hashfunc
                              (accumArray (flip (:))
                                          []
                                          (0, arrsize-1)
                                          (map (\(a,b) - (hashfunc a,b))

 Typo: should be

 map (\(a,b) - (hashfunc a, (a,b))

Wait! Have you typed that definition into the msg off the top of your
head? :)

I went back to using Strings instead of ByteStrings and with that
hashtable the program finishes in 31.5s! w00t!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] haskelldb + sqlite problem.

2009-06-22 Thread John Goerzen
Magicloud Magiclouds wrote:
 Hi,
   I am using haskelldb and haskelldb-hdbc-sqlite3. Well, I finally got
 the source compiled and ran, I got this error:
 App: user error (SQL error: SqlError {seState = , seNativeError =
 21, seErrorMsg = prepare 74: SELECT subject,\n   timestamp\nFROM
 notes as T1\nORDER BY timestamp DESC: library routine called out of
 sequence})
   Any clue what I should check? Thanks.

At the HDBC level, I would say:

I suspect that you have used a function that returns results lazily, but
haven't completely read them before calling back into the database with
something else.  As an example, you should probably use quickQuery'
instead of quickQuery, unless you are fully prepared to accept the
consequences of reading data lazily from a database.

I am not very familiar with HaskellDB, and can't really comment on what
it's doing under the hood.  If it is returning results to you lazily,
make sure you have completely consumed them before sending more queries
to the database.

If you can post some example code, it would likely help.

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


Re: [Haskell-cafe] Re: Optimizing spelling correction program

2009-06-22 Thread Bulat Ziganshin
Hello Kamil,

Tuesday, June 23, 2009, 12:54:49 AM, you wrote:

 I went back to using Strings instead of ByteStrings and with that
 hashtable the program finishes in 31.5s! w00t!

and GC times are? also, try ByteString+HT, it should be pretty easy to
write hashByteString


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

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


Re: [Haskell-cafe] Re: haskelldb + sqlite problem.

2009-06-22 Thread John Goerzen
GüŸnther Schmidt wrote:
 Hi Cloud,
 
 this often occurs when the path to the database includes a non-ascii 
 character.
 
 In my dev environment, the path to the database deliberately contains an 
 umlaut and the original code base of hdbc.sqlite3 from John Goerzen, 
 version 2.0  version 2.1 thus does not work.

This is conflating many issues.

I do recall some discussion about data within a database; I don't recall
one about the filename of it, which would certainly be a separate
discussion.  I can see why a connectRaw or some such function could be
useful if you want to pass a raw binary string as the file path to
Sqlite3.  (I don't think any other DB would have a use for such a thing).


 John Goerzen, the author of HDBC has considerably rewritten some parts 
 of his hdbc package to use utf8-string wrapping, which includes wrapping 
   the connection string, and in my case caused considerable problems, it 
 just wouldn't work. So my solution was to rollback all these changes 
 where he used the utf8-wrapping, which was quite a lot of work. I did 

And unnecessary work at that, if all you cared about was the filename.

I see your point on the filename, and tweaking that would have been a
one-line fix for you.

The mess we had before was this huge cloud of **UNDEFINED BEHAVIOR**
when dealing with anything other than 7-bit ASCII.  Databases could have
some encodings, systems could have encodings, and it was all a huge fiasco.

So with HDBC 2, what we have is:

 * If you want to communicate with the database in a raw manner, use
ByteStrings.  If you want a String out of it, convert it yourself.

 * If you want to use Strings to communicate with the databases, these
will automatically be converted to the appropriate Unicode
representation by the library.  For all current database backends, that
means converting them to a UTF-8 CStringLen type of thing, and back.

 Anyway what you can do, for now, is to put your sqlite3 database file 
 into a location where the path contains no non-ascii characters, that 
 should fix the problem.

His problem is not caused by non-ASCII characters.

 You may experience other, utf8-wrapping related problems, for instance 
 when you want to insert non-ascii strings into varchar columns. They may 
 not come back as you put them in.

They will, unless you are doing something weird like putting Latin1
8-bit text into a String and passing it to HDBC as a String, when the
documentation specifically states that Strings are expected to be in the
Unicode space.  As I recall, that is specifically what you were doing.

That doesn't mean I haven't provided an outlet for you to do deal with
things in the Latin1 space (see the ByteString discussion above.)

But in truth, HDBC is not a character set conversion library, nor should
it be.  If you have more complex needs than Unicode Strings, use one of
the many quality encoding libraries available for Haskell, and combine
it with the ByteString features in HDBC.

Every popular database that I am aware of can either speak UTF-8
directly, or convert transparently to and from it.

So, to summarize:

1) This is not the original poster's problem.

2) HDBC 2 is simpler than HDBC 1, and actually defines behavior in terms
of character sets rather than leaving it completely undefined.

3) HDBC 2 standardizes character sets around UTF-8, the most common
global standard, and structures its API in a way that this is
transparent when you want it to be, and available for manual processing
when you want that.

4) Nothing requires you to use UTF-8, which is why the ByteString API is
there.

5) A one-line patch would have fixed your filename connection issue.

6) If memory serves, your not getting things back is because you are
storing non-Unicode data in your Strings, and then using an improper API
to store it.

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


Re: [Haskell-cafe] Re: Optimizing spelling correction program

2009-06-22 Thread Daniel Fischer
Am Montag 22 Juni 2009 22:54:49 schrieb Kamil Dworakowski:
 Wait! Have you typed that definition into the msg off the top of your
 head? :)

No, took a bit of looking.


 I went back to using Strings instead of ByteStrings and with that
 hashtable the program finishes in 31.5s! w00t!

Nice :D

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


Re: [Haskell-cafe] Re: Optimizing spelling correction program

2009-06-22 Thread Don Stewart
kamil:
 On Jun 22, 9:10 am, Ketil Malde ke...@malde.org wrote:
  Kamil Dworakowski ka...@dworakowski.name writes:
   Right... Python uses hashtables while here I have a tree with log n
   access time. I did not want to use the Data.HashTable, it would
   pervade my program with IO. The alternative is an ideal hashmap that never
   gets changed. This program creates a dictionary at start which then is 
   only
   being used to read from: an ideal application for the Data.PerfectHash
   by Mark Wotton available on Hackage [3].
 
  If you are considering alternative data structures, you might want to
  look at tries or Bloom filters, both have O(n) lookup, both have
  Haskell implementations.  The latter is probably faster but
  probabilistic (i.e. it will occasionally fail to detect a
  misspelling - which you can of course check against a real
  dictionary).
 
 Using Bryan O'Sullivan's fantastic BloomFilter I got it down below
 Python's run time! Now it is 35.56s, 28% of the time is spent on GC,
 which I think means there is still some room for improvement.

One easy way to fix the GC time is to increase the default heap size.

 ./a.out +RTS -A200M 

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


Re: [Haskell-cafe] Re: haskelldb + sqlite problem.

2009-06-22 Thread John Goerzen
John Goerzen wrote:
 I do recall some discussion about data within a database; I don't recall
 one about the filename of it, which would certainly be a separate
 discussion.  I can see why a connectRaw or some such function could be

I have just pushed a patch to my git repo that adds connectSqlite3Raw to
help in these cases.

You can grab the diff directly here:

http://git.complete.org/hdbc-sqlite3?a=commitdiff_plain;h=0ef5df694d74cfaea7da3fcfc97037411d3f13bb

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


Re: [Haskell-cafe] coding standard question

2009-06-22 Thread Henning Thielemann


On Mon, 22 Jun 2009, Jules Bean wrote:


Miguel Mitrofanov wrote:

I so don't want to be the one supporting your code...


Well, that's lucky. Because you aren't.


I think the most frequent warning which denotes actually an error for me, 
is the 'unused identifier' warning, since there are often identifiers that 
I planned to use but forgot to use. The shadowing problem is less often a 
problem for me. When I refer to the wrong identifier this usually spotted 
by the type system, but the type system cannot find out the reason for the 
problem, namely two identifiers with the same name in the same scope. 
Sometimes I wish warnings would be emitted before (type) errors. For 
reading the code however it is a clear advantage to have separate names 
for separate things. The prime is not enough for me. Even more in a GHC 
error message, I often think identifier `bar'' refers to bar not 
bar'.

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


Re: [Haskell-cafe] coding standard question

2009-06-22 Thread Henning Thielemann


On Mon, 22 Jun 2009, Malcolm Wallace wrote:


Example:

 f a b = g (a+b) (b-a)
   where g a c = a*c

ghc warns that g's parameter a shadows the parameter to f.  So we
introduce a primed identifier to eliminate the warning:

 f a b = g (a+b) (b-a)
   where g a' c = a*c

Now, no warnings!  But, oops, this function does not do the same thing.
We forgot to add a prime to all occurrences of a on the right-hand-side.


Actually there will be the warning, that a' is unused.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Re: Optimizing spelling correction program

2009-06-22 Thread Bulat Ziganshin
Hello Don,

Tuesday, June 23, 2009, 1:22:46 AM, you wrote:

 One easy way to fix the GC time is to increase the default heap size.

  ./a.out +RTS -A200M 

to be exact, -A isn't a heap size - it's frequency of generation-1
collections. by default, collection perfromed every 512kbytes, tied to
L2 cache of CPUs

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

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


[Haskell-cafe] Re: haskelldb + sqlite problem.

2009-06-22 Thread GüŸnther Schmidt

Hi John,

let me first of all apologize, I didn't mean to criticize you, I'm sure 
you had good reasons for those changes, I'm merely mean to state how 
they did affect me after switching to HDBC 2.1.


Since after the rollback they no longer occurred I surmise that there is 
a connection.


The error that Magicloud describes I recall only occurring when an 
umlaut in the path to the database file, that may or may not be due to 
the utf8-wrapping or it may just be a problem of the sqlite3.dll. No 
harm in trying if it can be solved this way by just moving the database 
file to one without any non-ascii characters. While I don't think that 
umlauts actually cause Magiclouds problem I did notice that he signs his 
emails with Chinese symbols, quite possible thus, that he has paths on 
his machine with non-ascii characters.


Günther


John Goerzen schrieb:

Magicloud Magiclouds wrote:

Hi,
  I am using haskelldb and haskelldb-hdbc-sqlite3. Well, I finally got
the source compiled and ran, I got this error:
App: user error (SQL error: SqlError {seState = , seNativeError =
21, seErrorMsg = prepare 74: SELECT subject,\n   timestamp\nFROM
notes as T1\nORDER BY timestamp DESC: library routine called out of
sequence})
  Any clue what I should check? Thanks.


At the HDBC level, I would say:

I suspect that you have used a function that returns results lazily, but
haven't completely read them before calling back into the database with
something else.  As an example, you should probably use quickQuery'
instead of quickQuery, unless you are fully prepared to accept the
consequences of reading data lazily from a database.

I am not very familiar with HaskellDB, and can't really comment on what
it's doing under the hood.  If it is returning results to you lazily,
make sure you have completely consumed them before sending more queries
to the database.

If you can post some example code, it would likely help.

-- John



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


Re: [Haskell-cafe] Re: haskelldb + sqlite problem.

2009-06-22 Thread John Goerzen
GüŸnther Schmidt wrote:
 Hi John,
 
 let me first of all apologize, I didn't mean to criticize you, I'm sure 
 you had good reasons for those changes, I'm merely mean to state how 
 they did affect me after switching to HDBC 2.1.

No, I completely understand and I'm not offended; but I didn't want
people reading this message to get the wrong idea about the state of
Unicode support in HBDC.

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


[Haskell-cafe] Haskell on the iPhone

2009-06-22 Thread Ryan Trinkle
Dear Haskellers,

Recently, there's been a groundswell of activity in the Haskell community
regarding the Haskell's use in developing iPhone games.  The iPhone is a
powerful, innovative platform (with a great monetization scheme, to boot),
and it's not surprising that many of us would want to develop apps for it in
our favorite language.

I am proud to announce today that my company, iPwn Studios Inc., is
currently preparing to release an open source patch to GHC that allows it to
output binaries for iPhone OS.  The patch will be released under a BSD
license as soon as possible and hopefully integrated into the GHC main-line
in the near future.  As the first (to my knowledge) Haskell-based game
studio, iPwn Studios is committed to giving back to the Haskell community
through open source - contributing to a rising tide that lifts us all.

I would like to take this opportunity to propose the creation of a
haskell-iphone mailing list, so that all Haskellers working with the iPhone
- whether for profit or for pleasure - can come together to make Haskell a
force to be reckoned with in the burgeoning iPhone App marketplace.


Best wishes,
Ryan Trinkle
President, iPwn Studios Inc.

P.S.: If you wish to be involved in the preparation of the GHC patch or in
the creation of iPwn Studios' first game, don't hesitate to contact me by
email (ryant5...@gmail.com), AIM (RyanT5000), or IRC (RyanT5000 on
irc.freenode.net).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] FFI and heap memory usage limit

2009-06-22 Thread Marcin Kosiba
Hello,
Recently I've come across a certain GC/FFI-related problem. I've 
googled a 
bit, but didn't find anything specific.
I'm running certain simulations, which tend to allocate a lot of 
garbage in 
memory. Since this causes the OOM-killer to kill my simulation at 98% 
completion, I used the -M switch, and all was well.
But because my simulation results are fairly big, I needed to compress 
them 
with bz2 before sending them over the network. So I used bzlib.
Now this took an odd turn, because the simulation started crashing with 
out-of-memory errors _after_ completing (during bz2 compression). I'm fairly 
certain this is a GC/FFI bug, because increasing the max heap didn't help. 
Moving the bz2 compression to a separate process provided a reasonable 
solution.
What I think is happening is that after the simulation completes, 
almost all 
of the available memory (within the -M limit) is filled with garbage. Then I 
run bzlib which tries to allocate more memory (from behind FFI?) to compress 
the results, which in turn causes an out-of-memory error instead of 
triggering a GC collection.
I'm writing to ask if this is a known/fixed issue. I'm using ghc 
6.10.3, 
bzlib 0.5.0.0. If this is something new then I'll try to come up with a small 
program which demonstrates the problem.
--
Marcin Kosiba
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell on the iPhone

2009-06-22 Thread Jason Dagit
On Mon, Jun 22, 2009 at 3:30 PM, Ryan Trinkle ryant5...@gmail.com wrote:

 Dear Haskellers,

 Recently, there's been a groundswell of activity in the Haskell community
 regarding the Haskell's use in developing iPhone games.  The iPhone is a
 powerful, innovative platform (with a great monetization scheme, to boot),
 and it's not surprising that many of us would want to develop apps for it in
 our favorite language.

 I am proud to announce today that my company, iPwn Studios Inc., is
 currently preparing to release an open source patch to GHC that allows it to
 output binaries for iPhone OS.  The patch will be released under a BSD
 license as soon as possible and hopefully integrated into the GHC main-line
 in the near future.  As the first (to my knowledge) Haskell-based game
 studio, iPwn Studios is committed to giving back to the Haskell community
 through open source - contributing to a rising tide that lifts us all.


Hi Ryan,

This is great news!  Thanks!  Does iPwn have any up coming titles?  Perhaps
a blog where we could read about them so the advertising doesn't hit the
list.




 I would like to take this opportunity to propose the creation of a
 haskell-iphone mailing list, so that all Haskellers working with the iPhone
 - whether for profit or for pleasure - can come together to make Haskell a
 force to be reckoned with in the burgeoning iPhone App marketplace.


Sounds good to me.  Please post back here if it gets created.

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


Re: [Haskell-cafe] Haskell on the iPhone

2009-06-22 Thread Ryan Trinkle
Jason,

iPwn is currently in pre-production for its first title, which will be an
action-RPG reminiscent of Diablo and Fallout.  I'll try to keep the
shameless plugging on Haskell-cafe to a minimum, but I make no promises :P
I will definitely let people know when our website is put together in some
useful way.


Ryan

On Mon, Jun 22, 2009 at 18:34, Jason Dagit da...@codersbase.com wrote:



 On Mon, Jun 22, 2009 at 3:30 PM, Ryan Trinkle ryant5...@gmail.com wrote:

 Dear Haskellers,

 Recently, there's been a groundswell of activity in the Haskell community
 regarding the Haskell's use in developing iPhone games.  The iPhone is a
 powerful, innovative platform (with a great monetization scheme, to boot),
 and it's not surprising that many of us would want to develop apps for it in
 our favorite language.

 I am proud to announce today that my company, iPwn Studios Inc., is
 currently preparing to release an open source patch to GHC that allows it to
 output binaries for iPhone OS.  The patch will be released under a BSD
 license as soon as possible and hopefully integrated into the GHC main-line
 in the near future.  As the first (to my knowledge) Haskell-based game
 studio, iPwn Studios is committed to giving back to the Haskell community
 through open source - contributing to a rising tide that lifts us all.


 Hi Ryan,

 This is great news!  Thanks!  Does iPwn have any up coming titles?  Perhaps
 a blog where we could read about them so the advertising doesn't hit the
 list.




 I would like to take this opportunity to propose the creation of a
 haskell-iphone mailing list, so that all Haskellers working with the iPhone
 - whether for profit or for pleasure - can come together to make Haskell a
 force to be reckoned with in the burgeoning iPhone App marketplace.


 Sounds good to me.  Please post back here if it gets created.

 Jason


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


Re: [Haskell-cafe] Haskell on the iPhone

2009-06-22 Thread Don Stewart
If you're doing it in Haskell, please feel free to keep plugging.

A new market for Haskell apps is highly welcome.

ryant5000:
 Jason,
 
 iPwn is currently in pre-production for its first title, which will be an
 action-RPG reminiscent of Diablo and Fallout.  I'll try to keep the shameless
 plugging on Haskell-cafe to a minimum, but I make no promises :P  I will
 definitely let people know when our website is put together in some useful 
 way.
 
 
 Ryan
 
 On Mon, Jun 22, 2009 at 18:34, Jason Dagit da...@codersbase.com wrote:
 
 
 
 On Mon, Jun 22, 2009 at 3:30 PM, Ryan Trinkle ryant5...@gmail.com wrote:
 
 Dear Haskellers,
 
 Recently, there's been a groundswell of activity in the Haskell
 community regarding the Haskell's use in developing iPhone games.  The
 iPhone is a powerful, innovative platform (with a great monetization
 scheme, to boot), and it's not surprising that many of us would want 
 to
 develop apps for it in our favorite language.
 
 I am proud to announce today that my company, iPwn Studios Inc., is
 currently preparing to release an open source patch to GHC that allows
 it to output binaries for iPhone OS.  The patch will be released under
 a BSD license as soon as possible and hopefully integrated into the 
 GHC
 main-line in the near future.  As the first (to my knowledge)
 Haskell-based game studio, iPwn Studios is committed to giving back to
 the Haskell community through open source - contributing to a rising
 tide that lifts us all.
 
 
 Hi Ryan,
 
 This is great news!  Thanks!  Does iPwn have any up coming titles?  
 Perhaps
 a blog where we could read about them so the advertising doesn't hit the
 list.
  
 
 
 
 I would like to take this opportunity to propose the creation of a
 haskell-iphone mailing list, so that all Haskellers working with the
 iPhone - whether for profit or for pleasure - can come together to 
 make
 Haskell a force to be reckoned with in the burgeoning iPhone App
 marketplace.
 
 
 Sounds good to me.  Please post back here if it gets created.
 
 Jason
 
 
 

 ___
 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] FFI and heap memory usage limit

2009-06-22 Thread Bulat Ziganshin
Hello Marcin,

Tuesday, June 23, 2009, 2:31:13 AM, you wrote:

 Now this took an odd turn, because the simulation started crashing 
 with
 out-of-memory errors _after_ completing (during bz2 compression). I'm fairly
 certain this is a GC/FFI bug, because increasing the max heap didn't help.
 Moving the bz2 compression to a separate process provided a reasonable
 solution.
 What I think is happening is that after the simulation completes, 
 almost all
 of the available memory (within the -M limit) is filled with garbage. Then I
 run bzlib which tries to allocate more memory (from behind FFI?) to compress
 the results, which in turn causes an out-of-memory error instead of 
 triggering a GC collection.

i can propose a quick fix - alloc 10 mb using allocBytes before
starting your algorithm, and free it just before starting bzlib. it
may help

i agree that this looks like a deficiency of memory allocator. it's
better to write at ghc-users maillist (or at least make a copy to
Simon Marlow) to attract attention to your message

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

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


[Haskell-cafe] HaRe (the Haskell Refactorer) in action - short screencast

2009-06-22 Thread Claus Reinke
I've heard that many Haskellers know HaRe only as a rumour. It has 
been many years since the original project finished, and HaRe hasn't
been maintained for quite some time, so just pointing to the sources 
isn't quite the right answer. 


The sources are still available, and build with GHC 6.8.3 (I had to fix
one lineending issue on windows, iirc, and copy one old bug fix that
hadn't made it into the latest release), but there is currently noone with 
the time or funding for maintenance, fixing bugs, making releases, or 
ironing out practical issues. If anyone would provide funding, people to 
do the work could be found, but the effort would probably be better 
spent on reimplementing the ideas in a GHC / Cabal environment 
(instead of the Haskell'98 environment targetted by our Refactoring 
Functional Programs project). If you've got the funding, please get

in touch - even a three month run could get something started at least!-)

In principle, the project experiences and lessons learned are quite well 
documented at the project site 


   http://www.cs.kent.ac.uk/projects/refactor-fp/

but that doesn't give anyone an idea of what working with HaRe was 
like. With the recent interest in screencasts, I thought I'd make a little
demo, for archival purposes. Nothing fancy, using only features that 
were already present in HaRe 0.3 (end of 2004), and not all of those, 
on a tiny 2-module example (screenspace is a bit crowded to keep 
the text readable on YouTube). 

I hope it might give a rough idea of what the papers, slides and reports 
are talking about, for Haskellers who weren't around at the time:


   http://www.youtube.com/watch?v=4I7VZV7elnY

For the old HaRe team,
Claus

--- YouTube video description:
HaRe - the Haskell Refactorer (a mini demo) [4:10]

The Haskell Refactorer HaRe was developed in our EPSRC project 
   Refactoring Functional Programs 
   http://www.cs.kent.ac.uk/projects/refactor-fp/ 
Building on Programatica's Haskell-in-Haskell frontend and Strafunski's 
generic programming library, it supported module-aware refactorings 
over the full Haskell'98 language standard. Interfaces to the refactoring 
engine were provided for both Vim and Emacs (this demo uses HaRe 
via GVim on Windows).


While HaRe has continued to see occasional contributions by students 
and researchers, who use its Haskell program transformation API as a 
platform for their own work, it is not currently maintained. As the Haskell 
environment marches on, this demo is meant to record a snapshot of 
what working with HaRe could be like when it still built (here with GHC 6.8.3). 

The lessons learned (note, eg, the preservation of comments, and the 
limited use of pretty-printing, to minimize layout changes) are well 
documented at the project site, and should be taken into account 
when porting the ideas to the GHC Api, or other Haskell frontends.



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


Re: [Haskell-cafe] Haskell on the iPhone

2009-06-22 Thread Daniel Peebles
How exciting! I fully support the creation of a new mailing list about
iphone+haskell :)

On Mon, Jun 22, 2009 at 6:30 PM, Ryan Trinkleryant5...@gmail.com wrote:
 Dear Haskellers,

 Recently, there's been a groundswell of activity in the Haskell community
 regarding the Haskell's use in developing iPhone games.  The iPhone is a
 powerful, innovative platform (with a great monetization scheme, to boot),
 and it's not surprising that many of us would want to develop apps for it in
 our favorite language.

 I am proud to announce today that my company, iPwn Studios Inc., is
 currently preparing to release an open source patch to GHC that allows it to
 output binaries for iPhone OS.  The patch will be released under a BSD
 license as soon as possible and hopefully integrated into the GHC main-line
 in the near future.  As the first (to my knowledge) Haskell-based game
 studio, iPwn Studios is committed to giving back to the Haskell community
 through open source - contributing to a rising tide that lifts us all.

 I would like to take this opportunity to propose the creation of a
 haskell-iphone mailing list, so that all Haskellers working with the iPhone
 - whether for profit or for pleasure - can come together to make Haskell a
 force to be reckoned with in the burgeoning iPhone App marketplace.


 Best wishes,
 Ryan Trinkle
 President, iPwn Studios Inc.

 P.S.: If you wish to be involved in the preparation of the GHC patch or in
 the creation of iPwn Studios' first game, don't hesitate to contact me by
 email (ryant5...@gmail.com), AIM (RyanT5000), or IRC (RyanT5000 on
 irc.freenode.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] GHCi infers a type but refuses it as type signature

2009-06-22 Thread Eric
Hi haskell helpers,

I am new to haskell (but enthusiast).

I have begun to play with State and StateT, but this very simple
exercice has led me to a strange situation where GHCi recognises
and accepts the type of a function but GHC won't allow it as a
type signature. Here is the example (which is also a try at
literate haskell).

 import Control.Monad.State

 type Play = Char
 type Game = [Play]  -- a game is a series of plays  

Now, you play by issuing a char, and you win if you have played
an already played char. That was my first play function,
returning True if you win.

 play :: Play - State Game Bool
 play p = do ps - get
 put (p:ps)
 return $  p `elem` ps  

I tested this one this way:

 play_abc :: State Game Bool
 play_abc = do play 'a'
   play 'b'
   play 'c'
 
 play_abca :: State Game Bool
 play_abca = play_abc  play 'a'  

Now in GHCi,
runState play_abc []  yields (False, cba)
runState play_abca [] yields (True, acba)

Good! I was happy, now trying StateT to add IO to get
console input:

 type IOGame = StateT Game IO
 
 run_io :: IOGame Bool - IO (Bool, Game)
 run_io x = runStateT x []  

Now I wanted a version of play that
reads a char, on the following model:

 play_once :: IOGame Bool
 play_once = do x - liftIO getChar
play' x  

Of course I first tried to express play' using play, and failed.
Eventually I copied-and-pasted play, only changing the
type signature, and it worked:

 play' :: Play - IOGame Bool
 play' x = do xs - get
  put (x:xs)
  return $  x `elem` xs  

Now, on GHCi I was happy to type:
run_io $ play_once
or even
run_io $ play_once  play_once  play_once

However, how to avoid the code duplication?  I just tried
to remove the type signature, and yes, play2
suddenly works in both State Game and StateT Game IO: 

 play2 x = do xs - get
  put (x:xs)
  return $  x `elem` xs
 
 play2_abc :: State Game Bool
 play2_abc = play2 'a'  play2 'b'  play2 'c'

 play2_once :: IOGame Bool
 play2_once = do x - liftIO getChar
 play2 x  

So what's the type of play2?

:t play2 yields:
(MonadState [a] m, Eq a) = a - m Bool

Wow, nice, I get it now!
However if I try to add that type signature, or even the second,
more specific one below, ghci fails (signatures commented out
because of that):

 -- play3 :: (MonadState [a] m, Eq a) = a - m Bool
 -- play3 :: (MonadState Game m) = Play - m Bool
 play3 x = do xs - get
  put (x:xs)
  return $  x `elem` xs  

It seems that an extension is required:

Non type-variable argument in the constraint: MonadState [a] m
(Use -XFlexibleContexts to permit this)
In the type signature for `play3':
  play3 :: (MonadState [a] m, Eq a) = a - m Bool

So how is it possible that GHCi can infer (and use) a type that you
cannot use as signature?

And is it really non standard to avoid such code duplication?
I was a bit surprised that such simple example should require a
compiler extension.

Thanks!

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


Re: [Haskell-cafe] GHCi infers a type but refuses it as type signature

2009-06-22 Thread Felipe Lessa
On Tue, Jun 23, 2009 at 02:02:25AM +0200, Eric wrote:
 It seems that an extension is required:

 Non type-variable argument in the constraint: MonadState [a] m
 (Use -XFlexibleContexts to permit this)
 In the type signature for `play3':
   play3 :: (MonadState [a] m, Eq a) = a - m Bool

 So how is it possible that GHCi can infer (and use) a type that you
 cannot use as signature?

Simple: the definition of MonadState uses those extensions.

If the library was part of your code you would have had to turn
on some extensions, but you could have used them only on some
files (e.g. using LANGUAGE pragma).  Here the same thing is
happening, but the library is not part of your code.  Errr, not a
great explanation, but I HTH anyway. :)

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


[Haskell-cafe] ANN: haskell-src-exts-1.0.0

2009-06-22 Thread Niklas Broberg
Fellow Haskelleers,

It is with great pleasure I hereby announce the first stable release
of the haskell-src-exts package, version 1.0.0!

haskell-src-exts is a package for Haskell source code manipulation. In
particular it defines an abstract syntax tree representation, and a
parser and pretty-printer to convert between this representation and
String. It handles (almost(*)) all syntactic extensions to the Haskell
98 standard implemented by GHC, and the parsing can be parametrised on
what extensions to recognise.

I wish to thank the glorious Haskell community, for giving me the
chance to work on this project as part of Haskell.org's GSoC
programme, but also for simply being such a nice place to be! Special
thanks to everyone who helped me with testing and bug reports during
the final stretch of release candidates, in particular the many
excellent reports from Ganesh Sittampalam, Sebastian Fischer, and Neil
Mitchell who is also mentoring the project. You're all awesome!

haskell-src-exts-1.0.0:
=

Via cabal: cabal install haskell-src-exts-1.0.0
Via darcs: darcs get http://code.haskell.org/haskell-src-exts
On hackage: http://hackage.haskell.org/package/haskell-src-exts-1.0.0


Changes from 0.5.7, the last release candidate:
==

* CPP lines are no longer ignored, which means haskell-src-exts will
now invariably give a parse error on files with CPP pragmas in them.
CPP is not supported by haskell-src-exts, and this is more intuitive
than parsing e.g. all branches of an #if pragma, which is invariably
give unintended results.

* Fixed a stupid introduced bug where extensions passed int he parse
mode were ignored.

* fromParseOk is now exported, not just defined (doh).

* ScopedTypeVariables now implies TypeOperators, as per GHC. I'm sure
there are more implications that are missing from haskell-src-exts, I
will add them as I find out about them.


Thanks once again, and Happy Haskell Hacking to all!

Cheers,

/Niklas


(*) The only two exceptions are NewQualifiedOperators and UnicodeSyntax.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] STM/Data Invariant related Segfault with GHC 6.10.3

2009-06-22 Thread Bertram Felgenhauer
Jan Schaumlöffel wrote:
 I just discovered that programs compiled with GHC 6.10.3 segfault when
 accessing a TVar created under certain conditions.

This is a known bug, but it hasn't gotten much attention:

  http://hackage.haskell.org/trac/ghc/ticket/3049

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


[Haskell-cafe] Re: ANN: haskell-src-exts-1.0.0

2009-06-22 Thread Maurí­cio

It is with great pleasure I hereby announce the first stable release
of the haskell-src-exts package, version 1.0.0!


There's a kind of programming work that have great intelectual
impact, as it lets you see your code in diferent ways. Yours,
however, is of a special kind, as it has a physical impact on
those who use it. With haskell-src-exts, all the time I'm typing
Haskell I feel less pain in my fingers, since now I can get
beautifull pretty-printed code with no thumb pain. Haskell is
now a more pleasant experience.


It handles (almost(*)) all syntactic extensions to the Haskell
98 standard implemented by GHC, (...)



(*) The only two exceptions are NewQualifiedOperators and UnicodeSyntax.


How far is Unicode from beeing parsed? It doesn't seem to be
a huge step (from my ill-informed viewpoint), and it would
not let behind those who are happy to be able to declare names
in their own native language. (Oh, and sorry for resorting to
politically correct blackmail...)

Best,
Maurício

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


[Haskell-cafe] IMO ghc 6.8.2 misleading warning messages

2009-06-22 Thread Vasili I. Galchin
Hello,


For:

parseOptional = Parse.parseOptional

I got warning messages:

Swish/HaskellUtils/ParseURI.hs:77:4:
Warning: Defined but not used: `parseOptional'

Swish/HaskellUtils/ParseURI.hs:77:4:
Warning: Definition but no type signature for `parseOptional'
 Inferred type: parseOptional :: forall a b.
 Parse.Parser a [b] - [a] -
[([b], [a])]

IMO the warning messages should be reversed! (parseOptional was never used
.. called ... but I would strongly prefer the type signature warning first.

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


[Haskell-cafe] Re: Haskell on the iPhone

2009-06-22 Thread Benjamin L . Russell
On Mon, 22 Jun 2009 18:30:50 -0400, Ryan Trinkle ryant5...@gmail.com
wrote:

[...]

I would like to take this opportunity to propose the creation of a
haskell-iphone mailing list, so that all Haskellers working with the iPhone
- whether for profit or for pleasure - can come together to make Haskell a
force to be reckoned with in the burgeoning iPhone App marketplace.

This sounds like a great idea.  Please count my vote in favor of this
new mailing list.

-- Benjamin L. Russell
-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
Furuike ya, kawazu tobikomu mizu no oto. 
-- Matsuo Basho^ 

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


Re: [Haskell-cafe] Haskell on the iPhone

2009-06-22 Thread Ryan Trinkle
Rick,

I know some work has been done on JVM - iirc, Don Stewart did some work back
in the day, www.cse.unsw.edu.au/~pls/thesis/dons-thesis.ps.gz, but I'm not
sure how comprehensive it is.

Is anyone else interested in JVM-based Haskell targets?


Ryan

On Mon, Jun 22, 2009 at 20:42, Rick R rick.richard...@gmail.com wrote:

 This is definitely good news!

 So...  who's doing the Android/JVM target?  ;)



 On Mon, Jun 22, 2009 at 7:37 PM, Daniel Peebles pumpkin...@gmail.comwrote:

 How exciting! I fully support the creation of a new mailing list about
 iphone+haskell :)

 On Mon, Jun 22, 2009 at 6:30 PM, Ryan Trinkleryant5...@gmail.com wrote:
  Dear Haskellers,
 
  Recently, there's been a groundswell of activity in the Haskell
 community
  regarding the Haskell's use in developing iPhone games.  The iPhone is a
  powerful, innovative platform (with a great monetization scheme, to
 boot),
  and it's not surprising that many of us would want to develop apps for
 it in
  our favorite language.
 
  I am proud to announce today that my company, iPwn Studios Inc., is
  currently preparing to release an open source patch to GHC that allows
 it to
  output binaries for iPhone OS.  The patch will be released under a BSD
  license as soon as possible and hopefully integrated into the GHC
 main-line
  in the near future.  As the first (to my knowledge) Haskell-based game
  studio, iPwn Studios is committed to giving back to the Haskell
 community
  through open source - contributing to a rising tide that lifts us all.
 
  I would like to take this opportunity to propose the creation of a
  haskell-iphone mailing list, so that all Haskellers working with the
 iPhone
  - whether for profit or for pleasure - can come together to make Haskell
 a
  force to be reckoned with in the burgeoning iPhone App marketplace.
 
 
  Best wishes,
  Ryan Trinkle
  President, iPwn Studios Inc.
 
  P.S.: If you wish to be involved in the preparation of the GHC patch or
 in
  the creation of iPwn Studios' first game, don't hesitate to contact me
 by
  email (ryant5...@gmail.com), AIM (RyanT5000), or IRC (RyanT5000 on
  irc.freenode.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




 --
 The greatest obstacle to discovering the shape of the earth, the
 continents, and the oceans was not ignorance but the illusion of knowledge.

 - Daniel J. Boorstin


 ___
 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