proarrow-0: Category theory with a central role for profunctors
Safe HaskellNone
LanguageHaskell2010

Proarrow.Category.Instance.ZX

Synopsis

Documentation

newtype Bitstring (n :: Nat) Source Comments #

Constructors

BS Int 

Instances

Instances details
KnownNat n => Bounded (Bitstring n) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.ZX

Enum (Bitstring n) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.ZX

Num (Bitstring n) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.ZX

KnownNat n => Show (Bitstring n) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.ZX

Eq (Bitstring n) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.ZX

Ord (Bitstring n) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.ZX

split :: forall (n :: Nat) (m :: Natural). KnownNat n => Bitstring (n + m) -> (Bitstring n, Bitstring m) Source Comments #

Split n + m bits into two parts: the lower n bits and the higher m bits.

combine :: forall (n :: Nat) (m :: Nat). KnownNat n => Bitstring n -> Bitstring m -> Bitstring (n + m) Source Comments #

Combine two bitstrings of lengths n and m into one bitstring with the n lower bits or m higher bits.

filterSparse :: forall (o :: Nat) (i :: Nat). SparseMatrix o i -> SparseMatrix o i Source Comments #

transpose :: forall (o :: Nat) (i :: Nat). SparseMatrix o i -> SparseMatrix i o Source Comments #

mirror :: forall (n :: Nat). KnownNat n => Bitstring n -> Bitstring (n + n) Source Comments #

enumAll :: forall (n :: Nat). KnownNat n => [Bitstring n] Source Comments #

nat :: forall (n :: Nat). KnownNat n => Int Source Comments #

data ZX (i :: Nat) (o :: Nat) where Source Comments #

Constructors

ZX :: forall (i :: Nat) (o :: Nat). (KnownNat i, KnownNat o) => SparseMatrix o i -> ZX i o 

Instances

Instances details
DaggerProfunctor ZX Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.ZX

Methods

dagger :: forall (a :: Nat) (b :: Nat). ZX a b -> ZX b a Source Comments #

Promonad ZX Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.ZX

Methods

id :: forall (a :: Nat). Ob a => ZX a a Source Comments #

(.) :: forall (b :: Nat) (c :: Nat) (a :: Nat). ZX b c -> ZX a b -> ZX a c Source Comments #

MonoidalProfunctor ZX Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.ZX

Methods

par0 :: ZX (Unit :: Nat) (Unit :: Nat) Source Comments #

par :: forall (x1 :: Nat) (x2 :: Nat) (y1 :: Nat) (y2 :: Nat). ZX x1 x2 -> ZX y1 y2 -> ZX (x1 ** y1) (x2 ** y2) Source Comments #

Profunctor ZX Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.ZX

Methods

dimap :: forall (c :: Nat) (a :: Nat) (b :: Nat) (d :: Nat). (c ~> a) -> (b ~> d) -> ZX a b -> ZX c d Source Comments #

(\\) :: forall (a :: Nat) (b :: Nat) r. ((Ob a, Ob b) => r) -> ZX a b -> r Source Comments #

Show (ZX a b) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.ZX

Methods

showsPrec :: Int -> ZX a b -> ShowS Comments #

show :: ZX a b -> String Comments #

showList :: [ZX a b] -> ShowS Comments #

zSpider :: forall (i :: Nat) (o :: Nat). (KnownNat i, KnownNat o) => Double -> ZX i o Source Comments #

xSpider :: forall (i :: Nat) (o :: Nat). (KnownNat i, KnownNat o) => Double -> ZX i o Source Comments #

cup :: forall (n :: Nat). KnownNat n => ZX 0 (n + n) Source Comments #

cap :: forall (n :: Nat). KnownNat n => ZX (n + n) 0 Source Comments #

cnot :: ZX 2 2 Source Comments #

Controlled NOT gate

ghzState :: ZX 0 3 Source Comments #

Greenberger–Horne–Zeilinger state

hadamard :: forall (n :: Nat). KnownNat n => ZX n n Source Comments #

Orphan instances

Monoidal Nat Source Comments # 
Instance details

Associated Types

type Unit 
Instance details

Defined in Proarrow.Category.Instance.ZX

type Unit = 0
type (p :: Natural) ** (q :: Natural) 
Instance details

Defined in Proarrow.Category.Instance.ZX

type (p :: Natural) ** (q :: Natural) = p + q

Methods

withOb2 :: forall (a :: Nat) (b :: Nat) r. (Ob a, Ob b) => (Ob (a ** b) => r) -> r Source Comments #

leftUnitor :: forall (a :: Nat). Ob a => ((Unit :: Nat) ** a) ~> a Source Comments #

leftUnitorInv :: forall (a :: Nat). Ob a => a ~> ((Unit :: Nat) ** a) Source Comments #

rightUnitor :: forall (a :: Nat). Ob a => (a ** (Unit :: Nat)) ~> a Source Comments #

rightUnitorInv :: forall (a :: Nat). Ob a => a ~> (a ** (Unit :: Nat)) Source Comments #

associator :: forall (a :: Nat) (b :: Nat) (c :: Nat). (Ob a, Ob b, Ob c) => ((a ** b) ** c) ~> (a ** (b ** c)) Source Comments #

associatorInv :: forall (a :: Nat) (b :: Nat) (c :: Nat). (Ob a, Ob b, Ob c) => (a ** (b ** c)) ~> ((a ** b) ** c) Source Comments #

SymMonoidal Nat Source Comments # 
Instance details

Methods

swap :: forall (a :: Nat) (b :: Nat). (Ob a, Ob b) => (a ** b) ~> (b ** a) Source Comments #

CategoryOf Nat Source Comments #

The category of qubits, to implement ZX calculus from quantum computing.

Instance details

Associated Types

type (~>) 
Instance details

Defined in Proarrow.Category.Instance.ZX

type (~>) = ZX
type Ob (a :: Nat) 
Instance details

Defined in Proarrow.Category.Instance.ZX

type Ob (a :: Nat) = KnownNat a
CompactClosed Nat Source Comments # 
Instance details

Methods

distribDual :: forall (a :: Nat) (b :: Nat). (Ob a, Ob b) => Dual (a ** b) ~> (Dual a ** Dual b) Source Comments #

dualUnit :: Dual (Unit :: Nat) ~> (Unit :: Nat) Source Comments #

StarAutonomous Nat Source Comments # 
Instance details

Associated Types

type Dual (x :: Nat) 
Instance details

Defined in Proarrow.Category.Instance.ZX

type Dual (x :: Nat) = x

Methods

dual :: forall (a :: Nat) (b :: Nat). (a ~> b) -> Dual b ~> Dual a Source Comments #

dualInv :: forall (a :: Nat) (b :: Nat). (Ob a, Ob b) => (Dual a ~> Dual b) -> b ~> a Source Comments #

linDist :: forall (a :: Nat) (b :: Nat) (c :: Nat). (Ob a, Ob b, Ob c) => ((a ** b) ~> Dual c) -> a ~> Dual (b ** c) Source Comments #

linDistInv :: forall (a :: Nat) (b :: Nat) (c :: Nat). (Ob a, Ob b, Ob c) => (a ~> Dual (b ** c)) -> (a ** b) ~> Dual c Source Comments #

Closed Nat Source Comments # 
Instance details

Associated Types

type (x :: Nat) ~~> (y :: Nat) 
Instance details

Defined in Proarrow.Category.Instance.ZX

type (x :: Nat) ~~> (y :: Nat) = ExpSA x y

Methods

withObExp :: forall (a :: Nat) (b :: Nat) r. (Ob a, Ob b) => (Ob (a ~~> b) => r) -> r Source Comments #

curry :: forall (a :: Nat) (b :: Nat) (c :: Nat). (Ob a, Ob b) => ((a ** b) ~> c) -> a ~> (b ~~> c) Source Comments #

uncurry :: forall (b :: Nat) (c :: Nat) (a :: Nat). (Ob b, Ob c) => (a ~> (b ~~> c)) -> (a ** b) ~> c Source Comments #

(^^^) :: forall (a :: Nat) (b :: Nat) (x :: Nat) (y :: Nat). (b ~> y) -> (x ~> a) -> (a ~~> b) ~> (x ~~> y) Source Comments #