Re: [Haskell-cafe] How to calculate de number of digits of an integer? (was: Is logBase right?)

2009-08-25 Thread George Pollard
You could also fudge the input: {-# LANGUAGE NoMonomorphismRestriction #-} log10 = floor . logBase 10 . (0.5+) . fromIntegral numDigits n | n < 0 = 1 + numDigits (-n) numDigits 0 = 1 numDigits n = 1 + log10 n -- checked [0..10^8], finding a counter-example is left as an exercise

Re: [Haskell-cafe] oauth in haskell - reviewers?

2009-08-25 Thread Diego Souza
I've found [obviously] a huge thread about licensing on haskell-c...@. After reading [most] of it, I realized the best thing to do is change the license and start using BSD3. -- ~dsouza yahoo!im: paravinicius gpg key fingerprint: 71B8 CE21 3A6E F894 5B1B 9ECE F88E 067F E891 651E

Re: [Haskell-cafe] Is it possible to prove type *non*-equality in Haskell?

2009-08-25 Thread Ryan Ingram
Hi Dan, thanks for the great reply! Some thoughts/questions follow. On Tue, Aug 25, 2009 at 3:39 PM, Dan Doel wrote: > Well, this isn't surprising; you wouldn't have it even in a more rigorous > proof environment. Instead, you'd have to make the return type something like > >  Either (a == b) (a

[Haskell-cafe] FFI link failing due to no main?

2009-08-25 Thread phil
Hi, After creating my stub objects etc using GHC, I'm trying to create a library with a C interface to some Haskell functions. I'm explicitly passing in -no-hs-main yet the linker still fails due to missing main? I'm sure I've had this working before with a slightly simpler example, but

[Haskell-cafe] Re: [Haskell] ANNOUNCE: jhc 0.7.1

2009-08-25 Thread John Meacham
On Tue, Aug 25, 2009 at 02:15:14PM +0100, Duncan Coutts wrote: > 1. Would it be possible to have a machine-readable form of: > jhc --list-libraries > > It's possible to parse the output of course but the worry is always that > the format will change again. Good Idea, I'll modify the output to be

Re: [Haskell-cafe] haddock: parse error in doc string

2009-08-25 Thread Gwern Branwen
On Tue, Aug 25, 2009 at 8:30 PM, Peter Verswyvelen wrote: > I'm getting the error mentioned in the subject, but without any indication > where in my file this error occurs. > What does this mean? > Thanks, > Peter It means exactly that - something in that file's comments is causing Haddock to chok

[Haskell-cafe] haddock: parse error in doc string

2009-08-25 Thread Peter Verswyvelen
I'm getting the error mentioned in the subject, but without any indication where in my file this error occurs. What does this mean? Thanks, Peter ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Is it possible to prove type *non*-equality in Haskell?

2009-08-25 Thread Dan Doel
On Tuesday 25 August 2009 6:03:31 pm Ryan Ingram wrote: > > proveEq :: Nat a -> Nat b -> Maybe (TEq a b) > > proveEq Nz Nz = return TEq > > proveEq (Ns a) (Ns b) = do > > TEq <- proveEq a b > > return TEq > > proveEq _ _ = Nothing > > But if you get "Nothing" back, there's no proof that the

[Haskell-cafe] Is it possible to prove type *non*-equality in Haskell?

2009-08-25 Thread Ryan Ingram
Short version: How can I get from (Z ~ S n) to a useful contradiction? Type equality coercions[1] let us write proofs in Haskell that two types are equal: > {-# LANGUAGE GADTs, RankNTypes, TypeFamilies #-} > {-# OPTIONS_GHC -Wall #-} > module TEq where > data TEq a b = (a ~ b) => TEq This provi

Re: [Haskell-cafe] How to convert a list to a vector encoding its length in its type?

2009-08-25 Thread Cristiano Paris
On Tue, Aug 25, 2009 at 7:15 PM, Ryan Ingram wrote: > On Tue, Aug 25, 2009 at 6:07 AM, Cristiano Paris wrote: >> On Tue, Aug 25, 2009 at 12:07 AM, Ryan Ingram wrote: {-# LANGUAGE GADTs, RankNTypes, TypeFamilies, ScopedTypeVariables, FlexibleContexts #-} {-# LANGUAGE FlexibleInstance

Re: [Haskell-cafe] How to convert a list to a vector encoding its length in its type?

2009-08-25 Thread Martijn van Steenbergen
David Menendez wrote: data SomeNat where SomeNat :: (Nat n) => n -> SomeNat toPeano :: Int -> SomeNat or, equivalently, by using a higher-order function. toPeano :: Int -> (forall n. Nat n => n -> t) -> t Nice! I thought the only way to create them was with a new datatype, but thi

[Haskell-cafe] Re: ANN: gitit 0.6.1

2009-08-25 Thread John MacFarlane
PS. I've put the library documentation here: http://gitit.johnmacfarlane.net/doc/gitit/index.html Does anyone understand why HackageDB is having trouble building filestore 0.3.2? http://hackage.haskell.org/packages/archive/filestore/0.3.2/logs/failure/ghc-6.10 John +++ John MacFarlane [Aug 25 09

Re: [Haskell-cafe] How to convert a list to a vector encoding its length in its type?

2009-08-25 Thread Ryan Ingram
On Tue, Aug 25, 2009 at 6:07 AM, Cristiano Paris wrote: > On Tue, Aug 25, 2009 at 12:07 AM, Ryan Ingram wrote: >>> {-# LANGUAGE GADTs, RankNTypes, TypeFamilies, ScopedTypeVariables, >>> FlexibleContexts #-} >>> {-# LANGUAGE FlexibleInstances #-} > Disturbing... I must admin it: I'll never be a Ha

Re: [Haskell-cafe] Re: Is logBase right?

2009-08-25 Thread Ketil Malde
Steve writes: > Also, I had a problem using floating point in Python where round(697.04157958254996, 10) > gave > 697.04157958259998 > Its been fixed in the latest versions of Python: round(697.04157958254996, 10) > 697.0415795825 > ghci> roundN 697.04157958254996 10 > 697.041579

[Haskell-cafe] ANN: epoll bindings 0.1.1

2009-08-25 Thread Toralf Wittner
Hi, I am pleased to announce the release of epoll bindings 0.1.1 available from: http://hackage.haskell.org/package/epoll Epoll is an I/O event notification facility for Linux similar to poll but with good scaling characteristics. Currently the bindings are fairly low level and close to the C API

[Haskell-cafe] Re: ANN: gitit 0.6.1

2009-08-25 Thread Eric Kow
> - the darcs team, for using gitit/darcsit for , > giving gitit a real-world test, I think other Darcs hackers will agree with me when I say that we're pretty thrilled with gitit (ahem, darcsit as Jason points out). Thanks to fantastic response by John and Gwern, we were

Re: [Haskell-cafe] oauth in haskell - reviewers?

2009-08-25 Thread Don Stewart
robgreayer: > On Mon, Aug 24, 2009 at 5:24 PM, Don Stewart wrote: > > I notice hoauth is packaged as LGPL. Since we use static linking in GHC, > > this makes it in practice GPL. Is that the intent? > > > > -- Don > > > > I don't think this is 100% true -- the requirement is to allow the end > user

Re: [Haskell-cafe] oauth in haskell - reviewers?

2009-08-25 Thread Robert Greayer
On Mon, Aug 24, 2009 at 5:24 PM, Don Stewart wrote: > I notice hoauth is packaged as LGPL. Since we use static linking in GHC, > this makes it in practice GPL. Is that the intent? > > -- Don > I don't think this is 100% true -- the requirement is to allow the end user the ability to replace the ve

Re: [Haskell-cafe] Re: Is logBase right?

2009-08-25 Thread Bryan O'Sullivan
2009/8/22 Roberto López > > You get the accuracy value in Perl, but there is the same problem in > Python. > It's a bit discouraging. > You don't get an accurate answer with Perl. It just lies to you to keep you happy in your ignorance. $ perl -e 'printf "%.22f\n", log(1000)/log(10);' 2.999

Re: [Haskell-cafe] ANN: gitit 0.6.1

2009-08-25 Thread Jason Dagit
Thanks John! On Tue, Aug 25, 2009 at 8:54 AM, John MacFarlane wrote: > I'm pleased to announce the release of gitit 0.6.1. > > Gitit is a wiki program that runs on happstack, the Haskell web > application server stack, and stores pages and other content in a > git or darcs filestore. The wiki can

[Haskell-cafe] ANN: gitit 0.6.1

2009-08-25 Thread John MacFarlane
I'm pleased to announce the release of gitit 0.6.1. Gitit is a wiki program that runs on happstack, the Haskell web application server stack, and stores pages and other content in a git or darcs filestore. The wiki can be updated either directly through the VCS or through gitit's web interface. Pa

Re: [Haskell-cafe] Re: Converting typeset mathematics into Haskell ?

2009-08-25 Thread Henning Thielemann
Bernd Brassel schrieb: > Sometimes the synchronicity of events is eery. Incidentally I have just > written a proposal for just such a project. > You can have a look at it at > > http://www-ps.informatik.uni-kiel.de/~bbr/WebOfProofs.html > > Although not directly mentioned in the proposal, there w

Re: [Haskell-cafe] How to calculate de number of digits of an integer?

2009-08-25 Thread Henning Thielemann
Bulat Ziganshin schrieb: > Hello Henning, > > Tuesday, August 25, 2009, 6:11:00 PM, you wrote: > >>> digits = iterate (`div` 10) >>> takeWhile (>0) >>> length > >> This needs quadratic time with respect to the number of digits, doesn't >> it? > > why? Because division by 10 needs linear time.

Re: [Haskell-cafe] Is logBase right?

2009-08-25 Thread Jeff Heard
I always thought that he who compares floating point numbers for equality was acting in tangent of reason... -- Jeff On Sat, Aug 22, 2009 at 4:02 AM, Mark Wotton wrote: > he who compares floating point numbers for equality is in a state of sin. > > mark > > On 22/08/2009, at 5:00 AM, Roberto wrot

Re: [Haskell-cafe] Re: Is logBase right?

2009-08-25 Thread Lennart Augustsson
I don't really care much one way or the other, but since C (math.h) provides functions for base 2 and base 10 with some additional accuracy, I wouldn't mind using them. For a constant base I'd expect the extra comparison to be constant folded, so that's ok. For a non-constant base there would be

Re[2]: [Haskell-cafe] How to calculate de number of digits of an integer? (was: Is logBase right?)

2009-08-25 Thread Bulat Ziganshin
Hello Henning, Tuesday, August 25, 2009, 6:11:00 PM, you wrote: >> digits = iterate (`div` 10) >>> takeWhile (>0) >>> length > This needs quadratic time with respect to the number of digits, doesn't > it? why? i think that `show` uses pretty the same way to build list of digits, so we just omi

Re: [Haskell-cafe] How to calculate de number of digits of an integer? (was: Is logBase right?)

2009-08-25 Thread Henning Thielemann
On Sat, 22 Aug 2009, Bulat Ziganshin wrote: Hello Roberto, Saturday, August 22, 2009, 9:19:26 PM, you wrote: I want to calculate the number of digits of a positive integer. I was fastest way digits = iterate (`div` 10) >>> takeWhile (>0) >>> length This needs quadratic time with respect

[Haskell-cafe] Re: [Haskell] ANNOUNCE: jhc 0.7.1

2009-08-25 Thread Duncan Coutts
On Mon, 2009-08-24 at 21:13 -0700, John Meacham wrote: > Hi, I am happy to announce the jhc optimizing haskell compiler version 0.7.1. Congratulations on getting a public release out. A few comments: 1. Would it be possible to have a machine-readable form of: jhc --list-libraries It's possib

Re: [Haskell-cafe] Converting typeset mathematics into Haskell ?

2009-08-25 Thread Henning Thielemann
Richard O'Keefe schrieb: > > On Aug 22, 2009, at 11:49 AM, Mark Wassell wrote: >> Think about how you would convert this into Haskell. You might then >> find yourself wondering why you have to convert it into Haskell at all. > > But very quickly you realise that it is because a lot of > mathemati

Re: [Haskell-cafe] Re: Is logBase right?

2009-08-25 Thread Henning Thielemann
On Sun, 23 Aug 2009, Lennart Augustsson wrote: You're absolutely right. It would be easy to change logBase to have special cases for, say, base 2 and base 10, and call the C library functions for those. In fact, I think it's a worth while change, since it's easy and get's better results for s

Re: [Haskell-cafe] How to convert a list to a vector encoding its length in its type?

2009-08-25 Thread Cristiano Paris
On Tue, Aug 25, 2009 at 12:07 AM, Ryan Ingram wrote: > unsafeCoerce is ugly and I wouldn't count on that working properly. > > Here's a real solution: > > >> {-# LANGUAGE GADTs, RankNTypes, TypeFamilies, ScopedTypeVariables, >> FlexibleContexts #-} >> {-# LANGUAGE FlexibleInstances #-} > ... Dist

Re: [Haskell-cafe] Generics for constructing Rows

2009-08-25 Thread Sean Leather
Hi Max, EMGM's > map demands traversion function to be non-polymorphic, i.e. type-checker > fails with the message, complaining it cannot match `E a` against > `E Name`, against `E Salary` etc. I'm wondering if you tried everywhere' (or everywhere) [1]. Here's one solution, but I'm not sure if i

Re: [Haskell-cafe] How to convert a list to a vector encoding its length in its type?

2009-08-25 Thread Ryan Ingram
Also, be aware that we are testing the edges of what the compiler supports for type families here. I ran into a bug in my initial implementation which I submitted as http://hackage.haskell.org/trac/ghc/ticket/3460 -- ryan ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] How to convert a list to a vector encoding its length in its type?

2009-08-25 Thread Ryan Ingram
On Mon, Aug 24, 2009 at 4:24 PM, Bas van Dijk wrote: > Thanks very much! I'm beginning to understand the code. > > The only thing I don't understand is why you need [witnessNat] > >> toList = ... induction (witnessNat :: n) ... >> fromList = ... induction (witnessNat :: n) ... > > However the follo

Re: [Haskell-cafe] ANNOUNCE: jhc 0.7.1

2009-08-25 Thread Eugene Kirpichov
WOW! Congratulations, I am impressed: I ran it on a small example program and jhc produced output that was 3x faster than ghc -O2! Serious stuff. However: I tried it on a different very simple program (a projecteuler one): module Main where isReversible n | n`mod`10 == 0 = False |