[Haskell-cafe] Re: ANN: System.FilePath 0.9
Bulat Ziganshin
bulat.ziganshin at gmail.com
Sun Jul 23 11:01:34 EDT 2006
Hello Brian,
Sunday, July 23, 2006, 5:31:35 PM, you wrote:
>>> instance IString ByteString.Char8 ...
>>> instance IString String ...
>> class ListLike ce e | ce->e
> class ISeq seq_a a | seq_a -> a where -- (*)
there is also Collection library:
darcs get --partial http://darcs.haskell.org/packages/collections/
it contains many classes, including:
-- | Class of sequential-access types.
-- In addition of the 'Collection' services, it provides deconstruction and concatenation.
class (Monoid c, Collection c a a) => Sequence c a where
-- | The first @i@ elements of a sequence.
take :: Int -> c -> c
-- | Elements of a sequence after the first @i at .
drop :: Int -> c -> c
-- | Split a sequence at a given index.
splitAt :: Int -> c -> (c,c)
-- | Reverse a sequence.
reverse :: c -> c
-- | Analyse the left end of a sequence.
front :: Monad m => c -> m (a,c)
-- | Analyse the right end of a sequence.
back :: Monad m => c -> m (c,a)
-- | Add an element to the left end of a sequence.
cons :: a -> c -> c
-- | Add an element to the right end of a sequence.
snoc :: c -> a -> c
-- | The 'isPrefix' function takes two seqences and returns True iff
-- the first is a prefix of the second.
isPrefix :: Eq a => c -> c -> Bool
but this class is not ideal for integration with ByteString library
which implements many custom algorithms which (i suppose) use details
of ByteString implementation. so, something like
class (Sequence c a) => ListLike c a where
split, splitBy....
would be useful. and then we should integrate your idea:
> class IChar c where
> class (IChar c, ISeq s c) => IString s where
--
Best regards,
Bulat mailto:Bulat.Ziganshin at gmail.com
More information about the Haskell-Cafe
mailing list