hops-0.7.2: Handy Operations on Power Series

CopyrightAnders Claesson 2015 2016
MaintainerAnders Claesson <anders.claesson@gmail.com>
Safe HaskellNone
LanguageHaskell98

HOPS.GF

Description

License : BSD-3

Synopsis

Documentation

packExpr :: Expr -> PackedExpr Source #

A compact representation of an Expr as a wrapped ByteString.

vars :: Core -> [Name] Source #

The list of variables in a program.

anums :: Core -> [Int] Source #

The list of A-numbers in a program.

insertVar :: ByteString -> Series n -> Env n -> Env n Source #

Insert a variable binding into the given environment.

data Core Source #

Constructors

App !Name ![Core] 
X 
A !Int 
Tag !Int 
Var !Name 
Lit !Rat 
Rats !Core 
Let !Name !Core 
Seq !Core !Core 

Instances

Eq Core Source # 

Methods

(==) :: Core -> Core -> Bool #

(/=) :: Core -> Core -> Bool #

Floating Core Source # 

Methods

pi :: Core #

exp :: Core -> Core #

log :: Core -> Core #

sqrt :: Core -> Core #

(**) :: Core -> Core -> Core #

logBase :: Core -> Core -> Core #

sin :: Core -> Core #

cos :: Core -> Core #

tan :: Core -> Core #

asin :: Core -> Core #

acos :: Core -> Core #

atan :: Core -> Core #

sinh :: Core -> Core #

cosh :: Core -> Core #

tanh :: Core -> Core #

asinh :: Core -> Core #

acosh :: Core -> Core #

atanh :: Core -> Core #

log1p :: Core -> Core #

expm1 :: Core -> Core #

log1pexp :: Core -> Core #

log1mexp :: Core -> Core #

Fractional Core Source # 

Methods

(/) :: Core -> Core -> Core #

recip :: Core -> Core #

fromRational :: Rational -> Core #

Num Core Source # 

Methods

(+) :: Core -> Core -> Core #

(-) :: Core -> Core -> Core #

(*) :: Core -> Core -> Core #

negate :: Core -> Core #

abs :: Core -> Core #

signum :: Core -> Core #

fromInteger :: Integer -> Core #

Ord Core Source # 

Methods

compare :: Core -> Core -> Ordering #

(<) :: Core -> Core -> Bool #

(<=) :: Core -> Core -> Bool #

(>) :: Core -> Core -> Bool #

(>=) :: Core -> Core -> Bool #

max :: Core -> Core -> Core #

min :: Core -> Core -> Core #

Show Core Source # 

Methods

showsPrec :: Int -> Core -> ShowS #

show :: Core -> String #

showList :: [Core] -> ShowS #

Pretty Core Source # 

data Env n Source #

An environment holds a mapping from A-numbers to series, and a mapping from names to series (assignments).

Constructors

Env 

Fields

Instances

Show (Env n) Source # 

Methods

showsPrec :: Int -> Env n -> ShowS #

show :: Env n -> String #

showList :: [Env n] -> ShowS #

evalCore :: KnownNat n => Env n -> Core -> Series n Source #

Evaluate a program in a given environment. E.g.

>>> evalCore (emptyEnv :: Env 4) [ log (1/(1-X)) ]
series (Proxy :: Proxy 4) [Val (0 % 1),Val (1 % 1),Val (1 % 2),Val (1 % 3)]

parseExpr :: ByteString -> Maybe Expr Source #

Parse an expression

parseExprErr :: ByteString -> Expr Source #

Parse a program and possibly fail with an error.