newsynth-0.2: Exact and approximate synthesis of quantum circuits

Safe HaskellSafe-Inferred

Quantum.Synthesis.SymReal

Contents

Description

This module provides a symbolic representation of real number expressions, as well as a type class of things that can be converted to arbitrary precision real numbers.

Synopsis

Symbolic real number expressions

data SymReal Source

A type to represent symbolic expressions for real numbers.

Caution: equality == at this type denotes symbolic equality of expressions, not equality of the defined real numbers.

Constructors

Const Integer

An integer constant.

Decimal Rational String

A decimal constant. This has a rational value and a string representation.

Plus SymReal SymReal

x + y.

Minus SymReal SymReal

x y.

Times SymReal SymReal

x * y.

Div SymReal SymReal

x / y.

Negate SymReal

x.

Abs SymReal

|x|.

Signum SymReal

signum(x).

Recip SymReal

1/x.

Pi

π.

Euler

e.

Exp SymReal

ex.

Sqrt SymReal

x.

Log SymReal

log x.

Power SymReal SymReal

xy.

Sin SymReal

sin x.

Tan SymReal

cos x.

Cos SymReal

cos x.

ASin SymReal

asin x.

ATan SymReal

atan x.

ACos SymReal

acos x.

Sinh SymReal

sinh x.

Tanh SymReal

tanh x.

Cosh SymReal

cosh x.

ASinh SymReal

asinh x.

ATanh SymReal

atanh x.

ACosh SymReal

acosh x.

ArcTan2 SymReal SymReal

arctan2 x y.

Conversion to real number types

class ToReal a whereSource

A type class for things that can be converted to a real number at arbitrary precision.

Methods

to_real :: (Floating r, ArcTan2 r) => a -> rSource

Dynamic conversion to FixedPrec

dynamic_fixedprec :: forall a r. ToReal r => Integer -> (forall e. Precision e => FixedPrec e -> a) -> r -> aSource

It would be useful to have a function for converting a symbolic real number to a fixed-precision real number with a chosen precision, such that the precision e depends on a parameter d:

 to_fixedprec :: (ToReal r) => Integer -> r -> FixedPrec e
 to_fixedprec d x = ...

However, since e is a type, d is a term, and Haskell is not dependently typed, this cannot be done directly.

The function dynamic_fixedprec is the closest thing we have to a workaround. The call dynamic_fixedprec d f x calls f(x'), where x' is the value x converted to d digits of precision. In other words, we have

 dynamic_fixedprec d f x = f (to_fixedprec d x),

with the restriction that the precision e cannot occur freely in the result type of f.

dynamic_fixedprec2 :: forall a r s. (ToReal r, ToReal s) => Integer -> (forall e. Precision e => FixedPrec e -> FixedPrec e -> a) -> r -> s -> aSource

Like dynamic_fixedprec, but take two real number arguments. In terms of the fictitious function to_fixedprec, we have:

 dynamic_fixedprec2 d f x y = f (to_fixedprec d x) (to_fixedprec d y).

A parser for real number expressions

Grammar specification

Each function in this section corresponds to a production rule for a context-free grammar. The type of each function is ReadP a, where a is the type of the semantic value produced by the grammar for that expression.

The parser uses simple precedences.

  • Unary "+" and "−" have precedence 6.
  • Binary "+" and "−" have precedence 6 and are left associative.
  • Binary "*" and "/" have precedence 7 and are left associative.
  • Binary "**" and "^" have precedence 8 and are right associative.
  • All unary operators other than "+" and "−" have precedence 10.

We use exp6 to denote an expression whose top-level operator has precedence 6 or higher, exp7 to denote an expression whose top-level operator has precedence 7 or higher, and so on.

We also allow whitespace between lexicographic entities. For simplicity, whitespace is not shown in the production rules, although it appears in the code.

integer :: ReadP SymRealSource

integer ::= digit digit*.

float :: ReadP SymRealSource

float ::= digit* "." digit*.

There must be at least one digit, either before or after the decimal point.

const_pi :: ReadP SymRealSource

const_pi ::= "pi".

const_e :: ReadP SymRealSource

const_e ::= "e".

negative :: ReadP (SymReal -> SymReal)Source

negative ::= "−".

positive :: ReadP (SymReal -> SymReal)Source

positive ::= "+".

plus_term :: ReadP (SymReal -> SymReal)Source

plus_term ::= "+" exp7.

minus_term :: ReadP (SymReal -> SymReal)Source

minus_term ::= "−" exp7.

times_term :: ReadP (SymReal -> SymReal)Source

times_term ::= "*" exp8.

div_term :: ReadP (SymReal -> SymReal)Source

div_term ::= "/" exp8.

power_term :: ReadP (SymReal -> SymReal)Source

power_term ::= exp10 "**" | exp10 "^".

unary_fun :: ReadP SymRealSource

unary_fun ::= unary_op exp10.

unary_op :: ReadP (SymReal -> SymReal)Source

unary_op ::= "abs" | "signum" | ...

binary_fun :: ReadP SymRealSource

binary_fun ::= binary_op exp10 exp10.

binary_op :: ReadP (SymReal -> SymReal -> SymReal)Source

binary_op ::= "abs" | "signum" | ...

exp6 :: ReadP SymRealSource

exp6 ::= (negative | positive)? exp7 ( plus_term | minus_term )*.

An expression whose top-level operator has precedence 6 or above. The operators of precedence 6 are "+" and "−".

exp7 :: ReadP SymRealSource

exp7 ::= exp8 ( times_term | div_term )*.

An expression whose top-level operator has precedence 7 or above. The operators of precedence 6 are "*" and "/".

exp8 :: ReadP SymRealSource

exp8 ::= ( power_term )* exp10

An expression whose top-level operator has precedence 8 or above. The operators of precedence 6 are "**" and "^".

exp10 :: ReadP SymRealSource

exp10 ::= parenthesized | const_pi | const_e | integer | float | unary_fun | binary_fun.

An expression whose top-level operator has precedence 10 or above. Such expressions are constants, applications of unary operators (except unary "−" and "+"), and parenthesized expressions.

parenthesized :: ReadP SymRealSource

parenthesized ::= "(" exp6 ")".

expression :: ReadP SymRealSource

expression ::= exp6 end-of-line.

This is a top-level expression.

Top-level parser

parse_SymReal :: String -> Maybe SymRealSource

Parse a symbolic real number expression. Typical strings that can be parsed are "1.0", "pi/128", "(1+sin(pi/3))^2", etc. If the expression cannot be parsed, return Nothing.