How can I make a counter without Monad?

Greetings, In a program, I want to give a unique name to some structures. As it is the only imperative thing I need, I don't want to use a monad. I have played with two solutions and have some questions : * unsafePerformIO : I create a counter : counter :: IORef Int counter = unsafePerformIO (newIORef 0) {-# NOINLINE counter #-} and a function to give a unique name: newNode a = unsafePerformIO $ do i <- readIORef counter writeIORef counter (i+1) return (i,a) {-# NOINLINE newNode #-} I now want to write a function : foo a = let n = newNode a in (n,n) How can I make sure ghc won't reduce it to foo a = (newNode a, newNode a) ? * 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? Are there other ways to implement a counter in Haskell? Thanks for your help, Best regards, Nicolas Oury

On Wed, Mar 16, 2005 at 01:17:51AM +0100, Nicolas Oury wrote:
Greetings,
In a program, I want to give a unique name to some structures.
As it is the only imperative thing I need, I don't want to use a monad.
You don't want to use the IO monad. Why not use some other monad?
I have played with two solutions and have some questions :
* unsafePerformIO :
This is asking for trouble. You are using an IO monad in an unsafe way. Don't do it.
* linear implicit parameters
[...]
Are there other ways to implement a counter in Haskell?
Using a State monad?
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

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

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

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.net⑆john⑈

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

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

On 2005-03-16 02:52:39 -0800, Nicolas Oury
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

On Wed, 16 Mar 2005, Peter Davis wrote:
On 2005-03-16 02:52:39 -0800, Nicolas Oury
said: instance Splittable Integer where split n = (2*n,2*n+1)
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)
If you recursively split the left-hand result then that overlaps with the
right-hand result.
Tony.
--
f.a.n.finch
participants (5)
-
John Meacham
-
Nicolas Oury
-
Peter Davis
-
Tomasz Zielonka
-
Tony Finch