Safe Haskell | None |
---|
This module provides type classes for dealing with various "shaped" quantum and classical data structures. Examples of data structures are tuples, lists, records, registers, arrays, indexed arrays, etc. Is it convenient to extend certain operations to arbitrary quantum data structures; for example, instead of measuring a single qubit and obtaining a bit, one may measure an n-tuple of qubits and obtain an n-tuple of bits. We call an operation "generic" if it can act on arbitrary data structures.
This module provides shaped types and low-level combinators, in terms of which higher-level generic quantum operations can be defined.
The low-level combinators provided by this module (with names
qcdata_* and qdata_*) should never be used directly in user
code (and for this reason, they are not re-exported by
Quipper). Instead, they are intended as building blocks for
user-level generic functions (in Quipper.Internal.Generic and related
modules). The only exception is that the functions may be used in
libraries or user-level code to define new quantum data
constructors. Modules that contain such definitions should import
Internal
.
Synopsis
- type family QCType x y a
- type family QTypeB a
- class (Labelable qc String, Typeable qc, Show qc, Show (LType qc), qc ~ QCType Qubit Bit qc, CType (QType qc) ~ CType qc, BType (CType qc) ~ BType qc, QCType Int Bool (CType qc) ~ BType qc) => QCData qc where
- qcdata_mapM :: Monad m => qc -> (q -> m q') -> (c -> m c') -> QCType q c qc -> m (QCType q' c' qc)
- qcdata_zip :: qc -> q -> c -> q' -> c' -> QCType q c qc -> QCType q' c' qc -> ErrMsg -> QCType (q, q') (c, c') qc
- qcdata_promote :: BType qc -> qc -> ErrMsg -> BType qc
- class QCData qc => SimpleType qc where
- fs_shape :: qc
- type QType a = QCType Qubit Qubit a
- type CType a = QCType Bit Bit a
- type BType a = QCType Bool Bool a
- type HType leaf qa = QCType leaf leaf (QType qa)
- dummy :: a
- qubit :: Qubit
- bit :: Bit
- bool :: Bool
- shapetype_q :: QData qa => QType qa -> qa
- shapetype_c :: QData qa => CType qa -> qa
- shapetype_b :: QData qa => BType qa -> qa
- shape :: a -> a
- type QData qa = (qa ~ QType (CType qa), qa ~ QTypeB (BType qa), qa ~ QCType Qubit Bool qa, qa ~ QType qa, QCData qa, QCData (CType qa))
- qdata_mapM :: (QData qa, Monad m) => qa -> (x -> m y) -> HType x qa -> m (HType y qa)
- qdata_zip :: QData qa => qa -> x -> y -> HType x qa -> HType y qa -> ErrMsg -> HType (x, y) qa
- qdata_promote :: QData qa => BType qa -> qa -> ErrMsg -> BType qa
- qdata_unzip :: QData s => s -> x -> y -> HType (x, y) s -> (HType x s, HType y s)
- qdata_map :: QData s => s -> (x -> y) -> HType x s -> HType y s
- qdata_fold :: QData s => s -> (x -> w -> w) -> HType x s -> w -> w
- qdata_fold_map :: QData s => s -> (x -> w -> (y, w)) -> HType x s -> w -> (HType y s, w)
- qdata_foldM :: (QData s, Monad m) => s -> (x -> w -> m w) -> HType x s -> w -> m w
- qdata_fold_mapM :: (QData s, Monad m) => s -> (x -> w -> m (y, w)) -> HType x s -> w -> m (HType y s, w)
- qdata_sequentialize :: QData s => s -> HType x s -> [x]
- qdata_unsequentialize :: QData s => s -> [x] -> HType x s
- qdata_makeshape :: QData qa => qa -> a -> HType a qa -> qa
- qdata_mapM_op :: (QData s, Monad m) => s -> (x -> m y) -> HType x s -> m (HType y s)
- qdata_promote_c :: QData s => BType s -> CType s -> ErrMsg -> BType s
- type CData ca = (QData (QType ca), CType (QType ca) ~ ca)
- type BData ba = (QData (QTypeB ba), BType (QTypeB ba) ~ ba)
- type QShape ba qa ca = (QData qa, BType qa ~ ba, CType qa ~ ca)
- qcdata_unzip :: QCData qc => qc -> q -> c -> q' -> c' -> QCType (q, q') (c, c') qc -> (QCType q c qc, QCType q' c' qc)
- qcdata_map :: QCData qc => qc -> (q -> q') -> (c -> c') -> QCType q c qc -> QCType q' c' qc
- qcdata_fold :: QCData qc => qc -> (q -> w -> w) -> (c -> w -> w) -> QCType q c qc -> w -> w
- qcdata_fold_map :: QCData qc => qc -> (q -> w -> (q', w)) -> (c -> w -> (c', w)) -> QCType q c qc -> w -> (QCType q' c' qc, w)
- qcdata_foldM :: (QCData qc, Monad m) => qc -> (q -> w -> m w) -> (c -> w -> m w) -> QCType q c qc -> w -> m w
- qcdata_fold_mapM :: (QCData qc, Monad m) => qc -> (q -> w -> m (q', w)) -> (c -> w -> m (c', w)) -> QCType q c qc -> w -> m (QCType q' c' qc, w)
- qcdata_sequentialize :: QCData qc => qc -> QCType q c qc -> [B_Endpoint q c]
- qcdata_unsequentialize :: QCData qc => qc -> [B_Endpoint q c] -> QCType q c qc
- qcdata_makeshape :: QCData qc => qc -> a -> b -> QCType a b qc -> qc
- qcdata_mapM_op :: (QCData qc, Monad m) => qc -> (q -> m q') -> (c -> m c') -> QCType q c qc -> m (QCType q' c' qc)
- type QCDataPlus qc = (QCData qc, QData (QType qc))
- type QCData_Simple qc = (QCData qc, SimpleType qc)
- type QCDataPlus_Simple qc = (QCDataPlus qc, SimpleType qc)
- class (QCData q, SimpleType q, ControlSource q, ControlSource (Signed q), Labelable q String, QCType Qubit Bit q ~ q, QCType Bool Bool q ~ Bool) => QCLeaf q
- data Qubit_Leaf = Qubit_Leaf
- data Bit_Leaf = Bit_Leaf
- canonical_shape :: QCData qc => qc -> String
- type LType a = QCType Qubit_Leaf Bit_Leaf a
Introduction
The data types we consider here come in two varieties: homogeneous and heterogeneous types.
A homogeneous data type describes a data structure that is built up from only one kind of basic data (for example, only qubits, only classical bits, or only boolean parameters). The following are typical examples of homogeneous types:
qa = (Qubit, Qubit, [Qubit]) ca = (Bit, Bit, [Bit]) ba = (Bool, Bool, [Bool]).
An important feature of homogeneous types is that they can be
related to each other by shape. For example, ca above is the
"classical version" of qa. We say that the above types qa,
ca, and ba all share the same shape type. On the other hand,
they differ in their leaf types, which are Qubit
, Bit
, and
Bool
, respectively.
When naming types, variables, and operations related to homogeneous data structures, we often use letters such as q, c, and b to denote, respectively, the quantum, classical, and boolean versions of some concept.
Homogeneous types are made available to Quipper programs via the
QData
and QShape
type classes.
A heterogeneous data type describes a data structure that may contain both classical and quantum bits. A typical example of a heterogeneous type is:
qc = (Qubit, Bit, [Qubit]).
Heterogeneous types are often used to represent sets of endpoints of a circuit, or the inputs or outputs to some circuit building function. We often use the letters qc in connection with heterogeneous types.
Heterogeneous types are made available to Quipper programs via the
QCData
and QCDataPlus
type classes.
Primitive definitions
The type classes of this module are all derived from four primitive items, which must be defined by induction on types:
- A type class
QCData
qc, representing structured data types made up from classical and quantum leaves. - A type family
QCType
x y qc, representing the type-level substitution operationqc [x / .Qubit
, y /Bit
] - A type family
QTypeB
ba, representing the type-level substitutionba [ .Qubit
/Bool
] - A type class
SimpleType
qc, representing "simple" data types. We say that a data type t is "simple" if any two elements of t have the same number of leaves. For example, tuples are simple, but lists are not.
An instance of QCData
, QCType
and QTypeB
must be defined for
each new kind of quantum data. If the quantum data is simple, an
instance of SimpleType
must also be defined.
All other notions in this module are defined in terms of the above four, and therefore need not be defined on a per-type basis.
The QCType operation
type family QCType x y a Source #
The type QCType
x y a represents the substitution
Qubit
, y / Bit
]
QCType x y (Qubit, Bit, [Qubit]) = (x, y, [x]).
An instance of this must be defined for each new kind of quantum data.
Instances
type QCType x y Char # | |
Defined in Quipper.Internal.QData | |
type QCType x y Float # | |
Defined in Quipper.Internal.QData | |
type QCType x y Double # | |
Defined in Quipper.Internal.QData | |
type QCType x y Int # | |
Defined in Quipper.Internal.QData | |
type QCType x y Integer # | |
Defined in Quipper.Internal.QData | |
type QCType x y () # | |
Defined in Quipper.Internal.QData type QCType x y () = () | |
type QCType x y Bit # | |
Defined in Quipper.Internal.QData | |
type QCType x y Qubit # | |
Defined in Quipper.Internal.QData | |
type QCType x y (Signed a) # | |
Defined in Quipper.Internal.QData | |
type QCType x y [a] # | |
Defined in Quipper.Internal.QData | |
type QCType x y (B_Endpoint a b) # | |
Defined in Quipper.Internal.QData | |
type QCType x y (a, b) # | |
Defined in Quipper.Internal.QData | |
type QCType x y (a, b, c) # | |
Defined in Quipper.Internal.QData | |
type QCType x y (a, b, c, d) # | |
type QCType x y (a, b, c, d, e) # | |
type QCType x y (a, b, c, d, e, f) # | |
type QCType x y (a, b, c, d, e, f, g) # | |
type QCType x y (a, b, c, d, e, f, g, h) # | |
type QCType x y (a, b, c, d, e, f, g, h, i) # | |
type QCType x y (a, b, c, d, e, f, g, h, i, j) # | |
The QTypeB operation
The type QTypeB
ba represents the substitution
Qubit
/ Bool
]
QTypeB (Bool, Bool, [Bool]) = (Qubit, Qubit, [Qubit]).
An instance of this must be defined for each new kind of quantum data.
Instances
type QTypeB Bool # | |
Defined in Quipper.Internal.QData | |
type QTypeB Char # | |
Defined in Quipper.Internal.QData | |
type QTypeB Double # | |
Defined in Quipper.Internal.QData | |
type QTypeB Float # | |
Defined in Quipper.Internal.QData | |
type QTypeB Int # | |
Defined in Quipper.Internal.QData | |
type QTypeB Integer # | |
Defined in Quipper.Internal.QData | |
type QTypeB () # | |
Defined in Quipper.Internal.QData type QTypeB () = () | |
type QTypeB [a] # | |
Defined in Quipper.Internal.QData | |
type QTypeB (Signed a) # | |
Defined in Quipper.Internal.QData | |
type QTypeB (a, b) # | |
Defined in Quipper.Internal.QData | |
type QTypeB (B_Endpoint a b) # | |
Defined in Quipper.Internal.QData | |
type QTypeB (a, b, c) # | |
Defined in Quipper.Internal.QData | |
type QTypeB (a, b, c, d) # | |
type QTypeB (a, b, c, d, e) # | |
type QTypeB (a, b, c, d, e, f) # | |
type QTypeB (a, b, c, d, e, f, g) # | |
type QTypeB (a, b, c, d, e, f, g, h) # | |
type QTypeB (a, b, c, d, e, f, g, h, i) # | |
type QTypeB (a, b, c, d, e, f, g, h, i, j) # | |
The QCData class
The QCData
class provides only three primitive combinators:
qcdata_mapM
, qcdata_zip
, and qcdata_promote
. These are
sufficient to define all other shape-generic operations.
An instance of this must be defined for each new kind of quantum data.
The functions qcdata_mapM
and qcdata_zip
require "shape type
parameters". These are dummy arguments whose value is ignored,
but whose type is used to determine the shape of the data to map
over. The dummy terms
and qubit
:: Qubit
may
be used to represent leaves in shape type arguments.bit
:: Bit
Note to programmers defining new QCData
instances: Instances
must ensure that the functions qcdata_mapM
and qcdata_zip
do not evaluate their dummy arguments. These arguments will often
be undefined
. In particular, if using a pattern match on this
argument, only a variable or a lazy pattern can be used.
class (Labelable qc String, Typeable qc, Show qc, Show (LType qc), qc ~ QCType Qubit Bit qc, CType (QType qc) ~ CType qc, BType (CType qc) ~ BType qc, QCType Int Bool (CType qc) ~ BType qc) => QCData qc where Source #
The QCData
type class contains heterogeneous data types built
up from leaves of type Qubit
and Bit
. It is the basis for
several generic operations that apply to classical and quantum
data, such as copying, transformers, simulation, and heterogeneous
versions of qterm and qdiscard.
QCData
and QData
are interrelated, in the sense that the
following implications hold:
QData qa implies QCData qa CData ca implies QCData ca
Implications in the converse direction also hold whenever qc is a fixed known type:
QCData qc implies QData (QType qc) QCData qc implies CData (CType qc) QCData qc implies BData (BType qc)
However, the type checker cannot prove the above implication in the
case where qc is a type variable; for this, the more flexible
(but more computationally expensive) QCDataPlus
class can be used.
qcdata_mapM :: Monad m => qc -> (q -> m q') -> (c -> m c') -> QCType q c qc -> m (QCType q' c' qc) Source #
Map two functions f and g over all the leaves of a
heterogeneous data structure. Apply f to all the leaves at
Qubit
positions, and g to all the leaves at Bit
positions.
The first argument is a shape type parameter.
Example (ignoring the monad for the sake of simplicity):
qcdata_mapM (qubit, bit, [qubit]) f g (x,y,[z,w]) = (f x, g y, [f z, f w]).
For data types that have a sense of direction, the mapping should preferably be performed from left to right, but this property is not guaranteed and may change without notice.
qcdata_zip :: qc -> q -> c -> q' -> c' -> QCType q c qc -> QCType q' c' qc -> ErrMsg -> QCType (q, q') (c, c') qc Source #
Zip two heterogeneous data structures together, to obtain a new data structure of the same shape, whose elements are pairs of the corresponding elements of the input data structures. The zipping is strict, meaning that both input data structure must have exactly the same shape (same length of lists, etc). The first five arguments are shape type parameters, representing the shape of the data structure, the two leaf types of the first data structure, and the two leaf types of the second data structure, respectively.
Example:
qcdata_zip (bit, [qubit]) int bool char string (True, [2,3]) ("b", ['c', 'd']) = ((True, "b"), [(2,'c'), (3,'d')]) where the shape parameters are: int = dummy :: Int bool = dummy :: Bool char = dummy :: Char string = dummy :: String
The ErrMsg
argument is a stub error message to be used in
case of failure.
qcdata_promote :: BType qc -> qc -> ErrMsg -> BType qc Source #
It is sometimes convenient to have a boolean parameter with
some aspect of its shape indeterminate. The function
qcdata_promote
takes such a boolean parameter, as well as a
piece of QCData
, and attempts to set the shape of the former to
that of the latter.
The kinds of promotions that are allowed depend on the data type.
For example, for simple types, qcdata_promote
has no work to do
and should just return the first argument. For types that are not
simple, but where no promotion is desired
(e.g. Qureg
), qcdata_promote
should
check that the shapes of the first and second argument agree, and
throw an error otherwise. For lists, we allow a longer list to be
promoted to a shorter one, but not the other way around. For
quantum integers, we allow an integer of indeterminate length to
be promoted to a determinate length, but we do not allow a
determinate length to be changed to another determinate length.
The ErrMsg
argument is a stub error message to be used in
case of failure.
Instances
QCData Char # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => Char -> (q -> m q') -> (c -> m c') -> QCType q c Char -> m (QCType q' c' Char) Source # qcdata_zip :: Char -> q -> c -> q' -> c' -> QCType q c Char -> QCType q' c' Char -> ErrMsg -> QCType (q, q') (c, c') Char Source # qcdata_promote :: BType Char -> Char -> ErrMsg -> BType Char Source # | |
QCData Double # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => Double -> (q -> m q') -> (c -> m c') -> QCType q c Double -> m (QCType q' c' Double) Source # qcdata_zip :: Double -> q -> c -> q' -> c' -> QCType q c Double -> QCType q' c' Double -> ErrMsg -> QCType (q, q') (c, c') Double Source # qcdata_promote :: BType Double -> Double -> ErrMsg -> BType Double Source # | |
QCData Float # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => Float -> (q -> m q') -> (c -> m c') -> QCType q c Float -> m (QCType q' c' Float) Source # qcdata_zip :: Float -> q -> c -> q' -> c' -> QCType q c Float -> QCType q' c' Float -> ErrMsg -> QCType (q, q') (c, c') Float Source # qcdata_promote :: BType Float -> Float -> ErrMsg -> BType Float Source # | |
QCData Int # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => Int -> (q -> m q') -> (c -> m c') -> QCType q c Int -> m (QCType q' c' Int) Source # qcdata_zip :: Int -> q -> c -> q' -> c' -> QCType q c Int -> QCType q' c' Int -> ErrMsg -> QCType (q, q') (c, c') Int Source # qcdata_promote :: BType Int -> Int -> ErrMsg -> BType Int Source # | |
QCData Integer # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => Integer -> (q -> m q') -> (c -> m c') -> QCType q c Integer -> m (QCType q' c' Integer) Source # qcdata_zip :: Integer -> q -> c -> q' -> c' -> QCType q c Integer -> QCType q' c' Integer -> ErrMsg -> QCType (q, q') (c, c') Integer Source # qcdata_promote :: BType Integer -> Integer -> ErrMsg -> BType Integer Source # | |
QCData () # | |
Defined in Quipper.Internal.QData | |
QCData Bit # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => Bit -> (q -> m q') -> (c -> m c') -> QCType q c Bit -> m (QCType q' c' Bit) Source # qcdata_zip :: Bit -> q -> c -> q' -> c' -> QCType q c Bit -> QCType q' c' Bit -> ErrMsg -> QCType (q, q') (c, c') Bit Source # qcdata_promote :: BType Bit -> Bit -> ErrMsg -> BType Bit Source # | |
QCData Qubit # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => Qubit -> (q -> m q') -> (c -> m c') -> QCType q c Qubit -> m (QCType q' c' Qubit) Source # qcdata_zip :: Qubit -> q -> c -> q' -> c' -> QCType q c Qubit -> QCType q' c' Qubit -> ErrMsg -> QCType (q, q') (c, c') Qubit Source # qcdata_promote :: BType Qubit -> Qubit -> ErrMsg -> BType Qubit Source # | |
QCData a => QCData [a] # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => [a] -> (q -> m q') -> (c -> m c') -> QCType q c [a] -> m (QCType q' c' [a]) Source # qcdata_zip :: [a] -> q -> c -> q' -> c' -> QCType q c [a] -> QCType q' c' [a] -> ErrMsg -> QCType (q, q') (c, c') [a] Source # qcdata_promote :: BType [a] -> [a] -> ErrMsg -> BType [a] Source # | |
QCData a => QCData (Signed a) # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => Signed a -> (q -> m q') -> (c -> m c') -> QCType q c (Signed a) -> m (QCType q' c' (Signed a)) Source # qcdata_zip :: Signed a -> q -> c -> q' -> c' -> QCType q c (Signed a) -> QCType q' c' (Signed a) -> ErrMsg -> QCType (q, q') (c, c') (Signed a) Source # qcdata_promote :: BType (Signed a) -> Signed a -> ErrMsg -> BType (Signed a) Source # | |
(QCData a, QCData b) => QCData (a, b) # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => (a, b) -> (q -> m q') -> (c -> m c') -> QCType q c (a, b) -> m (QCType q' c' (a, b)) Source # qcdata_zip :: (a, b) -> q -> c -> q' -> c' -> QCType q c (a, b) -> QCType q' c' (a, b) -> ErrMsg -> QCType (q, q') (c, c') (a, b) Source # qcdata_promote :: BType (a, b) -> (a, b) -> ErrMsg -> BType (a, b) Source # | |
(QCData a, QCData b) => QCData (B_Endpoint a b) # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => B_Endpoint a b -> (q -> m q') -> (c -> m c') -> QCType q c (B_Endpoint a b) -> m (QCType q' c' (B_Endpoint a b)) Source # qcdata_zip :: B_Endpoint a b -> q -> c -> q' -> c' -> QCType q c (B_Endpoint a b) -> QCType q' c' (B_Endpoint a b) -> ErrMsg -> QCType (q, q') (c, c') (B_Endpoint a b) Source # qcdata_promote :: BType (B_Endpoint a b) -> B_Endpoint a b -> ErrMsg -> BType (B_Endpoint a b) Source # | |
(QCData a, QCData b, QCData c) => QCData (a, b, c) # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => (a, b, c) -> (q -> m q') -> (c0 -> m c') -> QCType q c0 (a, b, c) -> m (QCType q' c' (a, b, c)) Source # qcdata_zip :: (a, b, c) -> q -> c0 -> q' -> c' -> QCType q c0 (a, b, c) -> QCType q' c' (a, b, c) -> ErrMsg -> QCType (q, q') (c0, c') (a, b, c) Source # qcdata_promote :: BType (a, b, c) -> (a, b, c) -> ErrMsg -> BType (a, b, c) Source # | |
(QCData a, QCData b, QCData c, QCData d) => QCData (a, b, c, d) # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => (a, b, c, d) -> (q -> m q') -> (c0 -> m c') -> QCType q c0 (a, b, c, d) -> m (QCType q' c' (a, b, c, d)) Source # qcdata_zip :: (a, b, c, d) -> q -> c0 -> q' -> c' -> QCType q c0 (a, b, c, d) -> QCType q' c' (a, b, c, d) -> ErrMsg -> QCType (q, q') (c0, c') (a, b, c, d) Source # qcdata_promote :: BType (a, b, c, d) -> (a, b, c, d) -> ErrMsg -> BType (a, b, c, d) Source # | |
(QCData a, QCData b, QCData c, QCData d, QCData e) => QCData (a, b, c, d, e) # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => (a, b, c, d, e) -> (q -> m q') -> (c0 -> m c') -> QCType q c0 (a, b, c, d, e) -> m (QCType q' c' (a, b, c, d, e)) Source # qcdata_zip :: (a, b, c, d, e) -> q -> c0 -> q' -> c' -> QCType q c0 (a, b, c, d, e) -> QCType q' c' (a, b, c, d, e) -> ErrMsg -> QCType (q, q') (c0, c') (a, b, c, d, e) Source # qcdata_promote :: BType (a, b, c, d, e) -> (a, b, c, d, e) -> ErrMsg -> BType (a, b, c, d, e) Source # | |
(QCData a, QCData b, QCData c, QCData d, QCData e, QCData f) => QCData (a, b, c, d, e, f) # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => (a, b, c, d, e, f) -> (q -> m q') -> (c0 -> m c') -> QCType q c0 (a, b, c, d, e, f) -> m (QCType q' c' (a, b, c, d, e, f)) Source # qcdata_zip :: (a, b, c, d, e, f) -> q -> c0 -> q' -> c' -> QCType q c0 (a, b, c, d, e, f) -> QCType q' c' (a, b, c, d, e, f) -> ErrMsg -> QCType (q, q') (c0, c') (a, b, c, d, e, f) Source # qcdata_promote :: BType (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> ErrMsg -> BType (a, b, c, d, e, f) Source # | |
(QCData a, QCData b, QCData c, QCData d, QCData e, QCData f, QCData g) => QCData (a, b, c, d, e, f, g) # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => (a, b, c, d, e, f, g) -> (q -> m q') -> (c0 -> m c') -> QCType q c0 (a, b, c, d, e, f, g) -> m (QCType q' c' (a, b, c, d, e, f, g)) Source # qcdata_zip :: (a, b, c, d, e, f, g) -> q -> c0 -> q' -> c' -> QCType q c0 (a, b, c, d, e, f, g) -> QCType q' c' (a, b, c, d, e, f, g) -> ErrMsg -> QCType (q, q') (c0, c') (a, b, c, d, e, f, g) Source # qcdata_promote :: BType (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> ErrMsg -> BType (a, b, c, d, e, f, g) Source # | |
(QCData a, QCData b, QCData c, QCData d, QCData e, QCData f, QCData g, QCData h) => QCData (a, b, c, d, e, f, g, h) # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => (a, b, c, d, e, f, g, h) -> (q -> m q') -> (c0 -> m c') -> QCType q c0 (a, b, c, d, e, f, g, h) -> m (QCType q' c' (a, b, c, d, e, f, g, h)) Source # qcdata_zip :: (a, b, c, d, e, f, g, h) -> q -> c0 -> q' -> c' -> QCType q c0 (a, b, c, d, e, f, g, h) -> QCType q' c' (a, b, c, d, e, f, g, h) -> ErrMsg -> QCType (q, q') (c0, c') (a, b, c, d, e, f, g, h) Source # qcdata_promote :: BType (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> ErrMsg -> BType (a, b, c, d, e, f, g, h) Source # | |
(QCData a, QCData b, QCData c, QCData d, QCData e, QCData f, QCData g, QCData h, QCData i) => QCData (a, b, c, d, e, f, g, h, i) # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => (a, b, c, d, e, f, g, h, i) -> (q -> m q') -> (c0 -> m c') -> QCType q c0 (a, b, c, d, e, f, g, h, i) -> m (QCType q' c' (a, b, c, d, e, f, g, h, i)) Source # qcdata_zip :: (a, b, c, d, e, f, g, h, i) -> q -> c0 -> q' -> c' -> QCType q c0 (a, b, c, d, e, f, g, h, i) -> QCType q' c' (a, b, c, d, e, f, g, h, i) -> ErrMsg -> QCType (q, q') (c0, c') (a, b, c, d, e, f, g, h, i) Source # qcdata_promote :: BType (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> ErrMsg -> BType (a, b, c, d, e, f, g, h, i) Source # | |
(QCData a, QCData b, QCData c, QCData d, QCData e, QCData f, QCData g, QCData h, QCData i, QCData j) => QCData (a, b, c, d, e, f, g, h, i, j) # | |
Defined in Quipper.Internal.QData qcdata_mapM :: Monad m => (a, b, c, d, e, f, g, h, i, j) -> (q -> m q') -> (c0 -> m c') -> QCType q c0 (a, b, c, d, e, f, g, h, i, j) -> m (QCType q' c' (a, b, c, d, e, f, g, h, i, j)) Source # qcdata_zip :: (a, b, c, d, e, f, g, h, i, j) -> q -> c0 -> q' -> c' -> QCType q c0 (a, b, c, d, e, f, g, h, i, j) -> QCType q' c' (a, b, c, d, e, f, g, h, i, j) -> ErrMsg -> QCType (q, q') (c0, c') (a, b, c, d, e, f, g, h, i, j) Source # qcdata_promote :: BType (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> ErrMsg -> BType (a, b, c, d, e, f, g, h, i, j) Source # |
The SimpleType class
class QCData qc => SimpleType qc where Source #
SimpleType
is a subclass of QCData
consisting of simple
types. We say that a data type t is "simple" if any two
elements of t have the same number of leaves. For example, tuples
are simple, but lists are not.
Produce a term of the given shape. This term will contain
well-defined data constructors, but may be undefined
at the
leaves.
Instances
Type conversions
We define convenient abbreviations for conversions to, or between, homogeneous types.
type QType a = QCType Qubit Qubit a Source #
The type operator QType
converts a classical or heterogeneous
type to a homogeneous quantum type. More precisely, the type
QType
a represents the substitution Qubit
/ Bit
]
QType (Bit, [Bit]) = (Qubit, [Qubit]) QType (Qubit, Bit) = (Qubit, Qubit)
type CType a = QCType Bit Bit a Source #
The type operator CType
converts a classical or heterogeneous
type to a homogeneous quantum type. More precisely, the type
CType
a represents the substitution Bit
/ Qubit
]
CType (Qubit, [Qubit]) = (Bit, [Bit]) CType (Qubit, Bit) = (Bit, Bit)
type BType a = QCType Bool Bool a Source #
The type operator BType
converts a classical, quantum, or
heterogeneous type to a homogeneous boolean type. More precisely,
the type BType
a represents the substitution
Bool
/ Qubit
, Bool
/ Bit
]
BType (Qubit, [Qubit]) = (Bool, [Bool]) BType (Qubit, Bit) = (Bool, Bool)
type HType leaf qa = QCType leaf leaf (QType qa) Source #
The type operator HType
x converts a classical, quantum, or
boolean type to a homogeneous type with leaves x. More precisely,
the type HType
x a represents the substitution
Qubit
, x / Bit
]
HType x (Qubit, [Qubit]) = (x, [x]) HType x (Qubit, Bit) = (x, x)
There is a very subtle difference between HType
x a and
QCType
x x a. Although these two types are equal for all
x and a, the type checker cannot actually prove that QCType
x x a is homogeneous from the assumption QCData
a. It
can, however, prove that HType
x a is homogeneous. Therefore
HType
(or the slightly more efficient special cases QType
,
CType
, BType
) should always be used to create a homogeneous
type from a heterogeneous one.
Shape parameters
Several operations, such as qcdata_mapM
and qcdata_zip
,
require a "shape type parameter". The purpose of such a parameter
is only to fix a type; its value is completely unused.
- Introduction to shape type parameters
The need for shape type parameters arises when dealing with a
data structure whose leaves are of some arbitrary type, rather than
Qubit
, Bit
, or Bool
. For example, consider the data structure
[(1, 2), (3, 4)]
This could be parsed in several different ways:
- as a data structure [(leaf, leaf), (leaf, leaf)], where each leaf is an integer;
- as a data structure [leaf, leaf], where each leaf is a pair of integers;
- as a data structure leaf, where each leaf is a list of pairs of integers.
The purpose of a shape type is to disambiguate this situation. In
shape types, the type Qubit
(and sometimes Bit
, in the case of
heterogeneous types) takes the place of a leaf. In the three
situations of the above example, the shape type would be [(Qubit
,
Qubit
)] in the first case; [Qubit
] in the second case, the
Qubit
in the third case.
- Difference between shape type parameters and shape term parameters
A shape type parameter exists only to describe a type; its value is irrelevant and often undefined. A shape type parameter describes the location of leaves in a type. On the other hand, the purpose of a shape term parameter is used to fix the number and locations of leaves in a data structure (for example, to fix the length of a list). Shape term parameters are also often just called "shape parameters" in Quipper.
The distinction is perhaps best illustrated in an example. A typical shape type parameter is
undefined :: (Qubit, [Qubit], [[Bit]])
A typical shape term parameter is
(qubit, [qubit, qubit, qubit], [[bit, bit], []]) :: (Qubit, [Qubit], [[Bit]])
Both of them have the same type. The shape type parameter specifies that the data structure is a triple consisting of a qubit, a list of qubits, and a list of lists of bits. The shape term parameter moreover specifies that the first list consists of exactly three qubits, and the second lists consists of a list of two bits and a list of zero bits.
Note that the value of the shape type parameter is undefined (we
often use the term dummy
instead of undefined
, to get more
meaningful error messages). On the other hand, the value of the
shape term parameter is partially defined; only the leaves are
of undefined value.
- Functions for specifying shape type parameters
Since it is not possible, in Haskell, to pass a type as an argument
to a function, we provide some terms whose only purpose is to
represent types. All of them have value undefined
. Effectively,
a shape type parameter is a type "written as a term".
The following terms can also be combined in data structures to represent composite types. For example:
(qubit, [bit]) :: (Qubit, [Bit])
A dummy term of any type. This term is undefined
and must never
be evaluated. Its only purpose is to hold a type.
A dummy term of type Qubit
. It can be used in shape parameters
(e.g., qc_init
), as well as shape type parameters (e.g.,
qcdata_mapM
).
A dummy term of type Bit
. It can be used in shape parameters
(e.g., qc_init
), as well as shape type parameters (e.g.,
qcdata_mapM
).
shapetype_q :: QData qa => QType qa -> qa Source #
Convert a piece of homogeneous quantum data to a shape type parameter. This is guaranteed to never evaluate x, and returns an undefined value.
shapetype_c :: QData qa => CType qa -> qa Source #
Convert a piece of homogeneous classical data to a shape type parameter. This is guaranteed to never evaluate x, and returns an undefined value.
shapetype_b :: QData qa => BType qa -> qa Source #
Convert a piece of homogeneous boolean data to a shape type
parameter. This is guaranteed to never evaluate x, and returns an
undefined value. Do not confuse this with the function
qshape
, which creates a shape value.
A dummy term of the same type as the given term. If x :: a,
then dummy
x :: a. This is guaranteed not to evaluate x,
and returns an undefined value.
Homogeneous types
The QData class
The QData
type class contains homogeneous data types built up
from leaves of type Qubit
. It contains no methods; all of its
functionality is derived from QCData
. It does, however, contain
a number of equations that help the type checker figure out how to
convert heterogeneous type to homogeneous ones and vice versa.
type QData qa = (qa ~ QType (CType qa), qa ~ QTypeB (BType qa), qa ~ QCType Qubit Bool qa, qa ~ QType qa, QCData qa, QCData (CType qa)) Source #
Derived combinators on QData
This section provides several convenient combinators for the
QData
class. All of them are definable from those of
QCData
.
qdata_mapM :: (QData qa, Monad m) => qa -> (x -> m y) -> HType x qa -> m (HType y qa) Source #
Map a function f over all the leaves of a data structure. The first argument is a dummy shape parameter: its value is ignored, but its type is used to determine the shape of the data to map over.
Example (ignoring the monad for the sake of simplicity):
qdata_mapM (leaf, [leaf]) f (x,[y,z,w]) = (f x, [f y, f z, f w]).
For data types that have a sense of direction, the mapping should preferably be performed from left to right, but this property is not guaranteed and may change without notice.
qdata_zip :: QData qa => qa -> x -> y -> HType x qa -> HType y qa -> ErrMsg -> HType (x, y) qa Source #
Zip two data structures with leaf types x and y together, to obtain a new data structure of the same shape with leaf type (x, y). The first three arguments are dummy shape type parameters, representing the shape type and the two leaf types, respectively.
The ErrMsg
argument is a stub error message to be used in case
of failure.
qdata_promote :: QData qa => BType qa -> qa -> ErrMsg -> BType qa Source #
Sometimes, it is possible to have a boolean parameter with some
aspect of its shape indeterminate. The function qdata_promote
takes such a boolean parameter, as well as a piece of quantum data,
and sets the shape of the former to that of the latter.
Indeterminate shapes can be used with certain operations, such as controlling and terminating, where some aspect of the shape of the parameter can be determined from the context in which it is used. This is useful, e.g., for quantum integers, where one may want to specify a control condition by an integer literal such as 17, without having to specify the number of bits. Thus, we can write, e.g.,
gate `controlled` qi .==. 17
instead of the more cumbersome
gate `controlled` qi .==. (intm (qdint_length qi) 17).
Another useful application of this arises in the use of infinite
lists of booleans (such as [
), to specify a control
condition for a finite list of qubits.False
..]
Because this function is used as a building block, we also pass an error message to be used in case of failure. This will hopefully make it clearer to the user which operation caused the error.
qdata_map :: QData s => s -> (x -> y) -> HType x s -> HType y s Source #
Map a function over every leaf in a data structure. Non-monadic
version of qdata_mapM
.
qdata_fold :: QData s => s -> (x -> w -> w) -> HType x s -> w -> w Source #
Visit every leaf in a data structure, updating an accumulator.
qdata_fold_map :: QData s => s -> (x -> w -> (y, w)) -> HType x s -> w -> (HType y s, w) Source #
Map a function over every leaf in a data structure, while also
updating an accumulator. This combines the functionality of
qdata_fold
and qdata_map
.
qdata_foldM :: (QData s, Monad m) => s -> (x -> w -> m w) -> HType x s -> w -> m w Source #
Monadic version of qdata_fold
: Visit every leaf in a data
structure, updating an accumulator.
qdata_fold_mapM :: (QData s, Monad m) => s -> (x -> w -> m (y, w)) -> HType x s -> w -> m (HType y s, w) Source #
Monadic version of qdata_fold_map
: Map a function over every
leaf in a data structure, while also updating an accumulator. This
combines the functionality of qdata_foldM
and qdata_mapM
.
qdata_sequentialize :: QData s => s -> HType x s -> [x] Source #
Return a list of leaves of the given homogeneous data structure. The first argument is a dummy shape type parameter, and is only used for its type.
The leaves are ordered in some deterministic, but arbitrary way. It is guaranteed that when two data structures of the same shape type and shape (same length of lists etc) are sequentialized, the leaves will be ordered the same way. No other property of the order is guaranteed, In particular, it might change without notice.
qdata_unsequentialize :: QData s => s -> [x] -> HType x s Source #
Take a specimen homogeneous data structure to specify the "shape"
desired (length of lists, etc); then reads the given list of leaves
in as a piece of homogeneous data of the same shape. The ordering
of the leaves is assumed to be the same as that which
qdata_sequentialize
produces for the given shape.
A "length mismatch" error occurs if the list does not have exactly the required length.
Please note that, by contrast with the function
qdata_sequentialize
, the first argument is a shape term
parameter, not a shape type parameter. It is used to decide where
the qubits should go in the data structure.
qdata_makeshape :: QData qa => qa -> a -> HType a qa -> qa Source #
Combine a shape type argument q, a leaf type argument a, and a shape size argument x into a single shape argument qx. Note:
- q captures only the type, but not the size of the data. Only the type of q is used; its value can be undefined. This is sufficient to determine the depth of leaves in a data structure, but not their number.
- x captures only the size of the data, but not its type. In particular, x may have leaves of non-atomic types. x must consist of well-defined constructors up to the depth of leaves of q, but the values at the actual leaves of x may be undefined.
- The output qx combines the type of q with the size of x,
and can therefore be used both as a shape type and a shape value.
Note that the actual leaves of qx will be
qubit
andbit
, which are synonyms forundefined
.
Example:
q = undefined :: ([Qubit], [[Qubit]]) x = ([undefined, 0], [[undefined], [0, 1]]) qdata_makeshape qc a x = ([qubit, qubit], [[qubit], [qubit, qubit]])
where a :: Int
.
qdata_mapM_op :: (QData s, Monad m) => s -> (x -> m y) -> HType x s -> m (HType y s) Source #
Like qdata_mapM
, except the leaves are visited in exactly the
opposite order. This is used primarily for cosmetic reasons: For
example, when initializing a bunch of ancillas, and then
terminating them, the circuit will look more symmetric if they are
terminated in the opposite order.
qdata_promote_c :: QData s => BType s -> CType s -> ErrMsg -> BType s Source #
Like qdata_promote
, except take a piece of classical data.
The CData and BData classes
The QShape class
By definition, QShape
ba qa ca means that ba, qa, and
ca are, respectively, boolean, quantum, and classical homogeneous
data types of the same common shape. The QShape
class directly
defined in terms of the QData
class. In fact, the two classes are
interchangeable in the following sense:
QShape ba qa ca implies QData qa,
and conversely,
QData qa implies QShape (BType qa) qa (CType qa).
Moreover, the functional dependencies ba -> qa, qa -> ca,
ca -> ba
ensure that each of the three types determines the
other two. Therefore, in many ways, QShape
is just a convenient
notation for functionality already present in QData
.
type QShape ba qa ca = (QData qa, BType qa ~ ba, CType qa ~ ca) Source #
The QShape
class allows the definition of generic functions that
can operate on quantum data of any "shape", for example, nested
tuples or lists of qubits.
In general, there are three kinds of data: quantum inputs (such as
Qubit
), classical inputs (such as Bit
), and classical
parameters (such as Bool
). For example, a Qubit
can be
initialized from a Bool
; a Qubit
can be measured, resulting in
a Bit
, etc. For this reason, the type class QShape
establishes a
relation between three types:
qa
- A data structure having
Qubit
at the leaves. ca
- A data structure of the same shape as
qa
, havingBit
at the leaves. ba
- A data structure of the same shape as
qa
, havingBool
at the leaves.
Some functions input a classical parameter for the sole purpose of establishing the "shape" of a piece of data. The shape refers to qualities of a data structure, such as the length of a list, which are not uniquely determined by the type. For example, two different lists of length 5 have the same shape. When performing a generic operation, such as reversing a circuit, it is often necessary to specify the shape of the inputs, but not the actual inputs.
In the common case where one only needs to declare one of the types
qa, ca, or ba, one of the simpler type classes QData
,
CData
, or BData
can be used.
Heterogeneous types
A heterogeneous type describes a data structure built up from
leaves of type Qubit
and Bit
. Such types are used, for example,
to represent sets of endpoints in circuits, parameters to
subroutines and circuit building functions. A typical example is:
(Bit, Qubit, [Qubit]).
Derived combinators on QCData
The QCData
type class only contains the three primitive
combinators qcdata_mapM
, qcdata_zip
, and qcdata_promote
.
Many other useful combinators are definable in terms of these, and
we provide several of them here.
qcdata_unzip :: QCData qc => qc -> q -> c -> q' -> c' -> QCType (q, q') (c, c') qc -> (QCType q c qc, QCType q' c' qc) Source #
The inverse of qcdata_zip
: Take a data structure whose leaves
are pairs, and return two data structures of the same shape,
collecting all the left components and all the right components,
respectively. The first five arguments are shape type parameters,
analogous to those of qcdata_zip
.
qcdata_map :: QCData qc => qc -> (q -> q') -> (c -> c') -> QCType q c qc -> QCType q' c' qc Source #
Map two functions f and g over the leaves of a heterogeneous
data structure. Apply f to all the leaves at Qubit
positions,
and g to all the leaves at Bit
positions. Non-monadic version
of qcdata_mapM
.
qcdata_fold :: QCData qc => qc -> (q -> w -> w) -> (c -> w -> w) -> QCType q c qc -> w -> w Source #
qcdata_fold_map :: QCData qc => qc -> (q -> w -> (q', w)) -> (c -> w -> (c', w)) -> QCType q c qc -> w -> (QCType q' c' qc, w) Source #
Map a function over every leaf in a data structure, while also
updating an accumulator. This combines the functionality of
qcdata_fold
and qcdata_map
.
qcdata_foldM :: (QCData qc, Monad m) => qc -> (q -> w -> m w) -> (c -> w -> m w) -> QCType q c qc -> w -> m w Source #
Monadic version of qcdata_fold
: Visit every leaf in a data
structure, updating an accumulator. This function requires two
accumulator functions f and g, to be used at Qubit
positions
and Bit
positions, respectively.
qcdata_fold_mapM :: (QCData qc, Monad m) => qc -> (q -> w -> m (q', w)) -> (c -> w -> m (c', w)) -> QCType q c qc -> w -> m (QCType q' c' qc, w) Source #
Monadic version of qcdata_fold_map
: Map a function over every
leaf in a data structure, while also updating an accumulator. This
combines the functionality of qcdata_foldM
and qcdata_mapM
.
qcdata_sequentialize :: QCData qc => qc -> QCType q c qc -> [B_Endpoint q c] Source #
Return a list of leaves of the given heterogeneous data structure. The first argument is a dummy shape type parameter, and is only used for its type. Leaves in qubit positions and bit positions are returned, respectively, as the left or right components of a disjoint union.
The leaves are ordered in some deterministic, but arbitrary way. It is guaranteed that when two data structures of the same shape type and shape (same length of lists etc) are sequentialized, the leaves will be ordered the same way. No other property of the order is guaranteed, In particular, it might change without notice.
qcdata_unsequentialize :: QCData qc => qc -> [B_Endpoint q c] -> QCType q c qc Source #
Take a specimen heterogeneous data structure to specify the
"shape" desired (length of lists, etc); then reads the given list
of leaves in as a piece of heterogeneous data of the same
shape. The ordering of the leaves, and the division of the leaves
into qubit and bit positions, is assumed to be the same as that
which qcdata_sequentialize
produces for the given shape.
A "length mismatch" error occurs if the list does not have
exactly the required length. A "shape mismatch" error occurs if
the list contains an Endpoint_Bit
entry corresponding to a
Qubit
position in the shape, or an Endpoint_Qubit
entry
corresponding to a Bit
position.
Please note that, by contrast with the function
qcdata_sequentialize
, the first argument is a shape term
parameter, not a shape type parameter. It is used to decide where
the qubits and bits should go in the data structure.
qcdata_makeshape :: QCData qc => qc -> a -> b -> QCType a b qc -> qc Source #
Combine a shape type argument q, two leaf type arguments a and b, and a shape size argument x into a single shape argument qx. Note:
- q captures only the type, but not the size of the data. Only the type of q is used; its value can be undefined. This is sufficient to determine the depth of leaves in a data structure, but not their number.
- x captures only the size of the data, but not its type. In particular, x may have leaves of non-atomic types. x must consist of well-defined constructors up to the depth of leaves of q, but the values at the actual leaves of x may be undefined.
- The output qx combines the type of q with the size of x,
and can therefore be used both as a shape type and a shape value.
Note that the actual leaves of qx will be
qubit
andbit
, which are synonyms forundefined
.
Example:
qc = undefined :: ([Qubit], [[Bit]]) x = ([undefined, (0,False)], [[undefined], [Just 2, Nothing]]) qcdata_makeshape qc a b x = ([qubit, qubit], [[bit], [bit, bit]])
where a :: (Int,Bool)
, b :: (Maybe Int)
.
qcdata_mapM_op :: (QCData qc, Monad m) => qc -> (q -> m q') -> (c -> m c') -> QCType q c qc -> m (QCType q' c' qc) Source #
Like qcdata_mapM
, except the leaves are visited in exactly the
opposite order. This is used primarily for cosmetic reasons: For
example, when initializing a bunch of ancillas, and then
terminating them, the circuit will look more symmetric if they are
terminated in the opposite order.
The QCDataPlus class
type QCDataPlus qc = (QCData qc, QData (QType qc)) Source #
The QCDataPlus
type class is almost identical to QCData
,
except that it contains one additional piece of information that
allows the type checker to prove the implications
QCDataPlus qc implies QShape (BType qc) (QType qc) (CType qc) QCDataPlus qc implies QData (QType qc) QCDataPlus qc implies CData (CType qc) QCDataPlus qc implies BData (BType qc)
This is sometimes useful, for example, in the context of a function
that inputs a QCData
, measures all the qubits, and returns a
CData
. However, the additional information for the type checker
comes at a price, which is drastically increased compilation time.
Therefore QCDataPlus
should only be used when QCData
is
insufficient.
Fixed size QCDataPlus
type QCData_Simple qc = (QCData qc, SimpleType qc) Source #
QCDataPlus_Simple
is a convenience type class that combines
QCDataPlus
and SimpleType
.
type QCDataPlus_Simple qc = (QCDataPlus qc, SimpleType qc) Source #
QCDataPlus_Simple
is a convenience type class that combines
QCDataPlus
and SimpleType
.
The QCLeaf class
class (QCData q, SimpleType q, ControlSource q, ControlSource (Signed q), Labelable q String, QCType Qubit Bit q ~ q, QCType Bool Bool q ~ Bool) => QCLeaf q Source #
The class QCLeaf
consists of the two types Qubit
and Bit
.
It is primarily used for convenience, in those cases (such as the
arithmetic library) where some class instance should be defined for
the cases Qubit
and Bit
, but not for general QCData
. It is
also used, e.g., in the definition of the 'Quipper.(./=.)' operator.
Instances
QCLeaf Bit # | |
Defined in Quipper.Internal.QData | |
QCLeaf Qubit # | |
Defined in Quipper.Internal.QData |
Canonical string representation
For the purpose of storing boxed subroutines, it is useful to
have a unique representation of QCData
shapes as strings. The
currently implementation relies on show
to give unique
representations. Therefore, when defining Show
instances for
QCData
, one should make sure that the generated strings contain
enough information to recover both the type and the shape uniquely.
data Qubit_Leaf Source #
Instances
Show Qubit_Leaf # | |
Defined in Quipper.Internal.QData showsPrec :: Int -> Qubit_Leaf -> ShowS # show :: Qubit_Leaf -> String # showList :: [Qubit_Leaf] -> ShowS # |
canonical_shape :: QCData qc => qc -> String Source #
type LType a = QCType Qubit_Leaf Bit_Leaf a Source #
The type operator LType
converts Qubit
to Qubit_Leaf
and
Bit
to Bit_Leaf
.
Defining new QCData instances
To define a new kind of quantum data, the following must be defined:
If the new type is simple, an class instance of SimpleType
should
also be defined.
If the new type may be integrated with Template Haskell, a class
instance of CircLiftingUnpack
should
also be defined.
To ensure that circuit labeling will work for the new type, a class
instance of Labelable
must also be defined for every member of
QCData
. See Quipper.Internal.Labels for detailed instructions on how to
do so.
Modules that define new kinds of quantum data should import Quipper.Internal.