Copyright | (c) Justin Le 2018 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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
- class HasNonEmpty s where
- type NE s = t | t -> s
- nonEmpty :: s -> Maybe (NE s)
- fromNonEmpty :: NE s -> s
- withNonEmpty :: r -> (NE s -> r) -> s -> r
- empty :: s
- isEmpty :: s -> Bool
- unsafeToNonEmpty :: s -> NE s
- pattern IsNonEmpty :: HasNonEmpty s => NE s -> s
- pattern IsEmpty :: HasNonEmpty s => s
- overNonEmpty :: (HasNonEmpty s, HasNonEmpty t) => (NE s -> NE t) -> s -> t
- onNonEmpty :: HasNonEmpty s => (NE s -> r) -> s -> Maybe r
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
should form an isomorphism (or that
empty
fromNonEmpty
. In addition,
the following properties should hold for most exectations:withNonEmpty
empty
fromNonEmpty
== id
(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.
nonEmpty :: s -> Maybe (NE s) Source #
"Smart constructor" for
given a (potentailly empty) NE
ss
.
Will return Nothing
if the s
was empty, and
if the
Just
ns
was not empty, with n ::
.NE
s
Should form an isomorphism with
.maybe
empty
fromNonEmpty
fromNonEmpty :: NE s -> s Source #
Convert a
(non-empty NE
ss
) 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.
should be withNonEmpty
empty
fromNonEmpty
id
.
An empty s
.
Check if an s
is empty.
unsafeToNonEmpty :: s -> NE s Source #
Unsafely coerce an s
into an
(non-empty NE
ss
). Is
undefined (throws a runtime exception when evaluation is attempted)
when the s
is empty.
Instances
HasNonEmpty IntSet Source # | |
Defined in Data.Containers.NonEmpty | |
HasNonEmpty (IntMap a) Source # | |
Defined in Data.Containers.NonEmpty | |
HasNonEmpty (Seq a) Source # | |
Defined in Data.Containers.NonEmpty | |
HasNonEmpty (Set a) Source # | |
Defined in Data.Containers.NonEmpty | |
HasNonEmpty (Vector a) Source # | |
Defined in Data.Containers.NonEmpty | |
HasNonEmpty [a] Source # | |
Defined in Data.Containers.NonEmpty | |
HasNonEmpty (Map k a) Source # | |
Defined in Data.Containers.NonEmpty |
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
(where IsNonEmpty
nn
is a non-empty version
of s
, type
) or an NE
sIsEmpty
.
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 safeheadIsEmpty
= 0 -- here, the list was empty
Matching on
means that the original input was not
empty, and you have a verified-non-empty IsNonEmpty
nn ::
to use.NE
s
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
back into an NE
ss
, "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
(where IsNonEmpty
nn
is a non-empty version
of s
, type
) or an NE
sIsEmpty
.
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
, you can
use NE
s -> 'Maybe r'
.withNonEmpty
Nothing
Since: 0.3.3.0