{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts, FlexibleInstances #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Data.NonNull (
    NonNull
  , fromNullable
  , impureNonNull
  , nonNull
  , toNullable
  , fromNonEmpty
  , toNonEmpty
  , ncons
  , nuncons
  , splitFirst
  , nfilter
  , nfilterM
  , nReplicate
  , head
  , tail
  , last
  , init
  , ofoldMap1
  , ofold1
  , ofoldr1
  , ofoldl1'
  , maximum
  , maximumBy
  , minimum
  , minimumBy
  , (<|)
  , toMinList
  , mapNonNull
  , GrowingAppend
) where
import Prelude hiding (head, tail, init, last, reverse, seq, filter, replicate, maximum, minimum)
import Control.Arrow (second)
import Control.Exception.Base (Exception, throw)
import Data.Data
import qualified Data.List.NonEmpty as NE
import Data.Maybe (fromMaybe)
import Data.MonoTraversable
import Data.Sequences
import Control.Monad.Trans.State.Strict (evalState, state)
data NullError = NullError String deriving (Int -> NullError -> ShowS
[NullError] -> ShowS
NullError -> String
(Int -> NullError -> ShowS)
-> (NullError -> String)
-> ([NullError] -> ShowS)
-> Show NullError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NullError -> ShowS
showsPrec :: Int -> NullError -> ShowS
$cshow :: NullError -> String
show :: NullError -> String
$cshowList :: [NullError] -> ShowS
showList :: [NullError] -> ShowS
Show, Typeable)
instance Exception NullError
newtype NonNull mono = NonNull
    { forall mono. NonNull mono -> mono
toNullable :: mono
    
    }
    deriving (NonNull mono -> NonNull mono -> Bool
(NonNull mono -> NonNull mono -> Bool)
-> (NonNull mono -> NonNull mono -> Bool) -> Eq (NonNull mono)
forall mono. Eq mono => NonNull mono -> NonNull mono -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall mono. Eq mono => NonNull mono -> NonNull mono -> Bool
== :: NonNull mono -> NonNull mono -> Bool
$c/= :: forall mono. Eq mono => NonNull mono -> NonNull mono -> Bool
/= :: NonNull mono -> NonNull mono -> Bool
Eq, Eq (NonNull mono)
Eq (NonNull mono) =>
(NonNull mono -> NonNull mono -> Ordering)
-> (NonNull mono -> NonNull mono -> Bool)
-> (NonNull mono -> NonNull mono -> Bool)
-> (NonNull mono -> NonNull mono -> Bool)
-> (NonNull mono -> NonNull mono -> Bool)
-> (NonNull mono -> NonNull mono -> NonNull mono)
-> (NonNull mono -> NonNull mono -> NonNull mono)
-> Ord (NonNull mono)
NonNull mono -> NonNull mono -> Bool
NonNull mono -> NonNull mono -> Ordering
NonNull mono -> NonNull mono -> NonNull mono
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall mono. Ord mono => Eq (NonNull mono)
forall mono. Ord mono => NonNull mono -> NonNull mono -> Bool
forall mono. Ord mono => NonNull mono -> NonNull mono -> Ordering
forall mono.
Ord mono =>
NonNull mono -> NonNull mono -> NonNull mono
$ccompare :: forall mono. Ord mono => NonNull mono -> NonNull mono -> Ordering
compare :: NonNull mono -> NonNull mono -> Ordering
$c< :: forall mono. Ord mono => NonNull mono -> NonNull mono -> Bool
< :: NonNull mono -> NonNull mono -> Bool
$c<= :: forall mono. Ord mono => NonNull mono -> NonNull mono -> Bool
<= :: NonNull mono -> NonNull mono -> Bool
$c> :: forall mono. Ord mono => NonNull mono -> NonNull mono -> Bool
> :: NonNull mono -> NonNull mono -> Bool
$c>= :: forall mono. Ord mono => NonNull mono -> NonNull mono -> Bool
>= :: NonNull mono -> NonNull mono -> Bool
$cmax :: forall mono.
Ord mono =>
NonNull mono -> NonNull mono -> NonNull mono
max :: NonNull mono -> NonNull mono -> NonNull mono
$cmin :: forall mono.
Ord mono =>
NonNull mono -> NonNull mono -> NonNull mono
min :: NonNull mono -> NonNull mono -> NonNull mono
Ord, ReadPrec [NonNull mono]
ReadPrec (NonNull mono)
Int -> ReadS (NonNull mono)
ReadS [NonNull mono]
(Int -> ReadS (NonNull mono))
-> ReadS [NonNull mono]
-> ReadPrec (NonNull mono)
-> ReadPrec [NonNull mono]
-> Read (NonNull mono)
forall mono. Read mono => ReadPrec [NonNull mono]
forall mono. Read mono => ReadPrec (NonNull mono)
forall mono. Read mono => Int -> ReadS (NonNull mono)
forall mono. Read mono => ReadS [NonNull mono]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall mono. Read mono => Int -> ReadS (NonNull mono)
readsPrec :: Int -> ReadS (NonNull mono)
$creadList :: forall mono. Read mono => ReadS [NonNull mono]
readList :: ReadS [NonNull mono]
$creadPrec :: forall mono. Read mono => ReadPrec (NonNull mono)
readPrec :: ReadPrec (NonNull mono)
$creadListPrec :: forall mono. Read mono => ReadPrec [NonNull mono]
readListPrec :: ReadPrec [NonNull mono]
Read, Int -> NonNull mono -> ShowS
[NonNull mono] -> ShowS
NonNull mono -> String
(Int -> NonNull mono -> ShowS)
-> (NonNull mono -> String)
-> ([NonNull mono] -> ShowS)
-> Show (NonNull mono)
forall mono. Show mono => Int -> NonNull mono -> ShowS
forall mono. Show mono => [NonNull mono] -> ShowS
forall mono. Show mono => NonNull mono -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall mono. Show mono => Int -> NonNull mono -> ShowS
showsPrec :: Int -> NonNull mono -> ShowS
$cshow :: forall mono. Show mono => NonNull mono -> String
show :: NonNull mono -> String
$cshowList :: forall mono. Show mono => [NonNull mono] -> ShowS
showList :: [NonNull mono] -> ShowS
Show, Typeable (NonNull mono)
Typeable (NonNull mono) =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> NonNull mono -> c (NonNull mono))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (NonNull mono))
-> (NonNull mono -> Constr)
-> (NonNull mono -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (NonNull mono)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (NonNull mono)))
-> ((forall b. Data b => b -> b) -> NonNull mono -> NonNull mono)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> NonNull mono -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> NonNull mono -> r)
-> (forall u. (forall d. Data d => d -> u) -> NonNull mono -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> NonNull mono -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono))
-> Data (NonNull mono)
NonNull mono -> Constr
NonNull mono -> DataType
(forall b. Data b => b -> b) -> NonNull mono -> NonNull mono
forall mono. Data mono => Typeable (NonNull mono)
forall mono. Data mono => NonNull mono -> Constr
forall mono. Data mono => NonNull mono -> DataType
forall mono.
Data mono =>
(forall b. Data b => b -> b) -> NonNull mono -> NonNull mono
forall mono u.
Data mono =>
Int -> (forall d. Data d => d -> u) -> NonNull mono -> u
forall mono u.
Data mono =>
(forall d. Data d => d -> u) -> NonNull mono -> [u]
forall mono r r'.
Data mono =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonNull mono -> r
forall mono r r'.
Data mono =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonNull mono -> r
forall mono (m :: * -> *).
(Data mono, Monad m) =>
(forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono)
forall mono (m :: * -> *).
(Data mono, MonadPlus m) =>
(forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono)
forall mono (c :: * -> *).
Data mono =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (NonNull mono)
forall mono (c :: * -> *).
Data mono =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonNull mono -> c (NonNull mono)
forall mono (t :: * -> *) (c :: * -> *).
(Data mono, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (NonNull mono))
forall mono (t :: * -> * -> *) (c :: * -> *).
(Data mono, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (NonNull mono))
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> NonNull mono -> u
forall u. (forall d. Data d => d -> u) -> NonNull mono -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonNull mono -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonNull mono -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (NonNull mono)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonNull mono -> c (NonNull mono)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (NonNull mono))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (NonNull mono))
$cgfoldl :: forall mono (c :: * -> *).
Data mono =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonNull mono -> c (NonNull mono)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonNull mono -> c (NonNull mono)
$cgunfold :: forall mono (c :: * -> *).
Data mono =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (NonNull mono)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (NonNull mono)
$ctoConstr :: forall mono. Data mono => NonNull mono -> Constr
toConstr :: NonNull mono -> Constr
$cdataTypeOf :: forall mono. Data mono => NonNull mono -> DataType
dataTypeOf :: NonNull mono -> DataType
$cdataCast1 :: forall mono (t :: * -> *) (c :: * -> *).
(Data mono, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (NonNull mono))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (NonNull mono))
$cdataCast2 :: forall mono (t :: * -> * -> *) (c :: * -> *).
(Data mono, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (NonNull mono))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (NonNull mono))
$cgmapT :: forall mono.
Data mono =>
(forall b. Data b => b -> b) -> NonNull mono -> NonNull mono
gmapT :: (forall b. Data b => b -> b) -> NonNull mono -> NonNull mono
$cgmapQl :: forall mono r r'.
Data mono =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonNull mono -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonNull mono -> r
$cgmapQr :: forall mono r r'.
Data mono =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonNull mono -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonNull mono -> r
$cgmapQ :: forall mono u.
Data mono =>
(forall d. Data d => d -> u) -> NonNull mono -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> NonNull mono -> [u]
$cgmapQi :: forall mono u.
Data mono =>
Int -> (forall d. Data d => d -> u) -> NonNull mono -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NonNull mono -> u
$cgmapM :: forall mono (m :: * -> *).
(Data mono, Monad m) =>
(forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono)
$cgmapMp :: forall mono (m :: * -> *).
(Data mono, MonadPlus m) =>
(forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono)
$cgmapMo :: forall mono (m :: * -> *).
(Data mono, MonadPlus m) =>
(forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono)
Data, Typeable)
type instance Element (NonNull mono) = Element mono
deriving instance MonoFunctor mono => MonoFunctor (NonNull mono)
deriving instance MonoFoldable mono => MonoFoldable (NonNull mono)
instance MonoTraversable mono => MonoTraversable (NonNull mono) where
    otraverse :: forall (f :: * -> *).
Applicative f =>
(Element (NonNull mono) -> f (Element (NonNull mono)))
-> NonNull mono -> f (NonNull mono)
otraverse Element (NonNull mono) -> f (Element (NonNull mono))
f (NonNull mono
x) = (mono -> NonNull mono) -> f mono -> f (NonNull mono)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap mono -> NonNull mono
forall mono. mono -> NonNull mono
NonNull ((Element mono -> f (Element mono)) -> mono -> f mono
forall mono (f :: * -> *).
(MonoTraversable mono, Applicative f) =>
(Element mono -> f (Element mono)) -> mono -> f mono
forall (f :: * -> *).
Applicative f =>
(Element mono -> f (Element mono)) -> mono -> f mono
otraverse Element mono -> f (Element mono)
Element (NonNull mono) -> f (Element (NonNull mono))
f mono
x)
    {-# INLINE otraverse #-}
instance GrowingAppend mono => GrowingAppend (NonNull mono)
instance (Semigroup mono, GrowingAppend mono) => Semigroup (NonNull mono) where
    NonNull mono
x <> :: NonNull mono -> NonNull mono -> NonNull mono
<> NonNull mono
y = mono -> NonNull mono
forall mono. mono -> NonNull mono
NonNull (mono
x mono -> mono -> mono
forall a. Semigroup a => a -> a -> a
<> mono
y)
instance SemiSequence seq => SemiSequence (NonNull seq) where
    type Index (NonNull seq) = Index seq
    intersperse :: Element (NonNull seq) -> NonNull seq -> NonNull seq
intersperse Element (NonNull seq)
e = (seq -> seq) -> NonNull seq -> NonNull seq
forall mono. (mono -> mono) -> NonNull mono -> NonNull mono
unsafeMap ((seq -> seq) -> NonNull seq -> NonNull seq)
-> (seq -> seq) -> NonNull seq -> NonNull seq
forall a b. (a -> b) -> a -> b
$ Element seq -> seq -> seq
forall seq. SemiSequence seq => Element seq -> seq -> seq
intersperse Element seq
Element (NonNull seq)
e
    reverse :: NonNull seq -> NonNull seq
reverse       = (seq -> seq) -> NonNull seq -> NonNull seq
forall mono. (mono -> mono) -> NonNull mono -> NonNull mono
unsafeMap seq -> seq
forall seq. SemiSequence seq => seq -> seq
reverse
    find :: (Element (NonNull seq) -> Bool)
-> NonNull seq -> Maybe (Element (NonNull seq))
find Element (NonNull seq) -> Bool
f        = (Element seq -> Bool) -> seq -> Maybe (Element seq)
forall seq.
SemiSequence seq =>
(Element seq -> Bool) -> seq -> Maybe (Element seq)
find Element seq -> Bool
Element (NonNull seq) -> Bool
f (seq -> Maybe (Element seq))
-> (NonNull seq -> seq) -> NonNull seq -> Maybe (Element seq)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNull seq -> seq
forall mono. NonNull mono -> mono
toNullable
    cons :: Element (NonNull seq) -> NonNull seq -> NonNull seq
cons Element (NonNull seq)
x        = (seq -> seq) -> NonNull seq -> NonNull seq
forall mono. (mono -> mono) -> NonNull mono -> NonNull mono
unsafeMap ((seq -> seq) -> NonNull seq -> NonNull seq)
-> (seq -> seq) -> NonNull seq -> NonNull seq
forall a b. (a -> b) -> a -> b
$ Element seq -> seq -> seq
forall seq. SemiSequence seq => Element seq -> seq -> seq
cons Element seq
Element (NonNull seq)
x
    snoc :: NonNull seq -> Element (NonNull seq) -> NonNull seq
snoc NonNull seq
xs Element (NonNull seq)
x     = (seq -> seq) -> NonNull seq -> NonNull seq
forall mono. (mono -> mono) -> NonNull mono -> NonNull mono
unsafeMap ((seq -> Element seq -> seq) -> Element seq -> seq -> seq
forall a b c. (a -> b -> c) -> b -> a -> c
flip seq -> Element seq -> seq
forall seq. SemiSequence seq => seq -> Element seq -> seq
snoc Element seq
Element (NonNull seq)
x) NonNull seq
xs
    sortBy :: (Element (NonNull seq) -> Element (NonNull seq) -> Ordering)
-> NonNull seq -> NonNull seq
sortBy Element (NonNull seq) -> Element (NonNull seq) -> Ordering
f      = (seq -> seq) -> NonNull seq -> NonNull seq
forall mono. (mono -> mono) -> NonNull mono -> NonNull mono
unsafeMap ((seq -> seq) -> NonNull seq -> NonNull seq)
-> (seq -> seq) -> NonNull seq -> NonNull seq
forall a b. (a -> b) -> a -> b
$ (Element seq -> Element seq -> Ordering) -> seq -> seq
forall seq.
SemiSequence seq =>
(Element seq -> Element seq -> Ordering) -> seq -> seq
sortBy Element seq -> Element seq -> Ordering
Element (NonNull seq) -> Element (NonNull seq) -> Ordering
f
unsafeMap :: (mono -> mono) -> NonNull mono -> NonNull mono
unsafeMap :: forall mono. (mono -> mono) -> NonNull mono -> NonNull mono
unsafeMap mono -> mono
f (NonNull mono
x) = mono -> NonNull mono
forall mono. mono -> NonNull mono
NonNull (mono -> mono
f mono
x)
instance MonoPointed mono => MonoPointed (NonNull mono) where
    opoint :: Element (NonNull mono) -> NonNull mono
opoint = mono -> NonNull mono
forall mono. mono -> NonNull mono
NonNull (mono -> NonNull mono)
-> (Element mono -> mono) -> Element mono -> NonNull mono
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element mono -> mono
forall mono. MonoPointed mono => Element mono -> mono
opoint
    {-# INLINE opoint #-}
instance IsSequence mono => MonoComonad (NonNull mono) where
        oextract :: NonNull mono -> Element (NonNull mono)
oextract  = NonNull mono -> Element mono
NonNull mono -> Element (NonNull mono)
forall mono. MonoFoldable mono => NonNull mono -> Element mono
head
        oextend :: (NonNull mono -> Element (NonNull mono))
-> NonNull mono -> NonNull mono
oextend NonNull mono -> Element (NonNull mono)
f (NonNull mono
mono) = mono -> NonNull mono
forall mono. mono -> NonNull mono
NonNull
                                 (mono -> NonNull mono)
-> ((mono -> (Element mono, mono)) -> mono)
-> (mono -> (Element mono, mono))
-> NonNull mono
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (State mono mono -> mono -> mono)
-> mono -> State mono mono -> mono
forall a b c. (a -> b -> c) -> b -> a -> c
flip State mono mono -> mono -> mono
forall s a. State s a -> s -> a
evalState mono
mono
                                 (State mono mono -> mono)
-> ((mono -> (Element mono, mono)) -> State mono mono)
-> (mono -> (Element mono, mono))
-> mono
forall b c a. (b -> c) -> (a -> b) -> a -> c
. mono
-> (Element mono -> StateT mono Identity (Element mono))
-> State mono mono
forall mono (f :: * -> *).
(MonoTraversable mono, Applicative f) =>
mono -> (Element mono -> f (Element mono)) -> f mono
ofor mono
mono
                                 ((Element mono -> StateT mono Identity (Element mono))
 -> State mono mono)
-> ((mono -> (Element mono, mono))
    -> Element mono -> StateT mono Identity (Element mono))
-> (mono -> (Element mono, mono))
-> State mono mono
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT mono Identity (Element mono)
-> Element mono -> StateT mono Identity (Element mono)
forall a b. a -> b -> a
const
                                 (StateT mono Identity (Element mono)
 -> Element mono -> StateT mono Identity (Element mono))
-> ((mono -> (Element mono, mono))
    -> StateT mono Identity (Element mono))
-> (mono -> (Element mono, mono))
-> Element mono
-> StateT mono Identity (Element mono)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (mono -> (Element mono, mono))
-> StateT mono Identity (Element mono)
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
state
                                 ((mono -> (Element mono, mono)) -> NonNull mono)
-> (mono -> (Element mono, mono)) -> NonNull mono
forall a b. (a -> b) -> a -> b
$ \mono
mono' -> (NonNull mono -> Element (NonNull mono)
f (mono -> NonNull mono
forall mono. mono -> NonNull mono
NonNull mono
mono'), mono -> mono
forall seq. IsSequence seq => seq -> seq
tailEx mono
mono')
fromNullable :: MonoFoldable mono => mono -> Maybe (NonNull mono)
fromNullable :: forall mono. MonoFoldable mono => mono -> Maybe (NonNull mono)
fromNullable mono
mono
    | mono -> Bool
forall mono. MonoFoldable mono => mono -> Bool
onull mono
mono = Maybe (NonNull mono)
forall a. Maybe a
Nothing
    | Bool
otherwise = NonNull mono -> Maybe (NonNull mono)
forall a. a -> Maybe a
Just (mono -> NonNull mono
forall mono. mono -> NonNull mono
NonNull mono
mono)
impureNonNull :: MonoFoldable mono => mono -> NonNull mono
impureNonNull :: forall mono. MonoFoldable mono => mono -> NonNull mono
impureNonNull mono
nullable =
  NonNull mono -> Maybe (NonNull mono) -> NonNull mono
forall a. a -> Maybe a -> a
fromMaybe (NullError -> NonNull mono
forall a e. Exception e => e -> a
throw (NullError -> NonNull mono) -> NullError -> NonNull mono
forall a b. (a -> b) -> a -> b
$ String -> NullError
NullError String
"Data.NonNull.impureNonNull (NonNull default): expected non-null")
          (Maybe (NonNull mono) -> NonNull mono)
-> Maybe (NonNull mono) -> NonNull mono
forall a b. (a -> b) -> a -> b
$ mono -> Maybe (NonNull mono)
forall mono. MonoFoldable mono => mono -> Maybe (NonNull mono)
fromNullable mono
nullable
nonNull :: MonoFoldable mono => mono -> NonNull mono
nonNull :: forall mono. MonoFoldable mono => mono -> NonNull mono
nonNull = mono -> NonNull mono
forall mono. MonoFoldable mono => mono -> NonNull mono
impureNonNull
{-# DEPRECATED nonNull "Please use the more explicit impureNonNull instead" #-}
fromNonEmpty :: IsSequence seq => NE.NonEmpty (Element seq) -> NonNull seq
fromNonEmpty :: forall seq. IsSequence seq => NonEmpty (Element seq) -> NonNull seq
fromNonEmpty = seq -> NonNull seq
forall mono. MonoFoldable mono => mono -> NonNull mono
impureNonNull (seq -> NonNull seq)
-> (NonEmpty (Element seq) -> seq)
-> NonEmpty (Element seq)
-> NonNull seq
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Element seq] -> seq
forall seq. IsSequence seq => [Element seq] -> seq
fromList ([Element seq] -> seq)
-> (NonEmpty (Element seq) -> [Element seq])
-> NonEmpty (Element seq)
-> seq
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty (Element seq) -> [Element seq]
forall a. NonEmpty a -> [a]
NE.toList
{-# INLINE fromNonEmpty #-}
toNonEmpty :: MonoFoldable mono => NonNull mono -> NE.NonEmpty (Element mono)
toNonEmpty :: forall mono.
MonoFoldable mono =>
NonNull mono -> NonEmpty (Element mono)
toNonEmpty = [Element mono] -> NonEmpty (Element mono)
forall a. HasCallStack => [a] -> NonEmpty a
NE.fromList ([Element mono] -> NonEmpty (Element mono))
-> (NonNull mono -> [Element mono])
-> NonNull mono
-> NonEmpty (Element mono)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNull mono -> [Element mono]
NonNull mono -> [Element (NonNull mono)]
forall mono. MonoFoldable mono => mono -> [Element mono]
otoList
toMinList :: NE.NonEmpty a -> NonNull [a]
toMinList :: forall a. NonEmpty a -> NonNull [a]
toMinList = NonEmpty a -> NonNull [a]
NonEmpty (Element [a]) -> NonNull [a]
forall seq. IsSequence seq => NonEmpty (Element seq) -> NonNull seq
fromNonEmpty
ncons :: SemiSequence seq => Element seq -> seq -> NonNull seq
ncons :: forall seq. SemiSequence seq => Element seq -> seq -> NonNull seq
ncons Element seq
x seq
xs = seq -> NonNull seq
forall mono. MonoFoldable mono => mono -> NonNull mono
nonNull (seq -> NonNull seq) -> seq -> NonNull seq
forall a b. (a -> b) -> a -> b
$ Element seq -> seq -> seq
forall seq. SemiSequence seq => Element seq -> seq -> seq
cons Element seq
x seq
xs
nuncons :: IsSequence seq => NonNull seq -> (Element seq, Maybe (NonNull seq))
nuncons :: forall seq.
IsSequence seq =>
NonNull seq -> (Element seq, Maybe (NonNull seq))
nuncons NonNull seq
xs =
  (seq -> Maybe (NonNull seq))
-> (Element seq, seq) -> (Element seq, Maybe (NonNull seq))
forall b c d. (b -> c) -> (d, b) -> (d, c)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second seq -> Maybe (NonNull seq)
forall mono. MonoFoldable mono => mono -> Maybe (NonNull mono)
fromNullable
    ((Element seq, seq) -> (Element seq, Maybe (NonNull seq)))
-> (Element seq, seq) -> (Element seq, Maybe (NonNull seq))
forall a b. (a -> b) -> a -> b
$ (Element seq, seq)
-> Maybe (Element seq, seq) -> (Element seq, seq)
forall a. a -> Maybe a -> a
fromMaybe (String -> (Element seq, seq)
forall a. HasCallStack => String -> a
error String
"Data.NonNull.nuncons: data structure is null, it should be non-null")
              (Maybe (Element seq, seq) -> (Element seq, seq))
-> Maybe (Element seq, seq) -> (Element seq, seq)
forall a b. (a -> b) -> a -> b
$ seq -> Maybe (Element seq, seq)
forall seq. IsSequence seq => seq -> Maybe (Element seq, seq)
uncons (NonNull seq -> seq
forall mono. NonNull mono -> mono
toNullable NonNull seq
xs)
splitFirst :: IsSequence seq => NonNull seq -> (Element seq, seq)
splitFirst :: forall seq. IsSequence seq => NonNull seq -> (Element seq, seq)
splitFirst NonNull seq
xs =
  (Element seq, seq)
-> Maybe (Element seq, seq) -> (Element seq, seq)
forall a. a -> Maybe a -> a
fromMaybe (String -> (Element seq, seq)
forall a. HasCallStack => String -> a
error String
"Data.NonNull.splitFirst: data structure is null, it should be non-null")
          (Maybe (Element seq, seq) -> (Element seq, seq))
-> Maybe (Element seq, seq) -> (Element seq, seq)
forall a b. (a -> b) -> a -> b
$ seq -> Maybe (Element seq, seq)
forall seq. IsSequence seq => seq -> Maybe (Element seq, seq)
uncons (NonNull seq -> seq
forall mono. NonNull mono -> mono
toNullable NonNull seq
xs)
nfilter :: IsSequence seq => (Element seq -> Bool) -> NonNull seq -> seq
nfilter :: forall seq.
IsSequence seq =>
(Element seq -> Bool) -> NonNull seq -> seq
nfilter Element seq -> Bool
f = (Element seq -> Bool) -> seq -> seq
forall seq. IsSequence seq => (Element seq -> Bool) -> seq -> seq
filter Element seq -> Bool
f (seq -> seq) -> (NonNull seq -> seq) -> NonNull seq -> seq
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNull seq -> seq
forall mono. NonNull mono -> mono
toNullable
nfilterM :: (Monad m, IsSequence seq) => (Element seq -> m Bool) -> NonNull seq -> m seq
nfilterM :: forall (m :: * -> *) seq.
(Monad m, IsSequence seq) =>
(Element seq -> m Bool) -> NonNull seq -> m seq
nfilterM Element seq -> m Bool
f = (Element seq -> m Bool) -> seq -> m seq
forall seq (m :: * -> *).
(IsSequence seq, Monad m) =>
(Element seq -> m Bool) -> seq -> m seq
forall (m :: * -> *).
Monad m =>
(Element seq -> m Bool) -> seq -> m seq
filterM Element seq -> m Bool
f (seq -> m seq) -> (NonNull seq -> seq) -> NonNull seq -> m seq
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNull seq -> seq
forall mono. NonNull mono -> mono
toNullable
nReplicate :: IsSequence seq => Index seq -> Element seq -> NonNull seq
nReplicate :: forall seq.
IsSequence seq =>
Index seq -> Element seq -> NonNull seq
nReplicate Index seq
i = seq -> NonNull seq
forall mono. MonoFoldable mono => mono -> NonNull mono
nonNull (seq -> NonNull seq)
-> (Element seq -> seq) -> Element seq -> NonNull seq
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index seq -> Element seq -> seq
forall seq. IsSequence seq => Index seq -> Element seq -> seq
replicate (Index seq -> Index seq -> Index seq
forall a. Ord a => a -> a -> a
max Index seq
1 Index seq
i)
tail :: IsSequence seq => NonNull seq -> seq
tail :: forall seq. IsSequence seq => NonNull seq -> seq
tail = seq -> seq
forall seq. IsSequence seq => seq -> seq
tailEx (seq -> seq) -> (NonNull seq -> seq) -> NonNull seq -> seq
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNull seq -> seq
forall mono. NonNull mono -> mono
toNullable
{-# INLINE tail #-}
init :: IsSequence seq => NonNull seq -> seq
init :: forall seq. IsSequence seq => NonNull seq -> seq
init = seq -> seq
forall seq. IsSequence seq => seq -> seq
initEx (seq -> seq) -> (NonNull seq -> seq) -> NonNull seq -> seq
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNull seq -> seq
forall mono. NonNull mono -> mono
toNullable
{-# INLINE init #-}
infixr 5 <|
(<|) :: SemiSequence seq => Element seq -> NonNull seq -> NonNull seq
Element seq
x <| :: forall seq.
SemiSequence seq =>
Element seq -> NonNull seq -> NonNull seq
<| NonNull seq
y = Element seq -> seq -> NonNull seq
forall seq. SemiSequence seq => Element seq -> seq -> NonNull seq
ncons Element seq
x (NonNull seq -> seq
forall mono. NonNull mono -> mono
toNullable NonNull seq
y)
head :: MonoFoldable mono => NonNull mono -> Element mono
head :: forall mono. MonoFoldable mono => NonNull mono -> Element mono
head = mono -> Element mono
forall mono. MonoFoldable mono => mono -> Element mono
headEx (mono -> Element mono)
-> (NonNull mono -> mono) -> NonNull mono -> Element mono
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNull mono -> mono
forall mono. NonNull mono -> mono
toNullable
{-# INLINE head #-}
last :: MonoFoldable mono => NonNull mono -> Element mono
last :: forall mono. MonoFoldable mono => NonNull mono -> Element mono
last = mono -> Element mono
forall mono. MonoFoldable mono => mono -> Element mono
lastEx (mono -> Element mono)
-> (NonNull mono -> mono) -> NonNull mono -> Element mono
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNull mono -> mono
forall mono. NonNull mono -> mono
toNullable
{-# INLINE last #-}
ofoldMap1 :: (MonoFoldable mono, Semigroup m) => (Element mono -> m) -> NonNull mono -> m
ofoldMap1 :: forall mono m.
(MonoFoldable mono, Semigroup m) =>
(Element mono -> m) -> NonNull mono -> m
ofoldMap1 Element mono -> m
f = (Element mono -> m) -> mono -> m
forall m. Semigroup m => (Element mono -> m) -> mono -> m
forall mono m.
(MonoFoldable mono, Semigroup m) =>
(Element mono -> m) -> mono -> m
ofoldMap1Ex Element mono -> m
f (mono -> m) -> (NonNull mono -> mono) -> NonNull mono -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNull mono -> mono
forall mono. NonNull mono -> mono
toNullable
{-# INLINE ofoldMap1 #-}
ofold1 :: (MonoFoldable mono, Semigroup (Element mono)) => NonNull mono -> Element mono
ofold1 :: forall mono.
(MonoFoldable mono, Semigroup (Element mono)) =>
NonNull mono -> Element mono
ofold1 = (Element mono -> Element mono) -> NonNull mono -> Element mono
forall mono m.
(MonoFoldable mono, Semigroup m) =>
(Element mono -> m) -> NonNull mono -> m
ofoldMap1 Element mono -> Element mono
forall a. a -> a
id
{-# INLINE ofold1 #-}
ofoldr1 :: MonoFoldable mono
        => (Element mono -> Element mono -> Element mono)
        -> NonNull mono
        -> Element mono
ofoldr1 :: forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Element mono)
-> NonNull mono -> Element mono
ofoldr1 Element mono -> Element mono -> Element mono
f = (Element mono -> Element mono -> Element mono)
-> mono -> Element mono
forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Element mono)
-> mono -> Element mono
ofoldr1Ex Element mono -> Element mono -> Element mono
f (mono -> Element mono)
-> (NonNull mono -> mono) -> NonNull mono -> Element mono
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNull mono -> mono
forall mono. NonNull mono -> mono
toNullable
{-# INLINE ofoldr1 #-}
ofoldl1' :: MonoFoldable mono
         => (Element mono -> Element mono -> Element mono)
         -> NonNull mono
         -> Element mono
ofoldl1' :: forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Element mono)
-> NonNull mono -> Element mono
ofoldl1' Element mono -> Element mono -> Element mono
f = (Element mono -> Element mono -> Element mono)
-> mono -> Element mono
forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Element mono)
-> mono -> Element mono
ofoldl1Ex' Element mono -> Element mono -> Element mono
f (mono -> Element mono)
-> (NonNull mono -> mono) -> NonNull mono -> Element mono
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNull mono -> mono
forall mono. NonNull mono -> mono
toNullable
{-# INLINE ofoldl1' #-}
maximum :: (MonoFoldable mono, Ord (Element mono))
        => NonNull mono
        -> Element mono
maximum :: forall mono.
(MonoFoldable mono, Ord (Element mono)) =>
NonNull mono -> Element mono
maximum = mono -> Element mono
forall mono.
(MonoFoldable mono, Ord (Element mono)) =>
mono -> Element mono
maximumEx (mono -> Element mono)
-> (NonNull mono -> mono) -> NonNull mono -> Element mono
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNull mono -> mono
forall mono. NonNull mono -> mono
toNullable
{-# INLINE maximum #-}
minimum :: (MonoFoldable mono, Ord (Element mono))
        => NonNull mono
        -> Element mono
minimum :: forall mono.
(MonoFoldable mono, Ord (Element mono)) =>
NonNull mono -> Element mono
minimum = mono -> Element mono
forall mono.
(MonoFoldable mono, Ord (Element mono)) =>
mono -> Element mono
minimumEx (mono -> Element mono)
-> (NonNull mono -> mono) -> NonNull mono -> Element mono
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNull mono -> mono
forall mono. NonNull mono -> mono
toNullable
{-# INLINE minimum #-}
maximumBy :: MonoFoldable mono
          => (Element mono -> Element mono -> Ordering)
          -> NonNull mono
          -> Element mono
maximumBy :: forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Ordering)
-> NonNull mono -> Element mono
maximumBy Element mono -> Element mono -> Ordering
cmp = (Element mono -> Element mono -> Ordering) -> mono -> Element mono
forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Ordering) -> mono -> Element mono
maximumByEx Element mono -> Element mono -> Ordering
cmp (mono -> Element mono)
-> (NonNull mono -> mono) -> NonNull mono -> Element mono
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNull mono -> mono
forall mono. NonNull mono -> mono
toNullable
{-# INLINE maximumBy #-}
minimumBy :: MonoFoldable mono
          => (Element mono -> Element mono -> Ordering)
          -> NonNull mono
          -> Element mono
minimumBy :: forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Ordering)
-> NonNull mono -> Element mono
minimumBy Element mono -> Element mono -> Ordering
cmp = (Element mono -> Element mono -> Ordering) -> mono -> Element mono
forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Ordering) -> mono -> Element mono
minimumByEx Element mono -> Element mono -> Ordering
cmp (mono -> Element mono)
-> (NonNull mono -> mono) -> NonNull mono -> Element mono
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNull mono -> mono
forall mono. NonNull mono -> mono
toNullable
{-# INLINE minimumBy #-}
mapNonNull :: (Functor f, MonoFoldable (f b))
           => (a -> b)
           -> NonNull (f a)
           -> NonNull (f b)
mapNonNull :: forall (f :: * -> *) b a.
(Functor f, MonoFoldable (f b)) =>
(a -> b) -> NonNull (f a) -> NonNull (f b)
mapNonNull a -> b
f = f b -> NonNull (f b)
forall mono. MonoFoldable mono => mono -> NonNull mono
impureNonNull (f b -> NonNull (f b))
-> (NonNull (f a) -> f b) -> NonNull (f a) -> NonNull (f b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> f a -> f b
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (f a -> f b) -> (NonNull (f a) -> f a) -> NonNull (f a) -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNull (f a) -> f a
forall mono. NonNull mono -> mono
toNullable