module Data.OneOrTwo (
  OneOrTwo (..),
  oneOrTwo,
) where

import Data.Data (Data)

-- | Either one of something, or two of it.
--
-- Use 'oneOrTwo' to deconstruct.
data OneOrTwo x
  = One !x
  | Two !x !x
  deriving
    ( OneOrTwo x -> OneOrTwo x -> Bool
(OneOrTwo x -> OneOrTwo x -> Bool)
-> (OneOrTwo x -> OneOrTwo x -> Bool) -> Eq (OneOrTwo x)
forall x. Eq x => OneOrTwo x -> OneOrTwo x -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OneOrTwo x -> OneOrTwo x -> Bool
$c/= :: forall x. Eq x => OneOrTwo x -> OneOrTwo x -> Bool
== :: OneOrTwo x -> OneOrTwo x -> Bool
$c== :: forall x. Eq x => OneOrTwo x -> OneOrTwo x -> Bool
Eq
    , Eq (OneOrTwo x)
Eq (OneOrTwo x)
-> (OneOrTwo x -> OneOrTwo x -> Ordering)
-> (OneOrTwo x -> OneOrTwo x -> Bool)
-> (OneOrTwo x -> OneOrTwo x -> Bool)
-> (OneOrTwo x -> OneOrTwo x -> Bool)
-> (OneOrTwo x -> OneOrTwo x -> Bool)
-> (OneOrTwo x -> OneOrTwo x -> OneOrTwo x)
-> (OneOrTwo x -> OneOrTwo x -> OneOrTwo x)
-> Ord (OneOrTwo x)
OneOrTwo x -> OneOrTwo x -> Bool
OneOrTwo x -> OneOrTwo x -> Ordering
OneOrTwo x -> OneOrTwo x -> OneOrTwo x
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 x. Ord x => Eq (OneOrTwo x)
forall x. Ord x => OneOrTwo x -> OneOrTwo x -> Bool
forall x. Ord x => OneOrTwo x -> OneOrTwo x -> Ordering
forall x. Ord x => OneOrTwo x -> OneOrTwo x -> OneOrTwo x
min :: OneOrTwo x -> OneOrTwo x -> OneOrTwo x
$cmin :: forall x. Ord x => OneOrTwo x -> OneOrTwo x -> OneOrTwo x
max :: OneOrTwo x -> OneOrTwo x -> OneOrTwo x
$cmax :: forall x. Ord x => OneOrTwo x -> OneOrTwo x -> OneOrTwo x
>= :: OneOrTwo x -> OneOrTwo x -> Bool
$c>= :: forall x. Ord x => OneOrTwo x -> OneOrTwo x -> Bool
> :: OneOrTwo x -> OneOrTwo x -> Bool
$c> :: forall x. Ord x => OneOrTwo x -> OneOrTwo x -> Bool
<= :: OneOrTwo x -> OneOrTwo x -> Bool
$c<= :: forall x. Ord x => OneOrTwo x -> OneOrTwo x -> Bool
< :: OneOrTwo x -> OneOrTwo x -> Bool
$c< :: forall x. Ord x => OneOrTwo x -> OneOrTwo x -> Bool
compare :: OneOrTwo x -> OneOrTwo x -> Ordering
$ccompare :: forall x. Ord x => OneOrTwo x -> OneOrTwo x -> Ordering
$cp1Ord :: forall x. Ord x => Eq (OneOrTwo x)
Ord
    , Int -> OneOrTwo x -> ShowS
[OneOrTwo x] -> ShowS
OneOrTwo x -> String
(Int -> OneOrTwo x -> ShowS)
-> (OneOrTwo x -> String)
-> ([OneOrTwo x] -> ShowS)
-> Show (OneOrTwo x)
forall x. Show x => Int -> OneOrTwo x -> ShowS
forall x. Show x => [OneOrTwo x] -> ShowS
forall x. Show x => OneOrTwo x -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OneOrTwo x] -> ShowS
$cshowList :: forall x. Show x => [OneOrTwo x] -> ShowS
show :: OneOrTwo x -> String
$cshow :: forall x. Show x => OneOrTwo x -> String
showsPrec :: Int -> OneOrTwo x -> ShowS
$cshowsPrec :: forall x. Show x => Int -> OneOrTwo x -> ShowS
Show
    , ReadPrec [OneOrTwo x]
ReadPrec (OneOrTwo x)
Int -> ReadS (OneOrTwo x)
ReadS [OneOrTwo x]
(Int -> ReadS (OneOrTwo x))
-> ReadS [OneOrTwo x]
-> ReadPrec (OneOrTwo x)
-> ReadPrec [OneOrTwo x]
-> Read (OneOrTwo x)
forall x. Read x => ReadPrec [OneOrTwo x]
forall x. Read x => ReadPrec (OneOrTwo x)
forall x. Read x => Int -> ReadS (OneOrTwo x)
forall x. Read x => ReadS [OneOrTwo x]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OneOrTwo x]
$creadListPrec :: forall x. Read x => ReadPrec [OneOrTwo x]
readPrec :: ReadPrec (OneOrTwo x)
$creadPrec :: forall x. Read x => ReadPrec (OneOrTwo x)
readList :: ReadS [OneOrTwo x]
$creadList :: forall x. Read x => ReadS [OneOrTwo x]
readsPrec :: Int -> ReadS (OneOrTwo x)
$creadsPrec :: forall x. Read x => Int -> ReadS (OneOrTwo x)
Read
    , (forall x. OneOrTwo x -> Rep (OneOrTwo x) x)
-> (forall x. Rep (OneOrTwo x) x -> OneOrTwo x)
-> Generic (OneOrTwo x)
forall x. Rep (OneOrTwo x) x -> OneOrTwo x
forall x. OneOrTwo x -> Rep (OneOrTwo x) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall x x. Rep (OneOrTwo x) x -> OneOrTwo x
forall x x. OneOrTwo x -> Rep (OneOrTwo x) x
$cto :: forall x x. Rep (OneOrTwo x) x -> OneOrTwo x
$cfrom :: forall x x. OneOrTwo x -> Rep (OneOrTwo x) x
Generic
    , Typeable (OneOrTwo x)
DataType
Constr
Typeable (OneOrTwo x)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> OneOrTwo x -> c (OneOrTwo x))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (OneOrTwo x))
-> (OneOrTwo x -> Constr)
-> (OneOrTwo x -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (OneOrTwo x)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (OneOrTwo x)))
-> ((forall b. Data b => b -> b) -> OneOrTwo x -> OneOrTwo x)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> OneOrTwo x -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> OneOrTwo x -> r)
-> (forall u. (forall d. Data d => d -> u) -> OneOrTwo x -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> OneOrTwo x -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> OneOrTwo x -> m (OneOrTwo x))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> OneOrTwo x -> m (OneOrTwo x))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> OneOrTwo x -> m (OneOrTwo x))
-> Data (OneOrTwo x)
OneOrTwo x -> DataType
OneOrTwo x -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (OneOrTwo x))
(forall b. Data b => b -> b) -> OneOrTwo x -> OneOrTwo x
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OneOrTwo x -> c (OneOrTwo x)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (OneOrTwo x)
forall x. Data x => Typeable (OneOrTwo x)
forall x. Data x => OneOrTwo x -> DataType
forall x. Data x => OneOrTwo x -> Constr
forall x.
Data x =>
(forall b. Data b => b -> b) -> OneOrTwo x -> OneOrTwo x
forall x u.
Data x =>
Int -> (forall d. Data d => d -> u) -> OneOrTwo x -> u
forall x u.
Data x =>
(forall d. Data d => d -> u) -> OneOrTwo x -> [u]
forall x r r'.
Data x =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OneOrTwo x -> r
forall x r r'.
Data x =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OneOrTwo x -> r
forall x (m :: * -> *).
(Data x, Monad m) =>
(forall d. Data d => d -> m d) -> OneOrTwo x -> m (OneOrTwo x)
forall x (m :: * -> *).
(Data x, MonadPlus m) =>
(forall d. Data d => d -> m d) -> OneOrTwo x -> m (OneOrTwo x)
forall x (c :: * -> *).
Data x =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (OneOrTwo x)
forall x (c :: * -> *).
Data x =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OneOrTwo x -> c (OneOrTwo x)
forall x (t :: * -> *) (c :: * -> *).
(Data x, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (OneOrTwo x))
forall x (t :: * -> * -> *) (c :: * -> *).
(Data x, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (OneOrTwo x))
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) -> OneOrTwo x -> u
forall u. (forall d. Data d => d -> u) -> OneOrTwo x -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OneOrTwo x -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OneOrTwo x -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OneOrTwo x -> m (OneOrTwo x)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OneOrTwo x -> m (OneOrTwo x)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (OneOrTwo x)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OneOrTwo x -> c (OneOrTwo x)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (OneOrTwo x))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (OneOrTwo x))
$cTwo :: Constr
$cOne :: Constr
$tOneOrTwo :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> OneOrTwo x -> m (OneOrTwo x)
$cgmapMo :: forall x (m :: * -> *).
(Data x, MonadPlus m) =>
(forall d. Data d => d -> m d) -> OneOrTwo x -> m (OneOrTwo x)
gmapMp :: (forall d. Data d => d -> m d) -> OneOrTwo x -> m (OneOrTwo x)
$cgmapMp :: forall x (m :: * -> *).
(Data x, MonadPlus m) =>
(forall d. Data d => d -> m d) -> OneOrTwo x -> m (OneOrTwo x)
gmapM :: (forall d. Data d => d -> m d) -> OneOrTwo x -> m (OneOrTwo x)
$cgmapM :: forall x (m :: * -> *).
(Data x, Monad m) =>
(forall d. Data d => d -> m d) -> OneOrTwo x -> m (OneOrTwo x)
gmapQi :: Int -> (forall d. Data d => d -> u) -> OneOrTwo x -> u
$cgmapQi :: forall x u.
Data x =>
Int -> (forall d. Data d => d -> u) -> OneOrTwo x -> u
gmapQ :: (forall d. Data d => d -> u) -> OneOrTwo x -> [u]
$cgmapQ :: forall x u.
Data x =>
(forall d. Data d => d -> u) -> OneOrTwo x -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OneOrTwo x -> r
$cgmapQr :: forall x r r'.
Data x =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OneOrTwo x -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OneOrTwo x -> r
$cgmapQl :: forall x r r'.
Data x =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OneOrTwo x -> r
gmapT :: (forall b. Data b => b -> b) -> OneOrTwo x -> OneOrTwo x
$cgmapT :: forall x.
Data x =>
(forall b. Data b => b -> b) -> OneOrTwo x -> OneOrTwo x
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (OneOrTwo x))
$cdataCast2 :: forall x (t :: * -> * -> *) (c :: * -> *).
(Data x, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (OneOrTwo x))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (OneOrTwo x))
$cdataCast1 :: forall x (t :: * -> *) (c :: * -> *).
(Data x, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (OneOrTwo x))
dataTypeOf :: OneOrTwo x -> DataType
$cdataTypeOf :: forall x. Data x => OneOrTwo x -> DataType
toConstr :: OneOrTwo x -> Constr
$ctoConstr :: forall x. Data x => OneOrTwo x -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (OneOrTwo x)
$cgunfold :: forall x (c :: * -> *).
Data x =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (OneOrTwo x)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OneOrTwo x -> c (OneOrTwo x)
$cgfoldl :: forall x (c :: * -> *).
Data x =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OneOrTwo x -> c (OneOrTwo x)
$cp1Data :: forall x. Data x => Typeable (OneOrTwo x)
Data
    , Typeable
    , a -> OneOrTwo b -> OneOrTwo a
(a -> b) -> OneOrTwo a -> OneOrTwo b
(forall a b. (a -> b) -> OneOrTwo a -> OneOrTwo b)
-> (forall a b. a -> OneOrTwo b -> OneOrTwo a) -> Functor OneOrTwo
forall a b. a -> OneOrTwo b -> OneOrTwo a
forall a b. (a -> b) -> OneOrTwo a -> OneOrTwo b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> OneOrTwo b -> OneOrTwo a
$c<$ :: forall a b. a -> OneOrTwo b -> OneOrTwo a
fmap :: (a -> b) -> OneOrTwo a -> OneOrTwo b
$cfmap :: forall a b. (a -> b) -> OneOrTwo a -> OneOrTwo b
Functor
    , OneOrTwo a -> Bool
(a -> m) -> OneOrTwo a -> m
(a -> b -> b) -> b -> OneOrTwo a -> b
(forall m. Monoid m => OneOrTwo m -> m)
-> (forall m a. Monoid m => (a -> m) -> OneOrTwo a -> m)
-> (forall m a. Monoid m => (a -> m) -> OneOrTwo a -> m)
-> (forall a b. (a -> b -> b) -> b -> OneOrTwo a -> b)
-> (forall a b. (a -> b -> b) -> b -> OneOrTwo a -> b)
-> (forall b a. (b -> a -> b) -> b -> OneOrTwo a -> b)
-> (forall b a. (b -> a -> b) -> b -> OneOrTwo a -> b)
-> (forall a. (a -> a -> a) -> OneOrTwo a -> a)
-> (forall a. (a -> a -> a) -> OneOrTwo a -> a)
-> (forall a. OneOrTwo a -> [a])
-> (forall a. OneOrTwo a -> Bool)
-> (forall a. OneOrTwo a -> Int)
-> (forall a. Eq a => a -> OneOrTwo a -> Bool)
-> (forall a. Ord a => OneOrTwo a -> a)
-> (forall a. Ord a => OneOrTwo a -> a)
-> (forall a. Num a => OneOrTwo a -> a)
-> (forall a. Num a => OneOrTwo a -> a)
-> Foldable OneOrTwo
forall a. Eq a => a -> OneOrTwo a -> Bool
forall a. Num a => OneOrTwo a -> a
forall a. Ord a => OneOrTwo a -> a
forall m. Monoid m => OneOrTwo m -> m
forall a. OneOrTwo a -> Bool
forall a. OneOrTwo a -> Int
forall a. OneOrTwo a -> [a]
forall a. (a -> a -> a) -> OneOrTwo a -> a
forall m a. Monoid m => (a -> m) -> OneOrTwo a -> m
forall b a. (b -> a -> b) -> b -> OneOrTwo a -> b
forall a b. (a -> b -> b) -> b -> OneOrTwo 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 :: OneOrTwo a -> a
$cproduct :: forall a. Num a => OneOrTwo a -> a
sum :: OneOrTwo a -> a
$csum :: forall a. Num a => OneOrTwo a -> a
minimum :: OneOrTwo a -> a
$cminimum :: forall a. Ord a => OneOrTwo a -> a
maximum :: OneOrTwo a -> a
$cmaximum :: forall a. Ord a => OneOrTwo a -> a
elem :: a -> OneOrTwo a -> Bool
$celem :: forall a. Eq a => a -> OneOrTwo a -> Bool
length :: OneOrTwo a -> Int
$clength :: forall a. OneOrTwo a -> Int
null :: OneOrTwo a -> Bool
$cnull :: forall a. OneOrTwo a -> Bool
toList :: OneOrTwo a -> [a]
$ctoList :: forall a. OneOrTwo a -> [a]
foldl1 :: (a -> a -> a) -> OneOrTwo a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> OneOrTwo a -> a
foldr1 :: (a -> a -> a) -> OneOrTwo a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> OneOrTwo a -> a
foldl' :: (b -> a -> b) -> b -> OneOrTwo a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> OneOrTwo a -> b
foldl :: (b -> a -> b) -> b -> OneOrTwo a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> OneOrTwo a -> b
foldr' :: (a -> b -> b) -> b -> OneOrTwo a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> OneOrTwo a -> b
foldr :: (a -> b -> b) -> b -> OneOrTwo a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> OneOrTwo a -> b
foldMap' :: (a -> m) -> OneOrTwo a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> OneOrTwo a -> m
foldMap :: (a -> m) -> OneOrTwo a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> OneOrTwo a -> m
fold :: OneOrTwo m -> m
$cfold :: forall m. Monoid m => OneOrTwo m -> m
Foldable
    , Functor OneOrTwo
Foldable OneOrTwo
Functor OneOrTwo
-> Foldable OneOrTwo
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> OneOrTwo a -> f (OneOrTwo b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    OneOrTwo (f a) -> f (OneOrTwo a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> OneOrTwo a -> m (OneOrTwo b))
-> (forall (m :: * -> *) a.
    Monad m =>
    OneOrTwo (m a) -> m (OneOrTwo a))
-> Traversable OneOrTwo
(a -> f b) -> OneOrTwo a -> f (OneOrTwo 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 => OneOrTwo (m a) -> m (OneOrTwo a)
forall (f :: * -> *) a.
Applicative f =>
OneOrTwo (f a) -> f (OneOrTwo a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> OneOrTwo a -> m (OneOrTwo b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> OneOrTwo a -> f (OneOrTwo b)
sequence :: OneOrTwo (m a) -> m (OneOrTwo a)
$csequence :: forall (m :: * -> *) a. Monad m => OneOrTwo (m a) -> m (OneOrTwo a)
mapM :: (a -> m b) -> OneOrTwo a -> m (OneOrTwo b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> OneOrTwo a -> m (OneOrTwo b)
sequenceA :: OneOrTwo (f a) -> f (OneOrTwo a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
OneOrTwo (f a) -> f (OneOrTwo a)
traverse :: (a -> f b) -> OneOrTwo a -> f (OneOrTwo b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> OneOrTwo a -> f (OneOrTwo b)
$cp2Traversable :: Foldable OneOrTwo
$cp1Traversable :: Functor OneOrTwo
Traversable
    )

-- | Apply a 'oneOrTwo' argument function appropriately.
oneOrTwo :: (x -> a) -> (x -> x -> a) -> OneOrTwo x -> a
oneOrTwo :: (x -> a) -> (x -> x -> a) -> OneOrTwo x -> a
oneOrTwo x -> a
f x -> x -> a
g = \case
  One x
x -> x -> a
f x
x
  Two x
x x
y -> x -> x -> a
g x
x x
y
{-# INLINE oneOrTwo #-}