Safe Haskell | None |
---|---|
Language | Haskell2010 |
Morley.Tezos.Core
Description
Core primitive Tezos types.
Synopsis
- newtype Mutez = UnsafeMutez {}
- mkMutez :: (Integral i, Bits i) => i -> Either Text Mutez
- unsafeMkMutez :: HasCallStack => Word64 -> Mutez
- toMutez :: Word32 -> Mutez
- addMutez :: Mutez -> Mutez -> Maybe Mutez
- unsafeAddMutez :: HasCallStack => Mutez -> Mutez -> Mutez
- subMutez :: Mutez -> Mutez -> Maybe Mutez
- unsafeSubMutez :: HasCallStack => Mutez -> Mutez -> Mutez
- mulMutez :: Integral a => Mutez -> a -> Maybe Mutez
- unsafeMulMutez :: Mutez -> Natural -> Mutez
- divModMutez :: Mutez -> Mutez -> Maybe (Word64, Mutez)
- divModMutezInt :: Integral a => Mutez -> a -> Maybe (Mutez, Mutez)
- zeroMutez :: Mutez
- oneMutez :: Mutez
- prettyTez :: Mutez -> Text
- newtype Timestamp = Timestamp {}
- timestampToSeconds :: Integral a => Timestamp -> a
- timestampFromSeconds :: Integer -> Timestamp
- timestampFromUTCTime :: UTCTime -> Timestamp
- timestampToUTCTime :: Timestamp -> UTCTime
- timestampPlusSeconds :: Timestamp -> Integer -> Timestamp
- formatTimestamp :: Timestamp -> Text
- parseTimestamp :: Text -> Maybe Timestamp
- timestampQuote :: QuasiQuoter
- getCurrentTime :: IO Timestamp
- farFuture :: Timestamp
- farPast :: Timestamp
- newtype ChainId = UnsafeChainId {}
- mkChainId :: ByteString -> Maybe ChainId
- unsafeMkChainId :: HasCallStack => ByteString -> ChainId
- dummyChainId :: ChainId
- formatChainId :: ChainId -> Text
- mformatChainId :: ChainId -> MText
- parseChainId :: Text -> Either ParseChainIdError ChainId
- chainIdLength :: Int
Mutez
Mutez is a wrapper over integer data type. 1 mutez is 1 token (μTz).
Constructors
UnsafeMutez | |
Instances
mkMutez :: (Integral i, Bits i) => i -> Either Text Mutez Source #
Safely creates Mutez
checking for
overflow and underflow. Accepts a number of any type.
unsafeMkMutez :: HasCallStack => Word64 -> Mutez Source #
toMutez :: Word32 -> Mutez Source #
Safely create Mutez
.
This is recommended way to create Mutez
from a numeric literal;
you can't construct all valid Mutez
values using this function
but for small values it works neat.
Warnings displayed when trying to construct invalid Natural
or Word
literal are hardcoded for these types in GHC implementation, so we can only
exploit these existing rules.
unsafeAddMutez :: HasCallStack => Mutez -> Mutez -> Mutez Source #
Partial addition of Mutez
, should be used only if you're
sure there'll be no overflow.
unsafeSubMutez :: HasCallStack => Mutez -> Mutez -> Mutez Source #
Partial subtraction of Mutez
, should be used only if you're
sure there'll be no underflow.
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 (Word64, 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 (toMutez 420)
0.00042 ꜩ
>>>
putTextLn $ prettyTez (toMutez 42000000)
42 ꜩ
Timestamp
Time in the real world. Use the functions below to convert it to/from Unix time in seconds.
Constructors
Timestamp | |
Fields |
Instances
timestampToSeconds :: Integral a => Timestamp -> a Source #
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.
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.
farFuture :: Timestamp Source #
Timestamp which is always greater than result of getCurrentTime
.
Timestamp which is always less than result of getCurrentTime
.
ChainId
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 | |
Fields |
Instances
unsafeMkChainId :: HasCallStack => ByteString -> ChainId Source #
Construct chain ID from raw bytes or fail otherwise. Expects exactly 4 bytes.
dummyChainId :: ChainId Source #
Identifier of a pseudo network.
formatChainId :: ChainId -> Text Source #
Pretty print ChainId
as it is displayed e.g. in
tezos-client rpc get chainsmain/chain_id
call.
Example of produced value: NetXUdfLh6Gm88t
.
mformatChainId :: ChainId -> MText Source #
chainIdLength :: Int Source #