lorentz-0.15.1: EDSL for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Lorentz.Base

Description

Foundation of Lorentz development.

Synopsis

Documentation

newtype (inp :: [Type]) :-> (out :: [Type]) infixr 1 Source #

Alias for instruction which hides inner types representation via T.

Constructors

LorentzInstr 

Fields

Instances

Instances details
(CanCastTo (ZippedStack i1) (ZippedStack i2), CanCastTo (ZippedStack o1) (ZippedStack o2)) => CanCastTo (i1 :-> o1 :: Type) (i2 :-> o2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (i1 :-> o1) -> Proxy (i2 :-> o2) -> () Source #

Monoid (s :-> s) Source # 
Instance details

Defined in Lorentz.Base

Methods

mempty :: s :-> s #

mappend :: (s :-> s) -> (s :-> s) -> s :-> s #

mconcat :: [s :-> s] -> s :-> s #

Semigroup (s :-> s) Source # 
Instance details

Defined in Lorentz.Base

Methods

(<>) :: (s :-> s) -> (s :-> s) -> s :-> s #

sconcat :: NonEmpty (s :-> s) -> s :-> s #

stimes :: Integral b => b -> (s :-> s) -> s :-> s #

Show (inp :-> out) Source # 
Instance details

Defined in Lorentz.Base

Methods

showsPrec :: Int -> (inp :-> out) -> ShowS #

show :: (inp :-> out) -> String #

showList :: [inp :-> out] -> ShowS #

NFData (i :-> o) Source # 
Instance details

Defined in Lorentz.Base

Methods

rnf :: (i :-> o) -> () #

Buildable (inp :-> out) Source # 
Instance details

Defined in Lorentz.Base

Methods

build :: (inp :-> out) -> Builder #

Eq (inp :-> out) Source # 
Instance details

Defined in Lorentz.Base

Methods

(==) :: (inp :-> out) -> (inp :-> out) -> Bool #

(/=) :: (inp :-> out) -> (inp :-> out) -> Bool #

NoLambdaCodeIsomorphismError => HasAnnotation (i :-> o) Source # 
Instance details

Defined in Lorentz.Base

MapLorentzInstr (i :-> o) Source # 
Instance details

Defined in Lorentz.Base

Methods

mapLorentzInstr :: (forall (i0 :: [Type]) (o0 :: [Type]). (i0 :-> o0) -> i0 :-> o0) -> (i :-> o) -> i :-> o Source #

ContainsDoc (i :-> o) Source # 
Instance details

Defined in Lorentz.Doc

ContainsUpdateableDoc (i :-> o) Source # 
Instance details

Defined in Lorentz.Doc

Methods

modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> (i :-> o) -> i :-> o #

RenderDoc (inp :-> out) Source # 
Instance details

Defined in Lorentz.Base

Methods

renderDoc :: RenderContext -> (inp :-> out) -> Doc

isRenderable :: (inp :-> out) -> Bool

(NoLambdaCodeIsomorphismError, WellTyped (LorentzCodeIsNotIsomorphicToMichelsonValues :: T)) => IsoValue (inp :-> out) Source # 
Instance details

Defined in Lorentz.Base

Associated Types

type ToT (inp :-> out) :: T #

Methods

toVal :: (inp :-> out) -> Value (ToT (inp :-> out)) #

fromVal :: Value (ToT (inp :-> out)) -> inp :-> out #

(i ~ arg, o ~ argl, o ~ argr, r ~ Bool, outb ~ out) => IsCondition (Expr i o r) arg argl argr outb out Source #

An expression producing Bool can be placed as condition to 'if'.

Instance details

Defined in Lorentz.Expr

Methods

ifThenElse :: Expr i o r -> (argl :-> outb) -> (argr :-> outb) -> arg :-> out Source #

type ToT (inp :-> out) Source # 
Instance details

Defined in Lorentz.Base

type ToT (inp :-> out)

type (%>) = (:->) infixr 1 Source #

Alias for :->, seems to make signatures more readable sometimes.

Let's someday decide which one of these two should remain.

type (&) (a :: Type) (b :: [Type]) = a ': b infixr 2 Source #

An alias for ':.

We discourage its use as this hinders reading error messages (the compiler inserts unnecessary parentheses and indentation).

(#) :: (a :-> b) -> (b :-> c) -> a :-> c infixl 8 Source #

Function composition for instructions.

Note that, unlike Morley's :# operator, (#) is left-associative.

pattern I :: Instr (ToTs inp) (ToTs out) -> inp :-> out Source #

pattern FI :: (forall out'. Instr (ToTs inp) out') -> inp :-> out Source #

iGenericIf :: (forall s'. Instr (ToTs a) s' -> Instr (ToTs b) s' -> Instr (ToTs c) s') -> (a :-> s) -> (b :-> s) -> c :-> s Source #

iAnyCode :: (inp :-> out) -> Instr (ToTs inp) (ToTs out) Source #

iNonFailingCode :: HasCallStack => (inp :-> out) -> Instr (ToTs inp) (ToTs out) Source #

iMapAnyCode :: (forall o'. Instr (ToTs i1) o' -> Instr (ToTs i2) o') -> (i1 :-> o) -> i2 :-> o Source #

iForceNotFail :: (i :-> o) -> i :-> o Source #

parseLorentzValue :: forall v. KnownValue v => MichelsonSource -> Text -> Either ParseLorentzError v Source #

Parse textual representation of a Michelson value and turn it into corresponding Haskell value.

Note: it won't work in some complex cases, e. g. if there is a lambda which uses an instruction which depends on current contract's type. Obviously it can not work, because we don't have any information about a contract to which this value belongs (there is no such contract at all).

transformStringsLorentz :: Bool -> (MText -> MText) -> (inp :-> out) -> inp :-> out Source #

Lorentz version of transformStrings.

transformBytesLorentz :: Bool -> (ByteString -> ByteString) -> (inp :-> out) -> inp :-> out Source #

Lorentz version of transformBytes.

optimizeLorentz :: (inp :-> out) -> inp :-> out Source #

optimizeLorentzWithConf :: OptimizerConf -> (inp :-> out) -> inp :-> out Source #

class MapLorentzInstr instr where Source #

Applicable for wrappers over Lorentz code.

Methods

mapLorentzInstr :: (forall i o. (i :-> o) -> i :-> o) -> instr -> instr Source #

Modify all the code under given entity.

Instances

Instances details
MapLorentzInstr (i :-> o) Source # 
Instance details

Defined in Lorentz.Base

Methods

mapLorentzInstr :: (forall (i0 :: [Type]) (o0 :: [Type]). (i0 :-> o0) -> i0 :-> o0) -> (i :-> o) -> i :-> o Source #

MapLorentzInstr (WrappedLambda inp out) Source # 
Instance details

Defined in Lorentz.Lambda

Methods

mapLorentzInstr :: (forall (i :: [Type]) (o :: [Type]). (i :-> o) -> i :-> o) -> WrappedLambda inp out -> WrappedLambda inp out Source #

type ContractOut st = '[([Operation], st)] Source #

newtype ContractCode cp st Source #

Wrap contract code capturing the constraint that the code is not inside a view.

Constructors

ContractCode 

Fields

Instances

Instances details
Show (ContractCode cp st) Source # 
Instance details

Defined in Lorentz.Base

Methods

showsPrec :: Int -> ContractCode cp st -> ShowS #

show :: ContractCode cp st -> String #

showList :: [ContractCode cp st] -> ShowS #

NFData (ContractCode cp st) Source # 
Instance details

Defined in Lorentz.Base

Methods

rnf :: ContractCode cp st -> () #

Eq (ContractCode cp st) Source # 
Instance details

Defined in Lorentz.Base

Methods

(==) :: ContractCode cp st -> ContractCode cp st -> Bool #

(/=) :: ContractCode cp st -> ContractCode cp st -> Bool #

ContainsDoc (ContractCode i o) Source # 
Instance details

Defined in Lorentz.Doc

ContainsUpdateableDoc (ContractCode i o) Source # 
Instance details

Defined in Lorentz.Doc

mkContractCode :: (IsNotInView => '[(cp, st)] :-> ContractOut st) -> ContractCode cp st Source #

A helper to construct ContractCode that provides IsNotInView constraint.

class IsNotInView #

Instances

Instances details
(TypeError ('Text "Not allowed on the top level of a view") :: Constraint) => IsNotInView 
Instance details

Defined in Morley.Michelson.Typed.Contract

type ViewCode arg st ret = '[(arg, st)] :-> '[ret] Source #

data Contract cp st vd Source #

Compiled Lorentz contract.

Note, that the views argument (views descriptor) is added comparing to the Michelson. In Michelson, ability to call a view is fully checked at runtime, but in Lorentz we want to make calls safer at compile-time.

Constructors

(NiceParameter cp, NiceStorage st, NiceViewsDescriptor vd) => Contract 

Fields

  • cMichelsonContract :: Contract (ToT cp) (ToT st)

    Ready contract code.

  • cDocumentedCode :: ~(ContractCode cp st)

    Contract that contains documentation.

    We have to keep it separately, since optimizer is free to destroy documentation blocks. Also, it is not ContractDoc but Lorentz code because the latter is easier to modify.

Instances

Instances details
Show (Contract cp st vd) Source # 
Instance details

Defined in Lorentz.Base

Methods

showsPrec :: Int -> Contract cp st vd -> ShowS #

show :: Contract cp st vd -> String #

showList :: [Contract cp st vd] -> ShowS #

NFData (Contract cp st vd) Source # 
Instance details

Defined in Lorentz.Base

Methods

rnf :: Contract cp st vd -> () #

Eq (Contract cp st vd) Source # 
Instance details

Defined in Lorentz.Base

Methods

(==) :: Contract cp st vd -> Contract cp st vd -> Bool #

(/=) :: Contract cp st vd -> Contract cp st vd -> Bool #

ToExpression (Contract cp st vd) Source # 
Instance details

Defined in Lorentz.Base

Methods

toExpression :: Contract cp st vd -> Expression

ContainsDoc (Contract cp st vd) Source # 
Instance details

Defined in Lorentz.Doc

ContainsUpdateableDoc (Contract cp st vd) Source # 
Instance details

Defined in Lorentz.Doc

Methods

modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> Contract cp st vd -> Contract cp st vd #

toMichelsonContract :: Contract cp st vd -> Contract (ToT cp) (ToT st) Source #

Demote Lorentz Contract to Michelson typed Contract.

type Fn a b = '[a] :-> '[b] Source #

An instruction sequence taking one stack element as input and returning one stack element as output. Essentially behaves as a Michelson lambda without any additional semantical meaning.

The reason for this distinction is Michelson lambdas allow instructions inside them that might be forbidden in the outer scope. This type doesn't add any such conditions.