{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}

{- |
Module      : Primus.One
Description : holds a singleton value
Copyright   : (c) Grant Weyburne, 2016
License     : BSD-3

handles a tuple of size one. this is a special type that distinguishes a singleton value from a ntuple
will be replaced by Solo when ghc 9.2 is standard and generics-sop is updated to support Solo
-}
module Primus.One (
  One (..),
  unOne,
) where

import Control.DeepSeq
import Data.Coerce
import Data.Data
import qualified Data.Functor.Apply as Apply
import Data.Semigroup.Foldable
import Data.Semigroup.Traversable
import GHC.Generics (Generic, Generic1)

-- | unwrap 'One'
unOne :: One a -> a
unOne :: One a -> a
unOne = One a -> a
coerce

-- | One holds a single value. To use wprint we need a SOP Generics instance
newtype One a = One a
  deriving stock (Typeable (One a)
DataType
Constr
Typeable (One a)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> One a -> c (One a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (One a))
-> (One a -> Constr)
-> (One a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (One a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (One a)))
-> ((forall b. Data b => b -> b) -> One a -> One a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> One a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> One a -> r)
-> (forall u. (forall d. Data d => d -> u) -> One a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> One a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> One a -> m (One a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> One a -> m (One a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> One a -> m (One a))
-> Data (One a)
One a -> DataType
One a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (One a))
(forall b. Data b => b -> b) -> One a -> One a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> One a -> c (One a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (One a)
forall a. Data a => Typeable (One a)
forall a. Data a => One a -> DataType
forall a. Data a => One a -> Constr
forall a. Data a => (forall b. Data b => b -> b) -> One a -> One a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> One a -> u
forall a u. Data a => (forall d. Data d => d -> u) -> One a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> One a -> r
forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> One a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> One a -> m (One a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> One a -> m (One a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (One a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> One a -> c (One a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (One a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (One a))
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) -> One a -> u
forall u. (forall d. Data d => d -> u) -> One a -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> One a -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> One a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> One a -> m (One a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> One a -> m (One a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (One a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> One a -> c (One a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (One a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (One a))
$cOne :: Constr
$tOne :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> One a -> m (One a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> One a -> m (One a)
gmapMp :: (forall d. Data d => d -> m d) -> One a -> m (One a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> One a -> m (One a)
gmapM :: (forall d. Data d => d -> m d) -> One a -> m (One a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> One a -> m (One a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> One a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> One a -> u
gmapQ :: (forall d. Data d => d -> u) -> One a -> [u]
$cgmapQ :: forall a u. Data a => (forall d. Data d => d -> u) -> One a -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> One a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> One a -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> One a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> One a -> r
gmapT :: (forall b. Data b => b -> b) -> One a -> One a
$cgmapT :: forall a. Data a => (forall b. Data b => b -> b) -> One a -> One a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (One a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (One a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (One a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (One a))
dataTypeOf :: One a -> DataType
$cdataTypeOf :: forall a. Data a => One a -> DataType
toConstr :: One a -> Constr
$ctoConstr :: forall a. Data a => One a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (One a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (One a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> One a -> c (One a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> One a -> c (One a)
$cp1Data :: forall a. Data a => Typeable (One a)
Data, (forall x. One a -> Rep (One a) x)
-> (forall x. Rep (One a) x -> One a) -> Generic (One a)
forall x. Rep (One a) x -> One a
forall x. One a -> Rep (One a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (One a) x -> One a
forall a x. One a -> Rep (One a) x
$cto :: forall a x. Rep (One a) x -> One a
$cfrom :: forall a x. One a -> Rep (One a) x
Generic, (forall a. One a -> Rep1 One a)
-> (forall a. Rep1 One a -> One a) -> Generic1 One
forall a. Rep1 One a -> One a
forall a. One a -> Rep1 One a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cto1 :: forall a. Rep1 One a -> One a
$cfrom1 :: forall a. One a -> Rep1 One a
Generic1, Int -> One a -> ShowS
[One a] -> ShowS
One a -> String
(Int -> One a -> ShowS)
-> (One a -> String) -> ([One a] -> ShowS) -> Show (One a)
forall a. Show a => Int -> One a -> ShowS
forall a. Show a => [One a] -> ShowS
forall a. Show a => One a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [One a] -> ShowS
$cshowList :: forall a. Show a => [One a] -> ShowS
show :: One a -> String
$cshow :: forall a. Show a => One a -> String
showsPrec :: Int -> One a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> One a -> ShowS
Show, One a -> One a -> Bool
(One a -> One a -> Bool) -> (One a -> One a -> Bool) -> Eq (One a)
forall a. Eq a => One a -> One a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: One a -> One a -> Bool
$c/= :: forall a. Eq a => One a -> One a -> Bool
== :: One a -> One a -> Bool
$c== :: forall a. Eq a => One a -> One a -> Bool
Eq, Eq (One a)
Eq (One a)
-> (One a -> One a -> Ordering)
-> (One a -> One a -> Bool)
-> (One a -> One a -> Bool)
-> (One a -> One a -> Bool)
-> (One a -> One a -> Bool)
-> (One a -> One a -> One a)
-> (One a -> One a -> One a)
-> Ord (One a)
One a -> One a -> Bool
One a -> One a -> Ordering
One a -> One a -> One a
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 a. Ord a => Eq (One a)
forall a. Ord a => One a -> One a -> Bool
forall a. Ord a => One a -> One a -> Ordering
forall a. Ord a => One a -> One a -> One a
min :: One a -> One a -> One a
$cmin :: forall a. Ord a => One a -> One a -> One a
max :: One a -> One a -> One a
$cmax :: forall a. Ord a => One a -> One a -> One a
>= :: One a -> One a -> Bool
$c>= :: forall a. Ord a => One a -> One a -> Bool
> :: One a -> One a -> Bool
$c> :: forall a. Ord a => One a -> One a -> Bool
<= :: One a -> One a -> Bool
$c<= :: forall a. Ord a => One a -> One a -> Bool
< :: One a -> One a -> Bool
$c< :: forall a. Ord a => One a -> One a -> Bool
compare :: One a -> One a -> Ordering
$ccompare :: forall a. Ord a => One a -> One a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (One a)
Ord, Functor One
Foldable One
Functor One
-> Foldable One
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> One a -> f (One b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    One (f a) -> f (One a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> One a -> m (One b))
-> (forall (m :: * -> *) a. Monad m => One (m a) -> m (One a))
-> Traversable One
(a -> f b) -> One a -> f (One b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => One (m a) -> m (One a)
forall (f :: * -> *) a. Applicative f => One (f a) -> f (One a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> One a -> m (One b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> One a -> f (One b)
sequence :: One (m a) -> m (One a)
$csequence :: forall (m :: * -> *) a. Monad m => One (m a) -> m (One a)
mapM :: (a -> m b) -> One a -> m (One b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> One a -> m (One b)
sequenceA :: One (f a) -> f (One a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => One (f a) -> f (One a)
traverse :: (a -> f b) -> One a -> f (One b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> One a -> f (One b)
$cp2Traversable :: Foldable One
$cp1Traversable :: Functor One
Traversable, ReadPrec [One a]
ReadPrec (One a)
Int -> ReadS (One a)
ReadS [One a]
(Int -> ReadS (One a))
-> ReadS [One a]
-> ReadPrec (One a)
-> ReadPrec [One a]
-> Read (One a)
forall a. Read a => ReadPrec [One a]
forall a. Read a => ReadPrec (One a)
forall a. Read a => Int -> ReadS (One a)
forall a. Read a => ReadS [One a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [One a]
$creadListPrec :: forall a. Read a => ReadPrec [One a]
readPrec :: ReadPrec (One a)
$creadPrec :: forall a. Read a => ReadPrec (One a)
readList :: ReadS [One a]
$creadList :: forall a. Read a => ReadS [One a]
readsPrec :: Int -> ReadS (One a)
$creadsPrec :: forall a. Read a => Int -> ReadS (One a)
Read, a -> One b -> One a
(a -> b) -> One a -> One b
(forall a b. (a -> b) -> One a -> One b)
-> (forall a b. a -> One b -> One a) -> Functor One
forall a b. a -> One b -> One a
forall a b. (a -> b) -> One a -> One b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> One b -> One a
$c<$ :: forall a b. a -> One b -> One a
fmap :: (a -> b) -> One a -> One b
$cfmap :: forall a b. (a -> b) -> One a -> One b
Functor, One a -> Bool
(a -> m) -> One a -> m
(a -> b -> b) -> b -> One a -> b
(forall m. Monoid m => One m -> m)
-> (forall m a. Monoid m => (a -> m) -> One a -> m)
-> (forall m a. Monoid m => (a -> m) -> One a -> m)
-> (forall a b. (a -> b -> b) -> b -> One a -> b)
-> (forall a b. (a -> b -> b) -> b -> One a -> b)
-> (forall b a. (b -> a -> b) -> b -> One a -> b)
-> (forall b a. (b -> a -> b) -> b -> One a -> b)
-> (forall a. (a -> a -> a) -> One a -> a)
-> (forall a. (a -> a -> a) -> One a -> a)
-> (forall a. One a -> [a])
-> (forall a. One a -> Bool)
-> (forall a. One a -> Int)
-> (forall a. Eq a => a -> One a -> Bool)
-> (forall a. Ord a => One a -> a)
-> (forall a. Ord a => One a -> a)
-> (forall a. Num a => One a -> a)
-> (forall a. Num a => One a -> a)
-> Foldable One
forall a. Eq a => a -> One a -> Bool
forall a. Num a => One a -> a
forall a. Ord a => One a -> a
forall m. Monoid m => One m -> m
forall a. One a -> Bool
forall a. One a -> Int
forall a. One a -> [a]
forall a. (a -> a -> a) -> One a -> a
forall m a. Monoid m => (a -> m) -> One a -> m
forall b a. (b -> a -> b) -> b -> One a -> b
forall a b. (a -> b -> b) -> b -> One a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: One a -> a
$cproduct :: forall a. Num a => One a -> a
sum :: One a -> a
$csum :: forall a. Num a => One a -> a
minimum :: One a -> a
$cminimum :: forall a. Ord a => One a -> a
maximum :: One a -> a
$cmaximum :: forall a. Ord a => One a -> a
elem :: a -> One a -> Bool
$celem :: forall a. Eq a => a -> One a -> Bool
length :: One a -> Int
$clength :: forall a. One a -> Int
null :: One a -> Bool
$cnull :: forall a. One a -> Bool
toList :: One a -> [a]
$ctoList :: forall a. One a -> [a]
foldl1 :: (a -> a -> a) -> One a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> One a -> a
foldr1 :: (a -> a -> a) -> One a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> One a -> a
foldl' :: (b -> a -> b) -> b -> One a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> One a -> b
foldl :: (b -> a -> b) -> b -> One a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> One a -> b
foldr' :: (a -> b -> b) -> b -> One a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> One a -> b
foldr :: (a -> b -> b) -> b -> One a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> One a -> b
foldMap' :: (a -> m) -> One a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> One a -> m
foldMap :: (a -> m) -> One a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> One a -> m
fold :: One m -> m
$cfold :: forall m. Monoid m => One m -> m
Foldable)
  deriving newtype (b -> One a -> One a
NonEmpty (One a) -> One a
One a -> One a -> One a
(One a -> One a -> One a)
-> (NonEmpty (One a) -> One a)
-> (forall b. Integral b => b -> One a -> One a)
-> Semigroup (One a)
forall b. Integral b => b -> One a -> One a
forall a. Semigroup a => NonEmpty (One a) -> One a
forall a. Semigroup a => One a -> One a -> One a
forall a b. (Semigroup a, Integral b) => b -> One a -> One a
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: b -> One a -> One a
$cstimes :: forall a b. (Semigroup a, Integral b) => b -> One a -> One a
sconcat :: NonEmpty (One a) -> One a
$csconcat :: forall a. Semigroup a => NonEmpty (One a) -> One a
<> :: One a -> One a -> One a
$c<> :: forall a. Semigroup a => One a -> One a -> One a
Semigroup, Semigroup (One a)
One a
Semigroup (One a)
-> One a
-> (One a -> One a -> One a)
-> ([One a] -> One a)
-> Monoid (One a)
[One a] -> One a
One a -> One a -> One a
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall a. Monoid a => Semigroup (One a)
forall a. Monoid a => One a
forall a. Monoid a => [One a] -> One a
forall a. Monoid a => One a -> One a -> One a
mconcat :: [One a] -> One a
$cmconcat :: forall a. Monoid a => [One a] -> One a
mappend :: One a -> One a -> One a
$cmappend :: forall a. Monoid a => One a -> One a -> One a
mempty :: One a
$cmempty :: forall a. Monoid a => One a
$cp1Monoid :: forall a. Monoid a => Semigroup (One a)
Monoid, One a -> ()
(One a -> ()) -> NFData (One a)
forall a. NFData a => One a -> ()
forall a. (a -> ()) -> NFData a
rnf :: One a -> ()
$crnf :: forall a. NFData a => One a -> ()
NFData)
  deriving anyclass ((forall a. (a -> ()) -> One a -> ()) -> NFData1 One
forall a. (a -> ()) -> One a -> ()
forall (f :: * -> *).
(forall a. (a -> ()) -> f a -> ()) -> NFData1 f
liftRnf :: (a -> ()) -> One a -> ()
$cliftRnf :: forall a. (a -> ()) -> One a -> ()
NFData1, Foldable One
Foldable One
-> (forall m. Semigroup m => One m -> m)
-> (forall m a. Semigroup m => (a -> m) -> One a -> m)
-> (forall a. One a -> NonEmpty a)
-> Foldable1 One
forall m. Semigroup m => One m -> m
forall a. One a -> NonEmpty a
forall m a. Semigroup m => (a -> m) -> One a -> m
forall (t :: * -> *).
Foldable t
-> (forall m. Semigroup m => t m -> m)
-> (forall m a. Semigroup m => (a -> m) -> t a -> m)
-> (forall a. t a -> NonEmpty a)
-> Foldable1 t
toNonEmpty :: One a -> NonEmpty a
$ctoNonEmpty :: forall a. One a -> NonEmpty a
foldMap1 :: (a -> m) -> One a -> m
$cfoldMap1 :: forall m a. Semigroup m => (a -> m) -> One a -> m
fold1 :: One m -> m
$cfold1 :: forall m. Semigroup m => One m -> m
$cp1Foldable1 :: Foldable One
Foldable1)

instance Applicative One where
  pure :: a -> One a
pure = a -> One a
coerce
  <*> :: One (a -> b) -> One a -> One b
(<*>) = One (a -> b) -> One a -> One b
coerce
instance Apply.Apply One where
  <.> :: One (a -> b) -> One a -> One b
(<.>) = One (a -> b) -> One a -> One b
coerce
instance Monad One where
  return :: a -> One a
return = a -> One a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
  One a
a >>= :: One a -> (a -> One b) -> One b
>>= a -> One b
amb = a -> One b
amb a
a
instance Traversable1 One where
  traverse1 :: (a -> f b) -> One a -> f (One b)
traverse1 a -> f b
afb = (b -> One b) -> f b -> f (One b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap b -> One b
forall a. a -> One a
One (f b -> f (One b)) -> (One a -> f b) -> One a -> f (One b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> f b
afb (a -> f b) -> (One a -> a) -> One a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. One a -> a
forall a. One a -> a
unOne