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

Data.Replicator.Linear

Description

This module defines a stream-like type named Replicator, which is mainly used in the definition of the Dupable class to provide efficient linear duplication. The API of Replicator is close to the one of an infinite stream: it can either produce a new value linearly (with next or next#), or be linearly discarded (with consume or extract).

A crucial aspect, from a performance standpoint, is that the pure function (which takes an unrestricted argument) is implemented efficiently: the Replicator returns the same value on each call to next. That is, the pointer is always shared. This will allow Movable types to be given an efficient instance of Dupable. Instances of both Movable and Dupable typically involve deep copies. The implementation of pure lets us make sure that, for Movable types, only one deep copy is performed, rather than one per additional replica.

Strictly speaking, the implementation of (<*>) plays a role in all this as well: For two pure Replicators fs and as, fs <*> as is a pure Replicator. Together, pure and (<*>) form the Applicative instance of Replicator.

Synopsis

Documentation

data Replicator a Source #

Replicator is a stream-like data structure used to linearly duplicate values.

Instances

Instances details
Applicative Replicator Source # 
Instance details

Defined in Data.Replicator.Linear.Internal.Instances

Methods

pure :: a -> Replicator a Source #

(<*>) :: Replicator (a %1 -> b) %1 -> Replicator a %1 -> Replicator b Source #

liftA2 :: (a %1 -> b %1 -> c) -> Replicator a %1 -> Replicator b %1 -> Replicator c Source #

Functor Replicator Source # 
Instance details

Defined in Data.Replicator.Linear.Internal.Instances

Methods

fmap :: (a %1 -> b) -> Replicator a %1 -> Replicator b Source #

Consumable (Replicator a) Source # 
Instance details

Defined in Data.Unrestricted.Linear.Internal.Consumable

Methods

consume :: Replicator a %1 -> () Source #

Dupable (Replicator a) Source # 
Instance details

Defined in Data.Unrestricted.Linear.Internal.Dupable

consume :: Replicator a %1 -> () Source #

map :: (a %1 -> b) -> Replicator a %1 -> Replicator b Source #

(<*>) :: Replicator (a %1 -> b) %1 -> Replicator a %1 -> Replicator b infixl 4 Source #

next :: Replicator a %1 -> (a, Replicator a) Source #

Extracts the next item from the "infinite stream" Replicator a.

next# :: Replicator a %1 -> (# a, Replicator a #) Source #

Extracts the next item from the "infinite stream" Replicator a. Same function as next, but returning an unboxed tuple.

take :: Int -> Replicator a %1 -> [a] Source #

take n as is a list of size n, containing n replicas from as.

extract :: Replicator a %1 -> a Source #

Returns the next item from Replicator a and efficiently consumes the replicator at the same time.

extend :: (Replicator a %1 -> b) -> Replicator a %1 -> Replicator b Source #

Comonadic extend function.

extend f = map f . duplicate

class Elim n a b Source #

Elim n a b is used to implement elim without recursion so that we can guarantee that elim will be inlined and unrolled.

Elim is solely used in the signature of elim.

Minimal complete definition

elim'

Instances

Instances details
Elim 'Z a b Source # 
Instance details

Defined in Data.Replicator.Linear.Internal

Methods

elim' :: FunN 'Z a b %1 -> Replicator a %1 -> b

Elim ('S n) a b => Elim ('S ('S n)) a b Source # 
Instance details

Defined in Data.Replicator.Linear.Internal

Methods

elim' :: FunN ('S ('S n)) a b %1 -> Replicator a %1 -> b

Elim ('S 'Z) a b Source # 
Instance details

Defined in Data.Replicator.Linear.Internal

Methods

elim' :: FunN ('S 'Z) a b %1 -> Replicator a %1 -> b

elim :: forall (n :: Nat) a b f. (Elim (NatToPeano n) a b, IsFunN a b f, f ~ FunN (NatToPeano n) a b, n ~ Arity b f) => f %1 -> Replicator a %1 -> b Source #

Takes a function of type a %1 -> a %1 -> ... %1 -> a %1 -> b, and returns a b . The replicator is used to supply all the items of type a required by the function.

For instance:

elim @1 :: (a %1 -> b) %1 -> Replicator a %1 -> b
elim @2 :: (a %1 -> a %1 -> b) %1 -> Replicator a %1 -> b
elim @3 :: (a %1 -> a %1 -> a %1 -> b) %1 -> Replicator a %1 -> b

It is not always necessary to give the arity argument. It can be inferred from the function argument.

elim (,) :: Replicator a %1 -> (a, a)
elim (,,) :: Replicator a %1 -> (a, a, a)

About the constraints of this function (they won't get in your way):

  • Elim (NatToPeano n) a b provides the actual implementation of elim; there is an instance of this class for any (n, a, b)
  • IsFunN a b f, f ~ FunN (NatToPeano n) a b, n ~ Arity b f indicate the shape of f to the typechecker (see documentation of IsFunN).