Jikka-5.0.11.1: 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.RestrictedPython.Language.Expr

Description

 
Synopsis

types

data Type Source #

Type represents the types of our restricted Python-like language.

\[ \newcommand\int{\mathbf{int}} \newcommand\bool{\mathbf{bool}} \newcommand\list{\mathbf{list}} \newcommand\string{\mathbf{string}} \begin{array}{rl} \tau ::= & \alpha \\ \vert & \int \\ \vert & \bool \\ \vert & \list(\tau) \\ \vert & \tau \times \tau \times \dots \times \tau \\ \vert & \tau \times \tau \times \dots \times \tau \to \tau \vert & \string \vert & \mathbf{side-effect} \end{array} \]

NOTE: \(\mathbf{None}\) is represented as the 0-tuple.

Instances

Instances details
Eq Type Source # 
Instance details

Defined in Jikka.RestrictedPython.Language.Expr

Methods

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

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

Ord Type Source # 
Instance details

Defined in Jikka.RestrictedPython.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.RestrictedPython.Language.Expr

Show Type Source # 
Instance details

Defined in Jikka.RestrictedPython.Language.Expr

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

pattern NoneTy :: Type Source #

operators

data UnaryOp Source #

Constructors

Invert

on int

Not

on bool

UAdd 
USub 

Instances

Instances details
Eq UnaryOp Source # 
Instance details

Defined in Jikka.Python.Language.Expr

Methods

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

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

Ord UnaryOp Source # 
Instance details

Defined in Jikka.Python.Language.Expr

Read UnaryOp Source # 
Instance details

Defined in Jikka.Python.Language.Expr

Show UnaryOp Source # 
Instance details

Defined in Jikka.Python.Language.Expr

data Operator Source #

Constructors

Add 
Sub 
Mult 
MatMult 
Div 
FloorDiv 
FloorMod 
CeilDiv

our extension

CeilMod

our extension

Pow 
BitLShift 
BitRShift 
BitOr 
BitXor 
BitAnd 
Max

our extension

Min

our extension

data BoolOp Source #

Constructors

And 
Or 
Implies

our extension

Instances

Instances details
Eq BoolOp Source # 
Instance details

Defined in Jikka.Python.Language.Expr

Methods

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

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

Ord BoolOp Source # 
Instance details

Defined in Jikka.Python.Language.Expr

Read BoolOp Source # 
Instance details

Defined in Jikka.Python.Language.Expr

Show BoolOp Source # 
Instance details

Defined in Jikka.Python.Language.Expr

data CmpOp Source #

Constructors

Eq' 
NotEq 
Lt 
LtE 
Gt 
GtE 
Is 
IsNot 
In 
NotIn 

Instances

Instances details
Eq CmpOp Source # 
Instance details

Defined in Jikka.Python.Language.Expr

Methods

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

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

Ord CmpOp Source # 
Instance details

Defined in Jikka.Python.Language.Expr

Methods

compare :: CmpOp -> CmpOp -> Ordering #

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

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

(>) :: CmpOp -> CmpOp -> Bool #

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

max :: CmpOp -> CmpOp -> CmpOp #

min :: CmpOp -> CmpOp -> CmpOp #

Read CmpOp Source # 
Instance details

Defined in Jikka.Python.Language.Expr

Show CmpOp Source # 
Instance details

Defined in Jikka.Python.Language.Expr

Methods

showsPrec :: Int -> CmpOp -> ShowS #

show :: CmpOp -> String #

showList :: [CmpOp] -> ShowS #

data CmpOp' Source #

CmpOp` is a type for comparision operators. This is annotated with its type as let-polymorphism.

Constructors

CmpOp' CmpOp Type 

data Builtin Source #

Constructors

BuiltinAbs

"abs" \(: \int \to \int\)

BuiltinPow

"pow" \((\lambda x k. x^k) : \int \times \int \to \int\)

BuiltinModPow

modulo power "pow" \((\lambda x k m. x^k \bmod m): \int \times \int \to \int\)

BuiltinDivMod

"divmod" \(: \int \times \int \to \int \times \int\)

BuiltinCeilDiv

ceil div \(: \int \times \int \to \int\)

BuiltinCeilMod

ceil mod \(: \int \times \int \to \int\)

BuiltinFloorDiv

floor div \(: \int \times \int \to \int\)

BuiltinFloorMod

floor mod \(: \int \times \int \to \int\)

BuiltinGcd

\(\gcd: \int \times \int \to \int\)

BuiltinLcm

\(\mathbf{lcm}: \int \times \int \to \int\)

BuiltinInt Type

"int" \(: \forall \alpha. \alpha \to \int\)

BuiltinBool Type

"bool" \(: \forall \alpha. \alpha \to \bool\)

BuiltinList Type

"list" \(: \forall \alpha. \list(\alpha) \to \list(\alpha)\)

BuiltinTuple [Type]

"tuple" \(: \forall \alpha_0 \alpha_1 \dots \alpha _ {n - 1}. \tau \to \tau\) where \(\tau = \alpha_0 \times \dots \times \alpha _ {n - 1}\)

BuiltinLen Type

"len" \(: \forall \alpha. \list(\alpha) \to \int\)

BuiltinMap [Type] Type

"map" \(: \forall \alpha_0 \alpha_1 \dots \alpha_n. (\alpha_0 \times \dots \times \alpha _ {n - 1} \to \alpha_n) \times \list(\alpha_0) \times \dots \list(\alpha _ {n - 1}) \to \list(\alpha_n)\)

BuiltinSorted Type

"sorted" \(: \forall \alpha. \list(\alpha) \to \list(\alpha)\)

BuiltinReversed Type

"reversed" \(: \forall \alpha. \list(\alpha) \to \list(\alpha)\)

BuiltinEnumerate Type

"enumerate" \(: \forall \alpha. \list(\alpha) \to \list(\int \times \alpha)\)

BuiltinFilter Type

"filter" \(: \forall \alpha. (\alpha \to \bool) \times \list(\alpha) \to \list(\alpha)\)

BuiltinZip [Type]

"zip" \(: \forall \alpha_0 \alpha_1 \dots \alpha _ {n - 1}. \list(\alpha_0) \times \dots \list(\alpha _ {n - 1}) \to \list(\alpha_0 \times \dots \times \alpha _ {n - 1})\)

BuiltinAll

"all" \(: \list(\bool) \to \bool\)

BuiltinAny

"any" \(: \list(\bool) \to \bool\)

BuiltinSum

"sum" \(: \list(\int) \to \int\)

BuiltinProduct

product \(: \list(\int) \to \int\)

BuiltinRange1

"range" \(: \int \to \list(\int)\)

BuiltinRange2

"range" \(: \int \times \int \to \list(\int)\)

BuiltinRange3

"range" \(: \int \times \int \times \int \to \list(\int)\)

BuiltinMax1 Type

"max" \(: \forall \alpha. \list(\alpha) \to \alpha\)

BuiltinMax Type Int

"max" \(: \forall \alpha. \underbrace{\alpha \times \alpha \times \dots \times \alpha} _ {n ~\text{times}} \to \alpha\)

BuiltinMin1 Type

"min" \(: \forall \alpha. \list(\alpha) \to \alpha\)

BuiltinMin Type Int

"min" \(: \forall \alpha. \underbrace{\alpha \times \alpha \times \dots \times \alpha} _ {n ~\text{times}} \to \alpha\)

BuiltinArgMax Type

\(: \forall \alpha. \list(\alpha) \to \int\)

BuiltinArgMin Type

\(: \forall \alpha. \list(\alpha) \to \int\)

BuiltinFact

factorial \((\lambda n. n!): \int \to \int\)

BuiltinChoose

\((\lambda n r. {} _ n C _ r): \int \times \int \to \int\)

BuiltinPermute

\((\lambda n r. {} _ n P _ r): \int \times \int \to \int\)

BuiltinMultiChoose

\((\lambda n r. {} _ n H _ r): \int \times \int \to \int\)

BuiltinModInv

modulo inverse \((\lambda x m. x^{-1} \bmod m): \int \times \int \to \int\)

BuiltinInput

"input" \(: \epsilon \to \string\)

BuiltinPrint [Type]

"print" \(: \forall \alpha_0 \alpha_1 \dots \alpha _ {n - 1}. \alpha_0 \times \dots \alpha _ {n - 1} \to \epsilon\)

data Attribute Source #

Constructors

UnresolvedAttribute AttributeName 
BuiltinCount Type

"list.count" \(: \forall \alpha. \list(\alpha) \to \alpha \to \int\)

BuiltinIndex Type

"list.index" \(: \forall \alpha. \list(\alpha) \to \alpha \to \int\)

BuiltinCopy Type

"list.copy" \(: \forall \alpha. \list(\alpha) \to \epsilon \to \list(\alpha)\)

BuiltinAppend Type

"list.append" \(: \forall \alpha. \list(\alpha) \to \alpha \to \mathbf{side-effect}\)

BuiltinSplit

"str.split" \(: \forall \alpha. \string \to \epsilon \to \list(\string)\)

exprs

data Expr Source #

Expr represents the exprs of our restricted Python-like language.

\[ \begin{array}{rl} e ::= & e \operatorname{boolop} e \\ \vert & e \operatorname{binop} e \\ \vert & \operatorname{unaryop} e \\ \vert & \lambda x _ \tau x _ \tau \dots x _ \tau. e \\ \vert & \mathbf{if}~ e ~\mathbf{then}~ e ~\mathbf{else}~ e \\ \vert & \lbrack e ~\mathbf{for}~ y ~\mathbf{in}~ e ~(\mathbf{if}~ e)? \rbrack \\ \vert & e \operatorname{cmpop} e \\ \vert & e (e, e, \dots, e) \\ \vert & \operatorname{constant} \\ \vert & e \lbrack e \rbrack \\ \vert & x \\ \vert & \lbrack e, e, \dots, e \rbrack _ \tau \\ \vert & e \lbrack e? \colon e? \colon e? \rbrack \\ \end{array} \]

Instances

Instances details
Eq Expr Source # 
Instance details

Defined in Jikka.RestrictedPython.Language.Expr

Methods

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

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

Ord Expr Source # 
Instance details

Defined in Jikka.RestrictedPython.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.RestrictedPython.Language.Expr

Show Expr Source # 
Instance details

Defined in Jikka.RestrictedPython.Language.Expr

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

statements

data Target Source #

Target represents the lvalue of our restricted Python-like language.

\[ \begin{array}{rl} y ::= & y \lbrack e \rbrack \\ \vert & x \\ \vert & (y, y, \dots, y) \\ \end{array} \]

data Statement Source #

Statement represents the statements of our restricted Python-like language. They appear in bodies of def.

\[ \begin{array}{rl} \mathrm{stmt} ::= & \mathbf{return}~ e \\ \vert & y \operatorname{binop} = e \\ \vert & y _ \tau := e \\ \vert & \mathbf{for}~ y ~\mathbf{in}~ e \colon\quad \mathrm{stmt}; \mathrm{stmt}; \dots; \mathrm{stmt} \\ \vert & \mathbf{if}~ e \colon\quad \mathrm{stmt}; \mathrm{stmt}; \dots; \mathrm{stmt};\quad \mathbf{else}\colon\quad \mathrm{stmt}; \mathrm{stmt}; \dots; \mathrm{stmt} \\ \vert & \mathbf{assert}~ e \\ \end{array} \]

pattern Append :: Maybe Loc -> Type -> Expr' -> Expr' -> Statement Source #

data ToplevelStatement Source #

TopLevelStatement represents the statements of our restricted Python-like language. They appear in the toplevel of programs.

\[ \begin{array}{rl} \mathrm{tlstmt} ::= & x _ \tau := e \\ \vert & \mathbf{def}~ x (x _ \tau, x _ \tau, \dots, x _ \tau) \to \tau \colon\quad \mathrm{stmt}; \mathrm{stmt}; \dots; \mathrm{stmt} \\ \vert & \mathbf{assert}~ e \\ \end{array} \]

type Program = [ToplevelStatement] Source #

Program represents the programs of our restricted Python-like language.

\[ \begin{array}{rl} \mathrm{prog} ::= & \mathrm{tlstmt}; \mathrm{tlstmt}; \dots; \mathrm{tlstmt} \\ \end{array} \]