
Hi, I the paper of Magnu Carlsson I noticed small, interesting class: class Monad m => Ref m r | m -> r where newRef :: a -> m (r a) readRef :: r a -> m a writeRef :: r a -> a -> m () He defined it locally, but it seems to be very useful generalization of IORef and STRef. Is there something like this in standard libraries? I couldn't find it... :( Is there any reason why isn't it included? Another question: priority queue. In libraries bundled with ghc we have Data.Queue, but I couldn't find PriorityQueue. Is there somewhere an implementation that everybody uses, but is not in the library? Thanks! -- Gracjan

Hello Gracjan, Tuesday, June 07, 2005, 2:25:50 PM, you wrote: class Monad m =>> Ref m r | m -> r where GP> newRef :: a -> m (r a) GP> readRef :: r a -> m a GP> writeRef :: r a -> a -> m () may be the following will be even more interesting: import Control.Monad import Data.IORef infixl 0 =:, +=, -=, =::, <<= ref = newIORef val = readIORef a=:b = writeIORef a b a+=b = modifyIORef a (\a-> a+b) a-=b = modifyIORef a (\a-> a-b) a=::b = ((a=:).b) =<< val a for :: [a] -> (a -> IO b) -> IO () for = flip mapM_ newList = ref [] list <<= x = list =:: (++[x]) push list x = list =:: (x:) pop list = do x:xs<-val list; list=:xs; return x main = do sum <- ref 0 lasti <- ref undefined for [1..5] $ \i -> do sum += i lasti =: i sum =:: (\sum-> 2*sum+1) print =<< val sum print =<< val lasti xs <- newList for [1..3] (push xs) xs <<= 10 xs <<= 20 print =<< val xs I use this module to simplify working with references in my program. The first inteface can be used for IORef/STRef/MVar/TVar and second for lists and Chan -- Best regards, Bulat mailto:bulatz@HotPOP.com

Bulat Ziganshin wrote:
Hello Gracjan,
Tuesday, June 07, 2005, 2:25:50 PM, you wrote: class Monad m =>> Ref m r | m -> r where GP> newRef :: a -> m (r a) GP> readRef :: r a -> m a GP> writeRef :: r a -> a -> m ()
may be the following will be even more interesting:
I like it very much!
import Control.Monad import Data.IORef
infixl 0 =:, +=, -=, =::, <<= ref = newIORef val = readIORef a=:b = writeIORef a b
Pretty shame := is already reserver :(. There is something alike Graphics.Rendering.OpenGL.GL.StateVar. The use $= for assignment. Generalizing "variables" (in respect to some monad) seems to be often reinvented idea :) As I see this could be generalized to all Ref-like constructs (IO,ST,others?)
a+=b = modifyIORef a (\a-> a+b) a-=b = modifyIORef a (\a-> a-b) a=::b = ((a=:).b) =<< val a Is this convoluted modify? Why doesn't it use modifyIORef? Or am I wrong?
for :: [a] -> (a -> IO b) -> IO () for = flip mapM_
I like: foreach = flip mapM foreach_ = flip mapM_
newList = ref [] list <<= x = list =:: (++[x])
Is this append?
push list x = list =:: (x:) pop list = do x:xs<-val list; list=:xs; return x
main = do sum <- ref 0 lasti <- ref undefined for [1..5] $ \i -> do sum += i lasti =: i sum =:: (\sum-> 2*sum+1) print =<< val sum print =<< val lasti
xs <- newList for [1..3] (push xs) xs <<= 10 xs <<= 20 print =<< val xs
Haskell as ultimate imperative language :)
I use this module to simplify working with references in my program. The first inteface can be used for IORef/STRef/MVar/TVar and second for lists and Chan
Then we should create classes for those interfaces. -- Gracjan

Hello Gracjan, Tuesday, June 07, 2005, 4:52:50 PM, you wrote:
a=:b = writeIORef a b
GP> Pretty shame := is already reserver :(. := reserved for infix data constructors, as any other symbols starting with ':' GP> As I see this could be generalized to all Ref-like constructs GP> (IO,ST,others?) i think so
a+=b = modifyIORef a (\a-> a+b) a-=b = modifyIORef a (\a-> a-b) a=::b = ((a=:).b) =<< val a GP> Is this convoluted modify? Why doesn't it use modifyIORef? Or am I wrong?
a=::(*2) doubles value of `a` and so on. i don't define this as `modifyIORef` equivalent just because it's is a funnier definition :) also i was interested to define all funcs via 2 primitives - `val` and '=:` (which is like readRef/writeRef in your example); such definitions will be more convenient for defining Ref as class: class Ref a where val .... (=:) ... instance Ref (MVar a) where val=takeMVar (=:)=putMVar where all other operations are defined via this two primitives. of course, it's not the best way - adding `modifyRef` to Ref class with default definition via 'val' and `=:' would be better
newList = ref [] list <<= x = list =:: (++[x]) GP> Is this append?
it is adding one value to end of list, for Chan'nels it would be `writeChan` GP> Haskell as ultimate imperative language :) it may be better, though :)
I use this module to simplify working with references in my program. The first inteface can be used for IORef/STRef/MVar/TVar and second for lists and Chan
GP> Then we should create classes for those interfaces. of course. i don't done it only because my own program use only IORefs with help of this defines my code was significantly lightened. see for example: crc <- ref aINIT_CRC origsize <- ref 0 let update_crc (DataChunk buf len) = do when (block_type/=DATA_BLOCK) $ do crc .<- updateCRC buf len origsize += toInteger len ..... acrc <- val crc >>== finishCRC aorigsize <- val origsize you can imagine how this code looked before, using newIORef, readIORef and so on... ('.<-' is `modifyIORef` in IO monad) but of course i will prefer more direct support of imperative programming. i have some proposal - translating x := @x + @y + @@f 1 2 to x1 <- val x y1 <- val y f1 <- f 1 2 x =: x1+y1+f1 but i guess that number of True Imperative Programmers among GHC users is not very large :) in any case, there is an interesting STPP array indexing preprocessor (http://www.isi.edu/~hdaume/STPP/stpp.tar.gz), which decides nearly the same problem -- Best regards, Bulat mailto:bulatz@HotPOP.com

On Tue, Jun 07, 2005 at 12:25:50PM +0200, Gracjan Polak wrote:
Another question: priority queue. In libraries bundled with ghc we have Data.Queue, but I couldn't find PriorityQueue. Is there somewhere an implementation that everybody uses, but is not in the library?
You can use the new Data.Map module for this (old Data.FiniteMap too, but a bit more clumsily), it has findMin, findMax, deleteFindMin, deleteFindMax, deleteMin, deleteMax. All these operations should have O(log N) cost. Best regards Tomasz

Tomasz Zielonka wrote:
On Tue, Jun 07, 2005 at 12:25:50PM +0200, Gracjan Polak wrote:
Another question: priority queue. In libraries bundled with ghc we have Data.Queue, but I couldn't find PriorityQueue. Is there somewhere an implementation that everybody uses, but is not in the library?
You can use the new Data.Map module for this (old Data.FiniteMap too, but a bit more clumsily), it has findMin, findMax, deleteFindMin, deleteFindMax, deleteMin, deleteMax. All these operations should have O(log N) cost.
Wow, I did not think about this. As far as I remember in imperative world priority queues had special implementation, with very good O() characteristics. Is O(log N) the best thing that can bo done in pure functional setting? To put it another way: is Data.Map only workaround to get something done, or is it The Right Way of doing PQs in Haskell?
Best regards Tomasz
-- Gracjan

On 6/8/05, Gracjan Polak
Tomasz Zielonka wrote:
On Tue, Jun 07, 2005 at 12:25:50PM +0200, Gracjan Polak wrote:
To put it another way: is Data.Map only workaround to get something done, or is it The Right Way of doing PQs in Haskell?
Another option is to look at Chris Okasaki's _Purely_Functional_Data_Structures_ (code available at his website). Pairing heaps and splay heaps (when bootstrapped) are said to have O(1) in everything but removeMin (new, insert, merge, findMin) and good constant factors. Colin DeVilbiss

On Jun 8, 2005, at 7:13 AM, Gracjan Polak wrote:
Tomasz Zielonka wrote:
[Data.Map can be used to implement priority queues]
Wow, I did not think about this.
As far as I remember in imperative world priority queues had special implementation, with very good O() characteristics. Is O(log N) the best thing that can bo done in pure functional setting?
Either insertion or deletion must be amortized O(lg N) unless you're using bounded priorities. Otherwise you'd be able to sort in better than O(N lg N) time by using a new improved queue--and that, of course, is impossible. It doesn't matter what setting you're in. For bounded priorities, it would be nice to see similar functionality in Data.IntMap. There, you have to squint funny, but stuff takes constant time if you assume the number of bits in a word (I believe this is W in the HaskellDoc) doesn't change. In practice you'd only pay for as many bits as you use (so if you use keys between -512 and 511, W=10 rather than, say, 32).
To put it another way: is Data.Map only workaround to get something done, or is it The Right Way of doing PQs in Haskell?
I believe there are heap data structures that make one or the other operation (insert or deleteMin) O(1). You might try one of Okasaki's heap implementations from "Purely Functional Data Structures". Heaps don't need to support lookup, and can focus on doing insertion and deletion well. -Jan-Willem Maessen
Best regards Tomasz
-- Gracjan _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Gracjan Polak
To put it another way: is Data.Map only workaround to get something done, or is it The Right Way of doing PQs in Haskell?
Another option is the priority queues from the Rabhi & Lapalme book: http://www.iro.umontreal.ca/~lapalme/Algorithms-functional.html -- It seems I've been living two lives. One life is a self-employed web developer In the other life, I'm shapr, functional programmer. | www.ScannedInAvian.com One of these lives has futures (and subcontinuations!)| --Shae Matijs Erisson

On Wed, Jun 08, 2005 at 01:13:47PM +0200, Gracjan Polak wrote:
To put it another way: is Data.Map only workaround to get something done, or is it The Right Way of doing PQs in Haskell?
I think it is a workaround. There is a problem with equal priorities - you have to do some additional work to handle them properly. Best regards Tomasz

G'day all.
Quoting Gracjan Polak
class Monad m => Ref m r | m -> r where newRef :: a -> m (r a) readRef :: r a -> m a writeRef :: r a -> a -> m () [...]
Is there something like this in standard libraries?
No.
Is there any reason why isn't it included?
Nobody could agree on the details. For example, MVars are perfectly respectable Refs on the IO monad. So would it make sense to add an instance for that? If so, the functional dependency should go, which introduces its own problems. Cheers, Andrew Bromage

ajb@spamcop.net wrote:
Quoting Gracjan Polak
: [...] Is there any reason why isn't it included?
Nobody could agree on the details. For example, MVars are perfectly respectable Refs on the IO monad. So would it make sense to add an instance for that? If so, the functional dependency should go, which introduces its own problems.
A few more design problems: * Due to the functional dependency, that class is not Haskell98, which is a *very* good reason IMHO not to standardize it, at least in that way. Remember: There are not only GHC and Hugs out there... * The 3 operations should not be packed together in a single class, because there might be e.g. references which you can't create (e.g. OpenGL's state variables), references which are read-only and even references which are write-only. * What about strictness of e.g. the setter? There is no "right" version, this depends on the intended usage. * Are the references located in the monad (like in the suggested class) or are they within objects, which have to be given as additional arguments (e.g. like wxHaskell's widgets/Attr/Prop). * Atomic operations might be needed, too. Cheers, S.

Sven Panne writes:
| ajb@spamcop.net wrote:
| > Quoting Gracjan Polak
{-# OPTIONS -fglasgow-exts #-}
import Control.Monad.Reader import Control.Monad.State import Control.Monad.ST import Data.STRef
class Monad m => MonadRef r m | m -> r where newRef :: a -> m (r a) readRef :: r a -> m a writeRef :: r a -> a -> m ()
instance MonadRef (STRef r) (ST r) where newRef = newSTRef readRef = readSTRef writeRef = writeSTRef
instance MonadRef r m => MonadRef r (ReaderT e m) where newRef = lift . newRef readRef = lift . readRef writeRef = (lift.) . writeRef
newtype RefToState r s m a = RTS (ReaderT (r s) m a) deriving (Functor, Monad)
instance MonadRef r m => MonadState s (RefToState r s m) where get = RTS (ask >>= readRef) put s = RTS (ask >>= \r -> writeRef r s)
evalRefToState :: MonadRef r m => RefToState r s m a -> s -> m a evalRefToState (RTS m) s0 = newRef s0 >>= runReaderT m
runRefToState :: MonadRef r m => RefToState r s m a -> s -> m (a, s) runRefToState (RTS m) s0 = do r <- newRef s0 x <- runReaderT m r s <- readRef r return (x,s) -- David Menendez
| "In this house, we obey the laws http://www.eyrie.org/~zednenem | of thermodynamics!"

David Menendez wrote: [many things deleted]...
I think the best way to look at MonadRef is as a generalization of MonadState.
This could be a way to transliterate (not translate, transliterate) many imperative programs to Haskell. And as such this could be a starting point for many imperative souls into functional liberation :) I do not think that, for beginners, limitation to Hugs or GHC is serious problem. -- Gracjan
participants (9)
-
ajb@spamcop.net
-
Bulat Ziganshin
-
Colin DeVilbiss
-
David Menendez
-
Gracjan Polak
-
Jan-Willem Maessen
-
Shae Matijs Erisson
-
Sven Panne
-
Tomasz Zielonka