cardano-api-8.36.1.1: The cardano api
Safe HaskellNone
LanguageHaskell2010

Cardano.Api.Query

Description

Queries from local clients to the node.

Synopsis

Queries

data QueryInEra era result where Source #

Constructors

QueryByronUpdateState :: QueryInEra ByronEra ByronUpdateState 
QueryInShelleyBasedEra :: ShelleyBasedEra era -> QueryInShelleyBasedEra era result -> QueryInEra era result 

Instances

Instances details
Show (QueryInEra era result) Source # 
Instance details

Defined in Cardano.Api.Query

Methods

showsPrec :: Int -> QueryInEra era result -> ShowS Source #

show :: QueryInEra era result -> String Source #

showList :: [QueryInEra era result] -> ShowS Source #

NodeToClientVersionOf (QueryInEra era result) Source # 
Instance details

Defined in Cardano.Api.Query

data QueryInShelleyBasedEra era result where Source #

Constructors

QueryEpoch :: QueryInShelleyBasedEra era EpochNo 
QueryGenesisParameters :: QueryInShelleyBasedEra era (GenesisParameters ShelleyEra) 
QueryProtocolParameters :: QueryInShelleyBasedEra era (PParams (ShelleyLedgerEra era)) 
QueryProtocolParametersUpdate :: QueryInShelleyBasedEra era (Map (Hash GenesisKey) ProtocolParametersUpdate) 
QueryStakeDistribution :: QueryInShelleyBasedEra era (Map (Hash StakePoolKey) Rational) 
QueryUTxO :: QueryUTxOFilter -> QueryInShelleyBasedEra era (UTxO era) 
QueryStakeAddresses :: Set StakeCredential -> NetworkId -> QueryInShelleyBasedEra era (Map StakeAddress Lovelace, Map StakeAddress PoolId) 
QueryStakePools :: QueryInShelleyBasedEra era (Set PoolId) 
QueryStakePoolParameters :: Set PoolId -> QueryInShelleyBasedEra era (Map PoolId StakePoolParameters) 
QueryDebugLedgerState :: QueryInShelleyBasedEra era (SerialisedDebugLedgerState era) 
QueryProtocolState :: QueryInShelleyBasedEra era (ProtocolState era) 
QueryCurrentEpochState :: QueryInShelleyBasedEra era (SerialisedCurrentEpochState era) 
QueryPoolState :: Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedPoolState era) 
QueryPoolDistribution :: Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedPoolDistribution era) 
QueryStakeSnapshot :: Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedStakeSnapshots era) 
QueryStakeDelegDeposits :: Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential Lovelace) 
QueryConstitution :: QueryInShelleyBasedEra era (Maybe (Constitution (ShelleyLedgerEra era))) 
QueryGovState :: QueryInShelleyBasedEra era (GovState (ShelleyLedgerEra era)) 
QueryDRepState :: Set (Credential DRepRole StandardCrypto) -> QueryInShelleyBasedEra era (Map (Credential DRepRole StandardCrypto) (DRepState StandardCrypto)) 
QueryDRepStakeDistr :: Set (DRep StandardCrypto) -> QueryInShelleyBasedEra era (Map (DRep StandardCrypto) Lovelace) 
QueryCommitteeMembersState :: Set (Credential ColdCommitteeRole StandardCrypto) -> Set (Credential HotCommitteeRole StandardCrypto) -> Set MemberStatus -> QueryInShelleyBasedEra era (Maybe (CommitteeMembersState StandardCrypto)) 
QueryStakeVoteDelegatees :: Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential (DRep StandardCrypto)) 

Instances

Instances details
Show (QueryInShelleyBasedEra era result) Source # 
Instance details

Defined in Cardano.Api.Query

NodeToClientVersionOf (QueryInShelleyBasedEra era result) Source #

Mapping for queries in Shelley-based eras returning minimal node-to-client protocol versions. More information about queries versioning can be found: * https://input-output-hk.github.io/ouroboros-network/ouroboros-network/Ouroboros-Network-NodeToClient.html#t:NodeToClientVersion * https://input-output-hk.github.io/ouroboros-consensus/docs/for-developers/QueryVersioning/#implementation

Instance details

Defined in Cardano.Api.Query

data QueryUTxOFilter Source #

Getting the whole UTxO is obviously not efficient since the result can be huge. Filtering by address is also not efficient because it requires a linear search.

The QueryUTxOFilterByTxIn is efficient since it fits with the structure of the UTxO (which is indexed by TxIn).

Constructors

QueryUTxOWhole

O(n) time and space for utxo size n

QueryUTxOByAddress (Set AddressAny)

O(n) time, O(m) space for utxo size n, and address set size m

QueryUTxOByTxIn (Set TxIn)

O(m log n) time, O(m) space for utxo size n, and address set size m

newtype UTxO era Source #

Constructors

UTxO 

Fields

Instances

Instances details
Eq (UTxO era) Source # 
Instance details

Defined in Cardano.Api.Query

Methods

(==) :: UTxO era -> UTxO era -> Bool Source #

(/=) :: UTxO era -> UTxO era -> Bool Source #

Show (UTxO era) Source # 
Instance details

Defined in Cardano.Api.Query

Methods

showsPrec :: Int -> UTxO era -> ShowS Source #

show :: UTxO era -> String Source #

showList :: [UTxO era] -> ShowS Source #

(IsShelleyBasedEra era, FromJSON (TxOut CtxUTxO era)) => FromJSON (UTxO era) Source # 
Instance details

Defined in Cardano.Api.Query

Methods

parseJSON :: Value -> Parser (UTxO era) #

parseJSONList :: Value -> Parser [UTxO era] #

omittedField :: Maybe (UTxO era) #

IsCardanoEra era => ToJSON (UTxO era) Source # 
Instance details

Defined in Cardano.Api.Query

Methods

toJSON :: UTxO era -> Value #

toEncoding :: UTxO era -> Encoding #

toJSONList :: [UTxO era] -> Value #

toEncodingList :: [UTxO era] -> Encoding #

omitField :: UTxO era -> Bool #

data UTxOInAnyEra where Source #

Constructors

UTxOInAnyEra :: CardanoEra era -> UTxO era -> UTxOInAnyEra 

Instances

Instances details
Show UTxOInAnyEra Source # 
Instance details

Defined in Cardano.Api.Query

Internal conversion functions

toConsensusQuery :: forall block result. CardanoBlock StandardCrypto ~ block => QueryInMode result -> Some (Query block) Source #

fromConsensusQueryResult :: forall block result result'. HasCallStack => CardanoBlock StandardCrypto ~ block => QueryInMode result -> Query block result' -> result' -> result Source #

Wrapper types used in queries

newtype SerialisedDebugLedgerState era Source #

Constructors

SerialisedDebugLedgerState (Serialised (NewEpochState (ShelleyLedgerEra era))) 

newtype ProtocolState era Source #

Constructors

ProtocolState (Serialised (ChainDepState (ConsensusProtocol era))) 

decodeProtocolState :: FromCBOR (ChainDepState (ConsensusProtocol era)) => ProtocolState era -> Either (ByteString, DecoderError) (ChainDepState (ConsensusProtocol era)) Source #

newtype DebugLedgerState era Source #

Constructors

DebugLedgerState 

Fields

Instances

Instances details
IsShelleyBasedEra era => FromCBOR (DebugLedgerState era) Source # 
Instance details

Defined in Cardano.Api.Query.Types

Methods

fromCBOR :: Decoder s (DebugLedgerState era) #

label :: Proxy (DebugLedgerState era) -> Text #

IsShelleyBasedEra era => ToJSON (DebugLedgerState era) Source # 
Instance details

Defined in Cardano.Api.Query.Types

Methods

toJSON :: DebugLedgerState era -> Value #

toEncoding :: DebugLedgerState era -> Encoding #

toJSONList :: [DebugLedgerState era] -> Value #

toEncodingList :: [DebugLedgerState era] -> Encoding #

omitField :: DebugLedgerState era -> Bool #

newtype SerialisedCurrentEpochState era Source #

Constructors

SerialisedCurrentEpochState (Serialised (EpochState (ShelleyLedgerEra era))) 

newtype CurrentEpochState era Source #

Constructors

CurrentEpochState (EpochState (ShelleyLedgerEra era)) 

newtype SerialisedPoolState era Source #

Constructors

SerialisedPoolState (Serialised (PState (ShelleyLedgerEra era))) 

newtype PoolState era Source #

Constructors

PoolState (PState (ShelleyLedgerEra era)) 

decodePoolState :: forall era. Era (ShelleyLedgerEra era) => DecCBOR (PState (ShelleyLedgerEra era)) => SerialisedPoolState era -> Either DecoderError (PoolState era) Source #

newtype SerialisedPoolDistribution era Source #

Constructors

SerialisedPoolDistribution (Serialised (PoolDistr (EraCrypto (ShelleyLedgerEra era)))) 

newtype PoolDistribution era Source #

Constructors

PoolDistribution 

Fields

newtype SerialisedStakeSnapshots era Source #

Constructors

SerialisedStakeSnapshots (Serialised (StakeSnapshots (EraCrypto (ShelleyLedgerEra era)))) 

newtype StakeSnapshot era Source #

Constructors

StakeSnapshot (StakeSnapshots (EraCrypto (ShelleyLedgerEra era))) 

decodeStakeSnapshot :: forall era. FromCBOR (StakeSnapshots (EraCrypto (ShelleyLedgerEra era))) => SerialisedStakeSnapshots era -> Either DecoderError (StakeSnapshot era) Source #

data EraHistory where Source #

Constructors

EraHistory :: CardanoBlock StandardCrypto ~ HardForkBlock xs => Interpreter xs -> EraHistory 

newtype SystemStart #

Constructors

SystemStart 

Fields

Instances

Instances details
Eq SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Show SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Generic SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Associated Types

type Rep SystemStart :: Type -> Type Source #

DecCBOR SystemStart 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.DecCBOR

Methods

decCBOR :: Decoder s SystemStart

dropCBOR :: Proxy SystemStart -> Decoder s ()

label :: Proxy SystemStart -> Text

EncCBOR SystemStart 
Instance details

Defined in Cardano.Ledger.Binary.Encoding.EncCBOR

Methods

encCBOR :: SystemStart -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy SystemStart -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [SystemStart] -> Size

FromCBOR SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Methods

fromCBOR :: Decoder s SystemStart #

label :: Proxy SystemStart -> Text #

FromJSON SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Methods

parseJSON :: Value -> Parser SystemStart #

parseJSONList :: Value -> Parser [SystemStart] #

omittedField :: Maybe SystemStart #

NoThunks SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Methods

noThunks :: Context -> SystemStart -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> SystemStart -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy SystemStart -> String

ToCBOR SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Methods

toCBOR :: SystemStart -> Encoding #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SystemStart -> Size #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SystemStart] -> Size #

ToJSON SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Methods

toJSON :: SystemStart -> Value #

toEncoding :: SystemStart -> Encoding #

toJSONList :: [SystemStart] -> Value #

toEncodingList :: [SystemStart] -> Encoding #

omitField :: SystemStart -> Bool #

Serialise SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Methods

encode :: SystemStart -> Encoding

decode :: Decoder s SystemStart

encodeList :: [SystemStart] -> Encoding

decodeList :: Decoder s [SystemStart]

type Rep SystemStart 
Instance details

Defined in Cardano.Slotting.Time

type Rep SystemStart = D1 ('MetaData "SystemStart" "Cardano.Slotting.Time" "cardano-slotting-0.1.2.0-JZWCVEKQdJpCQ0vwyYdDil" 'True) (C1 ('MetaCons "SystemStart" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSystemStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime)))

newtype LedgerEpochInfo Source #

Constructors

LedgerEpochInfo 

Fields

newtype SlotsInEpoch Source #

Constructors

SlotsInEpoch Word64 

data family LedgerState blk #

Instances

Instances details
Isomorphic LedgerState 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

Methods

project :: NoHardForks blk => LedgerState (HardForkBlock '[blk]) -> LedgerState blk

inject :: NoHardForks blk => LedgerState blk -> LedgerState (HardForkBlock '[blk])

CanHardFork xs => Eq (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

(==) :: LedgerState (HardForkBlock xs) -> LedgerState (HardForkBlock xs) -> Bool Source #

(/=) :: LedgerState (HardForkBlock xs) -> LedgerState (HardForkBlock xs) -> Bool Source #

CanHardFork xs => Show (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

showsPrec :: Int -> LedgerState (HardForkBlock xs) -> ShowS Source #

show :: LedgerState (HardForkBlock xs) -> String Source #

showList :: [LedgerState (HardForkBlock xs)] -> ShowS Source #

CanHardFork xs => NoThunks (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks :: Context -> LedgerState (HardForkBlock xs) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> LedgerState (HardForkBlock xs) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (LedgerState (HardForkBlock xs)) -> String

Isomorphic (Ticked :.: LedgerState) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

Methods

project :: NoHardForks blk => (Ticked :.: LedgerState) (HardForkBlock '[blk]) -> (Ticked :.: LedgerState) blk

inject :: NoHardForks blk => (Ticked :.: LedgerState) blk -> (Ticked :.: LedgerState) (HardForkBlock '[blk])

data LedgerState ByronBlock 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

data LedgerState ByronBlock = ByronLedgerState {}
type HeaderHash (LedgerState blk :: Type) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

type HeaderHash (LedgerState blk :: Type) = HeaderHash blk
type TranslationError era (LedgerState :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type TranslationError era (LedgerState :.: ShelleyBlock proto) = Void
type Rep (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type Rep (LedgerState ByronBlock) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Byron.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-Eqi8jwiFHKoKVljS76Ugkh" 'False) (C1 ('MetaCons "ByronLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "byronLedgerTipBlockNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin BlockNo)) :*: (S1 ('MetaSel ('Just "byronLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChainValidationState) :*: S1 ('MetaSel ('Just "byronLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ByronTransition))))
type Rep (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (LedgerState (ShelleyBlock proto era)) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-Eqi8jwiFHKoKVljS76Ugkh" 'False) (C1 ('MetaCons "ShelleyLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyLedgerTip") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin (ShelleyTip proto era))) :*: (S1 ('MetaSel ('Just "shelleyLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NewEpochState era)) :*: S1 ('MetaSel ('Just "shelleyLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShelleyTransition))))
type Rep (Ticked (LedgerState ByronBlock)) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type Rep (Ticked (LedgerState ByronBlock)) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Byron.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-Eqi8jwiFHKoKVljS76Ugkh" 'False) (C1 ('MetaCons "TickedByronLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedByronLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChainValidationState) :*: S1 ('MetaSel ('Just "untickedByronLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ByronTransition)))
type Rep (Ticked (LedgerState (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (Ticked (LedgerState (HardForkBlock xs))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.14.0.0-Pi7Pac7NlEeztBZ96b84" 'False) (C1 ('MetaCons "TickedHardForkLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedHardForkLedgerStateTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TransitionInfo) :*: S1 ('MetaSel ('Just "tickedHardForkLedgerStatePerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HardForkState (Ticked :.: LedgerState) xs))))
type Rep (Ticked (LedgerState (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (Ticked (LedgerState (ShelleyBlock proto era))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-Eqi8jwiFHKoKVljS76Ugkh" 'False) (C1 ('MetaCons "TickedShelleyLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "untickedShelleyLedgerTip") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin (ShelleyTip proto era))) :*: (S1 ('MetaSel ('Just "tickedShelleyLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShelleyTransition) :*: S1 ('MetaSel ('Just "tickedShelleyLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NewEpochState era)))))
type AuxLedgerEvent (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type AuxLedgerEvent (LedgerState ByronBlock) = VoidLedgerEvent (LedgerState ByronBlock)
type AuxLedgerEvent (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type AuxLedgerEvent (LedgerState (HardForkBlock xs)) = OneEraLedgerEvent xs
type AuxLedgerEvent (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type AuxLedgerEvent (LedgerState (ShelleyBlock proto era)) = ShelleyLedgerEvent era
type LedgerErr (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type LedgerErr (LedgerState ByronBlock) = ChainValidationError
type LedgerErr (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type LedgerErr (LedgerState (HardForkBlock xs)) = HardForkLedgerError xs
type LedgerErr (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type LedgerErr (LedgerState (ShelleyBlock proto era)) = ShelleyLedgerError era
type LedgerCfg (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type LedgerCfg (LedgerState ByronBlock) = Config
type LedgerCfg (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type LedgerCfg (LedgerState (HardForkBlock xs)) = HardForkLedgerConfig xs
type LedgerCfg (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type LedgerCfg (LedgerState (ShelleyBlock proto era)) = ShelleyLedgerConfig era
newtype LedgerState (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

newtype LedgerState (HardForkBlock xs) = HardForkLedgerState {}
data Ticked (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

data Ticked (LedgerState ByronBlock) = TickedByronLedgerState {}
data Ticked (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState (HardForkBlock xs)) = TickedHardForkLedgerState {}
data Ticked (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

data Ticked (LedgerState (ShelleyBlock proto era)) = TickedShelleyLedgerState {}
data LedgerState (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

data LedgerState (ShelleyBlock proto era) = ShelleyLedgerState {}

getProgress :: SlotNo -> EraHistory -> Either PastHorizonException (RelativeTime, SlotLength) Source #

getSlotForRelativeTime :: RelativeTime -> EraHistory -> Either PastHorizonException SlotNo Source #

Returns the slot number for provided relative time from SystemStart

Internal conversion functions