Dear all,

Ross Peterson wrote:

> The favourite customer for FDs has been the monad transformer library.
> ...
> What other libraries should Haskell' support, and what are their
> requirements?

Here are some classes from Yampa/earlier versions of FRP.

I shouldn't think they're particularly demanding.

Also, I'm not saying these classes could not be defined
differently/better. They are just examples of what
seems to me reasonable uses of FDs.

---------------------------------------------------------

-- Minimal instance: zeroVector, (*^), (^+^), dot
class Floating a => VectorSpace v a | v -> a where
    zeroVector   :: v
    (*^)         :: a -> v -> v
    (^/)         :: v -> a -> v
    negateVector :: v -> v
    (^+^)        :: v -> v -> v
    (^-^)        :: v -> v -> v
    dot          :: v -> v -> a
    norm         :: v -> a
    normalize    :: v -> v

----------------------------------------------------------

-- Minimal instance: origin, .+^, .^.
class (Floating a, VectorSpace v a) =>
      AffineSpace p v a | p -> v, v -> a where
    origin   :: p
    (.+^)    :: p -> v -> p
    (.-^)    :: p -> v -> p
    (.-.)    :: p -> p -> v
    distance :: p -> p -> a

----------------------------------------------------------

From an old version of FRP:

FRPCore.lhs:> class MixSwitchable s a b | s a -> b where
FRPCore.lhs:> class Switchable s i | s -> i where
FRPCore.lhs:  class RunningIn a b i | a -> i where
FRPCore.lhs:> class ImpAs a b | a -> b where
FRPTask.lhs:  class RunningInTask a t i | a t -> i where
FRPTask.lhs:> class Monad m => StateMonad s m | m -> s where
FRPTask.lhs:> class Monad m => EnvMonad env m | m -> env where
FRPTask.lhs:> class GTask t => MsgTask t m | t -> m where
FRPTask.lhs:> class MsgTaskMap mt m nt n | mt -> m, nt -> n where

/Henrik

--
Henrik Nilsson
School of Computer Science and Information Technology
The University of Nottingham
[EMAIL PROTECTED]

This message has been checked for viruses but the contents of an attachment
may still contain software viruses, which could damage your computer system:
you are advised to perform your own checks. Email communications with the
University of Nottingham may be monitored as permitted by UK legislation.

_______________________________________________
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime

Reply via email to