[Haskell-cafe] class Ref...

Bulat Ziganshin bulatz at HotPOP.com
Tue Jun 7 12:22:28 EDT 2005


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 at HotPOP.com





More information about the Haskell-Cafe mailing list