morley-1.12.0: Developer tools for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Tezos.Core

Description

Core primitive Tezos types.

Synopsis

Mutez

data Mutez Source #

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

Instances

Instances details
Bounded Mutez Source # 
Instance details

Defined in Tezos.Core

Enum Mutez Source # 
Instance details

Defined in Tezos.Core

Eq Mutez Source # 
Instance details

Defined in Tezos.Core

Methods

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

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

Data Mutez Source # 
Instance details

Defined in Tezos.Core

Methods

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

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

toConstr :: Mutez -> Constr #

dataTypeOf :: Mutez -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Mutez Source # 
Instance details

Defined in 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 #

Show Mutez Source # 
Instance details

Defined in Tezos.Core

Methods

showsPrec :: Int -> Mutez -> ShowS #

show :: Mutez -> String #

showList :: [Mutez] -> ShowS #

Generic Mutez Source # 
Instance details

Defined in Tezos.Core

Associated Types

type Rep Mutez :: Type -> Type #

Methods

from :: Mutez -> Rep Mutez x #

to :: Rep Mutez x -> Mutez #

ToJSON Mutez Source # 
Instance details

Defined in Tezos.Core

FromJSON Mutez Source # 
Instance details

Defined in Tezos.Core

NFData Mutez Source # 
Instance details

Defined in Tezos.Core

Methods

rnf :: Mutez -> () #

Buildable Mutez Source # 
Instance details

Defined in Tezos.Core

Methods

build :: Mutez -> Builder #

HasCLReader Mutez Source # 
Instance details

Defined in Tezos.Core

IsoValue Mutez Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Mutez :: T Source #

TypeHasDoc Mutez Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type Rep Mutez Source # 
Instance details

Defined in Tezos.Core

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

Defined in Michelson.Typed.Haskell.Value

type ToT Mutez = 'TMutez
type TypeDocFieldDescriptions Mutez Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

mkMutez :: Word64 -> Maybe Mutez Source #

Safely create Mutez checking for overflow.

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

Version of mkMutez that accepts a number of any type.

unsafeMkMutez :: HasCallStack => Word64 -> Mutez Source #

Partial function for Mutez creation, it's pre-condition is that the argument must not exceed the maximal Mutez value.

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.

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.

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.

mutezToInt64 :: Mutez -> Int64 Source #

Convert mutez to signed number.

TODO [#423]: try to provide a generic safe conversion method

prettyTez :: Mutez -> Text Source #

>>> prettyTez (toMutez 420)
"0.00042 ꜩ"
>>> prettyTez (toMutez 42000000)
"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
Eq Timestamp Source # 
Instance details

Defined in Tezos.Core

Data Timestamp Source # 
Instance details

Defined in 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 #

Ord Timestamp Source # 
Instance details

Defined in Tezos.Core

Show Timestamp Source # 
Instance details

Defined in Tezos.Core

Generic Timestamp Source # 
Instance details

Defined in Tezos.Core

Associated Types

type Rep Timestamp :: Type -> Type #

ToJSON Timestamp Source # 
Instance details

Defined in Tezos.Core

FromJSON Timestamp Source # 
Instance details

Defined in Tezos.Core

NFData Timestamp Source # 
Instance details

Defined in Tezos.Core

Methods

rnf :: Timestamp -> () #

Buildable Timestamp Source # 
Instance details

Defined in Tezos.Core

Methods

build :: Timestamp -> Builder #

IsoValue Timestamp Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Timestamp :: T Source #

TypeHasDoc Timestamp Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type Rep Timestamp Source # 
Instance details

Defined in Tezos.Core

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

Defined in Michelson.Typed.Haskell.Value

type TypeDocFieldDescriptions Timestamp Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

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

ChainIdUnsafe 

Instances

Instances details
Eq ChainId Source # 
Instance details

Defined in Tezos.Core

Methods

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

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

Show ChainId Source # 
Instance details

Defined in Tezos.Core

Generic ChainId Source # 
Instance details

Defined in Tezos.Core

Associated Types

type Rep ChainId :: Type -> Type #

Methods

from :: ChainId -> Rep ChainId x #

to :: Rep ChainId x -> ChainId #

ToJSON ChainId Source # 
Instance details

Defined in Tezos.Core

FromJSON ChainId Source # 
Instance details

Defined in Tezos.Core

NFData ChainId Source # 
Instance details

Defined in Tezos.Core

Methods

rnf :: ChainId -> () #

Buildable ChainId Source # 
Instance details

Defined in Tezos.Core

Methods

build :: ChainId -> Builder #

IsoValue ChainId Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT ChainId :: T Source #

TypeHasDoc ChainId Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type Rep ChainId Source # 
Instance details

Defined in Tezos.Core

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

Defined in Michelson.Typed.Haskell.Value

type TypeDocFieldDescriptions ChainId Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

mkChainId :: ByteString -> Maybe ChainId Source #

Construct chain ID from raw bytes.

mkChainIdUnsafe :: 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.

parseChainId :: Text -> Either ParseChainIdError ChainId Source #