Jikka-5.0.11.2: 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.Core.Language.Expr

Description

Expr module has the basic data types for our core language. They are similar to the GHC Core language.

Synopsis

Documentation

newtype VarName Source #

Constructors

VarName String 

Instances

Instances details
Eq VarName Source # 
Instance details

Defined in Jikka.Core.Language.Expr

Methods

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

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

Ord VarName Source # 
Instance details

Defined in Jikka.Core.Language.Expr

Read VarName Source # 
Instance details

Defined in Jikka.Core.Language.Expr

Show VarName Source # 
Instance details

Defined in Jikka.Core.Language.Expr

IsString VarName Source # 
Instance details

Defined in Jikka.Core.Language.Expr

Methods

fromString :: String -> VarName #

data Type Source #

Type represents the types of our core language. This is similar to the Type of GHC Core. See also commentarycompilertype-type.

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

Instances

Instances details
Eq Type Source # 
Instance details

Defined in Jikka.Core.Language.Expr

Methods

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

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

Ord Type Source # 
Instance details

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

Show Type Source # 
Instance details

Defined in Jikka.Core.Language.Expr

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

data Builtin Source #

TODO: What is the difference between Literal and Builtin?

Constructors

Negate

\(: \int \to \int\)

Plus

\(: \int \to \int \to \int\)

Minus

\(: \int \to \int \to \int\)

Mult

\(: \int \to \int \to \int\)

FloorDiv

\(: \int \to \int \to \int\)

FloorMod

\(: \int \to \int \to \int\)

CeilDiv

\(: \int \to \int \to \int\)

CeilMod

\(: \int \to \int \to \int\)

Pow

\(: \int \to \int \to \int\)

Abs

\(: \int \to \int\)

Gcd

\(: \int \to \int \to \int\)

Lcm

\(: \int \to \int \to \int\)

Min2 Type

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

Max2 Type

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

Iterate Type

iterated application \((\lambda k f x. f^k(x)): \forall \alpha. \int \to (\alpha \to \alpha) \to \alpha \to \alpha\)

Not

\(: \bool \to \bool\)

And

\(: \bool \to \bool \to \bool\)

Or

\(: \bool \to \bool \to \bool\)

Implies

\(: \bool \to \bool \to \bool\)

If Type

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

BitNot

\(: \int \to \int\)

BitAnd

\(: \int \to \int \to \int\)

BitOr

\(: \int \to \int \to \int\)

BitXor

\(: \int \to \int \to \int\)

BitLeftShift

\(: \int \to \int \to \int\)

BitRightShift

\(: \int \to \int \to \int\)

MatAp Int Int

matrix application \(: \int^{H \times W} \to \int^W \to \int^H\)

MatZero Int

zero matrix \(: \to \int^{n \times n}\)

MatOne Int

unit matrix \(: \to \int^{n \times n}\)

MatAdd Int Int

matrix addition \(: \int^{H \times W} \to \int^{H \times W} \to \int^{H \times W}\)

MatMul Int Int Int

matrix multiplication \(: \int^{H \times n} \to \int^{n \times W} \to \int^{H \times W}\)

MatPow Int

matrix power \(: \int^{n \times n} \to \int \to \int^{n \times n}\)

VecFloorMod Int

vector point-wise floor-mod \(: \int^{n} \to \int \to \int^{n}\)

MatFloorMod Int Int

matrix point-wise floor-mod \(: \int^{H \times W} \to \int \to \int^{H \times W}\)

ModNegate

\(: \int \to \int \to \int\)

ModPlus

\(: \int \to \int \to \int \to \int\)

ModMinus

\(: \int \to \int \to \int \to \int\)

ModMult

\(: \int \to \int \to \int \to \int\)

ModInv

\(: \int \to \int \to \int\)

ModPow

\(: \int \to \int \to \int \to \int\)

ModMatAp Int Int

matrix application \(: \int^{H \times W} \to \int^W \to \int \to \int^H\)

ModMatAdd Int Int

matrix addition \(: \int^{H \times W} \to \int^{H \times W} \to \int \to \int^{H \times W}\)

ModMatMul Int Int Int

matrix multiplication \(: \int^{H \times n} \to \int^{n \times W} \to \int \to \int^{H \times W}\)

ModMatPow Int

matrix power \(: \int^{n \times n} \to \int \to \int^{n \times n}\)

Cons Type

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

Snoc Type

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

Foldl Type Type

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

Scanl Type Type

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

Build Type

\(\lambda f a n.\) repeat a <- snoc a (f a) n times \(: \forall \alpha. (\list(\alpha) \to \alpha) \to \list(\alpha) \to \int \to \list(\alpha)\)

Len Type

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

Map Type Type

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

Filter Type

\(: \forall \alpha \beta. (\alpha \to \bool) \to \list(\alpha) \to \list(\beta)\)

At Type

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

SetAt Type

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

Elem Type

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

Sum

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

Product

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

ModSum

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

ModProduct

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

Min1 Type

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

Max1 Type

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

ArgMin Type

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

ArgMax Type

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

All

\(: \list(\bool) \to \bool\)

Any

\(: \list(\bool) \to \bool\)

Sorted Type

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

Reversed Type

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

Range1

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

Range2

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

Range3

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

Tuple [Type]

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

Proj [Type] Int

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

LessThan Type

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

LessEqual Type

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

GreaterThan Type

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

GreaterEqual Type

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

Equal Type

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

NotEqual Type

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

Fact

\(: \int \to \int\)

Choose

\(: \int \to \int \to \int\)

Permute

\(: \int \to \int \to \int\)

MultiChoose

\(: \int \to \int \to \int\)

ConvexHullTrickInit

\(: \mathrm{convex-hull-trick}\)

ConvexHullTrickGetMin

\(: \mathrm{convex-hull-trick} \to \int \to \int\)

ConvexHullTrickInsert

\(: \mathrm{convex-hull-trick} \to \int \to \int \to \mathrm{convex-hull-trick}\)

SegmentTreeInitList Semigroup'

\(: \forall S. \list(S) \to \mathrm{segment-tree}(S)\)

SegmentTreeGetRange Semigroup'

\(: \forall S. \mathrm{segment-tree}(S) \to \int \to \int \to S\)

SegmentTreeSetPoint Semigroup'

\(: \forall S. \mathrm{segment-tree}(S) \to \int \to S \to \mathrm{segment-tree}(S)\)

Instances

Instances details
Eq Builtin Source # 
Instance details

Defined in Jikka.Core.Language.Expr

Methods

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

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

Ord Builtin Source # 
Instance details

Defined in Jikka.Core.Language.Expr

Read Builtin Source # 
Instance details

Defined in Jikka.Core.Language.Expr

Show Builtin Source # 
Instance details

Defined in Jikka.Core.Language.Expr

data Literal Source #

Constructors

LitBuiltin Builtin 
LitInt Integer

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

LitBool Bool

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

LitNil Type

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

LitBottom Type String

\(: \bot : \forall \alpha. \alpha\). The second argument is its error message.

Instances

Instances details
Eq Literal Source # 
Instance details

Defined in Jikka.Core.Language.Expr

Methods

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

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

Ord Literal Source # 
Instance details

Defined in Jikka.Core.Language.Expr

Read Literal Source # 
Instance details

Defined in Jikka.Core.Language.Expr

Show Literal Source # 
Instance details

Defined in Jikka.Core.Language.Expr

data Expr Source #

Expr represents the exprs of our core language. This is similar to the Expr of GHC Core. See also commentarycompilercore-syn-type.

\[ \begin{array}{rl} e ::= & x \\ \vert & \mathrm{literal}\ldots \\ \vert & e_0(e_1, e_2, \dots, e_n) \\ \vert & \lambda ~ x_0\colon \tau_0, x_1\colon \tau_1, \dots, x_{n-1}\colon \tau_{n-1}. ~ e \\ \vert & \mathbf{let} ~ x\colon \tau = e_1 ~ \mathbf{in} ~ e_2 \end{array} \]

Constructors

Var VarName 
Lit Literal 
App Expr Expr

The functions are not curried.

Lam VarName Type Expr

The lambdas are also not curried.

Let VarName Type Expr Expr

This "let" is not recursive.

Instances

Instances details
Eq Expr Source # 
Instance details

Defined in Jikka.Core.Language.Expr

Methods

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

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

Ord Expr Source # 
Instance details

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

Show Expr Source # 
Instance details

Defined in Jikka.Core.Language.Expr

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

pattern Fun2Ty :: Type -> Type -> Type -> Type Source #

pattern Fun3Ty :: Type -> Type -> Type -> Type -> Type Source #

pattern Fun1STy :: Type -> Type Source #

pattern Fun2STy :: Type -> Type Source #

pattern Fun3STy :: Type -> Type Source #

pattern FunLTy :: Type -> Type Source #

pattern UnitTy :: Type Source #

pattern LitInt' :: Integer -> Expr Source #

pattern Lit0 :: Expr Source #

pattern Lit1 :: Expr Source #

pattern Lit2 :: Expr Source #

pattern LitMinus1 :: Expr Source #

pattern LitBool' :: Bool -> Expr Source #

pattern LitTrue :: Expr Source #

pattern LitFalse :: Expr Source #

pattern Builtin :: Builtin -> Expr Source #

pattern App2 :: Expr -> Expr -> Expr -> Expr Source #

pattern App3 :: Expr -> Expr -> Expr -> Expr -> Expr Source #

pattern App4 :: Expr -> Expr -> Expr -> Expr -> Expr -> Expr Source #

pattern AppBuiltin :: Builtin -> Expr -> Expr Source #

pattern AppBuiltin2 :: Builtin -> Expr -> Expr -> Expr Source #

pattern AppBuiltin3 :: Builtin -> Expr -> Expr -> Expr -> Expr Source #

pattern Lam2 :: VarName -> Type -> VarName -> Type -> Expr -> Expr Source #

pattern Lam3 :: VarName -> Type -> VarName -> Type -> VarName -> Type -> Expr -> Expr Source #

pattern LamId :: VarName -> Type -> Expr Source #

data ToplevelExpr Source #

ToplevelExpr is the toplevel exprs. In our core, "let rec" is allowed only on the toplevel.

\[ \begin{array}{rl} \mathrm{tle} ::= & e \\ \vert & \mathbf{let}~ x: \tau = e ~\mathbf{in}~ \mathrm{tle} \\ \vert & \mathbf{let~rec}~ x(x: \tau, x: \tau, \dots, x: \tau): \tau = e ~\mathbf{in}~ \mathrm{tle} \end{array} \]