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
   | otherwise = all (`elem` 1357) . show $ (n +
(read.reverse.show$n))
main = putStrLn . show . length . filter isReversible $ [1..100::Int]

ghc took 6s on this one, whereas jhc took 2 minutes real time (of
which 5s user time and 5s system time), which also froze the system
completely! Most probably it allocated a ton of memory, because the
system was very slow for a while after the program completed.

Same thing happened with a different but bigger number-crunching program.

Also: I tried to build a program that uses uvector, and for that I
needed an uvector.hl file: I unarchived the package and did this:
j...@jkff-laptop:~/.cabal/packages/hackage.haskell.org/uvector/0.1.0.4/uvector-0.1.0.4$
jhc --build-hl uvector.cabal
jhc --build-hl uvector.cabal
jhc 0.7.1 (0.7.0-13)
Creating library from description file: uvector.cabal
Reading: uvector.cabal
Finding Dependencies...
Using Ho Cache: '/home/jkff/.jhc/cache'
Typechecking...
Compiling...
Writing Library: uvector-0.1.0.4.hl
j...@jkff-laptop:~/.cabal/packages/hackage.haskell.org/uvector/0.1.0.4/uvector-0.1.0.4$
ls -l uvector-0.1.0.4.hl
-rw-r--r-- 1 jkff jkff 1248 2009-08-25 10:58 uvector-0.1.0.4.hl

(is it correct that actually no compilation occured at all?)

j...@jkff-laptop:~/projects/for-fun/haskell/mandelbrot$ jhc -p
/home/jkff/.cabal/packages/hackage.haskell.org/uvector/0.1.0.4/uvector-0.1.0.4/uvector-0.1.0.4.hl
Low.hs
jhc -p 
/home/jkff/.cabal/packages/hackage.haskell.org/uvector/0.1.0.4/uvector-0.1.0.4/uvector-0.1.0.4.hl
Low.hs
jhc 0.7.1 (0.7.0-13)
Finding Dependencies...
Using Ho Cache: '/home/jkff/.jhc/cache'
Library was not found
'/home/jkff/.cabal/packages/hackage.haskell.org/uvector/0.1.0.4/uvector-0.1.0.4/uvector-0.1.0.4.hl'

Now this seems strange.

The documentation to jhc was not of much help. What should be done to
use libraries from hackage?
Would it be hard to give jhc some integration with ghc's package.conf?

2009/8/25 John Meacham j...@repetae.net:
 Hi, I am happy to announce the jhc optimizing haskell compiler version 0.7.1.

 Information on installing jhc is here: 
 http://repetae.net/computer/jhc/building.shtml
 And the Main page is here:  http://repetae.net/computer/jhc

 There have been a lot of changes since the last public release, Some
 notable ones are:

  * The use of a general compiler cache by default rather than object
   files. This means work done by jhc is shared between projects, jhc
   uses cryptographic hashes internally to never compile the same piece of
   code more than once. This has numerous benefits, a notable one being
   speed.
  * Reworked library support. Jhc libraries are now much more general,
   when linking only the bits needed are loaded from the hl
   file, libraries are allowed to re-export modules from other
   libraries, making versioning or providing multiple interfaces to the
   same functionality a lot simpler. Library conflicts are 'lazy', like
   ambiguity errors now.
  * Updated Manual, clearer build instructions
  * Support for writing pure C libraries in Haskell.
  * numerous library updates, filled out many IO routines that were stubs
   before
  * Smart progress meters when compiler for a better user experience
  * performs all typechecking before compilation, for a faster
   edit-compile loop when writing code with jhc.
  * various bug fixes
  * Cross Compilation improvements, for instance you can compile for windows 
 transparently on
   a linux box. Or for an embedded target that is independent of the
   host.
  * Better Mac OSX Support, as both a host and target.


 If you are wondering about the large version number bump since the last
 release, It is because several versions were released only internally to
 the jhc list for testing. If you are interested in jhc, join the list at:
 http://www.haskell.org/mailman/listinfo/jhc

        John

 --
 John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
 ___
 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] 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 Dijkv.dijk@gmail.com 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 following also works:

 toList = ... induction (undefined :: n) ...
 fromList = ... induction (undefined :: n) ...

Yes, that's true.  But because we have lazy evaluation, witnessNat
never gets evaluated, so it doesn't matter :)

And I prefer to keep the (undefined/error) calls, along with
recursion, in my code to a minimum, since both of those can lead to
_|_ and runtime errors.  So, by keeping the calls to undefined and
the use of recursion limited to induction and witnessNat, I create
a very small 'trusted core' of code that has to be checked carefully
for errors.  Other code that uses these functions are entirely safe as
long as we keep those functions total and avoid explicit recursion.

This is why I called out fromJust in my example; it's the one use of
non-totality outside of the kernel.

 Although it looks like that a case analysis on 'n' is made at run-time in:

 instance Nat n = Nat (S n) where
   caseNat (S n) _ s = s n

 But I guess that is desugared away because 'S' is implemented as a newtype:

 newtype S n = S n

Yes, in my original post[1] I comment about this nicety; if I used
data instead of newtype I would have implemented it as
]  instance Nat Z where caseNat ~Z z _ = z
]  instance Nat n = Nat (S n) where caseNat ~(S n) _ s = s n

 Again, thanks very much for this!

 Do you mind if I use this code in the levmar package (soon to be
 released on hackage)?

No problem.  I hereby release this code under the WTFPL[2], version 2
with the no warranty clause.

  -- ryan

[1] Lightweight type-level dependent programming in Haskell.
http://www.haskell.org/pipermail/haskell-cafe/2009-June/062690.html
[2] http://sam.zoy.org/wtfpl/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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


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 it does what you what it to.

--

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TemplateHaskell #-}

module Rows where

import qualified Generics.EMGM as G
import Generics.EMGM.Derive

data Row = Row (Either (Maybe Int) (Maybe String)) (Either (Maybe Int)
(Maybe Float)) (Either (Maybe Int) (Maybe Integer))
  deriving Show

$(derive ''Row)

gmap :: (Rep (Everywhere' (Either (Maybe Int) (Maybe a))) Row) = (Either
(Maybe Int) (Maybe a) - Either (Maybe Int) (Maybe a)) - Row - Row
gmap = G.everywhere' -- top-down

readRow :: [String] - Row - Row
readRow l = gmap app
  where
app :: Either (Maybe Int) (Maybe String) - Either (Maybe Int) (Maybe
String)
app (Left (Just ri)) = Right (l `atMay` ri = G.read)
app x = x

atMay :: [a] - Int - Maybe a
atMay = undefined

--

This appears to implement your desired functionality. Here are some points
to note about what I did to get it working:

* EMGM has problems resolving type synonyms, so I expanded your E here.
* I just defined gmap to show what the type signature would be here. You
could get rid of gmap and just use everywhere'.
* I used everywhere' instead of everywhere, because you appear to want a
top-down traversal. Depending on your types, it may not matter.
* I gave app a concrete type signature, because as you noted, EMGM needs to
be non-polymorphic here.
* I also gave app a fallback case, so you don't get any unexpected surprises
at runtime.
* I used EMGM's read function [2] which seemed to be what you wanted for
readMay. You could still use readMay here, of course.

[1]
http://hackage.haskell.org/packages/archive/emgm/0.3.1/doc/html/Generics-EMGM-Functions-Everywhere.html
[2]
http://hackage.haskell.org/packages/archive/emgm/0.3.1/doc/html/Generics-EMGM-Functions-Read.html

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


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 Ingramryani.s...@gmail.com 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 #-}
 ...

Disturbing... I must admin it: I'll never be a Haskell Guru (tm).

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


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 some cases.


I think, the current implementation should left as it is. For fractional 
bases, no one would easily detect such imprecise results and report them 
as problem. So, it seems like people need a logarithm of integers, so they 
should be supplied with a special logarithm function for integers. For the 
other use cases, where 10 as base is one choice amongst a continuous set 
of rational numbers it would not be a problem to give the imprecise 
result. In the general case I would not accept a speed loss due to a check 
against 2 and 10 as base.


In dynamically typed languages like Python this might be different, 
because their users might not care much about types. It may not be 
important for them, whether a number is an integer or a floating point 
number that is accidentally integral. However, Python distinguishes 
between these two kinds of integers, but only dynamically.

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


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
 mathematical notation is heavily ambiguous and requires
 fairly sophisticated N.I. to parse correctly.

Thus I had the idea to do it the other round: Typeset formulas as
executable Haskell programs that can be converted and pretty printed by
LaTeX. lhs2TeX allows a bit of this procedure.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 possible to parse the output of course but the worry is always that
the format will change again.


2. In older jhc versions it was possible to specify .hl libraries by
name and version, eg jhc -p filepath-1.0.1.1. In the latest release it
is only possible by name. Is this intentional? I know jhc uses hashes to
uniquely identify installed packages, perhaps it should be possible to
specify packages by hash for the case that one has several instances of
the same package (possibly different versions, or built against
different versions of various dependencies).


3. Related to 1 and 2, what does the jhc --list-libraries output look
like when there are several packages of the same version but with a
different hash? Maybe a machine readable --list-libraries should list
the hash too.


4. Is there a way to get back the library/package description that jhc
bakes into the .hl files? There's a --show-ho. Perhaps we want a
--show-hl that dumps the library description? I guess that should also
tell us the package hash.


5. The ./configure doesn't check for the Haskell readline package.


Duncan

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


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 to the number of digits, doesn't 
it? If (show . length) is not fast enough, I would try to catch the 
magnitude by repeated squaring of 10. If you have found a 'k' with

   10^(2^k) = n  10^(2^(k+1))
 then you can start to find the exact number of digits with bisection.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 omit unneeded computations


-- 
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: 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 a small penalty.

  -- Lennart

On Tue, Aug 25, 2009 at 3:20 PM, Henning
Thielemannlemm...@henning-thielemann.de wrote:

 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 some cases.

 I think, the current implementation should left as it is. For fractional
 bases, no one would easily detect such imprecise results and report them as
 problem. So, it seems like people need a logarithm of integers, so they
 should be supplied with a special logarithm function for integers. For the
 other use cases, where 10 as base is one choice amongst a continuous set of
 rational numbers it would not be a problem to give the imprecise result. In
 the general case I would not accept a speed loss due to a check against 2
 and 10 as base.

 In dynamically typed languages like Python this might be different, because
 their users might not care much about types. It may not be important for
 them, whether a number is an integer or a floating point number that is
 accidentally integral. However, Python distinguishes between these two kinds
 of integers, but only dynamically.

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


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 Wottonmwot...@gmail.com 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 wrote:

 Hi,

 There is a mistake is logBase:

 $ ghci
 GHCi, version 6.10.4: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.
 Prelude logBase 10 10
 1.0
 Prelude logBase 10 100
 2.0
 Prelude logBase 10 1000
 2.9996                  --- rrgg!
 Prelude logBase 10 1
 4.0


 My host is a Debian GNU/Linux 5.0.2 (lenny) with the following GHC
 packages:

 ii  ghc6                                 6.10.4-1
 ii  ghc6-doc                             6.10.4-1
 ii  libghc6-mtl-dev                      1.1.0.2-7+b1
 ii  libghc6-utf8-string-dev              0.3.5-1+b1
 ii  libghc6-x11-dev                      1.4.5-6
 rc  libghc6-x11-doc                      1.4.2-1
 ii  libghc6-x11-xft-dev                  0.3-3+b3
 ii  libghc6-xmonad-contrib-dev           0.8.1-3+b3
 rc  libghc6-xmonad-contrib-doc           0.8-2
 ii  libghc6-xmonad-dev                   0.8.1-5

 Regards!


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

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

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


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.

 i think that `show` uses pretty the same way to build list of
 digits, so we just omit unneeded computations

I hope that 'show' will not need quadratic time but will employ a more
efficient algorithm that is certainly implemented in the GNU
multiprecision library. I assume that a division by 10^(2^k) will
require about 2^k * k operations. At least, it should be considerably
faster than repeatedly dividing by 10.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 will be a lot of
 Converting typeset mathematics into Haskell going on.

For completeness I want to add a pointer to other projects supporting
the semantic math web:
  http://kwarc.info/kohlhase/research.html

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


[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. Pages can be written
in (extended) markdown, reStructuredText, HTML, or LaTeX, and exported
in ten different formats. TeX math is rendered using MathML by default,
and syntax highlighting is provided for over fifty languages.

demo:   http://gitit.johnmacfarlane.net
manual: http://gitit.johnmacfarlane.net/README
api:http://hackage.haskell.org/package/gitit-0.6.1
code:   http://github.com/jgm/gitit
bugs:   http://code.google.com/p/gitit/issues/list
group:  http://groups.google.com/group/gitit-discuss

Here is how you can install and run gitit. You'll need GHC and
cabal-install. If you don't have these, install the Haskell Platform
http://hackage.haskell.org/platform/. Then:

cabal update
cabal install gitit
mkdir mywiki
cd mywiki
gitit  # now browse to http://localhost:5001

Or, if you want to change the defaults (say, reStructuredText
instead of markdown, or darcs instead of git):

gitit --print-default-config  gitit.conf
# edit gitit.conf, which is self-documenting
gitit -f gitit.conf

The whole code base has been overhauled since the last release.
Gitit is now faster, more memory efficient, more modular, and more
secure. It also has many new features, including

  - page metadata and categories
  - atom feeds (sitewide and per-page)
  - support for literate Haskell
  - a better configuration system
  - an improved caching system
  - a Haskell library exporting happstack wiki handlers
  - a plugin system

The last two items are the most exciting and deserve special comment.

First, in addition to providing an executable, gitit now provides a
library, Network.Gitit, which makes it easy to include a gitit
wiki (or many of them) in any happstack application. It is
even possible to use the containing application's authentication
system for the wiki.

Second, gitit can now be extended through plugins, short Haskell
programs that are loaded dynamically when the server starts. For
examples of the things that can be done with plugins, see the
plugins directory, which contains (among other things) a plugin
for adding graphviz diagrams to pages and a plugin for adding
interwiki links.  For a full description of the plugin system,
see the haddock documentation for Network.Gitit.Interface.

Full changes from version 0.5.3, as well as upgrade instructions,
are available in the file CHANGES.

Thanks are due to

- the happstack team, for big improvements in happstack-server
  that make it much easier to work with,

- the darcs team, for using gitit/darcsit for http://wiki.darcs.net,
  giving gitit a real-world test,

- Gwern Branwen, who helped to optimize gitit, wrote the
  InterwikiPlugin, and wrote the guts of the Feed module,

- Simon Michael, who contributed several patches,

- Henry Laxen, who added support for password resets and helped with
  the apache proxy instructions,

- Anton van Straaten, who made the process of page generation
  more modular by adding Gitit.ContentTransformer,

- Robin Green, who helped improve the plugin API and interface,
  fixed a security problem with the reset password code, and made
  saving of the user's file more robust,

- Thomas Hartman, who helped improve the index page, making directory
  browsing persistent,

- Kohei Ozaki, who contributed the ImgTexPlugin,

- mightybyte, who suggested making gitit available as a library,
  and contributed a patch to the authentication system,

- and everyone else who contributed suggestions and bug reports.

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


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 MacFarlanefiddlosop...@gmail.com 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 be updated either directly
 through the VCS or through gitit's web interface. Pages can be written
 in (extended) markdown, reStructuredText, HTML, or LaTeX, and exported
 in ten different formats. TeX math is rendered using MathML by default,
 and syntax highlighting is provided for over fifty languages.

 demo:   http://gitit.johnmacfarlane.net
 manual: http://gitit.johnmacfarlane.net/README
 api:    http://hackage.haskell.org/package/gitit-0.6.1
 code:   http://github.com/jgm/gitit
 bugs:   http://code.google.com/p/gitit/issues/list
 group:  http://groups.google.com/group/gitit-discuss

If anyone would like to see an example of gitit using the darcs
filestore (we affectionately call it 'darcsit'), you can take a look
at the darcs project wiki:
http://wiki.darcs.net/

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


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

2009-08-25 Thread Bryan O'Sullivan
2009/8/22 Roberto López plasterm...@hotmail.com


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


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

2009-08-25 Thread Robert Greayer
On Mon, Aug 24, 2009 at 5:24 PM, Don Stewartd...@galois.com 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 version of the library they're using
with something else, which can be accomplished by dynamically linked
libraries, but also means that if the rest of the program is open
source (but not GPL), the requirement is satisfied.  LGPL is generally
compatible with GPL-incompatible open-source, whether statically
linked or not.  It is true it is incompatible with closed source
licensing.

There are some real situations where this might matter -- you could
use this library in an an executable in which the remainder of the
source was MPL, I think, as long as there were the possibility of
relinking with a different version of the LGPL library.  You couldn't
do this if it were GPL.  This is the section of the LGPL that mentions
this:

Do one of the following:

* 0) Convey the Minimal Corresponding Source under the terms of
this License, and the Corresponding Application Code in a form
suitable for, and under terms that permit, the user to recombine or
relink the Application with a modified version of the Linked Version
to produce a modified Combined Work, in the manner specified by
section 6 of the GNU GPL for conveying Corresponding Source.
*1) Use a suitable shared library mechanism for linking with the
Library. A suitable mechanism is one that (a) uses at run time a copy
of the Library already present on the user's computer system, and (b)
will operate properly with a modified version of the Library that is
interface-compatible with the Linked Version.

So, Haskell libraries licensed under LGPL (without the static linking
exception) force option 0, but that doesn't make them completely
equivalent to GPL. At least that's my understanding (which could be
flawed!).

-Rob

 wei.hoo:
 I recommend Learn you a Haskell for great good:
 http://learnyouahaskell.com/functors-applicative-functors-and-monoids#applicative-functors

 On Sun, Aug 23, 2009 at 12:25 PM, Diego Souzadso...@bitforest.org wrote:
  A quick search pointed me to this:
  http://www.soi.city.ac.uk/~ross/papers/Applicative.html
 
  Is there any other resources you would suggest me to read?
 
  Thanks at lot,
  --
  ~dsouza
  yahoo!im: paravinicius
  gpg key fingerprint: 71B8 CE21 3A6E F894 5B1B  9ECE F88E 067F E891 651E
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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

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


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

2009-08-25 Thread Don Stewart
robgreayer:
 On Mon, Aug 24, 2009 at 5:24 PM, Don Stewartd...@galois.com 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 version of the library they're using
 with something else, which can be accomplished by dynamically linked
 libraries, but also means that if the rest of the program is open
 source (but not GPL), the requirement is satisfied.  LGPL is generally
 compatible with GPL-incompatible open-source, whether statically
 linked or not.  It is true it is incompatible with closed source
 licensing.
 
 There are some real situations where this might matter -- you could
 use this library in an an executable in which the remainder of the
 source was MPL, I think, as long as there were the possibility of
 relinking with a different version of the LGPL library.  You couldn't
 do this if it were GPL.  This is the section of the LGPL that mentions
 this:
 
 Do one of the following:
 
 * 0) Convey the Minimal Corresponding Source under the terms of
 this License, and the Corresponding Application Code in a form
 suitable for, and under terms that permit, the user to recombine or
 relink the Application with a modified version of the Linked Version
 to produce a modified Combined Work, in the manner specified by
 section 6 of the GNU GPL for conveying Corresponding Source.
 *1) Use a suitable shared library mechanism for linking with the
 Library. A suitable mechanism is one that (a) uses at run time a copy
 of the Library already present on the user's computer system, and (b)
 will operate properly with a modified version of the Library that is
 interface-compatible with the Linked Version.
 
 So, Haskell libraries licensed under LGPL (without the static linking
 exception) force option 0, but that doesn't make them completely
 equivalent to GPL. At least that's my understanding (which could be
 flawed!).


That's quite true. It's not completely equivalent. It is just very
difficult to distribute your Haskell app in such a way that it can be
relinked against LGPL licensed Haskell libraries.

If the intent is that the improvements to the source remain open, and
are contributed back, but you want to allow commercial use, a different
license would be appropriate.

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


[Haskell-cafe] Re: ANN: gitit 0.6.1

2009-08-25 Thread Eric Kow
 - the darcs team, for using gitit/darcsit for http://wiki.darcs.net,
   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 able to work
through the initial web spider hiccups.

It's great to be able to just
  darcs get --lazy http://wiki.darcs.net
and go!

-- 
Eric Kow http://www.nltg.brighton.ac.uk/home/Eric.Kow
PGP Key ID: 08AC04F9


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


[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. In the future I hope to add
some buffer or stream abstraction on top. Eventually, when GHC can
make use of epoll/kqueue etc. in addition to select, this library will
not be needed anymore. Until then it might be useful for applications
which monitor large numbers of file descriptors.

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


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

2009-08-25 Thread Ketil Malde
Steve stevech1...@yahoo.com.au 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.0415795826

Is there something special with this number?

  Python 2.6.2 (release26-maint, Apr 19 2009, 01:56:41) 
  [GCC 4.3.3] on linux2
  Type help, copyright, credits or license for more information.
   697.04157958259998
  697.04157958259998
   12345.678901234567890
  12345.678901234567

  GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
  Loading package base ... linking ... done.
  Prelude 697.04157958259998
  697.0415795826
  Prelude 12345.678901234567890
  12345.678901234567

So, Python manages to keep more decimals than GHC for your number, but
for other numbers, the precision appears to be the same.

-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 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 Parisfr...@theshire.org wrote:
 On Tue, Aug 25, 2009 at 12:07 AM, Ryan Ingramryani.s...@gmail.com wrote:
 {-# LANGUAGE GADTs, RankNTypes, TypeFamilies, ScopedTypeVariables, 
 FlexibleContexts #-}
 {-# LANGUAGE FlexibleInstances #-}

 Disturbing... I must admin it: I'll never be a Haskell Guru (tm).

That's funny, I consider GADTs, RankNTypes, and ScopedTypeVariables to
be the starting point for real code.  They just go at the top of the
file without thinking at this point.  (Well, sometimes I leave GADTs
out)

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


[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 08:54 ]:
 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. Pages can be written
 in (extended) markdown, reStructuredText, HTML, or LaTeX, and exported
 in ten different formats. TeX math is rendered using MathML by default,
 and syntax highlighting is provided for over fifty languages.
 
 demo:   http://gitit.johnmacfarlane.net
 manual: http://gitit.johnmacfarlane.net/README
 api:http://hackage.haskell.org/package/gitit-0.6.1
 code:   http://github.com/jgm/gitit
 bugs:   http://code.google.com/p/gitit/issues/list
 group:  http://groups.google.com/group/gitit-discuss
 
 Here is how you can install and run gitit. You'll need GHC and
 cabal-install. If you don't have these, install the Haskell Platform
 http://hackage.haskell.org/platform/. Then:
 
 cabal update
 cabal install gitit
 mkdir mywiki
 cd mywiki
 gitit  # now browse to http://localhost:5001
 
 Or, if you want to change the defaults (say, reStructuredText
 instead of markdown, or darcs instead of git):
 
 gitit --print-default-config  gitit.conf
 # edit gitit.conf, which is self-documenting
 gitit -f gitit.conf
 
 The whole code base has been overhauled since the last release.
 Gitit is now faster, more memory efficient, more modular, and more
 secure. It also has many new features, including
 
   - page metadata and categories
   - atom feeds (sitewide and per-page)
   - support for literate Haskell
   - a better configuration system
   - an improved caching system
   - a Haskell library exporting happstack wiki handlers
   - a plugin system
 
 The last two items are the most exciting and deserve special comment.
 
 First, in addition to providing an executable, gitit now provides a
 library, Network.Gitit, which makes it easy to include a gitit
 wiki (or many of them) in any happstack application. It is
 even possible to use the containing application's authentication
 system for the wiki.
 
 Second, gitit can now be extended through plugins, short Haskell
 programs that are loaded dynamically when the server starts. For
 examples of the things that can be done with plugins, see the
 plugins directory, which contains (among other things) a plugin
 for adding graphviz diagrams to pages and a plugin for adding
 interwiki links.  For a full description of the plugin system,
 see the haddock documentation for Network.Gitit.Interface.
 
 Full changes from version 0.5.3, as well as upgrade instructions,
 are available in the file CHANGES.
 
 Thanks are due to
 
 - the happstack team, for big improvements in happstack-server
   that make it much easier to work with,
 
 - the darcs team, for using gitit/darcsit for http://wiki.darcs.net,
   giving gitit a real-world test,
 
 - Gwern Branwen, who helped to optimize gitit, wrote the
   InterwikiPlugin, and wrote the guts of the Feed module,
 
 - Simon Michael, who contributed several patches,
 
 - Henry Laxen, who added support for password resets and helped with
   the apache proxy instructions,
 
 - Anton van Straaten, who made the process of page generation
   more modular by adding Gitit.ContentTransformer,
 
 - Robin Green, who helped improve the plugin API and interface,
   fixed a security problem with the reset password code, and made
   saving of the user's file more robust,
 
 - Thomas Hartman, who helped improve the index page, making directory
   browsing persistent,
 
 - Kohei Ozaki, who contributed the ImgTexPlugin,
 
 - mightybyte, who suggested making gitit available as a library,
   and contributed a patch to the authentication system,
 
 - and everyone else who contributed suggestions and bug reports.
 
 ___
 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 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 this works too. I guess the nontrivial bit to think of is the 
introduction of a fresh type (t in this case). Thanks for this insight!


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


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 Ingramryani.s...@gmail.com wrote:
 On Tue, Aug 25, 2009 at 6:07 AM, Cristiano Parisfr...@theshire.org wrote:
 On Tue, Aug 25, 2009 at 12:07 AM, Ryan Ingramryani.s...@gmail.com wrote:
 {-# LANGUAGE GADTs, RankNTypes, TypeFamilies, ScopedTypeVariables, 
 FlexibleContexts #-}
 {-# LANGUAGE FlexibleInstances #-}

 Disturbing... I must admin it: I'll never be a Haskell Guru (tm).

 That's funny, I consider GADTs, RankNTypes, and ScopedTypeVariables to
 be the starting point for real code.  They just go at the top of the
 file without thinking at this point.  (Well, sometimes I leave GADTs
 out)

It was not the pragmas, it was the type machinery that bit of scared me :)

Cristiano
___
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 two types are
 in fact non-equal.

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 /= b)

 You can use _|_ as negation:
  newtype Not p = Contr { contradiction :: forall a. p - a }
 
  nsymm :: Not (TEq a b) - Not (TEq b a)
  nsymm pf = Contr (contradiction pf . symm)

 We know by parametricity that contradiction n p isn't inhabited as
 its type is (forall a. a)

But in Haskell, we know that it _is_ inhabited, because every type is 
inhabited by bottom. And one way to access this element is with undefined.

 But I can't figure out a way to write this without error:
  notZeqS :: forall n. Not (TEq Z (S n))
  notZeqS = Contr (\x - x `seq` error impossible)

 As a first step, I'd like to write this:
  -- notZeqS = Contr (\TEq - error impossible)

Well, matching against TEq is not going to work. The way you do this in Agda, 
for instance, is:

  notZeqS :: forall n - Not (TEq Z (S n))
  notZeqS = Contr (\())

Where () is the 'absurd pattern'. It's used to indicate that argument is 
expected to have an uninhabited type, and if Agda can prove that it is 
uninhabited, then a lambda expression like the above denotes the empty 
function.

But Haskell has no such animal. You could kind of adapt it to empty case 
expressions:

  notZeqS = Contr (\pf - case pf of {})

And perhaps require that the type system can verify that the types of such 
cases are uninhabited except for bottom (although that isn't strictly 
necessary; you could leave it as simply desugaring to a catch-all call to 
error and it'd work), if that's even a feasible thing to do.

Currently, though, you'll get a parse error on }.

 but the compiler complains immediately about the pattern match being
 unsound: TEq.lhs:39:20:
 Couldn't match expected type `S n' against inferred type `Z'
 In the pattern: TEq
 In the first argument of `Contr', namely
 `(\ TEq - error impossible)'
 In the expression: Contr (\ TEq - error impossible)

 Is there any way to use the obvious unsoundness we get from (Z ~ S n) to
 generate a contradiction?

 Ideally I'd like to be able to implement
 ] natEqDec :: Nat a - Nat b - Either (TEq a b) (Not (TEq a b))

 as follows:
  predEq :: TEq (f a) (f b) - TEq a b
  predEq TEq = TEq
 
  natEqDec :: Nat a - Nat b - Either (TEq a b) (Not (TEq a b))
  natEqDec Nz Nz = Left TEq
  natEqDec (Ns a) (Ns b) = case natEqDec a b of
  Left TEq - Left TEq
  Right pf - Right $ Contr $ \eq - contradiction pf (predEq eq)
  natEqDec Nz (Ns _) = Right notZeqS
  natEqDec (Ns _) Nz = Right (nsymm notZeqS)

 Which compiles successfully, but the error call in notZeqS is a
 big wart.  Is there a better implementation of Not that allows us to
 avoid this wart?

You could build more complex, positive proofs of inequality (having a 3-way 
decision between m  n, m == n and m  n might be a good one), but I don't 
think you'll find a notion of negation that avoids some sort of call to 
undefined in GHC as it currently stands.

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


[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] haddock: parse error in doc string

2009-08-25 Thread Gwern Branwen
On Tue, Aug 25, 2009 at 8:30 PM, Peter Verswyvelenbugf...@gmail.com 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 choke. It could be using '*' inside some --s, it could be
something else. Haddock won't really say. Your best bet is the old
bisect/binary-search method: remove half the comments  retry,
narrowing it down until you've found the offending line and then
character. Then you can either remove it or read the Haddock manual
and see what the right thing looks like.

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


[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 a proper YAML file with a few
guarenteed fields, that will leave room for expansion later and
backwards compatability.

 2. In older jhc versions it was possible to specify .hl libraries by
 name and version, eg jhc -p filepath-1.0.1.1. In the latest release it
 is only possible by name. Is this intentional? I know jhc uses hashes to
 uniquely identify installed packages, perhaps it should be possible to
 specify packages by hash for the case that one has several instances of
 the same package (possibly different versions, or built against
 different versions of various dependencies).

Ah, this is an unintentional regression. I intended to keep the behavior
of being able to specify a library name/version or file name. Being able
to specify a hash is also a good idea.


 like when there are several packages of the same version but with a
 different hash? Maybe a machine readable --list-libraries should list
 the hash too.


 4. Is there a way to get back the library/package description that jhc
 bakes into the .hl files? There's a --show-ho. Perhaps we want a
 --show-hl that dumps the library description? I guess that should also
 tell us the package hash.

--show-ho will also work on hl files, which probably isn't mentioned
anywhere in the manual. I think I will add a verbose mode to
--list-libraries that will also spit out much of this meta-info (in the
aforementioned YAML format)

 5. The ./configure doesn't check for the Haskell readline package.

Yeah, I am currently only checking for the purpose of ghc 6.8/6.10
compatibility, but adding checks for all dependencies is a good idea.


As an aside, here are the principles that guided the design of the new
library system and ho cache. The main motivations were ameliorating two
notable shortcomings of jhc, its speed and compatibility with other
compilers:

 * Ho files will only affect speed of compilation, never results. No
   matter what. This allows the shared ho cache and decoupling the unit
   of caching from module granularity.

 * Only the interface of libraries explicitly mentioned on the command
   line shall affect code compiled by jhc. For instance, a libraries
   implementation can use an alternate prelude without hurting its
   compatibility with haskell 98 code.


 * From the users perspective, a library defines an interface, which is
   not necessarily coupled to the implementation. I have thought long
   and hard on the problem of being able to maintain some level of compatibility
   with ghc and hackage without sacrificing jhc's ability to innovate, or
   tying its development to the ghc libraries. Making libraries
   logical 'interfaces' rather than 'implementations' decouples
   compatibility issues from the compiler itself, anyone can write a
   library that emulates a particular interface.

   For instance, a compat-ghc-base3 library might have things like
   'Reexport: Compat.Haskell98.Prelude as Prelude, Compat.Ghc.Base3.Monad as
   Control.Monad, ... '.

   Or more interestingly, you might create your own library that does a
   'Reexport: MyApplicativePrelude as Prelude' to get your own prelude.

   (this is not fully realized yet in 0.7.1, but will be in a point
   release soon. The mechanism and framework is there though.)

 * Stateless. There is no such thing as hidden libraries, libraries
   mentioned on the command line are available, libraries not mentioned
   are not. Since libraries can re-export modules
   this won't cause a command line explosion. For instance, a
   -phaskell-platform could pull in and make available all the libraries
   in the haskell platform.

 * Adding libraries, even incompatible ones, won't break working builds
   unless said libraries are explicitly mentioned by the build in a
   non-precise way. This is necessary so a theoretical 'jhc-pkg' tool need
   only worry about adding required libraries, not cleaning up or worrying
   about finding consistent sets of libraries. A simple recursive download
   on dependencies suffices as a rudimentary cabal-install style tool.

 John

-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 can't work out what is wrong here.


If I give it a main (to humor it - it's not a solution), then it links  
and produces an executable - so it looks to me like I'm not telling  
the linker what I want correctly?


Any ideas?

Cheers,

Phil.


ghc -O2 --make -no-hs-main -package mtl   -package array -optl '- 
shared' FFI/Octave/MyInterface.c FFI/Octave/OptionInterface_stub.o FFI/ 
Octave/OptionInterface.o ./FrameworkInterface.o ./Maths/Prime.o ./ 
MonteCarlo/DataStructures.o ./MonteCarlo/European.o ./MonteCarlo/ 
Framework.o ./MonteCarlo/Interface.o ./MonteCarlo/Lookback.o ./Normal/ 
Acklam.o ./Normal/BoxMuller.o ./Normal/Framework.o ./Normal/ 
Interface.o ./Random/Framework.o ./Random/Halton.o ./Random/ 
Interface.o ./Random/Ranq1.o   -o FFI/Octave/libMyInterface.so

Linking FFI/Octave/libMyInterface.so ...
Undefined symbols:
  ___stginit_ZCMain, referenced from:
  ___stginit_ZCMain$non_lazy_ptr in libHSrts.a(Main.o)
  _ZCMain_main_closure, referenced from:
  _ZCMain_main_closure$non_lazy_ptr in libHSrts.a(Main.o)
ld: symbol(s) not found
collect2: ld returned 1 exit status

___
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 Ryan Ingram
Hi Dan, thanks for the great reply!  Some thoughts/questions follow.

On Tue, Aug 25, 2009 at 3:39 PM, Dan Doeldan.d...@gmail.com 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 /= b)

Yes, and as you see I immediately headed in that direction :)

 We know by parametricity that contradiction n p isn't inhabited as
 its type is (forall a. a)

 But in Haskell, we know that it _is_ inhabited, because every type is
 inhabited by bottom. And one way to access this element is with undefined.

Of course.  But it is uninhabited in the sense that if you case
analyze on it, you're guaranteed not to reach the RHS of the case.
Which is as close to uninhabited as you get in Haskell.

 Well, matching against TEq is not going to work. The way you do this in Agda,
 for instance, is:

  notZeqS :: forall n - Not (TEq Z (S n))
  notZeqS = Contr (\())

Yes, I had seen Agda's notation for this and I think it is quite
elegant.  Perhaps {} as a pattern in Haskell as an extension?  I'm
happy if it desugars into (\x - x `seq` undefined) after the
typechecker proves that x is uninhabited except by _|_.  (This
guarantees that undefined never gets evaluated and any
exception/infinite loop happens inside of x.)

In fact, I would be happy if there was a way to localize the call to
error to a single location, which could then be the center of a
trusted kernel of logic functions for inequality.  But right now it
seems that I need to make a separate notEq for each pair of concrete
types, which isn't really acceptable to me.

Can you think of any way to do so?

Basically what I want is this function:
   notEq :: (compiler can prove a ~ b is unsound) = Not (TEq a b)

Sadly, I think you are right that there isn't a way to write this in
current GHC.

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


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


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