heterogeneous-comparison
Copyright(c) L. S. Leary 2025
Safe HaskellNone
LanguageGHC2021

Data.Hetero.Some

Contents

Description

An (almost) drop-in replacement for Data.Some.

Differences

  • Broader Eq and Ord instances via HetEq and HetOrd, which generalise GEq and GCompare respectively.
  • No GShow or GNFData classes for Show and NFData; it suffices to wield QuantifiedConstraints.
  • Hashable instance using the same approach.
  • For simplicity, Read is neglected.
Synopsis

Some

data Some (f :: k -> Type) where Source #

Existentials sans indirection.

Bundled Patterns

pattern Some :: forall {k} f (x :: k). () => f x -> Some f 

Instances

Instances details
(forall (x :: k). NFData (f x)) => NFData (Some f) Source # 
Instance details

Defined in Data.Hetero.Some

Methods

rnf :: Some f -> () #

Applicative f => Monoid (Some f) Source # 
Instance details

Defined in Data.Hetero.Some

Methods

mempty :: Some f #

mappend :: Some f -> Some f -> Some f #

mconcat :: [Some f] -> Some f #

Applicative f => Semigroup (Some f) Source # 
Instance details

Defined in Data.Hetero.Some

Methods

(<>) :: Some f -> Some f -> Some f #

sconcat :: NonEmpty (Some f) -> Some f #

stimes :: Integral b => b -> Some f -> Some f #

(forall (x :: k). Show (f x)) => Show (Some f) Source # 
Instance details

Defined in Data.Hetero.Some

Methods

showsPrec :: Int -> Some f -> ShowS #

show :: Some f -> String #

showList :: [Some f] -> ShowS #

HetEq f => Eq (Some f) Source # 
Instance details

Defined in Data.Hetero.Some

Methods

(==) :: Some f -> Some f -> Bool #

(/=) :: Some f -> Some f -> Bool #

HetOrd f => Ord (Some f) Source # 
Instance details

Defined in Data.Hetero.Some

Methods

compare :: Some f -> Some f -> Ordering #

(<) :: Some f -> Some f -> Bool #

(<=) :: Some f -> Some f -> Bool #

(>) :: Some f -> Some f -> Bool #

(>=) :: Some f -> Some f -> Bool #

max :: Some f -> Some f -> Some f #

min :: Some f -> Some f -> Some f #

(forall (x :: k). Hashable (f x), HetEq f) => Hashable (Some f) Source # 
Instance details

Defined in Data.Hetero.Some

Methods

hashWithSalt :: Int -> Some f -> Int #

hash :: Some f -> Int #

mkSome :: forall {k} f (x :: k). f x -> Some f Source #

withSome :: Some f -> (forall (x :: k). f x -> r) -> r Source #

withSomeM :: forall {k} m f r. Monad m => m (Some f) -> (forall (x :: k). f x -> m r) -> m r Source #

mapSome :: (forall (x :: k). f x -> g x) -> Some f -> Some g Source #

foldSome :: (forall (x :: k). f x -> b) -> Some f -> b Source #

traverseSome :: forall {k} h f g. Applicative h => (forall (x :: k). f x -> h (g x)) -> Some f -> h (Some g) Source #