Jikka-5.5.0.0: A transpiler from Python to C++ for competitive programming
Copyright(c) Kimiyuki Onaka 2020
LicenseApache License 2.0
Maintainerkimiyuki95@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Jikka.CPlusPlus.Language.Expr

Description

Expr module has the basic data types for C++ language. The data types are intended to use for the code generation.

Documentation

newtype VarName Source #

Constructors

VarName 

Fields

newtype FunName Source #

Constructors

FunName 

Fields

data Type Source #

Constructors

TyAuto
auto
TyVoid
void
TyBool
bool
TyInt
int
TyInt32
int32_t
TyInt64
int64_t
TyTuple [Type]
std::tuple<T1, T2, ...>
TyVector Type
std::vector<T>
TyArray Type Integer
std::arrya<T, n>
TyString
std::string
TyFunction Type [Type]
std::function<Tr (T1, T2, ...)>
TyConvexHullTrick
jikka::convex_hull_trick
TySegmentTree Monoid'
atcoder::segtree<T, op, e>
TyIntValue Integer

an integer n for template parameters

Instances

Instances details
Eq Type Source # 
Instance details

Defined in Jikka.CPlusPlus.Language.Expr

Methods

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

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

Ord Type Source # 
Instance details

Defined in Jikka.CPlusPlus.Language.Expr

Methods

compare :: Type -> Type -> Ordering #

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

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

(>) :: Type -> Type -> Bool #

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

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

Read Type Source # 
Instance details

Defined in Jikka.CPlusPlus.Language.Expr

Show Type Source # 
Instance details

Defined in Jikka.CPlusPlus.Language.Expr

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

data Monoid' Source #

Constructors

MonoidIntPlus

\((\mathbb{Z}, +, 0)\)

MonoidIntMin

\((\mathrm{int64\_t}, \min, \mathrm{INT64\_MAX})\)

MonoidIntMax

\((\mathrm{int64\_t}, \max, \mathrm{INT64\_MIN})\)

MonoidIntGcd

\((\mathbb{Z}, \gcd, 0)\)

MonoidIntLcm

\((\mathbb{Z}, \mathrm{lcm}, 1)\)

data Function Source #

Constructors

Function FunName [Type]

other functions

Method FunName

other methods

At

subscription e1[e2]

SetAt Type

updated array auto tmp = e1; tmp[e2] = e3; return tmp;

Cast Type

cast (T)e

StdTuple [Type]

functio std::tuple<T1, T2, ...>(e1, e2, ...)

StdGet Integer

function std::get<T, n>(e)

ArrayExt Type
std::array<T, n>{e1, e2, ..., en}
VecExt Type
std::vector<T>{e1, e2, ...}
VecCtor Type

constructors std::vector<T>() std::vector<T>(n) std::vector<T>(n, e)

Range

function std::vector<int> jikka::range(int n), which is similar to Python's range or Boost's boost::range

MethodSize

size method of std::vector<T>

ConvexHullTrickCtor

the constructor of jikka::convex_hull_trick

ConvexHullTrickCopyAddLine

This makes a copy of jikka::convex_hull_trick and updates it. This is removed at run.

SegmentTreeCtor Monoid'

the constructors of atcoder::segtree<T, op, e>

SegmentTreeCopySetPoint Monoid'

This makes a copy of atcoder::segtree<T, op, e> and updates it. This is removed at run.

data UnaryOp Source #

Constructors

IntNop
+
Negate
-
BitNot
~
Not

! / not

Deref
*

data Expr Source #

Constructors

Var VarName 
Lit Literal 
UnOp UnaryOp Expr 
BinOp BinaryOp Expr Expr 
Cond Expr Expr Expr
e1 ? e2 : e3
Lam [(Type, VarName)] Type [Statement]

lambda expression [=](T1 x1, T2 x2, ...) -> Tr { stmt1; stmt2; ... }

Call Function [Expr]

f(e1, e2, ...) for a fixed function f

CallExpr Expr [Expr]

e(e1, e2, ...) for an callable expr e

Instances

Instances details
Eq Expr Source # 
Instance details

Defined in Jikka.CPlusPlus.Language.Expr

Methods

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

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

Ord Expr Source # 
Instance details

Defined in Jikka.CPlusPlus.Language.Expr

Methods

compare :: Expr -> Expr -> Ordering #

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

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

(>) :: Expr -> Expr -> Bool #

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

max :: Expr -> Expr -> Expr #

min :: Expr -> Expr -> Expr #

Read Expr Source # 
Instance details

Defined in Jikka.CPlusPlus.Language.Expr

Show Expr Source # 
Instance details

Defined in Jikka.CPlusPlus.Language.Expr

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

data Statement Source #

Constructors

ExprStatement Expr
e;
Block [Statement]
{ stmt1; stmts2; ...; }
If Expr [Statement] (Maybe [Statement])

if (e) { stmt1; stmts2; ...; } / if (e) { stmt1; stmts2; ...; } else { stmt1'; stmt2'; ...; }

For Type VarName Expr Expr AssignExpr [Statement]
for (T x = e1; e2; e3) { stmt1; stmts2; ...; }
ForEach Type VarName Expr [Statement]
for (T x : e) { stmt1; stmts2; ...; }
While Expr [Statement]
while (e) { stmt1; stmts2; ...; }
Declare Type VarName DeclareRight

Declarations with/witout initializations. See DeclareRight.

DeclareDestructure [VarName] Expr
auto [x1, x2, ...] = e;
Assign AssignExpr
e1 op= e2;
Assert Expr
assert (e);
Return Expr
return e;

newtype Program Source #

Constructors

Program