nonempty-containers-0.3.3.0: Non-empty variants of containers data types, with full API

Copyright(c) Justin Le 2018
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Containers.NonEmpty

Description

Non-Empty Typeclass

Provides the typeclass HasNonEmpty, which abstracts over different types which have a "non-empty" variant.

Used to convert between and in between possibly-empty and non-empty types. Instances are provided for all modules in this package, as well as for NonEmpty in base and NonEmptyVector.

Synopsis

Documentation

class HasNonEmpty s where Source #

If s is an instance of HasNonEmpty, it means that there is a corresponding "non-empty" version of s, NE s.

In order for things to be well-behaved, we expect that nonEmpty and maybe empty fromNonEmpty should form an isomorphism (or that withNonEmpty empty fromNonEmpty == id. In addition, the following properties should hold for most exectations:

  • (x == empty) ==> isEmpty x
  • (x == empty) ==> isNothing (nonEmpty x)
  • isEmpty x    ==> isNothing (nonEmpty x)
  • unsafeToNonEmpty x == fromJust (nonEmpty x)
  • Usually, not (isEmpty x) ==> isJust (nonEmpty x), but this isn't necessary.

Minimal complete definition

(nonEmpty | withNonEmpty), fromNonEmpty, empty

Associated Types

type NE s = t | t -> s Source #

NE s is the "non-empty" version of s.

Methods

nonEmpty :: s -> Maybe (NE s) Source #

"Smart constructor" for NE s given a (potentailly empty) s. Will return Nothing if the s was empty, and Just n if the s was not empty, with n :: NE s.

Should form an isomorphism with maybe empty fromNonEmpty.

fromNonEmpty :: NE s -> s Source #

Convert a NE s (non-empty s) back into an s, "obscuring" its non-emptiness from its type.

withNonEmpty :: r -> (NE s -> r) -> s -> r Source #

Continuation-based version of nonEmpty, which can be more efficient in certain situations.

withNonEmpty empty fromNonEmpty should be id.

empty :: s Source #

An empty s.

isEmpty :: s -> Bool Source #

Check if an s is empty.

unsafeToNonEmpty :: s -> NE s Source #

Unsafely coerce an s into an NE s (non-empty s). Is undefined (throws a runtime exception when evaluation is attempted) when the s is empty.

Instances
HasNonEmpty IntSet Source # 
Instance details

Defined in Data.Containers.NonEmpty

Associated Types

type NE IntSet = (t :: Type) Source #

HasNonEmpty [a] Source # 
Instance details

Defined in Data.Containers.NonEmpty

Associated Types

type NE [a] = (t :: Type) Source #

Methods

nonEmpty :: [a] -> Maybe (NE [a]) Source #

fromNonEmpty :: NE [a] -> [a] Source #

withNonEmpty :: r -> (NE [a] -> r) -> [a] -> r Source #

empty :: [a] Source #

isEmpty :: [a] -> Bool Source #

unsafeToNonEmpty :: [a] -> NE [a] Source #

HasNonEmpty (IntMap a) Source # 
Instance details

Defined in Data.Containers.NonEmpty

Associated Types

type NE (IntMap a) = (t :: Type) Source #

HasNonEmpty (Seq a) Source # 
Instance details

Defined in Data.Containers.NonEmpty

Associated Types

type NE (Seq a) = (t :: Type) Source #

Methods

nonEmpty :: Seq a -> Maybe (NE (Seq a)) Source #

fromNonEmpty :: NE (Seq a) -> Seq a Source #

withNonEmpty :: r -> (NE (Seq a) -> r) -> Seq a -> r Source #

empty :: Seq a Source #

isEmpty :: Seq a -> Bool Source #

unsafeToNonEmpty :: Seq a -> NE (Seq a) Source #

HasNonEmpty (Set a) Source # 
Instance details

Defined in Data.Containers.NonEmpty

Associated Types

type NE (Set a) = (t :: Type) Source #

Methods

nonEmpty :: Set a -> Maybe (NE (Set a)) Source #

fromNonEmpty :: NE (Set a) -> Set a Source #

withNonEmpty :: r -> (NE (Set a) -> r) -> Set a -> r Source #

empty :: Set a Source #

isEmpty :: Set a -> Bool Source #

unsafeToNonEmpty :: Set a -> NE (Set a) Source #

HasNonEmpty (Vector a) Source # 
Instance details

Defined in Data.Containers.NonEmpty

Associated Types

type NE (Vector a) = (t :: Type) Source #

HasNonEmpty (Map k a) Source # 
Instance details

Defined in Data.Containers.NonEmpty

Associated Types

type NE (Map k a) = (t :: Type) Source #

Methods

nonEmpty :: Map k a -> Maybe (NE (Map k a)) Source #

fromNonEmpty :: NE (Map k a) -> Map k a Source #

withNonEmpty :: r -> (NE (Map k a) -> r) -> Map k a -> r Source #

empty :: Map k a Source #

isEmpty :: Map k a -> Bool Source #

unsafeToNonEmpty :: Map k a -> NE (Map k a) Source #

pattern IsNonEmpty :: HasNonEmpty s => NE s -> s Source #

The IsNonEmpty and IsEmpty patterns allow you to treat a s as if it were either a IsNonEmpty n (where n is a non-empty version of s, type NE s) or an IsEmpty.

For example, you can pattern match on a list to get a NonEmpty (non-empty list):

safeHead :: [Int] -> Int
safeHead (IsNonEmpty (x :| _)) = x     -- here, the list was not empty
safehead IsEmpty               = 0     -- here, the list was empty

Matching on IsNonEmpty n means that the original input was not empty, and you have a verified-non-empty n :: NE s to use.

Note that because of the way coverage checking works for polymorphic pattern synonyms, you will unfortunatelly still get incomplete pattern match warnings if you match on both IsNonEmpty and NonEmpty, even though the two are meant to provide complete coverage. However, many instances of HasNonEmpty (like NEMap, NEIntMap, NESet, NEIntSet) will provide their own monomorphic versions of these patterns that can be verified as complete covers by GHC.

This is a bidirectional pattern, so you can use IsNonEmpty to convert a NE s back into an s, "obscuring" its non-emptiness (see fromNonEmpty).

pattern IsEmpty :: HasNonEmpty s => s Source #

The IsNonEmpty and IsEmpty patterns allow you to treat a s as if it were either a IsNonEmpty n (where n is a non-empty version of s, type NE s) or an IsEmpty.

Matching on IsEmpty means that the original item was empty.

This is a bidirectional pattern, so you can use IsEmpty as an expression, and it will be interpreted as empty.

Note that because of the way coverage checking works for polymorphic pattern synonyms, you will unfortunatelly still get incomplete pattern match warnings if you match on both IsNonEmpty and NonEmpty, even though the two are meant to provide complete coverage. However, many instances of HasNonEmpty (like NEMap, NEIntMap, NESet, NEIntSet) will provide their own monomorphic versions of these patterns that can be verified as complete covers by GHC.

See IsNonEmpty for more information.

overNonEmpty :: (HasNonEmpty s, HasNonEmpty t) => (NE s -> NE t) -> s -> t Source #

Useful function for mapping over the "non-empty" representation of a type.

Since: 0.3.3.0

onNonEmpty :: HasNonEmpty s => (NE s -> r) -> s -> Maybe r Source #

Useful function for applying a function on the "non-empty" representation of a type.

If you want a continuation taking NE s -> 'Maybe r', you can use withNonEmpty Nothing.

Since: 0.3.3.0