Where prelude alternatives/ classes and types to get values?

Bulat Ziganshin bulat.ziganshin at gmail.com
Sat Feb 17 11:48:41 EST 2007


Hello Marc,

Saturday, February 17, 2007, 7:48:15 PM, you wrote:

> It would be much nicer to use
> class Empty where
> empty :: a

there are two libraries, Edisson and Collections, which includes large
hierarchies of collection type classes

about references. my program includes the following minilib:

infixl 0 =:, +=, -=, ++=, .=, .<-, <<=

-- Simple variables
ref = newIORef
new = newIORef
val = readIORef
a=:b = writeIORef a b
a+=b = modifyIORef a (\a->a+b)
a-=b = modifyIORef a (\a->a-b)
a.=b = modifyIORef a (\a->b a)
a++=b = modifyIORef a (\a->a++b)
a.<-b = modifyIORefIO a (\a->b a)
withRef init  =  with' (ref init) val

-- Accumulation lists
newtype AccList a = AccList [a]
newList   = ref$ AccList []
a<<=b     = a .= (\(AccList x) -> AccList$ b:x)
listVal a = val a >>== (\(AccList x) -> reverse x)
withList  =  with' newList listVal


addToIORef :: IORef [a] -> a -> IO ()
addToIORef var x  =  var .= (x:)

modifyIORefIO :: IORef a -> (a -> IO a) -> IO ()
modifyIORefIO var action = do
  readIORef var  >>=  action  >>=  writeIORef var

with' init finish action  =  do a <- init;  action a;  finish a



usage examples:


  blocks <- withList $ \found -> do
             scanArchiveSearchingDescriptors archive arcname found buf arcsize

scanArchiveSearchingDescriptors archive arcname found buf arcsize = do
  pos' <- ref base_pos
  ...
    pos' =: blPos block
    found <<= block
  pos <- val pos'
  if pos > base_pos
    ...

  processDir filelist  =  do let (dirs,files)  =  partition fiIsDir filelist
                             files2delete ++= files
                             dirs2delete  ++= dirs

  let update_crc buf len =  do when (block_type/=DATA_BLOCK) $ do
                                   crc .<- updateCRC buf len
                               origsize += len

                             
   errors' <- ref (length bad)
   ...
        when (crc/=original_crc) $ do
          errors' += 1
   ...
   errors <- val errors'
   when (errors>0) $ do


uiStartDeCompression = do
  time <- getCPUTime
  refArchiveProcessingTime -= time

uiFinishDeCompression = do
  time <- getCPUTime
  refArchiveProcessingTime += time
   


-- 
Best regards,
 Bulat                            mailto:Bulat.Ziganshin at gmail.com



More information about the Libraries mailing list