[Haskell-cafe] Class-like features for explicit arguments (was: Ord for partially ordered sets)

Carter Schonwald carter.schonwald at gmail.com
Sat Apr 25 01:56:44 UTC 2015


hrm, wouldn't your proposed extension be largely accomplished by using
Record pun and Record WildCards?

eg

{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE  RecordPuns #-}
module Foo where
data Relation a = Rel{related :: a -> a ->Bool,unrelated :: a -> a -> Bool}

foo :: Relation A -> A -> A -> Bool
foo Rel{..} x y = related x y

------
or am i over looking something?
I do realize this may not quite be what youre suggesting, and if so, could
you help me understand better? :)


On Fri, Apr 24, 2015 at 4:26 PM, Ertugrul Söylemez <ertesx at gmx.de> wrote:

> > 3. NonStrictPoSet, which is the class of all partially ordered
> > set-like things, but without the requirement that a <= b and b <= a
> > implies a Equal b.
>
> Those are preorders.  An antisymmetric preorder is a non-strict poset.
>
> Also it's difficult to capture all of those various order types in
> Haskell's class system.  A type can have many orders and many underlying
> equivalence relations in the case of partial and total orders, and there
> are different ways to combine them.  For example equality is a partial
> order, modular equivalence is a preorder, etc.  Those denote bags and
> groups more than sequences or trees.
>
> Perhaps it's time to add a type class-like system to Haskell, but for
> explicitly passed arguments:
>
>     record Relation a where
>         related :: a -> a -> Bool
>
>         unrelated :: a -> a -> Bool
>         unrelated x y = not (related x y)
>
>     func1 :: Relation A -> A -> A -> A
>     func1 _ x y = ... related x y ...
>
>     func2 :: Relation A -> Relation A -> A -> A -> A
>     func2 r1 r2 x y = ... r1.related x y ... r2.unrelated x y ...
>
> In a lot of cases this is much more appropriate than a type class, and
> it would turn many things that are currently types into regular
> functions, thus making them a lot more composable:
>
>     down :: Ord a -> Ord a
>     down o =
>         Ord { compare x y = o.compare y x }
>         -- The remaining Ord functions are defaulted.
>
> Perhaps all we need is to generalise default definitions to data types
> and add module-like dot syntax for records (mainly to preserve infix
> operators).  Formally speaking there is also little that prevents us
> From having associated types in those records that can be used on the
> type level.
>
> For actual record types (i.e. single-constructor types) we could even
> have specialisation and get a nice performance boost that way, if we ask
> for it:
>
>     {-# SPECIALISE down someOrder :: Ord SomeType #-}
>
> This would be extremely useful.
>
>
> > 4. Things like above, but with the requirement of a Zero, with the
> > requirement of a One, and the requirement fo both a Zero and a One.
>
> Zero and one as in minBound and maxBound or rather as in Monoid and a
> hypothetical Semiring?  In the latter case I believe they don't really
> belong into an additional class, unless you have some ordering-related
> laws for the zeroes and ones.  If not, you can always simply use an
> Ord+Semiring constraint.
>
> There may be some motivation to make Bounded a subclass of Ord though.
>
>
> Greets,
> Ertugrul
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150424/47fbf8c7/attachment.html>


More information about the Haskell-Cafe mailing list