lorentz-0.6.1: EDSL for the Michelson Language
Safe HaskellNone
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 #

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

Defined in Lorentz.Base

Methods

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

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

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

Defined in Lorentz.Base

Methods

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

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

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

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 #

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 #

Each '[Typeable :: [Type] -> Constraint, ReifyList TypeHasDoc] '[i, o] => TypeHasDoc (i :-> o) Source # 
Instance details

Defined in Lorentz.Doc

Associated Types

type TypeDocFieldDescriptions (i :-> o) :: FieldDescriptions #

Methods

typeDocName :: Proxy (i :-> o) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (i :-> o) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (i :-> o) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (i :-> o) #

typeDocMichelsonRep :: TypeDocMichelsonRep (i :-> o) #

(WellTypedToT (ZippedStack inp), WellTypedToT (ZippedStack out), ZipInstr inp, ZipInstr out) => IsoValue (inp :-> out) Source # 
Instance details

Defined in Lorentz.Zip

Associated Types

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

Methods

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

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

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

Defined in Lorentz.Zip

Methods

getAnnotation :: FollowEntrypointFlag -> Notes (ToT (i :-> o)) Source #

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 #

(i ~ (MUStore oldTempl newTempl diff touched ': s), o ~ (MUStore oldTempl newTempl ('[] :: [DiffItem]) touched ': s), RequireEmptyDiff diff) => MigrationFinishCheckPosition (i :-> o) Source #

This version can be used in mkUStoreMigration.

Instance details

Defined in Lorentz.UStore.Migration.Blocks

Methods

migrationFinish :: i :-> o Source #

type TypeDocFieldDescriptions (i :-> o) Source # 
Instance details

Defined in Lorentz.Doc

type TypeDocFieldDescriptions (i :-> o) = '[] :: [(Symbol, (Maybe Symbol, [(Symbol, Symbol)]))]
type ToT (inp :-> out) Source # 
Instance details

Defined in Lorentz.Zip

type ToT (inp :-> out) = 'TLambda (ToT (ZippedStack inp)) (ToT (ZippedStack 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 #

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

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

Version of # which performs some optimizations immediately.

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 #

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.

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 (UStoreMigration os ns) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

Methods

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 #

type Lambda i o = '[i] :-> '[o] Source #