Re: How can I make a counter without Monad?

2005-03-16 Thread Nicolas Oury
Thanks for your help.
Are there other ways to implement a counter in Haskell?
Using a State monad?

If I use your example on :
test   = let Node x l = enumeratedTree ( Node 'a' [undefined, Node 'b' 
[]])
			in tail l

GHCI answers
[Node (*** Exception: Prelude.undefined
A monadic counter imposes an order of evaluation.
In my program, I don't care about the order of the numbers.
I only want them to be all different.
I think a monad is too restrictive for what I need.

From some of my code:
let enumeratedTree =
(`evalState` (0::Int)) $ (`mapTreeM` t) $
\x - do n - next
 return (n, x)
next = do a - get; put $! succ a; return a
where
mapTreeM :: Monad m = (a - m b) - Tree a - m (Tree b)
mapTreeM f (Node a ts) = do
b - f a
ts' - mapM (mapTreeM f) ts
return (Node b ts')
(which could also be an instance of a popular non-standard FunctorM
class)
Best regards
Tomasz
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: alpha problems with ghc 6.4

2005-03-16 Thread Simon Marlow
On 16 March 2005 04:14, Ian Lynagh wrote:

 An alpha build of ghc 6.4 quickly fails because of the
 
 #if alpha_TARGET_ARCH
 import PrimRep  ( getPrimRepSize, isFloatingRep )
 import Type ( typePrimRep )
 #endif
 
 in ghc/compiler/typecheck/TcForeign.lhs which no longer exist.
 Fortunately, the imported functions aren't used either.
 
 Unfortunately, the build then fails when it comes to try to compile
 this 
 same file as the typeMachRepRep function, used in this piece of code:
 
 \begin{code}
 #include nativeGen/NCG.h
 #if alpha_TARGET_ARCH
 checkFEDArgs arg_tys
   = check (integral_args = 32) err
   where
 integral_args = sum [ machRepByteWidth rep
 | (rep,hint) - map typeMachRepRep arg_tys,
   hint /= FloatHint ]
 err = ptext SLIT(On Alpha, I can only handle 4
 non-floating-point arguments to foreign export dynamic) #else
 checkFEDArgs arg_tys = returnM ()
 #endif
 \end{code}
 
 doesn't exist. Is this fixable?

I think you want to use something like typeMachRep in
deSugar/DsForeign.lhs.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How can I make a counter without Monad?

2005-03-16 Thread Tomasz Zielonka
On Wed, Mar 16, 2005 at 10:51:08AM +0100, Nicolas Oury wrote:
 
 Thanks for your help.
 
 Are there other ways to implement a counter in Haskell?
 
 Using a State monad?
 
 
 If I use your example on :
 
 test   = let Node x l = enumeratedTree ( Node 'a' [undefined, Node 'b' 
 []])
   in tail l
 
 GHCI answers
 [Node (*** Exception: Prelude.undefined
 A monadic counter imposes an order of evaluation.
 In my program, I don't care about the order of the numbers.
 I only want them to be all different.
 I think a monad is too restrictive for what I need.

OK, I understand. In this situation you probably want either splittable
name supply. Let me get back to your first post...

Best regards
Tomasz
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How can I make a counter without Monad?

2005-03-16 Thread Tomasz Zielonka
On Wed, Mar 16, 2005 at 01:17:51AM +0100, Nicolas Oury wrote:
 * linear implicit parameters
 
 instance Splittable Int where
   split n = (2*n,2*n+1)
 
 But I have a problem : the counter value increases exponentially. (I 
 can only count up to 32 elements...)
 
 Is there another way to split Int?

You could use unbounded Integers, or forget about numbers and use lists
of bits.

  newtype BitString = BitString [Bool]

  instance Splittable BitString where
split (BitString bs) = (BitString (False : bs), BitString (True : bs))

Best regards
Tomasz
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: ghc-pkg too happy to create ~/.ghc

2005-03-16 Thread Simon Marlow
Thanks, I've committed a version of your patch.

Cheers,
Simon

On 16 March 2005 04:07, Ian Lynagh wrote:

 The Debian autobuilders don't let you write to ~ (which seems
 reasonable, as they are only compiling the software, not running it),
 so 
 my builds are failing with
 
 --
 ==fptools== /usr/bin/make boot -wr;
  in /build/buildd/ghc6-6.4/ghc/rts
 [...]
 ../utils/ghc-pkg/ghc-pkg-inplace --force --update-package
 package.conf.inplace Creating user package database in
 /org/buildd/.ghc/sparc-linux-6.4/package.conf 
 
 Fail: createDirectory: permission denied (Permission denied)
 --
 
 The patch below fixes it. I'm not sure I understand why the code is
 written as it is, though. It looks to me like if any config file given
 by a FlagConfig is missing then the readFile in readParseDatabase is
 going to fall over. I don't know what should happen when modifying if
 there are -f options, so can't suggest a complete replacement.
 
 
 Thanks
 Ian
 
 
 --- ghc6-6.4.orig/ghc/utils/ghc-pkg/Main.hs
 +++ ghc6-6.4/ghc/utils/ghc-pkg/Main.hs
 @@ -269,10 +269,6 @@
 archdir   = appdir `joinFileName` subdir
 user_conf = archdir `joinFileName` package.conf
b - doesFileExist user_conf
 -  when (not b) $ do
 -   putStrLn (Creating user package database in  ++ user_conf)
 -   createDirectoryIfMissing True archdir
 -   writeFile user_conf emptyPackageConfig
 
let
 -- The semantics here are slightly strange.  If we are
 @@ -281,20 +277,23 @@
 -- If we are not modifying (eg. list, describe etc.) then
 -- the user database is included by default.
 databases
 - | modify = foldl addDB [global_conf] flags
 - | not modify = foldl addDB [user_conf,global_conf] flags
 + | modify || not b = foldl addDB [global_conf] flags
 + | not modify  = foldl addDB [user_conf,global_conf] flags
 
 -- implement the following rules:
 --  --user means overlap with the user database
 --  --global means reset to just the global database
 --  -f file means overlap with file
 -   addDB dbs FlagUser   = if user_conf `elem` dbs
 -   then dbs
 -   else user_conf : dbs
 +   addDB dbs FlagUser
 +| (modify || b)  (user_conf `notElem` dbs) = user_conf : dbs
 addDB dbs FlagGlobal = [global_conf]
 addDB dbs (FlagConfig f) = f : dbs
 addDB dbs _  = dbs
 
 +  when (not b  user_conf `elem` databases) $ do
 +   putStrLn (Creating user package database in  ++ user_conf)
 +   createDirectoryIfMissing True archdir
 +   writeFile user_conf emptyPackageConfig
db_stack - mapM readParseDatabase databases
return db_stack
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: [Haskell] RE: ANNOUNCE: GHC version 6.4

2005-03-16 Thread Simon Marlow
On 15 March 2005 18:26, Sebastian Sylvan wrote:

 Ah, that did it! However, some packages seem to be missing, like HGL
 for instance.
 rts-1.0, base-1.0, haskell98-1.0, template-haskell-1.0, unix-1.0,
 Cabal-1.0, parsec-1.0, haskell-src-1.0, network-1.0,
 QuickCheck-1.0, HUnit-1.1, mtl-1.0, fgl-5.2, OpenGL-2.0, stm-1.0,
 readline-1.0, (lang-1.0), (concurrent-1.0), (posix-1.0),
 (util-1.0), (data-1.0), (text-1.0), (net-1.0), (hssource-1.0)
 
 How would one go about just installing every damn package availble?

It looks like the configure machinery didn't detect the X11 libraries,
or for some other reason failed to build the X11 package and hence also
omitted the HGL package.

Could you send the full ./configure output?

Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How can I make a counter without Monad?

2005-03-16 Thread Nicolas Oury
Le 16 mars 05, à 11:08, Tomasz Zielonka a écrit :
On Wed, Mar 16, 2005 at 01:17:51AM +0100, Nicolas Oury wrote:
* linear implicit parameters
instance Splittable Int where
  split n = (2*n,2*n+1)
But I have a problem : the counter value increases exponentially. (I
can only count up to 32 elements...)
Is there another way to split Int?
You could use unbounded Integers, or forget about numbers and use lists
of bits.
  newtype BitString = BitString [Bool]
  instance Splittable BitString where
split (BitString bs) = (BitString (False : bs), BitString (True : 
bs))

Best regards
Tomasz
OK, I have written
instance Splittable Integer where
  split n = (2*n,2*n+1)
foo::(%x::Integer) = [a] - [(a,Integer)]
foo [] = []
foo (a:l) = (a,%x):(foo l)
test = let %x = 1 in foo [1..15000]
But, in this example, the numbering is linear and so test becomes 
quadratic.
The main complexity of the program come from the numbering...
(When you test it with ghci, this example is really slow)

The same thing hapens with a list of bools.
Best regards,
Nicolas Oury
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How can I make a counter without Monad?

2005-03-16 Thread Peter Davis
On 2005-03-16 02:52:39 -0800, Nicolas Oury [EMAIL PROTECTED] said:
instance Splittable Integer where
   split n = (2*n,2*n+1)
foo::(%x::Integer) = [a] - [(a,Integer)]
foo [] = []
foo (a:l) = (a,%x):(foo l)
test = let %x = 1 in foo [1..15000]
But, in this example, the numbering is linear and so test becomes quadratic.
The main complexity of the program come from the numbering...
(When you test it with ghci, this example is really slow)
I haven't played much with the Splittable class yet, but what would be 
wrong with

instance Splittable Integer where
  split n = (n,n+1)
?
--
Peter Davis [EMAIL PROTECTED]
Furthermore, I believe bacon prevents hair loss!
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How can I make a counter without Monad?

2005-03-16 Thread John Meacham
On Wed, Mar 16, 2005 at 10:51:08AM +0100, Nicolas Oury wrote:
 A monadic counter imposes an order of evaluation.
 In my program, I don't care about the order of the numbers.
 I only want them to be all different.
 I think a monad is too restrictive for what I need.

This is a common misconception, there is nothing about monads that
requires an order of evaluation. for instance none of 

Control.Monad.Identity - isomorphic to not using monads at all
Control.Monad.Reader - distributes a value to subcomputations
Control.Monad.Writer - collects values from subcomputations

imply any particular order of evaluation. This is one of the major
powers of Monads,  they can encapsulate all sorts of 'side effects', not
just order of evaluation or linear state. 

for this app, I would use Control.Monad.State or if I needed the extra
lazyness, Control.Monad.Reader with an explicitly splittable namesupply.
John


-- 
John Meacham - repetae.netjohn 
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users