Safe Haskell | None |
---|---|
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
- (##) :: (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
- iWithVarAnnotations :: HasCallStack => [Text] -> (inp :-> out) -> inp :-> out
- parseLorentzValue :: forall v. KnownValue v => 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)]
- type ContractCode cp st = '[(cp, st)] :-> ContractOut st
- data SomeContractCode where
- SomeContractCode :: (NiceParameterFull cp, NiceStorage st) => ContractCode cp st -> SomeContractCode
- type Lambda i o = '[i] :-> '[o]
Documentation
newtype (inp :: [Type]) :-> (out :: [Type]) infixr 1 Source #
Alias for instruction which hides inner types representation via T
.
LorentzInstr | |
|
Instances
type (%>) = (:->) infixr 1 Source #
Alias for :->
, seems to make signatures more readable sometimes.
Let's someday decide which one of these two should remain.
(##) :: (a :-> b) -> (b :-> c) -> a :-> c Source #
Version of #
which performs some optimizations immediately.
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 #
iWithVarAnnotations :: HasCallStack => [Text] -> (inp :-> out) -> inp :-> out Source #
Wrap Lorentz instruction with variable annotations, annots
list has to be
non-empty, otherwise this function raises an error.
parseLorentzValue :: forall v. KnownValue v => 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 | |
MapLorentzInstr (UStoreMigration os ns) Source # | |
Defined in Lorentz.UStore.Migration.Base mapLorentzInstr :: (forall (i :: [Type]) (o :: [Type]). (i :-> o) -> i :-> o) -> UStoreMigration os ns -> UStoreMigration os ns Source # |
type ContractOut st = '[([Operation], st)] Source #
type ContractCode cp st = '[(cp, st)] :-> ContractOut st Source #
data SomeContractCode where Source #
SomeContractCode :: (NiceParameterFull cp, NiceStorage st) => ContractCode cp st -> SomeContractCode |