Re: [Haskell-cafe] Snow Leopard Breaks GHC

2009-08-29 Thread Thomas Davie


If it is closed, it is fixed in the HEAD.


Any ideas how to get hold of a copy of HEAD, when my Haskell compiler  
currently outputs rubbish?


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


Re: [Haskell-cafe] Snow Leopard Breaks GHC

2009-08-29 Thread Dmitri Sosnik
Here - http://hackage.haskell.org/trac/ghc/wiki/Building, but it won't  
help, cause you need working ghc to build ghc.


D

On 29/08/2009, at 6:33 PM, Thomas Davie wrote:



If it is closed, it is fixed in the HEAD.


Any ideas how to get hold of a copy of HEAD, when my Haskell  
compiler currently outputs rubbish?


Bob
___
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] Edinburgh Saturday Meetup - we are here! (Henderson's)

2009-08-29 Thread Eric Y. Kow
Dear Haskellers,

Just for info, we are currently at Henderson's Cafe on Hanover St (just
around the corner from the RCPE).

If anybody needs to get in touch:
Eric - +44 75187 28483
Dougal - +44 7814 412539

More details on the wiki if we move:
http://www.haskell.org/haskellwiki/Hac7

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


pgp9L0swITMVt.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with monadic formlets

2009-08-29 Thread Jeremy Shaw
Hello,

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

- jeremy

At Fri, 28 Aug 2009 12:49:08 +0100,
Colin Paul Adams wrote:
 
  Colin == Colin Paul Adams co...@colina.demon.co.uk writes:
 
  Jeremy == Jeremy Shaw jer...@n-heptane.com writes:
 
 Colin apparent data corruprion is occurring. I am suspecting a
 Colin bug in the formlets library (I have version 0.6).
 
 Colin So I have created a slightly cut-down (no database
 Colin involved) complete working program. Can you see if this
 Colin works ok with your version of formlets:
 
 I managed to uninstall formlets-0.6 myself, and then installed 0.5
 instead. After adding the necessary extra argument to runFormletState
 (an empty string), the test program works fine. So this seems to be a
 bug in formlets-0.6.
 -- 
 Colin Adams
 Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Snow Leopard Breaks GHC

2009-08-29 Thread Max Bolingbroke
Hi,

If you compile with:

-opta -m32 -optl -m32

Then you can get GHC to produce binaries again.

WARNING: currently you cannot use this trick to build a Snow Leopard
compatible GHC using the HEAD snapshot at
http://www.haskell.org/ghc/dist/current/d ist/, because the most
recent (20090828) does not include the relevant patch. You have to use
HEAD directly, at least until the next packaged source release shows
up in that directory.

Once you have the source code from HEAD, you can add those flags to
SRC_HC_OPTS in your mk/build.mk and it should work. Disclaimer: I
haven't actually tried this yet.

Cheers,
Max

2009/8/29 Dmitri Sosnik dim...@gmail.com:
 Here - http://hackage.haskell.org/trac/ghc/wiki/Building, but it won't help,
 cause you need working ghc to build ghc.

 D

 On 29/08/2009, at 6:33 PM, Thomas Davie wrote:


 If it is closed, it is fixed in the HEAD.

 Any ideas how to get hold of a copy of HEAD, when my Haskell compiler
 currently outputs rubbish?

 Bob
 ___
 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] GUI library

2009-08-29 Thread Michael Mossey
I want to choose a GUI library for my project. Some background: I'm a 
beginner to functional programming and have been working through Haskell 
books for a few months now. I'm not just learning Haskell for s**ts and 
giggles; my purpose is to write music-composition-related code; in 
particular, I want to write a graphical musical score editor. (Why write my 
own editor, you may ask? Because I want to fully integrate it with 
computer-assisted-composition algorithms that I plan to write, also in 
Haskell.) I decided to use Haskell for its great features as a functional 
programming language.


Regarding a choice of GUI library, I want these factors:

- it needs to provide at a minimum a drawing surface, a place I can draw 
lines and insert characters, in addition to all the standard widgets and 
layout capabilities we have to come to expect from a GUI library.


- This is a Windows application.

- it needs to be non-confusing for an intermediate-beginner Haskeller. 
Hopefully good documentation and examples will exist on the web.


- It might be nice to have advanced graphics capability such as Qt 
provides, things like antialiasied shapes, and a canvas with efficient 
refresh (refereshes only the area that was exposed, and if your canvas 
items are only primitives, it can do refreshes from within C++ (no need to 
touch your Haskell code at all). However I'm wondering if qtHaskell fits my 
criteria well-documented and lots of examples aimed at beginners.


Thanks,
Mike
___
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-29 Thread Bertram Felgenhauer
Uwe Hollerbach wrote:
 Here's my version... maybe not as elegant as some, but it seems to
 work. For base 2 (or 2^k), it's probably possible to make this even
 more efficient by just walking along the integer as stored in memory,
 but that difference probably won't show up until at least tens of
 thousands of digits.
 
 Uwe
 
 ilogb :: Integer - Integer - Integer
 ilogb b n | n  0  = ilogb b (- n)
   | n  b  = 0
   | otherwise  = (up 1) - 1
   where up a = if n  (b ^ a)
   then bin (quot a 2) a
   else up (2*a)
 bin lo hi = if (hi - lo) = 1
then hi
else let av = quot (lo + hi) 2
 in if n  (b ^ av)
   then bin lo av
   else bin av hi

We can streamline this algorithm, avoiding the repeated iterated squaring
of the base that (^) does:

-- numDigits b n | n  0 = 1 + numDigits b (-n)
numDigits b n = 1 + fst (ilog b n) where
ilog b n
| n  b = (0, n)
| otherwise = let (e, r) = ilog (b*b) n
  in  if r  b then (2*e, r) else (2*e+1, r `div` b)

It's a worthwhile optimization, as timings on n = 2^100 show:

Prelude T length (show n)
301030
(0.48 secs, 17531388 bytes)
Prelude T numDigits 10 n
301030
(0.10 secs, 4233728 bytes)
Prelude T ilogb 10 n
301029
(1.00 secs, 43026552 bytes)

(Code compiled with -O2, but the interpreted version is just as fast; the
bulk of the time is spent in gmp anyway.)

Regards,

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


Re: [Haskell-cafe] Snow Leopard Breaks GHC

2009-08-29 Thread David Leimbach
Well if I build GHC on Leopard from HEAD and then copy it to Snow Leopard
would that not work?
Dave

On Sat, Aug 29, 2009 at 1:52 AM, Dmitri Sosnik dim...@gmail.com wrote:

 Here - http://hackage.haskell.org/trac/ghc/wiki/Building, but it won't
 help, cause you need working ghc to build ghc.

 D


 On 29/08/2009, at 6:33 PM, Thomas Davie wrote:


 If it is closed, it is fixed in the HEAD.


 Any ideas how to get hold of a copy of HEAD, when my Haskell compiler
 currently outputs rubbish?

 Bob
 ___
 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] Error during hlint install ?

2009-08-29 Thread Neil Mitchell
Hi Dusan,

  Am I doing something wrong if I get the following error during cabal
 installation of hlint? Is there any way how to solve it?

The problem is that version 1.15 of hscolour released recently is
incompatible with 1.13 which HLint was being tested against.

I've now switched over to hscolour 1.15 and released HLint 1.6.6,
which does work with hscolour 1.15. This should solve your problem.

I didn't spot this email as I've been busy recently and have not had a
chance to read through haskell-cafe, but I did get your personal email
(but replied to everyone so that everyone can see the solution). In
general when emailing about my packages it's usually best to email
haskell-cafe and CC me.

Thanks for reporting the issue, and do let me know if the new version
still doesn't work. To upgrade you should be able to do:

cabal update  cabal install hlint

Thanks

Neil



 I run on:
 Linux pc 2.6.30-ARCH #1 SMP PREEMPT Fri Jul 31 07:30:28 CEST 2009 x86_64
 Intel(R) Core(TM)2 Quad CPU Q9300 @ 2.50GHz GenuineIntel GNU/Linux
 The Glorious Glasgow Haskell Compilation System, version 6.10.4

 Error:
 cabal install hlint
 Resolving dependencies...
 Configuring hlint-1.6.5...
 Preprocessing executables for hlint-1.6.5...
 Building hlint-1.6.5...
 [ 1 of 25] Compiling Paths_hlint      ( dist/build/autogen/Paths_hlint.hs,
 dist/build/hlint/hlint-tmp/Paths_hlint.o )
 [ 2 of 25] Compiling Parallel         ( src/Parallel.hs,
 dist/build/hlint/hlint-tmp/Parallel.o )
 [ 3 of 25] Compiling HSE.Generics     ( src/HSE/Generics.hs,
 dist/build/hlint/hlint-tmp/HSE/Generics.o )
 [ 4 of 25] Compiling HSE.NameMatch    ( src/HSE/NameMatch.hs,
 dist/build/hlint/hlint-tmp/HSE/NameMatch.o )
 [ 5 of 25] Compiling Util             ( src/Util.hs,
 dist/build/hlint/hlint-tmp/Util.o )
 [ 6 of 25] Compiling HSE.Util         ( src/HSE/Util.hs,
 dist/build/hlint/hlint-tmp/HSE/Util.o )
 [ 7 of 25] Compiling HSE.Match        ( src/HSE/Match.hs,
 dist/build/hlint/hlint-tmp/HSE/Match.o )
 [ 8 of 25] Compiling HSE.Bracket      ( src/HSE/Bracket.hs,
 dist/build/hlint/hlint-tmp/HSE/Bracket.o )
 [ 9 of 25] Compiling HSE.Evaluate     ( src/HSE/Evaluate.hs,
 dist/build/hlint/hlint-tmp/HSE/Evaluate.o )
 [10 of 25] Compiling HSE.All          ( src/HSE/All.hs,
 dist/build/hlint/hlint-tmp/HSE/All.o )
 [11 of 25] Compiling CmdLine          ( src/CmdLine.hs,
 dist/build/hlint/hlint-tmp/CmdLine.o )
 [12 of 25] Compiling Type             ( src/Type.hs,
 dist/build/hlint/hlint-tmp/Type.o )
 [13 of 25] Compiling Hint.Naming      ( src/Hint/Naming.hs,
 dist/build/hlint/hlint-tmp/Hint/Naming.o )
 [14 of 25] Compiling Hint.Bracket     ( src/Hint/Bracket.hs,
 dist/build/hlint/hlint-tmp/Hint/Bracket.o )
 [15 of 25] Compiling Hint.Lambda      ( src/Hint/Lambda.hs,
 dist/build/hlint/hlint-tmp/Hint/Lambda.o )
 [16 of 25] Compiling Hint.Monad       ( src/Hint/Monad.hs,
 dist/build/hlint/hlint-tmp/Hint/Monad.o )
 [17 of 25] Compiling Hint.ListRec     ( src/Hint/ListRec.hs,
 dist/build/hlint/hlint-tmp/Hint/ListRec.o )
 [18 of 25] Compiling Hint.List        ( src/Hint/List.hs,
 dist/build/hlint/hlint-tmp/Hint/List.o )
 [19 of 25] Compiling Hint.Match       ( src/Hint/Match.hs,
 dist/build/hlint/hlint-tmp/Hint/Match.o )
 [20 of 25] Compiling Settings         ( src/Settings.hs,
 dist/build/hlint/hlint-tmp/Settings.o )
 [21 of 25] Compiling Report           ( src/Report.hs,
 dist/build/hlint/hlint-tmp/Report.o )

 src/Report.hs:49:22:
   Couldn't match expected type `String' against inferred type `Bool'
   In the second argument of `hscolour', namely `True'
   In the expression: hscolour False True 
   In the definition of `code': code = hscolour False True 
 cabal: Error: some packages failed to install:
 hlint-1.6.5 failed during the building phase. The exception was:
 exit: ExitFailure 1


 Regards

  Dušan


 P.S.
 Registered packages:
 Cabal-1.6.0.3, HUnit-1.2.0.3, QuickCheck-1.2.0.0, array-0.2.0.0,
   base-3.0.3.1, base-4.1.0.0, bytestring-0.9.1.4, containers-0.2.0.1,
   cpphs-1.8, directory-1.0.0.3, (dph-base-0.3), (dph-par-0.3),
   (dph-prim-interface-0.3), (dph-prim-par-0.3), (dph-prim-seq-0.3),
   (dph-seq-0.3), extensible-exceptions-0.1.1.0, filepath-1.1.0.2,
   (ghc-6.10.4), ghc-prim-0.1.0.0, haddock-2.4.2, haskell-src-1.0.1.3,
   haskell-src-exts-1.0.1, haskell98-1.0.1.0, hpc-0.5.0.3,
   hscolour-1.15, html-1.0.1.2, integer-0.1.0.1, mtl-1.1.0.2,
   network-2.2.1.2, old-locale-1.0.0.1, old-time-1.0.0.2,
   packedstring-0.1.0.1, parallel-1.1.0.1, parsec-2.1.0.1,
   pretty-1.0.1.0, process-1.0.1.1, random-1.0.0.1,
   regex-base-0.72.0.2, regex-compat-0.71.0.1, regex-posix-0.72.0.3,
   rts-1.0, stm-2.1.1.2, syb-0.1.0.1, template-haskell-2.3.0.1,
   time-1.1.4, uniplate-1.2.0.3, unix-2.3.2.0, xhtml-3000.2.0.1

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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org

Re: [Haskell-cafe] GUI library

2009-08-29 Thread Michael Mossey



Hi Jean-Denis,

Thanks for the information. Do you know how WxHaskell fits my needs? For 
example, does it have good docs and examples for a beginner? Does it have 
the ability to draw lines and characters on a surface? Does it have a type 
of canvas which usually refers to an optimized drawing surface?


Thanks,
Mike


Jean-Denis Koeck wrote:

I began writing a commercial app with a GUI using Gtk2hs,
but it looked ugly on Windows. I'm switching to WxHaskell.

2009/8/29 Michael Mossey m...@alumni.caltech.edu 
mailto:m...@alumni.caltech.edu


I want to choose a GUI library for my project. Some background: I'm
a beginner to functional programming and have been working through
Haskell books for a few months now. I'm not just learning Haskell
for s**ts and giggles; my purpose is to write
music-composition-related code; in particular, I want to write a
graphical musical score editor. (Why write my own editor, you may
ask? Because I want to fully integrate it with
computer-assisted-composition algorithms that I plan to write, also
in Haskell.) I decided to use Haskell for its great features as a
functional programming language.

Regarding a choice of GUI library, I want these factors:

- it needs to provide at a minimum a drawing surface, a place I can
draw lines and insert characters, in addition to all the standard
widgets and layout capabilities we have to come to expect from a GUI
library.

- This is a Windows application.

- it needs to be non-confusing for an intermediate-beginner
Haskeller. Hopefully good documentation and examples will exist on
the web.

- It might be nice to have advanced graphics capability such as Qt
provides, things like antialiasied shapes, and a canvas with
efficient refresh (refereshes only the area that was exposed, and if
your canvas items are only primitives, it can do refreshes from
within C++ (no need to touch your Haskell code at all). However I'm
wondering if qtHaskell fits my criteria well-documented and lots
of examples aimed at beginners.

Thanks,
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org mailto: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] GUI library

2009-08-29 Thread Jason Dagit
On Sat, Aug 29, 2009 at 8:03 AM, Michael Mosseym...@alumni.caltech.edu wrote:
 I want to choose a GUI library for my project. Some background: I'm a
 beginner to functional programming and have been working through Haskell
 books for a few months now. I'm not just learning Haskell for s**ts and
 giggles; my purpose is to write music-composition-related code; in
 particular, I want to write a graphical musical score editor. (Why write my
 own editor, you may ask? Because I want to fully integrate it with
 computer-assisted-composition algorithms that I plan to write, also in
 Haskell.) I decided to use Haskell for its great features as a functional
 programming language.

 Regarding a choice of GUI library, I want these factors:

 - it needs to provide at a minimum a drawing surface, a place I can draw
 lines and insert characters, in addition to all the standard widgets and
 layout capabilities we have to come to expect from a GUI library.

 - This is a Windows application.

 - it needs to be non-confusing for an intermediate-beginner Haskeller.
 Hopefully good documentation and examples will exist on the web.

 - It might be nice to have advanced graphics capability such as Qt provides,
 things like antialiasied shapes, and a canvas with efficient refresh
 (refereshes only the area that was exposed, and if your canvas items are
 only primitives, it can do refreshes from within C++ (no need to touch your
 Haskell code at all). However I'm wondering if qtHaskell fits my criteria
 well-documented and lots of examples aimed at beginners.

I've never used it myself, but if you're going to be drawing a lot
perhaps cairo is right for you?
http://cairographics.org/hscairo/

I suspect you'll have to be self-taught here.  Gtk2Hs and WxHaskell
are probably the most mature gui libs for Haskell.  Yet with either
one you may end up dropping down into GDI/GDI+ or opengl on windows to
get what you want.  GDI/GDI+ is confusing in any language, but good
books/resources do exist.  So perhaps the trick here is to translate
good documentation from other languages/sources into Haskell examples.
 You could do this as a warm up exercise before starting on your music
editor.

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


[Haskell-cafe] Composition of n-arity functions

2009-08-29 Thread Bas van Dijk
Hello,

In the levmar binding[1][2] me and my brother are working on, I need a
function composition operator that is overloaded to work on functions
of any arity. Basically its type needs to be something like the
following:

(.*) :: (b - c) - NFunction n a b - NFunction n a c

where 'NFunction n a b' represents the function 'a_0 - a_1 - ... - a_n - b'

I have written the following implementation:

(my question to this list is below)

-- Begin ---

{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleContexts #-}

module ComposeN where


-- Type-level naturals (from an idea by Ryan Ingram)


data Z = Z
newtype S n = S n

type N0 = Z
type N1 = S N0
type N2 = S N1
type N3 = S N2

class Nat n where
   caseNat :: forall r.
  n
   - (n ~ Z = r)
   - (forall p. (n ~ S p, Nat p) = p - r)
   - r

instance Nat Z where
   caseNat _ z _ = z

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

induction :: forall p n. Nat n
  = n
  - p Z
  - (forall x. Nat x = p x - p (S x))
  - p n
induction n z s = caseNat n isZ isS
where
  isZ :: n ~ Z = p n
  isZ = z

  isS :: forall x. (n ~ S x, Nat x) = x - p n
  isS x = s (induction x z s)

newtype Witness x = Witness { unWitness :: x }

witnessNat :: forall n. Nat n = n
witnessNat = theWitness
where
  theWitness = unWitness $ induction (undefined `asTypeOf` theWitness)
 (Witness Z)
 (Witness . S . unWitness)



-- N-arity functions


-- | A @NFunction n a b@ is a function which takes @n@ arguments of
-- type @a@ and returns a @b...@.
-- For example: NFunction (S (S (S Z))) a b ~ (a - a - a - b)
type family NFunction n a b :: *

type instance NFunction Z a b = b
type instance NFunction (S n) a b = a - NFunction n a b

-- | @f .* g@ composes @f@ with the /n/-arity function @g...@.
(.*) :: forall n a b c. (ComposeN n) = (b - c) - NFunction n a b -
NFunction n a c
(.*) = compose (witnessNat :: n) (undefined :: a)

infixr 9 .* -- same as .

class Nat n = ComposeN n where
compose :: forall a b c. n - a -
   (b - c) - NFunction n a b - NFunction n a c

-- Note that the 'n' and 'a' arguments to 'compose' are needed so that the type
-- checker has enough information to select the right 'compose' instance.

instance ComposeN Z where
compose Z _ = ($)

instance ComposeN n = ComposeN (S n) where
compose (S n) (_ :: a) f g = compose n (undefined :: a) f . g



-- Test


foo :: NFunction N3 Integer Integer
foo x y z = x + y + z

bar :: Integer - Integer
bar k = k - 1

test1 = compose (witnessNat :: N3)
(undefined  :: Integer)
bar foo 1 2 3

test2 = (bar .* foo) 1 2 3


-- The End -

The problem is test1 type checks and evaluates to 5 as expected but
test2 gives the following type error:

Couldn't match expected type `NFunction n a Integer'
   against inferred type `Integer - Integer - Integer - Integer'
In the second argument of `(.*)', namely `foo'

However if I ask ghci to infer the type of (bar .* foo) I get:

*ComposeN:t (bar .* foo)
(bar .* foo)
  :: (Integer - Integer - Integer - Integer
~
  NFunction n a Integer,
  ComposeN n) =
 NFunction n a Integer

Here we see that the context contains the type equality:

(Integer - Integer - Integer - Integer ~ NFunction n a Integer

So why is ghci unable to match the expected type `NFunction n a Integer'
against the inferred type `Integer - Integer - Integer - Integer'
while the context contains just this equality?

regards,

Bas

[1] http://code.haskell.org/~basvandijk/code/bindings-levmar/
[2] http://code.haskell.org/~basvandijk/code/levmar/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Composition of n-arity functions

2009-08-29 Thread Daniel Peebles
As far as I can tell, it's because the NFunction type family isn't (at
least from GHC's point of view) invertible. Data families are
injective, but type families need not be, so it's quite fine for you
to write something like

type instance TypeFunction A = Q
type instance TypeFunction B = Q

Now if you try to say that TypeFunction n should unify with Q, what
should n be? There's the same issue with NFunction, in that it knows
how to make an n-ary function if you provide a type-level natural as a
parameter, but given an n-ary function, it doesn't know how to get the
type-level natural that corresponds to it back.

I don't really know of a solution to this, but it may be possible to
write an inverse type family to get the arity back. Not sure how
you'd tell GHC though. It'd be cool if in future we could have some
sort of annotation to declare that our type functions are injective,
without explicitly going to data families.

Hope this helps (and that I'm not completely wrong)!

Dan

On Sat, Aug 29, 2009 at 2:03 PM, Bas van Dijkv.dijk@gmail.com wrote:
 Hello,

 In the levmar binding[1][2] me and my brother are working on, I need a
 function composition operator that is overloaded to work on functions
 of any arity. Basically its type needs to be something like the
 following:

 (.*) :: (b - c) - NFunction n a b - NFunction n a c

 where 'NFunction n a b' represents the function 'a_0 - a_1 - ... - a_n - 
 b'

 I have written the following implementation:

 (my question to this list is below)

 -- Begin 
 ---

 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE FlexibleContexts #-}

 module ComposeN where

 
 -- Type-level naturals (from an idea by Ryan Ingram)
 

 data Z = Z
 newtype S n = S n

 type N0 = Z
 type N1 = S N0
 type N2 = S N1
 type N3 = S N2

 class Nat n where
   caseNat :: forall r.
              n
           - (n ~ Z = r)
           - (forall p. (n ~ S p, Nat p) = p - r)
           - r

 instance Nat Z where
   caseNat _ z _ = z

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

 induction :: forall p n. Nat n
          = n
          - p Z
          - (forall x. Nat x = p x - p (S x))
          - p n
 induction n z s = caseNat n isZ isS
    where
      isZ :: n ~ Z = p n
      isZ = z

      isS :: forall x. (n ~ S x, Nat x) = x - p n
      isS x = s (induction x z s)

 newtype Witness x = Witness { unWitness :: x }

 witnessNat :: forall n. Nat n = n
 witnessNat = theWitness
    where
      theWitness = unWitness $ induction (undefined `asTypeOf` theWitness)
                                         (Witness Z)
                                         (Witness . S . unWitness)


 
 -- N-arity functions
 

 -- | A @NFunction n a b@ is a function which takes @n@ arguments of
 -- type @a@ and returns a @b...@.
 -- For example: NFunction (S (S (S Z))) a b ~ (a - a - a - b)
 type family NFunction n a b :: *

 type instance NFunction Z     a b = b
 type instance NFunction (S n) a b = a - NFunction n a b

 -- | @f .* g@ composes @f@ with the /n/-arity function @g...@.
 (.*) :: forall n a b c. (ComposeN n) = (b - c) - NFunction n a b -
 NFunction n a c
 (.*) = compose (witnessNat :: n) (undefined :: a)

 infixr 9 .* -- same as .

 class Nat n = ComposeN n where
    compose :: forall a b c. n - a -
               (b - c) - NFunction n a b - NFunction n a c

 -- Note that the 'n' and 'a' arguments to 'compose' are needed so that the 
 type
 -- checker has enough information to select the right 'compose' instance.

 instance ComposeN Z where
    compose Z _ = ($)

 instance ComposeN n = ComposeN (S n) where
    compose (S n) (_ :: a) f g = compose n (undefined :: a) f . g


 
 -- Test
 

 foo :: NFunction N3 Integer Integer
 foo x y z = x + y + z

 bar :: Integer - Integer
 bar k = k - 1

 test1 = compose (witnessNat :: N3)
                (undefined  :: Integer)
                bar foo 1 2 3

 test2 = (bar .* foo) 1 2 3


 -- The End 
 -

 The problem is test1 type checks and evaluates to 5 as expected but
 test2 gives the following type error:

 Couldn't match expected type `NFunction n a Integer'
           against inferred type `Integer - Integer - Integer - Integer'
    In the second argument of `(.*)', namely `foo'

 However if I ask ghci to infer the type of (bar .* foo) I get:

 *ComposeN:t (bar .* foo)
 (bar .* foo)
 

Re: [Haskell-cafe] Error during hlint install ?

2009-08-29 Thread Dušan Kolář

Yes, it works fine, now.

Thank you!

Dušan

Neil Mitchell wrote:

Hi Dusan,

  

 Am I doing something wrong if I get the following error during cabal
installation of hlint? Is there any way how to solve it?



The problem is that version 1.15 of hscolour released recently is
incompatible with 1.13 which HLint was being tested against.

I've now switched over to hscolour 1.15 and released HLint 1.6.6,
which does work with hscolour 1.15. This should solve your problem.

I didn't spot this email as I've been busy recently and have not had a
chance to read through haskell-cafe, but I did get your personal email
(but replied to everyone so that everyone can see the solution). In
general when emailing about my packages it's usually best to email
haskell-cafe and CC me.

Thanks for reporting the issue, and do let me know if the new version
still doesn't work. To upgrade you should be able to do:

cabal update  cabal install hlint

Thanks

Neil
  


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


Re: [Haskell-cafe] Problem with monadic formlets

2009-08-29 Thread Jeremy Shaw
At Sat, 29 Aug 2009 15:46:42 +0100,
Chris Eidhof (formlets) wrote:
 
 Confirmed. checkM is broken, thanks for noticing! I'll have a look  
 into it, I'm not sure whether it can be fixed. I was thinking of  
 removing all the monadic stuff from the formlets. I think this will  
 make for a much cleaner interface, monadic checking can then be done  
 afterwards.

I am still a fan of (and use) this version of Form:

newtype Form xml m a = Form { deform :: Env - State FormState (Collector (m 
(Failing a)), xml, FormContentType) }

not sure how I would feel about the removal of 'm' from the
Collector. But 'xml' is nicer for me than 'm xml' because my collector
and xml generator are often in different monads. I can, of course make
them be in the same monad if I want:

type MyForm a = Form (IO XML) IO a

but I also have the option of just doing:

type MyForm a = Form (IO XML) IO a

or:

type MyForm a = Form (HSP XML) IO a

At present, I actually have my collector do all the validation and
update the database. As a use case, let's assume that the form is
creating a new user account. One possible error would be using a
username that is already in use. Doing that check requires a database
query. In fact, it seems best if it does a database update, so that
there is no race condition between checking if the name is in use, and
actually attempting to create the account with that username.

If you remove the ability to do IO in the collector, then I believe I
would need to:

 1. run the collector to do the pure part of the validation.

 2. if the pure part succeeds, use the returned value to do the impure
 validation

 3. if that fails, then redisplay the form using the same environment
 that I used for #1, but passing in the impure validation errors.

One potential drawback that I see with this is that it may make it
difficult to the pass the error messages back to the specific formlet
element that failed so that you can display the errors in-line.

[Note: the following discussion reflects the pre-0.6 design].

Currently the environment we pass in is something like:

type Env = [(String, Either String File)]

The first component of the tuple is the name of the element. aka,
input0, input1, etc.

I would propose that we also pass in a Failures argument:

type Failures = [(String, ErrorMsg)]

where the first component of the tuple is the name of the element
(input0, intpu1, etc) and the second element contains ErrorMsg.

or perhaps modify Env to:

type Env = [(String, (Maybe ErrorMsg, Either String File)]

We would need to modify the Failing data type to:

data Failing a = Failure [(String, ErrorMsg)] | Success a

so that Failures would contain their location. 

Not all errors correspond to a specific form element. Let's say that
you have 3 drop-down boxes that combine together to form a date
selector. You want to validate the result of all three combined to
make sure they picked a valid date, and if it is invalid, you produce
an error message for that group, not a specific element. The problem
then is that there is no 'location' that corresponds to that group, so
what do you put in the Failure tuple?

I think you can use freshName to generate an extra 'virtual' name that
corresponds to the group as a whole.

I have been meaning to prototype this in the near future and see if it
actually works. I'll try to get something worked up in the next two
weeks (my sister is getting married next week, so my schedule is
pretty full).

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


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

2009-08-29 Thread Uwe Hollerbach
Ouch! That is indeed an improvement... I don't recall all the details
of this codelet, but I think I got the seed off the net somewhere
(perhaps this list?), and it might well have been better originally.
So, brightly brightly and with beauty, I probably executed a
verschlimmbesserung. After a year and a half, I find I still have
almost no intuition about performance issues in haskell... guess I
have to practice more.

Uwe

On 8/29/09, Bertram Felgenhauer bertram.felgenha...@googlemail.com wrote:
 Uwe Hollerbach wrote:
 Here's my version... maybe not as elegant as some, but it seems to
 work. For base 2 (or 2^k), it's probably possible to make this even
 more efficient by just walking along the integer as stored in memory,
 but that difference probably won't show up until at least tens of
 thousands of digits.

 Uwe

 ilogb :: Integer - Integer - Integer
 ilogb b n | n  0  = ilogb b (- n)
   | n  b  = 0
   | otherwise  = (up 1) - 1
   where up a = if n  (b ^ a)
   then bin (quot a 2) a
   else up (2*a)
 bin lo hi = if (hi - lo) = 1
then hi
else let av = quot (lo + hi) 2
 in if n  (b ^ av)
   then bin lo av
   else bin av hi

 We can streamline this algorithm, avoiding the repeated iterated squaring
 of the base that (^) does:

 -- numDigits b n | n  0 = 1 + numDigits b (-n)
 numDigits b n = 1 + fst (ilog b n) where
 ilog b n
 | n  b = (0, n)
 | otherwise = let (e, r) = ilog (b*b) n
   in  if r  b then (2*e, r) else (2*e+1, r `div` b)

 It's a worthwhile optimization, as timings on n = 2^100 show:

 Prelude T length (show n)
 301030
 (0.48 secs, 17531388 bytes)
 Prelude T numDigits 10 n
 301030
 (0.10 secs, 4233728 bytes)
 Prelude T ilogb 10 n
 301029
 (1.00 secs, 43026552 bytes)

 (Code compiled with -O2, but the interpreted version is just as fast; the
 bulk of the time is spent in gmp anyway.)

 Regards,

 Bertram
 ___
 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] Hackage rankings : August 2009

2009-08-29 Thread Don Stewart
Monthly statistics on the most popular Haskell applications and
libraries on Hackage. August 2009 edition now up:


http://donsbot.wordpress.com/2009/08/29/haskell-popularity-rankings-september-2009/

-- Don
___
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-29 Thread Henning Thielemann
Bulat Ziganshin schrieb:
 Hello Henning,
 
 Tuesday, August 25, 2009, 7:01:24 PM, you wrote:
 
 I hope that 'show' will not need quadratic time but will employ a more
 efficient algorithm
 
 yes, you are right

I thought a little about it. If I had to implement that in GMP it could
be done quite fast in many cases: Count the number of bits, say it is
'k' and multiply with logBase 10 2. If 2^k and 2^(k+1)-1 have the same
number of decimal digits, we are done. Otherwise we have to process some
of the most significant bits. If the number is between n*2^k and
(n+1)*2^k-1 and both bounds have the same number of decimal digits
(logBase 10 n + k * logBase 10 2), we are also done. Only for numbers
close to powers of 10 we have to process the whole integer.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GUI library

2009-08-29 Thread Michael Mossey



Jason Dagit wrote:

I've never used it myself, but if you're going to be drawing a lot
perhaps cairo is right for you?
http://cairographics.org/hscairo/

I suspect you'll have to be self-taught here.  Gtk2Hs and WxHaskell
are probably the most mature gui libs for Haskell.  Yet with either
one you may end up dropping down into GDI/GDI+ or opengl on windows to
get what you want.  GDI/GDI+ is confusing in any language, but good
books/resources do exist.  So perhaps the trick here is to translate
good documentation from other languages/sources into Haskell examples.
 You could do this as a warm up exercise before starting on your music
editor.

Jason


Thanks, Jason. My drawing needs are pretty rudimentary. A music editor 
doesn't need much more than the ability to draw lines and characters. A 
nice addition would be antialiased curves such as Qt offers but that is 
optional. A so-called canvas sometimes offers optimized drawing updates, 
so the editor doesn't have to redraw the entire page if one portion of it 
changes. That is not strictly necessary, and in fact it wouldn't be hard to 
implement a bit of that functionality myself.


-Mike
___
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-29 Thread Edward Kmett
I have a version of this inside of the monoid library buried in the
Data.Ring.Semi.BitSet module:
http://comonad.com/haskell/monoids/dist/doc/html/monoids/src/Data-Ring-Semi-BitSet.html#hwm

http://comonad.com/haskell/monoids/dist/doc/html/monoids/src/Data-Ring-Semi-BitSet.html#hwmTo
do any better by walking the raw Integer internals you need to know the
'finger' size for the GMP for your platform, which isn't possible to do
portably.

-Edward Kmett


On Wed, Aug 26, 2009 at 10:42 AM, Uwe Hollerbach uhollerb...@gmail.comwrote:

 Here's my version... maybe not as elegant as some, but it seems to
 work. For base 2 (or 2^k), it's probably possible to make this even
 more efficient by just walking along the integer as stored in memory,
 but that difference probably won't show up until at least tens of
 thousands of digits.

 Uwe

 ilogb :: Integer - Integer - Integer
 ilogb b n | n  0  = ilogb b (- n)
  | n  b  = 0
  | otherwise  = (up 1) - 1
  where up a = if n  (b ^ a)
  then bin (quot a 2) a
  else up (2*a)
bin lo hi = if (hi - lo) = 1
   then hi
   else let av = quot (lo + hi) 2
in if n  (b ^ av)
  then bin lo av
  else bin av hi

 numDigits n = 1 + ilogb 10 n

 [fire up ghci, load, etc]

 *Main numDigits (10^1500 - 1)
 1500
 *Main numDigits (10^1500)
 1501
 ___
 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? (was: Is logBase right?)

2009-08-29 Thread Daniel Peebles
Although this isn't a very general approach, I just submitted a
patch to GHC (not yet merged) with a gmp binding to mpz_sizeinbase,
which would allow for very quick computation of number of digits in
any base.

On Sat, Aug 29, 2009 at 9:12 PM, Edward Kmettekm...@gmail.com wrote:
 I have a version of this inside of the monoid library buried in the
 Data.Ring.Semi.BitSet module:
 http://comonad.com/haskell/monoids/dist/doc/html/monoids/src/Data-Ring-Semi-BitSet.html#hwm
 To do any better by walking the raw Integer internals you need to know the
 'finger' size for the GMP for your platform, which isn't possible to do
 portably.
 -Edward Kmett

 On Wed, Aug 26, 2009 at 10:42 AM, Uwe Hollerbach uhollerb...@gmail.com
 wrote:

 Here's my version... maybe not as elegant as some, but it seems to
 work. For base 2 (or 2^k), it's probably possible to make this even
 more efficient by just walking along the integer as stored in memory,
 but that difference probably won't show up until at least tens of
 thousands of digits.

 Uwe

 ilogb :: Integer - Integer - Integer
 ilogb b n | n  0      = ilogb b (- n)
          | n  b      = 0
          | otherwise  = (up 1) - 1
  where up a = if n  (b ^ a)
                  then bin (quot a 2) a
                  else up (2*a)
        bin lo hi = if (hi - lo) = 1
                       then hi
                       else let av = quot (lo + hi) 2
                            in if n  (b ^ av)
                                  then bin lo av
                                  else bin av hi

 numDigits n = 1 + ilogb 10 n

 [fire up ghci, load, etc]

 *Main numDigits (10^1500 - 1)
 1500
 *Main numDigits (10^1500)
 1501
 ___
 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