Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Foundation of Lorentz development.
Synopsis
- newtype (inp :: [Type]) :-> (out :: [Type]) = LorentzInstr {
- unLorentzInstr :: RemFail Instr (ToTs inp) (ToTs out)
- type (%>) = (:->)
- type (&) (a :: Type) (b :: [Type]) = a ': b
- (#) :: (a :-> b) -> (b :-> c) -> a :-> c
- pattern I :: Instr (ToTs inp) (ToTs out) -> inp :-> out
- pattern FI :: (forall out'. Instr (ToTs inp) out') -> inp :-> out
- iGenericIf :: (forall s'. Instr (ToTs a) s' -> Instr (ToTs b) s' -> Instr (ToTs c) s') -> (a :-> s) -> (b :-> s) -> c :-> s
- iAnyCode :: (inp :-> out) -> Instr (ToTs inp) (ToTs out)
- iNonFailingCode :: HasCallStack => (inp :-> out) -> Instr (ToTs inp) (ToTs out)
- iMapAnyCode :: (forall o'. Instr (ToTs i1) o' -> Instr (ToTs i2) o') -> (i1 :-> o) -> i2 :-> o
- iForceNotFail :: (i :-> o) -> i :-> o
- parseLorentzValue :: forall v. KnownValue v => MichelsonSource -> Text -> Either ParseLorentzError v
- transformStringsLorentz :: Bool -> (MText -> MText) -> (inp :-> out) -> inp :-> out
- transformBytesLorentz :: Bool -> (ByteString -> ByteString) -> (inp :-> out) -> inp :-> out
- optimizeLorentz :: (inp :-> out) -> inp :-> out
- optimizeLorentzWithConf :: OptimizerConf -> (inp :-> out) -> inp :-> out
- class MapLorentzInstr instr where
- mapLorentzInstr :: (forall i o. (i :-> o) -> i :-> o) -> instr -> instr
- type ContractOut st = '[([Operation], st)]
- newtype ContractCode cp st = ContractCode {
- unContractCode :: '[(cp, st)] :-> ContractOut st
- mkContractCode :: (IsNotInView => '[(cp, st)] :-> ContractOut st) -> ContractCode cp st
- class IsNotInView
- data SomeContractCode where
- SomeContractCode :: (NiceParameter cp, NiceStorage st) => ContractCode cp st -> SomeContractCode
- type ViewCode arg st ret = '[(arg, st)] :-> '[ret]
- data Contract cp st vd = (NiceParameter cp, NiceStorage st, NiceViewsDescriptor vd) => Contract {
- cMichelsonContract :: Contract (ToT cp) (ToT st)
- cDocumentedCode :: ~(ContractCode cp st)
- toMichelsonContract :: Contract cp st vd -> Contract (ToT cp) (ToT st)
- type Fn a b = '[a] :-> '[b]
Documentation
newtype (inp :: [Type]) :-> (out :: [Type]) infixr 1 Source #
Alias for instruction which hides inner types representation via T
.
LorentzInstr | |
|
Instances
(CanCastTo (ZippedStack i1) (ZippedStack i2), CanCastTo (ZippedStack o1) (ZippedStack o2)) => CanCastTo (i1 :-> o1 :: Type) (i2 :-> o2 :: Type) Source # | |
Monoid (s :-> s) Source # | |
Semigroup (s :-> s) Source # | |
Show (inp :-> out) Source # | |
NFData (i :-> o) Source # | |
Defined in Lorentz.Base | |
Buildable (inp :-> out) Source # | |
Defined in Lorentz.Base | |
Eq (inp :-> out) Source # | |
(HasAnnotation (ZippedStack i), HasAnnotation (ZippedStack o)) => HasAnnotation (i :-> o) Source # | |
Defined in Lorentz.Zip getAnnotation :: FollowEntrypointFlag -> Notes (ToT (i :-> o)) Source # | |
MapLorentzInstr (i :-> o) Source # | |
Defined in Lorentz.Base | |
HasRPCRepr (inp :-> out) | |
Defined in Lorentz.Zip type AsRPC (inp :-> out) | |
ContainsDoc (i :-> o) Source # | |
Defined in Lorentz.Doc buildDocUnfinalized :: (i :-> o) -> ContractDoc # | |
ContainsUpdateableDoc (i :-> o) Source # | |
Defined in Lorentz.Doc modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> (i :-> o) -> i :-> o # | |
RenderDoc (inp :-> out) Source # | |
Defined in Lorentz.Base | |
(WellTypedToT (ZippedStack inp), WellTypedToT (ZippedStack out), ZipInstr inp, ZipInstr out) => IsoValue (inp :-> out) Source # | |
(i ~ arg, o ~ argl, o ~ argr, r ~ Bool, outb ~ out) => IsCondition (Expr i o r) arg argl argr outb out Source # | An expression producing |
Defined in Lorentz.Expr | |
type AsRPC (inp :-> out) | |
Defined in Lorentz.Zip | |
type ToT (inp :-> out) Source # | |
Defined in Lorentz.Zip |
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).
iGenericIf :: (forall s'. Instr (ToTs a) s' -> Instr (ToTs b) s' -> Instr (ToTs c) s') -> (a :-> s) -> (b :-> s) -> c :-> s 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.
mapLorentzInstr :: (forall i o. (i :-> o) -> i :-> o) -> instr -> instr Source #
Modify all the code under given entity.
Instances
MapLorentzInstr (i :-> o) Source # | |
Defined in Lorentz.Base |
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.
ContractCode | |
|
Instances
Show (ContractCode cp st) Source # | |
Defined in Lorentz.Base showsPrec :: Int -> ContractCode cp st -> ShowS # show :: ContractCode cp st -> String # showList :: [ContractCode cp st] -> ShowS # | |
NFData (ContractCode cp st) Source # | |
Defined in Lorentz.Base rnf :: ContractCode cp st -> () # | |
Eq (ContractCode cp st) Source # | |
Defined in Lorentz.Base (==) :: ContractCode cp st -> ContractCode cp st -> Bool # (/=) :: ContractCode cp st -> ContractCode cp st -> Bool # | |
ContainsDoc (ContractCode i o) Source # | |
Defined in Lorentz.Doc buildDocUnfinalized :: ContractCode i o -> ContractDoc # | |
ContainsUpdateableDoc (ContractCode i o) Source # | |
Defined in Lorentz.Doc modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> ContractCode i o -> ContractCode i o # |
mkContractCode :: (IsNotInView => '[(cp, st)] :-> ContractOut st) -> ContractCode cp st Source #
A helper to construct ContractCode
that provides IsNotInView
constraint.
class IsNotInView #
Instances
(TypeError ('Text "Not allowed on the top level of a view") :: Constraint) => IsNotInView | |
Defined in Morley.Michelson.Typed.Contract |
data SomeContractCode where Source #
SomeContractCode :: (NiceParameter cp, NiceStorage st) => ContractCode cp st -> SomeContractCode |
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.
(NiceParameter cp, NiceStorage st, NiceViewsDescriptor vd) => Contract | |
|
Instances
Show (Contract cp st vd) Source # | |
NFData (Contract cp st vd) Source # | |
Defined in Lorentz.Base | |
Eq (Contract cp st vd) Source # | |
ToExpression (Contract cp st vd) Source # | |
Defined in Lorentz.Base toExpression :: Contract cp st vd -> Expression | |
ContainsDoc (Contract cp st vd) Source # | |
Defined in Lorentz.Doc buildDocUnfinalized :: Contract cp st vd -> ContractDoc # | |
ContainsUpdateableDoc (Contract cp st vd) Source # | |
Defined in Lorentz.Doc 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.