Where prelude alternatives/ classes and types to get values?

The prelude has some issues such like Map.empty, Sequnce.empty, Set.empty It would be much nicer to use class Empty where empty :: a except of more complicated error messages (especially for newbies) Are there already some proposals? Is this the right place to discuss these topics? I got this idea because I'm currently learning more about webfunctions. Some states (eg counters) are implemented using IORefs. I could imagine a class class ModifyIO m c where modify :: IORef a -> ( a -> a ) -> m c data Old a data New a data OldNew a = OldNew a a; modify f = do a <- readIORef io let new = f a writeIORef io new return $ f old new instance ModifyIO IO (Old a) = modify io f = modify io (\old _ -> Old old) instance ModifyIO IO (New a) = modify io f = modify io (\_ new -> New new) instance ModifyIO IO (OldNew a) = modify io f = modify io OldNew which would lead to code such as ... = do (New count) <- modify ioCounterRef (+1) ... compared to ... = do count <- readIORef ioCounterRef let count = count + 1 writeIORef ioCounterRef count ... Do you think this style is insane? Marc Weber

Hi
I could imagine a class
class ModifyIO m c where modify :: IORef a -> ( a -> a ) -> m c
m would have to be IO, c would be a bit pointless - so IO () is a better return type. You can then Hoogle for it: IORef a -> (a -> a) -> IO () http://haskell.org/hoogle/?q=IORef%20a%20-%3E%20(a%20-%3E%20a)%20-%3E%20IO%2...) ... = do (New count) <- modify ioCounterRef (+1) = do newcount <- modifyIORef ioCounterRef (+1) It already exists :) Thanks Neil

m would have to be IO, c would be a bit pointless - so IO () is a better return type. It doesn't have to be IO. It can also be implemented using liftIO . modify .. Then you can use htis modify function from any monad beeing an instance of IOMonad..
You can then Hoogle for it: IORef a -> (a -> a) -> IO ()
http://haskell.org/hoogle/?q=IORef%20a%20-%3E%20(a%20-%3E%20a)%20-%3E%20IO%2...)
... = do (New count) <- modify ioCounterRef (+1)
= do newcount <- modifyIORef ioCounterRef (+1)
It already exists :) Hi Neil. Thanks for your hint. This time I already have found modifyIORef ;) But as hoogle states:
Searched for modifyIORef Results 1 - 2 of 2 Data.IORef. modifyIORef :: IORef a -> (a -> a) -> IO () Data.IORef. atomicModifyIORef :: IORef a -> (a -> (a, b)) -> IO b the return type of modifyIORef is IO (), not IO <new value> So only using this function wouldn't solve the problem, right? Marc

On Sat, Feb 17, 2007 at 05:48:15PM +0100, Marc Weber wrote:
The prelude has some issues such like Map.empty, Sequnce.empty, Set.empty
It would be much nicer to use class Empty where empty :: a except of more complicated error messages (especially for newbies)
Are there already some proposals? Is this the right place to discuss these topics?
Yes, and Yes. In my opinion, Haskell should take a cue from the videogame industry and create an EasyPrelude, normal Prelude, and HardPrelude. The EasyPrelude would be something like the Helium prelude - very little overloading. The normal prelude would be the Haskell 98 prelude, modulo bugfixes. The hard prelude would be everything we want, newbies can be ignored. Classes for functors, emptyable functors, catenable functors, applicative functors, monoids, semigroups, (+) and (++) overloaded, etc, etc, etc.
I got this idea because I'm currently learning more about webfunctions. Some states (eg counters) are implemented using IORefs.
I could imagine a class ...
Look at Bulat's ArrayRef library. http://haskell.org/haskellwiki/Library/ArrayRef

Hi
In my opinion, Haskell should take a cue from the videogame industry and create an EasyPrelude, normal Prelude, and HardPrelude.
The EasyPrelude would be something like the Helium prelude - very little overloading.
The main reason for something like this is that error messages aren't as clear. Wouldn't a better solution be a "-beginner" flag which on seeing x ++ xs gives the hint "x is not a list, it doesn't have to be, but you probably wanted it to be". Or perhaps someone could research good type error messages? I don't like the idea of partitioning Haskell users into discrete sets based on their ability - its not a nice culture to have, but more practically it makes a painful jump between each stage. Thanks Neil

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@gmail.com
participants (4)
-
Bulat Ziganshin
-
Marc Weber
-
Neil Mitchell
-
Stefan O'Rear