morley-1.19.0: Developer tools for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Tezos.Core

Description

Core primitive Tezos types.

Synopsis

Mutez

newtype Mutez Source #

Mutez is a wrapper over integer data type. 1 mutez is 1 token (μTz).

The constructor is marked Unsafe since GHC does not warn on overflowing literals (exceeding custom Word63 type bounds), thus the resultant Mutez value may get truncated silently.

>>> UnsafeMutez 9223372036854775809
UnsafeMutez {unMutez = 1}

Constructors

UnsafeMutez 

Fields

Instances

Instances details
FromJSON Mutez Source # 
Instance details

Defined in Morley.Tezos.Core

ToJSON Mutez Source # 
Instance details

Defined in Morley.Tezos.Core

Bounded Mutez Source # 
Instance details

Defined in Morley.Tezos.Core

Enum Mutez Source # 
Instance details

Defined in Morley.Tezos.Core

Generic Mutez Source # 
Instance details

Defined in Morley.Tezos.Core

Associated Types

type Rep Mutez :: Type -> Type #

Methods

from :: Mutez -> Rep Mutez x #

to :: Rep Mutez x -> Mutez #

Show Mutez Source # 
Instance details

Defined in Morley.Tezos.Core

Methods

showsPrec :: Int -> Mutez -> ShowS #

show :: Mutez -> String #

showList :: [Mutez] -> ShowS #

NFData Mutez Source # 
Instance details

Defined in Morley.Tezos.Core

Methods

rnf :: Mutez -> () #

Buildable Mutez Source # 
Instance details

Defined in Morley.Tezos.Core

Methods

build :: Mutez -> Builder #

Eq Mutez Source # 
Instance details

Defined in Morley.Tezos.Core

Methods

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

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

Ord Mutez Source # 
Instance details

Defined in Morley.Tezos.Core

Methods

compare :: Mutez -> Mutez -> Ordering #

(<) :: Mutez -> Mutez -> Bool #

(<=) :: Mutez -> Mutez -> Bool #

(>) :: Mutez -> Mutez -> Bool #

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

max :: Mutez -> Mutez -> Mutez #

min :: Mutez -> Mutez -> Mutez #

HasRPCRepr Mutez Source # 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC Mutez Source #

TypeHasDoc Mutez Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

IsoValue Mutez Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Mutez :: T Source #

HasCLReader Mutez Source # 
Instance details

Defined in Morley.Tezos.Core

type Rep Mutez Source # 
Instance details

Defined in Morley.Tezos.Core

type Rep Mutez = D1 ('MetaData "Mutez" "Morley.Tezos.Core" "morley-1.19.0-inplace" 'True) (C1 ('MetaCons "UnsafeMutez" 'PrefixI 'True) (S1 ('MetaSel ('Just "unMutez") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word63)))
type AsRPC Mutez Source # 
Instance details

Defined in Morley.AsRPC

type TypeDocFieldDescriptions Mutez Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT Mutez Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT Mutez = 'TMutez

tz :: QuasiQuoter Source #

Quotes a Mutez value.

The value is in XTZ, i.e. 1e6 Mutez, with optional suffix representing a unit:

  • k, kilo -- 1000 XTZ
  • M, Mega, mega -- 1000000 XTZ
  • m, milli -- 0.001 XTZ
  • u, μ, micro -- 0.000001 XTZ

This is the safest and recommended way to create Mutez from a numeric literal.

The suffix can be separated from the number by whitespace. You can also use underscores as a delimiter (those will be ignored), and scientific notation, e.g. 123.456e6. Note that if the scientific notation represents a mutez fraction, that is a compile-time error.

>>> [tz|123|]
UnsafeMutez {unMutez = 123000000}
>>> [tz|123k|]
UnsafeMutez {unMutez = 123000000000}
>>> [tz|123 kilo|]
UnsafeMutez {unMutez = 123000000000}
>>> [tz|123M|]
UnsafeMutez {unMutez = 123000000000000}
>>> [tz|123 Mega|]
UnsafeMutez {unMutez = 123000000000000}
>>> [tz|123 mega|]
UnsafeMutez {unMutez = 123000000000000}
>>> [tz|123e6|]
UnsafeMutez {unMutez = 123000000000000}
>>> [tz|123m|]
UnsafeMutez {unMutez = 123000}
>>> [tz|123 milli|]
UnsafeMutez {unMutez = 123000}
>>> [tz|123u|]
UnsafeMutez {unMutez = 123}
>>> [tz|123μ|]
UnsafeMutez {unMutez = 123}
>>> [tz|123 micro|]
UnsafeMutez {unMutez = 123}
>>> [tz| 123.456_789 |]
UnsafeMutez {unMutez = 123456789}
>>> [tz|123.456u|]
...
... error:
...  • The number is a mutez fraction. The smallest possible subdivision is 0.000001 XTZ
...
>>> [tz|0.012_345_6|]
...
... error:
...  • The number is a mutez fraction. The smallest possible subdivision is 0.000001 XTZ
...
>>> [tz| 9223372.036854775807 M |]
UnsafeMutez {unMutez = 9223372036854775807}
>>> [tz| 9223372.036854775808 M |]
...
... error:
...  • The number is out of mutez bounds. It must be between 0 and 9223372036854.775807 XTZ (inclusive).
...
>>> [tz| -1 |]
...
... error:
...  • The number is out of mutez bounds. It must be between 0 and 9223372036854.775807 XTZ (inclusive).
...

mkMutez :: Integral i => i -> Either Text Mutez Source #

Safely creates Mutez checking for overflow and underflow. Accepts a number of any type.

toMutez :: (Integral a, CheckIntSubType a Word63) => a -> Mutez Source #

Safely create Mutez.

When constructing literals, you'll need to specify the type of the literal. GHC will check for literal overflow on builtin types like Word16 and Word32, but not on Word62 or Word63, so those can overflow silently.

It's recommended to use tz quasiquote for literals instead.

addMutez :: Mutez -> Mutez -> Maybe Mutez Source #

Addition of Mutez values. Returns Nothing in case of overflow.

unsafeAddMutez :: HasCallStack => Mutez -> Mutez -> Mutez Source #

Partial addition of Mutez, should be used only if you're sure there'll be no overflow.

subMutez :: Mutez -> Mutez -> Maybe Mutez Source #

Subtraction of Mutez values. Returns Nothing when the subtrahend is greater than the minuend, and Just otherwise.

unsafeSubMutez :: HasCallStack => Mutez -> Mutez -> Mutez Source #

Partial subtraction of Mutez, should be used only if you're sure there'll be no underflow.

mulMutez :: Integral a => Mutez -> a -> Maybe Mutez Source #

Multiplication of Mutez and an integral number. Returns Nothing in case of overflow.

unsafeMulMutez :: Mutez -> Natural -> Mutez Source #

Partial multiplication of Mutez and an Natural number. Should be used only if you're sure there'll be no overflow.

divModMutez :: Mutez -> Mutez -> Maybe (Word63, Mutez) Source #

Euclidian division of two Mutez values.

divModMutezInt :: Integral a => Mutez -> a -> Maybe (Mutez, Mutez) Source #

Euclidian division of Mutez and a number.

prettyTez :: Mutez -> Text Source #

>>> putTextLn $ prettyTez [tz|420u|]
0.00042 ꜩ
>>> putTextLn $ prettyTez [tz|42|]
42 ꜩ

Timestamp

newtype Timestamp Source #

Time in the real world. Use the functions below to convert it to/from Unix time in seconds.

Constructors

Timestamp 

Instances

Instances details
FromJSON Timestamp Source # 
Instance details

Defined in Morley.Tezos.Core

ToJSON Timestamp Source # 
Instance details

Defined in Morley.Tezos.Core

Data Timestamp Source # 
Instance details

Defined in Morley.Tezos.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Timestamp -> c Timestamp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Timestamp #

toConstr :: Timestamp -> Constr #

dataTypeOf :: Timestamp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Timestamp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Timestamp) #

gmapT :: (forall b. Data b => b -> b) -> Timestamp -> Timestamp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Timestamp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Timestamp -> r #

gmapQ :: (forall d. Data d => d -> u) -> Timestamp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Timestamp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Timestamp -> m Timestamp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Timestamp -> m Timestamp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Timestamp -> m Timestamp #

Generic Timestamp Source # 
Instance details

Defined in Morley.Tezos.Core

Associated Types

type Rep Timestamp :: Type -> Type #

Show Timestamp Source # 
Instance details

Defined in Morley.Tezos.Core

NFData Timestamp Source # 
Instance details

Defined in Morley.Tezos.Core

Methods

rnf :: Timestamp -> () #

Buildable Timestamp Source # 
Instance details

Defined in Morley.Tezos.Core

Methods

build :: Timestamp -> Builder #

Eq Timestamp Source # 
Instance details

Defined in Morley.Tezos.Core

Ord Timestamp Source # 
Instance details

Defined in Morley.Tezos.Core

HasRPCRepr Timestamp Source # 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC Timestamp Source #

TypeHasDoc Timestamp Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

IsoValue Timestamp Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Timestamp :: T Source #

type Rep Timestamp Source # 
Instance details

Defined in Morley.Tezos.Core

type Rep Timestamp = D1 ('MetaData "Timestamp" "Morley.Tezos.Core" "morley-1.19.0-inplace" 'True) (C1 ('MetaCons "Timestamp" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTimestamp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 POSIXTime)))
type AsRPC Timestamp Source # 
Instance details

Defined in Morley.AsRPC

type TypeDocFieldDescriptions Timestamp Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT Timestamp Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

timestampPlusSeconds :: Timestamp -> Integer -> Timestamp Source #

Add given amount of seconds to a Timestamp.

formatTimestamp :: Timestamp -> Text Source #

Display timestamp in human-readable way as used by Michelson. Uses UTC timezone, though maybe we should take it as an argument.

NB: this will render timestamp with up to seconds precision.

parseTimestamp :: Text -> Maybe Timestamp Source #

Parse textual representation of Timestamp.

timestampQuote :: QuasiQuoter Source #

Quote a value of type Timestamp in yyyy-mm-ddThh:mm:ss[.sss]Z format.

>>> formatTimestamp [timestampQuote| 2019-02-21T16:54:12.2344523Z |]
"2019-02-21T16:54:12Z"

Inspired by 'time-quote' library.

getCurrentTime :: IO Timestamp Source #

Return current time as Timestamp.

farFuture :: Timestamp Source #

Timestamp which is always greater than result of getCurrentTime.

farPast :: Timestamp Source #

Timestamp which is always less than result of getCurrentTime.

ChainId

newtype ChainId Source #

Identifier of a network (babylonnet, mainnet, test network or other). Evaluated as hash of the genesis block.

The only operation supported for this type is packing. Use case: multisig contract, for instance, now includes chain ID into signed data "in order to add extra replay protection between the main chain and the test chain".

Constructors

UnsafeChainId 

Instances

Instances details
FromJSON ChainId Source # 
Instance details

Defined in Morley.Tezos.Core

ToJSON ChainId Source # 
Instance details

Defined in Morley.Tezos.Core

Generic ChainId Source # 
Instance details

Defined in Morley.Tezos.Core

Associated Types

type Rep ChainId :: Type -> Type #

Methods

from :: ChainId -> Rep ChainId x #

to :: Rep ChainId x -> ChainId #

Show ChainId Source # 
Instance details

Defined in Morley.Tezos.Core

NFData ChainId Source # 
Instance details

Defined in Morley.Tezos.Core

Methods

rnf :: ChainId -> () #

Buildable ChainId Source # 
Instance details

Defined in Morley.Tezos.Core

Methods

build :: ChainId -> Builder #

Eq ChainId Source # 
Instance details

Defined in Morley.Tezos.Core

Methods

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

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

Ord ChainId Source # 
Instance details

Defined in Morley.Tezos.Core

HasRPCRepr ChainId Source # 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC ChainId Source #

TypeHasDoc ChainId Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

IsoValue ChainId Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT ChainId :: T Source #

type Rep ChainId Source # 
Instance details

Defined in Morley.Tezos.Core

type Rep ChainId = D1 ('MetaData "ChainId" "Morley.Tezos.Core" "morley-1.19.0-inplace" 'True) (C1 ('MetaCons "UnsafeChainId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unChainId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))
type AsRPC ChainId Source # 
Instance details

Defined in Morley.AsRPC

type TypeDocFieldDescriptions ChainId Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT ChainId Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

mkChainId :: ByteString -> Either ParseChainIdError ChainId Source #

Construct chain ID from raw bytes.

dummyChainId :: ChainId Source #

Identifier of a pseudo network.

formatChainId :: ChainId -> Text Source #

Pretty print ChainId as it is displayed e.g. in octez-client rpc get chainsmain/chain_id call.

Example of produced value: NetXUdfLh6Gm88t.

parseChainId :: Text -> Either ParseChainIdError ChainId Source #