Bulat Ziganshin wrote:
Hello Brian,
Sunday, July 23, 2006, 1:20:36 AM, you wrote:
instance IString ByteString.Char8 ...
instance IString String ...
i think that we should ask Donald Stewart who is patronized SoC
project involving development of such type class. If he will say that
such type class is not developed, i feel himself enough interested to
start developing such class. i can add this module to ByteString lib,
if there is no better variants
i propose something like this:
class ListLike ce e | ce->e
instance ListLike [a] a
instance ListLike Data.ByteString.ByteString Word8
instance ListLike Data.ByteString.Lazy.ByteString Word8
instance ListLike Data.ByteString.Char8.ByteString Char
instance ListLike Data.ByteString.Lazy.Char8.ByteString Char
Hi Bulat -
I've been thinking of a sequence class for the project I'm working on at the
moment, something like:
class ISeq seq_a a | seq_a -> a where -- (*)
empty :: seq_a
single :: a -> seq_a
length :: seq_a -> Int
append :: seq_a -> seq_a -> seq_a
pushL :: a -> seq_a -> seq_a -- (**)
pushR :: seq_a -> a -> seq_a
at :: seq_a -> Int -> a
atL :: seq_a -> a -- (***)
atR :: seq_a -> a
viewL :: seq_a -> ViewL
-- plus lots of other ops
toList :: seq_a -> [a]
fromList :: [a] -> seq_a
data ViewL seq_a a = EmptyL | PushL !a !seq_a
-- this is strict so we don't pay an extra laziness penalty
(meaningful names such as pushL, pushR etc inspired by the absolutely
brilliant C++ STL library as opposed to odd lispy names like cons and snoc
(do we really want to have to start reading lexemes backwards then apply a
quirky historical reference to understand code?)) then the IString class
would be something like:
class IChar c where
toCChar :: c -> CChar
fromCChar :: CChar -> c
class (IChar c, ISeq s c) => IString s where
withCString :: MonadIO m => s -> (Ptr CChar -> IO a) -> m a
withCStringLen :: MonadIO m => s -> (Ptr CChar -> Int -> IO a) -> m
a
withCAString :: MonadIO m => s -> (Ptr CChar -> IO a) -> m a
withCAStringLen :: MonadIO m => s -> (Ptr CChar -> Int -> IO a) -> m
a
-- possibly also withCWString etc
peekCString :: Ptr CChar -> s
peekCAString :: Ptr CChar -> s
ie the IString class deals with the complexity of marshalling character
strings which may or may not be in Unicode.
(*) I assume that the reason for putting the collection type first is
because usually you want to map a collection of elements to a collection of
some different element type rather than mapping between different collection
types.
(**) I think conventional names like "foldr" should be replaced by "foldR"
so that camel case is followed consistently and so that confusing names like
"reducer", which is a word by itself in English, cannot arise when "reduceR"
was meant.
(***) "atL" and "atR" are more visual than the conventional names "head" and
"last". I think names should be chosen so that the syntactic differences
between lexemes indicate similarity of meaning, thus it's clear that "atL"
"atR" and "at" all do something similar, whereas "head", "last", and
"index" are just 3 random English words whose perceived commonality depends
on many years programming experience and is therefore vague and loose.
Anyway - it's just a rough idea at the moment,
Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.
http://www.metamilk.com
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe