Re: ANNOUNCE: attribute 0.1

2003-11-13 Thread Derek Elkins
On Thu, 13 Nov 2003 16:06:24 -0500
"Abraham Egnor" <[EMAIL PROTECTED]> wrote:

Sorry that I'm too lazy to download the the tar.bz2 and see for myself,
but...

>   that applies those functions to a monadic reference.  Instances for
>   MRef are provided for both IORef and STRef.

Assuming MRef is like the below, did you include Lazy.ST too?

On a more general note, sticking something like MonadRef somewhere in
the heirarchical libs seems like it would be useful.  Or perhaps Iavor's
monad library?

instance MonadRef IO IORef where
newRef = newIORef
readRef = readIORef
writeRef = writeIORef

instance MonadRef (Lazy.ST s) (STRef s) where
newRef = Lazy.strictToLazyST . newSTRef
readRef = Lazy.strictToLazyST . readSTRef
writeRef = (Lazy.strictToLazyST .) . writeSTRef

instance MonadRef (Strict.ST s) (STRef s) where
newRef = newSTRef
readRef = readSTRef
writeRef = writeSTRef

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


ANNOUNCE: attribute 0.1

2003-11-13 Thread Abraham Egnor
Attribute is a library for storing and retrieving named values from
haskell datatypes in arbitrary monads.

Many of the haskell GUI libraries have implemented something similar; in
one of my current projects, I discovered that such a thing would be
useful.  However, I didn't want to tie it to my specific use, the result
of which is this library.  The README included with the source is
hopefully enough documentation to get started, the text of which is
included at the end of this email.

A tarball is available at "http://abe.egnor.name/attribute-0.1.tar.bz2";. 
Source can also be obtained via arch:
 tla register-archive http://ofb.net/~abe/archive/2003
 tla get [EMAIL PROTECTED]/attribute--main

=== README ===

This is attribute, monadic attributes for haskell datatypes. See COPYRIGHT
for copying information.

Building:
  edit the Makefile for the install path
  make
  make install (as root)

  The only dependency is a recent version of ghc (>=6).

Use:
  Abstractly, an attribute represents a value that can be retrieved from or
  stored into a specific type in a specific monad; an attribute can either
  be readable, writable, or both, represented by the types Read, Write, and
  ReadWrite.

  A note on naming conventions: I've used general words (such as Read,
Write,
  set, get, etc.) for most functions; this does not follow Haskell
convention,
  but does follow the ideas at
"http://haskell.org/hawiki/UsingQualifiedNames";,
  which makes far more sense to me.  If you can't live without prefixes,
  qualify the import.

  Example: "ReadWrite Int String IO" represents a String that can be both
  extracted from and stored into an Int in the IO monad (although such a
  property is unlikely to be useful).  A more useful attribute might be
  something like:

  contents :: Read FilePath String IO

  which would represent the contents of a file, probably read in via
  getContents or some such.

  Attributes can be constructed directly from setter or getter functions:

  data (Monad m) => Read o d m = Read (o -> m d)
  data (Monad m) => Write o d m = Write (o -> d -> m ())
  data (Monad m) => ReadWrite o d m = ReadWrite (o -> m d) (o -> d -> m ())

  A few convenience functions are provided for constructing attributes:

  attrMRef :: (MRef r m) => (a -> b -> b)
-> (b -> a)
-> ReadWrite (r b) a m

  attrMRefT :: String -> ExpQ

  attrMRef takes a pure mutator and extractor, and creates an attribute
  that applies those functions to a monadic reference.  Instances for MRef
  are provided for both IORef and STRef.

  attrMRefT simplifies a common case, where you have a pure datatype
  defined with named records and you'd like to make attributes for some
  of the records:

  data Foo = Foo { fooBar :: Int, fooBaz :: String }
  bar :: (MRef r m) => ReadWrite (r Foo) Int m
  bar = $(attrMRefT "Main:fooBar")
  baz :: (MRef r m) => ReadWrite (r Foo) String m
  baz = $(attrMRefT "Main:fooBaz")

  The String passed to attrMRefT is the name of one of the records;
  the current implementation of template haskell requires that it be
  prefixed with the name of the module in which it's defined.
  
  attributes are bound to values by creating a Property; the constructors
  for property are ":=", ":~", "::=", and "::~", which are pure set, pure
  mutate, monadic set, and monadic mutate respectively.  To reuse the Foo
  example from above:

  test :: IO (Int, String)
  test = do ref <- newMRef $ Foo { fooBar = 3, fooBaz = "hello" }
set ref [ bar := 5, baz :~ (++" world") ]
bar' <- get ref bar
baz' <- get ref baz
return (bar', baz')
  
  will return (5, "hello world").  Note that because attributes created
with
  attrMRef or attrMRefT are qualified by monad type, this example could
  be changed to use the ST monad simply by changing the type signature.

  Two functions are provided for manipulating attributes: "set" and "get".
  
  set :: (Monad m) => o -> [Property o m] -> m ()
  get :: (Monad m, CanRead a) => o -> a o d m -> m d

  The "CanRead" class constraint simply enforces the readability of the
  particular attribute; both Read and ReadWrite are instances.  There is a
  similarly used "CanWrite" class:

  class CanRead a where
aGet :: (Monad m) => (a o d m) -> (o -> m d)

  class CanWrite a where
aSet :: (Monad m) => (a o d m) -> (o -> d -> m ())

  While you are certainly free to define new instances of the classes, I
have
  yet to find a use case where the simple Read/Write/ReadWrite types do not
  suffice.
  
  See the files in src/test/ for examples.

  Have fun!

Abe Egnor ([EMAIL PROTECTED])

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell