linear-base-0.1.0: Standard library for linear types.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Unrestricted.Internal.Dupable

Contents

Synopsis

Dupable

class Consumable a => Dupable a where Source #

The laws of Dupable are dual to those of Monoid:

  • first consume (dup2 a) ≃ a ≃ second consume (dup2 a) (neutrality)
  • first dup2 (dup2 a) ≃ (second dup2 (dup2 a)) (associativity)

Where the (≃) sign represents equality up to type isomorphism.

When implementing Dupable instances for composite types, using dupV should be more convenient since V has a zipping Applicative instance.

Minimal complete definition

dupV | dup2

Methods

dupV :: forall n. KnownNat n => a %1 -> V n a Source #

dup2 :: a %1 -> (a, a) Source #

Instances

Instances details
Dupable Bool Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

dupV :: forall (n :: Nat). KnownNat n => Bool %1 -> V n Bool Source #

dup2 :: Bool %1 -> (Bool, Bool) Source #

Dupable Char Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

dupV :: forall (n :: Nat). KnownNat n => Char %1 -> V n Char Source #

dup2 :: Char %1 -> (Char, Char) Source #

Dupable Double Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

dupV :: forall (n :: Nat). KnownNat n => Double %1 -> V n Double Source #

dup2 :: Double %1 -> (Double, Double) Source #

Dupable Int Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

dupV :: forall (n :: Nat). KnownNat n => Int %1 -> V n Int Source #

dup2 :: Int %1 -> (Int, Int) Source #

Dupable Ordering Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

dupV :: forall (n :: Nat). KnownNat n => Ordering %1 -> V n Ordering Source #

dup2 :: Ordering %1 -> (Ordering, Ordering) Source #

Dupable () Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

dupV :: forall (n :: Nat). KnownNat n => () %1 -> V n () Source #

dup2 :: () %1 -> ((), ()) Source #

Dupable Any Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

dupV :: forall (n :: Nat). KnownNat n => Any %1 -> V n Any Source #

dup2 :: Any %1 -> (Any, Any) Source #

Dupable All Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

dupV :: forall (n :: Nat). KnownNat n => All %1 -> V n All Source #

dup2 :: All %1 -> (All, All) Source #

Dupable Pool Source # 
Instance details

Defined in Foreign.Marshal.Pure

Methods

dupV :: forall (n :: Nat). KnownNat n => Pool %1 -> V n Pool Source #

dup2 :: Pool %1 -> (Pool, Pool) Source #

Dupable a => Dupable [a] Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

dupV :: forall (n :: Nat). KnownNat n => [a] %1 -> V n [a] Source #

dup2 :: [a] %1 -> ([a], [a]) Source #

Dupable a => Dupable (Maybe a) Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

dupV :: forall (n :: Nat). KnownNat n => Maybe a %1 -> V n (Maybe a) Source #

dup2 :: Maybe a %1 -> (Maybe a, Maybe a) Source #

Dupable a => Dupable (Sum a) Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

dupV :: forall (n :: Nat). KnownNat n => Sum a %1 -> V n (Sum a) Source #

dup2 :: Sum a %1 -> (Sum a, Sum a) Source #

Dupable a => Dupable (Product a) Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

dupV :: forall (n :: Nat). KnownNat n => Product a %1 -> V n (Product a) Source #

dup2 :: Product a %1 -> (Product a, Product a) Source #

Dupable a => Dupable (NonEmpty a) Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

dupV :: forall (n :: Nat). KnownNat n => NonEmpty a %1 -> V n (NonEmpty a) Source #

dup2 :: NonEmpty a %1 -> (NonEmpty a, NonEmpty a) Source #

Dupable (Ur a) Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

dupV :: forall (n :: Nat). KnownNat n => Ur a %1 -> V n (Ur a) Source #

dup2 :: Ur a %1 -> (Ur a, Ur a) Source #

Dupable (Array a) Source # 
Instance details

Defined in Data.Array.Mutable.Linear

Methods

dupV :: forall (n :: Nat). KnownNat n => Array a %1 -> V n (Array a) Source #

dup2 :: Array a %1 -> (Array a, Array a) Source #

Dupable (Vector a) Source # 
Instance details

Defined in Data.Vector.Mutable.Linear

Methods

dupV :: forall (n :: Nat). KnownNat n => Vector a %1 -> V n (Vector a) Source #

dup2 :: Vector a %1 -> (Vector a, Vector a) Source #

Dupable (Set a) Source # 
Instance details

Defined in Data.Set.Mutable.Linear

Methods

dupV :: forall (n :: Nat). KnownNat n => Set a %1 -> V n (Set a) Source #

dup2 :: Set a %1 -> (Set a, Set a) Source #

(Dupable a, Dupable b) => Dupable (Either a b) Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

dupV :: forall (n :: Nat). KnownNat n => Either a b %1 -> V n (Either a b) Source #

dup2 :: Either a b %1 -> (Either a b, Either a b) Source #

(Dupable a, Dupable b) => Dupable (a, b) Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

dupV :: forall (n :: Nat). KnownNat n => (a, b) %1 -> V n (a, b) Source #

dup2 :: (a, b) %1 -> ((a, b), (a, b)) Source #

Dupable (HashMap k v) Source # 
Instance details

Defined in Data.HashMap.Mutable.Linear

Methods

dupV :: forall (n :: Nat). KnownNat n => HashMap k v %1 -> V n (HashMap k v) Source #

dup2 :: HashMap k v %1 -> (HashMap k v, HashMap k v) Source #

(Dupable a, Dupable b, Dupable c) => Dupable (a, b, c) Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

dupV :: forall (n :: Nat). KnownNat n => (a, b, c) %1 -> V n (a, b, c) Source #

dup2 :: (a, b, c) %1 -> ((a, b, c), (a, b, c)) Source #

dup :: Dupable a => a %1 -> (a, a) Source #

dup3 :: Dupable a => a %1 -> (a, a, a) Source #