morley-0.2.0.1: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Tezos.Core

Contents

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
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 :: (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 #

Arbitrary Mutez Source # 
Instance details

Defined in Morley.Test.Gen

Methods

arbitrary :: Gen Mutez #

shrink :: Mutez -> [Mutez] #

ToJSON Mutez Source # 
Instance details

Defined in Tezos.Core

FromJSON Mutez Source # 
Instance details

Defined in Tezos.Core

Buildable Mutez Source # 
Instance details

Defined in Tezos.Core

Methods

build :: Mutez -> Builder #

FromCVal Mutez Source # 
Instance details

Defined in Michelson.Typed.CValue

ToCVal Mutez Source # 
Instance details

Defined in Michelson.Typed.CValue

Methods

toCVal :: Mutez -> CVal (ToCT Mutez) Source #

FromVal Mutez Source # 
Instance details

Defined in Michelson.Typed.Value

Methods

fromVal :: Val instr (ToT Mutez) -> Mutez Source #

ToVal Mutez Source # 
Instance details

Defined in Michelson.Typed.Value

Methods

toVal :: Mutez -> Val instr (ToT Mutez) Source #

type Rep Mutez Source # 
Instance details

Defined in Tezos.Core

type Rep Mutez = D1 (MetaData "Mutez" "Tezos.Core" "morley-0.2.0.1-FliIoxX7mVfHuhHSaQftJN" True) (C1 (MetaCons "Mutez" PrefixI True) (S1 (MetaSel (Just "unMutez") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)))

mkMutez :: Word64 -> Maybe Mutez Source #

Safely create Mutez checking for overflow.

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.

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.

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
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 :: (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 #

Arbitrary Timestamp Source # 
Instance details

Defined in Morley.Test.Gen

ToJSON Timestamp Source # 
Instance details

Defined in Tezos.Core

FromJSON Timestamp Source # 
Instance details

Defined in Tezos.Core

Buildable Timestamp Source # 
Instance details

Defined in Tezos.Core

Methods

build :: Timestamp -> Builder #

FromCVal Timestamp Source # 
Instance details

Defined in Michelson.Typed.CValue

ToCVal Timestamp Source # 
Instance details

Defined in Michelson.Typed.CValue

FromVal Timestamp Source # 
Instance details

Defined in Michelson.Typed.Value

Methods

fromVal :: Val instr (ToT Timestamp) -> Timestamp Source #

ToVal Timestamp Source # 
Instance details

Defined in Michelson.Typed.Value

Methods

toVal :: Timestamp -> Val instr (ToT Timestamp) Source #

type Rep Timestamp Source # 
Instance details

Defined in Tezos.Core

type Rep Timestamp = D1 (MetaData "Timestamp" "Tezos.Core" "morley-0.2.0.1-FliIoxX7mVfHuhHSaQftJN" True) (C1 (MetaCons "Timestamp" PrefixI True) (S1 (MetaSel (Just "unTimestamp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 POSIXTime)))

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.

parseTimestamp :: Text -> Maybe Timestamp Source #

Parse textual representation of Timestamp.

getCurrentTime :: IO Timestamp Source #

Return current time as Timestamp.